vivid-0.5.2.0: Sound synthesis with SuperCollider
Safe HaskellNone
LanguageHaskell2010

Vivid.SCServer.Types

Synopsis

Documentation

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 #

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)

class IsNode a where Source #

Methods

getNodeId :: a -> NodeId Source #

Instances

Instances details
IsNode NodeId Source # 
Instance details

Defined in Vivid.SCServer.Types

IsNode Group Source # 
Instance details

Defined in Vivid.SCServer.Types

IsNode ParGroup 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 #

class IsNode a => SynthOrNodeId a Source #

For gradually-typed free

Instances

Instances details
SynthOrNodeId NodeId Source # 
Instance details

Defined in Vivid.SCServer.Types

SynthOrNodeId (Synth x) Source # 
Instance details

Defined in Vivid.SCServer.Types

class IsNode g => IsGroup g Source #

Instances

Instances details
IsGroup Group Source # 
Instance details

Defined in Vivid.SCServer.Types

IsGroup ParGroup Source # 
Instance details

Defined in Vivid.SCServer.Types