What's the right way of doing error handling? #149
Replies: 4 comments 6 replies
-
|
sorry i haven't understood your problem, but allow me to guess, you complained that catchError doesn't remove the constraint maybe you want to use reinterpret to introduce internal effects? |
Beta Was this translation helpful? Give feedback.
-
|
I think I was asking if there was a way not to use data FileSystem :: Effect where
ReadFile :: Name -> FileSystem m Textsince runFileSystemIO
:: (IOE :> es, Error FsError :> es)
=> Eff (FileSystem : es) a
-> Eff es a
runFileSystemIO = interpret $ \_ -> \case
ReadFile path -> adapt $ IO.readFile path
where
adapt m = liftIO m `catch` \(e::IOException) -> throwError . FsError $ show eso the exception is converted to a action
& runFileSystemIO
& runError @FsError
& runEffwe have access to what the error was only after discharging the So it seems like the only way of having the caller be able to handle the error without running the data FileSystem :: Effect where
ReadFile :: Name -> FileSystem m (Either FsError Text)and the interpreter to runFileSystemIO
:: (IOE :> es)
=> Eff (FileSystem : es) a
-> Eff es a
runFileSystemIO = interpret $ \_ -> \case
ReadFile path -> adapt $ IO.readFile path
where
adapt m = liftIO m `catch` \(e::IOException) -> pure $ Left $ FsError $ show eI'd like to also have the errors be more fine grained so then maybe I'd have data FileSystem :: Effect where
ReadFile :: Name -> FileSystem m (Either FsReadError Text)
WriteFile :: Name -> FileSystem m (Either FsWriteError Text)I also want to have the option to handle these errors now or later so it seems I need to write helper functions... readFile :: (HasCallStack, FileSystem :> es, Error FsReadError) => Name -> Eff es Text
readFile path = do
result <- send (ReadFile path)
eitherToError result
writeFile :: (HasCallStack, FileSystem :> es, Error FsWriteError) => Name -> Eff es Text
writeFile path content = do
result <- send (WriteFile path content)
eitherToError resultthen I can I was just wondering if this is a good idea. I tried it the other way by just having the errors effects pop out when running the |
Beta Was this translation helpful? Give feedback.
-
|
I think this would be a very convenient addition to the API: #152 |
Beta Was this translation helpful? Give feedback.
-
|
@eddiemundo if you do what I did in #149 (reply in thread), then handlers will look a bit different. Here's a complete example with the modified import Control.Exception
import qualified Control.Monad.Catch as C
import qualified Data.Map.Strict as M
import qualified System.IO as IO
import Effectful
import Effectful.Dispatch.Dynamic
import Effectful.Error.Static
import Effectful.State.Static.Local
----------------------------------------
-- Errors
newtype FsReadError = FsReadError String
deriving stock Show
deriving anyclass Exception
newtype FsWriteError = FsWriteError String
deriving stock Show
deriving anyclass Exception
----------------------------------------
-- Effect
data FileSystem :: Effect where
ReadFile :: Error FsReadError :> es => FilePath -> FileSystem (Eff es) String
WriteFile :: Error FsWriteError :> es => FilePath -> String -> FileSystem (Eff es) ()
type instance DispatchOf FileSystem = Dynamic
readFile
:: (Error FsReadError :> es, FileSystem :> es)
=> FilePath
-> Eff es String
readFile path = send (ReadFile path)
writeFile
:: (Error FsWriteError :> es, FileSystem :> es)
=> FilePath
-> String
-> Eff es ()
writeFile path content = send (WriteFile path content)
----------------------------------------
-- Handlers
runFileSystemIO
:: IOE :> es
=> Eff (FileSystem : es) a
-> Eff es a
runFileSystemIO = interpret $ \env -> \case
ReadFile path -> adapt env FsReadError $ IO.readFile path
WriteFile path contents -> adapt env FsWriteError $ IO.writeFile path contents
where
adapt env errCon m = liftIO m `C.catch` \(e::IOException) -> do
-- The error effect is in scope only in the local environment.
localSeqUnlift env $ \unlift -> unlift . throwError . errCon $ show e
runFileSystemPure
:: M.Map FilePath String
-> Eff (FileSystem : es) a
-> Eff es a
runFileSystemPure fs0 = reinterpret (evalState fs0) $ \env -> \case
ReadFile path -> gets (M.lookup path) >>= \case
Just contents -> pure contents
Nothing -> localSeqUnlift env $ \unlift -> do
unlift . throwError . FsReadError $ "File not found: " ++ show path
WriteFile path contents -> modify $ M.insert path contentsNow you don't need the I'll add this as an alternative design to haddock when I have a bit of time since people seem to not be aware of the trick of substituting |
Beta Was this translation helpful? Give feedback.
Uh oh!
There was an error while loading. Please reload this page.
Uh oh!
There was an error while loading. Please reload this page.
-
effectfulallows us to do stuff likeUsing
catchErrordoesn't remove the constraint so not sure how to properly use that either.Do we just create an interpreter like
but that seems kinda unwieldy.
The other issue is that let's say that the interpreter holds mutable state then if you want to "materialize" the error you need to first call the interpreter with the mutable state, then call
runErrorThis kind of means that you need your mutable state in scope whenever you want to look at an error...
So is the right way something more traditional looking?
and then you can decide after calling
MyOp1orMyOp2tothrowErrorand short circuit at those call sites, and then if you want to handle those errors else later you canrunError?Beta Was this translation helpful? Give feedback.
All reactions