|  | @@ -1,7 +1,10 @@
 | 
												
													
														
															|  |  {-# LANGUAGE TemplateHaskell #-}
 |  |  {-# LANGUAGE TemplateHaskell #-}
 | 
												
													
														
															|  | 
 |  | +{-# LANGUAGE OverloadedLists #-}
 | 
												
													
														
															|  | 
 |  | +{-# LANGUAGE GADTs #-}
 | 
												
													
														
															|  |  
 |  |  
 | 
												
													
														
															|  |  module Hypsibius.Data where
 |  |  module Hypsibius.Data where
 | 
												
													
														
															|  |  
 |  |  
 | 
												
													
														
															|  | 
 |  | +import           Data.Adnot
 | 
												
													
														
															|  |  import           Data.Sequence (Seq)
 |  |  import           Data.Sequence (Seq)
 | 
												
													
														
															|  |  import           Data.Text (Text)
 |  |  import           Data.Text (Text)
 | 
												
													
														
															|  |  import           Data.Word (Word8)
 |  |  import           Data.Word (Word8)
 | 
												
											
												
													
														
															|  | @@ -39,8 +42,20 @@ $(makeLenses ''InstrRef)
 | 
												
													
														
															|  |  data Note = Note
 |  |  data Note = Note
 | 
												
													
														
															|  |    { _noteCents      :: Double
 |  |    { _noteCents      :: Double
 | 
												
													
														
															|  |    , _noteAppearance :: Text
 |  |    , _noteAppearance :: Text
 | 
												
													
														
															|  | 
 |  | +  , _noteColor      :: Maybe Text
 | 
												
													
														
															|  |    } deriving (Eq, Show)
 |  |    } deriving (Eq, Show)
 | 
												
													
														
															|  |  
 |  |  
 | 
												
													
														
															|  | 
 |  | +instance FromAdnot Note where
 | 
												
													
														
															|  | 
 |  | +  parseAdnot = withSum "Note" go
 | 
												
													
														
															|  | 
 |  | +    where go "note" [name, cents] =
 | 
												
													
														
															|  | 
 |  | +            Note <$> parseAdnot cents <*> parseAdnot name <*> pure Nothing
 | 
												
													
														
															|  | 
 |  | +          go "note" [name, cents, color] =
 | 
												
													
														
															|  | 
 |  | +            Note <$> parseAdnot cents
 | 
												
													
														
															|  | 
 |  | +                 <*> parseAdnot name
 | 
												
													
														
															|  | 
 |  | +                 <*> (Just <$> parseAdnot color)
 | 
												
													
														
															|  | 
 |  | +          go "note" _ = fail "Unknown argument structure"
 | 
												
													
														
															|  | 
 |  | +          go c _ = fail ("Expected note, got " ++ show c)
 | 
												
													
														
															|  | 
 |  | +
 | 
												
													
														
															|  |  $(makeLenses ''Note)
 |  |  $(makeLenses ''Note)
 | 
												
													
														
															|  |  
 |  |  
 | 
												
													
														
															|  |  -- | We'll maintain a list of notes and refer to them using indices. For type
 |  |  -- | We'll maintain a list of notes and refer to them using indices. For type
 | 
												
											
												
													
														
															|  | @@ -58,6 +73,12 @@ data Scale = Scale
 | 
												
													
														
															|  |    , _scaleNotes      :: Seq Note
 |  |    , _scaleNotes      :: Seq Note
 | 
												
													
														
															|  |    } deriving (Eq, Show)
 |  |    } deriving (Eq, Show)
 | 
												
													
														
															|  |  
 |  |  
 | 
												
													
														
															|  | 
 |  | +instance FromAdnot Scale where
 | 
												
													
														
															|  | 
 |  | +  parseAdnot = withProduct "Scale" $ \o ->
 | 
												
													
														
															|  | 
 |  | +    Scale <$> o .: "name"
 | 
												
													
														
															|  | 
 |  | +          <*> o .: "size"
 | 
												
													
														
															|  | 
 |  | +          <*> o .: "notes"
 | 
												
													
														
															|  | 
 |  | +
 | 
												
													
														
															|  |  $(makeLenses ''Scale)
 |  |  $(makeLenses ''Scale)
 | 
												
													
														
															|  |  
 |  |  
 | 
												
													
														
															|  |  -- | An 'Event' is a typical event associated with a song.
 |  |  -- | An 'Event' is a typical event associated with a song.
 | 
												
											
												
													
														
															|  | @@ -91,7 +112,6 @@ data Track = Track
 | 
												
													
														
															|  |    } deriving (Eq, Show)
 |  |    } deriving (Eq, Show)
 | 
												
													
														
															|  |  
 |  |  
 | 
												
													
														
															|  |  
 |  |  
 | 
												
													
														
															|  | -
 |  | 
 | 
												
													
														
															|  |  data Song = Song
 |  |  data Song = Song
 | 
												
													
														
															|  |    { _songScale  :: Scale
 |  |    { _songScale  :: Scale
 | 
												
													
														
															|  |    , _songTracks :: Seq Track
 |  |    , _songTracks :: Seq Track
 |