hommage-0.0.5: Haskell Offline Music Manipulation And Generation EDSLSource codeContentsIndex
Sound.Hommage.Notation
Contents
Duration
Music Notation
Musical class
Notation and Midi
More Notation functions
Synopsis
type Dur = Ratio Int
absDur :: Dur -> Int
class IsDur d where
durFrom :: d -> Dur
durUpdate :: (Dur -> Dur) -> d -> d
newtype IsDur d => WithDur d a = WithDur {
unWithDur :: d -> a
}
data Notation a
= Note Dur a
| Rest Dur
| (Notation a) :+: (Notation a)
| (Notation a) :=: (Notation a)
| Stretch Dur (Notation a)
runNotation :: Musical m => Notation m -> m
runNotationWith :: Musical m => (a -> m) -> Notation a -> m
class Stretchable a where
stretch :: Dur -> a -> a
class Arrangeable a where
parallel :: a -> a -> a
sequent :: a -> a -> a
class (Stretchable a, Arrangeable a) => Musical a where
rest :: a
rest0 :: Musical a => a
(-=-) :: Arrangeable a => a -> a -> a
(->-) :: Arrangeable a => a -> a -> a
line :: Musical a => [a] -> a
line' :: Musical a => [a] -> a
chord :: Musical a => [a] -> a
proportional :: Musical a => (Int, Int) -> a -> a -> a
writeMidiSyncNotation :: FilePath -> [Notation MidiNote] -> IO ()
midi :: IsDur d => MidiNote -> WithDur d MidiMusic
midi' :: IsDur d => WithDur d MidiNote -> WithDur d MidiMusic
midiSyncFile :: Ticks -> [WithDur Dur MidiMusic] -> MidiFile
note :: a -> Notation a
mapNotation :: (a -> b) -> Notation a -> Notation b
joinNotation :: Notation (Notation a) -> Notation a
unmaybeNotation :: Notation (Maybe a) -> Notation a
durationNotation :: Notation a -> Ratio Int
positionNotation :: Notation a -> Notation (Dur, a)
reverseNotation :: Notation a -> Notation a
takeNotation :: Ratio Int -> Notation a -> Notation a
dropNotation :: Ratio Int -> Notation a -> Notation a
filterNotation :: (Musical (m a), Monad m) => (a -> Bool) -> m a -> m a
filterNotation' :: (Musical (m a), Musical (m b), Monad m) => (a -> Maybe b) -> m a -> m b
sequenceNotation :: (a -> b -> c) -> Dur -> [a] -> Notation b -> Notation c
Duration
type Dur = Ratio IntSource
The duration (of a note, e. g).
absDur :: Dur -> IntSource
Calculates the absolute duration by dividing the numerator with the denominator. Because of rounding error this makes only sense if the result is a relative big number.
class IsDur d whereSource
Methods
durFrom :: d -> DurSource
durUpdate :: (Dur -> Dur) -> d -> dSource
show/hide Instances
newtype IsDur d => WithDur d a Source
Constructors
WithDur
unWithDur :: d -> a
show/hide Instances
Music Notation
data Notation a Source
A Notation is a constant, tree-like structure that represents a musical notation. It has a type parameter for flexible usage reasons.
Constructors
Note Dur aA note with given duration and a value of type a.
Rest DurA rest with given duration.
(Notation a) :+: (Notation a)Sequential composition of two notations.
(Notation a) :=: (Notation a)Parallel composition of two notations.
Stretch Dur (Notation a)Stretches the duration of the sub-music by given factor.
show/hide Instances
runNotation :: Musical m => Notation m -> mSource
A Notation can be interpreted if the contained type is an instance of class Musical.
runNotationWith :: Musical m => (a -> m) -> Notation a -> mSource
Musical class
class Stretchable a whereSource
A type/structure that can be stretched.
Methods
stretch :: Dur -> a -> aSource
show/hide Instances
class Arrangeable a whereSource
Types/structures that can be composed in two ways, parallel and sequent.
Methods
parallel :: a -> a -> aSource
sequent :: a -> a -> aSource
show/hide Instances
class (Stretchable a, Arrangeable a) => Musical a whereSource
Instances of class Musical must be Stretchable, Arrangeable and they must implement the method rest.
Methods
rest :: aSource
show/hide Instances
rest0 :: Musical a => aSource
(-=-) :: Arrangeable a => a -> a -> aSource
(->-) :: Arrangeable a => a -> a -> aSource
line :: Musical a => [a] -> aSource
A sequence of sounds
line' :: Musical a => [a] -> aSource
A sequence of sounds that will be stretched to length=1
chord :: Musical a => [a] -> aSource
proportional :: Musical a => (Int, Int) -> a -> a -> aSource
Composes the notations sequentially and stretches them proportionally.
Notation and Midi
writeMidiSyncNotation :: FilePath -> [Notation MidiNote] -> IO ()Source
A convenient function to write a set of midi notations to a synchronous MIDI-file. NOTE: For unknown reasons not any Ticks value seemes to work. This function uses 96 Ticks per quarter.
midi :: IsDur d => MidiNote -> WithDur d MidiMusicSource
A Notation MidiNote can be interpreted using runNotationWith and midi.
midi' :: IsDur d => WithDur d MidiNote -> WithDur d MidiMusicSource
midiSyncFile :: Ticks -> [WithDur Dur MidiMusic] -> MidiFileSource
More Notation functions
note :: a -> Notation aSource
Creates a note with length 1. Is a synonym for Note (1%1)
mapNotation :: (a -> b) -> Notation a -> Notation bSource
Notation is instance of the class Functor.
joinNotation :: Notation (Notation a) -> Notation aSource
Notation is instance of the class Monad. Joining will replace every (outer) Note by its contained (inner) Notation. The inner Notation will be stretched by the duration of the (outer) Note.
unmaybeNotation :: Notation (Maybe a) -> Notation aSource
Replaces any Note that contains Nothing by a rest (with same duration).
durationNotation :: Notation a -> Ratio IntSource
Calculates the (relative) duration of a Notation (Must be finite!).
positionNotation :: Notation a -> Notation (Dur, a)Source
Calculates the offset for each note.
reverseNotation :: Notation a -> Notation aSource
Reverses a Notation (Must be finite!).
takeNotation :: Ratio Int -> Notation a -> Notation aSource
Takes the beginning of Notation, result has the given duration if possible or is shorter otherwise. Notes that overlap with the end of duration are not taken but replaced by the (fitted) rests.
dropNotation :: Ratio Int -> Notation a -> Notation aSource
Drops the beginning of Notation. Notes that would be split are replaced by fitted rests.
filterNotation :: (Musical (m a), Monad m) => (a -> Bool) -> m a -> m aSource
Replaces notes where the predicate fails with rests. filterNotation :: (a -> Bool) -> Notation a -> Notation a
filterNotation' :: (Musical (m a), Musical (m b), Monad m) => (a -> Maybe b) -> m a -> m bSource
sequenceNotation :: (a -> b -> c) -> Dur -> [a] -> Notation b -> Notation cSource
A parallel composition of a sequence of values and a Notation Each value of the sequence has the same given duration. Every Note is updated by a function that gets the actual value of the sequence. NOTE: This function is not tested yet!
Produced by Haddock version 2.4.2