{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
module FRP.Rhine.Schedule.Trans where
import Data.MonadicStreamFunction.InternalCore
import Control.Monad.Schedule
import FRP.Rhine.Clock
import FRP.Rhine.Schedule
schedule
:: ( Monad m
, Clock (ScheduleT (Diff (Time cl1)) m) cl1
, Clock (ScheduleT (Diff (Time cl1)) m) cl2
, Time cl1 ~ Time cl2
, Ord (Diff (Time cl1))
, Num (Diff (Time cl1))
)
=> Schedule (ScheduleT (Diff (Time cl1)) m) cl1 cl2
schedule = Schedule {..}
where
initSchedule cl1 cl2 = do
(runningClock1, initTime) <- initClock cl1
(runningClock2, _) <- initClock cl2
return
( runningSchedule cl1 cl2 runningClock1 runningClock2
, initTime
)
runningSchedule
:: ( Monad m
, Clock (ScheduleT (Diff (Time cl1)) m) cl1
, Clock (ScheduleT (Diff (Time cl2)) m) cl2
, Time cl1 ~ Time cl2
, Ord (Diff (Time cl1))
, Num (Diff (Time cl1))
)
=> cl1 -> cl2
-> MSF (ScheduleT (Diff (Time cl1)) m) () (Time cl1, Tag cl1)
-> MSF (ScheduleT (Diff (Time cl1)) m) () (Time cl2, Tag cl2)
-> MSF (ScheduleT (Diff (Time cl1)) m) () (Time cl1, Either (Tag cl1) (Tag cl2))
runningSchedule cl1 cl2 rc1 rc2 = MSF $ \_ -> do
raceResult <- race (unMSF rc1 ()) (unMSF rc2 ())
case raceResult of
Left (((time, tag1), rc1'), cont2) -> return
( (time, Left tag1)
, runningSchedule cl1 cl2 rc1' (MSF $ const cont2)
)
Right (cont1, ((time, tag2), rc2')) -> return
( (time, Right tag2)
, runningSchedule cl1 cl2 (MSF $ const cont1) rc2'
)