hsc3-0.20: Haskell SuperCollider
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sound.Sc3.Server.Graphdef

Description

Binary 'Graph Definition' as understood by scsynth. There are both binary and text 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
Show Input Source # 
Instance details

Defined in Sound.Sc3.Server.Graphdef

Methods

showsPrec :: Int -> Input -> ShowS #

show :: Input -> String #

showList :: [Input] -> ShowS #

Eq Input Source # 
Instance details

Defined in Sound.Sc3.Server.Graphdef

Methods

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

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

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
Show Graphdef Source # 
Instance details

Defined in Sound.Sc3.Server.Graphdef

Eq 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

playAt :: 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.

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_input :: Monad m => m Int -> m Input Source #

Get an Input.

get_ugen :: Monad m => (Get_Functions m, m Int) -> m Ugen Source #

Get a Ugen

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)

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

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"