module Music.LilyPond.Light.Model where

import Data.Monoid
import qualified Music.Theory.Clef as C {- hmt -}
import Music.Theory.Pitch
import Music.Theory.Pitch.Note
import Music.Theory.Duration
import Music.Theory.Dynamic_Mark
import Music.Theory.Key
import Music.Theory.Time_Signature

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_right :: Bool
                   , ragged_last :: Bool
                   , ragged_bottom :: Bool
                   , ragged_last_bottom :: Bool
                   , right_margin :: Length
                   , top_margin :: Length
                   , two_sided :: Bool
                   , print_page_number :: Bool
                   , min_systems_per_page :: Maybe Integer
                   , max_systems_per_page :: Maybe Integer
                   , systems_per_page :: Maybe Integer
                   , systems_count :: Maybe Integer
                   , page_count :: Maybe Integer
                   , system_separator_markup :: Maybe String
                   }
             deriving (Eq, Show)

data Header = Header { dedication :: String
                     , title :: String
                     , subtitle :: String
                     , subsubtitle :: String
                     , instrument :: String
                     , composer :: String
                     , opus :: String
                     , poet :: String
                     , tagline :: String }
              deriving (Eq, 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 = Dynamic_Mark Dynamic_Mark_T
               | Hairpin Hairpin_T
               | Espressivo
                 deriving (Eq, Show)

data Phrasing_T = Begin_Slur
                | End_Slur
                | Begin_PhrasingSlur
                | End_PhrasingSlur
                | Begin_Beam
                | End_Beam
                | SustainOn
                | SustainOff
                  deriving (Eq, Show)

data Text_T = Text_Symbol | Text_Plain | Text_Markup
              deriving (Eq, Show)

data Annotation = Articulation Articulation_T
                | Dynamic Dynamic_T
                | Phrasing Phrasing_T
                | Begin_Tie
                | Place_Above | Place_Default | Place_Below
                | Text_Mark | Text Text_T String
                | ReminderAccidental | CautionaryAccidental
                | CompositeAnnotation [Annotation]
                  deriving (Eq, Show)

data Bar_T = NormalBarline
           | DoubleBarline
           | LeftRepeatBarline
           | RightRepeatBarline
           | FinalBarline
           | DottedBarline
           | DashedBarline
           | TickBarline
             deriving (Eq, Show)

data Command_T = AutoBeamOff
               | Bar Bar_T
               | BarlineCheck
               | BarNumberCheck Integer
               | Break -- Line 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 Tuplet_T = (Integer, Integer)

data Tuplet_Mode = Normal_Tuplet
                 | Scale_Durations
                   deriving (Eq, Show)

-- | 'Music' element category enumeration.
data Music_C = Note_C
             | Chord_C
             | Tremolo_C
             | Rest_C | MMRest_C | Skip_C
             | Repeat_C
             | Tuplet_C
             | Grace_C | AfterGrace_C
             | Join_C
             | Clef_C
             | Time_C
             | Key_C
             | Tempo_C
             | Command_C
             | Polyphony_C
             | Empty_C
               deriving (Eq,Enum,Bounded)

-- | Categorise 'Music' element.
music_c :: Music -> Music_C
music_c m =
    case m of
      Note {} -> Note_C
      Chord {} -> Chord_C
      Tremolo _ _ -> Tremolo_C
      Rest _ _ _ -> Rest_C
      MMRest {} -> MMRest_C
      Skip _ _ -> Skip_C
      Repeat _ _ -> Repeat_C
      Tuplet {} -> Tuplet_C
      Grace _ -> Grace_C
      AfterGrace _ _ -> AfterGrace_C
      Join _ -> Join_C
      Clef _ -> Clef_C
      Time _ -> Time_C
      Key {} -> Key_C
      Tempo _ _ _ -> Tempo_C
      Command _ _ -> Command_C
      Polyphony _ _ -> Polyphony_C
      Empty -> Empty_C

-- | Type of rest.  Perhaps MMRest should be given here also.
data Rest_T = Normal_Rest | Spacer_Rest 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 (Either Music (Music,Music)) Integer
           | Rest Rest_T Duration [Annotation]
           | MMRest Integer Time_Signature [Annotation]
           | Skip Duration [Annotation]
           | Repeat Integer Music
           | Tuplet Tuplet_Mode Tuplet_T Music
           | Grace Music
           | AfterGrace Music Music
           | Join [Music]
           | Clef (C.Clef Int)
           | Time Time_Signature
           | Key Note_T (Maybe Alteration_T) Mode_T
           | Tempo (Maybe String) Duration Rational
           | Command Command_T [Annotation]
           | Polyphony Music Music
           | Empty
             deriving (Eq, Show)

instance Monoid Music where
    mempty = Empty
    mappend x y = Join [x,y]
    mconcat = Join

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
                   ,hide_time_signatures :: Bool
                   ,remove_empty_staves :: Bool
                   ,remove_empty_staves_first_system :: 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)

data Fragment = Fragment { fragment_version :: Version
                         , fragment_paper :: Paper
                         , fragment_staff :: Staff }
                deriving (Eq, Show)

data Format = PDF | PS | PNG
              deriving (Enum,Eq,Show)


-- * Default values

default_version :: Version
default_version = Version "2.14.2"

default_header :: Header
default_header =
    Header {dedication = ""
           ,title = ""
           ,subtitle = ""
           ,subsubtitle = ""
           ,instrument = ""
           ,composer = ""
           ,opus = ""
           ,poet = ""
           ,tagline = ""}

default_score_settings :: Score_Settings
default_score_settings =
    Score_Settings {independent_time_signatures = False
                   ,hide_time_signatures = False
                   ,remove_empty_staves = False
                   ,remove_empty_staves_first_system = False}

-- * Translation

ly_bool :: Bool -> String
ly_bool c = if c then "##t" else "##f"