{-# LANGUAGE Arrows #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module FRP.Rhine.Clock.FixedStep where
import Data.Maybe (fromMaybe)
import GHC.TypeLits
import Data.Vector.Sized (Vector, fromList)
import Data.MonadicStreamFunction.Async (concatS)
import FRP.Rhine.Clock
import FRP.Rhine.ResamplingBuffer
import FRP.Rhine.ResamplingBuffer.Collect
import FRP.Rhine.ResamplingBuffer.Util
import FRP.Rhine.Schedule
data FixedStep (n :: Nat) where
FixedStep :: KnownNat n => FixedStep n
stepsize :: FixedStep n -> Integer
stepsize fixedStep@FixedStep = natVal fixedStep
instance Monad m => Clock m (FixedStep n) where
type Time (FixedStep n) = Integer
type Tag (FixedStep n) = ()
initClock cl = return
( count >>> arr (* stepsize cl)
&&& arr (const ())
, 0
)
type Count = FixedStep 1
scheduleFixedStep
:: Monad m
=> Schedule m (FixedStep n1) (FixedStep n2)
scheduleFixedStep = 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 ]
downsampleFixedStep
:: (KnownNat n, Monad m)
=> ResamplingBuffer m (FixedStep k) (FixedStep (n * k)) a (Vector n a)
downsampleFixedStep = collect >>-^ arr (fromList >>> assumeSize)
where
assumeSize = fromMaybe $ error $ unwords
[ "You are using an incorrectly implemented schedule"
, "for two FixedStep clocks."
, "Use a correct schedule like downsampleFixedStep."
]