hsc3-0.15: Haskell SuperCollider

Safe HaskellNone
LanguageHaskell98

Sound.SC3.Server.Transport.Monad

Contents

Description

Monad variant of interaction with the scsynth server.

Synopsis

hosc variants

send :: SendOSC m => Message -> m () Source

Synonym for sendMessage.

async :: DuplexOSC m => Message -> m Message Source

Send a Message and waitReply for a /done reply.

withSC3 :: Connection UDP a -> IO a Source

Bracket SC3 communication. withTransport at standard SC3 UDP port.

import Sound.SC3.Server.Command
withSC3 (send status >> waitReply "/status.reply")

Server control

stop :: SendOSC m => m () Source

Free all nodes (g_freeAll) at group 1.

Composite

reset :: SendOSC m => m () Source

clearSched, free all nodes (g_freeAll) at, and then re-create, groups 1 and 2.

playGraphdef :: DuplexOSC m => (Int, AddAction, Int) -> Graphdef -> m () Source

Send d_recv and s_new messages to scsynth.

playSynthdef :: DuplexOSC m => (Int, AddAction, Int) -> Synthdef -> m () Source

Send d_recv and s_new messages to scsynth.

playUGen :: DuplexOSC m => (Int, AddAction, Int) -> UGen -> m () Source

Send an anonymous instrument definition using playSynthdef.

NRT

run_bundle :: Transport m => Time -> Bundle -> m () Source

Wait (pauseThreadUntil) until bundle is due to be sent relative to the initial Time, then send each message, asynchronously if required.

performNRT :: Transport m => NRT -> m () Source

Perform an NRT score (as would be rendered by writeNRT). Asynchronous commands at time 0 are separated out and run before the initial time-stamp is taken. This re-orders synchronous commands in relation to asynchronous at time 0.

let sc = NRT [bundle 1 [s_new0 "default" (-1) AddToHead 1]
             ,bundle 2 [n_set1 (-1) "gate" 0]]
in withSC3 (performNRT sc)

Audible

class Audible e where Source

Class for values that can be encoded and send to scsynth for audition.

Minimal complete definition

play_at

Methods

play_at :: Transport m => (Int, AddAction, Int) -> e -> m () Source

play :: Transport m => e -> m () Source

Variant where id is -1.

audition :: Audible e => e -> IO () Source

Variant where id is -1.

Notifications

withNotifications :: DuplexOSC m => m a -> m a Source

Turn on notifications, run f, turn off notifications, return result.

Buffer

b_getn1_data :: DuplexOSC m => Int -> (Int, Int) -> m [Double] Source

Variant of b_getn1 that waits for return message and unpacks it.

withSC3 (b_getn1_data 0 (0,5))

b_getn1_data_segment :: DuplexOSC m => Int -> Int -> (Int, Int) -> m [Double] Source

Variant of b_getn1_data that segments individual b_getn messages to n elements.

withSC3 (b_getn1_data_segment 1 0 (0,5))

b_fetch :: DuplexOSC m => Int -> Int -> m [Double] Source

Variant of b_getn1_data_segment that gets the entire buffer.

Status

serverStatus :: DuplexOSC m => m [String] Source

Collect server status information.

serverSampleRateNominal :: DuplexOSC m => m Double Source

Read nominal sample rate of server.

withSC3 serverSampleRateNominal

serverSampleRateActual :: DuplexOSC m => m Double Source

Read actual sample rate of server.

withSC3 serverSampleRateActual

serverStatusData :: DuplexOSC m => m [Datum] Source

Retrieve status data from server.