fadno-xml-1.1.1: XML/XSD combinators/schemas/codegen

Safe HaskellNone
LanguageHaskell2010

Fadno.MusicXml.MusicXml20

Synopsis

Documentation

newtype ID Source #

xs:ID (simple)

Constructors

ID 

Fields

Instances

Eq ID Source # 

Methods

(==) :: ID -> ID -> Bool #

(/=) :: ID -> ID -> Bool #

Ord ID Source # 

Methods

compare :: ID -> ID -> Ordering #

(<) :: ID -> ID -> Bool #

(<=) :: ID -> ID -> Bool #

(>) :: ID -> ID -> Bool #

(>=) :: ID -> ID -> Bool #

max :: ID -> ID -> ID #

min :: ID -> ID -> ID #

Read ID Source # 
Show ID Source # 

Methods

showsPrec :: Int -> ID -> ShowS #

show :: ID -> String #

showList :: [ID] -> ShowS #

IsString ID Source # 

Methods

fromString :: String -> ID #

Generic ID Source # 

Associated Types

type Rep ID :: * -> * #

Methods

from :: ID -> Rep ID x #

to :: Rep ID x -> ID #

EmitXml ID Source # 

Methods

emitXml :: ID -> XmlRep Source #

type Rep ID Source # 
type Rep ID = D1 * (MetaData "ID" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "ID" PrefixI True) (S1 * (MetaSel (Just Symbol "iD") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NCName)))

newtype IDREF Source #

xs:IDREF (simple)

Constructors

IDREF 

Fields

Instances

Eq IDREF Source # 

Methods

(==) :: IDREF -> IDREF -> Bool #

(/=) :: IDREF -> IDREF -> Bool #

Ord IDREF Source # 

Methods

compare :: IDREF -> IDREF -> Ordering #

(<) :: IDREF -> IDREF -> Bool #

(<=) :: IDREF -> IDREF -> Bool #

(>) :: IDREF -> IDREF -> Bool #

(>=) :: IDREF -> IDREF -> Bool #

max :: IDREF -> IDREF -> IDREF #

min :: IDREF -> IDREF -> IDREF #

Read IDREF Source # 
Show IDREF Source # 

Methods

showsPrec :: Int -> IDREF -> ShowS #

show :: IDREF -> String #

showList :: [IDREF] -> ShowS #

IsString IDREF Source # 

Methods

fromString :: String -> IDREF #

Generic IDREF Source # 

Associated Types

type Rep IDREF :: * -> * #

Methods

from :: IDREF -> Rep IDREF x #

to :: Rep IDREF x -> IDREF #

EmitXml IDREF Source # 

Methods

emitXml :: IDREF -> XmlRep Source #

type Rep IDREF Source # 
type Rep IDREF = D1 * (MetaData "IDREF" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "IDREF" PrefixI True) (S1 * (MetaSel (Just Symbol "iDREF") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NCName)))

newtype NCName Source #

xs:NCName (simple)

Constructors

NCName 

Fields

Instances

Eq NCName Source # 

Methods

(==) :: NCName -> NCName -> Bool #

(/=) :: NCName -> NCName -> Bool #

Ord NCName Source # 
Read NCName Source # 
Show NCName Source # 
IsString NCName Source # 

Methods

fromString :: String -> NCName #

Generic NCName Source # 

Associated Types

type Rep NCName :: * -> * #

Methods

from :: NCName -> Rep NCName x #

to :: Rep NCName x -> NCName #

EmitXml NCName Source # 
type Rep NCName Source # 
type Rep NCName = D1 * (MetaData "NCName" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "NCName" PrefixI True) (S1 * (MetaSel (Just Symbol "nCName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Name)))

newtype NMTOKEN Source #

xs:NMTOKEN (simple)

Constructors

NMTOKEN 

Fields

Instances

newtype Name Source #

xs:Name (simple)

Constructors

Name 

Fields

Instances

Eq Name Source # 

Methods

(==) :: Name -> Name -> Bool #

(/=) :: Name -> Name -> Bool #

Ord Name Source # 

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

(>=) :: Name -> Name -> Bool #

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

Read Name Source # 
Show Name Source # 

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

IsString Name Source # 

Methods

fromString :: String -> Name #

Generic Name Source # 

Associated Types

type Rep Name :: * -> * #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

EmitXml Name Source # 

Methods

emitXml :: Name -> XmlRep Source #

type Rep Name Source # 
type Rep Name = D1 * (MetaData "Name" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "Name" PrefixI True) (S1 * (MetaSel (Just Symbol "name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Token)))

data AboveBelow Source #

above-below (simple)

The above-below type is used to indicate whether one element appears above or below another element.

Constructors

AboveBelowAbove

above

AboveBelowBelow

below

Instances

Bounded AboveBelow Source # 
Enum AboveBelow Source # 
Eq AboveBelow Source # 
Ord AboveBelow Source # 
Show AboveBelow Source # 
Generic AboveBelow Source # 

Associated Types

type Rep AboveBelow :: * -> * #

EmitXml AboveBelow Source # 
type Rep AboveBelow Source # 
type Rep AboveBelow = D1 * (MetaData "AboveBelow" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "AboveBelowAbove" PrefixI False) (U1 *)) (C1 * (MetaCons "AboveBelowBelow" PrefixI False) (U1 *)))

data AccidentalValue Source #

accidental-value (simple)

The accidental-value type represents notated accidentals supported by MusicXML. In the MusicXML 2.0 DTD this was a string with values that could be included. The XSD strengthens the data typing to an enumerated list.

Instances

Bounded AccidentalValue Source # 
Enum AccidentalValue Source # 
Eq AccidentalValue Source # 
Ord AccidentalValue Source # 
Show AccidentalValue Source # 
Generic AccidentalValue Source # 
EmitXml AccidentalValue Source # 
type Rep AccidentalValue Source # 
type Rep AccidentalValue = D1 * (MetaData "AccidentalValue" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "AccidentalValueSharp" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "AccidentalValueNatural" PrefixI False) (U1 *)) (C1 * (MetaCons "AccidentalValueFlat" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "AccidentalValueDoubleSharp" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "AccidentalValueSharpSharp" PrefixI False) (U1 *)) (C1 * (MetaCons "AccidentalValueFlatFlat" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "AccidentalValueNaturalSharp" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "AccidentalValueNaturalFlat" PrefixI False) (U1 *)) (C1 * (MetaCons "AccidentalValueQuarterFlat" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "AccidentalValueQuarterSharp" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "AccidentalValueThreeQuartersFlat" PrefixI False) (U1 *)) (C1 * (MetaCons "AccidentalValueThreeQuartersSharp" PrefixI False) (U1 *))))))

newtype AccordionMiddle Source #

accordion-middle (simple)

The accordion-middle type may have values of 1, 2, or 3, corresponding to having 1 to 3 dots in the middle section of the accordion registration symbol.

Instances

Bounded AccordionMiddle Source # 
Enum AccordionMiddle Source # 
Eq AccordionMiddle Source # 
Integral AccordionMiddle Source # 
Num AccordionMiddle Source # 
Ord AccordionMiddle Source # 
Read AccordionMiddle Source # 
Real AccordionMiddle Source # 
Show AccordionMiddle Source # 
Generic AccordionMiddle Source # 
EmitXml AccordionMiddle Source # 
type Rep AccordionMiddle Source # 
type Rep AccordionMiddle = D1 * (MetaData "AccordionMiddle" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "AccordionMiddle" PrefixI True) (S1 * (MetaSel (Just Symbol "accordionMiddle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PositiveInteger)))

data Actuate Source #

xlink:actuate (simple)

Constructors

ActuateOnRequest

onRequest

ActuateOnLoad

onLoad

ActuateOther

other

ActuateNone

none

Instances

Bounded Actuate Source # 
Enum Actuate Source # 
Eq Actuate Source # 

Methods

(==) :: Actuate -> Actuate -> Bool #

(/=) :: Actuate -> Actuate -> Bool #

Ord Actuate Source # 
Show Actuate Source # 
Generic Actuate Source # 

Associated Types

type Rep Actuate :: * -> * #

Methods

from :: Actuate -> Rep Actuate x #

to :: Rep Actuate x -> Actuate #

EmitXml Actuate Source # 
type Rep Actuate Source # 
type Rep Actuate = D1 * (MetaData "Actuate" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * (C1 * (MetaCons "ActuateOnRequest" PrefixI False) (U1 *)) (C1 * (MetaCons "ActuateOnLoad" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "ActuateOther" PrefixI False) (U1 *)) (C1 * (MetaCons "ActuateNone" PrefixI False) (U1 *))))

data BackwardForward Source #

backward-forward (simple)

The backward-forward type is used to specify repeat directions. The start of the repeat has a forward direction while the end of the repeat has a backward direction.

Instances

Bounded BackwardForward Source # 
Enum BackwardForward Source # 
Eq BackwardForward Source # 
Ord BackwardForward Source # 
Show BackwardForward Source # 
Generic BackwardForward Source # 
EmitXml BackwardForward Source # 
type Rep BackwardForward Source # 
type Rep BackwardForward = D1 * (MetaData "BackwardForward" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "BackwardForwardBackward" PrefixI False) (U1 *)) (C1 * (MetaCons "BackwardForwardForward" PrefixI False) (U1 *)))

data BarStyle Source #

bar-style (simple)

The bar-style type represents barline style information. Choices are regular, dotted, dashed, heavy, light-light, light-heavy, heavy-light, heavy-heavy, tick (a short stroke through the top line), short (a partial barline between the 2nd and 4th lines), and none.

Instances

Bounded BarStyle Source # 
Enum BarStyle Source # 
Eq BarStyle Source # 
Ord BarStyle Source # 
Show BarStyle Source # 
Generic BarStyle Source # 

Associated Types

type Rep BarStyle :: * -> * #

Methods

from :: BarStyle -> Rep BarStyle x #

to :: Rep BarStyle x -> BarStyle #

EmitXml BarStyle Source # 
type Rep BarStyle Source # 
type Rep BarStyle = D1 * (MetaData "BarStyle" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "BarStyleRegular" PrefixI False) (U1 *)) (C1 * (MetaCons "BarStyleDotted" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "BarStyleDashed" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "BarStyleHeavy" PrefixI False) (U1 *)) (C1 * (MetaCons "BarStyleLightLight" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "BarStyleLightHeavy" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "BarStyleHeavyLight" PrefixI False) (U1 *)) (C1 * (MetaCons "BarStyleHeavyHeavy" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "BarStyleTick" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "BarStyleShort" PrefixI False) (U1 *)) (C1 * (MetaCons "BarStyleNone" PrefixI False) (U1 *))))))

newtype BeamLevel Source #

beam-level (simple)

The MusicXML format supports six levels of beaming, up to 256th notes. Unlike the number-level type, the beam-level type identifies concurrent beams in a beam group. It does not distinguish overlapping beams such as grace notes within regular notes, or beams used in different voices.

Constructors

BeamLevel 

Instances

Bounded BeamLevel Source # 
Enum BeamLevel Source # 
Eq BeamLevel Source # 
Integral BeamLevel Source # 
Num BeamLevel Source # 
Ord BeamLevel Source # 
Read BeamLevel Source # 
Real BeamLevel Source # 
Show BeamLevel Source # 
Generic BeamLevel Source # 

Associated Types

type Rep BeamLevel :: * -> * #

EmitXml BeamLevel Source # 
type Rep BeamLevel Source # 
type Rep BeamLevel = D1 * (MetaData "BeamLevel" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "BeamLevel" PrefixI True) (S1 * (MetaSel (Just Symbol "beamLevel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PositiveInteger)))

data BeamValue Source #

beam-value (simple)

The beam-value type represents the type of beam associated with each of 6 beam levels (up to 256th notes) available for each note.

Instances

Bounded BeamValue Source # 
Enum BeamValue Source # 
Eq BeamValue Source # 
Ord BeamValue Source # 
Show BeamValue Source # 
Generic BeamValue Source # 

Associated Types

type Rep BeamValue :: * -> * #

EmitXml BeamValue Source # 
type Rep BeamValue Source # 
type Rep BeamValue = D1 * (MetaData "BeamValue" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * (C1 * (MetaCons "BeamValueBegin" PrefixI False) (U1 *)) (C1 * (MetaCons "BeamValueContinue" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "BeamValueEnd" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "BeamValueForwardHook" PrefixI False) (U1 *)) (C1 * (MetaCons "BeamValueBackwardHook" PrefixI False) (U1 *)))))

data ClefSign Source #

clef-sign (simple)

The clef-sign element represents the different clef symbols.

Instances

Bounded ClefSign Source # 
Enum ClefSign Source # 
Eq ClefSign Source # 
Ord ClefSign Source # 
Show ClefSign Source # 
Generic ClefSign Source # 

Associated Types

type Rep ClefSign :: * -> * #

Methods

from :: ClefSign -> Rep ClefSign x #

to :: Rep ClefSign x -> ClefSign #

EmitXml ClefSign Source # 
type Rep ClefSign Source # 
type Rep ClefSign = D1 * (MetaData "ClefSign" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * (C1 * (MetaCons "ClefSignG" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ClefSignF" PrefixI False) (U1 *)) (C1 * (MetaCons "ClefSignC" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "ClefSignPercussion" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ClefSignTAB" PrefixI False) (U1 *)) (C1 * (MetaCons "ClefSignNone" PrefixI False) (U1 *)))))

newtype Color Source #

color (simple)

The color type indicates the color of an element. Color may be represented as hexadecimal RGB triples, as in HTML, or as hexadecimal ARGB tuples, with the A indicating alpha of transparency. An alpha value of 00 is totally transparent; FF is totally opaque. If RGB is used, the A value is assumed to be FF.

For instance, the RGB value "40800080" would be a transparent purple.

As in SVG 1.1, colors are defined in terms of the sRGB color space (IEC 61966).

Constructors

Color 

Fields

Instances

Eq Color Source # 

Methods

(==) :: Color -> Color -> Bool #

(/=) :: Color -> Color -> Bool #

Ord Color Source # 

Methods

compare :: Color -> Color -> Ordering #

(<) :: Color -> Color -> Bool #

(<=) :: Color -> Color -> Bool #

(>) :: Color -> Color -> Bool #

(>=) :: Color -> Color -> Bool #

max :: Color -> Color -> Color #

min :: Color -> Color -> Color #

Read Color Source # 
Show Color Source # 

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

IsString Color Source # 

Methods

fromString :: String -> Color #

Generic Color Source # 

Associated Types

type Rep Color :: * -> * #

Methods

from :: Color -> Rep Color x #

to :: Rep Color x -> Color #

EmitXml Color Source # 

Methods

emitXml :: Color -> XmlRep Source #

type Rep Color Source # 
type Rep Color = D1 * (MetaData "Color" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "Color" PrefixI True) (S1 * (MetaSel (Just Symbol "color") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Token)))

newtype CommaSeparatedText Source #

comma-separated-text (simple)

The comma-separated-text type is used to specify a comma-separated list of text elements, as is used by the font-family attribute.

Instances

Eq CommaSeparatedText Source # 
Ord CommaSeparatedText Source # 
Read CommaSeparatedText Source # 
Show CommaSeparatedText Source # 
IsString CommaSeparatedText Source # 
Generic CommaSeparatedText Source # 
EmitXml CommaSeparatedText Source # 
type Rep CommaSeparatedText Source # 
type Rep CommaSeparatedText = D1 * (MetaData "CommaSeparatedText" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "CommaSeparatedText" PrefixI True) (S1 * (MetaSel (Just Symbol "commaSeparatedText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Token)))

data CssFontSize Source #

css-font-size (simple)

The css-font-size type includes the CSS font sizes used as an alternative to a numeric point size.

Instances

Bounded CssFontSize Source # 
Enum CssFontSize Source # 
Eq CssFontSize Source # 
Ord CssFontSize Source # 
Show CssFontSize Source # 
Generic CssFontSize Source # 

Associated Types

type Rep CssFontSize :: * -> * #

EmitXml CssFontSize Source # 
type Rep CssFontSize Source # 
type Rep CssFontSize = D1 * (MetaData "CssFontSize" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * (C1 * (MetaCons "CssFontSizeXxSmall" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CssFontSizeXSmall" PrefixI False) (U1 *)) (C1 * (MetaCons "CssFontSizeSmall" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "CssFontSizeMedium" PrefixI False) (U1 *)) (C1 * (MetaCons "CssFontSizeLarge" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CssFontSizeXLarge" PrefixI False) (U1 *)) (C1 * (MetaCons "CssFontSizeXxLarge" PrefixI False) (U1 *)))))

data DegreeTypeValue Source #

degree-type-value (simple)

The degree-type-value type indicates whether the current degree element is an addition, alteration, or subtraction to the kind of the current chord in the harmony element.

Instances

Bounded DegreeTypeValue Source # 
Enum DegreeTypeValue Source # 
Eq DegreeTypeValue Source # 
Ord DegreeTypeValue Source # 
Show DegreeTypeValue Source # 
Generic DegreeTypeValue Source # 
EmitXml DegreeTypeValue Source # 
type Rep DegreeTypeValue Source # 
type Rep DegreeTypeValue = D1 * (MetaData "DegreeTypeValue" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "DegreeTypeValueAdd" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "DegreeTypeValueAlter" PrefixI False) (U1 *)) (C1 * (MetaCons "DegreeTypeValueSubtract" PrefixI False) (U1 *))))

newtype Divisions Source #

divisions (simple)

The divisions type is used to express values in terms of the musical divisions defined by the divisions element. It is preferred that these be integer values both for MIDI interoperability and to avoid roundoff errors.

Constructors

Divisions 

Fields

Instances

Eq Divisions Source # 
Fractional Divisions Source # 
Num Divisions Source # 
Ord Divisions Source # 
Read Divisions Source # 
Real Divisions Source # 
RealFrac Divisions Source # 
Show Divisions Source # 
Generic Divisions Source # 

Associated Types

type Rep Divisions :: * -> * #

EmitXml Divisions Source # 
type Rep Divisions Source # 
type Rep Divisions = D1 * (MetaData "Divisions" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "Divisions" PrefixI True) (S1 * (MetaSel (Just Symbol "divisions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Decimal)))

data Enclosure Source #

enclosure (simple)

The enclosure type describes the shape and presence / absence of an enclosure around text.

Instances

Bounded Enclosure Source # 
Enum Enclosure Source # 
Eq Enclosure Source # 
Ord Enclosure Source # 
Show Enclosure Source # 
Generic Enclosure Source # 

Associated Types

type Rep Enclosure :: * -> * #

EmitXml Enclosure Source # 
type Rep Enclosure Source # 
type Rep Enclosure = D1 * (MetaData "Enclosure" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "EnclosureRectangle" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "EnclosureOval" PrefixI False) (U1 *)) (C1 * (MetaCons "EnclosureNone" PrefixI False) (U1 *))))

newtype EndingNumber Source #

ending-number (simple)

The ending-number type is used to specify either a comma-separated list of positive integers without leading zeros, or a string of zero or more spaces. It is used for the number attribute of the ending element. The zero or more spaces version is used when software knows that an ending is present, but cannot determine the type of the ending.

Constructors

EndingNumber 

Fields

data Fan Source #

fan (simple)

The fan type represents the type of beam fanning present on a note, used to represent accelerandos and ritardandos.

Constructors

FanAccel

accel

FanRit

rit

FanNone

none

Instances

Bounded Fan Source # 

Methods

minBound :: Fan #

maxBound :: Fan #

Enum Fan Source # 

Methods

succ :: Fan -> Fan #

pred :: Fan -> Fan #

toEnum :: Int -> Fan #

fromEnum :: Fan -> Int #

enumFrom :: Fan -> [Fan] #

enumFromThen :: Fan -> Fan -> [Fan] #

enumFromTo :: Fan -> Fan -> [Fan] #

enumFromThenTo :: Fan -> Fan -> Fan -> [Fan] #

Eq Fan Source # 

Methods

(==) :: Fan -> Fan -> Bool #

(/=) :: Fan -> Fan -> Bool #

Ord Fan Source # 

Methods

compare :: Fan -> Fan -> Ordering #

(<) :: Fan -> Fan -> Bool #

(<=) :: Fan -> Fan -> Bool #

(>) :: Fan -> Fan -> Bool #

(>=) :: Fan -> Fan -> Bool #

max :: Fan -> Fan -> Fan #

min :: Fan -> Fan -> Fan #

Show Fan Source # 

Methods

showsPrec :: Int -> Fan -> ShowS #

show :: Fan -> String #

showList :: [Fan] -> ShowS #

Generic Fan Source # 

Associated Types

type Rep Fan :: * -> * #

Methods

from :: Fan -> Rep Fan x #

to :: Rep Fan x -> Fan #

EmitXml Fan Source # 

Methods

emitXml :: Fan -> XmlRep Source #

type Rep Fan Source # 
type Rep Fan = D1 * (MetaData "Fan" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "FanAccel" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "FanRit" PrefixI False) (U1 *)) (C1 * (MetaCons "FanNone" PrefixI False) (U1 *))))

data FermataShape Source #

fermata-shape (simple)

The fermata-shape type represents the shape of the fermata sign. The empty value is equivalent to the normal value.

Instances

Bounded FermataShape Source # 
Enum FermataShape Source # 
Eq FermataShape Source # 
Ord FermataShape Source # 
Show FermataShape Source # 
Generic FermataShape Source # 

Associated Types

type Rep FermataShape :: * -> * #

EmitXml FermataShape Source # 
type Rep FermataShape Source # 
type Rep FermataShape = D1 * (MetaData "FermataShape" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * (C1 * (MetaCons "FermataShapeNormal" PrefixI False) (U1 *)) (C1 * (MetaCons "FermataShapeAngled" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "FermataShapeSquare" PrefixI False) (U1 *)) (C1 * (MetaCons "FermataShape" PrefixI False) (U1 *))))

newtype Fifths Source #

fifths (simple)

The fifths type represents the number of flats or sharps in a traditional key signature. Negative numbers are used for flats and positive numbers for sharps, reflecting the key's placement within the circle of fifths (hence the type name).

Constructors

Fifths 

Fields

Instances

Bounded Fifths Source # 
Enum Fifths Source # 
Eq Fifths Source # 

Methods

(==) :: Fifths -> Fifths -> Bool #

(/=) :: Fifths -> Fifths -> Bool #

Integral Fifths Source # 
Num Fifths Source # 
Ord Fifths Source # 
Read Fifths Source # 
Real Fifths Source # 
Show Fifths Source # 
Generic Fifths Source # 

Associated Types

type Rep Fifths :: * -> * #

Methods

from :: Fifths -> Rep Fifths x #

to :: Rep Fifths x -> Fifths #

EmitXml Fifths Source # 
type Rep Fifths Source # 
type Rep Fifths = D1 * (MetaData "Fifths" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "Fifths" PrefixI True) (S1 * (MetaSel (Just Symbol "fifths") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))

data FontSize Source #

font-size (simple)

The font-size can be one of the CSS font sizes or a numeric point size.

Instances

Eq FontSize Source # 
Show FontSize Source # 
Generic FontSize Source # 

Associated Types

type Rep FontSize :: * -> * #

Methods

from :: FontSize -> Rep FontSize x #

to :: Rep FontSize x -> FontSize #

EmitXml FontSize Source # 
type Rep FontSize Source # 
type Rep FontSize = D1 * (MetaData "FontSize" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "FontSizeDecimal" PrefixI True) (S1 * (MetaSel (Just Symbol "fontSize1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Decimal))) (C1 * (MetaCons "FontSizeCssFontSize" PrefixI True) (S1 * (MetaSel (Just Symbol "fontSize2") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CssFontSize))))

data FontStyle Source #

font-style (simple)

The font-style type represents a simplified version of the CSS font-style property.

Constructors

FontStyleNormal

normal

FontStyleItalic

italic

Instances

Bounded FontStyle Source # 
Enum FontStyle Source # 
Eq FontStyle Source # 
Ord FontStyle Source # 
Show FontStyle Source # 
Generic FontStyle Source # 

Associated Types

type Rep FontStyle :: * -> * #

EmitXml FontStyle Source # 
type Rep FontStyle Source # 
type Rep FontStyle = D1 * (MetaData "FontStyle" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "FontStyleNormal" PrefixI False) (U1 *)) (C1 * (MetaCons "FontStyleItalic" PrefixI False) (U1 *)))

data FontWeight Source #

font-weight (simple)

The font-weight type represents a simplified version of the CSS font-weight property.

Constructors

FontWeightNormal

normal

FontWeightBold

bold

Instances

Bounded FontWeight Source # 
Enum FontWeight Source # 
Eq FontWeight Source # 
Ord FontWeight Source # 
Show FontWeight Source # 
Generic FontWeight Source # 

Associated Types

type Rep FontWeight :: * -> * #

EmitXml FontWeight Source # 
type Rep FontWeight Source # 
type Rep FontWeight = D1 * (MetaData "FontWeight" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "FontWeightNormal" PrefixI False) (U1 *)) (C1 * (MetaCons "FontWeightBold" PrefixI False) (U1 *)))

data GroupBarlineValue Source #

group-barline-value (simple)

The group-barline-value type indicates if the group should have common barlines.

Instances

Bounded GroupBarlineValue Source # 
Enum GroupBarlineValue Source # 
Eq GroupBarlineValue Source # 
Ord GroupBarlineValue Source # 
Show GroupBarlineValue Source # 
Generic GroupBarlineValue Source # 
EmitXml GroupBarlineValue Source # 
type Rep GroupBarlineValue Source # 
type Rep GroupBarlineValue = D1 * (MetaData "GroupBarlineValue" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "GroupBarlineValueYes" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "GroupBarlineValueNo" PrefixI False) (U1 *)) (C1 * (MetaCons "GroupBarlineValueMensurstrich" PrefixI False) (U1 *))))

data GroupSymbolValue Source #

group-symbol-value (simple)

The group-symbol-value type indicates how the symbol for a group is indicated in the score. The default value is none.

Instances

Bounded GroupSymbolValue Source # 
Enum GroupSymbolValue Source # 
Eq GroupSymbolValue Source # 
Ord GroupSymbolValue Source # 
Show GroupSymbolValue Source # 
Generic GroupSymbolValue Source # 
EmitXml GroupSymbolValue Source # 
type Rep GroupSymbolValue Source # 
type Rep GroupSymbolValue = D1 * (MetaData "GroupSymbolValue" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * (C1 * (MetaCons "GroupSymbolValueNone" PrefixI False) (U1 *)) (C1 * (MetaCons "GroupSymbolValueBrace" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "GroupSymbolValueLine" PrefixI False) (U1 *)) (C1 * (MetaCons "GroupSymbolValueBracket" PrefixI False) (U1 *))))

data HarmonyType Source #

harmony-type (simple)

The harmony-type type differentiates different types of harmonies when alternate harmonies are possible. Explicit harmonies have all note present in the music; implied have some notes missing but implied; alternate represents alternate analyses.

Instances

Bounded HarmonyType Source # 
Enum HarmonyType Source # 
Eq HarmonyType Source # 
Ord HarmonyType Source # 
Show HarmonyType Source # 
Generic HarmonyType Source # 

Associated Types

type Rep HarmonyType :: * -> * #

EmitXml HarmonyType Source # 
type Rep HarmonyType Source # 
type Rep HarmonyType = D1 * (MetaData "HarmonyType" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "HarmonyTypeExplicit" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "HarmonyTypeImplied" PrefixI False) (U1 *)) (C1 * (MetaCons "HarmonyTypeAlternate" PrefixI False) (U1 *))))

data KindValue Source #

kind-value (simple)

A kind-value indicates the type of chord. Degree elements can then add, subtract, or alter from these starting points. Values include:

	
Triads:
	major (major third, perfect fifth)
	minor (minor third, perfect fifth)
	augmented (major third, augmented fifth)
	diminished (minor third, diminished fifth)
Sevenths:
	dominant (major triad, minor seventh)
	major-seventh (major triad, major seventh)
	minor-seventh (minor triad, minor seventh)
	diminished-seventh (diminished triad, diminished seventh)
	augmented-seventh (augmented triad, minor seventh)
	half-diminished (diminished triad, minor seventh)
	major-minor (minor triad, major seventh)
Sixths:
	major-sixth (major triad, added sixth)
	minor-sixth (minor triad, added sixth)
Ninths:
	dominant-ninth (dominant-seventh, major ninth)
	major-ninth (major-seventh, major ninth)
	minor-ninth (minor-seventh, major ninth)
11ths (usually as the basis for alteration):
	dominant-11th (dominant-ninth, perfect 11th)
	major-11th (major-ninth, perfect 11th)
	minor-11th (minor-ninth, perfect 11th)
13ths (usually as the basis for alteration):
	dominant-13th (dominant-11th, major 13th)
	major-13th (major-11th, major 13th)
	minor-13th (minor-11th, major 13th)
Suspended:
	suspended-second (major second, perfect fifth)
	suspended-fourth (perfect fourth, perfect fifth)
Functional sixths:
	Neapolitan
	Italian
	French
	German
Other:
	pedal (pedal-point bass)
	power (perfect fifth)
	Tristan
	
The "other" kind is used when the harmony is entirely composed of add elements. The "none" kind is used to explicitly encode absence of chords or functional harmony.

Instances

Bounded KindValue Source # 
Enum KindValue Source # 
Eq KindValue Source # 
Ord KindValue Source # 
Show KindValue Source # 
Generic KindValue Source # 

Associated Types

type Rep KindValue :: * -> * #

EmitXml KindValue Source # 
type Rep KindValue Source # 
type Rep KindValue = D1 * (MetaData "KindValue" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "KindValueMajor" PrefixI False) (U1 *)) (C1 * (MetaCons "KindValueMinor" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "KindValueAugmented" PrefixI False) (U1 *)) (C1 * (MetaCons "KindValueDiminished" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "KindValueDominant" PrefixI False) (U1 *)) (C1 * (MetaCons "KindValueMajorSeventh" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "KindValueMinorSeventh" PrefixI False) (U1 *)) (C1 * (MetaCons "KindValueDiminishedSeventh" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "KindValueAugmentedSeventh" PrefixI False) (U1 *)) (C1 * (MetaCons "KindValueHalfDiminished" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "KindValueMajorMinor" PrefixI False) (U1 *)) (C1 * (MetaCons "KindValueMajorSixth" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "KindValueMinorSixth" PrefixI False) (U1 *)) (C1 * (MetaCons "KindValueDominantNinth" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "KindValueMajorNinth" PrefixI False) (U1 *)) (C1 * (MetaCons "KindValueMinorNinth" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "KindValueDominant11th" PrefixI False) (U1 *)) (C1 * (MetaCons "KindValueMajor11th" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "KindValueMinor11th" PrefixI False) (U1 *)) (C1 * (MetaCons "KindValueDominant13th" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "KindValueMajor13th" PrefixI False) (U1 *)) (C1 * (MetaCons "KindValueMinor13th" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "KindValueSuspendedSecond" PrefixI False) (U1 *)) (C1 * (MetaCons "KindValueSuspendedFourth" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "KindValueNeapolitan" PrefixI False) (U1 *)) (C1 * (MetaCons "KindValueItalian" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "KindValueFrench" PrefixI False) (U1 *)) (C1 * (MetaCons "KindValueGerman" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "KindValuePedal" PrefixI False) (U1 *)) (C1 * (MetaCons "KindValuePower" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "KindValueTristan" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "KindValueOther" PrefixI False) (U1 *)) (C1 * (MetaCons "KindValueNone" PrefixI False) (U1 *))))))))

data Lang Source #

xml:lang (simple)

Constructors

LangLanguage 

Fields

LangLang 

Fields

Instances

Eq Lang Source # 

Methods

(==) :: Lang -> Lang -> Bool #

(/=) :: Lang -> Lang -> Bool #

Show Lang Source # 

Methods

showsPrec :: Int -> Lang -> ShowS #

show :: Lang -> String #

showList :: [Lang] -> ShowS #

Generic Lang Source # 

Associated Types

type Rep Lang :: * -> * #

Methods

from :: Lang -> Rep Lang x #

to :: Rep Lang x -> Lang #

EmitXml Lang Source # 

Methods

emitXml :: Lang -> XmlRep Source #

type Rep Lang Source # 
type Rep Lang = D1 * (MetaData "Lang" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "LangLanguage" PrefixI True) (S1 * (MetaSel (Just Symbol "lang1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Language))) (C1 * (MetaCons "LangLang" PrefixI True) (S1 * (MetaSel (Just Symbol "lang2") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * SumLang))))

newtype Language Source #

xs:language (simple)

Constructors

Language 

Fields

data LeftCenterRight Source #

left-center-right (simple)

The left-center-right type is used to define horizontal alignment and text justification.

Instances

Bounded LeftCenterRight Source # 
Enum LeftCenterRight Source # 
Eq LeftCenterRight Source # 
Ord LeftCenterRight Source # 
Show LeftCenterRight Source # 
Generic LeftCenterRight Source # 
EmitXml LeftCenterRight Source # 
type Rep LeftCenterRight Source # 
type Rep LeftCenterRight = D1 * (MetaData "LeftCenterRight" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "LeftCenterRightLeft" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "LeftCenterRightCenter" PrefixI False) (U1 *)) (C1 * (MetaCons "LeftCenterRightRight" PrefixI False) (U1 *))))

data LeftRight Source #

left-right (simple)

The left-right type is used to indicate whether one element appears to the left or the right of another element.

Constructors

LeftRightLeft

left

LeftRightRight

right

Instances

Bounded LeftRight Source # 
Enum LeftRight Source # 
Eq LeftRight Source # 
Ord LeftRight Source # 
Show LeftRight Source # 
Generic LeftRight Source # 

Associated Types

type Rep LeftRight :: * -> * #

EmitXml LeftRight Source # 
type Rep LeftRight Source # 
type Rep LeftRight = D1 * (MetaData "LeftRight" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "LeftRightLeft" PrefixI False) (U1 *)) (C1 * (MetaCons "LeftRightRight" PrefixI False) (U1 *)))

data LineEnd Source #

line-end (simple)

The line-end type specifies if there is a jog up or down (or both), an arrow, or nothing at the start or end of a bracket.

Instances

Bounded LineEnd Source # 
Enum LineEnd Source # 
Eq LineEnd Source # 

Methods

(==) :: LineEnd -> LineEnd -> Bool #

(/=) :: LineEnd -> LineEnd -> Bool #

Ord LineEnd Source # 
Show LineEnd Source # 
Generic LineEnd Source # 

Associated Types

type Rep LineEnd :: * -> * #

Methods

from :: LineEnd -> Rep LineEnd x #

to :: Rep LineEnd x -> LineEnd #

EmitXml LineEnd Source # 
type Rep LineEnd Source # 
type Rep LineEnd = D1 * (MetaData "LineEnd" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * (C1 * (MetaCons "LineEndUp" PrefixI False) (U1 *)) (C1 * (MetaCons "LineEndDown" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "LineEndBoth" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "LineEndArrow" PrefixI False) (U1 *)) (C1 * (MetaCons "LineEndNone" PrefixI False) (U1 *)))))

data LineShape Source #

line-shape (simple)

The line-shape type distinguishes between straight and curved lines.

Constructors

LineShapeStraight

straight

LineShapeCurved

curved

Instances

Bounded LineShape Source # 
Enum LineShape Source # 
Eq LineShape Source # 
Ord LineShape Source # 
Show LineShape Source # 
Generic LineShape Source # 

Associated Types

type Rep LineShape :: * -> * #

EmitXml LineShape Source # 
type Rep LineShape Source # 
type Rep LineShape = D1 * (MetaData "LineShape" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "LineShapeStraight" PrefixI False) (U1 *)) (C1 * (MetaCons "LineShapeCurved" PrefixI False) (U1 *)))

data LineType Source #

line-type (simple)

The line-type type distinguishes between solid, dashed, dotted, and wavy lines.

Instances

Bounded LineType Source # 
Enum LineType Source # 
Eq LineType Source # 
Ord LineType Source # 
Show LineType Source # 
Generic LineType Source # 

Associated Types

type Rep LineType :: * -> * #

Methods

from :: LineType -> Rep LineType x #

to :: Rep LineType x -> LineType #

EmitXml LineType Source # 
type Rep LineType Source # 
type Rep LineType = D1 * (MetaData "LineType" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * (C1 * (MetaCons "LineTypeSolid" PrefixI False) (U1 *)) (C1 * (MetaCons "LineTypeDashed" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "LineTypeDotted" PrefixI False) (U1 *)) (C1 * (MetaCons "LineTypeWavy" PrefixI False) (U1 *))))

newtype LineWidthType Source #

line-width-type (simple)

The line-width-type defines what type of line is being defined in a line-width element. Values include beam, bracket, dashes, enclosure, ending, extend, heavy barline, leger, light barline, octave shift, pedal, slur middle, slur tip, staff, stem, tie middle, tie tip, tuplet bracket, and wedge. This is left as a string so that other application-specific types can be defined, but it is made a separate type so that it can be redefined more strictly.

Constructors

LineWidthType 

Fields

Instances

Eq LineWidthType Source # 
Ord LineWidthType Source # 
Read LineWidthType Source # 
Show LineWidthType Source # 
IsString LineWidthType Source # 
Generic LineWidthType Source # 

Associated Types

type Rep LineWidthType :: * -> * #

EmitXml LineWidthType Source # 
type Rep LineWidthType Source # 
type Rep LineWidthType = D1 * (MetaData "LineWidthType" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "LineWidthType" PrefixI True) (S1 * (MetaSel (Just Symbol "lineWidthType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Token)))

data MarginType Source #

margin-type (simple)

The margin-type type specifies whether margins apply to even page, odd pages, or both.

Instances

Bounded MarginType Source # 
Enum MarginType Source # 
Eq MarginType Source # 
Ord MarginType Source # 
Show MarginType Source # 
Generic MarginType Source # 

Associated Types

type Rep MarginType :: * -> * #

EmitXml MarginType Source # 
type Rep MarginType Source # 
type Rep MarginType = D1 * (MetaData "MarginType" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "MarginTypeOdd" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "MarginTypeEven" PrefixI False) (U1 *)) (C1 * (MetaCons "MarginTypeBoth" PrefixI False) (U1 *))))

data MeasureNumberingValue Source #

measure-numbering-value (simple)

The measure-numbering-value type describes how measure numbers are displayed on this part: no numbers, numbers every measure, or numbers every system.

Instances

Bounded MeasureNumberingValue Source # 
Enum MeasureNumberingValue Source # 
Eq MeasureNumberingValue Source # 
Ord MeasureNumberingValue Source # 
Show MeasureNumberingValue Source # 
Generic MeasureNumberingValue Source # 
EmitXml MeasureNumberingValue Source # 
type Rep MeasureNumberingValue Source # 
type Rep MeasureNumberingValue = D1 * (MetaData "MeasureNumberingValue" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "MeasureNumberingValueNone" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "MeasureNumberingValueMeasure" PrefixI False) (U1 *)) (C1 * (MetaCons "MeasureNumberingValueSystem" PrefixI False) (U1 *))))

newtype Midi128 Source #

midi-128 (simple)

The midi-16 type is used to express MIDI 1.0 values that range from 1 to 128.

Constructors

Midi128 

Instances

Bounded Midi128 Source # 
Enum Midi128 Source # 
Eq Midi128 Source # 

Methods

(==) :: Midi128 -> Midi128 -> Bool #

(/=) :: Midi128 -> Midi128 -> Bool #

Integral Midi128 Source # 
Num Midi128 Source # 
Ord Midi128 Source # 
Read Midi128 Source # 
Real Midi128 Source # 
Show Midi128 Source # 
Generic Midi128 Source # 

Associated Types

type Rep Midi128 :: * -> * #

Methods

from :: Midi128 -> Rep Midi128 x #

to :: Rep Midi128 x -> Midi128 #

EmitXml Midi128 Source # 
type Rep Midi128 Source # 
type Rep Midi128 = D1 * (MetaData "Midi128" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "Midi128" PrefixI True) (S1 * (MetaSel (Just Symbol "midi128") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PositiveInteger)))

newtype Midi16 Source #

midi-16 (simple)

The midi-16 type is used to express MIDI 1.0 values that range from 1 to 16.

Constructors

Midi16 

Instances

Bounded Midi16 Source # 
Enum Midi16 Source # 
Eq Midi16 Source # 

Methods

(==) :: Midi16 -> Midi16 -> Bool #

(/=) :: Midi16 -> Midi16 -> Bool #

Integral Midi16 Source # 
Num Midi16 Source # 
Ord Midi16 Source # 
Read Midi16 Source # 
Real Midi16 Source # 
Show Midi16 Source # 
Generic Midi16 Source # 

Associated Types

type Rep Midi16 :: * -> * #

Methods

from :: Midi16 -> Rep Midi16 x #

to :: Rep Midi16 x -> Midi16 #

EmitXml Midi16 Source # 
type Rep Midi16 Source # 
type Rep Midi16 = D1 * (MetaData "Midi16" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "Midi16" PrefixI True) (S1 * (MetaSel (Just Symbol "midi16") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PositiveInteger)))

newtype Midi16384 Source #

midi-16384 (simple)

The midi-16 type is used to express MIDI 1.0 values that range from 1 to 16,384.

Constructors

Midi16384 

Instances

Bounded Midi16384 Source # 
Enum Midi16384 Source # 
Eq Midi16384 Source # 
Integral Midi16384 Source # 
Num Midi16384 Source # 
Ord Midi16384 Source # 
Read Midi16384 Source # 
Real Midi16384 Source # 
Show Midi16384 Source # 
Generic Midi16384 Source # 

Associated Types

type Rep Midi16384 :: * -> * #

EmitXml Midi16384 Source # 
type Rep Midi16384 Source # 
type Rep Midi16384 = D1 * (MetaData "Midi16384" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "Midi16384" PrefixI True) (S1 * (MetaSel (Just Symbol "midi16384") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PositiveInteger)))

newtype Millimeters Source #

millimeters (simple)

The millimeters type is a number representing millimeters. This is used in the scaling element to provide a default scaling from tenths to physical units.

Constructors

Millimeters 

Fields

Instances

Eq Millimeters Source # 
Fractional Millimeters Source # 
Num Millimeters Source # 
Ord Millimeters Source # 
Read Millimeters Source # 
Real Millimeters Source # 
RealFrac Millimeters Source # 
Show Millimeters Source # 
Generic Millimeters Source # 

Associated Types

type Rep Millimeters :: * -> * #

EmitXml Millimeters Source # 
type Rep Millimeters Source # 
type Rep Millimeters = D1 * (MetaData "Millimeters" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "Millimeters" PrefixI True) (S1 * (MetaSel (Just Symbol "millimeters") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Decimal)))

newtype Mode Source #

mode (simple)

The mode type is used to specify major/minor and other mode distinctions. Valid mode values include major, minor, dorian, phrygian, lydian, mixolydian, aeolian, ionian, and locrian.

Constructors

Mode 

Fields

Instances

Eq Mode Source # 

Methods

(==) :: Mode -> Mode -> Bool #

(/=) :: Mode -> Mode -> Bool #

Ord Mode Source # 

Methods

compare :: Mode -> Mode -> Ordering #

(<) :: Mode -> Mode -> Bool #

(<=) :: Mode -> Mode -> Bool #

(>) :: Mode -> Mode -> Bool #

(>=) :: Mode -> Mode -> Bool #

max :: Mode -> Mode -> Mode #

min :: Mode -> Mode -> Mode #

Read Mode Source # 
Show Mode Source # 

Methods

showsPrec :: Int -> Mode -> ShowS #

show :: Mode -> String #

showList :: [Mode] -> ShowS #

IsString Mode Source # 

Methods

fromString :: String -> Mode #

Generic Mode Source # 

Associated Types

type Rep Mode :: * -> * #

Methods

from :: Mode -> Rep Mode x #

to :: Rep Mode x -> Mode #

EmitXml Mode Source # 

Methods

emitXml :: Mode -> XmlRep Source #

type Rep Mode Source # 
type Rep Mode = D1 * (MetaData "Mode" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "Mode" PrefixI True) (S1 * (MetaSel (Just Symbol "mode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)))

newtype NonNegativeDecimal Source #

non-negative-decimal (simple)

The non-negative-decimal type specifies a non-negative decimal value.

Instances

Eq NonNegativeDecimal Source # 
Fractional NonNegativeDecimal Source # 
Num NonNegativeDecimal Source # 
Ord NonNegativeDecimal Source # 
Read NonNegativeDecimal Source # 
Real NonNegativeDecimal Source # 
RealFrac NonNegativeDecimal Source # 
Show NonNegativeDecimal Source # 
Generic NonNegativeDecimal Source # 
EmitXml NonNegativeDecimal Source # 
type Rep NonNegativeDecimal Source # 
type Rep NonNegativeDecimal = D1 * (MetaData "NonNegativeDecimal" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "NonNegativeDecimal" PrefixI True) (S1 * (MetaSel (Just Symbol "nonNegativeDecimal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Decimal)))

newtype NonNegativeInteger Source #

xs:nonNegativeInteger (simple)

Constructors

NonNegativeInteger 

Instances

Bounded NonNegativeInteger Source # 
Enum NonNegativeInteger Source # 
Eq NonNegativeInteger Source # 
Integral NonNegativeInteger Source # 
Num NonNegativeInteger Source # 
Ord NonNegativeInteger Source # 
Read NonNegativeInteger Source # 
Real NonNegativeInteger Source # 
Show NonNegativeInteger Source # 
Generic NonNegativeInteger Source # 
EmitXml NonNegativeInteger Source # 
type Rep NonNegativeInteger Source # 
type Rep NonNegativeInteger = D1 * (MetaData "NonNegativeInteger" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "NonNegativeInteger" PrefixI True) (S1 * (MetaSel (Just Symbol "nonNegativeInteger") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))

newtype NormalizedString Source #

xs:normalizedString (simple)

Constructors

NormalizedString 

Instances

Eq NormalizedString Source # 
Ord NormalizedString Source # 
Read NormalizedString Source # 
Show NormalizedString Source # 
IsString NormalizedString Source # 
Generic NormalizedString Source # 
EmitXml NormalizedString Source # 
type Rep NormalizedString Source # 
type Rep NormalizedString = D1 * (MetaData "NormalizedString" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "NormalizedString" PrefixI True) (S1 * (MetaSel (Just Symbol "normalizedString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)))

data NoteSizeType Source #

note-size-type (simple)

The note-size-type type indicates the type of note being defined by a note-size element. The grace type is used for notes of cue size that that include a grace element. The cue type is used for all other notes with cue size, whether defined explicitly or implicitly via a cue element. The large type is used for notes of large size.

Instances

Bounded NoteSizeType Source # 
Enum NoteSizeType Source # 
Eq NoteSizeType Source # 
Ord NoteSizeType Source # 
Show NoteSizeType Source # 
Generic NoteSizeType Source # 

Associated Types

type Rep NoteSizeType :: * -> * #

EmitXml NoteSizeType Source # 
type Rep NoteSizeType Source # 
type Rep NoteSizeType = D1 * (MetaData "NoteSizeType" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "NoteSizeTypeCue" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "NoteSizeTypeGrace" PrefixI False) (U1 *)) (C1 * (MetaCons "NoteSizeTypeLarge" PrefixI False) (U1 *))))

data NoteTypeValue Source #

note-type-value (simple)

The note-type type is used for the MusicXML type element and represents the graphic note type, from 256th (shortest) to long (longest).

Instances

Bounded NoteTypeValue Source # 
Enum NoteTypeValue Source # 
Eq NoteTypeValue Source # 
Ord NoteTypeValue Source # 
Show NoteTypeValue Source # 
Generic NoteTypeValue Source # 

Associated Types

type Rep NoteTypeValue :: * -> * #

EmitXml NoteTypeValue Source # 
type Rep NoteTypeValue Source # 
type Rep NoteTypeValue = D1 * (MetaData "NoteTypeValue" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "NoteTypeValue256th" PrefixI False) (U1 *)) (C1 * (MetaCons "NoteTypeValue128th" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "NoteTypeValue64th" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "NoteTypeValue32nd" PrefixI False) (U1 *)) (C1 * (MetaCons "NoteTypeValue16th" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "NoteTypeValueEighth" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "NoteTypeValueQuarter" PrefixI False) (U1 *)) (C1 * (MetaCons "NoteTypeValueHalf" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "NoteTypeValueWhole" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "NoteTypeValueBreve" PrefixI False) (U1 *)) (C1 * (MetaCons "NoteTypeValueLong" PrefixI False) (U1 *))))))

data NoteheadValue Source #

notehead-value (simple)

The notehead type indicates shapes other than the open and closed ovals associated with note durations. The values do, re, mi, fa, so, la, and ti correspond to Aikin's 7-shape system.

The arrow shapes differ from triangle and inverted triangle by being centered on the stem. Slashed and back slashed notes include both the normal notehead and a slash. The triangle shape has the tip of the triangle pointing up; the inverted triangle shape has the tip of the triangle pointing down.

Instances

Bounded NoteheadValue Source # 
Enum NoteheadValue Source # 
Eq NoteheadValue Source # 
Ord NoteheadValue Source # 
Show NoteheadValue Source # 
Generic NoteheadValue Source # 

Associated Types

type Rep NoteheadValue :: * -> * #

EmitXml NoteheadValue Source # 
type Rep NoteheadValue Source # 
type Rep NoteheadValue = D1 * (MetaData "NoteheadValue" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "NoteheadValueSlash" PrefixI False) (U1 *)) (C1 * (MetaCons "NoteheadValueTriangle" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "NoteheadValueDiamond" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "NoteheadValueSquare" PrefixI False) (U1 *)) (C1 * (MetaCons "NoteheadValueCross" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "NoteheadValueX" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "NoteheadValueCircleX" PrefixI False) (U1 *)) (C1 * (MetaCons "NoteheadValueInvertedTriangle" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "NoteheadValueArrowDown" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "NoteheadValueArrowUp" PrefixI False) (U1 *)) (C1 * (MetaCons "NoteheadValueSlashed" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "NoteheadValueBackSlashed" PrefixI False) (U1 *)) (C1 * (MetaCons "NoteheadValueNormal" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "NoteheadValueCluster" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "NoteheadValueNone" PrefixI False) (U1 *)) (C1 * (MetaCons "NoteheadValueDo" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "NoteheadValueRe" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "NoteheadValueMi" PrefixI False) (U1 *)) (C1 * (MetaCons "NoteheadValueFa" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "NoteheadValueSo" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "NoteheadValueLa" PrefixI False) (U1 *)) (C1 * (MetaCons "NoteheadValueTi" PrefixI False) (U1 *)))))))

newtype NumberLevel Source #

number-level (simple)

Slurs, tuplets, and many other features can be concurrent and overlapping within a single musical part. The number-level type distinguishes up to six concurrent objects of the same type. A reading program should be prepared to handle cases where the number-levels stop in an arbitrary order. Different numbers are needed when the features overlap in MusicXML file order. When a number-level value is implied, the value is 1 by default.

Constructors

NumberLevel 

Instances

Bounded NumberLevel Source # 
Enum NumberLevel Source # 
Eq NumberLevel Source # 
Integral NumberLevel Source # 
Num NumberLevel Source # 
Ord NumberLevel Source # 
Read NumberLevel Source # 
Real NumberLevel Source # 
Show NumberLevel Source # 
Generic NumberLevel Source # 

Associated Types

type Rep NumberLevel :: * -> * #

EmitXml NumberLevel Source # 
type Rep NumberLevel Source # 
type Rep NumberLevel = D1 * (MetaData "NumberLevel" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "NumberLevel" PrefixI True) (S1 * (MetaSel (Just Symbol "numberLevel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PositiveInteger)))

newtype NumberOfLines Source #

number-of-lines (simple)

The number-of-lines type is used to specify the number of lines in text decoration attributes.

Instances

Bounded NumberOfLines Source # 
Enum NumberOfLines Source # 
Eq NumberOfLines Source # 
Integral NumberOfLines Source # 
Num NumberOfLines Source # 
Ord NumberOfLines Source # 
Read NumberOfLines Source # 
Real NumberOfLines Source # 
Show NumberOfLines Source # 
Generic NumberOfLines Source # 

Associated Types

type Rep NumberOfLines :: * -> * #

EmitXml NumberOfLines Source # 
type Rep NumberOfLines Source # 
type Rep NumberOfLines = D1 * (MetaData "NumberOfLines" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "NumberOfLines" PrefixI True) (S1 * (MetaSel (Just Symbol "numberOfLines") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NonNegativeInteger)))

data NumberOrNormal Source #

number-or-normal (simple)

The number-or-normal values can be either a decimal number or the string "normal". This is used by the line-height and letter-spacing attributes.

Instances

newtype Octave Source #

octave (simple)

Octaves are represented by the numbers 0 to 9, where 4 indicates the octave started by middle C.

Constructors

Octave 

Fields

Instances

Bounded Octave Source # 
Enum Octave Source # 
Eq Octave Source # 

Methods

(==) :: Octave -> Octave -> Bool #

(/=) :: Octave -> Octave -> Bool #

Integral Octave Source # 
Num Octave Source # 
Ord Octave Source # 
Read Octave Source # 
Real Octave Source # 
Show Octave Source # 
Generic Octave Source # 

Associated Types

type Rep Octave :: * -> * #

Methods

from :: Octave -> Rep Octave x #

to :: Rep Octave x -> Octave #

EmitXml Octave Source # 
type Rep Octave Source # 
type Rep Octave = D1 * (MetaData "Octave" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "Octave" PrefixI True) (S1 * (MetaSel (Just Symbol "octave") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))

data OverUnder Source #

over-under (simple)

The over-under type is used to indicate whether the tips of curved lines such as slurs and ties are overhand (tips down) or underhand (tips up).

Constructors

OverUnderOver

over

OverUnderUnder

under

Instances

Bounded OverUnder Source # 
Enum OverUnder Source # 
Eq OverUnder Source # 
Ord OverUnder Source # 
Show OverUnder Source # 
Generic OverUnder Source # 

Associated Types

type Rep OverUnder :: * -> * #

EmitXml OverUnder Source # 
type Rep OverUnder Source # 
type Rep OverUnder = D1 * (MetaData "OverUnder" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "OverUnderOver" PrefixI False) (U1 *)) (C1 * (MetaCons "OverUnderUnder" PrefixI False) (U1 *)))

newtype Percent Source #

percent (simple)

The percent type specifies a percentage from 0 to 100.

Constructors

Percent 

Fields

Instances

Eq Percent Source # 

Methods

(==) :: Percent -> Percent -> Bool #

(/=) :: Percent -> Percent -> Bool #

Fractional Percent Source # 
Num Percent Source # 
Ord Percent Source # 
Read Percent Source # 
Real Percent Source # 
RealFrac Percent Source # 

Methods

properFraction :: Integral b => Percent -> (b, Percent) #

truncate :: Integral b => Percent -> b #

round :: Integral b => Percent -> b #

ceiling :: Integral b => Percent -> b #

floor :: Integral b => Percent -> b #

Show Percent Source # 
Generic Percent Source # 

Associated Types

type Rep Percent :: * -> * #

Methods

from :: Percent -> Rep Percent x #

to :: Rep Percent x -> Percent #

EmitXml Percent Source # 
type Rep Percent Source # 
type Rep Percent = D1 * (MetaData "Percent" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "Percent" PrefixI True) (S1 * (MetaSel (Just Symbol "percent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Decimal)))

newtype PositiveDivisions Source #

positive-divisions (simple)

The positive-divisions type restricts divisions values to positive numbers.

Instances

Eq PositiveDivisions Source # 
Fractional PositiveDivisions Source # 
Num PositiveDivisions Source # 
Ord PositiveDivisions Source # 
Read PositiveDivisions Source # 
Real PositiveDivisions Source # 
RealFrac PositiveDivisions Source # 
Show PositiveDivisions Source # 
Generic PositiveDivisions Source # 
EmitXml PositiveDivisions Source # 
type Rep PositiveDivisions Source # 
type Rep PositiveDivisions = D1 * (MetaData "PositiveDivisions" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "PositiveDivisions" PrefixI True) (S1 * (MetaSel (Just Symbol "positiveDivisions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Divisions)))

data PositiveIntegerOrEmpty Source #

positive-integer-or-empty (simple)

The positive-integer-or-empty values can be either a positive integer or an empty string.

newtype PositiveInteger Source #

xs:positiveInteger (simple)

Instances

Bounded PositiveInteger Source # 
Enum PositiveInteger Source # 
Eq PositiveInteger Source # 
Integral PositiveInteger Source # 
Num PositiveInteger Source # 
Ord PositiveInteger Source # 
Read PositiveInteger Source # 
Real PositiveInteger Source # 
Show PositiveInteger Source # 
Generic PositiveInteger Source # 
EmitXml PositiveInteger Source # 
type Rep PositiveInteger Source # 
type Rep PositiveInteger = D1 * (MetaData "PositiveInteger" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "PositiveInteger" PrefixI True) (S1 * (MetaSel (Just Symbol "positiveInteger") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NonNegativeInteger)))

data RehearsalEnclosure Source #

rehearsal-enclosure (simple)

The rehearsal-enclosure type describes the shape and presence / absence of an enclosure around rehearsal text.

Instances

Bounded RehearsalEnclosure Source # 
Enum RehearsalEnclosure Source # 
Eq RehearsalEnclosure Source # 
Ord RehearsalEnclosure Source # 
Show RehearsalEnclosure Source # 
Generic RehearsalEnclosure Source # 
EmitXml RehearsalEnclosure Source # 
type Rep RehearsalEnclosure Source # 
type Rep RehearsalEnclosure = D1 * (MetaData "RehearsalEnclosure" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "RehearsalEnclosureSquare" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "RehearsalEnclosureCircle" PrefixI False) (U1 *)) (C1 * (MetaCons "RehearsalEnclosureNone" PrefixI False) (U1 *))))

data RightLeftMiddle Source #

right-left-middle (simple)

The right-left-middle type is used to specify barline location.

Instances

Bounded RightLeftMiddle Source # 
Enum RightLeftMiddle Source # 
Eq RightLeftMiddle Source # 
Ord RightLeftMiddle Source # 
Show RightLeftMiddle Source # 
Generic RightLeftMiddle Source # 
EmitXml RightLeftMiddle Source # 
type Rep RightLeftMiddle Source # 
type Rep RightLeftMiddle = D1 * (MetaData "RightLeftMiddle" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "RightLeftMiddleRight" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "RightLeftMiddleLeft" PrefixI False) (U1 *)) (C1 * (MetaCons "RightLeftMiddleMiddle" PrefixI False) (U1 *))))

newtype RotationDegrees Source #

rotation-degrees (simple)

The rotation-degrees type specifies rotation, pan, and elevation values in degrees. Values range from -180 to 180.

Constructors

RotationDegrees 

Instances

Eq RotationDegrees Source # 
Fractional RotationDegrees Source # 
Num RotationDegrees Source # 
Ord RotationDegrees Source # 
Read RotationDegrees Source # 
Real RotationDegrees Source # 
RealFrac RotationDegrees Source # 
Show RotationDegrees Source # 
Generic RotationDegrees Source # 
EmitXml RotationDegrees Source # 
type Rep RotationDegrees Source # 
type Rep RotationDegrees = D1 * (MetaData "RotationDegrees" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "RotationDegrees" PrefixI True) (S1 * (MetaSel (Just Symbol "rotationDegrees") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Decimal)))

newtype Semitones Source #

semitones (simple)

The semintones type is a number representing semitones, used for chromatic alteration. A value of -1 corresponds to a flat and a value of 1 to a sharp. Decimal values like 0.5 (quarter tone sharp) may be used for microtones.

Constructors

Semitones 

Fields

Instances

Eq Semitones Source # 
Fractional Semitones Source # 
Num Semitones Source # 
Ord Semitones Source # 
Read Semitones Source # 
Real Semitones Source # 
RealFrac Semitones Source # 
Show Semitones Source # 
Generic Semitones Source # 

Associated Types

type Rep Semitones :: * -> * #

EmitXml Semitones Source # 
type Rep Semitones Source # 
type Rep Semitones = D1 * (MetaData "Semitones" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "Semitones" PrefixI True) (S1 * (MetaSel (Just Symbol "semitones") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Decimal)))

data SmpShow Source #

xlink:show (simple)

Constructors

ShowNew

new

ShowReplace

replace

ShowEmbed

embed

ShowOther

other

ShowNone

none

Instances

Bounded SmpShow Source # 
Enum SmpShow Source # 
Eq SmpShow Source # 

Methods

(==) :: SmpShow -> SmpShow -> Bool #

(/=) :: SmpShow -> SmpShow -> Bool #

Ord SmpShow Source # 
Show SmpShow Source # 
Generic SmpShow Source # 

Associated Types

type Rep SmpShow :: * -> * #

Methods

from :: SmpShow -> Rep SmpShow x #

to :: Rep SmpShow x -> SmpShow #

EmitXml SmpShow Source # 
type Rep SmpShow Source # 
type Rep SmpShow = D1 * (MetaData "SmpShow" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * (C1 * (MetaCons "ShowNew" PrefixI False) (U1 *)) (C1 * (MetaCons "ShowReplace" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "ShowEmbed" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ShowOther" PrefixI False) (U1 *)) (C1 * (MetaCons "ShowNone" PrefixI False) (U1 *)))))

data ShowFrets Source #

show-frets (simple)

The show-frets type indicates whether to show tablature frets as numbers (0, 1, 2) or letters (a, b, c). The default choice is numbers.

Constructors

ShowFretsNumbers

numbers

ShowFretsLetters

letters

Instances

Bounded ShowFrets Source # 
Enum ShowFrets Source # 
Eq ShowFrets Source # 
Ord ShowFrets Source # 
Show ShowFrets Source # 
Generic ShowFrets Source # 

Associated Types

type Rep ShowFrets :: * -> * #

EmitXml ShowFrets Source # 
type Rep ShowFrets Source # 
type Rep ShowFrets = D1 * (MetaData "ShowFrets" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "ShowFretsNumbers" PrefixI False) (U1 *)) (C1 * (MetaCons "ShowFretsLetters" PrefixI False) (U1 *)))

data ShowTuplet Source #

show-tuplet (simple)

The show-tuplet type indicates whether to show a part of a tuplet relating to the tuplet-actual element, both the tuplet-actual and tuplet-normal elements, or neither.

Instances

Bounded ShowTuplet Source # 
Enum ShowTuplet Source # 
Eq ShowTuplet Source # 
Ord ShowTuplet Source # 
Show ShowTuplet Source # 
Generic ShowTuplet Source # 

Associated Types

type Rep ShowTuplet :: * -> * #

EmitXml ShowTuplet Source # 
type Rep ShowTuplet Source # 
type Rep ShowTuplet = D1 * (MetaData "ShowTuplet" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "ShowTupletActual" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ShowTupletBoth" PrefixI False) (U1 *)) (C1 * (MetaCons "ShowTupletNone" PrefixI False) (U1 *))))

newtype StaffLine Source #

staff-line (simple)

The staff-line type indicates the line on a given staff. Staff lines are numbered from bottom to top, with 1 being the bottom line on a staff. Staff line values can be used to specify positions outside the staff, such as a C clef positioned in the middle of a grand staff.

Constructors

StaffLine 

Fields

Instances

Bounded StaffLine Source # 
Enum StaffLine Source # 
Eq StaffLine Source # 
Integral StaffLine Source # 
Num StaffLine Source # 
Ord StaffLine Source # 
Read StaffLine Source # 
Real StaffLine Source # 
Show StaffLine Source # 
Generic StaffLine Source # 

Associated Types

type Rep StaffLine :: * -> * #

EmitXml StaffLine Source # 
type Rep StaffLine Source # 
type Rep StaffLine = D1 * (MetaData "StaffLine" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "StaffLine" PrefixI True) (S1 * (MetaSel (Just Symbol "staffLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))

newtype StaffNumber Source #

staff-number (simple)

The staff-number type indicates staff numbers within a multi-staff part. Staves are numbered from top to bottom, with 1 being the top staff on a part.

Constructors

StaffNumber 

Instances

Bounded StaffNumber Source # 
Enum StaffNumber Source # 
Eq StaffNumber Source # 
Integral StaffNumber Source # 
Num StaffNumber Source # 
Ord StaffNumber Source # 
Read StaffNumber Source # 
Real StaffNumber Source # 
Show StaffNumber Source # 
Generic StaffNumber Source # 

Associated Types

type Rep StaffNumber :: * -> * #

EmitXml StaffNumber Source # 
type Rep StaffNumber Source # 
type Rep StaffNumber = D1 * (MetaData "StaffNumber" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "StaffNumber" PrefixI True) (S1 * (MetaSel (Just Symbol "staffNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PositiveInteger)))

data StaffType Source #

staff-type (simple)

The staff-type value can be ossia, cue, editorial, regular, or alternate. An alternate staff indicates one that shares the same musical data as the prior staff, but displayed differently (e.g., treble and bass clef, standard notation and tab).

Instances

Bounded StaffType Source # 
Enum StaffType Source # 
Eq StaffType Source # 
Ord StaffType Source # 
Show StaffType Source # 
Generic StaffType Source # 

Associated Types

type Rep StaffType :: * -> * #

EmitXml StaffType Source # 
type Rep StaffType Source # 
type Rep StaffType = D1 * (MetaData "StaffType" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * (C1 * (MetaCons "StaffTypeOssia" PrefixI False) (U1 *)) (C1 * (MetaCons "StaffTypeCue" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "StaffTypeEditorial" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "StaffTypeRegular" PrefixI False) (U1 *)) (C1 * (MetaCons "StaffTypeAlternate" PrefixI False) (U1 *)))))

data StartNote Source #

start-note (simple)

The start-note type describes the starting note of trills and mordents for playback, relative to the current note.

Instances

Bounded StartNote Source # 
Enum StartNote Source # 
Eq StartNote Source # 
Ord StartNote Source # 
Show StartNote Source # 
Generic StartNote Source # 

Associated Types

type Rep StartNote :: * -> * #

EmitXml StartNote Source # 
type Rep StartNote Source # 
type Rep StartNote = D1 * (MetaData "StartNote" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "StartNoteUpper" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "StartNoteMain" PrefixI False) (U1 *)) (C1 * (MetaCons "StartNoteBelow" PrefixI False) (U1 *))))

data StartStop Source #

start-stop (simple)

The start-stop type is used for an attribute of musical elements that can either start or stop, such as tuplets, wedges, and lines.

Constructors

StartStopStart

start

StartStopStop

stop

Instances

Bounded StartStop Source # 
Enum StartStop Source # 
Eq StartStop Source # 
Ord StartStop Source # 
Show StartStop Source # 
Generic StartStop Source # 

Associated Types

type Rep StartStop :: * -> * #

EmitXml StartStop Source # 
type Rep StartStop Source # 
type Rep StartStop = D1 * (MetaData "StartStop" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "StartStopStart" PrefixI False) (U1 *)) (C1 * (MetaCons "StartStopStop" PrefixI False) (U1 *)))

data StartStopChange Source #

start-stop-change (simple)

The start-stop-change type is used to distinguish types of pedal directions.

Instances

Bounded StartStopChange Source # 
Enum StartStopChange Source # 
Eq StartStopChange Source # 
Ord StartStopChange Source # 
Show StartStopChange Source # 
Generic StartStopChange Source # 
EmitXml StartStopChange Source # 
type Rep StartStopChange Source # 
type Rep StartStopChange = D1 * (MetaData "StartStopChange" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "StartStopChangeStart" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "StartStopChangeStop" PrefixI False) (U1 *)) (C1 * (MetaCons "StartStopChangeChange" PrefixI False) (U1 *))))

data StartStopContinue Source #

start-stop-continue (simple)

The start-stop-continue type is used for an attribute of musical elements that can either start or stop, but also need to refer to an intermediate point in the symbol, as for complex slurs.

Instances

Bounded StartStopContinue Source # 
Enum StartStopContinue Source # 
Eq StartStopContinue Source # 
Ord StartStopContinue Source # 
Show StartStopContinue Source # 
Generic StartStopContinue Source # 
EmitXml StartStopContinue Source # 
type Rep StartStopContinue Source # 
type Rep StartStopContinue = D1 * (MetaData "StartStopContinue" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "StartStopContinueStart" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "StartStopContinueStop" PrefixI False) (U1 *)) (C1 * (MetaCons "StartStopContinueContinue" PrefixI False) (U1 *))))

data StartStopDiscontinue Source #

start-stop-discontinue (simple)

The start-stop-discontinue type is used to specify ending types. Typically, the start type is associated with the left barline of the first measure in an ending. The stop and discontinue types are associated with the right barline of the last measure in an ending. Stop is used when the ending mark concludes with a downward jog, as is typical for first endings. Discontinue is used when there is no downward jog, as is typical for second endings that do not conclude a piece.

Instances

Bounded StartStopDiscontinue Source # 
Enum StartStopDiscontinue Source # 
Eq StartStopDiscontinue Source # 
Ord StartStopDiscontinue Source # 
Show StartStopDiscontinue Source # 
Generic StartStopDiscontinue Source # 
EmitXml StartStopDiscontinue Source # 
type Rep StartStopDiscontinue Source # 
type Rep StartStopDiscontinue = D1 * (MetaData "StartStopDiscontinue" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "StartStopDiscontinueStart" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "StartStopDiscontinueStop" PrefixI False) (U1 *)) (C1 * (MetaCons "StartStopDiscontinueDiscontinue" PrefixI False) (U1 *))))

data StartStopSingle Source #

start-stop-single (simple)

The start-stop-single type is used for an attribute of musical elements that can be used for either multi-note or single-note musical elements, as for tremolos.

Instances

Bounded StartStopSingle Source # 
Enum StartStopSingle Source # 
Eq StartStopSingle Source # 
Ord StartStopSingle Source # 
Show StartStopSingle Source # 
Generic StartStopSingle Source # 
EmitXml StartStopSingle Source # 
type Rep StartStopSingle Source # 
type Rep StartStopSingle = D1 * (MetaData "StartStopSingle" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "StartStopSingleStart" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "StartStopSingleStop" PrefixI False) (U1 *)) (C1 * (MetaCons "StartStopSingleSingle" PrefixI False) (U1 *))))

data StemValue Source #

stem-value (simple)

The stem type represents the notated stem direction.

Instances

Bounded StemValue Source # 
Enum StemValue Source # 
Eq StemValue Source # 
Ord StemValue Source # 
Show StemValue Source # 
Generic StemValue Source # 

Associated Types

type Rep StemValue :: * -> * #

EmitXml StemValue Source # 
type Rep StemValue Source # 
type Rep StemValue = D1 * (MetaData "StemValue" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * (C1 * (MetaCons "StemValueDown" PrefixI False) (U1 *)) (C1 * (MetaCons "StemValueUp" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "StemValueDouble" PrefixI False) (U1 *)) (C1 * (MetaCons "StemValueNone" PrefixI False) (U1 *))))

data Step Source #

step (simple)

The step type represents a step of the diatonic scale, represented using the English letters A through G.

Instances

Bounded Step Source # 
Enum Step Source # 

Methods

succ :: Step -> Step #

pred :: Step -> Step #

toEnum :: Int -> Step #

fromEnum :: Step -> Int #

enumFrom :: Step -> [Step] #

enumFromThen :: Step -> Step -> [Step] #

enumFromTo :: Step -> Step -> [Step] #

enumFromThenTo :: Step -> Step -> Step -> [Step] #

Eq Step Source # 

Methods

(==) :: Step -> Step -> Bool #

(/=) :: Step -> Step -> Bool #

Ord Step Source # 

Methods

compare :: Step -> Step -> Ordering #

(<) :: Step -> Step -> Bool #

(<=) :: Step -> Step -> Bool #

(>) :: Step -> Step -> Bool #

(>=) :: Step -> Step -> Bool #

max :: Step -> Step -> Step #

min :: Step -> Step -> Step #

Show Step Source # 

Methods

showsPrec :: Int -> Step -> ShowS #

show :: Step -> String #

showList :: [Step] -> ShowS #

Generic Step Source # 

Associated Types

type Rep Step :: * -> * #

Methods

from :: Step -> Rep Step x #

to :: Rep Step x -> Step #

EmitXml Step Source # 

Methods

emitXml :: Step -> XmlRep Source #

type Rep Step Source # 
type Rep Step = D1 * (MetaData "Step" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * (C1 * (MetaCons "StepA" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "StepB" PrefixI False) (U1 *)) (C1 * (MetaCons "StepC" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "StepD" PrefixI False) (U1 *)) (C1 * (MetaCons "StepE" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "StepF" PrefixI False) (U1 *)) (C1 * (MetaCons "StepG" PrefixI False) (U1 *)))))

newtype StringNumber Source #

string-number (simple)

The string-number type indicates a string number. Strings are numbered from high to low, with 1 being the highest pitched string.

Constructors

StringNumber 

Instances

Bounded StringNumber Source # 
Enum StringNumber Source # 
Eq StringNumber Source # 
Integral StringNumber Source # 
Num StringNumber Source # 
Ord StringNumber Source # 
Read StringNumber Source # 
Real StringNumber Source # 
Show StringNumber Source # 
Generic StringNumber Source # 

Associated Types

type Rep StringNumber :: * -> * #

EmitXml StringNumber Source # 
type Rep StringNumber Source # 
type Rep StringNumber = D1 * (MetaData "StringNumber" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "StringNumber" PrefixI True) (S1 * (MetaSel (Just Symbol "stringNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PositiveInteger)))

data Syllabic Source #

syllabic (simple)

Lyric hyphenation is indicated by the syllabic type. The single, begin, end, and middle values represent single-syllable words, word-beginning syllables, word-ending syllables, and mid-word syllables, respectively.

Instances

Bounded Syllabic Source # 
Enum Syllabic Source # 
Eq Syllabic Source # 
Ord Syllabic Source # 
Show Syllabic Source # 
Generic Syllabic Source # 

Associated Types

type Rep Syllabic :: * -> * #

Methods

from :: Syllabic -> Rep Syllabic x #

to :: Rep Syllabic x -> Syllabic #

EmitXml Syllabic Source # 
type Rep Syllabic Source # 
type Rep Syllabic = D1 * (MetaData "Syllabic" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * (C1 * (MetaCons "SyllabicSingle" PrefixI False) (U1 *)) (C1 * (MetaCons "SyllabicBegin" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "SyllabicEnd" PrefixI False) (U1 *)) (C1 * (MetaCons "SyllabicMiddle" PrefixI False) (U1 *))))

data SymbolSize Source #

symbol-size (simple)

The symbol-size type is used to indicate full vs. cue-sized vs. oversized symbols. The large value for oversized symbols was added in version 1.1.

Instances

Bounded SymbolSize Source # 
Enum SymbolSize Source # 
Eq SymbolSize Source # 
Ord SymbolSize Source # 
Show SymbolSize Source # 
Generic SymbolSize Source # 

Associated Types

type Rep SymbolSize :: * -> * #

EmitXml SymbolSize Source # 
type Rep SymbolSize Source # 
type Rep SymbolSize = D1 * (MetaData "SymbolSize" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "SymbolSizeFull" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "SymbolSizeCue" PrefixI False) (U1 *)) (C1 * (MetaCons "SymbolSizeLarge" PrefixI False) (U1 *))))

newtype Tenths Source #

tenths (simple)

The tenths type is a number representing tenths of interline staff space (positive or negative). Both integer and decimal values are allowed, such as 5 for a half space and 2.5 for a quarter space. Interline space is measured from the middle of a staff line.

Distances in a MusicXML file are measured in tenths of staff space. Tenths are then scaled to millimeters within the scaling element, used in the defaults element at the start of a score. Individual staves can apply a scaling factor to adjust staff size. When a MusicXML element or attribute refers to tenths, it means the global tenths defined by the scaling element, not the local tenths as adjusted by the staff-size element.

Constructors

Tenths 

Fields

Instances

Eq Tenths Source # 

Methods

(==) :: Tenths -> Tenths -> Bool #

(/=) :: Tenths -> Tenths -> Bool #

Fractional Tenths Source # 
Num Tenths Source # 
Ord Tenths Source # 
Read Tenths Source # 
Real Tenths Source # 
RealFrac Tenths Source # 

Methods

properFraction :: Integral b => Tenths -> (b, Tenths) #

truncate :: Integral b => Tenths -> b #

round :: Integral b => Tenths -> b #

ceiling :: Integral b => Tenths -> b #

floor :: Integral b => Tenths -> b #

Show Tenths Source # 
Generic Tenths Source # 

Associated Types

type Rep Tenths :: * -> * #

Methods

from :: Tenths -> Rep Tenths x #

to :: Rep Tenths x -> Tenths #

EmitXml Tenths Source # 
type Rep Tenths Source # 
type Rep Tenths = D1 * (MetaData "Tenths" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "Tenths" PrefixI True) (S1 * (MetaSel (Just Symbol "tenths") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Decimal)))

data TextDirection Source #

text-direction (simple)

The text-direction type is used to adjust and override the Unicode bidirectional text algorithm, similar to the W3C Internationalization Tag Set recommendation. Values are ltr (left-to-right embed), rtl (right-to-left embed), lro (left-to-right bidi-override), and rlo (right-to-left bidi-override). The default value is ltr. This type is typically used by applications that store text in left-to-right visual order rather than logical order. Such applications can use the lro value to better communicate with other applications that more fully support bidirectional text.

Instances

Bounded TextDirection Source # 
Enum TextDirection Source # 
Eq TextDirection Source # 
Ord TextDirection Source # 
Show TextDirection Source # 
Generic TextDirection Source # 

Associated Types

type Rep TextDirection :: * -> * #

EmitXml TextDirection Source # 
type Rep TextDirection Source # 
type Rep TextDirection = D1 * (MetaData "TextDirection" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * (C1 * (MetaCons "TextDirectionLtr" PrefixI False) (U1 *)) (C1 * (MetaCons "TextDirectionRtl" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "TextDirectionLro" PrefixI False) (U1 *)) (C1 * (MetaCons "TextDirectionRlo" PrefixI False) (U1 *))))

data TimeSymbol Source #

time-symbol (simple)

The time-symbol type indicates how to display a time signature. The normal value is the usual fractional display, and is the implied symbol type if none is specified. Other options are the common and cut time symbols, as well as a single number with an implied denominator.

Instances

Bounded TimeSymbol Source # 
Enum TimeSymbol Source # 
Eq TimeSymbol Source # 
Ord TimeSymbol Source # 
Show TimeSymbol Source # 
Generic TimeSymbol Source # 

Associated Types

type Rep TimeSymbol :: * -> * #

EmitXml TimeSymbol Source # 
type Rep TimeSymbol Source # 
type Rep TimeSymbol = D1 * (MetaData "TimeSymbol" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * (C1 * (MetaCons "TimeSymbolCommon" PrefixI False) (U1 *)) (C1 * (MetaCons "TimeSymbolCut" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "TimeSymbolSingleNumber" PrefixI False) (U1 *)) (C1 * (MetaCons "TimeSymbolNormal" PrefixI False) (U1 *))))

newtype Token Source #

xs:token (simple)

Constructors

Token 

Instances

Eq Token Source # 

Methods

(==) :: Token -> Token -> Bool #

(/=) :: Token -> Token -> Bool #

Ord Token Source # 

Methods

compare :: Token -> Token -> Ordering #

(<) :: Token -> Token -> Bool #

(<=) :: Token -> Token -> Bool #

(>) :: Token -> Token -> Bool #

(>=) :: Token -> Token -> Bool #

max :: Token -> Token -> Token #

min :: Token -> Token -> Token #

Read Token Source # 
Show Token Source # 

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

IsString Token Source # 

Methods

fromString :: String -> Token #

Generic Token Source # 

Associated Types

type Rep Token :: * -> * #

Methods

from :: Token -> Rep Token x #

to :: Rep Token x -> Token #

EmitXml Token Source # 

Methods

emitXml :: Token -> XmlRep Source #

type Rep Token Source # 
type Rep Token = D1 * (MetaData "Token" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "Token" PrefixI True) (S1 * (MetaSel (Just Symbol "token") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NormalizedString)))

data TopBottom Source #

top-bottom (simple)

The top-bottom type is used to indicate the top or bottom part of a vertical shape like non-arpeggiate.

Constructors

TopBottomTop

top

TopBottomBottom

bottom

Instances

Bounded TopBottom Source # 
Enum TopBottom Source # 
Eq TopBottom Source # 
Ord TopBottom Source # 
Show TopBottom Source # 
Generic TopBottom Source # 

Associated Types

type Rep TopBottom :: * -> * #

EmitXml TopBottom Source # 
type Rep TopBottom Source # 
type Rep TopBottom = D1 * (MetaData "TopBottom" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "TopBottomTop" PrefixI False) (U1 *)) (C1 * (MetaCons "TopBottomBottom" PrefixI False) (U1 *)))

newtype TremoloMarks Source #

tremolo-marks (simple)

The number of tremolo marks is represented by a number from 0 to 6: the same as beam-level with 0 added.

Constructors

TremoloMarks 

Fields

Instances

Bounded TremoloMarks Source # 
Enum TremoloMarks Source # 
Eq TremoloMarks Source # 
Integral TremoloMarks Source # 
Num TremoloMarks Source # 
Ord TremoloMarks Source # 
Read TremoloMarks Source # 
Real TremoloMarks Source # 
Show TremoloMarks Source # 
Generic TremoloMarks Source # 

Associated Types

type Rep TremoloMarks :: * -> * #

EmitXml TremoloMarks Source # 
type Rep TremoloMarks Source # 
type Rep TremoloMarks = D1 * (MetaData "TremoloMarks" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "TremoloMarks" PrefixI True) (S1 * (MetaSel (Just Symbol "tremoloMarks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))

newtype TrillBeats Source #

trill-beats (simple)

The trill-beats type specifies the beats used in a trill-sound or bend-sound attribute group. It is a decimal value with a minimum value of 2.

Constructors

TrillBeats 

Fields

Instances

Eq TrillBeats Source # 
Fractional TrillBeats Source # 
Num TrillBeats Source # 
Ord TrillBeats Source # 
Read TrillBeats Source # 
Real TrillBeats Source # 
RealFrac TrillBeats Source # 
Show TrillBeats Source # 
Generic TrillBeats Source # 

Associated Types

type Rep TrillBeats :: * -> * #

EmitXml TrillBeats Source # 
type Rep TrillBeats Source # 
type Rep TrillBeats = D1 * (MetaData "TrillBeats" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" True) (C1 * (MetaCons "TrillBeats" PrefixI True) (S1 * (MetaSel (Just Symbol "trillBeats") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Decimal)))

data TrillStep Source #

trill-step (simple)

The trill-step type describes the alternating note of trills and mordents for playback, relative to the current note.

Instances

Bounded TrillStep Source # 
Enum TrillStep Source # 
Eq TrillStep Source # 
Ord TrillStep Source # 
Show TrillStep Source # 
Generic TrillStep Source # 

Associated Types

type Rep TrillStep :: * -> * #

EmitXml TrillStep Source # 
type Rep TrillStep Source # 
type Rep TrillStep = D1 * (MetaData "TrillStep" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "TrillStepWhole" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "TrillStepHalf" PrefixI False) (U1 *)) (C1 * (MetaCons "TrillStepUnison" PrefixI False) (U1 *))))

data TwoNoteTurn Source #

two-note-turn (simple)

The two-note-turn type describes the ending notes of trills and mordents for playback, relative to the current note.

Instances

Bounded TwoNoteTurn Source # 
Enum TwoNoteTurn Source # 
Eq TwoNoteTurn Source # 
Ord TwoNoteTurn Source # 
Show TwoNoteTurn Source # 
Generic TwoNoteTurn Source # 

Associated Types

type Rep TwoNoteTurn :: * -> * #

EmitXml TwoNoteTurn Source # 
type Rep TwoNoteTurn Source # 
type Rep TwoNoteTurn = D1 * (MetaData "TwoNoteTurn" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "TwoNoteTurnWhole" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "TwoNoteTurnHalf" PrefixI False) (U1 *)) (C1 * (MetaCons "TwoNoteTurnNone" PrefixI False) (U1 *))))

data Type Source #

xlink:type (simple)

Constructors

TypeSimple

simple

Instances

Bounded Type Source # 
Enum Type Source # 

Methods

succ :: Type -> Type #

pred :: Type -> Type #

toEnum :: Int -> Type #

fromEnum :: Type -> Int #

enumFrom :: Type -> [Type] #

enumFromThen :: Type -> Type -> [Type] #

enumFromTo :: Type -> Type -> [Type] #

enumFromThenTo :: Type -> Type -> Type -> [Type] #

Eq Type Source # 

Methods

(==) :: Type -> Type -> Bool #

(/=) :: Type -> Type -> Bool #

Ord Type Source # 

Methods

compare :: Type -> Type -> Ordering #

(<) :: Type -> Type -> Bool #

(<=) :: Type -> Type -> Bool #

(>) :: Type -> Type -> Bool #

(>=) :: Type -> Type -> Bool #

max :: Type -> Type -> Type #

min :: Type -> Type -> Type #

Show Type Source # 

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Generic Type Source # 

Associated Types

type Rep Type :: * -> * #

Methods

from :: Type -> Rep Type x #

to :: Rep Type x -> Type #

EmitXml Type Source # 

Methods

emitXml :: Type -> XmlRep Source #

type Rep Type Source # 
type Rep Type = D1 * (MetaData "Type" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "TypeSimple" PrefixI False) (U1 *))

data UpDown Source #

up-down (simple)

The up-down type is used for arrow direction, indicating which way the tip is pointing.

Constructors

UpDownUp

up

UpDownDown

down

Instances

Bounded UpDown Source # 
Enum UpDown Source # 
Eq UpDown Source # 

Methods

(==) :: UpDown -> UpDown -> Bool #

(/=) :: UpDown -> UpDown -> Bool #

Ord UpDown Source # 
Show UpDown Source # 
Generic UpDown Source # 

Associated Types

type Rep UpDown :: * -> * #

Methods

from :: UpDown -> Rep UpDown x #

to :: Rep UpDown x -> UpDown #

EmitXml UpDown Source # 
type Rep UpDown Source # 
type Rep UpDown = D1 * (MetaData "UpDown" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "UpDownUp" PrefixI False) (U1 *)) (C1 * (MetaCons "UpDownDown" PrefixI False) (U1 *)))

data UpDownStop Source #

up-down-stop (simple)

The up-down-stop type is used for octave-shift elements, indicating the direction of the shift from their true pitched values because of printing difficulty.

Instances

Bounded UpDownStop Source # 
Enum UpDownStop Source # 
Eq UpDownStop Source # 
Ord UpDownStop Source # 
Show UpDownStop Source # 
Generic UpDownStop Source # 

Associated Types

type Rep UpDownStop :: * -> * #

EmitXml UpDownStop Source # 
type Rep UpDownStop Source # 
type Rep UpDownStop = D1 * (MetaData "UpDownStop" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "UpDownStopUp" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "UpDownStopDown" PrefixI False) (U1 *)) (C1 * (MetaCons "UpDownStopStop" PrefixI False) (U1 *))))

data UprightInverted Source #

upright-inverted (simple)

The upright-inverted type describes the appearance of a fermata element. The value is upright if not specified.

Instances

Bounded UprightInverted Source # 
Enum UprightInverted Source # 
Eq UprightInverted Source # 
Ord UprightInverted Source # 
Show UprightInverted Source # 
Generic UprightInverted Source # 
EmitXml UprightInverted Source # 
type Rep UprightInverted Source # 
type Rep UprightInverted = D1 * (MetaData "UprightInverted" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "UprightInvertedUpright" PrefixI False) (U1 *)) (C1 * (MetaCons "UprightInvertedInverted" PrefixI False) (U1 *)))

data Valign Source #

valign (simple)

The valign type is used to indicate vertical alignment to the top, middle, bottom, or baseline of the text. Defaults are implementation-dependent.

Constructors

ValignTop

top

ValignMiddle

middle

ValignBottom

bottom

ValignBaseline

baseline

Instances

Bounded Valign Source # 
Enum Valign Source # 
Eq Valign Source # 

Methods

(==) :: Valign -> Valign -> Bool #

(/=) :: Valign -> Valign -> Bool #

Ord Valign Source # 
Show Valign Source # 
Generic Valign Source # 

Associated Types

type Rep Valign :: * -> * #

Methods

from :: Valign -> Rep Valign x #

to :: Rep Valign x -> Valign #

EmitXml Valign Source # 
type Rep Valign Source # 
type Rep Valign = D1 * (MetaData "Valign" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * (C1 * (MetaCons "ValignTop" PrefixI False) (U1 *)) (C1 * (MetaCons "ValignMiddle" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "ValignBottom" PrefixI False) (U1 *)) (C1 * (MetaCons "ValignBaseline" PrefixI False) (U1 *))))

data ValignImage Source #

valign-image (simple)

The valign-image type is used to indicate vertical alignment for images and graphics, so it does not include a baseline value. Defaults are implementation-dependent.

Instances

Bounded ValignImage Source # 
Enum ValignImage Source # 
Eq ValignImage Source # 
Ord ValignImage Source # 
Show ValignImage Source # 
Generic ValignImage Source # 

Associated Types

type Rep ValignImage :: * -> * #

EmitXml ValignImage Source # 
type Rep ValignImage Source # 
type Rep ValignImage = D1 * (MetaData "ValignImage" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "ValignImageTop" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ValignImageMiddle" PrefixI False) (U1 *)) (C1 * (MetaCons "ValignImageBottom" PrefixI False) (U1 *))))

data WedgeType Source #

wedge-type (simple)

The wedge type is crescendo for the start of a wedge that is closed at the left side, diminuendo for the start of a wedge that is closed on the right side, and stop for the end of a wedge.

Constructors

WedgeTypeCrescendo

crescendo

WedgeTypeDiminuendo

diminuendo

WedgeTypeStop

stop

Instances

Bounded WedgeType Source # 
Enum WedgeType Source # 
Eq WedgeType Source # 
Ord WedgeType Source # 
Show WedgeType Source # 
Generic WedgeType Source # 

Associated Types

type Rep WedgeType :: * -> * #

EmitXml WedgeType Source # 
type Rep WedgeType Source # 
type Rep WedgeType = D1 * (MetaData "WedgeType" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "WedgeTypeCrescendo" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "WedgeTypeDiminuendo" PrefixI False) (U1 *)) (C1 * (MetaCons "WedgeTypeStop" PrefixI False) (U1 *))))

data YesNo Source #

yes-no (simple)

The yes-no type is used for boolean-like attributes. We cannot use W3C XML Schema booleans due to their restrictions on expression of boolean values.

Constructors

YesNoYes

yes

YesNoNo

no

Instances

Bounded YesNo Source # 
Enum YesNo Source # 
Eq YesNo Source # 

Methods

(==) :: YesNo -> YesNo -> Bool #

(/=) :: YesNo -> YesNo -> Bool #

Ord YesNo Source # 

Methods

compare :: YesNo -> YesNo -> Ordering #

(<) :: YesNo -> YesNo -> Bool #

(<=) :: YesNo -> YesNo -> Bool #

(>) :: YesNo -> YesNo -> Bool #

(>=) :: YesNo -> YesNo -> Bool #

max :: YesNo -> YesNo -> YesNo #

min :: YesNo -> YesNo -> YesNo #

Show YesNo Source # 

Methods

showsPrec :: Int -> YesNo -> ShowS #

show :: YesNo -> String #

showList :: [YesNo] -> ShowS #

Generic YesNo Source # 

Associated Types

type Rep YesNo :: * -> * #

Methods

from :: YesNo -> Rep YesNo x #

to :: Rep YesNo x -> YesNo #

EmitXml YesNo Source # 

Methods

emitXml :: YesNo -> XmlRep Source #

type Rep YesNo Source # 
type Rep YesNo = D1 * (MetaData "YesNo" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "YesNoYes" PrefixI False) (U1 *)) (C1 * (MetaCons "YesNoNo" PrefixI False) (U1 *)))

data YesNoNumber Source #

yes-no-number (simple)

The yes-no-number type is used for attributes that can be either boolean or numeric values.

Instances

Eq YesNoNumber Source # 
Show YesNoNumber Source # 
Generic YesNoNumber Source # 

Associated Types

type Rep YesNoNumber :: * -> * #

EmitXml YesNoNumber Source # 
type Rep YesNoNumber Source # 
type Rep YesNoNumber = D1 * (MetaData "YesNoNumber" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "YesNoNumberYesNo" PrefixI True) (S1 * (MetaSel (Just Symbol "yesNoNumber1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * YesNo))) (C1 * (MetaCons "YesNoNumberDecimal" PrefixI True) (S1 * (MetaSel (Just Symbol "yesNoNumber2") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Decimal))))

newtype YyyyMmDd Source #

yyyy-mm-dd (simple)

Calendar dates are represented yyyy-mm-dd format, following ISO 8601. This is a W3C XML Schema date type, but without the optional timezone data.

Constructors

YyyyMmDd 

Fields

data SumLang Source #

xml:lang (union)

Constructors

SumLang

//

Instances

Bounded SumLang Source # 
Enum SumLang Source # 
Eq SumLang Source # 

Methods

(==) :: SumLang -> SumLang -> Bool #

(/=) :: SumLang -> SumLang -> Bool #

Ord SumLang Source # 
Show SumLang Source # 
Generic SumLang Source # 

Associated Types

type Rep SumLang :: * -> * #

Methods

from :: SumLang -> Rep SumLang x #

to :: Rep SumLang x -> SumLang #

EmitXml SumLang Source # 
type Rep SumLang Source # 
type Rep SumLang = D1 * (MetaData "SumLang" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "SumLang" PrefixI False) (U1 *))

data SumNumberOrNormal Source #

number-or-normal (union)

Constructors

NumberOrNormalNormal

normal

Instances

Bounded SumNumberOrNormal Source # 
Enum SumNumberOrNormal Source # 
Eq SumNumberOrNormal Source # 
Ord SumNumberOrNormal Source # 
Show SumNumberOrNormal Source # 
Generic SumNumberOrNormal Source # 
EmitXml SumNumberOrNormal Source # 
type Rep SumNumberOrNormal Source # 
type Rep SumNumberOrNormal = D1 * (MetaData "SumNumberOrNormal" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "NumberOrNormalNormal" PrefixI False) (U1 *))

data SumPositiveIntegerOrEmpty Source #

positive-integer-or-empty (union)

Instances

Bounded SumPositiveIntegerOrEmpty Source # 
Enum SumPositiveIntegerOrEmpty Source # 
Eq SumPositiveIntegerOrEmpty Source # 
Ord SumPositiveIntegerOrEmpty Source # 
Show SumPositiveIntegerOrEmpty Source # 
Generic SumPositiveIntegerOrEmpty Source # 
EmitXml SumPositiveIntegerOrEmpty Source # 
type Rep SumPositiveIntegerOrEmpty Source # 
type Rep SumPositiveIntegerOrEmpty = D1 * (MetaData "SumPositiveIntegerOrEmpty" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "SumPositiveIntegerOrEmpty" PrefixI False) (U1 *))

data Accidental Source #

accidental (complex)

The accidental type represents actual notated accidentals. Editorial and cautionary indications are indicated by attributes. Values for these attributes are "no" if not present. Specific graphic display such as parentheses, brackets, and size are controlled by the level-display attribute group.

Constructors

Accidental 

Fields

Instances

Eq Accidental Source # 
Show Accidental Source # 
Generic Accidental Source # 

Associated Types

type Rep Accidental :: * -> * #

EmitXml Accidental Source # 
type Rep Accidental Source # 
type Rep Accidental = D1 * (MetaData "Accidental" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Accidental" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalAccidentalValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * AccidentalValue)) ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalCautionary") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))) (S1 * (MetaSel (Just Symbol "accidentalEditorial") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalParentheses") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))) (S1 * (MetaSel (Just Symbol "accidentalBracket") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo)))) ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe SymbolSize))) (S1 * (MetaSel (Just Symbol "accidentalDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "accidentalRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "accidentalFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))) (S1 * (MetaSel (Just Symbol "accidentalFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize)))) ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) (S1 * (MetaSel (Just Symbol "accidentalColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))))))))

data AccidentalMark Source #

accidental-mark (complex)

An accidental-mark can be used as a separate notation or as part of an ornament. When used in an ornament, position and placement are relative to the ornament, not relative to the note.

Constructors

AccidentalMark 

Instances

Eq AccidentalMark Source # 
Show AccidentalMark Source # 
Generic AccidentalMark Source # 

Associated Types

type Rep AccidentalMark :: * -> * #

EmitXml AccidentalMark Source # 
type Rep AccidentalMark Source # 
type Rep AccidentalMark = D1 * (MetaData "AccidentalMark" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "AccidentalMark" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalMarkAccidentalValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * AccidentalValue)) (S1 * (MetaSel (Just Symbol "accidentalMarkDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalMarkDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalMarkRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "accidentalMarkRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalMarkFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalMarkFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))) (S1 * (MetaSel (Just Symbol "accidentalMarkFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))))) ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalMarkFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalMarkColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) (S1 * (MetaSel (Just Symbol "accidentalMarkPlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe AboveBelow))))))))

data AccidentalText Source #

accidental-text (complex)

The accidental-text type represents an element with an accidental value and text-formatting attributes.

Instances

Eq AccidentalText Source # 
Show AccidentalText Source # 
Generic AccidentalText Source # 

Associated Types

type Rep AccidentalText :: * -> * #

EmitXml AccidentalText Source # 
type Rep AccidentalText Source # 
type Rep AccidentalText = D1 * (MetaData "AccidentalText" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "AccidentalText" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalTextAccidentalValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * AccidentalValue)) (S1 * (MetaSel (Just Symbol "accidentalTextLang") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Lang)))) ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalTextEnclosure") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Enclosure))) ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalTextJustify") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe LeftCenterRight))) (S1 * (MetaSel (Just Symbol "accidentalTextHalign") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe LeftCenterRight)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalTextValign") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Valign))) ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalTextDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "accidentalTextDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))))) ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalTextRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalTextRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "accidentalTextFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalTextFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))) (S1 * (MetaSel (Just Symbol "accidentalTextFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize)))) ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalTextFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalTextColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) (S1 * (MetaSel (Just Symbol "accidentalTextUnderline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NumberOfLines)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalTextOverline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NumberOfLines))) ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalTextLineThrough") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NumberOfLines))) (S1 * (MetaSel (Just Symbol "accidentalTextRotation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe RotationDegrees))))) ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalTextLetterSpacing") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NumberOrNormal))) ((:*:) * (S1 * (MetaSel (Just Symbol "accidentalTextLineHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NumberOrNormal))) (S1 * (MetaSel (Just Symbol "accidentalTextDir") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe TextDirection)))))))))

data Accord Source #

accord (complex)

The accord type represents the tuning of a single string in the scordatura element. It uses the same group of elements as the staff-tuning element. Strings are numbered from high to low.

Constructors

Accord 

Fields

Instances

Eq Accord Source # 

Methods

(==) :: Accord -> Accord -> Bool #

(/=) :: Accord -> Accord -> Bool #

Show Accord Source # 
Generic Accord Source # 

Associated Types

type Rep Accord :: * -> * #

Methods

from :: Accord -> Rep Accord x #

to :: Rep Accord x -> Accord #

EmitXml Accord Source # 
type Rep Accord Source # 
type Rep Accord = D1 * (MetaData "Accord" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Accord" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "accordString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe StringNumber))) (S1 * (MetaSel (Just Symbol "accordTuning") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Tuning))))

mkAccord :: Tuning -> Accord Source #

Smart constructor for Accord

data AccordionRegistration Source #

accordion-registration (complex)

The accordion-registration type is use for accordion registration symbols. These are circular symbols divided horizontally into high, middle, and low sections that correspond to 4', 8', and 16' pipes. Each accordion-high, accordion-middle, and accordion-low element represents the presence of one or more dots in the registration diagram. An accordion-registration element needs to have at least one of the child elements present.

Instances

Eq AccordionRegistration Source # 
Show AccordionRegistration Source # 
Generic AccordionRegistration Source # 
EmitXml AccordionRegistration Source # 
type Rep AccordionRegistration Source # 
type Rep AccordionRegistration = D1 * (MetaData "AccordionRegistration" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "AccordionRegistration" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "accordionRegistrationDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "accordionRegistrationDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "accordionRegistrationRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))))) ((:*:) * (S1 * (MetaSel (Just Symbol "accordionRegistrationRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "accordionRegistrationFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) (S1 * (MetaSel (Just Symbol "accordionRegistrationFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "accordionRegistrationFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) ((:*:) * (S1 * (MetaSel (Just Symbol "accordionRegistrationFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) (S1 * (MetaSel (Just Symbol "accordionRegistrationColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))))) ((:*:) * (S1 * (MetaSel (Just Symbol "accordionRegistrationAccordionHigh") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Empty))) ((:*:) * (S1 * (MetaSel (Just Symbol "accordionRegistrationAccordionMiddle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe AccordionMiddle))) (S1 * (MetaSel (Just Symbol "accordionRegistrationAccordionLow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Empty))))))))

data Appearance Source #

appearance (complex)

The appearance type controls general graphical settings for the music's final form appearance on a printed page of display. Currently this includes support for line widths and definitions for note sizes, plus an extension element for other aspects of appearance.

Constructors

Appearance 

Fields

Instances

Eq Appearance Source # 
Show Appearance Source # 
Generic Appearance Source # 

Associated Types

type Rep Appearance :: * -> * #

EmitXml Appearance Source # 
type Rep Appearance Source # 
type Rep Appearance = D1 * (MetaData "Appearance" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Appearance" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "appearanceLineWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [LineWidth])) ((:*:) * (S1 * (MetaSel (Just Symbol "appearanceNoteSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [NoteSize])) (S1 * (MetaSel (Just Symbol "appearanceOtherAppearance") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [OtherAppearance])))))

mkAppearance :: Appearance Source #

Smart constructor for Appearance

data Arpeggiate Source #

arpeggiate (complex)

The arpeggiate type indicates that this note is part of an arpeggiated chord. The number attribute can be used to distinguish between two simultaneous chords arpeggiated separately (different numbers) or together (same number). The up-down attribute is used if there is an arrow on the arpeggio sign. By default, arpeggios go from the lowest to highest note.

Constructors

Arpeggiate 

Fields

Instances

Eq Arpeggiate Source # 
Show Arpeggiate Source # 
Generic Arpeggiate Source # 

Associated Types

type Rep Arpeggiate :: * -> * #

EmitXml Arpeggiate Source # 
type Rep Arpeggiate Source # 

mkArpeggiate :: Arpeggiate Source #

Smart constructor for Arpeggiate

data Articulations Source #

articulations (complex)

Articulations and accents are grouped together here.

Instances

Eq Articulations Source # 
Show Articulations Source # 
Generic Articulations Source # 

Associated Types

type Rep Articulations :: * -> * #

EmitXml Articulations Source # 
type Rep Articulations Source # 
type Rep Articulations = D1 * (MetaData "Articulations" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Articulations" PrefixI True) (S1 * (MetaSel (Just Symbol "articulationsArticulations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ChxArticulations])))

data Attributes Source #

attributes (complex)

The attributes element contains musical information that typically changes on measure boundaries. This includes key and time signatures, clefs, transpositions, and staving.

Constructors

Attributes 

Fields

Instances

Eq Attributes Source # 
Show Attributes Source # 
Generic Attributes Source # 

Associated Types

type Rep Attributes :: * -> * #

EmitXml Attributes Source # 
type Rep Attributes Source # 
type Rep Attributes = D1 * (MetaData "Attributes" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Attributes" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "attributesEditorial") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Editorial)) ((:*:) * (S1 * (MetaSel (Just Symbol "attributesDivisions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe PositiveDivisions))) (S1 * (MetaSel (Just Symbol "attributesKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Key])))) ((:*:) * (S1 * (MetaSel (Just Symbol "attributesTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Time])) ((:*:) * (S1 * (MetaSel (Just Symbol "attributesStaves") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NonNegativeInteger))) (S1 * (MetaSel (Just Symbol "attributesPartSymbol") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe PartSymbol)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "attributesInstruments") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NonNegativeInteger))) ((:*:) * (S1 * (MetaSel (Just Symbol "attributesClef") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Clef])) (S1 * (MetaSel (Just Symbol "attributesStaffDetails") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [StaffDetails])))) ((:*:) * (S1 * (MetaSel (Just Symbol "attributesTranspose") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Transpose))) ((:*:) * (S1 * (MetaSel (Just Symbol "attributesDirective") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Directive])) (S1 * (MetaSel (Just Symbol "attributesMeasureStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [MeasureStyle])))))))

mkAttributes :: Editorial -> Attributes Source #

Smart constructor for Attributes

data Backup Source #

backup (complex)

The backup and forward elements are required to coordinate multiple voices in one part, including music on multiple staves. The backup type is generally used to move between voices and staves. Thus the backup element does not include voice or staff elements. Duration values should always be positive, and should not cross measure boundaries.

Instances

Eq Backup Source # 

Methods

(==) :: Backup -> Backup -> Bool #

(/=) :: Backup -> Backup -> Bool #

Show Backup Source # 
Generic Backup Source # 

Associated Types

type Rep Backup :: * -> * #

Methods

from :: Backup -> Rep Backup x #

to :: Rep Backup x -> Backup #

EmitXml Backup Source # 
type Rep Backup Source # 
type Rep Backup = D1 * (MetaData "Backup" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Backup" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "backupDuration") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Duration)) (S1 * (MetaSel (Just Symbol "backupEditorial") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Editorial))))

mkBackup :: Duration -> Editorial -> Backup Source #

Smart constructor for Backup

data BarStyleColor Source #

bar-style-color (complex)

The bar-style-color type contains barline style and color information.

Constructors

BarStyleColor 

Fields

data Barline Source #

barline (complex)

If a barline is other than a normal single barline, it should be represented by a barline type that describes it. This includes information about repeats and multiple endings, as well as line style. Barline data is on the same level as the other musical data in a score - a child of a measure in a partwise score, or a part in a timewise score. This allows for barlines within measures, as in dotted barlines that subdivide measures in complex meters. The two fermata elements allow for fermatas on both sides of the barline (the lower one inverted).

Barlines have a location attribute to make it easier to process barlines independently of the other musical data in a score. It is often easier to set up measures separately from entering notes. The location attribute must match where the barline element occurs within the rest of the musical data in the score. If location is left, it should be the first element in the measure, aside from the print, bookmark, and link elements. If location is right, it should be the last element, again with the possible exception of the print, bookmark, and link elements. If no location is specified, the right barline is the default. The segno, coda, and divisions attributes work the same way as in the sound element. They are used for playback when barline elements contain segno or coda child elements.

Constructors

Barline 

Fields

Instances

Eq Barline Source # 

Methods

(==) :: Barline -> Barline -> Bool #

(/=) :: Barline -> Barline -> Bool #

Show Barline Source # 
Generic Barline Source # 

Associated Types

type Rep Barline :: * -> * #

Methods

from :: Barline -> Rep Barline x #

to :: Rep Barline x -> Barline #

EmitXml Barline Source # 
type Rep Barline Source # 
type Rep Barline = D1 * (MetaData "Barline" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Barline" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "barlineLocation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe RightLeftMiddle))) ((:*:) * (S1 * (MetaSel (Just Symbol "barlineSegno") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Token))) (S1 * (MetaSel (Just Symbol "barlineCoda") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Token))))) ((:*:) * (S1 * (MetaSel (Just Symbol "barlineDivisions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Divisions))) ((:*:) * (S1 * (MetaSel (Just Symbol "barlineBarStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe BarStyleColor))) (S1 * (MetaSel (Just Symbol "barlineEditorial") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Editorial))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "barlineWavyLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe WavyLine))) ((:*:) * (S1 * (MetaSel (Just Symbol "barlineSegno1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe EmptyPrintStyle))) (S1 * (MetaSel (Just Symbol "barlineCoda1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe EmptyPrintStyle))))) ((:*:) * (S1 * (MetaSel (Just Symbol "barlineFermata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Fermata])) ((:*:) * (S1 * (MetaSel (Just Symbol "barlineEnding") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Ending))) (S1 * (MetaSel (Just Symbol "barlineRepeat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Repeat))))))))

mkBarline :: Editorial -> Barline Source #

Smart constructor for Barline

data Barre Source #

barre (complex)

The barre element indicates placing a finger over multiple strings on a single fret. The type is "start" for the lowest pitched string (e.g., the string with the highest MusicXML number) and is "stop" for the highest pitched string.

Constructors

Barre 

Fields

Instances

Eq Barre Source # 

Methods

(==) :: Barre -> Barre -> Bool #

(/=) :: Barre -> Barre -> Bool #

Show Barre Source # 

Methods

showsPrec :: Int -> Barre -> ShowS #

show :: Barre -> String #

showList :: [Barre] -> ShowS #

Generic Barre Source # 

Associated Types

type Rep Barre :: * -> * #

Methods

from :: Barre -> Rep Barre x #

to :: Rep Barre x -> Barre #

EmitXml Barre Source # 

Methods

emitXml :: Barre -> XmlRep Source #

type Rep Barre Source # 
type Rep Barre = D1 * (MetaData "Barre" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Barre" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "barreType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * StartStop)) (S1 * (MetaSel (Just Symbol "barreColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color)))))

mkBarre :: StartStop -> Barre Source #

Smart constructor for Barre

data Bass Source #

bass (complex)

The bass type is used to indicate a bass note in popular music chord symbols, e.g. G/C. It is generally not used in functional harmony, as inversion is generally not used in pop chord symbols. As with root, it is divided into step and alter elements, similar to pitches.

Constructors

Bass 

Fields

Instances

Eq Bass Source # 

Methods

(==) :: Bass -> Bass -> Bool #

(/=) :: Bass -> Bass -> Bool #

Show Bass Source # 

Methods

showsPrec :: Int -> Bass -> ShowS #

show :: Bass -> String #

showList :: [Bass] -> ShowS #

Generic Bass Source # 

Associated Types

type Rep Bass :: * -> * #

Methods

from :: Bass -> Rep Bass x #

to :: Rep Bass x -> Bass #

EmitXml Bass Source # 

Methods

emitXml :: Bass -> XmlRep Source #

type Rep Bass Source # 
type Rep Bass = D1 * (MetaData "Bass" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Bass" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "bassBassStep") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * BassStep)) (S1 * (MetaSel (Just Symbol "bassBassAlter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe BassAlter)))))

mkBass :: BassStep -> Bass Source #

Smart constructor for Bass

data BassAlter Source #

bass-alter (complex)

The bass-alter type represents the chromatic alteration of the bass of the current chord within the harmony element. In some chord styles, the text for the bass-step element may include bass-alter information. In that case, the print-object attribute of the bass-alter element can be set to no. The location attribute indicates whether the alteration should appear to the left or the right of the bass-step; it is right by default.

Constructors

BassAlter 

Fields

Instances

Eq BassAlter Source # 
Show BassAlter Source # 
Generic BassAlter Source # 

Associated Types

type Rep BassAlter :: * -> * #

EmitXml BassAlter Source # 
type Rep BassAlter Source # 
type Rep BassAlter = D1 * (MetaData "BassAlter" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "BassAlter" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "bassAlterSemitones") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Semitones)) ((:*:) * (S1 * (MetaSel (Just Symbol "bassAlterLocation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe LeftRight))) (S1 * (MetaSel (Just Symbol "bassAlterPrintObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))))) ((:*:) * (S1 * (MetaSel (Just Symbol "bassAlterDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "bassAlterDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "bassAlterRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "bassAlterRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "bassAlterFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) (S1 * (MetaSel (Just Symbol "bassAlterFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))))) ((:*:) * (S1 * (MetaSel (Just Symbol "bassAlterFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) ((:*:) * (S1 * (MetaSel (Just Symbol "bassAlterFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) (S1 * (MetaSel (Just Symbol "bassAlterColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))))))))

mkBassAlter :: Semitones -> BassAlter Source #

Smart constructor for BassAlter

data BassStep Source #

bass-step (complex)

The bass-step type represents the pitch step of the bass of the current chord within the harmony element. The text attribute indicates how the bass should appear on the page if not using the element contents.

Constructors

BassStep 

Fields

Instances

Eq BassStep Source # 
Show BassStep Source # 
Generic BassStep Source # 

Associated Types

type Rep BassStep :: * -> * #

Methods

from :: BassStep -> Rep BassStep x #

to :: Rep BassStep x -> BassStep #

EmitXml BassStep Source # 
type Rep BassStep Source # 
type Rep BassStep = D1 * (MetaData "BassStep" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "BassStep" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "bassStepStep") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Step)) (S1 * (MetaSel (Just Symbol "bassStepText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Token)))) ((:*:) * (S1 * (MetaSel (Just Symbol "bassStepDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "bassStepDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "bassStepRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "bassStepRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "bassStepFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) (S1 * (MetaSel (Just Symbol "bassStepFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))))) ((:*:) * (S1 * (MetaSel (Just Symbol "bassStepFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) ((:*:) * (S1 * (MetaSel (Just Symbol "bassStepFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) (S1 * (MetaSel (Just Symbol "bassStepColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))))))))

mkBassStep :: Step -> BassStep Source #

Smart constructor for BassStep

data Beam Source #

beam (complex)

Beam values include begin, continue, end, forward hook, and backward hook. Up to six concurrent beam levels are available to cover up to 256th notes. The repeater attribute, used for tremolos, needs to be specified with a "yes" value for each beam using it. Beams that have a begin value can also have a fan attribute to indicate accelerandos and ritardandos using fanned beams. The fan attribute may also be used with a continue value if the fanning direction changes on that note. The value is "none" if not specified.

Note that the beam number does not distinguish sets of beams that overlap, as it does for slur and other elements. Beaming groups are distinguished by being in different voices and/or the presence or absence of grace and cue elements.

Constructors

Beam 

Fields

Instances

Eq Beam Source # 

Methods

(==) :: Beam -> Beam -> Bool #

(/=) :: Beam -> Beam -> Bool #

Show Beam Source # 

Methods

showsPrec :: Int -> Beam -> ShowS #

show :: Beam -> String #

showList :: [Beam] -> ShowS #

Generic Beam Source # 

Associated Types

type Rep Beam :: * -> * #

Methods

from :: Beam -> Rep Beam x #

to :: Rep Beam x -> Beam #

EmitXml Beam Source # 

Methods

emitXml :: Beam -> XmlRep Source #

type Rep Beam Source # 

mkBeam :: BeamValue -> Beam Source #

Smart constructor for Beam

data BeatRepeat Source #

beat-repeat (complex)

The beat-repeat type is used to indicate that a single beat (but possibly many notes) is repeated. Both the start and stop of the beat being repeated should be specified. The slashes attribute specifies the number of slashes to use in the symbol. The use-dots attribute indicates whether or not to use dots as well (for instance, with mixed rhythm patterns). By default, the value for slashes is 1 and the value for use-dots is no.

The beat-repeat element specifies a notation style for repetitions. The actual music being repeated needs to be repeated within the MusicXML file. This element specifies the notation that indicates the repeat.

Constructors

BeatRepeat 

Fields

mkBeatRepeat :: StartStop -> BeatRepeat Source #

Smart constructor for BeatRepeat

data Bend Source #

bend (complex)

The bend type is used in guitar and tablature. The bend-alter element indicates the number of steps in the bend, similar to the alter element. As with the alter element, numbers like 0.5 can be used to indicate microtones. Negative numbers indicate pre-bends or releases; the pre-bend and release elements are used to distinguish what is intended. A with-bar element indicates that the bend is to be done at the bridge with a whammy or vibrato bar. The content of the element indicates how this should be notated.

Constructors

Bend 

Fields

Instances

Eq Bend Source # 

Methods

(==) :: Bend -> Bend -> Bool #

(/=) :: Bend -> Bend -> Bool #

Show Bend Source # 

Methods

showsPrec :: Int -> Bend -> ShowS #

show :: Bend -> String #

showList :: [Bend] -> ShowS #

Generic Bend Source # 

Associated Types

type Rep Bend :: * -> * #

Methods

from :: Bend -> Rep Bend x #

to :: Rep Bend x -> Bend #

EmitXml Bend Source # 

Methods

emitXml :: Bend -> XmlRep Source #

type Rep Bend Source # 
type Rep Bend = D1 * (MetaData "Bend" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Bend" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "bendDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "bendDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "bendRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "bendRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "bendFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) (S1 * (MetaSel (Just Symbol "bendFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle)))) ((:*:) * (S1 * (MetaSel (Just Symbol "bendFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) (S1 * (MetaSel (Just Symbol "bendFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "bendColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) (S1 * (MetaSel (Just Symbol "bendAccelerate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo)))) ((:*:) * (S1 * (MetaSel (Just Symbol "bendBeats") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe TrillBeats))) (S1 * (MetaSel (Just Symbol "bendFirstBeat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Percent))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "bendLastBeat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Percent))) (S1 * (MetaSel (Just Symbol "bendBendAlter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Semitones))) ((:*:) * (S1 * (MetaSel (Just Symbol "bendBend") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe ChxBend))) (S1 * (MetaSel (Just Symbol "bendWithBar") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe PlacementText))))))))

mkBend :: Semitones -> Bend Source #

Smart constructor for Bend

data Bookmark Source #

bookmark (complex)

The bookmark type serves as a well-defined target for an incoming simple XLink.

Constructors

Bookmark 

Fields

mkBookmark :: ID -> Bookmark Source #

Smart constructor for Bookmark

data Bracket Source #

bracket (complex)

Brackets are combined with words in a variety of modern directions. The line-end attribute specifies if there is a jog up or down (or both), an arrow, or nothing at the start or end of the bracket. If the line-end is up or down, the length of the jog can be specified using the end-length attribute. The line-type is solid by default.

Constructors

Bracket 

Fields

Instances

Eq Bracket Source # 

Methods

(==) :: Bracket -> Bracket -> Bool #

(/=) :: Bracket -> Bracket -> Bool #

Show Bracket Source # 
Generic Bracket Source # 

Associated Types

type Rep Bracket :: * -> * #

Methods

from :: Bracket -> Rep Bracket x #

to :: Rep Bracket x -> Bracket #

EmitXml Bracket Source # 
type Rep Bracket Source # 

mkBracket :: StartStop -> LineEnd -> Bracket Source #

Smart constructor for Bracket

data Cancel Source #

cancel (complex)

A cancel element indicates that the old key signature should be cancelled before the new one appears. This will always happen when changing to C major or A minor and need not be specified then. The cancel value matches the fifths value of the cancelled key signature (e.g., a cancel of -2 will provide an explicit cancellation for changing from B flat major to F major). The optional location attribute indicates whether the cancellation appears to the left or the right of the new key signature. It is left by default.

Constructors

Cancel 

Fields

Instances

Eq Cancel Source # 

Methods

(==) :: Cancel -> Cancel -> Bool #

(/=) :: Cancel -> Cancel -> Bool #

Show Cancel Source # 
Generic Cancel Source # 

Associated Types

type Rep Cancel :: * -> * #

Methods

from :: Cancel -> Rep Cancel x #

to :: Rep Cancel x -> Cancel #

EmitXml Cancel Source # 
type Rep Cancel Source # 
type Rep Cancel = D1 * (MetaData "Cancel" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Cancel" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "cancelFifths") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Fifths)) (S1 * (MetaSel (Just Symbol "cancelLocation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe LeftRight)))))

mkCancel :: Fifths -> Cancel Source #

Smart constructor for Cancel

data Clef Source #

clef (complex)

Clefs are represented by a combination of sign, line, and clef-octave-change elements. The optional number attribute refers to staff numbers within the part. A value of 1 is assumed if not present.

Sometimes clefs are added to the staff in non-standard line positions, either to indicate cue passages, or when there are multiple clefs present simultaneously on one staff. In this situation, the additional attribute is set to "yes" and the line value is ignored. The size attribute is used for clefs where the additional attribute is "yes". It is typically used to indicate cue clefs.

Constructors

Clef 

Fields

Instances

Eq Clef Source # 

Methods

(==) :: Clef -> Clef -> Bool #

(/=) :: Clef -> Clef -> Bool #

Show Clef Source # 

Methods

showsPrec :: Int -> Clef -> ShowS #

show :: Clef -> String #

showList :: [Clef] -> ShowS #

Generic Clef Source # 

Associated Types

type Rep Clef :: * -> * #

Methods

from :: Clef -> Rep Clef x #

to :: Rep Clef x -> Clef #

EmitXml Clef Source # 

Methods

emitXml :: Clef -> XmlRep Source #

type Rep Clef Source # 
type Rep Clef = D1 * (MetaData "Clef" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Clef" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "clefNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe StaffNumber))) (S1 * (MetaSel (Just Symbol "clefAdditional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo)))) ((:*:) * (S1 * (MetaSel (Just Symbol "clefSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe SymbolSize))) (S1 * (MetaSel (Just Symbol "clefDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "clefDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "clefRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "clefRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "clefFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "clefFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))) (S1 * (MetaSel (Just Symbol "clefFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize)))) ((:*:) * (S1 * (MetaSel (Just Symbol "clefFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) (S1 * (MetaSel (Just Symbol "clefColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "clefPrintObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))) (S1 * (MetaSel (Just Symbol "clefSign") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ClefSign))) ((:*:) * (S1 * (MetaSel (Just Symbol "clefLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe StaffLine))) (S1 * (MetaSel (Just Symbol "clefClefOctaveChange") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int))))))))

mkClef :: ClefSign -> Clef Source #

Smart constructor for Clef

data Credit Source #

credit (complex)

The credit type represents the appearance of the title, composer, arranger, lyricist, copyright, dedication, and other text and graphics that commonly appears on the first page of a score. The credit-words and credit-image elements are similar to the words and image elements for directions. However, since the credit is not part of a measure, the default-x and default-y attributes adjust the origin relative to the bottom left-hand corner of the first page. The enclosure for credit-words is none by default.

By default, a series of credit-words elements within a single credit element follow one another in sequence visually. Non-positional formatting attributes are carried over from the previous element by default.

The page attribute for the credit element, new in Version 2.0, specifies the page number where the credit should appear. This is an integer value that starts with 1 for the first page. Its value is 1 by default. Since credits occur before the music, these page numbers do not refer to the page numbering specified by the print element's page-number attribute.

Constructors

Credit 

Fields

Instances

Eq Credit Source # 

Methods

(==) :: Credit -> Credit -> Bool #

(/=) :: Credit -> Credit -> Bool #

Show Credit Source # 
Generic Credit Source # 

Associated Types

type Rep Credit :: * -> * #

Methods

from :: Credit -> Rep Credit x #

to :: Rep Credit x -> Credit #

EmitXml Credit Source # 
type Rep Credit Source # 

mkCredit :: ChxCredit -> Credit Source #

Smart constructor for Credit

data Dashes Source #

dashes (complex)

The dashes type represents dashes, used for instance with cresc. and dim. marks.

Constructors

Dashes 

Fields

Instances

Eq Dashes Source # 

Methods

(==) :: Dashes -> Dashes -> Bool #

(/=) :: Dashes -> Dashes -> Bool #

Show Dashes Source # 
Generic Dashes Source # 

Associated Types

type Rep Dashes :: * -> * #

Methods

from :: Dashes -> Rep Dashes x #

to :: Rep Dashes x -> Dashes #

EmitXml Dashes Source # 
type Rep Dashes Source # 

mkDashes :: StartStop -> Dashes Source #

Smart constructor for Dashes

data Defaults Source #

defaults (complex)

The defaults type specifies score-wide defaults for scaling, layout, and appearance.

Constructors

Defaults 

Fields

Instances

Eq Defaults Source # 
Show Defaults Source # 
Generic Defaults Source # 

Associated Types

type Rep Defaults :: * -> * #

Methods

from :: Defaults -> Rep Defaults x #

to :: Rep Defaults x -> Defaults #

EmitXml Defaults Source # 
type Rep Defaults Source # 

mkDefaults :: Layout -> Defaults Source #

Smart constructor for Defaults

data Degree Source #

degree (complex)

The degree type is used to add, alter, or subtract individual notes in the chord. The print-object attribute can be used to keep the degree from printing separately when it has already taken into account in the text attribute of the kind element. The degree-value and degree-type text attributes specify how the value and type of the degree should be displayed.

A harmony of kind "other" can be spelled explicitly by using a series of degree elements together with a root.

Constructors

Degree 

Fields

Instances

Eq Degree Source # 

Methods

(==) :: Degree -> Degree -> Bool #

(/=) :: Degree -> Degree -> Bool #

Show Degree Source # 
Generic Degree Source # 

Associated Types

type Rep Degree :: * -> * #

Methods

from :: Degree -> Rep Degree x #

to :: Rep Degree x -> Degree #

EmitXml Degree Source # 
type Rep Degree Source # 
type Rep Degree = D1 * (MetaData "Degree" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Degree" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "degreePrintObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))) (S1 * (MetaSel (Just Symbol "degreeDegreeValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * DegreeValue))) ((:*:) * (S1 * (MetaSel (Just Symbol "degreeDegreeAlter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * DegreeAlter)) (S1 * (MetaSel (Just Symbol "degreeDegreeType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * DegreeType)))))

mkDegree :: DegreeValue -> DegreeAlter -> DegreeType -> Degree Source #

Smart constructor for Degree

data DegreeAlter Source #

degree-alter (complex)

The degree-alter type represents the chromatic alteration for the current degree. If the degree-type value is alter or subtract, the degree-alter value is relative to the degree already in the chord based on its kind element. If the degree-type value is add, the degree-alter is relative to a dominant chord (major and perfect intervals except for a minor seventh). The plus-minus attribute is used to indicate if plus and minus symbols should be used instead of sharp and flat symbols to display the degree alteration; it is no by default.

Constructors

DegreeAlter 

Fields

Instances

Eq DegreeAlter Source # 
Show DegreeAlter Source # 
Generic DegreeAlter Source # 

Associated Types

type Rep DegreeAlter :: * -> * #

EmitXml DegreeAlter Source # 
type Rep DegreeAlter Source # 
type Rep DegreeAlter = D1 * (MetaData "DegreeAlter" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "DegreeAlter" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "degreeAlterSemitones") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Semitones)) (S1 * (MetaSel (Just Symbol "degreeAlterPlusMinus") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo)))) ((:*:) * (S1 * (MetaSel (Just Symbol "degreeAlterDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "degreeAlterDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "degreeAlterRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "degreeAlterRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "degreeAlterFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) (S1 * (MetaSel (Just Symbol "degreeAlterFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))))) ((:*:) * (S1 * (MetaSel (Just Symbol "degreeAlterFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) ((:*:) * (S1 * (MetaSel (Just Symbol "degreeAlterFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) (S1 * (MetaSel (Just Symbol "degreeAlterColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))))))))

data DegreeType Source #

degree-type (complex)

The degree-type type indicates if this degree is an addition, alteration, or subtraction relative to the kind of the current chord. The value of the degree-type element affects the interpretation of the value of the degree-alter element. The text attribute specifies how the type of the degree should be displayed.

Constructors

DegreeType 

Fields

Instances

Eq DegreeType Source # 
Show DegreeType Source # 
Generic DegreeType Source # 

Associated Types

type Rep DegreeType :: * -> * #

EmitXml DegreeType Source # 
type Rep DegreeType Source # 
type Rep DegreeType = D1 * (MetaData "DegreeType" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "DegreeType" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "degreeTypeDegreeTypeValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * DegreeTypeValue)) (S1 * (MetaSel (Just Symbol "degreeTypeText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Token)))) ((:*:) * (S1 * (MetaSel (Just Symbol "degreeTypeDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "degreeTypeDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "degreeTypeRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "degreeTypeRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "degreeTypeFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) (S1 * (MetaSel (Just Symbol "degreeTypeFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))))) ((:*:) * (S1 * (MetaSel (Just Symbol "degreeTypeFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) ((:*:) * (S1 * (MetaSel (Just Symbol "degreeTypeFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) (S1 * (MetaSel (Just Symbol "degreeTypeColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))))))))

data DegreeValue Source #

degree-value (complex)

The content of the degree-value type is a number indicating the degree of the chord (1 for the root, 3 for third, etc). The text attribute specifies how the type of the degree should be displayed.

Constructors

DegreeValue 

Fields

Instances

Eq DegreeValue Source # 
Show DegreeValue Source # 
Generic DegreeValue Source # 

Associated Types

type Rep DegreeValue :: * -> * #

EmitXml DegreeValue Source # 
type Rep DegreeValue Source # 
type Rep DegreeValue = D1 * (MetaData "DegreeValue" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "DegreeValue" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "degreeValuePositiveInteger") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PositiveInteger)) (S1 * (MetaSel (Just Symbol "degreeValueText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Token)))) ((:*:) * (S1 * (MetaSel (Just Symbol "degreeValueDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "degreeValueDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "degreeValueRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "degreeValueRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "degreeValueFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) (S1 * (MetaSel (Just Symbol "degreeValueFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))))) ((:*:) * (S1 * (MetaSel (Just Symbol "degreeValueFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) ((:*:) * (S1 * (MetaSel (Just Symbol "degreeValueFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) (S1 * (MetaSel (Just Symbol "degreeValueColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))))))))

data Direction Source #

direction (complex)

A direction is a musical indication that is not attached to a specific note. Two or more may be combined to indicate starts and stops of wedges, dashes, etc.

By default, a series of direction-type elements and a series of child elements of a direction-type within a single direction element follow one another in sequence visually. For a series of direction-type children, non-positional formatting attributes are carried over from the previous element by default.

Constructors

Direction 

Fields

Instances

Eq Direction Source # 
Show Direction Source # 
Generic Direction Source # 

Associated Types

type Rep Direction :: * -> * #

EmitXml Direction Source # 
type Rep Direction Source # 

data DirectionType Source #

direction-type (complex)

Textual direction types may have more than 1 component due to multiple fonts. The dynamics element may also be used in the notations element. Attribute groups related to print suggestions apply to the individual direction-type, not to the overall direction.

Instances

Eq DirectionType Source # 
Show DirectionType Source # 
Generic DirectionType Source # 

Associated Types

type Rep DirectionType :: * -> * #

EmitXml DirectionType Source # 
type Rep DirectionType Source # 
type Rep DirectionType = D1 * (MetaData "DirectionType" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "DirectionType" PrefixI True) (S1 * (MetaSel (Just Symbol "directionTypeDirectionType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ChxDirectionType)))

data Directive Source #

directive (complex)

Constructors

Directive 

Fields

Instances

Eq Directive Source # 
Show Directive Source # 
Generic Directive Source # 

Associated Types

type Rep Directive :: * -> * #

EmitXml Directive Source # 
type Rep Directive Source # 
type Rep Directive = D1 * (MetaData "Directive" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Directive" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "directiveString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "directiveLang") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Lang)))) ((:*:) * (S1 * (MetaSel (Just Symbol "directiveDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "directiveDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "directiveRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "directiveRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "directiveFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) (S1 * (MetaSel (Just Symbol "directiveFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))))) ((:*:) * (S1 * (MetaSel (Just Symbol "directiveFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) ((:*:) * (S1 * (MetaSel (Just Symbol "directiveFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) (S1 * (MetaSel (Just Symbol "directiveColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))))))))

mkDirective :: String -> Directive Source #

Smart constructor for Directive

data DisplayStepOctave Source #

display-step-octave (complex)

The display-step-octave type contains the sequence of elements used by both the rest and unpitched elements. This group is used to place rests and unpitched elements on the staff without implying that these elements have pitch. Positioning follows the current clef. If percussion clef is used, the display-step and display-octave elements are interpreted as if in treble clef, with a G in octave 4 on line 2. If not present, the note is placed on the middle line of the staff, generally used for one-line staffs.

data Dynamics Source #

dynamics (complex)

Dynamics can be associated either with a note or a general musical direction. To avoid inconsistencies between and amongst the letter abbreviations for dynamics (what is sf vs. sfz, standing alone or with a trailing dynamic that is not always piano), we use the actual letters as the names of these dynamic elements. The other-dynamics element allows other dynamic marks that are not covered here, but many of those should perhaps be included in a more general musical direction element. Dynamics elements may also be combined to create marks not covered by a single element, such as sfmp.

These letter dynamic symbols are separated from crescendo, decrescendo, and wedge indications. Dynamic representation is inconsistent in scores. Many things are assumed by the composer and left out, such as returns to original dynamics. Systematic representations are quite complex: for example, Humdrum has at least 3 representation formats related to dynamics. The MusicXML format captures what is in the score, but does not try to be optimal for analysis or synthesis of dynamics.

Constructors

Dynamics 

Fields

Instances

Eq Dynamics Source # 
Show Dynamics Source # 
Generic Dynamics Source # 

Associated Types

type Rep Dynamics :: * -> * #

Methods

from :: Dynamics -> Rep Dynamics x #

to :: Rep Dynamics x -> Dynamics #

EmitXml Dynamics Source # 
type Rep Dynamics Source # 
type Rep Dynamics = D1 * (MetaData "Dynamics" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Dynamics" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "dynamicsDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "dynamicsDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "dynamicsRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "dynamicsRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "dynamicsFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "dynamicsFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))) ((:*:) * (S1 * (MetaSel (Just Symbol "dynamicsFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) (S1 * (MetaSel (Just Symbol "dynamicsFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))))) ((:*:) * (S1 * (MetaSel (Just Symbol "dynamicsColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) ((:*:) * (S1 * (MetaSel (Just Symbol "dynamicsPlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe AboveBelow))) (S1 * (MetaSel (Just Symbol "dynamicsDynamics") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ChxDynamics])))))))

mkDynamics :: Dynamics Source #

Smart constructor for Dynamics

data Elision Source #

elision (complex)

In Version 2.0, the content of the elision type is used to specify the symbol used to display the elision. Common values are a no-break space (Unicode 00A0), an underscore (Unicode 005F), or an undertie (Unicode 203F).

Constructors

Elision 

Fields

mkElision :: String -> Elision Source #

Smart constructor for Elision

data Empty Source #

empty (complex)

The empty type represents an empty element with no attributes.

Constructors

Empty 

Instances

Eq Empty Source # 

Methods

(==) :: Empty -> Empty -> Bool #

(/=) :: Empty -> Empty -> Bool #

Show Empty Source # 

Methods

showsPrec :: Int -> Empty -> ShowS #

show :: Empty -> String #

showList :: [Empty] -> ShowS #

Generic Empty Source # 

Associated Types

type Rep Empty :: * -> * #

Methods

from :: Empty -> Rep Empty x #

to :: Rep Empty x -> Empty #

EmitXml Empty Source # 

Methods

emitXml :: Empty -> XmlRep Source #

type Rep Empty Source # 
type Rep Empty = D1 * (MetaData "Empty" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Empty" PrefixI False) (U1 *))

mkEmpty :: Empty Source #

Smart constructor for Empty

data EmptyFont Source #

empty-font (complex)

The empty-font type represents an empty element with font attributes.

Constructors

EmptyFont 

Fields

mkEmptyFont :: EmptyFont Source #

Smart constructor for EmptyFont

data EmptyLine Source #

empty-line (complex)

The empty-line type represents an empty element with line-shape, line-type, print-style and placement attributes.

Constructors

EmptyLine 

Fields

Instances

Eq EmptyLine Source # 
Show EmptyLine Source # 
Generic EmptyLine Source # 

Associated Types

type Rep EmptyLine :: * -> * #

EmitXml EmptyLine Source # 
type Rep EmptyLine Source # 
type Rep EmptyLine = D1 * (MetaData "EmptyLine" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "EmptyLine" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "emptyLineLineShape") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe LineShape))) ((:*:) * (S1 * (MetaSel (Just Symbol "emptyLineLineType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe LineType))) (S1 * (MetaSel (Just Symbol "emptyLineDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))))) ((:*:) * (S1 * (MetaSel (Just Symbol "emptyLineDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "emptyLineRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "emptyLineRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "emptyLineFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) ((:*:) * (S1 * (MetaSel (Just Symbol "emptyLineFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))) (S1 * (MetaSel (Just Symbol "emptyLineFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))))) ((:*:) * (S1 * (MetaSel (Just Symbol "emptyLineFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) ((:*:) * (S1 * (MetaSel (Just Symbol "emptyLineColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) (S1 * (MetaSel (Just Symbol "emptyLinePlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe AboveBelow))))))))

mkEmptyLine :: EmptyLine Source #

Smart constructor for EmptyLine

data EmptyPlacement Source #

empty-placement (complex)

The empty-placement type represents an empty element with print-style and placement attributes.

Constructors

EmptyPlacement 

Fields

Instances

Eq EmptyPlacement Source # 
Show EmptyPlacement Source # 
Generic EmptyPlacement Source # 

Associated Types

type Rep EmptyPlacement :: * -> * #

EmitXml EmptyPlacement Source # 
type Rep EmptyPlacement Source # 
type Rep EmptyPlacement = D1 * (MetaData "EmptyPlacement" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "EmptyPlacement" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "emptyPlacementDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "emptyPlacementDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "emptyPlacementRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "emptyPlacementRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "emptyPlacementFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "emptyPlacementFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))) (S1 * (MetaSel (Just Symbol "emptyPlacementFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize)))) ((:*:) * (S1 * (MetaSel (Just Symbol "emptyPlacementFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) ((:*:) * (S1 * (MetaSel (Just Symbol "emptyPlacementColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) (S1 * (MetaSel (Just Symbol "emptyPlacementPlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe AboveBelow))))))))

data EmptyPrintStyle Source #

empty-print-style (complex)

The empty-print-style type represents an empty element with print-style attributes.

Constructors

EmptyPrintStyle 

Fields

Instances

Eq EmptyPrintStyle Source # 
Show EmptyPrintStyle Source # 
Generic EmptyPrintStyle Source # 
EmitXml EmptyPrintStyle Source # 
type Rep EmptyPrintStyle Source # 
type Rep EmptyPrintStyle = D1 * (MetaData "EmptyPrintStyle" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "EmptyPrintStyle" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "emptyPrintStyleDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "emptyPrintStyleDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "emptyPrintStyleRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "emptyPrintStyleRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "emptyPrintStyleFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) (S1 * (MetaSel (Just Symbol "emptyPrintStyleFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle)))) ((:*:) * (S1 * (MetaSel (Just Symbol "emptyPrintStyleFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) ((:*:) * (S1 * (MetaSel (Just Symbol "emptyPrintStyleFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) (S1 * (MetaSel (Just Symbol "emptyPrintStyleColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))))))))

data EmptyTrillSound Source #

empty-trill-sound (complex)

The empty-trill-sound type represents an empty element with print-style, placement, and trill-sound attributes.

Constructors

EmptyTrillSound 

Fields

Instances

Eq EmptyTrillSound Source # 
Show EmptyTrillSound Source # 
Generic EmptyTrillSound Source # 
EmitXml EmptyTrillSound Source # 
type Rep EmptyTrillSound Source # 
type Rep EmptyTrillSound = D1 * (MetaData "EmptyTrillSound" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "EmptyTrillSound" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "emptyTrillSoundDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "emptyTrillSoundDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "emptyTrillSoundRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "emptyTrillSoundRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "emptyTrillSoundFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) (S1 * (MetaSel (Just Symbol "emptyTrillSoundFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle)))) ((:*:) * (S1 * (MetaSel (Just Symbol "emptyTrillSoundFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) (S1 * (MetaSel (Just Symbol "emptyTrillSoundFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "emptyTrillSoundColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) (S1 * (MetaSel (Just Symbol "emptyTrillSoundPlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe AboveBelow)))) ((:*:) * (S1 * (MetaSel (Just Symbol "emptyTrillSoundStartNote") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe StartNote))) (S1 * (MetaSel (Just Symbol "emptyTrillSoundTrillStep") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe TrillStep))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "emptyTrillSoundTwoNoteTurn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe TwoNoteTurn))) (S1 * (MetaSel (Just Symbol "emptyTrillSoundAccelerate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo)))) ((:*:) * (S1 * (MetaSel (Just Symbol "emptyTrillSoundBeats") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe TrillBeats))) ((:*:) * (S1 * (MetaSel (Just Symbol "emptyTrillSoundSecondBeat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Percent))) (S1 * (MetaSel (Just Symbol "emptyTrillSoundLastBeat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Percent)))))))))

data Encoding Source #

encoding (complex)

The encoding element contains information about who did the digital encoding, when, with what software, and in what aspects. Standard type values for the encoder element are music, words, and arrangement, but other types may be used. The type attribute is only needed when there are multiple encoder elements.

Constructors

Encoding 

Instances

Eq Encoding Source # 
Show Encoding Source # 
Generic Encoding Source # 

Associated Types

type Rep Encoding :: * -> * #

Methods

from :: Encoding -> Rep Encoding x #

to :: Rep Encoding x -> Encoding #

EmitXml Encoding Source # 
type Rep Encoding Source # 
type Rep Encoding = D1 * (MetaData "Encoding" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Encoding" PrefixI True) (S1 * (MetaSel (Just Symbol "encodingEncoding") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ChxEncoding])))

mkEncoding :: Encoding Source #

Smart constructor for Encoding

data Ending Source #

ending (complex)

The ending type represents multiple (e.g. first and second) endings. Typically, the start type is associated with the left barline of the first measure in an ending. The stop and discontinue types are associated with the right barline of the last measure in an ending. Stop is used when the ending mark concludes with a downward jog, as is typical for first endings. Discontinue is used when there is no downward jog, as is typical for second endings that do not conclude a piece. The length of the jog can be specified using the end-length attribute. The text-x and text-y attributes are offsets that specify where the baseline of the start of the ending text appears, relative to the start of the ending line.

The number attribute reflects the numeric values of what is under the ending line. Single endings such as "1" or comma-separated multiple endings such as "1,2" may be used. The ending element text is used when the text displayed in the ending is different than what appears in the number attribute. The print-object element is used to indicate when an ending is present but not printed, as is often the case for many parts in a full score.

Constructors

Ending 

Fields

Instances

Eq Ending Source # 

Methods

(==) :: Ending -> Ending -> Bool #

(/=) :: Ending -> Ending -> Bool #

Show Ending Source # 
Generic Ending Source # 

Associated Types

type Rep Ending :: * -> * #

Methods

from :: Ending -> Rep Ending x #

to :: Rep Ending x -> Ending #

EmitXml Ending Source # 
type Rep Ending Source # 
type Rep Ending = D1 * (MetaData "Ending" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Ending" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "endingString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "cmpendingNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EndingNumber))) ((:*:) * (S1 * (MetaSel (Just Symbol "endingType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * StartStopDiscontinue)) (S1 * (MetaSel (Just Symbol "endingEndLength") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "endingTextX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "endingTextY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "endingPrintObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))) (S1 * (MetaSel (Just Symbol "endingDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "endingDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "endingRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "endingRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "endingFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "endingFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))) (S1 * (MetaSel (Just Symbol "endingFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize)))) ((:*:) * (S1 * (MetaSel (Just Symbol "endingFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) (S1 * (MetaSel (Just Symbol "endingColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))))))))

data Extend Source #

extend (complex)

The extend type represents word extensions for lyrics.

Constructors

Extend 

Fields

mkExtend :: Extend Source #

Smart constructor for Extend

data Feature Source #

feature (complex)

The feature type is a part of the grouping element used for musical analysis. The type attribute represents the type of the feature and the element content represents its value. This type is flexible to allow for different analyses.

Constructors

Feature 

Fields

Instances

Eq Feature Source # 

Methods

(==) :: Feature -> Feature -> Bool #

(/=) :: Feature -> Feature -> Bool #

Show Feature Source # 
Generic Feature Source # 

Associated Types

type Rep Feature :: * -> * #

Methods

from :: Feature -> Rep Feature x #

to :: Rep Feature x -> Feature #

EmitXml Feature Source # 
type Rep Feature Source # 
type Rep Feature = D1 * (MetaData "Feature" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Feature" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "featureString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "featureType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Token)))))

mkFeature :: String -> Feature Source #

Smart constructor for Feature

data Fermata Source #

fermata (complex)

The fermata text content represents the shape of the fermata sign. An empty fermata element represents a normal fermata. The fermata type is upright if not specified.

Constructors

Fermata 

Fields

Instances

Eq Fermata Source # 

Methods

(==) :: Fermata -> Fermata -> Bool #

(/=) :: Fermata -> Fermata -> Bool #

Show Fermata Source # 
Generic Fermata Source # 

Associated Types

type Rep Fermata :: * -> * #

Methods

from :: Fermata -> Rep Fermata x #

to :: Rep Fermata x -> Fermata #

EmitXml Fermata Source # 
type Rep Fermata Source # 
type Rep Fermata = D1 * (MetaData "Fermata" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Fermata" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "fermataFermataShape") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FermataShape)) (S1 * (MetaSel (Just Symbol "fermataType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe UprightInverted)))) ((:*:) * (S1 * (MetaSel (Just Symbol "fermataDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "fermataDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "fermataRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "fermataRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "fermataFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) (S1 * (MetaSel (Just Symbol "fermataFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))))) ((:*:) * (S1 * (MetaSel (Just Symbol "fermataFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) ((:*:) * (S1 * (MetaSel (Just Symbol "fermataFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) (S1 * (MetaSel (Just Symbol "fermataColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))))))))

mkFermata :: FermataShape -> Fermata Source #

Smart constructor for Fermata

data Figure Source #

figure (complex)

The figure type represents a single figure within a figured-bass element.

Constructors

Figure 

Fields

Instances

Eq Figure Source # 

Methods

(==) :: Figure -> Figure -> Bool #

(/=) :: Figure -> Figure -> Bool #

Show Figure Source # 
Generic Figure Source # 

Associated Types

type Rep Figure :: * -> * #

Methods

from :: Figure -> Rep Figure x #

to :: Rep Figure x -> Figure #

EmitXml Figure Source # 
type Rep Figure Source # 
type Rep Figure = D1 * (MetaData "Figure" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Figure" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "figurePrefix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe StyleText))) (S1 * (MetaSel (Just Symbol "figureFigureNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe StyleText)))) ((:*:) * (S1 * (MetaSel (Just Symbol "figureSuffix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe StyleText))) (S1 * (MetaSel (Just Symbol "figureExtend") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Extend))))))

mkFigure :: Figure Source #

Smart constructor for Figure

data FiguredBass Source #

figured-bass (complex)

The figured-bass element represents figured bass notation. Figured bass elements take their position from the first regular note that follows. Figures are ordered from top to bottom. The value of parentheses is "no" if not present.

Constructors

FiguredBass 

Fields

Instances

Eq FiguredBass Source # 
Show FiguredBass Source # 
Generic FiguredBass Source # 

Associated Types

type Rep FiguredBass :: * -> * #

EmitXml FiguredBass Source # 
type Rep FiguredBass Source # 
type Rep FiguredBass = D1 * (MetaData "FiguredBass" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "FiguredBass" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "figuredBassParentheses") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))) (S1 * (MetaSel (Just Symbol "figuredBassDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "figuredBassDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "figuredBassRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "figuredBassRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "figuredBassFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText)))) ((:*:) * (S1 * (MetaSel (Just Symbol "figuredBassFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))) (S1 * (MetaSel (Just Symbol "figuredBassFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "figuredBassFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) (S1 * (MetaSel (Just Symbol "figuredBassColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color)))) ((:*:) * (S1 * (MetaSel (Just Symbol "figuredBassPrintDot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))) (S1 * (MetaSel (Just Symbol "figuredBassPrintLyric") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "figuredBassPrintObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))) (S1 * (MetaSel (Just Symbol "figuredBassPrintSpacing") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo)))) ((:*:) * (S1 * (MetaSel (Just Symbol "figuredBassFigure") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Figure])) ((:*:) * (S1 * (MetaSel (Just Symbol "figuredBassDuration") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Duration))) (S1 * (MetaSel (Just Symbol "figuredBassEditorial") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Editorial))))))))

data Fingering Source #

fingering (complex)

Fingering is typically indicated 1,2,3,4,5. Multiple fingerings may be given, typically to substitute fingerings in the middle of a note. The substitution and alternate values are "no" if the attribute is not present. For guitar and other fretted instruments, the fingering element represents the fretting finger; the pluck element represents the plucking finger.

Constructors

Fingering 

Fields

Instances

Eq Fingering Source # 
Show Fingering Source # 
Generic Fingering Source # 

Associated Types

type Rep Fingering :: * -> * #

EmitXml Fingering Source # 
type Rep Fingering Source # 
type Rep Fingering = D1 * (MetaData "Fingering" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Fingering" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "fingeringString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) ((:*:) * (S1 * (MetaSel (Just Symbol "fingeringSubstitution") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))) (S1 * (MetaSel (Just Symbol "fingeringAlternate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))))) ((:*:) * (S1 * (MetaSel (Just Symbol "fingeringDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "fingeringDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "fingeringRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "fingeringRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "fingeringFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) (S1 * (MetaSel (Just Symbol "fingeringFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "fingeringFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) (S1 * (MetaSel (Just Symbol "fingeringFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight)))) ((:*:) * (S1 * (MetaSel (Just Symbol "fingeringColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) (S1 * (MetaSel (Just Symbol "fingeringPlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe AboveBelow))))))))

mkFingering :: String -> Fingering Source #

Smart constructor for Fingering

data FirstFret Source #

first-fret (complex)

The first-fret type indicates which fret is shown in the top space of the frame; it is fret 1 if the element is not present. The optional text attribute indicates how this is represented in the fret diagram, while the location attribute indicates whether the text appears to the left or right of the frame.

Constructors

FirstFret 

Fields

Instances

Eq FirstFret Source # 
Show FirstFret Source # 
Generic FirstFret Source # 

Associated Types

type Rep FirstFret :: * -> * #

EmitXml FirstFret Source # 
type Rep FirstFret Source # 
type Rep FirstFret = D1 * (MetaData "FirstFret" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "FirstFret" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "firstFretPositiveInteger") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PositiveInteger)) ((:*:) * (S1 * (MetaSel (Just Symbol "firstFretText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Token))) (S1 * (MetaSel (Just Symbol "firstFretLocation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe LeftRight))))))

data FormattedText Source #

formatted-text (complex)

The formatted-text type represents a text element with text-formatting attributes.

Constructors

FormattedText 

Instances

Eq FormattedText Source # 
Show FormattedText Source # 
Generic FormattedText Source # 

Associated Types

type Rep FormattedText :: * -> * #

EmitXml FormattedText Source # 
type Rep FormattedText Source # 
type Rep FormattedText = D1 * (MetaData "FormattedText" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "FormattedText" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "formattedTextString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "formattedTextLang") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Lang)))) ((:*:) * (S1 * (MetaSel (Just Symbol "formattedTextEnclosure") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Enclosure))) ((:*:) * (S1 * (MetaSel (Just Symbol "formattedTextJustify") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe LeftCenterRight))) (S1 * (MetaSel (Just Symbol "formattedTextHalign") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe LeftCenterRight)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "formattedTextValign") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Valign))) ((:*:) * (S1 * (MetaSel (Just Symbol "formattedTextDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "formattedTextDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))))) ((:*:) * (S1 * (MetaSel (Just Symbol "formattedTextRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "formattedTextRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "formattedTextFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "formattedTextFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))) (S1 * (MetaSel (Just Symbol "formattedTextFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize)))) ((:*:) * (S1 * (MetaSel (Just Symbol "formattedTextFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) ((:*:) * (S1 * (MetaSel (Just Symbol "formattedTextColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) (S1 * (MetaSel (Just Symbol "formattedTextUnderline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NumberOfLines)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "formattedTextOverline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NumberOfLines))) ((:*:) * (S1 * (MetaSel (Just Symbol "formattedTextLineThrough") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NumberOfLines))) (S1 * (MetaSel (Just Symbol "formattedTextRotation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe RotationDegrees))))) ((:*:) * (S1 * (MetaSel (Just Symbol "formattedTextLetterSpacing") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NumberOrNormal))) ((:*:) * (S1 * (MetaSel (Just Symbol "formattedTextLineHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NumberOrNormal))) (S1 * (MetaSel (Just Symbol "formattedTextDir") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe TextDirection)))))))))

data Forward Source #

forward (complex)

The backup and forward elements are required to coordinate multiple voices in one part, including music on multiple staves. The forward element is generally used within voices and staves. Duration values should always be positive, and should not cross measure boundaries.

Instances

Eq Forward Source # 

Methods

(==) :: Forward -> Forward -> Bool #

(/=) :: Forward -> Forward -> Bool #

Show Forward Source # 
Generic Forward Source # 

Associated Types

type Rep Forward :: * -> * #

Methods

from :: Forward -> Rep Forward x #

to :: Rep Forward x -> Forward #

EmitXml Forward Source # 
type Rep Forward Source # 
type Rep Forward = D1 * (MetaData "Forward" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Forward" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "forwardDuration") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Duration)) ((:*:) * (S1 * (MetaSel (Just Symbol "forwardEditorialVoice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EditorialVoice)) (S1 * (MetaSel (Just Symbol "forwardStaff") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Staff))))))

mkForward :: Duration -> EditorialVoice -> Forward Source #

Smart constructor for Forward

data Frame Source #

frame (complex)

The frame type represents a frame or fretboard diagram used together with a chord symbol. The representation is based on the NIFF guitar grid with additional information.

Constructors

Frame 

Fields

Instances

Eq Frame Source # 

Methods

(==) :: Frame -> Frame -> Bool #

(/=) :: Frame -> Frame -> Bool #

Show Frame Source # 

Methods

showsPrec :: Int -> Frame -> ShowS #

show :: Frame -> String #

showList :: [Frame] -> ShowS #

Generic Frame Source # 

Associated Types

type Rep Frame :: * -> * #

Methods

from :: Frame -> Rep Frame x #

to :: Rep Frame x -> Frame #

EmitXml Frame Source # 

Methods

emitXml :: Frame -> XmlRep Source #

type Rep Frame Source # 
type Rep Frame = D1 * (MetaData "Frame" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Frame" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "frameHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "frameWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "frameDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))))) ((:*:) * (S1 * (MetaSel (Just Symbol "frameDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "frameRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "frameRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "frameColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) ((:*:) * (S1 * (MetaSel (Just Symbol "frameHalign") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe LeftCenterRight))) (S1 * (MetaSel (Just Symbol "frameValign") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Valign))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "frameFrameStrings") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PositiveInteger)) (S1 * (MetaSel (Just Symbol "frameFrameFrets") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PositiveInteger))) ((:*:) * (S1 * (MetaSel (Just Symbol "frameFirstFret") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FirstFret))) (S1 * (MetaSel (Just Symbol "frameFrameNote") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [FrameNote])))))))

mkFrame :: PositiveInteger -> PositiveInteger -> Frame Source #

Smart constructor for Frame

data FrameNote Source #

frame-note (complex)

The frame-note type represents each note included in the frame. An open string will have a fret value of 0, while a muted string will not be associated with a frame-note element.

Constructors

FrameNote 

Fields

mkFrameNote :: CmpString -> Fret -> FrameNote Source #

Smart constructor for FrameNote

data Fret Source #

fret (complex)

The fret element is used with tablature notation and chord diagrams. Fret numbers start with 0 for an open string and 1 for the first fret.

Constructors

Fret 

Fields

mkFret :: NonNegativeInteger -> Fret Source #

Smart constructor for Fret

data Glissando Source #

glissando (complex)

Glissando and slide types both indicate rapidly moving from one pitch to the other so that individual notes are not discerned. The distinction is similar to that between NIFF's glissando and portamento elements. A glissando sounds the half notes in between the slide and defaults to a wavy line. The optional text is printed alongside the line.

Constructors

Glissando 

Fields

Instances

Eq Glissando Source # 
Show Glissando Source # 
Generic Glissando Source # 

Associated Types

type Rep Glissando :: * -> * #

EmitXml Glissando Source # 
type Rep Glissando Source # 
type Rep Glissando = D1 * (MetaData "Glissando" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Glissando" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "glissandoString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) ((:*:) * (S1 * (MetaSel (Just Symbol "glissandoType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * StartStop)) (S1 * (MetaSel (Just Symbol "glissandoNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NumberLevel))))) ((:*:) * (S1 * (MetaSel (Just Symbol "glissandoLineType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe LineType))) ((:*:) * (S1 * (MetaSel (Just Symbol "glissandoDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "glissandoDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "glissandoRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "glissandoRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "glissandoFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "glissandoFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))) (S1 * (MetaSel (Just Symbol "glissandoFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize)))) ((:*:) * (S1 * (MetaSel (Just Symbol "glissandoFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) (S1 * (MetaSel (Just Symbol "glissandoColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))))))))

mkGlissando :: String -> StartStop -> Glissando Source #

Smart constructor for Glissando

data Grace Source #

grace (complex)

The grace type indicates the presence of a grace note. The slash attribute for a grace note is yes for slashed eighth notes. The other grace note attributes come from MuseData sound suggestions. Steal-time-previous indicates the percentage of time to steal from the previous note for the grace note. Steal-time-following indicates the percentage of time to steal from the following note for the grace note. Make-time indicates to make time, not steal time; the units are in real-time divisions for the grace note.

Constructors

Grace 

Fields

Instances

Eq Grace Source # 

Methods

(==) :: Grace -> Grace -> Bool #

(/=) :: Grace -> Grace -> Bool #

Show Grace Source # 

Methods

showsPrec :: Int -> Grace -> ShowS #

show :: Grace -> String #

showList :: [Grace] -> ShowS #

Generic Grace Source # 

Associated Types

type Rep Grace :: * -> * #

Methods

from :: Grace -> Rep Grace x #

to :: Rep Grace x -> Grace #

EmitXml Grace Source # 

Methods

emitXml :: Grace -> XmlRep Source #

type Rep Grace Source # 
type Rep Grace = D1 * (MetaData "Grace" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Grace" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "graceStealTimePrevious") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Percent))) (S1 * (MetaSel (Just Symbol "graceStealTimeFollowing") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Percent)))) ((:*:) * (S1 * (MetaSel (Just Symbol "graceMakeTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Divisions))) (S1 * (MetaSel (Just Symbol "graceSlash") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))))))

mkGrace :: Grace Source #

Smart constructor for Grace

data GroupBarline Source #

group-barline (complex)

The group-barline type indicates if the group should have common barlines.

Instances

Eq GroupBarline Source # 
Show GroupBarline Source # 
Generic GroupBarline Source # 

Associated Types

type Rep GroupBarline :: * -> * #

EmitXml GroupBarline Source # 
type Rep GroupBarline Source # 
type Rep GroupBarline = D1 * (MetaData "GroupBarline" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "GroupBarline" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "groupBarlineGroupBarlineValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * GroupBarlineValue)) (S1 * (MetaSel (Just Symbol "groupBarlineColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color)))))

data GroupName Source #

group-name (complex)

The group-name type describes the name or abbreviation of a part-group element. Formatting attributes in the group-name type are deprecated in Version 2.0 in favor of the new group-name-display and group-abbreviation-display elements.

Constructors

GroupName 

Fields

Instances

Eq GroupName Source # 
Show GroupName Source # 
Generic GroupName Source # 

Associated Types

type Rep GroupName :: * -> * #

EmitXml GroupName Source # 
type Rep GroupName Source # 
type Rep GroupName = D1 * (MetaData "GroupName" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "GroupName" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "groupNameString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "groupNameDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "groupNameDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "groupNameRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "groupNameRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "groupNameFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) ((:*:) * (S1 * (MetaSel (Just Symbol "groupNameFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))) (S1 * (MetaSel (Just Symbol "groupNameFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))))) ((:*:) * (S1 * (MetaSel (Just Symbol "groupNameFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) ((:*:) * (S1 * (MetaSel (Just Symbol "groupNameColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) (S1 * (MetaSel (Just Symbol "groupNameJustify") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe LeftCenterRight))))))))

mkGroupName :: String -> GroupName Source #

Smart constructor for GroupName

data GroupSymbol Source #

group-symbol (complex)

The group-symbol type indicates how the symbol for a group is indicated in the score.

Constructors

GroupSymbol 

Fields

Instances

Eq GroupSymbol Source # 
Show GroupSymbol Source # 
Generic GroupSymbol Source # 

Associated Types

type Rep GroupSymbol :: * -> * #

EmitXml GroupSymbol Source # 
type Rep GroupSymbol Source # 
type Rep GroupSymbol = D1 * (MetaData "GroupSymbol" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "GroupSymbol" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "groupSymbolGroupSymbolValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * GroupSymbolValue)) ((:*:) * (S1 * (MetaSel (Just Symbol "groupSymbolDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "groupSymbolDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))))) ((:*:) * (S1 * (MetaSel (Just Symbol "groupSymbolRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "groupSymbolRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "groupSymbolColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color)))))))

data Grouping Source #

grouping (complex)

The grouping type is used for musical analysis. When the type attribute is "start" or "single", it usually contains one or more feature elements. The number attribute is used for distinguishing between overlapping and hierarchical groupings. The member-of attribute allows for easy distinguishing of what grouping elements are in what hierarchy. Feature elements contained within a "stop" type of grouping may be ignored.

This element is flexible to allow for different types of analyses. Future versions of the MusicXML format may add elements that can represent more standardized categories of analysis data, allowing for easier data sharing.

Constructors

Grouping 

Fields

Instances

mkGrouping :: StartStopSingle -> Grouping Source #

Smart constructor for Grouping

data HammerOnPullOff Source #

hammer-on-pull-off (complex)

The hammer-on and pull-off elements are used in guitar and fretted instrument notation. Since a single slur can be marked over many notes, the hammer-on and pull-off elements are separate so the individual pair of notes can be specified. The element content can be used to specify how the hammer-on or pull-off should be notated. An empty element leaves this choice up to the application.

Constructors

HammerOnPullOff 

Instances

Eq HammerOnPullOff Source # 
Show HammerOnPullOff Source # 
Generic HammerOnPullOff Source # 
EmitXml HammerOnPullOff Source # 
type Rep HammerOnPullOff Source # 
type Rep HammerOnPullOff = D1 * (MetaData "HammerOnPullOff" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "HammerOnPullOff" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "hammerOnPullOffString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) ((:*:) * (S1 * (MetaSel (Just Symbol "hammerOnPullOffType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * StartStop)) (S1 * (MetaSel (Just Symbol "hammerOnPullOffNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NumberLevel))))) ((:*:) * (S1 * (MetaSel (Just Symbol "hammerOnPullOffDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "hammerOnPullOffDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "hammerOnPullOffRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "hammerOnPullOffRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "hammerOnPullOffFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) (S1 * (MetaSel (Just Symbol "hammerOnPullOffFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "hammerOnPullOffFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) (S1 * (MetaSel (Just Symbol "hammerOnPullOffFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight)))) ((:*:) * (S1 * (MetaSel (Just Symbol "hammerOnPullOffColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) (S1 * (MetaSel (Just Symbol "hammerOnPullOffPlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe AboveBelow))))))))

data Harmonic Source #

harmonic (complex)

The harmonic type indicates natural and artificial harmonics. Allowing the type of pitch to be specified, combined with controls for appearance/playback differences, allows both the notation and the sound to be represented. Artificial harmonics can add a notated touching-pitch; artificial pinch harmonics will usually not notate a touching pitch. The attributes for the harmonic element refer to the use of the circular harmonic symbol, typically but not always used with natural harmonics.

Constructors

Harmonic 

Fields

Instances

Eq Harmonic Source # 
Show Harmonic Source # 
Generic Harmonic Source # 

Associated Types

type Rep Harmonic :: * -> * #

Methods

from :: Harmonic -> Rep Harmonic x #

to :: Rep Harmonic x -> Harmonic #

EmitXml Harmonic Source # 
type Rep Harmonic Source # 
type Rep Harmonic = D1 * (MetaData "Harmonic" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Harmonic" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "harmonicPrintObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))) ((:*:) * (S1 * (MetaSel (Just Symbol "harmonicDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "harmonicDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))))) ((:*:) * (S1 * (MetaSel (Just Symbol "harmonicRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "harmonicRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "harmonicFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "harmonicFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))) ((:*:) * (S1 * (MetaSel (Just Symbol "harmonicFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) (S1 * (MetaSel (Just Symbol "harmonicFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "harmonicColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) (S1 * (MetaSel (Just Symbol "harmonicPlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe AboveBelow)))) ((:*:) * (S1 * (MetaSel (Just Symbol "harmonicHarmonic") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe ChxHarmonic))) (S1 * (MetaSel (Just Symbol "harmonicHarmonic1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe ChxHarmonic1))))))))

mkHarmonic :: Harmonic Source #

Smart constructor for Harmonic

data Harmony Source #

harmony (complex)

The harmony type is based on Humdrum's **harm encoding, extended to support chord symbols in popular music as well as functional harmony analysis in classical music.

If there are alternate harmonies possible, this can be specified using multiple harmony elements differentiated by type. Explicit harmonies have all note present in the music; implied have some notes missing but implied; alternate represents alternate analyses.

The harmony object may be used for analysis or for chord symbols. The print-object attribute controls whether or not anything is printed due to the harmony element. The print-frame attribute controls printing of a frame or fretboard diagram. The print-style attribute group sets the default for the harmony, but individual elements can override this with their own print-style values.

Constructors

Harmony 

Fields

Instances

Eq Harmony Source # 

Methods

(==) :: Harmony -> Harmony -> Bool #

(/=) :: Harmony -> Harmony -> Bool #

Show Harmony Source # 
Generic Harmony Source # 

Associated Types

type Rep Harmony :: * -> * #

Methods

from :: Harmony -> Rep Harmony x #

to :: Rep Harmony x -> Harmony #

EmitXml Harmony Source # 
type Rep Harmony Source # 
type Rep Harmony = D1 * (MetaData "Harmony" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Harmony" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "harmonyType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe HarmonyType))) (S1 * (MetaSel (Just Symbol "harmonyPrintFrame") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo)))) ((:*:) * (S1 * (MetaSel (Just Symbol "harmonyPrintObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))) (S1 * (MetaSel (Just Symbol "harmonyDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "harmonyDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "harmonyRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "harmonyRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "harmonyFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) (S1 * (MetaSel (Just Symbol "harmonyFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "harmonyFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) (S1 * (MetaSel (Just Symbol "harmonyFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight)))) ((:*:) * (S1 * (MetaSel (Just Symbol "harmonyColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) (S1 * (MetaSel (Just Symbol "harmonyPlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe AboveBelow))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "harmonyHarmonyChord") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [HarmonyChord])) (S1 * (MetaSel (Just Symbol "harmonyFrame") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Frame)))) ((:*:) * (S1 * (MetaSel (Just Symbol "harmonyOffset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Offset))) ((:*:) * (S1 * (MetaSel (Just Symbol "harmonyEditorial") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Editorial)) (S1 * (MetaSel (Just Symbol "harmonyStaff") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Staff)))))))))

mkHarmony :: Editorial -> Harmony Source #

Smart constructor for Harmony

data HarpPedals Source #

harp-pedals (complex)

The harp-pedals type is used to create harp pedal diagrams. The pedal-step and pedal-alter elements use the same values as the step and alter elements. For easiest reading, the pedal-tuning elements should follow standard harp pedal order, with pedal-step values of D, C, B, E, F, G, and A.

Constructors

HarpPedals 

Fields

Instances

Eq HarpPedals Source # 
Show HarpPedals Source # 
Generic HarpPedals Source # 

Associated Types

type Rep HarpPedals :: * -> * #

EmitXml HarpPedals Source # 
type Rep HarpPedals Source # 
type Rep HarpPedals = D1 * (MetaData "HarpPedals" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "HarpPedals" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "harpPedalsDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "harpPedalsDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "harpPedalsRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "harpPedalsRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "harpPedalsFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "harpPedalsFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))) (S1 * (MetaSel (Just Symbol "harpPedalsFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize)))) ((:*:) * (S1 * (MetaSel (Just Symbol "harpPedalsFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) ((:*:) * (S1 * (MetaSel (Just Symbol "harpPedalsColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) (S1 * (MetaSel (Just Symbol "harpPedalsPedalTuning") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [PedalTuning])))))))

mkHarpPedals :: HarpPedals Source #

Smart constructor for HarpPedals

data HeelToe Source #

heel-toe (complex)

The heel and toe elements are used with organ pedals. The substitution value is "no" if the attribute is not present.

Constructors

HeelToe 

Fields

Instances

Eq HeelToe Source # 

Methods

(==) :: HeelToe -> HeelToe -> Bool #

(/=) :: HeelToe -> HeelToe -> Bool #

Show HeelToe Source # 
Generic HeelToe Source # 

Associated Types

type Rep HeelToe :: * -> * #

Methods

from :: HeelToe -> Rep HeelToe x #

to :: Rep HeelToe x -> HeelToe #

EmitXml HeelToe Source # 
type Rep HeelToe Source # 
type Rep HeelToe = D1 * (MetaData "HeelToe" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "HeelToe" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "heelToeEmptyPlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * HeelToe)) (S1 * (MetaSel (Just Symbol "heelToeSubstitution") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo)))))

mkHeelToe :: HeelToe -> HeelToe Source #

Smart constructor for HeelToe

data Identification Source #

identification (complex)

Identification contains basic metadata about the score. It includes the information in MuseData headers that may apply at a score-wide, movement-wide, or part-wide level. The creator, rights, source, and relation elements are based on Dublin Core.

Constructors

Identification 

Fields

Instances

Eq Identification Source # 
Show Identification Source # 
Generic Identification Source # 

Associated Types

type Rep Identification :: * -> * #

EmitXml Identification Source # 
type Rep Identification Source # 
type Rep Identification = D1 * (MetaData "Identification" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Identification" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "identificationCreator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [TypedText])) ((:*:) * (S1 * (MetaSel (Just Symbol "identificationRights") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [TypedText])) (S1 * (MetaSel (Just Symbol "identificationEncoding") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Encoding))))) ((:*:) * (S1 * (MetaSel (Just Symbol "identificationSource") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe String))) ((:*:) * (S1 * (MetaSel (Just Symbol "identificationRelation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [TypedText])) (S1 * (MetaSel (Just Symbol "identificationMiscellaneous") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Miscellaneous)))))))

data Image Source #

image (complex)

The image type is used to include graphical images in a score.

Constructors

Image 

Fields

Instances

Eq Image Source # 

Methods

(==) :: Image -> Image -> Bool #

(/=) :: Image -> Image -> Bool #

Show Image Source # 

Methods

showsPrec :: Int -> Image -> ShowS #

show :: Image -> String #

showList :: [Image] -> ShowS #

Generic Image Source # 

Associated Types

type Rep Image :: * -> * #

Methods

from :: Image -> Rep Image x #

to :: Rep Image x -> Image #

EmitXml Image Source # 

Methods

emitXml :: Image -> XmlRep Source #

type Rep Image Source # 

mkImage :: String -> Token -> Image Source #

Smart constructor for Image

data Instrument Source #

instrument (complex)

The instrument type distinguishes between score-instrument elements in a score-part. The id attribute is an IDREF back to the score-instrument ID. If multiple score-instruments are specified on a score-part, there should be an instrument element for each note in the part.

Constructors

Instrument 

Fields

Instances

Eq Instrument Source # 
Show Instrument Source # 
Generic Instrument Source # 

Associated Types

type Rep Instrument :: * -> * #

EmitXml Instrument Source # 
type Rep Instrument Source # 
type Rep Instrument = D1 * (MetaData "Instrument" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Instrument" PrefixI True) (S1 * (MetaSel (Just Symbol "instrumentId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * IDREF)))

mkInstrument :: IDREF -> Instrument Source #

Smart constructor for Instrument

data Inversion Source #

inversion (complex)

The inversion type represents harmony inversions. The value is a number indicating which inversion is used: 0 for root position, 1 for first inversion, etc.

Constructors

Inversion 

Fields

Instances

Eq Inversion Source # 
Show Inversion Source # 
Generic Inversion Source # 

Associated Types

type Rep Inversion :: * -> * #

EmitXml Inversion Source # 
type Rep Inversion Source # 
type Rep Inversion = D1 * (MetaData "Inversion" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Inversion" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "inversionNonNegativeInteger") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NonNegativeInteger)) (S1 * (MetaSel (Just Symbol "inversionDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "inversionDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "inversionRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "inversionRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "inversionFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) (S1 * (MetaSel (Just Symbol "inversionFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle)))) ((:*:) * (S1 * (MetaSel (Just Symbol "inversionFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) ((:*:) * (S1 * (MetaSel (Just Symbol "inversionFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) (S1 * (MetaSel (Just Symbol "inversionColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))))))))

data Key Source #

key (complex)

The key type represents a key signature. Both traditional and non-traditional key signatures are supported. The optional number attribute refers to staff numbers. If absent, the key signature applies to all staves in the part.

Constructors

Key 

Fields

Instances

Eq Key Source # 

Methods

(==) :: Key -> Key -> Bool #

(/=) :: Key -> Key -> Bool #

Show Key Source # 

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Generic Key Source # 

Associated Types

type Rep Key :: * -> * #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

EmitXml Key Source # 

Methods

emitXml :: Key -> XmlRep Source #

type Rep Key Source # 
type Rep Key = D1 * (MetaData "Key" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Key" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "keyNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe StaffNumber))) ((:*:) * (S1 * (MetaSel (Just Symbol "keyDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "keyDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))))) ((:*:) * (S1 * (MetaSel (Just Symbol "keyRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "keyRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "keyFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "keyFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))) ((:*:) * (S1 * (MetaSel (Just Symbol "keyFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) (S1 * (MetaSel (Just Symbol "keyFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "keyColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) (S1 * (MetaSel (Just Symbol "keyPrintObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo)))) ((:*:) * (S1 * (MetaSel (Just Symbol "keyKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ChxKey)) (S1 * (MetaSel (Just Symbol "keyKeyOctave") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [KeyOctave])))))))

mkKey :: ChxKey -> Key Source #

Smart constructor for Key

data KeyOctave Source #

key-octave (complex)

The key-octave element specifies in which octave an element of a key signature appears. The content specifies the octave value using the same values as the display-octave element. The number attribute is a positive integer that refers to the key signature element in left-to-right order. If the cancel attribute is set to yes, then this number refers to an element specified by the cancel element. It is no by default.

Constructors

KeyOctave 

Fields

Instances

Eq KeyOctave Source # 
Show KeyOctave Source # 
Generic KeyOctave Source # 

Associated Types

type Rep KeyOctave :: * -> * #

EmitXml KeyOctave Source # 
type Rep KeyOctave Source # 
type Rep KeyOctave = D1 * (MetaData "KeyOctave" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "KeyOctave" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "keyOctaveOctave") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Octave)) ((:*:) * (S1 * (MetaSel (Just Symbol "keyOctaveNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PositiveInteger)) (S1 * (MetaSel (Just Symbol "keyOctaveCancel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))))))

data Kind Source #

kind (complex)

Kind indicates the type of chord. Degree elements can then add, subtract, or alter from these starting points

	
The attributes are used to indicate the formatting of the symbol. Since the kind element is the constant in all the harmony-chord groups that can make up a polychord, many formatting attributes are here.
	
The use-symbols attribute is yes if the kind should be represented when possible with harmony symbols rather than letters and numbers. These symbols include:
	
	major: a triangle, like Unicode 25B3
	minor: -, like Unicode 002D
	augmented: +, like Unicode 002B
	diminished: °, like Unicode 00B0
	half-diminished: ø, like Unicode 00F8
	
The text attribute describes how the kind should be spelled if not using symbols; it is ignored if use-symbols is yes. The stack-degrees attribute is yes if the degree elements should be stacked above each other. The parentheses-degrees attribute is yes if all the degrees should be in parentheses. The bracket-degrees attribute is yes if all the degrees should be in a bracket. If not specified, these values are implementation-specific. The alignment attributes are for the entire harmony-chord group of which this kind element is a part.

Constructors

Kind 

Fields

Instances

Eq Kind Source # 

Methods

(==) :: Kind -> Kind -> Bool #

(/=) :: Kind -> Kind -> Bool #

Show Kind Source # 

Methods

showsPrec :: Int -> Kind -> ShowS #

show :: Kind -> String #

showList :: [Kind] -> ShowS #

Generic Kind Source # 

Associated Types

type Rep Kind :: * -> * #

Methods

from :: Kind -> Rep Kind x #

to :: Rep Kind x -> Kind #

EmitXml Kind Source # 

Methods

emitXml :: Kind -> XmlRep Source #

type Rep Kind Source # 
type Rep Kind = D1 * (MetaData "Kind" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Kind" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "kindKindValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * KindValue)) (S1 * (MetaSel (Just Symbol "kindUseSymbols") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo)))) ((:*:) * (S1 * (MetaSel (Just Symbol "kindText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Token))) (S1 * (MetaSel (Just Symbol "kindStackDegrees") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "kindParenthesesDegrees") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))) (S1 * (MetaSel (Just Symbol "kindBracketDegrees") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo)))) ((:*:) * (S1 * (MetaSel (Just Symbol "kindDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "kindDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "kindRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "kindRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "kindFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) (S1 * (MetaSel (Just Symbol "kindFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "kindFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) (S1 * (MetaSel (Just Symbol "kindFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight)))) ((:*:) * (S1 * (MetaSel (Just Symbol "kindColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) ((:*:) * (S1 * (MetaSel (Just Symbol "kindHalign") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe LeftCenterRight))) (S1 * (MetaSel (Just Symbol "kindValign") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Valign)))))))))

mkKind :: KindValue -> Kind Source #

Smart constructor for Kind

data Level Source #

level (complex)

The level type is used to specify editorial information for different MusicXML elements. If the reference attribute for the level element is yes, this indicates editorial information that is for display only and should not affect playback. For instance, a modern edition of older music may set reference="yes" on the attributes containing the music's original clef, key, and time signature. It is no by default.

Constructors

Level 

Fields

Instances

Eq Level Source # 

Methods

(==) :: Level -> Level -> Bool #

(/=) :: Level -> Level -> Bool #

Show Level Source # 

Methods

showsPrec :: Int -> Level -> ShowS #

show :: Level -> String #

showList :: [Level] -> ShowS #

Generic Level Source # 

Associated Types

type Rep Level :: * -> * #

Methods

from :: Level -> Rep Level x #

to :: Rep Level x -> Level #

EmitXml Level Source # 

Methods

emitXml :: Level -> XmlRep Source #

type Rep Level Source # 

mkLevel :: String -> Level Source #

Smart constructor for Level

data LineWidth Source #

line-width (complex)

The line-width type indicates the width of a line type in tenths. The type attribute defines what type of line is being defined. Values include beam, bracket, dashes, enclosure, ending, extend, heavy barline, leger, light barline, octave shift, pedal, slur middle, slur tip, staff, stem, tie middle, tie tip, tuplet bracket, and wedge. The text content is expressed in tenths.

Constructors

LineWidth 

Fields

Instances

Eq LineWidth Source # 
Show LineWidth Source # 
Generic LineWidth Source # 

Associated Types

type Rep LineWidth :: * -> * #

EmitXml LineWidth Source # 
type Rep LineWidth Source # 
type Rep LineWidth = D1 * (MetaData "LineWidth" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "LineWidth" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "lineWidthTenths") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Tenths)) (S1 * (MetaSel (Just Symbol "cmplineWidthType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * LineWidthType))))

data Link Source #

link (complex)

The link type serves as an outgoing simple XLink. It is also used to connect a MusicXML score with a MusicXML opus.

Constructors

Link 

Fields

mkLink :: String -> Link Source #

Smart constructor for Link

data Lyric Source #

lyric (complex)

The lyric type represents text underlays for lyrics, based on Humdrum with support for other formats. Two text elements that are not separated by an elision element are part of the same syllable, but may have different text formatting. The MusicXML 2.0 XSD is more strict than the 2.0 DTD in enforcing this by disallowing a second syllabic element unless preceded by an elision element. The lyric number indicates multiple lines, though a name can be used as well (as in Finale's verse chorus section specification). Justification is center by default; placement is below by default.

Constructors

Lyric 

Fields

Instances

Eq Lyric Source # 

Methods

(==) :: Lyric -> Lyric -> Bool #

(/=) :: Lyric -> Lyric -> Bool #

Show Lyric Source # 

Methods

showsPrec :: Int -> Lyric -> ShowS #

show :: Lyric -> String #

showList :: [Lyric] -> ShowS #

Generic Lyric Source # 

Associated Types

type Rep Lyric :: * -> * #

Methods

from :: Lyric -> Rep Lyric x #

to :: Rep Lyric x -> Lyric #

EmitXml Lyric Source # 

Methods

emitXml :: Lyric -> XmlRep Source #

type Rep Lyric Source # 
type Rep Lyric = D1 * (MetaData "Lyric" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Lyric" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "lyricNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NMTOKEN))) ((:*:) * (S1 * (MetaSel (Just Symbol "lyricName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Token))) (S1 * (MetaSel (Just Symbol "lyricJustify") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe LeftCenterRight))))) ((:*:) * (S1 * (MetaSel (Just Symbol "lyricDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "lyricDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "lyricRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "lyricRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "lyricPlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe AboveBelow))) (S1 * (MetaSel (Just Symbol "lyricColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "lyricLyric") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ChxLyric)) (S1 * (MetaSel (Just Symbol "lyricEndLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Empty)))) ((:*:) * (S1 * (MetaSel (Just Symbol "lyricEndParagraph") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Empty))) (S1 * (MetaSel (Just Symbol "lyricEditorial") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Editorial)))))))

mkLyric :: ChxLyric -> Editorial -> Lyric Source #

Smart constructor for Lyric

data LyricFont Source #

lyric-font (complex)

The lyric-font type specifies the default font for a particular name and number of lyric.

Constructors

LyricFont 

Fields

Instances

Eq LyricFont Source # 
Show LyricFont Source # 
Generic LyricFont Source # 

Associated Types

type Rep LyricFont :: * -> * #

EmitXml LyricFont Source # 
type Rep LyricFont Source # 

mkLyricFont :: LyricFont Source #

Smart constructor for LyricFont

data LyricLanguage Source #

lyric-language (complex)

The lyric-language type specifies the default language for a particular name and number of lyric.

Constructors

LyricLanguage 

Fields

data Measure Source #

measure (complex)

Constructors

Measure 

Fields

Instances

mkMeasure :: Token -> MusicData -> Measure Source #

Smart constructor for Measure

data CmpMeasure Source #

measure (complex)

Constructors

CmpMeasure 

Fields

mkCmpMeasure :: Token -> CmpMeasure Source #

Smart constructor for CmpMeasure

data MeasureLayout Source #

measure-layout (complex)

The measure-layout type includes the horizontal distance from the previous measure.

Constructors

MeasureLayout 

Fields

Instances

Eq MeasureLayout Source # 
Show MeasureLayout Source # 
Generic MeasureLayout Source # 

Associated Types

type Rep MeasureLayout :: * -> * #

EmitXml MeasureLayout Source # 
type Rep MeasureLayout Source # 
type Rep MeasureLayout = D1 * (MetaData "MeasureLayout" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "MeasureLayout" PrefixI True) (S1 * (MetaSel (Just Symbol "measureLayoutMeasureDistance") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))))

data MeasureNumbering Source #

measure-numbering (complex)

The measure-numbering type describes how frequently measure numbers are displayed on this part. The number attribute from the measure element is used for printing. Measures with an implicit attribute set to "yes" never display a measure number, regardless of the measure-numbering setting.

Instances

Eq MeasureNumbering Source # 
Show MeasureNumbering Source # 
Generic MeasureNumbering Source # 
EmitXml MeasureNumbering Source # 
type Rep MeasureNumbering Source # 
type Rep MeasureNumbering = D1 * (MetaData "MeasureNumbering" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "MeasureNumbering" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "measureNumberingMeasureNumberingValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MeasureNumberingValue)) (S1 * (MetaSel (Just Symbol "measureNumberingDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "measureNumberingDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "measureNumberingRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "measureNumberingRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "measureNumberingFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) (S1 * (MetaSel (Just Symbol "measureNumberingFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle)))) ((:*:) * (S1 * (MetaSel (Just Symbol "measureNumberingFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) ((:*:) * (S1 * (MetaSel (Just Symbol "measureNumberingFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) (S1 * (MetaSel (Just Symbol "measureNumberingColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))))))))

data MeasureRepeat Source #

measure-repeat (complex)

The measure-repeat type is used for both single and multiple measure repeats. The text of the element indicates the number of measures to be repeated in a single pattern. The slashes attribute specifies the number of slashes to use in the repeat sign. It is 1 if not specified. Both the start and the stop of the measure-repeat must be specified. The text of the element is ignored when the type is stop.

The measure-repeat element specifies a notation style for repetitions. The actual music being repeated needs to be repeated within the MusicXML file. This element specifies the notation that indicates the repeat.

data MeasureStyle Source #

measure-style (complex)

A measure-style indicates a special way to print partial to multiple measures within a part. This includes multiple rests over several measures, repeats of beats, single, or multiple measures, and use of slash notation.

The multiple-rest and measure-repeat symbols indicate the number of measures covered in the element content. The beat-repeat and slash elements can cover partial measures. All but the multiple-rest element use a type attribute to indicate starting and stopping the use of the style. The optional number attribute specifies the staff number from top to bottom on the system, as with clef.

Instances

Eq MeasureStyle Source # 
Show MeasureStyle Source # 
Generic MeasureStyle Source # 

Associated Types

type Rep MeasureStyle :: * -> * #

EmitXml MeasureStyle Source # 
type Rep MeasureStyle Source # 

data Metronome Source #

metronome (complex)

The metronome type represents metronome marks and other metric relationships. The beat-unit group and per-minute element specify regular metronome marks. The metronome-note and metronome-relation elements allow for the specification of more complicated metric relationships, such as swing tempo marks where two eighths are equated to a quarter note / eighth note triplet. The parentheses attribute indicates whether or not to put the metronome mark in parentheses; its value is no if not specified.

Constructors

Metronome 

Fields

Instances

Eq Metronome Source # 
Show Metronome Source # 
Generic Metronome Source # 

Associated Types

type Rep Metronome :: * -> * #

EmitXml Metronome Source # 
type Rep Metronome Source # 
type Rep Metronome = D1 * (MetaData "Metronome" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Metronome" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "metronomeParentheses") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))) (S1 * (MetaSel (Just Symbol "metronomeDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "metronomeDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "metronomeRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "metronomeRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "metronomeFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) ((:*:) * (S1 * (MetaSel (Just Symbol "metronomeFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))) (S1 * (MetaSel (Just Symbol "metronomeFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))))) ((:*:) * (S1 * (MetaSel (Just Symbol "metronomeFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) ((:*:) * (S1 * (MetaSel (Just Symbol "metronomeColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) (S1 * (MetaSel (Just Symbol "metronomeMetronome") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ChxMetronome)))))))

mkMetronome :: ChxMetronome -> Metronome Source #

Smart constructor for Metronome

data MetronomeBeam Source #

metronome-beam (complex)

The metronome-beam type works like the beam type in defining metric relationships, but does not include all the attributes available in the beam type.

Constructors

MetronomeBeam 

Fields

data MetronomeNote Source #

metronome-note (complex)

The metronome-note type defines the appearance of a note within a metric relationship mark.

Constructors

MetronomeNote 

Fields

data MetronomeTuplet Source #

metronome-tuplet (complex)

The metronome-tuplet type uses the same element structure as the time-modification element along with some attributes from the tuplet element.

data MidiDevice Source #

midi-device (complex)

The midi-device type corresponds to the DeviceName meta event in Standard MIDI Files. The optional port attribute is a number from 1 to 16 that can be used with the unofficial MIDI port (or cable) meta event.

Constructors

MidiDevice 

Fields

Instances

Eq MidiDevice Source # 
Show MidiDevice Source # 
Generic MidiDevice Source # 

Associated Types

type Rep MidiDevice :: * -> * #

EmitXml MidiDevice Source # 
type Rep MidiDevice Source # 
type Rep MidiDevice = D1 * (MetaData "MidiDevice" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "MidiDevice" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "midiDeviceString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "midiDevicePort") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Midi16)))))

mkMidiDevice :: String -> MidiDevice Source #

Smart constructor for MidiDevice

data MidiInstrument Source #

midi-instrument (complex)

The midi-instrument type defines MIDI 1.0 instrument playback. The midi-instrument element can be a part of either the score-instrument element at the start of a part, or the sound element within a part. The id attribute refers to the score-instrument affected by the change.

Constructors

MidiInstrument 

Fields

Instances

Eq MidiInstrument Source # 
Show MidiInstrument Source # 
Generic MidiInstrument Source # 

Associated Types

type Rep MidiInstrument :: * -> * #

EmitXml MidiInstrument Source # 
type Rep MidiInstrument Source # 

data Miscellaneous Source #

miscellaneous (complex)

If a program has other metadata not yet supported in the MusicXML format, it can go in the miscellaneous element. The miscellaneous type puts each separate part of metadata into its own miscellaneous-field type.

Constructors

Miscellaneous 

Fields

Instances

Eq Miscellaneous Source # 
Show Miscellaneous Source # 
Generic Miscellaneous Source # 

Associated Types

type Rep Miscellaneous :: * -> * #

EmitXml Miscellaneous Source # 
type Rep Miscellaneous Source # 
type Rep Miscellaneous = D1 * (MetaData "Miscellaneous" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Miscellaneous" PrefixI True) (S1 * (MetaSel (Just Symbol "miscellaneousMiscellaneousField") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [MiscellaneousField])))

data MiscellaneousField Source #

miscellaneous-field (complex)

If a program has other metadata not yet supported in the MusicXML format, each type of metadata can go in a miscellaneous-field element. The required name attribute indicates the type of metadata the element content represents.

Constructors

MiscellaneousField 

Fields

data Mordent Source #

mordent (complex)

The mordent type is used for both represents the mordent sign with the vertical line and the inverted-mordent sign without the line. The long attribute is "no" by default.

Constructors

Mordent 

Instances

Eq Mordent Source # 

Methods

(==) :: Mordent -> Mordent -> Bool #

(/=) :: Mordent -> Mordent -> Bool #

Show Mordent Source # 
Generic Mordent Source # 

Associated Types

type Rep Mordent :: * -> * #

Methods

from :: Mordent -> Rep Mordent x #

to :: Rep Mordent x -> Mordent #

EmitXml Mordent Source # 
type Rep Mordent Source # 
type Rep Mordent = D1 * (MetaData "Mordent" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Mordent" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "mordentEmptyTrillSound") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Mordent)) (S1 * (MetaSel (Just Symbol "mordentLong") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo)))))

mkMordent :: Mordent -> Mordent Source #

Smart constructor for Mordent

data MultipleRest Source #

multiple-rest (complex)

The text of the multiple-rest type indicates the number of measures in the multiple rest. Multiple rests may use the 1-bar 2-bar 4-bar rest symbols, or a single shape. The use-symbols attribute indicates which to use; it is no if not specified. The element text is ignored when the type is stop.

Instances

Eq MultipleRest Source # 
Show MultipleRest Source # 
Generic MultipleRest Source # 

Associated Types

type Rep MultipleRest :: * -> * #

EmitXml MultipleRest Source # 
type Rep MultipleRest Source # 
type Rep MultipleRest = D1 * (MetaData "MultipleRest" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "MultipleRest" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "multipleRestPositiveIntegerOrEmpty") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PositiveIntegerOrEmpty)) (S1 * (MetaSel (Just Symbol "multipleRestUseSymbols") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo)))))

data NameDisplay Source #

name-display (complex)

The name-display type is used for exact formatting of multi-font text in part and group names to the left of the system. The print-object attribute can be used to determine what, if anything, is printed at the start of each system. Enclosure for the display-text element is none by default. Language for the display-text element is Italian ("it") by default.

Constructors

NameDisplay 

Instances

Eq NameDisplay Source # 
Show NameDisplay Source # 
Generic NameDisplay Source # 

Associated Types

type Rep NameDisplay :: * -> * #

EmitXml NameDisplay Source # 
type Rep NameDisplay Source # 
type Rep NameDisplay = D1 * (MetaData "NameDisplay" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "NameDisplay" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "nameDisplayPrintObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))) (S1 * (MetaSel (Just Symbol "nameDisplayNameDisplay") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ChxNameDisplay]))))

mkNameDisplay :: NameDisplay Source #

Smart constructor for NameDisplay

data NonArpeggiate Source #

non-arpeggiate (complex)

The non-arpeggiate type indicates that this note is at the top or bottom of a bracket indicating to not arpeggiate these notes. Since this does not involve playback, it is only used on the top or bottom notes, not on each note as for the arpeggiate type.

Constructors

NonArpeggiate 

Fields

Instances

Eq NonArpeggiate Source # 
Show NonArpeggiate Source # 
Generic NonArpeggiate Source # 

Associated Types

type Rep NonArpeggiate :: * -> * #

EmitXml NonArpeggiate Source # 
type Rep NonArpeggiate Source # 

data Notations Source #

notations (complex)

Notations refer to musical notations, not XML notations. Multiple notations are allowed in order to represent multiple editorial levels. The set of notations may be refined and expanded over time, especially to handle more instrument-specific technical notations.

Instances

Eq Notations Source # 
Show Notations Source # 
Generic Notations Source # 

Associated Types

type Rep Notations :: * -> * #

EmitXml Notations Source # 
type Rep Notations Source # 
type Rep Notations = D1 * (MetaData "Notations" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Notations" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "notationsEditorial") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Editorial)) (S1 * (MetaSel (Just Symbol "notationsNotations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ChxNotations]))))

mkNotations :: Editorial -> Notations Source #

Smart constructor for Notations

data Note Source #

note (complex)

Notes are the most common type of MusicXML data. The MusicXML format keeps the MuseData distinction between elements used for sound information and elements used for notation information (e.g., tie is used for sound, tied for notation). Thus grace notes do not have a duration element. Cue notes have a duration element, as do forward elements, but no tie elements. Having these two types of information available can make interchange considerably easier, as some programs handle one type of information much more readily than the other.

The dynamics and end-dynamics attributes correspond to MIDI 1.0's Note On and Note Off velocities, respectively. They are expressed in terms of percentages of the default forte value (90 for MIDI 1.0). The attack and release attributes are used to alter the staring and stopping time of the note from when it would otherwise occur based on the flow of durations - information that is specific to a performance. They are expressed in terms of divisions, either positive or negative. A note that starts a tie should not have a release attribute, and a note that stops a tie should not have an attack attribute. If a note is played only one time through a repeat, the time-only attribute shows which time to play the note. The pizzicato attribute is used when just this note is sounded pizzicato, vs. the pizzicato element which changes overall playback between pizzicato and arco.

Constructors

Note 

Fields

Instances

Eq Note Source # 

Methods

(==) :: Note -> Note -> Bool #

(/=) :: Note -> Note -> Bool #

Show Note Source # 

Methods

showsPrec :: Int -> Note -> ShowS #

show :: Note -> String #

showList :: [Note] -> ShowS #

Generic Note Source # 

Associated Types

type Rep Note :: * -> * #

Methods

from :: Note -> Rep Note x #

to :: Rep Note x -> Note #

EmitXml Note Source # 

Methods

emitXml :: Note -> XmlRep Source #

type Rep Note Source # 
type Rep Note = D1 * (MetaData "Note" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Note" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "noteDynamics") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NonNegativeDecimal))) (S1 * (MetaSel (Just Symbol "noteEndDynamics") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NonNegativeDecimal)))) ((:*:) * (S1 * (MetaSel (Just Symbol "noteAttack") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Divisions))) (S1 * (MetaSel (Just Symbol "noteRelease") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Divisions))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "noteTimeOnly") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Token))) (S1 * (MetaSel (Just Symbol "notePizzicato") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo)))) ((:*:) * (S1 * (MetaSel (Just Symbol "noteDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "noteDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "noteRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "noteRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "noteFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) (S1 * (MetaSel (Just Symbol "noteFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "noteFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) (S1 * (MetaSel (Just Symbol "noteFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight)))) ((:*:) * (S1 * (MetaSel (Just Symbol "noteColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) (S1 * (MetaSel (Just Symbol "notePrintDot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))))))) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "notePrintLyric") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))) (S1 * (MetaSel (Just Symbol "notePrintObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo)))) ((:*:) * (S1 * (MetaSel (Just Symbol "notePrintSpacing") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))) (S1 * (MetaSel (Just Symbol "noteNote") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ChxNote)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "noteInstrument") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Instrument))) (S1 * (MetaSel (Just Symbol "noteEditorialVoice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EditorialVoice))) ((:*:) * (S1 * (MetaSel (Just Symbol "noteType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NoteType))) (S1 * (MetaSel (Just Symbol "noteDot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [EmptyPlacement]))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "noteAccidental") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Accidental))) (S1 * (MetaSel (Just Symbol "noteTimeModification") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe TimeModification)))) ((:*:) * (S1 * (MetaSel (Just Symbol "noteStem") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Stem))) (S1 * (MetaSel (Just Symbol "noteNotehead") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Notehead))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "noteStaff") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Staff))) (S1 * (MetaSel (Just Symbol "noteBeam") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Beam]))) ((:*:) * (S1 * (MetaSel (Just Symbol "noteNotations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Notations])) (S1 * (MetaSel (Just Symbol "noteLyric") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Lyric]))))))))

mkNote :: ChxNote -> EditorialVoice -> Note Source #

Smart constructor for Note

data NoteSize Source #

note-size (complex)

The note-size type indicates the percentage of the regular note size to use for notes with a cue and large size as defined in the type element. The grace type is used for notes of cue size that that include a grace element. The cue type is used for all other notes with cue size, whether defined explicitly or implicitly via a cue element. The large type is used for notes of large size. The text content represent the numeric percentage. A value of 100 would be identical to the size of a regular note as defined by the music font.

Constructors

NoteSize 

Instances

Eq NoteSize Source # 
Show NoteSize Source # 
Generic NoteSize Source # 

Associated Types

type Rep NoteSize :: * -> * #

Methods

from :: NoteSize -> Rep NoteSize x #

to :: Rep NoteSize x -> NoteSize #

EmitXml NoteSize Source # 
type Rep NoteSize Source # 
type Rep NoteSize = D1 * (MetaData "NoteSize" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "NoteSize" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "noteSizeNonNegativeDecimal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NonNegativeDecimal)) (S1 * (MetaSel (Just Symbol "noteSizeType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NoteSizeType))))

data NoteType Source #

note-type (complex)

The note-type type indicates the graphic note type. Values range from 256th to long. The size attribute indicates full, cue, or large size, with full the default for regular notes and cue the default for cue and grace notes.

Constructors

NoteType 

Fields

Instances

Eq NoteType Source # 
Show NoteType Source # 
Generic NoteType Source # 

Associated Types

type Rep NoteType :: * -> * #

Methods

from :: NoteType -> Rep NoteType x #

to :: Rep NoteType x -> NoteType #

EmitXml NoteType Source # 
type Rep NoteType Source # 
type Rep NoteType = D1 * (MetaData "NoteType" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "NoteType" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "noteTypeNoteTypeValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NoteTypeValue)) (S1 * (MetaSel (Just Symbol "noteTypeSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe SymbolSize)))))

mkNoteType :: NoteTypeValue -> NoteType Source #

Smart constructor for NoteType

data Notehead Source #

notehead (complex)

The notehead element indicates shapes other than the open and closed ovals associated with note durations.

For the enclosed shapes, the default is to be hollow for half notes and longer, and filled otherwise. The filled attribute can be set to change this if needed.

If the parentheses attribute is set to yes, the notehead is parenthesized. It is no by default.

Constructors

Notehead 

Fields

Instances

Eq Notehead Source # 
Show Notehead Source # 
Generic Notehead Source # 

Associated Types

type Rep Notehead :: * -> * #

Methods

from :: Notehead -> Rep Notehead x #

to :: Rep Notehead x -> Notehead #

EmitXml Notehead Source # 
type Rep Notehead Source # 

mkNotehead :: NoteheadValue -> Notehead Source #

Smart constructor for Notehead

data OctaveShift Source #

octave-shift (complex)

The octave shift type indicates where notes are shifted up or down from their true pitched values because of printing difficulty. Thus a treble clef line noted with 8va will be indicated with an octave-shift down from the pitch data indicated in the notes. A size of 8 indicates one octave; a size of 15 indicates two octaves.

Constructors

OctaveShift 

Fields

Instances

Eq OctaveShift Source # 
Show OctaveShift Source # 
Generic OctaveShift Source # 

Associated Types

type Rep OctaveShift :: * -> * #

EmitXml OctaveShift Source # 
type Rep OctaveShift Source # 
type Rep OctaveShift = D1 * (MetaData "OctaveShift" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "OctaveShift" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "octaveShiftType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * UpDownStop)) ((:*:) * (S1 * (MetaSel (Just Symbol "octaveShiftNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NumberLevel))) (S1 * (MetaSel (Just Symbol "octaveShiftSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe PositiveInteger))))) ((:*:) * (S1 * (MetaSel (Just Symbol "octaveShiftDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "octaveShiftDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "octaveShiftRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "octaveShiftRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "octaveShiftFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) (S1 * (MetaSel (Just Symbol "octaveShiftFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))))) ((:*:) * (S1 * (MetaSel (Just Symbol "octaveShiftFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) ((:*:) * (S1 * (MetaSel (Just Symbol "octaveShiftFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) (S1 * (MetaSel (Just Symbol "octaveShiftColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))))))))

data Offset Source #

offset (complex)

An offset is represented in terms of divisions, and indicates where the direction will appear relative to the current musical location. This affects the visual appearance of the direction. If the sound attribute is "yes", then the offset affects playback too. If the sound attribute is "no", then any sound associated with the direction takes effect at the current location. The sound attribute is "no" by default for compatibility with earlier versions of the MusicXML format. If an element within a direction includes a default-x attribute, the offset value will be ignored when determining the appearance of that element.

Constructors

Offset 

Fields

Instances

Eq Offset Source # 

Methods

(==) :: Offset -> Offset -> Bool #

(/=) :: Offset -> Offset -> Bool #

Show Offset Source # 
Generic Offset Source # 

Associated Types

type Rep Offset :: * -> * #

Methods

from :: Offset -> Rep Offset x #

to :: Rep Offset x -> Offset #

EmitXml Offset Source # 
type Rep Offset Source # 
type Rep Offset = D1 * (MetaData "Offset" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Offset" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "offsetDivisions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Divisions)) (S1 * (MetaSel (Just Symbol "offsetSound") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo)))))

mkOffset :: Divisions -> Offset Source #

Smart constructor for Offset

data Opus Source #

opus (complex)

The opus type represents a link to a MusicXML opus document that composes multiple MusicXML scores into a collection.

Constructors

Opus 

Fields

mkOpus :: String -> Opus Source #

Smart constructor for Opus

data Ornaments Source #

ornaments (complex)

Ornaments can be any of several types, followed optionally by accidentals. The accidental-mark element's content is represented the same as an accidental element, but with a different name to reflect the different musical meaning.

Constructors

Ornaments 

Instances

Eq Ornaments Source # 
Show Ornaments Source # 
Generic Ornaments Source # 

Associated Types

type Rep Ornaments :: * -> * #

EmitXml Ornaments Source # 
type Rep Ornaments Source # 
type Rep Ornaments = D1 * (MetaData "Ornaments" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Ornaments" PrefixI True) (S1 * (MetaSel (Just Symbol "ornamentsOrnaments") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [SeqOrnaments])))

mkOrnaments :: Ornaments Source #

Smart constructor for Ornaments

data OtherAppearance Source #

other-appearance (complex)

The other-appearance type is used to define any graphical settings not yet in the current version of the MusicXML format. This allows extended representation, though without application interoperability.

Constructors

OtherAppearance 

Fields

data OtherDirection Source #

other-direction (complex)

The other-direction type is used to define any direction symbols not yet in the current version of the MusicXML format. This allows extended representation, though without application interoperability.

Constructors

OtherDirection 

Fields

Instances

Eq OtherDirection Source # 
Show OtherDirection Source # 
Generic OtherDirection Source # 

Associated Types

type Rep OtherDirection :: * -> * #

EmitXml OtherDirection Source # 
type Rep OtherDirection Source # 
type Rep OtherDirection = D1 * (MetaData "OtherDirection" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "OtherDirection" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "otherDirectionString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "otherDirectionPrintObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo)))) ((:*:) * (S1 * (MetaSel (Just Symbol "otherDirectionDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "otherDirectionDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "otherDirectionRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "otherDirectionRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "otherDirectionFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) (S1 * (MetaSel (Just Symbol "otherDirectionFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))))) ((:*:) * (S1 * (MetaSel (Just Symbol "otherDirectionFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) ((:*:) * (S1 * (MetaSel (Just Symbol "otherDirectionFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) (S1 * (MetaSel (Just Symbol "otherDirectionColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))))))))

data OtherNotation Source #

other-notation (complex)

The other-notation type is used to define any notations not yet in the MusicXML format. This allows extended representation, though without application interoperability. It handles notations where more specific extension elements such as other-dynamics and other-technical are not appropriate.

Constructors

OtherNotation 

Fields

Instances

Eq OtherNotation Source # 
Show OtherNotation Source # 
Generic OtherNotation Source # 

Associated Types

type Rep OtherNotation :: * -> * #

EmitXml OtherNotation Source # 
type Rep OtherNotation Source # 
type Rep OtherNotation = D1 * (MetaData "OtherNotation" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "OtherNotation" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "otherNotationString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) ((:*:) * (S1 * (MetaSel (Just Symbol "otherNotationType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * StartStopSingle)) (S1 * (MetaSel (Just Symbol "otherNotationNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NumberLevel))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "otherNotationPrintObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))) (S1 * (MetaSel (Just Symbol "otherNotationDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "otherNotationDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "otherNotationRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "otherNotationRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "otherNotationFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) (S1 * (MetaSel (Just Symbol "otherNotationFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "otherNotationFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) (S1 * (MetaSel (Just Symbol "otherNotationFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight)))) ((:*:) * (S1 * (MetaSel (Just Symbol "otherNotationColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) (S1 * (MetaSel (Just Symbol "otherNotationPlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe AboveBelow))))))))

data PageLayout Source #

page-layout (complex)

Page layout can be defined both in score-wide defaults and in the print element. Page margins are specified either for both even and odd pages, or via separate odd and even page number values. The type is not needed when used as part of a print element. If omitted when used in the defaults element, "both" is the default.

Constructors

PageLayout 

Instances

Eq PageLayout Source # 
Show PageLayout Source # 
Generic PageLayout Source # 

Associated Types

type Rep PageLayout :: * -> * #

EmitXml PageLayout Source # 
type Rep PageLayout Source # 
type Rep PageLayout = D1 * (MetaData "PageLayout" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "PageLayout" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "pageLayoutPageLayout") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe SeqPageLayout))) (S1 * (MetaSel (Just Symbol "pageLayoutPageMargins") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [PageMargins]))))

mkPageLayout :: PageLayout Source #

Smart constructor for PageLayout

data PageMargins Source #

page-margins (complex)

Page margins are specified either for both even and odd pages, or via separate odd and even page number values. The type attribute is not needed when used as part of a print element. If omitted when the page-margins type is used in the defaults element, "both" is the default value.

Instances

Eq PageMargins Source # 
Show PageMargins Source # 
Generic PageMargins Source # 

Associated Types

type Rep PageMargins :: * -> * #

EmitXml PageMargins Source # 
type Rep PageMargins Source # 
type Rep PageMargins = D1 * (MetaData "PageMargins" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "PageMargins" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "pageMarginsType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe MarginType))) (S1 * (MetaSel (Just Symbol "pageMarginsAllMargins") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * AllMargins))))

data CmpPart Source #

part (complex)

Constructors

CmpPart 

Fields

Instances

Eq CmpPart Source # 

Methods

(==) :: CmpPart -> CmpPart -> Bool #

(/=) :: CmpPart -> CmpPart -> Bool #

Show CmpPart Source # 
Generic CmpPart Source # 

Associated Types

type Rep CmpPart :: * -> * #

Methods

from :: CmpPart -> Rep CmpPart x #

to :: Rep CmpPart x -> CmpPart #

EmitXml CmpPart Source # 
type Rep CmpPart Source # 
type Rep CmpPart = D1 * (MetaData "CmpPart" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "CmpPart" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "partId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * IDREF)) (S1 * (MetaSel (Just Symbol "partMeasure") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Measure]))))

mkCmpPart :: IDREF -> CmpPart Source #

Smart constructor for CmpPart

data Part Source #

part (complex)

Constructors

Part 

Fields

Instances

Eq Part Source # 

Methods

(==) :: Part -> Part -> Bool #

(/=) :: Part -> Part -> Bool #

Show Part Source # 

Methods

showsPrec :: Int -> Part -> ShowS #

show :: Part -> String #

showList :: [Part] -> ShowS #

Generic Part Source # 

Associated Types

type Rep Part :: * -> * #

Methods

from :: Part -> Rep Part x #

to :: Rep Part x -> Part #

EmitXml Part Source # 

Methods

emitXml :: Part -> XmlRep Source #

type Rep Part Source # 
type Rep Part = D1 * (MetaData "Part" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Part" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "cmppartId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * IDREF)) (S1 * (MetaSel (Just Symbol "partMusicData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MusicData))))

mkPart :: IDREF -> MusicData -> Part Source #

Smart constructor for Part

data PartGroup Source #

part-group (complex)

The part-group element indicates groupings of parts in the score, usually indicated by braces and brackets. Braces that are used for multi-staff parts should be defined in the attributes element for that part. The part-group start element appears before the first score-part in the group. The part-group stop element appears after the last score-part in the group.

The number attribute is used to distinguish overlapping and nested part-groups, not the sequence of groups. As with parts, groups can have a name and abbreviation. Values for the child elements are ignored at the stop of a group.

A part-group element is not needed for a single multi-staff part. By default, multi-staff parts include a brace symbol and (if appropriate given the bar-style) common barlines. The symbol formatting for a multi-staff part can be more fully specified using the part-symbol element.

Constructors

PartGroup 

Fields

Instances

Eq PartGroup Source # 
Show PartGroup Source # 
Generic PartGroup Source # 

Associated Types

type Rep PartGroup :: * -> * #

EmitXml PartGroup Source # 
type Rep PartGroup Source # 
type Rep PartGroup = D1 * (MetaData "PartGroup" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "PartGroup" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "partGroupType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * StartStop)) (S1 * (MetaSel (Just Symbol "partGroupNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Token)))) ((:*:) * (S1 * (MetaSel (Just Symbol "partGroupGroupName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe GroupName))) ((:*:) * (S1 * (MetaSel (Just Symbol "partGroupGroupNameDisplay") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NameDisplay))) (S1 * (MetaSel (Just Symbol "partGroupGroupAbbreviation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe GroupName)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "partGroupGroupAbbreviationDisplay") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NameDisplay))) (S1 * (MetaSel (Just Symbol "partGroupGroupSymbol") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe GroupSymbol)))) ((:*:) * (S1 * (MetaSel (Just Symbol "partGroupGroupBarline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe GroupBarline))) ((:*:) * (S1 * (MetaSel (Just Symbol "partGroupGroupTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Empty))) (S1 * (MetaSel (Just Symbol "partGroupEditorial") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Editorial)))))))

mkPartGroup :: StartStop -> Editorial -> PartGroup Source #

Smart constructor for PartGroup

data PartList Source #

part-list (complex)

The part-list identifies the different musical parts in this movement. Each part has an ID that is used later within the musical data. Since parts may be encoded separately and combined later, identification elements are present at both the score and score-part levels. There must be at least one score-part, combined as desired with part-group elements that indicate braces and brackets. Parts are ordered from top to bottom in a score based on the order in which they appear in the part-list.

Instances

Eq PartList Source # 
Show PartList Source # 
Generic PartList Source # 

Associated Types

type Rep PartList :: * -> * #

Methods

from :: PartList -> Rep PartList x #

to :: Rep PartList x -> PartList #

EmitXml PartList Source # 
type Rep PartList Source # 
type Rep PartList = D1 * (MetaData "PartList" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "PartList" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "partListPartGroup") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [GrpPartGroup])) ((:*:) * (S1 * (MetaSel (Just Symbol "partListScorePart") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ScorePart)) (S1 * (MetaSel (Just Symbol "partListPartList") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ChxPartList])))))

mkPartList :: ScorePart -> PartList Source #

Smart constructor for PartList

data PartName Source #

part-name (complex)

The part-name type describes the name or abbreviation of a score-part element. Formatting attributes for the part-name element are deprecated in Version 2.0 in favor of the new part-name-display and part-abbreviation-display elements.

Constructors

PartName 

Fields

Instances

Eq PartName Source # 
Show PartName Source # 
Generic PartName Source # 

Associated Types

type Rep PartName :: * -> * #

Methods

from :: PartName -> Rep PartName x #

to :: Rep PartName x -> PartName #

EmitXml PartName Source # 
type Rep PartName Source # 
type Rep PartName = D1 * (MetaData "PartName" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "PartName" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "partNameString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) ((:*:) * (S1 * (MetaSel (Just Symbol "partNameDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "partNameDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))))) ((:*:) * (S1 * (MetaSel (Just Symbol "partNameRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "partNameRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "partNameFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "partNameFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))) ((:*:) * (S1 * (MetaSel (Just Symbol "partNameFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) (S1 * (MetaSel (Just Symbol "partNameFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))))) ((:*:) * (S1 * (MetaSel (Just Symbol "partNameColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) ((:*:) * (S1 * (MetaSel (Just Symbol "partNamePrintObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))) (S1 * (MetaSel (Just Symbol "partNameJustify") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe LeftCenterRight))))))))

mkPartName :: String -> PartName Source #

Smart constructor for PartName

data PartSymbol Source #

part-symbol (complex)

The part-symbol element indicates how a symbol for a multi-staff part is indicated in the score. Values include none, brace, line, and bracket; brace is the default. The top-staff and bottom-staff elements are used when the brace does not extend across the entire part. For example, in a 3-staff organ part, the top-staff will typically be 1 for the right hand, while the bottom-staff will typically be 2 for the left hand. Staff 3 for the pedals is usually outside the brace.

Constructors

PartSymbol 

Fields

Instances

Eq PartSymbol Source # 
Show PartSymbol Source # 
Generic PartSymbol Source # 

Associated Types

type Rep PartSymbol :: * -> * #

EmitXml PartSymbol Source # 
type Rep PartSymbol Source # 

data Pedal Source #

pedal (complex)

The pedal type represents piano pedal marks. The line attribute is yes if pedal lines are used, no if Ped and * signs are used. The change type is used with line set to yes.

Constructors

Pedal 

Fields

Instances

Eq Pedal Source # 

Methods

(==) :: Pedal -> Pedal -> Bool #

(/=) :: Pedal -> Pedal -> Bool #

Show Pedal Source # 

Methods

showsPrec :: Int -> Pedal -> ShowS #

show :: Pedal -> String #

showList :: [Pedal] -> ShowS #

Generic Pedal Source # 

Associated Types

type Rep Pedal :: * -> * #

Methods

from :: Pedal -> Rep Pedal x #

to :: Rep Pedal x -> Pedal #

EmitXml Pedal Source # 

Methods

emitXml :: Pedal -> XmlRep Source #

type Rep Pedal Source # 
type Rep Pedal = D1 * (MetaData "Pedal" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Pedal" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "pedalType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * StartStopChange)) (S1 * (MetaSel (Just Symbol "pedalLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo)))) ((:*:) * (S1 * (MetaSel (Just Symbol "pedalDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "pedalDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "pedalRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "pedalRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "pedalFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) (S1 * (MetaSel (Just Symbol "pedalFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))))) ((:*:) * (S1 * (MetaSel (Just Symbol "pedalFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) ((:*:) * (S1 * (MetaSel (Just Symbol "pedalFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) (S1 * (MetaSel (Just Symbol "pedalColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))))))))

mkPedal :: StartStopChange -> Pedal Source #

Smart constructor for Pedal

data PedalTuning Source #

pedal-tuning (complex)

The pedal-tuning type specifies the tuning of a single harp pedal.

Constructors

PedalTuning 

Fields

Instances

Eq PedalTuning Source # 
Show PedalTuning Source # 
Generic PedalTuning Source # 

Associated Types

type Rep PedalTuning :: * -> * #

EmitXml PedalTuning Source # 
type Rep PedalTuning Source # 
type Rep PedalTuning = D1 * (MetaData "PedalTuning" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "PedalTuning" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "pedalTuningPedalStep") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Step)) (S1 * (MetaSel (Just Symbol "pedalTuningPedalAlter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Semitones))))

data PerMinute Source #

per-minute (complex)

The per-minute type can be a number, or a text description including numbers. If a font is specified, it overrides the font specified for the overall metronome element. This allows separate specification of a music font for the beat-unit and a text font for the numeric value, in cases where a single metronome font is not used.

Constructors

PerMinute 

Fields

mkPerMinute :: String -> PerMinute Source #

Smart constructor for PerMinute

data Pitch Source #

pitch (complex)

Pitch is represented as a combination of the step of the diatonic scale, the chromatic alteration, and the octave.

Constructors

Pitch 

Fields

Instances

Eq Pitch Source # 

Methods

(==) :: Pitch -> Pitch -> Bool #

(/=) :: Pitch -> Pitch -> Bool #

Show Pitch Source # 

Methods

showsPrec :: Int -> Pitch -> ShowS #

show :: Pitch -> String #

showList :: [Pitch] -> ShowS #

Generic Pitch Source # 

Associated Types

type Rep Pitch :: * -> * #

Methods

from :: Pitch -> Rep Pitch x #

to :: Rep Pitch x -> Pitch #

EmitXml Pitch Source # 

Methods

emitXml :: Pitch -> XmlRep Source #

type Rep Pitch Source # 
type Rep Pitch = D1 * (MetaData "Pitch" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Pitch" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "pitchStep") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Step)) ((:*:) * (S1 * (MetaSel (Just Symbol "pitchAlter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Semitones))) (S1 * (MetaSel (Just Symbol "pitchOctave") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Octave)))))

mkPitch :: Step -> Octave -> Pitch Source #

Smart constructor for Pitch

data PlacementText Source #

placement-text (complex)

The placement-text type represents a text element with print-style and placement attribute groups.

Constructors

PlacementText 

Fields

Instances

Eq PlacementText Source # 
Show PlacementText Source # 
Generic PlacementText Source # 

Associated Types

type Rep PlacementText :: * -> * #

EmitXml PlacementText Source # 
type Rep PlacementText Source # 
type Rep PlacementText = D1 * (MetaData "PlacementText" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "PlacementText" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "placementTextString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "placementTextDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "placementTextDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "placementTextRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "placementTextRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "placementTextFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) ((:*:) * (S1 * (MetaSel (Just Symbol "placementTextFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))) (S1 * (MetaSel (Just Symbol "placementTextFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))))) ((:*:) * (S1 * (MetaSel (Just Symbol "placementTextFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) ((:*:) * (S1 * (MetaSel (Just Symbol "placementTextColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) (S1 * (MetaSel (Just Symbol "placementTextPlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe AboveBelow))))))))

data Print Source #

print (complex)

The print type contains general printing parameters, including the layout elements defined in the layout.mod file. The part-name-display and part-abbreviation-display elements used in the score.mod file may also be used here to change how a part name or abbreviation is displayed over the course of a piece. They take effect when the current measure or a succeeding measure starts a new system.

Layout elements in a print statement only apply to the current page, system, staff, or measure. Music that follows continues to take the default values from the layout included in the defaults element.

Constructors

Print 

Fields

Instances

Eq Print Source # 

Methods

(==) :: Print -> Print -> Bool #

(/=) :: Print -> Print -> Bool #

Show Print Source # 

Methods

showsPrec :: Int -> Print -> ShowS #

show :: Print -> String #

showList :: [Print] -> ShowS #

Generic Print Source # 

Associated Types

type Rep Print :: * -> * #

Methods

from :: Print -> Rep Print x #

to :: Rep Print x -> Print #

EmitXml Print Source # 

Methods

emitXml :: Print -> XmlRep Source #

type Rep Print Source # 
type Rep Print = D1 * (MetaData "Print" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Print" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "printStaffSpacing") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "printNewSystem") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo)))) ((:*:) * (S1 * (MetaSel (Just Symbol "printNewPage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))) ((:*:) * (S1 * (MetaSel (Just Symbol "printBlankPage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe PositiveInteger))) (S1 * (MetaSel (Just Symbol "printPageNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Token)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "printLayout") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Layout)) (S1 * (MetaSel (Just Symbol "printMeasureLayout") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe MeasureLayout)))) ((:*:) * (S1 * (MetaSel (Just Symbol "printMeasureNumbering") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe MeasureNumbering))) ((:*:) * (S1 * (MetaSel (Just Symbol "printPartNameDisplay") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NameDisplay))) (S1 * (MetaSel (Just Symbol "printPartAbbreviationDisplay") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NameDisplay))))))))

mkPrint :: Layout -> Print Source #

Smart constructor for Print

data Rehearsal Source #

rehearsal (complex)

The rehearsal type specifies a rehearsal mark. Language is Italian ("it") by default. Enclosure is square by default.

Constructors

Rehearsal 

Fields

Instances

Eq Rehearsal Source # 
Show Rehearsal Source # 
Generic Rehearsal Source # 

Associated Types

type Rep Rehearsal :: * -> * #

EmitXml Rehearsal Source # 
type Rep Rehearsal Source # 
type Rep Rehearsal = D1 * (MetaData "Rehearsal" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Rehearsal" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "rehearsalString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "rehearsalLang") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Lang)))) ((:*:) * (S1 * (MetaSel (Just Symbol "rehearsalEnclosure") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe RehearsalEnclosure))) (S1 * (MetaSel (Just Symbol "rehearsalDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "rehearsalDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "rehearsalRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "rehearsalRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "rehearsalFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "rehearsalFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))) (S1 * (MetaSel (Just Symbol "rehearsalFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize)))) ((:*:) * (S1 * (MetaSel (Just Symbol "rehearsalFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) (S1 * (MetaSel (Just Symbol "rehearsalColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "rehearsalUnderline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NumberOfLines))) (S1 * (MetaSel (Just Symbol "rehearsalOverline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NumberOfLines)))) ((:*:) * (S1 * (MetaSel (Just Symbol "rehearsalLineThrough") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NumberOfLines))) ((:*:) * (S1 * (MetaSel (Just Symbol "rehearsalDir") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe TextDirection))) (S1 * (MetaSel (Just Symbol "rehearsalRotation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe RotationDegrees)))))))))

mkRehearsal :: String -> Rehearsal Source #

Smart constructor for Rehearsal

data Repeat Source #

repeat (complex)

The repeat type represents repeat marks. The start of the repeat has a forward direction while the end of the repeat has a backward direction. Backward repeats that are not part of an ending can use the times attribute to indicate the number of times the repeated section is played.

Constructors

Repeat 

Fields

Instances

Eq Repeat Source # 

Methods

(==) :: Repeat -> Repeat -> Bool #

(/=) :: Repeat -> Repeat -> Bool #

Show Repeat Source # 
Generic Repeat Source # 

Associated Types

type Rep Repeat :: * -> * #

Methods

from :: Repeat -> Rep Repeat x #

to :: Rep Repeat x -> Repeat #

EmitXml Repeat Source # 
type Rep Repeat Source # 
type Rep Repeat = D1 * (MetaData "Repeat" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Repeat" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "repeatDirection") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * BackwardForward)) (S1 * (MetaSel (Just Symbol "repeatTimes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NonNegativeInteger)))))

mkRepeat :: BackwardForward -> Repeat Source #

Smart constructor for Repeat

data Root Source #

root (complex)

The root type indicates a pitch like C, D, E vs. a function indication like I, II, III. It is used with chord symbols in popular music. The root element has a root-step and optional root-alter element similar to the step and alter elements, but renamed to distinguish the different musical meanings.

Constructors

Root 

Fields

Instances

Eq Root Source # 

Methods

(==) :: Root -> Root -> Bool #

(/=) :: Root -> Root -> Bool #

Show Root Source # 

Methods

showsPrec :: Int -> Root -> ShowS #

show :: Root -> String #

showList :: [Root] -> ShowS #

Generic Root Source # 

Associated Types

type Rep Root :: * -> * #

Methods

from :: Root -> Rep Root x #

to :: Rep Root x -> Root #

EmitXml Root Source # 

Methods

emitXml :: Root -> XmlRep Source #

type Rep Root Source # 
type Rep Root = D1 * (MetaData "Root" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Root" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "rootRootStep") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * RootStep)) (S1 * (MetaSel (Just Symbol "rootRootAlter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe RootAlter)))))

mkRoot :: RootStep -> Root Source #

Smart constructor for Root

data RootAlter Source #

root-alter (complex)

The root-alter type represents the chromatic alteration of the root of the current chord within the harmony element. In some chord styles, the text for the root-step element may include root-alter information. In that case, the print-object attribute of the root-alter element can be set to no. The location attribute indicates whether the alteration should appear to the left or the right of the root-step; it is right by default.

Constructors

RootAlter 

Fields

Instances

Eq RootAlter Source # 
Show RootAlter Source # 
Generic RootAlter Source # 

Associated Types

type Rep RootAlter :: * -> * #

EmitXml RootAlter Source # 
type Rep RootAlter Source # 
type Rep RootAlter = D1 * (MetaData "RootAlter" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "RootAlter" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "rootAlterSemitones") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Semitones)) ((:*:) * (S1 * (MetaSel (Just Symbol "rootAlterLocation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe LeftRight))) (S1 * (MetaSel (Just Symbol "rootAlterPrintObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))))) ((:*:) * (S1 * (MetaSel (Just Symbol "rootAlterDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "rootAlterDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "rootAlterRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "rootAlterRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "rootAlterFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) (S1 * (MetaSel (Just Symbol "rootAlterFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))))) ((:*:) * (S1 * (MetaSel (Just Symbol "rootAlterFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) ((:*:) * (S1 * (MetaSel (Just Symbol "rootAlterFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) (S1 * (MetaSel (Just Symbol "rootAlterColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))))))))

mkRootAlter :: Semitones -> RootAlter Source #

Smart constructor for RootAlter

data RootStep Source #

root-step (complex)

The root-step type represents the pitch step of the root of the current chord within the harmony element. The text attribute indicates how the root should appear on the page if not using the element contents.

Constructors

RootStep 

Fields

Instances

Eq RootStep Source # 
Show RootStep Source # 
Generic RootStep Source # 

Associated Types

type Rep RootStep :: * -> * #

Methods

from :: RootStep -> Rep RootStep x #

to :: Rep RootStep x -> RootStep #

EmitXml RootStep Source # 
type Rep RootStep Source # 
type Rep RootStep = D1 * (MetaData "RootStep" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "RootStep" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "rootStepStep") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Step)) (S1 * (MetaSel (Just Symbol "rootStepText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Token)))) ((:*:) * (S1 * (MetaSel (Just Symbol "rootStepDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "rootStepDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "rootStepRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "rootStepRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "rootStepFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) (S1 * (MetaSel (Just Symbol "rootStepFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))))) ((:*:) * (S1 * (MetaSel (Just Symbol "rootStepFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) ((:*:) * (S1 * (MetaSel (Just Symbol "rootStepFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) (S1 * (MetaSel (Just Symbol "rootStepColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))))))))

mkRootStep :: Step -> RootStep Source #

Smart constructor for RootStep

data Scaling Source #

scaling (complex)

Margins, page sizes, and distances are all measured in tenths to keep MusicXML data in a consistent coordinate system as much as possible. The translation to absolute units is done with the scaling type, which specifies how many millimeters are equal to how many tenths. For a staff height of 7 mm, millimeters would be set to 7 while tenths is set to 40. The ability to set a formula rather than a single scaling factor helps avoid roundoff errors.

Constructors

Scaling 

Fields

Instances

Eq Scaling Source # 

Methods

(==) :: Scaling -> Scaling -> Bool #

(/=) :: Scaling -> Scaling -> Bool #

Show Scaling Source # 
Generic Scaling Source # 

Associated Types

type Rep Scaling :: * -> * #

Methods

from :: Scaling -> Rep Scaling x #

to :: Rep Scaling x -> Scaling #

EmitXml Scaling Source # 
type Rep Scaling Source # 
type Rep Scaling = D1 * (MetaData "Scaling" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Scaling" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "scalingMillimeters") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Millimeters)) (S1 * (MetaSel (Just Symbol "scalingTenths") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Tenths))))

mkScaling :: Millimeters -> Tenths -> Scaling Source #

Smart constructor for Scaling

data Scordatura Source #

scordatura (complex)

Scordatura string tunings are represented by a series of accord elements, similar to the staff-tuning elements. Strings are numbered from high to low.

Constructors

Scordatura 

Fields

Instances

Eq Scordatura Source # 
Show Scordatura Source # 
Generic Scordatura Source # 

Associated Types

type Rep Scordatura :: * -> * #

EmitXml Scordatura Source # 
type Rep Scordatura Source # 
type Rep Scordatura = D1 * (MetaData "Scordatura" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Scordatura" PrefixI True) (S1 * (MetaSel (Just Symbol "scordaturaAccord") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Accord])))

mkScordatura :: Scordatura Source #

Smart constructor for Scordatura

data ScoreInstrument Source #

score-instrument (complex)

The score-instrument type represents a single instrument within a score-part. As with the score-part type, each score-instrument has a required ID attribute, a name, and an optional abbreviation.

A score-instrument type is also required if the score specifies MIDI 1.0 channels, banks, or programs. An initial midi-instrument assignment can also be made here. MusicXML software should be able to automatically assign reasonable channels and instruments without these elements in simple cases, such as where part names match General MIDI instrument names.

Constructors

ScoreInstrument 

Fields

data CmpScorePart Source #

score-part (complex)

Each MusicXML part corresponds to a track in a Standard MIDI Format 1 file. The score-instrument elements are used when there are multiple instruments per track. The midi-device element is used to make a MIDI device or port assignment for the given track. Initial midi-instrument assignments may be made here as well.

Constructors

CmpScorePart 

Fields

Instances

Eq CmpScorePart Source # 
Show CmpScorePart Source # 
Generic CmpScorePart Source # 

Associated Types

type Rep CmpScorePart :: * -> * #

EmitXml CmpScorePart Source # 
type Rep CmpScorePart Source # 
type Rep CmpScorePart = D1 * (MetaData "CmpScorePart" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "CmpScorePart" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "scorePartId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ID)) (S1 * (MetaSel (Just Symbol "scorePartIdentification") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Identification)))) ((:*:) * (S1 * (MetaSel (Just Symbol "scorePartPartName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PartName)) ((:*:) * (S1 * (MetaSel (Just Symbol "scorePartPartNameDisplay") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NameDisplay))) (S1 * (MetaSel (Just Symbol "scorePartPartAbbreviation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe PartName)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "scorePartPartAbbreviationDisplay") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NameDisplay))) (S1 * (MetaSel (Just Symbol "scorePartGroup") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [String]))) ((:*:) * (S1 * (MetaSel (Just Symbol "scorePartScoreInstrument") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ScoreInstrument])) ((:*:) * (S1 * (MetaSel (Just Symbol "scorePartMidiDevice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe MidiDevice))) (S1 * (MetaSel (Just Symbol "scorePartMidiInstrument") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [MidiInstrument])))))))

data ScorePartwise Source #

score-partwise (complex)

Constructors

ScorePartwise 

data ScoreTimewise Source #

score-timewise (complex)

Constructors

ScoreTimewise 

data CmpSlash Source #

slash (complex)

The slash type is used to indicate that slash notation is to be used. If the slash is on every beat, use-stems is no (the default). To indicate rhythms but not pitches, use-stems is set to yes. The type attribute indicates whether this is the start or stop of a slash notation style. The use-dots attribute works as for the beat-repeat element, and only has effect if use-stems is no.

Constructors

CmpSlash 

Fields

mkCmpSlash :: StartStop -> CmpSlash Source #

Smart constructor for CmpSlash

data Slide Source #

slide (complex)

Glissando and slide types both indicate rapidly moving from one pitch to the other so that individual notes are not discerned. The distinction is similar to that between NIFF's glissando and portamento elements. A slide is continuous between two notes and defaults to a solid line. The optional text for a is printed alongside the line.

Constructors

Slide 

Fields

Instances

Eq Slide Source # 

Methods

(==) :: Slide -> Slide -> Bool #

(/=) :: Slide -> Slide -> Bool #

Show Slide Source # 

Methods

showsPrec :: Int -> Slide -> ShowS #

show :: Slide -> String #

showList :: [Slide] -> ShowS #

Generic Slide Source # 

Associated Types

type Rep Slide :: * -> * #

Methods

from :: Slide -> Rep Slide x #

to :: Rep Slide x -> Slide #

EmitXml Slide Source # 

Methods

emitXml :: Slide -> XmlRep Source #

type Rep Slide Source # 
type Rep Slide = D1 * (MetaData "Slide" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Slide" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "slideString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "slideType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * StartStop))) ((:*:) * (S1 * (MetaSel (Just Symbol "slideNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NumberLevel))) (S1 * (MetaSel (Just Symbol "slideLineType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe LineType))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "slideDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "slideDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "slideRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "slideRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "slideFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) (S1 * (MetaSel (Just Symbol "slideFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle)))) ((:*:) * (S1 * (MetaSel (Just Symbol "slideFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) (S1 * (MetaSel (Just Symbol "slideFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "slideColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) (S1 * (MetaSel (Just Symbol "slideAccelerate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo)))) ((:*:) * (S1 * (MetaSel (Just Symbol "slideBeats") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe TrillBeats))) ((:*:) * (S1 * (MetaSel (Just Symbol "slideFirstBeat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Percent))) (S1 * (MetaSel (Just Symbol "slideLastBeat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Percent)))))))))

mkSlide :: String -> StartStop -> Slide Source #

Smart constructor for Slide

data Slur Source #

slur (complex)

Slur types are empty. Most slurs are represented with two elements: one with a start type, and one with a stop type. Slurs can add more elements using a continue type. This is typically used to specify the formatting of cross-system slurs, or to specify the shape of very complex slurs.

Constructors

Slur 

Fields

Instances

Eq Slur Source # 

Methods

(==) :: Slur -> Slur -> Bool #

(/=) :: Slur -> Slur -> Bool #

Show Slur Source # 

Methods

showsPrec :: Int -> Slur -> ShowS #

show :: Slur -> String #

showList :: [Slur] -> ShowS #

Generic Slur Source # 

Associated Types

type Rep Slur :: * -> * #

Methods

from :: Slur -> Rep Slur x #

to :: Rep Slur x -> Slur #

EmitXml Slur Source # 

Methods

emitXml :: Slur -> XmlRep Source #

type Rep Slur Source # 
type Rep Slur = D1 * (MetaData "Slur" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Slur" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "slurType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * StartStopContinue)) (S1 * (MetaSel (Just Symbol "slurNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NumberLevel)))) ((:*:) * (S1 * (MetaSel (Just Symbol "slurLineType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe LineType))) (S1 * (MetaSel (Just Symbol "slurDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "slurDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "slurRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "slurRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "slurPlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe AboveBelow)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "slurOrientation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe OverUnder))) (S1 * (MetaSel (Just Symbol "slurBezierOffset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Divisions)))) ((:*:) * (S1 * (MetaSel (Just Symbol "slurBezierOffset2") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Divisions))) (S1 * (MetaSel (Just Symbol "slurBezierX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "slurBezierY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "slurBezierX2") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "slurBezierY2") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "slurColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))))))))

mkSlur :: StartStopContinue -> Slur Source #

Smart constructor for Slur

data Sound Source #

sound (complex)

The sound element contains general playback parameters. They can stand alone within a part/measure, or be a component element within a direction.

	
Tempo is expressed in quarter notes per minute. If 0, the sound-generating program should prompt the user at the time of compiling a sound (MIDI) file.
	
Dynamics (or MIDI velocity) are expressed as a percentage of the default forte value (90 for MIDI 1.0).
	
Dacapo indicates to go back to the beginning of the movement. When used it always has the value "yes".
	
Segno and dalsegno are used for backwards jumps to a segno sign; coda and tocoda are used for forward jumps to a coda sign. If there are multiple jumps, the value of these parameters can be used to name and distinguish them. If segno or coda is used, the divisions attribute can also be used to indicate the number of divisions per quarter note. Otherwise sound and MIDI generating programs may have to recompute this.
	
By default, a dalsegno or dacapo attribute indicates that the jump should occur the first time through, while a tocoda attribute indicates the jump should occur the second time through. The time that jumps occur can be changed by using the time-only attribute.
	
Forward-repeat is used when a forward repeat sign is implied, and usually follows a bar line. When used it always has the value of "yes".
	
The fine attribute follows the final note or rest in a movement with a da capo or dal segno direction. If numeric, the value represents the actual duration of the final note or rest, which can be ambiguous in written notation and different among parts and voices. The value may also be "yes" to indicate no change to the final duration.
	
If the sound element applies only one time through a repeat, the time-only attribute indicates which time to apply the sound element.
	
Pizzicato in a sound element effects all following notes. Yes indicates pizzicato, no indicates arco.

The pan and elevation attributes are deprecated in Version 2.0. The pan and elevation elements in the midi-instrument element should be used instead. The meaning of the pan and elevation attributes is the same as for the pan and elevation elements. If both are present, the mid-instrument elements take priority.
	
The damper-pedal, soft-pedal, and sostenuto-pedal attributes effect playback of the three common piano pedals and their MIDI controller equivalents. The yes value indicates the pedal is depressed; no indicates the pedal is released. A numeric value from 0 to 100 may also be used for half pedaling. This value is the percentage that the pedal is depressed. A value of 0 is equivalent to no, and a value of 100 is equivalent to yes.
	
MIDI instruments are changed using the midi-instrument element.

The offset element is used to indicate that the sound takes place offset from the current score position. If the sound element is a child of a direction element, the sound offset element overrides the direction offset element if both elements are present. Note that the offset reflects the intended musical position for the change in sound. It should not be used to compensate for latency issues in particular hardware configurations.

Constructors

Sound 

Fields

Instances

Eq Sound Source # 

Methods

(==) :: Sound -> Sound -> Bool #

(/=) :: Sound -> Sound -> Bool #

Show Sound Source # 

Methods

showsPrec :: Int -> Sound -> ShowS #

show :: Sound -> String #

showList :: [Sound] -> ShowS #

Generic Sound Source # 

Associated Types

type Rep Sound :: * -> * #

Methods

from :: Sound -> Rep Sound x #

to :: Rep Sound x -> Sound #

EmitXml Sound Source # 

Methods

emitXml :: Sound -> XmlRep Source #

type Rep Sound Source # 
type Rep Sound = D1 * (MetaData "Sound" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Sound" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "soundTempo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NonNegativeDecimal))) (S1 * (MetaSel (Just Symbol "soundDynamics") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NonNegativeDecimal)))) ((:*:) * (S1 * (MetaSel (Just Symbol "soundDacapo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))) (S1 * (MetaSel (Just Symbol "soundSegno") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Token))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "soundDalsegno") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Token))) (S1 * (MetaSel (Just Symbol "soundCoda") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Token)))) ((:*:) * (S1 * (MetaSel (Just Symbol "soundTocoda") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Token))) ((:*:) * (S1 * (MetaSel (Just Symbol "soundDivisions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Divisions))) (S1 * (MetaSel (Just Symbol "soundForwardRepeat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "soundFine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Token))) (S1 * (MetaSel (Just Symbol "soundTimeOnly") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Token)))) ((:*:) * (S1 * (MetaSel (Just Symbol "soundPizzicato") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))) ((:*:) * (S1 * (MetaSel (Just Symbol "soundPan") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe RotationDegrees))) (S1 * (MetaSel (Just Symbol "soundElevation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe RotationDegrees)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "soundDamperPedal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNoNumber))) (S1 * (MetaSel (Just Symbol "soundSoftPedal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNoNumber)))) ((:*:) * (S1 * (MetaSel (Just Symbol "soundSostenutoPedal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNoNumber))) ((:*:) * (S1 * (MetaSel (Just Symbol "soundMidiInstrument") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [MidiInstrument])) (S1 * (MetaSel (Just Symbol "soundOffset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Offset)))))))))

mkSound :: Sound Source #

Smart constructor for Sound

data StaffDetails Source #

staff-details (complex)

The staff-details element is used to indicate different types of staves. The optional number attribute specifies the staff number from top to bottom on the system, as with clef. The print-object attribute is used to indicate when a staff is not printed in a part, usually in large scores where empty parts are omitted. It is yes by default. If print-spacing is yes while print-object is no, the score is printed in cutaway format where vertical space is left for the empty part.

Constructors

StaffDetails 

Fields

Instances

Eq StaffDetails Source # 
Show StaffDetails Source # 
Generic StaffDetails Source # 

Associated Types

type Rep StaffDetails :: * -> * #

EmitXml StaffDetails Source # 
type Rep StaffDetails Source # 

data StaffLayout Source #

staff-layout (complex)

Staff layout includes the vertical distance from the bottom line of the previous staff in this system to the top line of the staff specified by the number attribute. The optional number attribute refers to staff numbers within the part, from top to bottom on the system. A value of 1 is assumed if not present. When used in the defaults element, the values apply to all parts. This value is ignored for the first staff in a system.

Constructors

StaffLayout 

Fields

Instances

Eq StaffLayout Source # 
Show StaffLayout Source # 
Generic StaffLayout Source # 

Associated Types

type Rep StaffLayout :: * -> * #

EmitXml StaffLayout Source # 
type Rep StaffLayout Source # 
type Rep StaffLayout = D1 * (MetaData "StaffLayout" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "StaffLayout" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "staffLayoutNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe StaffNumber))) (S1 * (MetaSel (Just Symbol "staffLayoutStaffDistance") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))

mkStaffLayout :: StaffLayout Source #

Smart constructor for StaffLayout

data StaffTuning Source #

staff-tuning (complex)

The staff-tuning type specifies the open, non-capo tuning of the lines on a tablature staff.

Constructors

StaffTuning 

Instances

Eq StaffTuning Source # 
Show StaffTuning Source # 
Generic StaffTuning Source # 

Associated Types

type Rep StaffTuning :: * -> * #

EmitXml StaffTuning Source # 
type Rep StaffTuning Source # 
type Rep StaffTuning = D1 * (MetaData "StaffTuning" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "StaffTuning" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "staffTuningLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe StaffLine))) (S1 * (MetaSel (Just Symbol "staffTuningTuning") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Tuning))))

mkStaffTuning :: Tuning -> StaffTuning Source #

Smart constructor for StaffTuning

data Stem Source #

stem (complex)

Stems can be down, up, none, or double. For down and up stems, the position attributes can be used to specify stem length. The relative values specify the end of the stem relative to the program default. Default values specify an absolute end stem position. Negative values of relative-y that would flip a stem instead of shortening it are ignored.

Constructors

Stem 

Fields

Instances

mkStem :: StemValue -> Stem Source #

Smart constructor for Stem

data CmpString Source #

string (complex)

The string type is used with tablature notation, regular notation (where it is often circled), and chord diagrams. String numbers start with 1 for the highest string.

Constructors

CmpString 

Fields

Instances

Eq CmpString Source # 
Show CmpString Source # 
Generic CmpString Source # 

Associated Types

type Rep CmpString :: * -> * #

EmitXml CmpString Source # 
type Rep CmpString Source # 
type Rep CmpString = D1 * (MetaData "CmpString" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "CmpString" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "stringStringNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * StringNumber)) (S1 * (MetaSel (Just Symbol "stringDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "stringDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "stringRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "stringRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "stringFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) ((:*:) * (S1 * (MetaSel (Just Symbol "stringFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))) (S1 * (MetaSel (Just Symbol "stringFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))))) ((:*:) * (S1 * (MetaSel (Just Symbol "stringFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) ((:*:) * (S1 * (MetaSel (Just Symbol "stringColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) (S1 * (MetaSel (Just Symbol "stringPlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe AboveBelow))))))))

mkCmpString :: StringNumber -> CmpString Source #

Smart constructor for CmpString

data StrongAccent Source #

strong-accent (complex)

The strong-accent type indicates a vertical accent mark. The type attribute indicates if the point of the accent is down or up.

Instances

data StyleText Source #

style-text (complex)

The style-text type represents a text element with a print-style attribute group.

Constructors

StyleText 

Fields

Instances

Eq StyleText Source # 
Show StyleText Source # 
Generic StyleText Source # 

Associated Types

type Rep StyleText :: * -> * #

EmitXml StyleText Source # 
type Rep StyleText Source # 
type Rep StyleText = D1 * (MetaData "StyleText" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "StyleText" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "styleTextString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "styleTextDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "styleTextDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "styleTextRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "styleTextRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "styleTextFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) (S1 * (MetaSel (Just Symbol "styleTextFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle)))) ((:*:) * (S1 * (MetaSel (Just Symbol "styleTextFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) ((:*:) * (S1 * (MetaSel (Just Symbol "styleTextFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) (S1 * (MetaSel (Just Symbol "styleTextColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))))))))

mkStyleText :: String -> StyleText Source #

Smart constructor for StyleText

data Supports Source #

supports (complex)

The supports type indicates if a MusicXML encoding supports a particular MusicXML element. This is recommended for elements like beam, stem, and accidental, where the absence of an element is ambiguous if you do not know if the encoding supports that element. For Version 2.0, the supports element is expanded to allow programs to indicate support for particular attributes or particular values. This lets applications communicate, for example, that all system and/or page breaks are contained in the MusicXML file.

Constructors

Supports 

Fields

Instances

mkSupports :: YesNo -> NMTOKEN -> Supports Source #

Smart constructor for Supports

data SystemLayout Source #

system-layout (complex)

System layout includes left and right margins and the vertical distance from the previous system. The system distance is measured from the bottom line of the previous system to the top line of the current system. It is ignored for the first system on a page. The top system distance is measured from the page's top margin to the top line of the first system. It is ignored for all but the first system on a page.

Sometimes the sum of measure widths in a system may not equal the system width specified by the layout elements due to roundoff or other errors. The behavior when reading MusicXML files in these cases is application-dependent. For instance, applications may find that the system layout data is more reliable than the sum of the measure widths, and adjust the measure widths accordingly.

Constructors

SystemLayout 

Fields

Instances

Eq SystemLayout Source # 
Show SystemLayout Source # 
Generic SystemLayout Source # 

Associated Types

type Rep SystemLayout :: * -> * #

EmitXml SystemLayout Source # 
type Rep SystemLayout Source # 
type Rep SystemLayout = D1 * (MetaData "SystemLayout" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "SystemLayout" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "systemLayoutSystemMargins") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe SystemMargins))) ((:*:) * (S1 * (MetaSel (Just Symbol "systemLayoutSystemDistance") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "systemLayoutTopSystemDistance") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))))))

data SystemMargins Source #

system-margins (complex)

System margins are relative to the page margins. Positive values indent and negative values reduce the margin size.

Instances

Eq SystemMargins Source # 
Show SystemMargins Source # 
Generic SystemMargins Source # 

Associated Types

type Rep SystemMargins :: * -> * #

EmitXml SystemMargins Source # 
type Rep SystemMargins Source # 
type Rep SystemMargins = D1 * (MetaData "SystemMargins" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "SystemMargins" PrefixI True) (S1 * (MetaSel (Just Symbol "systemMarginsLeftRightMargins") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * LeftRightMargins)))

data Technical Source #

technical (complex)

Technical indications give performance information for individual instruments.

Constructors

Technical 

Instances

Eq Technical Source # 
Show Technical Source # 
Generic Technical Source # 

Associated Types

type Rep Technical :: * -> * #

EmitXml Technical Source # 
type Rep Technical Source # 
type Rep Technical = D1 * (MetaData "Technical" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Technical" PrefixI True) (S1 * (MetaSel (Just Symbol "technicalTechnical") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ChxTechnical])))

mkTechnical :: Technical Source #

Smart constructor for Technical

data TextElementData Source #

text-element-data (complex)

The text-element-data type represents a syllable or portion of a syllable for lyric text underlay. A hyphen in the string content should only be used for an actual hyphenated word. Language names for text elements come from ISO 639, with optional country subcodes from ISO 3166.

Instances

Eq TextElementData Source # 
Show TextElementData Source # 
Generic TextElementData Source # 
EmitXml TextElementData Source # 
type Rep TextElementData Source # 
type Rep TextElementData = D1 * (MetaData "TextElementData" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "TextElementData" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "textElementDataString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) ((:*:) * (S1 * (MetaSel (Just Symbol "textElementDataLang") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Lang))) (S1 * (MetaSel (Just Symbol "textElementDataFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))))) ((:*:) * (S1 * (MetaSel (Just Symbol "textElementDataFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))) ((:*:) * (S1 * (MetaSel (Just Symbol "textElementDataFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) (S1 * (MetaSel (Just Symbol "textElementDataFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "textElementDataColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) ((:*:) * (S1 * (MetaSel (Just Symbol "textElementDataUnderline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NumberOfLines))) (S1 * (MetaSel (Just Symbol "textElementDataOverline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NumberOfLines))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "textElementDataLineThrough") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NumberOfLines))) (S1 * (MetaSel (Just Symbol "textElementDataRotation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe RotationDegrees)))) ((:*:) * (S1 * (MetaSel (Just Symbol "textElementDataLetterSpacing") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NumberOrNormal))) (S1 * (MetaSel (Just Symbol "textElementDataDir") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe TextDirection))))))))

data Tie Source #

tie (complex)

The tie element indicates that a tie begins or ends with this note. The tie element indicates sound; the tied element indicates notation.

Constructors

Tie 

Fields

Instances

Eq Tie Source # 

Methods

(==) :: Tie -> Tie -> Bool #

(/=) :: Tie -> Tie -> Bool #

Show Tie Source # 

Methods

showsPrec :: Int -> Tie -> ShowS #

show :: Tie -> String #

showList :: [Tie] -> ShowS #

Generic Tie Source # 

Associated Types

type Rep Tie :: * -> * #

Methods

from :: Tie -> Rep Tie x #

to :: Rep Tie x -> Tie #

EmitXml Tie Source # 

Methods

emitXml :: Tie -> XmlRep Source #

type Rep Tie Source # 
type Rep Tie = D1 * (MetaData "Tie" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Tie" PrefixI True) (S1 * (MetaSel (Just Symbol "tieType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * StartStop)))

mkTie :: StartStop -> Tie Source #

Smart constructor for Tie

data Tied Source #

tied (complex)

The tied type represents the notated tie. The tie element represents the tie sound.

Constructors

Tied 

Fields

Instances

Eq Tied Source # 

Methods

(==) :: Tied -> Tied -> Bool #

(/=) :: Tied -> Tied -> Bool #

Show Tied Source # 

Methods

showsPrec :: Int -> Tied -> ShowS #

show :: Tied -> String #

showList :: [Tied] -> ShowS #

Generic Tied Source # 

Associated Types

type Rep Tied :: * -> * #

Methods

from :: Tied -> Rep Tied x #

to :: Rep Tied x -> Tied #

EmitXml Tied Source # 

Methods

emitXml :: Tied -> XmlRep Source #

type Rep Tied Source # 
type Rep Tied = D1 * (MetaData "Tied" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Tied" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "tiedType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * StartStop)) (S1 * (MetaSel (Just Symbol "tiedNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NumberLevel)))) ((:*:) * (S1 * (MetaSel (Just Symbol "tiedLineType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe LineType))) (S1 * (MetaSel (Just Symbol "tiedDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "tiedDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "tiedRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "tiedRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "tiedPlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe AboveBelow)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "tiedOrientation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe OverUnder))) (S1 * (MetaSel (Just Symbol "tiedBezierOffset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Divisions)))) ((:*:) * (S1 * (MetaSel (Just Symbol "tiedBezierOffset2") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Divisions))) (S1 * (MetaSel (Just Symbol "tiedBezierX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "tiedBezierY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "tiedBezierX2") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "tiedBezierY2") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "tiedColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))))))))

mkTied :: StartStop -> Tied Source #

Smart constructor for Tied

data Time Source #

time (complex)

Time signatures are represented by the beats element for the numerator and the beat-type element for the denominator. The symbol attribute is used indicate common and cut time symbols as well as a single number display. Multiple pairs of beat and beat-type elements are used for composite time signatures with multiple denominators, such as 24 + 38. A composite such as 3+28 requires only one beatbeat-type pair.

The print-object attribute allows a time signature to be specified but not printed, as is the case for excerpts from the middle of a score. The value is "yes" if not present. The optional number attribute refers to staff numbers within the part. If absent, the time signature applies to all staves in the part.

Constructors

Time 

Fields

Instances

Eq Time Source # 

Methods

(==) :: Time -> Time -> Bool #

(/=) :: Time -> Time -> Bool #

Show Time Source # 

Methods

showsPrec :: Int -> Time -> ShowS #

show :: Time -> String #

showList :: [Time] -> ShowS #

Generic Time Source # 

Associated Types

type Rep Time :: * -> * #

Methods

from :: Time -> Rep Time x #

to :: Rep Time x -> Time #

EmitXml Time Source # 

Methods

emitXml :: Time -> XmlRep Source #

type Rep Time Source # 
type Rep Time = D1 * (MetaData "Time" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Time" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "timeNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe StaffNumber))) ((:*:) * (S1 * (MetaSel (Just Symbol "timeSymbol") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe TimeSymbol))) (S1 * (MetaSel (Just Symbol "timeDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))))) ((:*:) * (S1 * (MetaSel (Just Symbol "timeDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "timeRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "timeRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "timeFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) ((:*:) * (S1 * (MetaSel (Just Symbol "timeFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))) (S1 * (MetaSel (Just Symbol "timeFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "timeFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) (S1 * (MetaSel (Just Symbol "timeColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color)))) ((:*:) * (S1 * (MetaSel (Just Symbol "timePrintObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))) (S1 * (MetaSel (Just Symbol "timeTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ChxTime)))))))

mkTime :: ChxTime -> Time Source #

Smart constructor for Time

data TimeModification Source #

time-modification (complex)

The time-modification type represents tuplets and other durational changes.

data Transpose Source #

transpose (complex)

The transpose type represents what must be added to a written pitch to get a correct sounding pitch.

Constructors

Transpose 

Fields

Instances

Eq Transpose Source # 
Show Transpose Source # 
Generic Transpose Source # 

Associated Types

type Rep Transpose :: * -> * #

EmitXml Transpose Source # 
type Rep Transpose Source # 
type Rep Transpose = D1 * (MetaData "Transpose" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Transpose" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "transposeDiatonic") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "transposeChromatic") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Semitones))) ((:*:) * (S1 * (MetaSel (Just Symbol "transposeOctaveChange") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "transposeDouble") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Empty))))))

mkTranspose :: Semitones -> Transpose Source #

Smart constructor for Transpose

data Tremolo Source #

tremolo (complex)

While using repeater beams was the original method for indicating tremolos, often playback and display are not well-enough integrated in an application to make that feasible. The tremolo ornament can be used to indicate either single-note or double-note tremolos. Single-note tremolos use the single type, while double-note tremolos use the start and stop types. The default is "single" for compatibility with Version 1.1. The text of the element indicates the number of tremolo marks and is an integer from 0 to 6. Note that the number of attached beams is not included in this value, but is represented separately using the beam element.

Constructors

Tremolo 

Fields

Instances

Eq Tremolo Source # 

Methods

(==) :: Tremolo -> Tremolo -> Bool #

(/=) :: Tremolo -> Tremolo -> Bool #

Show Tremolo Source # 
Generic Tremolo Source # 

Associated Types

type Rep Tremolo :: * -> * #

Methods

from :: Tremolo -> Rep Tremolo x #

to :: Rep Tremolo x -> Tremolo #

EmitXml Tremolo Source # 
type Rep Tremolo Source # 
type Rep Tremolo = D1 * (MetaData "Tremolo" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Tremolo" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "tremoloTremoloMarks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * TremoloMarks)) ((:*:) * (S1 * (MetaSel (Just Symbol "tremoloType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe StartStopSingle))) (S1 * (MetaSel (Just Symbol "tremoloDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))))) ((:*:) * (S1 * (MetaSel (Just Symbol "tremoloDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "tremoloRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "tremoloRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "tremoloFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) ((:*:) * (S1 * (MetaSel (Just Symbol "tremoloFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))) (S1 * (MetaSel (Just Symbol "tremoloFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))))) ((:*:) * (S1 * (MetaSel (Just Symbol "tremoloFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) ((:*:) * (S1 * (MetaSel (Just Symbol "tremoloColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) (S1 * (MetaSel (Just Symbol "tremoloPlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe AboveBelow))))))))

mkTremolo :: TremoloMarks -> Tremolo Source #

Smart constructor for Tremolo

data Tuplet Source #

tuplet (complex)

A tuplet element is present when a tuplet is to be displayed graphically, in addition to the sound data provided by the time-modification elements. The number attribute is used to distinguish nested tuplets. The bracket attribute is used to indicate the presence of a bracket. If unspecified, the results are implementation-dependent. The line-shape attribute is used to specify whether the bracket is straight or in the older curved or slurred style. It is straight by default.

Whereas a time-modification element shows how the cumulative, sounding effect of tuplets compare to the written note type, the tuplet element describes how each tuplet is displayed.

The show-number attribute is used to display either the number of actual notes, the number of both actual and normal notes, or neither. It is actual by default. The show-type attribute is used to display either the actual type, both the actual and normal types, or neither. It is none by default.

Constructors

Tuplet 

Fields

Instances

Eq Tuplet Source # 

Methods

(==) :: Tuplet -> Tuplet -> Bool #

(/=) :: Tuplet -> Tuplet -> Bool #

Show Tuplet Source # 
Generic Tuplet Source # 

Associated Types

type Rep Tuplet :: * -> * #

Methods

from :: Tuplet -> Rep Tuplet x #

to :: Rep Tuplet x -> Tuplet #

EmitXml Tuplet Source # 
type Rep Tuplet Source # 
type Rep Tuplet = D1 * (MetaData "Tuplet" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Tuplet" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "tupletType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * StartStop)) ((:*:) * (S1 * (MetaSel (Just Symbol "tupletNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NumberLevel))) (S1 * (MetaSel (Just Symbol "tupletBracket") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))))) ((:*:) * (S1 * (MetaSel (Just Symbol "tupletShowNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe ShowTuplet))) ((:*:) * (S1 * (MetaSel (Just Symbol "tupletShowType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe ShowTuplet))) (S1 * (MetaSel (Just Symbol "tupletLineShape") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe LineShape)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "tupletDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) ((:*:) * (S1 * (MetaSel (Just Symbol "tupletDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "tupletRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "tupletRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "tupletPlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe AboveBelow)))) ((:*:) * (S1 * (MetaSel (Just Symbol "tupletTupletActual") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe TupletPortion))) (S1 * (MetaSel (Just Symbol "tupletTupletNormal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe TupletPortion))))))))

mkTuplet :: StartStop -> Tuplet Source #

Smart constructor for Tuplet

data TupletDot Source #

tuplet-dot (complex)

The tuplet-dot type is used to specify dotted normal tuplet types.

Constructors

TupletDot 

Fields

mkTupletDot :: TupletDot Source #

Smart constructor for TupletDot

data TupletNumber Source #

tuplet-number (complex)

The tuplet-number type indicates the number of notes for this portion of the tuplet.

Instances

Eq TupletNumber Source # 
Show TupletNumber Source # 
Generic TupletNumber Source # 

Associated Types

type Rep TupletNumber :: * -> * #

EmitXml TupletNumber Source # 
type Rep TupletNumber Source # 
type Rep TupletNumber = D1 * (MetaData "TupletNumber" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "TupletNumber" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "tupletNumberNonNegativeInteger") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NonNegativeInteger)) ((:*:) * (S1 * (MetaSel (Just Symbol "tupletNumberFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CommaSeparatedText))) (S1 * (MetaSel (Just Symbol "tupletNumberFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontStyle))))) ((:*:) * (S1 * (MetaSel (Just Symbol "tupletNumberFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontSize))) ((:*:) * (S1 * (MetaSel (Just Symbol "tupletNumberFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontWeight))) (S1 * (MetaSel (Just Symbol "tupletNumberColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color)))))))

data TupletPortion Source #

tuplet-portion (complex)

The tuplet-portion type provides optional full control over tuplet specifications. It allows the number and note type (including dots) to be set for the actual and normal portions of a single tuplet. If any of these elements are absent, their values are based on the time-modification element.

Constructors

TupletPortion 

Fields

data TupletType Source #

tuplet-type (complex)

The tuplet-type type indicates the graphical note type of the notes for this portion of the tuplet.

Constructors

TupletType 

Fields

Instances

Eq TupletType Source # 
Show TupletType Source # 
Generic TupletType Source # 

Associated Types

type Rep TupletType :: * -> * #

EmitXml TupletType Source # 
type Rep TupletType Source # 

data TypedText Source #

typed-text (complex)

The typed-text type represents a text element with a type attributes.

Constructors

TypedText 

Fields

Instances

Eq TypedText Source # 
Show TypedText Source # 
Generic TypedText Source # 

Associated Types

type Rep TypedText :: * -> * #

EmitXml TypedText Source # 
type Rep TypedText Source # 
type Rep TypedText = D1 * (MetaData "TypedText" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "TypedText" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "typedTextString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "typedTextType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Token)))))

mkTypedText :: String -> TypedText Source #

Smart constructor for TypedText

data WavyLine Source #

wavy-line (complex)

Wavy lines are one way to indicate trills. When used with a measure element, they should always have type="continue" set.

Constructors

WavyLine 

Fields

Instances

Eq WavyLine Source # 
Show WavyLine Source # 
Generic WavyLine Source # 

Associated Types

type Rep WavyLine :: * -> * #

Methods

from :: WavyLine -> Rep WavyLine x #

to :: Rep WavyLine x -> WavyLine #

EmitXml WavyLine Source # 
type Rep WavyLine Source # 
type Rep WavyLine = D1 * (MetaData "WavyLine" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "WavyLine" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "wavyLineType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * StartStopContinue)) ((:*:) * (S1 * (MetaSel (Just Symbol "wavyLineNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NumberLevel))) (S1 * (MetaSel (Just Symbol "wavyLineDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "wavyLineDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "wavyLineRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths)))) ((:*:) * (S1 * (MetaSel (Just Symbol "wavyLineRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tenths))) (S1 * (MetaSel (Just Symbol "wavyLinePlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe AboveBelow)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "wavyLineColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) (S1 * (MetaSel (Just Symbol "wavyLineStartNote") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe StartNote)))) ((:*:) * (S1 * (MetaSel (Just Symbol "wavyLineTrillStep") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe TrillStep))) (S1 * (MetaSel (Just Symbol "wavyLineTwoNoteTurn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe TwoNoteTurn))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "wavyLineAccelerate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe YesNo))) (S1 * (MetaSel (Just Symbol "wavyLineBeats") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe TrillBeats)))) ((:*:) * (S1 * (MetaSel (Just Symbol "wavyLineSecondBeat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Percent))) (S1 * (MetaSel (Just Symbol "wavyLineLastBeat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Percent))))))))

data Wedge Source #

wedge (complex)

The wedge type represents crescendo and diminuendo wedge symbols. The type attribute is crescendo for the start of a wedge that is closed at the left side, and diminuendo for the start of a wedge that is closed on the right side. Spread values are measured in tenths; those at the start of a crescendo wedge or end of a diminuendo wedge are ignored.

Constructors

Wedge 

Fields

Instances

Eq Wedge Source # 

Methods

(==) :: Wedge -> Wedge -> Bool #

(/=) :: Wedge -> Wedge -> Bool #

Show Wedge Source # 

Methods

showsPrec :: Int -> Wedge -> ShowS #

show :: Wedge -> String #

showList :: [Wedge] -> ShowS #

Generic Wedge Source # 

Associated Types

type Rep Wedge :: * -> * #

Methods

from :: Wedge -> Rep Wedge x #

to :: Rep Wedge x -> Wedge #

EmitXml Wedge Source # 

Methods

emitXml :: Wedge -> XmlRep Source #

type Rep Wedge Source # 

mkWedge :: WedgeType -> Wedge Source #

Smart constructor for Wedge

data Work Source #

work (complex)

Works are optionally identified by number and title. The work type also may indicate a link to the opus document that composes multiple scores into a collection.

Constructors

Work 

Fields

Instances

Eq Work Source # 

Methods

(==) :: Work -> Work -> Bool #

(/=) :: Work -> Work -> Bool #

Show Work Source # 

Methods

showsPrec :: Int -> Work -> ShowS #

show :: Work -> String #

showList :: [Work] -> ShowS #

Generic Work Source # 

Associated Types

type Rep Work :: * -> * #

Methods

from :: Work -> Rep Work x #

to :: Rep Work x -> Work #

EmitXml Work Source # 

Methods

emitXml :: Work -> XmlRep Source #

type Rep Work Source # 
type Rep Work = D1 * (MetaData "Work" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Work" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "workWorkNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe String))) ((:*:) * (S1 * (MetaSel (Just Symbol "workWorkTitle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe String))) (S1 * (MetaSel (Just Symbol "workOpus") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Opus))))))

mkWork :: Work Source #

Smart constructor for Work

data ChxArticulations Source #

articulations (choice)

Instances

Eq ChxArticulations Source # 
Show ChxArticulations Source # 
Generic ChxArticulations Source # 
EmitXml ChxArticulations Source # 
type Rep ChxArticulations Source # 
type Rep ChxArticulations = D1 * (MetaData "ChxArticulations" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "ArticulationsAccent" PrefixI True) (S1 * (MetaSel (Just Symbol "articulationsAccent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyPlacement))) (C1 * (MetaCons "ArticulationsStrongAccent" PrefixI True) (S1 * (MetaSel (Just Symbol "articulationsStrongAccent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * StrongAccent)))) ((:+:) * (C1 * (MetaCons "ArticulationsStaccato" PrefixI True) (S1 * (MetaSel (Just Symbol "articulationsStaccato") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyPlacement))) (C1 * (MetaCons "ArticulationsTenuto" PrefixI True) (S1 * (MetaSel (Just Symbol "articulationsTenuto") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyPlacement))))) ((:+:) * ((:+:) * (C1 * (MetaCons "ArticulationsDetachedLegato" PrefixI True) (S1 * (MetaSel (Just Symbol "articulationsDetachedLegato") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyPlacement))) (C1 * (MetaCons "ArticulationsStaccatissimo" PrefixI True) (S1 * (MetaSel (Just Symbol "articulationsStaccatissimo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyPlacement)))) ((:+:) * (C1 * (MetaCons "ArticulationsSpiccato" PrefixI True) (S1 * (MetaSel (Just Symbol "articulationsSpiccato") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyPlacement))) (C1 * (MetaCons "ArticulationsScoop" PrefixI True) (S1 * (MetaSel (Just Symbol "articulationsScoop") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyLine)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "ArticulationsPlop" PrefixI True) (S1 * (MetaSel (Just Symbol "articulationsPlop") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyLine))) (C1 * (MetaCons "ArticulationsDoit" PrefixI True) (S1 * (MetaSel (Just Symbol "articulationsDoit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyLine)))) ((:+:) * (C1 * (MetaCons "ArticulationsFalloff" PrefixI True) (S1 * (MetaSel (Just Symbol "articulationsFalloff") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyLine))) (C1 * (MetaCons "ArticulationsBreathMark" PrefixI True) (S1 * (MetaSel (Just Symbol "articulationsBreathMark") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyPlacement))))) ((:+:) * ((:+:) * (C1 * (MetaCons "ArticulationsCaesura" PrefixI True) (S1 * (MetaSel (Just Symbol "articulationsCaesura") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyPlacement))) (C1 * (MetaCons "ArticulationsStress" PrefixI True) (S1 * (MetaSel (Just Symbol "articulationsStress") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyPlacement)))) ((:+:) * (C1 * (MetaCons "ArticulationsUnstress" PrefixI True) (S1 * (MetaSel (Just Symbol "articulationsUnstress") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyPlacement))) (C1 * (MetaCons "ArticulationsOtherArticulation" PrefixI True) (S1 * (MetaSel (Just Symbol "articulationsOtherArticulation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PlacementText)))))))

data ChxBend Source #

bend (choice)

Constructors

BendPreBend 

Fields

BendRelease 

Fields

Instances

Eq ChxBend Source # 

Methods

(==) :: ChxBend -> ChxBend -> Bool #

(/=) :: ChxBend -> ChxBend -> Bool #

Show ChxBend Source # 
Generic ChxBend Source # 

Associated Types

type Rep ChxBend :: * -> * #

Methods

from :: ChxBend -> Rep ChxBend x #

to :: Rep ChxBend x -> ChxBend #

EmitXml ChxBend Source # 
type Rep ChxBend Source # 
type Rep ChxBend = D1 * (MetaData "ChxBend" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "BendPreBend" PrefixI True) (S1 * (MetaSel (Just Symbol "bendPreBend") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty))) (C1 * (MetaCons "BendRelease" PrefixI True) (S1 * (MetaSel (Just Symbol "bendRelease") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty))))

mkBendPreBend :: Empty -> ChxBend Source #

Smart constructor for BendPreBend

mkBendRelease :: Empty -> ChxBend Source #

Smart constructor for BendRelease

data ChxCredit Source #

credit (choice)

Constructors

CreditCreditImage 

Fields

CreditCreditWords 

Fields

Instances

Eq ChxCredit Source # 
Show ChxCredit Source # 
Generic ChxCredit Source # 

Associated Types

type Rep ChxCredit :: * -> * #

EmitXml ChxCredit Source # 
type Rep ChxCredit Source # 
type Rep ChxCredit = D1 * (MetaData "ChxCredit" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "CreditCreditImage" PrefixI True) (S1 * (MetaSel (Just Symbol "creditCreditImage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Image))) (C1 * (MetaCons "CreditCreditWords" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "creditCreditWords") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FormattedText)) (S1 * (MetaSel (Just Symbol "chxcreditCredit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [SeqCredit])))))

data ChxDirectionType Source #

direction-type (choice)

Constructors

DirectionTypeRehearsal 

Fields

DirectionTypeSegno 

Fields

DirectionTypeWords 

Fields

DirectionTypeCoda 

Fields

DirectionTypeWedge 

Fields

DirectionTypeDynamics 

Fields

DirectionTypeDashes 

Fields

DirectionTypeBracket 

Fields

DirectionTypePedal 

Fields

DirectionTypeMetronome 

Fields

DirectionTypeOctaveShift 

Fields

DirectionTypeHarpPedals 

Fields

DirectionTypeDamp 

Fields

DirectionTypeDampAll 

Fields

DirectionTypeEyeglasses 

Fields

DirectionTypeScordatura 

Fields

DirectionTypeImage 

Fields

DirectionTypeAccordionRegistration 

Fields

DirectionTypeOtherDirection 

Fields

Instances

Eq ChxDirectionType Source # 
Show ChxDirectionType Source # 
Generic ChxDirectionType Source # 
EmitXml ChxDirectionType Source # 
type Rep ChxDirectionType Source # 
type Rep ChxDirectionType = D1 * (MetaData "ChxDirectionType" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "DirectionTypeRehearsal" PrefixI True) (S1 * (MetaSel (Just Symbol "directionTypeRehearsal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Rehearsal]))) (C1 * (MetaCons "DirectionTypeSegno" PrefixI True) (S1 * (MetaSel (Just Symbol "directionTypeSegno") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [EmptyPrintStyle])))) ((:+:) * (C1 * (MetaCons "DirectionTypeWords" PrefixI True) (S1 * (MetaSel (Just Symbol "directionTypeWords") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [FormattedText]))) (C1 * (MetaCons "DirectionTypeCoda" PrefixI True) (S1 * (MetaSel (Just Symbol "directionTypeCoda") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [EmptyPrintStyle]))))) ((:+:) * ((:+:) * (C1 * (MetaCons "DirectionTypeWedge" PrefixI True) (S1 * (MetaSel (Just Symbol "directionTypeWedge") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Wedge))) (C1 * (MetaCons "DirectionTypeDynamics" PrefixI True) (S1 * (MetaSel (Just Symbol "directionTypeDynamics") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Dynamics])))) ((:+:) * (C1 * (MetaCons "DirectionTypeDashes" PrefixI True) (S1 * (MetaSel (Just Symbol "directionTypeDashes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Dashes))) ((:+:) * (C1 * (MetaCons "DirectionTypeBracket" PrefixI True) (S1 * (MetaSel (Just Symbol "directionTypeBracket") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bracket))) (C1 * (MetaCons "DirectionTypePedal" PrefixI True) (S1 * (MetaSel (Just Symbol "directionTypePedal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Pedal))))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "DirectionTypeMetronome" PrefixI True) (S1 * (MetaSel (Just Symbol "directionTypeMetronome") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Metronome))) (C1 * (MetaCons "DirectionTypeOctaveShift" PrefixI True) (S1 * (MetaSel (Just Symbol "directionTypeOctaveShift") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * OctaveShift)))) ((:+:) * (C1 * (MetaCons "DirectionTypeHarpPedals" PrefixI True) (S1 * (MetaSel (Just Symbol "directionTypeHarpPedals") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * HarpPedals))) ((:+:) * (C1 * (MetaCons "DirectionTypeDamp" PrefixI True) (S1 * (MetaSel (Just Symbol "directionTypeDamp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyPrintStyle))) (C1 * (MetaCons "DirectionTypeDampAll" PrefixI True) (S1 * (MetaSel (Just Symbol "directionTypeDampAll") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyPrintStyle)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "DirectionTypeEyeglasses" PrefixI True) (S1 * (MetaSel (Just Symbol "directionTypeEyeglasses") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyPrintStyle))) (C1 * (MetaCons "DirectionTypeScordatura" PrefixI True) (S1 * (MetaSel (Just Symbol "directionTypeScordatura") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Scordatura)))) ((:+:) * (C1 * (MetaCons "DirectionTypeImage" PrefixI True) (S1 * (MetaSel (Just Symbol "directionTypeImage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Image))) ((:+:) * (C1 * (MetaCons "DirectionTypeAccordionRegistration" PrefixI True) (S1 * (MetaSel (Just Symbol "directionTypeAccordionRegistration") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * AccordionRegistration))) (C1 * (MetaCons "DirectionTypeOtherDirection" PrefixI True) (S1 * (MetaSel (Just Symbol "directionTypeOtherDirection") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * OtherDirection))))))))

data ChxDynamics Source #

dynamics (choice)

Constructors

DynamicsP 

Fields

DynamicsPp 

Fields

DynamicsPpp 

Fields

DynamicsPppp 

Fields

DynamicsPpppp 

Fields

DynamicsPppppp 

Fields

DynamicsF 

Fields

DynamicsFf 

Fields

DynamicsFff 

Fields

DynamicsFfff 

Fields

DynamicsFffff 

Fields

DynamicsFfffff 

Fields

DynamicsMp 

Fields

DynamicsMf 

Fields

DynamicsSf 

Fields

DynamicsSfp 

Fields

DynamicsSfpp 

Fields

DynamicsFp 

Fields

DynamicsRf 

Fields

DynamicsRfz 

Fields

DynamicsSfz 

Fields

DynamicsSffz 

Fields

DynamicsFz 

Fields

DynamicsOtherDynamics 

Fields

Instances

Eq ChxDynamics Source # 
Show ChxDynamics Source # 
Generic ChxDynamics Source # 

Associated Types

type Rep ChxDynamics :: * -> * #

EmitXml ChxDynamics Source # 
type Rep ChxDynamics Source # 
type Rep ChxDynamics = D1 * (MetaData "ChxDynamics" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "DynamicsP" PrefixI True) (S1 * (MetaSel (Just Symbol "dynamicsP") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty))) ((:+:) * (C1 * (MetaCons "DynamicsPp" PrefixI True) (S1 * (MetaSel (Just Symbol "dynamicsPp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty))) (C1 * (MetaCons "DynamicsPpp" PrefixI True) (S1 * (MetaSel (Just Symbol "dynamicsPpp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty))))) ((:+:) * (C1 * (MetaCons "DynamicsPppp" PrefixI True) (S1 * (MetaSel (Just Symbol "dynamicsPppp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty))) ((:+:) * (C1 * (MetaCons "DynamicsPpppp" PrefixI True) (S1 * (MetaSel (Just Symbol "dynamicsPpppp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty))) (C1 * (MetaCons "DynamicsPppppp" PrefixI True) (S1 * (MetaSel (Just Symbol "dynamicsPppppp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "DynamicsF" PrefixI True) (S1 * (MetaSel (Just Symbol "dynamicsF") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty))) ((:+:) * (C1 * (MetaCons "DynamicsFf" PrefixI True) (S1 * (MetaSel (Just Symbol "dynamicsFf") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty))) (C1 * (MetaCons "DynamicsFff" PrefixI True) (S1 * (MetaSel (Just Symbol "dynamicsFff") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty))))) ((:+:) * (C1 * (MetaCons "DynamicsFfff" PrefixI True) (S1 * (MetaSel (Just Symbol "dynamicsFfff") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty))) ((:+:) * (C1 * (MetaCons "DynamicsFffff" PrefixI True) (S1 * (MetaSel (Just Symbol "dynamicsFffff") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty))) (C1 * (MetaCons "DynamicsFfffff" PrefixI True) (S1 * (MetaSel (Just Symbol "dynamicsFfffff") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty))))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "DynamicsMp" PrefixI True) (S1 * (MetaSel (Just Symbol "dynamicsMp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty))) ((:+:) * (C1 * (MetaCons "DynamicsMf" PrefixI True) (S1 * (MetaSel (Just Symbol "dynamicsMf") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty))) (C1 * (MetaCons "DynamicsSf" PrefixI True) (S1 * (MetaSel (Just Symbol "dynamicsSf") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty))))) ((:+:) * (C1 * (MetaCons "DynamicsSfp" PrefixI True) (S1 * (MetaSel (Just Symbol "dynamicsSfp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty))) ((:+:) * (C1 * (MetaCons "DynamicsSfpp" PrefixI True) (S1 * (MetaSel (Just Symbol "dynamicsSfpp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty))) (C1 * (MetaCons "DynamicsFp" PrefixI True) (S1 * (MetaSel (Just Symbol "dynamicsFp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "DynamicsRf" PrefixI True) (S1 * (MetaSel (Just Symbol "dynamicsRf") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty))) ((:+:) * (C1 * (MetaCons "DynamicsRfz" PrefixI True) (S1 * (MetaSel (Just Symbol "dynamicsRfz") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty))) (C1 * (MetaCons "DynamicsSfz" PrefixI True) (S1 * (MetaSel (Just Symbol "dynamicsSfz") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty))))) ((:+:) * (C1 * (MetaCons "DynamicsSffz" PrefixI True) (S1 * (MetaSel (Just Symbol "dynamicsSffz") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty))) ((:+:) * (C1 * (MetaCons "DynamicsFz" PrefixI True) (S1 * (MetaSel (Just Symbol "dynamicsFz") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty))) (C1 * (MetaCons "DynamicsOtherDynamics" PrefixI True) (S1 * (MetaSel (Just Symbol "dynamicsOtherDynamics") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))))))))

mkDynamicsP :: Empty -> ChxDynamics Source #

Smart constructor for DynamicsP

mkDynamicsPp :: Empty -> ChxDynamics Source #

Smart constructor for DynamicsPp

mkDynamicsPpp :: Empty -> ChxDynamics Source #

Smart constructor for DynamicsPpp

mkDynamicsF :: Empty -> ChxDynamics Source #

Smart constructor for DynamicsF

mkDynamicsFf :: Empty -> ChxDynamics Source #

Smart constructor for DynamicsFf

mkDynamicsFff :: Empty -> ChxDynamics Source #

Smart constructor for DynamicsFff

mkDynamicsMp :: Empty -> ChxDynamics Source #

Smart constructor for DynamicsMp

mkDynamicsMf :: Empty -> ChxDynamics Source #

Smart constructor for DynamicsMf

mkDynamicsSf :: Empty -> ChxDynamics Source #

Smart constructor for DynamicsSf

mkDynamicsSfp :: Empty -> ChxDynamics Source #

Smart constructor for DynamicsSfp

mkDynamicsFp :: Empty -> ChxDynamics Source #

Smart constructor for DynamicsFp

mkDynamicsRf :: Empty -> ChxDynamics Source #

Smart constructor for DynamicsRf

mkDynamicsRfz :: Empty -> ChxDynamics Source #

Smart constructor for DynamicsRfz

mkDynamicsSfz :: Empty -> ChxDynamics Source #

Smart constructor for DynamicsSfz

mkDynamicsFz :: Empty -> ChxDynamics Source #

Smart constructor for DynamicsFz

data ChxEncoding Source #

encoding (choice)

Constructors

EncodingEncodingDate 

Fields

EncodingEncoder 

Fields

EncodingSoftware 

Fields

EncodingEncodingDescription 

Fields

EncodingSupports 

Fields

Instances

Eq ChxEncoding Source # 
Show ChxEncoding Source # 
Generic ChxEncoding Source # 

Associated Types

type Rep ChxEncoding :: * -> * #

EmitXml ChxEncoding Source # 
type Rep ChxEncoding Source # 
type Rep ChxEncoding = D1 * (MetaData "ChxEncoding" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * (C1 * (MetaCons "EncodingEncodingDate" PrefixI True) (S1 * (MetaSel (Just Symbol "encodingEncodingDate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * YyyyMmDd))) (C1 * (MetaCons "EncodingEncoder" PrefixI True) (S1 * (MetaSel (Just Symbol "encodingEncoder") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * TypedText)))) ((:+:) * (C1 * (MetaCons "EncodingSoftware" PrefixI True) (S1 * (MetaSel (Just Symbol "encodingSoftware") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))) ((:+:) * (C1 * (MetaCons "EncodingEncodingDescription" PrefixI True) (S1 * (MetaSel (Just Symbol "encodingEncodingDescription") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))) (C1 * (MetaCons "EncodingSupports" PrefixI True) (S1 * (MetaSel (Just Symbol "encodingSupports") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Supports))))))

data FullNote Source #

full-note (choice)

Constructors

FullNotePitch 

Fields

FullNoteUnpitched 

Fields

FullNoteRest 

Fields

Instances

Eq FullNote Source # 
Show FullNote Source # 
Generic FullNote Source # 

Associated Types

type Rep FullNote :: * -> * #

Methods

from :: FullNote -> Rep FullNote x #

to :: Rep FullNote x -> FullNote #

EmitXml FullNote Source # 
type Rep FullNote Source # 
type Rep FullNote = D1 * (MetaData "FullNote" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "FullNotePitch" PrefixI True) (S1 * (MetaSel (Just Symbol "fullNotePitch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Pitch))) ((:+:) * (C1 * (MetaCons "FullNoteUnpitched" PrefixI True) (S1 * (MetaSel (Just Symbol "fullNoteUnpitched") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * DisplayStepOctave))) (C1 * (MetaCons "FullNoteRest" PrefixI True) (S1 * (MetaSel (Just Symbol "fullNoteRest") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * DisplayStepOctave)))))

mkFullNotePitch :: Pitch -> FullNote Source #

Smart constructor for FullNotePitch

data ChxHarmonic Source #

harmonic (choice)

Constructors

HarmonicNatural 

Fields

HarmonicArtificial 

Fields

Instances

Eq ChxHarmonic Source # 
Show ChxHarmonic Source # 
Generic ChxHarmonic Source # 

Associated Types

type Rep ChxHarmonic :: * -> * #

EmitXml ChxHarmonic Source # 
type Rep ChxHarmonic Source # 
type Rep ChxHarmonic = D1 * (MetaData "ChxHarmonic" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "HarmonicNatural" PrefixI True) (S1 * (MetaSel (Just Symbol "harmonicNatural") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty))) (C1 * (MetaCons "HarmonicArtificial" PrefixI True) (S1 * (MetaSel (Just Symbol "harmonicArtificial") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty))))

data ChxHarmonic1 Source #

harmonic (choice)

Constructors

HarmonicBasePitch 

Fields

HarmonicTouchingPitch 

Fields

HarmonicSoundingPitch 

Fields

Instances

Eq ChxHarmonic1 Source # 
Show ChxHarmonic1 Source # 
Generic ChxHarmonic1 Source # 

Associated Types

type Rep ChxHarmonic1 :: * -> * #

EmitXml ChxHarmonic1 Source # 
type Rep ChxHarmonic1 Source # 
type Rep ChxHarmonic1 = D1 * (MetaData "ChxHarmonic1" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "HarmonicBasePitch" PrefixI True) (S1 * (MetaSel (Just Symbol "harmonicBasePitch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty))) ((:+:) * (C1 * (MetaCons "HarmonicTouchingPitch" PrefixI True) (S1 * (MetaSel (Just Symbol "harmonicTouchingPitch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty))) (C1 * (MetaCons "HarmonicSoundingPitch" PrefixI True) (S1 * (MetaSel (Just Symbol "harmonicSoundingPitch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty)))))

data ChxHarmonyChord Source #

harmony-chord (choice)

Constructors

HarmonyChordRoot 

Fields

HarmonyChordFunction 

Fields

data ChxKey Source #

key (choice)

Instances

Eq ChxKey Source # 

Methods

(==) :: ChxKey -> ChxKey -> Bool #

(/=) :: ChxKey -> ChxKey -> Bool #

Show ChxKey Source # 
Generic ChxKey Source # 

Associated Types

type Rep ChxKey :: * -> * #

Methods

from :: ChxKey -> Rep ChxKey x #

to :: Rep ChxKey x -> ChxKey #

EmitXml ChxKey Source # 
type Rep ChxKey Source # 
type Rep ChxKey = D1 * (MetaData "ChxKey" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "KeyTraditionalKey" PrefixI True) (S1 * (MetaSel (Just Symbol "keyTraditionalKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * TraditionalKey))) (C1 * (MetaCons "KeyNonTraditionalKey" PrefixI True) (S1 * (MetaSel (Just Symbol "keyNonTraditionalKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [NonTraditionalKey]))))

data ChxLyric Source #

lyric (choice)

Constructors

LyricSyllabic 

Fields

LyricExtend 

Fields

LyricLaughing 

Fields

LyricHumming 

Fields

Instances

Eq ChxLyric Source # 
Show ChxLyric Source # 
Generic ChxLyric Source # 

Associated Types

type Rep ChxLyric :: * -> * #

Methods

from :: ChxLyric -> Rep ChxLyric x #

to :: Rep ChxLyric x -> ChxLyric #

EmitXml ChxLyric Source # 
type Rep ChxLyric Source # 

mkLyricExtend :: Extend -> ChxLyric Source #

Smart constructor for LyricExtend

mkLyricLaughing :: Empty -> ChxLyric Source #

Smart constructor for LyricLaughing

mkLyricHumming :: Empty -> ChxLyric Source #

Smart constructor for LyricHumming

data ChxMeasureStyle Source #

measure-style (choice)

Constructors

MeasureStyleMultipleRest 

Fields

MeasureStyleMeasureRepeat 

Fields

MeasureStyleBeatRepeat 

Fields

MeasureStyleSlash 

Fields

Instances

Eq ChxMeasureStyle Source # 
Show ChxMeasureStyle Source # 
Generic ChxMeasureStyle Source # 
EmitXml ChxMeasureStyle Source # 
type Rep ChxMeasureStyle Source # 
type Rep ChxMeasureStyle = D1 * (MetaData "ChxMeasureStyle" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * (C1 * (MetaCons "MeasureStyleMultipleRest" PrefixI True) (S1 * (MetaSel (Just Symbol "measureStyleMultipleRest") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MultipleRest))) (C1 * (MetaCons "MeasureStyleMeasureRepeat" PrefixI True) (S1 * (MetaSel (Just Symbol "measureStyleMeasureRepeat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MeasureRepeat)))) ((:+:) * (C1 * (MetaCons "MeasureStyleBeatRepeat" PrefixI True) (S1 * (MetaSel (Just Symbol "measureStyleBeatRepeat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * BeatRepeat))) (C1 * (MetaCons "MeasureStyleSlash" PrefixI True) (S1 * (MetaSel (Just Symbol "measureStyleSlash") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CmpSlash)))))

data ChxMetronome0 Source #

metronome (choice)

Constructors

MetronomePerMinute 

Fields

MetronomeBeatUnit 

Instances

Eq ChxMetronome0 Source # 
Show ChxMetronome0 Source # 
Generic ChxMetronome0 Source # 

Associated Types

type Rep ChxMetronome0 :: * -> * #

EmitXml ChxMetronome0 Source # 
type Rep ChxMetronome0 Source # 
type Rep ChxMetronome0 = D1 * (MetaData "ChxMetronome0" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "MetronomePerMinute" PrefixI True) (S1 * (MetaSel (Just Symbol "metronomePerMinute") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PerMinute))) (C1 * (MetaCons "MetronomeBeatUnit" PrefixI True) (S1 * (MetaSel (Just Symbol "metronomeBeatUnit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * BeatUnit))))

data ChxMetronome Source #

metronome (choice)

Instances

data ChxMusicData Source #

music-data (choice)

Constructors

MusicDataNote 

Fields

MusicDataBackup 

Fields

MusicDataForward 

Fields

MusicDataDirection 

Fields

MusicDataAttributes 

Fields

MusicDataHarmony 

Fields

MusicDataFiguredBass 

Fields

MusicDataPrint 

Fields

MusicDataSound 

Fields

MusicDataBarline 

Fields

MusicDataGrouping 

Fields

MusicDataLink 

Fields

MusicDataBookmark 

Fields

Instances

Eq ChxMusicData Source # 
Show ChxMusicData Source # 
Generic ChxMusicData Source # 

Associated Types

type Rep ChxMusicData :: * -> * #

EmitXml ChxMusicData Source # 
type Rep ChxMusicData Source # 
type Rep ChxMusicData = D1 * (MetaData "ChxMusicData" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "MusicDataNote" PrefixI True) (S1 * (MetaSel (Just Symbol "musicDataNote") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Note))) ((:+:) * (C1 * (MetaCons "MusicDataBackup" PrefixI True) (S1 * (MetaSel (Just Symbol "musicDataBackup") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Backup))) (C1 * (MetaCons "MusicDataForward" PrefixI True) (S1 * (MetaSel (Just Symbol "musicDataForward") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Forward))))) ((:+:) * (C1 * (MetaCons "MusicDataDirection" PrefixI True) (S1 * (MetaSel (Just Symbol "musicDataDirection") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Direction))) ((:+:) * (C1 * (MetaCons "MusicDataAttributes" PrefixI True) (S1 * (MetaSel (Just Symbol "musicDataAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Attributes))) (C1 * (MetaCons "MusicDataHarmony" PrefixI True) (S1 * (MetaSel (Just Symbol "musicDataHarmony") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Harmony)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "MusicDataFiguredBass" PrefixI True) (S1 * (MetaSel (Just Symbol "musicDataFiguredBass") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FiguredBass))) ((:+:) * (C1 * (MetaCons "MusicDataPrint" PrefixI True) (S1 * (MetaSel (Just Symbol "musicDataPrint") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Print))) (C1 * (MetaCons "MusicDataSound" PrefixI True) (S1 * (MetaSel (Just Symbol "musicDataSound") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Sound))))) ((:+:) * ((:+:) * (C1 * (MetaCons "MusicDataBarline" PrefixI True) (S1 * (MetaSel (Just Symbol "musicDataBarline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Barline))) (C1 * (MetaCons "MusicDataGrouping" PrefixI True) (S1 * (MetaSel (Just Symbol "musicDataGrouping") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Grouping)))) ((:+:) * (C1 * (MetaCons "MusicDataLink" PrefixI True) (S1 * (MetaSel (Just Symbol "musicDataLink") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Link))) (C1 * (MetaCons "MusicDataBookmark" PrefixI True) (S1 * (MetaSel (Just Symbol "musicDataBookmark") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bookmark)))))))

data ChxNameDisplay Source #

name-display (choice)

Constructors

NameDisplayDisplayText 

Fields

NameDisplayAccidentalText 

Fields

Instances

Eq ChxNameDisplay Source # 
Show ChxNameDisplay Source # 
Generic ChxNameDisplay Source # 

Associated Types

type Rep ChxNameDisplay :: * -> * #

EmitXml ChxNameDisplay Source # 
type Rep ChxNameDisplay Source # 
type Rep ChxNameDisplay = D1 * (MetaData "ChxNameDisplay" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "NameDisplayDisplayText" PrefixI True) (S1 * (MetaSel (Just Symbol "nameDisplayDisplayText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FormattedText))) (C1 * (MetaCons "NameDisplayAccidentalText" PrefixI True) (S1 * (MetaSel (Just Symbol "nameDisplayAccidentalText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * AccidentalText))))

data ChxNotations Source #

notations (choice)

Constructors

NotationsTied 

Fields

NotationsSlur 

Fields

NotationsTuplet 

Fields

NotationsGlissando 

Fields

NotationsSlide 

Fields

NotationsOrnaments 

Fields

NotationsTechnical 

Fields

NotationsArticulations 

Fields

NotationsDynamics 

Fields

NotationsFermata 

Fields

NotationsArpeggiate 

Fields

NotationsNonArpeggiate 

Fields

NotationsAccidentalMark 

Fields

NotationsOtherNotation 

Fields

Instances

Eq ChxNotations Source # 
Show ChxNotations Source # 
Generic ChxNotations Source # 

Associated Types

type Rep ChxNotations :: * -> * #

EmitXml ChxNotations Source # 
type Rep ChxNotations Source # 
type Rep ChxNotations = D1 * (MetaData "ChxNotations" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "NotationsTied" PrefixI True) (S1 * (MetaSel (Just Symbol "notationsTied") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Tied))) ((:+:) * (C1 * (MetaCons "NotationsSlur" PrefixI True) (S1 * (MetaSel (Just Symbol "notationsSlur") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Slur))) (C1 * (MetaCons "NotationsTuplet" PrefixI True) (S1 * (MetaSel (Just Symbol "notationsTuplet") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Tuplet))))) ((:+:) * ((:+:) * (C1 * (MetaCons "NotationsGlissando" PrefixI True) (S1 * (MetaSel (Just Symbol "notationsGlissando") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Glissando))) (C1 * (MetaCons "NotationsSlide" PrefixI True) (S1 * (MetaSel (Just Symbol "notationsSlide") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Slide)))) ((:+:) * (C1 * (MetaCons "NotationsOrnaments" PrefixI True) (S1 * (MetaSel (Just Symbol "notationsOrnaments") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Ornaments))) (C1 * (MetaCons "NotationsTechnical" PrefixI True) (S1 * (MetaSel (Just Symbol "notationsTechnical") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Technical)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "NotationsArticulations" PrefixI True) (S1 * (MetaSel (Just Symbol "notationsArticulations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Articulations))) ((:+:) * (C1 * (MetaCons "NotationsDynamics" PrefixI True) (S1 * (MetaSel (Just Symbol "notationsDynamics") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Dynamics))) (C1 * (MetaCons "NotationsFermata" PrefixI True) (S1 * (MetaSel (Just Symbol "notationsFermata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Fermata))))) ((:+:) * ((:+:) * (C1 * (MetaCons "NotationsArpeggiate" PrefixI True) (S1 * (MetaSel (Just Symbol "notationsArpeggiate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Arpeggiate))) (C1 * (MetaCons "NotationsNonArpeggiate" PrefixI True) (S1 * (MetaSel (Just Symbol "notationsNonArpeggiate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NonArpeggiate)))) ((:+:) * (C1 * (MetaCons "NotationsAccidentalMark" PrefixI True) (S1 * (MetaSel (Just Symbol "notationsAccidentalMark") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * AccidentalMark))) (C1 * (MetaCons "NotationsOtherNotation" PrefixI True) (S1 * (MetaSel (Just Symbol "notationsOtherNotation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * OtherNotation)))))))

data ChxNote Source #

note (choice)

Constructors

NoteGrace 

Fields

NoteCue 

Fields

NoteFullNote 

Fields

Instances

Eq ChxNote Source # 

Methods

(==) :: ChxNote -> ChxNote -> Bool #

(/=) :: ChxNote -> ChxNote -> Bool #

Show ChxNote Source # 
Generic ChxNote Source # 

Associated Types

type Rep ChxNote :: * -> * #

Methods

from :: ChxNote -> Rep ChxNote x #

to :: Rep ChxNote x -> ChxNote #

EmitXml ChxNote Source # 
type Rep ChxNote Source # 

mkNoteGrace :: Grace -> GrpFullNote -> ChxNote Source #

Smart constructor for NoteGrace

mkNoteCue :: Empty -> GrpFullNote -> Duration -> ChxNote Source #

Smart constructor for NoteCue

data ChxOrnaments Source #

ornaments (choice)

Constructors

OrnamentsTrillMark 

Fields

OrnamentsTurn 

Fields

OrnamentsDelayedTurn 

Fields

OrnamentsInvertedTurn 

Fields

OrnamentsShake 

Fields

OrnamentsWavyLine 

Fields

OrnamentsMordent 

Fields

OrnamentsInvertedMordent 

Fields

OrnamentsSchleifer 

Fields

OrnamentsTremolo 

Fields

OrnamentsOtherOrnament 

Fields

Instances

Eq ChxOrnaments Source # 
Show ChxOrnaments Source # 
Generic ChxOrnaments Source # 

Associated Types

type Rep ChxOrnaments :: * -> * #

EmitXml ChxOrnaments Source # 
type Rep ChxOrnaments Source # 
type Rep ChxOrnaments = D1 * (MetaData "ChxOrnaments" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "OrnamentsTrillMark" PrefixI True) (S1 * (MetaSel (Just Symbol "ornamentsTrillMark") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyTrillSound))) (C1 * (MetaCons "OrnamentsTurn" PrefixI True) (S1 * (MetaSel (Just Symbol "ornamentsTurn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyTrillSound)))) ((:+:) * (C1 * (MetaCons "OrnamentsDelayedTurn" PrefixI True) (S1 * (MetaSel (Just Symbol "ornamentsDelayedTurn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyTrillSound))) ((:+:) * (C1 * (MetaCons "OrnamentsInvertedTurn" PrefixI True) (S1 * (MetaSel (Just Symbol "ornamentsInvertedTurn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyTrillSound))) (C1 * (MetaCons "OrnamentsShake" PrefixI True) (S1 * (MetaSel (Just Symbol "ornamentsShake") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyTrillSound)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "OrnamentsWavyLine" PrefixI True) (S1 * (MetaSel (Just Symbol "ornamentsWavyLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * WavyLine))) ((:+:) * (C1 * (MetaCons "OrnamentsMordent" PrefixI True) (S1 * (MetaSel (Just Symbol "ornamentsMordent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Mordent))) (C1 * (MetaCons "OrnamentsInvertedMordent" PrefixI True) (S1 * (MetaSel (Just Symbol "ornamentsInvertedMordent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Mordent))))) ((:+:) * (C1 * (MetaCons "OrnamentsSchleifer" PrefixI True) (S1 * (MetaSel (Just Symbol "ornamentsSchleifer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyPlacement))) ((:+:) * (C1 * (MetaCons "OrnamentsTremolo" PrefixI True) (S1 * (MetaSel (Just Symbol "ornamentsTremolo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Tremolo))) (C1 * (MetaCons "OrnamentsOtherOrnament" PrefixI True) (S1 * (MetaSel (Just Symbol "ornamentsOtherOrnament") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PlacementText)))))))

data ChxPartList Source #

part-list (choice)

Instances

Eq ChxPartList Source # 
Show ChxPartList Source # 
Generic ChxPartList Source # 

Associated Types

type Rep ChxPartList :: * -> * #

EmitXml ChxPartList Source # 
type Rep ChxPartList Source # 
type Rep ChxPartList = D1 * (MetaData "ChxPartList" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "PartListPartGroup" PrefixI True) (S1 * (MetaSel (Just Symbol "chxpartListPartGroup") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * GrpPartGroup))) (C1 * (MetaCons "PartListScorePart" PrefixI True) (S1 * (MetaSel (Just Symbol "chxpartListScorePart") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ScorePart))))

data ChxTechnical Source #

technical (choice)

Constructors

TechnicalUpBow 

Fields

TechnicalDownBow 

Fields

TechnicalHarmonic 

Fields

TechnicalOpenString 

Fields

TechnicalThumbPosition 

Fields

TechnicalFingering 

Fields

TechnicalPluck 

Fields

TechnicalDoubleTongue 

Fields

TechnicalTripleTongue 

Fields

TechnicalStopped 

Fields

TechnicalSnapPizzicato 

Fields

TechnicalFret 

Fields

TechnicalString 

Fields

TechnicalHammerOn 

Fields

TechnicalPullOff 

Fields

TechnicalBend 

Fields

TechnicalTap 

Fields

TechnicalHeel 

Fields

TechnicalToe 

Fields

TechnicalFingernails 

Fields

TechnicalOtherTechnical 

Fields

Instances

Eq ChxTechnical Source # 
Show ChxTechnical Source # 
Generic ChxTechnical Source # 

Associated Types

type Rep ChxTechnical :: * -> * #

EmitXml ChxTechnical Source # 
type Rep ChxTechnical Source # 
type Rep ChxTechnical = D1 * (MetaData "ChxTechnical" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "TechnicalUpBow" PrefixI True) (S1 * (MetaSel (Just Symbol "technicalUpBow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyPlacement))) (C1 * (MetaCons "TechnicalDownBow" PrefixI True) (S1 * (MetaSel (Just Symbol "technicalDownBow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyPlacement)))) ((:+:) * (C1 * (MetaCons "TechnicalHarmonic" PrefixI True) (S1 * (MetaSel (Just Symbol "technicalHarmonic") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Harmonic))) ((:+:) * (C1 * (MetaCons "TechnicalOpenString" PrefixI True) (S1 * (MetaSel (Just Symbol "technicalOpenString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyPlacement))) (C1 * (MetaCons "TechnicalThumbPosition" PrefixI True) (S1 * (MetaSel (Just Symbol "technicalThumbPosition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyPlacement)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "TechnicalFingering" PrefixI True) (S1 * (MetaSel (Just Symbol "technicalFingering") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Fingering))) (C1 * (MetaCons "TechnicalPluck" PrefixI True) (S1 * (MetaSel (Just Symbol "technicalPluck") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PlacementText)))) ((:+:) * (C1 * (MetaCons "TechnicalDoubleTongue" PrefixI True) (S1 * (MetaSel (Just Symbol "technicalDoubleTongue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyPlacement))) ((:+:) * (C1 * (MetaCons "TechnicalTripleTongue" PrefixI True) (S1 * (MetaSel (Just Symbol "technicalTripleTongue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyPlacement))) (C1 * (MetaCons "TechnicalStopped" PrefixI True) (S1 * (MetaSel (Just Symbol "technicalStopped") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyPlacement))))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "TechnicalSnapPizzicato" PrefixI True) (S1 * (MetaSel (Just Symbol "technicalSnapPizzicato") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyPlacement))) (C1 * (MetaCons "TechnicalFret" PrefixI True) (S1 * (MetaSel (Just Symbol "technicalFret") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Fret)))) ((:+:) * (C1 * (MetaCons "TechnicalString" PrefixI True) (S1 * (MetaSel (Just Symbol "technicalString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CmpString))) ((:+:) * (C1 * (MetaCons "TechnicalHammerOn" PrefixI True) (S1 * (MetaSel (Just Symbol "technicalHammerOn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * HammerOnPullOff))) (C1 * (MetaCons "TechnicalPullOff" PrefixI True) (S1 * (MetaSel (Just Symbol "technicalPullOff") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * HammerOnPullOff)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "TechnicalBend" PrefixI True) (S1 * (MetaSel (Just Symbol "technicalBend") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bend))) ((:+:) * (C1 * (MetaCons "TechnicalTap" PrefixI True) (S1 * (MetaSel (Just Symbol "technicalTap") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PlacementText))) (C1 * (MetaCons "TechnicalHeel" PrefixI True) (S1 * (MetaSel (Just Symbol "technicalHeel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * HeelToe))))) ((:+:) * (C1 * (MetaCons "TechnicalToe" PrefixI True) (S1 * (MetaSel (Just Symbol "technicalToe") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * HeelToe))) ((:+:) * (C1 * (MetaCons "TechnicalFingernails" PrefixI True) (S1 * (MetaSel (Just Symbol "technicalFingernails") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EmptyPlacement))) (C1 * (MetaCons "TechnicalOtherTechnical" PrefixI True) (S1 * (MetaSel (Just Symbol "technicalOtherTechnical") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PlacementText))))))))

data ChxTime Source #

time (choice)

Constructors

TimeTime 

Fields

TimeSenzaMisura 

Fields

Instances

Eq ChxTime Source # 

Methods

(==) :: ChxTime -> ChxTime -> Bool #

(/=) :: ChxTime -> ChxTime -> Bool #

Show ChxTime Source # 
Generic ChxTime Source # 

Associated Types

type Rep ChxTime :: * -> * #

Methods

from :: ChxTime -> Rep ChxTime x #

to :: Rep ChxTime x -> ChxTime #

EmitXml ChxTime Source # 
type Rep ChxTime Source # 
type Rep ChxTime = D1 * (MetaData "ChxTime" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) ((:+:) * (C1 * (MetaCons "TimeTime" PrefixI True) (S1 * (MetaSel (Just Symbol "chxtimeTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [SeqTime]))) (C1 * (MetaCons "TimeSenzaMisura" PrefixI True) (S1 * (MetaSel (Just Symbol "timeSenzaMisura") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Empty))))

mkTimeTime :: ChxTime Source #

Smart constructor for TimeTime

data SeqCredit Source #

credit (sequence)

Constructors

SeqCredit 

Fields

Instances

Eq SeqCredit Source # 
Show SeqCredit Source # 
Generic SeqCredit Source # 

Associated Types

type Rep SeqCredit :: * -> * #

EmitXml SeqCredit Source # 
type Rep SeqCredit Source # 
type Rep SeqCredit = D1 * (MetaData "SeqCredit" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "SeqCredit" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "seqcreditLink") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Link])) ((:*:) * (S1 * (MetaSel (Just Symbol "seqcreditBookmark") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Bookmark])) (S1 * (MetaSel (Just Symbol "seqcreditCreditWords") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FormattedText)))))

data SeqLyric0 Source #

lyric (sequence)

Constructors

SeqLyric0 

Fields

Instances

Eq SeqLyric0 Source # 
Show SeqLyric0 Source # 
Generic SeqLyric0 Source # 

Associated Types

type Rep SeqLyric0 :: * -> * #

EmitXml SeqLyric0 Source # 
type Rep SeqLyric0 Source # 
type Rep SeqLyric0 = D1 * (MetaData "SeqLyric0" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "SeqLyric0" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "lyricElision") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Elision)) (S1 * (MetaSel (Just Symbol "seqlyricSyllabic") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Syllabic)))))

mkSeqLyric0 :: Elision -> SeqLyric0 Source #

Smart constructor for SeqLyric0

data SeqLyric Source #

lyric (sequence)

Constructors

SeqLyric 

Instances

Eq SeqLyric Source # 
Show SeqLyric Source # 
Generic SeqLyric Source # 

Associated Types

type Rep SeqLyric :: * -> * #

Methods

from :: SeqLyric -> Rep SeqLyric x #

to :: Rep SeqLyric x -> SeqLyric #

EmitXml SeqLyric Source # 
type Rep SeqLyric Source # 
type Rep SeqLyric = D1 * (MetaData "SeqLyric" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "SeqLyric" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "seqlyricLyric") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe SeqLyric0))) (S1 * (MetaSel (Just Symbol "seqlyricText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * TextElementData))))

mkSeqLyric :: TextElementData -> SeqLyric Source #

Smart constructor for SeqLyric

data SeqMetronome Source #

metronome (sequence)

Constructors

SeqMetronome 

Fields

Instances

Eq SeqMetronome Source # 
Show SeqMetronome Source # 
Generic SeqMetronome Source # 

Associated Types

type Rep SeqMetronome :: * -> * #

EmitXml SeqMetronome Source # 
type Rep SeqMetronome Source # 
type Rep SeqMetronome = D1 * (MetaData "SeqMetronome" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "SeqMetronome" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "metronomeMetronomeRelation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "seqmetronomeMetronomeNote") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [MetronomeNote]))))

data SeqOrnaments Source #

ornaments (sequence)

Constructors

SeqOrnaments 

Fields

Instances

data SeqPageLayout Source #

page-layout (sequence)

Constructors

SeqPageLayout 

Fields

data SeqTime Source #

time (sequence)

Constructors

SeqTime 

Fields

Instances

Eq SeqTime Source # 

Methods

(==) :: SeqTime -> SeqTime -> Bool #

(/=) :: SeqTime -> SeqTime -> Bool #

Show SeqTime Source # 
Generic SeqTime Source # 

Associated Types

type Rep SeqTime :: * -> * #

Methods

from :: SeqTime -> Rep SeqTime x #

to :: Rep SeqTime x -> SeqTime #

EmitXml SeqTime Source # 
type Rep SeqTime Source # 
type Rep SeqTime = D1 * (MetaData "SeqTime" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "SeqTime" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "timeBeats") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "timeBeatType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))))

mkSeqTime :: String -> String -> SeqTime Source #

Smart constructor for SeqTime

data AllMargins Source #

all-margins (group)

Constructors

AllMargins 

Fields

Instances

Eq AllMargins Source # 
Show AllMargins Source # 
Generic AllMargins Source # 

Associated Types

type Rep AllMargins :: * -> * #

EmitXml AllMargins Source # 
type Rep AllMargins Source # 
type Rep AllMargins = D1 * (MetaData "AllMargins" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "AllMargins" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "allMarginsLeftRightMargins") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * LeftRightMargins)) ((:*:) * (S1 * (MetaSel (Just Symbol "allMarginsTopMargin") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Tenths)) (S1 * (MetaSel (Just Symbol "allMarginsBottomMargin") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Tenths)))))

data BeatUnit Source #

beat-unit (group)

Constructors

BeatUnit 

Fields

Instances

Eq BeatUnit Source # 
Show BeatUnit Source # 
Generic BeatUnit Source # 

Associated Types

type Rep BeatUnit :: * -> * #

Methods

from :: BeatUnit -> Rep BeatUnit x #

to :: Rep BeatUnit x -> BeatUnit #

EmitXml BeatUnit Source # 
type Rep BeatUnit Source # 
type Rep BeatUnit = D1 * (MetaData "BeatUnit" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "BeatUnit" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "beatUnitBeatUnit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NoteTypeValue)) (S1 * (MetaSel (Just Symbol "beatUnitBeatUnitDot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Empty]))))

mkBeatUnit :: NoteTypeValue -> BeatUnit Source #

Smart constructor for BeatUnit

data Duration Source #

duration (group)

Constructors

Duration 

Fields

Instances

Eq Duration Source # 
Show Duration Source # 
Generic Duration Source # 

Associated Types

type Rep Duration :: * -> * #

Methods

from :: Duration -> Rep Duration x #

to :: Rep Duration x -> Duration #

EmitXml Duration Source # 
type Rep Duration Source # 
type Rep Duration = D1 * (MetaData "Duration" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Duration" PrefixI True) (S1 * (MetaSel (Just Symbol "durationDuration") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PositiveDivisions)))

data Editorial Source #

editorial (group)

Instances

Eq Editorial Source # 
Show Editorial Source # 
Generic Editorial Source # 

Associated Types

type Rep Editorial :: * -> * #

EmitXml Editorial Source # 
type Rep Editorial Source # 
type Rep Editorial = D1 * (MetaData "Editorial" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Editorial" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "editorialFootnote") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Footnote))) (S1 * (MetaSel (Just Symbol "editorialLevel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe GrpLevel)))))

mkEditorial :: Editorial Source #

Smart constructor for Editorial

data EditorialVoiceDirection Source #

editorial-voice-direction (group)

data Footnote Source #

footnote (group)

Constructors

Footnote 

Fields

Instances

Eq Footnote Source # 
Show Footnote Source # 
Generic Footnote Source # 

Associated Types

type Rep Footnote :: * -> * #

Methods

from :: Footnote -> Rep Footnote x #

to :: Rep Footnote x -> Footnote #

EmitXml Footnote Source # 
type Rep Footnote Source # 
type Rep Footnote = D1 * (MetaData "Footnote" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Footnote" PrefixI True) (S1 * (MetaSel (Just Symbol "footnoteFootnote") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FormattedText)))

mkFootnote :: FormattedText -> Footnote Source #

Smart constructor for Footnote

data GrpFullNote Source #

full-note (group)

Constructors

GrpFullNote 

Fields

Instances

Eq GrpFullNote Source # 
Show GrpFullNote Source # 
Generic GrpFullNote Source # 

Associated Types

type Rep GrpFullNote :: * -> * #

EmitXml GrpFullNote Source # 
type Rep GrpFullNote Source # 
type Rep GrpFullNote = D1 * (MetaData "GrpFullNote" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "GrpFullNote" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "fullNoteChord") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Empty))) (S1 * (MetaSel (Just Symbol "fullNoteFullNote") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FullNote))))

data HarmonyChord Source #

harmony-chord (group)

Constructors

HarmonyChord 

Fields

data Layout Source #

layout (group)

Constructors

Layout 

Fields

Instances

Eq Layout Source # 

Methods

(==) :: Layout -> Layout -> Bool #

(/=) :: Layout -> Layout -> Bool #

Show Layout Source # 
Generic Layout Source # 

Associated Types

type Rep Layout :: * -> * #

Methods

from :: Layout -> Rep Layout x #

to :: Rep Layout x -> Layout #

EmitXml Layout Source # 
type Rep Layout Source # 
type Rep Layout = D1 * (MetaData "Layout" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Layout" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "layoutPageLayout") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe PageLayout))) ((:*:) * (S1 * (MetaSel (Just Symbol "layoutSystemLayout") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe SystemLayout))) (S1 * (MetaSel (Just Symbol "layoutStaffLayout") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [StaffLayout])))))

mkLayout :: Layout Source #

Smart constructor for Layout

data LeftRightMargins Source #

left-right-margins (group)

Constructors

LeftRightMargins 

Fields

data GrpLevel Source #

level (group)

Constructors

GrpLevel 

Fields

Instances

Eq GrpLevel Source # 
Show GrpLevel Source # 
Generic GrpLevel Source # 

Associated Types

type Rep GrpLevel :: * -> * #

Methods

from :: GrpLevel -> Rep GrpLevel x #

to :: Rep GrpLevel x -> GrpLevel #

EmitXml GrpLevel Source # 
type Rep GrpLevel Source # 
type Rep GrpLevel = D1 * (MetaData "GrpLevel" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "GrpLevel" PrefixI True) (S1 * (MetaSel (Just Symbol "levelLevel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Level)))

mkGrpLevel :: Level -> GrpLevel Source #

Smart constructor for GrpLevel

data MusicData Source #

music-data (group)

Constructors

MusicData 

Instances

Eq MusicData Source # 
Show MusicData Source # 
Generic MusicData Source # 

Associated Types

type Rep MusicData :: * -> * #

EmitXml MusicData Source # 
type Rep MusicData Source # 
type Rep MusicData = D1 * (MetaData "MusicData" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "MusicData" PrefixI True) (S1 * (MetaSel (Just Symbol "musicDataMusicData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ChxMusicData])))

mkMusicData :: MusicData Source #

Smart constructor for MusicData

data NonTraditionalKey Source #

non-traditional-key (group)

Constructors

NonTraditionalKey 

Fields

data GrpPartGroup Source #

part-group (group)

Constructors

GrpPartGroup 

Fields

Instances

Eq GrpPartGroup Source # 
Show GrpPartGroup Source # 
Generic GrpPartGroup Source # 

Associated Types

type Rep GrpPartGroup :: * -> * #

EmitXml GrpPartGroup Source # 
type Rep GrpPartGroup Source # 
type Rep GrpPartGroup = D1 * (MetaData "GrpPartGroup" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "GrpPartGroup" PrefixI True) (S1 * (MetaSel (Just Symbol "partGroupPartGroup") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PartGroup)))

data ScoreHeader Source #

score-header (group)

Constructors

ScoreHeader 

Fields

Instances

Eq ScoreHeader Source # 
Show ScoreHeader Source # 
Generic ScoreHeader Source # 

Associated Types

type Rep ScoreHeader :: * -> * #

EmitXml ScoreHeader Source # 
type Rep ScoreHeader Source # 
type Rep ScoreHeader = D1 * (MetaData "ScoreHeader" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "ScoreHeader" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "scoreHeaderWork") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Work))) ((:*:) * (S1 * (MetaSel (Just Symbol "scoreHeaderMovementNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe String))) (S1 * (MetaSel (Just Symbol "scoreHeaderMovementTitle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe String))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "scoreHeaderIdentification") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Identification))) (S1 * (MetaSel (Just Symbol "scoreHeaderDefaults") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Defaults)))) ((:*:) * (S1 * (MetaSel (Just Symbol "scoreHeaderCredit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Credit])) (S1 * (MetaSel (Just Symbol "scoreHeaderPartList") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PartList))))))

data ScorePart Source #

score-part (group)

Constructors

ScorePart 

Fields

Instances

Eq ScorePart Source # 
Show ScorePart Source # 
Generic ScorePart Source # 

Associated Types

type Rep ScorePart :: * -> * #

EmitXml ScorePart Source # 
type Rep ScorePart Source # 
type Rep ScorePart = D1 * (MetaData "ScorePart" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "ScorePart" PrefixI True) (S1 * (MetaSel (Just Symbol "scorePartScorePart") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CmpScorePart)))

mkScorePart :: CmpScorePart -> ScorePart Source #

Smart constructor for ScorePart

data Slash Source #

slash (group)

Constructors

Slash 

Fields

Instances

Eq Slash Source # 

Methods

(==) :: Slash -> Slash -> Bool #

(/=) :: Slash -> Slash -> Bool #

Show Slash Source # 

Methods

showsPrec :: Int -> Slash -> ShowS #

show :: Slash -> String #

showList :: [Slash] -> ShowS #

Generic Slash Source # 

Associated Types

type Rep Slash :: * -> * #

Methods

from :: Slash -> Rep Slash x #

to :: Rep Slash x -> Slash #

EmitXml Slash Source # 

Methods

emitXml :: Slash -> XmlRep Source #

type Rep Slash Source # 
type Rep Slash = D1 * (MetaData "Slash" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Slash" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "slashSlashType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NoteTypeValue)) (S1 * (MetaSel (Just Symbol "slashSlashDot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Empty]))))

mkSlash :: NoteTypeValue -> Slash Source #

Smart constructor for Slash

data Staff Source #

staff (group)

Constructors

Staff 

Fields

Instances

Eq Staff Source # 

Methods

(==) :: Staff -> Staff -> Bool #

(/=) :: Staff -> Staff -> Bool #

Show Staff Source # 

Methods

showsPrec :: Int -> Staff -> ShowS #

show :: Staff -> String #

showList :: [Staff] -> ShowS #

Generic Staff Source # 

Associated Types

type Rep Staff :: * -> * #

Methods

from :: Staff -> Rep Staff x #

to :: Rep Staff x -> Staff #

EmitXml Staff Source # 

Methods

emitXml :: Staff -> XmlRep Source #

type Rep Staff Source # 
type Rep Staff = D1 * (MetaData "Staff" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Staff" PrefixI True) (S1 * (MetaSel (Just Symbol "staffStaff") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PositiveInteger)))

mkStaff :: PositiveInteger -> Staff Source #

Smart constructor for Staff

data TraditionalKey Source #

traditional-key (group)

Constructors

TraditionalKey 

Fields

data Tuning Source #

tuning (group)

Constructors

Tuning 

Fields

Instances

Eq Tuning Source # 

Methods

(==) :: Tuning -> Tuning -> Bool #

(/=) :: Tuning -> Tuning -> Bool #

Show Tuning Source # 
Generic Tuning Source # 

Associated Types

type Rep Tuning :: * -> * #

Methods

from :: Tuning -> Rep Tuning x #

to :: Rep Tuning x -> Tuning #

EmitXml Tuning Source # 
type Rep Tuning Source # 
type Rep Tuning = D1 * (MetaData "Tuning" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Tuning" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "tuningTuningStep") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Step)) ((:*:) * (S1 * (MetaSel (Just Symbol "tuningTuningAlter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Semitones))) (S1 * (MetaSel (Just Symbol "tuningTuningOctave") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Octave)))))

mkTuning :: Step -> Octave -> Tuning Source #

Smart constructor for Tuning

data Voice Source #

voice (group)

Constructors

Voice 

Fields

Instances

Eq Voice Source # 

Methods

(==) :: Voice -> Voice -> Bool #

(/=) :: Voice -> Voice -> Bool #

Show Voice Source # 

Methods

showsPrec :: Int -> Voice -> ShowS #

show :: Voice -> String #

showList :: [Voice] -> ShowS #

Generic Voice Source # 

Associated Types

type Rep Voice :: * -> * #

Methods

from :: Voice -> Rep Voice x #

to :: Rep Voice x -> Voice #

EmitXml Voice Source # 

Methods

emitXml :: Voice -> XmlRep Source #

type Rep Voice Source # 
type Rep Voice = D1 * (MetaData "Voice" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.1-Dcfp5nXbYFYCBmngx9xJB4" False) (C1 * (MetaCons "Voice" PrefixI True) (S1 * (MetaSel (Just Symbol "voiceVoice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)))

mkVoice :: String -> Voice Source #

Smart constructor for Voice