]> gitweb @ CieloNegro.org - EsounD.git/blob - Sound/EsounD/Player.hs
Writable class
[EsounD.git] / Sound / EsounD / Player.hs
1 {-# LANGUAGE
2     FlexibleInstances
3   , KindSignatures
4   , MultiParamTypeClasses
5   , UnicodeSyntax
6   , ScopedTypeVariables
7   #-}
8 -- | EsounD player streams.
9 module Sound.EsounD.Player
10     ( Player
11     , openPlayer
12     )
13     where
14 import Bindings.EsounD
15 import Control.Monad.IO.Class
16 import Control.Monad.Trans.Region
17 import Control.Monad.Trans.Region.OnExit
18 import Control.Monad.Unicode
19 import Data.Bits
20 import Data.StorableVector.Lazy as Lazy
21 import Foreign.C.String
22 import Network
23 import Prelude.Unicode
24 import Sound.EsounD.Streams 
25 import Sound.EsounD.Internals
26 import System.IO
27 import System.IO.SaferFileHandles.Unsafe
28
29
30 -- ^ An opaque ESD handle for playing a stream.
31 data Player fr ch (r ∷ ★ → ★)
32     = Player {
33         plRate   ∷ !Int
34       -- THINKME: We really want to use RegionalFileHandle but we
35       -- can't, because safer-file-handles currently provides no ways
36       -- to wrap ordinary handles into safer handles.
37       , plHandle ∷ !Handle
38       , plCloseH ∷ !(FinalizerHandle r)
39       }
40
41 instance Dup (Player fr ch) where
42     dup pl = do ch' ← dup (plCloseH pl)
43                 return pl { plCloseH = ch' }
44
45 instance Frame fr ⇒ Writable (Player fr Mono) (Lazy.Vector fr) where
46     write pl v
47         = liftIO $ sanitizeIOError $ Lazy.hPut (plHandle pl) v
48
49 -- | Open an ESD handle for playing a stream.
50 openPlayer ∷ ∀fr ch s pr.
51                ( Frame fr
52                , Channels ch
53                , MonadIO pr
54                )
55            ⇒ Int          -- ^ sample rate for the stream.
56            → HostName     -- ^ host to connect to.
57            → Maybe String -- ^ name used to identify this stream to
58                            --   ESD (if any).
59            → RegionT s pr (Player fr ch (RegionT s pr))
60 openPlayer rate host name
61     = do h  ← liftIO openSocket
62          ch ← onExit $ sanitizeIOError $ closeSocket h
63          return Player {
64                       plRate   = rate
65                     , plHandle = h
66                     , plCloseH = ch
67                     }
68     where
69       fmt :: C'esd_format_t
70       fmt = frameFmt   ((⊥) ∷ fr) .&.
71             channelFmt ((⊥) ∷ ch) .&.
72             c'ESD_STREAM            .&.
73             c'ESD_PLAY
74
75       openSocket :: IO Handle
76       openSocket = withCString    host $ \hostPtr →
77                    withCStrOrNull name $ \namePtr →
78                        c'esd_play_stream
79                        fmt
80                        (fromIntegral rate)
81                        hostPtr
82                        namePtr
83                        ≫= wrapSocket "esd_play_stream() returned an error"