{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
module FRP.Rhine.Reactimation.Combinators where
import FRP.Rhine.Clock
import FRP.Rhine.ClSF.Core
import FRP.Rhine.ResamplingBuffer
import FRP.Rhine.Schedule
import FRP.Rhine.SN
import FRP.Rhine.SN.Combinators
import FRP.Rhine.Type
infix 5 @@
(@@) :: ( cl ~ In cl
, cl ~ Out cl )
=> ClSF m cl a b -> cl -> Rhine m cl a b
(@@) = Rhine . Synchronous
data ResamplingPoint m cla clb a b = ResamplingPoint
(ResamplingBuffer m (Out cla) (In clb) a b)
(Schedule m cla clb)
infix 8 -@-
(-@-) :: ResamplingBuffer m (Out cl1) (In cl2) a b
-> Schedule m cl1 cl2
-> ResamplingPoint m cl1 cl2 a b
(-@-) = ResamplingPoint
infix 2 >--
data RhineAndResamplingPoint m cl1 cl2 a c = forall b.
RhineAndResamplingPoint (Rhine m cl1 a b) (ResamplingPoint m cl1 cl2 b c)
(>--) :: Rhine m cl1 a b
-> ResamplingPoint m cl1 cl2 b c
-> RhineAndResamplingPoint m cl1 cl2 a c
(>--) = RhineAndResamplingPoint
infixr 1 -->
(-->) :: ( Clock m cl1
, Clock m cl2
, Time cl1 ~ Time cl2
, Time (Out cl1) ~ Time cl1
, Time (In cl2) ~ Time cl2
, Clock m (Out cl1)
, Clock m (In cl2)
)
=> RhineAndResamplingPoint m cl1 cl2 a b
-> Rhine m cl2 b c
-> Rhine m (SequentialClock m cl1 cl2) a c
RhineAndResamplingPoint (Rhine sn1 cl1) (ResamplingPoint rb cc) --> (Rhine sn2 cl2)
= Rhine (Sequential sn1 rb sn2) (SequentialClock cl1 cl2 cc)
data RhineParallelAndSchedule m clL clR a b
= RhineParallelAndSchedule (Rhine m clL a b) (Schedule m clL clR)
infix 4 ++@
(++@)
:: Rhine m clL a b
-> Schedule m clL clR
-> RhineParallelAndSchedule m clL clR a b
(++@) = RhineParallelAndSchedule
infix 3 @++
(@++)
:: ( Monad m, Clock m clL, Clock m clR
, Time clL ~ Time (Out clL), Time clR ~ Time (Out clR)
, Time clL ~ Time (In clL), Time clR ~ Time (In clR)
, Time clL ~ Time clR
)
=> RhineParallelAndSchedule m clL clR a b
-> Rhine m clR a c
-> Rhine m (ParallelClock m clL clR) a (Either b c)
RhineParallelAndSchedule (Rhine sn1 clL) schedule @++ (Rhine sn2 clR)
= Rhine (sn1 ++++ sn2) (ParallelClock clL clR schedule)
infix 4 ||@
(||@)
:: Rhine m clL a b
-> Schedule m clL clR
-> RhineParallelAndSchedule m clL clR a b
(||@) = RhineParallelAndSchedule
infix 3 @||
(@||)
:: ( Monad m, Clock m clL, Clock m clR
, Time clL ~ Time (Out clL), Time clR ~ Time (Out clR)
, Time clL ~ Time (In clL), Time clR ~ Time (In clR)
, Time clL ~ Time clR
)
=> RhineParallelAndSchedule m clL clR a b
-> Rhine m clR a b
-> Rhine m (ParallelClock m clL clR) a b
RhineParallelAndSchedule (Rhine sn1 clL) schedule @|| (Rhine sn2 clR)
= Rhine (sn1 |||| sn2) (ParallelClock clL clR schedule)