Browse Source

Some refining of data types

Getty Ritter 7 years ago
parent
commit
3b51335d37
2 changed files with 38 additions and 6 deletions
  1. 1 0
      hypsibius.cabal
  2. 37 6
      src/Hypsibius/Data.hs

+ 1 - 0
hypsibius.cabal

@@ -26,6 +26,7 @@ executable hypsibius
   build-depends:       base >=4.7 && <4.9
                      , brick
                      , lens-family-core
+                     , lens-family-th
                      , text
                      , containers
                      , vty

+ 37 - 6
src/Hypsibius/Data.hs

@@ -1,35 +1,49 @@
+{-# LANGUAGE TemplateHaskell #-}
+
 module Hypsibius.Data where
 
 import           Data.Sequence (Seq)
 import qualified Data.Sequence as S
 import           Data.Text (Text)
+import           Data.Word (Word8)
+import           Lens.Family2.TH
+
+data Oscillator
+  = OscSine
+  | OscSquare
+    deriving (Eq, Show)
 
 data Instrument = Instrument
   { _instrSource :: Oscillator
   } deriving (Eq, Show)
 
-newtype InstrRef = InstrRef { fromInstrRef :: Int }
+$(makeLenses ''Instrument)
+
+newtype InstrRef = InstrRef { _fromInstrRef :: Int }
   deriving (Eq, Show)
 
-data Oscillator
-  = OscSine
-  | OscSquare
-    deriving (Eq, Show)
+$(makeLenses ''InstrRef)
 
 data Note = Note
   { _noteCents      :: Double
   , _noteAppearance :: Text
   } deriving (Eq, Show)
 
-newtype NoteRef = NoteRef { fromNoteRef :: Int }
+$(makeLenses ''Note)
+
+newtype NoteRef = NoteRef { _fromNoteRef :: Int }
   deriving (Eq, Show)
 
+$(makeLenses ''NoteRef)
+
 data Scale = Scale
   { _scaleName       :: Text
   , _scaleTotalCents :: Double
   , _scaleNotes      :: Seq Note
   } deriving (Eq, Show)
 
+$(makeLenses ''Scale)
+
 data Event = Event
   deriving (Eq, Show)
 
@@ -37,7 +51,24 @@ data Track = Track
   {
   } deriving (Eq, Show)
 
+data Beats
+  = BeatsSimple Word8
+  | BeatsAdditive [Word8]
+  | BeatsFractional Word8 Word8
+    deriving (Eq, Show)
+
+$(makeTraversals ''Beats)
+
+data Signature = Signature
+  { _sigPerBar   :: Beats
+  , _sigBeatUnit :: Word8
+  } deriving (Eq, Show)
+
+$(makeLenses ''Signature)
+
 data Song = Song
   { _songScale  :: Scale
   , _songTracks :: Seq Track
   } deriving (Eq, Show)
+
+$(makeLenses ''Song)