fadno-xml-1.2.1: XML/XSD combinators/schemas/codegen
Safe HaskellSafe-Inferred
LanguageHaskell2010

Fadno.MusicXml.MusicXml31

Synopsis

Documentation

newtype ID Source #

xs:ID (simple)

Constructors

ID 

Fields

Instances

Instances details
IsString ID Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

fromString :: String -> ID #

Generic ID Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ID :: Type -> Type #

Methods

from :: ID -> Rep ID x #

to :: Rep ID x -> ID #

Read ID Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show ID Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> ID -> ShowS #

show :: ID -> String #

showList :: [ID] -> ShowS #

EmitXml ID Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: ID -> XmlRep Source #

Eq ID Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord ID Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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 #

type Rep ID Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ID = D1 ('MetaData "ID" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
IsString IDREF Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

fromString :: String -> IDREF #

Generic IDREF Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep IDREF :: Type -> Type #

Methods

from :: IDREF -> Rep IDREF x #

to :: Rep IDREF x -> IDREF #

Read IDREF Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show IDREF Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> IDREF -> ShowS #

show :: IDREF -> String #

showList :: [IDREF] -> ShowS #

EmitXml IDREF Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: IDREF -> XmlRep Source #

Eq IDREF Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord IDREF Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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 #

type Rep IDREF Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep IDREF = D1 ('MetaData "IDREF" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
IsString NCName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

fromString :: String -> NCName #

Generic NCName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep NCName :: Type -> Type #

Methods

from :: NCName -> Rep NCName x #

to :: Rep NCName x -> NCName #

Read NCName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show NCName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml NCName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq NCName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord NCName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NCName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NCName = D1 ('MetaData "NCName" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
IsString NMTOKEN Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

fromString :: String -> NMTOKEN #

Generic NMTOKEN Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep NMTOKEN :: Type -> Type #

Methods

from :: NMTOKEN -> Rep NMTOKEN x #

to :: Rep NMTOKEN x -> NMTOKEN #

Read NMTOKEN Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show NMTOKEN Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml NMTOKEN Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq NMTOKEN Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord NMTOKEN Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NMTOKEN Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NMTOKEN = D1 ('MetaData "NMTOKEN" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
IsString Name Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

fromString :: String -> Name #

Generic Name Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Name :: Type -> Type #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

Read Name Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show Name Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

EmitXml Name Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Name -> XmlRep Source #

Eq Name Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord Name Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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 #

type Rep Name Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Name = D1 ('MetaData "Name" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded AboveBelow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum AboveBelow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic AboveBelow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep AboveBelow :: Type -> Type #

Show AboveBelow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml AboveBelow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq AboveBelow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord AboveBelow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep AboveBelow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep AboveBelow = D1 ('MetaData "AboveBelow" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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. The quarter- and three-quarters- accidentals are Tartini-style quarter-tone accidentals. The -down and -up accidentals are quarter-tone accidentals that include arrows pointing down or up. The slash- accidentals are used in Turkish classical music. The numbered sharp and flat accidentals are superscripted versions of the accidental signs, used in Turkish folk music. The sori and koron accidentals are microtonal sharp and flat accidentals used in Iranian and Persian music. The other accidental covers accidentals other than those listed here. It is usually used in combination with the smufl attribute to specify a particular SMuFL accidental. The smufl attribute may be used with any accidental value to help specify the appearance of symbols that share the same MusicXML semantics.

Instances

Instances details
Bounded AccidentalValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum AccidentalValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic AccidentalValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep AccidentalValue :: Type -> Type #

Show AccidentalValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml AccidentalValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq AccidentalValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord AccidentalValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep AccidentalValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep AccidentalValue = D1 ('MetaData "AccidentalValue" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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)) :+: (C1 ('MetaCons "AccidentalValueSharpDown" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AccidentalValueSharpUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AccidentalValueNaturalDown" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "AccidentalValueNaturalUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AccidentalValueFlatDown" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AccidentalValueFlatUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AccidentalValueDoubleSharpDown" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AccidentalValueDoubleSharpUp" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "AccidentalValueFlatFlatDown" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AccidentalValueFlatFlatUp" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AccidentalValueArrowDown" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AccidentalValueArrowUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AccidentalValueTripleSharp" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "AccidentalValueTripleFlat" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AccidentalValueSlashQuarterSharp" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AccidentalValueSlashSharp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AccidentalValueSlashFlat" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AccidentalValueDoubleSlashFlat" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "AccidentalValueSharp1" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AccidentalValueSharp2" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AccidentalValueSharp3" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AccidentalValueSharp5" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AccidentalValueFlat1" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "AccidentalValueFlat2" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AccidentalValueFlat3" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AccidentalValueFlat4" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "AccidentalValueSori" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AccidentalValueKoron" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AccidentalValueOther" '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. This type is not used if no dots are present.

Instances

Instances details
Bounded AccordionMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum AccordionMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic AccordionMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep AccordionMiddle :: Type -> Type #

Num AccordionMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Read AccordionMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Integral AccordionMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Real AccordionMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show AccordionMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml AccordionMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq AccordionMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord AccordionMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep AccordionMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep AccordionMiddle = D1 ('MetaData "AccordionMiddle" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded Actuate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum Actuate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic Actuate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Actuate :: Type -> Type #

Methods

from :: Actuate -> Rep Actuate x #

to :: Rep Actuate x -> Actuate #

Show Actuate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Actuate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Actuate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord Actuate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Actuate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Actuate = D1 ('MetaData "Actuate" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 ArrowDirection Source #

arrow-direction (simple)

The arrow-direction type represents the direction in which an arrow points, using Unicode arrow terminology.

Instances

Instances details
Bounded ArrowDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum ArrowDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic ArrowDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ArrowDirection :: Type -> Type #

Show ArrowDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ArrowDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ArrowDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord ArrowDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ArrowDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ArrowDirection = D1 ('MetaData "ArrowDirection" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (((C1 ('MetaCons "ArrowDirectionLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ArrowDirectionUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ArrowDirectionRight" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "ArrowDirectionDown" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ArrowDirectionNorthwest" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ArrowDirectionNortheast" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ArrowDirectionSoutheast" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ArrowDirectionSouthwest" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ArrowDirectionLeftRight" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ArrowDirectionUpDown" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ArrowDirectionNorthwestSoutheast" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ArrowDirectionNortheastSouthwest" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ArrowDirectionOther" 'PrefixI 'False) (U1 :: Type -> Type)))))

data ArrowStyle Source #

arrow-style (simple)

The arrow-style type represents the style of an arrow, using Unicode arrow terminology. Filled and hollow arrows indicate polygonal single arrows. Paired arrows are duplicate single arrows in the same direction. Combined arrows apply to double direction arrows like left right, indicating that an arrow in one direction should be combined with an arrow in the other direction.

Instances

Instances details
Bounded ArrowStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum ArrowStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic ArrowStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ArrowStyle :: Type -> Type #

Show ArrowStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ArrowStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ArrowStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord ArrowStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ArrowStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ArrowStyle = D1 ('MetaData "ArrowStyle" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) ((C1 ('MetaCons "ArrowStyleSingle" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ArrowStyleDouble" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ArrowStyleFilled" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ArrowStyleHollow" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ArrowStylePaired" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ArrowStyleCombined" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ArrowStyleOther" '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

Instances details
Bounded BackwardForward Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum BackwardForward Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic BackwardForward Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep BackwardForward :: Type -> Type #

Show BackwardForward Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml BackwardForward Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq BackwardForward Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord BackwardForward Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep BackwardForward Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep BackwardForward = D1 ('MetaData "BackwardForward" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded BarStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum BarStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic BarStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep BarStyle :: Type -> Type #

Methods

from :: BarStyle -> Rep BarStyle x #

to :: Rep BarStyle x -> BarStyle #

Show BarStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml BarStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq BarStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord BarStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep BarStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep BarStyle = D1 ('MetaData "BarStyle" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 1024th 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

Instances details
Bounded BeamLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum BeamLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic BeamLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep BeamLevel :: Type -> Type #

Num BeamLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Read BeamLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Integral BeamLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Real BeamLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show BeamLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml BeamLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq BeamLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord BeamLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep BeamLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep BeamLevel = D1 ('MetaData "BeamLevel" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 8 beam levels (up to 1024th notes) available for each note.

Instances

Instances details
Bounded BeamValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum BeamValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic BeamValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep BeamValue :: Type -> Type #

Show BeamValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml BeamValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq BeamValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord BeamValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep BeamValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep BeamValue = D1 ('MetaData "BeamValue" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 BeaterValue Source #

beater-value (simple)

The beater-value type represents pictograms for beaters, mallets, and sticks that do not have different materials represented in the pictogram. The finger and hammer values are in addition to Stone's list.

Instances

Instances details
Bounded BeaterValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum BeaterValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic BeaterValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep BeaterValue :: Type -> Type #

Show BeaterValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml BeaterValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq BeaterValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord BeaterValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep BeaterValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep BeaterValue = D1 ('MetaData "BeaterValue" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) ((((C1 ('MetaCons "BeaterValueBow" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BeaterValueChimeHammer" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BeaterValueCoin" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BeaterValueDrumStick" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BeaterValueFinger" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "BeaterValueFingernail" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BeaterValueFist" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BeaterValueGuiroScraper" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BeaterValueHammer" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BeaterValueHand" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "BeaterValueJazzStick" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BeaterValueKnittingNeedle" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BeaterValueMetalHammer" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BeaterValueSlideBrushOnGong" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BeaterValueSnareStick" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "BeaterValueSpoonMallet" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BeaterValueSuperball" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BeaterValueTriangleBeater" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BeaterValueTriangleBeaterPlain" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BeaterValueWireBrush" 'PrefixI 'False) (U1 :: Type -> Type))))))

data BreathMarkValue Source #

breath-mark-value (simple)

The breath-mark-value type represents the symbol used for a breath mark.

Instances

Instances details
Bounded BreathMarkValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum BreathMarkValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic BreathMarkValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep BreathMarkValue :: Type -> Type #

Show BreathMarkValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml BreathMarkValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq BreathMarkValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord BreathMarkValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep BreathMarkValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep BreathMarkValue = D1 ('MetaData "BreathMarkValue" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) ((C1 ('MetaCons "BreathMarkValue" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BreathMarkValueComma" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BreathMarkValueTick" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BreathMarkValueUpbow" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BreathMarkValueSalzedo" 'PrefixI 'False) (U1 :: Type -> Type))))

data CaesuraValue Source #

caesura-value (simple)

The caesura-value type represents the shape of the caesura sign.

Instances

Instances details
Bounded CaesuraValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum CaesuraValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic CaesuraValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep CaesuraValue :: Type -> Type #

Show CaesuraValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml CaesuraValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq CaesuraValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord CaesuraValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep CaesuraValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep CaesuraValue = D1 ('MetaData "CaesuraValue" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) ((C1 ('MetaCons "CaesuraValueNormal" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CaesuraValueThick" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CaesuraValueShort" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "CaesuraValueCurved" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CaesuraValueSingle" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CaesuraValue" 'PrefixI 'False) (U1 :: Type -> Type))))

data CancelLocation Source #

cancel-location (simple)

The cancel-location type is used to indicate where a key signature cancellation appears relative to a new key signature: to the left, to the right, or before the barline and to the left. It is left by default. For mid-measure key elements, a cancel-location of before-barline should be treated like a cancel-location of left.

Instances

Instances details
Bounded CancelLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum CancelLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic CancelLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep CancelLocation :: Type -> Type #

Show CancelLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml CancelLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq CancelLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord CancelLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep CancelLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep CancelLocation = D1 ('MetaData "CancelLocation" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "CancelLocationLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CancelLocationRight" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CancelLocationBeforeBarline" 'PrefixI 'False) (U1 :: Type -> Type)))

data CircularArrow Source #

circular-arrow (simple)

The circular-arrow type represents the direction in which a circular arrow points, using Unicode arrow terminology.

Constructors

CircularArrowClockwise

clockwise

CircularArrowAnticlockwise

anticlockwise

Instances

Instances details
Bounded CircularArrow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum CircularArrow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic CircularArrow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep CircularArrow :: Type -> Type #

Show CircularArrow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml CircularArrow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq CircularArrow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord CircularArrow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep CircularArrow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep CircularArrow = D1 ('MetaData "CircularArrow" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "CircularArrowClockwise" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CircularArrowAnticlockwise" 'PrefixI 'False) (U1 :: Type -> Type))

data ClefSign Source #

clef-sign (simple)

The clef-sign element represents the different clef symbols. The jianpu sign indicates that the music that follows should be in jianpu numbered notation, just as the TAB sign indicates that the music that follows should be in tablature notation. Unlike TAB, a jianpu sign does not correspond to a visual clef notation.

Instances

Instances details
Bounded ClefSign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum ClefSign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic ClefSign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ClefSign :: Type -> Type #

Methods

from :: ClefSign -> Rep ClefSign x #

to :: Rep ClefSign x -> ClefSign #

Show ClefSign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ClefSign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ClefSign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord ClefSign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ClefSign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ClefSign = D1 ('MetaData "ClefSign" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 "ClefSignJianpu" '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 "#800080" represents purple. An ARGB value of "#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

Instances details
IsString Color Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

fromString :: String -> Color #

Generic Color Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Color :: Type -> Type #

Methods

from :: Color -> Rep Color x #

to :: Rep Color x -> Color #

Read Color Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show Color Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

EmitXml Color Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Color -> XmlRep Source #

Eq Color Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord Color Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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 #

type Rep Color Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Color = D1 ('MetaData "Color" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
IsString CommaSeparatedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic CommaSeparatedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep CommaSeparatedText :: Type -> Type #

Read CommaSeparatedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show CommaSeparatedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml CommaSeparatedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq CommaSeparatedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord CommaSeparatedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep CommaSeparatedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep CommaSeparatedText = D1 ('MetaData "CommaSeparatedText" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded CssFontSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum CssFontSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic CssFontSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep CssFontSize :: Type -> Type #

Show CssFontSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml CssFontSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq CssFontSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord CssFontSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep CssFontSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep CssFontSize = D1 ('MetaData "CssFontSize" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 DegreeSymbolValue Source #

degree-symbol-value (simple)

The degree-symbol-value type indicates indicates that a symbol should be used in specifying the degree.

Instances

Instances details
Bounded DegreeSymbolValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum DegreeSymbolValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic DegreeSymbolValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep DegreeSymbolValue :: Type -> Type #

Show DegreeSymbolValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml DegreeSymbolValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq DegreeSymbolValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord DegreeSymbolValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep DegreeSymbolValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep DegreeSymbolValue = D1 ('MetaData "DegreeSymbolValue" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) ((C1 ('MetaCons "DegreeSymbolValueMajor" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DegreeSymbolValueMinor" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DegreeSymbolValueAugmented" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DegreeSymbolValueDiminished" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DegreeSymbolValueHalfDiminished" '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

Instances details
Bounded DegreeTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum DegreeTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic DegreeTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep DegreeTypeValue :: Type -> Type #

Show DegreeTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml DegreeTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq DegreeTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord DegreeTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep DegreeTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep DegreeTypeValue = D1 ('MetaData "DegreeTypeValue" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 DistanceType Source #

distance-type (simple)

The distance-type defines what type of distance is being defined in a distance element. Values include beam and hyphen. 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

DistanceType 

Fields

Instances

Instances details
IsString DistanceType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic DistanceType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep DistanceType :: Type -> Type #

Read DistanceType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show DistanceType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml DistanceType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq DistanceType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord DistanceType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep DistanceType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep DistanceType = D1 ('MetaData "DistanceType" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'True) (C1 ('MetaCons "DistanceType" 'PrefixI 'True) (S1 ('MetaSel ('Just "distanceType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Token)))

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

Instances details
Generic Divisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Divisions :: Type -> Type #

Num Divisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Read Divisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Fractional Divisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Real Divisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

RealFrac Divisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show Divisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Divisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Divisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord Divisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Divisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Divisions = D1 ('MetaData "Divisions" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'True) (C1 ('MetaCons "Divisions" 'PrefixI 'True) (S1 ('MetaSel ('Just "divisions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Decimal)))

data Effect Source #

effect (simple)

The effect type represents pictograms for sound effect percussion instruments. The cannon, lotus flute, and megaphone values are in addition to Stone's list.

Constructors

EffectAnvil

anvil

EffectAutoHorn

auto horn

EffectBirdWhistle

bird whistle

EffectCannon

cannon

EffectDuckCall

duck call

EffectGunShot

gun shot

EffectKlaxonHorn

klaxon horn

EffectLionsRoar

lions roar

EffectLotusFlute

lotus flute

EffectMegaphone

megaphone

EffectPoliceWhistle

police whistle

EffectSiren

siren

EffectSlideWhistle

slide whistle

EffectThunderSheet

thunder sheet

EffectWindMachine

wind machine

EffectWindWhistle

wind whistle

Instances

Instances details
Bounded Effect Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum Effect Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic Effect Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Effect :: Type -> Type #

Methods

from :: Effect -> Rep Effect x #

to :: Rep Effect x -> Effect #

Show Effect Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Effect Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Effect Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord Effect Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Effect Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Effect = D1 ('MetaData "Effect" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) ((((C1 ('MetaCons "EffectAnvil" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EffectAutoHorn" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EffectBirdWhistle" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EffectCannon" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "EffectDuckCall" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EffectGunShot" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EffectKlaxonHorn" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EffectLionsRoar" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "EffectLotusFlute" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EffectMegaphone" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EffectPoliceWhistle" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EffectSiren" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "EffectSlideWhistle" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EffectThunderSheet" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EffectWindMachine" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EffectWindWhistle" 'PrefixI 'False) (U1 :: Type -> Type)))))

data EnclosureShape Source #

enclosure-shape (simple)

The enclosure-shape type describes the shape and presence / absence of an enclosure around text or symbols. A bracket enclosure is similar to a rectangle with the bottom line missing, as is common in jazz notation.

Instances

Instances details
Bounded EnclosureShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum EnclosureShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic EnclosureShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep EnclosureShape :: Type -> Type #

Show EnclosureShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml EnclosureShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq EnclosureShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord EnclosureShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep EnclosureShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep EnclosureShape = D1 ('MetaData "EnclosureShape" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (((C1 ('MetaCons "EnclosureShapeRectangle" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EnclosureShapeSquare" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EnclosureShapeOval" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "EnclosureShapeCircle" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EnclosureShapeBracket" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EnclosureShapeTriangle" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EnclosureShapeDiamond" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "EnclosureShapePentagon" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EnclosureShapeHexagon" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EnclosureShapeHeptagon" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "EnclosureShapeOctagon" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EnclosureShapeNonagon" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EnclosureShapeDecagon" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EnclosureShapeNone" '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

Instances details
IsString EndingNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic EndingNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep EndingNumber :: Type -> Type #

Read EndingNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show EndingNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml EndingNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq EndingNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord EndingNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep EndingNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep EndingNumber = D1 ('MetaData "EndingNumber" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded Fan Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

minBound :: Fan #

maxBound :: Fan #

Enum Fan Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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] #

Generic Fan Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Fan :: Type -> Type #

Methods

from :: Fan -> Rep Fan x #

to :: Rep Fan x -> Fan #

Show Fan Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Fan -> ShowS #

show :: Fan -> String #

showList :: [Fan] -> ShowS #

EmitXml Fan Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Fan -> XmlRep Source #

Eq Fan Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord Fan Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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 #

type Rep Fan Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Fan = D1 ('MetaData "Fan" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded FermataShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum FermataShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic FermataShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep FermataShape :: Type -> Type #

Show FermataShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml FermataShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq FermataShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord FermataShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep FermataShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep FermataShape = D1 ('MetaData "FermataShape" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 "FermataShapeDoubleAngled" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "FermataShapeDoubleSquare" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FermataShapeDoubleDot" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FermataShapeHalfCurve" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FermataShapeCurlew" '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

Instances details
Bounded Fifths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum Fifths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic Fifths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Fifths :: Type -> Type #

Methods

from :: Fifths -> Rep Fifths x #

to :: Rep Fifths x -> Fifths #

Num Fifths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Read Fifths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Integral Fifths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Real Fifths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show Fifths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Fifths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Fifths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord Fifths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Fifths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Fifths = D1 ('MetaData "Fifths" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic FontSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep FontSize :: Type -> Type #

Methods

from :: FontSize -> Rep FontSize x #

to :: Rep FontSize x -> FontSize #

Show FontSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml FontSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq FontSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep FontSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep FontSize = D1 ('MetaData "FontSize" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded FontStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum FontStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic FontStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep FontStyle :: Type -> Type #

Show FontStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml FontStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq FontStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord FontStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep FontStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep FontStyle = D1 ('MetaData "FontStyle" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded FontWeight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum FontWeight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic FontWeight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep FontWeight :: Type -> Type #

Show FontWeight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml FontWeight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq FontWeight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord FontWeight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep FontWeight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep FontWeight = D1 ('MetaData "FontWeight" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "FontWeightNormal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FontWeightBold" 'PrefixI 'False) (U1 :: Type -> Type))

data GlassValue Source #

glass-value (simple)

The glass-value type represents pictograms for glass percussion instruments.

Constructors

GlassValueGlassHarmonica

glass harmonica

GlassValueGlassHarp

glass harp

GlassValueWindChimes

wind chimes

Instances

Instances details
Bounded GlassValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum GlassValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic GlassValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep GlassValue :: Type -> Type #

Show GlassValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml GlassValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq GlassValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord GlassValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep GlassValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep GlassValue = D1 ('MetaData "GlassValue" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "GlassValueGlassHarmonica" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GlassValueGlassHarp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GlassValueWindChimes" 'PrefixI 'False) (U1 :: Type -> Type)))

newtype GlyphType Source #

glyph-type (simple)

The glyph-type defines what type of glyph is being defined in a glyph element. Values include quarter-rest, g-clef-ottava-bassa, c-clef, f-clef, percussion-clef, octave-shift-up-8, octave-shift-down-8, octave-shift-continue-8, octave-shift-down-15, octave-shift-up-15, octave-shift-continue-15, octave-shift-down-22, octave-shift-up-22, and octave-shift-continue-22. 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.

A quarter-rest type specifies the glyph to use when a note has a rest element and a type value of quarter. The c-clef, f-clef, and percussion-clef types specify the glyph to use when a clef sign element value is C, F, or percussion respectively. The g-clef-ottava-bassa type specifies the glyph to use when a clef sign element value is G and the clef-octave-change element value is -1. The octave-shift types specify the glyph to use when an octave-shift type attribute value is up, down, or continue and the octave-shift size attribute value is 8, 15, or 22.

Constructors

GlyphType 

Fields

Instances

Instances details
IsString GlyphType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic GlyphType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep GlyphType :: Type -> Type #

Read GlyphType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show GlyphType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml GlyphType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq GlyphType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord GlyphType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep GlyphType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep GlyphType = D1 ('MetaData "GlyphType" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'True) (C1 ('MetaCons "GlyphType" 'PrefixI 'True) (S1 ('MetaSel ('Just "glyphType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Token)))

data GroupBarlineValue Source #

group-barline-value (simple)

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

Instances

Instances details
Bounded GroupBarlineValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum GroupBarlineValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic GroupBarlineValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep GroupBarlineValue :: Type -> Type #

Show GroupBarlineValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml GroupBarlineValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq GroupBarlineValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord GroupBarlineValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep GroupBarlineValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep GroupBarlineValue = D1 ('MetaData "GroupBarlineValue" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded GroupSymbolValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum GroupSymbolValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic GroupSymbolValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep GroupSymbolValue :: Type -> Type #

Show GroupSymbolValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml GroupSymbolValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq GroupSymbolValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord GroupSymbolValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep GroupSymbolValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep GroupSymbolValue = D1 ('MetaData "GroupSymbolValue" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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) :+: C1 ('MetaCons "GroupSymbolValueSquare" 'PrefixI 'False) (U1 :: Type -> Type))))

data HandbellValue Source #

handbell-value (simple)

The handbell-value type represents the type of handbell technique being notated.

Instances

Instances details
Bounded HandbellValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum HandbellValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic HandbellValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep HandbellValue :: Type -> Type #

Show HandbellValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml HandbellValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq HandbellValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord HandbellValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep HandbellValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep HandbellValue = D1 ('MetaData "HandbellValue" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (((C1 ('MetaCons "HandbellValueBelltree" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HandbellValueDamp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HandbellValueEcho" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "HandbellValueGyro" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HandbellValueHandMartellato" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HandbellValueMalletLift" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "HandbellValueMalletTable" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HandbellValueMartellato" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HandbellValueMartellatoLift" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "HandbellValueMutedMartellato" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HandbellValuePluckLift" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HandbellValueSwing" 'PrefixI 'False) (U1 :: Type -> Type)))))

data HarmonClosedLocation Source #

harmon-closed-location (simple)

The harmon-closed-location type indicates which portion of the symbol is filled in when the corresponding harmon-closed-value is half.

Instances

Instances details
Bounded HarmonClosedLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum HarmonClosedLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic HarmonClosedLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep HarmonClosedLocation :: Type -> Type #

Show HarmonClosedLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml HarmonClosedLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq HarmonClosedLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord HarmonClosedLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep HarmonClosedLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep HarmonClosedLocation = D1 ('MetaData "HarmonClosedLocation" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) ((C1 ('MetaCons "HarmonClosedLocationRight" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HarmonClosedLocationBottom" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HarmonClosedLocationLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HarmonClosedLocationTop" 'PrefixI 'False) (U1 :: Type -> Type)))

data HarmonClosedValue Source #

harmon-closed-value (simple)

The harmon-closed-value type represents whether the harmon mute is closed, open, or half-open.

Instances

Instances details
Bounded HarmonClosedValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum HarmonClosedValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic HarmonClosedValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep HarmonClosedValue :: Type -> Type #

Show HarmonClosedValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml HarmonClosedValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq HarmonClosedValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord HarmonClosedValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep HarmonClosedValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep HarmonClosedValue = D1 ('MetaData "HarmonClosedValue" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "HarmonClosedValueYes" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HarmonClosedValueNo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HarmonClosedValueHalf" '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

Instances details
Bounded HarmonyType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum HarmonyType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic HarmonyType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep HarmonyType :: Type -> Type #

Show HarmonyType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml HarmonyType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq HarmonyType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord HarmonyType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep HarmonyType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep HarmonyType = D1 ('MetaData "HarmonyType" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 HoleClosedLocation Source #

hole-closed-location (simple)

The hole-closed-location type indicates which portion of the hole is filled in when the corresponding hole-closed-value is half.

Instances

Instances details
Bounded HoleClosedLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum HoleClosedLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic HoleClosedLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep HoleClosedLocation :: Type -> Type #

Show HoleClosedLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml HoleClosedLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq HoleClosedLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord HoleClosedLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep HoleClosedLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep HoleClosedLocation = D1 ('MetaData "HoleClosedLocation" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) ((C1 ('MetaCons "HoleClosedLocationRight" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HoleClosedLocationBottom" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HoleClosedLocationLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HoleClosedLocationTop" 'PrefixI 'False) (U1 :: Type -> Type)))

data HoleClosedValue Source #

hole-closed-value (simple)

The hole-closed-value type represents whether the hole is closed, open, or half-open.

Instances

Instances details
Bounded HoleClosedValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum HoleClosedValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic HoleClosedValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep HoleClosedValue :: Type -> Type #

Show HoleClosedValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml HoleClosedValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq HoleClosedValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord HoleClosedValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep HoleClosedValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep HoleClosedValue = D1 ('MetaData "HoleClosedValue" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "HoleClosedValueYes" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HoleClosedValueNo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HoleClosedValueHalf" '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

Instances details
Bounded KindValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum KindValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic KindValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep KindValue :: Type -> Type #

Show KindValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml KindValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq KindValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord KindValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep KindValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep KindValue = D1 ('MetaData "KindValue" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic Lang Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Lang :: Type -> Type #

Methods

from :: Lang -> Rep Lang x #

to :: Rep Lang x -> Lang #

Show Lang Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Lang -> ShowS #

show :: Lang -> String #

showList :: [Lang] -> ShowS #

EmitXml Lang Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Lang -> XmlRep Source #

Eq Lang Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Lang Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Lang = D1 ('MetaData "Lang" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
IsString Language Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic Language Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Language :: Type -> Type #

Methods

from :: Language -> Rep Language x #

to :: Rep Language x -> Language #

Read Language Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show Language Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Language Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Language Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord Language Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Language Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Language = D1 ('MetaData "Language" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded LeftCenterRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum LeftCenterRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic LeftCenterRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep LeftCenterRight :: Type -> Type #

Show LeftCenterRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml LeftCenterRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq LeftCenterRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord LeftCenterRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep LeftCenterRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep LeftCenterRight = D1 ('MetaData "LeftCenterRight" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded LeftRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum LeftRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic LeftRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep LeftRight :: Type -> Type #

Show LeftRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml LeftRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq LeftRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord LeftRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep LeftRight Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep LeftRight = D1 ('MetaData "LeftRight" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded LineEnd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum LineEnd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic LineEnd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep LineEnd :: Type -> Type #

Methods

from :: LineEnd -> Rep LineEnd x #

to :: Rep LineEnd x -> LineEnd #

Show LineEnd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml LineEnd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq LineEnd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord LineEnd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep LineEnd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep LineEnd = D1 ('MetaData "LineEnd" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 LineLength Source #

line-length (simple)

The line-length type distinguishes between different line lengths for doit, falloff, plop, and scoop articulations.

Instances

Instances details
Bounded LineLength Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum LineLength Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic LineLength Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep LineLength :: Type -> Type #

Show LineLength Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml LineLength Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq LineLength Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord LineLength Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep LineLength Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep LineLength = D1 ('MetaData "LineLength" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "LineLengthShort" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LineLengthMedium" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LineLengthLong" '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

Instances details
Bounded LineShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum LineShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic LineShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep LineShape :: Type -> Type #

Show LineShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml LineShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq LineShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord LineShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep LineShape Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep LineShape = D1 ('MetaData "LineShape" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded LineType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum LineType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic LineType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep LineType :: Type -> Type #

Methods

from :: LineType -> Rep LineType x #

to :: Rep LineType x -> LineType #

Show LineType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml LineType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq LineType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord LineType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep LineType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep LineType = D1 ('MetaData "LineType" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
IsString LineWidthType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic LineWidthType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep LineWidthType :: Type -> Type #

Read LineWidthType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show LineWidthType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml LineWidthType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq LineWidthType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord LineWidthType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep LineWidthType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep LineWidthType = D1 ('MetaData "LineWidthType" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded MarginType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum MarginType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic MarginType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep MarginType :: Type -> Type #

Show MarginType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml MarginType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq MarginType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord MarginType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MarginType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MarginType = D1 ('MetaData "MarginType" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded MeasureNumberingValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum MeasureNumberingValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic MeasureNumberingValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep MeasureNumberingValue :: Type -> Type #

Show MeasureNumberingValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml MeasureNumberingValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq MeasureNumberingValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord MeasureNumberingValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MeasureNumberingValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MeasureNumberingValue = D1 ('MetaData "MeasureNumberingValue" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 MeasureText Source #

measure-text (simple)

The measure-text type is used for the text attribute of measure elements. It has at least one character. The implicit attribute of the measure element should be set to "yes" rather than setting the text attribute to an empty string.

Constructors

MeasureText 

Fields

Instances

Instances details
IsString MeasureText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic MeasureText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep MeasureText :: Type -> Type #

Read MeasureText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show MeasureText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml MeasureText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq MeasureText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord MeasureText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MeasureText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MeasureText = D1 ('MetaData "MeasureText" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'True) (C1 ('MetaCons "MeasureText" 'PrefixI 'True) (S1 ('MetaSel ('Just "measureText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Token)))

data Membrane Source #

membrane (simple)

The membrane type represents pictograms for membrane percussion instruments.

Instances

Instances details
Bounded Membrane Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum Membrane Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic Membrane Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Membrane :: Type -> Type #

Methods

from :: Membrane -> Rep Membrane x #

to :: Rep Membrane x -> Membrane #

Show Membrane Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Membrane Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Membrane Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord Membrane Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Membrane Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Membrane = D1 ('MetaData "Membrane" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) ((((C1 ('MetaCons "MembraneBassDrum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MembraneBassDrumOnSide" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MembraneBongos" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MembraneChineseTomtom" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "MembraneCongaDrum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MembraneCuica" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MembraneGobletDrum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MembraneIndoAmericanTomtom" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "MembraneJapaneseTomtom" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MembraneMilitaryDrum" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MembraneSnareDrum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MembraneSnareDrumSnaresOff" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "MembraneTabla" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MembraneTambourine" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MembraneTenorDrum" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MembraneTimbales" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MembraneTomtom" 'PrefixI 'False) (U1 :: Type -> Type))))))

data Metal Source #

metal (simple)

The metal type represents pictograms for metal percussion instruments. The hi-hat value refers to a pictogram like Stone's high-hat cymbals but without the long vertical line at the bottom.

Constructors

MetalAgogo

agogo

MetalAlmglocken

almglocken

MetalBell

bell

MetalBellPlate

bell plate

MetalBellTree

bell tree

MetalBrakeDrum

brake drum

MetalCencerro

cencerro

MetalChainRattle

chain rattle

MetalChineseCymbal

Chinese cymbal

MetalCowbell

cowbell

MetalCrashCymbals

crash cymbals

MetalCrotale

crotale

MetalCymbalTongs

cymbal tongs

MetalDomedGong

domed gong

MetalFingerCymbals

finger cymbals

MetalFlexatone

flexatone

MetalGong

gong

MetalHiHat

hi-hat

MetalHighHatCymbals

high-hat cymbals

MetalHandbell

handbell

MetalJawHarp

jaw harp

MetalJingleBells

jingle bells

MetalMusicalSaw

musical saw

MetalShellBells

shell bells

MetalSistrum

sistrum

MetalSizzleCymbal

sizzle cymbal

MetalSleighBells

sleigh bells

MetalSuspendedCymbal

suspended cymbal

MetalTamTam

tam tam

MetalTamTamWithBeater

tam tam with beater

MetalTriangle

triangle

MetalVietnameseHat

Vietnamese hat

Instances

Instances details
Bounded Metal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum Metal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic Metal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Metal :: Type -> Type #

Methods

from :: Metal -> Rep Metal x #

to :: Rep Metal x -> Metal #

Show Metal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Metal -> ShowS #

show :: Metal -> String #

showList :: [Metal] -> ShowS #

EmitXml Metal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Metal -> XmlRep Source #

Eq Metal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord Metal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

compare :: Metal -> Metal -> Ordering #

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

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

(>) :: Metal -> Metal -> Bool #

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

max :: Metal -> Metal -> Metal #

min :: Metal -> Metal -> Metal #

type Rep Metal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Metal = D1 ('MetaData "Metal" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (((((C1 ('MetaCons "MetalAgogo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MetalAlmglocken" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MetalBell" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MetalBellPlate" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "MetalBellTree" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MetalBrakeDrum" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MetalCencerro" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MetalChainRattle" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "MetalChineseCymbal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MetalCowbell" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MetalCrashCymbals" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MetalCrotale" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "MetalCymbalTongs" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MetalDomedGong" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MetalFingerCymbals" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MetalFlexatone" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "MetalGong" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MetalHiHat" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MetalHighHatCymbals" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MetalHandbell" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "MetalJawHarp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MetalJingleBells" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MetalMusicalSaw" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MetalShellBells" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "MetalSistrum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MetalSizzleCymbal" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MetalSleighBells" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MetalSuspendedCymbal" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "MetalTamTam" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MetalTamTamWithBeater" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MetalTriangle" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MetalVietnameseHat" '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

Instances details
Bounded Midi128 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum Midi128 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic Midi128 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Midi128 :: Type -> Type #

Methods

from :: Midi128 -> Rep Midi128 x #

to :: Rep Midi128 x -> Midi128 #

Num Midi128 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Read Midi128 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Integral Midi128 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Real Midi128 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show Midi128 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Midi128 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Midi128 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord Midi128 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Midi128 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Midi128 = D1 ('MetaData "Midi128" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded Midi16 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum Midi16 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic Midi16 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Midi16 :: Type -> Type #

Methods

from :: Midi16 -> Rep Midi16 x #

to :: Rep Midi16 x -> Midi16 #

Num Midi16 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Read Midi16 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Integral Midi16 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Real Midi16 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show Midi16 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Midi16 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Midi16 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord Midi16 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Midi16 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Midi16 = D1 ('MetaData "Midi16" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded Midi16384 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum Midi16384 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic Midi16384 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Midi16384 :: Type -> Type #

Num Midi16384 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Read Midi16384 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Integral Midi16384 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Real Midi16384 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show Midi16384 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Midi16384 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Midi16384 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord Midi16384 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Midi16384 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Midi16384 = D1 ('MetaData "Midi16384" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic Millimeters Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Millimeters :: Type -> Type #

Num Millimeters Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Read Millimeters Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Fractional Millimeters Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Real Millimeters Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

RealFrac Millimeters Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show Millimeters Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Millimeters Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Millimeters Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord Millimeters Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Millimeters Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Millimeters = D1 ('MetaData "Millimeters" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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, locrian, and none.

Constructors

Mode 

Fields

Instances

Instances details
IsString Mode Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

fromString :: String -> Mode #

Generic Mode Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Mode :: Type -> Type #

Methods

from :: Mode -> Rep Mode x #

to :: Rep Mode x -> Mode #

Read Mode Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show Mode Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Mode -> ShowS #

show :: Mode -> String #

showList :: [Mode] -> ShowS #

EmitXml Mode Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Mode -> XmlRep Source #

Eq Mode Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord Mode Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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 #

type Rep Mode Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Mode = D1 ('MetaData "Mode" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'True) (C1 ('MetaCons "Mode" 'PrefixI 'True) (S1 ('MetaSel ('Just "mode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

data Mute Source #

mute (simple)

The mute type represents muting for different instruments, including brass, winds, and strings. The on and off values are used for undifferentiated mutes. The remaining values represent specific mutes.

Constructors

MuteOn

on

MuteOff

off

MuteStraight

straight

MuteCup

cup

MuteHarmonNoStem

harmon-no-stem

MuteHarmonStem

harmon-stem

MuteBucket

bucket

MutePlunger

plunger

MuteHat

hat

MuteSolotone

solotone

MutePractice

practice

MuteStopMute

stop-mute

MuteStopHand

stop-hand

MuteEcho

echo

MutePalm

palm

Instances

Instances details
Bounded Mute Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum Mute Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

succ :: Mute -> Mute #

pred :: Mute -> Mute #

toEnum :: Int -> Mute #

fromEnum :: Mute -> Int #

enumFrom :: Mute -> [Mute] #

enumFromThen :: Mute -> Mute -> [Mute] #

enumFromTo :: Mute -> Mute -> [Mute] #

enumFromThenTo :: Mute -> Mute -> Mute -> [Mute] #

Generic Mute Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Mute :: Type -> Type #

Methods

from :: Mute -> Rep Mute x #

to :: Rep Mute x -> Mute #

Show Mute Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Mute -> ShowS #

show :: Mute -> String #

showList :: [Mute] -> ShowS #

EmitXml Mute Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Mute -> XmlRep Source #

Eq Mute Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord Mute Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

compare :: Mute -> Mute -> Ordering #

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

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

(>) :: Mute -> Mute -> Bool #

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

max :: Mute -> Mute -> Mute #

min :: Mute -> Mute -> Mute #

type Rep Mute Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Mute = D1 ('MetaData "Mute" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (((C1 ('MetaCons "MuteOn" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MuteOff" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MuteStraight" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "MuteCup" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MuteHarmonNoStem" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MuteHarmonStem" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MuteBucket" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "MutePlunger" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MuteHat" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MuteSolotone" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MutePractice" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "MuteStopMute" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MuteStopHand" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MuteEcho" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MutePalm" 'PrefixI 'False) (U1 :: Type -> Type)))))

newtype NonNegativeDecimal Source #

non-negative-decimal (simple)

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

Instances

Instances details
Generic NonNegativeDecimal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep NonNegativeDecimal :: Type -> Type #

Num NonNegativeDecimal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Read NonNegativeDecimal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Fractional NonNegativeDecimal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Real NonNegativeDecimal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

RealFrac NonNegativeDecimal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show NonNegativeDecimal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml NonNegativeDecimal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq NonNegativeDecimal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord NonNegativeDecimal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NonNegativeDecimal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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

newtype NonNegativeInteger Source #

xs:nonNegativeInteger (simple)

Constructors

NonNegativeInteger 

Instances

Instances details
Bounded NonNegativeInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum NonNegativeInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic NonNegativeInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep NonNegativeInteger :: Type -> Type #

Num NonNegativeInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Read NonNegativeInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Integral NonNegativeInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Real NonNegativeInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show NonNegativeInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml NonNegativeInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq NonNegativeInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord NonNegativeInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NonNegativeInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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

newtype NormalizedString Source #

xs:normalizedString (simple)

Constructors

NormalizedString 

Instances

Instances details
IsString NormalizedString Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic NormalizedString Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep NormalizedString :: Type -> Type #

Read NormalizedString Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show NormalizedString Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml NormalizedString Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq NormalizedString Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord NormalizedString Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NormalizedString Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NormalizedString = D1 ('MetaData "NormalizedString" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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-cue type is used for notes of grace-cue size. The grace type is used for notes of cue size 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

Instances details
Bounded NoteSizeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum NoteSizeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic NoteSizeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep NoteSizeType :: Type -> Type #

Show NoteSizeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml NoteSizeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq NoteSizeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord NoteSizeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NoteSizeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NoteSizeType = D1 ('MetaData "NoteSizeType" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) ((C1 ('MetaCons "NoteSizeTypeCue" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoteSizeTypeGrace" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NoteSizeTypeGraceCue" '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 1024th (shortest) to maxima (longest).

Instances

Instances details
Bounded NoteTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum NoteTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic NoteTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep NoteTypeValue :: Type -> Type #

Show NoteTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml NoteTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq NoteTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord NoteTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NoteTypeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NoteTypeValue = D1 ('MetaData "NoteTypeValue" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (((C1 ('MetaCons "NoteTypeValue1024th" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NoteTypeValue512th" 'PrefixI 'False) (U1 :: Type -> Type) :+: 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) :+: C1 ('MetaCons "NoteTypeValueMaxima" 'PrefixI 'False) (U1 :: Type -> Type)))))

data NoteheadValue Source #

notehead-value (simple)

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

The values do, re, mi, fa, fa up, so, la, and ti correspond to Aikin's 7-shape system. The fa up shape is typically used with upstems; the fa shape is typically used with downstems or no stems.

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. The left triangle shape is a right triangle with the hypotenuse facing up and to the left.

The other notehead covers noteheads other than those listed here. It is usually used in combination with the smufl attribute to specify a particular SMuFL notehead. The smufl attribute may be used with any notehead value to help specify the appearance of symbols that share the same MusicXML semantics. Noteheads in the SMuFL "Note name noteheads" range (U+E150–U+E1AF) should not use the smufl attribute or the "other" value, but instead use the notehead-text element.

Instances

Instances details
Bounded NoteheadValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum NoteheadValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic NoteheadValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep NoteheadValue :: Type -> Type #

Show NoteheadValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml NoteheadValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq NoteheadValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord NoteheadValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NoteheadValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NoteheadValue = D1 ('MetaData "NoteheadValue" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 "NoteheadValueCircled" '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 "NoteheadValueCircleDot" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoteheadValueLeftTriangle" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "NoteheadValueRectangle" '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 "NoteheadValueFaUp" '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) :+: C1 ('MetaCons "NoteheadValueOther" '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 document order. When a number-level value is optional, the value is 1 by default.

Constructors

NumberLevel 

Instances

Instances details
Bounded NumberLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum NumberLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic NumberLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep NumberLevel :: Type -> Type #

Num NumberLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Read NumberLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Integral NumberLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Real NumberLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show NumberLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml NumberLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq NumberLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord NumberLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NumberLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NumberLevel = D1 ('MetaData "NumberLevel" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded NumberOfLines Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum NumberOfLines Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic NumberOfLines Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep NumberOfLines :: Type -> Type #

Num NumberOfLines Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Read NumberOfLines Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Integral NumberOfLines Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Real NumberOfLines Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show NumberOfLines Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml NumberOfLines Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq NumberOfLines Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord NumberOfLines Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NumberOfLines Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NumberOfLines = D1 ('MetaData "NumberOfLines" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic NumberOrNormal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep NumberOrNormal :: Type -> Type #

Show NumberOrNormal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml NumberOrNormal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq NumberOrNormal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NumberOrNormal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NumberOrNormal = D1 ('MetaData "NumberOrNormal" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded Octave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum Octave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic Octave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Octave :: Type -> Type #

Methods

from :: Octave -> Rep Octave x #

to :: Rep Octave x -> Octave #

Num Octave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Read Octave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Integral Octave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Real Octave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show Octave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Octave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Octave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord Octave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Octave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Octave = D1 ('MetaData "Octave" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'True) (C1 ('MetaCons "Octave" 'PrefixI 'True) (S1 ('MetaSel ('Just "octave") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

data OnOff Source #

on-off (simple)

The on-off type is used for notation elements such as string mutes.

Constructors

OnOffOn

on

OnOffOff

off

Instances

Instances details
Bounded OnOff Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum OnOff Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic OnOff Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep OnOff :: Type -> Type #

Methods

from :: OnOff -> Rep OnOff x #

to :: Rep OnOff x -> OnOff #

Show OnOff Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> OnOff -> ShowS #

show :: OnOff -> String #

showList :: [OnOff] -> ShowS #

EmitXml OnOff Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: OnOff -> XmlRep Source #

Eq OnOff Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord OnOff Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

compare :: OnOff -> OnOff -> Ordering #

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

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

(>) :: OnOff -> OnOff -> Bool #

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

max :: OnOff -> OnOff -> OnOff #

min :: OnOff -> OnOff -> OnOff #

type Rep OnOff Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep OnOff = D1 ('MetaData "OnOff" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "OnOffOn" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OnOffOff" 'PrefixI 'False) (U1 :: Type -> Type))

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

Instances details
Bounded OverUnder Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum OverUnder Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic OverUnder Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep OverUnder :: Type -> Type #

Show OverUnder Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml OverUnder Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq OverUnder Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord OverUnder Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep OverUnder Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep OverUnder = D1 ('MetaData "OverUnder" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "OverUnderOver" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OverUnderUnder" 'PrefixI 'False) (U1 :: Type -> Type))

data PedalType Source #

pedal-type (simple)

The pedal-type simple type is used to distinguish types of pedal directions. The start value indicates the start of a damper pedal, while the sostenuto value indicates the start of a sostenuto pedal. The change, continue, and stop values can be used with either the damper or sostenuto pedal. The soft pedal is not included here because there is no special symbol or graphic used for it beyond what can be specified with words and bracket elements.

Instances

Instances details
Bounded PedalType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum PedalType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic PedalType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep PedalType :: Type -> Type #

Show PedalType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml PedalType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq PedalType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord PedalType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PedalType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PedalType = D1 ('MetaData "PedalType" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) ((C1 ('MetaCons "PedalTypeStart" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PedalTypeStop" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PedalTypeSostenuto" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PedalTypeChange" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PedalTypeContinue" 'PrefixI 'False) (U1 :: Type -> Type))))

newtype Percent Source #

percent (simple)

The percent type specifies a percentage from 0 to 100.

Constructors

Percent 

Fields

Instances

Instances details
Generic Percent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Percent :: Type -> Type #

Methods

from :: Percent -> Rep Percent x #

to :: Rep Percent x -> Percent #

Num Percent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Read Percent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Fractional Percent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Real Percent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

RealFrac Percent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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.MusicXml31

EmitXml Percent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Percent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord Percent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Percent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Percent = D1 ('MetaData "Percent" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'True) (C1 ('MetaCons "Percent" 'PrefixI 'True) (S1 ('MetaSel ('Just "percent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Decimal)))

data PitchedValue Source #

pitched-value (simple)

The pitched-value type represents pictograms for pitched percussion instruments. The chimes and tubular chimes values distinguish the single-line and double-line versions of the pictogram.

Instances

Instances details
Bounded PitchedValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum PitchedValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic PitchedValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep PitchedValue :: Type -> Type #

Show PitchedValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml PitchedValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq PitchedValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord PitchedValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PitchedValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PitchedValue = D1 ('MetaData "PitchedValue" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (((C1 ('MetaCons "PitchedValueCelesta" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PitchedValueChimes" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PitchedValueGlockenspiel" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PitchedValueLithophone" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PitchedValueMallet" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "PitchedValueMarimba" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PitchedValueSteelDrums" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PitchedValueTubaphone" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "PitchedValueTubularChimes" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PitchedValueVibraphone" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PitchedValueXylophone" 'PrefixI 'False) (U1 :: Type -> Type)))))

newtype PositiveDivisions Source #

positive-divisions (simple)

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

Instances

Instances details
Generic PositiveDivisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep PositiveDivisions :: Type -> Type #

Num PositiveDivisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Read PositiveDivisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Fractional PositiveDivisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Real PositiveDivisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

RealFrac PositiveDivisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show PositiveDivisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml PositiveDivisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq PositiveDivisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord PositiveDivisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PositiveDivisions Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PositiveDivisions = D1 ('MetaData "PositiveDivisions" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic PositiveIntegerOrEmpty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep PositiveIntegerOrEmpty :: Type -> Type #

Show PositiveIntegerOrEmpty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml PositiveIntegerOrEmpty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq PositiveIntegerOrEmpty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PositiveIntegerOrEmpty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PositiveIntegerOrEmpty = D1 ('MetaData "PositiveIntegerOrEmpty" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded PositiveInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum PositiveInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic PositiveInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep PositiveInteger :: Type -> Type #

Num PositiveInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Read PositiveInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Integral PositiveInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Real PositiveInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show PositiveInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml PositiveInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq PositiveInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord PositiveInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PositiveInteger Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PositiveInteger = D1 ('MetaData "PositiveInteger" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'True) (C1 ('MetaCons "PositiveInteger" 'PrefixI 'True) (S1 ('MetaSel ('Just "positiveInteger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NonNegativeInteger)))

data PrincipalVoiceSymbol Source #

principal-voice-symbol (simple)

The principal-voice-symbol type represents the type of symbol used to indicate the start of a principal or secondary voice. The "plain" value represents a plain square bracket. The value of "none" is used for analysis markup when the principal-voice element does not have a corresponding appearance in the score.

Instances

Instances details
Bounded PrincipalVoiceSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum PrincipalVoiceSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic PrincipalVoiceSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep PrincipalVoiceSymbol :: Type -> Type #

Show PrincipalVoiceSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml PrincipalVoiceSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq PrincipalVoiceSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord PrincipalVoiceSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PrincipalVoiceSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PrincipalVoiceSymbol = D1 ('MetaData "PrincipalVoiceSymbol" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) ((C1 ('MetaCons "PrincipalVoiceSymbolHauptstimme" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrincipalVoiceSymbolNebenstimme" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PrincipalVoiceSymbolPlain" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrincipalVoiceSymbolNone" 'PrefixI 'False) (U1 :: Type -> Type)))

data RightLeftMiddle Source #

right-left-middle (simple)

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

Instances

Instances details
Bounded RightLeftMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum RightLeftMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic RightLeftMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep RightLeftMiddle :: Type -> Type #

Show RightLeftMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml RightLeftMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq RightLeftMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord RightLeftMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep RightLeftMiddle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep RightLeftMiddle = D1 ('MetaData "RightLeftMiddle" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic RotationDegrees Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep RotationDegrees :: Type -> Type #

Num RotationDegrees Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Read RotationDegrees Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Fractional RotationDegrees Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Real RotationDegrees Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

RealFrac RotationDegrees Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show RotationDegrees Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml RotationDegrees Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq RotationDegrees Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord RotationDegrees Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep RotationDegrees Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep RotationDegrees = D1 ('MetaData "RotationDegrees" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'True) (C1 ('MetaCons "RotationDegrees" 'PrefixI 'True) (S1 ('MetaSel ('Just "rotationDegrees") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Decimal)))

data SemiPitched Source #

semi-pitched (simple)

The semi-pitched type represents categories of indefinite pitch for percussion instruments.

Instances

Instances details
Bounded SemiPitched Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum SemiPitched Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic SemiPitched Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep SemiPitched :: Type -> Type #

Show SemiPitched Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml SemiPitched Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq SemiPitched Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord SemiPitched Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SemiPitched Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SemiPitched = D1 ('MetaData "SemiPitched" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) ((C1 ('MetaCons "SemiPitchedHigh" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SemiPitchedMediumHigh" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SemiPitchedMedium" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "SemiPitchedMediumLow" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SemiPitchedLow" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SemiPitchedVeryLow" 'PrefixI 'False) (U1 :: Type -> Type))))

newtype Semitones Source #

semitones (simple)

The semitones 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) are used for microtones.

Constructors

Semitones 

Fields

Instances

Instances details
Generic Semitones Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Semitones :: Type -> Type #

Num Semitones Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Read Semitones Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Fractional Semitones Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Real Semitones Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

RealFrac Semitones Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show Semitones Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Semitones Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Semitones Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord Semitones Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Semitones Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Semitones = D1 ('MetaData "Semitones" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded SmpShow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum SmpShow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic SmpShow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep SmpShow :: Type -> Type #

Methods

from :: SmpShow -> Rep SmpShow x #

to :: Rep SmpShow x -> SmpShow #

Show SmpShow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml SmpShow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq SmpShow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord SmpShow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SmpShow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SmpShow = D1 ('MetaData "SmpShow" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded ShowFrets Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum ShowFrets Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic ShowFrets Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ShowFrets :: Type -> Type #

Show ShowFrets Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ShowFrets Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ShowFrets Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord ShowFrets Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ShowFrets Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ShowFrets = D1 ('MetaData "ShowFrets" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded ShowTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum ShowTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic ShowTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ShowTuplet :: Type -> Type #

Show ShowTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ShowTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ShowTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord ShowTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ShowTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ShowTuplet = D1 ('MetaData "ShowTuplet" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 SmuflAccidentalGlyphName Source #

smufl-accidental-glyph-name (simple)

The smufl-accidental-glyph-name type is used to reference a specific Standard Music Font Layout (SMuFL) accidental character. The value is a SMuFL canonical glyph name that starts with acc.

Instances

Instances details
IsString SmuflAccidentalGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic SmuflAccidentalGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep SmuflAccidentalGlyphName :: Type -> Type #

Read SmuflAccidentalGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show SmuflAccidentalGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml SmuflAccidentalGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq SmuflAccidentalGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord SmuflAccidentalGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SmuflAccidentalGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SmuflAccidentalGlyphName = D1 ('MetaData "SmuflAccidentalGlyphName" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'True) (C1 ('MetaCons "SmuflAccidentalGlyphName" 'PrefixI 'True) (S1 ('MetaSel ('Just "smuflAccidentalGlyphName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SmuflGlyphName)))

newtype SmuflCodaGlyphName Source #

smufl-coda-glyph-name (simple)

The smufl-coda-glyph-name type is used to reference a specific Standard Music Font Layout (SMuFL) coda character. The value is a SMuFL canonical glyph name that starts with coda.

Instances

Instances details
IsString SmuflCodaGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic SmuflCodaGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep SmuflCodaGlyphName :: Type -> Type #

Read SmuflCodaGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show SmuflCodaGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml SmuflCodaGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq SmuflCodaGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord SmuflCodaGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SmuflCodaGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SmuflCodaGlyphName = D1 ('MetaData "SmuflCodaGlyphName" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'True) (C1 ('MetaCons "SmuflCodaGlyphName" 'PrefixI 'True) (S1 ('MetaSel ('Just "smuflCodaGlyphName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SmuflGlyphName)))

newtype SmuflGlyphName Source #

smufl-glyph-name (simple)

The smufl-glyph-name type is used for attributes that reference a specific Standard Music Font Layout (SMuFL) character. The value is a SMuFL canonical glyph name, not a code point. For instance, the value for a standard piano pedal mark would be keyboardPedalPed, not U+E650.

Constructors

SmuflGlyphName 

Instances

Instances details
IsString SmuflGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic SmuflGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep SmuflGlyphName :: Type -> Type #

Read SmuflGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show SmuflGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml SmuflGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq SmuflGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord SmuflGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SmuflGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SmuflGlyphName = D1 ('MetaData "SmuflGlyphName" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'True) (C1 ('MetaCons "SmuflGlyphName" 'PrefixI 'True) (S1 ('MetaSel ('Just "smuflGlyphName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NMTOKEN)))

newtype SmuflLyricsGlyphName Source #

smufl-lyrics-glyph-name (simple)

The smufl-lyrics-glyph-name type is used to reference a specific Standard Music Font Layout (SMuFL) lyrics elision character. The value is a SMuFL canonical glyph name that starts with lyrics.

Instances

Instances details
IsString SmuflLyricsGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic SmuflLyricsGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep SmuflLyricsGlyphName :: Type -> Type #

Read SmuflLyricsGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show SmuflLyricsGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml SmuflLyricsGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq SmuflLyricsGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord SmuflLyricsGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SmuflLyricsGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SmuflLyricsGlyphName = D1 ('MetaData "SmuflLyricsGlyphName" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'True) (C1 ('MetaCons "SmuflLyricsGlyphName" 'PrefixI 'True) (S1 ('MetaSel ('Just "smuflLyricsGlyphName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SmuflGlyphName)))

newtype SmuflPictogramGlyphName Source #

smufl-pictogram-glyph-name (simple)

The smufl-pictogram-glyph-name type is used to reference a specific Standard Music Font Layout (SMuFL) percussion pictogram character. The value is a SMuFL canonical glyph name that starts with pict.

Instances

Instances details
IsString SmuflPictogramGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic SmuflPictogramGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep SmuflPictogramGlyphName :: Type -> Type #

Read SmuflPictogramGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show SmuflPictogramGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml SmuflPictogramGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq SmuflPictogramGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord SmuflPictogramGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SmuflPictogramGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SmuflPictogramGlyphName = D1 ('MetaData "SmuflPictogramGlyphName" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'True) (C1 ('MetaCons "SmuflPictogramGlyphName" 'PrefixI 'True) (S1 ('MetaSel ('Just "smuflPictogramGlyphName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SmuflGlyphName)))

newtype SmuflSegnoGlyphName Source #

smufl-segno-glyph-name (simple)

The smufl-segno-glyph-name type is used to reference a specific Standard Music Font Layout (SMuFL) segno character. The value is a SMuFL canonical glyph name that starts with segno.

Instances

Instances details
IsString SmuflSegnoGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic SmuflSegnoGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep SmuflSegnoGlyphName :: Type -> Type #

Read SmuflSegnoGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show SmuflSegnoGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml SmuflSegnoGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq SmuflSegnoGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord SmuflSegnoGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SmuflSegnoGlyphName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SmuflSegnoGlyphName = D1 ('MetaData "SmuflSegnoGlyphName" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'True) (C1 ('MetaCons "SmuflSegnoGlyphName" 'PrefixI 'True) (S1 ('MetaSel ('Just "smuflSegnoGlyphName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SmuflGlyphName)))

data Space Source #

xml:space (simple)

Constructors

SpaceDefault

default

SpacePreserve

preserve

Instances

Instances details
Bounded Space Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum Space Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic Space Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Space :: Type -> Type #

Methods

from :: Space -> Rep Space x #

to :: Rep Space x -> Space #

Show Space Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Space -> ShowS #

show :: Space -> String #

showList :: [Space] -> ShowS #

EmitXml Space Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Space -> XmlRep Source #

Eq Space Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord Space Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

compare :: Space -> Space -> Ordering #

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

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

(>) :: Space -> Space -> Bool #

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

max :: Space -> Space -> Space #

min :: Space -> Space -> Space #

type Rep Space Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Space = D1 ('MetaData "Space" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "SpaceDefault" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SpacePreserve" 'PrefixI 'False) (U1 :: Type -> Type))

data StaffDivideSymbol Source #

staff-divide-symbol (simple)

The staff-divide-symbol type is used for staff division symbols. The down, up, and up-down values correspond to SMuFL code points U+E00B, U+E00C, and U+E00D respectively.

Instances

Instances details
Bounded StaffDivideSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum StaffDivideSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic StaffDivideSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep StaffDivideSymbol :: Type -> Type #

Show StaffDivideSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml StaffDivideSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq StaffDivideSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord StaffDivideSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StaffDivideSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StaffDivideSymbol = D1 ('MetaData "StaffDivideSymbol" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "StaffDivideSymbolDown" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "StaffDivideSymbolUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StaffDivideSymbolUpDown" '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

Instances details
Bounded StaffLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum StaffLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic StaffLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep StaffLine :: Type -> Type #

Num StaffLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Read StaffLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Integral StaffLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Real StaffLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show StaffLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml StaffLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq StaffLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord StaffLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StaffLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StaffLine = D1 ('MetaData "StaffLine" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded StaffNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum StaffNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic StaffNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep StaffNumber :: Type -> Type #

Num StaffNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Read StaffNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Integral StaffNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Real StaffNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show StaffNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml StaffNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq StaffNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord StaffNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StaffNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StaffNumber = D1 ('MetaData "StaffNumber" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded StaffType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum StaffType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic StaffType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep StaffType :: Type -> Type #

Show StaffType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml StaffType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq StaffType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord StaffType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StaffType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StaffType = D1 ('MetaData "StaffType" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded StartNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum StartNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic StartNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep StartNote :: Type -> Type #

Show StartNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml StartNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq StartNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord StartNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StartNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StartNote = D1 ('MetaData "StartNote" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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.

The values of start and stop refer to how an element appears in musical score order, not in MusicXML document order. An element with a stop attribute may precede the corresponding element with a start attribute within a MusicXML document. This is particularly common in multi-staff music. For example, the stopping point for a tuplet may appear in staff 1 before the starting point for the tuplet appears in staff 2 later in the document.

Constructors

StartStopStart

start

StartStopStop

stop

Instances

Instances details
Bounded StartStop Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum StartStop Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic StartStop Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep StartStop :: Type -> Type #

Show StartStop Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml StartStop Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq StartStop Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord StartStop Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StartStop Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StartStop = D1 ('MetaData "StartStop" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "StartStopStart" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StartStopStop" '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 or for formatting of symbols across system breaks.

The values of start, stop, and continue refer to how an element appears in musical score order, not in MusicXML document order. An element with a stop attribute may precede the corresponding element with a start attribute within a MusicXML document. This is particularly common in multi-staff music. For example, the stopping point for a slur may appear in staff 1 before the starting point for the slur appears in staff 2 later in the document.

Instances

Instances details
Bounded StartStopContinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum StartStopContinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic StartStopContinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep StartStopContinue :: Type -> Type #

Show StartStopContinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml StartStopContinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq StartStopContinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord StartStopContinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StartStopContinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StartStopContinue = D1 ('MetaData "StartStopContinue" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded StartStopDiscontinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum StartStopDiscontinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic StartStopDiscontinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep StartStopDiscontinue :: Type -> Type #

Show StartStopDiscontinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml StartStopDiscontinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq StartStopDiscontinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord StartStopDiscontinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StartStopDiscontinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StartStopDiscontinue = D1 ('MetaData "StartStopDiscontinue" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 groupings.

Instances

Instances details
Bounded StartStopSingle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum StartStopSingle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic StartStopSingle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep StartStopSingle :: Type -> Type #

Show StartStopSingle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml StartStopSingle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq StartStopSingle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord StartStopSingle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StartStopSingle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StartStopSingle = D1 ('MetaData "StartStopSingle" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded StemValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum StemValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic StemValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep StemValue :: Type -> Type #

Show StemValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml StemValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq StemValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord StemValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StemValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StemValue = D1 ('MetaData "StemValue" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded Step Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum Step Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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] #

Generic Step Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Step :: Type -> Type #

Methods

from :: Step -> Rep Step x #

to :: Rep Step x -> Step #

Show Step Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Step -> ShowS #

show :: Step -> String #

showList :: [Step] -> ShowS #

EmitXml Step Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Step -> XmlRep Source #

Eq Step Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord Step Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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 #

type Rep Step Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Step = D1 ('MetaData "Step" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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))))

data StickLocation Source #

stick-location (simple)

The stick-location type represents pictograms for the location of sticks, beaters, or mallets on cymbals, gongs, drums, and other instruments.

Instances

Instances details
Bounded StickLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum StickLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic StickLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep StickLocation :: Type -> Type #

Show StickLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml StickLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq StickLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord StickLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StickLocation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StickLocation = D1 ('MetaData "StickLocation" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) ((C1 ('MetaCons "StickLocationCenter" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StickLocationRim" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "StickLocationCymbalBell" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StickLocationCymbalEdge" 'PrefixI 'False) (U1 :: Type -> Type)))

data StickMaterial Source #

stick-material (simple)

The stick-material type represents the material being displayed in a stick pictogram.

Instances

Instances details
Bounded StickMaterial Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum StickMaterial Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic StickMaterial Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep StickMaterial :: Type -> Type #

Show StickMaterial Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml StickMaterial Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq StickMaterial Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord StickMaterial Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StickMaterial Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StickMaterial = D1 ('MetaData "StickMaterial" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) ((C1 ('MetaCons "StickMaterialSoft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StickMaterialMedium" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "StickMaterialHard" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "StickMaterialShaded" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StickMaterialX" 'PrefixI 'False) (U1 :: Type -> Type))))

data StickType Source #

stick-type (simple)

The stick-type type represents the shape of pictograms where the material in the stick, mallet, or beater is represented in the pictogram.

Instances

Instances details
Bounded StickType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum StickType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic StickType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep StickType :: Type -> Type #

Show StickType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml StickType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq StickType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord StickType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StickType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StickType = D1 ('MetaData "StickType" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (((C1 ('MetaCons "StickTypeBassDrum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StickTypeDoubleBassDrum" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "StickTypeGlockenspiel" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "StickTypeGum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StickTypeHammer" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "StickTypeSuperball" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StickTypeTimpani" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "StickTypeWound" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "StickTypeXylophone" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StickTypeYarn" '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 full-length string.

Constructors

StringNumber 

Instances

Instances details
Bounded StringNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum StringNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic StringNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep StringNumber :: Type -> Type #

Num StringNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Read StringNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Integral StringNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Real StringNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show StringNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml StringNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq StringNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord StringNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StringNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StringNumber = D1 ('MetaData "StringNumber" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded Syllabic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum Syllabic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic Syllabic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Syllabic :: Type -> Type #

Methods

from :: Syllabic -> Rep Syllabic x #

to :: Rep Syllabic x -> Syllabic #

Show Syllabic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Syllabic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Syllabic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord Syllabic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Syllabic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Syllabic = D1 ('MetaData "Syllabic" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 distinguish between full, cue sized, grace cue sized, and oversized symbols.

Instances

Instances details
Bounded SymbolSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum SymbolSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic SymbolSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep SymbolSize :: Type -> Type #

Show SymbolSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml SymbolSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq SymbolSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord SymbolSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SymbolSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SymbolSize = D1 ('MetaData "SymbolSize" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) ((C1 ('MetaCons "SymbolSizeFull" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SymbolSizeCue" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SymbolSizeGraceCue" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SymbolSizeLarge" 'PrefixI 'False) (U1 :: Type -> Type)))

data TapHand Source #

tap-hand (simple)

The tap-hand type represents the symbol to use for a tap element. The left and right values refer to the SMuFL guitarLeftHandTapping and guitarRightHandTapping glyphs respectively.

Constructors

TapHandLeft

left

TapHandRight

right

Instances

Instances details
Bounded TapHand Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum TapHand Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic TapHand Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep TapHand :: Type -> Type #

Methods

from :: TapHand -> Rep TapHand x #

to :: Rep TapHand x -> TapHand #

Show TapHand Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml TapHand Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq TapHand Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord TapHand Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TapHand Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TapHand = D1 ('MetaData "TapHand" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "TapHandLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TapHandRight" '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

Instances details
Generic Tenths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Tenths :: Type -> Type #

Methods

from :: Tenths -> Rep Tenths x #

to :: Rep Tenths x -> Tenths #

Num Tenths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Read Tenths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Fractional Tenths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Real Tenths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

RealFrac Tenths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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.MusicXml31

EmitXml Tenths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Tenths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord Tenths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Tenths Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Tenths = D1 ('MetaData "Tenths" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded TextDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum TextDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic TextDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep TextDirection :: Type -> Type #

Show TextDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml TextDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq TextDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord TextDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TextDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TextDirection = D1 ('MetaData "TextDirection" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 TiedType Source #

tied-type (simple)

The tied-type type is used as an attribute of the tied element to specify where the visual representation of a tie begins and ends. A tied element which joins two notes of the same pitch can be specified with tied-type start on the first note and tied-type stop on the second note. To indicate a note should be undamped, use a single tied element with tied-type let-ring. For other ties that are visually attached to a single note, such as a tie leading into or out of a repeated section or coda, use two tied elements on the same note, one start and one stop.

In start-stop cases, ties can add more elements using a continue type. This is typically used to specify the formatting of cross-system ties.

Instances

Instances details
Bounded TiedType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum TiedType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic TiedType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep TiedType :: Type -> Type #

Methods

from :: TiedType -> Rep TiedType x #

to :: Rep TiedType x -> TiedType #

Show TiedType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml TiedType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq TiedType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord TiedType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TiedType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TiedType = D1 ('MetaData "TiedType" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) ((C1 ('MetaCons "TiedTypeStart" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TiedTypeStop" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TiedTypeContinue" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TiedTypeLetRing" 'PrefixI 'False) (U1 :: Type -> Type)))

newtype TimeOnly Source #

time-only (simple)

The time-only type is used to indicate that a particular playback-related element only applies particular times through a repeated section. The value is a comma-separated list of positive integers arranged in ascending order, indicating which times through the repeated section that the element applies.

Constructors

TimeOnly 

Fields

Instances

Instances details
IsString TimeOnly Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic TimeOnly Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep TimeOnly :: Type -> Type #

Methods

from :: TimeOnly -> Rep TimeOnly x #

to :: Rep TimeOnly x -> TimeOnly #

Read TimeOnly Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show TimeOnly Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml TimeOnly Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq TimeOnly Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord TimeOnly Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TimeOnly Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TimeOnly = D1 ('MetaData "TimeOnly" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'True) (C1 ('MetaCons "TimeOnly" 'PrefixI 'True) (S1 ('MetaSel ('Just "timeOnly") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Token)))

data TimeRelation Source #

time-relation (simple)

The time-relation type indicates the symbol used to represent the interchangeable aspect of dual time signatures.

Instances

Instances details
Bounded TimeRelation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum TimeRelation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic TimeRelation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep TimeRelation :: Type -> Type #

Show TimeRelation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml TimeRelation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq TimeRelation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord TimeRelation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TimeRelation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TimeRelation = D1 ('MetaData "TimeRelation" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) ((C1 ('MetaCons "TimeRelationParentheses" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TimeRelationBracket" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TimeRelationEquals" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "TimeRelationSlash" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TimeRelationSpace" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TimeRelationHyphen" 'PrefixI 'False) (U1 :: Type -> Type))))

data TimeSeparator Source #

time-separator (simple)

The time-separator type indicates how to display the arrangement between the beats and beat-type values in a time signature. The default value is none. The horizontal, diagonal, and vertical values represent horizontal, diagonal lower-left to upper-right, and vertical lines respectively. For these values, the beats and beat-type values are arranged on either side of the separator line. The none value represents no separator with the beats and beat-type arranged vertically. The adjacent value represents no separator with the beats and beat-type arranged horizontally.

Instances

Instances details
Bounded TimeSeparator Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum TimeSeparator Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic TimeSeparator Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep TimeSeparator :: Type -> Type #

Show TimeSeparator Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml TimeSeparator Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq TimeSeparator Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord TimeSeparator Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TimeSeparator Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TimeSeparator = D1 ('MetaData "TimeSeparator" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) ((C1 ('MetaCons "TimeSeparatorNone" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TimeSeparatorHorizontal" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TimeSeparatorDiagonal" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TimeSeparatorVertical" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TimeSeparatorAdjacent" '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. The note symbol indicates that the beat-type should be represented with the corresponding downstem note rather than a number. The dotted-note symbol indicates that the beat-type should be represented with a dotted downstem note that corresponds to three times the beat-type value, and a numerator that is one third the beats value.

Instances

Instances details
Bounded TimeSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum TimeSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic TimeSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep TimeSymbol :: Type -> Type #

Show TimeSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml TimeSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq TimeSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord TimeSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TimeSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TimeSymbol = D1 ('MetaData "TimeSymbol" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 "TimeSymbolNote" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TimeSymbolDottedNote" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TimeSymbolNormal" 'PrefixI 'False) (U1 :: Type -> Type))))

data TipDirection Source #

tip-direction (simple)

The tip-direction type represents the direction in which the tip of a stick or beater points, using Unicode arrow terminology.

Instances

Instances details
Bounded TipDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum TipDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic TipDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep TipDirection :: Type -> Type #

Show TipDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml TipDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq TipDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord TipDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TipDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TipDirection = D1 ('MetaData "TipDirection" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (((C1 ('MetaCons "TipDirectionUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TipDirectionDown" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TipDirectionLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TipDirectionRight" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TipDirectionNorthwest" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TipDirectionNortheast" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TipDirectionSoutheast" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TipDirectionSouthwest" 'PrefixI 'False) (U1 :: Type -> Type))))

newtype Token Source #

xs:token (simple)

Constructors

Token 

Instances

Instances details
IsString Token Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

fromString :: String -> Token #

Generic Token Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Token :: Type -> Type #

Methods

from :: Token -> Rep Token x #

to :: Rep Token x -> Token #

Read Token Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show Token Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

EmitXml Token Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Token -> XmlRep Source #

Eq Token Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord Token Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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 #

type Rep Token Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Token = D1 ('MetaData "Token" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded TopBottom Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum TopBottom Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic TopBottom Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep TopBottom :: Type -> Type #

Show TopBottom Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml TopBottom Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq TopBottom Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord TopBottom Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TopBottom Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TopBottom = D1 ('MetaData "TopBottom" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 8: the same as beam-level with 0 added.

Constructors

TremoloMarks 

Fields

Instances

Instances details
Bounded TremoloMarks Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum TremoloMarks Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic TremoloMarks Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep TremoloMarks :: Type -> Type #

Num TremoloMarks Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Read TremoloMarks Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Integral TremoloMarks Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Real TremoloMarks Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show TremoloMarks Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml TremoloMarks Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq TremoloMarks Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord TremoloMarks Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TremoloMarks Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TremoloMarks = D1 ('MetaData "TremoloMarks" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'True) (C1 ('MetaCons "TremoloMarks" 'PrefixI 'True) (S1 ('MetaSel ('Just "tremoloMarks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

data TremoloType Source #

tremolo-type (simple)

The tremolo-type is used to distinguish multi-note, single-note, and unmeasured tremolos.

Instances

Instances details
Bounded TremoloType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum TremoloType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic TremoloType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep TremoloType :: Type -> Type #

Show TremoloType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml TremoloType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq TremoloType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord TremoloType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TremoloType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TremoloType = D1 ('MetaData "TremoloType" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) ((C1 ('MetaCons "TremoloTypeStart" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TremoloTypeStop" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TremoloTypeSingle" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TremoloTypeUnmeasured" 'PrefixI 'False) (U1 :: Type -> Type)))

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

Instances details
Generic TrillBeats Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep TrillBeats :: Type -> Type #

Num TrillBeats Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Read TrillBeats Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Fractional TrillBeats Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Real TrillBeats Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

RealFrac TrillBeats Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show TrillBeats Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml TrillBeats Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq TrillBeats Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord TrillBeats Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TrillBeats Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TrillBeats = D1 ('MetaData "TrillBeats" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded TrillStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum TrillStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic TrillStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep TrillStep :: Type -> Type #

Show TrillStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml TrillStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq TrillStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord TrillStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TrillStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TrillStep = D1 ('MetaData "TrillStep" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded TwoNoteTurn Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum TwoNoteTurn Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic TwoNoteTurn Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep TwoNoteTurn :: Type -> Type #

Show TwoNoteTurn Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml TwoNoteTurn Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq TwoNoteTurn Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord TwoNoteTurn Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TwoNoteTurn Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TwoNoteTurn = D1 ('MetaData "TwoNoteTurn" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded Type Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum Type Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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] #

Generic Type Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Type :: Type -> Type #

Methods

from :: Type -> Rep Type x #

to :: Rep Type x -> Type #

Show Type Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

EmitXml Type Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Type -> XmlRep Source #

Eq Type Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord Type Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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 #

type Rep Type Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Type = D1 ('MetaData "Type" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "TypeSimple" 'PrefixI 'False) (U1 :: Type -> Type))

data UpDown Source #

up-down (simple)

The up-down type is used for the direction of arrows and other pointed symbols like vertical accents, indicating which way the tip is pointing.

Constructors

UpDownUp

up

UpDownDown

down

Instances

Instances details
Bounded UpDown Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum UpDown Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic UpDown Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep UpDown :: Type -> Type #

Methods

from :: UpDown -> Rep UpDown x #

to :: Rep UpDown x -> UpDown #

Show UpDown Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml UpDown Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq UpDown Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord UpDown Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep UpDown Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep UpDown = D1 ('MetaData "UpDown" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "UpDownUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UpDownDown" 'PrefixI 'False) (U1 :: Type -> Type))

data UpDownStopContinue Source #

up-down-stop-continue (simple)

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

Instances

Instances details
Bounded UpDownStopContinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum UpDownStopContinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic UpDownStopContinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep UpDownStopContinue :: Type -> Type #

Show UpDownStopContinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml UpDownStopContinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq UpDownStopContinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord UpDownStopContinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep UpDownStopContinue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep UpDownStopContinue = D1 ('MetaData "UpDownStopContinue" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) ((C1 ('MetaCons "UpDownStopContinueUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UpDownStopContinueDown" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UpDownStopContinueStop" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UpDownStopContinueContinue" '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

Instances details
Bounded UprightInverted Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum UprightInverted Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic UprightInverted Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep UprightInverted :: Type -> Type #

Show UprightInverted Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml UprightInverted Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq UprightInverted Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord UprightInverted Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep UprightInverted Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep UprightInverted = D1 ('MetaData "UprightInverted" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded Valign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum Valign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic Valign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Valign :: Type -> Type #

Methods

from :: Valign -> Rep Valign x #

to :: Rep Valign x -> Valign #

Show Valign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Valign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Valign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord Valign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Valign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Valign = D1 ('MetaData "Valign" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Bounded ValignImage Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum ValignImage Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic ValignImage Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ValignImage :: Type -> Type #

Show ValignImage Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ValignImage Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ValignImage Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord ValignImage Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ValignImage Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ValignImage = D1 ('MetaData "ValignImage" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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. The continue type is used for formatting wedges over a system break, or for other situations where a single wedge is divided into multiple segments.

Instances

Instances details
Bounded WedgeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum WedgeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic WedgeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep WedgeType :: Type -> Type #

Show WedgeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml WedgeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq WedgeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord WedgeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep WedgeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep WedgeType = D1 ('MetaData "WedgeType" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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) :+: C1 ('MetaCons "WedgeTypeContinue" 'PrefixI 'False) (U1 :: Type -> Type)))

data Winged Source #

winged (simple)

The winged attribute indicates whether the repeat has winged extensions that appear above and below the barline. The straight and curved values represent single wings, while the double-straight and double-curved values represent double wings. The none value indicates no wings and is the default.

Constructors

WingedNone

none

WingedStraight

straight

WingedCurved

curved

WingedDoubleStraight

double-straight

WingedDoubleCurved

double-curved

Instances

Instances details
Bounded Winged Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum Winged Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic Winged Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Winged :: Type -> Type #

Methods

from :: Winged -> Rep Winged x #

to :: Rep Winged x -> Winged #

Show Winged Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Winged Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Winged Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord Winged Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Winged Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Winged = D1 ('MetaData "Winged" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) ((C1 ('MetaCons "WingedNone" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WingedStraight" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "WingedCurved" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "WingedDoubleStraight" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WingedDoubleCurved" 'PrefixI 'False) (U1 :: Type -> Type))))

data Wood Source #

wood (simple)

The wood type represents pictograms for wood percussion instruments. The maraca and maracas values distinguish the one- and two-maraca versions of the pictogram.

Constructors

WoodBambooScraper

bamboo scraper

WoodBoardClapper

board clapper

WoodCabasa

cabasa

WoodCastanets

castanets

WoodCastanetsWithHandle

castanets with handle

WoodClaves

claves

WoodFootballRattle

football rattle

WoodGuiro

guiro

WoodLogDrum

log drum

WoodMaraca

maraca

WoodMaracas

maracas

WoodQuijada

quijada

WoodRainstick

rainstick

WoodRatchet

ratchet

WoodRecoReco

reco-reco

WoodSandpaperBlocks

sandpaper blocks

WoodSlitDrum

slit drum

WoodTempleBlock

temple block

WoodVibraslap

vibraslap

WoodWhip

whip

WoodWoodBlock

wood block

Instances

Instances details
Bounded Wood Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum Wood Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

succ :: Wood -> Wood #

pred :: Wood -> Wood #

toEnum :: Int -> Wood #

fromEnum :: Wood -> Int #

enumFrom :: Wood -> [Wood] #

enumFromThen :: Wood -> Wood -> [Wood] #

enumFromTo :: Wood -> Wood -> [Wood] #

enumFromThenTo :: Wood -> Wood -> Wood -> [Wood] #

Generic Wood Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Wood :: Type -> Type #

Methods

from :: Wood -> Rep Wood x #

to :: Rep Wood x -> Wood #

Show Wood Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Wood -> ShowS #

show :: Wood -> String #

showList :: [Wood] -> ShowS #

EmitXml Wood Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Wood -> XmlRep Source #

Eq Wood Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord Wood Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

compare :: Wood -> Wood -> Ordering #

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

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

(>) :: Wood -> Wood -> Bool #

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

max :: Wood -> Wood -> Wood #

min :: Wood -> Wood -> Wood #

type Rep Wood Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Wood = D1 ('MetaData "Wood" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) ((((C1 ('MetaCons "WoodBambooScraper" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WoodBoardClapper" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "WoodCabasa" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "WoodCastanets" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WoodCastanetsWithHandle" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "WoodClaves" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WoodFootballRattle" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "WoodGuiro" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "WoodLogDrum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WoodMaraca" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "WoodMaracas" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WoodQuijada" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "WoodRainstick" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "WoodRatchet" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WoodRecoReco" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "WoodSandpaperBlocks" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "WoodSlitDrum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WoodTempleBlock" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "WoodVibraslap" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "WoodWhip" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WoodWoodBlock" '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

Instances details
Bounded YesNo Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum YesNo Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic YesNo Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep YesNo :: Type -> Type #

Methods

from :: YesNo -> Rep YesNo x #

to :: Rep YesNo x -> YesNo #

Show YesNo Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> YesNo -> ShowS #

show :: YesNo -> String #

showList :: [YesNo] -> ShowS #

EmitXml YesNo Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: YesNo -> XmlRep Source #

Eq YesNo Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord YesNo Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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 #

type Rep YesNo Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep YesNo = D1 ('MetaData "YesNo" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic YesNoNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep YesNoNumber :: Type -> Type #

Show YesNoNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml YesNoNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq YesNoNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep YesNoNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep YesNoNumber = D1 ('MetaData "YesNoNumber" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
IsString YyyyMmDd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic YyyyMmDd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep YyyyMmDd :: Type -> Type #

Methods

from :: YyyyMmDd -> Rep YyyyMmDd x #

to :: Rep YyyyMmDd x -> YyyyMmDd #

Read YyyyMmDd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Show YyyyMmDd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml YyyyMmDd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq YyyyMmDd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord YyyyMmDd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep YyyyMmDd Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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

data SumLang Source #

xml:lang (union)

Constructors

SumLang

//

Instances

Instances details
Bounded SumLang Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum SumLang Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic SumLang Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep SumLang :: Type -> Type #

Methods

from :: SumLang -> Rep SumLang x #

to :: Rep SumLang x -> SumLang #

Show SumLang Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml SumLang Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq SumLang Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

Ord SumLang Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SumLang Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SumLang = D1 ('MetaData "SumLang" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "SumLang" 'PrefixI 'False) (U1 :: Type -> Type))

data SumNumberOrNormal Source #

number-or-normal (union)

Constructors

NumberOrNormalNormal

normal

Instances

Instances details
Bounded SumNumberOrNormal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum SumNumberOrNormal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic SumNumberOrNormal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep SumNumberOrNormal :: Type -> Type #

Show SumNumberOrNormal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml SumNumberOrNormal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq SumNumberOrNormal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord SumNumberOrNormal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SumNumberOrNormal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SumNumberOrNormal = D1 ('MetaData "SumNumberOrNormal" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "NumberOrNormalNormal" 'PrefixI 'False) (U1 :: Type -> Type))

data SumPositiveIntegerOrEmpty Source #

positive-integer-or-empty (union)

Instances

Instances details
Bounded SumPositiveIntegerOrEmpty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Enum SumPositiveIntegerOrEmpty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Generic SumPositiveIntegerOrEmpty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep SumPositiveIntegerOrEmpty :: Type -> Type #

Show SumPositiveIntegerOrEmpty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml SumPositiveIntegerOrEmpty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq SumPositiveIntegerOrEmpty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Ord SumPositiveIntegerOrEmpty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SumPositiveIntegerOrEmpty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SumPositiveIntegerOrEmpty = D1 ('MetaData "SumPositiveIntegerOrEmpty" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic Accidental Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Accidental :: Type -> Type #

Show Accidental Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Accidental Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Accidental Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Accidental Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Accidental = D1 ('MetaData "Accidental" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 "accidentalSmufl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SmuflAccidentalGlyphName)))) :*: ((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.

Instances

Instances details
Generic AccidentalMark Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep AccidentalMark :: Type -> Type #

Show AccidentalMark Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml AccidentalMark Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq AccidentalMark Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep AccidentalMark Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep AccidentalMark = D1 ('MetaData "AccidentalMark" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "AccidentalMark" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "accidentalMarkAccidentalValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccidentalValue) :*: S1 ('MetaSel ('Just "accidentalMarkSmufl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SmuflAccidentalGlyphName))) :*: (S1 ('MetaSel ('Just "accidentalMarkParentheses") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 ('MetaSel ('Just "accidentalMarkBracket") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe YesNo)))) :*: ((S1 ('MetaSel ('Just "accidentalMarkSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SymbolSize)) :*: 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)) :*: S1 ('MetaSel ('Just "accidentalMarkId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)))))))

data AccidentalText Source #

accidental-text (complex)

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

Constructors

AccidentalText 

Instances

Instances details
Generic AccidentalText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep AccidentalText :: Type -> Type #

Show AccidentalText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml AccidentalText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq AccidentalText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep AccidentalText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep AccidentalText = D1 ('MetaData "AccidentalText" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "AccidentalText" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "accidentalTextAccidentalValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccidentalValue) :*: (S1 ('MetaSel ('Just "accidentalTextSmufl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SmuflAccidentalGlyphName)) :*: S1 ('MetaSel ('Just "accidentalTextLang") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Lang)))) :*: (S1 ('MetaSel ('Just "accidentalTextSpace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Space)) :*: (S1 ('MetaSel ('Just "accidentalTextJustify") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LeftCenterRight)) :*: 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 "accidentalTextHalign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LeftCenterRight)))) :*: (S1 ('MetaSel ('Just "accidentalTextValign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Valign)) :*: (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)) :*: S1 ('MetaSel ('Just "accidentalTextEnclosure") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe EnclosureShape))))))))

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

Instances details
Generic Accord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Accord :: Type -> Type #

Methods

from :: Accord -> Rep Accord x #

to :: Rep Accord x -> Accord #

Show Accord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Accord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Accord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Accord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Accord = D1 ('MetaData "Accord" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic AccordionRegistration Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep AccordionRegistration :: Type -> Type #

Show AccordionRegistration Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml AccordionRegistration Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq AccordionRegistration Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep AccordionRegistration Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep AccordionRegistration = D1 ('MetaData "AccordionRegistration" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 "accordionRegistrationHalign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LeftCenterRight)) :*: S1 ('MetaSel ('Just "accordionRegistrationValign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Valign)))) :*: ((S1 ('MetaSel ('Just "accordionRegistrationId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)) :*: 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. This includes support for line widths, definitions for note sizes, and standard distances between notation elements, plus an extension element for other aspects of appearance.

Constructors

Appearance 

Fields

Instances

Instances details
Generic Appearance Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Appearance :: Type -> Type #

Show Appearance Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Appearance Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Appearance Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Appearance Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Appearance = D1 ('MetaData "Appearance" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 "appearanceDistance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Distance]) :*: (S1 ('MetaSel ('Just "appearanceGlyph") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Glyph]) :*: 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

Instances details
Generic Arpeggiate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Arpeggiate :: Type -> Type #

Show Arpeggiate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Arpeggiate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Arpeggiate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Arpeggiate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Arpeggiate = D1 ('MetaData "Arpeggiate" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Arpeggiate" 'PrefixI 'True) (((S1 ('MetaSel ('Just "arpeggiateNumber") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NumberLevel)) :*: S1 ('MetaSel ('Just "arpeggiateDirection") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe UpDown))) :*: (S1 ('MetaSel ('Just "arpeggiateDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "arpeggiateDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)))) :*: ((S1 ('MetaSel ('Just "arpeggiateRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "arpeggiateRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 ('MetaSel ('Just "arpeggiatePlacement") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AboveBelow)) :*: (S1 ('MetaSel ('Just "arpeggiateColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)) :*: S1 ('MetaSel ('Just "arpeggiateId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)))))))

mkArpeggiate :: Arpeggiate Source #

Smart constructor for Arpeggiate

data Arrow Source #

arrow (complex)

The arrow element represents an arrow used for a musical technical indication. It can represent both Unicode and SMuFL arrows. The presence of an arrowhead element indicates that only the arrowhead is displayed, not the arrow stem. The smufl attribute distinguishes different SMuFL glyphs that have an arrow appearance such as arrowBlackUp, guitarStrumUp, or handbellsSwingUp. The specified glyph should match the descriptive representation.

Constructors

Arrow 

Fields

Instances

Instances details
Generic Arrow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Arrow :: Type -> Type #

Methods

from :: Arrow -> Rep Arrow x #

to :: Rep Arrow x -> Arrow #

Show Arrow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Arrow -> ShowS #

show :: Arrow -> String #

showList :: [Arrow] -> ShowS #

EmitXml Arrow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Arrow -> XmlRep Source #

Eq Arrow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Arrow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Arrow = D1 ('MetaData "Arrow" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Arrow" 'PrefixI 'True) (((S1 ('MetaSel ('Just "arrowDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "arrowDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "arrowRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)))) :*: (S1 ('MetaSel ('Just "arrowRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "arrowFontFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 ('MetaSel ('Just "arrowFontStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontStyle))))) :*: ((S1 ('MetaSel ('Just "arrowFontSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontSize)) :*: (S1 ('MetaSel ('Just "arrowFontWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontWeight)) :*: S1 ('MetaSel ('Just "arrowColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)))) :*: (S1 ('MetaSel ('Just "arrowPlacement") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AboveBelow)) :*: (S1 ('MetaSel ('Just "arrowSmufl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SmuflGlyphName)) :*: S1 ('MetaSel ('Just "arrowArrow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChxArrow))))))

mkArrow :: ChxArrow -> Arrow Source #

Smart constructor for Arrow

data Articulations Source #

articulations (complex)

Articulations and accents are grouped together here.

Instances

Instances details
Generic Articulations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Articulations :: Type -> Type #

Show Articulations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Articulations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Articulations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Articulations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Articulations = D1 ('MetaData "Articulations" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Articulations" 'PrefixI 'True) (S1 ('MetaSel ('Just "articulationsId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)) :*: 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. When attributes are changed mid-measure, it affects the music in score order, not in MusicXML document order.

Constructors

Attributes 

Fields

Instances

Instances details
Generic Attributes Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Attributes :: Type -> Type #

Show Attributes Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Attributes Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Attributes Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Attributes Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Attributes = D1 ('MetaData "Attributes" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 [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 or mid-measure changes in the divisions value.

Instances

Instances details
Generic Backup Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Backup :: Type -> Type #

Methods

from :: Backup -> Rep Backup x #

to :: Rep Backup x -> Backup #

Show Backup Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Backup Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Backup Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Backup Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Backup = D1 ('MetaData "Backup" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic BarStyleColor Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep BarStyleColor :: Type -> Type #

Show BarStyleColor Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml BarStyleColor Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq BarStyleColor Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep BarStyleColor Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep BarStyleColor = D1 ('MetaData "BarStyleColor" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic Barline Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Barline :: Type -> Type #

Methods

from :: Barline -> Rep Barline x #

to :: Rep Barline x -> Barline #

Show Barline Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Barline Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Barline Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Barline Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Barline = D1 ('MetaData "Barline" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 "barlineId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)) :*: 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 Segno)))) :*: ((S1 ('MetaSel ('Just "barlineCoda1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Coda)) :*: 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

Instances details
Generic Barre Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Barre :: Type -> Type #

Methods

from :: Barre -> Rep Barre x #

to :: Rep Barre x -> Barre #

Show Barre Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Barre -> ShowS #

show :: Barre -> String #

showList :: [Barre] -> ShowS #

EmitXml Barre Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Barre -> XmlRep Source #

Eq Barre Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Barre Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Barre = D1 ('MetaData "Barre" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic Bass Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Bass :: Type -> Type #

Methods

from :: Bass -> Rep Bass x #

to :: Rep Bass x -> Bass #

Show Bass Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Bass -> ShowS #

show :: Bass -> String #

showList :: [Bass] -> ShowS #

EmitXml Bass Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Bass -> XmlRep Source #

Eq Bass Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Bass Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Bass = D1 ('MetaData "Bass" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic BassAlter Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep BassAlter :: Type -> Type #

Show BassAlter Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml BassAlter Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq BassAlter Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep BassAlter Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep BassAlter = D1 ('MetaData "BassAlter" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 in a score if not using the element contents.

Constructors

BassStep 

Fields

Instances

Instances details
Generic BassStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep BassStep :: Type -> Type #

Methods

from :: BassStep -> Rep BassStep x #

to :: Rep BassStep x -> BassStep #

Show BassStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml BassStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq BassStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep BassStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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

mkBassStep :: Step -> BassStep Source #

Smart constructor for BassStep

data Beam Source #

beam (complex)

Beam values include begin, continue, end, forward hook, and backward hook. Up to eight concurrent beams are available to cover up to 1024th notes. Each beam in a note is represented with a separate beam element, starting with the eighth note beam using a number attribute of 1.

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.

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.

The repeater attribute has been deprecated in MusicXML 3.0. Formerly used for tremolos, it needs to be specified with a "yes" value for each beam using it.

Constructors

Beam 

Fields

Instances

Instances details
Generic Beam Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Beam :: Type -> Type #

Methods

from :: Beam -> Rep Beam x #

to :: Rep Beam x -> Beam #

Show Beam Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Beam -> ShowS #

show :: Beam -> String #

showList :: [Beam] -> ShowS #

EmitXml Beam Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Beam -> XmlRep Source #

Eq Beam Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Beam Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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

Instances details
Generic BeatRepeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep BeatRepeat :: Type -> Type #

Show BeatRepeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml BeatRepeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq BeatRepeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep BeatRepeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep BeatRepeat = D1 ('MetaData "BeatRepeat" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 BeatUnitTied Source #

beat-unit-tied (complex)

The beat-unit-tied type indicates a beat-unit within a metronome mark that is tied to the preceding beat-unit. This allows or two or more tied notes to be associated with a per-minute value in a metronome mark, whereas the metronome-tied element is restricted to metric relationship marks.

Instances

Instances details
Generic BeatUnitTied Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep BeatUnitTied :: Type -> Type #

Show BeatUnitTied Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml BeatUnitTied Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq BeatUnitTied Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep BeatUnitTied Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep BeatUnitTied = D1 ('MetaData "BeatUnitTied" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "BeatUnitTied" 'PrefixI 'True) (S1 ('MetaSel ('Just "beatUnitTiedBeatUnit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BeatUnit)))

data Beater Source #

beater (complex)

The beater type represents pictograms for beaters, mallets, and sticks that do not have different materials represented in the pictogram.

Constructors

Beater 

Fields

Instances

Instances details
Generic Beater Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Beater :: Type -> Type #

Methods

from :: Beater -> Rep Beater x #

to :: Rep Beater x -> Beater #

Show Beater Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Beater Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Beater Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Beater Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Beater = D1 ('MetaData "Beater" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Beater" 'PrefixI 'True) (S1 ('MetaSel ('Just "beaterBeaterValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BeaterValue) :*: S1 ('MetaSel ('Just "beaterTip") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TipDirection))))

mkBeater :: BeaterValue -> Beater Source #

Smart constructor for Beater

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

Instances details
Generic Bend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Bend :: Type -> Type #

Methods

from :: Bend -> Rep Bend x #

to :: Rep Bend x -> Bend #

Show Bend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Bend -> ShowS #

show :: Bend -> String #

showList :: [Bend] -> ShowS #

EmitXml Bend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Bend -> XmlRep Source #

Eq Bend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Bend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Bend = D1 ('MetaData "Bend" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic Bookmark Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Bookmark :: Type -> Type #

Methods

from :: Bookmark -> Rep Bookmark x #

to :: Rep Bookmark x -> Bookmark #

Show Bookmark Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Bookmark Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Bookmark Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Bookmark Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Bookmark = D1 ('MetaData "Bookmark" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic Bracket Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Bracket :: Type -> Type #

Methods

from :: Bracket -> Rep Bracket x #

to :: Rep Bracket x -> Bracket #

Show Bracket Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Bracket Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Bracket Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Bracket Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Bracket = D1 ('MetaData "Bracket" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Bracket" 'PrefixI 'True) (((S1 ('MetaSel ('Just "bracketType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StartStopContinue) :*: (S1 ('MetaSel ('Just "bracketNumber") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NumberLevel)) :*: S1 ('MetaSel ('Just "bracketLineEnd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LineEnd))) :*: (S1 ('MetaSel ('Just "bracketEndLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "bracketLineType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LineType)) :*: S1 ('MetaSel ('Just "bracketDashLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 ('MetaSel ('Just "bracketSpaceLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "bracketDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "bracketDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)))) :*: ((S1 ('MetaSel ('Just "bracketRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "bracketRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 ('MetaSel ('Just "bracketColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)) :*: S1 ('MetaSel ('Just "bracketId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)))))))

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

Smart constructor for Bracket

data BreathMark Source #

breath-mark (complex)

The breath-mark element indicates a place to take a breath.

Constructors

BreathMark 

Fields

Instances

Instances details
Generic BreathMark Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep BreathMark :: Type -> Type #

Show BreathMark Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml BreathMark Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq BreathMark Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep BreathMark Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep BreathMark = D1 ('MetaData "BreathMark" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "BreathMark" 'PrefixI 'True) (((S1 ('MetaSel ('Just "breathMarkBreathMarkValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BreathMarkValue) :*: S1 ('MetaSel ('Just "breathMarkDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 ('MetaSel ('Just "breathMarkDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "breathMarkRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "breathMarkRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 ('MetaSel ('Just "breathMarkFontFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: (S1 ('MetaSel ('Just "breathMarkFontStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontStyle)) :*: S1 ('MetaSel ('Just "breathMarkFontSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontSize)))) :*: (S1 ('MetaSel ('Just "breathMarkFontWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontWeight)) :*: (S1 ('MetaSel ('Just "breathMarkColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)) :*: S1 ('MetaSel ('Just "breathMarkPlacement") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AboveBelow)))))))

data Caesura Source #

caesura (complex)

The caesura element indicates a slight pause. It is notated using a "railroad tracks" symbol or other variations specified in the element content.

Constructors

Caesura 

Fields

Instances

Instances details
Generic Caesura Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Caesura :: Type -> Type #

Methods

from :: Caesura -> Rep Caesura x #

to :: Rep Caesura x -> Caesura #

Show Caesura Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Caesura Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Caesura Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Caesura Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Caesura = D1 ('MetaData "Caesura" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Caesura" 'PrefixI 'True) (((S1 ('MetaSel ('Just "caesuraCaesuraValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CaesuraValue) :*: S1 ('MetaSel ('Just "caesuraDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 ('MetaSel ('Just "caesuraDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "caesuraRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "caesuraRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 ('MetaSel ('Just "caesuraFontFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: (S1 ('MetaSel ('Just "caesuraFontStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontStyle)) :*: S1 ('MetaSel ('Just "caesuraFontSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontSize)))) :*: (S1 ('MetaSel ('Just "caesuraFontWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontWeight)) :*: (S1 ('MetaSel ('Just "caesuraColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)) :*: S1 ('MetaSel ('Just "caesuraPlacement") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AboveBelow)))))))

mkCaesura :: CaesuraValue -> Caesura Source #

Smart constructor for Caesura

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 where the cancellation appears relative to the new key signature.

Constructors

Cancel 

Fields

Instances

Instances details
Generic Cancel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Cancel :: Type -> Type #

Methods

from :: Cancel -> Rep Cancel x #

to :: Rep Cancel x -> Cancel #

Show Cancel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Cancel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Cancel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Cancel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Cancel = D1 ('MetaData "Cancel" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Cancel" 'PrefixI 'True) (S1 ('MetaSel ('Just "cancelFifths") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Fifths) :*: S1 ('MetaSel ('Just "cancelLocation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CancelLocation))))

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.

Sometimes clefs at the start of a measure need to appear after the barline rather than before, as for cues or for use after a repeated section. The after-barline attribute is set to "yes" in this situation. The attribute is ignored for mid-measure clefs.

Clefs appear at the start of each system unless the print-object attribute has been set to "no" or the additional attribute has been set to "yes".

Constructors

Clef 

Fields

Instances

Instances details
Generic Clef Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Clef :: Type -> Type #

Methods

from :: Clef -> Rep Clef x #

to :: Rep Clef x -> Clef #

Show Clef Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Clef -> ShowS #

show :: Clef -> String #

showList :: [Clef] -> ShowS #

EmitXml Clef Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Clef -> XmlRep Source #

Eq Clef Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Clef Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Clef = D1 ('MetaData "Clef" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 "clefAfterBarline") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe YesNo)))) :*: ((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 "clefId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID))) :*: (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 Coda Source #

coda (complex)

The coda type is the visual indicator of a coda sign. The exact glyph can be specified with the smufl attribute. A sound element is also needed to guide playback applications reliably.

Constructors

Coda 

Fields

Instances

Instances details
Generic Coda Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Coda :: Type -> Type #

Methods

from :: Coda -> Rep Coda x #

to :: Rep Coda x -> Coda #

Show Coda Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Coda -> ShowS #

show :: Coda -> String #

showList :: [Coda] -> ShowS #

EmitXml Coda Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Coda -> XmlRep Source #

Eq Coda Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Coda Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Coda = D1 ('MetaData "Coda" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Coda" 'PrefixI 'True) (((S1 ('MetaSel ('Just "codaSmufl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SmuflCodaGlyphName)) :*: (S1 ('MetaSel ('Just "codaDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "codaDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)))) :*: (S1 ('MetaSel ('Just "codaRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "codaRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "codaFontFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CommaSeparatedText))))) :*: ((S1 ('MetaSel ('Just "codaFontStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontStyle)) :*: (S1 ('MetaSel ('Just "codaFontSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontSize)) :*: S1 ('MetaSel ('Just "codaFontWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontWeight)))) :*: ((S1 ('MetaSel ('Just "codaColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)) :*: S1 ('MetaSel ('Just "codaHalign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LeftCenterRight))) :*: (S1 ('MetaSel ('Just "codaValign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Valign)) :*: S1 ('MetaSel ('Just "codaId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)))))))

mkCoda :: Coda Source #

Smart constructor for Coda

data Credit Source #

credit (complex)

The credit type represents the appearance of the title, composer, arranger, lyricist, copyright, dedication, and other text, symbols, and graphics that commonly appear on the first page of a score. The credit-words, credit-symbol, and credit-image elements are similar to the words, symbol, 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 page. The enclosure for credit-words and credit-symbol is none by default.

By default, a series of credit-words and credit-symbol 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 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.

The credit-type element indicates the purpose behind a credit. Multiple types of data may be combined in a single credit, so multiple elements may be used. Standard values include page number, title, subtitle, composer, arranger, lyricist, and rights.

Constructors

Credit 

Fields

Instances

Instances details
Generic Credit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Credit :: Type -> Type #

Methods

from :: Credit -> Rep Credit x #

to :: Rep Credit x -> Credit #

Show Credit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Credit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Credit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Credit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Credit = D1 ('MetaData "Credit" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Credit" 'PrefixI 'True) ((S1 ('MetaSel ('Just "creditPage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PositiveInteger)) :*: (S1 ('MetaSel ('Just "creditId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)) :*: S1 ('MetaSel ('Just "creditCreditType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))) :*: (S1 ('MetaSel ('Just "creditLink") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Link]) :*: (S1 ('MetaSel ('Just "creditBookmark") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Bookmark]) :*: S1 ('MetaSel ('Just "creditCredit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChxCredit)))))

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

Instances details
Generic Dashes Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Dashes :: Type -> Type #

Methods

from :: Dashes -> Rep Dashes x #

to :: Rep Dashes x -> Dashes #

Show Dashes Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Dashes Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Dashes Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Dashes Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

mkDashes :: StartStopContinue -> 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

Instances details
Generic Defaults Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Defaults :: Type -> Type #

Methods

from :: Defaults -> Rep Defaults x #

to :: Rep Defaults x -> Defaults #

Show Defaults Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Defaults Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Defaults Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Defaults Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Defaults = D1 ('MetaData "Defaults" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Defaults" 'PrefixI 'True) ((S1 ('MetaSel ('Just "defaultsScaling") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Scaling)) :*: (S1 ('MetaSel ('Just "defaultsLayout") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Layout) :*: S1 ('MetaSel ('Just "defaultsAppearance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Appearance)))) :*: ((S1 ('MetaSel ('Just "defaultsMusicFont") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe EmptyFont)) :*: S1 ('MetaSel ('Just "defaultsWordFont") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe EmptyFont))) :*: (S1 ('MetaSel ('Just "defaultsLyricFont") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [LyricFont]) :*: S1 ('MetaSel ('Just "defaultsLyricLanguage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [LyricLanguage])))))

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

Instances details
Generic Degree Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Degree :: Type -> Type #

Methods

from :: Degree -> Rep Degree x #

to :: Rep Degree x -> Degree #

Show Degree Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Degree Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Degree Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Degree Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Degree = D1 ('MetaData "Degree" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic DegreeAlter Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep DegreeAlter :: Type -> Type #

Show DegreeAlter Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml DegreeAlter Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq DegreeAlter Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep DegreeAlter Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep DegreeAlter = D1 ('MetaData "DegreeAlter" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 in a score.

Constructors

DegreeType 

Fields

Instances

Instances details
Generic DegreeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep DegreeType :: Type -> Type #

Show DegreeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml DegreeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq DegreeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep DegreeType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep DegreeType = D1 ('MetaData "DegreeType" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 in a score. The degree-value symbol attribute indicates that a symbol should be used in specifying the degree. If the symbol attribute is present, the value of the text attribute follows the symbol.

Constructors

DegreeValue 

Fields

Instances

Instances details
Generic DegreeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep DegreeValue :: Type -> Type #

Show DegreeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml DegreeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq DegreeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep DegreeValue Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep DegreeValue = D1 ('MetaData "DegreeValue" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "DegreeValue" 'PrefixI 'True) (((S1 ('MetaSel ('Just "degreeValuePositiveInteger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PositiveInteger) :*: (S1 ('MetaSel ('Just "degreeValueSymbol") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DegreeSymbolValue)) :*: 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 necessarily attached to a specific note. Two or more may be combined to indicate starts and stops of wedges, dashes, etc. For applications where a specific direction is indeed attached to a specific note, the direction element can be associated with the note element that follows it in score order that is not in a different voice.

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

Instances details
Generic Direction Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Direction :: Type -> Type #

Show Direction Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Direction Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Direction Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Direction Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Direction = D1 ('MetaData "Direction" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Direction" 'PrefixI 'True) (((S1 ('MetaSel ('Just "directionPlacement") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AboveBelow)) :*: S1 ('MetaSel ('Just "directionDirective") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe YesNo))) :*: (S1 ('MetaSel ('Just "directionId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)) :*: S1 ('MetaSel ('Just "directionDirectionType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DirectionType]))) :*: ((S1 ('MetaSel ('Just "directionOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Offset)) :*: S1 ('MetaSel ('Just "directionEditorialVoiceDirection") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EditorialVoiceDirection)) :*: (S1 ('MetaSel ('Just "directionStaff") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Staff)) :*: S1 ('MetaSel ('Just "directionSound") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Sound))))))

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

Instances details
Generic DirectionType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep DirectionType :: Type -> Type #

Show DirectionType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml DirectionType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq DirectionType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep DirectionType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep DirectionType = D1 ('MetaData "DirectionType" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "DirectionType" 'PrefixI 'True) (S1 ('MetaSel ('Just "directionTypeId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)) :*: S1 ('MetaSel ('Just "directionTypeDirectionType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChxDirectionType)))

data Directive Source #

directive (complex)

Constructors

Directive 

Fields

Instances

Instances details
Generic Directive Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Directive :: Type -> Type #

Show Directive Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Directive Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Directive Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Directive Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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

mkDirective :: String -> Directive Source #

Smart constructor for Directive

data Distance Source #

distance (complex)

The distance element represents standard distances between notation elements in tenths. The type attribute defines what type of distance is being defined. Valid values include hyphen (for hyphens in lyrics) and beam.

Constructors

Distance 

Fields

Instances

Instances details
Generic Distance Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Distance :: Type -> Type #

Methods

from :: Distance -> Rep Distance x #

to :: Rep Distance x -> Distance #

Show Distance Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Distance Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Distance Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Distance Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Distance = D1 ('MetaData "Distance" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Distance" 'PrefixI 'True) (S1 ('MetaSel ('Just "distanceTenths") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Tenths) :*: S1 ('MetaSel ('Just "cmpdistanceType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DistanceType)))

mkDistance :: Tenths -> DistanceType -> Distance Source #

Smart constructor for Distance

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

Instances details
Generic Dynamics Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Dynamics :: Type -> Type #

Methods

from :: Dynamics -> Rep Dynamics x #

to :: Rep Dynamics x -> Dynamics #

Show Dynamics Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Dynamics Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Dynamics Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Dynamics Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Dynamics = D1 ('MetaData "Dynamics" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Dynamics" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "dynamicsDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "dynamicsDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 ('MetaSel ('Just "dynamicsRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "dynamicsRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)))) :*: ((S1 ('MetaSel ('Just "dynamicsFontFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 ('MetaSel ('Just "dynamicsFontStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontStyle))) :*: (S1 ('MetaSel ('Just "dynamicsFontSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontSize)) :*: (S1 ('MetaSel ('Just "dynamicsFontWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontWeight)) :*: S1 ('MetaSel ('Just "dynamicsColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)))))) :*: (((S1 ('MetaSel ('Just "dynamicsHalign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LeftCenterRight)) :*: S1 ('MetaSel ('Just "dynamicsValign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Valign))) :*: (S1 ('MetaSel ('Just "dynamicsPlacement") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AboveBelow)) :*: S1 ('MetaSel ('Just "dynamicsUnderline") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NumberOfLines)))) :*: ((S1 ('MetaSel ('Just "dynamicsOverline") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NumberOfLines)) :*: S1 ('MetaSel ('Just "dynamicsLineThrough") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NumberOfLines))) :*: (S1 ('MetaSel ('Just "dynamicsEnclosure") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe EnclosureShape)) :*: (S1 ('MetaSel ('Just "dynamicsId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)) :*: S1 ('MetaSel ('Just "dynamicsDynamics") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ChxDynamics])))))))

mkDynamics :: Dynamics Source #

Smart constructor for Dynamics

data Elision Source #

elision (complex)

The elision type represents an elision between lyric syllables. The text content specifies 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). If the text content is empty, the smufl attribute is used to specify the symbol to use. Its value is a SMuFL canonical glyph name that starts with lyrics. The SMuFL attribute is ignored if the elision glyph is already specified by the text content. If neither text content nor a smufl attribute are present, the elision glyph is application-specific.

Constructors

Elision 

Fields

Instances

Instances details
Generic Elision Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Elision :: Type -> Type #

Methods

from :: Elision -> Rep Elision x #

to :: Rep Elision x -> Elision #

Show Elision Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Elision Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Elision Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Elision Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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

Instances details
Generic Empty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Empty :: Type -> Type #

Methods

from :: Empty -> Rep Empty x #

to :: Rep Empty x -> Empty #

Show Empty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Empty -> ShowS #

show :: Empty -> String #

showList :: [Empty] -> ShowS #

EmitXml Empty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Empty -> XmlRep Source #

Eq Empty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Empty Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Empty = D1 ('MetaData "Empty" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic EmptyFont Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep EmptyFont :: Type -> Type #

Show EmptyFont Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml EmptyFont Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq EmptyFont Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep EmptyFont Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep EmptyFont = D1 ('MetaData "EmptyFont" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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, line-length, dashed-formatting, print-style and placement attributes.

Constructors

EmptyLine 

Fields

Instances

Instances details
Generic EmptyLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep EmptyLine :: Type -> Type #

Show EmptyLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml EmptyLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq EmptyLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep EmptyLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep EmptyLine = D1 ('MetaData "EmptyLine" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 "emptyLineLineLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LineLength)))) :*: ((S1 ('MetaSel ('Just "emptyLineDashLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "emptyLineSpaceLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))) :*: (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

Instances details
Generic EmptyPlacement Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep EmptyPlacement :: Type -> Type #

Show EmptyPlacement Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml EmptyPlacement Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq EmptyPlacement Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep EmptyPlacement Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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

data EmptyPlacementSmufl Source #

empty-placement-smufl (complex)

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

Instances

Instances details
Generic EmptyPlacementSmufl Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep EmptyPlacementSmufl :: Type -> Type #

Show EmptyPlacementSmufl Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml EmptyPlacementSmufl Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq EmptyPlacementSmufl Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep EmptyPlacementSmufl Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep EmptyPlacementSmufl = D1 ('MetaData "EmptyPlacementSmufl" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "EmptyPlacementSmufl" 'PrefixI 'True) (((S1 ('MetaSel ('Just "emptyPlacementSmuflDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "emptyPlacementSmuflDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 ('MetaSel ('Just "emptyPlacementSmuflRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "emptyPlacementSmuflRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "emptyPlacementSmuflFontFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CommaSeparatedText))))) :*: ((S1 ('MetaSel ('Just "emptyPlacementSmuflFontStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontStyle)) :*: (S1 ('MetaSel ('Just "emptyPlacementSmuflFontSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontSize)) :*: S1 ('MetaSel ('Just "emptyPlacementSmuflFontWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontWeight)))) :*: (S1 ('MetaSel ('Just "emptyPlacementSmuflColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)) :*: (S1 ('MetaSel ('Just "emptyPlacementSmuflPlacement") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AboveBelow)) :*: S1 ('MetaSel ('Just "emptyPlacementSmuflSmufl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SmuflGlyphName)))))))

data EmptyPrintObjectStyleAlign Source #

empty-print-object-style-align (complex)

The empty-print-style-align-object type represents an empty element with print-object and print-style-align attribute groups.

Instances

Instances details
Generic EmptyPrintObjectStyleAlign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep EmptyPrintObjectStyleAlign :: Type -> Type #

Show EmptyPrintObjectStyleAlign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml EmptyPrintObjectStyleAlign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq EmptyPrintObjectStyleAlign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep EmptyPrintObjectStyleAlign Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep EmptyPrintObjectStyleAlign = D1 ('MetaData "EmptyPrintObjectStyleAlign" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "EmptyPrintObjectStyleAlign" 'PrefixI 'True) (((S1 ('MetaSel ('Just "emptyPrintObjectStyleAlignPrintObject") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe YesNo)) :*: (S1 ('MetaSel ('Just "emptyPrintObjectStyleAlignDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "emptyPrintObjectStyleAlignDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)))) :*: (S1 ('MetaSel ('Just "emptyPrintObjectStyleAlignRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "emptyPrintObjectStyleAlignRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "emptyPrintObjectStyleAlignFontFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CommaSeparatedText))))) :*: ((S1 ('MetaSel ('Just "emptyPrintObjectStyleAlignFontStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontStyle)) :*: (S1 ('MetaSel ('Just "emptyPrintObjectStyleAlignFontSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontSize)) :*: S1 ('MetaSel ('Just "emptyPrintObjectStyleAlignFontWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontWeight)))) :*: (S1 ('MetaSel ('Just "emptyPrintObjectStyleAlignColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)) :*: (S1 ('MetaSel ('Just "emptyPrintObjectStyleAlignHalign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LeftCenterRight)) :*: S1 ('MetaSel ('Just "emptyPrintObjectStyleAlignValign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Valign)))))))

data EmptyPrintStyleAlignId Source #

empty-print-style-align-id (complex)

The empty-print-style-align-id type represents an empty element with print-style-align and optional-unique-id attribute groups.

Instances

Instances details
Generic EmptyPrintStyleAlignId Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep EmptyPrintStyleAlignId :: Type -> Type #

Show EmptyPrintStyleAlignId Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml EmptyPrintStyleAlignId Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq EmptyPrintStyleAlignId Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep EmptyPrintStyleAlignId Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep EmptyPrintStyleAlignId = D1 ('MetaData "EmptyPrintStyleAlignId" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "EmptyPrintStyleAlignId" 'PrefixI 'True) (((S1 ('MetaSel ('Just "emptyPrintStyleAlignIdDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "emptyPrintStyleAlignIdDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "emptyPrintStyleAlignIdRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)))) :*: (S1 ('MetaSel ('Just "emptyPrintStyleAlignIdRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "emptyPrintStyleAlignIdFontFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 ('MetaSel ('Just "emptyPrintStyleAlignIdFontStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontStyle))))) :*: ((S1 ('MetaSel ('Just "emptyPrintStyleAlignIdFontSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontSize)) :*: (S1 ('MetaSel ('Just "emptyPrintStyleAlignIdFontWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontWeight)) :*: S1 ('MetaSel ('Just "emptyPrintStyleAlignIdColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)))) :*: (S1 ('MetaSel ('Just "emptyPrintStyleAlignIdHalign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LeftCenterRight)) :*: (S1 ('MetaSel ('Just "emptyPrintStyleAlignIdValign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Valign)) :*: S1 ('MetaSel ('Just "emptyPrintStyleAlignIdId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)))))))

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

Instances details
Generic EmptyTrillSound Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep EmptyTrillSound :: Type -> Type #

Show EmptyTrillSound Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml EmptyTrillSound Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq EmptyTrillSound Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep EmptyTrillSound Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep EmptyTrillSound = D1 ('MetaData "EmptyTrillSound" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic Encoding Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Encoding :: Type -> Type #

Methods

from :: Encoding -> Rep Encoding x #

to :: Rep Encoding x -> Encoding #

Show Encoding Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Encoding Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Encoding Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Encoding Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Encoding = D1 ('MetaData "Encoding" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic Ending Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Ending :: Type -> Type #

Methods

from :: Ending -> Rep Ending x #

to :: Rep Ending x -> Ending #

Show Ending Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Ending Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Ending Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Ending Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Ending = D1 ('MetaData "Ending" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 lyric word extension / melisma lines as well as figured bass extensions. The optional type and position attributes are added in Version 3.0 to provide better formatting control.

Constructors

Extend 

Fields

Instances

Instances details
Generic Extend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Extend :: Type -> Type #

Methods

from :: Extend -> Rep Extend x #

to :: Rep Extend x -> Extend #

Show Extend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Extend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Extend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Extend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Extend = D1 ('MetaData "Extend" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Extend" 'PrefixI 'True) ((S1 ('MetaSel ('Just "extendType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe StartStopContinue)) :*: (S1 ('MetaSel ('Just "extendDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "extendDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)))) :*: (S1 ('MetaSel ('Just "extendRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "extendRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "extendColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color))))))

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

Instances details
Generic Feature Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Feature :: Type -> Type #

Methods

from :: Feature -> Rep Feature x #

to :: Rep Feature x -> Feature #

Show Feature Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Feature Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Feature Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Feature Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Feature = D1 ('MetaData "Feature" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic Fermata Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Fermata :: Type -> Type #

Methods

from :: Fermata -> Rep Fermata x #

to :: Rep Fermata x -> Fermata #

Show Fermata Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Fermata Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Fermata Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Fermata Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Fermata = D1 ('MetaData "Fermata" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Fermata" 'PrefixI 'True) (((S1 ('MetaSel ('Just "fermataFermataShape") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FermataShape) :*: (S1 ('MetaSel ('Just "fermataType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe UprightInverted)) :*: S1 ('MetaSel ('Just "fermataDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)))) :*: (S1 ('MetaSel ('Just "fermataDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "fermataRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "fermataRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 ('MetaSel ('Just "fermataFontFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: (S1 ('MetaSel ('Just "fermataFontStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontStyle)) :*: S1 ('MetaSel ('Just "fermataFontSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontSize)))) :*: (S1 ('MetaSel ('Just "fermataFontWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontWeight)) :*: (S1 ('MetaSel ('Just "fermataColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)) :*: S1 ('MetaSel ('Just "fermataId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)))))))

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

Instances details
Generic Figure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Figure :: Type -> Type #

Methods

from :: Figure -> Rep Figure x #

to :: Rep Figure x -> Figure #

Show Figure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Figure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Figure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Figure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Figure = D1 ('MetaData "Figure" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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)) :*: S1 ('MetaSel ('Just "figureEditorial") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Editorial)))))

mkFigure :: Editorial -> 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 (not a grace note or chord note) that follows in score order. The optional duration element is used to indicate changes of figures under a note.

Figures are ordered from top to bottom. The value of parentheses is "no" if not present.

Constructors

FiguredBass 

Fields

Instances

Instances details
Generic FiguredBass Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep FiguredBass :: Type -> Type #

Show FiguredBass Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml FiguredBass Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq FiguredBass Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep FiguredBass Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep FiguredBass = D1 ('MetaData "FiguredBass" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 "figuredBassId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID))) :*: (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

Instances details
Generic Fingering Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Fingering :: Type -> Type #

Show Fingering Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Fingering Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Fingering Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Fingering Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Fingering = D1 ('MetaData "Fingering" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic FirstFret Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep FirstFret :: Type -> Type #

Show FirstFret Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml FirstFret Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq FirstFret Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep FirstFret Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep FirstFret = D1 ('MetaData "FirstFret" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 FormattedSymbolId Source #

formatted-symbol-id (complex)

The formatted-symbol-id type represents a SMuFL musical symbol element with formatting and id attributes.

Instances

Instances details
Generic FormattedSymbolId Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep FormattedSymbolId :: Type -> Type #

Show FormattedSymbolId Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml FormattedSymbolId Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq FormattedSymbolId Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep FormattedSymbolId Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep FormattedSymbolId = D1 ('MetaData "FormattedSymbolId" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "FormattedSymbolId" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "formattedSymbolIdSmuflGlyphName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SmuflGlyphName) :*: S1 ('MetaSel ('Just "formattedSymbolIdJustify") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LeftCenterRight))) :*: (S1 ('MetaSel ('Just "formattedSymbolIdDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "formattedSymbolIdDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "formattedSymbolIdRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 ('MetaSel ('Just "formattedSymbolIdRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "formattedSymbolIdFontFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 ('MetaSel ('Just "formattedSymbolIdFontStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontStyle)))) :*: (S1 ('MetaSel ('Just "formattedSymbolIdFontSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontSize)) :*: (S1 ('MetaSel ('Just "formattedSymbolIdFontWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontWeight)) :*: S1 ('MetaSel ('Just "formattedSymbolIdColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)))))) :*: (((S1 ('MetaSel ('Just "formattedSymbolIdHalign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LeftCenterRight)) :*: S1 ('MetaSel ('Just "formattedSymbolIdValign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Valign))) :*: (S1 ('MetaSel ('Just "formattedSymbolIdUnderline") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NumberOfLines)) :*: (S1 ('MetaSel ('Just "formattedSymbolIdOverline") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NumberOfLines)) :*: S1 ('MetaSel ('Just "formattedSymbolIdLineThrough") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NumberOfLines))))) :*: ((S1 ('MetaSel ('Just "formattedSymbolIdRotation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe RotationDegrees)) :*: (S1 ('MetaSel ('Just "formattedSymbolIdLetterSpacing") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NumberOrNormal)) :*: S1 ('MetaSel ('Just "formattedSymbolIdLineHeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NumberOrNormal)))) :*: (S1 ('MetaSel ('Just "formattedSymbolIdDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TextDirection)) :*: (S1 ('MetaSel ('Just "formattedSymbolIdEnclosure") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe EnclosureShape)) :*: S1 ('MetaSel ('Just "formattedSymbolIdId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID))))))))

data FormattedText Source #

formatted-text (complex)

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

Constructors

FormattedText 

Instances

Instances details
Generic FormattedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep FormattedText :: Type -> Type #

Show FormattedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml FormattedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq FormattedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep FormattedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep FormattedText = D1 ('MetaData "FormattedText" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 "formattedTextSpace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Space)) :*: (S1 ('MetaSel ('Just "formattedTextJustify") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LeftCenterRight)) :*: 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 "formattedTextHalign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LeftCenterRight)))) :*: (S1 ('MetaSel ('Just "formattedTextValign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Valign)) :*: (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)) :*: S1 ('MetaSel ('Just "formattedTextEnclosure") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe EnclosureShape))))))))

data FormattedTextId Source #

formatted-text-id (complex)

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

Instances

Instances details
Generic FormattedTextId Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep FormattedTextId :: Type -> Type #

Show FormattedTextId Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml FormattedTextId Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq FormattedTextId Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep FormattedTextId Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep FormattedTextId = D1 ('MetaData "FormattedTextId" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "FormattedTextId" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "formattedTextIdString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Just "formattedTextIdLang") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Lang)) :*: S1 ('MetaSel ('Just "formattedTextIdSpace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Space)))) :*: (S1 ('MetaSel ('Just "formattedTextIdJustify") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LeftCenterRight)) :*: (S1 ('MetaSel ('Just "formattedTextIdDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "formattedTextIdDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 ('MetaSel ('Just "formattedTextIdRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "formattedTextIdRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "formattedTextIdFontFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CommaSeparatedText)))) :*: (S1 ('MetaSel ('Just "formattedTextIdFontStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontStyle)) :*: (S1 ('MetaSel ('Just "formattedTextIdFontSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontSize)) :*: S1 ('MetaSel ('Just "formattedTextIdFontWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontWeight)))))) :*: (((S1 ('MetaSel ('Just "formattedTextIdColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)) :*: (S1 ('MetaSel ('Just "formattedTextIdHalign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LeftCenterRight)) :*: S1 ('MetaSel ('Just "formattedTextIdValign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Valign)))) :*: (S1 ('MetaSel ('Just "formattedTextIdUnderline") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NumberOfLines)) :*: (S1 ('MetaSel ('Just "formattedTextIdOverline") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NumberOfLines)) :*: S1 ('MetaSel ('Just "formattedTextIdLineThrough") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NumberOfLines))))) :*: ((S1 ('MetaSel ('Just "formattedTextIdRotation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe RotationDegrees)) :*: (S1 ('MetaSel ('Just "formattedTextIdLetterSpacing") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NumberOrNormal)) :*: S1 ('MetaSel ('Just "formattedTextIdLineHeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NumberOrNormal)))) :*: (S1 ('MetaSel ('Just "formattedTextIdDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TextDirection)) :*: (S1 ('MetaSel ('Just "formattedTextIdEnclosure") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe EnclosureShape)) :*: S1 ('MetaSel ('Just "formattedTextIdId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID))))))))

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 or mid-measure changes in the divisions value.

Instances

Instances details
Generic Forward Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Forward :: Type -> Type #

Methods

from :: Forward -> Rep Forward x #

to :: Rep Forward x -> Forward #

Show Forward Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Forward Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Forward Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Forward Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Forward = D1 ('MetaData "Forward" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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. The frame type's unplayed attribute indicates what to display above a string that has no associated frame-note element. Typical values are x and the empty string. If the attribute is not present, the display of the unplayed string is application-defined.

Constructors

Frame 

Fields

Instances

Instances details
Generic Frame Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Frame :: Type -> Type #

Methods

from :: Frame -> Rep Frame x #

to :: Rep Frame x -> Frame #

Show Frame Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Frame -> ShowS #

show :: Frame -> String #

showList :: [Frame] -> ShowS #

EmitXml Frame Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Frame -> XmlRep Source #

Eq Frame Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Frame Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Frame = D1 ('MetaData "Frame" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 "frameUnplayed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Token)))) :*: ((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 ValignImage)) :*: S1 ('MetaSel ('Just "frameId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)))) :*: ((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

Instances details
Generic FrameNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep FrameNote :: Type -> Type #

Show FrameNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml FrameNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq FrameNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep FrameNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep FrameNote = D1 ('MetaData "FrameNote" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic Fret Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Fret :: Type -> Type #

Methods

from :: Fret -> Rep Fret x #

to :: Rep Fret x -> Fret #

Show Fret Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Fret -> ShowS #

show :: Fret -> String #

showList :: [Fret] -> ShowS #

EmitXml Fret Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Fret -> XmlRep Source #

Eq Fret Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Fret Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

mkFret :: NonNegativeInteger -> Fret Source #

Smart constructor for Fret

data Glass Source #

glass (complex)

The glass type represents pictograms for glass percussion instruments. The smufl attribute is used to distinguish different SMuFL glyphs for wind chimes in the chimes pictograms range, including those made of materials other than glass.

Constructors

Glass 

Fields

Instances

Instances details
Generic Glass Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Glass :: Type -> Type #

Methods

from :: Glass -> Rep Glass x #

to :: Rep Glass x -> Glass #

Show Glass Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Glass -> ShowS #

show :: Glass -> String #

showList :: [Glass] -> ShowS #

EmitXml Glass Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Glass -> XmlRep Source #

Eq Glass Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Glass Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Glass = D1 ('MetaData "Glass" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Glass" 'PrefixI 'True) (S1 ('MetaSel ('Just "glassGlassValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlassValue) :*: S1 ('MetaSel ('Just "glassSmufl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SmuflPictogramGlyphName))))

mkGlass :: GlassValue -> Glass Source #

Smart constructor for Glass

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

Instances details
Generic Glissando Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Glissando :: Type -> Type #

Show Glissando Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Glissando Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Glissando Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Glissando Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Glissando = D1 ('MetaData "Glissando" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 "glissandoDashLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "glissandoSpaceLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))) :*: (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)) :*: S1 ('MetaSel ('Just "glissandoId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)))))))

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

Smart constructor for Glissando

data Glyph Source #

glyph (complex)

The glyph element represents what SMuFL glyph should be used for different variations of symbols that are semantically identical. The type attribute specifies what type of glyph is being defined. The element value specifies what SMuFL glyph to use, including recommended stylistic alternates. The SMuFL glyph name should match the type. For instance, a type of quarter-rest would use values restQuarter, restQuarterOld, or restQuarterZ. A type of g-clef-ottava-bassa would use values gClef8vb, gClef8vbOld, or gClef8vbCClef. A type of octave-shift-up-8 would use values ottava, ottavaBassa, ottavaBassaBa, ottavaBassaVb, or octaveBassa.

Constructors

Glyph 

Fields

Instances

Instances details
Generic Glyph Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Glyph :: Type -> Type #

Methods

from :: Glyph -> Rep Glyph x #

to :: Rep Glyph x -> Glyph #

Show Glyph Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Glyph -> ShowS #

show :: Glyph -> String #

showList :: [Glyph] -> ShowS #

EmitXml Glyph Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Glyph -> XmlRep Source #

Eq Glyph Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Glyph Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Glyph = D1 ('MetaData "Glyph" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Glyph" 'PrefixI 'True) (S1 ('MetaSel ('Just "glyphSmuflGlyphName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SmuflGlyphName) :*: S1 ('MetaSel ('Just "cmpglyphType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlyphType)))

mkGlyph :: SmuflGlyphName -> GlyphType -> Glyph Source #

Smart constructor for Glyph

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. The steal-time-previous attribute indicates the percentage of time to steal from the previous note for the grace note. The steal-time-following attribute indicates the percentage of time to steal from the following note for the grace note, as for appoggiaturas. The make-time attribute indicates to make time, not steal time; the units are in real-time divisions for the grace note.

Constructors

Grace 

Fields

Instances

Instances details
Generic Grace Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Grace :: Type -> Type #

Methods

from :: Grace -> Rep Grace x #

to :: Rep Grace x -> Grace #

Show Grace Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Grace -> ShowS #

show :: Grace -> String #

showList :: [Grace] -> ShowS #

EmitXml Grace Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Grace -> XmlRep Source #

Eq Grace Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Grace Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Grace = D1 ('MetaData "Grace" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic GroupBarline Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep GroupBarline :: Type -> Type #

Show GroupBarline Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml GroupBarline Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq GroupBarline Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep GroupBarline Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep GroupBarline = D1 ('MetaData "GroupBarline" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic GroupName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep GroupName :: Type -> Type #

Show GroupName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml GroupName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq GroupName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep GroupName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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

mkGroupName :: String -> GroupName Source #

Smart constructor for GroupName

data GroupSymbol Source #

group-symbol (complex)

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

Constructors

GroupSymbol 

Fields

Instances

Instances details
Generic GroupSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep GroupSymbol :: Type -> Type #

Show GroupSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml GroupSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq GroupSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep GroupSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep GroupSymbol = D1 ('MetaData "GroupSymbol" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic Grouping Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Grouping :: Type -> Type #

Methods

from :: Grouping -> Rep Grouping x #

to :: Rep Grouping x -> Grouping #

Show Grouping Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Grouping Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Grouping Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Grouping Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Grouping = D1 ('MetaData "Grouping" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 "groupingId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)) :*: 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

Instances details
Generic HammerOnPullOff Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep HammerOnPullOff :: Type -> Type #

Show HammerOnPullOff Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml HammerOnPullOff Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq HammerOnPullOff Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep HammerOnPullOff Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep HammerOnPullOff = D1 ('MetaData "HammerOnPullOff" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 Handbell Source #

handbell (complex)

The handbell element represents notation for various techniques used in handbell and handchime music.

Constructors

Handbell 

Fields

Instances

Instances details
Generic Handbell Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Handbell :: Type -> Type #

Methods

from :: Handbell -> Rep Handbell x #

to :: Rep Handbell x -> Handbell #

Show Handbell Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Handbell Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Handbell Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Handbell Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Handbell = D1 ('MetaData "Handbell" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Handbell" 'PrefixI 'True) (((S1 ('MetaSel ('Just "handbellHandbellValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HandbellValue) :*: S1 ('MetaSel ('Just "handbellDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 ('MetaSel ('Just "handbellDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "handbellRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "handbellRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 ('MetaSel ('Just "handbellFontFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: (S1 ('MetaSel ('Just "handbellFontStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontStyle)) :*: S1 ('MetaSel ('Just "handbellFontSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontSize)))) :*: (S1 ('MetaSel ('Just "handbellFontWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontWeight)) :*: (S1 ('MetaSel ('Just "handbellColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)) :*: S1 ('MetaSel ('Just "handbellPlacement") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AboveBelow)))))))

mkHandbell :: HandbellValue -> Handbell Source #

Smart constructor for Handbell

data HarmonClosed Source #

harmon-closed (complex)

The harmon-closed type represents whether the harmon mute is closed, open, or half-open. The optional location attribute indicates which portion of the symbol is filled in when the element value is half.

Instances

Instances details
Generic HarmonClosed Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep HarmonClosed :: Type -> Type #

Show HarmonClosed Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml HarmonClosed Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq HarmonClosed Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep HarmonClosed Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep HarmonClosed = D1 ('MetaData "HarmonClosed" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "HarmonClosed" 'PrefixI 'True) (S1 ('MetaSel ('Just "harmonClosedHarmonClosedValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HarmonClosedValue) :*: S1 ('MetaSel ('Just "harmonClosedLocation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe HarmonClosedLocation))))

data HarmonMute Source #

harmon-mute (complex)

The harmon-mute type represents the symbols used for harmon mutes in brass notation.

Constructors

HarmonMute 

Fields

Instances

Instances details
Generic HarmonMute Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep HarmonMute :: Type -> Type #

Show HarmonMute Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml HarmonMute Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq HarmonMute Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep HarmonMute Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep HarmonMute = D1 ('MetaData "HarmonMute" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "HarmonMute" 'PrefixI 'True) (((S1 ('MetaSel ('Just "harmonMuteDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "harmonMuteDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 ('MetaSel ('Just "harmonMuteRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "harmonMuteRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "harmonMuteFontFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CommaSeparatedText))))) :*: ((S1 ('MetaSel ('Just "harmonMuteFontStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontStyle)) :*: (S1 ('MetaSel ('Just "harmonMuteFontSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontSize)) :*: S1 ('MetaSel ('Just "harmonMuteFontWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontWeight)))) :*: (S1 ('MetaSel ('Just "harmonMuteColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)) :*: (S1 ('MetaSel ('Just "harmonMutePlacement") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AboveBelow)) :*: S1 ('MetaSel ('Just "harmonMuteHarmonClosed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HarmonClosed))))))

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

Instances details
Generic Harmonic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Harmonic :: Type -> Type #

Methods

from :: Harmonic -> Rep Harmonic x #

to :: Rep Harmonic x -> Harmonic #

Show Harmonic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Harmonic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Harmonic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Harmonic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Harmonic = D1 ('MetaData "Harmonic" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic Harmony Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Harmony :: Type -> Type #

Methods

from :: Harmony -> Rep Harmony x #

to :: Rep Harmony x -> Harmony #

Show Harmony Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Harmony Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Harmony Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Harmony Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Harmony = D1 ('MetaData "Harmony" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 "harmonyId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID))))) :*: ((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

Instances details
Generic HarpPedals Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep HarpPedals :: Type -> Type #

Show HarpPedals Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml HarpPedals Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq HarpPedals Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep HarpPedals Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep HarpPedals = D1 ('MetaData "HarpPedals" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "HarpPedals" 'PrefixI 'True) (((S1 ('MetaSel ('Just "harpPedalsDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "harpPedalsDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "harpPedalsRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)))) :*: (S1 ('MetaSel ('Just "harpPedalsRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "harpPedalsFontFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 ('MetaSel ('Just "harpPedalsFontStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontStyle))))) :*: ((S1 ('MetaSel ('Just "harpPedalsFontSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontSize)) :*: (S1 ('MetaSel ('Just "harpPedalsFontWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontWeight)) :*: S1 ('MetaSel ('Just "harpPedalsColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)))) :*: ((S1 ('MetaSel ('Just "harpPedalsHalign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LeftCenterRight)) :*: S1 ('MetaSel ('Just "harpPedalsValign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Valign))) :*: (S1 ('MetaSel ('Just "harpPedalsId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)) :*: S1 ('MetaSel ('Just "harpPedalsPedalTuning") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PedalTuning]))))))

mkHarpPedals :: HarpPedals Source #

Smart constructor for HarpPedals

data HeelToe Source #

heel-toe (complex)

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

Constructors

HeelToe 

Fields

Instances

Instances details
Generic HeelToe Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep HeelToe :: Type -> Type #

Methods

from :: HeelToe -> Rep HeelToe x #

to :: Rep HeelToe x -> HeelToe #

Show HeelToe Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml HeelToe Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq HeelToe Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep HeelToe Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep HeelToe = D1 ('MetaData "HeelToe" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 Hole Source #

hole (complex)

The hole type represents the symbols used for woodwind and brass fingerings as well as other notations.

Constructors

Hole 

Fields

Instances

Instances details
Generic Hole Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Hole :: Type -> Type #

Methods

from :: Hole -> Rep Hole x #

to :: Rep Hole x -> Hole #

Show Hole Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Hole -> ShowS #

show :: Hole -> String #

showList :: [Hole] -> ShowS #

EmitXml Hole Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Hole -> XmlRep Source #

Eq Hole Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Hole Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Hole = D1 ('MetaData "Hole" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Hole" 'PrefixI 'True) (((S1 ('MetaSel ('Just "holeDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "holeDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "holeRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)))) :*: (S1 ('MetaSel ('Just "holeRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "holeFontFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 ('MetaSel ('Just "holeFontStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontStyle))))) :*: ((S1 ('MetaSel ('Just "holeFontSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontSize)) :*: (S1 ('MetaSel ('Just "holeFontWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontWeight)) :*: S1 ('MetaSel ('Just "holeColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)))) :*: ((S1 ('MetaSel ('Just "holePlacement") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AboveBelow)) :*: S1 ('MetaSel ('Just "holeHoleType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))) :*: (S1 ('MetaSel ('Just "holeHoleClosed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HoleClosed) :*: S1 ('MetaSel ('Just "holeHoleShape") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)))))))

mkHole :: HoleClosed -> Hole Source #

Smart constructor for Hole

data HoleClosed Source #

hole-closed (complex)

The hole-closed type represents whether the hole is closed, open, or half-open. The optional location attribute indicates which portion of the hole is filled in when the element value is half.

Instances

Instances details
Generic HoleClosed Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep HoleClosed :: Type -> Type #

Show HoleClosed Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml HoleClosed Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq HoleClosed Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep HoleClosed Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep HoleClosed = D1 ('MetaData "HoleClosed" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "HoleClosed" 'PrefixI 'True) (S1 ('MetaSel ('Just "holeClosedHoleClosedValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HoleClosedValue) :*: S1 ('MetaSel ('Just "holeClosedLocation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe HoleClosedLocation))))

data HorizontalTurn Source #

horizontal-turn (complex)

The horizontal-turn type represents turn elements that are horizontal rather than vertical. These are empty elements with print-style, placement, trill-sound, and slash attributes. If the slash attribute is yes, then a vertical line is used to slash the turn; it is no by default.

Constructors

HorizontalTurn 

Fields

Instances

Instances details
Generic HorizontalTurn Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep HorizontalTurn :: Type -> Type #

Show HorizontalTurn Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml HorizontalTurn Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq HorizontalTurn Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep HorizontalTurn Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep HorizontalTurn = D1 ('MetaData "HorizontalTurn" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "HorizontalTurn" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "horizontalTurnSlash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 ('MetaSel ('Just "horizontalTurnDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 ('MetaSel ('Just "horizontalTurnDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "horizontalTurnRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)))) :*: ((S1 ('MetaSel ('Just "horizontalTurnRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "horizontalTurnFontFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CommaSeparatedText))) :*: (S1 ('MetaSel ('Just "horizontalTurnFontStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontStyle)) :*: (S1 ('MetaSel ('Just "horizontalTurnFontSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontSize)) :*: S1 ('MetaSel ('Just "horizontalTurnFontWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontWeight)))))) :*: (((S1 ('MetaSel ('Just "horizontalTurnColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)) :*: S1 ('MetaSel ('Just "horizontalTurnPlacement") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AboveBelow))) :*: (S1 ('MetaSel ('Just "horizontalTurnStartNote") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe StartNote)) :*: S1 ('MetaSel ('Just "horizontalTurnTrillStep") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TrillStep)))) :*: ((S1 ('MetaSel ('Just "horizontalTurnTwoNoteTurn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TwoNoteTurn)) :*: S1 ('MetaSel ('Just "horizontalTurnAccelerate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe YesNo))) :*: (S1 ('MetaSel ('Just "horizontalTurnBeats") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TrillBeats)) :*: (S1 ('MetaSel ('Just "horizontalTurnSecondBeat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Percent)) :*: S1 ('MetaSel ('Just "horizontalTurnLastBeat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Percent))))))))

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

Instances details
Generic Identification Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Identification :: Type -> Type #

Show Identification Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Identification Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Identification Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Identification Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Identification = D1 ('MetaData "Identification" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic Image Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Image :: Type -> Type #

Methods

from :: Image -> Rep Image x #

to :: Rep Image x -> Image #

Show Image Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Image -> ShowS #

show :: Image -> String #

showList :: [Image] -> ShowS #

EmitXml Image Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Image -> XmlRep Source #

Eq Image Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Image Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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

Instances details
Generic Instrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Instrument :: Type -> Type #

Show Instrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Instrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Instrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Instrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Instrument = D1 ('MetaData "Instrument" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Instrument" 'PrefixI 'True) (S1 ('MetaSel ('Just "instrumentId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IDREF)))

mkInstrument :: IDREF -> Instrument Source #

Smart constructor for Instrument

data Interchangeable Source #

interchangeable (complex)

The interchangeable type is used to represent the second in a pair of interchangeable dual time signatures, such as the 68 in 34 (6/8). A separate symbol attribute value is available compared to the time element's symbol attribute, which applies to the first of the dual time signatures.

Instances

Instances details
Generic Interchangeable Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Interchangeable :: Type -> Type #

Show Interchangeable Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Interchangeable Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Interchangeable Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Interchangeable Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Interchangeable = D1 ('MetaData "Interchangeable" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Interchangeable" 'PrefixI 'True) ((S1 ('MetaSel ('Just "interchangeableSymbol") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TimeSymbol)) :*: S1 ('MetaSel ('Just "interchangeableSeparator") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TimeSeparator))) :*: (S1 ('MetaSel ('Just "interchangeableTimeRelation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TimeRelation)) :*: S1 ('MetaSel ('Just "interchangeableTimeSignature") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TimeSignature]))))

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

Instances details
Generic Inversion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Inversion :: Type -> Type #

Show Inversion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Inversion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Inversion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Inversion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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. Key signatures appear at the start of each system unless the print-object attribute has been set to "no".

Constructors

Key 

Fields

Instances

Instances details
Generic Key Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Key :: Type -> Type #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

Show Key Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

EmitXml Key Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Key -> XmlRep Source #

Eq Key Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Key Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Key = D1 ('MetaData "Key" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 "keyId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID))) :*: (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 KeyAccidental Source #

key-accidental (complex)

The key-accidental type indicates the accidental to be displayed in a non-traditional key signature, represented in the same manner as the accidental type without the formatting attributes.

Instances

Instances details
Generic KeyAccidental Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep KeyAccidental :: Type -> Type #

Show KeyAccidental Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml KeyAccidental Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq KeyAccidental Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep KeyAccidental Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep KeyAccidental = D1 ('MetaData "KeyAccidental" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "KeyAccidental" 'PrefixI 'True) (S1 ('MetaSel ('Just "keyAccidentalAccidentalValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccidentalValue) :*: S1 ('MetaSel ('Just "keyAccidentalSmufl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SmuflAccidentalGlyphName))))

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 the canceling key signature specified by the cancel element in the parent key element. The cancel attribute cannot be set to yes if there is no corresponding cancel element within the parent key element. It is no by default.

Constructors

KeyOctave 

Fields

Instances

Instances details
Generic KeyOctave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep KeyOctave :: Type -> Type #

Show KeyOctave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml KeyOctave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq KeyOctave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep KeyOctave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep KeyOctave = D1 ('MetaData "KeyOctave" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

For the major-minor kind, only the minor symbol is used when use-symbols is yes. The major symbol is set using the symbol attribute in the degree-value element. The corresponding degree-alter value will usually be 0 in this case.

The text attribute describes how the kind should be spelled in a score. If use-symbols is yes, the value of the text attribute follows the symbol. 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

Instances details
Generic Kind Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Kind :: Type -> Type #

Methods

from :: Kind -> Rep Kind x #

to :: Rep Kind x -> Kind #

Show Kind Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Kind -> ShowS #

show :: Kind -> String #

showList :: [Kind] -> ShowS #

EmitXml Kind Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Kind -> XmlRep Source #

Eq Kind Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Kind Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Kind = D1 ('MetaData "Kind" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic Level Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Level :: Type -> Type #

Methods

from :: Level -> Rep Level x #

to :: Rep Level x -> Level #

Show Level Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Level -> ShowS #

show :: Level -> String #

showList :: [Level] -> ShowS #

EmitXml Level Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Level -> XmlRep Source #

Eq Level Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Level Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Level = D1 ('MetaData "Level" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Level" 'PrefixI 'True) ((S1 ('MetaSel ('Just "levelString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "levelReference") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe YesNo))) :*: (S1 ('MetaSel ('Just "levelParentheses") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe YesNo)) :*: (S1 ('MetaSel ('Just "levelBracket") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 ('MetaSel ('Just "levelSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SymbolSize))))))

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

Instances details
Generic LineWidth Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep LineWidth :: Type -> Type #

Show LineWidth Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml LineWidth Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq LineWidth Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep LineWidth Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep LineWidth = D1 ('MetaData "LineWidth" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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. If a relative link is used within a document that is part of a compressed MusicXML file, the link is relative to the root folder of the zip file.

Constructors

Link 

Fields

Instances

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 XSD is more strict than the 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. The print-object attribute can override a note's print-lyric attribute in cases where only some lyrics on a note are printed, as when lyrics for later verses are printed in a block of text rather than with each note. The time-only attribute precisely specifies which lyrics are to be sung which time through a repeated section.

Constructors

Lyric 

Fields

Instances

Instances details
Generic Lyric Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Lyric :: Type -> Type #

Methods

from :: Lyric -> Rep Lyric x #

to :: Rep Lyric x -> Lyric #

Show Lyric Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Lyric -> ShowS #

show :: Lyric -> String #

showList :: [Lyric] -> ShowS #

EmitXml Lyric Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Lyric -> XmlRep Source #

Eq Lyric Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Lyric Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Lyric = D1 ('MetaData "Lyric" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 "lyricTimeOnly") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TimeOnly)) :*: 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 "lyricPrintObject") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 ('MetaSel ('Just "lyricId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)))) :*: ((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

Instances details
Generic LyricFont Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep LyricFont :: Type -> Type #

Show LyricFont Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml LyricFont Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq LyricFont Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep LyricFont Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep LyricFont = D1 ('MetaData "LyricFont" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "LyricFont" 'PrefixI 'True) ((S1 ('MetaSel ('Just "lyricFontNumber") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NMTOKEN)) :*: (S1 ('MetaSel ('Just "lyricFontName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Token)) :*: S1 ('MetaSel ('Just "lyricFontFontFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CommaSeparatedText)))) :*: (S1 ('MetaSel ('Just "lyricFontFontStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontStyle)) :*: (S1 ('MetaSel ('Just "lyricFontFontSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontSize)) :*: S1 ('MetaSel ('Just "lyricFontFontWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontWeight))))))

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

Instances details
Generic LyricLanguage Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep LyricLanguage :: Type -> Type #

Show LyricLanguage Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml LyricLanguage Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq LyricLanguage Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep LyricLanguage Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep LyricLanguage = D1 ('MetaData "LyricLanguage" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic Measure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Measure :: Type -> Type #

Methods

from :: Measure -> Rep Measure x #

to :: Rep Measure x -> Measure #

Show Measure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Measure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Measure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Measure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Measure = D1 ('MetaData "Measure" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Measure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "measureNumber") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Token) :*: (S1 ('MetaSel ('Just "cmpmeasureText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MeasureText)) :*: 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 "measureId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)) :*: 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

Instances details
Generic CmpMeasure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep CmpMeasure :: Type -> Type #

Show CmpMeasure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml CmpMeasure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq CmpMeasure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep CmpMeasure Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep CmpMeasure = D1 ('MetaData "CmpMeasure" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "CmpMeasure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "cmpmeasureNumber") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Token) :*: (S1 ('MetaSel ('Just "cmpmeasureText1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MeasureText)) :*: 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 "cmpmeasureId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)) :*: 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

Instances details
Generic MeasureLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep MeasureLayout :: Type -> Type #

Show MeasureLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml MeasureLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq MeasureLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MeasureLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MeasureLayout = D1 ('MetaData "MeasureLayout" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic MeasureNumbering Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep MeasureNumbering :: Type -> Type #

Show MeasureNumbering Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml MeasureNumbering Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq MeasureNumbering Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MeasureNumbering Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MeasureNumbering = D1 ('MetaData "MeasureNumbering" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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)) :*: (S1 ('MetaSel ('Just "measureNumberingHalign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LeftCenterRight)) :*: S1 ('MetaSel ('Just "measureNumberingValign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Valign)))))))

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

Instances details
Generic MeasureRepeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep MeasureRepeat :: Type -> Type #

Show MeasureRepeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml MeasureRepeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq MeasureRepeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MeasureRepeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MeasureRepeat = D1 ('MetaData "MeasureRepeat" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic MeasureStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep MeasureStyle :: Type -> Type #

Show MeasureStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml MeasureStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq MeasureStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MeasureStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MeasureStyle = D1 ('MetaData "MeasureStyle" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "MeasureStyle" 'PrefixI 'True) (((S1 ('MetaSel ('Just "measureStyleNumber") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe StaffNumber)) :*: S1 ('MetaSel ('Just "measureStyleFontFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CommaSeparatedText))) :*: (S1 ('MetaSel ('Just "measureStyleFontStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontStyle)) :*: S1 ('MetaSel ('Just "measureStyleFontSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontSize)))) :*: ((S1 ('MetaSel ('Just "measureStyleFontWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontWeight)) :*: S1 ('MetaSel ('Just "measureStyleColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color))) :*: (S1 ('MetaSel ('Just "measureStyleId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)) :*: S1 ('MetaSel ('Just "measureStyleMeasureStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChxMeasureStyle)))))

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 metric modulations and other metric relationships, such as swing tempo marks where two eighths are equated to a quarter note / eighth note triplet. Tied notes can be represented in both types of metronome marks by using the beat-unit-tied and metronome-tied elements. 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

Instances details
Generic Metronome Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Metronome :: Type -> Type #

Show Metronome Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Metronome Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Metronome Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Metronome Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Metronome = D1 ('MetaData "Metronome" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 "metronomeHalign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LeftCenterRight)))) :*: ((S1 ('MetaSel ('Just "metronomeValign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Valign)) :*: S1 ('MetaSel ('Just "metronomeJustify") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LeftCenterRight))) :*: (S1 ('MetaSel ('Just "metronomeId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)) :*: 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

Instances details
Generic MetronomeBeam Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep MetronomeBeam :: Type -> Type #

Show MetronomeBeam Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml MetronomeBeam Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq MetronomeBeam Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MetronomeBeam Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MetronomeBeam = D1 ('MetaData "MetronomeBeam" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic MetronomeNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep MetronomeNote :: Type -> Type #

Show MetronomeNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml MetronomeNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq MetronomeNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MetronomeNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MetronomeNote = D1 ('MetaData "MetronomeNote" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 "metronomeNoteMetronomeTied") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MetronomeTied)) :*: S1 ('MetaSel ('Just "metronomeNoteMetronomeTuplet") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MetronomeTuplet))))))

data MetronomeTied Source #

metronome-tied (complex)

The metronome-tied indicates the presence of a tie within a metric relationship mark. As with the tied element, both the start and stop of the tie should be specified, in this case within separate metronome-note elements.

Constructors

MetronomeTied 

Fields

Instances

Instances details
Generic MetronomeTied Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep MetronomeTied :: Type -> Type #

Show MetronomeTied Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml MetronomeTied Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq MetronomeTied Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MetronomeTied Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MetronomeTied = D1 ('MetaData "MetronomeTied" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "MetronomeTied" 'PrefixI 'True) (S1 ('MetaSel ('Just "metronomeTiedType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StartStop)))

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

Instances details
Generic MetronomeTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep MetronomeTuplet :: Type -> Type #

Show MetronomeTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml MetronomeTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq MetronomeTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MetronomeTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MetronomeTuplet = D1 ('MetaData "MetronomeTuplet" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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. Unlike the DeviceName meta event, there can be multiple midi-device elements per MusicXML part starting in MusicXML 3.0. The optional id attribute refers to the score-instrument assigned to this device. If missing, the device assignment affects all score-instrument elements in the score-part.

Constructors

MidiDevice 

Fields

Instances

Instances details
Generic MidiDevice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep MidiDevice :: Type -> Type #

Show MidiDevice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml MidiDevice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq MidiDevice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MidiDevice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MidiDevice = D1 ('MetaData "MidiDevice" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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)) :*: S1 ('MetaSel ('Just "midiDeviceId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe IDREF)))))

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

Instances details
Generic MidiInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep MidiInstrument :: Type -> Type #

Show MidiInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml MidiInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq MidiInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MidiInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MidiInstrument = D1 ('MetaData "MidiInstrument" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "MidiInstrument" 'PrefixI 'True) (((S1 ('MetaSel ('Just "midiInstrumentId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IDREF) :*: S1 ('MetaSel ('Just "midiInstrumentMidiChannel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Midi16))) :*: (S1 ('MetaSel ('Just "midiInstrumentMidiName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Just "midiInstrumentMidiBank") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Midi16384)))) :*: ((S1 ('MetaSel ('Just "midiInstrumentMidiProgram") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Midi128)) :*: S1 ('MetaSel ('Just "midiInstrumentMidiUnpitched") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Midi128))) :*: (S1 ('MetaSel ('Just "midiInstrumentVolume") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Percent)) :*: (S1 ('MetaSel ('Just "midiInstrumentPan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe RotationDegrees)) :*: S1 ('MetaSel ('Just "midiInstrumentElevation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe RotationDegrees)))))))

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

Instances details
Generic Miscellaneous Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Miscellaneous :: Type -> Type #

Show Miscellaneous Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Miscellaneous Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Miscellaneous Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Miscellaneous Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Miscellaneous = D1 ('MetaData "Miscellaneous" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic MiscellaneousField Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep MiscellaneousField :: Type -> Type #

Show MiscellaneousField Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml MiscellaneousField Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq MiscellaneousField Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MiscellaneousField Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MiscellaneousField = D1 ('MetaData "MiscellaneousField" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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. The approach and departure attributes are used for compound ornaments, indicating how the beginning and ending of the ornament look relative to the main part of the mordent.

Constructors

Mordent 

Fields

Instances

Instances details
Generic Mordent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Mordent :: Type -> Type #

Methods

from :: Mordent -> Rep Mordent x #

to :: Rep Mordent x -> Mordent #

Show Mordent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Mordent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Mordent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Mordent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Mordent = D1 ('MetaData "Mordent" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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))) :*: (S1 ('MetaSel ('Just "mordentApproach") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AboveBelow)) :*: S1 ('MetaSel ('Just "mordentDeparture") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AboveBelow)))))

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.

Instances

Instances details
Generic MultipleRest Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep MultipleRest :: Type -> Type #

Show MultipleRest Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml MultipleRest Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq MultipleRest Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MultipleRest Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MultipleRest = D1 ('MetaData "MultipleRest" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic NameDisplay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep NameDisplay :: Type -> Type #

Show NameDisplay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml NameDisplay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq NameDisplay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NameDisplay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NameDisplay = D1 ('MetaData "NameDisplay" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic NonArpeggiate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep NonArpeggiate :: Type -> Type #

Show NonArpeggiate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml NonArpeggiate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq NonArpeggiate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NonArpeggiate Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NonArpeggiate = D1 ('MetaData "NonArpeggiate" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "NonArpeggiate" 'PrefixI 'True) (((S1 ('MetaSel ('Just "nonArpeggiateType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TopBottom) :*: S1 ('MetaSel ('Just "nonArpeggiateNumber") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NumberLevel))) :*: (S1 ('MetaSel ('Just "nonArpeggiateDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "nonArpeggiateDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)))) :*: ((S1 ('MetaSel ('Just "nonArpeggiateRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "nonArpeggiateRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 ('MetaSel ('Just "nonArpeggiatePlacement") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AboveBelow)) :*: (S1 ('MetaSel ('Just "nonArpeggiateColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)) :*: S1 ('MetaSel ('Just "nonArpeggiateId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)))))))

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 print-object attribute, added in Version 3.0, allows notations to represent details of performance technique, such as fingerings, without having them appear in the score.

Constructors

Notations 

Instances

Instances details
Generic Notations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Notations :: Type -> Type #

Show Notations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Notations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Notations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Notations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Notations = D1 ('MetaData "Notations" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Notations" 'PrefixI 'True) ((S1 ('MetaSel ('Just "notationsPrintObject") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 ('MetaSel ('Just "notationsId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID))) :*: (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 print-leger attribute is used to indicate whether leger lines are printed. Notes without leger lines are used to indicate indeterminate high and low notes. By default, it is set to yes. If print-object is set to no, print-leger is interpreted to also be set to no if not present. This attribute is ignored for rests.

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 starting 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. The attack and release attributes are independent of each other. The attack attribute only changes the starting time of a note, and the release attribute only changes the stopping time of a note.

If a note is played only particular times through a repeat, the time-only attribute shows which times 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

Instances details
Generic Note Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Note :: Type -> Type #

Methods

from :: Note -> Rep Note x #

to :: Rep Note x -> Note #

Show Note Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Note -> ShowS #

show :: Note -> String #

showList :: [Note] -> ShowS #

EmitXml Note Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Note -> XmlRep Source #

Eq Note Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Note Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Note = D1 ('MetaData "Note" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Note" 'PrefixI 'True) (((((S1 ('MetaSel ('Just "notePrintLeger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe YesNo)) :*: 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 TimeOnly))) :*: (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 "noteId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)) :*: 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 "noteNoteheadText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NoteheadText)))) :*: ((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]) :*: S1 ('MetaSel ('Just "notePlay") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Play)))))))))

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

Instances details
Generic NoteSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep NoteSize :: Type -> Type #

Methods

from :: NoteSize -> Rep NoteSize x #

to :: Rep NoteSize x -> NoteSize #

Show NoteSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml NoteSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq NoteSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NoteSize Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NoteSize = D1 ('MetaData "NoteSize" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 1024th to maxima. The size attribute indicates full, cue, grace-cue, or large size. The default is full for regular notes, grace-cue for notes that contain both grace and cue elements, and cue for notes that contain either a cue or a grace element, but not both.

Constructors

NoteType 

Fields

Instances

Instances details
Generic NoteType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep NoteType :: Type -> Type #

Methods

from :: NoteType -> Rep NoteType x #

to :: Rep NoteType x -> NoteType #

Show NoteType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml NoteType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq NoteType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NoteType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NoteType = D1 ('MetaData "NoteType" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 type indicates shapes other than the open and closed ovals associated with note durations.

The smufl attribute can be used to specify a particular notehead, allowing application interoperability without requiring every SMuFL glyph to have a MusicXML element equivalent. This attribute can be used either with the "other" value, or to refine a specific notehead value such as "cluster". Noteheads in the SMuFL "Note name noteheads" range (U+E150–U+E1AF) should not use the smufl attribute or the "other" value, but instead use the notehead-text element.

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

Instances details
Generic Notehead Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Notehead :: Type -> Type #

Methods

from :: Notehead -> Rep Notehead x #

to :: Rep Notehead x -> Notehead #

Show Notehead Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Notehead Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Notehead Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Notehead Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

mkNotehead :: NoteheadValue -> Notehead Source #

Smart constructor for Notehead

data NoteheadText Source #

notehead-text (complex)

The notehead-text type represents text that is displayed inside a notehead, as is done in some educational music. It is not needed for the numbers used in tablature or jianpu notation. The presence of a TAB or jianpu clefs is sufficient to indicate that numbers are used. The display-text and accidental-text elements allow display of fully formatted text and accidentals.

Instances

Instances details
Generic NoteheadText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep NoteheadText :: Type -> Type #

Show NoteheadText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml NoteheadText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq NoteheadText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NoteheadText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NoteheadText = D1 ('MetaData "NoteheadText" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "NoteheadText" 'PrefixI 'True) (S1 ('MetaSel ('Just "noteheadTextNoteheadText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ChxNoteheadText])))

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

Instances details
Generic OctaveShift Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep OctaveShift :: Type -> Type #

Show OctaveShift Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml OctaveShift Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq OctaveShift Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep OctaveShift Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep OctaveShift = D1 ('MetaData "OctaveShift" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "OctaveShift" 'PrefixI 'True) (((S1 ('MetaSel ('Just "octaveShiftType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UpDownStopContinue) :*: (S1 ('MetaSel ('Just "octaveShiftNumber") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NumberLevel)) :*: S1 ('MetaSel ('Just "octaveShiftSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PositiveInteger)))) :*: ((S1 ('MetaSel ('Just "octaveShiftDashLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "octaveShiftSpaceLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))) :*: (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)) :*: S1 ('MetaSel ('Just "octaveShiftId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)))))))

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

Instances details
Generic Offset Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Offset :: Type -> Type #

Methods

from :: Offset -> Rep Offset x #

to :: Rep Offset x -> Offset #

Show Offset Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Offset Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Offset Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Offset Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Offset = D1 ('MetaData "Offset" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic Opus Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Opus :: Type -> Type #

Methods

from :: Opus -> Rep Opus x #

to :: Rep Opus x -> Opus #

Show Opus Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Opus -> ShowS #

show :: Opus -> String #

showList :: [Opus] -> ShowS #

EmitXml Opus Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Opus -> XmlRep Source #

Eq Opus Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Opus Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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

Instances details
Generic Ornaments Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Ornaments :: Type -> Type #

Show Ornaments Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Ornaments Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Ornaments Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Ornaments Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Ornaments = D1 ('MetaData "Ornaments" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Ornaments" 'PrefixI 'True) (S1 ('MetaSel ('Just "ornamentsId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)) :*: 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

Instances details
Generic OtherAppearance Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep OtherAppearance :: Type -> Type #

Show OtherAppearance Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml OtherAppearance Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq OtherAppearance Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep OtherAppearance Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep OtherAppearance = D1 ('MetaData "OtherAppearance" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 MusicXML format. The smufl attribute can be used to specify a particular direction symbol, allowing application interoperability without requiring every SMuFL glyph to have a MusicXML element equivalent. Using the other-direction type without the smufl attribute allows for extended representation, though without application interoperability.

Constructors

OtherDirection 

Fields

Instances

Instances details
Generic OtherDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep OtherDirection :: Type -> Type #

Show OtherDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml OtherDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq OtherDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep OtherDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep OtherDirection = D1 ('MetaData "OtherDirection" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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)))) :*: ((S1 ('MetaSel ('Just "otherDirectionHalign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LeftCenterRight)) :*: S1 ('MetaSel ('Just "otherDirectionValign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Valign))) :*: (S1 ('MetaSel ('Just "otherDirectionSmufl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SmuflGlyphName)) :*: S1 ('MetaSel ('Just "otherDirectionId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)))))))

data OtherNotation Source #

other-notation (complex)

The other-notation type is used to define any notations not yet in the MusicXML format. It handles notations where more specific extension elements such as other-dynamics and other-technical are not appropriate. The smufl attribute can be used to specify a particular notation, allowing application interoperability without requiring every SMuFL glyph to have a MusicXML element equivalent. Using the other-notation type without the smufl attribute allows for extended representation, though without application interoperability.

Constructors

OtherNotation 

Fields

Instances

Instances details
Generic OtherNotation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep OtherNotation :: Type -> Type #

Show OtherNotation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml OtherNotation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq OtherNotation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep OtherNotation Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep OtherNotation = D1 ('MetaData "OtherNotation" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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))) :*: (S1 ('MetaSel ('Just "otherNotationSmufl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SmuflGlyphName)) :*: S1 ('MetaSel ('Just "otherNotationId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)))))))

data OtherPlacementText Source #

other-placement-text (complex)

The other-placement-text type represents a text element with print-style, placement, and smufl attribute groups. This type is used by MusicXML notation extension elements to allow specification of specific SMuFL glyphs without needed to add every glyph as a MusicXML element.

Instances

Instances details
Generic OtherPlacementText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep OtherPlacementText :: Type -> Type #

Show OtherPlacementText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml OtherPlacementText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq OtherPlacementText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep OtherPlacementText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep OtherPlacementText = D1 ('MetaData "OtherPlacementText" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "OtherPlacementText" 'PrefixI 'True) (((S1 ('MetaSel ('Just "otherPlacementTextString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Just "otherPlacementTextDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "otherPlacementTextDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)))) :*: (S1 ('MetaSel ('Just "otherPlacementTextRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "otherPlacementTextRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "otherPlacementTextFontFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CommaSeparatedText))))) :*: ((S1 ('MetaSel ('Just "otherPlacementTextFontStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontStyle)) :*: (S1 ('MetaSel ('Just "otherPlacementTextFontSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontSize)) :*: S1 ('MetaSel ('Just "otherPlacementTextFontWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontWeight)))) :*: (S1 ('MetaSel ('Just "otherPlacementTextColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)) :*: (S1 ('MetaSel ('Just "otherPlacementTextPlacement") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AboveBelow)) :*: S1 ('MetaSel ('Just "otherPlacementTextSmufl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SmuflGlyphName)))))))

data OtherPlay Source #

other-play (complex)

The other-play element represents other types of playback. The required type attribute indicates the type of playback to which the element content applies.

Constructors

OtherPlay 

Fields

Instances

Instances details
Generic OtherPlay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep OtherPlay :: Type -> Type #

Show OtherPlay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml OtherPlay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq OtherPlay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep OtherPlay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep OtherPlay = D1 ('MetaData "OtherPlay" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "OtherPlay" 'PrefixI 'True) (S1 ('MetaSel ('Just "otherPlayString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "otherPlayType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Token)))

mkOtherPlay :: String -> Token -> OtherPlay Source #

Smart constructor for OtherPlay

data OtherText Source #

other-text (complex)

The other-text type represents a text element with a smufl attribute group. This type is used by MusicXML direction extension elements to allow specification of specific SMuFL glyphs without needed to add every glyph as a MusicXML element.

Constructors

OtherText 

Fields

Instances

Instances details
Generic OtherText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep OtherText :: Type -> Type #

Show OtherText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml OtherText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq OtherText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep OtherText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep OtherText = D1 ('MetaData "OtherText" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "OtherText" 'PrefixI 'True) (S1 ('MetaSel ('Just "otherTextString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "otherTextSmufl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SmuflGlyphName))))

mkOtherText :: String -> OtherText Source #

Smart constructor for OtherText

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

Instances details
Generic PageLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep PageLayout :: Type -> Type #

Show PageLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml PageLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq PageLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PageLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PageLayout = D1 ('MetaData "PageLayout" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic PageMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep PageMargins :: Type -> Type #

Show PageMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml PageMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq PageMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PageMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PageMargins = D1 ('MetaData "PageMargins" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic CmpPart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep CmpPart :: Type -> Type #

Methods

from :: CmpPart -> Rep CmpPart x #

to :: Rep CmpPart x -> CmpPart #

Show CmpPart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml CmpPart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq CmpPart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep CmpPart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep CmpPart = D1 ('MetaData "CmpPart" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic Part Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Part :: Type -> Type #

Methods

from :: Part -> Rep Part x #

to :: Rep Part x -> Part #

Show Part Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Part -> ShowS #

show :: Part -> String #

showList :: [Part] -> ShowS #

EmitXml Part Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Part -> XmlRep Source #

Eq Part Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Part Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Part = D1 ('MetaData "Part" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic PartGroup Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep PartGroup :: Type -> Type #

Show PartGroup Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml PartGroup Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq PartGroup Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PartGroup Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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

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

Smart constructor for PartGroup

data PartList Source #

part-list (complex)

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

Instances

Instances details
Generic PartList Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep PartList :: Type -> Type #

Methods

from :: PartList -> Rep PartList x #

to :: Rep PartList x -> PartList #

Show PartList Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml PartList Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq PartList Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PartList Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PartList = D1 ('MetaData "PartList" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic PartName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep PartName :: Type -> Type #

Methods

from :: PartName -> Rep PartName x #

to :: Rep PartName x -> PartName #

Show PartName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml PartName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq PartName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PartName Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PartName = D1 ('MetaData "PartName" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 type indicates how a symbol for a multi-staff part is indicated in the score; brace is the default value. 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

Instances details
Generic PartSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep PartSymbol :: Type -> Type #

Show PartSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml PartSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq PartSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PartSymbol Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PartSymbol = D1 ('MetaData "PartSymbol" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "PartSymbol" 'PrefixI 'True) (((S1 ('MetaSel ('Just "partSymbolGroupSymbolValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GroupSymbolValue) :*: S1 ('MetaSel ('Just "partSymbolTopStaff") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe StaffNumber))) :*: (S1 ('MetaSel ('Just "partSymbolBottomStaff") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe StaffNumber)) :*: S1 ('MetaSel ('Just "partSymbolDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)))) :*: ((S1 ('MetaSel ('Just "partSymbolDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "partSymbolRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 ('MetaSel ('Just "partSymbolRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "partSymbolColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color))))))

data Pedal Source #

pedal (complex)

The pedal type represents piano pedal marks. In MusicXML 3.1 this includes sostenuto as well as damper pedal marks. The line attribute is yes if pedal lines are used. The sign attribute is yes if Ped, Sost, and * signs are used. For MusicXML 2.0 compatibility, the sign attribute is yes by default if the line attribute is no, and is no by default if the line attribute is yes. If the sign attribute is set to yes and the type is start or sostenuto, the abbreviated attribute is yes if the short P and S signs are used, and no if the full Ped and Sost signs are used. It is no by default. Otherwise the abbreviated attribute is ignored.

The change and continue types are used when the line attribute is yes. The change type indicates a pedal lift and retake indicated with an inverted V marking. The continue type allows more precise formatting across system breaks and for more complex pedaling lines. The alignment attributes are ignored if the line attribute is yes.

Constructors

Pedal 

Fields

Instances

Instances details
Generic Pedal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Pedal :: Type -> Type #

Methods

from :: Pedal -> Rep Pedal x #

to :: Rep Pedal x -> Pedal #

Show Pedal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Pedal -> ShowS #

show :: Pedal -> String #

showList :: [Pedal] -> ShowS #

EmitXml Pedal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Pedal -> XmlRep Source #

Eq Pedal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Pedal Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Pedal = D1 ('MetaData "Pedal" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Pedal" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "pedalType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PedalType) :*: S1 ('MetaSel ('Just "pedalNumber") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NumberLevel))) :*: (S1 ('MetaSel ('Just "pedalLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 ('MetaSel ('Just "pedalSign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe YesNo)))) :*: ((S1 ('MetaSel ('Just "pedalAbbreviated") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 ('MetaSel ('Just "pedalDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 ('MetaSel ('Just "pedalDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "pedalRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))))) :*: (((S1 ('MetaSel ('Just "pedalRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "pedalFontFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CommaSeparatedText))) :*: (S1 ('MetaSel ('Just "pedalFontStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontStyle)) :*: S1 ('MetaSel ('Just "pedalFontSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontSize)))) :*: ((S1 ('MetaSel ('Just "pedalFontWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontWeight)) :*: S1 ('MetaSel ('Just "pedalColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color))) :*: (S1 ('MetaSel ('Just "pedalHalign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LeftCenterRight)) :*: (S1 ('MetaSel ('Just "pedalValign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Valign)) :*: S1 ('MetaSel ('Just "pedalId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID))))))))

mkPedal :: PedalType -> 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

Instances details
Generic PedalTuning Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep PedalTuning :: Type -> Type #

Show PedalTuning Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml PedalTuning Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq PedalTuning Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PedalTuning Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PedalTuning = D1 ('MetaData "PedalTuning" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic PerMinute Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep PerMinute :: Type -> Type #

Show PerMinute Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml PerMinute Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq PerMinute Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PerMinute Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PerMinute = D1 ('MetaData "PerMinute" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 Percussion Source #

percussion (complex)

The percussion element is used to define percussion pictogram symbols. Definitions for these symbols can be found in Kurt Stone's "Music Notation in the Twentieth Century" on pages 206-212 and 223. Some values are added to these based on how usage has evolved in the 30 years since Stone's book was published.

Constructors

Percussion 

Fields

Instances

Instances details
Generic Percussion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Percussion :: Type -> Type #

Show Percussion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Percussion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Percussion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Percussion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Percussion = D1 ('MetaData "Percussion" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Percussion" 'PrefixI 'True) (((S1 ('MetaSel ('Just "percussionDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "percussionDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "percussionRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)))) :*: ((S1 ('MetaSel ('Just "percussionRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "percussionFontFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CommaSeparatedText))) :*: (S1 ('MetaSel ('Just "percussionFontStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontStyle)) :*: S1 ('MetaSel ('Just "percussionFontSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontSize))))) :*: ((S1 ('MetaSel ('Just "percussionFontWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontWeight)) :*: (S1 ('MetaSel ('Just "percussionColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)) :*: S1 ('MetaSel ('Just "percussionHalign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LeftCenterRight)))) :*: ((S1 ('MetaSel ('Just "percussionValign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Valign)) :*: S1 ('MetaSel ('Just "percussionEnclosure") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe EnclosureShape))) :*: (S1 ('MetaSel ('Just "percussionId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)) :*: S1 ('MetaSel ('Just "percussionPercussion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChxPercussion))))))

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

Instances details
Generic Pitch Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Pitch :: Type -> Type #

Methods

from :: Pitch -> Rep Pitch x #

to :: Rep Pitch x -> Pitch #

Show Pitch Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Pitch -> ShowS #

show :: Pitch -> String #

showList :: [Pitch] -> ShowS #

EmitXml Pitch Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Pitch -> XmlRep Source #

Eq Pitch Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Pitch Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Pitch = D1 ('MetaData "Pitch" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 Pitched Source #

pitched (complex)

The pitched-value type represents pictograms for pitched percussion instruments. The smufl attribute is used to distinguish different SMuFL glyphs for a particular pictogram within the tuned mallet percussion pictograms range.

Constructors

Pitched 

Instances

Instances details
Generic Pitched Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Pitched :: Type -> Type #

Methods

from :: Pitched -> Rep Pitched x #

to :: Rep Pitched x -> Pitched #

Show Pitched Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Pitched Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Pitched Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Pitched Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Pitched = D1 ('MetaData "Pitched" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Pitched" 'PrefixI 'True) (S1 ('MetaSel ('Just "pitchedPitchedValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PitchedValue) :*: S1 ('MetaSel ('Just "pitchedSmufl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SmuflPictogramGlyphName))))

mkPitched :: PitchedValue -> Pitched Source #

Smart constructor for Pitched

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

Instances details
Generic PlacementText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep PlacementText :: Type -> Type #

Show PlacementText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml PlacementText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq PlacementText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PlacementText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PlacementText = D1 ('MetaData "PlacementText" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 Play Source #

play (complex)

The play type, new in Version 3.0, specifies playback techniques to be used in conjunction with the instrument-sound element. When used as part of a sound element, it applies to all notes going forward in score order. In multi-instrument parts, the affected instrument should be specified using the id attribute. When used as part of a note element, it applies to the current note only.

Constructors

Play 

Fields

Instances

Instances details
Generic Play Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Play :: Type -> Type #

Methods

from :: Play -> Rep Play x #

to :: Rep Play x -> Play #

Show Play Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Play -> ShowS #

show :: Play -> String #

showList :: [Play] -> ShowS #

EmitXml Play Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Play -> XmlRep Source #

Eq Play Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Play Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Play = D1 ('MetaData "Play" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Play" 'PrefixI 'True) (S1 ('MetaSel ('Just "playId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe IDREF)) :*: S1 ('MetaSel ('Just "playPlay") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ChxPlay])))

mkPlay :: Play Source #

Smart constructor for Play

data PrincipalVoice Source #

principal-voice (complex)

The principal-voice element represents principal and secondary voices in a score, either for analysis or for square bracket symbols that appear in a score. The symbol attribute indicates the type of symbol used at the start of the principal-voice. The content of the principal-voice element is used for analysis and may be any text value. When used for analysis separate from any printed score markings, the symbol attribute should be set to "none".

Constructors

PrincipalVoice 

Instances

Instances details
Generic PrincipalVoice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep PrincipalVoice :: Type -> Type #

Show PrincipalVoice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml PrincipalVoice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq PrincipalVoice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PrincipalVoice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep PrincipalVoice = D1 ('MetaData "PrincipalVoice" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "PrincipalVoice" 'PrefixI 'True) (((S1 ('MetaSel ('Just "principalVoiceString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Just "principalVoiceType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StartStop) :*: S1 ('MetaSel ('Just "principalVoiceSymbol") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrincipalVoiceSymbol))) :*: ((S1 ('MetaSel ('Just "principalVoiceDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "principalVoiceDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 ('MetaSel ('Just "principalVoiceRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "principalVoiceRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))))) :*: (((S1 ('MetaSel ('Just "principalVoiceFontFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 ('MetaSel ('Just "principalVoiceFontStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontStyle))) :*: (S1 ('MetaSel ('Just "principalVoiceFontSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontSize)) :*: S1 ('MetaSel ('Just "principalVoiceFontWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontWeight)))) :*: ((S1 ('MetaSel ('Just "principalVoiceColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)) :*: S1 ('MetaSel ('Just "principalVoiceHalign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LeftCenterRight))) :*: (S1 ('MetaSel ('Just "principalVoiceValign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Valign)) :*: S1 ('MetaSel ('Just "principalVoiceId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)))))))

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

Instances details
Generic Print Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Print :: Type -> Type #

Methods

from :: Print -> Rep Print x #

to :: Rep Print x -> Print #

Show Print Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Print -> ShowS #

show :: Print -> String #

showList :: [Print] -> ShowS #

EmitXml Print Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Print -> XmlRep Source #

Eq Print Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Print Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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

mkPrint :: Layout -> Print Source #

Smart constructor for Print

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

Instances details
Generic Repeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Repeat :: Type -> Type #

Methods

from :: Repeat -> Rep Repeat x #

to :: Rep Repeat x -> Repeat #

Show Repeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Repeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Repeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Repeat Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Repeat = D1 ('MetaData "Repeat" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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)) :*: S1 ('MetaSel ('Just "repeatWinged") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Winged)))))

mkRepeat :: BackwardForward -> Repeat Source #

Smart constructor for Repeat

data Rest Source #

rest (complex)

The rest element indicates notated rests or silences. Rest elements are usually empty, but placement on the staff can be specified using display-step and display-octave elements. If the measure attribute is set to yes, this indicates this is a complete measure rest.

Constructors

Rest 

Instances

Instances details
Generic Rest Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Rest :: Type -> Type #

Methods

from :: Rest -> Rep Rest x #

to :: Rep Rest x -> Rest #

Show Rest Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Rest -> ShowS #

show :: Rest -> String #

showList :: [Rest] -> ShowS #

EmitXml Rest Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Rest -> XmlRep Source #

Eq Rest Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Rest Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Rest = D1 ('MetaData "Rest" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Rest" 'PrefixI 'True) (S1 ('MetaSel ('Just "restMeasure") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 ('MetaSel ('Just "restDisplayStepOctave") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DisplayStepOctave))))

mkRest :: Rest Source #

Smart constructor for Rest

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

Instances details
Generic Root Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Root :: Type -> Type #

Methods

from :: Root -> Rep Root x #

to :: Rep Root x -> Root #

Show Root Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Root -> ShowS #

show :: Root -> String #

showList :: [Root] -> ShowS #

EmitXml Root Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Root -> XmlRep Source #

Eq Root Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Root Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Root = D1 ('MetaData "Root" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic RootAlter Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep RootAlter :: Type -> Type #

Show RootAlter Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml RootAlter Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq RootAlter Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep RootAlter Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep RootAlter = D1 ('MetaData "RootAlter" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 in a score if not using the element contents.

Constructors

RootStep 

Fields

Instances

Instances details
Generic RootStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep RootStep :: Type -> Type #

Methods

from :: RootStep -> Rep RootStep x #

to :: Rep RootStep x -> RootStep #

Show RootStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml RootStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq RootStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep RootStep Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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

mkRootStep :: Step -> RootStep Source #

Smart constructor for RootStep

data Scaling Source #

scaling (complex)

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

Constructors

Scaling 

Fields

Instances

Instances details
Generic Scaling Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Scaling :: Type -> Type #

Methods

from :: Scaling -> Rep Scaling x #

to :: Rep Scaling x -> Scaling #

Show Scaling Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Scaling Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Scaling Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Scaling Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Scaling = D1 ('MetaData "Scaling" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic Scordatura Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Scordatura :: Type -> Type #

Show Scordatura Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Scordatura Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Scordatura Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Scordatura Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Scordatura = D1 ('MetaData "Scordatura" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Scordatura" 'PrefixI 'True) (S1 ('MetaSel ('Just "scordaturaId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)) :*: 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

Instances details
Generic ScoreInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ScoreInstrument :: Type -> Type #

Show ScoreInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ScoreInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ScoreInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ScoreInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ScoreInstrument = D1 ('MetaData "ScoreInstrument" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 "scoreInstrumentInstrumentSound") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: (S1 ('MetaSel ('Just "scoreInstrumentScoreInstrument") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ChxScoreInstrument)) :*: S1 ('MetaSel ('Just "scoreInstrumentVirtualInstrument") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe VirtualInstrument))))))

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 or specific MIDI instruments. Initial midi-instrument assignments may be made here as well.

Constructors

CmpScorePart 

Fields

Instances

Instances details
Generic CmpScorePart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep CmpScorePart :: Type -> Type #

Show CmpScorePart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml CmpScorePart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq CmpScorePart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep CmpScorePart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep CmpScorePart = D1 ('MetaData "CmpScorePart" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "CmpScorePart" 'PrefixI 'True) (((S1 ('MetaSel ('Just "scorePartId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ID) :*: S1 ('MetaSel ('Just "scorePartIdentification") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Identification))) :*: (S1 ('MetaSel ('Just "scorePartPartName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PartName) :*: S1 ('MetaSel ('Just "scorePartPartNameDisplay") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NameDisplay)))) :*: ((S1 ('MetaSel ('Just "scorePartPartAbbreviation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PartName)) :*: S1 ('MetaSel ('Just "scorePartPartAbbreviationDisplay") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NameDisplay))) :*: (S1 ('MetaSel ('Just "scorePartGroup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: (S1 ('MetaSel ('Just "scorePartScoreInstrument") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ScoreInstrument]) :*: S1 ('MetaSel ('Just "scorePartScorePart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SeqScorePart]))))))

data ScorePartwise Source #

score-partwise (complex)

Constructors

ScorePartwise 

Instances

Instances details
Generic ScorePartwise Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ScorePartwise :: Type -> Type #

Show ScorePartwise Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ScorePartwise Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ScorePartwise Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ScorePartwise Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ScorePartwise = D1 ('MetaData "ScorePartwise" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic ScoreTimewise Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ScoreTimewise :: Type -> Type #

Show ScoreTimewise Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ScoreTimewise Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ScoreTimewise Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ScoreTimewise Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ScoreTimewise = D1 ('MetaData "ScoreTimewise" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 Segno Source #

segno (complex)

The segno type is the visual indicator of a segno sign. The exact glyph can be specified with the smufl attribute. A sound element is also needed to guide playback applications reliably.

Constructors

Segno 

Fields

Instances

Instances details
Generic Segno Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Segno :: Type -> Type #

Methods

from :: Segno -> Rep Segno x #

to :: Rep Segno x -> Segno #

Show Segno Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Segno -> ShowS #

show :: Segno -> String #

showList :: [Segno] -> ShowS #

EmitXml Segno Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Segno -> XmlRep Source #

Eq Segno Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Segno Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Segno = D1 ('MetaData "Segno" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Segno" 'PrefixI 'True) (((S1 ('MetaSel ('Just "segnoSmufl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SmuflSegnoGlyphName)) :*: (S1 ('MetaSel ('Just "segnoDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "segnoDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)))) :*: (S1 ('MetaSel ('Just "segnoRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "segnoRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "segnoFontFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CommaSeparatedText))))) :*: ((S1 ('MetaSel ('Just "segnoFontStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontStyle)) :*: (S1 ('MetaSel ('Just "segnoFontSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontSize)) :*: S1 ('MetaSel ('Just "segnoFontWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontWeight)))) :*: ((S1 ('MetaSel ('Just "segnoColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)) :*: S1 ('MetaSel ('Just "segnoHalign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LeftCenterRight))) :*: (S1 ('MetaSel ('Just "segnoValign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Valign)) :*: S1 ('MetaSel ('Just "segnoId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)))))))

mkSegno :: Segno Source #

Smart constructor for Segno

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

Instances details
Generic CmpSlash Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep CmpSlash :: Type -> Type #

Methods

from :: CmpSlash -> Rep CmpSlash x #

to :: Rep CmpSlash x -> CmpSlash #

Show CmpSlash Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml CmpSlash Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq CmpSlash Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep CmpSlash Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep CmpSlash = D1 ('MetaData "CmpSlash" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic Slide Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Slide :: Type -> Type #

Methods

from :: Slide -> Rep Slide x #

to :: Rep Slide x -> Slide #

Show Slide Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Slide -> ShowS #

show :: Slide -> String #

showList :: [Slide] -> ShowS #

EmitXml Slide Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Slide -> XmlRep Source #

Eq Slide Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Slide Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Slide = D1 ('MetaData "Slide" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 "slideDashLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 ('MetaSel ('Just "slideSpaceLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: 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)) :*: S1 ('MetaSel ('Just "slideId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID))))))))

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

Instances details
Generic Slur Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Slur :: Type -> Type #

Methods

from :: Slur -> Rep Slur x #

to :: Rep Slur x -> Slur #

Show Slur Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Slur -> ShowS #

show :: Slur -> String #

showList :: [Slur] -> ShowS #

EmitXml Slur Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Slur -> XmlRep Source #

Eq Slur Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Slur Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Slur = D1 ('MetaData "Slur" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 "slurDashLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)))) :*: ((S1 ('MetaSel ('Just "slurSpaceLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: 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 "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 "slurBezierOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Divisions))) :*: (S1 ('MetaSel ('Just "slurBezierOffset2") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Divisions)) :*: (S1 ('MetaSel ('Just "slurColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)) :*: S1 ('MetaSel ('Just "slurId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID))))))))

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 particular times through a repeat, the time-only attribute indicates which times 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 devices, MIDI instruments, and playback techniques are changed using the midi-device, midi-instrument, and play elements. When there are multiple instances of these elements, they should be grouped together by instrument using the id attribute values.

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

Instances details
Generic Sound Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Sound :: Type -> Type #

Methods

from :: Sound -> Rep Sound x #

to :: Rep Sound x -> Sound #

Show Sound Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Sound -> ShowS #

show :: Sound -> String #

showList :: [Sound] -> ShowS #

EmitXml Sound Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Sound -> XmlRep Source #

Eq Sound Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Sound Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Sound = D1 ('MetaData "Sound" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 TimeOnly)) :*: 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 "soundId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)) :*: (S1 ('MetaSel ('Just "soundSound") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SeqSound]) :*: 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

Instances details
Generic StaffDetails Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep StaffDetails :: Type -> Type #

Show StaffDetails Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml StaffDetails Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq StaffDetails Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StaffDetails Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StaffDetails = D1 ('MetaData "StaffDetails" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "StaffDetails" 'PrefixI 'True) (((S1 ('MetaSel ('Just "staffDetailsNumber") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe StaffNumber)) :*: S1 ('MetaSel ('Just "staffDetailsShowFrets") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ShowFrets))) :*: (S1 ('MetaSel ('Just "staffDetailsPrintObject") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe YesNo)) :*: S1 ('MetaSel ('Just "staffDetailsPrintSpacing") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe YesNo)))) :*: ((S1 ('MetaSel ('Just "staffDetailsStaffType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe StaffType)) :*: S1 ('MetaSel ('Just "staffDetailsStaffLines") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NonNegativeInteger))) :*: (S1 ('MetaSel ('Just "staffDetailsStaffTuning") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [StaffTuning]) :*: (S1 ('MetaSel ('Just "staffDetailsCapo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NonNegativeInteger)) :*: S1 ('MetaSel ('Just "staffDetailsStaffSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NonNegativeDecimal)))))))

data StaffDivide Source #

staff-divide (complex)

The staff-divide element represents the staff division arrow symbols found at SMuFL code points U+E00B, U+E00C, and U+E00D.

Constructors

StaffDivide 

Fields

Instances

Instances details
Generic StaffDivide Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep StaffDivide :: Type -> Type #

Show StaffDivide Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml StaffDivide Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq StaffDivide Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StaffDivide Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StaffDivide = D1 ('MetaData "StaffDivide" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "StaffDivide" 'PrefixI 'True) (((S1 ('MetaSel ('Just "staffDivideType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StaffDivideSymbol) :*: (S1 ('MetaSel ('Just "staffDivideDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "staffDivideDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)))) :*: (S1 ('MetaSel ('Just "staffDivideRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "staffDivideRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "staffDivideFontFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CommaSeparatedText))))) :*: ((S1 ('MetaSel ('Just "staffDivideFontStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontStyle)) :*: (S1 ('MetaSel ('Just "staffDivideFontSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontSize)) :*: S1 ('MetaSel ('Just "staffDivideFontWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontWeight)))) :*: ((S1 ('MetaSel ('Just "staffDivideColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)) :*: S1 ('MetaSel ('Just "staffDivideHalign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LeftCenterRight))) :*: (S1 ('MetaSel ('Just "staffDivideValign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Valign)) :*: S1 ('MetaSel ('Just "staffDivideId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)))))))

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

Instances details
Generic StaffLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep StaffLayout :: Type -> Type #

Show StaffLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml StaffLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq StaffLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StaffLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StaffLayout = D1 ('MetaData "StaffLayout" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic StaffTuning Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep StaffTuning :: Type -> Type #

Show StaffTuning Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml StaffTuning Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq StaffTuning Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StaffTuning Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StaffTuning = D1 ('MetaData "StaffTuning" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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. A stem element associated with a rest refers to a stemlet.

Constructors

Stem 

Fields

Instances

Instances details
Generic Stem Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Stem :: Type -> Type #

Methods

from :: Stem -> Rep Stem x #

to :: Rep Stem x -> Stem #

Show Stem Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Stem -> ShowS #

show :: Stem -> String #

showList :: [Stem] -> ShowS #

EmitXml Stem Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Stem -> XmlRep Source #

Eq Stem Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Stem Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

mkStem :: StemValue -> Stem Source #

Smart constructor for Stem

data Stick Source #

stick (complex)

The stick type represents pictograms where the material of the stick, mallet, or beater is included.The parentheses and dashed-circle attributes indicate the presence of these marks around the round beater part of a pictogram. Values for these attributes are "no" if not present.

Constructors

Stick 

Fields

Instances

Instances details
Generic Stick Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Stick :: Type -> Type #

Methods

from :: Stick -> Rep Stick x #

to :: Rep Stick x -> Stick #

Show Stick Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Stick -> ShowS #

show :: Stick -> String #

showList :: [Stick] -> ShowS #

EmitXml Stick Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Stick -> XmlRep Source #

Eq Stick Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Stick Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Stick = D1 ('MetaData "Stick" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Stick" 'PrefixI 'True) ((S1 ('MetaSel ('Just "stickTip") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TipDirection)) :*: S1 ('MetaSel ('Just "stickParentheses") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe YesNo))) :*: (S1 ('MetaSel ('Just "stickDashedCircle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe YesNo)) :*: (S1 ('MetaSel ('Just "stickStickType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StickType) :*: S1 ('MetaSel ('Just "stickStickMaterial") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StickMaterial)))))

mkStick :: StickType -> StickMaterial -> Stick Source #

Smart constructor for Stick

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 pitched full-length string.

Constructors

CmpString 

Fields

Instances

Instances details
Generic CmpString Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep CmpString :: Type -> Type #

Show CmpString Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml CmpString Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq CmpString Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep CmpString Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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

mkCmpString :: StringNumber -> CmpString Source #

Smart constructor for CmpString

data StringMute Source #

string-mute (complex)

The string-mute type represents string mute on and mute off symbols.

Constructors

StringMute 

Fields

Instances

Instances details
Generic StringMute Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep StringMute :: Type -> Type #

Show StringMute Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml StringMute Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq StringMute Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StringMute Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StringMute = D1 ('MetaData "StringMute" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "StringMute" 'PrefixI 'True) (((S1 ('MetaSel ('Just "stringMuteType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OnOff) :*: (S1 ('MetaSel ('Just "stringMuteDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "stringMuteDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)))) :*: (S1 ('MetaSel ('Just "stringMuteRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "stringMuteRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "stringMuteFontFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CommaSeparatedText))))) :*: ((S1 ('MetaSel ('Just "stringMuteFontStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontStyle)) :*: (S1 ('MetaSel ('Just "stringMuteFontSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontSize)) :*: S1 ('MetaSel ('Just "stringMuteFontWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontWeight)))) :*: ((S1 ('MetaSel ('Just "stringMuteColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)) :*: S1 ('MetaSel ('Just "stringMuteHalign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LeftCenterRight))) :*: (S1 ('MetaSel ('Just "stringMuteValign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Valign)) :*: S1 ('MetaSel ('Just "stringMuteId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)))))))

mkStringMute :: OnOff -> StringMute Source #

Smart constructor for StringMute

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

Instances details
Generic StrongAccent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep StrongAccent :: Type -> Type #

Show StrongAccent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml StrongAccent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq StrongAccent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StrongAccent Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StrongAccent = D1 ('MetaData "StrongAccent" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic StyleText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep StyleText :: Type -> Type #

Show StyleText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml StyleText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq StyleText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep StyleText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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

Instances details
Generic Supports Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Supports :: Type -> Type #

Methods

from :: Supports -> Rep Supports x #

to :: Rep Supports x -> Supports #

Show Supports Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Supports Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Supports Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Supports Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Supports = D1 ('MetaData "Supports" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 SystemDividers Source #

system-dividers (complex)

The system-dividers element indicates the presence or absence of system dividers (also known as system separation marks) between systems displayed on the same page. Dividers on the left and right side of the page are controlled by the left-divider and right-divider elements respectively. The default vertical position is half the system-distance value from the top of the system that is below the divider. The default horizontal position is the left and right system margin, respectively.

When used in the print element, the system-dividers element affects the dividers that would appear between the current system and the previous system.

Constructors

SystemDividers 

Instances

Instances details
Generic SystemDividers Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep SystemDividers :: Type -> Type #

Show SystemDividers Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml SystemDividers Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq SystemDividers Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SystemDividers Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SystemDividers = D1 ('MetaData "SystemDividers" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "SystemDividers" 'PrefixI 'True) (S1 ('MetaSel ('Just "systemDividersLeftDivider") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EmptyPrintObjectStyleAlign) :*: S1 ('MetaSel ('Just "systemDividersRightDivider") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EmptyPrintObjectStyleAlign)))

data SystemLayout Source #

system-layout (complex)

A system is a group of staves that are read and played simultaneously. 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

Instances details
Generic SystemLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep SystemLayout :: Type -> Type #

Show SystemLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml SystemLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq SystemLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SystemLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SystemLayout = D1 ('MetaData "SystemLayout" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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)) :*: S1 ('MetaSel ('Just "systemLayoutSystemDividers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SystemDividers)))))

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

Instances details
Generic SystemMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep SystemMargins :: Type -> Type #

Show SystemMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml SystemMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq SystemMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SystemMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SystemMargins = D1 ('MetaData "SystemMargins" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "SystemMargins" 'PrefixI 'True) (S1 ('MetaSel ('Just "systemMarginsLeftRightMargins") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LeftRightMargins)))

data Tap Source #

tap (complex)

The tap type indicates a tap on the fretboard. The text content allows specification of the notation; + and T are common choices. If the element is empty, the hand attribute is used to specify the symbol to use. The hand attribute is ignored if the tap glyph is already specified by the text content. If neither text content nor the hand attribute are present, the display is application-specific.

Constructors

Tap 

Fields

Instances

Instances details
Generic Tap Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Tap :: Type -> Type #

Methods

from :: Tap -> Rep Tap x #

to :: Rep Tap x -> Tap #

Show Tap Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Tap -> ShowS #

show :: Tap -> String #

showList :: [Tap] -> ShowS #

EmitXml Tap Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Tap -> XmlRep Source #

Eq Tap Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Tap Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Tap = D1 ('MetaData "Tap" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Tap" 'PrefixI 'True) (((S1 ('MetaSel ('Just "tapString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Just "tapHand") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TapHand)) :*: S1 ('MetaSel ('Just "tapDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)))) :*: (S1 ('MetaSel ('Just "tapDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "tapRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "tapRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 ('MetaSel ('Just "tapFontFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: (S1 ('MetaSel ('Just "tapFontStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontStyle)) :*: S1 ('MetaSel ('Just "tapFontSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontSize)))) :*: (S1 ('MetaSel ('Just "tapFontWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontWeight)) :*: (S1 ('MetaSel ('Just "tapColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)) :*: S1 ('MetaSel ('Just "tapPlacement") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AboveBelow)))))))

mkTap :: String -> Tap Source #

Smart constructor for Tap

data Technical Source #

technical (complex)

Technical indications give performance information for individual instruments.

Constructors

Technical 

Instances

Instances details
Generic Technical Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Technical :: Type -> Type #

Show Technical Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Technical Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Technical Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Technical Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Technical = D1 ('MetaData "Technical" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Technical" 'PrefixI 'True) (S1 ('MetaSel ('Just "technicalId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)) :*: 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

Instances details
Generic TextElementData Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep TextElementData :: Type -> Type #

Show TextElementData Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml TextElementData Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq TextElementData Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TextElementData Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TextElementData = D1 ('MetaData "TextElementData" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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. If the tie element applies only particular times through a repeat, the time-only attribute indicates which times to apply it. The tie element indicates sound; the tied element indicates notation.

Constructors

Tie 

Fields

Instances

Instances details
Generic Tie Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Tie :: Type -> Type #

Methods

from :: Tie -> Rep Tie x #

to :: Rep Tie x -> Tie #

Show Tie Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Tie -> ShowS #

show :: Tie -> String #

showList :: [Tie] -> ShowS #

EmitXml Tie Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Tie -> XmlRep Source #

Eq Tie Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Tie Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Tie = D1 ('MetaData "Tie" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Tie" 'PrefixI 'True) (S1 ('MetaSel ('Just "tieType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StartStop) :*: S1 ('MetaSel ('Just "tieTimeOnly") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TimeOnly))))

mkTie :: StartStop -> Tie Source #

Smart constructor for Tie

data Tied Source #

tied (complex)

The tied element represents the notated tie. The tie element represents the tie sound.

The number attribute is rarely needed to disambiguate ties, since note pitches will usually suffice. The attribute is implied rather than defaulting to 1 as with most elements. It is available for use in more complex tied notation situations.

Ties that join two notes of the same pitch together should be represented with a tied element on the first note with type="start" and a tied element on the second note with type="stop". This can also be done if the two notes being tied are enharmonically equivalent, but have different step values. It is not recommended to use tied elements to join two notes with enharmonically inequivalent pitches.

Ties that indicate that an instrument should be undamped are specified with a single tied element with type="let-ring".

Ties that are visually attached to only one note, other than undamped ties, should be specified with two tied elements on the same note, first type="start" then type="stop". This can be used to represent ties into or out of repeated sections or codas.

Constructors

Tied 

Fields

Instances

Instances details
Generic Tied Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Tied :: Type -> Type #

Methods

from :: Tied -> Rep Tied x #

to :: Rep Tied x -> Tied #

Show Tied Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Tied -> ShowS #

show :: Tied -> String #

showList :: [Tied] -> ShowS #

EmitXml Tied Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Tied -> XmlRep Source #

Eq Tied Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Tied Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Tied = D1 ('MetaData "Tied" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Tied" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "tiedType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TiedType) :*: S1 ('MetaSel ('Just "tiedNumber") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NumberLevel))) :*: (S1 ('MetaSel ('Just "tiedLineType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LineType)) :*: S1 ('MetaSel ('Just "tiedDashLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)))) :*: ((S1 ('MetaSel ('Just "tiedSpaceLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: 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 "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 "tiedBezierOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Divisions))) :*: (S1 ('MetaSel ('Just "tiedBezierOffset2") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Divisions)) :*: (S1 ('MetaSel ('Just "tiedColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)) :*: S1 ('MetaSel ('Just "tiedId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID))))))))

mkTied :: TiedType -> 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

Instances details
Generic Time Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Time :: Type -> Type #

Methods

from :: Time -> Rep Time x #

to :: Rep Time x -> Time #

Show Time Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Time -> ShowS #

show :: Time -> String #

showList :: [Time] -> ShowS #

EmitXml Time Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Time -> XmlRep Source #

Eq Time Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Time Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Time = D1 ('MetaData "Time" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 "timeSeparator") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TimeSeparator)) :*: 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 "timeHalign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LeftCenterRight)) :*: S1 ('MetaSel ('Just "timeValign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Valign))) :*: (S1 ('MetaSel ('Just "timePrintObject") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe YesNo)) :*: (S1 ('MetaSel ('Just "timeId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)) :*: S1 ('MetaSel ('Just "timeTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChxTime)))))))

mkTime :: ChxTime -> Time Source #

Smart constructor for Time

data TimeModification Source #

time-modification (complex)

Time modification indicates tuplets, double-note tremolos, and other durational changes. A time-modification element shows how the cumulative, sounding effect of tuplets and double-note tremolos compare to the written note type represented by the type and dot elements. Nested tuplets and other notations that use more detailed information need both the time-modification and tuplet elements to be represented accurately.

Instances

Instances details
Generic TimeModification Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep TimeModification :: Type -> Type #

Show TimeModification Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml TimeModification Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq TimeModification Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TimeModification Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TimeModification = D1 ('MetaData "TimeModification" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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. The optional number attribute refers to staff numbers, from top to bottom on the system. If absent, the transposition applies to all staves in the part. Per-staff transposition is most often used in parts that represent multiple instruments.

Constructors

Transpose 

Fields

Instances

Instances details
Generic Transpose Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Transpose :: Type -> Type #

Show Transpose Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Transpose Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Transpose Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Transpose Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Transpose = D1 ('MetaData "Transpose" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Transpose" 'PrefixI 'True) ((S1 ('MetaSel ('Just "transposeNumber") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe StaffNumber)) :*: (S1 ('MetaSel ('Just "transposeId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)) :*: 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)

The tremolo ornament can be used to indicate single-note, double-note, or unmeasured tremolos. Single-note tremolos use the single type, double-note tremolos use the start and stop types, and unmeasured tremolos use the unmeasured type. 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 8. Note that the number of attached beams is not included in this value, but is represented separately using the beam element. The value should be 0 for unmeasured tremolos.

When using double-note tremolos, the duration of each note in the tremolo should correspond to half of the notated type value. A time-modification element should also be added with an actual-notes value of 2 and a normal-notes value of 1. If used within a tuplet, this 2/1 ratio should be multiplied by the existing tuplet ratio.

The smufl attribute specifies the glyph to use from the SMuFL tremolos range for an unmeasured tremolo. It is ignored for other tremolo types. The SMuFL buzzRoll glyph is used by default if the attribute is missing.

Using repeater beams for indicating tremolos is deprecated as of MusicXML 3.0.

Constructors

Tremolo 

Fields

Instances

Instances details
Generic Tremolo Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Tremolo :: Type -> Type #

Methods

from :: Tremolo -> Rep Tremolo x #

to :: Rep Tremolo x -> Tremolo #

Show Tremolo Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Tremolo Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Tremolo Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Tremolo Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Tremolo = D1 ('MetaData "Tremolo" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Tremolo" 'PrefixI 'True) (((S1 ('MetaSel ('Just "tremoloTremoloMarks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TremoloMarks) :*: (S1 ('MetaSel ('Just "tremoloType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TremoloType)) :*: 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)) :*: S1 ('MetaSel ('Just "tremoloSmufl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SmuflGlyphName)))))))

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 and double-note tremolos compare to the written note type, the tuplet element describes how this is displayed. The tuplet element also provides more detailed representation information than the time-modification element, and is needed to represent nested tuplets and other complex tuplets accurately.

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

Instances details
Generic Tuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Tuplet :: Type -> Type #

Methods

from :: Tuplet -> Rep Tuplet x #

to :: Rep Tuplet x -> Tuplet #

Show Tuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Tuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Tuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Tuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Tuplet = D1 ('MetaData "Tuplet" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 "tupletId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID))) :*: (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

Instances details
Generic TupletDot Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep TupletDot :: Type -> Type #

Show TupletDot Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml TupletDot Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq TupletDot Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TupletDot Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TupletDot = D1 ('MetaData "TupletDot" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic TupletNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep TupletNumber :: Type -> Type #

Show TupletNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml TupletNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq TupletNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TupletNumber Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TupletNumber = D1 ('MetaData "TupletNumber" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic TupletPortion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep TupletPortion :: Type -> Type #

Show TupletPortion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml TupletPortion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq TupletPortion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TupletPortion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TupletPortion = D1 ('MetaData "TupletPortion" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic TupletType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep TupletType :: Type -> Type #

Show TupletType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml TupletType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq TupletType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TupletType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TupletType = D1 ('MetaData "TupletType" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "TupletType" 'PrefixI 'True) ((S1 ('MetaSel ('Just "tupletTypeNoteTypeValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NoteTypeValue) :*: (S1 ('MetaSel ('Just "tupletTypeFontFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CommaSeparatedText)) :*: S1 ('MetaSel ('Just "tupletTypeFontStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontStyle)))) :*: (S1 ('MetaSel ('Just "tupletTypeFontSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontSize)) :*: (S1 ('MetaSel ('Just "tupletTypeFontWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FontWeight)) :*: S1 ('MetaSel ('Just "tupletTypeColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color))))))

data TypedText Source #

typed-text (complex)

The typed-text type represents a text element with a type attributes.

Constructors

TypedText 

Fields

Instances

Instances details
Generic TypedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep TypedText :: Type -> Type #

Show TypedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml TypedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq TypedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TypedText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TypedText = D1 ('MetaData "TypedText" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 Unpitched Source #

unpitched (complex)

The unpitched type represents musical elements that are notated on the staff but lack definite pitch, such as unpitched percussion and speaking voice.

Instances

Instances details
Generic Unpitched Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Unpitched :: Type -> Type #

Show Unpitched Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Unpitched Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Unpitched Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Unpitched Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Unpitched = D1 ('MetaData "Unpitched" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Unpitched" 'PrefixI 'True) (S1 ('MetaSel ('Just "unpitchedDisplayStepOctave") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DisplayStepOctave))))

mkUnpitched :: Unpitched Source #

Smart constructor for Unpitched

data VirtualInstrument Source #

virtual-instrument (complex)

The virtual-instrument element defines a specific virtual instrument used for an instrument sound.

Constructors

VirtualInstrument 

Fields

Instances

Instances details
Generic VirtualInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep VirtualInstrument :: Type -> Type #

Show VirtualInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml VirtualInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq VirtualInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep VirtualInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep VirtualInstrument = D1 ('MetaData "VirtualInstrument" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "VirtualInstrument" 'PrefixI 'True) (S1 ('MetaSel ('Just "virtualInstrumentVirtualLibrary") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Just "virtualInstrumentVirtualName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))))

data WavyLine Source #

wavy-line (complex)

Wavy lines are one way to indicate trills. When used with a barline element, they should always have type="continue" set.

Constructors

WavyLine 

Fields

Instances

Instances details
Generic WavyLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep WavyLine :: Type -> Type #

Methods

from :: WavyLine -> Rep WavyLine x #

to :: Rep WavyLine x -> WavyLine #

Show WavyLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml WavyLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq WavyLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep WavyLine Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep WavyLine = D1 ('MetaData "WavyLine" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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. The niente attribute is yes if a circle appears at the point of the wedge, indicating a crescendo from nothing or diminuendo to nothing. It is no by default, and used only when the type is crescendo, or the type is stop for a wedge that began with a diminuendo type. The line-type is solid by default.

Constructors

Wedge 

Fields

Instances

Instances details
Generic Wedge Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Wedge :: Type -> Type #

Methods

from :: Wedge -> Rep Wedge x #

to :: Rep Wedge x -> Wedge #

Show Wedge Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Wedge -> ShowS #

show :: Wedge -> String #

showList :: [Wedge] -> ShowS #

EmitXml Wedge Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Wedge -> XmlRep Source #

Eq Wedge Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Wedge Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Wedge = D1 ('MetaData "Wedge" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Wedge" 'PrefixI 'True) (((S1 ('MetaSel ('Just "wedgeType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 WedgeType) :*: (S1 ('MetaSel ('Just "wedgeNumber") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NumberLevel)) :*: S1 ('MetaSel ('Just "wedgeSpread") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)))) :*: (S1 ('MetaSel ('Just "wedgeNiente") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe YesNo)) :*: (S1 ('MetaSel ('Just "wedgeLineType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LineType)) :*: S1 ('MetaSel ('Just "wedgeDashLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))))) :*: ((S1 ('MetaSel ('Just "wedgeSpaceLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: (S1 ('MetaSel ('Just "wedgeDefaultX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "wedgeDefaultY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)))) :*: ((S1 ('MetaSel ('Just "wedgeRelativeX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths)) :*: S1 ('MetaSel ('Just "wedgeRelativeY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tenths))) :*: (S1 ('MetaSel ('Just "wedgeColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)) :*: S1 ('MetaSel ('Just "wedgeId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ID)))))))

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

Instances details
Generic Work Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Work :: Type -> Type #

Methods

from :: Work -> Rep Work x #

to :: Rep Work x -> Work #

Show Work Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Work -> ShowS #

show :: Work -> String #

showList :: [Work] -> ShowS #

EmitXml Work Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Work -> XmlRep Source #

Eq Work Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Work Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Work = D1 ('MetaData "Work" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 ChxArrow Source #

arrow (choice)

Constructors

ArrowArrowDirection 

Fields

ArrowCircularArrow 

Fields

Instances

Instances details
Generic ChxArrow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxArrow :: Type -> Type #

Methods

from :: ChxArrow -> Rep ChxArrow x #

to :: Rep ChxArrow x -> ChxArrow #

Show ChxArrow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxArrow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxArrow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxArrow Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxArrow = D1 ('MetaData "ChxArrow" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "ArrowArrowDirection" 'PrefixI 'True) (S1 ('MetaSel ('Just "arrowArrowDirection") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ArrowDirection) :*: (S1 ('MetaSel ('Just "arrowArrowStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ArrowStyle)) :*: S1 ('MetaSel ('Just "arrowArrowhead") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Empty)))) :+: C1 ('MetaCons "ArrowCircularArrow" 'PrefixI 'True) (S1 ('MetaSel ('Just "arrowCircularArrow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CircularArrow)))

data ChxArticulations Source #

articulations (choice)

Constructors

ArticulationsAccent 

Fields

ArticulationsStrongAccent 

Fields

ArticulationsStaccato 

Fields

ArticulationsTenuto 

Fields

ArticulationsDetachedLegato 

Fields

ArticulationsStaccatissimo 

Fields

ArticulationsSpiccato 

Fields

ArticulationsScoop 

Fields

ArticulationsPlop 

Fields

ArticulationsDoit 

Fields

ArticulationsFalloff 

Fields

ArticulationsBreathMark 

Fields

ArticulationsCaesura 

Fields

ArticulationsStress 

Fields

ArticulationsUnstress 

Fields

ArticulationsSoftAccent 

Fields

ArticulationsOtherArticulation 

Fields

Instances

Instances details
Generic ChxArticulations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxArticulations :: Type -> Type #

Show ChxArticulations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxArticulations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxArticulations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxArticulations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxArticulations = D1 ('MetaData "ChxArticulations" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 BreathMark)))) :+: ((C1 ('MetaCons "ArticulationsCaesura" 'PrefixI 'True) (S1 ('MetaSel ('Just "articulationsCaesura") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Caesura)) :+: 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 "ArticulationsSoftAccent" 'PrefixI 'True) (S1 ('MetaSel ('Just "articulationsSoftAccent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EmptyPlacement)) :+: C1 ('MetaCons "ArticulationsOtherArticulation" 'PrefixI 'True) (S1 ('MetaSel ('Just "articulationsOtherArticulation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OtherPlacementText)))))))

data ChxBend Source #

bend (choice)

Constructors

BendPreBend 

Fields

BendRelease 

Fields

Instances

Instances details
Generic ChxBend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxBend :: Type -> Type #

Methods

from :: ChxBend -> Rep ChxBend x #

to :: Rep ChxBend x -> ChxBend #

Show ChxBend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxBend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxBend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep ChxBend Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxBend = D1 ('MetaData "ChxBend" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 ChxCredit0 Source #

credit (choice)

Constructors

CreditCreditWords 

Fields

CreditCreditSymbol 

Fields

Instances

Instances details
Generic ChxCredit0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxCredit0 :: Type -> Type #

Show ChxCredit0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxCredit0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxCredit0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxCredit0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxCredit0 = D1 ('MetaData "ChxCredit0" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "CreditCreditWords" 'PrefixI 'True) (S1 ('MetaSel ('Just "creditCreditWords") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FormattedTextId)) :+: C1 ('MetaCons "CreditCreditSymbol" 'PrefixI 'True) (S1 ('MetaSel ('Just "creditCreditSymbol") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FormattedSymbolId)))

data ChxCredit1 Source #

credit (choice)

Constructors

ChxCreditCreditWords 

Fields

ChxCreditCreditSymbol 

Fields

Instances

Instances details
Generic ChxCredit1 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxCredit1 :: Type -> Type #

Show ChxCredit1 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxCredit1 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxCredit1 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxCredit1 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxCredit1 = D1 ('MetaData "ChxCredit1" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "ChxCreditCreditWords" 'PrefixI 'True) (S1 ('MetaSel ('Just "chxcreditCreditWords") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FormattedTextId)) :+: C1 ('MetaCons "ChxCreditCreditSymbol" 'PrefixI 'True) (S1 ('MetaSel ('Just "chxcreditCreditSymbol") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FormattedSymbolId)))

data ChxCredit Source #

credit (choice)

Constructors

CreditCreditImage 

Fields

CreditCredit 

Instances

Instances details
Generic ChxCredit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxCredit :: Type -> Type #

Show ChxCredit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxCredit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxCredit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxCredit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxCredit = D1 ('MetaData "ChxCredit" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "CreditCreditImage" 'PrefixI 'True) (S1 ('MetaSel ('Just "creditCreditImage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Image)) :+: C1 ('MetaCons "CreditCredit" 'PrefixI 'True) (S1 ('MetaSel ('Just "chxcreditCredit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChxCredit0) :*: S1 ('MetaSel ('Just "creditCredit1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SeqCredit])))

data ChxDirectionType0 Source #

direction-type (choice)

Constructors

DirectionTypeWords 

Fields

DirectionTypeSymbol 

Fields

Instances

Instances details
Generic ChxDirectionType0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxDirectionType0 :: Type -> Type #

Show ChxDirectionType0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxDirectionType0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxDirectionType0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxDirectionType0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxDirectionType0 = D1 ('MetaData "ChxDirectionType0" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "DirectionTypeWords" 'PrefixI 'True) (S1 ('MetaSel ('Just "directionTypeWords") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FormattedTextId)) :+: C1 ('MetaCons "DirectionTypeSymbol" 'PrefixI 'True) (S1 ('MetaSel ('Just "directionTypeSymbol") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FormattedSymbolId)))

data ChxDirectionType Source #

direction-type (choice)

Constructors

DirectionTypeRehearsal 

Fields

DirectionTypeSegno 

Fields

DirectionTypeCoda 

Fields

DirectionTypeDirectionType 
DirectionTypeWedge 

Fields

DirectionTypeDynamics 

Fields

DirectionTypeDashes 

Fields

DirectionTypeBracket 

Fields

DirectionTypePedal 

Fields

DirectionTypeMetronome 

Fields

DirectionTypeOctaveShift 

Fields

DirectionTypeHarpPedals 

Fields

DirectionTypeDamp 

Fields

DirectionTypeDampAll 

Fields

DirectionTypeEyeglasses 

Fields

DirectionTypeStringMute 

Fields

DirectionTypeScordatura 

Fields

DirectionTypeImage 

Fields

DirectionTypePrincipalVoice 

Fields

DirectionTypePercussion 

Fields

DirectionTypeAccordionRegistration 

Fields

DirectionTypeStaffDivide 

Fields

DirectionTypeOtherDirection 

Fields

Instances

Instances details
Generic ChxDirectionType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxDirectionType :: Type -> Type #

Show ChxDirectionType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxDirectionType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxDirectionType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxDirectionType Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxDirectionType = D1 ('MetaData "ChxDirectionType" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) ((((C1 ('MetaCons "DirectionTypeRehearsal" 'PrefixI 'True) (S1 ('MetaSel ('Just "directionTypeRehearsal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FormattedTextId])) :+: C1 ('MetaCons "DirectionTypeSegno" 'PrefixI 'True) (S1 ('MetaSel ('Just "directionTypeSegno") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Segno]))) :+: (C1 ('MetaCons "DirectionTypeCoda" 'PrefixI 'True) (S1 ('MetaSel ('Just "directionTypeCoda") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Coda])) :+: (C1 ('MetaCons "DirectionTypeDirectionType" 'PrefixI 'True) (S1 ('MetaSel ('Just "chxdirectionTypeDirectionType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ChxDirectionType0])) :+: 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 EmptyPrintStyleAlignId)) :+: C1 ('MetaCons "DirectionTypeDampAll" 'PrefixI 'True) (S1 ('MetaSel ('Just "directionTypeDampAll") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EmptyPrintStyleAlignId)))) :+: (C1 ('MetaCons "DirectionTypeEyeglasses" 'PrefixI 'True) (S1 ('MetaSel ('Just "directionTypeEyeglasses") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EmptyPrintStyleAlignId)) :+: (C1 ('MetaCons "DirectionTypeStringMute" 'PrefixI 'True) (S1 ('MetaSel ('Just "directionTypeStringMute") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StringMute)) :+: 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 "DirectionTypePrincipalVoice" 'PrefixI 'True) (S1 ('MetaSel ('Just "directionTypePrincipalVoice") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrincipalVoice)) :+: C1 ('MetaCons "DirectionTypePercussion" 'PrefixI 'True) (S1 ('MetaSel ('Just "directionTypePercussion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Percussion])))) :+: (C1 ('MetaCons "DirectionTypeAccordionRegistration" 'PrefixI 'True) (S1 ('MetaSel ('Just "directionTypeAccordionRegistration") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccordionRegistration)) :+: (C1 ('MetaCons "DirectionTypeStaffDivide" 'PrefixI 'True) (S1 ('MetaSel ('Just "directionTypeStaffDivide") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StaffDivide)) :+: 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

DynamicsN 

Fields

DynamicsPf 

Fields

DynamicsSfzp 

Fields

DynamicsOtherDynamics 

Fields

Instances

Instances details
Generic ChxDynamics Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxDynamics :: Type -> Type #

Show ChxDynamics Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxDynamics Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxDynamics Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxDynamics Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxDynamics = D1 ('MetaData "ChxDynamics" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 "DynamicsN" 'PrefixI 'True) (S1 ('MetaSel ('Just "dynamicsN") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Empty)) :+: C1 ('MetaCons "DynamicsPf" 'PrefixI 'True) (S1 ('MetaSel ('Just "dynamicsPf") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Empty))) :+: (C1 ('MetaCons "DynamicsSfzp" 'PrefixI 'True) (S1 ('MetaSel ('Just "dynamicsSfzp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Empty)) :+: C1 ('MetaCons "DynamicsOtherDynamics" 'PrefixI 'True) (S1 ('MetaSel ('Just "dynamicsOtherDynamics") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OtherText)))))))

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

mkDynamicsN :: Empty -> ChxDynamics Source #

Smart constructor for DynamicsN

mkDynamicsPf :: Empty -> ChxDynamics Source #

Smart constructor for DynamicsPf

data ChxEncoding Source #

encoding (choice)

Constructors

EncodingEncodingDate 

Fields

EncodingEncoder 

Fields

EncodingSoftware 

Fields

EncodingEncodingDescription 

Fields

EncodingSupports 

Fields

Instances

Instances details
Generic ChxEncoding Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxEncoding :: Type -> Type #

Show ChxEncoding Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxEncoding Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxEncoding Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxEncoding Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxEncoding = D1 ('MetaData "ChxEncoding" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic FullNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep FullNote :: Type -> Type #

Methods

from :: FullNote -> Rep FullNote x #

to :: Rep FullNote x -> FullNote #

Show FullNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml FullNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq FullNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep FullNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep FullNote = D1 ('MetaData "FullNote" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 Unpitched)) :+: C1 ('MetaCons "FullNoteRest" 'PrefixI 'True) (S1 ('MetaSel ('Just "fullNoteRest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rest))))

mkFullNotePitch :: Pitch -> FullNote Source #

Smart constructor for FullNotePitch

mkFullNoteRest :: Rest -> FullNote Source #

Smart constructor for FullNoteRest

data ChxHarmonic Source #

harmonic (choice)

Constructors

HarmonicNatural 

Fields

HarmonicArtificial 

Fields

Instances

Instances details
Generic ChxHarmonic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxHarmonic :: Type -> Type #

Show ChxHarmonic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxHarmonic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxHarmonic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxHarmonic Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxHarmonic = D1 ('MetaData "ChxHarmonic" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic ChxHarmonic1 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxHarmonic1 :: Type -> Type #

Show ChxHarmonic1 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxHarmonic1 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxHarmonic1 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxHarmonic1 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxHarmonic1 = D1 ('MetaData "ChxHarmonic1" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic ChxHarmonyChord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxHarmonyChord :: Type -> Type #

Show ChxHarmonyChord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxHarmonyChord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxHarmonyChord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxHarmonyChord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxHarmonyChord = D1 ('MetaData "ChxHarmonyChord" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic ChxKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxKey :: Type -> Type #

Methods

from :: ChxKey -> Rep ChxKey x #

to :: Rep ChxKey x -> ChxKey #

Show ChxKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep ChxKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxKey = D1 ('MetaData "ChxKey" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic ChxLyric Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxLyric :: Type -> Type #

Methods

from :: ChxLyric -> Rep ChxLyric x #

to :: Rep ChxLyric x -> ChxLyric #

Show ChxLyric Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxLyric Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxLyric Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxLyric Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxLyric = D1 ('MetaData "ChxLyric" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) ((C1 ('MetaCons "LyricSyllabic" 'PrefixI 'True) ((S1 ('MetaSel ('Just "lyricSyllabic") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Syllabic)) :*: S1 ('MetaSel ('Just "lyricText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TextElementData)) :*: (S1 ('MetaSel ('Just "chxlyricLyric") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SeqLyric]) :*: S1 ('MetaSel ('Just "lyricExtend") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Extend)))) :+: C1 ('MetaCons "LyricExtend" 'PrefixI 'True) (S1 ('MetaSel ('Just "lyricExtend1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Extend))) :+: (C1 ('MetaCons "LyricLaughing" 'PrefixI 'True) (S1 ('MetaSel ('Just "lyricLaughing") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Empty)) :+: C1 ('MetaCons "LyricHumming" 'PrefixI 'True) (S1 ('MetaSel ('Just "lyricHumming") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Empty))))

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

Instances details
Generic ChxMeasureStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxMeasureStyle :: Type -> Type #

Show ChxMeasureStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxMeasureStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxMeasureStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxMeasureStyle Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxMeasureStyle = D1 ('MetaData "ChxMeasureStyle" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 

Fields

Instances

Instances details
Generic ChxMetronome0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxMetronome0 :: Type -> Type #

Show ChxMetronome0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxMetronome0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxMetronome0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxMetronome0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxMetronome0 = D1 ('MetaData "ChxMetronome0" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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) :*: S1 ('MetaSel ('Just "metronomeBeatUnitTied") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BeatUnitTied])))

data ChxMetronome Source #

metronome (choice)

Instances

Instances details
Generic ChxMetronome Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxMetronome :: Type -> Type #

Show ChxMetronome Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxMetronome Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxMetronome Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxMetronome Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxMetronome = D1 ('MetaData "ChxMetronome" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "ChxMetronomeBeatUnit" 'PrefixI 'True) (S1 ('MetaSel ('Just "chxmetronomeBeatUnit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BeatUnit) :*: (S1 ('MetaSel ('Just "chxmetronomeBeatUnitTied") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BeatUnitTied]) :*: S1 ('MetaSel ('Just "chxmetronomeMetronome") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChxMetronome0))) :+: C1 ('MetaCons "MetronomeMetronomeArrows" 'PrefixI 'True) (S1 ('MetaSel ('Just "metronomeMetronomeArrows") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Empty)) :*: (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

Instances details
Generic ChxMusicData Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxMusicData :: Type -> Type #

Show ChxMusicData Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxMusicData Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxMusicData Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxMusicData Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxMusicData = D1 ('MetaData "ChxMusicData" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic ChxNameDisplay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxNameDisplay :: Type -> Type #

Show ChxNameDisplay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxNameDisplay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxNameDisplay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxNameDisplay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxNameDisplay = D1 ('MetaData "ChxNameDisplay" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic ChxNotations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxNotations :: Type -> Type #

Show ChxNotations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxNotations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxNotations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxNotations Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxNotations = D1 ('MetaData "ChxNotations" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 ChxNote0 Source #

note (choice)

Constructors

NoteFullNote 

Fields

NoteCue 

Fields

Instances

Instances details
Generic ChxNote0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxNote0 :: Type -> Type #

Methods

from :: ChxNote0 -> Rep ChxNote0 x #

to :: Rep ChxNote0 x -> ChxNote0 #

Show ChxNote0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxNote0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxNote0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxNote0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxNote0 = D1 ('MetaData "ChxNote0" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "NoteFullNote" 'PrefixI 'True) (S1 ('MetaSel ('Just "noteFullNote") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GrpFullNote) :*: S1 ('MetaSel ('Just "noteTie") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tie])) :+: C1 ('MetaCons "NoteCue" 'PrefixI 'True) (S1 ('MetaSel ('Just "noteCue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Empty) :*: S1 ('MetaSel ('Just "noteFullNote1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GrpFullNote)))

mkNoteCue :: Empty -> GrpFullNote -> ChxNote0 Source #

Smart constructor for NoteCue

data ChxNote Source #

note (choice)

Constructors

NoteGrace 

Fields

ChxNoteCue 
ChxNoteFullNote 

Fields

Instances

Instances details
Generic ChxNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxNote :: Type -> Type #

Methods

from :: ChxNote -> Rep ChxNote x #

to :: Rep ChxNote x -> ChxNote #

Show ChxNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep ChxNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

mkNoteGrace :: Grace -> ChxNote0 -> ChxNote Source #

Smart constructor for NoteGrace

mkChxNoteCue :: Empty -> GrpFullNote -> Duration -> ChxNote Source #

Smart constructor for ChxNoteCue

data ChxNoteheadText Source #

notehead-text (choice)

Constructors

NoteheadTextDisplayText 

Fields

NoteheadTextAccidentalText 

Fields

Instances

Instances details
Generic ChxNoteheadText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxNoteheadText :: Type -> Type #

Show ChxNoteheadText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxNoteheadText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxNoteheadText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxNoteheadText Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxNoteheadText = D1 ('MetaData "ChxNoteheadText" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "NoteheadTextDisplayText" 'PrefixI 'True) (S1 ('MetaSel ('Just "noteheadTextDisplayText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FormattedText)) :+: C1 ('MetaCons "NoteheadTextAccidentalText" 'PrefixI 'True) (S1 ('MetaSel ('Just "noteheadTextAccidentalText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccidentalText)))

data ChxOrnaments Source #

ornaments (choice)

Constructors

OrnamentsTrillMark 

Fields

OrnamentsTurn 

Fields

OrnamentsDelayedTurn 

Fields

OrnamentsInvertedTurn 

Fields

OrnamentsDelayedInvertedTurn 

Fields

OrnamentsVerticalTurn 

Fields

OrnamentsInvertedVerticalTurn 

Fields

OrnamentsShake 

Fields

OrnamentsWavyLine 

Fields

OrnamentsMordent 

Fields

OrnamentsInvertedMordent 

Fields

OrnamentsSchleifer 

Fields

OrnamentsTremolo 

Fields

OrnamentsHaydn 

Fields

OrnamentsOtherOrnament 

Fields

Instances

Instances details
Generic ChxOrnaments Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxOrnaments :: Type -> Type #

Show ChxOrnaments Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxOrnaments Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxOrnaments Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxOrnaments Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxOrnaments = D1 ('MetaData "ChxOrnaments" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 HorizontalTurn)) :+: C1 ('MetaCons "OrnamentsDelayedTurn" 'PrefixI 'True) (S1 ('MetaSel ('Just "ornamentsDelayedTurn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HorizontalTurn)))) :+: ((C1 ('MetaCons "OrnamentsInvertedTurn" 'PrefixI 'True) (S1 ('MetaSel ('Just "ornamentsInvertedTurn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HorizontalTurn)) :+: C1 ('MetaCons "OrnamentsDelayedInvertedTurn" 'PrefixI 'True) (S1 ('MetaSel ('Just "ornamentsDelayedInvertedTurn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HorizontalTurn))) :+: (C1 ('MetaCons "OrnamentsVerticalTurn" 'PrefixI 'True) (S1 ('MetaSel ('Just "ornamentsVerticalTurn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EmptyTrillSound)) :+: C1 ('MetaCons "OrnamentsInvertedVerticalTurn" 'PrefixI 'True) (S1 ('MetaSel ('Just "ornamentsInvertedVerticalTurn") '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 "OrnamentsHaydn" 'PrefixI 'True) (S1 ('MetaSel ('Just "ornamentsHaydn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EmptyTrillSound)) :+: C1 ('MetaCons "OrnamentsOtherOrnament" 'PrefixI 'True) (S1 ('MetaSel ('Just "ornamentsOtherOrnament") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OtherPlacementText))))))

data ChxPartList Source #

part-list (choice)

Instances

Instances details
Generic ChxPartList Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxPartList :: Type -> Type #

Show ChxPartList Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxPartList Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxPartList Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxPartList Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxPartList = D1 ('MetaData "ChxPartList" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 ChxPercussion Source #

percussion (choice)

Constructors

PercussionGlass 

Fields

PercussionMetal 

Fields

PercussionWood 

Fields

PercussionPitched 

Fields

PercussionMembrane 

Fields

PercussionEffect 

Fields

PercussionTimpani 

Fields

PercussionBeater 

Fields

PercussionStick 

Fields

PercussionStickLocation 

Fields

PercussionOtherPercussion 

Fields

Instances

Instances details
Generic ChxPercussion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxPercussion :: Type -> Type #

Show ChxPercussion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxPercussion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxPercussion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxPercussion Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxPercussion = D1 ('MetaData "ChxPercussion" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (((C1 ('MetaCons "PercussionGlass" 'PrefixI 'True) (S1 ('MetaSel ('Just "percussionGlass") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Glass)) :+: C1 ('MetaCons "PercussionMetal" 'PrefixI 'True) (S1 ('MetaSel ('Just "percussionMetal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Metal))) :+: (C1 ('MetaCons "PercussionWood" 'PrefixI 'True) (S1 ('MetaSel ('Just "percussionWood") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Wood)) :+: (C1 ('MetaCons "PercussionPitched" 'PrefixI 'True) (S1 ('MetaSel ('Just "percussionPitched") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pitched)) :+: C1 ('MetaCons "PercussionMembrane" 'PrefixI 'True) (S1 ('MetaSel ('Just "percussionMembrane") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Membrane))))) :+: ((C1 ('MetaCons "PercussionEffect" 'PrefixI 'True) (S1 ('MetaSel ('Just "percussionEffect") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Effect)) :+: (C1 ('MetaCons "PercussionTimpani" 'PrefixI 'True) (S1 ('MetaSel ('Just "percussionTimpani") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Empty)) :+: C1 ('MetaCons "PercussionBeater" 'PrefixI 'True) (S1 ('MetaSel ('Just "percussionBeater") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Beater)))) :+: (C1 ('MetaCons "PercussionStick" 'PrefixI 'True) (S1 ('MetaSel ('Just "percussionStick") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Stick)) :+: (C1 ('MetaCons "PercussionStickLocation" 'PrefixI 'True) (S1 ('MetaSel ('Just "percussionStickLocation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StickLocation)) :+: C1 ('MetaCons "PercussionOtherPercussion" 'PrefixI 'True) (S1 ('MetaSel ('Just "percussionOtherPercussion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OtherText))))))

data ChxPlay Source #

play (choice)

Constructors

PlayIpa 

Fields

PlayMute 

Fields

PlaySemiPitched 

Fields

PlayOtherPlay 

Fields

Instances

Instances details
Generic ChxPlay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxPlay :: Type -> Type #

Methods

from :: ChxPlay -> Rep ChxPlay x #

to :: Rep ChxPlay x -> ChxPlay #

Show ChxPlay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxPlay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxPlay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep ChxPlay Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxPlay = D1 ('MetaData "ChxPlay" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) ((C1 ('MetaCons "PlayIpa" 'PrefixI 'True) (S1 ('MetaSel ('Just "playIpa") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "PlayMute" 'PrefixI 'True) (S1 ('MetaSel ('Just "playMute") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Mute))) :+: (C1 ('MetaCons "PlaySemiPitched" 'PrefixI 'True) (S1 ('MetaSel ('Just "playSemiPitched") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SemiPitched)) :+: C1 ('MetaCons "PlayOtherPlay" 'PrefixI 'True) (S1 ('MetaSel ('Just "playOtherPlay") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OtherPlay))))

mkPlayIpa :: String -> ChxPlay Source #

Smart constructor for PlayIpa

mkPlayMute :: Mute -> ChxPlay Source #

Smart constructor for PlayMute

data ChxScoreInstrument Source #

score-instrument (choice)

Constructors

ScoreInstrumentSolo 

Fields

ScoreInstrumentEnsemble 

Fields

Instances

Instances details
Generic ChxScoreInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxScoreInstrument :: Type -> Type #

Show ChxScoreInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxScoreInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxScoreInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxScoreInstrument Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxScoreInstrument = D1 ('MetaData "ChxScoreInstrument" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

TechnicalHole 

Fields

TechnicalArrow 

Fields

TechnicalHandbell 

Fields

TechnicalBrassBend 

Fields

TechnicalFlip 

Fields

TechnicalSmear 

Fields

TechnicalOpen 

Fields

TechnicalHalfMuted 

Fields

TechnicalHarmonMute 

Fields

TechnicalGolpe 

Fields

TechnicalOtherTechnical 

Fields

Instances

Instances details
Generic ChxTechnical Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxTechnical :: Type -> Type #

Show ChxTechnical Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxTechnical Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxTechnical Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxTechnical Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxTechnical = D1 ('MetaData "ChxTechnical" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 EmptyPlacementSmufl)) :+: 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 Tap))) :+: (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 "TechnicalHole" 'PrefixI 'True) (S1 ('MetaSel ('Just "technicalHole") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Hole))) :+: (C1 ('MetaCons "TechnicalArrow" 'PrefixI 'True) (S1 ('MetaSel ('Just "technicalArrow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Arrow)) :+: C1 ('MetaCons "TechnicalHandbell" 'PrefixI 'True) (S1 ('MetaSel ('Just "technicalHandbell") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Handbell))))) :+: (((C1 ('MetaCons "TechnicalBrassBend" 'PrefixI 'True) (S1 ('MetaSel ('Just "technicalBrassBend") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EmptyPlacement)) :+: C1 ('MetaCons "TechnicalFlip" 'PrefixI 'True) (S1 ('MetaSel ('Just "technicalFlip") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EmptyPlacement))) :+: (C1 ('MetaCons "TechnicalSmear" 'PrefixI 'True) (S1 ('MetaSel ('Just "technicalSmear") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EmptyPlacement)) :+: C1 ('MetaCons "TechnicalOpen" 'PrefixI 'True) (S1 ('MetaSel ('Just "technicalOpen") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EmptyPlacementSmufl)))) :+: ((C1 ('MetaCons "TechnicalHalfMuted" 'PrefixI 'True) (S1 ('MetaSel ('Just "technicalHalfMuted") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EmptyPlacementSmufl)) :+: C1 ('MetaCons "TechnicalHarmonMute" 'PrefixI 'True) (S1 ('MetaSel ('Just "technicalHarmonMute") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HarmonMute))) :+: (C1 ('MetaCons "TechnicalGolpe" 'PrefixI 'True) (S1 ('MetaSel ('Just "technicalGolpe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EmptyPlacement)) :+: C1 ('MetaCons "TechnicalOtherTechnical" 'PrefixI 'True) (S1 ('MetaSel ('Just "technicalOtherTechnical") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OtherPlacementText)))))))

mkTechnicalTap :: Tap -> ChxTechnical Source #

Smart constructor for TechnicalTap

data ChxTime Source #

time (choice)

Constructors

TimeTimeSignature 

Fields

TimeSenzaMisura 

Fields

Instances

Instances details
Generic ChxTime Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ChxTime :: Type -> Type #

Methods

from :: ChxTime -> Rep ChxTime x #

to :: Rep ChxTime x -> ChxTime #

Show ChxTime Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ChxTime Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ChxTime Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep ChxTime Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ChxTime = D1 ('MetaData "ChxTime" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "TimeTimeSignature" 'PrefixI 'True) (S1 ('MetaSel ('Just "timeTimeSignature") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TimeSignature]) :*: S1 ('MetaSel ('Just "timeInterchangeable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Interchangeable))) :+: C1 ('MetaCons "TimeSenzaMisura" 'PrefixI 'True) (S1 ('MetaSel ('Just "timeSenzaMisura") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

data SeqCredit Source #

credit (sequence)

Constructors

SeqCredit 

Fields

Instances

Instances details
Generic SeqCredit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep SeqCredit :: Type -> Type #

Show SeqCredit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml SeqCredit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq SeqCredit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SeqCredit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SeqCredit = D1 ('MetaData "SeqCredit" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 "seqcreditCredit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChxCredit1))))

mkSeqCredit :: ChxCredit1 -> SeqCredit Source #

Smart constructor for SeqCredit

data SeqLyric0 Source #

lyric (sequence)

Constructors

SeqLyric0 

Fields

Instances

Instances details
Generic SeqLyric0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep SeqLyric0 :: Type -> Type #

Show SeqLyric0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml SeqLyric0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq SeqLyric0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SeqLyric0 Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SeqLyric0 = D1 ('MetaData "SeqLyric0" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic SeqLyric Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep SeqLyric :: Type -> Type #

Methods

from :: SeqLyric -> Rep SeqLyric x #

to :: Rep SeqLyric x -> SeqLyric #

Show SeqLyric Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml SeqLyric Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq SeqLyric Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SeqLyric Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SeqLyric = D1 ('MetaData "SeqLyric" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic SeqMetronome Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep SeqMetronome :: Type -> Type #

Show SeqMetronome Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml SeqMetronome Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq SeqMetronome Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SeqMetronome Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SeqMetronome = D1 ('MetaData "SeqMetronome" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic SeqMetronomeTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep SeqMetronomeTuplet :: Type -> Type #

Show SeqMetronomeTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml SeqMetronomeTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq SeqMetronomeTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SeqMetronomeTuplet Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SeqMetronomeTuplet = D1 ('MetaData "SeqMetronomeTuplet" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic SeqOrnaments Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep SeqOrnaments :: Type -> Type #

Show SeqOrnaments Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml SeqOrnaments Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq SeqOrnaments Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SeqOrnaments Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SeqOrnaments = D1 ('MetaData "SeqOrnaments" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic SeqPageLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep SeqPageLayout :: Type -> Type #

Show SeqPageLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml SeqPageLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq SeqPageLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SeqPageLayout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SeqPageLayout = D1 ('MetaData "SeqPageLayout" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 SeqScorePart Source #

score-part (sequence)

Constructors

SeqScorePart 

Fields

Instances

Instances details
Generic SeqScorePart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep SeqScorePart :: Type -> Type #

Show SeqScorePart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml SeqScorePart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq SeqScorePart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SeqScorePart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SeqScorePart = D1 ('MetaData "SeqScorePart" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "SeqScorePart" 'PrefixI 'True) (S1 ('MetaSel ('Just "scorePartMidiDevice") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MidiDevice)) :*: S1 ('MetaSel ('Just "scorePartMidiInstrument") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MidiInstrument))))

data SeqSlash Source #

slash (sequence)

Constructors

SeqSlash 

Fields

Instances

Instances details
Generic SeqSlash Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep SeqSlash :: Type -> Type #

Methods

from :: SeqSlash -> Rep SeqSlash x #

to :: Rep SeqSlash x -> SeqSlash #

Show SeqSlash Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml SeqSlash Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq SeqSlash Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SeqSlash Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SeqSlash = D1 ('MetaData "SeqSlash" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "SeqSlash" 'PrefixI 'True) (S1 ('MetaSel ('Just "slashSlashType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NoteTypeValue) :*: S1 ('MetaSel ('Just "slashSlashDot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Empty])))

mkSeqSlash :: NoteTypeValue -> SeqSlash Source #

Smart constructor for SeqSlash

data SeqSound Source #

sound (sequence)

Constructors

SeqSound 

Fields

Instances

Instances details
Generic SeqSound Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep SeqSound :: Type -> Type #

Methods

from :: SeqSound -> Rep SeqSound x #

to :: Rep SeqSound x -> SeqSound #

Show SeqSound Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml SeqSound Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq SeqSound Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SeqSound Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SeqSound = D1 ('MetaData "SeqSound" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "SeqSound" 'PrefixI 'True) (S1 ('MetaSel ('Just "soundMidiDevice") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MidiDevice)) :*: (S1 ('MetaSel ('Just "soundMidiInstrument") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MidiInstrument)) :*: S1 ('MetaSel ('Just "soundPlay") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Play)))))

mkSeqSound :: SeqSound Source #

Smart constructor for SeqSound

data SeqTimeModification Source #

time-modification (sequence)

Constructors

SeqTimeModification 

Fields

Instances

Instances details
Generic SeqTimeModification Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep SeqTimeModification :: Type -> Type #

Show SeqTimeModification Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml SeqTimeModification Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq SeqTimeModification Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SeqTimeModification Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep SeqTimeModification = D1 ('MetaData "SeqTimeModification" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "SeqTimeModification" 'PrefixI 'True) (S1 ('MetaSel ('Just "timeModificationNormalType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NoteTypeValue) :*: S1 ('MetaSel ('Just "timeModificationNormalDot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Empty])))

data AllMargins Source #

all-margins (group)

Constructors

AllMargins 

Fields

Instances

Instances details
Generic AllMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep AllMargins :: Type -> Type #

Show AllMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml AllMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq AllMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep AllMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep AllMargins = D1 ('MetaData "AllMargins" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic BeatUnit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep BeatUnit :: Type -> Type #

Methods

from :: BeatUnit -> Rep BeatUnit x #

to :: Rep BeatUnit x -> BeatUnit #

Show BeatUnit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml BeatUnit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq BeatUnit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep BeatUnit Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep BeatUnit = D1 ('MetaData "BeatUnit" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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 DisplayStepOctave Source #

display-step-octave (group)

Constructors

DisplayStepOctave 

Fields

Instances

Instances details
Generic DisplayStepOctave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep DisplayStepOctave :: Type -> Type #

Show DisplayStepOctave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml DisplayStepOctave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq DisplayStepOctave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep DisplayStepOctave Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep DisplayStepOctave = D1 ('MetaData "DisplayStepOctave" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "DisplayStepOctave" 'PrefixI 'True) (S1 ('MetaSel ('Just "displayStepOctaveDisplayStep") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Step) :*: S1 ('MetaSel ('Just "displayStepOctaveDisplayOctave") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Octave)))

data Duration Source #

duration (group)

Constructors

Duration 

Fields

Instances

Instances details
Generic Duration Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Duration :: Type -> Type #

Methods

from :: Duration -> Rep Duration x #

to :: Rep Duration x -> Duration #

Show Duration Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Duration Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Duration Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Duration Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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

data Editorial Source #

editorial (group)

Instances

Instances details
Generic Editorial Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Editorial :: Type -> Type #

Show Editorial Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Editorial Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Editorial Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Editorial Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Editorial = D1 ('MetaData "Editorial" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic EditorialVoice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep EditorialVoice :: Type -> Type #

Show EditorialVoice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml EditorialVoice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq EditorialVoice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep EditorialVoice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep EditorialVoice = D1 ('MetaData "EditorialVoice" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic EditorialVoiceDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep EditorialVoiceDirection :: Type -> Type #

Show EditorialVoiceDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml EditorialVoiceDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq EditorialVoiceDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep EditorialVoiceDirection Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep EditorialVoiceDirection = D1 ('MetaData "EditorialVoiceDirection" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic Footnote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Footnote :: Type -> Type #

Methods

from :: Footnote -> Rep Footnote x #

to :: Rep Footnote x -> Footnote #

Show Footnote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Footnote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Footnote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Footnote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Footnote = D1 ('MetaData "Footnote" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic GrpFullNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep GrpFullNote :: Type -> Type #

Show GrpFullNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml GrpFullNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq GrpFullNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep GrpFullNote Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep GrpFullNote = D1 ('MetaData "GrpFullNote" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic HarmonyChord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep HarmonyChord :: Type -> Type #

Show HarmonyChord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml HarmonyChord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq HarmonyChord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep HarmonyChord Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep HarmonyChord = D1 ('MetaData "HarmonyChord" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic Layout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Layout :: Type -> Type #

Methods

from :: Layout -> Rep Layout x #

to :: Rep Layout x -> Layout #

Show Layout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Layout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Layout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Layout Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Layout = D1 ('MetaData "Layout" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic LeftRightMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep LeftRightMargins :: Type -> Type #

Show LeftRightMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml LeftRightMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq LeftRightMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep LeftRightMargins Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep LeftRightMargins = D1 ('MetaData "LeftRightMargins" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic GrpLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep GrpLevel :: Type -> Type #

Methods

from :: GrpLevel -> Rep GrpLevel x #

to :: Rep GrpLevel x -> GrpLevel #

Show GrpLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml GrpLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq GrpLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep GrpLevel Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep GrpLevel = D1 ('MetaData "GrpLevel" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic MusicData Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep MusicData :: Type -> Type #

Show MusicData Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml MusicData Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq MusicData Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MusicData Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep MusicData = D1 ('MetaData "MusicData" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic NonTraditionalKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep NonTraditionalKey :: Type -> Type #

Show NonTraditionalKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml NonTraditionalKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq NonTraditionalKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NonTraditionalKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep NonTraditionalKey = D1 ('MetaData "NonTraditionalKey" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "NonTraditionalKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "nonTraditionalKeyKeyStep") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Step) :*: (S1 ('MetaSel ('Just "nonTraditionalKeyKeyAlter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Semitones) :*: S1 ('MetaSel ('Just "nonTraditionalKeyKeyAccidental") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe KeyAccidental)))))

data GrpPartGroup Source #

part-group (group)

Constructors

GrpPartGroup 

Fields

Instances

Instances details
Generic GrpPartGroup Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep GrpPartGroup :: Type -> Type #

Show GrpPartGroup Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml GrpPartGroup Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq GrpPartGroup Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep GrpPartGroup Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep GrpPartGroup = D1 ('MetaData "GrpPartGroup" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic ScoreHeader Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ScoreHeader :: Type -> Type #

Show ScoreHeader Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ScoreHeader Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ScoreHeader Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ScoreHeader Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ScoreHeader = D1 ('MetaData "ScoreHeader" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic ScorePart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep ScorePart :: Type -> Type #

Show ScorePart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml ScorePart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq ScorePart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ScorePart Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep ScorePart = D1 ('MetaData "ScorePart" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "ScorePart" 'PrefixI 'True) (S1 ('MetaSel ('Just "grpscorePartScorePart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CmpScorePart)))

mkScorePart :: CmpScorePart -> ScorePart Source #

Smart constructor for ScorePart

data Slash Source #

slash (group)

Constructors

Slash 

Fields

Instances

Instances details
Generic Slash Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Slash :: Type -> Type #

Methods

from :: Slash -> Rep Slash x #

to :: Rep Slash x -> Slash #

Show Slash Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Slash -> ShowS #

show :: Slash -> String #

showList :: [Slash] -> ShowS #

EmitXml Slash Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Slash -> XmlRep Source #

Eq Slash Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Slash Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Slash = D1 ('MetaData "Slash" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "Slash" 'PrefixI 'True) (S1 ('MetaSel ('Just "grpslashSlash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SeqSlash)) :*: S1 ('MetaSel ('Just "slashExceptVoice") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])))

mkSlash :: Slash Source #

Smart constructor for Slash

data Staff Source #

staff (group)

Constructors

Staff 

Fields

Instances

Instances details
Generic Staff Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Staff :: Type -> Type #

Methods

from :: Staff -> Rep Staff x #

to :: Rep Staff x -> Staff #

Show Staff Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Staff -> ShowS #

show :: Staff -> String #

showList :: [Staff] -> ShowS #

EmitXml Staff Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Staff -> XmlRep Source #

Eq Staff Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Staff Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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

mkStaff :: PositiveInteger -> Staff Source #

Smart constructor for Staff

data TimeSignature Source #

time-signature (group)

Constructors

TimeSignature 

Fields

Instances

Instances details
Generic TimeSignature Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep TimeSignature :: Type -> Type #

Show TimeSignature Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml TimeSignature Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq TimeSignature Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TimeSignature Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TimeSignature = D1 ('MetaData "TimeSignature" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" 'False) (C1 ('MetaCons "TimeSignature" 'PrefixI 'True) (S1 ('MetaSel ('Just "timeSignatureBeats") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "timeSignatureBeatType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

data TraditionalKey Source #

traditional-key (group)

Constructors

TraditionalKey 

Fields

Instances

Instances details
Generic TraditionalKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep TraditionalKey :: Type -> Type #

Show TraditionalKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml TraditionalKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq TraditionalKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TraditionalKey Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep TraditionalKey = D1 ('MetaData "TraditionalKey" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic Tuning Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Tuning :: Type -> Type #

Methods

from :: Tuning -> Rep Tuning x #

to :: Rep Tuning x -> Tuning #

Show Tuning Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

EmitXml Tuning Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Eq Tuning Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Tuning Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

type Rep Tuning = D1 ('MetaData "Tuning" "Fadno.MusicXml.MusicXml31" "fadno-xml-1.2.1-FxsdrLn5vyXHX48wsPBBu6" '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

Instances details
Generic Voice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Associated Types

type Rep Voice :: Type -> Type #

Methods

from :: Voice -> Rep Voice x #

to :: Rep Voice x -> Voice #

Show Voice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

showsPrec :: Int -> Voice -> ShowS #

show :: Voice -> String #

showList :: [Voice] -> ShowS #

EmitXml Voice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

emitXml :: Voice -> XmlRep Source #

Eq Voice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

Methods

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

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

type Rep Voice Source # 
Instance details

Defined in Fadno.MusicXml.MusicXml31

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

mkVoice :: String -> Voice Source #

Smart constructor for Voice