| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
Sound.SC3.Server.State.Monad
- data Server a
- runServer :: Server a -> ServerOptions -> Connection -> IO a
- class Monad m => MonadServer m where
- serverOptions :: m ServerOptions
- rootNodeId :: m NodeId
- serverOption :: MonadServer m => (ServerOptions -> a) -> m a
- data BufferId
- data BufferIdAllocator
- data ControlBusId
- data ControlBusIdAllocator
- data AudioBusId
- data AudioBusIdAllocator
- data NodeId
- data NodeIdAllocator
- class Monad m => MonadIdAllocator m where
- data Allocator m a
- nodeIdAllocator :: Allocator m NodeIdAllocator
- syncIdAllocator :: Allocator m SyncIdAllocator
- bufferIdAllocator :: Allocator m BufferIdAllocator
- audioBusIdAllocator :: Allocator m AudioBusIdAllocator
- controlBusIdAllocator :: Allocator m ControlBusIdAllocator
- alloc :: IdAllocator a => Allocator m a -> m (Id a)
- free :: IdAllocator a => Allocator m a -> Id a -> m ()
- statistics :: IdAllocator a => Allocator m a -> m Statistics
- allocRange :: RangeAllocator a => Allocator m a -> Int -> m (Range (Id a))
- freeRange :: RangeAllocator a => Allocator m a -> Range (Id a) -> m ()
- class Monad m => SendOSC m where
- class SendOSC m => RequestOSC m where
- request :: OSC o => o -> Notification a -> m a
- requestAll :: OSC o => o -> [Notification a] -> m [a]
- data SyncId
- data SyncIdAllocator
- sync :: Packet -> Server ()
- unsafeSync :: Server ()
- asTransport :: AsTransport a -> Server a
- fork :: Server () -> Server ThreadId
Server Monad
Instances
| Monad Server | |
| Functor Server | |
| MonadFix Server | |
| Applicative Server | |
| MonadIO Server | |
| SendOSC Server | |
| RequestOSC Server | |
| MonadIdAllocator Server | |
| MonadServer Server | |
| Failure AllocFailure Server | |
| MonadBase IO Server | |
| MonadBaseControl IO Server | |
| data Allocator Server = Allocator (State -> MVar a) | |
| type StM Server a = a |
runServer :: Server a -> ServerOptions -> Connection -> IO a Source
Run a Server computation given a connection and return the result.
Server options
class Monad m => MonadServer m where Source
Methods
serverOptions :: m ServerOptions Source
Return the server options.
rootNodeId :: m NodeId Source
Return the root node id.
Instances
| MonadServer Server | |
| MonadServer m => MonadServer (Request m) |
serverOption :: MonadServer m => (ServerOptions -> a) -> m a Source
Return a server option.
Allocation
Buffer id.
data ControlBusId Source
Control bus id.
data ControlBusIdAllocator Source
Control bus id allocator.
data AudioBusId Source
Audio bus id.
data AudioBusIdAllocator Source
Audio bus id allocator.
Node id.
class Monad m => MonadIdAllocator m where Source
Monadic resource id management interface.
Methods
nodeIdAllocator :: Allocator m NodeIdAllocator Source
NodeId allocator.
syncIdAllocator :: Allocator m SyncIdAllocator Source
SyncId allocator.
bufferIdAllocator :: Allocator m BufferIdAllocator Source
BufferId allocator.
audioBusIdAllocator :: Allocator m AudioBusIdAllocator Source
AudioBusId allocator.
controlBusIdAllocator :: Allocator m ControlBusIdAllocator Source
ControlBusId allocator.
alloc :: IdAllocator a => Allocator m a -> m (Id a) Source
Allocate an id using the given allocator.
free :: IdAllocator a => Allocator m a -> Id a -> m () Source
Free an id using the given allocator.
statistics :: IdAllocator a => Allocator m a -> m Statistics Source
Return allocator statistics
allocRange :: RangeAllocator a => Allocator m a -> Int -> m (Range (Id a)) Source
Allocate a contiguous range of ids using the given allocator.
freeRange :: RangeAllocator a => Allocator m a -> Range (Id a) -> m () Source
Free a contiguous range of ids using the given allocator.
Instances
Communication and synchronization
class SendOSC m => RequestOSC m where Source
Methods
request :: OSC o => o -> Notification a -> m a Source
Wait for a notification and return the result.
requestAll :: OSC o => o -> [Notification a] -> m [a] Source
Wait for a set of notifications and return their results in unspecified order.
Instances
Synchronisation barrier id.
unsafeSync :: Server () Source
asTransport :: AsTransport a -> Server a Source