module Music.LilyPond.Light.Model where import Data.Monoid import Music.Theory.Pitch import Music.Theory.Duration import Music.Theory.Key data Version = Version String deriving (Eq, Show) data Units = MM | CM deriving (Eq, Show) data Length = Length Double Units deriving (Eq, Show) data Paper = Paper { binding_offset :: Length , bottom_margin :: Length , indent :: Length , inner_margin :: Length , left_margin :: Length , outer_margin :: Length , paper_width :: Length , paper_height :: Length , ragged_last :: Bool , ragged_last_bottom :: Bool , right_margin :: Length , systems_per_page :: Maybe Integer , top_margin :: Length , two_sided :: Bool } deriving (Eq, Show) data Header = Header { dedication :: String , title :: String , subtitle :: String , composer :: String , tagline :: String } deriving (Eq, Show) data Clef_T = Bass | Tenor | Alto | Treble | Percussion deriving (Eq, Ord, Show) data Articulation_T = Accent | Arpeggio | ArpeggioDown | ArpeggioNeutral | ArpeggioUp | DownBow | Fermata | Flageolet | Glissando | Harmonic | LaissezVibrer | Marcato | Open | Portato | Staccato | StemTremolo Integer | Stopped | Tenuto | Trill | UpBow deriving (Eq, Show) data Dynamic_T = PPPP | PPP | Pianissimo | Piano | MezzoPiano | MezzoForte | Forte | Fortissimo | FFF | FFFF | FP | SFZ | Espressivo | Begin_Crescendo | Begin_Decrescendo | End_Dynamic deriving (Eq, Show) data Phrasing_T = Begin_Slur | End_Slur | Begin_PhrasingSlur | End_PhrasingSlur | Begin_Beam | End_Beam | SustainOn | SustainOff deriving (Eq, Show) data Annotation = Articulation Articulation_T | Dynamic Dynamic_T | Phrasing Phrasing_T | Begin_Tie | Above | Below | Text String | ReminderAccidental | CautionaryAccidental | CompositeAnnotation [Annotation] deriving (Eq, Show) data Bar_T = NormalBarline | DoubleBarline | LeftRepeatBarline | RightRepeatBarline | FinalBarline deriving (Eq, Show) data Command_T = AutoBeamOff | Bar Bar_T | BarlineCheck | BarNumberCheck Integer | Break | Change String | DynamicDown | DynamicNeutral | DynamicUp | NoBreak | NoPageBreak | Octavation Integer | PageBreak | Partial Duration | StemDown | StemNeutral | StemUp | TupletDown | TupletNeutral | TupletUp | User String | VoiceOne | VoiceTwo | VoiceThree | VoiceFour deriving (Eq, Show) type TimeSignature = (Integer, Integer) type Tuplet_T = (Integer, Integer) data Tuplet_Mode = Normal_Tuplet | Scale_Durations deriving (Eq, Show) data Music = Note { note_pitch :: Pitch , note_duration :: (Maybe Duration) , note_annotations :: [Annotation] } | Chord { chord_notes :: [Music] , chord_duration :: Duration , chord_annotations :: [Annotation] } | Tremolo (Music,Music) Integer | Rest Duration [Annotation] | MMRest Integer TimeSignature [Annotation] | Skip Duration | Repeat Integer Music | Tuplet Tuplet_Mode Tuplet_T Music | Grace Music | AfterGrace Music Music | Join [Music] | Clef Clef_T Int | Time TimeSignature | Key Note_T (Maybe Alteration_T) Mode_T | Tempo Duration Integer | Command Command_T | Polyphony Music Music | Empty deriving (Eq, Show) instance Monoid Music where mempty = Empty mappend x y = Join [x,y] mconcat xs = Join xs type Staff_Name = (String,String) type Staff_ID = String data Staff_T = Normal_Staff | Rhythmic_Staff deriving (Eq, Show) data Part = Part (Maybe String) [Music] | MultipleParts [[Music]] deriving (Eq, Show) data Staff_Set_T = ChoirStaff | GrandStaff | PianoStaff | StaffGroup | StaffGroup_SquareBracket deriving (Eq, Show) type Staff_Scalar = Int data Staff_Settings = Staff_Settings Staff_T Staff_ID Staff_Scalar deriving (Eq, Show) data Staff = Staff Staff_Settings Staff_Name Part | Staff_Set Staff_Set_T Staff_Name [Staff] deriving (Eq, Show) data Score_Settings = Score_Settings { independent_time_signatures :: Bool } deriving (Eq, Show) data Score = Score Score_Settings [Staff] deriving (Eq, Show) data Work = Work { work_version :: Version , work_paper :: Paper , work_header :: Header , work_score :: Score } deriving (Eq, Show)