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

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

Music.Score.Ties

Contents

Description

Provides a representation for tied notes, and a class to split a single note into a pair of tied notes.

Synopsis

Tiable class

class Tiable a whereSource

Class of types that can be tied. Ties are added to a score by splitting a single note into two and annotating them with a begin tie and end tie mark respectively.

Minimal definition: toTied, or both beginTie and endTie.

Methods

beginTie :: a -> aSource

Modify a note to be the first note in a tied note pair.

endTie :: a -> aSource

Modify a note to be the second note in a tied note pair.

toTied :: a -> (a, a)Source

Split a single note into a pair of tied notes.

The first returned element should have the original onset and the second element should have the original offset. Formally

 (onset . fst . toTied) a = onset a
 (offset . snd . toTied) a = offset a

Instances

Tiable Char 
Tiable Double 
Tiable Float 
Tiable Int 
Tiable Integer 
Tiable () 
Tiable DynamicNotation 
Tiable ArticulationNotation 
Tiable a => Tiable [a] 
Tiable (Ratio a) 
Tiable a => Tiable (Maybe a) 
Tiable a => Tiable (Sum a) 
Tiable a => Tiable (Product a) 
Tiable a => Tiable (Score a) 
Tiable a => Tiable (Behavior a) 
Tiable a => Tiable (TieT a) 
Tiable a => Tiable (SlideT a) 
Tiable a => Tiable (TremoloT a) 
Tiable a => Tiable (TextT a) 
Tiable a => Tiable (HarmonicT a) 
Tiable a => Tiable (ColorT a) 
Tiable a => Tiable (c, a) 
Tiable a => Tiable (PartT n a) 
(Tiable n, Tiable a) => Tiable (DynamicT n a) 
(Tiable n, Tiable a) => Tiable (ArticulationT n a) 

newtype TieT a Source

Constructors

TieT 

Fields

getTieT :: ((Any, Any), a)
 

Instances

Monad TieT 
Functor TieT 
Typeable1 TieT 
Applicative TieT 
Foldable TieT 
Comonad TieT 
HasBackendNote NoteList a => HasBackendNote NoteList (TieT a) 
HasBackendNote Midi a => HasBackendNote Midi (TieT a) 
HasBackendNote SuperCollider a => HasBackendNote SuperCollider (TieT a) 
HasBackendNote Lilypond a => HasBackendNote Lilypond (TieT a) 
HasBackendNote MusicXml a => HasBackendNote MusicXml (TieT a) 
Bounded a => Bounded (TieT a) 
Enum a => Enum (TieT a) 
Eq a => Eq (TieT a) 
Floating a => Floating (TieT a) 
Fractional a => Fractional (TieT a) 
(Real a, Enum a, Integral a) => Integral (TieT a) 
Num a => Num (TieT a) 
Ord a => Ord (TieT a) 
(Num a, Ord a, Real a) => Real (TieT a) 
Show a => Show (TieT a) 
Semigroup a => Semigroup (TieT a) 
Wrapped (TieT a)

Unsafe: Do not use Wrapped instances

IsDynamics a => IsDynamics (TieT a) 
IsPitch a => IsPitch (TieT a) 
Augmentable a => Augmentable (TieT a) 
Alterable a => Alterable (TieT a) 
Transformable a => Transformable (TieT a) 
Reversible a => Reversible (TieT a) 
Tiable a => Tiable (TieT a) 
HasSlide a => HasSlide (TieT a) 
HasTremolo a => HasTremolo (TieT a) 
HasText a => HasText (TieT a) 
HasHarmonic a => HasHarmonic (TieT a) 
HasColor a => HasColor (TieT a) 
Rewrapped (TieT a) (TieT b) 
HasPitches a b => HasPitches (TieT a) (TieT b) 
HasPitch a b => HasPitch (TieT a) (TieT b) 
HasDynamics a b => HasDynamics (TieT a) (TieT b) 
HasDynamic a b => HasDynamic (TieT a) (TieT b) 
HasArticulations a b => HasArticulations (TieT a) (TieT b) 
HasArticulation a b => HasArticulation (TieT a) (TieT b) 

Splitting tied notes in scores

splitTiesVoiceAt :: Tiable a => [Duration] -> Voice a -> [Voice a]Source

Split all voice into bars, using the given bar durations. Music that does not fit into the given durations is discarded.

Notes that cross a barlines are split into tied notes.