hsc3-server-0.6.0: SuperCollider server resource management and synchronization.

Safe HaskellNone

Sound.SC3.Server.State.Monad

Contents

Synopsis

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.

serverOption :: MonadServer m => (ServerOptions -> a) -> m aSource

Return a server option.

Allocation

data NodeIdAllocator Source

Node id allocator.

class Monad m => MonadIdAllocator m whereSource

Monadic resource id management interface.

Associated Types

data Allocator m a Source

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.

Communication and synchronization

class Monad m => SendOSC m where

Sender monad.

Methods

sendOSC :: OSC o => o -> m ()

Encode and send an OSC packet.

Instances

SendOSC AsTransport 
SendOSC Server 
(Monad (Request m), Monad m) => SendOSC (Request m)

Bundles are flattened into the resulting bundle because scsynth doesn't support nested bundles.

(Monad (ReaderT t io), Transport t, MonadIO io) => SendOSC (ReaderT t io) 

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

data SyncId Source

Synchronisation barrier id.

data SyncIdAllocator Source

Synchronisation barrier id allocator.

sync :: Packet -> Server ()Source

Send an OSC packet and wait for the synchronization barrier.

Concurrency

fork :: Server () -> Server ThreadIdSource

Fork a computation in a new thread and return the thread id.

This is an alias for fork.