vivid-0.2.0.5: Sound synthesis with SuperCollider

Safe HaskellNone
LanguageHaskell98
Extensions
  • ScopedTypeVariables
  • BangPatterns
  • OverloadedStrings
  • InstanceSigs
  • TypeSynonymInstances
  • FlexibleInstances
  • KindSignatures
  • ExplicitForAll
  • LambdaCase

Vivid.SCServer

Contents

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

newtype Timestamp Source

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

Constructors

Timestamp Double 

Nodes

data Node args 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.

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

Or:

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

Or:

> n <- synthG foo ()

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

Constructors

Node 

Fields

unNode :: NodeId
 

Instances

Buffers

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 hard drive!

Note that like "makeBuffer" this is synchronous

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

Write a buffer to a file

Synchronous.

Manual management of SC server connection

createSCServerConnection :: SCConnectConfig -> IO 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 :: 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

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

_scConnectConfig_hostName :: HostName
 
_scConnectConfig_port :: ServiceName
 
_scConnectConfig_clientId :: Int32

To prevent NodeId clashes when multiple clients are connected to the same server, each client should have a separate clientId, which keeps the nodeId separate. Sclang's default clientId is 0, and ours is 1, so you can run both at the same time without config.

_scConnectConfig_connProtocol :: ConnProtocol
 
_scConnectConfig_serverMessageFunction :: OSC -> IO ()
 

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.

shrinkNodeArgs :: Subset new old => Node old -> Node new Source

So let's say you have a node:

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

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

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

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

ns' = shrinkNodeArgs foo : ns

(The same thing exists for SynthDefs -- shrinkSDArgs)