]> gitweb @ CieloNegro.org - EsounD.git/commitdiff
openPlayer should accept Nothing for the hostname
authorPHO <pho@cielonegro.org>
Sat, 1 Jan 2011 08:07:55 +0000 (17:07 +0900)
committerPHO <pho@cielonegro.org>
Sat, 1 Jan 2011 08:07:55 +0000 (17:07 +0900)
Sound/EsounD/Internals.hs
Sound/EsounD/Player.hs
examples/EsdPlayerExample.hs

index ef8c659ddd104d0646b9ca770800b6fcf2ab3f48..8d28ed8e346bf2aefcaf54d4459e6ef085f7da9c 100644 (file)
@@ -52,6 +52,7 @@ data Stereo
 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
index cfb4e31edb9b9f3f70d5c1dcf04f071860b90426..7f7eb223a88ddb2c593c7dfd695b58a2076c7f9d 100644 (file)
@@ -19,7 +19,6 @@ import Control.Monad.Trans.Region.OnExit
 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
@@ -57,10 +56,10 @@ openPlayer ∷ ∀fr ch s pr.
                , 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
@@ -72,17 +71,27 @@ openPlayer rate host name
                     }
     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"
+                               )
index 1d3ec4f311836b4703ceb2d3a458701446f1b943..1083e8b70e850d260483c997c787e9523a145113 100644 (file)
@@ -3,12 +3,15 @@
   #-}
 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"