hsc3-0.19.1: Haskell SuperCollider
Safe HaskellNone
LanguageHaskell2010

Sound.SC3.Server.Transport.Monad

Description

Monad variant of interaction with the scsynth server.

Synopsis

hosc variants

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

sendMessage and waitReply for a /done reply.

maybe_async :: DuplexOSC m => Message -> m () Source #

If isAsync then async_ else sendMessage.

maybe_async_at :: DuplexOSC m => Time -> Message -> m () Source #

Variant that timestamps synchronous messages.

sc3_default_udp :: (String, Int) Source #

Local host (ie. 127.0.0.1) at port sc3_port_def

sc3_udp_limit :: Num n => n Source #

Maximum packet size, in bytes, that can be sent over UDP. However, see also https://tools.ietf.org/html/rfc2675

withSC3At :: (String, Int) -> Connection UDP a -> IO a Source #

Bracket SC3 communication at indicated host and port.

withSC3 :: Connection UDP a -> IO a Source #

Bracket SC3 communication, ie. withSC3At sc3_default_udp.

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

withSC3At_seq :: (String, Int) -> Int -> Connection UDP a -> IO [a] Source #

Run f at k scsynth servers with sequential port numbers starting at sc3_port_def.

withSC3At_seq sc3_default_udp 2 (sendMessage status >> waitReply "/status.reply")

withSC3At_seq_ :: (String, Int) -> Int -> Connection UDP a -> IO () Source #

void of withSC3_seq.

Server control

stop :: SendOSC m => m () Source #

Free all nodes (g_freeAll) at group 1.

Composite

reset :: SendOSC m => m () Source #

Runs clearSched and then frees and re-creates groups 1 and 2.

type Play_Opt = (Node_Id, AddAction, Group_Id, [(String, Double)]) Source #

(node-id,add-action,group-id,parameters)

play_graphdef_msg :: Play_Opt -> Graphdef -> Message Source #

Make s_new message to play Graphdef.

recv_or_load_graphdef :: Transport m => Graphdef -> m Message Source #

If the graph size is less than sc3_udp_limit encode and send using d_recv_bytes, else write to temporary directory and read using d_load.

playGraphdef :: Transport m => Play_Opt -> Graphdef -> m () Source #

Send d_recv and s_new messages to scsynth.

playSynthdef :: Transport m => Play_Opt -> Synthdef -> m () Source #

Send d_recv and s_new messages to scsynth.

playUGen :: Transport m => Play_Opt -> 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.

nrt_play :: Transport m => NRT -> m () Source #

Play an NRT score (as would be rendered by writeNRT).

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

nrt_play_reorder :: Transport m => NRT -> m () Source #

Variant where 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.

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 => Play_Opt -> e -> m () Source #

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

Variant where id is -1.

Instances

Instances details
Audible Graphdef Source # 
Instance details

Defined in Sound.SC3.Server.Transport.Monad

Methods

play_at :: Transport m => Play_Opt -> Graphdef -> m () Source #

play :: Transport m => Graphdef -> m () Source #

Audible UGen Source # 
Instance details

Defined in Sound.SC3.Server.Transport.Monad

Methods

play_at :: Transport m => Play_Opt -> UGen -> m () Source #

play :: Transport m => UGen -> m () Source #

Audible Synthdef Source # 
Instance details

Defined in Sound.SC3.Server.Transport.Monad

Methods

play_at :: Transport m => Play_Opt -> Synthdef -> m () Source #

play :: Transport m => Synthdef -> m () Source #

audition_at_seq :: Audible e => (String, Int) -> Play_Opt -> Int -> e -> IO () Source #

withSC3_seq of play_at.

def_play_opt :: Play_Opt Source #

Default Play_Opt, ie. (-1,addToHead,1,[])

Notifications

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

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

Buffer & control & node variants.

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

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

withSC3_tm 1.0 (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_tm 1.0 (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.

b_fetch1 :: DuplexOSC m => Int -> Int -> m [Double] Source #

First channel of b_fetch, errors if there is no data.

withSC3 (b_fetch1 512 123456789)

b_fetch_hdr :: Transport m => Int -> Int -> m ((Int, Int, Int, Double), [[Double]]) Source #

Combination of b_query1_unpack and b_fetch.

b_query1_unpack_generic :: (DuplexOSC m, Num n, Fractional r) => Int -> m (n, n, n, r) Source #

b_info_unpack_err of b_query1.

b_query1_unpack :: DuplexOSC m => Buffer_Id -> m (Int, Int, Int, Double) Source #

Type specialised b_query1_unpack_generic.

withSC3 (b_query1_unpack 0)

c_getn1_data :: (DuplexOSC m, Floating t) => (Int, Int) -> m [t] Source #

Variant of c_getn1 that waits for the reply and unpacks the data.

n_query1_unpack_f :: DuplexOSC m => (Message -> t) -> Node_Id -> m t Source #

Apply f to result of n_query.

n_query1_unpack :: DuplexOSC m => Node_Id -> m (Maybe (Int, Int, Int, Int, Int, Maybe (Int, Int))) Source #

Variant of n_query that waits for and unpacks the reply.

n_query1_unpack_plain :: DuplexOSC m => Node_Id -> m [Int] Source #

Variant of n_query1_unpack that returns plain (un-lifted) result.

g_queryTree1_unpack :: DuplexOSC m => Group_Id -> m Query_Node Source #

Variant of g_queryTree that waits for and unpacks the reply.

Status

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

Collect server status information.

withSC3 serverStatus >>= mapM putStrLn

server_status_concise :: DuplexOSC m => m String Source #

Collect server status information.

withSC3 server_status_concise >>= putStrLn

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.

Tree

serverTree :: DuplexOSC m => m [String] Source #

Collect server node tree information.

withSC3 serverTree >>= mapM_ putStrLn