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

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

Music.Score.Part

Contents

Description

Provides functions for manipulating parts.

Synopsis

Articulation type functions

type family Part s :: *Source

Parts type.

type family SetPart b s :: *Source

Part type.

Accessing parts

class (Transformable (Part s), Transformable (Part t)) => HasParts s t whereSource

Class of types that provide a part traversal.

Methods

parts :: Traversal s t (Part s) (Part t)Source

Part type.

Instances

(~ * b (Part b), Transformable b) => HasParts Bool b 
HasParts Float Float 
HasParts Int Int 
HasParts Integer Integer 
(~ * b (Part b), Transformable b) => HasParts Ordering b 
(~ * b (Part b), Transformable b) => HasParts () b 
HasParts a b => HasParts [a] [b] 
HasParts a b => HasParts (Maybe a) (Maybe b) 
HasParts a b => HasParts (Voice a) (Voice b) 
HasParts a b => HasParts (Note a) (Note b) 
HasParts a b => HasParts (Score a) (Score b) 
(HasPart a a, HasPart a b) => HasParts (Behavior a) (Behavior b) 
(HasPart a a, HasPart a b) => HasParts (Segment a) (Segment b) 
HasParts a b => HasParts (Either c a) (Either c b) 
HasParts a b => HasParts (c, a) (c, b) 
(Transformable p, Transformable p') => HasParts (PartT p a) (PartT p' a) 

class HasParts s t => HasPart s t whereSource

Class of types that provide a single part.

Methods

part :: Lens s t (Part s) (Part t)Source

Part type.

Instances

(~ * b (Part b), Transformable b) => HasPart Bool b 
HasPart Float Float 
HasPart Int Int 
HasPart Integer Integer 
(~ * b (Part b), Transformable b) => HasPart Ordering b 
(~ * b (Part b), Transformable b) => HasPart () b 
HasPart a b => HasPart (Note a) (Note b) 
(HasPart a a, HasPart a b) => HasPart (Behavior a) (Behavior b) 
(HasPart a a, HasPart a b) => HasPart (Segment a) (Segment b) 
HasPart a b => HasPart (c, a) (c, b) 
(Transformable p, Transformable p') => HasPart (PartT p a) (PartT p' a) 

type HasPart' a = HasPart a aSource

part' :: (HasPart s t, s ~ t) => Lens' s (Part s)Source

Part type.

parts' :: (HasParts s t, s ~ t) => Traversal' s (Part s)Source

Part type.

Listing parts

allParts :: (Ord (Part a), HasParts' a) => a -> [Part a]Source

List all the parts

Extracting parts

extracted :: (Ord (Part a), HasPart' a) => Iso (Score a) (Score b) [Score a] [Score b]Source

extracted' :: (Ord (Part a), Ord (Part b), HasPart' a, HasPart' b) => Iso (Score a) (Score b) [(Part a, Score a)] [(Part b, Score b)]Source

extractPart :: (Eq (Part a), HasPart' a) => Part a -> Score a -> Score aSource

List all the parts

extractParts :: (Ord (Part a), HasPart' a) => Score a -> [Score a]Source

List all the parts

extractParts' :: (Ord (Part a), HasPart' a) => Score a -> [(Part a, Score a)]Source

Manipulating parts

Part representation

newtype PartT n a Source

Constructors

PartT 

Fields

getPartT :: (n, a)
 

Instances

Typeable2 PartT 
HasBackendNote NoteList a => HasBackendNote NoteList (PartT n a) 
HasBackendNote Midi a => HasBackendNote Midi (PartT n a) 
HasBackendNote SuperCollider a => HasBackendNote SuperCollider (PartT n a) 
HasBackendNote Lilypond a => HasBackendNote Lilypond (PartT n a) 
HasBackendNote MusicXml a => HasBackendNote MusicXml (PartT n a) 
Monoid n => Monad (PartT n) 
Functor (PartT n) 
Monoid n => Applicative (PartT n) 
Comonad (PartT n) 
(Enum v, Bounded a) => Bounded (PartT v a) 
(Enum v, Enum a) => Enum (PartT v a) 
(Eq n, Eq a) => Eq (PartT n a) 
(Enum v, Ord v, Real a, Enum a, Integral a) => Integral (PartT v a) 
(Enum v, Eq v, Num a) => Num (PartT v a) 
(Ord n, Ord a) => Ord (PartT n a) 
(Enum v, Ord v, Num a, Ord a, Real a) => Real (PartT v a) 
(Show n, Show a) => Show (PartT n a) 
Semigroup a => Semigroup (PartT n a) 
Wrapped (PartT p a)

Unsafe: Do not use Wrapped instances

(IsDynamics a, Enum n) => IsDynamics (PartT n a) 
(IsPitch a, Enum n) => IsPitch (PartT n a) 
Augmentable a => Augmentable (PartT n a) 
Alterable a => Alterable (PartT n a) 
Transformable a => Transformable (PartT n a) 
Reversible a => Reversible (PartT p a) 
Tiable a => Tiable (PartT n a) 
HasSlide a => HasSlide (PartT n a) 
HasTremolo a => HasTremolo (PartT n a) 
HasText a => HasText (PartT n a) 
HasHarmonic a => HasHarmonic (PartT n a) 
HasColor a => HasColor (PartT n a) 
Rewrapped (PartT p a) (PartT p' b) 
(Transformable p, Transformable p') => HasParts (PartT p a) (PartT p' a) 
(Transformable p, Transformable p') => HasPart (PartT p a) (PartT p' a) 
HasPitches a b => HasPitches (PartT p a) (PartT p b) 
HasPitch a b => HasPitch (PartT p a) (PartT p b) 
HasDynamics a b => HasDynamics (PartT p a) (PartT p b) 
HasDynamic a b => HasDynamic (PartT p a) (PartT p b) 
HasArticulations a b => HasArticulations (PartT p a) (PartT p b) 
HasArticulation a b => HasArticulation (PartT p a) (PartT p b)