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.Time.Voice

Contents

Description

 

Synopsis

Voice type

data Voice a Source

A Voice is a sequential composition of values. Events may not overlap.

Instances

Alternative Voice 
Monad Voice 
Functor Voice 
MonadPlus Voice 
Applicative Voice 
Foldable Voice 
Traversable Voice 
(HasPart' a, HasMidiProgram (Part a)) => HasBackendScore Midi (Voice a) 
HasBackendScore SuperCollider (Voice (Maybe a)) 
Enum a => Enum (Voice a) 
Eq a => Eq (Voice a) 
Num a => Num (Voice a) 
(Show a, Transformable a) => Show (Voice a) 
IsString a => IsString (Voice a) 
Monoid (Voice a) 
Semigroup (Voice a) 
Wrapped (Voice a) 
VectorSpace (Voice a) 
IsDynamics a => IsDynamics (Voice a) 
IsPitch a => IsPitch (Voice a) 
IsInterval a => IsInterval (Voice a) 
AdditiveGroup (Voice a) 
Transformable (Voice a) 
HasDuration (Voice a) 
Splittable a => Splittable (Voice a) 
Reversible a => Reversible (Voice a) 
HasSlide a => HasSlide (Voice a) 
HasText a => HasText (Voice a) 
Rewrapped (Voice a) (Voice b) 
HasParts a b => HasParts (Voice a) (Voice b) 
HasPitches a b => HasPitches (Voice a) (Voice b) 
HasDynamics a b => HasDynamics (Voice a) (Voice b) 
HasArticulations a b => HasArticulations (Voice a) (Voice b) 
HasPhrases (PVoice a) (PVoice b) a b 
HasPhrases (MVoice a) (MVoice b) a b

Traverses all phrases in a voice.

Cons (Voice a) (Voice b) (Stretched a) (Stretched b) 
Snoc (Voice a) (Voice b) (Stretched a) (Stretched b) 
Typeable (* -> *) Voice 
type SetPart g (Voice a) = Voice (SetPart g a) 
type SetPitch b (Voice a) = Voice (SetPitch b a) 
type SetDynamic b (Voice a) = Voice (SetDynamic b a) 
type SetArticulation b (Voice a) = Voice (SetArticulation b a) 
type BackendScoreEvent Midi (Voice a) = a 
type BackendScoreEvent SuperCollider (Voice (Maybe a)) = a 
type Unwrapped (Voice a) 
type Scalar (Voice a) = Duration 
type Part (Voice a) = Part a 
type Pitch (Voice a) = Pitch a 
type Dynamic (Voice a) = Dynamic a 
type Articulation (Voice a) = Articulation a 

Construction

voice :: Getter [Stretched a] (Voice a) Source

Create a Voice from a list of Stretched values.

This is a Getter (rather than a function) for consistency:

[ (0 <-> 1, 10)^.stretched,
  (1 <-> 2, 20)^.stretched,
  (3 <-> 4, 30)^.stretched ]^.voice
view voice $ map (view stretched) [(0 <-> 1, 1)]

Se also stretcheds.

Extracting values

stretcheds :: Lens (Voice a) (Voice b) [Stretched a] [Stretched b] Source

View a Voice as a list of Stretched values.

view stretcheds                        :: Voice a -> [Stretched a]
set  stretcheds                        :: [Stretched a] -> Voice a -> Voice a
over stretcheds                        :: ([Stretched a] -> [Stretched b]) -> Voice a -> Voice b
preview  (stretcheds . each)           :: Voice a -> Maybe (Stretched a)
preview  (stretcheds . element 1)      :: Voice a -> Maybe (Stretched a)
preview  (stretcheds . elements odd)   :: Voice a -> Maybe (Stretched a)
set      (stretcheds . each)           :: Stretched a -> Voice a -> Voice a
set      (stretcheds . element 1)      :: Stretched a -> Voice a -> Voice a
set      (stretcheds . elements odd)   :: Stretched a -> Voice a -> Voice a
over     (stretcheds . each)           :: (Stretched a -> Stretched b) -> Voice a -> Voice b
over     (stretcheds . element 1)      :: (Stretched a -> Stretched a) -> Voice a -> Voice a
over     (stretcheds . elements odd)   :: (Stretched a -> Stretched a) -> Voice a -> Voice a
toListOf (stretcheds . each)                :: Voice a -> [Stretched a]
toListOf (stretcheds . elements odd)        :: Voice a -> [Stretched a]
toListOf (stretcheds . each . filtered
             (\x -> _duration x < 2))  :: Voice a -> [Stretched a]

This is not an Iso, as the note list representation does not contain meta-data. To construct a score from a note list, use score or flip (set stretcheds) empty.

eventsV :: Lens (Voice a) (Voice b) [(Duration, a)] [(Duration, b)] Source

singleStretched :: Prism' (Voice a) (Stretched a) Source

Deprecated: Use 'unsafeStretcheds . single'

Fusion

fuse :: Eq a => Voice a -> Voice a Source

Merge consecutive equal notes.

fuseBy :: (a -> a -> Bool) -> Voice a -> Voice a Source

Merge consecutive equal notes using the given function.

Fuse rests

fuseRests :: Voice (Maybe a) -> Voice (Maybe a) Source

Fuse all rests in the given voice. The resulting voice will have no consecutive rests.

coverRests :: Voice (Maybe a) -> Maybe (Voice a) Source

Remove all rests in the given voice by prolonging the previous note. Returns Nothing if and only if the given voice contains rests only.

Traversal

Separating rhythms and values

valuesV :: Lens (Voice a) (Voice b) [a] [b] Source

withValues :: ([a] -> [b]) -> Voice a -> Voice b Source

Transform the values, leaving durations intact.

withDurations :: ([Duration] -> [Duration]) -> Voice a -> Voice a Source

Transform the durations, leaving values intact.

rotateValues :: Int -> Voice a -> Voice a Source

Rotate values by the given number of steps, leaving durations intact.

rotateDurations :: Int -> Voice a -> Voice a Source

Rotate durations by the given number of steps, leaving values intact.

reverseValues :: Voice a -> Voice a Source

Reverse values, leaving durations intact.

reverseDurations :: Voice a -> Voice a Source

Reverse durations, leaving values intact.

Zips

unzipVoice :: Voice (a, b) -> (Voice a, Voice b) Source

Unzip the given voice. This is specialization of unzipR.

zipVoice :: Voice a -> Voice b -> Voice (a, b) Source

Join the given voices by multiplying durations and pairing values.

zipVoice3 :: Voice a -> Voice b -> Voice c -> Voice (a, (b, c)) Source

Join the given voices by multiplying durations and pairing values.

zipVoice4 :: Voice a -> Voice b -> Voice c -> Voice d -> Voice (a, (b, (c, d))) Source

Join the given voices by multiplying durations and pairing values.

zipVoiceNoScale :: Voice a -> Voice b -> Voice (a, b) Source

Join the given voices by pairing values and selecting the first duration.

zipVoiceNoScale3 :: Voice a -> Voice b -> Voice c -> Voice (a, (b, c)) Source

Join the given voices by pairing values and selecting the first duration.

zipVoiceNoScale4 :: Voice a -> Voice b -> Voice c -> Voice d -> Voice (a, (b, (c, d))) Source

Join the given voices by pairing values and selecting the first duration.

zipVoiceWith :: (a -> b -> c) -> Voice a -> Voice b -> Voice c Source

Join the given voices by multiplying durations and combining values using the given function.

zipVoiceWith' :: (Duration -> Duration -> Duration) -> (a -> b -> c) -> Voice a -> Voice b -> Voice c Source

Join the given voices by combining durations and values using the given function.

zipVoiceWithNoScale :: (a -> b -> c) -> Voice a -> Voice b -> Voice c Source

Join the given voices without combining durations.

Context

voiceLens :: (s -> a) -> (b -> s -> t) -> Lens (Voice s) (Voice t) (Voice a) (Voice b) Source

voiceAsList :: Iso (Voice a) (Voice b) [a] [b] Source

listAsVoice :: Iso [a] [b] (Voice a) (Voice b) Source

Unsafe versions