haskore-0.0.5: The Haskore Computer Music SystemSource codeContentsIndex
Haskore.Interface.CSound.SoundMap
Documentation
type SoundId = InstrumentSource
type InstrumentId = SoundIdSource
type DrumId = SoundIdSource
type Attribute = PFieldSource
type AttributeList = [Attribute]Source
type ToSound instr = instr -> (AttributeList, SoundId)Source
attributeControl :: Int -> SigExpSource
type InstrumentTable out instr = [(instr, InstrumentSigExp out)]Source
type InstrumentTableWithAttributes out instr = [InstrumentAssociation out instr]Source
type InstrumentSigExp out = SigExp -> SigExp -> SigExp -> outSource
data InstrumentAssociation out instr Source
Constructors
InstrumentAssociation InstrumentId (instr -> Maybe AttributeList) out
lookupInstrument :: InstrumentTableWithAttributes out instr -> ToSound instrSource
instrumentTableToInstrBlocks :: InstrumentTableWithAttributes out instr -> [InstrBlock out]Source
addInstrumentControls :: InstrumentSigExp out -> outSource
instrumentAssociation :: (parameterTuple -> AttributeList) -> (graph -> InstrumentSigExp out) -> InstrumentId -> (instr -> Maybe parameterTuple) -> graph -> InstrumentAssociation out instrSource
instrument :: InstrumentId -> (instr -> Maybe ()) -> InstrumentSigExp out -> InstrumentAssociation out instrSource
instrumentEq :: Eq instrument => InstrumentId -> instrument -> InstrumentSigExp out -> InstrumentAssociation out instrumentSource
instrument1 :: InstrumentId -> (instr -> Maybe Attribute) -> (SigExp -> InstrumentSigExp out) -> InstrumentAssociation out instrSource
instrument2 :: InstrumentId -> (instr -> Maybe (Attribute, Attribute)) -> (SigExp -> SigExp -> InstrumentSigExp out) -> InstrumentAssociation out instrSource
instrument3 :: InstrumentId -> (instr -> Maybe (Attribute, Attribute, Attribute)) -> (SigExp -> SigExp -> SigExp -> InstrumentSigExp out) -> InstrumentAssociation out instrSource
instrument4 :: InstrumentId -> (instr -> Maybe (Attribute, Attribute, Attribute, Attribute)) -> (SigExp -> SigExp -> SigExp -> SigExp -> InstrumentSigExp out) -> InstrumentAssociation out instrSource
type DrumTable out drum = [(drum, DrumSigExp out)]Source
type DrumTableWithAttributes out drum = [DrumAssociation out drum]Source
type DrumSigExp out = SigExp -> SigExp -> outSource
data DrumAssociation out drum Source
Constructors
DrumAssociation DrumId (drum -> Maybe AttributeList) out
lookupDrum :: DrumTableWithAttributes out drum -> ToSound drumSource
drumTableToInstrBlocks :: DrumTableWithAttributes out instr -> [InstrBlock out]Source
addDrumControls :: DrumSigExp out -> outSource
drumAssociation :: (parameterTuple -> AttributeList) -> (graph -> DrumSigExp out) -> DrumId -> (drum -> Maybe parameterTuple) -> graph -> DrumAssociation out drumSource
drum :: DrumId -> (drum -> Maybe ()) -> DrumSigExp out -> DrumAssociation out drumSource
drumEq :: Eq drum => DrumId -> drum -> DrumSigExp out -> DrumAssociation out drumSource
drum1 :: DrumId -> (drum -> Maybe Attribute) -> (SigExp -> DrumSigExp out) -> DrumAssociation out drumSource
drum2 :: DrumId -> (drum -> Maybe (Attribute, Attribute)) -> (SigExp -> SigExp -> DrumSigExp out) -> DrumAssociation out drumSource
drum3 :: DrumId -> (drum -> Maybe (Attribute, Attribute, Attribute)) -> (SigExp -> SigExp -> SigExp -> DrumSigExp out) -> DrumAssociation out drumSource
drum4 :: DrumId -> (drum -> Maybe (Attribute, Attribute, Attribute, Attribute)) -> (SigExp -> SigExp -> SigExp -> SigExp -> DrumSigExp out) -> DrumAssociation out drumSource
Produced by Haddock version 2.3.0