Aoide-0.1.0.2: A simple music library with the capability of generating .ly and .mid files.

Safe HaskellNone
LanguageHaskell2010

Composition.Notes

Description

This module contains some data structures for describing note sequences and time signatures, and a QuasiQuoter for note sequences.

Synopsis

Documentation

data Accidental Source #

Accidentals.

Constructors

Flat 
Natural 
Sharp 
Instances
Eq Accidental Source # 
Instance details

Defined in Composition.Notes

Show Accidental Source # 
Instance details

Defined in Composition.Notes

data Note Source #

Note. The first argument is the octave.

Constructors

Note Int Note_name 
Instances
Enum Note Source # 
Instance details

Defined in Composition.Notes

Methods

succ :: Note -> Note #

pred :: Note -> Note #

toEnum :: Int -> Note #

fromEnum :: Note -> Int #

enumFrom :: Note -> [Note] #

enumFromThen :: Note -> Note -> [Note] #

enumFromTo :: Note -> Note -> [Note] #

enumFromThenTo :: Note -> Note -> Note -> [Note] #

Eq Note Source # 
Instance details

Defined in Composition.Notes

Methods

(==) :: Note -> Note -> Bool #

(/=) :: Note -> Note -> Bool #

Ord Note Source # 
Instance details

Defined in Composition.Notes

Methods

compare :: Note -> Note -> Ordering #

(<) :: Note -> Note -> Bool #

(<=) :: Note -> Note -> Bool #

(>) :: Note -> Note -> Bool #

(>=) :: Note -> Note -> Bool #

max :: Note -> Note -> Note #

min :: Note -> Note -> Note #

Show Note Source # 
Instance details

Defined in Composition.Notes

Methods

showsPrec :: Int -> Note -> ShowS #

show :: Note -> String #

showList :: [Note] -> ShowS #

Lift Note Source # 
Instance details

Defined in Composition.Notes

Methods

lift :: Note -> Q Exp #

data Note_name' Source #

An alternative representation of note names that is more convenient for algorithms.

Instances
Eq Note_name' Source # 
Instance details

Defined in Composition.Notes

Show Note_name' Source # 
Instance details

Defined in Composition.Notes

type Rat = Ratio Int Source #

Rationals with limited numerators and denominators for representing note lengths.

data Simultaneous Source #

A collection of notes of same length that sound simultaneously. Non-positive length will result in runtime errors when attempting to generate Lilypond and MIDI files.

Constructors

Simultaneous [Note] Rat 
Instances
Show Simultaneous Source # 
Instance details

Defined in Composition.Notes

Lift Simultaneous Source # 
Instance details

Defined in Composition.Notes

Methods

lift :: Simultaneous -> Q Exp #

data Time Source #

Time signature. The first argument describes the subdivisions of the bar. For example, 2 beats per bar is encoded as [2], 3 as [3], 4 as [2, 2], 6 as [2, 3], 9 as [3, 3]. The second argument is the inverse of the length of the beat. Note that non-positive numbers in either numerator or denominator will result in errors, and Lilypond does not accept denominators that are not a power of two.

Constructors

Time [Int] Int 
Instances
Show Time Source # 
Instance details

Defined in Composition.Notes

Methods

showsPrec :: Int -> Time -> ShowS #

show :: Time -> String #

showList :: [Time] -> ShowS #

data Time_and_position Source #

Time signature and the starting position of the first bar. For example, if the piece starts with a full bar, the initial position is 0. If the piece is in 34 and starts with a 14-note bar, the initial position is 1/2.

Constructors

Time_and_position Time Rat 

construct_note_name :: Note_name' -> Note_name Source #

Construct the note name from a natural note name and an accidental.

deconstruct_note_name :: Note_name -> Note_name' Source #

Deconstruct a note name into the natural note name and the accidental.

ly :: QuasiQuoter Source #

A QuasiQuoter for compile-time parsing of note sequences. The syntax is loosely based on Lilypond. Some example of use:

  • An empty note sequence: [ly||].
  • A single note: [ly|<C0>1|].
  • Two consecutive notes: [ly|<C0>1 <C0>1|].
  • A rest, a single note and two simultaneous notes: [ly|<>1 <C0>1 <C0 D0>1|].
  • All natural notes from C to B: [ly|<C0 D0 E0 F0 G0 A0 B0>1|].
  • Accidentals: [ly|<Cb0 C0 C#0>1|].
  • Different octaves: [ly|<C-1 C0 C1>1|].
  • Rests of length 1/3, 1/2, 2/3, 1, 3/2, 2 and 3: [ly|<>3 <>2 <>3~3 <>1 <>1. <>1~1 <>1~1~1|].

measure_length :: Time -> Rat Source #

The length of one measure.

sequential_length :: [Simultaneous] -> Rat Source #

The length of a note sequence.

simultaneous_length :: Simultaneous -> Rat Source #

The length of a collection of notes.

subdivision :: Time -> Time Source #

Discards the topmost division of the bar. For example, 1/1 is transformed into 1/2, 2/2 into 1/2, 3/4 into 1/4, 4/4 into 2/4, 6/8 into 3/8, 9/16 into 3/16.