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

Copyright(c) Hans Hoglund 2012-2014
LicenseBSD-style
Maintainerhans@hanshoglund.se
Stabilityexperimental
Portabilitynon-portable (TF,GNTD)
Safe HaskellNone
LanguageHaskell2010

Music.Score.Pitch

Contents

Description

Provides functions for manipulating pitch.

Synopsis

Pitch type

type family Pitch s :: * Source

This type fuction is used to access the pitch type for a given type.

Instances

type Pitch Bool = Bool 
type Pitch Char = Char 
type Pitch Double = Double 
type Pitch Float = Float 
type Pitch Int = Int 
type Pitch Integer = Integer 
type Pitch Ordering = Ordering 
type Pitch () = () 
type Pitch [a] = Pitch a 
type Pitch (Maybe a) = Pitch a 
type Pitch (Sum a) = Pitch a 
type Pitch (Stretched a) = Pitch a 
type Pitch (Voice a) = Pitch a 
type Pitch (Delayed a) = Pitch a 
type Pitch (Chord a) = Pitch a 
type Pitch (Track a) = Pitch a 
type Pitch (Note a) = Pitch a 
type Pitch (Score a) = Pitch a 
type Pitch (Behavior a) = Behavior a 
type Pitch (TieT a) = Pitch a 
type Pitch (SlideT a) = Pitch a 
type Pitch (TextT a) = Pitch a 
type Pitch (HarmonicT a) = Pitch a 
type Pitch (TremoloT a) = Pitch a 
type Pitch (ColorT a) = Pitch a 
type Pitch (Either c a) = Pitch a 
type Pitch (c, a) = Pitch a 
type Pitch (Couple c a) = Pitch a 
type Pitch (PartT p a) = Pitch a 
type Pitch (DynamicT p a) = Pitch a 
type Pitch (ArticulationT p a) = Pitch a 

type family SetPitch b s :: * Source

This type fuction is used to update the pitch type for a given type. The first argument is the new type.

Instances

type SetPitch a Double = a 
type SetPitch a Float = a 
type SetPitch a Integer = a 
type SetPitch a Int = a 
type SetPitch a Char = a 
type SetPitch a Ordering = a 
type SetPitch a Bool = a 
type SetPitch a () = a 
type SetPitch g (SlideT a) = SlideT (SetPitch g a) 
type SetPitch g (TieT a) = TieT (SetPitch g a) 
type SetPitch g (HarmonicT a) = HarmonicT (SetPitch g a) 
type SetPitch g (TextT a) = TextT (SetPitch g a) 
type SetPitch b (Behavior a) = b 
type SetPitch b (Sum a) = Sum (SetPitch b a) 
type SetPitch b (Score a) = Score (SetPitch b a) 
type SetPitch b (Track a) = Track (SetPitch b a) 
type SetPitch b (Chord a) = Chord (SetPitch b a) 
type SetPitch b (Voice a) = Voice (SetPitch b a) 
type SetPitch b (Stretched a) = Stretched (SetPitch b a) 
type SetPitch b (Delayed a) = Delayed (SetPitch b a) 
type SetPitch b (Note a) = Note (SetPitch b a) 
type SetPitch b (Maybe a) = Maybe (SetPitch b a) 
type SetPitch b [a] = [SetPitch b a] 
type SetPitch g (TremoloT a) = TremoloT (SetPitch g a) 
type SetPitch g (ColorT a) = ColorT (SetPitch g a) 
type SetPitch g (Couple c a) = Couple c (SetPitch g a) 
type SetPitch b (Either c a) = Either c (SetPitch b a) 
type SetPitch b (c, a) = (c, SetPitch b a) 
type SetPitch b (ArticulationT p a) = ArticulationT p (SetPitch b a) 
type SetPitch b (DynamicT p a) = DynamicT p (SetPitch b a) 
type SetPitch b (PartT p a) = PartT p (SetPitch b a) 

type Interval a = Diff (Pitch a) Source

Associated interval type.

HasPitch classes

class HasPitches s t => HasPitch s t where Source

Class of types that provide a single pitch.

Methods

pitch :: Lens s t (Pitch s) (Pitch t) Source

Access the pitch.

As this is a Traversal, you can use all combinators from the lens package, for example:

  pitch .~ c    :: (HasPitch' a, IsPitch a)      => a -> a
  pitch +~ 2    :: (HasPitch' a, Num (Pitch a))  => a -> a
  pitch %~ succ :: (HasPitch' a, Enum (Pitch a)) => a -> a
  view pitch    :: HasPitches' a                 => a -> Pitch a
  set  pitch    :: HasPitches a b                => Pitch b -> a -> b
  over pitch    :: HasPitches a b                => (Pitch a -> Pitch b) -> a -> b
  

Instances

(Transformable a, (~) * a (Pitch a)) => HasPitch Bool a 
(Transformable a, (~) * a (Pitch a)) => HasPitch Char a 
(Transformable a, (~) * a (Pitch a)) => HasPitch Double a 
(Transformable a, (~) * a (Pitch a)) => HasPitch Float a 
(Transformable a, (~) * a (Pitch a)) => HasPitch Int a 
(Transformable a, (~) * a (Pitch a)) => HasPitch Integer a 
(Transformable a, (~) * a (Pitch a)) => HasPitch Ordering a 
(Transformable a, (~) * a (Pitch a)) => HasPitch () a 
(Transformable a, Transformable b, (~) * b (Pitch b)) => HasPitch (Behavior a) b 
HasPitch a b => HasPitch (Stretched a) (Stretched b) 
HasPitch a b => HasPitch (Delayed a) (Delayed b) 
HasPitch a b => HasPitch (Note a) (Note b) 
HasPitch a b => HasPitch (TieT a) (TieT b) 
HasPitch a b => HasPitch (SlideT a) (SlideT b) 
HasPitch a b => HasPitch (TextT a) (TextT b) 
HasPitch a b => HasPitch (HarmonicT a) (HarmonicT b) 
HasPitch a b => HasPitch (TremoloT a) (TremoloT b) 
HasPitch a b => HasPitch (ColorT a) (ColorT b) 
HasPitch a b => HasPitch (c, a) (c, b) 
HasPitch a b => HasPitch (Couple c a) (Couple c b) 
HasPitch a b => HasPitch (PartT p a) (PartT p b) 
HasPitch a b => HasPitch (DynamicT p a) (DynamicT p b) 
HasPitch a b => HasPitch (ArticulationT p a) (ArticulationT p b) 

class (Transformable (Pitch s), Transformable (Pitch t), SetPitch (Pitch t) s ~ t) => HasPitches s t where Source

Class of types that provide zero or more pitches.

Methods

pitches :: Traversal s t (Pitch s) (Pitch t) Source

Access all pitches.

As this is a Traversal, you can use all combinators from the lens package, for example:

  toListOf pitches  :: HasPitches' a                  => a -> [Pitch a]
  allOf pitches     :: (HasPitches' a)                => (Pitch a -> Bool) -> a -> Bool
  maximumOf pitches :: (HasPitches' a, Ord (Pitch a)) => a -> Maybe (Pitch a)
  set  pitches      :: HasPitches a b                 => Pitch b -> a -> b
  over pitches      :: HasPitches a b                 => (Pitch a -> Pitch b) -> a -> b
  

Instances

(Transformable a, (~) * a (Pitch a)) => HasPitches Bool a 
(Transformable a, (~) * a (Pitch a)) => HasPitches Char a 
(Transformable a, (~) * a (Pitch a)) => HasPitches Double a 
(Transformable a, (~) * a (Pitch a)) => HasPitches Float a 
(Transformable a, (~) * a (Pitch a)) => HasPitches Int a 
(Transformable a, (~) * a (Pitch a)) => HasPitches Integer a 
(Transformable a, (~) * a (Pitch a)) => HasPitches Ordering a 
(Transformable a, (~) * a (Pitch a)) => HasPitches () a 
(Transformable a, Transformable b, (~) * b (Pitch b)) => HasPitches (Behavior a) b 
HasPitches a b => HasPitches [a] [b] 
HasPitches a b => HasPitches (Maybe a) (Maybe b) 
HasPitches a b => HasPitches (Sum a) (Sum b) 
HasPitches a b => HasPitches (Stretched a) (Stretched b) 
HasPitches a b => HasPitches (Voice a) (Voice b) 
HasPitches a b => HasPitches (Delayed a) (Delayed b) 
HasPitches a b => HasPitches (Chord a) (Chord b) 
HasPitches a b => HasPitches (Track a) (Track b) 
HasPitches a b => HasPitches (Note a) (Note b) 
HasPitches a b => HasPitches (Score a) (Score b) 
HasPitches a b => HasPitches (TieT a) (TieT b) 
HasPitches a b => HasPitches (SlideT a) (SlideT b) 
HasPitches a b => HasPitches (TextT a) (TextT b) 
HasPitches a b => HasPitches (HarmonicT a) (HarmonicT b) 
HasPitches a b => HasPitches (TremoloT a) (TremoloT b) 
HasPitches a b => HasPitches (ColorT a) (ColorT b) 
HasPitches a b => HasPitches (Either c a) (Either c b) 
HasPitches a b => HasPitches (c, a) (c, b) 
HasPitches a b => HasPitches (Couple c a) (Couple c b) 
HasPitches a b => HasPitches (PartT p a) (PartT p b) 
HasPitches a b => HasPitches (DynamicT p a) (DynamicT p b) 
HasPitches a b => HasPitches (ArticulationT p a) (ArticulationT p b) 

fromPitch' :: (HasPitches' a, IsPitch a) => Pitch a -> a Source

Inject a pitch into some larger type.

Simple versions

pitch' :: (HasPitch s t, s ~ t) => Lens' s (Pitch s) Source

Access the pitch.

Same as pitch, but without polymorphic update.

pitches' :: (HasPitches s t, s ~ t) => Traversal' s (Pitch s) Source

Access all pitches.

Same as pitches, but without polymorphic update.

Transposition

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

Transpose pitch upwards.

Not to be confused with matrix transposition.

>>> up m3 c
eb
>>> up _P5 [c,d,e :: Pitch]
[g,a,b]
>>> up _P5 [440 :: Hertz, 442, 810]
[g,a,b]

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

Transpose pitch downwards.

Not to be confused with matrix transposition.

>>> down m3 c
a
>>> down _P5 [c,d,e]
[f_,g_,a_]

above :: (Semigroup a, Transposable a) => Interval a -> a -> a Source

Add the given interval above.

>>> above _P8 [c]
[c,c']

below :: (Semigroup a, Transposable a) => Interval a -> a -> a Source

Add the given interval below.

>>> below _P8 [c]
[c,c_]

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

Transpose up by the given number of octaves.

>>> octavesUp 2 c
c''
>>> octavesUp 1 [c,d,e]
[c',d',e']
>>> octavesUp (-1) [c,d,e]
[c_,d_,e_]

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

Transpose down by the given number of octaves.

>>> octavesDown 2 c
c__
>>> octavesDown 1 [c,d,e]
[c_,d_,e_]
>>> octavesDown (-1) [c,d,e]
[c',d',e']

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

Add the given octave above.

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

Add the given octave below.

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

Transpose up by the given number of fifths.

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

Transpose down by the given number of fifths.

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

Add the given octave above.

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

Add the given octave below.

_15va :: Transposable a => a -> a Source

Shorthand for octavesUp 2.

_8va :: Transposable a => a -> a Source

Shorthand for octavesUp 1.

_8vb :: Transposable a => a -> a Source

Shorthand for octavesDown 1.

_15vb :: Transposable a => a -> a Source

Shorthand for octavesDown 2.

Inversion

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

Deprecated: Use invertPitches

invertPitches :: Transposable a => Pitch a -> a -> a Source

Invert pitches.

Folds

highest :: (HasPitches' a, Ord (Pitch a)) => a -> Maybe (Pitch a) Source

Return the highest pitch in the given music.

lowest :: (HasPitches' a, Ord (Pitch a)) => a -> Maybe (Pitch a) Source

Return the lowest pitch in the given music.

meanPitch :: (HasPitches' a, Fractional (Pitch a)) => a -> Pitch a Source

Return the mean pitch in the given music.

type PitchPair v w = (Num (Scalar v), IsInterval v, IsPitch w) Source

type Transposable a = (HasPitches' a, AffinePair (Interval a) (Pitch a), PitchPair (Interval a) (Pitch a)) Source

Class of types that can be transposed, inverted and so on.