Skip to content

Commit

Permalink
split
Browse files Browse the repository at this point in the history
  • Loading branch information
ejconlon committed Feb 19, 2024
1 parent a0f79ba commit 41e76f8
Show file tree
Hide file tree
Showing 8 changed files with 384 additions and 301 deletions.
1 change: 1 addition & 0 deletions minipat-dirt/minipat-dirt.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@ library
Minipat.Dirt.Boot
Minipat.Dirt.Combinators
Minipat.Dirt.Core
Minipat.Dirt.DirtCore
Minipat.Dirt.Logger
Minipat.Dirt.Notes
Minipat.Dirt.Osc
Expand Down
6 changes: 6 additions & 0 deletions minipat-dirt/src/Minipat/Dirt/Attrs.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@ module Minipat.Dirt.Attrs
, attrsFromList
, attrsLookup
, attrsInsert
, attrsDefault
, attrsDelete
, attrsToList
, IsAttrs (..)
Expand Down Expand Up @@ -90,6 +91,11 @@ attrsLookup k (Attrs m) = Map.lookup k m
attrsInsert :: Text -> Datum -> Attrs -> Attrs
attrsInsert k v (Attrs m) = Attrs (Map.insert k v m)

attrsDefault :: Text -> Datum -> Attrs -> Attrs
attrsDefault k v a@(Attrs m) = case Map.lookup k m of
Nothing -> Attrs (Map.insert k v m)
Just _ -> a

attrsDelete :: Text -> Attrs -> Attrs
attrsDelete k (Attrs m) = Attrs (Map.delete k m)

Expand Down
9 changes: 5 additions & 4 deletions minipat-dirt/src/Minipat/Dirt/Boot.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,20 +5,21 @@ module Minipat.Dirt.Boot where

import Minipat.Dirt.Attrs (Attrs, IsAttrs (..))
import Minipat.Dirt.Core qualified as C
import Minipat.Dirt.DirtCore qualified as D
import Minipat.Dirt.Logger qualified as L
import Minipat.EStream (EStream)
import Minipat.Stream (Stream)
import Nanotime (TimeDelta)
import Prettyprinter (Pretty)

class Minipat where
minipat :: C.St
minipat :: D.DirtSt

initialize :: IO C.St
initialize :: IO D.DirtSt
initialize = do
logger <- L.newLogger
L.logInfo logger "Initializing"
C.initSt logger C.defaultEnv
C.initSt logger D.dirtImpl (C.defaultEnv D.defaultDirtEnv)

dispose :: (Minipat) => IO ()
dispose = C.disposeSt minipat
Expand Down Expand Up @@ -81,7 +82,7 @@ stop :: (Minipat) => IO ()
stop = setPlaying False

handshake :: (Minipat) => IO ()
handshake = C.handshake minipat
handshake = D.handshake minipat

checkTasks :: (Minipat) => IO ()
checkTasks = C.checkTasks minipat
Expand Down
Loading

0 comments on commit 41e76f8

Please sign in to comment.