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

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

Music.Score.Pitch

Description

Provides pitch manipulation.

Synopsis

Documentation

class HasPitch a whereSource

Associated Types

type Pitch a :: *Source

Associated pitch type. Should implement Eq and Show to be usable.

Methods

getPitch :: a -> Pitch aSource

Get the pitch of the given note.

setPitch :: Pitch a -> a -> aSource

Set the pitch of the given note.

modifyPitch :: (Pitch a -> Pitch a) -> a -> aSource

Modify the pitch of the given note.

newtype PitchT p a Source

Constructors

PitchT 

Fields

getPitchT :: (p, a)
 

Instances

Functor (PitchT p) 
(Eq p, Eq a) => Eq (PitchT p a) 
(Ord p, Ord a) => Ord (PitchT p a) 
(Show p, Show a) => Show (PitchT p a) 
HasPitch (PitchT p a) 

getPitches :: (HasPitch a, Eq v, v ~ Pitch a, Foldable s, p ~ Pitch a) => s a -> [p]Source

Get all pitches in the given score. Returns a list of pitches.

 Score a -> [Pitch]

setPitches :: (HasPitch a, Functor s, p ~ Pitch a) => p -> s a -> s aSource

Set all pitches in the given score.

 Pitch -> Score a -> Score a

modifyPitches :: (HasPitch a, Functor s, p ~ Pitch a) => (p -> p) -> s a -> s aSource

Modify all pitches in the given score.

 (Pitch -> Pitch) -> Score a -> Score a

up :: (HasPitch a, Functor s, AffineSpace p, p ~ Pitch a) => Diff p -> s a -> s aSource

down :: (HasPitch a, Functor s, AffineSpace p, p ~ Pitch a) => Diff p -> s a -> s aSource