Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Binary 'Graph Definition' as understood by scsynth
.
There are both binary and text encoders and decoders.
Synopsis
- type Name = Ascii
- type Control = (Name, Int)
- type Sample = Double
- type Ugen_Index = Int
- type Port_Index = Int
- constant_index :: Ugen_Index
- data Input = Input Ugen_Index Port_Index
- type Rate = Int
- type Output = Rate
- type Special = Int
- type Ugen = (Name, Rate, [Input], [Output], Special)
- ugen_name_str :: Ugen -> String
- ugen_name_op :: Ugen -> String
- ugen_rate :: Ugen -> Rate
- ugen_rate_enum :: Ugen -> Rate
- ugen_inputs :: Ugen -> [Input]
- ugen_outputs :: Ugen -> [Output]
- ugen_is_control :: Ugen -> Bool
- input_is_control :: Graphdef -> Input -> Bool
- data Graphdef = Graphdef {
- graphdef_name :: Name
- graphdef_constants :: [Sample]
- graphdef_controls :: [(Control, Sample)]
- graphdef_ugens :: [Ugen]
- graphdef_ugen :: Graphdef -> Ugen_Index -> Ugen
- graphdef_control :: Graphdef -> Int -> (Control, Sample)
- graphdef_constant_nid :: Graphdef -> Int -> Int
- graphdef_control_nid :: Graphdef -> Int -> Int
- graphdef_ugen_nid :: Graphdef -> Int -> Int
- scgf_i32 :: Num n => n
- type Get_Functions m = (m Name, m Int, m Int, m Int, m Double)
- get_control :: Monad m => (Get_Functions m, m Int) -> m Control
- get_input :: Monad m => m Int -> m Input
- get_ugen :: Monad m => (Get_Functions m, m Int) -> m Ugen
- get_graphdef :: Monad m => Get_Functions m -> m Graphdef
- type Encode_Functions t = ([t] -> t, Name -> t, Int -> t, Int -> t, Int -> t, Double -> t, String -> t)
- encode_input_f :: Encode_Functions t -> Input -> t
- encode_control_f :: Encode_Functions t -> Control -> t
- encode_ugen_f :: Encode_Functions t -> Ugen -> t
- encode_graphdef_f :: Encode_Functions t -> Graphdef -> t
- graphdef_stat :: Graphdef -> String
- ugen_dump_ugen_str :: [Sample] -> [Ugen] -> Ugen_Index -> Ugen -> String
- graphdef_dump_ugens_str :: Graphdef -> [String]
- graphdef_dump_ugens :: Graphdef -> IO ()
Type
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.
Inputs are a ugen-index and a port-index.
ugen_rate_enum :: Ugen -> Rate Source #
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.
Graph definition type.
Graphdef | |
|
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.
scgf_i32 :: Num n => n Source #
SCgf encoded as 32-bit unsigned integer.
map fromEnum "SCgf" == [83, 67, 103, 102] Byte.decode_i32 (Byte.encode_ascii (Datum.ascii "SCgf"))
Get
type Get_Functions 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)
get_control :: Monad m => (Get_Functions m, m Int) -> m Control Source #
Get a Control
.
get_graphdef :: Monad m => Get_Functions m -> m Graphdef Source #
Get a Graphdef
. Supports version 0|1 and version 2 files. Ignores variants.
Encode (version zero)
type Encode_Functions t = ([t] -> t, Name -> t, Int -> t, Int -> t, Int -> t, Double -> t, String -> t) Source #
Encode functions for Graphdef types (join_f,str_f,i8_f,i16_f,i32_f,f32_f,com_f)
encode_input_f :: Encode_Functions t -> Input -> t Source #
encode_control_f :: Encode_Functions t -> Control -> t Source #
encode_ugen_f :: Encode_Functions t -> Ugen -> t Source #
encode_graphdef_f :: Encode_Functions t -> Graphdef -> t Source #
Stat
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
import Sound.Sc3.Server.Graphdef 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"