instance Channels Stereo where
channelFmt _ = c'ESD_STEREO
+{-# INLINE interleave #-}
interleave ∷ Frame fr ⇒ L.Vector fr → L.Vector fr → L.Vector fr
interleave l r
-- THINKME: consider using storablevector-streamfusion
import Control.Monad.Unicode
import Data.Bits
import Data.StorableVector.Lazy as L
-import Foreign.C.String
import Network
import Prelude.Unicode
import Sound.EsounD.Streams
, Channels ch
, MonadIO pr
)
- ⇒ Int -- ^ sample rate for the stream.
- → HostName -- ^ host to connect to.
- → Maybe String -- ^ name used to identify this stream to
- -- ESD (if any).
+ ⇒ Int -- ^ sample rate for the stream.
+ → Maybe HostName -- ^ host to connect to.
+ → Maybe String -- ^ name used to identify this stream to
+ -- ESD (if any).
→ RegionT s pr (Player fr ch (RegionT s pr))
openPlayer rate host name
= do h ← liftIO openSocket
}
where
fmt :: C'esd_format_t
- fmt = frameFmt ((⊥) ∷ fr) .&.
- channelFmt ((⊥) ∷ ch) .&.
- c'ESD_STREAM .&.
+ fmt = frameFmt ((⊥) ∷ fr) .|.
+ channelFmt ((⊥) ∷ ch) .|.
+ c'ESD_STREAM .|.
c'ESD_PLAY
openSocket :: IO Handle
- openSocket = withCString host $ \hostPtr →
+ openSocket = withCStrOrNull host $ \hostPtr →
withCStrOrNull name $ \namePtr →
c'esd_play_stream
fmt
(fromIntegral rate)
hostPtr
namePtr
- ≫= wrapSocket "esd_play_stream() returned an error"
+ ≫= wrapSocket
+ ( "esd_play_stream("
+ ⧺ show fmt
+ ⧺ ", "
+ ⧺ show rate
+ ⧺ ", "
+ ⧺ show host
+ ⧺ ", "
+ ⧺ show name
+ ⧺ ") returned an error"
+ )
#-}
module Main where
import Control.Monad.Trans.Region
-import Sound.EsounD.Player
+import Data.Int
+import Sound.EsounD.Player
+import Sound.EsounD.Types
main ∷ IO ()
-main = return ()
-{-
main = runRegionT $
- do pl ← openPlayer 44100 "localhost" Nothing
- fail "FIXME"
--}
+ do pl ← openPlayer 44100 Nothing Nothing
+ playMono16Sine pl
+
+playMono16Sine ∷ Monad m ⇒ Player Int16 Mono m → m ()
+playMono16Sine pl
+ = fail "FIXME"