Safe Haskell | None |
---|---|
Language | Haskell2010 |
Extensions |
|
Vivid.SC.SynthDef.Literally
Description
You probably don't need to use this directly -- use Vivid.SynthDef instead
This is a representation of how SynthDefs are sent over the wire, as described in the Synth Definition File Format helpfile.
- data LiteralSynthDef = LiteralSynthDef {}
- encodeSynthDefFile :: SynthDefFile -> ByteString
- decodeSynthDefFile :: ByteString -> Either String SynthDefFile
- encodeLiteralSynthDef :: LiteralSynthDef -> ByteString
- decodeLiteralSynthDef :: ByteString -> (LiteralSynthDef, ByteString)
- getLiteralSynthDef' :: Get LiteralSynthDef
- putLiteralSynthDef' :: LiteralSynthDef -> Put
- data UGenSpec = UGenSpec {}
- data InputSpec
- data ParamName = ParamName {}
- data SynthDefFile = SynthDefFile [LiteralSynthDef]
- data OutputSpec = OutputSpec {}
- data VariantSpec = VariantSpec {}
- uOpToSpecialI :: UnaryOp -> Int16
- biOpToSpecialI :: BinaryOp -> Int16
- specialIToUOp :: Int16 -> UnaryOp
- specialIToBiOp :: Int16 -> BinaryOp
- sdLitPretty :: LiteralSynthDef -> String
- putPString' :: ByteString -> Put
- getPString' :: Get ByteString
- encodePString :: ByteString -> ByteString
- getPString :: ByteString -> (ByteString, ByteString)
- getParamName :: ByteString -> (ParamName, ByteString)
- getParamName' :: Get ParamName
- putParamName' :: ParamName -> Put
- encodeParamName :: ParamName -> ByteString
- getInputSpec' :: Get InputSpec
- putInputSpec' :: InputSpec -> Put
- getInputSpec :: ByteString -> (InputSpec, ByteString)
- encodeInputSpec :: InputSpec -> ByteString
- getOutputSpec' :: Get OutputSpec
- putOutputSpec' :: OutputSpec -> Put
- getOutputSpec :: ByteString -> (OutputSpec, ByteString)
- encodeOutputSpec :: OutputSpec -> ByteString
- getCalcRate' :: Get CalculationRate
- putCalcRate' :: CalculationRate -> Put
- getUGenSpec :: ByteString -> (UGenSpec, ByteString)
- getUGenSpec' :: Get UGenSpec
- encodeUGenSpec :: UGenSpec -> ByteString
- putUGenSpec' :: UGenSpec -> Put
- getVariantSpec :: Int32 -> ByteString -> (VariantSpec, ByteString)
- getVariantSpec' :: Int32 -> Get VariantSpec
- putVariantSpec' :: VariantSpec -> Put
- encodeVariantSpec :: VariantSpec -> ByteString
Documentation
data LiteralSynthDef Source #
Constructors
LiteralSynthDef | |
Fields
|
Instances
Constructors
UGenSpec | |
Fields |
These record fields are deprecated as it's a variant -- don't use!
Constructors
InputSpec_UGen | |
Fields | |
InputSpec_Constant | |
Fields |
Constructors
ParamName | |
Fields |
uOpToSpecialI :: UnaryOp -> Int16 Source #
biOpToSpecialI :: BinaryOp -> Int16 Source #
specialIToUOp :: Int16 -> UnaryOp Source #
specialIToBiOp :: Int16 -> BinaryOp Source #
sdLitPretty :: LiteralSynthDef -> String Source #
putPString' :: ByteString -> Put Source #
getPString' :: Get ByteString Source #
A "pascal format string"
encodePString :: ByteString -> ByteString Source #
getPString :: ByteString -> (ByteString, ByteString) Source #
getParamName :: ByteString -> (ParamName, ByteString) Source #
putParamName' :: ParamName -> Put Source #
putInputSpec' :: InputSpec -> Put Source #
getInputSpec :: ByteString -> (InputSpec, ByteString) Source #
putOutputSpec' :: OutputSpec -> Put Source #
getOutputSpec :: ByteString -> (OutputSpec, ByteString) Source #
putCalcRate' :: CalculationRate -> Put Source #
getUGenSpec :: ByteString -> (UGenSpec, ByteString) Source #
encodeUGenSpec :: UGenSpec -> ByteString Source #
putUGenSpec' :: UGenSpec -> Put Source #
getVariantSpec :: Int32 -> ByteString -> (VariantSpec, ByteString) Source #
getVariantSpec' :: Int32 -> Get VariantSpec Source #
putVariantSpec' :: VariantSpec -> Put Source #