module Effectful.Timeout
(
Timeout
, runTimeout
, timeout
) where
import System.Timeout qualified as T
import Effectful
import Effectful.Dispatch.Static
data Timeout :: Effect
type instance DispatchOf Timeout = Static WithSideEffects
data instance StaticRep Timeout = Timeout
runTimeout :: IOE :> es => Eff (Timeout : es) a -> Eff es a
runTimeout :: forall (es :: [Effect]) a.
(IOE :> es) =>
Eff (Timeout : es) a -> Eff es a
runTimeout = StaticRep Timeout -> Eff (Timeout : es) a -> Eff es a
forall (e :: Effect) (sideEffects :: SideEffects) (es :: [Effect])
a.
(DispatchOf e ~ 'Static sideEffects, MaybeIOE sideEffects es) =>
StaticRep e -> Eff (e : es) a -> Eff es a
evalStaticRep StaticRep Timeout
Timeout
timeout
:: Timeout :> es
=> Int
-> Eff es a
-> Eff es (Maybe a)
timeout :: forall (es :: [Effect]) a.
(Timeout :> es) =>
Int -> Eff es a -> Eff es (Maybe a)
timeout = (IO a -> IO (Maybe a)) -> Eff es a -> Eff es (Maybe a)
forall a b (es :: [Effect]).
HasCallStack =>
(IO a -> IO b) -> Eff es a -> Eff es b
unsafeLiftMapIO ((IO a -> IO (Maybe a)) -> Eff es a -> Eff es (Maybe a))
-> (Int -> IO a -> IO (Maybe a))
-> Int
-> Eff es a
-> Eff es (Maybe a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> IO a -> IO (Maybe a)
forall a. Int -> IO a -> IO (Maybe a)
T.timeout