music-score-1.6: Musical score and part representation.

Portabilitynon-portable (TF,GNTD)
Stabilityexperimental
Maintainerhans@hanshoglund.se
Safe HaskellNone

Music.Score.Pitch

Contents

Description

Provides functions for manipulating pitch.

Synopsis

Accessors

pitch' :: HasPitch' a => Lens' a (Pitch a)Source

A lens to the pitch in a note, score or other structure.

pitch :: HasPitch a b => Lens a b (Pitch a) (Pitch b)Source

A lens to the pitch in a note, score or other structure.

Transformations

Transformations

inv :: Transposable a => Pitch a -> a -> aSource

Invert pitches.

Transformations

up :: Transposable a => Interval a -> a -> aSource

Transpose up.

down :: Transposable a => Interval a -> a -> aSource

Transpose down.

fifthsUp :: Transposable a => Scalar (Interval a) -> a -> aSource

Add the given interval below.

fifthsDown :: Transposable a => Scalar (Interval a) -> a -> aSource

Add the given interval below.

octavesUp :: Transposable a => Scalar (Interval a) -> a -> aSource

Transpose up by the given number of octaves.

octavesDown :: Transposable a => Scalar (Interval a) -> a -> aSource

Transpose down by the given number of octaves.

Transformations

fifthsAbove :: (Semigroup a, Transposable a) => Scalar (Interval a) -> a -> aSource

Add the given interval below.

fifthsBelow :: (Semigroup a, Transposable a) => Scalar (Interval a) -> a -> aSource

Add the given interval below.

octavesAbove :: (Semigroup a, Transposable a) => Scalar (Interval a) -> a -> aSource

Add the given interval below.

octavesBelow :: (Semigroup a, Transposable a) => Scalar (Interval a) -> a -> aSource

Add the given interval below.

Pitch representation

type family Pitch a Source

class SetPitch (Pitch t) s ~ t => HasSetPitch s t whereSource

Class of types with mutable pitch.

Either setPitch or mapPitch can be implemented. If both are implemented, the following laws should be satisfied:

 setPitch x = mapPitch (const x)
 mapPitch f x = setPitch p x where p = f (__getPitch x)

For types that are Functors, the following instance can be used

 type instance Pitch (T a) = Pitch a
 instance HasSetPitch a b => HasSetPitch (T a) (T b) where
     type SetPitch g (T a) = T (SetPitch g a)
     mapPitch = fmap . mapPitch

Associated Types

type SetPitch b s :: *Source

Methods

__setPitch :: Pitch t -> s -> tSource

__mapPitch :: (Pitch s -> Pitch t) -> s -> tSource