module Ribosome.Host.Error where

import Ribosome.Host.Data.BootError (BootError (BootError))
import Ribosome.Host.Data.RpcError (RpcError)
import Ribosome.Host.Effect.Rpc (Rpc)

-- |Run a 'Sem' that uses 'Rpc' and discard 'RpcError's, interpreting 'Rpc' to @'Rpc' '!!' 'RpcError'@.
ignoreRpcError ::
  Member (Rpc !! RpcError) r =>
  Sem (Rpc : r) a ->
  Sem r ()
ignoreRpcError :: forall (r :: EffectRow) a.
Member (Rpc !! RpcError) r =>
Sem (Rpc : r) a -> Sem r ()
ignoreRpcError =
  Sem (Rpc : r) () -> Sem r ()
forall err (eff :: (* -> *) -> * -> *) (r :: EffectRow).
Member (Resumable err eff) r =>
Sem (eff : r) () -> Sem r ()
resume_ (Sem (Rpc : r) () -> Sem r ())
-> (Sem (Rpc : r) a -> Sem (Rpc : r) ())
-> Sem (Rpc : r) a
-> Sem r ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sem (Rpc : r) a -> Sem (Rpc : r) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void

-- |Run a 'Sem' that uses 'Rpc' and catch 'RpcError's with the supplied function, interpreting 'Rpc' to @'Rpc' '!!'
-- 'RpcError'@.
onRpcError ::
  Member (Rpc !! RpcError) r =>
  (RpcError -> Sem r a) ->
  Sem (Rpc : r) a ->
  Sem r a
onRpcError :: forall (r :: EffectRow) a.
Member (Rpc !! RpcError) r =>
(RpcError -> Sem r a) -> Sem (Rpc : r) a -> Sem r a
onRpcError =
  (RpcError -> Sem r a) -> Sem (Rpc : r) a -> Sem r a
forall err (eff :: (* -> *) -> * -> *) (r :: EffectRow) a.
Member (Resumable err eff) r =>
(err -> Sem r a) -> Sem (eff : r) a -> Sem r a
resuming

-- |Resume an error by transforming it to @'Error' 'BootError'@.
resumeBootError ::
   eff err r .
  Show err =>
  Members [eff !! err, Error BootError] r =>
  InterpreterFor eff r
resumeBootError :: forall (eff :: (* -> *) -> * -> *) err (r :: EffectRow).
(Show err, Members '[eff !! err, Error BootError] r) =>
InterpreterFor eff r
resumeBootError =
  forall err (eff :: (* -> *) -> * -> *) err' (r :: EffectRow) a.
Members '[Resumable err eff, Error err'] r =>
(err -> err') -> Sem (eff : r) a -> Sem r a
resumeHoistError @_ @eff (Text -> BootError
BootError (Text -> BootError) -> (err -> Text) -> err -> BootError
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b a. (Show a, IsString b) => a -> b
show @Text)