vivid-0.5.1.0: Sound synthesis with SuperCollider
Safe HaskellNone
LanguageHaskell2010
ExtensionsOverloadedStrings

Vivid.SCServer

Description

Library for interacting with the SuperCollider server.

You don't need to use much of this day-to-day

There's a toplevel scServerState that stores the current state of the SC server

Synopsis

Documentation

cmdPeriod :: VividAction m => m () Source #

Your "emergency" button. Run this and everything playing on the SC server will be freed -- silence!

Corresponds to the cmd-. / ctrl-. key command in the SuperCollider IDE

freeAll :: VividAction m => m () Source #

Alias of cmdPeriod

data Timestamp #

This is stored as the number of seconds since Jan 1 1900. You can get it with getTime

Constructors

Timestamp Double 

Nodes

newtype NodeId #

Constructors

NodeId 

Fields

Instances

Instances details
Eq NodeId 
Instance details

Defined in Vivid.SC.Server.Types

Methods

(==) :: NodeId -> NodeId -> Bool #

(/=) :: NodeId -> NodeId -> Bool #

Ord NodeId 
Instance details

Defined in Vivid.SC.Server.Types

Read NodeId 
Instance details

Defined in Vivid.SC.Server.Types

Show NodeId 
Instance details

Defined in Vivid.SC.Server.Types

SynthOrNodeId NodeId Source # 
Instance details

Defined in Vivid.SCServer.Types

IsNode NodeId Source # 
Instance details

Defined in Vivid.SCServer.Types

newtype Synth (args :: [Symbol]) Source #

This enforces type safety of the arguments -- e.g. if you have a synthdef

> let x = sd (3 ::I "foo") bar
> s <- synth x ()

Then this won't typecheck (because "bar" isn't an argument to x):

> set s (4 ::I "bar")

Note that if you don't want this type safety, you can e.g.

> Synth n <- synth foo ()
> setG n (0.1 ::I "vol")

Or:

> ns <- mapM (flip synth ()) [foo, bar, baz]
> map (setG (0::I "asdf") . unSynth) ns

Or:

> n <- synthG foo ()

(You also may want to look at shrinkSynthArgs if you want to construct a list which has synthdefs or nodes of different types)

Constructors

Synth 

Fields

Instances

Instances details
Eq (Synth args) Source # 
Instance details

Defined in Vivid.SCServer.Types

Methods

(==) :: Synth args -> Synth args -> Bool #

(/=) :: Synth args -> Synth args -> Bool #

Ord (Synth args) Source # 
Instance details

Defined in Vivid.SCServer.Types

Methods

compare :: Synth args -> Synth args -> Ordering #

(<) :: Synth args -> Synth args -> Bool #

(<=) :: Synth args -> Synth args -> Bool #

(>) :: Synth args -> Synth args -> Bool #

(>=) :: Synth args -> Synth args -> Bool #

max :: Synth args -> Synth args -> Synth args #

min :: Synth args -> Synth args -> Synth args #

Read (Synth args) Source # 
Instance details

Defined in Vivid.SCServer.Types

Methods

readsPrec :: Int -> ReadS (Synth args) #

readList :: ReadS [Synth args] #

readPrec :: ReadPrec (Synth args) #

readListPrec :: ReadPrec [Synth args] #

Show (Synth args) Source # 
Instance details

Defined in Vivid.SCServer.Types

Methods

showsPrec :: Int -> Synth args -> ShowS #

show :: Synth args -> String #

showList :: [Synth args] -> ShowS #

SynthOrNodeId (Synth x) Source # 
Instance details

Defined in Vivid.SCServer.Types

IsNode (Synth a) Source # 
Instance details

Defined in Vivid.SCServer.Types

Methods

getNodeId :: Synth a -> NodeId Source #

newtype Group #

Constructors

Group 

Fields

Instances

Instances details
Eq Group 
Instance details

Defined in Vivid.SC.Server.Types

Methods

(==) :: Group -> Group -> Bool #

(/=) :: Group -> Group -> Bool #

Ord Group 
Instance details

Defined in Vivid.SC.Server.Types

Methods

compare :: Group -> Group -> Ordering #

(<) :: Group -> Group -> Bool #

(<=) :: Group -> Group -> Bool #

(>) :: Group -> Group -> Bool #

(>=) :: Group -> Group -> Bool #

max :: Group -> Group -> Group #

min :: Group -> Group -> Group #

Read Group 
Instance details

Defined in Vivid.SC.Server.Types

Show Group 
Instance details

Defined in Vivid.SC.Server.Types

Methods

showsPrec :: Int -> Group -> ShowS #

show :: Group -> String #

showList :: [Group] -> ShowS #

IsGroup Group Source # 
Instance details

Defined in Vivid.SCServer.Types

IsNode Group Source # 
Instance details

Defined in Vivid.SCServer.Types

newtype ParGroup #

Constructors

ParGroup 

Fields

Instances

Instances details
Eq ParGroup 
Instance details

Defined in Vivid.SC.Server.Types

Ord ParGroup 
Instance details

Defined in Vivid.SC.Server.Types

Read ParGroup 
Instance details

Defined in Vivid.SC.Server.Types

Show ParGroup 
Instance details

Defined in Vivid.SC.Server.Types

IsGroup ParGroup Source # 
Instance details

Defined in Vivid.SCServer.Types

IsNode ParGroup Source # 
Instance details

Defined in Vivid.SCServer.Types

Buffers

newtype BufferId #

Constructors

BufferId 

Fields

Instances

Instances details
Eq BufferId 
Instance details

Defined in Vivid.SC.Server.Types

Ord BufferId 
Instance details

Defined in Vivid.SC.Server.Types

Read BufferId 
Instance details

Defined in Vivid.SC.Server.Types

Show BufferId 
Instance details

Defined in Vivid.SC.Server.Types

ToSig BufferId args Source # 
Instance details

Defined in Vivid.SynthDef.ToSig

Methods

toSig :: BufferId -> SDBody' args Signal Source #

newBuffer :: VividAction m => Int32 -> m BufferId Source #

Make an empty buffer

The Int32 is the buffer length in samples. Multiply seconds by the default sample rate of the server (usually 48000) to get the number of samples

Note that this is synchronous -- it doesn't return until the buffer is allocated (in theory, this could hang if e.g. the UDP packet is lost)

newBufferFromFile :: VividAction m => FilePath -> m BufferId Source #

Make a buffer and fill it with sound data from a file

The file path should be absolute (not relative), and if you're connecting to a non-localhost server don't expect it to be able to read files from your local hard drive!

Note that like makeBuffer this is synchronous

saveBuffer :: VividAction m => BufferId -> FilePath -> m () Source #

Write a buffer to a file

Alias of writeBuffer

Synchronous.

data WriteBufArgs Source #

We may add arguments in the future ; to future-proof your code, just update fields of defaultWBArgs

Constructors

WriteBufArgs 

Fields

closeBuffer :: VividAction m => BufferId -> m () Source #

Close an open soundfile and write header information

Synchronous

zeroBuf :: VividAction m => BufferId -> m () Source #

Zero the sample data in a buffer

Synchronous

Manual management of SC server connection

createSCServerConnection' :: SCServerState -> SCConnectConfig -> IO (Either String Socket) Source #

You usually don't need to call this function

Use this if to connect on a non-default port or to a server not at localhost

Otherwise the connection is created when it's needed. You can also use this to explicitly create the connection, so the computation is done upfront

The HostName is the ip address or "localhost". The ServiceName is the port

closeSCServerConnection' :: SCServerState -> IO () Source #

Explicitly close Vivid's connection to a SC server.

Day-to-day, you can usually just let your program run without using this.

For example though, if you're running code that uses Vivid in ghci, and you ":r", you'll want to disconnect first -- there are processes running which can step on the toes of your new instance (TODO: this isn't fully true - I ":r" all the time - what do I mean here?)

Also if you want to change the params of your connection (e.g. to connect to a different server), you'll want to disconnect from the other connection first

data SCConnectConfig Source #

Constructors

SCConnectConfig 

Fields

defaultConnectConfig :: SCConnectConfig Source #

The default _scConnectConfig_clientId is 1, and sclang's is 0, so you should be able to run vivid side-by-side with the SC IDE out of the box.

shrinkSynthArgs :: Subset new old => Synth old -> Synth new Source #

So let's say you have a node:

foo :: Synth '["amp", "freq", "phase"]

and you want to add it to a list of nodes:

ns :: [Synth '["freq", "phase"]]

If you don't plan on setting the "amp" argument, you can "shrink" to the compatible arguments:

ns' = shrinkSynthArgs foo : ns

(The same thing exists for SynthDefs -- shrinkSDArgs)