haskore-supercollider-0.1: Haskore back-end for SuperColliderSource codeContentsIndex
Haskore.Interface.SuperCollider.SoundMap
Contents
Generic definitions
Generic sound maps
Instrument maps
Drum maps
Sound Maps with Channel management
Description
This module is quite specific to Haskore.Music.Rhythmic. Maybe the module name should reflect this?
Synopsis
type Name = String
type Attribute = Double
type AttributeList = [Attribute]
type ToSound instr = instr -> (AttributeList, Name)
attributeControl :: Int -> UGen
attributeName :: Int -> String
attributeNames :: [String]
control :: String -> UGen
pitchName :: String
velocityName :: String
durationName :: String
with0Attributes :: (() -> AttributeList, sound -> sound)
with1Attribute :: (Attribute -> AttributeList, (UGen -> sound) -> sound)
with2Attributes :: ((Attribute, Attribute) -> AttributeList, (UGen -> UGen -> sound) -> sound)
with3Attributes :: ((Attribute, Attribute, Attribute) -> AttributeList, (UGen -> UGen -> UGen -> sound) -> sound)
with4Attributes :: ((Attribute, Attribute, Attribute, Attribute) -> AttributeList, (UGen -> UGen -> UGen -> UGen -> sound) -> sound)
type Table params sound = [(sound, Sound params)]
type TableWithAttributes params sound = [Assign params sound]
type TableWithChannels params sound = [(Channel, Assign params sound)]
type Sound params = params -> UGen
class SoundParameters params where
soundParameters :: params
ugenFromSound :: SoundParameters params => Sound params -> UGen
data Assign params sound = Assign Name (sound -> Maybe AttributeList) (Sound params)
lookup :: TableWithAttributes params sound -> ToSound sound
assignGeneric :: (attributeTuple -> AttributeList, soundGen -> Sound params) -> Name -> (sound -> Maybe attributeTuple) -> soundGen -> Assign params sound
assign :: Name -> (sound -> Maybe ()) -> Sound params -> Assign params sound
assignEq :: Eq sound => Name -> sound -> Sound params -> Assign params sound
assign1 :: Name -> (sound -> Maybe Attribute) -> (UGen -> Sound params) -> Assign params sound
assign2 :: Name -> (sound -> Maybe (Attribute, Attribute)) -> (UGen -> UGen -> Sound params) -> Assign params sound
assign3 :: Name -> (sound -> Maybe (Attribute, Attribute, Attribute)) -> (UGen -> UGen -> UGen -> Sound params) -> Assign params sound
assign4 :: Name -> (sound -> Maybe (Attribute, Attribute, Attribute, Attribute)) -> (UGen -> UGen -> UGen -> UGen -> Sound params) -> Assign params sound
withDuration :: (UGen -> Sound params) -> Sound params
data InstrumentParameters = InstrumentParameters {
instrumentDuration :: UGen
instrumentVelocity :: UGen
instrumentFrequency :: UGen
}
instrumentParameters :: InstrumentParameters
type InstrumentTable instr = Table InstrumentParameters instr
type InstrumentTableWithAttributes instr = TableWithAttributes InstrumentParameters instr
type InstrumentTableWithChannels instr = TableWithChannels InstrumentParameters instr
type Instrument = Sound InstrumentParameters
type InstrumentAssign instr = Assign InstrumentParameters instr
instrumentFromUGen :: (UGen -> UGen -> UGen) -> Instrument
data DrumParameters = DrumParameters {
drumDuration :: UGen
drumVelocity :: UGen
}
drumParameters :: DrumParameters
type DrumTable instr = Table DrumParameters instr
type DrumTableWithAttributes instr = TableWithAttributes DrumParameters instr
type DrumTableWithChannels instr = TableWithChannels DrumParameters instr
type Drum = Sound DrumParameters
type DrumAssign instr = Assign DrumParameters instr
drumFromUGen :: (UGen -> UGen) -> Drum
newtype ChannelMap drum instr = ChannelMap {
runChannelMap :: Channel -> (UGen, (DrumTableWithChannels drum, InstrumentTableWithChannels instr))
}
registerSound :: params -> ((Channel, Assign params sound) -> (DrumTableWithChannels drum, InstrumentTableWithChannels instr) -> (DrumTableWithChannels drum, InstrumentTableWithChannels instr)) -> Assign params sound -> (UGen -> ChannelMap drum instr) -> ChannelMap drum instr
registerInstrument :: InstrumentAssign instr -> (UGen -> ChannelMap drum instr) -> ChannelMap drum instr
registerDrum :: DrumAssign drum -> (UGen -> ChannelMap drum instr) -> ChannelMap drum instr
soundEffect :: UGen -> ChannelMap drum instr
Generic definitions
type Name = StringSource
type Attribute = DoubleSource
Attribute means an optional information for a note. Compare with InstrumentParameters.
type AttributeList = [Attribute]Source
type ToSound instr = instr -> (AttributeList, Name)Source
attributeControl :: Int -> UGenSource
attributeName :: Int -> StringSource
attributeNames :: [String]Source
control :: String -> UGenSource
pitchName :: StringSource
velocityName :: StringSource
durationName :: StringSource
Generic sound maps
with0Attributes :: (() -> AttributeList, sound -> sound)Source
with1Attribute :: (Attribute -> AttributeList, (UGen -> sound) -> sound)Source
with2Attributes :: ((Attribute, Attribute) -> AttributeList, (UGen -> UGen -> sound) -> sound)Source
with3Attributes :: ((Attribute, Attribute, Attribute) -> AttributeList, (UGen -> UGen -> UGen -> sound) -> sound)Source
with4Attributes :: ((Attribute, Attribute, Attribute, Attribute) -> AttributeList, (UGen -> UGen -> UGen -> UGen -> sound) -> sound)Source
type Table params sound = [(sound, Sound params)]Source
type TableWithAttributes params sound = [Assign params sound]Source
type TableWithChannels params sound = [(Channel, Assign params sound)]Source
type Sound params = params -> UGenSource
class SoundParameters params whereSource
Methods
soundParameters :: paramsSource
show/hide Instances
ugenFromSound :: SoundParameters params => Sound params -> UGenSource
data Assign params sound Source
Constructors
Assign Name (sound -> Maybe AttributeList) (Sound params)
lookup :: TableWithAttributes params sound -> ToSound soundSource
assignGeneric :: (attributeTuple -> AttributeList, soundGen -> Sound params) -> Name -> (sound -> Maybe attributeTuple) -> soundGen -> Assign params soundSource
assign :: Name -> (sound -> Maybe ()) -> Sound params -> Assign params soundSource
assignEq :: Eq sound => Name -> sound -> Sound params -> Assign params soundSource
assign1 :: Name -> (sound -> Maybe Attribute) -> (UGen -> Sound params) -> Assign params soundSource
assign2 :: Name -> (sound -> Maybe (Attribute, Attribute)) -> (UGen -> UGen -> Sound params) -> Assign params soundSource
assign3 :: Name -> (sound -> Maybe (Attribute, Attribute, Attribute)) -> (UGen -> UGen -> UGen -> Sound params) -> Assign params soundSource
assign4 :: Name -> (sound -> Maybe (Attribute, Attribute, Attribute, Attribute)) -> (UGen -> UGen -> UGen -> UGen -> Sound params) -> Assign params soundSource
withDuration :: (UGen -> Sound params) -> Sound paramsSource
Instrument maps
data InstrumentParameters Source
Parameter means an obligatory information for a note, like frequency, velocity, duration. Compare with Attribute.
Constructors
InstrumentParameters
instrumentDuration :: UGen
instrumentVelocity :: UGen
instrumentFrequency :: UGen
show/hide Instances
instrumentParameters :: InstrumentParametersSource
type InstrumentTable instr = Table InstrumentParameters instrSource
type InstrumentTableWithAttributes instr = TableWithAttributes InstrumentParameters instrSource
type InstrumentTableWithChannels instr = TableWithChannels InstrumentParameters instrSource
type Instrument = Sound InstrumentParametersSource
type InstrumentAssign instr = Assign InstrumentParameters instrSource
instrumentFromUGen :: (UGen -> UGen -> UGen) -> InstrumentSource
Drum maps
data DrumParameters Source
Constructors
DrumParameters
drumDuration :: UGen
drumVelocity :: UGen
show/hide Instances
drumParameters :: DrumParametersSource
type DrumTable instr = Table DrumParameters instrSource
type DrumTableWithAttributes instr = TableWithAttributes DrumParameters instrSource
type DrumTableWithChannels instr = TableWithChannels DrumParameters instrSource
type Drum = Sound DrumParametersSource
type DrumAssign instr = Assign DrumParameters instrSource
drumFromUGen :: (UGen -> UGen) -> DrumSource
Sound Maps with Channel management
newtype ChannelMap drum instr Source
Like a State+Writer monad with the binding operation baked into registerInstrument. This way we can suppress ignoring of results of registerInstrument, which is easily possible with 'do' notation.
Constructors
ChannelMap
runChannelMap :: Channel -> (UGen, (DrumTableWithChannels drum, InstrumentTableWithChannels instr))
registerSound :: params -> ((Channel, Assign params sound) -> (DrumTableWithChannels drum, InstrumentTableWithChannels instr) -> (DrumTableWithChannels drum, InstrumentTableWithChannels instr)) -> Assign params sound -> (UGen -> ChannelMap drum instr) -> ChannelMap drum instrSource
registerInstrument :: InstrumentAssign instr -> (UGen -> ChannelMap drum instr) -> ChannelMap drum instrSource
registerDrum :: DrumAssign drum -> (UGen -> ChannelMap drum instr) -> ChannelMap drum instrSource
soundEffect :: UGen -> ChannelMap drum instrSource
Produced by Haddock version 2.6.0