hsc3-0.19.1: Haskell SuperCollider
Safe HaskellNone
LanguageHaskell2010

Sound.SC3.Server.Graphdef

Description

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

Synopsis

Type

type Name = ASCII Source #

Names are ASCII strings (ie. ByteString.Char8)

type Control = (Name, Int) Source #

Controls are a name and a ugen-index.

type Sample = Double Source #

Constants are floating point.

type UGen_Index = Int Source #

UGen indices are Int.

type Port_Index = Int Source #

Port indices are Int.

constant_index :: UGen_Index Source #

Index used to indicate constants at UGen inputs. Ie. if the ugen-index is this value (-1) it indicates a constant.

data Input Source #

Inputs are a ugen-index and a port-index.

Instances

Instances details
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 #

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_name_op :: UGen -> String Source #

UGen name, using operator name if appropriate.

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 (ie. not a constant, indicated by a ugen-index of -1) and the UGen is a control.

data Graphdef Source #

Graph definition type.

Instances

Instances details
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 -> UGen_Index -> 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.

BINARY GET (version 0|1 or 2)

get_pstr :: Get Name Source #

Get a Name (Pascal string).

type GET_F m = (m Name, m Int, m Int, m Int, m Double) Source #

Get functions for Graphdef types, (str_f,i8_f,i16_f,i32_f,f32_f)

binary_get_f :: GET_F Get Source #

GET_F for binary .scsyndef files.

get_control :: Monad m => (GET_F m, m Int) -> m Control Source #

Get a Control.

get_input :: Monad m => m Int -> m Input Source #

Get an Input.

get_ugen :: Monad m => (GET_F m, m Int) -> m UGen Source #

Get a UGen

get_graphdef :: Monad m => GET_F m -> m Graphdef Source #

Get a Graphdef. Supports version 0|1 and version 2 files. Ignores variants.

READ

read_graphdef_file :: FilePath -> IO Graphdef Source #

Read Graphdef from .scsyndef 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"

STAT

Encode (version zero)

type ENCODE_F t = ([t] -> t, Name -> t, Int -> t, Int -> t, Int -> t, Double -> t, String -> t) Source #

(join_f,str_f,i8_f,i16_f,i32_f,f32_f,com_f)

encode_pstr :: Name -> ByteString Source #

Pascal (length prefixed) encoding of Name.

encode_sample :: Sample -> ByteString Source #

Encode Sample as 32-bit IEEE float.

scgf_i32 :: Num n => n Source #

SCgf encoded as 32-bit unsigned integer.

Byte.decode_i32 (Byte.encode_ascii (Datum.ascii "SCgf"))

IO

graphdefWrite :: FilePath -> Graphdef -> IO () Source #

Write Graphdef to indicated file.

graphdefWrite_dir :: FilePath -> Graphdef -> IO () Source #

Write Graphdef to indicated directory. The filename is the graphdef_name with the appropriate extension (scsyndef).

Stat

graphdef_stat :: Graphdef -> String Source #

Simple statistics printer for Graphdef.

Dump UGens

ugen_dump_ugen_str :: [Sample] -> [UGen] -> UGen_Index -> UGen -> String Source #

Pretty print UGen in the manner of SynthDef>>dumpUGens.

graphdef_dump_ugens_str :: Graphdef -> [String] Source #

Print graphdef in format equivalent to SynthDef>>dumpUGens in SuperCollider

graphdef_dump_ugens :: Graphdef -> IO () Source #

putStrLn of unlines of graphdef_dump_ugens_str

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