]> gitweb @ CieloNegro.org - EsounD.git/blobdiff - Sound/EsounD/Internals.hs
Controller (partway)
[EsounD.git] / Sound / EsounD / Internals.hs
index ef8c659ddd104d0646b9ca770800b6fcf2ab3f48..f4b067f0903cf30fc9a23b62ccb13dee41c5e4fe 100644 (file)
@@ -11,19 +11,24 @@ module Sound.EsounD.Internals
     , Mono
     , Stereo
     , interleave
+    , deinterleave
 
+    , toLSV
     , wrapSocket
     , closeSocket
     , withCStrOrNull
+    , failOnError
     )
     where
 import Bindings.EsounD
 import Data.Int
+import Data.StorableVector      as S
 import Data.StorableVector.Lazy as L
 import Foreign.C.String
 import Foreign.C.Types
 import Foreign.Ptr
 import Foreign.Storable
+import Prelude.Unicode
 import System.IO
 import System.Posix.IO
 import System.Posix.Types
@@ -52,7 +57,8 @@ data Stereo
 instance Channels Stereo where
     channelFmt _ = c'ESD_STEREO
 
-interleave ∷ Frame fr ⇒ L.Vector fr → L.Vector fr → L.Vector fr
+{-# INLINE interleave #-}
+interleave ∷ Storable α ⇒ L.Vector α → L.Vector α → L.Vector α
 interleave l r
     -- THINKME: consider using storablevector-streamfusion
     = let Just (lFr, l') = L.viewL l
@@ -61,7 +67,25 @@ interleave l r
       in
         L.cons lFr (L.cons rFr lr')
 
+{-# INLINE deinterleave #-}
+deinterleave ∷ Storable α ⇒ L.Vector α → (L.Vector α, L.Vector α)
+deinterleave v
+    -- THINKME: consider using storablevector-streamfusion
+    = let (lr, v') = L.splitAt 2 v
+      in
+        if L.null lr then
+            (L.empty, L.empty)
+        else
+            let Just (lFr, r) = L.viewL lr
+                Just (rFr, _) = L.viewL r
+                (l', r') = deinterleave v'
+            in
+              (L.cons lFr l', L.cons rFr r')
+
 -- Utility functions
+toLSV ∷ Storable α ⇒ S.Vector α → L.Vector α
+toLSV v = L.fromChunks [v]
+
 wrapSocket ∷ String → CInt → IO Handle
 wrapSocket e (-1) = fail e
 wrapSocket _ fd   = fdToHandle (Fd fd)
@@ -74,3 +98,8 @@ closeSocket h = do (Fd fd) ← handleToFd h
 withCStrOrNull ∷ Maybe String → (CString → IO a) → IO a
 withCStrOrNull Nothing  f = f nullPtr
 withCStrOrNull (Just s) f = withCString s f
+
+failOnError ∷ Monad m ⇒ String → CInt → m ()
+failOnError msg rv
+    | rv ≤ 0   = fail msg
+    | otherwise = return ()