Portability | non-portable (TF,GNTD) |
---|---|
Stability | experimental |
Maintainer | hans@hanshoglund.se |
Safe Haskell | None |
Music.Score.Pitch
Contents
Description
Provides functions for manipulating pitch.
- type family Pitch s :: *
- type family SetPitch b s :: *
- type Interval a = Diff (Pitch a)
- class (Transformable (Pitch s), Transformable (Pitch t), SetPitch (Pitch t) s ~ t) => HasPitches s t where
- class HasPitches s t => HasPitch s t where
- type HasPitches' a = HasPitches a a
- type HasPitch' a = HasPitch a a
- pitch' :: (HasPitch s t, s ~ t) => Lens' s (Pitch s)
- pitches' :: (HasPitches s t, s ~ t) => Traversal' s (Pitch s)
- fromPitch' :: (HasPitches' a, IsPitch a) => Pitch a -> a
- type Transposable a = (HasPitches a a, VectorSpace (Interval a), AffineSpace (Pitch a), IsInterval (Interval a), IsPitch (Pitch a), Num (Scalar (Interval a)))
- up :: Transposable a => Interval a -> a -> a
- down :: Transposable a => Interval a -> a -> a
- above :: (Semigroup a, Transposable a) => Interval a -> a -> a
- below :: (Semigroup a, Transposable a) => Interval a -> a -> a
- inv :: Transposable a => Pitch a -> a -> a
- invertPitches :: Transposable a => Pitch a -> a -> a
- octavesUp :: Transposable a => Scalar (Interval a) -> a -> a
- octavesDown :: Transposable a => Scalar (Interval a) -> a -> a
- octavesAbove :: (Semigroup a, Transposable a) => Scalar (Interval a) -> a -> a
- octavesBelow :: (Semigroup a, Transposable a) => Scalar (Interval a) -> a -> a
- fifthsUp :: Transposable a => Scalar (Interval a) -> a -> a
- fifthsDown :: Transposable a => Scalar (Interval a) -> a -> a
- fifthsAbove :: (Semigroup a, Transposable a) => Scalar (Interval a) -> a -> a
- fifthsBelow :: (Semigroup a, Transposable a) => Scalar (Interval a) -> a -> a
- _15va :: Transposable a => a -> a
- _8va :: Transposable a => a -> a
- _8vb :: Transposable a => a -> a
- _15vb :: Transposable a => a -> a
- highestPitch :: (HasPitches' a, Ord (Pitch a)) => a -> Pitch a
- lowestPitch :: (HasPitches' a, Ord (Pitch a)) => a -> Pitch a
- meanPitch :: (HasPitches' a, Fractional (Pitch a)) => a -> Pitch a
- augmentIntervals :: (HasPhrases' s a, Transposable a) => Interval a -> s -> s
Pitch type functions
type family Pitch s :: *Source
This type fuction is used to retrive the pitch type for a given concrete type.
For types representing pitch, it is generally Identity
, i.e
Pitch Integer ~ Integer Pitch Double ~ Double
and so on.
For containers, Pitch
provides a morphism:
Pitch
(c,a) ~Pitch
aPitch
[a] ~Pitch
aPitch
(Note
a) ~Pitch
aPitch
(Delayed
a) ~Pitch
aPitch
(Stretched
a) ~Pitch
aPitch
(Voice
a) ~Pitch
aPitch
(Chord
a) ~Pitch
aPitch
(Track
a) ~Pitch
aPitch
(Score
a) ~Pitch
a
type family SetPitch b s :: *Source
This type fuction is used to retrive the pitch type for a given concrete type.
For types representing pitch, it is generally Constant
, i.e
SetPitch a Double ~ a SetPitch a Integer ~ a
For containers, Pitch
provides a morphism:
SetPitch
b (c,a) ~ (c,SetPitch
b a)SetPitch
b [a] ~ [SetPitch
b a]SetPitch
g (Note
a) ~ Note (SetPitch
g a)SetPitch
g (Delayed
a) ~ Delayed (SetPitch
g a)SetPitch
g (Stretched
a) ~ Stretched (SetPitch
g a)SetPitch
g (Voice
a) ~Voice
(SetPitch
g a)SetPitch
g (Chord
a) ~Chord
(SetPitch
g a)SetPitch
g (Track
a) ~Track
(SetPitch
g a)SetPitch
g (Score
a) ~Score
(SetPitch
g a)
Accessing pitch
class (Transformable (Pitch s), Transformable (Pitch t), SetPitch (Pitch t) s ~ t) => HasPitches s t whereSource
Class of types that provide a pitch traversal.
Methods
Instances
class HasPitches s t => HasPitch s t whereSource
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:
view
pitch
:: HasPitch a a
over
pitch
:: HasPitch' a => a -> Pitch apitch
%~succ
:: HasPitch' a => a -> apitch
+~ 2 :: (HasPitch' a, Num (Pitch a)) => a -> apitch
.~ c :: (HasPitch' a, IsPitch a) => a -> a
Instances
Simple versions
type HasPitches' a = HasPitches a aSource
pitches' :: (HasPitches s t, s ~ t) => Traversal' s (Pitch s)Source
Pitch type.
Converting pitch to container
fromPitch' :: (HasPitches' a, IsPitch a) => Pitch a -> aSource
Manipulating pitch
type Transposable a = (HasPitches a a, VectorSpace (Interval a), AffineSpace (Pitch a), IsInterval (Interval a), IsPitch (Pitch a), Num (Scalar (Interval a)))Source
Class of types that can be transposed, inverted and so on.
up :: Transposable a => Interval a -> a -> aSource
Transpose up.
down :: Transposable a => Interval a -> a -> aSource
Transpose down.
above :: (Semigroup a, Transposable a) => Interval a -> a -> aSource
Add the given interval above.
below :: (Semigroup a, Transposable a) => Interval a -> a -> aSource
Add the given interval below.
inv :: Transposable a => Pitch a -> a -> aSource
Deprecated: Use invertPitches
invertPitches :: Transposable a => Pitch a -> a -> aSource
Invert pitches.
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.
octavesAbove :: (Semigroup a, Transposable a) => Scalar (Interval a) -> a -> aSource
Add the given octave above.
octavesBelow :: (Semigroup a, Transposable a) => Scalar (Interval a) -> a -> aSource
Add the given octave below.
fifthsUp :: Transposable a => Scalar (Interval a) -> a -> aSource
Transpose up by the given number of fifths.
fifthsDown :: Transposable a => Scalar (Interval a) -> a -> aSource
Transpose down by the given number of fifths.
fifthsAbove :: (Semigroup a, Transposable a) => Scalar (Interval a) -> a -> aSource
Add the given octave above.
fifthsBelow :: (Semigroup a, Transposable a) => Scalar (Interval a) -> a -> aSource
Add the given octave below.
Utility
_15va :: Transposable a => a -> aSource
Shorthand for
.
octavesUp
2
_8va :: Transposable a => a -> aSource
Shorthand for
.
octavesUp
1
_8vb :: Transposable a => a -> aSource
Shorthand for
.
octavesDown
1
_15vb :: Transposable a => a -> aSource
Shorthand for
.
octavesDown
2
Inspecting pitch
highestPitch :: (HasPitches' a, Ord (Pitch a)) => a -> Pitch aSource
Return the highest pitch in the given music.
lowestPitch :: (HasPitches' a, Ord (Pitch a)) => a -> Pitch aSource
Return the lowest pitch in the given music.
meanPitch :: (HasPitches' a, Fractional (Pitch a)) => a -> Pitch aSource
Return the mean pitch in the given music.
Intervals
augmentIntervals :: (HasPhrases' s a, Transposable a) => Interval a -> s -> sSource