| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Fadno.MusicXml.MusicXml20
- newtype ID = ID {}
- parseID :: String -> XParse ID
- newtype IDREF = IDREF {}
- parseIDREF :: String -> XParse IDREF
- newtype NCName = NCName {}
- parseNCName :: String -> XParse NCName
- newtype NMTOKEN = NMTOKEN {}
- parseNMTOKEN :: String -> XParse NMTOKEN
- newtype Name = Name {}
- parseName :: String -> XParse Name
- data AboveBelow
- parseAboveBelow :: String -> XParse AboveBelow
- data AccidentalValue
- = AccidentalValueSharp
- | AccidentalValueNatural
- | AccidentalValueFlat
- | AccidentalValueDoubleSharp
- | AccidentalValueSharpSharp
- | AccidentalValueFlatFlat
- | AccidentalValueNaturalSharp
- | AccidentalValueNaturalFlat
- | AccidentalValueQuarterFlat
- | AccidentalValueQuarterSharp
- | AccidentalValueThreeQuartersFlat
- | AccidentalValueThreeQuartersSharp
- parseAccidentalValue :: String -> XParse AccidentalValue
- newtype AccordionMiddle = AccordionMiddle {}
- parseAccordionMiddle :: String -> XParse AccordionMiddle
- data Actuate
- parseActuate :: String -> XParse Actuate
- data BackwardForward
- parseBackwardForward :: String -> XParse BackwardForward
- data BarStyle
- parseBarStyle :: String -> XParse BarStyle
- newtype BeamLevel = BeamLevel {}
- parseBeamLevel :: String -> XParse BeamLevel
- data BeamValue
- parseBeamValue :: String -> XParse BeamValue
- data ClefSign
- parseClefSign :: String -> XParse ClefSign
- newtype Color = Color {}
- parseColor :: String -> XParse Color
- newtype CommaSeparatedText = CommaSeparatedText {}
- parseCommaSeparatedText :: String -> XParse CommaSeparatedText
- data CssFontSize
- parseCssFontSize :: String -> XParse CssFontSize
- data DegreeTypeValue
- parseDegreeTypeValue :: String -> XParse DegreeTypeValue
- newtype Divisions = Divisions {}
- parseDivisions :: String -> XParse Divisions
- data Enclosure
- parseEnclosure :: String -> XParse Enclosure
- newtype EndingNumber = EndingNumber {}
- parseEndingNumber :: String -> XParse EndingNumber
- data Fan
- parseFan :: String -> XParse Fan
- data FermataShape
- parseFermataShape :: String -> XParse FermataShape
- newtype Fifths = Fifths {}
- parseFifths :: String -> XParse Fifths
- data FontSize
- = FontSizeDecimal { }
- | FontSizeCssFontSize { }
- parseFontSize :: String -> XParse FontSize
- data FontStyle
- parseFontStyle :: String -> XParse FontStyle
- data FontWeight
- parseFontWeight :: String -> XParse FontWeight
- data GroupBarlineValue
- parseGroupBarlineValue :: String -> XParse GroupBarlineValue
- data GroupSymbolValue
- parseGroupSymbolValue :: String -> XParse GroupSymbolValue
- data HarmonyType
- parseHarmonyType :: String -> XParse HarmonyType
- data KindValue
- = KindValueMajor
- | KindValueMinor
- | KindValueAugmented
- | KindValueDiminished
- | KindValueDominant
- | KindValueMajorSeventh
- | KindValueMinorSeventh
- | KindValueDiminishedSeventh
- | KindValueAugmentedSeventh
- | KindValueHalfDiminished
- | KindValueMajorMinor
- | KindValueMajorSixth
- | KindValueMinorSixth
- | KindValueDominantNinth
- | KindValueMajorNinth
- | KindValueMinorNinth
- | KindValueDominant11th
- | KindValueMajor11th
- | KindValueMinor11th
- | KindValueDominant13th
- | KindValueMajor13th
- | KindValueMinor13th
- | KindValueSuspendedSecond
- | KindValueSuspendedFourth
- | KindValueNeapolitan
- | KindValueItalian
- | KindValueFrench
- | KindValueGerman
- | KindValuePedal
- | KindValuePower
- | KindValueTristan
- | KindValueOther
- | KindValueNone
- parseKindValue :: String -> XParse KindValue
- data Lang
- parseLang :: String -> XParse Lang
- newtype Language = Language {}
- parseLanguage :: String -> XParse Language
- data LeftCenterRight
- parseLeftCenterRight :: String -> XParse LeftCenterRight
- data LeftRight
- parseLeftRight :: String -> XParse LeftRight
- data LineEnd
- parseLineEnd :: String -> XParse LineEnd
- data LineShape
- parseLineShape :: String -> XParse LineShape
- data LineType
- parseLineType :: String -> XParse LineType
- newtype LineWidthType = LineWidthType {}
- parseLineWidthType :: String -> XParse LineWidthType
- data MarginType
- parseMarginType :: String -> XParse MarginType
- data MeasureNumberingValue
- parseMeasureNumberingValue :: String -> XParse MeasureNumberingValue
- newtype Midi128 = Midi128 {}
- parseMidi128 :: String -> XParse Midi128
- newtype Midi16 = Midi16 {}
- parseMidi16 :: String -> XParse Midi16
- newtype Midi16384 = Midi16384 {}
- parseMidi16384 :: String -> XParse Midi16384
- newtype Millimeters = Millimeters {}
- parseMillimeters :: String -> XParse Millimeters
- newtype Mode = Mode {}
- parseMode :: String -> XParse Mode
- newtype NonNegativeDecimal = NonNegativeDecimal {}
- parseNonNegativeDecimal :: String -> XParse NonNegativeDecimal
- newtype NonNegativeInteger = NonNegativeInteger {}
- parseNonNegativeInteger :: String -> XParse NonNegativeInteger
- newtype NormalizedString = NormalizedString {}
- parseNormalizedString :: String -> XParse NormalizedString
- data NoteSizeType
- parseNoteSizeType :: String -> XParse NoteSizeType
- data NoteTypeValue
- parseNoteTypeValue :: String -> XParse NoteTypeValue
- data NoteheadValue
- = NoteheadValueSlash
- | NoteheadValueTriangle
- | NoteheadValueDiamond
- | NoteheadValueSquare
- | NoteheadValueCross
- | NoteheadValueX
- | NoteheadValueCircleX
- | NoteheadValueInvertedTriangle
- | NoteheadValueArrowDown
- | NoteheadValueArrowUp
- | NoteheadValueSlashed
- | NoteheadValueBackSlashed
- | NoteheadValueNormal
- | NoteheadValueCluster
- | NoteheadValueNone
- | NoteheadValueDo
- | NoteheadValueRe
- | NoteheadValueMi
- | NoteheadValueFa
- | NoteheadValueSo
- | NoteheadValueLa
- | NoteheadValueTi
- parseNoteheadValue :: String -> XParse NoteheadValue
- newtype NumberLevel = NumberLevel {}
- parseNumberLevel :: String -> XParse NumberLevel
- newtype NumberOfLines = NumberOfLines {}
- parseNumberOfLines :: String -> XParse NumberOfLines
- data NumberOrNormal
- parseNumberOrNormal :: String -> XParse NumberOrNormal
- newtype Octave = Octave {}
- parseOctave :: String -> XParse Octave
- data OverUnder
- parseOverUnder :: String -> XParse OverUnder
- newtype Percent = Percent {}
- parsePercent :: String -> XParse Percent
- newtype PositiveDivisions = PositiveDivisions {}
- parsePositiveDivisions :: String -> XParse PositiveDivisions
- data PositiveIntegerOrEmpty
- parsePositiveIntegerOrEmpty :: String -> XParse PositiveIntegerOrEmpty
- newtype PositiveInteger = PositiveInteger {}
- parsePositiveInteger :: String -> XParse PositiveInteger
- data RehearsalEnclosure
- parseRehearsalEnclosure :: String -> XParse RehearsalEnclosure
- data RightLeftMiddle
- parseRightLeftMiddle :: String -> XParse RightLeftMiddle
- newtype RotationDegrees = RotationDegrees {}
- parseRotationDegrees :: String -> XParse RotationDegrees
- newtype Semitones = Semitones {}
- parseSemitones :: String -> XParse Semitones
- data SmpShow
- parseSmpShow :: String -> XParse SmpShow
- data ShowFrets
- parseShowFrets :: String -> XParse ShowFrets
- data ShowTuplet
- parseShowTuplet :: String -> XParse ShowTuplet
- newtype StaffLine = StaffLine {}
- parseStaffLine :: String -> XParse StaffLine
- newtype StaffNumber = StaffNumber {}
- parseStaffNumber :: String -> XParse StaffNumber
- data StaffType
- parseStaffType :: String -> XParse StaffType
- data StartNote
- parseStartNote :: String -> XParse StartNote
- data StartStop
- parseStartStop :: String -> XParse StartStop
- data StartStopChange
- parseStartStopChange :: String -> XParse StartStopChange
- data StartStopContinue
- parseStartStopContinue :: String -> XParse StartStopContinue
- data StartStopDiscontinue
- parseStartStopDiscontinue :: String -> XParse StartStopDiscontinue
- data StartStopSingle
- parseStartStopSingle :: String -> XParse StartStopSingle
- data StemValue
- parseStemValue :: String -> XParse StemValue
- data Step
- parseStep :: String -> XParse Step
- newtype StringNumber = StringNumber {}
- parseStringNumber :: String -> XParse StringNumber
- data Syllabic
- parseSyllabic :: String -> XParse Syllabic
- data SymbolSize
- parseSymbolSize :: String -> XParse SymbolSize
- newtype Tenths = Tenths {}
- parseTenths :: String -> XParse Tenths
- data TextDirection
- parseTextDirection :: String -> XParse TextDirection
- data TimeSymbol
- parseTimeSymbol :: String -> XParse TimeSymbol
- newtype Token = Token {}
- parseToken :: String -> XParse Token
- data TopBottom
- parseTopBottom :: String -> XParse TopBottom
- newtype TremoloMarks = TremoloMarks {
- tremoloMarks :: Int
- parseTremoloMarks :: String -> XParse TremoloMarks
- newtype TrillBeats = TrillBeats {}
- parseTrillBeats :: String -> XParse TrillBeats
- data TrillStep
- parseTrillStep :: String -> XParse TrillStep
- data TwoNoteTurn
- parseTwoNoteTurn :: String -> XParse TwoNoteTurn
- data Type = TypeSimple
- parseType :: String -> XParse Type
- data UpDown
- parseUpDown :: String -> XParse UpDown
- data UpDownStop
- parseUpDownStop :: String -> XParse UpDownStop
- data UprightInverted
- parseUprightInverted :: String -> XParse UprightInverted
- data Valign
- parseValign :: String -> XParse Valign
- data ValignImage
- parseValignImage :: String -> XParse ValignImage
- data WedgeType
- parseWedgeType :: String -> XParse WedgeType
- data YesNo
- parseYesNo :: String -> XParse YesNo
- data YesNoNumber
- = YesNoNumberYesNo { }
- | YesNoNumberDecimal { }
- parseYesNoNumber :: String -> XParse YesNoNumber
- newtype YyyyMmDd = YyyyMmDd {}
- parseYyyyMmDd :: String -> XParse YyyyMmDd
- data SumLang = SumLang
- parseSumLang :: String -> XParse SumLang
- data SumNumberOrNormal = NumberOrNormalNormal
- parseSumNumberOrNormal :: String -> XParse SumNumberOrNormal
- data SumPositiveIntegerOrEmpty = SumPositiveIntegerOrEmpty
- parseSumPositiveIntegerOrEmpty :: String -> XParse SumPositiveIntegerOrEmpty
- data Accidental = Accidental {
- accidentalAccidentalValue :: AccidentalValue
- accidentalCautionary :: Maybe YesNo
- accidentalEditorial :: Maybe YesNo
- accidentalParentheses :: Maybe YesNo
- accidentalBracket :: Maybe YesNo
- accidentalSize :: Maybe SymbolSize
- accidentalDefaultX :: Maybe Tenths
- accidentalDefaultY :: Maybe Tenths
- accidentalRelativeX :: Maybe Tenths
- accidentalRelativeY :: Maybe Tenths
- accidentalFontFamily :: Maybe CommaSeparatedText
- accidentalFontStyle :: Maybe FontStyle
- accidentalFontSize :: Maybe FontSize
- accidentalFontWeight :: Maybe FontWeight
- accidentalColor :: Maybe Color
- parseAccidental :: XParse Accidental
- mkAccidental :: AccidentalValue -> Accidental
- data AccidentalMark = AccidentalMark {
- accidentalMarkAccidentalValue :: AccidentalValue
- accidentalMarkDefaultX :: Maybe Tenths
- accidentalMarkDefaultY :: Maybe Tenths
- accidentalMarkRelativeX :: Maybe Tenths
- accidentalMarkRelativeY :: Maybe Tenths
- accidentalMarkFontFamily :: Maybe CommaSeparatedText
- accidentalMarkFontStyle :: Maybe FontStyle
- accidentalMarkFontSize :: Maybe FontSize
- accidentalMarkFontWeight :: Maybe FontWeight
- accidentalMarkColor :: Maybe Color
- accidentalMarkPlacement :: Maybe AboveBelow
- parseAccidentalMark :: XParse AccidentalMark
- mkAccidentalMark :: AccidentalValue -> AccidentalMark
- data AccidentalText = AccidentalText {
- accidentalTextAccidentalValue :: AccidentalValue
- accidentalTextLang :: Maybe Lang
- accidentalTextEnclosure :: Maybe Enclosure
- accidentalTextJustify :: Maybe LeftCenterRight
- accidentalTextHalign :: Maybe LeftCenterRight
- accidentalTextValign :: Maybe Valign
- accidentalTextDefaultX :: Maybe Tenths
- accidentalTextDefaultY :: Maybe Tenths
- accidentalTextRelativeX :: Maybe Tenths
- accidentalTextRelativeY :: Maybe Tenths
- accidentalTextFontFamily :: Maybe CommaSeparatedText
- accidentalTextFontStyle :: Maybe FontStyle
- accidentalTextFontSize :: Maybe FontSize
- accidentalTextFontWeight :: Maybe FontWeight
- accidentalTextColor :: Maybe Color
- accidentalTextUnderline :: Maybe NumberOfLines
- accidentalTextOverline :: Maybe NumberOfLines
- accidentalTextLineThrough :: Maybe NumberOfLines
- accidentalTextRotation :: Maybe RotationDegrees
- accidentalTextLetterSpacing :: Maybe NumberOrNormal
- accidentalTextLineHeight :: Maybe NumberOrNormal
- accidentalTextDir :: Maybe TextDirection
- parseAccidentalText :: XParse AccidentalText
- mkAccidentalText :: AccidentalValue -> AccidentalText
- data Accord = Accord {}
- parseAccord :: XParse Accord
- mkAccord :: Tuning -> Accord
- data AccordionRegistration = AccordionRegistration {
- accordionRegistrationDefaultX :: Maybe Tenths
- accordionRegistrationDefaultY :: Maybe Tenths
- accordionRegistrationRelativeX :: Maybe Tenths
- accordionRegistrationRelativeY :: Maybe Tenths
- accordionRegistrationFontFamily :: Maybe CommaSeparatedText
- accordionRegistrationFontStyle :: Maybe FontStyle
- accordionRegistrationFontSize :: Maybe FontSize
- accordionRegistrationFontWeight :: Maybe FontWeight
- accordionRegistrationColor :: Maybe Color
- accordionRegistrationAccordionHigh :: Maybe Empty
- accordionRegistrationAccordionMiddle :: Maybe AccordionMiddle
- accordionRegistrationAccordionLow :: Maybe Empty
- parseAccordionRegistration :: XParse AccordionRegistration
- mkAccordionRegistration :: AccordionRegistration
- data Appearance = Appearance {}
- parseAppearance :: XParse Appearance
- mkAppearance :: Appearance
- data Arpeggiate = Arpeggiate {}
- parseArpeggiate :: XParse Arpeggiate
- mkArpeggiate :: Arpeggiate
- data Articulations = Articulations {}
- parseArticulations :: XParse Articulations
- mkArticulations :: Articulations
- data Attributes = Attributes {
- attributesEditorial :: Editorial
- attributesDivisions :: Maybe PositiveDivisions
- attributesKey :: [Key]
- attributesTime :: [Time]
- attributesStaves :: Maybe NonNegativeInteger
- attributesPartSymbol :: Maybe PartSymbol
- attributesInstruments :: Maybe NonNegativeInteger
- attributesClef :: [Clef]
- attributesStaffDetails :: [StaffDetails]
- attributesTranspose :: Maybe Transpose
- attributesDirective :: [Directive]
- attributesMeasureStyle :: [MeasureStyle]
- parseAttributes :: XParse Attributes
- mkAttributes :: Editorial -> Attributes
- data Backup = Backup {}
- parseBackup :: XParse Backup
- mkBackup :: Duration -> Editorial -> Backup
- data BarStyleColor = BarStyleColor {}
- parseBarStyleColor :: XParse BarStyleColor
- mkBarStyleColor :: BarStyle -> BarStyleColor
- data Barline = Barline {
- barlineLocation :: Maybe RightLeftMiddle
- barlineSegno :: Maybe Token
- barlineCoda :: Maybe Token
- barlineDivisions :: Maybe Divisions
- barlineBarStyle :: Maybe BarStyleColor
- barlineEditorial :: Editorial
- barlineWavyLine :: Maybe WavyLine
- barlineSegno1 :: Maybe EmptyPrintStyle
- barlineCoda1 :: Maybe EmptyPrintStyle
- barlineFermata :: [Fermata]
- barlineEnding :: Maybe Ending
- barlineRepeat :: Maybe Repeat
- parseBarline :: XParse Barline
- mkBarline :: Editorial -> Barline
- data Barre = Barre {}
- parseBarre :: XParse Barre
- mkBarre :: StartStop -> Barre
- data Bass = Bass {}
- parseBass :: XParse Bass
- mkBass :: BassStep -> Bass
- data BassAlter = BassAlter {
- bassAlterSemitones :: Semitones
- bassAlterLocation :: Maybe LeftRight
- bassAlterPrintObject :: Maybe YesNo
- bassAlterDefaultX :: Maybe Tenths
- bassAlterDefaultY :: Maybe Tenths
- bassAlterRelativeX :: Maybe Tenths
- bassAlterRelativeY :: Maybe Tenths
- bassAlterFontFamily :: Maybe CommaSeparatedText
- bassAlterFontStyle :: Maybe FontStyle
- bassAlterFontSize :: Maybe FontSize
- bassAlterFontWeight :: Maybe FontWeight
- bassAlterColor :: Maybe Color
- parseBassAlter :: XParse BassAlter
- mkBassAlter :: Semitones -> BassAlter
- data BassStep = BassStep {
- bassStepStep :: Step
- bassStepText :: Maybe Token
- bassStepDefaultX :: Maybe Tenths
- bassStepDefaultY :: Maybe Tenths
- bassStepRelativeX :: Maybe Tenths
- bassStepRelativeY :: Maybe Tenths
- bassStepFontFamily :: Maybe CommaSeparatedText
- bassStepFontStyle :: Maybe FontStyle
- bassStepFontSize :: Maybe FontSize
- bassStepFontWeight :: Maybe FontWeight
- bassStepColor :: Maybe Color
- parseBassStep :: XParse BassStep
- mkBassStep :: Step -> BassStep
- data Beam = Beam {}
- parseBeam :: XParse Beam
- mkBeam :: BeamValue -> Beam
- data BeatRepeat = BeatRepeat {}
- parseBeatRepeat :: XParse BeatRepeat
- mkBeatRepeat :: StartStop -> BeatRepeat
- data Bend = Bend {
- bendDefaultX :: Maybe Tenths
- bendDefaultY :: Maybe Tenths
- bendRelativeX :: Maybe Tenths
- bendRelativeY :: Maybe Tenths
- bendFontFamily :: Maybe CommaSeparatedText
- bendFontStyle :: Maybe FontStyle
- bendFontSize :: Maybe FontSize
- bendFontWeight :: Maybe FontWeight
- bendColor :: Maybe Color
- bendAccelerate :: Maybe YesNo
- bendBeats :: Maybe TrillBeats
- bendFirstBeat :: Maybe Percent
- bendLastBeat :: Maybe Percent
- bendBendAlter :: Semitones
- bendBend :: Maybe ChxBend
- bendWithBar :: Maybe PlacementText
- parseBend :: XParse Bend
- mkBend :: Semitones -> Bend
- data Bookmark = Bookmark {}
- parseBookmark :: XParse Bookmark
- mkBookmark :: ID -> Bookmark
- data Bracket = Bracket {
- bracketType :: StartStop
- bracketNumber :: Maybe NumberLevel
- bracketLineEnd :: LineEnd
- bracketEndLength :: Maybe Tenths
- bracketLineType :: Maybe LineType
- bracketDefaultX :: Maybe Tenths
- bracketDefaultY :: Maybe Tenths
- bracketRelativeX :: Maybe Tenths
- bracketRelativeY :: Maybe Tenths
- bracketColor :: Maybe Color
- parseBracket :: XParse Bracket
- mkBracket :: StartStop -> LineEnd -> Bracket
- data Cancel = Cancel {}
- parseCancel :: XParse Cancel
- mkCancel :: Fifths -> Cancel
- data Clef = Clef {
- clefNumber :: Maybe StaffNumber
- clefAdditional :: Maybe YesNo
- clefSize :: Maybe SymbolSize
- clefDefaultX :: Maybe Tenths
- clefDefaultY :: Maybe Tenths
- clefRelativeX :: Maybe Tenths
- clefRelativeY :: Maybe Tenths
- clefFontFamily :: Maybe CommaSeparatedText
- clefFontStyle :: Maybe FontStyle
- clefFontSize :: Maybe FontSize
- clefFontWeight :: Maybe FontWeight
- clefColor :: Maybe Color
- clefPrintObject :: Maybe YesNo
- clefSign :: ClefSign
- clefLine :: Maybe StaffLine
- clefClefOctaveChange :: Maybe Int
- parseClef :: XParse Clef
- mkClef :: ClefSign -> Clef
- data Credit = Credit {}
- parseCredit :: XParse Credit
- mkCredit :: ChxCredit -> Credit
- data Dashes = Dashes {}
- parseDashes :: XParse Dashes
- mkDashes :: StartStop -> Dashes
- data Defaults = Defaults {}
- parseDefaults :: XParse Defaults
- mkDefaults :: Layout -> Defaults
- data Degree = Degree {}
- parseDegree :: XParse Degree
- mkDegree :: DegreeValue -> DegreeAlter -> DegreeType -> Degree
- data DegreeAlter = DegreeAlter {
- degreeAlterSemitones :: Semitones
- degreeAlterPlusMinus :: Maybe YesNo
- degreeAlterDefaultX :: Maybe Tenths
- degreeAlterDefaultY :: Maybe Tenths
- degreeAlterRelativeX :: Maybe Tenths
- degreeAlterRelativeY :: Maybe Tenths
- degreeAlterFontFamily :: Maybe CommaSeparatedText
- degreeAlterFontStyle :: Maybe FontStyle
- degreeAlterFontSize :: Maybe FontSize
- degreeAlterFontWeight :: Maybe FontWeight
- degreeAlterColor :: Maybe Color
- parseDegreeAlter :: XParse DegreeAlter
- mkDegreeAlter :: Semitones -> DegreeAlter
- data DegreeType = DegreeType {
- degreeTypeDegreeTypeValue :: DegreeTypeValue
- degreeTypeText :: Maybe Token
- degreeTypeDefaultX :: Maybe Tenths
- degreeTypeDefaultY :: Maybe Tenths
- degreeTypeRelativeX :: Maybe Tenths
- degreeTypeRelativeY :: Maybe Tenths
- degreeTypeFontFamily :: Maybe CommaSeparatedText
- degreeTypeFontStyle :: Maybe FontStyle
- degreeTypeFontSize :: Maybe FontSize
- degreeTypeFontWeight :: Maybe FontWeight
- degreeTypeColor :: Maybe Color
- parseDegreeType :: XParse DegreeType
- mkDegreeType :: DegreeTypeValue -> DegreeType
- data DegreeValue = DegreeValue {
- degreeValuePositiveInteger :: PositiveInteger
- degreeValueText :: Maybe Token
- degreeValueDefaultX :: Maybe Tenths
- degreeValueDefaultY :: Maybe Tenths
- degreeValueRelativeX :: Maybe Tenths
- degreeValueRelativeY :: Maybe Tenths
- degreeValueFontFamily :: Maybe CommaSeparatedText
- degreeValueFontStyle :: Maybe FontStyle
- degreeValueFontSize :: Maybe FontSize
- degreeValueFontWeight :: Maybe FontWeight
- degreeValueColor :: Maybe Color
- parseDegreeValue :: XParse DegreeValue
- mkDegreeValue :: PositiveInteger -> DegreeValue
- data Direction = Direction {}
- parseDirection :: XParse Direction
- mkDirection :: EditorialVoiceDirection -> Direction
- data DirectionType = DirectionType {}
- parseDirectionType :: XParse DirectionType
- mkDirectionType :: ChxDirectionType -> DirectionType
- data Directive = Directive {
- directiveString :: String
- directiveLang :: Maybe Lang
- directiveDefaultX :: Maybe Tenths
- directiveDefaultY :: Maybe Tenths
- directiveRelativeX :: Maybe Tenths
- directiveRelativeY :: Maybe Tenths
- directiveFontFamily :: Maybe CommaSeparatedText
- directiveFontStyle :: Maybe FontStyle
- directiveFontSize :: Maybe FontSize
- directiveFontWeight :: Maybe FontWeight
- directiveColor :: Maybe Color
- parseDirective :: XParse Directive
- mkDirective :: String -> Directive
- data DisplayStepOctave = DisplayStepOctave {}
- parseDisplayStepOctave :: XParse DisplayStepOctave
- mkDisplayStepOctave :: DisplayStepOctave
- data Dynamics = Dynamics {
- dynamicsDefaultX :: Maybe Tenths
- dynamicsDefaultY :: Maybe Tenths
- dynamicsRelativeX :: Maybe Tenths
- dynamicsRelativeY :: Maybe Tenths
- dynamicsFontFamily :: Maybe CommaSeparatedText
- dynamicsFontStyle :: Maybe FontStyle
- dynamicsFontSize :: Maybe FontSize
- dynamicsFontWeight :: Maybe FontWeight
- dynamicsColor :: Maybe Color
- dynamicsPlacement :: Maybe AboveBelow
- dynamicsDynamics :: [ChxDynamics]
- parseDynamics :: XParse Dynamics
- mkDynamics :: Dynamics
- data Elision = Elision {}
- parseElision :: XParse Elision
- mkElision :: String -> Elision
- data Empty = Empty
- parseEmpty :: XParse Empty
- mkEmpty :: Empty
- data EmptyFont = EmptyFont {}
- parseEmptyFont :: XParse EmptyFont
- mkEmptyFont :: EmptyFont
- data EmptyLine = EmptyLine {
- emptyLineLineShape :: Maybe LineShape
- emptyLineLineType :: Maybe LineType
- emptyLineDefaultX :: Maybe Tenths
- emptyLineDefaultY :: Maybe Tenths
- emptyLineRelativeX :: Maybe Tenths
- emptyLineRelativeY :: Maybe Tenths
- emptyLineFontFamily :: Maybe CommaSeparatedText
- emptyLineFontStyle :: Maybe FontStyle
- emptyLineFontSize :: Maybe FontSize
- emptyLineFontWeight :: Maybe FontWeight
- emptyLineColor :: Maybe Color
- emptyLinePlacement :: Maybe AboveBelow
- parseEmptyLine :: XParse EmptyLine
- mkEmptyLine :: EmptyLine
- data EmptyPlacement = EmptyPlacement {
- emptyPlacementDefaultX :: Maybe Tenths
- emptyPlacementDefaultY :: Maybe Tenths
- emptyPlacementRelativeX :: Maybe Tenths
- emptyPlacementRelativeY :: Maybe Tenths
- emptyPlacementFontFamily :: Maybe CommaSeparatedText
- emptyPlacementFontStyle :: Maybe FontStyle
- emptyPlacementFontSize :: Maybe FontSize
- emptyPlacementFontWeight :: Maybe FontWeight
- emptyPlacementColor :: Maybe Color
- emptyPlacementPlacement :: Maybe AboveBelow
- parseEmptyPlacement :: XParse EmptyPlacement
- mkEmptyPlacement :: EmptyPlacement
- data EmptyPrintStyle = EmptyPrintStyle {
- emptyPrintStyleDefaultX :: Maybe Tenths
- emptyPrintStyleDefaultY :: Maybe Tenths
- emptyPrintStyleRelativeX :: Maybe Tenths
- emptyPrintStyleRelativeY :: Maybe Tenths
- emptyPrintStyleFontFamily :: Maybe CommaSeparatedText
- emptyPrintStyleFontStyle :: Maybe FontStyle
- emptyPrintStyleFontSize :: Maybe FontSize
- emptyPrintStyleFontWeight :: Maybe FontWeight
- emptyPrintStyleColor :: Maybe Color
- parseEmptyPrintStyle :: XParse EmptyPrintStyle
- mkEmptyPrintStyle :: EmptyPrintStyle
- data EmptyTrillSound = EmptyTrillSound {
- emptyTrillSoundDefaultX :: Maybe Tenths
- emptyTrillSoundDefaultY :: Maybe Tenths
- emptyTrillSoundRelativeX :: Maybe Tenths
- emptyTrillSoundRelativeY :: Maybe Tenths
- emptyTrillSoundFontFamily :: Maybe CommaSeparatedText
- emptyTrillSoundFontStyle :: Maybe FontStyle
- emptyTrillSoundFontSize :: Maybe FontSize
- emptyTrillSoundFontWeight :: Maybe FontWeight
- emptyTrillSoundColor :: Maybe Color
- emptyTrillSoundPlacement :: Maybe AboveBelow
- emptyTrillSoundStartNote :: Maybe StartNote
- emptyTrillSoundTrillStep :: Maybe TrillStep
- emptyTrillSoundTwoNoteTurn :: Maybe TwoNoteTurn
- emptyTrillSoundAccelerate :: Maybe YesNo
- emptyTrillSoundBeats :: Maybe TrillBeats
- emptyTrillSoundSecondBeat :: Maybe Percent
- emptyTrillSoundLastBeat :: Maybe Percent
- parseEmptyTrillSound :: XParse EmptyTrillSound
- mkEmptyTrillSound :: EmptyTrillSound
- data Encoding = Encoding {}
- parseEncoding :: XParse Encoding
- mkEncoding :: Encoding
- data Ending = Ending {
- endingString :: String
- cmpendingNumber :: EndingNumber
- endingType :: StartStopDiscontinue
- endingEndLength :: Maybe Tenths
- endingTextX :: Maybe Tenths
- endingTextY :: Maybe Tenths
- endingPrintObject :: Maybe YesNo
- endingDefaultX :: Maybe Tenths
- endingDefaultY :: Maybe Tenths
- endingRelativeX :: Maybe Tenths
- endingRelativeY :: Maybe Tenths
- endingFontFamily :: Maybe CommaSeparatedText
- endingFontStyle :: Maybe FontStyle
- endingFontSize :: Maybe FontSize
- endingFontWeight :: Maybe FontWeight
- endingColor :: Maybe Color
- parseEnding :: XParse Ending
- mkEnding :: String -> EndingNumber -> StartStopDiscontinue -> Ending
- data Extend = Extend {}
- parseExtend :: XParse Extend
- mkExtend :: Extend
- data Feature = Feature {}
- parseFeature :: XParse Feature
- mkFeature :: String -> Feature
- data Fermata = Fermata {
- fermataFermataShape :: FermataShape
- fermataType :: Maybe UprightInverted
- fermataDefaultX :: Maybe Tenths
- fermataDefaultY :: Maybe Tenths
- fermataRelativeX :: Maybe Tenths
- fermataRelativeY :: Maybe Tenths
- fermataFontFamily :: Maybe CommaSeparatedText
- fermataFontStyle :: Maybe FontStyle
- fermataFontSize :: Maybe FontSize
- fermataFontWeight :: Maybe FontWeight
- fermataColor :: Maybe Color
- parseFermata :: XParse Fermata
- mkFermata :: FermataShape -> Fermata
- data Figure = Figure {}
- parseFigure :: XParse Figure
- mkFigure :: Figure
- data FiguredBass = FiguredBass {
- figuredBassParentheses :: Maybe YesNo
- figuredBassDefaultX :: Maybe Tenths
- figuredBassDefaultY :: Maybe Tenths
- figuredBassRelativeX :: Maybe Tenths
- figuredBassRelativeY :: Maybe Tenths
- figuredBassFontFamily :: Maybe CommaSeparatedText
- figuredBassFontStyle :: Maybe FontStyle
- figuredBassFontSize :: Maybe FontSize
- figuredBassFontWeight :: Maybe FontWeight
- figuredBassColor :: Maybe Color
- figuredBassPrintDot :: Maybe YesNo
- figuredBassPrintLyric :: Maybe YesNo
- figuredBassPrintObject :: Maybe YesNo
- figuredBassPrintSpacing :: Maybe YesNo
- figuredBassFigure :: [Figure]
- figuredBassDuration :: Maybe Duration
- figuredBassEditorial :: Editorial
- parseFiguredBass :: XParse FiguredBass
- mkFiguredBass :: Editorial -> FiguredBass
- data Fingering = Fingering {
- fingeringString :: String
- fingeringSubstitution :: Maybe YesNo
- fingeringAlternate :: Maybe YesNo
- fingeringDefaultX :: Maybe Tenths
- fingeringDefaultY :: Maybe Tenths
- fingeringRelativeX :: Maybe Tenths
- fingeringRelativeY :: Maybe Tenths
- fingeringFontFamily :: Maybe CommaSeparatedText
- fingeringFontStyle :: Maybe FontStyle
- fingeringFontSize :: Maybe FontSize
- fingeringFontWeight :: Maybe FontWeight
- fingeringColor :: Maybe Color
- fingeringPlacement :: Maybe AboveBelow
- parseFingering :: XParse Fingering
- mkFingering :: String -> Fingering
- data FirstFret = FirstFret {}
- parseFirstFret :: XParse FirstFret
- mkFirstFret :: PositiveInteger -> FirstFret
- data FormattedText = FormattedText {
- formattedTextString :: String
- formattedTextLang :: Maybe Lang
- formattedTextEnclosure :: Maybe Enclosure
- formattedTextJustify :: Maybe LeftCenterRight
- formattedTextHalign :: Maybe LeftCenterRight
- formattedTextValign :: Maybe Valign
- formattedTextDefaultX :: Maybe Tenths
- formattedTextDefaultY :: Maybe Tenths
- formattedTextRelativeX :: Maybe Tenths
- formattedTextRelativeY :: Maybe Tenths
- formattedTextFontFamily :: Maybe CommaSeparatedText
- formattedTextFontStyle :: Maybe FontStyle
- formattedTextFontSize :: Maybe FontSize
- formattedTextFontWeight :: Maybe FontWeight
- formattedTextColor :: Maybe Color
- formattedTextUnderline :: Maybe NumberOfLines
- formattedTextOverline :: Maybe NumberOfLines
- formattedTextLineThrough :: Maybe NumberOfLines
- formattedTextRotation :: Maybe RotationDegrees
- formattedTextLetterSpacing :: Maybe NumberOrNormal
- formattedTextLineHeight :: Maybe NumberOrNormal
- formattedTextDir :: Maybe TextDirection
- parseFormattedText :: XParse FormattedText
- mkFormattedText :: String -> FormattedText
- data Forward = Forward {}
- parseForward :: XParse Forward
- mkForward :: Duration -> EditorialVoice -> Forward
- data Frame = Frame {
- frameHeight :: Maybe Tenths
- frameWidth :: Maybe Tenths
- frameDefaultX :: Maybe Tenths
- frameDefaultY :: Maybe Tenths
- frameRelativeX :: Maybe Tenths
- frameRelativeY :: Maybe Tenths
- frameColor :: Maybe Color
- frameHalign :: Maybe LeftCenterRight
- frameValign :: Maybe Valign
- frameFrameStrings :: PositiveInteger
- frameFrameFrets :: PositiveInteger
- frameFirstFret :: Maybe FirstFret
- frameFrameNote :: [FrameNote]
- parseFrame :: XParse Frame
- mkFrame :: PositiveInteger -> PositiveInteger -> Frame
- data FrameNote = FrameNote {}
- parseFrameNote :: XParse FrameNote
- mkFrameNote :: CmpString -> Fret -> FrameNote
- data Fret = Fret {}
- parseFret :: XParse Fret
- mkFret :: NonNegativeInteger -> Fret
- data Glissando = Glissando {
- glissandoString :: String
- glissandoType :: StartStop
- glissandoNumber :: Maybe NumberLevel
- glissandoLineType :: Maybe LineType
- glissandoDefaultX :: Maybe Tenths
- glissandoDefaultY :: Maybe Tenths
- glissandoRelativeX :: Maybe Tenths
- glissandoRelativeY :: Maybe Tenths
- glissandoFontFamily :: Maybe CommaSeparatedText
- glissandoFontStyle :: Maybe FontStyle
- glissandoFontSize :: Maybe FontSize
- glissandoFontWeight :: Maybe FontWeight
- glissandoColor :: Maybe Color
- parseGlissando :: XParse Glissando
- mkGlissando :: String -> StartStop -> Glissando
- data Grace = Grace {}
- parseGrace :: XParse Grace
- mkGrace :: Grace
- data GroupBarline = GroupBarline {}
- parseGroupBarline :: XParse GroupBarline
- mkGroupBarline :: GroupBarlineValue -> GroupBarline
- data GroupName = GroupName {
- groupNameString :: String
- groupNameDefaultX :: Maybe Tenths
- groupNameDefaultY :: Maybe Tenths
- groupNameRelativeX :: Maybe Tenths
- groupNameRelativeY :: Maybe Tenths
- groupNameFontFamily :: Maybe CommaSeparatedText
- groupNameFontStyle :: Maybe FontStyle
- groupNameFontSize :: Maybe FontSize
- groupNameFontWeight :: Maybe FontWeight
- groupNameColor :: Maybe Color
- groupNameJustify :: Maybe LeftCenterRight
- parseGroupName :: XParse GroupName
- mkGroupName :: String -> GroupName
- data GroupSymbol = GroupSymbol {}
- parseGroupSymbol :: XParse GroupSymbol
- mkGroupSymbol :: GroupSymbolValue -> GroupSymbol
- data Grouping = Grouping {}
- parseGrouping :: XParse Grouping
- mkGrouping :: StartStopSingle -> Grouping
- data HammerOnPullOff = HammerOnPullOff {
- hammerOnPullOffString :: String
- hammerOnPullOffType :: StartStop
- hammerOnPullOffNumber :: Maybe NumberLevel
- hammerOnPullOffDefaultX :: Maybe Tenths
- hammerOnPullOffDefaultY :: Maybe Tenths
- hammerOnPullOffRelativeX :: Maybe Tenths
- hammerOnPullOffRelativeY :: Maybe Tenths
- hammerOnPullOffFontFamily :: Maybe CommaSeparatedText
- hammerOnPullOffFontStyle :: Maybe FontStyle
- hammerOnPullOffFontSize :: Maybe FontSize
- hammerOnPullOffFontWeight :: Maybe FontWeight
- hammerOnPullOffColor :: Maybe Color
- hammerOnPullOffPlacement :: Maybe AboveBelow
- parseHammerOnPullOff :: XParse HammerOnPullOff
- mkHammerOnPullOff :: String -> StartStop -> HammerOnPullOff
- data Harmonic = Harmonic {
- harmonicPrintObject :: Maybe YesNo
- harmonicDefaultX :: Maybe Tenths
- harmonicDefaultY :: Maybe Tenths
- harmonicRelativeX :: Maybe Tenths
- harmonicRelativeY :: Maybe Tenths
- harmonicFontFamily :: Maybe CommaSeparatedText
- harmonicFontStyle :: Maybe FontStyle
- harmonicFontSize :: Maybe FontSize
- harmonicFontWeight :: Maybe FontWeight
- harmonicColor :: Maybe Color
- harmonicPlacement :: Maybe AboveBelow
- harmonicHarmonic :: Maybe ChxHarmonic
- harmonicHarmonic1 :: Maybe ChxHarmonic1
- parseHarmonic :: XParse Harmonic
- mkHarmonic :: Harmonic
- data Harmony = Harmony {
- harmonyType :: Maybe HarmonyType
- harmonyPrintFrame :: Maybe YesNo
- harmonyPrintObject :: Maybe YesNo
- harmonyDefaultX :: Maybe Tenths
- harmonyDefaultY :: Maybe Tenths
- harmonyRelativeX :: Maybe Tenths
- harmonyRelativeY :: Maybe Tenths
- harmonyFontFamily :: Maybe CommaSeparatedText
- harmonyFontStyle :: Maybe FontStyle
- harmonyFontSize :: Maybe FontSize
- harmonyFontWeight :: Maybe FontWeight
- harmonyColor :: Maybe Color
- harmonyPlacement :: Maybe AboveBelow
- harmonyHarmonyChord :: [HarmonyChord]
- harmonyFrame :: Maybe Frame
- harmonyOffset :: Maybe Offset
- harmonyEditorial :: Editorial
- harmonyStaff :: Maybe Staff
- parseHarmony :: XParse Harmony
- mkHarmony :: Editorial -> Harmony
- data HarpPedals = HarpPedals {
- harpPedalsDefaultX :: Maybe Tenths
- harpPedalsDefaultY :: Maybe Tenths
- harpPedalsRelativeX :: Maybe Tenths
- harpPedalsRelativeY :: Maybe Tenths
- harpPedalsFontFamily :: Maybe CommaSeparatedText
- harpPedalsFontStyle :: Maybe FontStyle
- harpPedalsFontSize :: Maybe FontSize
- harpPedalsFontWeight :: Maybe FontWeight
- harpPedalsColor :: Maybe Color
- harpPedalsPedalTuning :: [PedalTuning]
- parseHarpPedals :: XParse HarpPedals
- mkHarpPedals :: HarpPedals
- data HeelToe = HeelToe {}
- parseHeelToe :: XParse HeelToe
- mkHeelToe :: HeelToe -> HeelToe
- data Identification = Identification {}
- parseIdentification :: XParse Identification
- mkIdentification :: Identification
- data Image = Image {}
- parseImage :: XParse Image
- mkImage :: String -> Token -> Image
- data Instrument = Instrument {}
- parseInstrument :: XParse Instrument
- mkInstrument :: IDREF -> Instrument
- data Inversion = Inversion {
- inversionNonNegativeInteger :: NonNegativeInteger
- inversionDefaultX :: Maybe Tenths
- inversionDefaultY :: Maybe Tenths
- inversionRelativeX :: Maybe Tenths
- inversionRelativeY :: Maybe Tenths
- inversionFontFamily :: Maybe CommaSeparatedText
- inversionFontStyle :: Maybe FontStyle
- inversionFontSize :: Maybe FontSize
- inversionFontWeight :: Maybe FontWeight
- inversionColor :: Maybe Color
- parseInversion :: XParse Inversion
- mkInversion :: NonNegativeInteger -> Inversion
- data Key = Key {
- keyNumber :: Maybe StaffNumber
- keyDefaultX :: Maybe Tenths
- keyDefaultY :: Maybe Tenths
- keyRelativeX :: Maybe Tenths
- keyRelativeY :: Maybe Tenths
- keyFontFamily :: Maybe CommaSeparatedText
- keyFontStyle :: Maybe FontStyle
- keyFontSize :: Maybe FontSize
- keyFontWeight :: Maybe FontWeight
- keyColor :: Maybe Color
- keyPrintObject :: Maybe YesNo
- keyKey :: ChxKey
- keyKeyOctave :: [KeyOctave]
- parseKey :: XParse Key
- mkKey :: ChxKey -> Key
- data KeyOctave = KeyOctave {}
- parseKeyOctave :: XParse KeyOctave
- mkKeyOctave :: Octave -> PositiveInteger -> KeyOctave
- data Kind = Kind {
- kindKindValue :: KindValue
- kindUseSymbols :: Maybe YesNo
- kindText :: Maybe Token
- kindStackDegrees :: Maybe YesNo
- kindParenthesesDegrees :: Maybe YesNo
- kindBracketDegrees :: Maybe YesNo
- kindDefaultX :: Maybe Tenths
- kindDefaultY :: Maybe Tenths
- kindRelativeX :: Maybe Tenths
- kindRelativeY :: Maybe Tenths
- kindFontFamily :: Maybe CommaSeparatedText
- kindFontStyle :: Maybe FontStyle
- kindFontSize :: Maybe FontSize
- kindFontWeight :: Maybe FontWeight
- kindColor :: Maybe Color
- kindHalign :: Maybe LeftCenterRight
- kindValign :: Maybe Valign
- parseKind :: XParse Kind
- mkKind :: KindValue -> Kind
- data Level = Level {}
- parseLevel :: XParse Level
- mkLevel :: String -> Level
- data LineWidth = LineWidth {}
- parseLineWidth :: XParse LineWidth
- mkLineWidth :: Tenths -> LineWidthType -> LineWidth
- data Link = Link {
- linkName :: Maybe Token
- linkHref :: String
- linkType :: Maybe Type
- linkRole :: Maybe Token
- linkTitle :: Maybe Token
- linkShow :: Maybe SmpShow
- linkActuate :: Maybe Actuate
- linkElement :: Maybe NMTOKEN
- linkPosition :: Maybe PositiveInteger
- linkDefaultX :: Maybe Tenths
- linkDefaultY :: Maybe Tenths
- linkRelativeX :: Maybe Tenths
- linkRelativeY :: Maybe Tenths
- parseLink :: XParse Link
- mkLink :: String -> Link
- data Lyric = Lyric {
- lyricNumber :: Maybe NMTOKEN
- lyricName :: Maybe Token
- lyricJustify :: Maybe LeftCenterRight
- lyricDefaultX :: Maybe Tenths
- lyricDefaultY :: Maybe Tenths
- lyricRelativeX :: Maybe Tenths
- lyricRelativeY :: Maybe Tenths
- lyricPlacement :: Maybe AboveBelow
- lyricColor :: Maybe Color
- lyricLyric :: ChxLyric
- lyricEndLine :: Maybe Empty
- lyricEndParagraph :: Maybe Empty
- lyricEditorial :: Editorial
- parseLyric :: XParse Lyric
- mkLyric :: ChxLyric -> Editorial -> Lyric
- data LyricFont = LyricFont {}
- parseLyricFont :: XParse LyricFont
- mkLyricFont :: LyricFont
- data LyricLanguage = LyricLanguage {}
- parseLyricLanguage :: XParse LyricLanguage
- mkLyricLanguage :: Lang -> LyricLanguage
- data Measure = Measure {}
- parseMeasure :: XParse Measure
- mkMeasure :: Token -> MusicData -> Measure
- data CmpMeasure = CmpMeasure {}
- parseCmpMeasure :: XParse CmpMeasure
- mkCmpMeasure :: Token -> CmpMeasure
- data MeasureLayout = MeasureLayout {}
- parseMeasureLayout :: XParse MeasureLayout
- mkMeasureLayout :: MeasureLayout
- data MeasureNumbering = MeasureNumbering {
- measureNumberingMeasureNumberingValue :: MeasureNumberingValue
- measureNumberingDefaultX :: Maybe Tenths
- measureNumberingDefaultY :: Maybe Tenths
- measureNumberingRelativeX :: Maybe Tenths
- measureNumberingRelativeY :: Maybe Tenths
- measureNumberingFontFamily :: Maybe CommaSeparatedText
- measureNumberingFontStyle :: Maybe FontStyle
- measureNumberingFontSize :: Maybe FontSize
- measureNumberingFontWeight :: Maybe FontWeight
- measureNumberingColor :: Maybe Color
- parseMeasureNumbering :: XParse MeasureNumbering
- mkMeasureNumbering :: MeasureNumberingValue -> MeasureNumbering
- data MeasureRepeat = MeasureRepeat {}
- parseMeasureRepeat :: XParse MeasureRepeat
- mkMeasureRepeat :: PositiveIntegerOrEmpty -> StartStop -> MeasureRepeat
- data MeasureStyle = MeasureStyle {}
- parseMeasureStyle :: XParse MeasureStyle
- mkMeasureStyle :: ChxMeasureStyle -> MeasureStyle
- data Metronome = Metronome {
- metronomeParentheses :: Maybe YesNo
- metronomeDefaultX :: Maybe Tenths
- metronomeDefaultY :: Maybe Tenths
- metronomeRelativeX :: Maybe Tenths
- metronomeRelativeY :: Maybe Tenths
- metronomeFontFamily :: Maybe CommaSeparatedText
- metronomeFontStyle :: Maybe FontStyle
- metronomeFontSize :: Maybe FontSize
- metronomeFontWeight :: Maybe FontWeight
- metronomeColor :: Maybe Color
- metronomeMetronome :: ChxMetronome
- parseMetronome :: XParse Metronome
- mkMetronome :: ChxMetronome -> Metronome
- data MetronomeBeam = MetronomeBeam {}
- parseMetronomeBeam :: XParse MetronomeBeam
- mkMetronomeBeam :: BeamValue -> MetronomeBeam
- data MetronomeNote = MetronomeNote {}
- parseMetronomeNote :: XParse MetronomeNote
- mkMetronomeNote :: NoteTypeValue -> MetronomeNote
- data MetronomeTuplet = MetronomeTuplet {}
- parseMetronomeTuplet :: XParse MetronomeTuplet
- mkMetronomeTuplet :: MetronomeTuplet -> StartStop -> MetronomeTuplet
- data MidiDevice = MidiDevice {}
- parseMidiDevice :: XParse MidiDevice
- mkMidiDevice :: String -> MidiDevice
- data MidiInstrument = MidiInstrument {
- midiInstrumentId :: IDREF
- midiInstrumentMidiChannel :: Maybe Midi16
- midiInstrumentMidiName :: Maybe String
- midiInstrumentMidiBank :: Maybe Midi16384
- midiInstrumentMidiProgram :: Maybe Midi128
- midiInstrumentMidiUnpitched :: Maybe Midi128
- midiInstrumentVolume :: Maybe Percent
- midiInstrumentPan :: Maybe RotationDegrees
- midiInstrumentElevation :: Maybe RotationDegrees
- parseMidiInstrument :: XParse MidiInstrument
- mkMidiInstrument :: IDREF -> MidiInstrument
- data Miscellaneous = Miscellaneous {}
- parseMiscellaneous :: XParse Miscellaneous
- mkMiscellaneous :: Miscellaneous
- data MiscellaneousField = MiscellaneousField {}
- parseMiscellaneousField :: XParse MiscellaneousField
- mkMiscellaneousField :: String -> Token -> MiscellaneousField
- data Mordent = Mordent {}
- parseMordent :: XParse Mordent
- mkMordent :: Mordent -> Mordent
- data MultipleRest = MultipleRest {}
- parseMultipleRest :: XParse MultipleRest
- mkMultipleRest :: PositiveIntegerOrEmpty -> MultipleRest
- data NameDisplay = NameDisplay {}
- parseNameDisplay :: XParse NameDisplay
- mkNameDisplay :: NameDisplay
- data NonArpeggiate = NonArpeggiate {}
- parseNonArpeggiate :: XParse NonArpeggiate
- mkNonArpeggiate :: TopBottom -> NonArpeggiate
- data Notations = Notations {}
- parseNotations :: XParse Notations
- mkNotations :: Editorial -> Notations
- data Note = Note {
- noteDynamics :: Maybe NonNegativeDecimal
- noteEndDynamics :: Maybe NonNegativeDecimal
- noteAttack :: Maybe Divisions
- noteRelease :: Maybe Divisions
- noteTimeOnly :: Maybe Token
- notePizzicato :: Maybe YesNo
- noteDefaultX :: Maybe Tenths
- noteDefaultY :: Maybe Tenths
- noteRelativeX :: Maybe Tenths
- noteRelativeY :: Maybe Tenths
- noteFontFamily :: Maybe CommaSeparatedText
- noteFontStyle :: Maybe FontStyle
- noteFontSize :: Maybe FontSize
- noteFontWeight :: Maybe FontWeight
- noteColor :: Maybe Color
- notePrintDot :: Maybe YesNo
- notePrintLyric :: Maybe YesNo
- notePrintObject :: Maybe YesNo
- notePrintSpacing :: Maybe YesNo
- noteNote :: ChxNote
- noteInstrument :: Maybe Instrument
- noteEditorialVoice :: EditorialVoice
- noteType :: Maybe NoteType
- noteDot :: [EmptyPlacement]
- noteAccidental :: Maybe Accidental
- noteTimeModification :: Maybe TimeModification
- noteStem :: Maybe Stem
- noteNotehead :: Maybe Notehead
- noteStaff :: Maybe Staff
- noteBeam :: [Beam]
- noteNotations :: [Notations]
- noteLyric :: [Lyric]
- parseNote :: XParse Note
- mkNote :: ChxNote -> EditorialVoice -> Note
- data NoteSize = NoteSize {}
- parseNoteSize :: XParse NoteSize
- mkNoteSize :: NonNegativeDecimal -> NoteSizeType -> NoteSize
- data NoteType = NoteType {}
- parseNoteType :: XParse NoteType
- mkNoteType :: NoteTypeValue -> NoteType
- data Notehead = Notehead {}
- parseNotehead :: XParse Notehead
- mkNotehead :: NoteheadValue -> Notehead
- data OctaveShift = OctaveShift {
- octaveShiftType :: UpDownStop
- octaveShiftNumber :: Maybe NumberLevel
- octaveShiftSize :: Maybe PositiveInteger
- octaveShiftDefaultX :: Maybe Tenths
- octaveShiftDefaultY :: Maybe Tenths
- octaveShiftRelativeX :: Maybe Tenths
- octaveShiftRelativeY :: Maybe Tenths
- octaveShiftFontFamily :: Maybe CommaSeparatedText
- octaveShiftFontStyle :: Maybe FontStyle
- octaveShiftFontSize :: Maybe FontSize
- octaveShiftFontWeight :: Maybe FontWeight
- octaveShiftColor :: Maybe Color
- parseOctaveShift :: XParse OctaveShift
- mkOctaveShift :: UpDownStop -> OctaveShift
- data Offset = Offset {}
- parseOffset :: XParse Offset
- mkOffset :: Divisions -> Offset
- data Opus = Opus {}
- parseOpus :: XParse Opus
- mkOpus :: String -> Opus
- data Ornaments = Ornaments {}
- parseOrnaments :: XParse Ornaments
- mkOrnaments :: Ornaments
- data OtherAppearance = OtherAppearance {}
- parseOtherAppearance :: XParse OtherAppearance
- mkOtherAppearance :: String -> Token -> OtherAppearance
- data OtherDirection = OtherDirection {
- otherDirectionString :: String
- otherDirectionPrintObject :: Maybe YesNo
- otherDirectionDefaultX :: Maybe Tenths
- otherDirectionDefaultY :: Maybe Tenths
- otherDirectionRelativeX :: Maybe Tenths
- otherDirectionRelativeY :: Maybe Tenths
- otherDirectionFontFamily :: Maybe CommaSeparatedText
- otherDirectionFontStyle :: Maybe FontStyle
- otherDirectionFontSize :: Maybe FontSize
- otherDirectionFontWeight :: Maybe FontWeight
- otherDirectionColor :: Maybe Color
- parseOtherDirection :: XParse OtherDirection
- mkOtherDirection :: String -> OtherDirection
- data OtherNotation = OtherNotation {
- otherNotationString :: String
- otherNotationType :: StartStopSingle
- otherNotationNumber :: Maybe NumberLevel
- otherNotationPrintObject :: Maybe YesNo
- otherNotationDefaultX :: Maybe Tenths
- otherNotationDefaultY :: Maybe Tenths
- otherNotationRelativeX :: Maybe Tenths
- otherNotationRelativeY :: Maybe Tenths
- otherNotationFontFamily :: Maybe CommaSeparatedText
- otherNotationFontStyle :: Maybe FontStyle
- otherNotationFontSize :: Maybe FontSize
- otherNotationFontWeight :: Maybe FontWeight
- otherNotationColor :: Maybe Color
- otherNotationPlacement :: Maybe AboveBelow
- parseOtherNotation :: XParse OtherNotation
- mkOtherNotation :: String -> StartStopSingle -> OtherNotation
- data PageLayout = PageLayout {}
- parsePageLayout :: XParse PageLayout
- mkPageLayout :: PageLayout
- data PageMargins = PageMargins {}
- parsePageMargins :: XParse PageMargins
- mkPageMargins :: AllMargins -> PageMargins
- data CmpPart = CmpPart {
- partId :: IDREF
- partMeasure :: [Measure]
- parseCmpPart :: XParse CmpPart
- mkCmpPart :: IDREF -> CmpPart
- data Part = Part {}
- parsePart :: XParse Part
- mkPart :: IDREF -> MusicData -> Part
- data PartGroup = PartGroup {
- partGroupType :: StartStop
- partGroupNumber :: Maybe Token
- partGroupGroupName :: Maybe GroupName
- partGroupGroupNameDisplay :: Maybe NameDisplay
- partGroupGroupAbbreviation :: Maybe GroupName
- partGroupGroupAbbreviationDisplay :: Maybe NameDisplay
- partGroupGroupSymbol :: Maybe GroupSymbol
- partGroupGroupBarline :: Maybe GroupBarline
- partGroupGroupTime :: Maybe Empty
- partGroupEditorial :: Editorial
- parsePartGroup :: XParse PartGroup
- mkPartGroup :: StartStop -> Editorial -> PartGroup
- data PartList = PartList {}
- parsePartList :: XParse PartList
- mkPartList :: ScorePart -> PartList
- data PartName = PartName {
- partNameString :: String
- partNameDefaultX :: Maybe Tenths
- partNameDefaultY :: Maybe Tenths
- partNameRelativeX :: Maybe Tenths
- partNameRelativeY :: Maybe Tenths
- partNameFontFamily :: Maybe CommaSeparatedText
- partNameFontStyle :: Maybe FontStyle
- partNameFontSize :: Maybe FontSize
- partNameFontWeight :: Maybe FontWeight
- partNameColor :: Maybe Color
- partNamePrintObject :: Maybe YesNo
- partNameJustify :: Maybe LeftCenterRight
- parsePartName :: XParse PartName
- mkPartName :: String -> PartName
- data PartSymbol = PartSymbol {}
- parsePartSymbol :: XParse PartSymbol
- mkPartSymbol :: GroupSymbolValue -> PartSymbol
- data Pedal = Pedal {
- pedalType :: StartStopChange
- pedalLine :: Maybe YesNo
- pedalDefaultX :: Maybe Tenths
- pedalDefaultY :: Maybe Tenths
- pedalRelativeX :: Maybe Tenths
- pedalRelativeY :: Maybe Tenths
- pedalFontFamily :: Maybe CommaSeparatedText
- pedalFontStyle :: Maybe FontStyle
- pedalFontSize :: Maybe FontSize
- pedalFontWeight :: Maybe FontWeight
- pedalColor :: Maybe Color
- parsePedal :: XParse Pedal
- mkPedal :: StartStopChange -> Pedal
- data PedalTuning = PedalTuning {}
- parsePedalTuning :: XParse PedalTuning
- mkPedalTuning :: Step -> Semitones -> PedalTuning
- data PerMinute = PerMinute {}
- parsePerMinute :: XParse PerMinute
- mkPerMinute :: String -> PerMinute
- data Pitch = Pitch {}
- parsePitch :: XParse Pitch
- mkPitch :: Step -> Octave -> Pitch
- data PlacementText = PlacementText {
- placementTextString :: String
- placementTextDefaultX :: Maybe Tenths
- placementTextDefaultY :: Maybe Tenths
- placementTextRelativeX :: Maybe Tenths
- placementTextRelativeY :: Maybe Tenths
- placementTextFontFamily :: Maybe CommaSeparatedText
- placementTextFontStyle :: Maybe FontStyle
- placementTextFontSize :: Maybe FontSize
- placementTextFontWeight :: Maybe FontWeight
- placementTextColor :: Maybe Color
- placementTextPlacement :: Maybe AboveBelow
- parsePlacementText :: XParse PlacementText
- mkPlacementText :: String -> PlacementText
- data Print = Print {
- printStaffSpacing :: Maybe Tenths
- printNewSystem :: Maybe YesNo
- printNewPage :: Maybe YesNo
- printBlankPage :: Maybe PositiveInteger
- printPageNumber :: Maybe Token
- printLayout :: Layout
- printMeasureLayout :: Maybe MeasureLayout
- printMeasureNumbering :: Maybe MeasureNumbering
- printPartNameDisplay :: Maybe NameDisplay
- printPartAbbreviationDisplay :: Maybe NameDisplay
- parsePrint :: XParse Print
- mkPrint :: Layout -> Print
- data Rehearsal = Rehearsal {
- rehearsalString :: String
- rehearsalLang :: Maybe Lang
- rehearsalEnclosure :: Maybe RehearsalEnclosure
- rehearsalDefaultX :: Maybe Tenths
- rehearsalDefaultY :: Maybe Tenths
- rehearsalRelativeX :: Maybe Tenths
- rehearsalRelativeY :: Maybe Tenths
- rehearsalFontFamily :: Maybe CommaSeparatedText
- rehearsalFontStyle :: Maybe FontStyle
- rehearsalFontSize :: Maybe FontSize
- rehearsalFontWeight :: Maybe FontWeight
- rehearsalColor :: Maybe Color
- rehearsalUnderline :: Maybe NumberOfLines
- rehearsalOverline :: Maybe NumberOfLines
- rehearsalLineThrough :: Maybe NumberOfLines
- rehearsalDir :: Maybe TextDirection
- rehearsalRotation :: Maybe RotationDegrees
- parseRehearsal :: XParse Rehearsal
- mkRehearsal :: String -> Rehearsal
- data Repeat = Repeat {}
- parseRepeat :: XParse Repeat
- mkRepeat :: BackwardForward -> Repeat
- data Root = Root {}
- parseRoot :: XParse Root
- mkRoot :: RootStep -> Root
- data RootAlter = RootAlter {
- rootAlterSemitones :: Semitones
- rootAlterLocation :: Maybe LeftRight
- rootAlterPrintObject :: Maybe YesNo
- rootAlterDefaultX :: Maybe Tenths
- rootAlterDefaultY :: Maybe Tenths
- rootAlterRelativeX :: Maybe Tenths
- rootAlterRelativeY :: Maybe Tenths
- rootAlterFontFamily :: Maybe CommaSeparatedText
- rootAlterFontStyle :: Maybe FontStyle
- rootAlterFontSize :: Maybe FontSize
- rootAlterFontWeight :: Maybe FontWeight
- rootAlterColor :: Maybe Color
- parseRootAlter :: XParse RootAlter
- mkRootAlter :: Semitones -> RootAlter
- data RootStep = RootStep {
- rootStepStep :: Step
- rootStepText :: Maybe Token
- rootStepDefaultX :: Maybe Tenths
- rootStepDefaultY :: Maybe Tenths
- rootStepRelativeX :: Maybe Tenths
- rootStepRelativeY :: Maybe Tenths
- rootStepFontFamily :: Maybe CommaSeparatedText
- rootStepFontStyle :: Maybe FontStyle
- rootStepFontSize :: Maybe FontSize
- rootStepFontWeight :: Maybe FontWeight
- rootStepColor :: Maybe Color
- parseRootStep :: XParse RootStep
- mkRootStep :: Step -> RootStep
- data Scaling = Scaling {}
- parseScaling :: XParse Scaling
- mkScaling :: Millimeters -> Tenths -> Scaling
- data Scordatura = Scordatura {
- scordaturaAccord :: [Accord]
- parseScordatura :: XParse Scordatura
- mkScordatura :: Scordatura
- data ScoreInstrument = ScoreInstrument {}
- parseScoreInstrument :: XParse ScoreInstrument
- mkScoreInstrument :: ID -> String -> ScoreInstrument
- data CmpScorePart = CmpScorePart {
- scorePartId :: ID
- scorePartIdentification :: Maybe Identification
- scorePartPartName :: PartName
- scorePartPartNameDisplay :: Maybe NameDisplay
- scorePartPartAbbreviation :: Maybe PartName
- scorePartPartAbbreviationDisplay :: Maybe NameDisplay
- scorePartGroup :: [String]
- scorePartScoreInstrument :: [ScoreInstrument]
- scorePartMidiDevice :: Maybe MidiDevice
- scorePartMidiInstrument :: [MidiInstrument]
- parseCmpScorePart :: XParse CmpScorePart
- mkCmpScorePart :: ID -> PartName -> CmpScorePart
- data ScorePartwise = ScorePartwise {}
- parseScorePartwise :: XParse ScorePartwise
- mkScorePartwise :: ScoreHeader -> ScorePartwise
- data ScoreTimewise = ScoreTimewise {}
- parseScoreTimewise :: XParse ScoreTimewise
- mkScoreTimewise :: ScoreHeader -> ScoreTimewise
- data CmpSlash = CmpSlash {}
- parseCmpSlash :: XParse CmpSlash
- mkCmpSlash :: StartStop -> CmpSlash
- data Slide = Slide {
- slideString :: String
- slideType :: StartStop
- slideNumber :: Maybe NumberLevel
- slideLineType :: Maybe LineType
- slideDefaultX :: Maybe Tenths
- slideDefaultY :: Maybe Tenths
- slideRelativeX :: Maybe Tenths
- slideRelativeY :: Maybe Tenths
- slideFontFamily :: Maybe CommaSeparatedText
- slideFontStyle :: Maybe FontStyle
- slideFontSize :: Maybe FontSize
- slideFontWeight :: Maybe FontWeight
- slideColor :: Maybe Color
- slideAccelerate :: Maybe YesNo
- slideBeats :: Maybe TrillBeats
- slideFirstBeat :: Maybe Percent
- slideLastBeat :: Maybe Percent
- parseSlide :: XParse Slide
- mkSlide :: String -> StartStop -> Slide
- data Slur = Slur {
- slurType :: StartStopContinue
- slurNumber :: Maybe NumberLevel
- slurLineType :: Maybe LineType
- slurDefaultX :: Maybe Tenths
- slurDefaultY :: Maybe Tenths
- slurRelativeX :: Maybe Tenths
- slurRelativeY :: Maybe Tenths
- slurPlacement :: Maybe AboveBelow
- slurOrientation :: Maybe OverUnder
- slurBezierOffset :: Maybe Divisions
- slurBezierOffset2 :: Maybe Divisions
- slurBezierX :: Maybe Tenths
- slurBezierY :: Maybe Tenths
- slurBezierX2 :: Maybe Tenths
- slurBezierY2 :: Maybe Tenths
- slurColor :: Maybe Color
- parseSlur :: XParse Slur
- mkSlur :: StartStopContinue -> Slur
- data Sound = Sound {
- soundTempo :: Maybe NonNegativeDecimal
- soundDynamics :: Maybe NonNegativeDecimal
- soundDacapo :: Maybe YesNo
- soundSegno :: Maybe Token
- soundDalsegno :: Maybe Token
- soundCoda :: Maybe Token
- soundTocoda :: Maybe Token
- soundDivisions :: Maybe Divisions
- soundForwardRepeat :: Maybe YesNo
- soundFine :: Maybe Token
- soundTimeOnly :: Maybe Token
- soundPizzicato :: Maybe YesNo
- soundPan :: Maybe RotationDegrees
- soundElevation :: Maybe RotationDegrees
- soundDamperPedal :: Maybe YesNoNumber
- soundSoftPedal :: Maybe YesNoNumber
- soundSostenutoPedal :: Maybe YesNoNumber
- soundMidiInstrument :: [MidiInstrument]
- soundOffset :: Maybe Offset
- parseSound :: XParse Sound
- mkSound :: Sound
- data StaffDetails = StaffDetails {
- staffDetailsNumber :: Maybe StaffNumber
- staffDetailsShowFrets :: Maybe ShowFrets
- staffDetailsPrintObject :: Maybe YesNo
- staffDetailsPrintSpacing :: Maybe YesNo
- staffDetailsStaffType :: Maybe StaffType
- staffDetailsStaffLines :: Maybe NonNegativeInteger
- staffDetailsStaffTuning :: [StaffTuning]
- staffDetailsCapo :: Maybe NonNegativeInteger
- staffDetailsStaffSize :: Maybe NonNegativeDecimal
- parseStaffDetails :: XParse StaffDetails
- mkStaffDetails :: StaffDetails
- data StaffLayout = StaffLayout {}
- parseStaffLayout :: XParse StaffLayout
- mkStaffLayout :: StaffLayout
- data StaffTuning = StaffTuning {}
- parseStaffTuning :: XParse StaffTuning
- mkStaffTuning :: Tuning -> StaffTuning
- data Stem = Stem {}
- parseStem :: XParse Stem
- mkStem :: StemValue -> Stem
- data CmpString = CmpString {
- stringStringNumber :: StringNumber
- stringDefaultX :: Maybe Tenths
- stringDefaultY :: Maybe Tenths
- stringRelativeX :: Maybe Tenths
- stringRelativeY :: Maybe Tenths
- stringFontFamily :: Maybe CommaSeparatedText
- stringFontStyle :: Maybe FontStyle
- stringFontSize :: Maybe FontSize
- stringFontWeight :: Maybe FontWeight
- stringColor :: Maybe Color
- stringPlacement :: Maybe AboveBelow
- parseCmpString :: XParse CmpString
- mkCmpString :: StringNumber -> CmpString
- data StrongAccent = StrongAccent {}
- parseStrongAccent :: XParse StrongAccent
- mkStrongAccent :: StrongAccent -> StrongAccent
- data StyleText = StyleText {
- styleTextString :: String
- styleTextDefaultX :: Maybe Tenths
- styleTextDefaultY :: Maybe Tenths
- styleTextRelativeX :: Maybe Tenths
- styleTextRelativeY :: Maybe Tenths
- styleTextFontFamily :: Maybe CommaSeparatedText
- styleTextFontStyle :: Maybe FontStyle
- styleTextFontSize :: Maybe FontSize
- styleTextFontWeight :: Maybe FontWeight
- styleTextColor :: Maybe Color
- parseStyleText :: XParse StyleText
- mkStyleText :: String -> StyleText
- data Supports = Supports {}
- parseSupports :: XParse Supports
- mkSupports :: YesNo -> NMTOKEN -> Supports
- data SystemLayout = SystemLayout {}
- parseSystemLayout :: XParse SystemLayout
- mkSystemLayout :: SystemLayout
- data SystemMargins = SystemMargins {}
- parseSystemMargins :: XParse SystemMargins
- mkSystemMargins :: LeftRightMargins -> SystemMargins
- data Technical = Technical {}
- parseTechnical :: XParse Technical
- mkTechnical :: Technical
- data TextElementData = TextElementData {
- textElementDataString :: String
- textElementDataLang :: Maybe Lang
- textElementDataFontFamily :: Maybe CommaSeparatedText
- textElementDataFontStyle :: Maybe FontStyle
- textElementDataFontSize :: Maybe FontSize
- textElementDataFontWeight :: Maybe FontWeight
- textElementDataColor :: Maybe Color
- textElementDataUnderline :: Maybe NumberOfLines
- textElementDataOverline :: Maybe NumberOfLines
- textElementDataLineThrough :: Maybe NumberOfLines
- textElementDataRotation :: Maybe RotationDegrees
- textElementDataLetterSpacing :: Maybe NumberOrNormal
- textElementDataDir :: Maybe TextDirection
- parseTextElementData :: XParse TextElementData
- mkTextElementData :: String -> TextElementData
- data Tie = Tie {}
- parseTie :: XParse Tie
- mkTie :: StartStop -> Tie
- data Tied = Tied {
- tiedType :: StartStop
- tiedNumber :: Maybe NumberLevel
- tiedLineType :: Maybe LineType
- tiedDefaultX :: Maybe Tenths
- tiedDefaultY :: Maybe Tenths
- tiedRelativeX :: Maybe Tenths
- tiedRelativeY :: Maybe Tenths
- tiedPlacement :: Maybe AboveBelow
- tiedOrientation :: Maybe OverUnder
- tiedBezierOffset :: Maybe Divisions
- tiedBezierOffset2 :: Maybe Divisions
- tiedBezierX :: Maybe Tenths
- tiedBezierY :: Maybe Tenths
- tiedBezierX2 :: Maybe Tenths
- tiedBezierY2 :: Maybe Tenths
- tiedColor :: Maybe Color
- parseTied :: XParse Tied
- mkTied :: StartStop -> Tied
- data Time = Time {
- timeNumber :: Maybe StaffNumber
- timeSymbol :: Maybe TimeSymbol
- timeDefaultX :: Maybe Tenths
- timeDefaultY :: Maybe Tenths
- timeRelativeX :: Maybe Tenths
- timeRelativeY :: Maybe Tenths
- timeFontFamily :: Maybe CommaSeparatedText
- timeFontStyle :: Maybe FontStyle
- timeFontSize :: Maybe FontSize
- timeFontWeight :: Maybe FontWeight
- timeColor :: Maybe Color
- timePrintObject :: Maybe YesNo
- timeTime :: ChxTime
- parseTime :: XParse Time
- mkTime :: ChxTime -> Time
- data TimeModification = TimeModification {}
- parseTimeModification :: XParse TimeModification
- mkTimeModification :: NonNegativeInteger -> NonNegativeInteger -> TimeModification
- data Transpose = Transpose {}
- parseTranspose :: XParse Transpose
- mkTranspose :: Semitones -> Transpose
- data Tremolo = Tremolo {
- tremoloTremoloMarks :: TremoloMarks
- tremoloType :: Maybe StartStopSingle
- tremoloDefaultX :: Maybe Tenths
- tremoloDefaultY :: Maybe Tenths
- tremoloRelativeX :: Maybe Tenths
- tremoloRelativeY :: Maybe Tenths
- tremoloFontFamily :: Maybe CommaSeparatedText
- tremoloFontStyle :: Maybe FontStyle
- tremoloFontSize :: Maybe FontSize
- tremoloFontWeight :: Maybe FontWeight
- tremoloColor :: Maybe Color
- tremoloPlacement :: Maybe AboveBelow
- parseTremolo :: XParse Tremolo
- mkTremolo :: TremoloMarks -> Tremolo
- data Tuplet = Tuplet {
- tupletType :: StartStop
- tupletNumber :: Maybe NumberLevel
- tupletBracket :: Maybe YesNo
- tupletShowNumber :: Maybe ShowTuplet
- tupletShowType :: Maybe ShowTuplet
- tupletLineShape :: Maybe LineShape
- tupletDefaultX :: Maybe Tenths
- tupletDefaultY :: Maybe Tenths
- tupletRelativeX :: Maybe Tenths
- tupletRelativeY :: Maybe Tenths
- tupletPlacement :: Maybe AboveBelow
- tupletTupletActual :: Maybe TupletPortion
- tupletTupletNormal :: Maybe TupletPortion
- parseTuplet :: XParse Tuplet
- mkTuplet :: StartStop -> Tuplet
- data TupletDot = TupletDot {}
- parseTupletDot :: XParse TupletDot
- mkTupletDot :: TupletDot
- data TupletNumber = TupletNumber {}
- parseTupletNumber :: XParse TupletNumber
- mkTupletNumber :: NonNegativeInteger -> TupletNumber
- data TupletPortion = TupletPortion {}
- parseTupletPortion :: XParse TupletPortion
- mkTupletPortion :: TupletPortion
- data TupletType = TupletType {}
- parseTupletType :: XParse TupletType
- mkTupletType :: NoteTypeValue -> TupletType
- data TypedText = TypedText {}
- parseTypedText :: XParse TypedText
- mkTypedText :: String -> TypedText
- data WavyLine = WavyLine {
- wavyLineType :: StartStopContinue
- wavyLineNumber :: Maybe NumberLevel
- wavyLineDefaultX :: Maybe Tenths
- wavyLineDefaultY :: Maybe Tenths
- wavyLineRelativeX :: Maybe Tenths
- wavyLineRelativeY :: Maybe Tenths
- wavyLinePlacement :: Maybe AboveBelow
- wavyLineColor :: Maybe Color
- wavyLineStartNote :: Maybe StartNote
- wavyLineTrillStep :: Maybe TrillStep
- wavyLineTwoNoteTurn :: Maybe TwoNoteTurn
- wavyLineAccelerate :: Maybe YesNo
- wavyLineBeats :: Maybe TrillBeats
- wavyLineSecondBeat :: Maybe Percent
- wavyLineLastBeat :: Maybe Percent
- parseWavyLine :: XParse WavyLine
- mkWavyLine :: StartStopContinue -> WavyLine
- data Wedge = Wedge {}
- parseWedge :: XParse Wedge
- mkWedge :: WedgeType -> Wedge
- data Work = Work {}
- parseWork :: XParse Work
- mkWork :: Work
- data ChxArticulations
- = ArticulationsAccent { }
- | ArticulationsStrongAccent { }
- | ArticulationsStaccato { }
- | ArticulationsTenuto { }
- | ArticulationsDetachedLegato { }
- | ArticulationsStaccatissimo { }
- | ArticulationsSpiccato { }
- | ArticulationsScoop { }
- | ArticulationsPlop { }
- | ArticulationsDoit { }
- | ArticulationsFalloff { }
- | ArticulationsBreathMark { }
- | ArticulationsCaesura { }
- | ArticulationsStress { }
- | ArticulationsUnstress { }
- | ArticulationsOtherArticulation { }
- parseChxArticulations :: XParse ChxArticulations
- mkArticulationsAccent :: EmptyPlacement -> ChxArticulations
- mkArticulationsStrongAccent :: StrongAccent -> ChxArticulations
- mkArticulationsStaccato :: EmptyPlacement -> ChxArticulations
- mkArticulationsTenuto :: EmptyPlacement -> ChxArticulations
- mkArticulationsDetachedLegato :: EmptyPlacement -> ChxArticulations
- mkArticulationsStaccatissimo :: EmptyPlacement -> ChxArticulations
- mkArticulationsSpiccato :: EmptyPlacement -> ChxArticulations
- mkArticulationsScoop :: EmptyLine -> ChxArticulations
- mkArticulationsPlop :: EmptyLine -> ChxArticulations
- mkArticulationsDoit :: EmptyLine -> ChxArticulations
- mkArticulationsFalloff :: EmptyLine -> ChxArticulations
- mkArticulationsBreathMark :: EmptyPlacement -> ChxArticulations
- mkArticulationsCaesura :: EmptyPlacement -> ChxArticulations
- mkArticulationsStress :: EmptyPlacement -> ChxArticulations
- mkArticulationsUnstress :: EmptyPlacement -> ChxArticulations
- mkArticulationsOtherArticulation :: PlacementText -> ChxArticulations
- data ChxBend
- = BendPreBend {
- bendPreBend :: Empty
- | BendRelease {
- bendRelease :: Empty
- = BendPreBend {
- parseChxBend :: XParse ChxBend
- mkBendPreBend :: Empty -> ChxBend
- mkBendRelease :: Empty -> ChxBend
- data ChxCredit
- = CreditCreditImage { }
- | CreditCreditWords { }
- parseChxCredit :: XParse ChxCredit
- mkCreditCreditImage :: Image -> ChxCredit
- mkCreditCreditWords :: FormattedText -> ChxCredit
- data ChxDirectionType
- = DirectionTypeRehearsal { }
- | DirectionTypeSegno { }
- | DirectionTypeWords { }
- | DirectionTypeCoda { }
- | DirectionTypeWedge { }
- | DirectionTypeDynamics { }
- | DirectionTypeDashes { }
- | DirectionTypeBracket { }
- | DirectionTypePedal { }
- | DirectionTypeMetronome { }
- | DirectionTypeOctaveShift { }
- | DirectionTypeHarpPedals { }
- | DirectionTypeDamp { }
- | DirectionTypeDampAll { }
- | DirectionTypeEyeglasses { }
- | DirectionTypeScordatura { }
- | DirectionTypeImage { }
- | DirectionTypeAccordionRegistration { }
- | DirectionTypeOtherDirection { }
- parseChxDirectionType :: XParse ChxDirectionType
- mkDirectionTypeRehearsal :: ChxDirectionType
- mkDirectionTypeSegno :: ChxDirectionType
- mkDirectionTypeWords :: ChxDirectionType
- mkDirectionTypeCoda :: ChxDirectionType
- mkDirectionTypeWedge :: Wedge -> ChxDirectionType
- mkDirectionTypeDynamics :: ChxDirectionType
- mkDirectionTypeDashes :: Dashes -> ChxDirectionType
- mkDirectionTypeBracket :: Bracket -> ChxDirectionType
- mkDirectionTypePedal :: Pedal -> ChxDirectionType
- mkDirectionTypeMetronome :: Metronome -> ChxDirectionType
- mkDirectionTypeOctaveShift :: OctaveShift -> ChxDirectionType
- mkDirectionTypeHarpPedals :: HarpPedals -> ChxDirectionType
- mkDirectionTypeDamp :: EmptyPrintStyle -> ChxDirectionType
- mkDirectionTypeDampAll :: EmptyPrintStyle -> ChxDirectionType
- mkDirectionTypeEyeglasses :: EmptyPrintStyle -> ChxDirectionType
- mkDirectionTypeScordatura :: Scordatura -> ChxDirectionType
- mkDirectionTypeImage :: Image -> ChxDirectionType
- mkDirectionTypeAccordionRegistration :: AccordionRegistration -> ChxDirectionType
- mkDirectionTypeOtherDirection :: OtherDirection -> ChxDirectionType
- data ChxDynamics
- = DynamicsP { }
- | DynamicsPp {
- dynamicsPp :: Empty
- | DynamicsPpp {
- dynamicsPpp :: Empty
- | DynamicsPppp { }
- | DynamicsPpppp { }
- | DynamicsPppppp { }
- | DynamicsF { }
- | DynamicsFf {
- dynamicsFf :: Empty
- | DynamicsFff {
- dynamicsFff :: Empty
- | DynamicsFfff { }
- | DynamicsFffff { }
- | DynamicsFfffff { }
- | DynamicsMp {
- dynamicsMp :: Empty
- | DynamicsMf {
- dynamicsMf :: Empty
- | DynamicsSf {
- dynamicsSf :: Empty
- | DynamicsSfp {
- dynamicsSfp :: Empty
- | DynamicsSfpp { }
- | DynamicsFp {
- dynamicsFp :: Empty
- | DynamicsRf {
- dynamicsRf :: Empty
- | DynamicsRfz {
- dynamicsRfz :: Empty
- | DynamicsSfz {
- dynamicsSfz :: Empty
- | DynamicsSffz { }
- | DynamicsFz {
- dynamicsFz :: Empty
- | DynamicsOtherDynamics { }
- parseChxDynamics :: XParse ChxDynamics
- mkDynamicsP :: Empty -> ChxDynamics
- mkDynamicsPp :: Empty -> ChxDynamics
- mkDynamicsPpp :: Empty -> ChxDynamics
- mkDynamicsPppp :: Empty -> ChxDynamics
- mkDynamicsPpppp :: Empty -> ChxDynamics
- mkDynamicsPppppp :: Empty -> ChxDynamics
- mkDynamicsF :: Empty -> ChxDynamics
- mkDynamicsFf :: Empty -> ChxDynamics
- mkDynamicsFff :: Empty -> ChxDynamics
- mkDynamicsFfff :: Empty -> ChxDynamics
- mkDynamicsFffff :: Empty -> ChxDynamics
- mkDynamicsFfffff :: Empty -> ChxDynamics
- mkDynamicsMp :: Empty -> ChxDynamics
- mkDynamicsMf :: Empty -> ChxDynamics
- mkDynamicsSf :: Empty -> ChxDynamics
- mkDynamicsSfp :: Empty -> ChxDynamics
- mkDynamicsSfpp :: Empty -> ChxDynamics
- mkDynamicsFp :: Empty -> ChxDynamics
- mkDynamicsRf :: Empty -> ChxDynamics
- mkDynamicsRfz :: Empty -> ChxDynamics
- mkDynamicsSfz :: Empty -> ChxDynamics
- mkDynamicsSffz :: Empty -> ChxDynamics
- mkDynamicsFz :: Empty -> ChxDynamics
- mkDynamicsOtherDynamics :: String -> ChxDynamics
- data ChxEncoding
- parseChxEncoding :: XParse ChxEncoding
- mkEncodingEncodingDate :: YyyyMmDd -> ChxEncoding
- mkEncodingEncoder :: TypedText -> ChxEncoding
- mkEncodingSoftware :: String -> ChxEncoding
- mkEncodingEncodingDescription :: String -> ChxEncoding
- mkEncodingSupports :: Supports -> ChxEncoding
- data FullNote
- = FullNotePitch { }
- | FullNoteUnpitched { }
- | FullNoteRest { }
- parseFullNote :: XParse FullNote
- mkFullNotePitch :: Pitch -> FullNote
- mkFullNoteUnpitched :: DisplayStepOctave -> FullNote
- mkFullNoteRest :: DisplayStepOctave -> FullNote
- data ChxHarmonic
- = HarmonicNatural { }
- | HarmonicArtificial { }
- parseChxHarmonic :: XParse ChxHarmonic
- mkHarmonicNatural :: Empty -> ChxHarmonic
- mkHarmonicArtificial :: Empty -> ChxHarmonic
- data ChxHarmonic1
- parseChxHarmonic1 :: XParse ChxHarmonic1
- mkHarmonicBasePitch :: Empty -> ChxHarmonic1
- mkHarmonicTouchingPitch :: Empty -> ChxHarmonic1
- mkHarmonicSoundingPitch :: Empty -> ChxHarmonic1
- data ChxHarmonyChord
- = HarmonyChordRoot { }
- | HarmonyChordFunction { }
- parseChxHarmonyChord :: XParse ChxHarmonyChord
- mkHarmonyChordRoot :: Root -> ChxHarmonyChord
- mkHarmonyChordFunction :: StyleText -> ChxHarmonyChord
- data ChxKey
- parseChxKey :: XParse ChxKey
- mkKeyTraditionalKey :: TraditionalKey -> ChxKey
- mkKeyNonTraditionalKey :: ChxKey
- data ChxLyric
- = LyricSyllabic { }
- | LyricExtend { }
- | LyricLaughing { }
- | LyricHumming { }
- parseChxLyric :: XParse ChxLyric
- mkLyricSyllabic :: TextElementData -> ChxLyric
- mkLyricExtend :: Extend -> ChxLyric
- mkLyricLaughing :: Empty -> ChxLyric
- mkLyricHumming :: Empty -> ChxLyric
- data ChxMeasureStyle
- parseChxMeasureStyle :: XParse ChxMeasureStyle
- mkMeasureStyleMultipleRest :: MultipleRest -> ChxMeasureStyle
- mkMeasureStyleMeasureRepeat :: MeasureRepeat -> ChxMeasureStyle
- mkMeasureStyleBeatRepeat :: BeatRepeat -> ChxMeasureStyle
- mkMeasureStyleSlash :: CmpSlash -> ChxMeasureStyle
- data ChxMetronome0
- = MetronomePerMinute { }
- | MetronomeBeatUnit { }
- parseChxMetronome0 :: XParse ChxMetronome0
- mkMetronomePerMinute :: PerMinute -> ChxMetronome0
- mkMetronomeBeatUnit :: BeatUnit -> ChxMetronome0
- data ChxMetronome
- parseChxMetronome :: XParse ChxMetronome
- mkChxMetronomeBeatUnit :: BeatUnit -> ChxMetronome0 -> ChxMetronome
- mkMetronomeMetronomeNote :: ChxMetronome
- data ChxMusicData
- = MusicDataNote { }
- | MusicDataBackup { }
- | MusicDataForward { }
- | MusicDataDirection { }
- | MusicDataAttributes { }
- | MusicDataHarmony { }
- | MusicDataFiguredBass { }
- | MusicDataPrint { }
- | MusicDataSound { }
- | MusicDataBarline { }
- | MusicDataGrouping { }
- | MusicDataLink { }
- | MusicDataBookmark { }
- parseChxMusicData :: XParse ChxMusicData
- mkMusicDataNote :: Note -> ChxMusicData
- mkMusicDataBackup :: Backup -> ChxMusicData
- mkMusicDataForward :: Forward -> ChxMusicData
- mkMusicDataDirection :: Direction -> ChxMusicData
- mkMusicDataAttributes :: Attributes -> ChxMusicData
- mkMusicDataHarmony :: Harmony -> ChxMusicData
- mkMusicDataFiguredBass :: FiguredBass -> ChxMusicData
- mkMusicDataPrint :: Print -> ChxMusicData
- mkMusicDataSound :: Sound -> ChxMusicData
- mkMusicDataBarline :: Barline -> ChxMusicData
- mkMusicDataGrouping :: Grouping -> ChxMusicData
- mkMusicDataLink :: Link -> ChxMusicData
- mkMusicDataBookmark :: Bookmark -> ChxMusicData
- data ChxNameDisplay
- parseChxNameDisplay :: XParse ChxNameDisplay
- mkNameDisplayDisplayText :: FormattedText -> ChxNameDisplay
- mkNameDisplayAccidentalText :: AccidentalText -> ChxNameDisplay
- data ChxNotations
- = NotationsTied { }
- | NotationsSlur { }
- | NotationsTuplet { }
- | NotationsGlissando { }
- | NotationsSlide { }
- | NotationsOrnaments { }
- | NotationsTechnical { }
- | NotationsArticulations { }
- | NotationsDynamics { }
- | NotationsFermata { }
- | NotationsArpeggiate { }
- | NotationsNonArpeggiate { }
- | NotationsAccidentalMark { }
- | NotationsOtherNotation { }
- parseChxNotations :: XParse ChxNotations
- mkNotationsTied :: Tied -> ChxNotations
- mkNotationsSlur :: Slur -> ChxNotations
- mkNotationsTuplet :: Tuplet -> ChxNotations
- mkNotationsGlissando :: Glissando -> ChxNotations
- mkNotationsSlide :: Slide -> ChxNotations
- mkNotationsOrnaments :: Ornaments -> ChxNotations
- mkNotationsTechnical :: Technical -> ChxNotations
- mkNotationsArticulations :: Articulations -> ChxNotations
- mkNotationsDynamics :: Dynamics -> ChxNotations
- mkNotationsFermata :: Fermata -> ChxNotations
- mkNotationsArpeggiate :: Arpeggiate -> ChxNotations
- mkNotationsNonArpeggiate :: NonArpeggiate -> ChxNotations
- mkNotationsAccidentalMark :: AccidentalMark -> ChxNotations
- mkNotationsOtherNotation :: OtherNotation -> ChxNotations
- data ChxNote
- = NoteGrace {
- noteGrace :: Grace
- noteFullNote :: GrpFullNote
- noteTie :: [Tie]
- | NoteCue { }
- | NoteFullNote {
- noteFullNote2 :: GrpFullNote
- noteDuration1 :: Duration
- noteTie1 :: [Tie]
- = NoteGrace {
- parseChxNote :: XParse ChxNote
- mkNoteGrace :: Grace -> GrpFullNote -> ChxNote
- mkNoteCue :: Empty -> GrpFullNote -> Duration -> ChxNote
- mkNoteFullNote :: GrpFullNote -> Duration -> ChxNote
- data ChxOrnaments
- = OrnamentsTrillMark { }
- | OrnamentsTurn { }
- | OrnamentsDelayedTurn { }
- | OrnamentsInvertedTurn { }
- | OrnamentsShake { }
- | OrnamentsWavyLine { }
- | OrnamentsMordent { }
- | OrnamentsInvertedMordent { }
- | OrnamentsSchleifer { }
- | OrnamentsTremolo { }
- | OrnamentsOtherOrnament { }
- parseChxOrnaments :: XParse ChxOrnaments
- mkOrnamentsTrillMark :: EmptyTrillSound -> ChxOrnaments
- mkOrnamentsTurn :: EmptyTrillSound -> ChxOrnaments
- mkOrnamentsDelayedTurn :: EmptyTrillSound -> ChxOrnaments
- mkOrnamentsInvertedTurn :: EmptyTrillSound -> ChxOrnaments
- mkOrnamentsShake :: EmptyTrillSound -> ChxOrnaments
- mkOrnamentsWavyLine :: WavyLine -> ChxOrnaments
- mkOrnamentsMordent :: Mordent -> ChxOrnaments
- mkOrnamentsInvertedMordent :: Mordent -> ChxOrnaments
- mkOrnamentsSchleifer :: EmptyPlacement -> ChxOrnaments
- mkOrnamentsTremolo :: Tremolo -> ChxOrnaments
- mkOrnamentsOtherOrnament :: PlacementText -> ChxOrnaments
- data ChxPartList
- parseChxPartList :: XParse ChxPartList
- mkPartListPartGroup :: GrpPartGroup -> ChxPartList
- mkPartListScorePart :: ScorePart -> ChxPartList
- data ChxScoreInstrument
- parseChxScoreInstrument :: XParse ChxScoreInstrument
- mkScoreInstrumentSolo :: Empty -> ChxScoreInstrument
- mkScoreInstrumentEnsemble :: PositiveIntegerOrEmpty -> ChxScoreInstrument
- data ChxTechnical
- = TechnicalUpBow { }
- | TechnicalDownBow { }
- | TechnicalHarmonic { }
- | TechnicalOpenString { }
- | TechnicalThumbPosition { }
- | TechnicalFingering { }
- | TechnicalPluck { }
- | TechnicalDoubleTongue { }
- | TechnicalTripleTongue { }
- | TechnicalStopped { }
- | TechnicalSnapPizzicato { }
- | TechnicalFret { }
- | TechnicalString { }
- | TechnicalHammerOn { }
- | TechnicalPullOff { }
- | TechnicalBend { }
- | TechnicalTap { }
- | TechnicalHeel { }
- | TechnicalToe { }
- | TechnicalFingernails { }
- | TechnicalOtherTechnical { }
- parseChxTechnical :: XParse ChxTechnical
- mkTechnicalUpBow :: EmptyPlacement -> ChxTechnical
- mkTechnicalDownBow :: EmptyPlacement -> ChxTechnical
- mkTechnicalHarmonic :: Harmonic -> ChxTechnical
- mkTechnicalOpenString :: EmptyPlacement -> ChxTechnical
- mkTechnicalThumbPosition :: EmptyPlacement -> ChxTechnical
- mkTechnicalFingering :: Fingering -> ChxTechnical
- mkTechnicalPluck :: PlacementText -> ChxTechnical
- mkTechnicalDoubleTongue :: EmptyPlacement -> ChxTechnical
- mkTechnicalTripleTongue :: EmptyPlacement -> ChxTechnical
- mkTechnicalStopped :: EmptyPlacement -> ChxTechnical
- mkTechnicalSnapPizzicato :: EmptyPlacement -> ChxTechnical
- mkTechnicalFret :: Fret -> ChxTechnical
- mkTechnicalString :: CmpString -> ChxTechnical
- mkTechnicalHammerOn :: HammerOnPullOff -> ChxTechnical
- mkTechnicalPullOff :: HammerOnPullOff -> ChxTechnical
- mkTechnicalBend :: Bend -> ChxTechnical
- mkTechnicalTap :: PlacementText -> ChxTechnical
- mkTechnicalHeel :: HeelToe -> ChxTechnical
- mkTechnicalToe :: HeelToe -> ChxTechnical
- mkTechnicalFingernails :: EmptyPlacement -> ChxTechnical
- mkTechnicalOtherTechnical :: PlacementText -> ChxTechnical
- data ChxTime
- = TimeTime {
- chxtimeTime :: [SeqTime]
- | TimeSenzaMisura { }
- = TimeTime {
- parseChxTime :: XParse ChxTime
- mkTimeTime :: ChxTime
- mkTimeSenzaMisura :: Empty -> ChxTime
- data SeqCredit = SeqCredit {}
- parseSeqCredit :: XParse SeqCredit
- mkSeqCredit :: FormattedText -> SeqCredit
- data SeqDisplayStepOctave = SeqDisplayStepOctave {}
- parseSeqDisplayStepOctave :: XParse SeqDisplayStepOctave
- mkSeqDisplayStepOctave :: Step -> Octave -> SeqDisplayStepOctave
- data SeqLyric0 = SeqLyric0 {}
- parseSeqLyric0 :: XParse SeqLyric0
- mkSeqLyric0 :: Elision -> SeqLyric0
- data SeqLyric = SeqLyric {}
- parseSeqLyric :: XParse SeqLyric
- mkSeqLyric :: TextElementData -> SeqLyric
- data SeqMetronome = SeqMetronome {}
- parseSeqMetronome :: XParse SeqMetronome
- mkSeqMetronome :: String -> SeqMetronome
- data SeqMetronomeTuplet = SeqMetronomeTuplet {}
- parseSeqMetronomeTuplet :: XParse SeqMetronomeTuplet
- mkSeqMetronomeTuplet :: NoteTypeValue -> SeqMetronomeTuplet
- data SeqOrnaments = SeqOrnaments {}
- parseSeqOrnaments :: XParse SeqOrnaments
- mkSeqOrnaments :: ChxOrnaments -> SeqOrnaments
- data SeqPageLayout = SeqPageLayout {}
- parseSeqPageLayout :: XParse SeqPageLayout
- mkSeqPageLayout :: Tenths -> Tenths -> SeqPageLayout
- data SeqTime = SeqTime {}
- parseSeqTime :: XParse SeqTime
- mkSeqTime :: String -> String -> SeqTime
- data SeqTimeModification = SeqTimeModification {}
- parseSeqTimeModification :: XParse SeqTimeModification
- mkSeqTimeModification :: NoteTypeValue -> SeqTimeModification
- data AllMargins = AllMargins {}
- parseAllMargins :: XParse AllMargins
- mkAllMargins :: LeftRightMargins -> Tenths -> Tenths -> AllMargins
- data BeatUnit = BeatUnit {}
- parseBeatUnit :: XParse BeatUnit
- mkBeatUnit :: NoteTypeValue -> BeatUnit
- data Duration = Duration {}
- parseDuration :: XParse Duration
- mkDuration :: PositiveDivisions -> Duration
- data Editorial = Editorial {}
- parseEditorial :: XParse Editorial
- mkEditorial :: Editorial
- data EditorialVoice = EditorialVoice {}
- parseEditorialVoice :: XParse EditorialVoice
- mkEditorialVoice :: EditorialVoice
- data EditorialVoiceDirection = EditorialVoiceDirection {}
- parseEditorialVoiceDirection :: XParse EditorialVoiceDirection
- mkEditorialVoiceDirection :: EditorialVoiceDirection
- data Footnote = Footnote {}
- parseFootnote :: XParse Footnote
- mkFootnote :: FormattedText -> Footnote
- data GrpFullNote = GrpFullNote {}
- parseGrpFullNote :: XParse GrpFullNote
- mkGrpFullNote :: FullNote -> GrpFullNote
- data HarmonyChord = HarmonyChord {}
- parseHarmonyChord :: XParse HarmonyChord
- mkHarmonyChord :: ChxHarmonyChord -> Kind -> HarmonyChord
- data Layout = Layout {}
- parseLayout :: XParse Layout
- mkLayout :: Layout
- data LeftRightMargins = LeftRightMargins {}
- parseLeftRightMargins :: XParse LeftRightMargins
- mkLeftRightMargins :: Tenths -> Tenths -> LeftRightMargins
- data GrpLevel = GrpLevel {
- levelLevel :: Level
- parseGrpLevel :: XParse GrpLevel
- mkGrpLevel :: Level -> GrpLevel
- data MusicData = MusicData {}
- parseMusicData :: XParse MusicData
- mkMusicData :: MusicData
- data NonTraditionalKey = NonTraditionalKey {}
- parseNonTraditionalKey :: XParse NonTraditionalKey
- mkNonTraditionalKey :: Step -> Semitones -> NonTraditionalKey
- data GrpPartGroup = GrpPartGroup {}
- parseGrpPartGroup :: XParse GrpPartGroup
- mkGrpPartGroup :: PartGroup -> GrpPartGroup
- data ScoreHeader = ScoreHeader {}
- parseScoreHeader :: XParse ScoreHeader
- mkScoreHeader :: PartList -> ScoreHeader
- data ScorePart = ScorePart {}
- parseScorePart :: XParse ScorePart
- mkScorePart :: CmpScorePart -> ScorePart
- data Slash = Slash {}
- parseSlash :: XParse Slash
- mkSlash :: NoteTypeValue -> Slash
- data Staff = Staff {}
- parseStaff :: XParse Staff
- mkStaff :: PositiveInteger -> Staff
- data TraditionalKey = TraditionalKey {}
- parseTraditionalKey :: XParse TraditionalKey
- mkTraditionalKey :: Fifths -> TraditionalKey
- data Tuning = Tuning {}
- parseTuning :: XParse Tuning
- mkTuning :: Step -> Octave -> Tuning
- data Voice = Voice {
- voiceVoice :: String
- parseVoice :: XParse Voice
- mkVoice :: String -> Voice
Documentation
xs:ID (simple)
xs:IDREF (simple)
xs:NCName (simple)
xs:NMTOKEN (simple)
xs:Name (simple)
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
parseAboveBelow :: String -> XParse AboveBelow Source #
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.
Constructors
| AccidentalValueSharp | sharp |
| AccidentalValueNatural | natural |
| AccidentalValueFlat | flat |
| AccidentalValueDoubleSharp | double-sharp |
| AccidentalValueSharpSharp | sharp-sharp |
| AccidentalValueFlatFlat | flat-flat |
| AccidentalValueNaturalSharp | natural-sharp |
| AccidentalValueNaturalFlat | natural-flat |
| AccidentalValueQuarterFlat | quarter-flat |
| AccidentalValueQuarterSharp | quarter-sharp |
| AccidentalValueThreeQuartersFlat | three-quarters-flat |
| AccidentalValueThreeQuartersSharp | three-quarters-sharp |
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.
Constructors
| AccordionMiddle | |
Fields | |
Instances
xlink:actuate (simple)
Constructors
| ActuateOnRequest | onRequest |
| ActuateOnLoad | onLoad |
| ActuateOther | other |
| ActuateNone | none |
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.
Constructors
| BackwardForwardBackward | backward |
| BackwardForwardForward | forward |
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.
Constructors
| BarStyleRegular | regular |
| BarStyleDotted | dotted |
| BarStyleDashed | dashed |
| BarStyleHeavy | heavy |
| BarStyleLightLight | light-light |
| BarStyleLightHeavy | light-heavy |
| BarStyleHeavyLight | heavy-light |
| BarStyleHeavyHeavy | heavy-heavy |
| BarStyleTick | tick |
| BarStyleShort | short |
| BarStyleNone | none |
beam-level (simple)
The MusicXML format supports six levels of beaming, up to 256th notes. Unlike the number-level type, the beam-level type identifies concurrent beams in a beam group. It does not distinguish overlapping beams such as grace notes within regular notes, or beams used in different voices.
Constructors
| BeamLevel | |
Fields | |
Instances
beam-value (simple)
The beam-value type represents the type of beam associated with each of 6 beam levels (up to 256th notes) available for each note.
Constructors
| BeamValueBegin | begin |
| BeamValueContinue | continue |
| BeamValueEnd | end |
| BeamValueForwardHook | forward hook |
| BeamValueBackwardHook | backward hook |
clef-sign (simple)
The clef-sign element represents the different clef symbols.
Constructors
| ClefSignG | G |
| ClefSignF | F |
| ClefSignC | C |
| ClefSignPercussion | percussion |
| ClefSignTAB | TAB |
| ClefSignNone | none |
color (simple)
The color type indicates the color of an element. Color may be represented as hexadecimal RGB triples, as in HTML, or as hexadecimal ARGB tuples, with the A indicating alpha of transparency. An alpha value of 00 is totally transparent; FF is totally opaque. If RGB is used, the A value is assumed to be FF.
For instance, the RGB value "40800080" would be a transparent purple.
As in SVG 1.1, colors are defined in terms of the sRGB color space (IEC 61966).
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.
Constructors
| CommaSeparatedText | |
Fields | |
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.
Constructors
| CssFontSizeXxSmall | xx-small |
| CssFontSizeXSmall | x-small |
| CssFontSizeSmall | small |
| CssFontSizeMedium | medium |
| CssFontSizeLarge | large |
| CssFontSizeXLarge | x-large |
| CssFontSizeXxLarge | xx-large |
Instances
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.
Constructors
| DegreeTypeValueAdd | add |
| DegreeTypeValueAlter | alter |
| DegreeTypeValueSubtract | subtract |
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.
enclosure (simple)
The enclosure type describes the shape and presence / absence of an enclosure around text.
Constructors
| EnclosureRectangle | rectangle |
| EnclosureOval | oval |
| EnclosureNone | none |
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 | |
fan (simple)
The fan type represents the type of beam fanning present on a note, used to represent accelerandos and ritardandos.
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.
Constructors
| FermataShapeNormal | normal |
| FermataShapeAngled | angled |
| FermataShapeSquare | square |
| FermataShape | // |
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).
font-size (simple)
The font-size can be one of the CSS font sizes or a numeric point size.
Constructors
| FontSizeDecimal | |
| FontSizeCssFontSize | |
Fields | |
font-style (simple)
The font-style type represents a simplified version of the CSS font-style property.
Constructors
| FontStyleNormal | normal |
| FontStyleItalic | italic |
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
parseFontWeight :: String -> XParse FontWeight Source #
data GroupBarlineValue Source #
group-barline-value (simple)
The group-barline-value type indicates if the group should have common barlines.
Constructors
| GroupBarlineValueYes | yes |
| GroupBarlineValueNo | no |
| GroupBarlineValueMensurstrich | Mensurstrich |
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.
Constructors
| GroupSymbolValueNone | none |
| GroupSymbolValueBrace | brace |
| GroupSymbolValueLine | line |
| GroupSymbolValueBracket | bracket |
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.
Constructors
| HarmonyTypeExplicit | explicit |
| HarmonyTypeImplied | implied |
| HarmonyTypeAlternate | alternate |
Instances
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.
Constructors
| KindValueMajor | major |
| KindValueMinor | minor |
| KindValueAugmented | augmented |
| KindValueDiminished | diminished |
| KindValueDominant | dominant |
| KindValueMajorSeventh | major-seventh |
| KindValueMinorSeventh | minor-seventh |
| KindValueDiminishedSeventh | diminished-seventh |
| KindValueAugmentedSeventh | augmented-seventh |
| KindValueHalfDiminished | half-diminished |
| KindValueMajorMinor | major-minor |
| KindValueMajorSixth | major-sixth |
| KindValueMinorSixth | minor-sixth |
| KindValueDominantNinth | dominant-ninth |
| KindValueMajorNinth | major-ninth |
| KindValueMinorNinth | minor-ninth |
| KindValueDominant11th | dominant-11th |
| KindValueMajor11th | major-11th |
| KindValueMinor11th | minor-11th |
| KindValueDominant13th | dominant-13th |
| KindValueMajor13th | major-13th |
| KindValueMinor13th | minor-13th |
| KindValueSuspendedSecond | suspended-second |
| KindValueSuspendedFourth | suspended-fourth |
| KindValueNeapolitan | Neapolitan |
| KindValueItalian | Italian |
| KindValueFrench | French |
| KindValueGerman | German |
| KindValuePedal | pedal |
| KindValuePower | power |
| KindValueTristan | Tristan |
| KindValueOther | other |
| KindValueNone | none |
xml:lang (simple)
xs:language (simple)
data LeftCenterRight Source #
left-center-right (simple)
The left-center-right type is used to define horizontal alignment and text justification.
Constructors
| LeftCenterRightLeft | left |
| LeftCenterRightCenter | center |
| LeftCenterRightRight | right |
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 |
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.
Constructors
| LineEndUp | up |
| LineEndDown | down |
| LineEndBoth | both |
| LineEndArrow | arrow |
| LineEndNone | none |
line-shape (simple)
The line-shape type distinguishes between straight and curved lines.
Constructors
| LineShapeStraight | straight |
| LineShapeCurved | curved |
line-type (simple)
The line-type type distinguishes between solid, dashed, dotted, and wavy lines.
Constructors
| LineTypeSolid | solid |
| LineTypeDashed | dashed |
| LineTypeDotted | dotted |
| LineTypeWavy | wavy |
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 | |
data MarginType Source #
margin-type (simple)
The margin-type type specifies whether margins apply to even page, odd pages, or both.
Constructors
| MarginTypeOdd | odd |
| MarginTypeEven | even |
| MarginTypeBoth | both |
Instances
parseMarginType :: String -> XParse MarginType Source #
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.
Constructors
| MeasureNumberingValueNone | none |
| MeasureNumberingValueMeasure | measure |
| MeasureNumberingValueSystem | system |
Instances
midi-128 (simple)
The midi-16 type is used to express MIDI 1.0 values that range from 1 to 128.
Constructors
| Midi128 | |
Fields | |
midi-16 (simple)
The midi-16 type is used to express MIDI 1.0 values that range from 1 to 16.
Constructors
| Midi16 | |
Fields | |
midi-16384 (simple)
The midi-16 type is used to express MIDI 1.0 values that range from 1 to 16,384.
Constructors
| Midi16384 | |
Fields | |
Instances
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
mode (simple)
The mode type is used to specify major/minor and other mode distinctions. Valid mode values include major, minor, dorian, phrygian, lydian, mixolydian, aeolian, ionian, and locrian.
newtype NonNegativeDecimal Source #
non-negative-decimal (simple)
The non-negative-decimal type specifies a non-negative decimal value.
Constructors
| NonNegativeDecimal | |
Fields | |
Instances
newtype NonNegativeInteger Source #
xs:nonNegativeInteger (simple)
Constructors
| NonNegativeInteger | |
Fields | |
Instances
data NoteSizeType Source #
note-size-type (simple)
The note-size-type type indicates the type of note being defined by a note-size element. The grace type is used for notes of cue size that that include a grace element. The cue type is used for all other notes with cue size, whether defined explicitly or implicitly via a cue element. The large type is used for notes of large size.
Constructors
| NoteSizeTypeCue | cue |
| NoteSizeTypeGrace | grace |
| NoteSizeTypeLarge | large |
data NoteTypeValue Source #
note-type-value (simple)
The note-type type is used for the MusicXML type element and represents the graphic note type, from 256th (shortest) to long (longest).
Constructors
| NoteTypeValue256th | 256th |
| NoteTypeValue128th | 128th |
| NoteTypeValue64th | 64th |
| NoteTypeValue32nd | 32nd |
| NoteTypeValue16th | 16th |
| NoteTypeValueEighth | eighth |
| NoteTypeValueQuarter | quarter |
| NoteTypeValueHalf | half |
| NoteTypeValueWhole | whole |
| NoteTypeValueBreve | breve |
| NoteTypeValueLong | long |
data NoteheadValue Source #
notehead-value (simple)
The notehead type indicates shapes other than the open and closed ovals associated with note durations. The values do, re, mi, fa, so, la, and ti correspond to Aikin's 7-shape system.
The arrow shapes differ from triangle and inverted triangle by being centered on the stem. Slashed and back slashed notes include both the normal notehead and a slash. The triangle shape has the tip of the triangle pointing up; the inverted triangle shape has the tip of the triangle pointing down.
Constructors
| NoteheadValueSlash | slash |
| NoteheadValueTriangle | triangle |
| NoteheadValueDiamond | diamond |
| NoteheadValueSquare | square |
| NoteheadValueCross | cross |
| NoteheadValueX | x |
| NoteheadValueCircleX | circle-x |
| NoteheadValueInvertedTriangle | inverted triangle |
| NoteheadValueArrowDown | arrow down |
| NoteheadValueArrowUp | arrow up |
| NoteheadValueSlashed | slashed |
| NoteheadValueBackSlashed | back slashed |
| NoteheadValueNormal | normal |
| NoteheadValueCluster | cluster |
| NoteheadValueNone | none |
| NoteheadValueDo | do |
| NoteheadValueRe | re |
| NoteheadValueMi | mi |
| NoteheadValueFa | fa |
| NoteheadValueSo | so |
| NoteheadValueLa | la |
| NoteheadValueTi | ti |
newtype NumberLevel Source #
number-level (simple)
Slurs, tuplets, and many other features can be concurrent and overlapping within a single musical part. The number-level type distinguishes up to six concurrent objects of the same type. A reading program should be prepared to handle cases where the number-levels stop in an arbitrary order. Different numbers are needed when the features overlap in MusicXML file order. When a number-level value is implied, the value is 1 by default.
Constructors
| NumberLevel | |
Fields | |
Instances
newtype NumberOfLines Source #
number-of-lines (simple)
The number-of-lines type is used to specify the number of lines in text decoration attributes.
Constructors
| NumberOfLines | |
Fields | |
Instances
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.
Constructors
| NumberOrNormalDecimal | |
Fields | |
| NumberOrNormalNumberOrNormal | |
Fields | |
Instances
octave (simple)
Octaves are represented by the numbers 0 to 9, where 4 indicates the octave started by middle C.
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 |
percent (simple)
The percent type specifies a percentage from 0 to 100.
newtype PositiveDivisions Source #
positive-divisions (simple)
The positive-divisions type restricts divisions values to positive numbers.
Constructors
| PositiveDivisions | |
Fields | |
Instances
data PositiveIntegerOrEmpty Source #
positive-integer-or-empty (simple)
The positive-integer-or-empty values can be either a positive integer or an empty string.
newtype PositiveInteger Source #
xs:positiveInteger (simple)
Constructors
| PositiveInteger | |
Fields | |
Instances
data RehearsalEnclosure Source #
rehearsal-enclosure (simple)
The rehearsal-enclosure type describes the shape and presence / absence of an enclosure around rehearsal text.
Constructors
| RehearsalEnclosureSquare | square |
| RehearsalEnclosureCircle | circle |
| RehearsalEnclosureNone | none |
data RightLeftMiddle Source #
right-left-middle (simple)
The right-left-middle type is used to specify barline location.
Constructors
| RightLeftMiddleRight | right |
| RightLeftMiddleLeft | left |
| RightLeftMiddleMiddle | middle |
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 | |
Fields | |
Instances
semitones (simple)
The semintones type is a number representing semitones, used for chromatic alteration. A value of -1 corresponds to a flat and a value of 1 to a sharp. Decimal values like 0.5 (quarter tone sharp) may be used for microtones.
xlink:show (simple)
Constructors
| ShowNew | new |
| ShowReplace | replace |
| ShowEmbed | embed |
| ShowOther | other |
| ShowNone | none |
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 |
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.
Constructors
| ShowTupletActual | actual |
| ShowTupletBoth | both |
| ShowTupletNone | none |
Instances
parseShowTuplet :: String -> XParse ShowTuplet 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.
Instances
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 | |
Fields | |
Instances
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).
Constructors
| StaffTypeOssia | ossia |
| StaffTypeCue | cue |
| StaffTypeEditorial | editorial |
| StaffTypeRegular | regular |
| StaffTypeAlternate | alternate |
start-note (simple)
The start-note type describes the starting note of trills and mordents for playback, relative to the current note.
Constructors
| StartNoteUpper | upper |
| StartNoteMain | main |
| StartNoteBelow | below |
start-stop (simple)
The start-stop type is used for an attribute of musical elements that can either start or stop, such as tuplets, wedges, and lines.
Constructors
| StartStopStart | start |
| StartStopStop | stop |
data StartStopChange Source #
start-stop-change (simple)
The start-stop-change type is used to distinguish types of pedal directions.
Constructors
| StartStopChangeStart | start |
| StartStopChangeStop | stop |
| StartStopChangeChange | change |
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.
Constructors
| StartStopContinueStart | start |
| StartStopContinueStop | stop |
| StartStopContinueContinue | continue |
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.
Constructors
| StartStopDiscontinueStart | start |
| StartStopDiscontinueStop | stop |
| StartStopDiscontinueDiscontinue | discontinue |
data StartStopSingle Source #
start-stop-single (simple)
The start-stop-single type is used for an attribute of musical elements that can be used for either multi-note or single-note musical elements, as for tremolos.
Constructors
| StartStopSingleStart | start |
| StartStopSingleStop | stop |
| StartStopSingleSingle | single |
stem-value (simple)
The stem type represents the notated stem direction.
Constructors
| StemValueDown | down |
| StemValueUp | up |
| StemValueDouble | double |
| StemValueNone | none |
step (simple)
The step type represents a step of the diatonic scale, represented using the English letters A through G.
newtype StringNumber Source #
string-number (simple)
The string-number type indicates a string number. Strings are numbered from high to low, with 1 being the highest pitched string.
Constructors
| StringNumber | |
Fields | |
Instances
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.
Constructors
| SyllabicSingle | single |
| SyllabicBegin | begin |
| SyllabicEnd | end |
| SyllabicMiddle | middle |
data SymbolSize Source #
symbol-size (simple)
The symbol-size type is used to indicate full vs. cue-sized vs. oversized symbols. The large value for oversized symbols was added in version 1.1.
Constructors
| SymbolSizeFull | full |
| SymbolSizeCue | cue |
| SymbolSizeLarge | large |
Instances
parseSymbolSize :: String -> XParse SymbolSize 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.
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.
Constructors
| TextDirectionLtr | ltr |
| TextDirectionRtl | rtl |
| TextDirectionLro | lro |
| TextDirectionRlo | rlo |
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.
Constructors
| TimeSymbolCommon | common |
| TimeSymbolCut | cut |
| TimeSymbolSingleNumber | single-number |
| TimeSymbolNormal | normal |
Instances
parseTimeSymbol :: String -> XParse TimeSymbol Source #
xs:token (simple)
Constructors
| Token | |
Fields | |
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 |
newtype TremoloMarks Source #
tremolo-marks (simple)
The number of tremolo marks is represented by a number from 0 to 6: the same as beam-level with 0 added.
Constructors
| TremoloMarks | |
Fields
| |
Instances
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
parseTrillBeats :: String -> XParse TrillBeats Source #
trill-step (simple)
The trill-step type describes the alternating note of trills and mordents for playback, relative to the current note.
Constructors
| TrillStepWhole | whole |
| TrillStepHalf | half |
| TrillStepUnison | unison |
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.
Constructors
| TwoNoteTurnWhole | whole |
| TwoNoteTurnHalf | half |
| TwoNoteTurnNone | none |
Instances
xlink:type (simple)
Constructors
| TypeSimple | simple |
up-down (simple)
The up-down type is used for arrow direction, indicating which way the tip is pointing.
Constructors
| UpDownUp | up |
| UpDownDown | down |
data UpDownStop Source #
up-down-stop (simple)
The up-down-stop type is used for octave-shift elements, indicating the direction of the shift from their true pitched values because of printing difficulty.
Constructors
| UpDownStopUp | up |
| UpDownStopDown | down |
| UpDownStopStop | stop |
Instances
parseUpDownStop :: String -> XParse UpDownStop Source #
data UprightInverted Source #
upright-inverted (simple)
The upright-inverted type describes the appearance of a fermata element. The value is upright if not specified.
Constructors
| UprightInvertedUpright | upright |
| UprightInvertedInverted | inverted |
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 |
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.
Constructors
| ValignImageTop | top |
| ValignImageMiddle | middle |
| ValignImageBottom | bottom |
Instances
wedge-type (simple)
The wedge type is crescendo for the start of a wedge that is closed at the left side, diminuendo for the start of a wedge that is closed on the right side, and stop for the end of a wedge.
Constructors
| WedgeTypeCrescendo | crescendo |
| WedgeTypeDiminuendo | diminuendo |
| WedgeTypeStop | stop |
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.
data YesNoNumber Source #
yes-no-number (simple)
The yes-no-number type is used for attributes that can be either boolean or numeric values.
Constructors
| YesNoNumberYesNo | |
Fields | |
| YesNoNumberDecimal | |
Fields | |
Instances
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.
xml:lang (union)
Constructors
| SumLang | // |
data SumPositiveIntegerOrEmpty Source #
positive-integer-or-empty (union)
Constructors
| SumPositiveIntegerOrEmpty | // |
Instances
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
mkAccidental :: AccidentalValue -> Accidental Source #
Smart constructor for Accidental
data AccidentalMark Source #
accidental-mark (complex)
An accidental-mark can be used as a separate notation or as part of an ornament. When used in an ornament, position and placement are relative to the ornament, not relative to the note.
Constructors
| AccidentalMark | |
Fields
| |
Instances
mkAccidentalMark :: AccidentalValue -> AccidentalMark Source #
Smart constructor for AccidentalMark
data AccidentalText Source #
accidental-text (complex)
The accidental-text type represents an element with an accidental value and text-formatting attributes.
Constructors
Instances
mkAccidentalText :: AccidentalValue -> AccidentalText Source #
Smart constructor for AccidentalText
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
| |
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.
Constructors
| AccordionRegistration | |
Fields
| |
mkAccordionRegistration :: AccordionRegistration Source #
Smart constructor for AccordionRegistration
data Appearance Source #
appearance (complex)
The appearance type controls general graphical settings for the music's final form appearance on a printed page of display. Currently this includes support for line widths and definitions for note sizes, plus an extension element for other aspects of appearance.
Constructors
| Appearance | |
Fields
| |
Instances
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
mkArpeggiate :: Arpeggiate Source #
Smart constructor for Arpeggiate
data Articulations Source #
articulations (complex)
Articulations and accents are grouped together here.
Constructors
| Articulations | |
Fields | |
Instances
mkArticulations :: Articulations Source #
Smart constructor for Articulations
data Attributes Source #
attributes (complex)
The attributes element contains musical information that typically changes on measure boundaries. This includes key and time signatures, clefs, transpositions, and staving.
Constructors
| Attributes | |
Fields
| |
Instances
mkAttributes :: Editorial -> Attributes Source #
Smart constructor for Attributes
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.
Constructors
| Backup | |
Fields | |
data BarStyleColor Source #
bar-style-color (complex)
The bar-style-color type contains barline style and color information.
Constructors
| BarStyleColor | |
Fields
| |
Instances
mkBarStyleColor :: BarStyle -> BarStyleColor Source #
Smart constructor for BarStyleColor
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
| |
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.
parseBarre :: XParse Barre 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
| |
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
| |
bass-step (complex)
The bass-step type represents the pitch step of the bass of the current chord within the harmony element. The text attribute indicates how the bass should appear on the page if not using the element contents.
Constructors
| BassStep | |
Fields
| |
beam (complex)
Beam values include begin, continue, end, forward hook, and backward hook. Up to six concurrent beam levels are available to cover up to 256th notes. The repeater attribute, used for tremolos, needs to be specified with a "yes" value for each beam using it. Beams that have a begin value can also have a fan attribute to indicate accelerandos and ritardandos using fanned beams. The fan attribute may also be used with a continue value if the fanning direction changes on that note. The value is "none" if not specified.
Note that the beam number does not distinguish sets of beams that overlap, as it does for slur and other elements. Beaming groups are distinguished by being in different voices and/or the presence or absence of grace and cue elements.
Constructors
| Beam | |
Fields
| |
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
mkBeatRepeat :: StartStop -> BeatRepeat Source #
Smart constructor for BeatRepeat
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
| |
bookmark (complex)
The bookmark type serves as a well-defined target for an incoming simple XLink.
Constructors
| Bookmark | |
Fields
| |
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
| |
cancel (complex)
A cancel element indicates that the old key signature should be cancelled before the new one appears. This will always happen when changing to C major or A minor and need not be specified then. The cancel value matches the fifths value of the cancelled key signature (e.g., a cancel of -2 will provide an explicit cancellation for changing from B flat major to F major). The optional location attribute indicates whether the cancellation appears to the left or the right of the new key signature. It is left by default.
Constructors
| Cancel | |
Fields
| |
clef (complex)
Clefs are represented by a combination of sign, line, and clef-octave-change elements. The optional number attribute refers to staff numbers within the part. A value of 1 is assumed if not present.
Sometimes clefs are added to the staff in non-standard line positions, either to indicate cue passages, or when there are multiple clefs present simultaneously on one staff. In this situation, the additional attribute is set to "yes" and the line value is ignored. The size attribute is used for clefs where the additional attribute is "yes". It is typically used to indicate cue clefs.
Constructors
| Clef | |
Fields
| |
credit (complex)
The credit type represents the appearance of the title, composer, arranger, lyricist, copyright, dedication, and other text and graphics that commonly appears on the first page of a score. The credit-words and credit-image elements are similar to the words and image elements for directions. However, since the credit is not part of a measure, the default-x and default-y attributes adjust the origin relative to the bottom left-hand corner of the first page. The enclosure for credit-words is none by default.
By default, a series of credit-words elements within a single credit element follow one another in sequence visually. Non-positional formatting attributes are carried over from the previous element by default.
The page attribute for the credit element, new in Version 2.0, specifies the page number where the credit should appear. This is an integer value that starts with 1 for the first page. Its value is 1 by default. Since credits occur before the music, these page numbers do not refer to the page numbering specified by the print element's page-number attribute.
Constructors
| Credit | |
Fields
| |
dashes (complex)
The dashes type represents dashes, used for instance with cresc. and dim. marks.
Constructors
| Dashes | |
Fields
| |
defaults (complex)
The defaults type specifies score-wide defaults for scaling, layout, and appearance.
Constructors
| Defaults | |
Fields
| |
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
| |
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
mkDegreeAlter :: Semitones -> DegreeAlter Source #
Smart constructor for DegreeAlter
data DegreeType Source #
degree-type (complex)
The degree-type type indicates if this degree is an addition, alteration, or subtraction relative to the kind of the current chord. The value of the degree-type element affects the interpretation of the value of the degree-alter element. The text attribute specifies how the type of the degree should be displayed.
Constructors
| DegreeType | |
Fields
| |
Instances
mkDegreeType :: DegreeTypeValue -> DegreeType Source #
Smart constructor for DegreeType
data DegreeValue Source #
degree-value (complex)
The content of the degree-value type is a number indicating the degree of the chord (1 for the root, 3 for third, etc). The text attribute specifies how the type of the degree should be displayed.
Constructors
| DegreeValue | |
Fields
| |
Instances
mkDegreeValue :: PositiveInteger -> DegreeValue Source #
Smart constructor for DegreeValue
direction (complex)
A direction is a musical indication that is not attached to a specific note. Two or more may be combined to indicate starts and stops of wedges, dashes, etc.
By default, a series of direction-type elements and a series of child elements of a direction-type within a single direction element follow one another in sequence visually. For a series of direction-type children, non-positional formatting attributes are carried over from the previous element by default.
Constructors
| Direction | |
Fields
| |
mkDirection :: EditorialVoiceDirection -> Direction Source #
Smart constructor for Direction
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.
Constructors
| DirectionType | |
Instances
mkDirectionType :: ChxDirectionType -> DirectionType Source #
Smart constructor for DirectionType
directive (complex)
Constructors
| Directive | |
Fields
| |
data DisplayStepOctave Source #
display-step-octave (complex)
The display-step-octave type contains the sequence of elements used by both the rest and unpitched elements. This group is used to place rests and unpitched elements on the staff without implying that these elements have pitch. Positioning follows the current clef. If percussion clef is used, the display-step and display-octave elements are interpreted as if in treble clef, with a G in octave 4 on line 2. If not present, the note is placed on the middle line of the staff, generally used for one-line staffs.
Constructors
| DisplayStepOctave | |
mkDisplayStepOctave :: DisplayStepOctave Source #
Smart constructor for DisplayStepOctave
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
| |
mkDynamics :: Dynamics Source #
Smart constructor for Dynamics
elision (complex)
In Version 2.0, the content of the elision type is used to specify the symbol used to display the elision. Common values are a no-break space (Unicode 00A0), an underscore (Unicode 005F), or an undertie (Unicode 203F).
Constructors
| Elision | |
Fields
| |
empty (complex)
The empty type represents an empty element with no attributes.
Constructors
| Empty |
parseEmpty :: XParse Empty Source #
empty-font (complex)
The empty-font type represents an empty element with font attributes.
Constructors
| EmptyFont | |
Fields
| |
mkEmptyFont :: EmptyFont Source #
Smart constructor for EmptyFont
empty-line (complex)
The empty-line type represents an empty element with line-shape, line-type, print-style and placement attributes.
Constructors
| EmptyLine | |
Fields
| |
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
mkEmptyPlacement :: EmptyPlacement Source #
Smart constructor for EmptyPlacement
data EmptyPrintStyle Source #
empty-print-style (complex)
The empty-print-style type represents an empty element with print-style attributes.
Constructors
| EmptyPrintStyle | |
Fields
| |
Instances
mkEmptyPrintStyle :: EmptyPrintStyle Source #
Smart constructor for EmptyPrintStyle
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
Instances
mkEmptyTrillSound :: EmptyTrillSound Source #
Smart constructor for EmptyTrillSound
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 | |
Fields | |
mkEncoding :: Encoding Source #
Smart constructor for Encoding
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
| |
mkEnding :: String -> EndingNumber -> StartStopDiscontinue -> Ending Source #
Smart constructor for Ending
extend (complex)
The extend type represents word extensions for lyrics.
Constructors
| Extend | |
Fields
| |
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
| |
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
| |
figure (complex)
The figure type represents a single figure within a figured-bass element.
Constructors
| Figure | |
Fields
| |
data FiguredBass Source #
figured-bass (complex)
The figured-bass element represents figured bass notation. Figured bass elements take their position from the first regular note that follows. Figures are ordered from top to bottom. The value of parentheses is "no" if not present.
Constructors
| FiguredBass | |
Fields
| |
Instances
mkFiguredBass :: Editorial -> FiguredBass Source #
Smart constructor for FiguredBass
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
| |
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
| |
mkFirstFret :: PositiveInteger -> FirstFret Source #
Smart constructor for FirstFret
data FormattedText Source #
formatted-text (complex)
The formatted-text type represents a text element with text-formatting attributes.
Constructors
Instances
mkFormattedText :: String -> FormattedText Source #
Smart constructor for FormattedText
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.
Constructors
| Forward | |
Fields | |
frame (complex)
The frame type represents a frame or fretboard diagram used together with a chord symbol. The representation is based on the NIFF guitar grid with additional information.
Constructors
| Frame | |
Fields
| |
parseFrame :: XParse Frame Source #
mkFrame :: PositiveInteger -> PositiveInteger -> Frame Source #
Smart constructor for Frame
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
| |
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
| |
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
| |
grace (complex)
The grace type indicates the presence of a grace note. The slash attribute for a grace note is yes for slashed eighth notes. The other grace note attributes come from MuseData sound suggestions. Steal-time-previous indicates the percentage of time to steal from the previous note for the grace note. Steal-time-following indicates the percentage of time to steal from the following note for the grace note. Make-time indicates to make time, not steal time; the units are in real-time divisions for the grace note.
Constructors
| Grace | |
Fields
| |
parseGrace :: XParse Grace Source #
data GroupBarline Source #
group-barline (complex)
The group-barline type indicates if the group should have common barlines.
Constructors
| GroupBarline | |
Fields
| |
Instances
mkGroupBarline :: GroupBarlineValue -> GroupBarline Source #
Smart constructor for GroupBarline
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
| |
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
mkGroupSymbol :: GroupSymbolValue -> GroupSymbol Source #
Smart constructor for GroupSymbol
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
| |
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 | |
Fields
| |
Instances
mkHammerOnPullOff :: String -> StartStop -> HammerOnPullOff Source #
Smart constructor for HammerOnPullOff
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
| |
mkHarmonic :: Harmonic Source #
Smart constructor for Harmonic
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
| |
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
mkHarpPedals :: HarpPedals Source #
Smart constructor for HarpPedals
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
| |
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
mkIdentification :: Identification Source #
Smart constructor for Identification
image (complex)
The image type is used to include graphical images in a score.
Constructors
| Image | |
Fields
| |
parseImage :: XParse Image Source #
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
mkInstrument :: IDREF -> Instrument Source #
Smart constructor for Instrument
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
| |
mkInversion :: NonNegativeInteger -> Inversion Source #
Smart constructor for Inversion
key (complex)
The key type represents a key signature. Both traditional and non-traditional key signatures are supported. The optional number attribute refers to staff numbers. If absent, the key signature applies to all staves in the part.
Constructors
| Key | |
Fields
| |
key-octave (complex)
The key-octave element specifies in which octave an element of a key signature appears. The content specifies the octave value using the same values as the display-octave element. The number attribute is a positive integer that refers to the key signature element in left-to-right order. If the cancel attribute is set to yes, then this number refers to an element specified by the cancel element. It is no by default.
Constructors
| KeyOctave | |
Fields
| |
mkKeyOctave :: Octave -> PositiveInteger -> KeyOctave Source #
Smart constructor for KeyOctave
kind (complex)
Kind indicates the type of chord. Degree elements can then add, subtract, or alter from these starting points
The attributes are used to indicate the formatting of the symbol. Since the kind element is the constant in all the harmony-chord groups that can make up a polychord, many formatting attributes are here. The use-symbols attribute is yes if the kind should be represented when possible with harmony symbols rather than letters and numbers. These symbols include: major: a triangle, like Unicode 25B3 minor: -, like Unicode 002D augmented: +, like Unicode 002B diminished: °, like Unicode 00B0 half-diminished: ø, like Unicode 00F8 The text attribute describes how the kind should be spelled if not using symbols; it is ignored if use-symbols is yes. The stack-degrees attribute is yes if the degree elements should be stacked above each other. The parentheses-degrees attribute is yes if all the degrees should be in parentheses. The bracket-degrees attribute is yes if all the degrees should be in a bracket. If not specified, these values are implementation-specific. The alignment attributes are for the entire harmony-chord group of which this kind element is a part.
Constructors
| Kind | |
Fields
| |
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
| |
parseLevel :: XParse Level 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
| |
mkLineWidth :: Tenths -> LineWidthType -> LineWidth Source #
Smart constructor for LineWidth
link (complex)
The link type serves as an outgoing simple XLink. It is also used to connect a MusicXML score with a MusicXML opus.
Constructors
| Link | |
Fields
| |
lyric (complex)
The lyric type represents text underlays for lyrics, based on Humdrum with support for other formats. Two text elements that are not separated by an elision element are part of the same syllable, but may have different text formatting. The MusicXML 2.0 XSD is more strict than the 2.0 DTD in enforcing this by disallowing a second syllabic element unless preceded by an elision element. The lyric number indicates multiple lines, though a name can be used as well (as in Finale's verse chorus section specification). Justification is center by default; placement is below by default.
Constructors
| Lyric | |
Fields
| |
parseLyric :: XParse Lyric Source #
lyric-font (complex)
The lyric-font type specifies the default font for a particular name and number of lyric.
Constructors
| LyricFont | |
Fields
| |
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
mkLyricLanguage :: Lang -> LyricLanguage Source #
Smart constructor for LyricLanguage
measure (complex)
Constructors
| Measure | |
Fields
| |
data CmpMeasure Source #
measure (complex)
Constructors
| CmpMeasure | |
Fields
| |
Instances
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
mkMeasureLayout :: MeasureLayout Source #
Smart constructor for MeasureLayout
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.
Constructors
| MeasureNumbering | |
Fields
| |
mkMeasureNumbering :: MeasureNumberingValue -> MeasureNumbering Source #
Smart constructor for MeasureNumbering
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.
Constructors
| MeasureRepeat | |
Fields
| |
Instances
mkMeasureRepeat :: PositiveIntegerOrEmpty -> StartStop -> MeasureRepeat Source #
Smart constructor for MeasureRepeat
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.
Constructors
| MeasureStyle | |
Fields
| |
Instances
mkMeasureStyle :: ChxMeasureStyle -> MeasureStyle Source #
Smart constructor for MeasureStyle
metronome (complex)
The metronome type represents metronome marks and other metric relationships. The beat-unit group and per-minute element specify regular metronome marks. The metronome-note and metronome-relation elements allow for the specification of more complicated metric relationships, such as swing tempo marks where two eighths are equated to a quarter note / eighth note triplet. The parentheses attribute indicates whether or not to put the metronome mark in parentheses; its value is no if not specified.
Constructors
| Metronome | |
Fields
| |
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
mkMetronomeBeam :: BeamValue -> MetronomeBeam Source #
Smart constructor for MetronomeBeam
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
mkMetronomeNote :: NoteTypeValue -> MetronomeNote Source #
Smart constructor for MetronomeNote
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.
Constructors
| MetronomeTuplet | |
Fields
| |
Instances
mkMetronomeTuplet :: MetronomeTuplet -> StartStop -> MetronomeTuplet Source #
Smart constructor for MetronomeTuplet
data MidiDevice Source #
midi-device (complex)
The midi-device type corresponds to the DeviceName meta event in Standard MIDI Files. The optional port attribute is a number from 1 to 16 that can be used with the unofficial MIDI port (or cable) meta event.
Constructors
| MidiDevice | |
Fields
| |
Instances
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
mkMidiInstrument :: IDREF -> MidiInstrument Source #
Smart constructor for MidiInstrument
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
mkMiscellaneous :: Miscellaneous Source #
Smart constructor for Miscellaneous
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
| |
mkMiscellaneousField :: String -> Token -> MiscellaneousField Source #
Smart constructor for MiscellaneousField
mordent (complex)
The mordent type is used for both represents the mordent sign with the vertical line and the inverted-mordent sign without the line. The long attribute is "no" by default.
Constructors
| Mordent | |
Fields
| |
data MultipleRest Source #
multiple-rest (complex)
The text of the multiple-rest type indicates the number of measures in the multiple rest. Multiple rests may use the 1-bar 2-bar 4-bar rest symbols, or a single shape. The use-symbols attribute indicates which to use; it is no if not specified. The element text is ignored when the type is stop.
Constructors
| MultipleRest | |
Fields
| |
Instances
mkMultipleRest :: PositiveIntegerOrEmpty -> MultipleRest Source #
Smart constructor for MultipleRest
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 | |
Fields
| |
Instances
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
mkNonArpeggiate :: TopBottom -> NonArpeggiate Source #
Smart constructor for NonArpeggiate
notations (complex)
Notations refer to musical notations, not XML notations. Multiple notations are allowed in order to represent multiple editorial levels. The set of notations may be refined and expanded over time, especially to handle more instrument-specific technical notations.
Constructors
| Notations | |
Fields | |
note (complex)
Notes are the most common type of MusicXML data. The MusicXML format keeps the MuseData distinction between elements used for sound information and elements used for notation information (e.g., tie is used for sound, tied for notation). Thus grace notes do not have a duration element. Cue notes have a duration element, as do forward elements, but no tie elements. Having these two types of information available can make interchange considerably easier, as some programs handle one type of information much more readily than the other.
The dynamics and end-dynamics attributes correspond to MIDI 1.0's Note On and Note Off velocities, respectively. They are expressed in terms of percentages of the default forte value (90 for MIDI 1.0). The attack and release attributes are used to alter the staring and stopping time of the note from when it would otherwise occur based on the flow of durations - information that is specific to a performance. They are expressed in terms of divisions, either positive or negative. A note that starts a tie should not have a release attribute, and a note that stops a tie should not have an attack attribute. If a note is played only one time through a repeat, the time-only attribute shows which time to play the note. The pizzicato attribute is used when just this note is sounded pizzicato, vs. the pizzicato element which changes overall playback between pizzicato and arco.
Constructors
note-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 | |
Fields
| |
mkNoteSize :: NonNegativeDecimal -> NoteSizeType -> NoteSize Source #
Smart constructor for NoteSize
note-type (complex)
The note-type type indicates the graphic note type. Values range from 256th to long. The size attribute indicates full, cue, or large size, with full the default for regular notes and cue the default for cue and grace notes.
Constructors
| NoteType | |
Fields
| |
mkNoteType :: NoteTypeValue -> NoteType Source #
Smart constructor for NoteType
notehead (complex)
The notehead element indicates shapes other than the open and closed ovals associated with note durations.
For the enclosed shapes, the default is to be hollow for half notes and longer, and filled otherwise. The filled attribute can be set to change this if needed.
If the parentheses attribute is set to yes, the notehead is parenthesized. It is no by default.
Constructors
| Notehead | |
Fields
| |
mkNotehead :: NoteheadValue -> Notehead Source #
Smart constructor for Notehead
data OctaveShift Source #
octave-shift (complex)
The octave shift type indicates where notes are shifted up or down from their true pitched values because of printing difficulty. Thus a treble clef line noted with 8va will be indicated with an octave-shift down from the pitch data indicated in the notes. A size of 8 indicates one octave; a size of 15 indicates two octaves.
Constructors
| OctaveShift | |
Fields
| |
Instances
mkOctaveShift :: UpDownStop -> OctaveShift Source #
Smart constructor for OctaveShift
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
| |
opus (complex)
The opus type represents a link to a MusicXML opus document that composes multiple MusicXML scores into a collection.
Constructors
| Opus | |
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 | |
Fields | |
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
mkOtherAppearance :: String -> Token -> OtherAppearance Source #
Smart constructor for OtherAppearance
data OtherDirection Source #
other-direction (complex)
The other-direction type is used to define any direction symbols not yet in the current version of the MusicXML format. This allows extended representation, though without application interoperability.
Constructors
| OtherDirection | |
Fields
| |
Instances
mkOtherDirection :: String -> OtherDirection Source #
Smart constructor for OtherDirection
data OtherNotation Source #
other-notation (complex)
The other-notation type is used to define any notations not yet in the MusicXML format. This allows extended representation, though without application interoperability. It handles notations where more specific extension elements such as other-dynamics and other-technical are not appropriate.
Constructors
| OtherNotation | |
Fields
| |
Instances
mkOtherNotation :: String -> StartStopSingle -> OtherNotation Source #
Smart constructor for OtherNotation
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 | |
Fields
| |
Instances
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.
Constructors
| PageMargins | |
Fields
| |
Instances
mkPageMargins :: AllMargins -> PageMargins Source #
Smart constructor for PageMargins
part (complex)
Constructors
| CmpPart | |
Fields
| |
part (complex)
Constructors
| Part | |
Fields
| |
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
| |
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.
Constructors
| PartList | |
Fields | |
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
| |
data PartSymbol Source #
part-symbol (complex)
The part-symbol element indicates how a symbol for a multi-staff part is indicated in the score. Values include none, brace, line, and bracket; brace is the default. The top-staff and bottom-staff elements are used when the brace does not extend across the entire part. For example, in a 3-staff organ part, the top-staff will typically be 1 for the right hand, while the bottom-staff will typically be 2 for the left hand. Staff 3 for the pedals is usually outside the brace.
Constructors
| PartSymbol | |
Fields
| |
Instances
mkPartSymbol :: GroupSymbolValue -> PartSymbol Source #
Smart constructor for PartSymbol
pedal (complex)
The pedal type represents piano pedal marks. The line attribute is yes if pedal lines are used, no if Ped and * signs are used. The change type is used with line set to yes.
Constructors
| Pedal | |
Fields
| |
parsePedal :: XParse Pedal Source #
data PedalTuning Source #
pedal-tuning (complex)
The pedal-tuning type specifies the tuning of a single harp pedal.
Constructors
| PedalTuning | |
Fields
| |
Instances
mkPedalTuning :: Step -> Semitones -> PedalTuning Source #
Smart constructor for PedalTuning
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
| |
pitch (complex)
Pitch is represented as a combination of the step of the diatonic scale, the chromatic alteration, and the octave.
Constructors
| Pitch | |
Fields
| |
parsePitch :: XParse Pitch Source #
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
mkPlacementText :: String -> PlacementText Source #
Smart constructor for PlacementText
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
Fields
| |
parsePrint :: XParse Print Source #
rehearsal (complex)
The rehearsal type specifies a rehearsal mark. Language is Italian ("it") by default. Enclosure is square by default.
Constructors
| Rehearsal | |
Fields
| |
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
| |
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
| |
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
| |
root-step (complex)
The root-step type represents the pitch step of the root of the current chord within the harmony element. The text attribute indicates how the root should appear on the page if not using the element contents.
Constructors
| RootStep | |
Fields
| |
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
| |
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
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
mkScoreInstrument :: ID -> String -> ScoreInstrument Source #
Smart constructor for ScoreInstrument
data CmpScorePart Source #
score-part (complex)
Each MusicXML part corresponds to a track in a Standard MIDI Format 1 file. The score-instrument elements are used when there are multiple instruments per track. The midi-device element is used to make a MIDI device or port assignment for the given track. Initial midi-instrument assignments may be made here as well.
Constructors
| CmpScorePart | |
Fields
| |
Instances
mkCmpScorePart :: ID -> PartName -> CmpScorePart Source #
Smart constructor for CmpScorePart
data ScorePartwise Source #
score-partwise (complex)
Constructors
| ScorePartwise | |
Fields
| |
Instances
mkScorePartwise :: ScoreHeader -> ScorePartwise Source #
Smart constructor for ScorePartwise
data ScoreTimewise Source #
score-timewise (complex)
Constructors
| ScoreTimewise | |
Fields
| |
Instances
mkScoreTimewise :: ScoreHeader -> ScoreTimewise Source #
Smart constructor for ScoreTimewise
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
| |
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
| |
parseSlide :: XParse Slide 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
| |
sound (complex)
The sound element contains general playback parameters. They can stand alone within a part/measure, or be a component element within a direction.
Tempo is expressed in quarter notes per minute. If 0, the sound-generating program should prompt the user at the time of compiling a sound (MIDI) file. Dynamics (or MIDI velocity) are expressed as a percentage of the default forte value (90 for MIDI 1.0). Dacapo indicates to go back to the beginning of the movement. When used it always has the value "yes". Segno and dalsegno are used for backwards jumps to a segno sign; coda and tocoda are used for forward jumps to a coda sign. If there are multiple jumps, the value of these parameters can be used to name and distinguish them. If segno or coda is used, the divisions attribute can also be used to indicate the number of divisions per quarter note. Otherwise sound and MIDI generating programs may have to recompute this. By default, a dalsegno or dacapo attribute indicates that the jump should occur the first time through, while a tocoda attribute indicates the jump should occur the second time through. The time that jumps occur can be changed by using the time-only attribute. Forward-repeat is used when a forward repeat sign is implied, and usually follows a bar line. When used it always has the value of "yes". The fine attribute follows the final note or rest in a movement with a da capo or dal segno direction. If numeric, the value represents the actual duration of the final note or rest, which can be ambiguous in written notation and different among parts and voices. The value may also be "yes" to indicate no change to the final duration. If the sound element applies only one time through a repeat, the time-only attribute indicates which time to apply the sound element. Pizzicato in a sound element effects all following notes. Yes indicates pizzicato, no indicates arco. The pan and elevation attributes are deprecated in Version 2.0. The pan and elevation elements in the midi-instrument element should be used instead. The meaning of the pan and elevation attributes is the same as for the pan and elevation elements. If both are present, the mid-instrument elements take priority. The damper-pedal, soft-pedal, and sostenuto-pedal attributes effect playback of the three common piano pedals and their MIDI controller equivalents. The yes value indicates the pedal is depressed; no indicates the pedal is released. A numeric value from 0 to 100 may also be used for half pedaling. This value is the percentage that the pedal is depressed. A value of 0 is equivalent to no, and a value of 100 is equivalent to yes. MIDI instruments are changed using the midi-instrument element. The offset element is used to indicate that the sound takes place offset from the current score position. If the sound element is a child of a direction element, the sound offset element overrides the direction offset element if both elements are present. Note that the offset reflects the intended musical position for the change in sound. It should not be used to compensate for latency issues in particular hardware configurations.
Constructors
| Sound | |
Fields
| |
parseSound :: XParse Sound Source #
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
mkStaffDetails :: StaffDetails Source #
Smart constructor for StaffDetails
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
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 | |
Fields
| |
Instances
mkStaffTuning :: Tuning -> StaffTuning Source #
Smart constructor for StaffTuning
stem (complex)
Stems can be down, up, none, or double. For down and up stems, the position attributes can be used to specify stem length. The relative values specify the end of the stem relative to the program default. Default values specify an absolute end stem position. Negative values of relative-y that would flip a stem instead of shortening it are ignored.
Constructors
| Stem | |
Fields
| |
string (complex)
The string type is used with tablature notation, regular notation (where it is often circled), and chord diagrams. String numbers start with 1 for the highest string.
Constructors
| CmpString | |
Fields
| |
mkCmpString :: StringNumber -> CmpString Source #
Smart constructor for CmpString
data StrongAccent Source #
strong-accent (complex)
The strong-accent type indicates a vertical accent mark. The type attribute indicates if the point of the accent is down or up.
Constructors
| StrongAccent | |
Fields
| |
Instances
mkStrongAccent :: StrongAccent -> StrongAccent Source #
Smart constructor for StrongAccent
style-text (complex)
The style-text type represents a text element with a print-style attribute group.
Constructors
| StyleText | |
Fields
| |
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
| |
data SystemLayout Source #
system-layout (complex)
System layout includes left and right margins and the vertical distance from the previous system. The system distance is measured from the bottom line of the previous system to the top line of the current system. It is ignored for the first system on a page. The top system distance is measured from the page's top margin to the top line of the first system. It is ignored for all but the first system on a page.
Sometimes the sum of measure widths in a system may not equal the system width specified by the layout elements due to roundoff or other errors. The behavior when reading MusicXML files in these cases is application-dependent. For instance, applications may find that the system layout data is more reliable than the sum of the measure widths, and adjust the measure widths accordingly.
Constructors
| SystemLayout | |
Fields
| |
Instances
mkSystemLayout :: SystemLayout Source #
Smart constructor for SystemLayout
data SystemMargins Source #
system-margins (complex)
System margins are relative to the page margins. Positive values indent and negative values reduce the margin size.
Constructors
| SystemMargins | |
Instances
mkSystemMargins :: LeftRightMargins -> SystemMargins Source #
Smart constructor for SystemMargins
technical (complex)
Technical indications give performance information for individual instruments.
Constructors
| Technical | |
Fields | |
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.
Constructors
| TextElementData | |
Fields
| |
Instances
mkTextElementData :: String -> TextElementData Source #
Smart constructor for TextElementData
tie (complex)
The tie element indicates that a tie begins or ends with this note. The tie element indicates sound; the tied element indicates notation.
tied (complex)
The tied type represents the notated tie. The tie element represents the tie sound.
Constructors
| Tied | |
Fields
| |
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
| |
data TimeModification Source #
time-modification (complex)
The time-modification type represents tuplets and other durational changes.
Constructors
| TimeModification | |
Fields
| |
mkTimeModification :: NonNegativeInteger -> NonNegativeInteger -> TimeModification Source #
Smart constructor for TimeModification
transpose (complex)
The transpose type represents what must be added to a written pitch to get a correct sounding pitch.
Constructors
| Transpose | |
Fields
| |
tremolo (complex)
While using repeater beams was the original method for indicating tremolos, often playback and display are not well-enough integrated in an application to make that feasible. The tremolo ornament can be used to indicate either single-note or double-note tremolos. Single-note tremolos use the single type, while double-note tremolos use the start and stop types. The default is "single" for compatibility with Version 1.1. The text of the element indicates the number of tremolo marks and is an integer from 0 to 6. Note that the number of attached beams is not included in this value, but is represented separately using the beam element.
Constructors
| Tremolo | |
Fields
| |
tuplet (complex)
A tuplet element is present when a tuplet is to be displayed graphically, in addition to the sound data provided by the time-modification elements. The number attribute is used to distinguish nested tuplets. The bracket attribute is used to indicate the presence of a bracket. If unspecified, the results are implementation-dependent. The line-shape attribute is used to specify whether the bracket is straight or in the older curved or slurred style. It is straight by default.
Whereas a time-modification element shows how the cumulative, sounding effect of tuplets compare to the written note type, the tuplet element describes how each tuplet is displayed.
The show-number attribute is used to display either the number of actual notes, the number of both actual and normal notes, or neither. It is actual by default. The show-type attribute is used to display either the actual type, both the actual and normal types, or neither. It is none by default.
Constructors
| Tuplet | |
Fields
| |
tuplet-dot (complex)
The tuplet-dot type is used to specify dotted normal tuplet types.
Constructors
| TupletDot | |
Fields
| |
mkTupletDot :: TupletDot Source #
Smart constructor for TupletDot
data TupletNumber Source #
tuplet-number (complex)
The tuplet-number type indicates the number of notes for this portion of the tuplet.
Constructors
| TupletNumber | |
Fields
| |
Instances
mkTupletNumber :: NonNegativeInteger -> TupletNumber Source #
Smart constructor for TupletNumber
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
mkTupletPortion :: TupletPortion Source #
Smart constructor for TupletPortion
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
mkTupletType :: NoteTypeValue -> TupletType Source #
Smart constructor for TupletType
typed-text (complex)
The typed-text type represents a text element with a type attributes.
Constructors
| TypedText | |
Fields
| |
wavy-line (complex)
Wavy lines are one way to indicate trills. When used with a measure element, they should always have type="continue" set.
Constructors
| WavyLine | |
Fields
| |
mkWavyLine :: StartStopContinue -> WavyLine Source #
Smart constructor for WavyLine
wedge (complex)
The wedge type represents crescendo and diminuendo wedge symbols. The type attribute is crescendo for the start of a wedge that is closed at the left side, and diminuendo for the start of a wedge that is closed on the right side. Spread values are measured in tenths; those at the start of a crescendo wedge or end of a diminuendo wedge are ignored.
Constructors
| Wedge | |
Fields
| |
parseWedge :: XParse Wedge 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
| |
data ChxArticulations Source #
articulations (choice)
Constructors
mkArticulationsAccent :: EmptyPlacement -> ChxArticulations Source #
Smart constructor for ArticulationsAccent
mkArticulationsStrongAccent :: StrongAccent -> ChxArticulations Source #
Smart constructor for ArticulationsStrongAccent
mkArticulationsStaccato :: EmptyPlacement -> ChxArticulations Source #
Smart constructor for ArticulationsStaccato
mkArticulationsTenuto :: EmptyPlacement -> ChxArticulations Source #
Smart constructor for ArticulationsTenuto
mkArticulationsDetachedLegato :: EmptyPlacement -> ChxArticulations Source #
Smart constructor for ArticulationsDetachedLegato
mkArticulationsStaccatissimo :: EmptyPlacement -> ChxArticulations Source #
Smart constructor for ArticulationsStaccatissimo
mkArticulationsSpiccato :: EmptyPlacement -> ChxArticulations Source #
Smart constructor for ArticulationsSpiccato
mkArticulationsScoop :: EmptyLine -> ChxArticulations Source #
Smart constructor for ArticulationsScoop
mkArticulationsPlop :: EmptyLine -> ChxArticulations Source #
Smart constructor for ArticulationsPlop
mkArticulationsDoit :: EmptyLine -> ChxArticulations Source #
Smart constructor for ArticulationsDoit
mkArticulationsFalloff :: EmptyLine -> ChxArticulations Source #
Smart constructor for ArticulationsFalloff
mkArticulationsBreathMark :: EmptyPlacement -> ChxArticulations Source #
Smart constructor for ArticulationsBreathMark
mkArticulationsCaesura :: EmptyPlacement -> ChxArticulations Source #
Smart constructor for ArticulationsCaesura
mkArticulationsStress :: EmptyPlacement -> ChxArticulations Source #
Smart constructor for ArticulationsStress
mkArticulationsUnstress :: EmptyPlacement -> ChxArticulations Source #
Smart constructor for ArticulationsUnstress
mkArticulationsOtherArticulation :: PlacementText -> ChxArticulations Source #
Smart constructor for ArticulationsOtherArticulation
bend (choice)
Constructors
| BendPreBend | |
Fields
| |
| BendRelease | |
Fields
| |
mkBendPreBend :: Empty -> ChxBend Source #
Smart constructor for BendPreBend
mkBendRelease :: Empty -> ChxBend Source #
Smart constructor for BendRelease
credit (choice)
Constructors
| CreditCreditImage | |
Fields
| |
| CreditCreditWords | |
Fields
| |
mkCreditCreditImage :: Image -> ChxCredit Source #
Smart constructor for CreditCreditImage
mkCreditCreditWords :: FormattedText -> ChxCredit Source #
Smart constructor for CreditCreditWords
data ChxDirectionType Source #
direction-type (choice)
Constructors
mkDirectionTypeRehearsal :: ChxDirectionType Source #
Smart constructor for DirectionTypeRehearsal
mkDirectionTypeSegno :: ChxDirectionType Source #
Smart constructor for DirectionTypeSegno
mkDirectionTypeWords :: ChxDirectionType Source #
Smart constructor for DirectionTypeWords
mkDirectionTypeCoda :: ChxDirectionType Source #
Smart constructor for DirectionTypeCoda
mkDirectionTypeWedge :: Wedge -> ChxDirectionType Source #
Smart constructor for DirectionTypeWedge
mkDirectionTypeDynamics :: ChxDirectionType Source #
Smart constructor for DirectionTypeDynamics
mkDirectionTypeDashes :: Dashes -> ChxDirectionType Source #
Smart constructor for DirectionTypeDashes
mkDirectionTypeBracket :: Bracket -> ChxDirectionType Source #
Smart constructor for DirectionTypeBracket
mkDirectionTypePedal :: Pedal -> ChxDirectionType Source #
Smart constructor for DirectionTypePedal
mkDirectionTypeMetronome :: Metronome -> ChxDirectionType Source #
Smart constructor for DirectionTypeMetronome
mkDirectionTypeOctaveShift :: OctaveShift -> ChxDirectionType Source #
Smart constructor for DirectionTypeOctaveShift
mkDirectionTypeHarpPedals :: HarpPedals -> ChxDirectionType Source #
Smart constructor for DirectionTypeHarpPedals
mkDirectionTypeDamp :: EmptyPrintStyle -> ChxDirectionType Source #
Smart constructor for DirectionTypeDamp
mkDirectionTypeDampAll :: EmptyPrintStyle -> ChxDirectionType Source #
Smart constructor for DirectionTypeDampAll
mkDirectionTypeEyeglasses :: EmptyPrintStyle -> ChxDirectionType Source #
Smart constructor for DirectionTypeEyeglasses
mkDirectionTypeScordatura :: Scordatura -> ChxDirectionType Source #
Smart constructor for DirectionTypeScordatura
mkDirectionTypeImage :: Image -> ChxDirectionType Source #
Smart constructor for DirectionTypeImage
mkDirectionTypeAccordionRegistration :: AccordionRegistration -> ChxDirectionType Source #
Smart constructor for DirectionTypeAccordionRegistration
mkDirectionTypeOtherDirection :: OtherDirection -> ChxDirectionType Source #
Smart constructor for DirectionTypeOtherDirection
data ChxDynamics Source #
dynamics (choice)
Constructors
Instances
mkDynamicsP :: Empty -> ChxDynamics Source #
Smart constructor for DynamicsP
mkDynamicsPp :: Empty -> ChxDynamics Source #
Smart constructor for DynamicsPp
mkDynamicsPpp :: Empty -> ChxDynamics Source #
Smart constructor for DynamicsPpp
mkDynamicsPppp :: Empty -> ChxDynamics Source #
Smart constructor for DynamicsPppp
mkDynamicsPpppp :: Empty -> ChxDynamics Source #
Smart constructor for DynamicsPpppp
mkDynamicsPppppp :: Empty -> ChxDynamics Source #
Smart constructor for DynamicsPppppp
mkDynamicsF :: Empty -> ChxDynamics Source #
Smart constructor for DynamicsF
mkDynamicsFf :: Empty -> ChxDynamics Source #
Smart constructor for DynamicsFf
mkDynamicsFff :: Empty -> ChxDynamics Source #
Smart constructor for DynamicsFff
mkDynamicsFfff :: Empty -> ChxDynamics Source #
Smart constructor for DynamicsFfff
mkDynamicsFffff :: Empty -> ChxDynamics Source #
Smart constructor for DynamicsFffff
mkDynamicsFfffff :: Empty -> ChxDynamics Source #
Smart constructor for DynamicsFfffff
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
mkDynamicsSfpp :: Empty -> ChxDynamics Source #
Smart constructor for DynamicsSfpp
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
mkDynamicsSffz :: Empty -> ChxDynamics Source #
Smart constructor for DynamicsSffz
mkDynamicsFz :: Empty -> ChxDynamics Source #
Smart constructor for DynamicsFz
mkDynamicsOtherDynamics :: String -> ChxDynamics Source #
Smart constructor for DynamicsOtherDynamics
data ChxEncoding Source #
encoding (choice)
Constructors
| EncodingEncodingDate | |
Fields
| |
| EncodingEncoder | |
Fields
| |
| EncodingSoftware | |
Fields
| |
| EncodingEncodingDescription | |
Fields
| |
| EncodingSupports | |
Fields
| |
Instances
mkEncodingEncodingDate :: YyyyMmDd -> ChxEncoding Source #
Smart constructor for EncodingEncodingDate
mkEncodingEncoder :: TypedText -> ChxEncoding Source #
Smart constructor for EncodingEncoder
mkEncodingSoftware :: String -> ChxEncoding Source #
Smart constructor for EncodingSoftware
mkEncodingEncodingDescription :: String -> ChxEncoding Source #
Smart constructor for EncodingEncodingDescription
mkEncodingSupports :: Supports -> ChxEncoding Source #
Smart constructor for EncodingSupports
full-note (choice)
Constructors
| FullNotePitch | |
Fields
| |
| FullNoteUnpitched | |
Fields
| |
| FullNoteRest | |
Fields
| |
mkFullNotePitch :: Pitch -> FullNote Source #
Smart constructor for FullNotePitch
mkFullNoteUnpitched :: DisplayStepOctave -> FullNote Source #
Smart constructor for FullNoteUnpitched
mkFullNoteRest :: DisplayStepOctave -> FullNote Source #
Smart constructor for FullNoteRest
data ChxHarmonic Source #
harmonic (choice)
Constructors
| HarmonicNatural | |
Fields
| |
| HarmonicArtificial | |
Fields
| |
Instances
mkHarmonicNatural :: Empty -> ChxHarmonic Source #
Smart constructor for HarmonicNatural
mkHarmonicArtificial :: Empty -> ChxHarmonic Source #
Smart constructor for HarmonicArtificial
data ChxHarmonic1 Source #
harmonic (choice)
Constructors
| HarmonicBasePitch | |
Fields
| |
| HarmonicTouchingPitch | |
Fields
| |
| HarmonicSoundingPitch | |
Fields
| |
Instances
mkHarmonicBasePitch :: Empty -> ChxHarmonic1 Source #
Smart constructor for HarmonicBasePitch
mkHarmonicTouchingPitch :: Empty -> ChxHarmonic1 Source #
Smart constructor for HarmonicTouchingPitch
mkHarmonicSoundingPitch :: Empty -> ChxHarmonic1 Source #
Smart constructor for HarmonicSoundingPitch
data ChxHarmonyChord Source #
harmony-chord (choice)
Constructors
| HarmonyChordRoot | |
Fields
| |
| HarmonyChordFunction | |
Fields
| |
Instances
mkHarmonyChordRoot :: Root -> ChxHarmonyChord Source #
Smart constructor for HarmonyChordRoot
mkHarmonyChordFunction :: StyleText -> ChxHarmonyChord Source #
Smart constructor for HarmonyChordFunction
key (choice)
Constructors
| KeyTraditionalKey | |
Fields | |
| KeyNonTraditionalKey | |
Fields | |
mkKeyTraditionalKey :: TraditionalKey -> ChxKey Source #
Smart constructor for KeyTraditionalKey
mkKeyNonTraditionalKey :: ChxKey Source #
Smart constructor for KeyNonTraditionalKey
lyric (choice)
Constructors
| LyricSyllabic | |
Fields
| |
| LyricExtend | |
Fields
| |
| LyricLaughing | |
Fields
| |
| LyricHumming | |
Fields
| |
mkLyricSyllabic :: TextElementData -> ChxLyric Source #
Smart constructor for LyricSyllabic
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
mkMeasureStyleMultipleRest :: MultipleRest -> ChxMeasureStyle Source #
Smart constructor for MeasureStyleMultipleRest
mkMeasureStyleMeasureRepeat :: MeasureRepeat -> ChxMeasureStyle Source #
Smart constructor for MeasureStyleMeasureRepeat
mkMeasureStyleBeatRepeat :: BeatRepeat -> ChxMeasureStyle Source #
Smart constructor for MeasureStyleBeatRepeat
mkMeasureStyleSlash :: CmpSlash -> ChxMeasureStyle Source #
Smart constructor for MeasureStyleSlash
data ChxMetronome0 Source #
metronome (choice)
Constructors
| MetronomePerMinute | |
Fields
| |
| MetronomeBeatUnit | |
Fields | |
Instances
mkMetronomePerMinute :: PerMinute -> ChxMetronome0 Source #
Smart constructor for MetronomePerMinute
mkMetronomeBeatUnit :: BeatUnit -> ChxMetronome0 Source #
Smart constructor for MetronomeBeatUnit
data ChxMetronome Source #
metronome (choice)
Constructors
| ChxMetronomeBeatUnit | |
| MetronomeMetronomeNote | |
Fields
| |
Instances
mkChxMetronomeBeatUnit :: BeatUnit -> ChxMetronome0 -> ChxMetronome Source #
Smart constructor for ChxMetronomeBeatUnit
mkMetronomeMetronomeNote :: ChxMetronome Source #
Smart constructor for MetronomeMetronomeNote
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
mkMusicDataNote :: Note -> ChxMusicData Source #
Smart constructor for MusicDataNote
mkMusicDataBackup :: Backup -> ChxMusicData Source #
Smart constructor for MusicDataBackup
mkMusicDataForward :: Forward -> ChxMusicData Source #
Smart constructor for MusicDataForward
mkMusicDataDirection :: Direction -> ChxMusicData Source #
Smart constructor for MusicDataDirection
mkMusicDataAttributes :: Attributes -> ChxMusicData Source #
Smart constructor for MusicDataAttributes
mkMusicDataHarmony :: Harmony -> ChxMusicData Source #
Smart constructor for MusicDataHarmony
mkMusicDataFiguredBass :: FiguredBass -> ChxMusicData Source #
Smart constructor for MusicDataFiguredBass
mkMusicDataPrint :: Print -> ChxMusicData Source #
Smart constructor for MusicDataPrint
mkMusicDataSound :: Sound -> ChxMusicData Source #
Smart constructor for MusicDataSound
mkMusicDataBarline :: Barline -> ChxMusicData Source #
Smart constructor for MusicDataBarline
mkMusicDataGrouping :: Grouping -> ChxMusicData Source #
Smart constructor for MusicDataGrouping
mkMusicDataLink :: Link -> ChxMusicData Source #
Smart constructor for MusicDataLink
mkMusicDataBookmark :: Bookmark -> ChxMusicData Source #
Smart constructor for MusicDataBookmark
data ChxNameDisplay Source #
name-display (choice)
Constructors
| NameDisplayDisplayText | |
Fields
| |
| NameDisplayAccidentalText | |
Fields
| |
Instances
mkNameDisplayDisplayText :: FormattedText -> ChxNameDisplay Source #
Smart constructor for NameDisplayDisplayText
mkNameDisplayAccidentalText :: AccidentalText -> ChxNameDisplay Source #
Smart constructor for NameDisplayAccidentalText
data ChxNotations Source #
notations (choice)
Constructors
Instances
mkNotationsTied :: Tied -> ChxNotations Source #
Smart constructor for NotationsTied
mkNotationsSlur :: Slur -> ChxNotations Source #
Smart constructor for NotationsSlur
mkNotationsTuplet :: Tuplet -> ChxNotations Source #
Smart constructor for NotationsTuplet
mkNotationsGlissando :: Glissando -> ChxNotations Source #
Smart constructor for NotationsGlissando
mkNotationsSlide :: Slide -> ChxNotations Source #
Smart constructor for NotationsSlide
mkNotationsOrnaments :: Ornaments -> ChxNotations Source #
Smart constructor for NotationsOrnaments
mkNotationsTechnical :: Technical -> ChxNotations Source #
Smart constructor for NotationsTechnical
mkNotationsArticulations :: Articulations -> ChxNotations Source #
Smart constructor for NotationsArticulations
mkNotationsDynamics :: Dynamics -> ChxNotations Source #
Smart constructor for NotationsDynamics
mkNotationsFermata :: Fermata -> ChxNotations Source #
Smart constructor for NotationsFermata
mkNotationsArpeggiate :: Arpeggiate -> ChxNotations Source #
Smart constructor for NotationsArpeggiate
mkNotationsNonArpeggiate :: NonArpeggiate -> ChxNotations Source #
Smart constructor for NotationsNonArpeggiate
mkNotationsAccidentalMark :: AccidentalMark -> ChxNotations Source #
Smart constructor for NotationsAccidentalMark
mkNotationsOtherNotation :: OtherNotation -> ChxNotations Source #
Smart constructor for NotationsOtherNotation
note (choice)
Constructors
| NoteGrace | |
Fields
| |
| NoteCue | |
Fields
| |
| NoteFullNote | |
Fields
| |
mkNoteGrace :: Grace -> GrpFullNote -> ChxNote Source #
Smart constructor for NoteGrace
mkNoteFullNote :: GrpFullNote -> Duration -> ChxNote Source #
Smart constructor for NoteFullNote
data ChxOrnaments Source #
ornaments (choice)
Constructors
| OrnamentsTrillMark | |
Fields
| |
| OrnamentsTurn | |
Fields
| |
| OrnamentsDelayedTurn | |
Fields
| |
| OrnamentsInvertedTurn | |
Fields
| |
| OrnamentsShake | |
Fields
| |
| OrnamentsWavyLine | |
Fields
| |
| OrnamentsMordent | |
Fields
| |
| OrnamentsInvertedMordent | |
Fields
| |
| OrnamentsSchleifer | |
Fields
| |
| OrnamentsTremolo | |
Fields
| |
| OrnamentsOtherOrnament | |
Fields
| |
Instances
mkOrnamentsTrillMark :: EmptyTrillSound -> ChxOrnaments Source #
Smart constructor for OrnamentsTrillMark
mkOrnamentsTurn :: EmptyTrillSound -> ChxOrnaments Source #
Smart constructor for OrnamentsTurn
mkOrnamentsDelayedTurn :: EmptyTrillSound -> ChxOrnaments Source #
Smart constructor for OrnamentsDelayedTurn
mkOrnamentsInvertedTurn :: EmptyTrillSound -> ChxOrnaments Source #
Smart constructor for OrnamentsInvertedTurn
mkOrnamentsShake :: EmptyTrillSound -> ChxOrnaments Source #
Smart constructor for OrnamentsShake
mkOrnamentsWavyLine :: WavyLine -> ChxOrnaments Source #
Smart constructor for OrnamentsWavyLine
mkOrnamentsMordent :: Mordent -> ChxOrnaments Source #
Smart constructor for OrnamentsMordent
mkOrnamentsInvertedMordent :: Mordent -> ChxOrnaments Source #
Smart constructor for OrnamentsInvertedMordent
mkOrnamentsSchleifer :: EmptyPlacement -> ChxOrnaments Source #
Smart constructor for OrnamentsSchleifer
mkOrnamentsTremolo :: Tremolo -> ChxOrnaments Source #
Smart constructor for OrnamentsTremolo
mkOrnamentsOtherOrnament :: PlacementText -> ChxOrnaments Source #
Smart constructor for OrnamentsOtherOrnament
data ChxPartList Source #
part-list (choice)
Constructors
| PartListPartGroup | |
Fields | |
| PartListScorePart | |
Fields | |
Instances
mkPartListPartGroup :: GrpPartGroup -> ChxPartList Source #
Smart constructor for PartListPartGroup
mkPartListScorePart :: ScorePart -> ChxPartList Source #
Smart constructor for PartListScorePart
data ChxScoreInstrument Source #
score-instrument (choice)
Constructors
| ScoreInstrumentSolo | |
Fields
| |
| ScoreInstrumentEnsemble | |
Fields
| |
mkScoreInstrumentSolo :: Empty -> ChxScoreInstrument Source #
Smart constructor for ScoreInstrumentSolo
mkScoreInstrumentEnsemble :: PositiveIntegerOrEmpty -> ChxScoreInstrument Source #
Smart constructor for ScoreInstrumentEnsemble
data ChxTechnical Source #
technical (choice)
Constructors
Instances
mkTechnicalUpBow :: EmptyPlacement -> ChxTechnical Source #
Smart constructor for TechnicalUpBow
mkTechnicalDownBow :: EmptyPlacement -> ChxTechnical Source #
Smart constructor for TechnicalDownBow
mkTechnicalHarmonic :: Harmonic -> ChxTechnical Source #
Smart constructor for TechnicalHarmonic
mkTechnicalOpenString :: EmptyPlacement -> ChxTechnical Source #
Smart constructor for TechnicalOpenString
mkTechnicalThumbPosition :: EmptyPlacement -> ChxTechnical Source #
Smart constructor for TechnicalThumbPosition
mkTechnicalFingering :: Fingering -> ChxTechnical Source #
Smart constructor for TechnicalFingering
mkTechnicalPluck :: PlacementText -> ChxTechnical Source #
Smart constructor for TechnicalPluck
mkTechnicalDoubleTongue :: EmptyPlacement -> ChxTechnical Source #
Smart constructor for TechnicalDoubleTongue
mkTechnicalTripleTongue :: EmptyPlacement -> ChxTechnical Source #
Smart constructor for TechnicalTripleTongue
mkTechnicalStopped :: EmptyPlacement -> ChxTechnical Source #
Smart constructor for TechnicalStopped
mkTechnicalSnapPizzicato :: EmptyPlacement -> ChxTechnical Source #
Smart constructor for TechnicalSnapPizzicato
mkTechnicalFret :: Fret -> ChxTechnical Source #
Smart constructor for TechnicalFret
mkTechnicalString :: CmpString -> ChxTechnical Source #
Smart constructor for TechnicalString
mkTechnicalHammerOn :: HammerOnPullOff -> ChxTechnical Source #
Smart constructor for TechnicalHammerOn
mkTechnicalPullOff :: HammerOnPullOff -> ChxTechnical Source #
Smart constructor for TechnicalPullOff
mkTechnicalBend :: Bend -> ChxTechnical Source #
Smart constructor for TechnicalBend
mkTechnicalTap :: PlacementText -> ChxTechnical Source #
Smart constructor for TechnicalTap
mkTechnicalHeel :: HeelToe -> ChxTechnical Source #
Smart constructor for TechnicalHeel
mkTechnicalToe :: HeelToe -> ChxTechnical Source #
Smart constructor for TechnicalToe
mkTechnicalFingernails :: EmptyPlacement -> ChxTechnical Source #
Smart constructor for TechnicalFingernails
mkTechnicalOtherTechnical :: PlacementText -> ChxTechnical Source #
Smart constructor for TechnicalOtherTechnical
time (choice)
Constructors
| TimeTime | |
Fields
| |
| TimeSenzaMisura | |
Fields
| |
mkTimeTime :: ChxTime Source #
Smart constructor for TimeTime
mkTimeSenzaMisura :: Empty -> ChxTime Source #
Smart constructor for TimeSenzaMisura
credit (sequence)
Constructors
| SeqCredit | |
Fields
| |
mkSeqCredit :: FormattedText -> SeqCredit Source #
Smart constructor for SeqCredit
data SeqDisplayStepOctave Source #
display-step-octave (sequence)
Constructors
| SeqDisplayStepOctave | |
Fields
| |
mkSeqDisplayStepOctave :: Step -> Octave -> SeqDisplayStepOctave Source #
Smart constructor for SeqDisplayStepOctave
lyric (sequence)
Constructors
| SeqLyric0 | |
Fields
| |
lyric (sequence)
Constructors
| SeqLyric | |
Fields
| |
mkSeqLyric :: TextElementData -> SeqLyric Source #
Smart constructor for SeqLyric
data SeqMetronome Source #
metronome (sequence)
Constructors
| SeqMetronome | |
Fields
| |
Instances
mkSeqMetronome :: String -> SeqMetronome Source #
Smart constructor for SeqMetronome
data SeqMetronomeTuplet Source #
metronome-tuplet (sequence)
Constructors
| SeqMetronomeTuplet | |
Fields
| |
mkSeqMetronomeTuplet :: NoteTypeValue -> SeqMetronomeTuplet Source #
Smart constructor for SeqMetronomeTuplet
data SeqOrnaments Source #
ornaments (sequence)
Constructors
| SeqOrnaments | |
Fields
| |
Instances
mkSeqOrnaments :: ChxOrnaments -> SeqOrnaments Source #
Smart constructor for SeqOrnaments
data SeqPageLayout Source #
page-layout (sequence)
Constructors
| SeqPageLayout | |
Fields
| |
Instances
mkSeqPageLayout :: Tenths -> Tenths -> SeqPageLayout Source #
Smart constructor for SeqPageLayout
time (sequence)
Constructors
| SeqTime | |
Fields
| |
data SeqTimeModification Source #
time-modification (sequence)
Constructors
| SeqTimeModification | |
Fields
| |
mkSeqTimeModification :: NoteTypeValue -> SeqTimeModification Source #
Smart constructor for SeqTimeModification
data AllMargins Source #
all-margins (group)
Constructors
| AllMargins | |
Fields
| |
Instances
mkAllMargins :: LeftRightMargins -> Tenths -> Tenths -> AllMargins Source #
Smart constructor for AllMargins
beat-unit (group)
Constructors
| BeatUnit | |
Fields
| |
mkBeatUnit :: NoteTypeValue -> BeatUnit Source #
Smart constructor for BeatUnit
duration (group)
Constructors
| Duration | |
Fields
| |
mkDuration :: PositiveDivisions -> Duration Source #
Smart constructor for Duration
editorial (group)
Constructors
| Editorial | |
Fields | |
mkEditorial :: Editorial Source #
Smart constructor for Editorial
mkEditorialVoice :: EditorialVoice Source #
Smart constructor for EditorialVoice
data EditorialVoiceDirection Source #
editorial-voice-direction (group)
Constructors
| EditorialVoiceDirection | |
mkEditorialVoiceDirection :: EditorialVoiceDirection Source #
Smart constructor for EditorialVoiceDirection
footnote (group)
Constructors
| Footnote | |
Fields
| |
mkFootnote :: FormattedText -> Footnote Source #
Smart constructor for Footnote
data GrpFullNote Source #
full-note (group)
Constructors
| GrpFullNote | |
Fields
| |
Instances
mkGrpFullNote :: FullNote -> GrpFullNote Source #
Smart constructor for GrpFullNote
data HarmonyChord Source #
harmony-chord (group)
Constructors
| HarmonyChord | |
Fields
| |
Instances
mkHarmonyChord :: ChxHarmonyChord -> Kind -> HarmonyChord Source #
Smart constructor for HarmonyChord
layout (group)
Constructors
| Layout | |
Fields
| |
data LeftRightMargins Source #
left-right-margins (group)
Constructors
| LeftRightMargins | |
Fields
| |
mkLeftRightMargins :: Tenths -> Tenths -> LeftRightMargins Source #
Smart constructor for LeftRightMargins
level (group)
Constructors
| GrpLevel | |
Fields
| |
music-data (group)
Constructors
| MusicData | |
Fields | |
mkMusicData :: MusicData Source #
Smart constructor for MusicData
data NonTraditionalKey Source #
non-traditional-key (group)
Constructors
| NonTraditionalKey | |
Fields
| |
mkNonTraditionalKey :: Step -> Semitones -> NonTraditionalKey Source #
Smart constructor for NonTraditionalKey
data GrpPartGroup Source #
part-group (group)
Constructors
| GrpPartGroup | |
Fields
| |
Instances
mkGrpPartGroup :: PartGroup -> GrpPartGroup Source #
Smart constructor for GrpPartGroup
data ScoreHeader Source #
score-header (group)
Constructors
| ScoreHeader | |
Fields
| |
Instances
mkScoreHeader :: PartList -> ScoreHeader Source #
Smart constructor for ScoreHeader
score-part (group)
Constructors
| ScorePart | |
Fields
| |
mkScorePart :: CmpScorePart -> ScorePart Source #
Smart constructor for ScorePart
slash (group)
Constructors
| Slash | |
Fields
| |
parseSlash :: XParse Slash Source #
staff (group)
Constructors
| Staff | |
Fields
| |
parseStaff :: XParse Staff Source #
data TraditionalKey Source #
traditional-key (group)
Constructors
| TraditionalKey | |
Fields
| |
Instances
mkTraditionalKey :: Fifths -> TraditionalKey Source #
Smart constructor for TraditionalKey
tuning (group)
Constructors
| Tuning | |
Fields
| |
voice (group)
Constructors
| Voice | |
Fields
| |
parseVoice :: XParse Voice Source #