Skip to content

Commit

Permalink
play
Browse files Browse the repository at this point in the history
  • Loading branch information
ejconlon committed Feb 20, 2024
1 parent 35800ed commit 9d17357
Show file tree
Hide file tree
Showing 3 changed files with 10 additions and 10 deletions.
2 changes: 1 addition & 1 deletion minipat-live/minipat-live.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -30,8 +30,8 @@ library
Minipat.Live.Core
Minipat.Live.Logger
Minipat.Live.Notes
Minipat.Live.Osc
Minipat.Live.Params
Minipat.Live.Play
Minipat.Live.Resources
other-modules:
Paths_minipat_live
Expand Down
4 changes: 2 additions & 2 deletions minipat-live/src/Minipat/Live/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@ import Data.Text qualified as T
import Minipat.EStream (EStream (..))
import Minipat.Live.Attrs (Attrs, Squishy (..), attrsDefault)
import Minipat.Live.Logger (LogAction, logDebug, logError, logInfo, logWarn, nullLogger)
import Minipat.Live.Osc (PlayEnv (..), PlayErr, convertTape)
import Minipat.Live.Play (PlayEnv (..), PlayErr, playTape)
import Minipat.Live.Resources (RelVar, Timed (..), acquireAwait, acquireLoop, relVarAcquire, relVarDispose, relVarUse)
import Minipat.Print (prettyPrint, prettyPrintAll, prettyShow, prettyShowAll)
import Minipat.Stream (Stream, streamRun, tapeToList)
Expand Down Expand Up @@ -465,7 +465,7 @@ genEventsSTM dom now = do
let tape = streamRun stream arc
origin = addTime now ahead
penv = PlayEnv origin start cps
mpevs = convertTape penv tape
mpevs = playTape penv tape
pure (penv, mpevs)

doGen :: LogAction -> Domain -> PosixTime -> IO ()
Expand Down
Original file line number Diff line number Diff line change
@@ -1,10 +1,10 @@
{-# LANGUAGE OverloadedStrings #-}

module Minipat.Live.Osc
module Minipat.Live.Play
( PlayErr (..)
, PlayEnv (..)
, convertEvent
, convertTape
, playEvent
, playTape
)
where

Expand Down Expand Up @@ -92,8 +92,8 @@ timeDeltaToMicros td =
let (_, ns) = timeDeltaToNanos td
in fromIntegral ns / 1000

convertEvent :: (Squishy Attrs a) => PlayEnv -> Ev a -> M (Maybe (Timed Attrs))
convertEvent (PlayEnv startTime startCyc cps) (Ev sp dat) =
playEvent :: (Squishy Attrs a) => PlayEnv -> Ev a -> M (Maybe (Timed Attrs))
playEvent (PlayEnv startTime startCyc cps) (Ev sp dat) =
case spanCycle sp of
Nothing ->
-- Only emit start events
Expand All @@ -115,5 +115,5 @@ traverseMaybe f = go Empty
Empty -> pure acc
a :<| as' -> f a >>= maybe (go acc as') (\b -> go (acc :|> b) as')

convertTape :: (Squishy Attrs a) => PlayEnv -> Tape a -> M (Seq (Timed Attrs))
convertTape penv = traverseMaybe (convertEvent penv) . Seq.fromList . tapeToList
playTape :: (Squishy Attrs a) => PlayEnv -> Tape a -> M (Seq (Timed Attrs))
playTape penv = traverseMaybe (playEvent penv) . Seq.fromList . tapeToList

0 comments on commit 9d17357

Please sign in to comment.