Safe Haskell | None |
---|---|
Language | Haskell2010 |
Extensions | OverloadedStrings |
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
- cmdPeriod :: VividAction m => m ()
- freeAll :: VividAction m => m ()
- data Timestamp = Timestamp Double
- newtype NodeId = NodeId {}
- newtype Synth (args :: [Symbol]) = Synth {}
- newtype Group = Group {}
- newtype ParGroup = ParGroup {}
- defaultGroup :: Group
- newtype BufferId = BufferId {
- _unBufferId :: Int32
- makeBuffer :: VividAction m => Int32 -> m BufferId
- makeBufferFromFile :: VividAction m => FilePath -> m BufferId
- newBuffer :: VividAction m => Int32 -> m BufferId
- newBufferFromFile :: VividAction m => FilePath -> m BufferId
- newBufferFromFileBetween :: VividAction m => Int32 -> Maybe Int32 -> FilePath -> m BufferId
- saveBuffer :: VividAction m => BufferId -> FilePath -> m ()
- writeBuffer :: VividAction m => BufferId -> FilePath -> m ()
- writeBufferWith :: VividAction m => WriteBufArgs -> BufferId -> FilePath -> m ()
- data WriteBufArgs = WriteBufArgs {
- _wb_keepOpen :: Bool
- defaultWBArgs :: WriteBufArgs
- closeBuf :: VividAction m => BufferId -> m ()
- closeBuffer :: VividAction m => BufferId -> m ()
- zeroBuf :: VividAction m => BufferId -> m ()
- createSCServerConnection' :: SCServerState -> SCConnectConfig -> IO (Either String Socket)
- closeSCServerConnection' :: SCServerState -> IO ()
- data SCConnectConfig = SCConnectConfig {}
- defaultConnectConfig :: SCConnectConfig
- module Vivid.SCServer.State
- shrinkSynthArgs :: Subset new old => Synth old -> Synth new
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
This is stored as the number of seconds since Jan 1 1900. You can get
it with getTime
Instances
Eq Timestamp | |
Ord Timestamp | |
Defined in Vivid.OSC | |
Read Timestamp | |
Show Timestamp | |
VividAction Scheduled Source # | |
Defined in Vivid.Actions.Scheduled callOSC :: OSC -> Scheduled () Source # callBS :: ByteString -> Scheduled () Source # waitForSync :: SyncId -> Scheduled () Source # wait :: Real n => n -> Scheduled () Source # getTime :: Scheduled Timestamp Source # newBufferId :: Scheduled BufferId Source # newNodeId :: Scheduled NodeId Source # newSyncId :: Scheduled SyncId Source # fork :: Scheduled () -> Scheduled () Source # defineSD :: forall (a :: [Symbol]). SynthDef a -> Scheduled () Source # |
Nodes
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)
Instances
Eq (Synth args) Source # | |
Ord (Synth args) Source # | |
Read (Synth args) Source # | |
Show (Synth args) Source # | |
SynthOrNodeId (Synth x) Source # | |
Defined in Vivid.SCServer.Types | |
IsNode (Synth a) Source # | |
defaultGroup :: Group Source #
Buffers
makeBuffer :: VividAction m => Int32 -> m BufferId Source #
makeBufferFromFile :: VividAction m => FilePath -> m BufferId 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
newBufferFromFileBetween :: VividAction m => Int32 -> Maybe Int32 -> FilePath -> m BufferId Source #
saveBuffer :: VividAction m => BufferId -> FilePath -> m () Source #
writeBuffer :: VividAction m => BufferId -> FilePath -> m () Source #
writeBufferWith :: VividAction m => WriteBufArgs -> BufferId -> FilePath -> m () Source #
data WriteBufArgs Source #
We may add arguments in the future ; to future-proof your code, just update
fields of defaultWBArgs
Instances
Eq WriteBufArgs Source # | |
Defined in Vivid.SCServer (==) :: WriteBufArgs -> WriteBufArgs -> Bool # (/=) :: WriteBufArgs -> WriteBufArgs -> Bool # | |
Ord WriteBufArgs Source # | |
Defined in Vivid.SCServer compare :: WriteBufArgs -> WriteBufArgs -> Ordering # (<) :: WriteBufArgs -> WriteBufArgs -> Bool # (<=) :: WriteBufArgs -> WriteBufArgs -> Bool # (>) :: WriteBufArgs -> WriteBufArgs -> Bool # (>=) :: WriteBufArgs -> WriteBufArgs -> Bool # max :: WriteBufArgs -> WriteBufArgs -> WriteBufArgs # min :: WriteBufArgs -> WriteBufArgs -> WriteBufArgs # | |
Read WriteBufArgs Source # | |
Defined in Vivid.SCServer readsPrec :: Int -> ReadS WriteBufArgs # readList :: ReadS [WriteBufArgs] # | |
Show WriteBufArgs Source # | |
Defined in Vivid.SCServer showsPrec :: Int -> WriteBufArgs -> ShowS # show :: WriteBufArgs -> String # showList :: [WriteBufArgs] -> ShowS # |
closeBuf :: VividAction m => BufferId -> m () Source #
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 #
SCConnectConfig | |
|
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.
module Vivid.SCServer.State
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
)