]> gitweb @ CieloNegro.org - EsounD.git/blobdiff - examples/EsdPlayerExample.hs
updating things to prepare EsounD-0.2
[EsounD.git] / examples / EsdPlayerExample.hs
index 1d3ec4f311836b4703ceb2d3a458701446f1b943..e25b1bee9baf075763fe4a2e87e324de5390a947 100644 (file)
@@ -2,13 +2,48 @@
     UnicodeSyntax
   #-}
 module Main where
+import Control.Monad.IO.Class
 import Control.Monad.Trans.Region
-import Sound.EsounD.Player 
+import Data.Int
+import qualified Data.StorableVector.Lazy as L
+import Prelude.Unicode
+import Sound.EsounD
 
 main ∷ IO ()
-main = return ()
-{-
 main = runRegionT $
-       do pl ← openPlayer 44100 "localhost" Nothing 
-          fail "FIXME"
--}
+       do pl ← openPlayer 44100 Nothing Nothing
+          -- Let's play an 'A' note for 1 sec.
+          playMono16Sine pl 44100 1 440
+
+playMono16Sine ∷ ( AncestorRegion pr cr
+                  , MonadIO cr
+                  )
+               ⇒ Player Int16 Mono pr
+               → Int
+               → Double
+               → Double
+               → cr ()
+playMono16Sine pl sampleFreq sec noteFreq
+    = writeFrames pl buffer
+    where
+      buffer ∷ L.Vector Int16
+      buffer = L.pack L.defaultChunkSize frames
+
+      frames ∷ [Int16]
+      frames = let nFrames = round $ sec ⋅ realToFrac sampleFreq
+               in
+                 map calcFrame [0 .. nFrames - 1]
+
+      calcFrame ∷ Int → Int16
+      calcFrame n = let frame = calcFrame' n
+                    in
+                      -- -1.0 ≤ frame ≤ 1.0
+                      floor $ fromIntegral ((maxBound ∷ Int16) - 1) ⋅ frame
+
+      calcFrame' ∷ Int → Double
+      calcFrame' n
+          = sin $
+            2
+            ⋅ π
+            ⋅ noteFreq
+            ⋅ (realToFrac n ÷ realToFrac sampleFreq)