haskore-0.0.5: The Haskore Computer Music SystemSource codeContentsIndex
Haskore.Music
Documentation
type Dur = TSource
type Atom note = Maybe noteSource
data Primitive note Source
Constructors
Atom Dur (Atom note)
show/hide Instances
Eq note => Eq (Primitive note)
Ord note => Ord (Primitive note)
Show note => Show (Primitive note)
C (Primitive note)
data Control Source
Constructors
Tempo DurRatio
Transpose Relative
Player PlayerName
Phrase PhraseAttribute
show/hide Instances
type DurRatio = DurSource
type PlayerName = StringSource
atom :: Dur -> Atom note -> T noteSource
control :: Control -> T note -> T noteSource
mkControl :: (a -> Control) -> a -> T note -> T noteSource
changeTempo :: DurRatio -> T note -> T noteSource
transpose :: Relative -> T note -> T noteSource
setPlayer :: PlayerName -> T note -> T noteSource
phrase :: PhraseAttribute -> T note -> T noteSource
type T note = T Control (Primitive note)Source
(=:=) :: T note -> T note -> T noteSource
rest :: Dur -> T noteSource
wnr :: T noteSource
dhnr :: T noteSource
ddqnr :: T noteSource
chord :: [T note] -> T noteSource
delay :: Dur -> T note -> T noteSource
repeat :: T note -> T noteSource
replicate :: Int -> T note -> T noteSource
dur :: T note -> DurSource
reverse :: T note -> T noteSource
take :: Dur -> T note -> T noteSource
takeLine :: Dur -> [T note] -> [T note]Source
take' :: Dur -> T note -> (Dur, T note)Source
takeLine' :: Dur -> [T note] -> (Dur, [T note])Source
(/=:) :: T note -> T note -> T noteSource
drop :: Dur -> T note -> T noteSource
dropLine :: Dur -> [T note] -> [T note]Source
drop' :: Dur -> T note -> (Dur, T note)Source
dropLine' :: Dur -> [T note] -> (Dur, [T note])Source
filter :: (note -> Bool) -> T note -> T noteSource
partition :: (note -> Bool) -> T note -> (T note, T note)Source
partitionMaybe :: (noteA -> Maybe noteB) -> T noteA -> (T noteB, T noteA)Source
applyPrimitive :: (Dur -> Atom note -> b) -> Primitive note -> bSource
switchBinary :: (Dur -> Atom note -> b) -> (Control -> T note -> b) -> (T note -> T note -> b) -> (T note -> T note -> b) -> b -> T note -> bSource
switchList :: (Dur -> Atom note -> b) -> (Control -> T note -> b) -> ([T note] -> b) -> ([T note] -> b) -> T note -> bSource
foldBin :: (Dur -> Atom note -> b) -> (Control -> b -> b) -> (b -> b -> b) -> (b -> b -> b) -> b -> T note -> bSource
foldList :: (Dur -> Atom note -> b) -> (Control -> b -> b) -> ([b] -> b) -> ([b] -> b) -> T note -> bSource
mapListFlat :: (Dur -> Atom noteA -> (Dur, Atom noteB)) -> (Control -> T noteA -> T noteB) -> ([T noteA] -> [T noteB]) -> ([T noteA] -> [T noteB]) -> T noteA -> T noteBSource
mapList :: (Dur -> Atom noteA -> (Dur, Atom noteB)) -> (Control -> T noteB -> T noteB) -> ([T noteB] -> [T noteB]) -> ([T noteB] -> [T noteB]) -> T noteA -> T noteBSource
mapNote :: (noteA -> noteB) -> T noteA -> T noteBSource
mapDurNote :: (Dur -> noteA -> noteB) -> T noteA -> T noteBSource
data PhraseAttribute Source
Constructors
Dyn Dynamic
Tmp Tempo
Art Articulation
Orn Ornament
show/hide Instances
data Dynamic Source
Constructors
Loudness Rational
Accent Rational
Crescendo Rational
Diminuendo Rational
show/hide Instances
data Tempo Source
Constructors
Ritardando Rational
Accelerando Rational
show/hide Instances
data Articulation Source
Constructors
Staccato Dur
Legato Dur
Slurred Dur
Tenuto
Marcato
Pedal
Fermata
FermataDown
Breath
DownBow
UpBow
Harmonic
Pizzicato
LeftPizz
BartokPizz
Swell
Wedge
Thumb
Stopped
show/hide Instances
data Ornament Source
Constructors
Trill
Mordent
InvMordent
DoubleMordent
Turn
TrilledTurn
ShortTrill
Arpeggio
ArpeggioUp
ArpeggioDown
Instruction String
Head NoteHead
show/hide Instances
data NoteHead Source
Constructors
DiamondHead
SquareHead
XHead
TriangleHead
TremoloHead
SlashHead
ArtHarmonic
NoHead
show/hide Instances
dynamic :: Dynamic -> T note -> T noteSource
tempo :: Tempo -> T note -> T noteSource
articulation :: Articulation -> T note -> T noteSource
ornament :: Ornament -> T note -> T noteSource
crescendo :: Rational -> T note -> T noteSource
legato :: Dur -> T note -> T noteSource
defltStaccato :: T note -> T noteSource
Produced by Haddock version 2.3.0