Safe Haskell | None |
---|---|
Language | Haskell2010 |
Binary 'Graph Definition' as understood by scsynth
.
There are both 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
- get_pstr :: Get Name
- type GET_F m = (m Name, m Int, m Int, m Int, m Double)
- binary_get_f :: GET_F Get
- get_control :: Monad m => (GET_F m, m Int) -> m Control
- get_input :: Monad m => m Int -> m Input
- get_ugen :: Monad m => (GET_F m, m Int) -> m UGen
- get_graphdef :: Monad m => GET_F m -> m Graphdef
- read_graphdef_file :: FilePath -> IO Graphdef
- scsyndef_stat :: FilePath -> IO String
- type ENCODE_F t = ([t] -> t, Name -> t, Int -> t, Int -> t, Int -> t, Double -> t, String -> t)
- enc_bytestring :: ENCODE_F ByteString
- encode_pstr :: Name -> ByteString
- encode_input_f :: ENCODE_F t -> Input -> t
- encode_input :: Input -> ByteString
- encode_control_f :: ENCODE_F t -> Control -> t
- encode_control :: Control -> ByteString
- encode_ugen_f :: ENCODE_F t -> UGen -> t
- encode_ugen :: UGen -> ByteString
- encode_sample :: Sample -> ByteString
- encode_graphdef_f :: ENCODE_F t -> Graphdef -> t
- encode_graphdef :: Graphdef -> ByteString
- scgf_i32 :: Num n => n
- graphdefWrite :: FilePath -> Graphdef -> IO ()
- graphdefWrite_dir :: FilePath -> Graphdef -> IO ()
- 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.
BINARY GET (version 0|1 or 2)
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_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
scsyndef_stat :: FilePath -> IO String Source #
read_graphdef_file
and run graphdef_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_input_f :: ENCODE_F t -> Input -> t Source #
encode_input :: Input -> ByteString Source #
Byte-encode Input
.
encode_control_f :: ENCODE_F t -> Control -> t Source #
encode_control :: Control -> ByteString Source #
Byte-encode Control
.
encode_ugen_f :: ENCODE_F t -> UGen -> t Source #
encode_ugen :: UGen -> ByteString Source #
Byte-encode UGen
.
encode_sample :: Sample -> ByteString Source #
Encode Sample
as 32-bit IEEE float.
encode_graphdef_f :: ENCODE_F t -> Graphdef -> t Source #
encode_graphdef :: Graphdef -> ByteString Source #
Encode Graphdef
.
scgf_i32 :: Num n => n Source #
SCgf encoded as 32-bit unsigned integer.
Byte.decode_i32 (Byte.encode_ascii (Datum.ascii "SCgf"))
IO
graphdefWrite_dir :: FilePath -> Graphdef -> IO () Source #
Write Graphdef
to indicated directory. The filename is the
graphdef_name
with the appropriate extension (scsyndef
).
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
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"