ParentContentsIndex
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 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 Int
The duration (of a note, e. g).
absDur :: Dur -> Int
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 where
Methods
durFrom :: d -> Dur
durUpdate :: (Dur -> Dur) -> d -> d
Instances
IsDur Dur
IsDur Duration
newtype WithDur d a
Constructors
WithDur
unWithDur :: (d -> a)
Instances
(IsDur d) => Stretchable (WithDur d a)
(IsDur d, Arrangeable a) => Arrangeable (WithDur d a)
(IsDur d) => Musical (WithDur d MidiMusic)
(IsDur d) => Musical (WithDur d (Seq a))
Music Notation
data Notation a
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 a A note with given duration and a value of type a.
Rest Dur A 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.
Instances
Functor Notation
Stretchable (Notation a)
Arrangeable (Notation a)
Musical (Notation a)
Monad Notation
runNotation :: (Musical m) => Notation m -> m
A Notation can be interpreted if the contained type is an instance of class Musical.
runNotationWith :: (Musical m) => (a -> m) -> Notation a -> m
Musical class
class Stretchable a where
A type/structure that can be stretched.
Methods
stretch :: Dur -> a -> a
Instances
(IsDur d) => Stretchable (WithDur d a)
(Stretchable a) => Stretchable (s -> a)
Stretchable (Notation a)
Stretchable (Play a)
Stretchable (RM a)
class Arrangeable a where
Types/structures that can be composed in two ways, parallel and sequent.
Methods
parallel :: a -> a -> a
sequent :: a -> a -> a
Instances
(IsDur d, Arrangeable a) => Arrangeable (WithDur d a)
(Arrangeable a) => Arrangeable (s -> a)
Arrangeable (Notation a)
Arrangeable MidiMusic
Arrangeable (RM a)
Arrangeable (Seq a)
class (Stretchable a, Arrangeable a) => Musical a where
Instances of class Musical must be Stretchable, Arrangeable and they must implement the method rest.
Methods
rest :: a
Instances
(Musical a) => Musical (s -> a)
Musical (Notation a)
(IsDur d) => Musical (WithDur d MidiMusic)
Musical (RM a)
(IsDur d) => Musical (WithDur d (Seq a))
rest0 :: (Musical a) => a
(-=-) :: (Arrangeable a) => a -> a -> a
(->-) :: (Arrangeable a) => a -> a -> a
line :: (Musical a) => [a] -> a
A sequence of sounds
line' :: (Musical a) => [a] -> a
A sequence of sounds that will be stretched to length=1
chord :: (Musical a) => [a] -> a
proportional :: (Musical a) => (Int, Int) -> a -> a -> a
Composes the notations sequentially and stretches them proportionally.
Notation and Midi
writeMidiSyncNotation :: FilePath -> [Notation MidiNote] -> IO ()
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 MidiMusic
A Notation MidiNote can be interpreted using runNotationWith and midi.
midi' :: (IsDur d) => WithDur d MidiNote -> WithDur d MidiMusic
midiSyncFile :: Ticks -> [WithDur Dur MidiMusic] -> MidiFile
More Notation functions
note :: a -> Notation a
Creates a note with length 1. Is a synonym for Note (1%1)
mapNotation :: (a -> b) -> Notation a -> Notation b
Notation is instance of the class Functor.
joinNotation :: Notation (Notation a) -> Notation a
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 a
Replaces any Note that contains Nothing by a rest (with same duration).
durationNotation :: Notation a -> Ratio Int
Calculates the (relative) duration of a Notation (Must be finite!).
positionNotation :: Notation a -> Notation (Dur, a)
Calculates the offset for each note.
reverseNotation :: Notation a -> Notation a
Reverses a Notation (Must be finite!).
takeNotation :: Ratio Int -> Notation a -> Notation a
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 a
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 a
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 b
sequenceNotation :: (a -> b -> c) -> Dur -> [a] -> Notation b -> Notation c
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 HADDOCK_VERSION