fadno-xml-1.1.2: 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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Ord ID Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ID Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> ID -> ShowS #

show :: ID -> String #

showList :: [ID] -> ShowS #

IsString ID Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

fromString :: String -> ID #

Generic ID Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ID :: Type -> Type #

Methods

from :: ID -> Rep ID x #

to :: Rep ID x -> ID #

EmitXml ID Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: ID -> XmlRep Source #

type Rep ID Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ID = D1 (MetaData "ID" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "ID" PrefixI True) (S1 (MetaSel (Just "iD") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NCName)))

newtype IDREF Source #

xs:IDREF (simple)

Constructors

IDREF 

Fields

Instances
Eq IDREF Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Ord IDREF Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show IDREF Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> IDREF -> ShowS #

show :: IDREF -> String #

showList :: [IDREF] -> ShowS #

IsString IDREF Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

fromString :: String -> IDREF #

Generic IDREF Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep IDREF :: Type -> Type #

Methods

from :: IDREF -> Rep IDREF x #

to :: Rep IDREF x -> IDREF #

EmitXml IDREF Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: IDREF -> XmlRep Source #

type Rep IDREF Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep IDREF = D1 (MetaData "IDREF" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "IDREF" PrefixI True) (S1 (MetaSel (Just "iDREF") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NCName)))

newtype NCName Source #

xs:NCName (simple)

Constructors

NCName 

Fields

Instances
Eq NCName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Ord NCName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read NCName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show NCName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

IsString NCName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

fromString :: String -> NCName #

Generic NCName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep NCName :: Type -> Type #

Methods

from :: NCName -> Rep NCName x #

to :: Rep NCName x -> NCName #

EmitXml NCName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NCName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NCName = D1 (MetaData "NCName" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "NCName" PrefixI True) (S1 (MetaSel (Just "nCName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)))

newtype NMTOKEN Source #

xs:NMTOKEN (simple)

Constructors

NMTOKEN 

Fields

Instances
Eq NMTOKEN Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Ord NMTOKEN Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read NMTOKEN Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show NMTOKEN Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

IsString NMTOKEN Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

fromString :: String -> NMTOKEN #

Generic NMTOKEN Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep NMTOKEN :: Type -> Type #

Methods

from :: NMTOKEN -> Rep NMTOKEN x #

to :: Rep NMTOKEN x -> NMTOKEN #

EmitXml NMTOKEN Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NMTOKEN Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NMTOKEN = D1 (MetaData "NMTOKEN" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "NMTOKEN" PrefixI True) (S1 (MetaSel (Just "nMTOKEN") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Token)))

newtype Name Source #

xs:Name (simple)

Constructors

Name 

Fields

Instances
Eq Name Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Ord Name Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Name Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

IsString Name Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

fromString :: String -> Name #

Generic Name Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Name :: Type -> Type #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

EmitXml Name Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Name -> XmlRep Source #

type Rep Name Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Name = D1 (MetaData "Name" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "Name" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum AboveBelow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq AboveBelow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord AboveBelow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show AboveBelow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic AboveBelow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep AboveBelow :: Type -> Type #

EmitXml AboveBelow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep AboveBelow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep AboveBelow = D1 (MetaData "AboveBelow" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "AboveBelowAbove" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "AboveBelowBelow" PrefixI False) (U1 :: Type -> Type))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum AccidentalValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq AccidentalValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord AccidentalValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show AccidentalValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic AccidentalValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep AccidentalValue :: Type -> Type #

EmitXml AccidentalValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep AccidentalValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep AccidentalValue = D1 (MetaData "AccidentalValue" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (((C1 (MetaCons "AccidentalValueSharp" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "AccidentalValueNatural" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "AccidentalValueFlat" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "AccidentalValueDoubleSharp" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "AccidentalValueSharpSharp" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "AccidentalValueFlatFlat" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "AccidentalValueNaturalSharp" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "AccidentalValueNaturalFlat" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "AccidentalValueQuarterFlat" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "AccidentalValueQuarterSharp" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "AccidentalValueThreeQuartersFlat" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "AccidentalValueThreeQuartersSharp" PrefixI False) (U1 :: Type -> Type)))))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum AccordionMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq AccordionMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Integral AccordionMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Num AccordionMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord AccordionMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read AccordionMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Real AccordionMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show AccordionMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic AccordionMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep AccordionMiddle :: Type -> Type #

EmitXml AccordionMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep AccordionMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep AccordionMiddle = D1 (MetaData "AccordionMiddle" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "AccordionMiddle" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum Actuate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq Actuate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Ord Actuate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Actuate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Actuate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Actuate :: Type -> Type #

Methods

from :: Actuate -> Rep Actuate x #

to :: Rep Actuate x -> Actuate #

EmitXml Actuate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Actuate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Actuate = D1 (MetaData "Actuate" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) ((C1 (MetaCons "ActuateOnRequest" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ActuateOnLoad" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "ActuateOther" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ActuateNone" PrefixI False) (U1 :: Type -> Type)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum BackwardForward Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq BackwardForward Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord BackwardForward Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show BackwardForward Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic BackwardForward Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep BackwardForward :: Type -> Type #

EmitXml BackwardForward Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep BackwardForward Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep BackwardForward = D1 (MetaData "BackwardForward" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "BackwardForwardBackward" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "BackwardForwardForward" PrefixI False) (U1 :: Type -> Type))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum BarStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq BarStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord BarStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show BarStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic BarStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep BarStyle :: Type -> Type #

Methods

from :: BarStyle -> Rep BarStyle x #

to :: Rep BarStyle x -> BarStyle #

EmitXml BarStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep BarStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep BarStyle = D1 (MetaData "BarStyle" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (((C1 (MetaCons "BarStyleRegular" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "BarStyleDotted" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "BarStyleDashed" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "BarStyleHeavy" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "BarStyleLightLight" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "BarStyleLightHeavy" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "BarStyleHeavyLight" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "BarStyleHeavyHeavy" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "BarStyleTick" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "BarStyleShort" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "BarStyleNone" PrefixI False) (U1 :: Type -> Type)))))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum BeamLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq BeamLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Integral BeamLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Num BeamLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord BeamLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read BeamLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Real BeamLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show BeamLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic BeamLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep BeamLevel :: Type -> Type #

EmitXml BeamLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep BeamLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep BeamLevel = D1 (MetaData "BeamLevel" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "BeamLevel" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum BeamValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq BeamValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord BeamValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show BeamValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic BeamValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep BeamValue :: Type -> Type #

EmitXml BeamValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep BeamValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep BeamValue = D1 (MetaData "BeamValue" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) ((C1 (MetaCons "BeamValueBegin" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "BeamValueContinue" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "BeamValueEnd" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "BeamValueForwardHook" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "BeamValueBackwardHook" PrefixI False) (U1 :: Type -> Type))))

data ClefSign Source #

clef-sign (simple)

The clef-sign element represents the different clef symbols.

Instances
Bounded ClefSign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum ClefSign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq ClefSign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord ClefSign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ClefSign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ClefSign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ClefSign :: Type -> Type #

Methods

from :: ClefSign -> Rep ClefSign x #

to :: Rep ClefSign x -> ClefSign #

EmitXml ClefSign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ClefSign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ClefSign = D1 (MetaData "ClefSign" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) ((C1 (MetaCons "ClefSignG" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ClefSignF" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ClefSignC" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "ClefSignPercussion" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ClefSignTAB" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ClefSignNone" PrefixI False) (U1 :: Type -> Type))))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Ord Color Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Color Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

IsString Color Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

fromString :: String -> Color #

Generic Color Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Color :: Type -> Type #

Methods

from :: Color -> Rep Color x #

to :: Rep Color x -> Color #

EmitXml Color Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Color -> XmlRep Source #

type Rep Color Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Color = D1 (MetaData "Color" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "Color" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord CommaSeparatedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read CommaSeparatedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show CommaSeparatedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

IsString CommaSeparatedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic CommaSeparatedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep CommaSeparatedText :: Type -> Type #

EmitXml CommaSeparatedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep CommaSeparatedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep CommaSeparatedText = D1 (MetaData "CommaSeparatedText" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "CommaSeparatedText" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum CssFontSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq CssFontSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord CssFontSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show CssFontSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic CssFontSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep CssFontSize :: Type -> Type #

EmitXml CssFontSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep CssFontSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep CssFontSize = D1 (MetaData "CssFontSize" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) ((C1 (MetaCons "CssFontSizeXxSmall" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CssFontSizeXSmall" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CssFontSizeSmall" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "CssFontSizeMedium" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CssFontSizeLarge" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CssFontSizeXLarge" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CssFontSizeXxLarge" PrefixI False) (U1 :: Type -> Type))))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum DegreeTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq DegreeTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord DegreeTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show DegreeTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic DegreeTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep DegreeTypeValue :: Type -> Type #

EmitXml DegreeTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep DegreeTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep DegreeTypeValue = D1 (MetaData "DegreeTypeValue" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "DegreeTypeValueAdd" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "DegreeTypeValueAlter" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DegreeTypeValueSubtract" PrefixI False) (U1 :: Type -> Type)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Fractional Divisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Num Divisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord Divisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read Divisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Real Divisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

RealFrac Divisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Divisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Divisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Divisions :: Type -> Type #

EmitXml Divisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Divisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Divisions = D1 (MetaData "Divisions" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "Divisions" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum Enclosure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq Enclosure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord Enclosure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Enclosure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Enclosure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Enclosure :: Type -> Type #

EmitXml Enclosure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Enclosure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Enclosure = D1 (MetaData "Enclosure" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "EnclosureRectangle" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "EnclosureOval" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "EnclosureNone" PrefixI False) (U1 :: Type -> Type)))

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

Instances
Eq EndingNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord EndingNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read EndingNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show EndingNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

IsString EndingNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic EndingNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep EndingNumber :: Type -> Type #

EmitXml EndingNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep EndingNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep EndingNumber = D1 (MetaData "EndingNumber" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "EndingNumber" PrefixI True) (S1 (MetaSel (Just "endingNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Token)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

minBound :: Fan #

maxBound :: Fan #

Enum Fan Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Ord Fan Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Fan -> ShowS #

show :: Fan -> String #

showList :: [Fan] -> ShowS #

Generic Fan Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Fan :: Type -> Type #

Methods

from :: Fan -> Rep Fan x #

to :: Rep Fan x -> Fan #

EmitXml Fan Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Fan -> XmlRep Source #

type Rep Fan Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Fan = D1 (MetaData "Fan" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "FanAccel" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "FanRit" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "FanNone" PrefixI False) (U1 :: Type -> Type)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum FermataShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq FermataShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord FermataShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show FermataShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic FermataShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep FermataShape :: Type -> Type #

EmitXml FermataShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep FermataShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep FermataShape = D1 (MetaData "FermataShape" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) ((C1 (MetaCons "FermataShapeNormal" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "FermataShapeAngled" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "FermataShapeSquare" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "FermataShape" PrefixI False) (U1 :: Type -> Type)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum Fifths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq Fifths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Integral Fifths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Num Fifths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord Fifths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read Fifths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Real Fifths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Fifths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Fifths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Fifths :: Type -> Type #

Methods

from :: Fifths -> Rep Fifths x #

to :: Rep Fifths x -> Fifths #

EmitXml Fifths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Fifths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Fifths = D1 (MetaData "Fifths" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "Fifths" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show FontSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic FontSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep FontSize :: Type -> Type #

Methods

from :: FontSize -> Rep FontSize x #

to :: Rep FontSize x -> FontSize #

EmitXml FontSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep FontSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep FontSize = D1 (MetaData "FontSize" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "FontSizeDecimal" PrefixI True) (S1 (MetaSel (Just "fontSize1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Decimal)) :+: C1 (MetaCons "FontSizeCssFontSize" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum FontStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq FontStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord FontStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show FontStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic FontStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep FontStyle :: Type -> Type #

EmitXml FontStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep FontStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep FontStyle = D1 (MetaData "FontStyle" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "FontStyleNormal" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "FontStyleItalic" PrefixI False) (U1 :: Type -> Type))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum FontWeight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq FontWeight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord FontWeight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show FontWeight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic FontWeight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep FontWeight :: Type -> Type #

EmitXml FontWeight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep FontWeight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep FontWeight = D1 (MetaData "FontWeight" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "FontWeightNormal" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "FontWeightBold" PrefixI False) (U1 :: Type -> Type))

data GroupBarlineValue Source #

group-barline-value (simple)

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

Instances
Bounded GroupBarlineValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum GroupBarlineValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq GroupBarlineValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord GroupBarlineValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show GroupBarlineValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic GroupBarlineValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep GroupBarlineValue :: Type -> Type #

EmitXml GroupBarlineValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep GroupBarlineValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep GroupBarlineValue = D1 (MetaData "GroupBarlineValue" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "GroupBarlineValueYes" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "GroupBarlineValueNo" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "GroupBarlineValueMensurstrich" PrefixI False) (U1 :: Type -> Type)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum GroupSymbolValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq GroupSymbolValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord GroupSymbolValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show GroupSymbolValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic GroupSymbolValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep GroupSymbolValue :: Type -> Type #

EmitXml GroupSymbolValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep GroupSymbolValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep GroupSymbolValue = D1 (MetaData "GroupSymbolValue" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) ((C1 (MetaCons "GroupSymbolValueNone" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "GroupSymbolValueBrace" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "GroupSymbolValueLine" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "GroupSymbolValueBracket" PrefixI False) (U1 :: Type -> Type)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum HarmonyType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq HarmonyType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord HarmonyType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show HarmonyType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic HarmonyType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep HarmonyType :: Type -> Type #

EmitXml HarmonyType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep HarmonyType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep HarmonyType = D1 (MetaData "HarmonyType" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "HarmonyTypeExplicit" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "HarmonyTypeImplied" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "HarmonyTypeAlternate" PrefixI False) (U1 :: Type -> Type)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum KindValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq KindValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord KindValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show KindValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic KindValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep KindValue :: Type -> Type #

EmitXml KindValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep KindValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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

data Lang Source #

xml:lang (simple)

Constructors

LangLanguage 

Fields

LangLang 

Fields

Instances
Eq Lang Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Lang Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Lang -> ShowS #

show :: Lang -> String #

showList :: [Lang] -> ShowS #

Generic Lang Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Lang :: Type -> Type #

Methods

from :: Lang -> Rep Lang x #

to :: Rep Lang x -> Lang #

EmitXml Lang Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Lang -> XmlRep Source #

type Rep Lang Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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

newtype Language Source #

xs:language (simple)

Constructors

Language 

Fields

Instances
Eq Language Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord Language Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read Language Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Language Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

IsString Language Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Language Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Language :: Type -> Type #

Methods

from :: Language -> Rep Language x #

to :: Rep Language x -> Language #

EmitXml Language Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Language Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Language = D1 (MetaData "Language" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "Language" PrefixI True) (S1 (MetaSel (Just "language") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Token)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum LeftCenterRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq LeftCenterRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord LeftCenterRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show LeftCenterRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic LeftCenterRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep LeftCenterRight :: Type -> Type #

EmitXml LeftCenterRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep LeftCenterRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep LeftCenterRight = D1 (MetaData "LeftCenterRight" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "LeftCenterRightLeft" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "LeftCenterRightCenter" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LeftCenterRightRight" PrefixI False) (U1 :: Type -> Type)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum LeftRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq LeftRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord LeftRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show LeftRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic LeftRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep LeftRight :: Type -> Type #

EmitXml LeftRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep LeftRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep LeftRight = D1 (MetaData "LeftRight" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "LeftRightLeft" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LeftRightRight" PrefixI False) (U1 :: Type -> Type))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum LineEnd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq LineEnd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Ord LineEnd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show LineEnd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic LineEnd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep LineEnd :: Type -> Type #

Methods

from :: LineEnd -> Rep LineEnd x #

to :: Rep LineEnd x -> LineEnd #

EmitXml LineEnd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep LineEnd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep LineEnd = D1 (MetaData "LineEnd" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) ((C1 (MetaCons "LineEndUp" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LineEndDown" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "LineEndBoth" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "LineEndArrow" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LineEndNone" PrefixI False) (U1 :: Type -> Type))))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum LineShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq LineShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord LineShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show LineShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic LineShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep LineShape :: Type -> Type #

EmitXml LineShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep LineShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep LineShape = D1 (MetaData "LineShape" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "LineShapeStraight" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LineShapeCurved" PrefixI False) (U1 :: Type -> Type))

data LineType Source #

line-type (simple)

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

Instances
Bounded LineType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum LineType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq LineType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord LineType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show LineType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic LineType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep LineType :: Type -> Type #

Methods

from :: LineType -> Rep LineType x #

to :: Rep LineType x -> LineType #

EmitXml LineType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep LineType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep LineType = D1 (MetaData "LineType" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) ((C1 (MetaCons "LineTypeSolid" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LineTypeDashed" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "LineTypeDotted" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LineTypeWavy" PrefixI False) (U1 :: Type -> Type)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord LineWidthType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read LineWidthType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show LineWidthType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

IsString LineWidthType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic LineWidthType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep LineWidthType :: Type -> Type #

EmitXml LineWidthType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep LineWidthType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep LineWidthType = D1 (MetaData "LineWidthType" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "LineWidthType" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum MarginType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq MarginType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord MarginType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show MarginType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic MarginType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep MarginType :: Type -> Type #

EmitXml MarginType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep MarginType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep MarginType = D1 (MetaData "MarginType" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "MarginTypeOdd" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "MarginTypeEven" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MarginTypeBoth" PrefixI False) (U1 :: Type -> Type)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum MeasureNumberingValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq MeasureNumberingValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord MeasureNumberingValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show MeasureNumberingValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic MeasureNumberingValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep MeasureNumberingValue :: Type -> Type #

EmitXml MeasureNumberingValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep MeasureNumberingValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep MeasureNumberingValue = D1 (MetaData "MeasureNumberingValue" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "MeasureNumberingValueNone" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "MeasureNumberingValueMeasure" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MeasureNumberingValueSystem" PrefixI False) (U1 :: Type -> Type)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum Midi128 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq Midi128 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Integral Midi128 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Num Midi128 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord Midi128 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read Midi128 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Real Midi128 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Midi128 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Midi128 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Midi128 :: Type -> Type #

Methods

from :: Midi128 -> Rep Midi128 x #

to :: Rep Midi128 x -> Midi128 #

EmitXml Midi128 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Midi128 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Midi128 = D1 (MetaData "Midi128" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "Midi128" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum Midi16 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq Midi16 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Integral Midi16 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Num Midi16 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord Midi16 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read Midi16 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Real Midi16 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Midi16 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Midi16 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Midi16 :: Type -> Type #

Methods

from :: Midi16 -> Rep Midi16 x #

to :: Rep Midi16 x -> Midi16 #

EmitXml Midi16 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Midi16 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Midi16 = D1 (MetaData "Midi16" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "Midi16" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum Midi16384 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq Midi16384 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Integral Midi16384 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Num Midi16384 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord Midi16384 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read Midi16384 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Real Midi16384 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Midi16384 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Midi16384 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Midi16384 :: Type -> Type #

EmitXml Midi16384 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Midi16384 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Midi16384 = D1 (MetaData "Midi16384" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "Midi16384" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Fractional Millimeters Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Num Millimeters Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord Millimeters Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read Millimeters Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Real Millimeters Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

RealFrac Millimeters Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Millimeters Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Millimeters Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Millimeters :: Type -> Type #

EmitXml Millimeters Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Millimeters Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Millimeters = D1 (MetaData "Millimeters" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "Millimeters" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Ord Mode Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Mode Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Mode -> ShowS #

show :: Mode -> String #

showList :: [Mode] -> ShowS #

IsString Mode Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

fromString :: String -> Mode #

Generic Mode Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Mode :: Type -> Type #

Methods

from :: Mode -> Rep Mode x #

to :: Rep Mode x -> Mode #

EmitXml Mode Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Mode -> XmlRep Source #

type Rep Mode Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Mode = D1 (MetaData "Mode" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "Mode" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Fractional NonNegativeDecimal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Num NonNegativeDecimal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord NonNegativeDecimal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read NonNegativeDecimal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Real NonNegativeDecimal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

RealFrac NonNegativeDecimal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show NonNegativeDecimal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic NonNegativeDecimal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep NonNegativeDecimal :: Type -> Type #

EmitXml NonNegativeDecimal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NonNegativeDecimal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NonNegativeDecimal = D1 (MetaData "NonNegativeDecimal" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "NonNegativeDecimal" PrefixI True) (S1 (MetaSel (Just "nonNegativeDecimal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Decimal)))

newtype NonNegativeInteger Source #

xs:nonNegativeInteger (simple)

Constructors

NonNegativeInteger 
Instances
Bounded NonNegativeInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum NonNegativeInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq NonNegativeInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Integral NonNegativeInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Num NonNegativeInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord NonNegativeInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read NonNegativeInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Real NonNegativeInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show NonNegativeInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic NonNegativeInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep NonNegativeInteger :: Type -> Type #

EmitXml NonNegativeInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NonNegativeInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NonNegativeInteger = D1 (MetaData "NonNegativeInteger" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "NonNegativeInteger" PrefixI True) (S1 (MetaSel (Just "nonNegativeInteger") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

newtype NormalizedString Source #

xs:normalizedString (simple)

Constructors

NormalizedString 
Instances
Eq NormalizedString Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord NormalizedString Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read NormalizedString Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show NormalizedString Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

IsString NormalizedString Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic NormalizedString Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep NormalizedString :: Type -> Type #

EmitXml NormalizedString Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NormalizedString Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NormalizedString = D1 (MetaData "NormalizedString" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "NormalizedString" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum NoteSizeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq NoteSizeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord NoteSizeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show NoteSizeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic NoteSizeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep NoteSizeType :: Type -> Type #

EmitXml NoteSizeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NoteSizeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NoteSizeType = D1 (MetaData "NoteSizeType" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "NoteSizeTypeCue" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "NoteSizeTypeGrace" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NoteSizeTypeLarge" PrefixI False) (U1 :: Type -> Type)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum NoteTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq NoteTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord NoteTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show NoteTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic NoteTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep NoteTypeValue :: Type -> Type #

EmitXml NoteTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NoteTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NoteTypeValue = D1 (MetaData "NoteTypeValue" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (((C1 (MetaCons "NoteTypeValue256th" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NoteTypeValue128th" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "NoteTypeValue64th" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "NoteTypeValue32nd" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NoteTypeValue16th" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "NoteTypeValueEighth" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "NoteTypeValueQuarter" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NoteTypeValueHalf" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "NoteTypeValueWhole" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "NoteTypeValueBreve" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NoteTypeValueLong" PrefixI False) (U1 :: Type -> Type)))))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum NoteheadValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq NoteheadValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord NoteheadValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show NoteheadValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic NoteheadValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep NoteheadValue :: Type -> Type #

EmitXml NoteheadValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NoteheadValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum NumberLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq NumberLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Integral NumberLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Num NumberLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord NumberLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read NumberLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Real NumberLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show NumberLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic NumberLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep NumberLevel :: Type -> Type #

EmitXml NumberLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NumberLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NumberLevel = D1 (MetaData "NumberLevel" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "NumberLevel" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum NumberOfLines Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq NumberOfLines Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Integral NumberOfLines Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Num NumberOfLines Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord NumberOfLines Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read NumberOfLines Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Real NumberOfLines Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show NumberOfLines Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic NumberOfLines Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep NumberOfLines :: Type -> Type #

EmitXml NumberOfLines Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NumberOfLines Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NumberOfLines = D1 (MetaData "NumberOfLines" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "NumberOfLines" PrefixI True) (S1 (MetaSel (Just "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
Eq NumberOrNormal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show NumberOrNormal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic NumberOrNormal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep NumberOrNormal :: Type -> Type #

EmitXml NumberOrNormal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NumberOrNormal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NumberOrNormal = D1 (MetaData "NumberOrNormal" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "NumberOrNormalDecimal" PrefixI True) (S1 (MetaSel (Just "numberOrNormal1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Decimal)) :+: C1 (MetaCons "NumberOrNormalNumberOrNormal" PrefixI True) (S1 (MetaSel (Just "numberOrNormal2") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SumNumberOrNormal)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum Octave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq Octave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Integral Octave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Num Octave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord Octave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read Octave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Real Octave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Octave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Octave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Octave :: Type -> Type #

Methods

from :: Octave -> Rep Octave x #

to :: Rep Octave x -> Octave #

EmitXml Octave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Octave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Octave = D1 (MetaData "Octave" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "Octave" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum OverUnder Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq OverUnder Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord OverUnder Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show OverUnder Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic OverUnder Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep OverUnder :: Type -> Type #

EmitXml OverUnder Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep OverUnder Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep OverUnder = D1 (MetaData "OverUnder" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "OverUnderOver" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OverUnderUnder" PrefixI False) (U1 :: Type -> Type))

newtype Percent Source #

percent (simple)

The percent type specifies a percentage from 0 to 100.

Constructors

Percent 

Fields

Instances
Eq Percent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Fractional Percent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Num Percent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord Percent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read Percent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Real Percent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

RealFrac Percent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Percent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Percent :: Type -> Type #

Methods

from :: Percent -> Rep Percent x #

to :: Rep Percent x -> Percent #

EmitXml Percent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Percent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Percent = D1 (MetaData "Percent" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "Percent" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Fractional PositiveDivisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Num PositiveDivisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord PositiveDivisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read PositiveDivisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Real PositiveDivisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

RealFrac PositiveDivisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show PositiveDivisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic PositiveDivisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep PositiveDivisions :: Type -> Type #

EmitXml PositiveDivisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep PositiveDivisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep PositiveDivisions = D1 (MetaData "PositiveDivisions" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "PositiveDivisions" PrefixI True) (S1 (MetaSel (Just "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.

Instances
Eq PositiveIntegerOrEmpty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show PositiveIntegerOrEmpty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic PositiveIntegerOrEmpty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep PositiveIntegerOrEmpty :: Type -> Type #

EmitXml PositiveIntegerOrEmpty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep PositiveIntegerOrEmpty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep PositiveIntegerOrEmpty = D1 (MetaData "PositiveIntegerOrEmpty" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "PositiveIntegerOrEmptyPositiveInteger" PrefixI True) (S1 (MetaSel (Just "positiveIntegerOrEmpty1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PositiveInteger)) :+: C1 (MetaCons "PositiveIntegerOrEmptyPositiveIntegerOrEmpty" PrefixI True) (S1 (MetaSel (Just "positiveIntegerOrEmpty2") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SumPositiveIntegerOrEmpty)))

newtype PositiveInteger Source #

xs:positiveInteger (simple)

Instances
Bounded PositiveInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum PositiveInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq PositiveInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Integral PositiveInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Num PositiveInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord PositiveInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read PositiveInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Real PositiveInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show PositiveInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic PositiveInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep PositiveInteger :: Type -> Type #

EmitXml PositiveInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep PositiveInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep PositiveInteger = D1 (MetaData "PositiveInteger" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "PositiveInteger" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum RehearsalEnclosure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq RehearsalEnclosure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord RehearsalEnclosure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show RehearsalEnclosure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic RehearsalEnclosure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep RehearsalEnclosure :: Type -> Type #

EmitXml RehearsalEnclosure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep RehearsalEnclosure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep RehearsalEnclosure = D1 (MetaData "RehearsalEnclosure" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "RehearsalEnclosureSquare" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "RehearsalEnclosureCircle" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "RehearsalEnclosureNone" PrefixI False) (U1 :: Type -> Type)))

data RightLeftMiddle Source #

right-left-middle (simple)

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

Instances
Bounded RightLeftMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum RightLeftMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq RightLeftMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord RightLeftMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show RightLeftMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic RightLeftMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep RightLeftMiddle :: Type -> Type #

EmitXml RightLeftMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep RightLeftMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep RightLeftMiddle = D1 (MetaData "RightLeftMiddle" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "RightLeftMiddleRight" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "RightLeftMiddleLeft" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "RightLeftMiddleMiddle" PrefixI False) (U1 :: Type -> Type)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Fractional RotationDegrees Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Num RotationDegrees Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord RotationDegrees Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read RotationDegrees Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Real RotationDegrees Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

RealFrac RotationDegrees Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show RotationDegrees Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic RotationDegrees Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep RotationDegrees :: Type -> Type #

EmitXml RotationDegrees Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep RotationDegrees Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep RotationDegrees = D1 (MetaData "RotationDegrees" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "RotationDegrees" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Fractional Semitones Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Num Semitones Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord Semitones Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read Semitones Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Real Semitones Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

RealFrac Semitones Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Semitones Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Semitones Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Semitones :: Type -> Type #

EmitXml Semitones Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Semitones Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Semitones = D1 (MetaData "Semitones" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "Semitones" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum SmpShow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq SmpShow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Ord SmpShow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show SmpShow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic SmpShow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep SmpShow :: Type -> Type #

Methods

from :: SmpShow -> Rep SmpShow x #

to :: Rep SmpShow x -> SmpShow #

EmitXml SmpShow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SmpShow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SmpShow = D1 (MetaData "SmpShow" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) ((C1 (MetaCons "ShowNew" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ShowReplace" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "ShowEmbed" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ShowOther" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ShowNone" PrefixI False) (U1 :: Type -> Type))))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum ShowFrets Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq ShowFrets Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord ShowFrets Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ShowFrets Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ShowFrets Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ShowFrets :: Type -> Type #

EmitXml ShowFrets Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ShowFrets Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ShowFrets = D1 (MetaData "ShowFrets" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "ShowFretsNumbers" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ShowFretsLetters" PrefixI False) (U1 :: Type -> Type))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum ShowTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq ShowTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord ShowTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ShowTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ShowTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ShowTuplet :: Type -> Type #

EmitXml ShowTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ShowTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ShowTuplet = D1 (MetaData "ShowTuplet" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "ShowTupletActual" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ShowTupletBoth" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ShowTupletNone" PrefixI False) (U1 :: Type -> Type)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum StaffLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq StaffLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Integral StaffLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Num StaffLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord StaffLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read StaffLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Real StaffLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show StaffLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic StaffLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep StaffLine :: Type -> Type #

EmitXml StaffLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StaffLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StaffLine = D1 (MetaData "StaffLine" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "StaffLine" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum StaffNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq StaffNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Integral StaffNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Num StaffNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord StaffNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read StaffNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Real StaffNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show StaffNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic StaffNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep StaffNumber :: Type -> Type #

EmitXml StaffNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StaffNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StaffNumber = D1 (MetaData "StaffNumber" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "StaffNumber" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum StaffType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq StaffType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord StaffType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show StaffType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic StaffType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep StaffType :: Type -> Type #

EmitXml StaffType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StaffType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StaffType = D1 (MetaData "StaffType" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) ((C1 (MetaCons "StaffTypeOssia" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StaffTypeCue" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "StaffTypeEditorial" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "StaffTypeRegular" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StaffTypeAlternate" PrefixI False) (U1 :: Type -> Type))))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum StartNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq StartNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord StartNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show StartNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic StartNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep StartNote :: Type -> Type #

EmitXml StartNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StartNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StartNote = D1 (MetaData "StartNote" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "StartNoteUpper" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "StartNoteMain" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StartNoteBelow" PrefixI False) (U1 :: Type -> Type)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum StartStop Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq StartStop Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord StartStop Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show StartStop Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic StartStop Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep StartStop :: Type -> Type #

EmitXml StartStop Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StartStop Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StartStop = D1 (MetaData "StartStop" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "StartStopStart" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StartStopStop" PrefixI False) (U1 :: Type -> Type))

data StartStopChange Source #

start-stop-change (simple)

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

Instances
Bounded StartStopChange Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum StartStopChange Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq StartStopChange Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord StartStopChange Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show StartStopChange Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic StartStopChange Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep StartStopChange :: Type -> Type #

EmitXml StartStopChange Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StartStopChange Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StartStopChange = D1 (MetaData "StartStopChange" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "StartStopChangeStart" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "StartStopChangeStop" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StartStopChangeChange" PrefixI False) (U1 :: Type -> Type)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum StartStopContinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq StartStopContinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord StartStopContinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show StartStopContinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic StartStopContinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep StartStopContinue :: Type -> Type #

EmitXml StartStopContinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StartStopContinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StartStopContinue = D1 (MetaData "StartStopContinue" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "StartStopContinueStart" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "StartStopContinueStop" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StartStopContinueContinue" PrefixI False) (U1 :: Type -> Type)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum StartStopDiscontinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq StartStopDiscontinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord StartStopDiscontinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show StartStopDiscontinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic StartStopDiscontinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep StartStopDiscontinue :: Type -> Type #

EmitXml StartStopDiscontinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StartStopDiscontinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StartStopDiscontinue = D1 (MetaData "StartStopDiscontinue" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "StartStopDiscontinueStart" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "StartStopDiscontinueStop" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StartStopDiscontinueDiscontinue" PrefixI False) (U1 :: Type -> Type)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum StartStopSingle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq StartStopSingle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord StartStopSingle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show StartStopSingle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic StartStopSingle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep StartStopSingle :: Type -> Type #

EmitXml StartStopSingle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StartStopSingle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StartStopSingle = D1 (MetaData "StartStopSingle" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "StartStopSingleStart" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "StartStopSingleStop" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StartStopSingleSingle" PrefixI False) (U1 :: Type -> Type)))

data StemValue Source #

stem-value (simple)

The stem type represents the notated stem direction.

Instances
Bounded StemValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum StemValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq StemValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord StemValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show StemValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic StemValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep StemValue :: Type -> Type #

EmitXml StemValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StemValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StemValue = D1 (MetaData "StemValue" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) ((C1 (MetaCons "StemValueDown" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StemValueUp" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "StemValueDouble" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StemValueNone" PrefixI False) (U1 :: Type -> Type)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum Step Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Ord Step Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Step -> ShowS #

show :: Step -> String #

showList :: [Step] -> ShowS #

Generic Step Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Step :: Type -> Type #

Methods

from :: Step -> Rep Step x #

to :: Rep Step x -> Step #

EmitXml Step Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Step -> XmlRep Source #

type Rep Step Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Step = D1 (MetaData "Step" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) ((C1 (MetaCons "StepA" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "StepB" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StepC" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "StepD" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StepE" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "StepF" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StepG" PrefixI False) (U1 :: Type -> Type))))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum StringNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq StringNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Integral StringNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Num StringNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord StringNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read StringNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Real StringNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show StringNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic StringNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep StringNumber :: Type -> Type #

EmitXml StringNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StringNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StringNumber = D1 (MetaData "StringNumber" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "StringNumber" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum Syllabic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq Syllabic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord Syllabic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Syllabic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Syllabic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Syllabic :: Type -> Type #

Methods

from :: Syllabic -> Rep Syllabic x #

to :: Rep Syllabic x -> Syllabic #

EmitXml Syllabic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Syllabic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Syllabic = D1 (MetaData "Syllabic" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) ((C1 (MetaCons "SyllabicSingle" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SyllabicBegin" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "SyllabicEnd" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SyllabicMiddle" PrefixI False) (U1 :: Type -> Type)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum SymbolSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq SymbolSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord SymbolSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show SymbolSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic SymbolSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep SymbolSize :: Type -> Type #

EmitXml SymbolSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SymbolSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SymbolSize = D1 (MetaData "SymbolSize" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "SymbolSizeFull" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "SymbolSizeCue" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SymbolSizeLarge" PrefixI False) (U1 :: Type -> Type)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Fractional Tenths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Num Tenths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord Tenths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read Tenths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Real Tenths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

RealFrac Tenths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Tenths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Tenths :: Type -> Type #

Methods

from :: Tenths -> Rep Tenths x #

to :: Rep Tenths x -> Tenths #

EmitXml Tenths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Tenths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Tenths = D1 (MetaData "Tenths" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "Tenths" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum TextDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq TextDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord TextDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show TextDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic TextDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep TextDirection :: Type -> Type #

EmitXml TextDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TextDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TextDirection = D1 (MetaData "TextDirection" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) ((C1 (MetaCons "TextDirectionLtr" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TextDirectionRtl" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "TextDirectionLro" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TextDirectionRlo" PrefixI False) (U1 :: Type -> Type)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum TimeSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq TimeSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord TimeSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show TimeSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic TimeSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep TimeSymbol :: Type -> Type #

EmitXml TimeSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TimeSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TimeSymbol = D1 (MetaData "TimeSymbol" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) ((C1 (MetaCons "TimeSymbolCommon" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TimeSymbolCut" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "TimeSymbolSingleNumber" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TimeSymbolNormal" PrefixI False) (U1 :: Type -> Type)))

newtype Token Source #

xs:token (simple)

Constructors

Token 
Instances
Eq Token Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Ord Token Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Token Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

IsString Token Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

fromString :: String -> Token #

Generic Token Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Token :: Type -> Type #

Methods

from :: Token -> Rep Token x #

to :: Rep Token x -> Token #

EmitXml Token Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Token -> XmlRep Source #

type Rep Token Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Token = D1 (MetaData "Token" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "Token" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum TopBottom Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq TopBottom Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord TopBottom Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show TopBottom Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic TopBottom Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep TopBottom :: Type -> Type #

EmitXml TopBottom Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TopBottom Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TopBottom = D1 (MetaData "TopBottom" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "TopBottomTop" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TopBottomBottom" PrefixI False) (U1 :: Type -> Type))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum TremoloMarks Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq TremoloMarks Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Integral TremoloMarks Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Num TremoloMarks Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord TremoloMarks Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read TremoloMarks Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Real TremoloMarks Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show TremoloMarks Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic TremoloMarks Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep TremoloMarks :: Type -> Type #

EmitXml TremoloMarks Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TremoloMarks Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TremoloMarks = D1 (MetaData "TremoloMarks" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "TremoloMarks" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Fractional TrillBeats Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Num TrillBeats Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord TrillBeats Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read TrillBeats Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Real TrillBeats Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

RealFrac TrillBeats Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show TrillBeats Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic TrillBeats Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep TrillBeats :: Type -> Type #

EmitXml TrillBeats Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TrillBeats Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TrillBeats = D1 (MetaData "TrillBeats" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "TrillBeats" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum TrillStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq TrillStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord TrillStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show TrillStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic TrillStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep TrillStep :: Type -> Type #

EmitXml TrillStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TrillStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TrillStep = D1 (MetaData "TrillStep" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "TrillStepWhole" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "TrillStepHalf" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TrillStepUnison" PrefixI False) (U1 :: Type -> Type)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum TwoNoteTurn Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq TwoNoteTurn Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord TwoNoteTurn Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show TwoNoteTurn Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic TwoNoteTurn Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep TwoNoteTurn :: Type -> Type #

EmitXml TwoNoteTurn Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TwoNoteTurn Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TwoNoteTurn = D1 (MetaData "TwoNoteTurn" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "TwoNoteTurnWhole" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "TwoNoteTurnHalf" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TwoNoteTurnNone" PrefixI False) (U1 :: Type -> Type)))

data Type Source #

xlink:type (simple)

Constructors

TypeSimple

simple

Instances
Bounded Type Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum Type Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Ord Type Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Generic Type Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Type :: Type -> Type #

Methods

from :: Type -> Rep Type x #

to :: Rep Type x -> Type #

EmitXml Type Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Type -> XmlRep Source #

type Rep Type Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Type = D1 (MetaData "Type" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "TypeSimple" PrefixI False) (U1 :: Type -> Type))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum UpDown Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq UpDown Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Ord UpDown Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show UpDown Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic UpDown Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep UpDown :: Type -> Type #

Methods

from :: UpDown -> Rep UpDown x #

to :: Rep UpDown x -> UpDown #

EmitXml UpDown Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep UpDown Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep UpDown = D1 (MetaData "UpDown" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "UpDownUp" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "UpDownDown" PrefixI False) (U1 :: Type -> Type))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum UpDownStop Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq UpDownStop Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord UpDownStop Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show UpDownStop Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic UpDownStop Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep UpDownStop :: Type -> Type #

EmitXml UpDownStop Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep UpDownStop Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep UpDownStop = D1 (MetaData "UpDownStop" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "UpDownStopUp" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "UpDownStopDown" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "UpDownStopStop" PrefixI False) (U1 :: Type -> Type)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum UprightInverted Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq UprightInverted Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord UprightInverted Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show UprightInverted Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic UprightInverted Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep UprightInverted :: Type -> Type #

EmitXml UprightInverted Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep UprightInverted Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep UprightInverted = D1 (MetaData "UprightInverted" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "UprightInvertedUpright" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "UprightInvertedInverted" PrefixI False) (U1 :: Type -> Type))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum Valign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq Valign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Ord Valign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Valign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Valign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Valign :: Type -> Type #

Methods

from :: Valign -> Rep Valign x #

to :: Rep Valign x -> Valign #

EmitXml Valign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Valign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Valign = D1 (MetaData "Valign" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) ((C1 (MetaCons "ValignTop" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ValignMiddle" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "ValignBottom" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ValignBaseline" PrefixI False) (U1 :: Type -> Type)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum ValignImage Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq ValignImage Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord ValignImage Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ValignImage Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ValignImage Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ValignImage :: Type -> Type #

EmitXml ValignImage Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ValignImage Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ValignImage = D1 (MetaData "ValignImage" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "ValignImageTop" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ValignImageMiddle" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ValignImageBottom" PrefixI False) (U1 :: Type -> Type)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum WedgeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq WedgeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord WedgeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show WedgeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic WedgeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep WedgeType :: Type -> Type #

EmitXml WedgeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep WedgeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep WedgeType = D1 (MetaData "WedgeType" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "WedgeTypeCrescendo" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "WedgeTypeDiminuendo" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "WedgeTypeStop" PrefixI False) (U1 :: Type -> Type)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum YesNo Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq YesNo Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Ord YesNo Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> YesNo -> ShowS #

show :: YesNo -> String #

showList :: [YesNo] -> ShowS #

Generic YesNo Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep YesNo :: Type -> Type #

Methods

from :: YesNo -> Rep YesNo x #

to :: Rep YesNo x -> YesNo #

EmitXml YesNo Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: YesNo -> XmlRep Source #

type Rep YesNo Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep YesNo = D1 (MetaData "YesNo" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "YesNoYes" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "YesNoNo" PrefixI False) (U1 :: Type -> Type))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show YesNoNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic YesNoNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep YesNoNumber :: Type -> Type #

EmitXml YesNoNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep YesNoNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep YesNoNumber = D1 (MetaData "YesNoNumber" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "YesNoNumberYesNo" PrefixI True) (S1 (MetaSel (Just "yesNoNumber1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 YesNo)) :+: C1 (MetaCons "YesNoNumberDecimal" PrefixI True) (S1 (MetaSel (Just "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

Instances
Eq YyyyMmDd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord YyyyMmDd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Read YyyyMmDd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show YyyyMmDd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

IsString YyyyMmDd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic YyyyMmDd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep YyyyMmDd :: Type -> Type #

Methods

from :: YyyyMmDd -> Rep YyyyMmDd x #

to :: Rep YyyyMmDd x -> YyyyMmDd #

EmitXml YyyyMmDd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep YyyyMmDd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep YyyyMmDd = D1 (MetaData "YyyyMmDd" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" True) (C1 (MetaCons "YyyyMmDd" PrefixI True) (S1 (MetaSel (Just "yyyyMmDd") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

data SumLang Source #

xml:lang (union)

Constructors

SumLang

//

Instances
Bounded SumLang Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum SumLang Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq SumLang Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Ord SumLang Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show SumLang Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic SumLang Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep SumLang :: Type -> Type #

Methods

from :: SumLang -> Rep SumLang x #

to :: Rep SumLang x -> SumLang #

EmitXml SumLang Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SumLang Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SumLang = D1 (MetaData "SumLang" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "SumLang" PrefixI False) (U1 :: Type -> Type))

data SumNumberOrNormal Source #

number-or-normal (union)

Constructors

NumberOrNormalNormal

normal

Instances
Bounded SumNumberOrNormal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum SumNumberOrNormal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq SumNumberOrNormal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord SumNumberOrNormal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show SumNumberOrNormal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic SumNumberOrNormal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep SumNumberOrNormal :: Type -> Type #

EmitXml SumNumberOrNormal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SumNumberOrNormal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SumNumberOrNormal = D1 (MetaData "SumNumberOrNormal" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "NumberOrNormalNormal" PrefixI False) (U1 :: Type -> Type))

data SumPositiveIntegerOrEmpty Source #

positive-integer-or-empty (union)

Instances
Bounded SumPositiveIntegerOrEmpty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Enum SumPositiveIntegerOrEmpty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Eq SumPositiveIntegerOrEmpty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Ord SumPositiveIntegerOrEmpty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show SumPositiveIntegerOrEmpty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic SumPositiveIntegerOrEmpty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep SumPositiveIntegerOrEmpty :: Type -> Type #

EmitXml SumPositiveIntegerOrEmpty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SumPositiveIntegerOrEmpty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SumPositiveIntegerOrEmpty = D1 (MetaData "SumPositiveIntegerOrEmpty" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "SumPositiveIntegerOrEmpty" PrefixI False) (U1 :: Type -> Type))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Accidental Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Accidental Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Accidental :: Type -> Type #

EmitXml Accidental Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Accidental Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Accidental = D1 (MetaData "Accidental" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Accidental" PrefixI True) (((S1 (MetaSel (Just "accidentalAccidentalValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AccidentalValue) :*: (S1 (MetaSel (Just "accidentalCautionary") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 (MetaSel (Just "accidentalEditorial") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)))) :*: ((S1 (MetaSel (Just "accidentalParentheses") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 (MetaSel (Just "accidentalBracket") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo))) :*: (S1 (MetaSel (Just "accidentalSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SymbolSize)) :*: S1 (MetaSel (Just "accidentalDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))))) :*: (((S1 (MetaSel (Just "accidentalDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "accidentalRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 (MetaSel (Just "accidentalRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "accidentalFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)))) :*: ((S1 (MetaSel (Just "accidentalFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)) :*: S1 (MetaSel (Just "accidentalFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize))) :*: (S1 (MetaSel (Just "accidentalFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show AccidentalMark Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic AccidentalMark Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep AccidentalMark :: Type -> Type #

EmitXml AccidentalMark Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep AccidentalMark Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep AccidentalMark = D1 (MetaData "AccidentalMark" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "AccidentalMark" PrefixI True) (((S1 (MetaSel (Just "accidentalMarkAccidentalValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AccidentalValue) :*: S1 (MetaSel (Just "accidentalMarkDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 (MetaSel (Just "accidentalMarkDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "accidentalMarkRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "accidentalMarkRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 (MetaSel (Just "accidentalMarkFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: (S1 (MetaSel (Just "accidentalMarkFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)) :*: S1 (MetaSel (Just "accidentalMarkFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)))) :*: (S1 (MetaSel (Just "accidentalMarkFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)) :*: (S1 (MetaSel (Just "accidentalMarkColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show AccidentalText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic AccidentalText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep AccidentalText :: Type -> Type #

EmitXml AccidentalText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep AccidentalText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep AccidentalText = D1 (MetaData "AccidentalText" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "AccidentalText" PrefixI True) ((((S1 (MetaSel (Just "accidentalTextAccidentalValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AccidentalValue) :*: S1 (MetaSel (Just "accidentalTextLang") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Lang))) :*: (S1 (MetaSel (Just "accidentalTextEnclosure") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Enclosure)) :*: (S1 (MetaSel (Just "accidentalTextJustify") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe LeftCenterRight)) :*: S1 (MetaSel (Just "accidentalTextHalign") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe LeftCenterRight))))) :*: ((S1 (MetaSel (Just "accidentalTextValign") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Valign)) :*: (S1 (MetaSel (Just "accidentalTextDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "accidentalTextDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)))) :*: (S1 (MetaSel (Just "accidentalTextRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "accidentalTextRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "accidentalTextFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)))))) :*: (((S1 (MetaSel (Just "accidentalTextFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)) :*: S1 (MetaSel (Just "accidentalTextFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize))) :*: (S1 (MetaSel (Just "accidentalTextFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)) :*: (S1 (MetaSel (Just "accidentalTextColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color)) :*: S1 (MetaSel (Just "accidentalTextUnderline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NumberOfLines))))) :*: ((S1 (MetaSel (Just "accidentalTextOverline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NumberOfLines)) :*: (S1 (MetaSel (Just "accidentalTextLineThrough") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NumberOfLines)) :*: S1 (MetaSel (Just "accidentalTextRotation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe RotationDegrees)))) :*: (S1 (MetaSel (Just "accidentalTextLetterSpacing") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NumberOrNormal)) :*: (S1 (MetaSel (Just "accidentalTextLineHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NumberOrNormal)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Accord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Accord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Accord :: Type -> Type #

Methods

from :: Accord -> Rep Accord x #

to :: Rep Accord x -> Accord #

EmitXml Accord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Accord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Accord = D1 (MetaData "Accord" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Accord" PrefixI True) (S1 (MetaSel (Just "accordString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe StringNumber)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show AccordionRegistration Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic AccordionRegistration Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep AccordionRegistration :: Type -> Type #

EmitXml AccordionRegistration Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep AccordionRegistration Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep AccordionRegistration = D1 (MetaData "AccordionRegistration" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "AccordionRegistration" PrefixI True) (((S1 (MetaSel (Just "accordionRegistrationDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "accordionRegistrationDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "accordionRegistrationRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)))) :*: (S1 (MetaSel (Just "accordionRegistrationRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "accordionRegistrationFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 (MetaSel (Just "accordionRegistrationFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle))))) :*: ((S1 (MetaSel (Just "accordionRegistrationFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)) :*: (S1 (MetaSel (Just "accordionRegistrationFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)) :*: S1 (MetaSel (Just "accordionRegistrationColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color)))) :*: (S1 (MetaSel (Just "accordionRegistrationAccordionHigh") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Empty)) :*: (S1 (MetaSel (Just "accordionRegistrationAccordionMiddle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe AccordionMiddle)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Appearance Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Appearance Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Appearance :: Type -> Type #

EmitXml Appearance Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Appearance Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Appearance = D1 (MetaData "Appearance" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Appearance" PrefixI True) (S1 (MetaSel (Just "appearanceLineWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [LineWidth]) :*: (S1 (MetaSel (Just "appearanceNoteSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [NoteSize]) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Arpeggiate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Arpeggiate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Arpeggiate :: Type -> Type #

EmitXml Arpeggiate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Arpeggiate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

mkArpeggiate :: Arpeggiate Source #

Smart constructor for Arpeggiate

data Articulations Source #

articulations (complex)

Articulations and accents are grouped together here.

Instances
Eq Articulations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Articulations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Articulations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Articulations :: Type -> Type #

EmitXml Articulations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Articulations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Articulations = D1 (MetaData "Articulations" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Articulations" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Attributes Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Attributes Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Attributes :: Type -> Type #

EmitXml Attributes Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Attributes Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Attributes = D1 (MetaData "Attributes" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Attributes" PrefixI True) (((S1 (MetaSel (Just "attributesEditorial") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Editorial) :*: (S1 (MetaSel (Just "attributesDivisions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe PositiveDivisions)) :*: S1 (MetaSel (Just "attributesKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Key]))) :*: (S1 (MetaSel (Just "attributesTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Time]) :*: (S1 (MetaSel (Just "attributesStaves") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NonNegativeInteger)) :*: S1 (MetaSel (Just "attributesPartSymbol") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe PartSymbol))))) :*: ((S1 (MetaSel (Just "attributesInstruments") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NonNegativeInteger)) :*: (S1 (MetaSel (Just "attributesClef") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Clef]) :*: S1 (MetaSel (Just "attributesStaffDetails") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [StaffDetails]))) :*: (S1 (MetaSel (Just "attributesTranspose") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Transpose)) :*: (S1 (MetaSel (Just "attributesDirective") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Directive]) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Backup Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Backup Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Backup :: Type -> Type #

Methods

from :: Backup -> Rep Backup x #

to :: Rep Backup x -> Backup #

EmitXml Backup Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Backup Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Backup = D1 (MetaData "Backup" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Backup" PrefixI True) (S1 (MetaSel (Just "backupDuration") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Duration) :*: S1 (MetaSel (Just "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

Instances
Eq BarStyleColor Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show BarStyleColor Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic BarStyleColor Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep BarStyleColor :: Type -> Type #

EmitXml BarStyleColor Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep BarStyleColor Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep BarStyleColor = D1 (MetaData "BarStyleColor" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "BarStyleColor" PrefixI True) (S1 (MetaSel (Just "barStyleColorBarStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BarStyle) :*: S1 (MetaSel (Just "barStyleColorColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color))))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Barline Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Barline Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Barline :: Type -> Type #

Methods

from :: Barline -> Rep Barline x #

to :: Rep Barline x -> Barline #

EmitXml Barline Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Barline Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Barline = D1 (MetaData "Barline" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Barline" PrefixI True) (((S1 (MetaSel (Just "barlineLocation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe RightLeftMiddle)) :*: (S1 (MetaSel (Just "barlineSegno") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Token)) :*: S1 (MetaSel (Just "barlineCoda") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Token)))) :*: (S1 (MetaSel (Just "barlineDivisions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Divisions)) :*: (S1 (MetaSel (Just "barlineBarStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe BarStyleColor)) :*: S1 (MetaSel (Just "barlineEditorial") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Editorial)))) :*: ((S1 (MetaSel (Just "barlineWavyLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe WavyLine)) :*: (S1 (MetaSel (Just "barlineSegno1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe EmptyPrintStyle)) :*: S1 (MetaSel (Just "barlineCoda1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe EmptyPrintStyle)))) :*: (S1 (MetaSel (Just "barlineFermata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Fermata]) :*: (S1 (MetaSel (Just "barlineEnding") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Ending)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Barre Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Barre -> ShowS #

show :: Barre -> String #

showList :: [Barre] -> ShowS #

Generic Barre Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Barre :: Type -> Type #

Methods

from :: Barre -> Rep Barre x #

to :: Rep Barre x -> Barre #

EmitXml Barre Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Barre -> XmlRep Source #

type Rep Barre Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Barre = D1 (MetaData "Barre" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Barre" PrefixI True) (S1 (MetaSel (Just "barreType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StartStop) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Bass Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Bass -> ShowS #

show :: Bass -> String #

showList :: [Bass] -> ShowS #

Generic Bass Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Bass :: Type -> Type #

Methods

from :: Bass -> Rep Bass x #

to :: Rep Bass x -> Bass #

EmitXml Bass Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Bass -> XmlRep Source #

type Rep Bass Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Bass = D1 (MetaData "Bass" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Bass" PrefixI True) (S1 (MetaSel (Just "bassBassStep") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BassStep) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show BassAlter Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic BassAlter Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep BassAlter :: Type -> Type #

EmitXml BassAlter Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep BassAlter Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep BassAlter = D1 (MetaData "BassAlter" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "BassAlter" PrefixI True) (((S1 (MetaSel (Just "bassAlterSemitones") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Semitones) :*: (S1 (MetaSel (Just "bassAlterLocation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe LeftRight)) :*: S1 (MetaSel (Just "bassAlterPrintObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)))) :*: (S1 (MetaSel (Just "bassAlterDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "bassAlterDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "bassAlterRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 (MetaSel (Just "bassAlterRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "bassAlterFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 (MetaSel (Just "bassAlterFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)))) :*: (S1 (MetaSel (Just "bassAlterFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)) :*: (S1 (MetaSel (Just "bassAlterFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show BassStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic BassStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep BassStep :: Type -> Type #

Methods

from :: BassStep -> Rep BassStep x #

to :: Rep BassStep x -> BassStep #

EmitXml BassStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep BassStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Beam Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Beam -> ShowS #

show :: Beam -> String #

showList :: [Beam] -> ShowS #

Generic Beam Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Beam :: Type -> Type #

Methods

from :: Beam -> Rep Beam x #

to :: Rep Beam x -> Beam #

EmitXml Beam Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Beam -> XmlRep Source #

type Rep Beam Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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

Instances
Eq BeatRepeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show BeatRepeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic BeatRepeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep BeatRepeat :: Type -> Type #

EmitXml BeatRepeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep BeatRepeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep BeatRepeat = D1 (MetaData "BeatRepeat" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "BeatRepeat" PrefixI True) ((S1 (MetaSel (Just "beatRepeatType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StartStop) :*: S1 (MetaSel (Just "beatRepeatSlashes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe PositiveInteger))) :*: (S1 (MetaSel (Just "beatRepeatUseDots") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 (MetaSel (Just "beatRepeatSlash") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Slash)))))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Bend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Bend -> ShowS #

show :: Bend -> String #

showList :: [Bend] -> ShowS #

Generic Bend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Bend :: Type -> Type #

Methods

from :: Bend -> Rep Bend x #

to :: Rep Bend x -> Bend #

EmitXml Bend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Bend -> XmlRep Source #

type Rep Bend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Bend = D1 (MetaData "Bend" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Bend" PrefixI True) ((((S1 (MetaSel (Just "bendDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "bendDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 (MetaSel (Just "bendRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "bendRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)))) :*: ((S1 (MetaSel (Just "bendFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 (MetaSel (Just "bendFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle))) :*: (S1 (MetaSel (Just "bendFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)) :*: S1 (MetaSel (Just "bendFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight))))) :*: (((S1 (MetaSel (Just "bendColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color)) :*: S1 (MetaSel (Just "bendAccelerate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo))) :*: (S1 (MetaSel (Just "bendBeats") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe TrillBeats)) :*: S1 (MetaSel (Just "bendFirstBeat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Percent)))) :*: ((S1 (MetaSel (Just "bendLastBeat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Percent)) :*: S1 (MetaSel (Just "bendBendAlter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Semitones)) :*: (S1 (MetaSel (Just "bendBend") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ChxBend)) :*: S1 (MetaSel (Just "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

Instances
Eq Bookmark Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Bookmark Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Bookmark Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Bookmark :: Type -> Type #

Methods

from :: Bookmark -> Rep Bookmark x #

to :: Rep Bookmark x -> Bookmark #

EmitXml Bookmark Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Bookmark Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Bookmark = D1 (MetaData "Bookmark" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Bookmark" PrefixI True) ((S1 (MetaSel (Just "bookmarkId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ID) :*: S1 (MetaSel (Just "bookmarkName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Token))) :*: (S1 (MetaSel (Just "bookmarkElement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NMTOKEN)) :*: S1 (MetaSel (Just "bookmarkPosition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe PositiveInteger)))))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Bracket Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Bracket Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Bracket :: Type -> Type #

Methods

from :: Bracket -> Rep Bracket x #

to :: Rep Bracket x -> Bracket #

EmitXml Bracket Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Bracket Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Cancel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Cancel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Cancel :: Type -> Type #

Methods

from :: Cancel -> Rep Cancel x #

to :: Rep Cancel x -> Cancel #

EmitXml Cancel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Cancel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Cancel = D1 (MetaData "Cancel" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Cancel" PrefixI True) (S1 (MetaSel (Just "cancelFifths") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Fifths) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Clef Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Clef -> ShowS #

show :: Clef -> String #

showList :: [Clef] -> ShowS #

Generic Clef Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Clef :: Type -> Type #

Methods

from :: Clef -> Rep Clef x #

to :: Rep Clef x -> Clef #

EmitXml Clef Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Clef -> XmlRep Source #

type Rep Clef Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Clef = D1 (MetaData "Clef" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Clef" PrefixI True) ((((S1 (MetaSel (Just "clefNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe StaffNumber)) :*: S1 (MetaSel (Just "clefAdditional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo))) :*: (S1 (MetaSel (Just "clefSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SymbolSize)) :*: S1 (MetaSel (Just "clefDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)))) :*: ((S1 (MetaSel (Just "clefDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "clefRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 (MetaSel (Just "clefRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "clefFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText))))) :*: (((S1 (MetaSel (Just "clefFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)) :*: S1 (MetaSel (Just "clefFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize))) :*: (S1 (MetaSel (Just "clefFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)) :*: S1 (MetaSel (Just "clefColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color)))) :*: ((S1 (MetaSel (Just "clefPrintObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 (MetaSel (Just "clefSign") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ClefSign)) :*: (S1 (MetaSel (Just "clefLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe StaffLine)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Credit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Credit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Credit :: Type -> Type #

Methods

from :: Credit -> Rep Credit x #

to :: Rep Credit x -> Credit #

EmitXml Credit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Credit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Dashes Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Dashes Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Dashes :: Type -> Type #

Methods

from :: Dashes -> Rep Dashes x #

to :: Rep Dashes x -> Dashes #

EmitXml Dashes Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Dashes Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Defaults Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Defaults Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Defaults :: Type -> Type #

Methods

from :: Defaults -> Rep Defaults x #

to :: Rep Defaults x -> Defaults #

EmitXml Defaults Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Defaults Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Degree Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Degree Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Degree :: Type -> Type #

Methods

from :: Degree -> Rep Degree x #

to :: Rep Degree x -> Degree #

EmitXml Degree Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Degree Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Degree = D1 (MetaData "Degree" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Degree" PrefixI True) ((S1 (MetaSel (Just "degreePrintObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 (MetaSel (Just "degreeDegreeValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DegreeValue)) :*: (S1 (MetaSel (Just "degreeDegreeAlter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DegreeAlter) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show DegreeAlter Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic DegreeAlter Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep DegreeAlter :: Type -> Type #

EmitXml DegreeAlter Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep DegreeAlter Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep DegreeAlter = D1 (MetaData "DegreeAlter" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "DegreeAlter" PrefixI True) (((S1 (MetaSel (Just "degreeAlterSemitones") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Semitones) :*: S1 (MetaSel (Just "degreeAlterPlusMinus") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo))) :*: (S1 (MetaSel (Just "degreeAlterDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "degreeAlterDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "degreeAlterRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 (MetaSel (Just "degreeAlterRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "degreeAlterFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 (MetaSel (Just "degreeAlterFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)))) :*: (S1 (MetaSel (Just "degreeAlterFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)) :*: (S1 (MetaSel (Just "degreeAlterFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show DegreeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic DegreeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep DegreeType :: Type -> Type #

EmitXml DegreeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep DegreeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep DegreeType = D1 (MetaData "DegreeType" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "DegreeType" PrefixI True) (((S1 (MetaSel (Just "degreeTypeDegreeTypeValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DegreeTypeValue) :*: S1 (MetaSel (Just "degreeTypeText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Token))) :*: (S1 (MetaSel (Just "degreeTypeDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "degreeTypeDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "degreeTypeRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 (MetaSel (Just "degreeTypeRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "degreeTypeFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 (MetaSel (Just "degreeTypeFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)))) :*: (S1 (MetaSel (Just "degreeTypeFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)) :*: (S1 (MetaSel (Just "degreeTypeFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show DegreeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic DegreeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep DegreeValue :: Type -> Type #

EmitXml DegreeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep DegreeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep DegreeValue = D1 (MetaData "DegreeValue" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "DegreeValue" PrefixI True) (((S1 (MetaSel (Just "degreeValuePositiveInteger") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PositiveInteger) :*: S1 (MetaSel (Just "degreeValueText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Token))) :*: (S1 (MetaSel (Just "degreeValueDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "degreeValueDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "degreeValueRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 (MetaSel (Just "degreeValueRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "degreeValueFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 (MetaSel (Just "degreeValueFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)))) :*: (S1 (MetaSel (Just "degreeValueFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)) :*: (S1 (MetaSel (Just "degreeValueFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Direction Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Direction Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Direction :: Type -> Type #

EmitXml Direction Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Direction Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show DirectionType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic DirectionType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep DirectionType :: Type -> Type #

EmitXml DirectionType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep DirectionType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep DirectionType = D1 (MetaData "DirectionType" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "DirectionType" PrefixI True) (S1 (MetaSel (Just "directionTypeDirectionType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ChxDirectionType)))

data Directive Source #

directive (complex)

Constructors

Directive 

Fields

Instances
Eq Directive Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Directive Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Directive Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Directive :: Type -> Type #

EmitXml Directive Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Directive Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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.

Instances
Eq DisplayStepOctave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show DisplayStepOctave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic DisplayStepOctave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep DisplayStepOctave :: Type -> Type #

EmitXml DisplayStepOctave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep DisplayStepOctave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep DisplayStepOctave = D1 (MetaData "DisplayStepOctave" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "DisplayStepOctave" PrefixI True) (S1 (MetaSel (Just "displayStepOctaveDisplayStepOctave") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SeqDisplayStepOctave))))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Dynamics Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Dynamics Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Dynamics :: Type -> Type #

Methods

from :: Dynamics -> Rep Dynamics x #

to :: Rep Dynamics x -> Dynamics #

EmitXml Dynamics Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Dynamics Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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

Instances
Eq Elision Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Elision Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Elision Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Elision :: Type -> Type #

Methods

from :: Elision -> Rep Elision x #

to :: Rep Elision x -> Elision #

EmitXml Elision Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Elision Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Empty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Empty -> ShowS #

show :: Empty -> String #

showList :: [Empty] -> ShowS #

Generic Empty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Empty :: Type -> Type #

Methods

from :: Empty -> Rep Empty x #

to :: Rep Empty x -> Empty #

EmitXml Empty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Empty -> XmlRep Source #

type Rep Empty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Empty = D1 (MetaData "Empty" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Empty" PrefixI False) (U1 :: Type -> Type))

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

Instances
Eq EmptyFont Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show EmptyFont Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic EmptyFont Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep EmptyFont :: Type -> Type #

EmitXml EmptyFont Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep EmptyFont Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep EmptyFont = D1 (MetaData "EmptyFont" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "EmptyFont" PrefixI True) ((S1 (MetaSel (Just "emptyFontFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 (MetaSel (Just "emptyFontFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle))) :*: (S1 (MetaSel (Just "emptyFontFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)) :*: S1 (MetaSel (Just "emptyFontFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)))))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show EmptyLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic EmptyLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep EmptyLine :: Type -> Type #

EmitXml EmptyLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep EmptyLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep EmptyLine = D1 (MetaData "EmptyLine" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "EmptyLine" PrefixI True) (((S1 (MetaSel (Just "emptyLineLineShape") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe LineShape)) :*: (S1 (MetaSel (Just "emptyLineLineType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe LineType)) :*: S1 (MetaSel (Just "emptyLineDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)))) :*: (S1 (MetaSel (Just "emptyLineDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "emptyLineRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "emptyLineRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 (MetaSel (Just "emptyLineFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: (S1 (MetaSel (Just "emptyLineFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)) :*: S1 (MetaSel (Just "emptyLineFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)))) :*: (S1 (MetaSel (Just "emptyLineFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)) :*: (S1 (MetaSel (Just "emptyLineColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show EmptyPlacement Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic EmptyPlacement Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep EmptyPlacement :: Type -> Type #

EmitXml EmptyPlacement Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep EmptyPlacement Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show EmptyPrintStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic EmptyPrintStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep EmptyPrintStyle :: Type -> Type #

EmitXml EmptyPrintStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep EmptyPrintStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep EmptyPrintStyle = D1 (MetaData "EmptyPrintStyle" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "EmptyPrintStyle" PrefixI True) (((S1 (MetaSel (Just "emptyPrintStyleDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "emptyPrintStyleDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 (MetaSel (Just "emptyPrintStyleRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "emptyPrintStyleRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)))) :*: ((S1 (MetaSel (Just "emptyPrintStyleFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 (MetaSel (Just "emptyPrintStyleFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle))) :*: (S1 (MetaSel (Just "emptyPrintStyleFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)) :*: (S1 (MetaSel (Just "emptyPrintStyleFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show EmptyTrillSound Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic EmptyTrillSound Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep EmptyTrillSound :: Type -> Type #

EmitXml EmptyTrillSound Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep EmptyTrillSound Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep EmptyTrillSound = D1 (MetaData "EmptyTrillSound" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "EmptyTrillSound" PrefixI True) ((((S1 (MetaSel (Just "emptyTrillSoundDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "emptyTrillSoundDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 (MetaSel (Just "emptyTrillSoundRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "emptyTrillSoundRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)))) :*: ((S1 (MetaSel (Just "emptyTrillSoundFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 (MetaSel (Just "emptyTrillSoundFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle))) :*: (S1 (MetaSel (Just "emptyTrillSoundFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)) :*: S1 (MetaSel (Just "emptyTrillSoundFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight))))) :*: (((S1 (MetaSel (Just "emptyTrillSoundColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color)) :*: S1 (MetaSel (Just "emptyTrillSoundPlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe AboveBelow))) :*: (S1 (MetaSel (Just "emptyTrillSoundStartNote") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe StartNote)) :*: S1 (MetaSel (Just "emptyTrillSoundTrillStep") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe TrillStep)))) :*: ((S1 (MetaSel (Just "emptyTrillSoundTwoNoteTurn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe TwoNoteTurn)) :*: S1 (MetaSel (Just "emptyTrillSoundAccelerate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo))) :*: (S1 (MetaSel (Just "emptyTrillSoundBeats") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe TrillBeats)) :*: (S1 (MetaSel (Just "emptyTrillSoundSecondBeat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Percent)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Encoding Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Encoding Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Encoding :: Type -> Type #

Methods

from :: Encoding -> Rep Encoding x #

to :: Rep Encoding x -> Encoding #

EmitXml Encoding Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Encoding Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Encoding = D1 (MetaData "Encoding" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Encoding" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Ending Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Ending Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Ending :: Type -> Type #

Methods

from :: Ending -> Rep Ending x #

to :: Rep Ending x -> Ending #

EmitXml Ending Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Ending Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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

data Extend Source #

extend (complex)

The extend type represents word extensions for lyrics.

Constructors

Extend 

Fields

Instances
Eq Extend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Extend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Extend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Extend :: Type -> Type #

Methods

from :: Extend -> Rep Extend x #

to :: Rep Extend x -> Extend #

EmitXml Extend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Extend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Feature Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Feature Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Feature :: Type -> Type #

Methods

from :: Feature -> Rep Feature x #

to :: Rep Feature x -> Feature #

EmitXml Feature Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Feature Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Feature = D1 (MetaData "Feature" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Feature" PrefixI True) (S1 (MetaSel (Just "featureString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Fermata Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Fermata Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Fermata :: Type -> Type #

Methods

from :: Fermata -> Rep Fermata x #

to :: Rep Fermata x -> Fermata #

EmitXml Fermata Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Fermata Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Figure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Figure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Figure :: Type -> Type #

Methods

from :: Figure -> Rep Figure x #

to :: Rep Figure x -> Figure #

EmitXml Figure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Figure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Figure = D1 (MetaData "Figure" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Figure" PrefixI True) ((S1 (MetaSel (Just "figurePrefix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe StyleText)) :*: S1 (MetaSel (Just "figureFigureNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe StyleText))) :*: (S1 (MetaSel (Just "figureSuffix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe StyleText)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show FiguredBass Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic FiguredBass Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep FiguredBass :: Type -> Type #

EmitXml FiguredBass Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep FiguredBass Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep FiguredBass = D1 (MetaData "FiguredBass" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "FiguredBass" PrefixI True) ((((S1 (MetaSel (Just "figuredBassParentheses") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 (MetaSel (Just "figuredBassDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 (MetaSel (Just "figuredBassDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "figuredBassRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)))) :*: ((S1 (MetaSel (Just "figuredBassRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "figuredBassFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText))) :*: (S1 (MetaSel (Just "figuredBassFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)) :*: S1 (MetaSel (Just "figuredBassFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize))))) :*: (((S1 (MetaSel (Just "figuredBassFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)) :*: S1 (MetaSel (Just "figuredBassColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color))) :*: (S1 (MetaSel (Just "figuredBassPrintDot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 (MetaSel (Just "figuredBassPrintLyric") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)))) :*: ((S1 (MetaSel (Just "figuredBassPrintObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 (MetaSel (Just "figuredBassPrintSpacing") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo))) :*: (S1 (MetaSel (Just "figuredBassFigure") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Figure]) :*: (S1 (MetaSel (Just "figuredBassDuration") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Duration)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Fingering Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Fingering Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Fingering :: Type -> Type #

EmitXml Fingering Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Fingering Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Fingering = D1 (MetaData "Fingering" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Fingering" PrefixI True) (((S1 (MetaSel (Just "fingeringString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: (S1 (MetaSel (Just "fingeringSubstitution") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 (MetaSel (Just "fingeringAlternate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)))) :*: (S1 (MetaSel (Just "fingeringDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "fingeringDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "fingeringRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 (MetaSel (Just "fingeringRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "fingeringFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 (MetaSel (Just "fingeringFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)))) :*: ((S1 (MetaSel (Just "fingeringFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)) :*: S1 (MetaSel (Just "fingeringFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight))) :*: (S1 (MetaSel (Just "fingeringColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show FirstFret Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic FirstFret Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep FirstFret :: Type -> Type #

EmitXml FirstFret Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep FirstFret Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep FirstFret = D1 (MetaData "FirstFret" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "FirstFret" PrefixI True) (S1 (MetaSel (Just "firstFretPositiveInteger") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PositiveInteger) :*: (S1 (MetaSel (Just "firstFretText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Token)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show FormattedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic FormattedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep FormattedText :: Type -> Type #

EmitXml FormattedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep FormattedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep FormattedText = D1 (MetaData "FormattedText" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "FormattedText" PrefixI True) ((((S1 (MetaSel (Just "formattedTextString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "formattedTextLang") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Lang))) :*: (S1 (MetaSel (Just "formattedTextEnclosure") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Enclosure)) :*: (S1 (MetaSel (Just "formattedTextJustify") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe LeftCenterRight)) :*: S1 (MetaSel (Just "formattedTextHalign") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe LeftCenterRight))))) :*: ((S1 (MetaSel (Just "formattedTextValign") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Valign)) :*: (S1 (MetaSel (Just "formattedTextDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "formattedTextDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)))) :*: (S1 (MetaSel (Just "formattedTextRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "formattedTextRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "formattedTextFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)))))) :*: (((S1 (MetaSel (Just "formattedTextFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)) :*: S1 (MetaSel (Just "formattedTextFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize))) :*: (S1 (MetaSel (Just "formattedTextFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)) :*: (S1 (MetaSel (Just "formattedTextColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color)) :*: S1 (MetaSel (Just "formattedTextUnderline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NumberOfLines))))) :*: ((S1 (MetaSel (Just "formattedTextOverline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NumberOfLines)) :*: (S1 (MetaSel (Just "formattedTextLineThrough") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NumberOfLines)) :*: S1 (MetaSel (Just "formattedTextRotation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe RotationDegrees)))) :*: (S1 (MetaSel (Just "formattedTextLetterSpacing") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NumberOrNormal)) :*: (S1 (MetaSel (Just "formattedTextLineHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NumberOrNormal)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Forward Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Forward Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Forward :: Type -> Type #

Methods

from :: Forward -> Rep Forward x #

to :: Rep Forward x -> Forward #

EmitXml Forward Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Forward Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Forward = D1 (MetaData "Forward" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Forward" PrefixI True) (S1 (MetaSel (Just "forwardDuration") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Duration) :*: (S1 (MetaSel (Just "forwardEditorialVoice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EditorialVoice) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Frame Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Frame -> ShowS #

show :: Frame -> String #

showList :: [Frame] -> ShowS #

Generic Frame Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Frame :: Type -> Type #

Methods

from :: Frame -> Rep Frame x #

to :: Rep Frame x -> Frame #

EmitXml Frame Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Frame -> XmlRep Source #

type Rep Frame Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Frame = D1 (MetaData "Frame" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Frame" PrefixI True) (((S1 (MetaSel (Just "frameHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "frameWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "frameDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)))) :*: (S1 (MetaSel (Just "frameDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "frameRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "frameRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 (MetaSel (Just "frameColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color)) :*: (S1 (MetaSel (Just "frameHalign") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe LeftCenterRight)) :*: S1 (MetaSel (Just "frameValign") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Valign)))) :*: ((S1 (MetaSel (Just "frameFrameStrings") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PositiveInteger) :*: S1 (MetaSel (Just "frameFrameFrets") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PositiveInteger)) :*: (S1 (MetaSel (Just "frameFirstFret") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FirstFret)) :*: S1 (MetaSel (Just "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

Instances
Eq FrameNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show FrameNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic FrameNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep FrameNote :: Type -> Type #

EmitXml FrameNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep FrameNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep FrameNote = D1 (MetaData "FrameNote" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "FrameNote" PrefixI True) ((S1 (MetaSel (Just "frameNoteString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CmpString) :*: S1 (MetaSel (Just "frameNoteFret") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Fret)) :*: (S1 (MetaSel (Just "frameNoteFingering") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Fingering)) :*: S1 (MetaSel (Just "frameNoteBarre") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Barre)))))

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

Instances
Eq Fret Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Fret Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Fret -> ShowS #

show :: Fret -> String #

showList :: [Fret] -> ShowS #

Generic Fret Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Fret :: Type -> Type #

Methods

from :: Fret -> Rep Fret x #

to :: Rep Fret x -> Fret #

EmitXml Fret Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Fret -> XmlRep Source #

type Rep Fret Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Glissando Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Glissando Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Glissando :: Type -> Type #

EmitXml Glissando Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Glissando Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Glissando = D1 (MetaData "Glissando" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Glissando" PrefixI True) (((S1 (MetaSel (Just "glissandoString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: (S1 (MetaSel (Just "glissandoType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StartStop) :*: S1 (MetaSel (Just "glissandoNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NumberLevel)))) :*: (S1 (MetaSel (Just "glissandoLineType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe LineType)) :*: (S1 (MetaSel (Just "glissandoDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "glissandoDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 (MetaSel (Just "glissandoRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "glissandoRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "glissandoFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)))) :*: ((S1 (MetaSel (Just "glissandoFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)) :*: S1 (MetaSel (Just "glissandoFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize))) :*: (S1 (MetaSel (Just "glissandoFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Grace Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Grace -> ShowS #

show :: Grace -> String #

showList :: [Grace] -> ShowS #

Generic Grace Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Grace :: Type -> Type #

Methods

from :: Grace -> Rep Grace x #

to :: Rep Grace x -> Grace #

EmitXml Grace Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Grace -> XmlRep Source #

type Rep Grace Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Grace = D1 (MetaData "Grace" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Grace" PrefixI True) ((S1 (MetaSel (Just "graceStealTimePrevious") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Percent)) :*: S1 (MetaSel (Just "graceStealTimeFollowing") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Percent))) :*: (S1 (MetaSel (Just "graceMakeTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Divisions)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show GroupBarline Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic GroupBarline Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep GroupBarline :: Type -> Type #

EmitXml GroupBarline Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep GroupBarline Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep GroupBarline = D1 (MetaData "GroupBarline" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "GroupBarline" PrefixI True) (S1 (MetaSel (Just "groupBarlineGroupBarlineValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 GroupBarlineValue) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show GroupName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic GroupName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep GroupName :: Type -> Type #

EmitXml GroupName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep GroupName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show GroupSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic GroupSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep GroupSymbol :: Type -> Type #

EmitXml GroupSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep GroupSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep GroupSymbol = D1 (MetaData "GroupSymbol" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "GroupSymbol" PrefixI True) ((S1 (MetaSel (Just "groupSymbolGroupSymbolValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 GroupSymbolValue) :*: (S1 (MetaSel (Just "groupSymbolDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "groupSymbolDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)))) :*: (S1 (MetaSel (Just "groupSymbolRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "groupSymbolRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "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
Eq Grouping Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Grouping Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Grouping Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Grouping :: Type -> Type #

Methods

from :: Grouping -> Rep Grouping x #

to :: Rep Grouping x -> Grouping #

EmitXml Grouping Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Grouping Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Grouping = D1 (MetaData "Grouping" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Grouping" PrefixI True) ((S1 (MetaSel (Just "groupingType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StartStopSingle) :*: S1 (MetaSel (Just "groupingNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Token))) :*: (S1 (MetaSel (Just "groupingMemberOf") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Token)) :*: S1 (MetaSel (Just "groupingFeature") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Feature]))))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show HammerOnPullOff Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic HammerOnPullOff Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep HammerOnPullOff :: Type -> Type #

EmitXml HammerOnPullOff Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep HammerOnPullOff Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep HammerOnPullOff = D1 (MetaData "HammerOnPullOff" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "HammerOnPullOff" PrefixI True) (((S1 (MetaSel (Just "hammerOnPullOffString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: (S1 (MetaSel (Just "hammerOnPullOffType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StartStop) :*: S1 (MetaSel (Just "hammerOnPullOffNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NumberLevel)))) :*: (S1 (MetaSel (Just "hammerOnPullOffDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "hammerOnPullOffDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "hammerOnPullOffRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 (MetaSel (Just "hammerOnPullOffRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "hammerOnPullOffFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 (MetaSel (Just "hammerOnPullOffFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)))) :*: ((S1 (MetaSel (Just "hammerOnPullOffFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)) :*: S1 (MetaSel (Just "hammerOnPullOffFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight))) :*: (S1 (MetaSel (Just "hammerOnPullOffColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Harmonic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Harmonic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Harmonic :: Type -> Type #

Methods

from :: Harmonic -> Rep Harmonic x #

to :: Rep Harmonic x -> Harmonic #

EmitXml Harmonic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Harmonic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Harmonic = D1 (MetaData "Harmonic" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Harmonic" PrefixI True) (((S1 (MetaSel (Just "harmonicPrintObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)) :*: (S1 (MetaSel (Just "harmonicDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "harmonicDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)))) :*: (S1 (MetaSel (Just "harmonicRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "harmonicRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "harmonicFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText))))) :*: ((S1 (MetaSel (Just "harmonicFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)) :*: (S1 (MetaSel (Just "harmonicFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)) :*: S1 (MetaSel (Just "harmonicFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)))) :*: ((S1 (MetaSel (Just "harmonicColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color)) :*: S1 (MetaSel (Just "harmonicPlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe AboveBelow))) :*: (S1 (MetaSel (Just "harmonicHarmonic") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ChxHarmonic)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Harmony Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Harmony Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Harmony :: Type -> Type #

Methods

from :: Harmony -> Rep Harmony x #

to :: Rep Harmony x -> Harmony #

EmitXml Harmony Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Harmony Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Harmony = D1 (MetaData "Harmony" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Harmony" PrefixI True) ((((S1 (MetaSel (Just "harmonyType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe HarmonyType)) :*: S1 (MetaSel (Just "harmonyPrintFrame") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo))) :*: (S1 (MetaSel (Just "harmonyPrintObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 (MetaSel (Just "harmonyDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)))) :*: ((S1 (MetaSel (Just "harmonyDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "harmonyRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 (MetaSel (Just "harmonyRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "harmonyFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 (MetaSel (Just "harmonyFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)))))) :*: (((S1 (MetaSel (Just "harmonyFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)) :*: S1 (MetaSel (Just "harmonyFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight))) :*: (S1 (MetaSel (Just "harmonyColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color)) :*: S1 (MetaSel (Just "harmonyPlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe AboveBelow)))) :*: ((S1 (MetaSel (Just "harmonyHarmonyChord") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [HarmonyChord]) :*: S1 (MetaSel (Just "harmonyFrame") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Frame))) :*: (S1 (MetaSel (Just "harmonyOffset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Offset)) :*: (S1 (MetaSel (Just "harmonyEditorial") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Editorial) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show HarpPedals Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic HarpPedals Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep HarpPedals :: Type -> Type #

EmitXml HarpPedals Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep HarpPedals Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show HeelToe Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic HeelToe Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep HeelToe :: Type -> Type #

Methods

from :: HeelToe -> Rep HeelToe x #

to :: Rep HeelToe x -> HeelToe #

EmitXml HeelToe Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep HeelToe Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep HeelToe = D1 (MetaData "HeelToe" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "HeelToe" PrefixI True) (S1 (MetaSel (Just "heelToeEmptyPlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HeelToe) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Identification Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Identification Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Identification :: Type -> Type #

EmitXml Identification Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Identification Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Identification = D1 (MetaData "Identification" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Identification" PrefixI True) ((S1 (MetaSel (Just "identificationCreator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypedText]) :*: (S1 (MetaSel (Just "identificationRights") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypedText]) :*: S1 (MetaSel (Just "identificationEncoding") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Encoding)))) :*: (S1 (MetaSel (Just "identificationSource") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String)) :*: (S1 (MetaSel (Just "identificationRelation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypedText]) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Image Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Image -> ShowS #

show :: Image -> String #

showList :: [Image] -> ShowS #

Generic Image Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Image :: Type -> Type #

Methods

from :: Image -> Rep Image x #

to :: Rep Image x -> Image #

EmitXml Image Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Image -> XmlRep Source #

type Rep Image Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Instrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Instrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Instrument :: Type -> Type #

EmitXml Instrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Instrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Instrument = D1 (MetaData "Instrument" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Instrument" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Inversion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Inversion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Inversion :: Type -> Type #

EmitXml Inversion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Inversion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Key Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Generic Key Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Key :: Type -> Type #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

EmitXml Key Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Key -> XmlRep Source #

type Rep Key Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Key = D1 (MetaData "Key" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Key" PrefixI True) (((S1 (MetaSel (Just "keyNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe StaffNumber)) :*: (S1 (MetaSel (Just "keyDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "keyDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)))) :*: (S1 (MetaSel (Just "keyRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "keyRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "keyFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText))))) :*: ((S1 (MetaSel (Just "keyFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)) :*: (S1 (MetaSel (Just "keyFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)) :*: S1 (MetaSel (Just "keyFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)))) :*: ((S1 (MetaSel (Just "keyColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color)) :*: S1 (MetaSel (Just "keyPrintObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo))) :*: (S1 (MetaSel (Just "keyKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ChxKey) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show KeyOctave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic KeyOctave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep KeyOctave :: Type -> Type #

EmitXml KeyOctave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep KeyOctave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep KeyOctave = D1 (MetaData "KeyOctave" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "KeyOctave" PrefixI True) (S1 (MetaSel (Just "keyOctaveOctave") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Octave) :*: (S1 (MetaSel (Just "keyOctaveNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PositiveInteger) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Kind Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Kind -> ShowS #

show :: Kind -> String #

showList :: [Kind] -> ShowS #

Generic Kind Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Kind :: Type -> Type #

Methods

from :: Kind -> Rep Kind x #

to :: Rep Kind x -> Kind #

EmitXml Kind Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Kind -> XmlRep Source #

type Rep Kind Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Kind = D1 (MetaData "Kind" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Kind" PrefixI True) ((((S1 (MetaSel (Just "kindKindValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 KindValue) :*: S1 (MetaSel (Just "kindUseSymbols") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo))) :*: (S1 (MetaSel (Just "kindText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Token)) :*: S1 (MetaSel (Just "kindStackDegrees") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)))) :*: ((S1 (MetaSel (Just "kindParenthesesDegrees") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 (MetaSel (Just "kindBracketDegrees") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo))) :*: (S1 (MetaSel (Just "kindDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "kindDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))))) :*: (((S1 (MetaSel (Just "kindRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "kindRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 (MetaSel (Just "kindFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 (MetaSel (Just "kindFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)))) :*: ((S1 (MetaSel (Just "kindFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)) :*: S1 (MetaSel (Just "kindFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight))) :*: (S1 (MetaSel (Just "kindColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color)) :*: (S1 (MetaSel (Just "kindHalign") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe LeftCenterRight)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Level Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Level -> ShowS #

show :: Level -> String #

showList :: [Level] -> ShowS #

Generic Level Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Level :: Type -> Type #

Methods

from :: Level -> Rep Level x #

to :: Rep Level x -> Level #

EmitXml Level Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Level -> XmlRep Source #

type Rep Level Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show LineWidth Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic LineWidth Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep LineWidth :: Type -> Type #

EmitXml LineWidth Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep LineWidth Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep LineWidth = D1 (MetaData "LineWidth" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "LineWidth" PrefixI True) (S1 (MetaSel (Just "lineWidthTenths") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Tenths) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Lyric Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Lyric -> ShowS #

show :: Lyric -> String #

showList :: [Lyric] -> ShowS #

Generic Lyric Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Lyric :: Type -> Type #

Methods

from :: Lyric -> Rep Lyric x #

to :: Rep Lyric x -> Lyric #

EmitXml Lyric Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Lyric -> XmlRep Source #

type Rep Lyric Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Lyric = D1 (MetaData "Lyric" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Lyric" PrefixI True) (((S1 (MetaSel (Just "lyricNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NMTOKEN)) :*: (S1 (MetaSel (Just "lyricName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Token)) :*: S1 (MetaSel (Just "lyricJustify") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe LeftCenterRight)))) :*: (S1 (MetaSel (Just "lyricDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "lyricDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "lyricRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 (MetaSel (Just "lyricRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "lyricPlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe AboveBelow)) :*: S1 (MetaSel (Just "lyricColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color)))) :*: ((S1 (MetaSel (Just "lyricLyric") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ChxLyric) :*: S1 (MetaSel (Just "lyricEndLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Empty))) :*: (S1 (MetaSel (Just "lyricEndParagraph") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Empty)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show LyricFont Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic LyricFont Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep LyricFont :: Type -> Type #

EmitXml LyricFont Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep LyricFont Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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

Instances
Eq LyricLanguage Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show LyricLanguage Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic LyricLanguage Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep LyricLanguage :: Type -> Type #

EmitXml LyricLanguage Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep LyricLanguage Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep LyricLanguage = D1 (MetaData "LyricLanguage" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "LyricLanguage" PrefixI True) (S1 (MetaSel (Just "lyricLanguageNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NMTOKEN)) :*: (S1 (MetaSel (Just "lyricLanguageName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Token)) :*: S1 (MetaSel (Just "lyricLanguageLang") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Lang))))

data Measure Source #

measure (complex)

Constructors

Measure 

Fields

Instances
Eq Measure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Measure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Measure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Measure :: Type -> Type #

Methods

from :: Measure -> Rep Measure x #

to :: Rep Measure x -> Measure #

EmitXml Measure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Measure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Measure = D1 (MetaData "Measure" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Measure" PrefixI True) ((S1 (MetaSel (Just "measureNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Token) :*: S1 (MetaSel (Just "measureImplicit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo))) :*: (S1 (MetaSel (Just "measureNonControlling") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)) :*: (S1 (MetaSel (Just "measureWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "measureMusicData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MusicData)))))

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

Smart constructor for Measure

data CmpMeasure Source #

measure (complex)

Constructors

CmpMeasure 

Fields

Instances
Eq CmpMeasure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show CmpMeasure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic CmpMeasure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep CmpMeasure :: Type -> Type #

EmitXml CmpMeasure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep CmpMeasure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep CmpMeasure = D1 (MetaData "CmpMeasure" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "CmpMeasure" PrefixI True) ((S1 (MetaSel (Just "cmpmeasureNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Token) :*: S1 (MetaSel (Just "cmpmeasureImplicit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo))) :*: (S1 (MetaSel (Just "cmpmeasureNonControlling") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)) :*: (S1 (MetaSel (Just "cmpmeasureWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "measurePart") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Part])))))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show MeasureLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic MeasureLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep MeasureLayout :: Type -> Type #

EmitXml MeasureLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep MeasureLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep MeasureLayout = D1 (MetaData "MeasureLayout" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "MeasureLayout" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show MeasureNumbering Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic MeasureNumbering Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep MeasureNumbering :: Type -> Type #

EmitXml MeasureNumbering Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep MeasureNumbering Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep MeasureNumbering = D1 (MetaData "MeasureNumbering" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "MeasureNumbering" PrefixI True) (((S1 (MetaSel (Just "measureNumberingMeasureNumberingValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MeasureNumberingValue) :*: S1 (MetaSel (Just "measureNumberingDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 (MetaSel (Just "measureNumberingDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "measureNumberingRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "measureNumberingRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 (MetaSel (Just "measureNumberingFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 (MetaSel (Just "measureNumberingFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle))) :*: (S1 (MetaSel (Just "measureNumberingFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)) :*: (S1 (MetaSel (Just "measureNumberingFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)) :*: S1 (MetaSel (Just "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.

Instances
Eq MeasureRepeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show MeasureRepeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic MeasureRepeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep MeasureRepeat :: Type -> Type #

EmitXml MeasureRepeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep MeasureRepeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep MeasureRepeat = D1 (MetaData "MeasureRepeat" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "MeasureRepeat" PrefixI True) (S1 (MetaSel (Just "measureRepeatPositiveIntegerOrEmpty") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PositiveIntegerOrEmpty) :*: (S1 (MetaSel (Just "measureRepeatType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StartStop) :*: S1 (MetaSel (Just "measureRepeatSlashes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe PositiveInteger)))))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show MeasureStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic MeasureStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep MeasureStyle :: Type -> Type #

EmitXml MeasureStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep MeasureStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Metronome Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Metronome Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Metronome :: Type -> Type #

EmitXml Metronome Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Metronome Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Metronome = D1 (MetaData "Metronome" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Metronome" PrefixI True) (((S1 (MetaSel (Just "metronomeParentheses") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 (MetaSel (Just "metronomeDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 (MetaSel (Just "metronomeDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "metronomeRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "metronomeRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 (MetaSel (Just "metronomeFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: (S1 (MetaSel (Just "metronomeFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)) :*: S1 (MetaSel (Just "metronomeFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)))) :*: (S1 (MetaSel (Just "metronomeFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)) :*: (S1 (MetaSel (Just "metronomeColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color)) :*: S1 (MetaSel (Just "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

Instances
Eq MetronomeBeam Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show MetronomeBeam Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic MetronomeBeam Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep MetronomeBeam :: Type -> Type #

EmitXml MetronomeBeam Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep MetronomeBeam Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep MetronomeBeam = D1 (MetaData "MetronomeBeam" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "MetronomeBeam" PrefixI True) (S1 (MetaSel (Just "metronomeBeamBeamValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BeamValue) :*: S1 (MetaSel (Just "metronomeBeamNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe BeamLevel))))

data MetronomeNote Source #

metronome-note (complex)

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

Constructors

MetronomeNote 

Fields

Instances
Eq MetronomeNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show MetronomeNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic MetronomeNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep MetronomeNote :: Type -> Type #

EmitXml MetronomeNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep MetronomeNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep MetronomeNote = D1 (MetaData "MetronomeNote" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "MetronomeNote" PrefixI True) ((S1 (MetaSel (Just "metronomeNoteMetronomeType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NoteTypeValue) :*: S1 (MetaSel (Just "metronomeNoteMetronomeDot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Empty])) :*: (S1 (MetaSel (Just "metronomeNoteMetronomeBeam") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [MetronomeBeam]) :*: S1 (MetaSel (Just "metronomeNoteMetronomeTuplet") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe MetronomeTuplet)))))

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.

Instances
Eq MetronomeTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show MetronomeTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic MetronomeTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep MetronomeTuplet :: Type -> Type #

EmitXml MetronomeTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep MetronomeTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep MetronomeTuplet = D1 (MetaData "MetronomeTuplet" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "MetronomeTuplet" PrefixI True) ((S1 (MetaSel (Just "metronomeTupletTimeModification") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MetronomeTuplet) :*: S1 (MetaSel (Just "metronomeTupletType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StartStop)) :*: (S1 (MetaSel (Just "metronomeTupletBracket") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 (MetaSel (Just "metronomeTupletShowNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ShowTuplet)))))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show MidiDevice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic MidiDevice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep MidiDevice :: Type -> Type #

EmitXml MidiDevice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep MidiDevice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep MidiDevice = D1 (MetaData "MidiDevice" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "MidiDevice" PrefixI True) (S1 (MetaSel (Just "midiDeviceString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show MidiInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic MidiInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep MidiInstrument :: Type -> Type #

EmitXml MidiInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep MidiInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Miscellaneous Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Miscellaneous Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Miscellaneous :: Type -> Type #

EmitXml Miscellaneous Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Miscellaneous Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Miscellaneous = D1 (MetaData "Miscellaneous" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Miscellaneous" PrefixI True) (S1 (MetaSel (Just "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

Instances
Eq MiscellaneousField Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show MiscellaneousField Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic MiscellaneousField Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep MiscellaneousField :: Type -> Type #

EmitXml MiscellaneousField Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep MiscellaneousField Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep MiscellaneousField = D1 (MetaData "MiscellaneousField" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "MiscellaneousField" PrefixI True) (S1 (MetaSel (Just "miscellaneousFieldString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "miscellaneousFieldName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Token)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Mordent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Mordent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Mordent :: Type -> Type #

Methods

from :: Mordent -> Rep Mordent x #

to :: Rep Mordent x -> Mordent #

EmitXml Mordent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Mordent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Mordent = D1 (MetaData "Mordent" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Mordent" PrefixI True) (S1 (MetaSel (Just "mordentEmptyTrillSound") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Mordent) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show MultipleRest Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic MultipleRest Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep MultipleRest :: Type -> Type #

EmitXml MultipleRest Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep MultipleRest Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep MultipleRest = D1 (MetaData "MultipleRest" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "MultipleRest" PrefixI True) (S1 (MetaSel (Just "multipleRestPositiveIntegerOrEmpty") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PositiveIntegerOrEmpty) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show NameDisplay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic NameDisplay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep NameDisplay :: Type -> Type #

EmitXml NameDisplay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NameDisplay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NameDisplay = D1 (MetaData "NameDisplay" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "NameDisplay" PrefixI True) (S1 (MetaSel (Just "nameDisplayPrintObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show NonArpeggiate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic NonArpeggiate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep NonArpeggiate :: Type -> Type #

EmitXml NonArpeggiate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NonArpeggiate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Notations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Notations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Notations :: Type -> Type #

EmitXml Notations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Notations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Notations = D1 (MetaData "Notations" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Notations" PrefixI True) (S1 (MetaSel (Just "notationsEditorial") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Editorial) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Note Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Note -> ShowS #

show :: Note -> String #

showList :: [Note] -> ShowS #

Generic Note Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Note :: Type -> Type #

Methods

from :: Note -> Rep Note x #

to :: Rep Note x -> Note #

EmitXml Note Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Note -> XmlRep Source #

type Rep Note Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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

Defined in Fadno.MusicXml.MusicXml20

Show NoteSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic NoteSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep NoteSize :: Type -> Type #

Methods

from :: NoteSize -> Rep NoteSize x #

to :: Rep NoteSize x -> NoteSize #

EmitXml NoteSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NoteSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NoteSize = D1 (MetaData "NoteSize" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "NoteSize" PrefixI True) (S1 (MetaSel (Just "noteSizeNonNegativeDecimal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NonNegativeDecimal) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show NoteType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic NoteType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep NoteType :: Type -> Type #

Methods

from :: NoteType -> Rep NoteType x #

to :: Rep NoteType x -> NoteType #

EmitXml NoteType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NoteType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NoteType = D1 (MetaData "NoteType" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "NoteType" PrefixI True) (S1 (MetaSel (Just "noteTypeNoteTypeValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NoteTypeValue) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Notehead Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Notehead Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Notehead :: Type -> Type #

Methods

from :: Notehead -> Rep Notehead x #

to :: Rep Notehead x -> Notehead #

EmitXml Notehead Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Notehead Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show OctaveShift Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic OctaveShift Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep OctaveShift :: Type -> Type #

EmitXml OctaveShift Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep OctaveShift Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep OctaveShift = D1 (MetaData "OctaveShift" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "OctaveShift" PrefixI True) (((S1 (MetaSel (Just "octaveShiftType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UpDownStop) :*: (S1 (MetaSel (Just "octaveShiftNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NumberLevel)) :*: S1 (MetaSel (Just "octaveShiftSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe PositiveInteger)))) :*: (S1 (MetaSel (Just "octaveShiftDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "octaveShiftDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "octaveShiftRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 (MetaSel (Just "octaveShiftRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "octaveShiftFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 (MetaSel (Just "octaveShiftFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)))) :*: (S1 (MetaSel (Just "octaveShiftFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)) :*: (S1 (MetaSel (Just "octaveShiftFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Offset Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Offset Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Offset :: Type -> Type #

Methods

from :: Offset -> Rep Offset x #

to :: Rep Offset x -> Offset #

EmitXml Offset Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Offset Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Offset = D1 (MetaData "Offset" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Offset" PrefixI True) (S1 (MetaSel (Just "offsetDivisions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Divisions) :*: S1 (MetaSel (Just "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

Instances
Eq Opus Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Opus Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Opus -> ShowS #

show :: Opus -> String #

showList :: [Opus] -> ShowS #

Generic Opus Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Opus :: Type -> Type #

Methods

from :: Opus -> Rep Opus x #

to :: Rep Opus x -> Opus #

EmitXml Opus Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Opus -> XmlRep Source #

type Rep Opus Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Ornaments Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Ornaments Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Ornaments :: Type -> Type #

EmitXml Ornaments Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Ornaments Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Ornaments = D1 (MetaData "Ornaments" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Ornaments" PrefixI True) (S1 (MetaSel (Just "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

Instances
Eq OtherAppearance Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show OtherAppearance Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic OtherAppearance Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep OtherAppearance :: Type -> Type #

EmitXml OtherAppearance Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep OtherAppearance Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep OtherAppearance = D1 (MetaData "OtherAppearance" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "OtherAppearance" PrefixI True) (S1 (MetaSel (Just "otherAppearanceString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "otherAppearanceType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Token)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show OtherDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic OtherDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep OtherDirection :: Type -> Type #

EmitXml OtherDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep OtherDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep OtherDirection = D1 (MetaData "OtherDirection" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "OtherDirection" PrefixI True) (((S1 (MetaSel (Just "otherDirectionString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "otherDirectionPrintObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo))) :*: (S1 (MetaSel (Just "otherDirectionDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "otherDirectionDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "otherDirectionRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 (MetaSel (Just "otherDirectionRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "otherDirectionFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 (MetaSel (Just "otherDirectionFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)))) :*: (S1 (MetaSel (Just "otherDirectionFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)) :*: (S1 (MetaSel (Just "otherDirectionFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show OtherNotation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic OtherNotation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep OtherNotation :: Type -> Type #

EmitXml OtherNotation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep OtherNotation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep OtherNotation = D1 (MetaData "OtherNotation" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "OtherNotation" PrefixI True) (((S1 (MetaSel (Just "otherNotationString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: (S1 (MetaSel (Just "otherNotationType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StartStopSingle) :*: S1 (MetaSel (Just "otherNotationNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NumberLevel)))) :*: ((S1 (MetaSel (Just "otherNotationPrintObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 (MetaSel (Just "otherNotationDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 (MetaSel (Just "otherNotationDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "otherNotationRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 (MetaSel (Just "otherNotationRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "otherNotationFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 (MetaSel (Just "otherNotationFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)))) :*: ((S1 (MetaSel (Just "otherNotationFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)) :*: S1 (MetaSel (Just "otherNotationFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight))) :*: (S1 (MetaSel (Just "otherNotationColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show PageLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic PageLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep PageLayout :: Type -> Type #

EmitXml PageLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep PageLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep PageLayout = D1 (MetaData "PageLayout" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "PageLayout" PrefixI True) (S1 (MetaSel (Just "pageLayoutPageLayout") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SeqPageLayout)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show PageMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic PageMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep PageMargins :: Type -> Type #

EmitXml PageMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep PageMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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

data CmpPart Source #

part (complex)

Constructors

CmpPart 

Fields

Instances
Eq CmpPart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show CmpPart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic CmpPart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep CmpPart :: Type -> Type #

Methods

from :: CmpPart -> Rep CmpPart x #

to :: Rep CmpPart x -> CmpPart #

EmitXml CmpPart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep CmpPart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep CmpPart = D1 (MetaData "CmpPart" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "CmpPart" PrefixI True) (S1 (MetaSel (Just "partId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IDREF) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Part Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Part -> ShowS #

show :: Part -> String #

showList :: [Part] -> ShowS #

Generic Part Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Part :: Type -> Type #

Methods

from :: Part -> Rep Part x #

to :: Rep Part x -> Part #

EmitXml Part Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Part -> XmlRep Source #

type Rep Part Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Part = D1 (MetaData "Part" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Part" PrefixI True) (S1 (MetaSel (Just "cmppartId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IDREF) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show PartGroup Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic PartGroup Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep PartGroup :: Type -> Type #

EmitXml PartGroup Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep PartGroup Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show PartList Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic PartList Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep PartList :: Type -> Type #

Methods

from :: PartList -> Rep PartList x #

to :: Rep PartList x -> PartList #

EmitXml PartList Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep PartList Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep PartList = D1 (MetaData "PartList" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "PartList" PrefixI True) (S1 (MetaSel (Just "partListPartGroup") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [GrpPartGroup]) :*: (S1 (MetaSel (Just "partListScorePart") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ScorePart) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show PartName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic PartName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep PartName :: Type -> Type #

Methods

from :: PartName -> Rep PartName x #

to :: Rep PartName x -> PartName #

EmitXml PartName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep PartName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep PartName = D1 (MetaData "PartName" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "PartName" PrefixI True) (((S1 (MetaSel (Just "partNameString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: (S1 (MetaSel (Just "partNameDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "partNameDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)))) :*: (S1 (MetaSel (Just "partNameRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "partNameRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "partNameFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText))))) :*: ((S1 (MetaSel (Just "partNameFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)) :*: (S1 (MetaSel (Just "partNameFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)) :*: S1 (MetaSel (Just "partNameFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)))) :*: (S1 (MetaSel (Just "partNameColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color)) :*: (S1 (MetaSel (Just "partNamePrintObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show PartSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic PartSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep PartSymbol :: Type -> Type #

EmitXml PartSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep PartSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Pedal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Pedal -> ShowS #

show :: Pedal -> String #

showList :: [Pedal] -> ShowS #

Generic Pedal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Pedal :: Type -> Type #

Methods

from :: Pedal -> Rep Pedal x #

to :: Rep Pedal x -> Pedal #

EmitXml Pedal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Pedal -> XmlRep Source #

type Rep Pedal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show PedalTuning Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic PedalTuning Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep PedalTuning :: Type -> Type #

EmitXml PedalTuning Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep PedalTuning Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep PedalTuning = D1 (MetaData "PedalTuning" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "PedalTuning" PrefixI True) (S1 (MetaSel (Just "pedalTuningPedalStep") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Step) :*: S1 (MetaSel (Just "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

Instances
Eq PerMinute Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show PerMinute Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic PerMinute Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep PerMinute :: Type -> Type #

EmitXml PerMinute Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep PerMinute Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep PerMinute = D1 (MetaData "PerMinute" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "PerMinute" PrefixI True) ((S1 (MetaSel (Just "perMinuteString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "perMinuteFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText))) :*: (S1 (MetaSel (Just "perMinuteFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)) :*: (S1 (MetaSel (Just "perMinuteFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)) :*: S1 (MetaSel (Just "perMinuteFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight))))))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Pitch Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Pitch -> ShowS #

show :: Pitch -> String #

showList :: [Pitch] -> ShowS #

Generic Pitch Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Pitch :: Type -> Type #

Methods

from :: Pitch -> Rep Pitch x #

to :: Rep Pitch x -> Pitch #

EmitXml Pitch Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Pitch -> XmlRep Source #

type Rep Pitch Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Pitch = D1 (MetaData "Pitch" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Pitch" PrefixI True) (S1 (MetaSel (Just "pitchStep") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Step) :*: (S1 (MetaSel (Just "pitchAlter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Semitones)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show PlacementText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic PlacementText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep PlacementText :: Type -> Type #

EmitXml PlacementText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep PlacementText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep PlacementText = D1 (MetaData "PlacementText" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "PlacementText" PrefixI True) (((S1 (MetaSel (Just "placementTextString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "placementTextDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 (MetaSel (Just "placementTextDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "placementTextRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "placementTextRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 (MetaSel (Just "placementTextFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: (S1 (MetaSel (Just "placementTextFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)) :*: S1 (MetaSel (Just "placementTextFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)))) :*: (S1 (MetaSel (Just "placementTextFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)) :*: (S1 (MetaSel (Just "placementTextColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Print Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Print -> ShowS #

show :: Print -> String #

showList :: [Print] -> ShowS #

Generic Print Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Print :: Type -> Type #

Methods

from :: Print -> Rep Print x #

to :: Rep Print x -> Print #

EmitXml Print Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Print -> XmlRep Source #

type Rep Print Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Rehearsal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Rehearsal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Rehearsal :: Type -> Type #

EmitXml Rehearsal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Rehearsal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Rehearsal = D1 (MetaData "Rehearsal" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Rehearsal" PrefixI True) ((((S1 (MetaSel (Just "rehearsalString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "rehearsalLang") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Lang))) :*: (S1 (MetaSel (Just "rehearsalEnclosure") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe RehearsalEnclosure)) :*: S1 (MetaSel (Just "rehearsalDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)))) :*: ((S1 (MetaSel (Just "rehearsalDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "rehearsalRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 (MetaSel (Just "rehearsalRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "rehearsalFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText))))) :*: (((S1 (MetaSel (Just "rehearsalFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)) :*: S1 (MetaSel (Just "rehearsalFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize))) :*: (S1 (MetaSel (Just "rehearsalFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)) :*: S1 (MetaSel (Just "rehearsalColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color)))) :*: ((S1 (MetaSel (Just "rehearsalUnderline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NumberOfLines)) :*: S1 (MetaSel (Just "rehearsalOverline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NumberOfLines))) :*: (S1 (MetaSel (Just "rehearsalLineThrough") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NumberOfLines)) :*: (S1 (MetaSel (Just "rehearsalDir") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe TextDirection)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Repeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Repeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Repeat :: Type -> Type #

Methods

from :: Repeat -> Rep Repeat x #

to :: Rep Repeat x -> Repeat #

EmitXml Repeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Repeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Repeat = D1 (MetaData "Repeat" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Repeat" PrefixI True) (S1 (MetaSel (Just "repeatDirection") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BackwardForward) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Root Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Root -> ShowS #

show :: Root -> String #

showList :: [Root] -> ShowS #

Generic Root Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Root :: Type -> Type #

Methods

from :: Root -> Rep Root x #

to :: Rep Root x -> Root #

EmitXml Root Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Root -> XmlRep Source #

type Rep Root Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Root = D1 (MetaData "Root" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Root" PrefixI True) (S1 (MetaSel (Just "rootRootStep") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RootStep) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show RootAlter Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic RootAlter Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep RootAlter :: Type -> Type #

EmitXml RootAlter Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep RootAlter Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep RootAlter = D1 (MetaData "RootAlter" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "RootAlter" PrefixI True) (((S1 (MetaSel (Just "rootAlterSemitones") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Semitones) :*: (S1 (MetaSel (Just "rootAlterLocation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe LeftRight)) :*: S1 (MetaSel (Just "rootAlterPrintObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)))) :*: (S1 (MetaSel (Just "rootAlterDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "rootAlterDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "rootAlterRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 (MetaSel (Just "rootAlterRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "rootAlterFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 (MetaSel (Just "rootAlterFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)))) :*: (S1 (MetaSel (Just "rootAlterFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)) :*: (S1 (MetaSel (Just "rootAlterFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show RootStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic RootStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep RootStep :: Type -> Type #

Methods

from :: RootStep -> Rep RootStep x #

to :: Rep RootStep x -> RootStep #

EmitXml RootStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep RootStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Scaling Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Scaling Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Scaling :: Type -> Type #

Methods

from :: Scaling -> Rep Scaling x #

to :: Rep Scaling x -> Scaling #

EmitXml Scaling Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Scaling Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Scaling = D1 (MetaData "Scaling" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Scaling" PrefixI True) (S1 (MetaSel (Just "scalingMillimeters") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Millimeters) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Scordatura Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Scordatura Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Scordatura :: Type -> Type #

EmitXml Scordatura Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Scordatura Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Scordatura = D1 (MetaData "Scordatura" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Scordatura" PrefixI True) (S1 (MetaSel (Just "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

Instances
Eq ScoreInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ScoreInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ScoreInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ScoreInstrument :: Type -> Type #

EmitXml ScoreInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ScoreInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ScoreInstrument = D1 (MetaData "ScoreInstrument" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "ScoreInstrument" PrefixI True) ((S1 (MetaSel (Just "scoreInstrumentId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ID) :*: S1 (MetaSel (Just "scoreInstrumentInstrumentName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :*: (S1 (MetaSel (Just "scoreInstrumentInstrumentAbbreviation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String)) :*: S1 (MetaSel (Just "scoreInstrumentScoreInstrument") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ChxScoreInstrument)))))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show CmpScorePart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic CmpScorePart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep CmpScorePart :: Type -> Type #

EmitXml CmpScorePart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep CmpScorePart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

data ScorePartwise Source #

score-partwise (complex)

Constructors

ScorePartwise 
Instances
Eq ScorePartwise Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ScorePartwise Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ScorePartwise Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ScorePartwise :: Type -> Type #

EmitXml ScorePartwise Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ScorePartwise Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ScorePartwise = D1 (MetaData "ScorePartwise" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "ScorePartwise" PrefixI True) (S1 (MetaSel (Just "scorePartwiseVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Token)) :*: (S1 (MetaSel (Just "scorePartwiseScoreHeader") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ScoreHeader) :*: S1 (MetaSel (Just "scorePartwisePart") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [CmpPart]))))

data ScoreTimewise Source #

score-timewise (complex)

Constructors

ScoreTimewise 
Instances
Eq ScoreTimewise Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ScoreTimewise Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ScoreTimewise Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ScoreTimewise :: Type -> Type #

EmitXml ScoreTimewise Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ScoreTimewise Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ScoreTimewise = D1 (MetaData "ScoreTimewise" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "ScoreTimewise" PrefixI True) (S1 (MetaSel (Just "scoreTimewiseVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Token)) :*: (S1 (MetaSel (Just "scoreTimewiseScoreHeader") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ScoreHeader) :*: S1 (MetaSel (Just "scoreTimewiseMeasure") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [CmpMeasure]))))

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

Instances
Eq CmpSlash Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show CmpSlash Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic CmpSlash Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep CmpSlash :: Type -> Type #

Methods

from :: CmpSlash -> Rep CmpSlash x #

to :: Rep CmpSlash x -> CmpSlash #

EmitXml CmpSlash Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep CmpSlash Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep CmpSlash = D1 (MetaData "CmpSlash" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "CmpSlash" PrefixI True) ((S1 (MetaSel (Just "slashType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StartStop) :*: S1 (MetaSel (Just "slashUseDots") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo))) :*: (S1 (MetaSel (Just "slashUseStems") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 (MetaSel (Just "slashSlash") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Slash)))))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Slide Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Slide -> ShowS #

show :: Slide -> String #

showList :: [Slide] -> ShowS #

Generic Slide Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Slide :: Type -> Type #

Methods

from :: Slide -> Rep Slide x #

to :: Rep Slide x -> Slide #

EmitXml Slide Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Slide -> XmlRep Source #

type Rep Slide Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Slide = D1 (MetaData "Slide" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Slide" PrefixI True) ((((S1 (MetaSel (Just "slideString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "slideType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StartStop)) :*: (S1 (MetaSel (Just "slideNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NumberLevel)) :*: S1 (MetaSel (Just "slideLineType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe LineType)))) :*: ((S1 (MetaSel (Just "slideDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "slideDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 (MetaSel (Just "slideRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "slideRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))))) :*: (((S1 (MetaSel (Just "slideFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 (MetaSel (Just "slideFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle))) :*: (S1 (MetaSel (Just "slideFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)) :*: S1 (MetaSel (Just "slideFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)))) :*: ((S1 (MetaSel (Just "slideColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color)) :*: S1 (MetaSel (Just "slideAccelerate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo))) :*: (S1 (MetaSel (Just "slideBeats") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe TrillBeats)) :*: (S1 (MetaSel (Just "slideFirstBeat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Percent)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Slur Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Slur -> ShowS #

show :: Slur -> String #

showList :: [Slur] -> ShowS #

Generic Slur Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Slur :: Type -> Type #

Methods

from :: Slur -> Rep Slur x #

to :: Rep Slur x -> Slur #

EmitXml Slur Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Slur -> XmlRep Source #

type Rep Slur Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Slur = D1 (MetaData "Slur" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Slur" PrefixI True) ((((S1 (MetaSel (Just "slurType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StartStopContinue) :*: S1 (MetaSel (Just "slurNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NumberLevel))) :*: (S1 (MetaSel (Just "slurLineType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe LineType)) :*: S1 (MetaSel (Just "slurDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)))) :*: ((S1 (MetaSel (Just "slurDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "slurRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 (MetaSel (Just "slurRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "slurPlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe AboveBelow))))) :*: (((S1 (MetaSel (Just "slurOrientation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe OverUnder)) :*: S1 (MetaSel (Just "slurBezierOffset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Divisions))) :*: (S1 (MetaSel (Just "slurBezierOffset2") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Divisions)) :*: S1 (MetaSel (Just "slurBezierX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)))) :*: ((S1 (MetaSel (Just "slurBezierY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "slurBezierX2") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 (MetaSel (Just "slurBezierY2") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Sound Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Sound -> ShowS #

show :: Sound -> String #

showList :: [Sound] -> ShowS #

Generic Sound Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Sound :: Type -> Type #

Methods

from :: Sound -> Rep Sound x #

to :: Rep Sound x -> Sound #

EmitXml Sound Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Sound -> XmlRep Source #

type Rep Sound Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Sound = D1 (MetaData "Sound" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Sound" PrefixI True) ((((S1 (MetaSel (Just "soundTempo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NonNegativeDecimal)) :*: S1 (MetaSel (Just "soundDynamics") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NonNegativeDecimal))) :*: (S1 (MetaSel (Just "soundDacapo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 (MetaSel (Just "soundSegno") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Token)))) :*: ((S1 (MetaSel (Just "soundDalsegno") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Token)) :*: S1 (MetaSel (Just "soundCoda") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Token))) :*: (S1 (MetaSel (Just "soundTocoda") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Token)) :*: (S1 (MetaSel (Just "soundDivisions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Divisions)) :*: S1 (MetaSel (Just "soundForwardRepeat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)))))) :*: (((S1 (MetaSel (Just "soundFine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Token)) :*: S1 (MetaSel (Just "soundTimeOnly") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Token))) :*: (S1 (MetaSel (Just "soundPizzicato") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)) :*: (S1 (MetaSel (Just "soundPan") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe RotationDegrees)) :*: S1 (MetaSel (Just "soundElevation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe RotationDegrees))))) :*: ((S1 (MetaSel (Just "soundDamperPedal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNoNumber)) :*: S1 (MetaSel (Just "soundSoftPedal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNoNumber))) :*: (S1 (MetaSel (Just "soundSostenutoPedal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNoNumber)) :*: (S1 (MetaSel (Just "soundMidiInstrument") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [MidiInstrument]) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show StaffDetails Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic StaffDetails Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep StaffDetails :: Type -> Type #

EmitXml StaffDetails Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StaffDetails Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show StaffLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic StaffLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep StaffLayout :: Type -> Type #

EmitXml StaffLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StaffLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StaffLayout = D1 (MetaData "StaffLayout" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "StaffLayout" PrefixI True) (S1 (MetaSel (Just "staffLayoutNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe StaffNumber)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show StaffTuning Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic StaffTuning Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep StaffTuning :: Type -> Type #

EmitXml StaffTuning Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StaffTuning Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StaffTuning = D1 (MetaData "StaffTuning" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "StaffTuning" PrefixI True) (S1 (MetaSel (Just "staffTuningLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe StaffLine)) :*: S1 (MetaSel (Just "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
Eq Stem Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Stem Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Stem -> ShowS #

show :: Stem -> String #

showList :: [Stem] -> ShowS #

Generic Stem Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Stem :: Type -> Type #

Methods

from :: Stem -> Rep Stem x #

to :: Rep Stem x -> Stem #

EmitXml Stem Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Stem -> XmlRep Source #

type Rep Stem Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show CmpString Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic CmpString Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep CmpString :: Type -> Type #

EmitXml CmpString Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep CmpString Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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
Eq StrongAccent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show StrongAccent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic StrongAccent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep StrongAccent :: Type -> Type #

EmitXml StrongAccent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StrongAccent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StrongAccent = D1 (MetaData "StrongAccent" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "StrongAccent" PrefixI True) (S1 (MetaSel (Just "strongAccentEmptyPlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StrongAccent) :*: S1 (MetaSel (Just "strongAccentType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe UpDown))))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show StyleText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic StyleText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep StyleText :: Type -> Type #

EmitXml StyleText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep StyleText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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
Eq Supports Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Supports Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Supports Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Supports :: Type -> Type #

Methods

from :: Supports -> Rep Supports x #

to :: Rep Supports x -> Supports #

EmitXml Supports Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Supports Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Supports = D1 (MetaData "Supports" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Supports" PrefixI True) ((S1 (MetaSel (Just "supportsType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 YesNo) :*: S1 (MetaSel (Just "supportsElement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NMTOKEN)) :*: (S1 (MetaSel (Just "supportsAttribute") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NMTOKEN)) :*: S1 (MetaSel (Just "supportsValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Token)))))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show SystemLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic SystemLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep SystemLayout :: Type -> Type #

EmitXml SystemLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SystemLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SystemLayout = D1 (MetaData "SystemLayout" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "SystemLayout" PrefixI True) (S1 (MetaSel (Just "systemLayoutSystemMargins") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SystemMargins)) :*: (S1 (MetaSel (Just "systemLayoutSystemDistance") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show SystemMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic SystemMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep SystemMargins :: Type -> Type #

EmitXml SystemMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SystemMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SystemMargins = D1 (MetaData "SystemMargins" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "SystemMargins" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Technical Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Technical Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Technical :: Type -> Type #

EmitXml Technical Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Technical Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Technical = D1 (MetaData "Technical" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Technical" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show TextElementData Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic TextElementData Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep TextElementData :: Type -> Type #

EmitXml TextElementData Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TextElementData Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TextElementData = D1 (MetaData "TextElementData" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "TextElementData" PrefixI True) (((S1 (MetaSel (Just "textElementDataString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: (S1 (MetaSel (Just "textElementDataLang") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Lang)) :*: S1 (MetaSel (Just "textElementDataFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)))) :*: (S1 (MetaSel (Just "textElementDataFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)) :*: (S1 (MetaSel (Just "textElementDataFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)) :*: S1 (MetaSel (Just "textElementDataFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight))))) :*: ((S1 (MetaSel (Just "textElementDataColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color)) :*: (S1 (MetaSel (Just "textElementDataUnderline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NumberOfLines)) :*: S1 (MetaSel (Just "textElementDataOverline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NumberOfLines)))) :*: ((S1 (MetaSel (Just "textElementDataLineThrough") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NumberOfLines)) :*: S1 (MetaSel (Just "textElementDataRotation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe RotationDegrees))) :*: (S1 (MetaSel (Just "textElementDataLetterSpacing") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NumberOrNormal)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Tie Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Tie -> ShowS #

show :: Tie -> String #

showList :: [Tie] -> ShowS #

Generic Tie Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Tie :: Type -> Type #

Methods

from :: Tie -> Rep Tie x #

to :: Rep Tie x -> Tie #

EmitXml Tie Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Tie -> XmlRep Source #

type Rep Tie Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Tie = D1 (MetaData "Tie" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Tie" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Tied Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Tied -> ShowS #

show :: Tied -> String #

showList :: [Tied] -> ShowS #

Generic Tied Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Tied :: Type -> Type #

Methods

from :: Tied -> Rep Tied x #

to :: Rep Tied x -> Tied #

EmitXml Tied Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Tied -> XmlRep Source #

type Rep Tied Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Tied = D1 (MetaData "Tied" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Tied" PrefixI True) ((((S1 (MetaSel (Just "tiedType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StartStop) :*: S1 (MetaSel (Just "tiedNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NumberLevel))) :*: (S1 (MetaSel (Just "tiedLineType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe LineType)) :*: S1 (MetaSel (Just "tiedDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)))) :*: ((S1 (MetaSel (Just "tiedDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "tiedRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 (MetaSel (Just "tiedRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "tiedPlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe AboveBelow))))) :*: (((S1 (MetaSel (Just "tiedOrientation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe OverUnder)) :*: S1 (MetaSel (Just "tiedBezierOffset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Divisions))) :*: (S1 (MetaSel (Just "tiedBezierOffset2") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Divisions)) :*: S1 (MetaSel (Just "tiedBezierX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)))) :*: ((S1 (MetaSel (Just "tiedBezierY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "tiedBezierX2") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 (MetaSel (Just "tiedBezierY2") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Time Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Time -> ShowS #

show :: Time -> String #

showList :: [Time] -> ShowS #

Generic Time Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Time :: Type -> Type #

Methods

from :: Time -> Rep Time x #

to :: Rep Time x -> Time #

EmitXml Time Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Time -> XmlRep Source #

type Rep Time Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Time = D1 (MetaData "Time" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Time" PrefixI True) (((S1 (MetaSel (Just "timeNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe StaffNumber)) :*: (S1 (MetaSel (Just "timeSymbol") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe TimeSymbol)) :*: S1 (MetaSel (Just "timeDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)))) :*: (S1 (MetaSel (Just "timeDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "timeRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "timeRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 (MetaSel (Just "timeFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: (S1 (MetaSel (Just "timeFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)) :*: S1 (MetaSel (Just "timeFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)))) :*: ((S1 (MetaSel (Just "timeFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)) :*: S1 (MetaSel (Just "timeColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color))) :*: (S1 (MetaSel (Just "timePrintObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 (MetaSel (Just "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.

Instances
Eq TimeModification Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show TimeModification Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic TimeModification Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep TimeModification :: Type -> Type #

EmitXml TimeModification Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TimeModification Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TimeModification = D1 (MetaData "TimeModification" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "TimeModification" PrefixI True) (S1 (MetaSel (Just "timeModificationActualNotes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NonNegativeInteger) :*: (S1 (MetaSel (Just "timeModificationNormalNotes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NonNegativeInteger) :*: S1 (MetaSel (Just "timeModificationTimeModification") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SeqTimeModification)))))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Transpose Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Transpose Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Transpose :: Type -> Type #

EmitXml Transpose Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Transpose Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Transpose = D1 (MetaData "Transpose" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Transpose" PrefixI True) ((S1 (MetaSel (Just "transposeDiatonic") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int)) :*: S1 (MetaSel (Just "transposeChromatic") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Semitones)) :*: (S1 (MetaSel (Just "transposeOctaveChange") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Tremolo Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Tremolo Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Tremolo :: Type -> Type #

Methods

from :: Tremolo -> Rep Tremolo x #

to :: Rep Tremolo x -> Tremolo #

EmitXml Tremolo Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Tremolo Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Tremolo = D1 (MetaData "Tremolo" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Tremolo" PrefixI True) (((S1 (MetaSel (Just "tremoloTremoloMarks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TremoloMarks) :*: (S1 (MetaSel (Just "tremoloType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe StartStopSingle)) :*: S1 (MetaSel (Just "tremoloDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)))) :*: (S1 (MetaSel (Just "tremoloDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "tremoloRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "tremoloRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 (MetaSel (Just "tremoloFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: (S1 (MetaSel (Just "tremoloFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)) :*: S1 (MetaSel (Just "tremoloFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)))) :*: (S1 (MetaSel (Just "tremoloFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)) :*: (S1 (MetaSel (Just "tremoloColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Tuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Tuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Tuplet :: Type -> Type #

Methods

from :: Tuplet -> Rep Tuplet x #

to :: Rep Tuplet x -> Tuplet #

EmitXml Tuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Tuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Tuplet = D1 (MetaData "Tuplet" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Tuplet" PrefixI True) (((S1 (MetaSel (Just "tupletType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StartStop) :*: (S1 (MetaSel (Just "tupletNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NumberLevel)) :*: S1 (MetaSel (Just "tupletBracket") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)))) :*: (S1 (MetaSel (Just "tupletShowNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ShowTuplet)) :*: (S1 (MetaSel (Just "tupletShowType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ShowTuplet)) :*: S1 (MetaSel (Just "tupletLineShape") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe LineShape))))) :*: ((S1 (MetaSel (Just "tupletDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 (MetaSel (Just "tupletDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "tupletRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)))) :*: ((S1 (MetaSel (Just "tupletRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "tupletPlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe AboveBelow))) :*: (S1 (MetaSel (Just "tupletTupletActual") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe TupletPortion)) :*: S1 (MetaSel (Just "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

Instances
Eq TupletDot Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show TupletDot Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic TupletDot Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep TupletDot :: Type -> Type #

EmitXml TupletDot Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TupletDot Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TupletDot = D1 (MetaData "TupletDot" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "TupletDot" PrefixI True) ((S1 (MetaSel (Just "tupletDotFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 (MetaSel (Just "tupletDotFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle))) :*: (S1 (MetaSel (Just "tupletDotFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)) :*: (S1 (MetaSel (Just "tupletDotFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)) :*: S1 (MetaSel (Just "tupletDotColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color))))))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show TupletNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic TupletNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep TupletNumber :: Type -> Type #

EmitXml TupletNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TupletNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TupletNumber = D1 (MetaData "TupletNumber" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "TupletNumber" PrefixI True) ((S1 (MetaSel (Just "tupletNumberNonNegativeInteger") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NonNegativeInteger) :*: (S1 (MetaSel (Just "tupletNumberFontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 (MetaSel (Just "tupletNumberFontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontStyle)))) :*: (S1 (MetaSel (Just "tupletNumberFontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontSize)) :*: (S1 (MetaSel (Just "tupletNumberFontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FontWeight)) :*: S1 (MetaSel (Just "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

Instances
Eq TupletPortion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show TupletPortion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic TupletPortion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep TupletPortion :: Type -> Type #

EmitXml TupletPortion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TupletPortion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TupletPortion = D1 (MetaData "TupletPortion" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "TupletPortion" PrefixI True) (S1 (MetaSel (Just "tupletPortionTupletNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe TupletNumber)) :*: (S1 (MetaSel (Just "tupletPortionTupletType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe TupletType)) :*: S1 (MetaSel (Just "tupletPortionTupletDot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TupletDot]))))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show TupletType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic TupletType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep TupletType :: Type -> Type #

EmitXml TupletType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TupletType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show TypedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic TypedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep TypedText :: Type -> Type #

EmitXml TypedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TypedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TypedText = D1 (MetaData "TypedText" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "TypedText" PrefixI True) (S1 (MetaSel (Just "typedTextString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show WavyLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic WavyLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep WavyLine :: Type -> Type #

Methods

from :: WavyLine -> Rep WavyLine x #

to :: Rep WavyLine x -> WavyLine #

EmitXml WavyLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep WavyLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep WavyLine = D1 (MetaData "WavyLine" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "WavyLine" PrefixI True) (((S1 (MetaSel (Just "wavyLineType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StartStopContinue) :*: (S1 (MetaSel (Just "wavyLineNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NumberLevel)) :*: S1 (MetaSel (Just "wavyLineDefaultX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)))) :*: ((S1 (MetaSel (Just "wavyLineDefaultY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "wavyLineRelativeX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 (MetaSel (Just "wavyLineRelativeY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 (MetaSel (Just "wavyLinePlacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe AboveBelow))))) :*: (((S1 (MetaSel (Just "wavyLineColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color)) :*: S1 (MetaSel (Just "wavyLineStartNote") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe StartNote))) :*: (S1 (MetaSel (Just "wavyLineTrillStep") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe TrillStep)) :*: S1 (MetaSel (Just "wavyLineTwoNoteTurn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe TwoNoteTurn)))) :*: ((S1 (MetaSel (Just "wavyLineAccelerate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 (MetaSel (Just "wavyLineBeats") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe TrillBeats))) :*: (S1 (MetaSel (Just "wavyLineSecondBeat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Percent)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Wedge Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Wedge -> ShowS #

show :: Wedge -> String #

showList :: [Wedge] -> ShowS #

Generic Wedge Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Wedge :: Type -> Type #

Methods

from :: Wedge -> Rep Wedge x #

to :: Rep Wedge x -> Wedge #

EmitXml Wedge Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Wedge -> XmlRep Source #

type Rep Wedge Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Work Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Work -> ShowS #

show :: Work -> String #

showList :: [Work] -> ShowS #

Generic Work Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Work :: Type -> Type #

Methods

from :: Work -> Rep Work x #

to :: Rep Work x -> Work #

EmitXml Work Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Work -> XmlRep Source #

type Rep Work Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Work = D1 (MetaData "Work" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Work" PrefixI True) (S1 (MetaSel (Just "workWorkNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String)) :*: (S1 (MetaSel (Just "workWorkTitle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String)) :*: S1 (MetaSel (Just "workOpus") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Opus)))))

mkWork :: Work Source #

Smart constructor for Work

data ChxArticulations Source #

articulations (choice)

Instances
Eq ChxArticulations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ChxArticulations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ChxArticulations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ChxArticulations :: Type -> Type #

EmitXml ChxArticulations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxArticulations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxArticulations = D1 (MetaData "ChxArticulations" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) ((((C1 (MetaCons "ArticulationsAccent" PrefixI True) (S1 (MetaSel (Just "articulationsAccent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyPlacement)) :+: C1 (MetaCons "ArticulationsStrongAccent" PrefixI True) (S1 (MetaSel (Just "articulationsStrongAccent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StrongAccent))) :+: (C1 (MetaCons "ArticulationsStaccato" PrefixI True) (S1 (MetaSel (Just "articulationsStaccato") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyPlacement)) :+: C1 (MetaCons "ArticulationsTenuto" PrefixI True) (S1 (MetaSel (Just "articulationsTenuto") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyPlacement)))) :+: ((C1 (MetaCons "ArticulationsDetachedLegato" PrefixI True) (S1 (MetaSel (Just "articulationsDetachedLegato") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyPlacement)) :+: C1 (MetaCons "ArticulationsStaccatissimo" PrefixI True) (S1 (MetaSel (Just "articulationsStaccatissimo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyPlacement))) :+: (C1 (MetaCons "ArticulationsSpiccato" PrefixI True) (S1 (MetaSel (Just "articulationsSpiccato") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyPlacement)) :+: C1 (MetaCons "ArticulationsScoop" PrefixI True) (S1 (MetaSel (Just "articulationsScoop") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyLine))))) :+: (((C1 (MetaCons "ArticulationsPlop" PrefixI True) (S1 (MetaSel (Just "articulationsPlop") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyLine)) :+: C1 (MetaCons "ArticulationsDoit" PrefixI True) (S1 (MetaSel (Just "articulationsDoit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyLine))) :+: (C1 (MetaCons "ArticulationsFalloff" PrefixI True) (S1 (MetaSel (Just "articulationsFalloff") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyLine)) :+: C1 (MetaCons "ArticulationsBreathMark" PrefixI True) (S1 (MetaSel (Just "articulationsBreathMark") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyPlacement)))) :+: ((C1 (MetaCons "ArticulationsCaesura" PrefixI True) (S1 (MetaSel (Just "articulationsCaesura") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyPlacement)) :+: C1 (MetaCons "ArticulationsStress" PrefixI True) (S1 (MetaSel (Just "articulationsStress") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyPlacement))) :+: (C1 (MetaCons "ArticulationsUnstress" PrefixI True) (S1 (MetaSel (Just "articulationsUnstress") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyPlacement)) :+: C1 (MetaCons "ArticulationsOtherArticulation" PrefixI True) (S1 (MetaSel (Just "articulationsOtherArticulation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PlacementText))))))

data ChxBend Source #

bend (choice)

Constructors

BendPreBend 

Fields

BendRelease 

Fields

Instances
Eq ChxBend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show ChxBend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ChxBend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ChxBend :: Type -> Type #

Methods

from :: ChxBend -> Rep ChxBend x #

to :: Rep ChxBend x -> ChxBend #

EmitXml ChxBend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxBend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxBend = D1 (MetaData "ChxBend" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "BendPreBend" PrefixI True) (S1 (MetaSel (Just "bendPreBend") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty)) :+: C1 (MetaCons "BendRelease" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ChxCredit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ChxCredit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ChxCredit :: Type -> Type #

EmitXml ChxCredit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxCredit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxCredit = D1 (MetaData "ChxCredit" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "CreditCreditImage" PrefixI True) (S1 (MetaSel (Just "creditCreditImage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Image)) :+: C1 (MetaCons "CreditCreditWords" PrefixI True) (S1 (MetaSel (Just "creditCreditWords") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FormattedText) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ChxDirectionType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ChxDirectionType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ChxDirectionType :: Type -> Type #

EmitXml ChxDirectionType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxDirectionType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxDirectionType = D1 (MetaData "ChxDirectionType" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) ((((C1 (MetaCons "DirectionTypeRehearsal" PrefixI True) (S1 (MetaSel (Just "directionTypeRehearsal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Rehearsal])) :+: C1 (MetaCons "DirectionTypeSegno" PrefixI True) (S1 (MetaSel (Just "directionTypeSegno") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [EmptyPrintStyle]))) :+: (C1 (MetaCons "DirectionTypeWords" PrefixI True) (S1 (MetaSel (Just "directionTypeWords") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FormattedText])) :+: C1 (MetaCons "DirectionTypeCoda" PrefixI True) (S1 (MetaSel (Just "directionTypeCoda") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [EmptyPrintStyle])))) :+: ((C1 (MetaCons "DirectionTypeWedge" PrefixI True) (S1 (MetaSel (Just "directionTypeWedge") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Wedge)) :+: C1 (MetaCons "DirectionTypeDynamics" PrefixI True) (S1 (MetaSel (Just "directionTypeDynamics") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Dynamics]))) :+: (C1 (MetaCons "DirectionTypeDashes" PrefixI True) (S1 (MetaSel (Just "directionTypeDashes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Dashes)) :+: (C1 (MetaCons "DirectionTypeBracket" PrefixI True) (S1 (MetaSel (Just "directionTypeBracket") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bracket)) :+: C1 (MetaCons "DirectionTypePedal" PrefixI True) (S1 (MetaSel (Just "directionTypePedal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Pedal)))))) :+: (((C1 (MetaCons "DirectionTypeMetronome" PrefixI True) (S1 (MetaSel (Just "directionTypeMetronome") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Metronome)) :+: C1 (MetaCons "DirectionTypeOctaveShift" PrefixI True) (S1 (MetaSel (Just "directionTypeOctaveShift") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OctaveShift))) :+: (C1 (MetaCons "DirectionTypeHarpPedals" PrefixI True) (S1 (MetaSel (Just "directionTypeHarpPedals") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HarpPedals)) :+: (C1 (MetaCons "DirectionTypeDamp" PrefixI True) (S1 (MetaSel (Just "directionTypeDamp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyPrintStyle)) :+: C1 (MetaCons "DirectionTypeDampAll" PrefixI True) (S1 (MetaSel (Just "directionTypeDampAll") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyPrintStyle))))) :+: ((C1 (MetaCons "DirectionTypeEyeglasses" PrefixI True) (S1 (MetaSel (Just "directionTypeEyeglasses") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyPrintStyle)) :+: C1 (MetaCons "DirectionTypeScordatura" PrefixI True) (S1 (MetaSel (Just "directionTypeScordatura") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scordatura))) :+: (C1 (MetaCons "DirectionTypeImage" PrefixI True) (S1 (MetaSel (Just "directionTypeImage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Image)) :+: (C1 (MetaCons "DirectionTypeAccordionRegistration" PrefixI True) (S1 (MetaSel (Just "directionTypeAccordionRegistration") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AccordionRegistration)) :+: C1 (MetaCons "DirectionTypeOtherDirection" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ChxDynamics Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ChxDynamics Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ChxDynamics :: Type -> Type #

EmitXml ChxDynamics Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxDynamics Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxDynamics = D1 (MetaData "ChxDynamics" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) ((((C1 (MetaCons "DynamicsP" PrefixI True) (S1 (MetaSel (Just "dynamicsP") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty)) :+: (C1 (MetaCons "DynamicsPp" PrefixI True) (S1 (MetaSel (Just "dynamicsPp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty)) :+: C1 (MetaCons "DynamicsPpp" PrefixI True) (S1 (MetaSel (Just "dynamicsPpp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty)))) :+: (C1 (MetaCons "DynamicsPppp" PrefixI True) (S1 (MetaSel (Just "dynamicsPppp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty)) :+: (C1 (MetaCons "DynamicsPpppp" PrefixI True) (S1 (MetaSel (Just "dynamicsPpppp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty)) :+: C1 (MetaCons "DynamicsPppppp" PrefixI True) (S1 (MetaSel (Just "dynamicsPppppp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty))))) :+: ((C1 (MetaCons "DynamicsF" PrefixI True) (S1 (MetaSel (Just "dynamicsF") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty)) :+: (C1 (MetaCons "DynamicsFf" PrefixI True) (S1 (MetaSel (Just "dynamicsFf") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty)) :+: C1 (MetaCons "DynamicsFff" PrefixI True) (S1 (MetaSel (Just "dynamicsFff") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty)))) :+: (C1 (MetaCons "DynamicsFfff" PrefixI True) (S1 (MetaSel (Just "dynamicsFfff") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty)) :+: (C1 (MetaCons "DynamicsFffff" PrefixI True) (S1 (MetaSel (Just "dynamicsFffff") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty)) :+: C1 (MetaCons "DynamicsFfffff" PrefixI True) (S1 (MetaSel (Just "dynamicsFfffff") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty)))))) :+: (((C1 (MetaCons "DynamicsMp" PrefixI True) (S1 (MetaSel (Just "dynamicsMp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty)) :+: (C1 (MetaCons "DynamicsMf" PrefixI True) (S1 (MetaSel (Just "dynamicsMf") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty)) :+: C1 (MetaCons "DynamicsSf" PrefixI True) (S1 (MetaSel (Just "dynamicsSf") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty)))) :+: (C1 (MetaCons "DynamicsSfp" PrefixI True) (S1 (MetaSel (Just "dynamicsSfp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty)) :+: (C1 (MetaCons "DynamicsSfpp" PrefixI True) (S1 (MetaSel (Just "dynamicsSfpp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty)) :+: C1 (MetaCons "DynamicsFp" PrefixI True) (S1 (MetaSel (Just "dynamicsFp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty))))) :+: ((C1 (MetaCons "DynamicsRf" PrefixI True) (S1 (MetaSel (Just "dynamicsRf") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty)) :+: (C1 (MetaCons "DynamicsRfz" PrefixI True) (S1 (MetaSel (Just "dynamicsRfz") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty)) :+: C1 (MetaCons "DynamicsSfz" PrefixI True) (S1 (MetaSel (Just "dynamicsSfz") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty)))) :+: (C1 (MetaCons "DynamicsSffz" PrefixI True) (S1 (MetaSel (Just "dynamicsSffz") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty)) :+: (C1 (MetaCons "DynamicsFz" PrefixI True) (S1 (MetaSel (Just "dynamicsFz") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty)) :+: C1 (MetaCons "DynamicsOtherDynamics" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ChxEncoding Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ChxEncoding Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ChxEncoding :: Type -> Type #

EmitXml ChxEncoding Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxEncoding Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxEncoding = D1 (MetaData "ChxEncoding" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) ((C1 (MetaCons "EncodingEncodingDate" PrefixI True) (S1 (MetaSel (Just "encodingEncodingDate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 YyyyMmDd)) :+: C1 (MetaCons "EncodingEncoder" PrefixI True) (S1 (MetaSel (Just "encodingEncoder") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypedText))) :+: (C1 (MetaCons "EncodingSoftware" PrefixI True) (S1 (MetaSel (Just "encodingSoftware") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: (C1 (MetaCons "EncodingEncodingDescription" PrefixI True) (S1 (MetaSel (Just "encodingEncodingDescription") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: C1 (MetaCons "EncodingSupports" PrefixI True) (S1 (MetaSel (Just "encodingSupports") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Supports)))))

data FullNote Source #

full-note (choice)

Constructors

FullNotePitch 

Fields

FullNoteUnpitched 

Fields

FullNoteRest 

Fields

Instances
Eq FullNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show FullNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic FullNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep FullNote :: Type -> Type #

Methods

from :: FullNote -> Rep FullNote x #

to :: Rep FullNote x -> FullNote #

EmitXml FullNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep FullNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep FullNote = D1 (MetaData "FullNote" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "FullNotePitch" PrefixI True) (S1 (MetaSel (Just "fullNotePitch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Pitch)) :+: (C1 (MetaCons "FullNoteUnpitched" PrefixI True) (S1 (MetaSel (Just "fullNoteUnpitched") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DisplayStepOctave)) :+: C1 (MetaCons "FullNoteRest" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ChxHarmonic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ChxHarmonic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ChxHarmonic :: Type -> Type #

EmitXml ChxHarmonic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxHarmonic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxHarmonic = D1 (MetaData "ChxHarmonic" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "HarmonicNatural" PrefixI True) (S1 (MetaSel (Just "harmonicNatural") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty)) :+: C1 (MetaCons "HarmonicArtificial" PrefixI True) (S1 (MetaSel (Just "harmonicArtificial") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty)))

data ChxHarmonic1 Source #

harmonic (choice)

Constructors

HarmonicBasePitch 

Fields

HarmonicTouchingPitch 

Fields

HarmonicSoundingPitch 

Fields

Instances
Eq ChxHarmonic1 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ChxHarmonic1 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ChxHarmonic1 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ChxHarmonic1 :: Type -> Type #

EmitXml ChxHarmonic1 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxHarmonic1 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxHarmonic1 = D1 (MetaData "ChxHarmonic1" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "HarmonicBasePitch" PrefixI True) (S1 (MetaSel (Just "harmonicBasePitch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty)) :+: (C1 (MetaCons "HarmonicTouchingPitch" PrefixI True) (S1 (MetaSel (Just "harmonicTouchingPitch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty)) :+: C1 (MetaCons "HarmonicSoundingPitch" PrefixI True) (S1 (MetaSel (Just "harmonicSoundingPitch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty))))

data ChxHarmonyChord Source #

harmony-chord (choice)

Constructors

HarmonyChordRoot 

Fields

HarmonyChordFunction 

Fields

Instances
Eq ChxHarmonyChord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ChxHarmonyChord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ChxHarmonyChord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ChxHarmonyChord :: Type -> Type #

EmitXml ChxHarmonyChord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxHarmonyChord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxHarmonyChord = D1 (MetaData "ChxHarmonyChord" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "HarmonyChordRoot" PrefixI True) (S1 (MetaSel (Just "harmonyChordRoot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Root)) :+: C1 (MetaCons "HarmonyChordFunction" PrefixI True) (S1 (MetaSel (Just "harmonyChordFunction") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StyleText)))

data ChxKey Source #

key (choice)

Instances
Eq ChxKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show ChxKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ChxKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ChxKey :: Type -> Type #

Methods

from :: ChxKey -> Rep ChxKey x #

to :: Rep ChxKey x -> ChxKey #

EmitXml ChxKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxKey = D1 (MetaData "ChxKey" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "KeyTraditionalKey" PrefixI True) (S1 (MetaSel (Just "keyTraditionalKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TraditionalKey)) :+: C1 (MetaCons "KeyNonTraditionalKey" PrefixI True) (S1 (MetaSel (Just "keyNonTraditionalKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [NonTraditionalKey])))

data ChxLyric Source #

lyric (choice)

Constructors

LyricSyllabic 

Fields

LyricExtend 

Fields

LyricLaughing 

Fields

LyricHumming 

Fields

Instances
Eq ChxLyric Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ChxLyric Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ChxLyric Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ChxLyric :: Type -> Type #

Methods

from :: ChxLyric -> Rep ChxLyric x #

to :: Rep ChxLyric x -> ChxLyric #

EmitXml ChxLyric Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxLyric Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ChxMeasureStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ChxMeasureStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ChxMeasureStyle :: Type -> Type #

EmitXml ChxMeasureStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxMeasureStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxMeasureStyle = D1 (MetaData "ChxMeasureStyle" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) ((C1 (MetaCons "MeasureStyleMultipleRest" PrefixI True) (S1 (MetaSel (Just "measureStyleMultipleRest") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MultipleRest)) :+: C1 (MetaCons "MeasureStyleMeasureRepeat" PrefixI True) (S1 (MetaSel (Just "measureStyleMeasureRepeat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MeasureRepeat))) :+: (C1 (MetaCons "MeasureStyleBeatRepeat" PrefixI True) (S1 (MetaSel (Just "measureStyleBeatRepeat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BeatRepeat)) :+: C1 (MetaCons "MeasureStyleSlash" PrefixI True) (S1 (MetaSel (Just "measureStyleSlash") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CmpSlash))))

data ChxMetronome0 Source #

metronome (choice)

Constructors

MetronomePerMinute 

Fields

MetronomeBeatUnit 
Instances
Eq ChxMetronome0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ChxMetronome0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ChxMetronome0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ChxMetronome0 :: Type -> Type #

EmitXml ChxMetronome0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxMetronome0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxMetronome0 = D1 (MetaData "ChxMetronome0" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "MetronomePerMinute" PrefixI True) (S1 (MetaSel (Just "metronomePerMinute") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PerMinute)) :+: C1 (MetaCons "MetronomeBeatUnit" PrefixI True) (S1 (MetaSel (Just "metronomeBeatUnit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BeatUnit)))

data ChxMetronome Source #

metronome (choice)

Instances
Eq ChxMetronome Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ChxMetronome Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ChxMetronome Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ChxMetronome :: Type -> Type #

EmitXml ChxMetronome Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxMetronome Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxMetronome = D1 (MetaData "ChxMetronome" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "ChxMetronomeBeatUnit" PrefixI True) (S1 (MetaSel (Just "chxmetronomeBeatUnit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BeatUnit) :*: S1 (MetaSel (Just "chxmetronomeMetronome") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ChxMetronome0)) :+: C1 (MetaCons "MetronomeMetronomeNote" PrefixI True) (S1 (MetaSel (Just "metronomeMetronomeNote") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [MetronomeNote]) :*: S1 (MetaSel (Just "metronomeMetronome1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SeqMetronome))))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ChxMusicData Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ChxMusicData Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ChxMusicData :: Type -> Type #

EmitXml ChxMusicData Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxMusicData Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxMusicData = D1 (MetaData "ChxMusicData" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (((C1 (MetaCons "MusicDataNote" PrefixI True) (S1 (MetaSel (Just "musicDataNote") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Note)) :+: (C1 (MetaCons "MusicDataBackup" PrefixI True) (S1 (MetaSel (Just "musicDataBackup") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Backup)) :+: C1 (MetaCons "MusicDataForward" PrefixI True) (S1 (MetaSel (Just "musicDataForward") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Forward)))) :+: (C1 (MetaCons "MusicDataDirection" PrefixI True) (S1 (MetaSel (Just "musicDataDirection") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Direction)) :+: (C1 (MetaCons "MusicDataAttributes" PrefixI True) (S1 (MetaSel (Just "musicDataAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Attributes)) :+: C1 (MetaCons "MusicDataHarmony" PrefixI True) (S1 (MetaSel (Just "musicDataHarmony") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Harmony))))) :+: ((C1 (MetaCons "MusicDataFiguredBass" PrefixI True) (S1 (MetaSel (Just "musicDataFiguredBass") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FiguredBass)) :+: (C1 (MetaCons "MusicDataPrint" PrefixI True) (S1 (MetaSel (Just "musicDataPrint") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Print)) :+: C1 (MetaCons "MusicDataSound" PrefixI True) (S1 (MetaSel (Just "musicDataSound") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Sound)))) :+: ((C1 (MetaCons "MusicDataBarline" PrefixI True) (S1 (MetaSel (Just "musicDataBarline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Barline)) :+: C1 (MetaCons "MusicDataGrouping" PrefixI True) (S1 (MetaSel (Just "musicDataGrouping") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Grouping))) :+: (C1 (MetaCons "MusicDataLink" PrefixI True) (S1 (MetaSel (Just "musicDataLink") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Link)) :+: C1 (MetaCons "MusicDataBookmark" PrefixI True) (S1 (MetaSel (Just "musicDataBookmark") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bookmark))))))

data ChxNameDisplay Source #

name-display (choice)

Constructors

NameDisplayDisplayText 

Fields

NameDisplayAccidentalText 

Fields

Instances
Eq ChxNameDisplay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ChxNameDisplay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ChxNameDisplay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ChxNameDisplay :: Type -> Type #

EmitXml ChxNameDisplay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxNameDisplay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxNameDisplay = D1 (MetaData "ChxNameDisplay" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "NameDisplayDisplayText" PrefixI True) (S1 (MetaSel (Just "nameDisplayDisplayText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FormattedText)) :+: C1 (MetaCons "NameDisplayAccidentalText" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ChxNotations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ChxNotations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ChxNotations :: Type -> Type #

EmitXml ChxNotations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxNotations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxNotations = D1 (MetaData "ChxNotations" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (((C1 (MetaCons "NotationsTied" PrefixI True) (S1 (MetaSel (Just "notationsTied") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Tied)) :+: (C1 (MetaCons "NotationsSlur" PrefixI True) (S1 (MetaSel (Just "notationsSlur") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Slur)) :+: C1 (MetaCons "NotationsTuplet" PrefixI True) (S1 (MetaSel (Just "notationsTuplet") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Tuplet)))) :+: ((C1 (MetaCons "NotationsGlissando" PrefixI True) (S1 (MetaSel (Just "notationsGlissando") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Glissando)) :+: C1 (MetaCons "NotationsSlide" PrefixI True) (S1 (MetaSel (Just "notationsSlide") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Slide))) :+: (C1 (MetaCons "NotationsOrnaments" PrefixI True) (S1 (MetaSel (Just "notationsOrnaments") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Ornaments)) :+: C1 (MetaCons "NotationsTechnical" PrefixI True) (S1 (MetaSel (Just "notationsTechnical") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Technical))))) :+: ((C1 (MetaCons "NotationsArticulations" PrefixI True) (S1 (MetaSel (Just "notationsArticulations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Articulations)) :+: (C1 (MetaCons "NotationsDynamics" PrefixI True) (S1 (MetaSel (Just "notationsDynamics") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Dynamics)) :+: C1 (MetaCons "NotationsFermata" PrefixI True) (S1 (MetaSel (Just "notationsFermata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Fermata)))) :+: ((C1 (MetaCons "NotationsArpeggiate" PrefixI True) (S1 (MetaSel (Just "notationsArpeggiate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Arpeggiate)) :+: C1 (MetaCons "NotationsNonArpeggiate" PrefixI True) (S1 (MetaSel (Just "notationsNonArpeggiate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NonArpeggiate))) :+: (C1 (MetaCons "NotationsAccidentalMark" PrefixI True) (S1 (MetaSel (Just "notationsAccidentalMark") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AccidentalMark)) :+: C1 (MetaCons "NotationsOtherNotation" PrefixI True) (S1 (MetaSel (Just "notationsOtherNotation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OtherNotation))))))

data ChxNote Source #

note (choice)

Constructors

NoteGrace 

Fields

NoteCue 

Fields

NoteFullNote 

Fields

Instances
Eq ChxNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show ChxNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ChxNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ChxNote :: Type -> Type #

Methods

from :: ChxNote -> Rep ChxNote x #

to :: Rep ChxNote x -> ChxNote #

EmitXml ChxNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ChxOrnaments Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ChxOrnaments Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ChxOrnaments :: Type -> Type #

EmitXml ChxOrnaments Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxOrnaments Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxOrnaments = D1 (MetaData "ChxOrnaments" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (((C1 (MetaCons "OrnamentsTrillMark" PrefixI True) (S1 (MetaSel (Just "ornamentsTrillMark") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyTrillSound)) :+: C1 (MetaCons "OrnamentsTurn" PrefixI True) (S1 (MetaSel (Just "ornamentsTurn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyTrillSound))) :+: (C1 (MetaCons "OrnamentsDelayedTurn" PrefixI True) (S1 (MetaSel (Just "ornamentsDelayedTurn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyTrillSound)) :+: (C1 (MetaCons "OrnamentsInvertedTurn" PrefixI True) (S1 (MetaSel (Just "ornamentsInvertedTurn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyTrillSound)) :+: C1 (MetaCons "OrnamentsShake" PrefixI True) (S1 (MetaSel (Just "ornamentsShake") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyTrillSound))))) :+: ((C1 (MetaCons "OrnamentsWavyLine" PrefixI True) (S1 (MetaSel (Just "ornamentsWavyLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 WavyLine)) :+: (C1 (MetaCons "OrnamentsMordent" PrefixI True) (S1 (MetaSel (Just "ornamentsMordent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Mordent)) :+: C1 (MetaCons "OrnamentsInvertedMordent" PrefixI True) (S1 (MetaSel (Just "ornamentsInvertedMordent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Mordent)))) :+: (C1 (MetaCons "OrnamentsSchleifer" PrefixI True) (S1 (MetaSel (Just "ornamentsSchleifer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyPlacement)) :+: (C1 (MetaCons "OrnamentsTremolo" PrefixI True) (S1 (MetaSel (Just "ornamentsTremolo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Tremolo)) :+: C1 (MetaCons "OrnamentsOtherOrnament" PrefixI True) (S1 (MetaSel (Just "ornamentsOtherOrnament") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PlacementText))))))

data ChxPartList Source #

part-list (choice)

Instances
Eq ChxPartList Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ChxPartList Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ChxPartList Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ChxPartList :: Type -> Type #

EmitXml ChxPartList Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxPartList Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxPartList = D1 (MetaData "ChxPartList" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "PartListPartGroup" PrefixI True) (S1 (MetaSel (Just "chxpartListPartGroup") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 GrpPartGroup)) :+: C1 (MetaCons "PartListScorePart" PrefixI True) (S1 (MetaSel (Just "chxpartListScorePart") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ScorePart)))

data ChxScoreInstrument Source #

score-instrument (choice)

Constructors

ScoreInstrumentSolo 

Fields

ScoreInstrumentEnsemble 

Fields

Instances
Eq ChxScoreInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ChxScoreInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ChxScoreInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ChxScoreInstrument :: Type -> Type #

EmitXml ChxScoreInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxScoreInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxScoreInstrument = D1 (MetaData "ChxScoreInstrument" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "ScoreInstrumentSolo" PrefixI True) (S1 (MetaSel (Just "scoreInstrumentSolo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Empty)) :+: C1 (MetaCons "ScoreInstrumentEnsemble" PrefixI True) (S1 (MetaSel (Just "scoreInstrumentEnsemble") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PositiveIntegerOrEmpty)))

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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ChxTechnical Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ChxTechnical Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ChxTechnical :: Type -> Type #

EmitXml ChxTechnical Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxTechnical Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxTechnical = D1 (MetaData "ChxTechnical" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) ((((C1 (MetaCons "TechnicalUpBow" PrefixI True) (S1 (MetaSel (Just "technicalUpBow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyPlacement)) :+: C1 (MetaCons "TechnicalDownBow" PrefixI True) (S1 (MetaSel (Just "technicalDownBow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyPlacement))) :+: (C1 (MetaCons "TechnicalHarmonic" PrefixI True) (S1 (MetaSel (Just "technicalHarmonic") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Harmonic)) :+: (C1 (MetaCons "TechnicalOpenString" PrefixI True) (S1 (MetaSel (Just "technicalOpenString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyPlacement)) :+: C1 (MetaCons "TechnicalThumbPosition" PrefixI True) (S1 (MetaSel (Just "technicalThumbPosition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyPlacement))))) :+: ((C1 (MetaCons "TechnicalFingering" PrefixI True) (S1 (MetaSel (Just "technicalFingering") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Fingering)) :+: C1 (MetaCons "TechnicalPluck" PrefixI True) (S1 (MetaSel (Just "technicalPluck") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PlacementText))) :+: (C1 (MetaCons "TechnicalDoubleTongue" PrefixI True) (S1 (MetaSel (Just "technicalDoubleTongue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyPlacement)) :+: (C1 (MetaCons "TechnicalTripleTongue" PrefixI True) (S1 (MetaSel (Just "technicalTripleTongue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyPlacement)) :+: C1 (MetaCons "TechnicalStopped" PrefixI True) (S1 (MetaSel (Just "technicalStopped") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyPlacement)))))) :+: (((C1 (MetaCons "TechnicalSnapPizzicato" PrefixI True) (S1 (MetaSel (Just "technicalSnapPizzicato") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyPlacement)) :+: C1 (MetaCons "TechnicalFret" PrefixI True) (S1 (MetaSel (Just "technicalFret") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Fret))) :+: (C1 (MetaCons "TechnicalString" PrefixI True) (S1 (MetaSel (Just "technicalString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CmpString)) :+: (C1 (MetaCons "TechnicalHammerOn" PrefixI True) (S1 (MetaSel (Just "technicalHammerOn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HammerOnPullOff)) :+: C1 (MetaCons "TechnicalPullOff" PrefixI True) (S1 (MetaSel (Just "technicalPullOff") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HammerOnPullOff))))) :+: ((C1 (MetaCons "TechnicalBend" PrefixI True) (S1 (MetaSel (Just "technicalBend") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bend)) :+: (C1 (MetaCons "TechnicalTap" PrefixI True) (S1 (MetaSel (Just "technicalTap") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PlacementText)) :+: C1 (MetaCons "TechnicalHeel" PrefixI True) (S1 (MetaSel (Just "technicalHeel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HeelToe)))) :+: (C1 (MetaCons "TechnicalToe" PrefixI True) (S1 (MetaSel (Just "technicalToe") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HeelToe)) :+: (C1 (MetaCons "TechnicalFingernails" PrefixI True) (S1 (MetaSel (Just "technicalFingernails") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmptyPlacement)) :+: C1 (MetaCons "TechnicalOtherTechnical" PrefixI True) (S1 (MetaSel (Just "technicalOtherTechnical") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PlacementText)))))))

data ChxTime Source #

time (choice)

Constructors

TimeTime 

Fields

TimeSenzaMisura 

Fields

Instances
Eq ChxTime Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show ChxTime Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ChxTime Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ChxTime :: Type -> Type #

Methods

from :: ChxTime -> Rep ChxTime x #

to :: Rep ChxTime x -> ChxTime #

EmitXml ChxTime Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxTime Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ChxTime = D1 (MetaData "ChxTime" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "TimeTime" PrefixI True) (S1 (MetaSel (Just "chxtimeTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [SeqTime])) :+: C1 (MetaCons "TimeSenzaMisura" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show SeqCredit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic SeqCredit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep SeqCredit :: Type -> Type #

EmitXml SeqCredit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SeqCredit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SeqCredit = D1 (MetaData "SeqCredit" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "SeqCredit" PrefixI True) (S1 (MetaSel (Just "seqcreditLink") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Link]) :*: (S1 (MetaSel (Just "seqcreditBookmark") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Bookmark]) :*: S1 (MetaSel (Just "seqcreditCreditWords") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FormattedText))))

data SeqDisplayStepOctave Source #

display-step-octave (sequence)

Constructors

SeqDisplayStepOctave 

Fields

data SeqLyric0 Source #

lyric (sequence)

Constructors

SeqLyric0 

Fields

Instances
Eq SeqLyric0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show SeqLyric0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic SeqLyric0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep SeqLyric0 :: Type -> Type #

EmitXml SeqLyric0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SeqLyric0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SeqLyric0 = D1 (MetaData "SeqLyric0" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "SeqLyric0" PrefixI True) (S1 (MetaSel (Just "lyricElision") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Elision) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show SeqLyric Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic SeqLyric Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep SeqLyric :: Type -> Type #

Methods

from :: SeqLyric -> Rep SeqLyric x #

to :: Rep SeqLyric x -> SeqLyric #

EmitXml SeqLyric Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SeqLyric Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SeqLyric = D1 (MetaData "SeqLyric" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "SeqLyric" PrefixI True) (S1 (MetaSel (Just "seqlyricLyric") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SeqLyric0)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show SeqMetronome Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic SeqMetronome Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep SeqMetronome :: Type -> Type #

EmitXml SeqMetronome Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SeqMetronome Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SeqMetronome = D1 (MetaData "SeqMetronome" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "SeqMetronome" PrefixI True) (S1 (MetaSel (Just "metronomeMetronomeRelation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "seqmetronomeMetronomeNote") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [MetronomeNote])))

data SeqMetronomeTuplet Source #

metronome-tuplet (sequence)

Constructors

SeqMetronomeTuplet 

Fields

Instances
Eq SeqMetronomeTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show SeqMetronomeTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic SeqMetronomeTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep SeqMetronomeTuplet :: Type -> Type #

EmitXml SeqMetronomeTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SeqMetronomeTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SeqMetronomeTuplet = D1 (MetaData "SeqMetronomeTuplet" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "SeqMetronomeTuplet" PrefixI True) (S1 (MetaSel (Just "metronomeTupletNormalType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NoteTypeValue) :*: S1 (MetaSel (Just "metronomeTupletNormalDot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Empty])))

data SeqOrnaments Source #

ornaments (sequence)

Constructors

SeqOrnaments 

Fields

Instances
Eq SeqOrnaments Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show SeqOrnaments Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic SeqOrnaments Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep SeqOrnaments :: Type -> Type #

EmitXml SeqOrnaments Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SeqOrnaments Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SeqOrnaments = D1 (MetaData "SeqOrnaments" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "SeqOrnaments" PrefixI True) (S1 (MetaSel (Just "seqornamentsOrnaments") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ChxOrnaments) :*: S1 (MetaSel (Just "ornamentsAccidentalMark") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [AccidentalMark])))

data SeqPageLayout Source #

page-layout (sequence)

Constructors

SeqPageLayout 

Fields

Instances
Eq SeqPageLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show SeqPageLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic SeqPageLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep SeqPageLayout :: Type -> Type #

EmitXml SeqPageLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SeqPageLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SeqPageLayout = D1 (MetaData "SeqPageLayout" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "SeqPageLayout" PrefixI True) (S1 (MetaSel (Just "pageLayoutPageHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Tenths) :*: S1 (MetaSel (Just "pageLayoutPageWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Tenths)))

data SeqTime Source #

time (sequence)

Constructors

SeqTime 

Fields

Instances
Eq SeqTime Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show SeqTime Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic SeqTime Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep SeqTime :: Type -> Type #

Methods

from :: SeqTime -> Rep SeqTime x #

to :: Rep SeqTime x -> SeqTime #

EmitXml SeqTime Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SeqTime Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep SeqTime = D1 (MetaData "SeqTime" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "SeqTime" PrefixI True) (S1 (MetaSel (Just "timeBeats") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "timeBeatType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

mkSeqTime :: String -> String -> SeqTime Source #

Smart constructor for SeqTime

data SeqTimeModification Source #

time-modification (sequence)

Constructors

SeqTimeModification 

Fields

data AllMargins Source #

all-margins (group)

Constructors

AllMargins 

Fields

Instances
Eq AllMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show AllMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic AllMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep AllMargins :: Type -> Type #

EmitXml AllMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep AllMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep AllMargins = D1 (MetaData "AllMargins" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "AllMargins" PrefixI True) (S1 (MetaSel (Just "allMarginsLeftRightMargins") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LeftRightMargins) :*: (S1 (MetaSel (Just "allMarginsTopMargin") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Tenths) :*: S1 (MetaSel (Just "allMarginsBottomMargin") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Tenths))))

data BeatUnit Source #

beat-unit (group)

Constructors

BeatUnit 

Fields

Instances
Eq BeatUnit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show BeatUnit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic BeatUnit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep BeatUnit :: Type -> Type #

Methods

from :: BeatUnit -> Rep BeatUnit x #

to :: Rep BeatUnit x -> BeatUnit #

EmitXml BeatUnit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep BeatUnit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep BeatUnit = D1 (MetaData "BeatUnit" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "BeatUnit" PrefixI True) (S1 (MetaSel (Just "beatUnitBeatUnit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NoteTypeValue) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Duration Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Duration Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Duration :: Type -> Type #

Methods

from :: Duration -> Rep Duration x #

to :: Rep Duration x -> Duration #

EmitXml Duration Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Duration Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Duration = D1 (MetaData "Duration" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Duration" PrefixI True) (S1 (MetaSel (Just "durationDuration") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PositiveDivisions)))

data Editorial Source #

editorial (group)

Instances
Eq Editorial Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Editorial Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Editorial Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Editorial :: Type -> Type #

EmitXml Editorial Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Editorial Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Editorial = D1 (MetaData "Editorial" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Editorial" PrefixI True) (S1 (MetaSel (Just "editorialFootnote") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Footnote)) :*: S1 (MetaSel (Just "editorialLevel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe GrpLevel))))

mkEditorial :: Editorial Source #

Smart constructor for Editorial

data EditorialVoice Source #

editorial-voice (group)

Instances
Eq EditorialVoice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show EditorialVoice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic EditorialVoice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep EditorialVoice :: Type -> Type #

EmitXml EditorialVoice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep EditorialVoice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep EditorialVoice = D1 (MetaData "EditorialVoice" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "EditorialVoice" PrefixI True) (S1 (MetaSel (Just "editorialVoiceFootnote") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Footnote)) :*: (S1 (MetaSel (Just "editorialVoiceLevel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe GrpLevel)) :*: S1 (MetaSel (Just "editorialVoiceVoice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Voice)))))

data EditorialVoiceDirection Source #

editorial-voice-direction (group)

Instances
Eq EditorialVoiceDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show EditorialVoiceDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic EditorialVoiceDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep EditorialVoiceDirection :: Type -> Type #

EmitXml EditorialVoiceDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep EditorialVoiceDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep EditorialVoiceDirection = D1 (MetaData "EditorialVoiceDirection" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "EditorialVoiceDirection" PrefixI True) (S1 (MetaSel (Just "editorialVoiceDirectionFootnote") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Footnote)) :*: (S1 (MetaSel (Just "editorialVoiceDirectionLevel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe GrpLevel)) :*: S1 (MetaSel (Just "editorialVoiceDirectionVoice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Voice)))))

data Footnote Source #

footnote (group)

Constructors

Footnote 

Fields

Instances
Eq Footnote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show Footnote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Footnote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Footnote :: Type -> Type #

Methods

from :: Footnote -> Rep Footnote x #

to :: Rep Footnote x -> Footnote #

EmitXml Footnote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Footnote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Footnote = D1 (MetaData "Footnote" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Footnote" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show GrpFullNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic GrpFullNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep GrpFullNote :: Type -> Type #

EmitXml GrpFullNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep GrpFullNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep GrpFullNote = D1 (MetaData "GrpFullNote" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "GrpFullNote" PrefixI True) (S1 (MetaSel (Just "fullNoteChord") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Empty)) :*: S1 (MetaSel (Just "fullNoteFullNote") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FullNote)))

data HarmonyChord Source #

harmony-chord (group)

Constructors

HarmonyChord 

Fields

Instances
Eq HarmonyChord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show HarmonyChord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic HarmonyChord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep HarmonyChord :: Type -> Type #

EmitXml HarmonyChord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep HarmonyChord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep HarmonyChord = D1 (MetaData "HarmonyChord" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "HarmonyChord" PrefixI True) ((S1 (MetaSel (Just "harmonyChordHarmonyChord") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ChxHarmonyChord) :*: S1 (MetaSel (Just "harmonyChordKind") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Kind)) :*: (S1 (MetaSel (Just "harmonyChordInversion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Inversion)) :*: (S1 (MetaSel (Just "harmonyChordBass") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bass)) :*: S1 (MetaSel (Just "harmonyChordDegree") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Degree])))))

data Layout Source #

layout (group)

Constructors

Layout 

Fields

Instances
Eq Layout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Layout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Layout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Layout :: Type -> Type #

Methods

from :: Layout -> Rep Layout x #

to :: Rep Layout x -> Layout #

EmitXml Layout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Layout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Layout = D1 (MetaData "Layout" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Layout" PrefixI True) (S1 (MetaSel (Just "layoutPageLayout") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe PageLayout)) :*: (S1 (MetaSel (Just "layoutSystemLayout") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SystemLayout)) :*: S1 (MetaSel (Just "layoutStaffLayout") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [StaffLayout]))))

mkLayout :: Layout Source #

Smart constructor for Layout

data LeftRightMargins Source #

left-right-margins (group)

Constructors

LeftRightMargins 

Fields

Instances
Eq LeftRightMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show LeftRightMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic LeftRightMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep LeftRightMargins :: Type -> Type #

EmitXml LeftRightMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep LeftRightMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep LeftRightMargins = D1 (MetaData "LeftRightMargins" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "LeftRightMargins" PrefixI True) (S1 (MetaSel (Just "leftRightMarginsLeftMargin") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Tenths) :*: S1 (MetaSel (Just "leftRightMarginsRightMargin") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Tenths)))

data GrpLevel Source #

level (group)

Constructors

GrpLevel 

Fields

Instances
Eq GrpLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show GrpLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic GrpLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep GrpLevel :: Type -> Type #

Methods

from :: GrpLevel -> Rep GrpLevel x #

to :: Rep GrpLevel x -> GrpLevel #

EmitXml GrpLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep GrpLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep GrpLevel = D1 (MetaData "GrpLevel" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "GrpLevel" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show MusicData Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic MusicData Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep MusicData :: Type -> Type #

EmitXml MusicData Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep MusicData Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep MusicData = D1 (MetaData "MusicData" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "MusicData" PrefixI True) (S1 (MetaSel (Just "musicDataMusicData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ChxMusicData])))

mkMusicData :: MusicData Source #

Smart constructor for MusicData

data NonTraditionalKey Source #

non-traditional-key (group)

Constructors

NonTraditionalKey 

Fields

Instances
Eq NonTraditionalKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show NonTraditionalKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic NonTraditionalKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep NonTraditionalKey :: Type -> Type #

EmitXml NonTraditionalKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NonTraditionalKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep NonTraditionalKey = D1 (MetaData "NonTraditionalKey" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "NonTraditionalKey" PrefixI True) (S1 (MetaSel (Just "nonTraditionalKeyKeyStep") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Step) :*: S1 (MetaSel (Just "nonTraditionalKeyKeyAlter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Semitones)))

data GrpPartGroup Source #

part-group (group)

Constructors

GrpPartGroup 

Fields

Instances
Eq GrpPartGroup Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show GrpPartGroup Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic GrpPartGroup Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep GrpPartGroup :: Type -> Type #

EmitXml GrpPartGroup Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep GrpPartGroup Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep GrpPartGroup = D1 (MetaData "GrpPartGroup" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "GrpPartGroup" PrefixI True) (S1 (MetaSel (Just "partGroupPartGroup") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PartGroup)))

data ScoreHeader Source #

score-header (group)

Constructors

ScoreHeader 

Fields

Instances
Eq ScoreHeader Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ScoreHeader Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ScoreHeader Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ScoreHeader :: Type -> Type #

EmitXml ScoreHeader Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ScoreHeader Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ScoreHeader = D1 (MetaData "ScoreHeader" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "ScoreHeader" PrefixI True) ((S1 (MetaSel (Just "scoreHeaderWork") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Work)) :*: (S1 (MetaSel (Just "scoreHeaderMovementNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String)) :*: S1 (MetaSel (Just "scoreHeaderMovementTitle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String)))) :*: ((S1 (MetaSel (Just "scoreHeaderIdentification") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Identification)) :*: S1 (MetaSel (Just "scoreHeaderDefaults") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Defaults))) :*: (S1 (MetaSel (Just "scoreHeaderCredit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Credit]) :*: S1 (MetaSel (Just "scoreHeaderPartList") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PartList)))))

data ScorePart Source #

score-part (group)

Constructors

ScorePart 

Fields

Instances
Eq ScorePart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show ScorePart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic ScorePart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep ScorePart :: Type -> Type #

EmitXml ScorePart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ScorePart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep ScorePart = D1 (MetaData "ScorePart" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "ScorePart" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Slash Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Slash -> ShowS #

show :: Slash -> String #

showList :: [Slash] -> ShowS #

Generic Slash Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Slash :: Type -> Type #

Methods

from :: Slash -> Rep Slash x #

to :: Rep Slash x -> Slash #

EmitXml Slash Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Slash -> XmlRep Source #

type Rep Slash Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Slash = D1 (MetaData "Slash" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Slash" PrefixI True) (S1 (MetaSel (Just "slashSlashType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NoteTypeValue) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Staff Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Staff -> ShowS #

show :: Staff -> String #

showList :: [Staff] -> ShowS #

Generic Staff Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Staff :: Type -> Type #

Methods

from :: Staff -> Rep Staff x #

to :: Rep Staff x -> Staff #

EmitXml Staff Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Staff -> XmlRep Source #

type Rep Staff Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Staff = D1 (MetaData "Staff" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Staff" PrefixI True) (S1 (MetaSel (Just "staffStaff") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PositiveInteger)))

mkStaff :: PositiveInteger -> Staff Source #

Smart constructor for Staff

data TraditionalKey Source #

traditional-key (group)

Constructors

TraditionalKey 

Fields

Instances
Eq TraditionalKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Show TraditionalKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic TraditionalKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep TraditionalKey :: Type -> Type #

EmitXml TraditionalKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TraditionalKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep TraditionalKey = D1 (MetaData "TraditionalKey" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "TraditionalKey" PrefixI True) (S1 (MetaSel (Just "traditionalKeyCancel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Cancel)) :*: (S1 (MetaSel (Just "traditionalKeyFifths") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Fifths) :*: S1 (MetaSel (Just "traditionalKeyMode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Mode)))))

data Tuning Source #

tuning (group)

Constructors

Tuning 

Fields

Instances
Eq Tuning Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Tuning Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Generic Tuning Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Tuning :: Type -> Type #

Methods

from :: Tuning -> Rep Tuning x #

to :: Rep Tuning x -> Tuning #

EmitXml Tuning Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Tuning Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Tuning = D1 (MetaData "Tuning" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Tuning" PrefixI True) (S1 (MetaSel (Just "tuningTuningStep") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Step) :*: (S1 (MetaSel (Just "tuningTuningAlter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Semitones)) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

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

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

Show Voice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

showsPrec :: Int -> Voice -> ShowS #

show :: Voice -> String #

showList :: [Voice] -> ShowS #

Generic Voice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Associated Types

type Rep Voice :: Type -> Type #

Methods

from :: Voice -> Rep Voice x #

to :: Rep Voice x -> Voice #

EmitXml Voice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

Methods

emitXml :: Voice -> XmlRep Source #

type Rep Voice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml20

type Rep Voice = D1 (MetaData "Voice" "Fadno.MusicXml.MusicXml20" "fadno-xml-1.1.2-GpVCM5B87jpIUN2yQhMObz" False) (C1 (MetaCons "Voice" PrefixI True) (S1 (MetaSel (Just "voiceVoice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

mkVoice :: String -> Voice Source #

Smart constructor for Voice