{-# LANGUAGE FlexibleInstances , KindSignatures , MultiParamTypeClasses , UnicodeSyntax , ScopedTypeVariables #-} -- | EsounD player streams. module Sound.EsounD.Player ( Player , openPlayer ) where import Bindings.EsounD import Control.Monad.IO.Class import Control.Monad.Trans.Region import Control.Monad.Trans.Region.OnExit import Control.Monad.Unicode import Data.Bits import Data.StorableVector.Lazy as Lazy import Foreign.C.String import Network import Prelude.Unicode import Sound.EsounD.Streams import Sound.EsounD.Internals import System.IO import System.IO.SaferFileHandles.Unsafe -- ^ An opaque ESD handle for playing a stream. data Player fr ch (r ∷ ★ → ★) = Player { plRate ∷ !Int -- THINKME: We really want to use RegionalFileHandle but we -- can't, because safer-file-handles currently provides no ways -- to wrap ordinary handles into safer handles. , plHandle ∷ !Handle , plCloseH ∷ !(FinalizerHandle r) } instance Dup (Player fr ch) where dup pl = do ch' ← dup (plCloseH pl) return pl { plCloseH = ch' } instance Frame fr ⇒ Writable (Player fr Mono) (Lazy.Vector fr) where write pl v = liftIO $ sanitizeIOError $ Lazy.hPut (plHandle pl) v -- | Open an ESD handle for playing a stream. openPlayer ∷ ∀fr ch s pr. ( Frame fr , 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). → RegionT s pr (Player fr ch (RegionT s pr)) openPlayer rate host name = do h ← liftIO openSocket ch ← onExit $ sanitizeIOError $ closeSocket h return Player { plRate = rate , plHandle = h , plCloseH = ch } where fmt :: C'esd_format_t fmt = frameFmt ((⊥) ∷ fr) .&. channelFmt ((⊥) ∷ ch) .&. c'ESD_STREAM .&. c'ESD_PLAY openSocket :: IO Handle openSocket = withCString host $ \hostPtr → withCStrOrNull name $ \namePtr → c'esd_play_stream fmt (fromIntegral rate) hostPtr namePtr ≫= wrapSocket "esd_play_stream() returned an error"