Reputation: 3230
Let's say I have a readEnv
function that reads two env vars and returns an Either value, with a ReadError
type as the Left value:
module Main where
import Control.Exception (SomeException(..), handle, throw)
import Data.Typeable (typeOf)
import System.Environment (getEnv)
data ReadError
= MissingHost
| MissingPort
deriving (Show)
main :: IO ()
main = do
eitherEnvs <- readEnv'
case eitherEnvs of
Left err -> print err
Right (port, host) -> print (port, host)
readEnv :: IO (Either ReadError (String, String))
readEnv = do
port <- getEnv "HOST"
host <- getEnv "PORT"
return $ Right (port, host)
readEnv' :: IO (Either ReadError (String, String))
readEnv' = handle missingEnv readEnv
missingEnv :: SomeException -> IO (Either ReadError (String, String))
missingEnv (SomeException e)
| isMissingHost e = do
print e
return $ Left $ MissingHost
| isMissingPort e = do
print e
return $ Left $ MissingPort
| otherwise = throw e
where
isMissingHost e = take 4 (show e) == "HOST"
isMissingPort e = take 4 (show e) == "PORT"
Since I know getEnv
is an IO that will throw if the env var is missing, (i know there is lookupEnv, but my question is about how to handle error, not how to avoid error), I made a readEnv'
function that will catch the IO Exception and converts it to the ReadError
type.
The above code works, however, I don't like this pattern/style to handle exception, because in order to handle the exception from getEnv "HOST"
, I have to put the handler outside of the entire readEnv
, and parse the error message in order to distinguish if the error is MissingHost
or MissingPort
. If the error message doesn't contain "HOST" or "PORT", then the missingEnv
can't distinguish which getEnv
call is the exception from.
Ideally, there is a way to handle the exception at where it happened and short circuits to return with the Left value. Since I know the only IOException in getEnv "HOST"
is MissingHost
error, then I don't need to parse the error message.
How to do that?
Upvotes: 2
Views: 124
Reputation: 531235
Using lookupEnv
really isn't that bad. The following provides the same locality of error handling as Thomas M. DuBuisson's answer.
module Main where
import System.Environment (lookupEnv)
data ReadError = MissingHost | MissingPort deriving (Show)
type EnvReadResult a = IO (Either ReadError a)
main :: IO ()
main = readEnv >>= either print print
parseEnv :: String -> ReadError -> EnvReadResult String
parseEnv name err = lookupEnv name >>= return . maybe (Left err) Right
readEnv :: EnvReadResult (String, String)
readEnv = do
host <- parseEnv "HOST" MissingHost -- host :: Either ReadError String
port <- parseEnv "PORT" MissingPort -- port :: ditto
return $ (,) <$> host <*> port -- Combine and lift back into IO
parseEnv
takes a variable name and the error to report if the variable is undefined, and returns an IO
-wrapped Either
value. The maybe
function acts as the "exception handler", rewrapping a Just
value with Right
or converting Nothing
to an appropriate Left
value.
The Applicative
instance for Either
effectively returns the first error found, or combines all Right
values into a single Right
value. For example:
(,) <$> Right "example.com" <*> Right "23456" == Right ("example.com", "23456")
(,) <$> Left MissingHost <*> Right "23456" == Left MissingHost
(,) <$> Right "example.com" <*> Left MissingPort == Left MissingPort
You can also take advantage of the fact that applicative functors compose.
readEnv = let host = parseEnv "HOST" MissingHost
port = parseEnv "PORT" MissingPort
in getCompose $ (,) <$> Compose host <*> Compose port
In particular, since IO
and Either ReadError
are both applicative functors, so is Compose IO (Either ReadError)
.
Upvotes: 1
Reputation: 3230
With the above two answers, I come up with a solution that
1) Doesn't require additional complexity (ExceptT)
2) Doesn't need to parse the error message to distinguish which action failed.
3) readEnv is kept flat.
module Main where
import Control.Exception (IOException, handle)
import System.Environment (getEnv)
data ReadError
= MissingHost
| MissingPort
deriving (Show)
main :: IO ()
main = do
eitherEnvs <- readEnv
either print print eitherEnvs
getEnv' :: String -> ReadError -> IO (Either ReadError String)
getEnv' env err = handle (missingEnv err) $ Right <$> (getEnv env)
readEnv :: IO (Either ReadError (String, String))
readEnv = do
eitherHost <- getEnv' "HOST" MissingHost
eitherPort <- getEnv' "PORT" MissingPort
return $ (,) <$> eitherHost <*> eitherPort
missingEnv :: ReadError -> IOException -> IO (Either ReadError String)
missingEnv err _ = return $ Left err
Upvotes: 0
Reputation: 64740
Considered using an ExceptT monad and adding the right abstraction to getEnv
.
For example:
First let's get past the boilerplate:
module Main where
import Control.Exception (SomeException(..), handle, throw)
-- N.B. Should use Control.Exception.Safe
import qualified Control.Exception as X
import Data.Typeable (typeOf)
import qualified System.Environment as Env
import Control.Monad.Trans.Except
We want to define something like IO but specialized to handling exceptions in a more composable manner and at least allow getEnv
. The monad is ExceptT IO:
type MyIO a = ExceptT ReadError IO a
runMyIO :: MyIO a -> IO (Either ReadError a)
runMyIO = runExceptT
And the operations we can perform in the monad should be lifted - remember, if the rest of your code is typing lift
a lot then you might not have your monad properly abstracted.
getEnv :: String -> MyIO String
getEnv s = ExceptT ((Right <$> Env.getEnv s) `X.catch` hdl)
where hdl :: X.SomeException -> IO (Either ReadError String)
hdl _ = pure $ Left (Missing s)
Now we can use this version of getEnv
in main:
main :: IO ()
main = do
eitherEnvs <- runMyIO ( (,) <$> getEnv "HOST" <*> getEnv "PORT" )
case eitherEnvs of
Left err -> print err
Right (port, host) -> print (port, host)
And yes, we did redefine the Error type:
data ReadError
= Missing String
-- N.B an enum strategy such as MissingPort is doable but often has a
-- data-dependency at the call site such as @getEnv "host" MissingHost@
--
-- That would be a lot like your 'missingEnv' function which forms a mapping
-- from user strings to the ADT enum 'ReadError'.
deriving (Show)
Upvotes: 1