module FRP.Rhine.Clock.Step where
import GHC.TypeLits
import FRP.Rhine
data Step (n :: Nat) where
Step :: KnownNat n => Step n
stepsize :: Step n -> Integer
stepsize step@Step = natVal step
instance Monad m => Clock m (Step n) where
type TimeDomainOf (Step n) = Integer
type Tag (Step n) = ()
startClock cl = return
( count >>> arr (* stepsize cl)
&&& arr (const ())
, 0
)
scheduleStep
:: Monad m
=> Schedule m (Step n1) (Step n2)
scheduleStep = Schedule f where
f cl1 cl2 = return (msf, 0)
where
n1 = stepsize cl1
n2 = stepsize cl2
msf = concatS $ proc _ -> do
k <- arr (+1) <<< count -< ()
returnA -< [ (k, Left ()) | k `mod` n1 == 0 ]
++ [ (k, Right ()) | k `mod` n2 == 0 ]
concatS :: Monad m => MSF m () [b] -> MSF m () b
concatS msf = MSF $ \_ -> tick msf []
where
tick msf (b:bs) = return (b, MSF $ \_ -> tick msf bs)
tick msf [] = do
(bs, msf') <- unMSF msf ()
tick msf' bs