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

Safe HaskellNone

Sound.SC3.Server.State.Monad.Command

Contents

Synopsis

Requests

data Request m a Source

Server-side action (or sequence of actions).

Instances

Monad m => Monad (Request m) 
Functor m => Functor (Request m) 
(Monad m, Functor m) => Applicative (Request m) 
Monad m => SendOSC (Request m)

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

MonadIdAllocator m => MonadIdAllocator (Request m) 
MonadServer m => MonadServer (Request m) 

exec :: (MonadIdAllocator m, RequestOSC m) => Time -> Request m a -> m aSource

Execute a request.

The commands after the last asynchronous command will be scheduled at the given time.

exec_ :: (MonadIdAllocator m, RequestOSC m) => Request m a -> m aSource

Execute a request immediately.

data Result a Source

Representation of a deferred server resource.

Resource resource values can only be observed with extract after the surrounding Request action has been executed with exec.

extract :: MonadIO m => Result a -> m aSource

Extract a 'Result'\'s value.

Master controls

status :: MonadIO m => Request m (Result Status)Source

Request server status.

statusM :: (MonadIdAllocator m, RequestOSC m, MonadIO m) => m StatusSource

Request server status.

data PrintLevel

Enumeration of Message printer types.

dumpOSC :: MonadIdAllocator m => PrintLevel -> Request m ()Source

Select printing of incoming Open Sound Control messages.

clearSched :: Monad m => Request m ()Source

Remove all bundles from the scheduling queue.

data ErrorScope

Error posting scope.

Constructors

Globally

Global scope

Locally

Bundle scope

data ErrorMode

Error posting mode.

Constructors

ErrorsOff

Turn error posting off

ErrorsOn

Turn error posting on

errorMode :: Monad m => ErrorScope -> ErrorMode -> Request m ()Source

Set error posting scope and mode.

Synth definitions

d_named :: String -> SynthDefSource

Construct a synth definition from a name.

d_default :: SynthDefSource

The default synth definition.

d_recv :: Monad m => String -> UGen -> Request m SynthDefSource

Compute a unique name for a UGen graph. graphName :: UGen -> String graphName = SHA.showBSasHex . SHA.hash SHA.SHA256 . BZip.compress . Synthdef.graphdef . Synthdef.synth

Create a new synth definition. d_new :: Monad m => String -> UGen -> Async m SynthDef d_new prefix ugen | length prefix < 127 = mkAsync $ return (sd, f) | otherwise = error d_new: name prefix too long, resulting string exceeds 255 characters where sd = SynthDef (prefix ++ - ++ graphName ugen) f osc = (mkC C.d_recv C.d_recv' osc) (Synthdef.synthdef (name sd) ugen)

Create a synth definition from a name and a UGen graph.

d_load :: Monad m => FilePath -> Request m ()Source

Load a synth definition from a named file. (Asynchronous)

d_loadDir :: Monad m => FilePath -> Request m ()Source

Load a directory of synth definition files. (Asynchronous)

d_free :: Monad m => SynthDef -> Request m ()Source

Remove definition once all nodes using it have ended.

Resources

Nodes

class Node a whereSource

Methods

nodeId :: a -> NodeIdSource

data AddAction

Enumeration of possible locations to add new nodes (s_new and g_new).

node :: (Eq n, Node n, Show n) => n -> AbstractNodeSource

Construct an abstract node wrapper.

n_after :: (Node a, Node b, Monad m) => a -> b -> Request m ()Source

Place node a after node b.

n_before :: (Node a, Node b, Monad m) => a -> b -> Request m ()Source

Place node a before node b.

n_fill :: (Node a, Monad m) => a -> [(String, Int, Double)] -> Request m ()Source

Fill ranges of a node's control values.

n_free :: (Node a, MonadIdAllocator m) => a -> Request m ()Source

Delete a node.

class BusMapping n b whereSource

Mapping node controls to buses.

Methods

n_map :: (Node n, Bus b, Monad m) => n -> String -> b -> Request m ()Source

Map a node's controls to read from a control bus.

n_unmap :: (Node n, Bus b, Monad m) => n -> String -> b -> Request m ()Source

Remove a control's mapping to a control bus.

n_query_ :: (Node a, Monad m) => a -> Request m ()Source

Query a node.

n_query :: (Node a, MonadIO m) => a -> Request m (Result NodeNotification)Source

Query a node.

n_queryM :: (Node a, MonadIdAllocator m, RequestOSC m, MonadIO m) => a -> m NodeNotificationSource

Query a node.

n_run_ :: (Node a, Monad m) => a -> Bool -> Request m ()Source

Turn node on or off.

n_set :: (Node a, Monad m) => a -> [(String, Double)] -> Request m ()Source

Set a node's control values.

n_setn :: (Node a, Monad m) => a -> [(String, [Double])] -> Request m ()Source

Set ranges of a node's control values.

n_trace :: (Node a, Monad m) => a -> Request m ()Source

Trace a node.

n_order :: (Node n, Monad m) => AddAction -> n -> [AbstractNode] -> Request m ()Source

Move an ordered sequence of nodes.

Synths

newtype Synth Source

Constructors

Synth NodeId 

s_new :: MonadIdAllocator m => SynthDef -> AddAction -> Group -> [(String, Double)] -> Request m SynthSource

Create a new synth.

s_new_ :: (MonadServer m, MonadIdAllocator m) => SynthDef -> AddAction -> [(String, Double)] -> Request m SynthSource

Create a new synth in the root group.

s_release :: MonadIdAllocator m => Double -> Synth -> Request m ()Source

Release a synth with a gate envelope control.

s_get :: MonadIO m => Synth -> [String] -> Request m (Result [(Either Int32 String, Float)])Source

Get control values.

s_getn :: MonadIO m => Synth -> [(String, Int)] -> Request m (Result [(Either Int32 String, [Float])])Source

Get ranges of control values.

s_noid :: MonadIdAllocator m => Synth -> Request m ()Source

Free a synth's ID and auto-reassign it to a reserved value (the node is not freed!).

Groups

newtype Group Source

Constructors

Group NodeId 

rootNode :: MonadServer m => m GroupSource

Return the server's root group.

g_new :: MonadIdAllocator m => AddAction -> Group -> Request m GroupSource

Create a new group.

g_new_ :: (MonadServer m, MonadIdAllocator m) => AddAction -> Request m GroupSource

Create a new group in the top level group.

g_deepFree :: Monad m => Group -> Request m ()Source

Free all synths in this group and all its sub-groups.

g_freeAll :: Monad m => Group -> Request m ()Source

Delete all nodes in a group.

g_head :: (Node n, Monad m) => Group -> n -> Request m ()Source

Add node to head of group.

g_tail :: (Node n, Monad m) => Group -> n -> Request m ()Source

Add node to tail of group.

g_dumpTree :: Monad m => [(Group, Bool)] -> Request m ()Source

Post a representation of a group's node subtree, optionally including the current control values for synths.

Plugin Commands

cmd :: Monad m => String -> [Datum] -> Request m ()Source

Send a plugin command.

Unit Generator Commands

u_cmd :: Monad m => AbstractNode -> Int -> String -> [Datum] -> Request m ()Source

Send a command to a unit generator.

Buffers

b_alloc :: MonadIdAllocator m => Int -> Int -> Request m BufferSource

Allocates zero filled buffer to number of channels and samples. (Asynchronous)

b_allocRead :: MonadIdAllocator m => FilePath -> Maybe Int -> Maybe Int -> Request m BufferSource

Allocate buffer space and read a sound file. (Asynchronous)

b_allocReadChannel :: MonadIdAllocator m => FilePath -> Maybe Int -> Maybe Int -> [Int] -> Request m BufferSource

Allocate buffer space and read a sound file, picking specific channels. (Asynchronous)

b_read :: Monad m => Buffer -> FilePath -> Maybe Int -> Maybe Int -> Maybe Int -> Bool -> Request m ()Source

Read sound file data into an existing buffer. (Asynchronous)

b_readChannel :: MonadIO m => Buffer -> FilePath -> Maybe Int -> Maybe Int -> Maybe Int -> Bool -> [Int] -> Request m ()Source

Read sound file data into an existing buffer, picking specific channels. (Asynchronous)

b_write :: MonadIO m => Buffer -> FilePath -> SoundFileFormat -> SampleFormat -> Maybe Int -> Maybe Int -> Bool -> Request m ()Source

Write sound file data. (Asynchronous)

b_free :: MonadIdAllocator m => Buffer -> Request m ()Source

Free buffer. (Asynchronous)

b_zero :: MonadIO m => Buffer -> Request m ()Source

Zero sample data. (Asynchronous)

b_set :: Monad m => Buffer -> [(Int, Double)] -> Request m ()Source

Set sample values.

b_setn :: Monad m => Buffer -> [(Int, [Double])] -> Request m ()Source

Set ranges of sample values.

b_fill :: Monad m => Buffer -> [(Int, Int, Double)] -> Request m ()Source

Fill ranges of sample values.

b_gen :: MonadIdAllocator m => Buffer -> String -> [Datum] -> Request m ()Source

Call a command to fill a buffer. (Asynchronous)

b_gen_sine1 :: MonadIdAllocator m => Buffer -> [B_Gen] -> [Double] -> Request m ()Source

Fill a buffer with partials, specifying amplitudes.

b_gen_sine2 :: MonadIdAllocator m => Buffer -> [B_Gen] -> [(Double, Double)] -> Request m ()Source

Fill a buffer with partials, specifying frequencies (in cycles per buffer) and amplitudes.

b_gen_sine3 :: MonadIdAllocator m => Buffer -> [B_Gen] -> [(Double, Double, Double)] -> Request m ()Source

Fill a buffer with partials, specifying frequencies (in cycles per buffer), amplitudes and phases.

b_gen_cheby :: MonadIdAllocator m => Buffer -> [B_Gen] -> [Double] -> Request m ()Source

Fills a buffer with a series of chebyshev polynomials.

b_gen_copy :: MonadIdAllocator m => Buffer -> Int -> Buffer -> Int -> Maybe Int -> Request m ()Source

Copy samples from the source buffer to the destination buffer.

b_close :: Monad m => Buffer -> Request m ()Source

Close attached soundfile and write header information. (Asynchronous)

b_query :: MonadIO m => Buffer -> Request m (Result BufferInfo)Source

Request BufferInfo.

b_queryM :: (MonadIdAllocator m, RequestOSC m, MonadIO m) => Buffer -> m BufferInfoSource

Request BufferInfo.

Buses

class Bus a whereSource

Abstract interface for control and audio rate buses.

Methods

rate :: a -> RateSource

Rate of computation.

numChannels :: a -> IntSource

Number of channels.

freeBus :: (MonadServer m, MonadIdAllocator m) => a -> m ()Source

Free bus.

audioBusId :: AudioBus -> AudioBusIdSource

Get audio bus id.

inputBus :: (MonadServer m, Failure AllocFailure m) => Int -> Int -> m AudioBusSource

Get hardware input bus.

outputBus :: (MonadServer m, Failure AllocFailure m) => Int -> Int -> m AudioBusSource

Get hardware output bus.

newAudioBus :: MonadIdAllocator m => Int -> m AudioBusSource

Allocate audio bus with the specified number of channels.

controlBusId :: ControlBus -> ControlBusIdSource

Get control bus ID.

newControlBus :: MonadIdAllocator m => Int -> m ControlBusSource

Allocate control bus with the specified number of channels.

Control Bus Commands