haskore-0.2.0.5: The Haskore Computer Music System

Safe HaskellSafe-Inferred

Haskore.Music

Documentation

type Dur = TSource

type Atom note = Maybe noteSource

data Primitive note Source

Constructors

Atom Dur (Atom note) 

Instances

Eq note => Eq (Primitive note) 
Ord note => Ord (Primitive note) 
Show note => Show (Primitive note) 
C (Primitive note) 

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

(=:=) :: T note -> T note -> T noteSource

rest :: Dur -> T noteSource

bnr :: T noteSource

sfnr :: T noteSource

tnr :: T noteSource

snr :: T noteSource

enr :: T noteSource

qnr :: T noteSource

hnr :: T noteSource

wnr :: T noteSource

dwnr :: T noteSource

dtnr :: T noteSource

dsnr :: T noteSource

denr :: T noteSource

dqnr :: T noteSource

dhnr :: T noteSource

ddhnr :: T noteSource

ddenr :: T noteSource

ddqnr :: T noteSource

line :: [T note] -> 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 Dynamic Source

Constructors

Loudness Rational 
Accent Rational 
Crescendo Rational 
Diminuendo Rational 

Instances

Eq Dynamic 
Ord Dynamic 
Show Dynamic 

data Tempo Source

Constructors

Ritardando Rational 
Accelerando Rational 

Instances

Eq Tempo 
Ord Tempo 
Show Tempo 

dynamic :: Dynamic -> T note -> T noteSource

tempo :: Tempo -> T note -> T noteSource

articulation :: Articulation -> T note -> T noteSource

ornament :: Ornament -> T note -> T noteSource

accent :: Rational -> T note -> T noteSource

accelerando :: Rational -> T note -> T noteSource

ritardando :: Rational -> T note -> T noteSource

loudness1 :: Rational -> T note -> T noteSource

diminuendo :: Rational -> T note -> T noteSource

crescendo :: Rational -> T note -> T noteSource

staccato :: Dur -> T note -> T noteSource

legato :: Dur -> T note -> T noteSource

defltLegato :: T note -> T noteSource

bigAccent :: T note -> T noteSource

defltAccent :: T note -> T noteSource

defltStaccato :: T note -> T noteSource