vivid-0.5.2.0: Sound synthesis with SuperCollider
Safe HaskellNone
LanguageHaskell2010
Extensions
  • TypeFamilies
  • OverloadedStrings
  • DataKinds
  • KindSignatures
  • ExplicitNamespaces

Vivid.SynthDef.Types

Description

Internal. Just use Vivid.SynthDef

Synopsis

Documentation

data Signal Source #

Instances

Instances details
Eq Signal Source # 
Instance details

Defined in Vivid.SynthDef.Types

Methods

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

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

Show Signal Source # 
Instance details

Defined in Vivid.SynthDef.Types

MonoOrPoly Signal Source # 
Instance details

Defined in Vivid.Actions

Methods

getPoly :: forall (a :: [Symbol]). SDBody' a Signal -> SDBody' a [Signal]

ToSig Signal args Source # 
Instance details

Defined in Vivid.SynthDef.ToSig

Methods

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

MonoOrPoly [Signal] Source # 
Instance details

Defined in Vivid.Actions

Methods

getPoly :: forall (a :: [Symbol]). SDBody' a [Signal] -> SDBody' a [Signal]

a ~ args => ToSig (SDBody' a Signal) args Source # 
Instance details

Defined in Vivid.SynthDef.ToSig

Methods

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

data SynthDef (args :: [Symbol]) Source #

Internal representation of Synth Definitions. Usually, use sd instead of making these by hand.

This representation (especially _sdUGens) might change in the future.

Constructors

SynthDef 

Instances

Instances details
Eq (SynthDef args) Source # 
Instance details

Defined in Vivid.SynthDef.Types

Methods

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

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

Show (SynthDef args) Source # 
Instance details

Defined in Vivid.SynthDef.Types

Methods

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

show :: SynthDef args -> String #

showList :: [SynthDef args] -> ShowS #

Hashable (SynthDef a) Source #

This is the hash of the UGen graph and params, but not the name! So (re)naming a SynthDef will not change its hash.

Instance details

Defined in Vivid.SynthDef

Methods

hashWithSalt :: Int -> SynthDef a -> Int #

hash :: SynthDef a -> Int #

a ~ args => ToSig (SDBody' a Signal) args Source # 
Instance details

Defined in Vivid.SynthDef.ToSig

Methods

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

data SDName Source #

Instances

Instances details
Eq SDName Source # 
Instance details

Defined in Vivid.SynthDef.Types

Methods

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

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

Ord SDName Source # 
Instance details

Defined in Vivid.SynthDef.Types

Read SDName Source # 
Instance details

Defined in Vivid.SynthDef.Types

Show SDName Source # 
Instance details

Defined in Vivid.SynthDef.Types

type SDBody' (args :: [Symbol]) = State ([Int], SynthDef args, VarSet args) Source #

State monad to construct SynthDefs

The SynthDef is an under-construction synth definition The [Int] is the id supply. Its type definitely could change in the future

zoomSDBody :: Subset inner outer => SDBody' inner a -> SDBody' outer a Source #

Given

good0 :: SDBody '["2"] ()
good0 = return ()
good1 :: SDBody '["3","1","3","1"] ()
good1 = return ()
bad0 :: SDBody '["bwahaha"] ()
bad0 = return ()
outer :: SDBody '[ "1", "2", "3"]()
outer = do
   zoomSDBody good0 -- works
   zoomSDBody good1 -- works
   -- zoomSDBody bad0 -- doesn't work - great!

data UGen Source #

Representation of Unit Generators. You usually won't be creating these by hand, but instead using things from the library in UGens

Instances

Instances details
Eq UGen Source # 
Instance details

Defined in Vivid.SynthDef.Types

Methods

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

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

Show UGen Source # 
Instance details

Defined in Vivid.SynthDef.Types

Methods

showsPrec :: Int -> UGen -> ShowS #

show :: UGen -> String #

showList :: [UGen] -> ShowS #

data UGenName Source #

Instances

Instances details
Eq UGenName Source # 
Instance details

Defined in Vivid.SynthDef.Types

Show UGenName Source # 
Instance details

Defined in Vivid.SynthDef.Types