Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- newtype ExceptClock cl e = ExceptClock {
- getExceptClock :: cl
- data CatchClock cl1 e cl2 = CatchClock cl1 (e -> cl2)
- catchClSF :: (Time cl1 ~ Time cl2, Monad m) => ClSF m cl1 a b -> ClSF m cl2 a b -> ClSF m (CatchClock cl1 e cl2) a b
- type SafeClock m = HoistClock (ExceptT Void m) m
- safeClock :: Functor m => cl -> SafeClock m cl
- data Single m time tag e = Single {}
- type DelayException m time cl e1 e2 = CatchClock cl e1 (Single m time e1 e2)
- delayException :: (Monad m, Clock (ExceptT e1 m) cl, MonadError e2 m) => cl -> (e1 -> e2) -> m (Time cl) -> DelayException m (Time cl) cl e1 e2
- delayException' :: (Monad m, MonadError e m, Clock (ExceptT e m) cl) => cl -> m (Time cl) -> DelayException m (Time cl) cl e e
- type DelayMonadIOException m cl e1 e2 = DelayException m UTCTime (ExceptClock cl e1) e1 e2
- delayMonadIOException :: (Exception e1, MonadIO m, MonadError e2 m, Clock IO cl, Time cl ~ UTCTime) => cl -> (e1 -> e2) -> DelayMonadIOException m cl e1 e2
- type DelayMonadIOError m cl e = DelayMonadIOException m cl IOError e
- delayMonadIOError :: (Exception e, MonadError e m, MonadIO m, Clock IO cl, Time cl ~ UTCTime) => cl -> (IOError -> e) -> DelayMonadIOError m cl e
- delayMonadIOError' :: (MonadError IOError m, MonadIO m, Clock IO cl, Time cl ~ UTCTime) => cl -> DelayMonadIOError m cl IOError
- type DelayIOException cl e1 e2 = DelayException (ExceptT e2 IO) UTCTime (ExceptClock cl e1) e1 e2
- delayIOException :: (Exception e1, Clock IO cl, Time cl ~ UTCTime) => cl -> (e1 -> e2) -> DelayIOException cl e1 e2
- delayIOException' :: (Exception e, Clock IO cl, Time cl ~ UTCTime) => cl -> DelayIOException cl e e
- type DelayIOError cl e = DelayIOException cl IOError e
- delayIOError :: (Time cl ~ UTCTime, Clock IO cl) => cl -> (IOError -> e) -> DelayIOError cl e
- delayIOError' :: (Time cl ~ UTCTime, Clock IO cl) => cl -> DelayIOError cl IOError
ExceptClock
newtype ExceptClock cl e Source #
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
.
ExceptClock | |
|
Instances
(Exception e, Clock IO cl, MonadIO eio, MonadError e eio) => Clock eio (ExceptClock cl e) Source # | |
Defined in FRP.Rhine.Clock.Except type Time (ExceptClock cl e) Source # type Tag (ExceptClock cl e) Source # initClock :: ExceptClock cl e -> RunningClockInit eio (Time (ExceptClock cl e)) (Tag (ExceptClock cl e)) Source # | |
GetClockProxy (ExceptClock cl e) Source # | |
Defined in FRP.Rhine.Clock.Except getClockProxy :: ClockProxy (ExceptClock cl e) Source # | |
type Tag (ExceptClock cl e) Source # | |
Defined in FRP.Rhine.Clock.Except | |
type Time (ExceptClock cl e) Source # | |
Defined in FRP.Rhine.Clock.Except |
CatchClock
data CatchClock cl1 e cl2 Source #
Catch an exception in one clock and proceed with another.
When cl1
throws an exception e
(in
) while running,
this exception is caught, and a clock ExceptT
ecl2
is started from the exception value.
For this to be possible, cl1
must run in the monad
, while ExceptT
e mcl2
must run in m
.
To give cl2
the ability to throw another exception, you need to add a further ExceptT
layer to the stack in m
.
CatchClock cl1 (e -> cl2) |
Instances
(Time cl1 ~ Time cl2, Clock (ExceptT e m) cl1, Clock m cl2, Monad m) => Clock m (CatchClock cl1 e cl2) Source # | |
Defined in FRP.Rhine.Clock.Except type Time (CatchClock cl1 e cl2) Source # type Tag (CatchClock cl1 e cl2) Source # initClock :: CatchClock cl1 e cl2 -> RunningClockInit m (Time (CatchClock cl1 e cl2)) (Tag (CatchClock cl1 e cl2)) Source # | |
GetClockProxy (CatchClock cl1 e cl2) Source # | |
Defined in FRP.Rhine.Clock.Except getClockProxy :: ClockProxy (CatchClock cl1 e cl2) Source # | |
type Tag (CatchClock cl1 e cl2) Source # | |
Defined in FRP.Rhine.Clock.Except | |
type Time (CatchClock cl1 e cl2) Source # | |
Defined in FRP.Rhine.Clock.Except |
:: (Time cl1 ~ Time cl2, Monad m) | |
=> ClSF m cl1 a b | Executed until |
-> ClSF m cl2 a b | Executed after |
-> ClSF m (CatchClock cl1 e cl2) a b |
Combine two ClSF
s under two different clocks.
SafeClock
safeClock :: Functor m => cl -> SafeClock m cl Source #
Remove ExceptT
from the monad of a clock, proving that no exception can be thrown.
Single
clock
data Single m time tag e Source #
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.
Instances
(TimeDomain time, MonadError e m) => Clock m (Single m time tag e) Source # | |
type Tag (Single m time tag e) Source # | |
Defined in FRP.Rhine.Clock.Except | |
type Time (Single m time tag e) Source # | |
Defined in FRP.Rhine.Clock.Except |
DelayException
type DelayException m time cl e1 e2 = CatchClock cl e1 (Single m time e1 e2) Source #
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.
:: (Monad m, Clock (ExceptT e1 m) cl, MonadError e2 m) | |
=> cl | The clock that will throw an exception |
-> (e1 -> e2) | How to transform the exception into the new exception that will be thrown later |
-> m (Time cl) | How to measure the current time |
-> DelayException m (Time cl) cl e1 e2 |
Construct a DelayException
clock.
delayException' :: (Monad m, MonadError e m, Clock (ExceptT e m) cl) => cl -> m (Time cl) -> DelayException m (Time cl) cl e e Source #
Like delayException
, but the exception thrown by cl
and by the DelayException
clock are the same.
type DelayMonadIOException m cl e1 e2 = DelayException m UTCTime (ExceptClock cl e1) e1 e2 Source #
delayMonadIOException :: (Exception e1, MonadIO m, MonadError e2 m, Clock IO cl, Time cl ~ UTCTime) => cl -> (e1 -> e2) -> DelayMonadIOException m cl e1 e2 Source #
Build a DelayMonadIOException
. The time will be measured using the system time.
type DelayMonadIOError m cl e = DelayMonadIOException m cl IOError e Source #
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 Source #
delayMonadIOException
specialised to IOError
.
delayMonadIOError' :: (MonadError IOError m, MonadIO m, Clock IO cl, Time cl ~ UTCTime) => cl -> DelayMonadIOError m cl IOError Source #
Like delayMonadIOError
, but throw the error without transforming it.
type DelayIOException cl e1 e2 = DelayException (ExceptT e2 IO) UTCTime (ExceptClock cl e1) e1 e2 Source #
DelayMonadIOException
specialised to the monad
.ExceptT
e2 IO
This is sometimes helpful when the type checker complains about an ambigous monad type variable.
delayIOException :: (Exception e1, Clock IO cl, Time cl ~ UTCTime) => cl -> (e1 -> e2) -> DelayIOException cl e1 e2 Source #
delayMonadIOException
specialised to the monad
.ExceptT
e2 IO
delayIOException' :: (Exception e, Clock IO cl, Time cl ~ UTCTime) => cl -> DelayIOException cl e e Source #
delayIOException'
, but throw the error without transforming it.
type DelayIOError cl e = DelayIOException cl IOError e Source #
DelayIOException
specialised to IOError
.
delayIOError :: (Time cl ~ UTCTime, Clock IO cl) => cl -> (IOError -> e) -> DelayIOError cl e Source #
delayIOException
specialised to IOError
.
delayIOError' :: (Time cl ~ UTCTime, Clock IO cl) => cl -> DelayIOError cl IOError Source #
delayIOError
, but throw the error without transforming it.