Skip to content

Commit

Permalink
Add Except, Catch, and Single clocks, and many utilities
Browse files Browse the repository at this point in the history
  • Loading branch information
turion committed Mar 13, 2024
1 parent 56cd545 commit 135d3df
Show file tree
Hide file tree
Showing 5 changed files with 314 additions and 1 deletion.
11 changes: 11 additions & 0 deletions rhine/rhine.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,8 @@ category: FRP
build-type: Simple
extra-source-files: ChangeLog.md
extra-doc-files: README.md

data-files: test/assets/*.txt
tested-with:
ghc ==9.0.2
ghc ==9.2.8
Expand All @@ -44,6 +46,8 @@ common opts
build-depends:
base >=4.14 && <4.18,
vector-sized >=1.4,
transformers >= 0.5,
text >= 1.2 && < 2.1,

if flag(dev)
ghc-options: -Werror
Expand Down Expand Up @@ -79,6 +83,7 @@ library
FRP.Rhine.ClSF.Upsample
FRP.Rhine.ClSF.Util
FRP.Rhine.Clock
FRP.Rhine.Clock.Except
FRP.Rhine.Clock.FixedStep
FRP.Rhine.Clock.Periodic
FRP.Rhine.Clock.Proxy
Expand Down Expand Up @@ -127,6 +132,7 @@ library
time >=1.8,
time-domain ^>=0.1.0.2,
transformers >=0.5,
mtl >= 2.2 && < 2.4,

-- Directories containing source files.
hs-source-dirs: src
Expand All @@ -138,16 +144,21 @@ test-suite test
main-is: Main.hs
other-modules:
Clock
Clock.Except
Clock.FixedStep
Clock.Millisecond
Schedule
Util

Paths_rhine
autogen-modules:
Paths_rhine
build-depends:
monad-schedule,
rhine,
tasty ^>=1.4,
tasty-hunit ^>=0.10,
mtl,

flag dev
description: Enable warnings as errors. Active on ci.
Expand Down
187 changes: 187 additions & 0 deletions rhine/src/FRP/Rhine/Clock/Except.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,187 @@
{-# LANGUAGE ImportQualifiedPost #-}

module FRP.Rhine.Clock.Except where

-- base
import Control.Arrow
import Control.Exception
import Control.Exception qualified as Exception
import Control.Monad ((<=<))
import Data.Functor ((<&>))
import Data.Void

-- transformers
import Control.Monad.Trans.MSF.Except

-- time
import Data.Time (UTCTime, getCurrentTime)

-- mtl
import Control.Monad.Error.Class
import Control.Monad.IO.Class (MonadIO, liftIO)
import Control.Monad.Trans.MSF qualified as MSFExcept

-- dunai
import Data.MonadicStreamFunction (morphS)

-- rhine
import FRP.Rhine.Clock (
Clock (..),
HoistClock (..),
TimeDomain,
)
import FRP.Rhine.Clock.Proxy (GetClockProxy)

{- | Handle 'IO' exceptions purely in 'ExceptT'.
The clock @cl@ may throw 'Exception's of type @e@ while running.
These exceptions are automatically caught, and raised as an error in 'ExceptT'
(or more generally in 'MonadError', which implies the presence of 'ExceptT' in the monad transformer stack)
It can then be caught and handled with 'CatchClock'.
-}
newtype ExceptClock cl e = ExceptClock {getExceptClock :: cl}

instance (Exception e, Clock IO cl, MonadIO eio, MonadError e eio) => Clock eio (ExceptClock cl e) where
type Time (ExceptClock cl e) = Time cl
type Tag (ExceptClock cl e) = Tag cl

initClock ExceptClock {getExceptClock} = do
ioerror $
Exception.try $
initClock getExceptClock
<&> first (morphS (ioerror . Exception.try))
where
ioerror :: (MonadError e eio, MonadIO eio) => IO (Either e a) -> eio a
ioerror = liftEither <=< liftIO

instance GetClockProxy (ExceptClock cl e)

{- | Catch an exception in one clock and proceed with another.
When @cl@ throws an exception @e@ (in @'ExceptT' e@) while running,
this exception is caught, and a clock @cl'@ is started from the exception value.
For this to be possible, @cl@ must run in the monad @'ExceptT' e m@, while @cl'@ must run in @m@.
To give @cl'@ the ability to throw another exception, you need to add a further 'ExceptT' layer to the stack in @m@.
-}
data CatchClock cl e cl' = CatchClock cl (e -> cl')

instance (Time cl ~ Time cl', Clock (ExceptT e m) cl, Clock m cl', Monad m) => Clock m (CatchClock cl e cl') where
type Time (CatchClock cl e cl') = Time cl
type Tag (CatchClock cl e cl') = Either (Tag cl) (Tag cl')
initClock (CatchClock cl handler) = do
tryToInit <- runExceptT $ first (>>> arr (second Left)) <$> initClock cl
-- FIXME Each of these branches needs a unit test
case tryToInit of
Right (runningClock, initTime) -> do
let catchingClock = safely $ do
e <- MSFExcept.try runningClock
let cl' = handler e
(runningClock', _) <- once_ $ initClock cl'
safe $ runningClock' >>> arr (second Right)
return (catchingClock, initTime)
Left e -> (fmap (first (>>> arr (second Right))) . initClock) $ handler e

instance (GetClockProxy (CatchClock cl e cl'))

-- | A clock that throws no exceptions.
type SafeClock m = HoistClock (ExceptT Void m) m

-- | Hoist the monad of a clock into 'ExceptT', without throwing an exception.
safeClock :: (Functor m) => cl -> SafeClock m cl
safeClock unhoistedClock =
HoistClock
{ unhoistedClock
, monadMorphism = fmap (either absurd id) . runExceptT
}

{- | A clock that emits a single tick, and then throws an exception.
The tag, time measurement and exception have to be supplied as clock value.
-}
data Single m time tag e = Single
{ singleTag :: tag
-- ^ The tag that will be emitted on the tick.
, getTime :: m time
-- ^ A method to measure the current time.
, exception :: e
-- ^ The exception to throw after the single tick.
}

instance (TimeDomain time, MonadError e m) => Clock m (Single m time tag e) where
type Time (Single m time tag e) = time
type Tag (Single m time tag e) = tag
initClock Single {singleTag, getTime, exception} = do
initTime <- getTime
let runningClock = morphS (errorT . runExceptT) $ runMSFExcept $ do
step_ (initTime, singleTag)
return exception
errorT :: (MonadError e m) => m (Either e a) -> m a
errorT = (>>= liftEither)
return (runningClock, initTime)

{- | Catch an exception in clock @cl@ and throw it after one time step.
This is particularly useful if you want to give your signal network a chance to save its current state in some way.
-}
type DelayException m time cl e e' = CatchClock cl e (Single m time e e')

-- | Construct a 'DelayException' clock.
delayException ::
(Monad m, Clock (ExceptT e m) cl, MonadError e' m) =>
-- | The clock that will throw an exception @e@
cl ->
-- | How to transform the exception into the new exception that will be thrown later
(e -> e') ->
-- | How to measure the current time
m (Time cl) ->
DelayException m (Time cl) cl e e'
delayException cl handler mTime = CatchClock cl $ \e -> Single e mTime $ handler e

-- | Like 'delayException', but the exception thrown by @cl@ and by the @DelayException@ clock are the same.
delayException' :: (Monad m, MonadError e m, Clock (ExceptT e m) cl) => cl -> m (Time cl) -> DelayException m (Time cl) cl e e
delayException' cl = delayException cl id

-- | Catch an 'IO' 'Exception', and throw it after one time step.
type DelayMonadIOException m cl e e' = DelayException m UTCTime (ExceptClock cl e) e e'

-- | Build a 'DelayMonadIOException'. The time will be measured using the system time.
delayMonadIOException :: (Exception e, MonadIO m, MonadError e' m, Clock IO cl, Time cl ~ UTCTime) => cl -> (e -> e') -> DelayMonadIOException m cl e e'
delayMonadIOException cl handler = delayException (ExceptClock cl) handler $ liftIO getCurrentTime

-- | 'DelayMonadIOException' specialised to 'IOError'.
type DelayMonadIOError m cl e = DelayMonadIOException m cl IOError e

-- | 'delayMonadIOException' specialised to 'IOError'.
delayMonadIOError :: (Exception e, MonadError e m, MonadIO m, Clock IO cl, Time cl ~ UTCTime) => cl -> (IOError -> e) -> DelayMonadIOError m cl e
delayMonadIOError = delayMonadIOException

-- | Like 'delayMonadIOError', but throw the error without transforming it.
delayMonadIOError' :: (MonadError IOError m, MonadIO m, Clock IO cl, Time cl ~ UTCTime) => cl -> DelayMonadIOError m cl IOError
delayMonadIOError' cl = delayMonadIOError cl id

{- | 'DelayMonadIOException' specialised to the monad @'ExceptT' e' 'IO'@.
This is sometimes helpful when the type checker complains about an ambigous monad type variable.
-}
type DelayIOException cl e e' = DelayException (ExceptT e' IO) UTCTime (ExceptClock cl e) e e'

-- | 'delayMonadIOException' specialised to the monad @'ExceptT' e' 'IO'@.
delayIOException :: (Exception e, Clock IO cl, Time cl ~ UTCTime) => cl -> (e -> e') -> DelayIOException cl e e'
delayIOException = delayMonadIOException

-- | 'delayIOException'', but throw the error without transforming it.
delayIOException' :: (Exception e, Clock IO cl, Time cl ~ UTCTime) => cl -> DelayIOException cl e e
delayIOException' cl = delayIOException cl id

-- | 'DelayIOException' specialised to 'IOError'.
type DelayIOError cl e = DelayIOException cl IOError e

-- | 'delayIOException' specialised to 'IOError'.
delayIOError :: (Time cl ~ UTCTime, Clock IO cl) => cl -> (IOError -> e) -> DelayIOError cl e
delayIOError = delayIOException

-- | 'delayIOError', but throw the error without transforming it.
delayIOError' :: (Time cl ~ UTCTime, Clock IO cl) => cl -> DelayIOError cl IOError
delayIOError' cl = delayIOException cl id
4 changes: 3 additions & 1 deletion rhine/test/Clock.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,12 +4,14 @@ module Clock where
import Test.Tasty

-- rhine
import Clock.Except
import Clock.FixedStep
import Clock.Millisecond

tests =
testGroup
"Clock"
[ Clock.FixedStep.tests
[ Clock.Except.tests
, Clock.FixedStep.tests
, Clock.Millisecond.tests
]
111 changes: 111 additions & 0 deletions rhine/test/Clock/Except.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,111 @@
{-# LANGUAGE Arrows #-}
{-# LANGUAGE OverloadedStrings #-}

module Clock.Except where

-- base
import Data.Either (isRight)
import GHC.IO.Handle (hDuplicateTo)
import System.IO (IOMode (ReadMode), stdin, withFile)
import System.IO.Error (isEOFError)

-- mtl
import Control.Monad.Writer.Class

-- transformers
-- Replace Strict by CPS when bumping mtl to 2.3
import Control.Monad.Trans.Writer.Strict hiding (tell)

-- text
import Data.Text (Text)

-- tasty
import Test.Tasty (testGroup)

-- tasty-hunit
import Test.Tasty.HUnit (testCase, (@?), (@?=))

-- rhine
import FRP.Rhine
import FRP.Rhine.Clock.Except (CatchClock (CatchClock), DelayIOError, DelayMonadIOError, ExceptClock (ExceptClock), delayIOError, delayMonadIOError')
import Paths_rhine

-- FIXME organisation: group functions & clock values closer to their test cases
type E = ExceptT IOError IO
type WT = WriterT [Text]
type M = WT E
type EClock = ExceptClock StdinClock IOError

type TestClock =
LiftClock
E
WT
( CatchClock
EClock
IOError
EClock
)

-- FIXME also need to test the other branch of CatchClock
testClock :: TestClock
testClock = liftClock $ CatchClock (ExceptClock StdinClock) $ const $ ExceptClock StdinClock

clsf :: ClSF M TestClock () ()
clsf = proc () -> do
tag <- tagS -< ()
arrMCl tell -< either (const ["weird"]) pure tag

type DelayedClock = DelayIOError StdinClock (Maybe [Text])

-- type DelayedClock = DelayException IO UTCTime (ExceptClock StdinClock IOError) IOError (Maybe [Text])

delayedClock :: DelayedClock
delayedClock = delayIOError StdinClock $ const Nothing

-- FIXME it would be cool if there were a utility that combines two clsfs under the two parts of the catchclock
clsf2 :: ClSF (ExceptT (Maybe [Text]) IO) DelayedClock () ()
clsf2 = proc () -> do
tag <- tagS -< ()
textSoFar <- mappendS -< either pure (const []) tag
throwOn' -< (isRight tag, Just textSoFar)

clsf3 :: ClSF (ExceptT (Maybe [Text]) IO) DelayedClock () ()
clsf3 = proc () -> do
tag <- tagS -< ()
_textSoFar <- mappendS -< either pure (const []) tag
returnA -< ()

-- clsf4 :: ClSF (ExceptT IOError (WriterT [Text] IO)) (LiftClock (WriterT [Text] IO) (ExceptT IOError) (DelayIOError StdinClock IOError)) () ()
clsf4 :: (Tag cl ~ Either Text a) => (MonadWriter [Text] m) => ClSF m cl () ()
clsf4 =
tagS >>> proc tag -> case tag of
Left text -> arrMCl tell -< [text]
Right _ -> returnA -< ()

tests =
testGroup
"ExceptClock"
[ testCase "Outputs the exception on EOF" $ withTestStdin $ do
Left result <- runExceptT $ runWriterT $ flow $ clsf @@ testClock
isEOFError result @? "It's an EOF error"
, testCase "DelayException delays error by 1 step" $ withTestStdin $ do
result <- runExceptT $ flow $ clsf2 @@ delayedClock
result @?= Left (Just ["data", "test"])
, testCase "DelayException throws error after 1 step" $ withTestStdin $ do
result <- runExceptT $ flow $ clsf3 @@ delayedClock
result @?= Left Nothing
, testCase "DelayException throws error after 1 step, but can write down results" $ withTestStdin $ do
(Left e, result) <- runWriterT $ runExceptT $ flow $ clsf4 @@ clWriterExcept
isEOFError e @? "is EOF"
result @?= ["test", "data"]
]

clWriterExcept :: DelayMonadIOError (ExceptT IOError (WriterT [Text] IO)) StdinClock IOError
clWriterExcept = delayMonadIOError' StdinClock

withTestStdin :: IO a -> IO a
withTestStdin action = do
testdataFile <- getDataFileName "test/assets/testdata.txt"
withFile testdataFile ReadMode $ \h -> do
hDuplicateTo h stdin
action
2 changes: 2 additions & 0 deletions rhine/test/assets/testdata.txt
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
test
data

0 comments on commit 135d3df

Please sign in to comment.