| Safe Haskell | None |
|---|
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 ()
- fork :: Server () -> Server ThreadId
Server Monad
runServer :: Server a -> ServerOptions -> Connection -> IO aSource
Run a Server computation given a connection and return the result.
Server options
class Monad m => MonadServer m whereSource
Methods
serverOptions :: m ServerOptionsSource
Return the server options.
rootNodeId :: m NodeIdSource
Return the root node id.
Instances
| MonadServer Server | |
| (Monad (Request m), MonadServer m) => MonadServer (Request m) |
serverOption :: MonadServer m => (ServerOptions -> a) -> m aSource
Return a server option.
Allocation
Buffer id.
data BufferIdAllocator Source
Buffer id allocator.
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 whereSource
Monadic resource id management interface.
Methods
nodeIdAllocator :: Allocator m NodeIdAllocatorSource
NodeId allocator.
syncIdAllocator :: Allocator m SyncIdAllocatorSource
SyncId allocator.
bufferIdAllocator :: Allocator m BufferIdAllocatorSource
BufferId allocator.
audioBusIdAllocator :: Allocator m AudioBusIdAllocatorSource
AudioBusId allocator.
controlBusIdAllocator :: Allocator m ControlBusIdAllocatorSource
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 StatisticsSource
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
| MonadIdAllocator Server | |
| (Monad (AllocT m), MonadIdAllocator m) => MonadIdAllocator (AllocT m) | |
| (Monad (Request m), MonadIdAllocator m) => MonadIdAllocator (Request m) |
Communication and synchronization
class SendOSC m => RequestOSC m whereSource
Methods
request :: OSC o => o -> Notification a -> m aSource
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