hsc3-0.17: Haskell SuperCollider

Safe HaskellNone
LanguageHaskell98

Sound.SC3.Server.Graphdef

Contents

Description

Binary 'Graph Definition' as understood by scsynth. There are both encoders and decoders.

Synopsis

Type

type Name = ASCII Source #

Names are ASCII strings.

type Control = (Name, Int) Source #

Controls are a name and a ugen-index.

type Sample = Double Source #

Constants are floating point.

data Input Source #

Inputs are a ugen-index and a port-index. If the ugen-index is -1 it indicates a constant.

Constructors

Input Int Int 
Instances
Eq Input Source # 
Instance details

Defined in Sound.SC3.Server.Graphdef

Methods

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

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

Show Input Source # 
Instance details

Defined in Sound.SC3.Server.Graphdef

Methods

showsPrec :: Int -> Input -> ShowS #

show :: Input -> String #

showList :: [Input] -> ShowS #

input_ugen_ix :: Input -> Maybe Int Source #

Read ugen-index of input, else Nothing.

type Rate = Int Source #

Rates are encoded as integers (IR = 0, KR = 1, AR = 2, DR = 3).

type Output = Rate Source #

Outputs each indicate a Rate.

type Special = Int Source #

Secondary (special) index, used by operator UGens to select operation.

type UGen = (Name, Rate, [Input], [Output], Special) Source #

Unit generator type.

ugen_is_control :: UGen -> Bool Source #

Predicate to examine Ugen name and decide if it is a control.

input_is_control :: Graphdef -> Input -> Bool Source #

Input is a UGen and the UGen is a control.

data Graphdef Source #

Graph definition type.

Instances
Eq Graphdef Source # 
Instance details

Defined in Sound.SC3.Server.Graphdef

Show Graphdef Source # 
Instance details

Defined in Sound.SC3.Server.Graphdef

Audible Graphdef Source # 
Instance details

Defined in Sound.SC3.Server.Transport.FD

Methods

play_id :: Transport t => Int -> t -> Graphdef -> IO () Source #

play :: Transport t => t -> Graphdef -> IO () Source #

Audible Graphdef Source # 
Instance details

Defined in Sound.SC3.Server.Transport.Monad

Methods

play_at :: Transport m => Play_Opt -> Graphdef -> m () Source #

play :: Transport m => Graphdef -> m () Source #

graphdef_ugen :: Graphdef -> Int -> UGen Source #

Lookup UGen by index.

graphdef_control :: Graphdef -> Int -> (Control, Sample) Source #

Lookup Control and default value by index.

graphdef_constant_nid :: Graphdef -> Int -> Int Source #

nid of constant.

graphdef_control_nid :: Graphdef -> Int -> Int Source #

nid of control.

graphdef_ugen_nid :: Graphdef -> Int -> Int Source #

nid of UGen.

Read (version 0 or 2).

read_input :: (Handle -> IO Int) -> Handle -> IO Input Source #

Read an Input.

read_output :: Handle -> IO Output Source #

Read an output.

read_ugen :: (Handle -> IO Int) -> Handle -> IO UGen Source #

Read a UGen.

read_graphdef :: Handle -> IO Graphdef Source #

Read a Graphdef. Ignores variants.

read_graphdef_file :: FilePath -> IO Graphdef Source #

Read Graphdef from file.

dir = "/home/rohan/sw/rsc3-disassembler/scsyndef/"
pp nm = read_graphdef_file (dir ++ nm) >>= putStrLn . graphdef_stat
pp "simple.scsyndef"
pp "with-ctl.scsyndef"
pp "mce.scsyndef"
pp "mrg.scsyndef"

Encode (version zero)

encode_pstr :: Name -> ByteString Source #

Pascal (length prefixed) encoding of string.

encode_sample :: Sample -> ByteString Source #

Encode Sample as 32-bit IEEE float.

Stat

graphdef_stat :: Graphdef -> String Source #

Simple statistics printer for Graphdef.