How to simplify the error handling in (IO (Either a b))












4















I'm using the following scenario as an example to learn how to handle errors in a simple way. The scenario is basically read a file path from an environment variable, then read and print the file with the file path.



The following code works, but I don't like the printFile because it has nested case of, a bit hard to read. I wonder if there is a clean way to get rid of it and keep the printFile function flat without using lookupEnv?



How would you simplify this error handling flow?



module Main where

import Control.Exception (IOException, handle, throw)
import System.Environment (getEnv)
import System.IO.Error (isDoesNotExistError)

data MissingError
= MissingEnv String
| MissingFile String
deriving (Show)

main :: IO ()
main = do
eitherFile <- printFile
either print print eitherFile

getEnv' :: String -> MissingError -> IO (Either MissingError String)
getEnv' env err = handle (missingEnv err) $ Right <$> (getEnv env)

readFile' :: FilePath -> MissingError -> IO (Either MissingError String)
readFile' path err = handle (missingFile err) $ Right <$> (readFile path)

missingEnv :: MissingError -> IOException -> IO (Either MissingError String)
missingEnv err = const $ return $ Left err

missingFile :: MissingError -> IOException -> IO (Either MissingError String)
missingFile err e
| isDoesNotExistError e = return $ Left err
| otherwise = throw e

printFile :: IO (Either MissingError String)
printFile = do
eitherFilePath <- getEnv' "FOLDER" (MissingEnv "FOLDER")
case eitherFilePath of
Left err -> return $ Left err
Right path -> readFile' path (MissingFile path)









share|improve this question

























  • Take a look to monad transformers. EitherT is what you are looking for.

    – Luis Morillo
    Nov 22 '18 at 8:30






  • 2





    @LuisMorillo There's no EitherT in the transformers package; it's called ExceptT. See e.g. reddit.com/r/haskell/comments/3ded39/…

    – Mark Seemann
    Nov 22 '18 at 8:46











  • @MarkSeemann my fault. I searched for EitherT and turns out that exists in Control.Monad.Trans.Either . Don't know if it has the same functionality

    – Luis Morillo
    Nov 22 '18 at 9:02
















4















I'm using the following scenario as an example to learn how to handle errors in a simple way. The scenario is basically read a file path from an environment variable, then read and print the file with the file path.



The following code works, but I don't like the printFile because it has nested case of, a bit hard to read. I wonder if there is a clean way to get rid of it and keep the printFile function flat without using lookupEnv?



How would you simplify this error handling flow?



module Main where

import Control.Exception (IOException, handle, throw)
import System.Environment (getEnv)
import System.IO.Error (isDoesNotExistError)

data MissingError
= MissingEnv String
| MissingFile String
deriving (Show)

main :: IO ()
main = do
eitherFile <- printFile
either print print eitherFile

getEnv' :: String -> MissingError -> IO (Either MissingError String)
getEnv' env err = handle (missingEnv err) $ Right <$> (getEnv env)

readFile' :: FilePath -> MissingError -> IO (Either MissingError String)
readFile' path err = handle (missingFile err) $ Right <$> (readFile path)

missingEnv :: MissingError -> IOException -> IO (Either MissingError String)
missingEnv err = const $ return $ Left err

missingFile :: MissingError -> IOException -> IO (Either MissingError String)
missingFile err e
| isDoesNotExistError e = return $ Left err
| otherwise = throw e

printFile :: IO (Either MissingError String)
printFile = do
eitherFilePath <- getEnv' "FOLDER" (MissingEnv "FOLDER")
case eitherFilePath of
Left err -> return $ Left err
Right path -> readFile' path (MissingFile path)









share|improve this question

























  • Take a look to monad transformers. EitherT is what you are looking for.

    – Luis Morillo
    Nov 22 '18 at 8:30






  • 2





    @LuisMorillo There's no EitherT in the transformers package; it's called ExceptT. See e.g. reddit.com/r/haskell/comments/3ded39/…

    – Mark Seemann
    Nov 22 '18 at 8:46











  • @MarkSeemann my fault. I searched for EitherT and turns out that exists in Control.Monad.Trans.Either . Don't know if it has the same functionality

    – Luis Morillo
    Nov 22 '18 at 9:02














4












4








4


1






I'm using the following scenario as an example to learn how to handle errors in a simple way. The scenario is basically read a file path from an environment variable, then read and print the file with the file path.



The following code works, but I don't like the printFile because it has nested case of, a bit hard to read. I wonder if there is a clean way to get rid of it and keep the printFile function flat without using lookupEnv?



How would you simplify this error handling flow?



module Main where

import Control.Exception (IOException, handle, throw)
import System.Environment (getEnv)
import System.IO.Error (isDoesNotExistError)

data MissingError
= MissingEnv String
| MissingFile String
deriving (Show)

main :: IO ()
main = do
eitherFile <- printFile
either print print eitherFile

getEnv' :: String -> MissingError -> IO (Either MissingError String)
getEnv' env err = handle (missingEnv err) $ Right <$> (getEnv env)

readFile' :: FilePath -> MissingError -> IO (Either MissingError String)
readFile' path err = handle (missingFile err) $ Right <$> (readFile path)

missingEnv :: MissingError -> IOException -> IO (Either MissingError String)
missingEnv err = const $ return $ Left err

missingFile :: MissingError -> IOException -> IO (Either MissingError String)
missingFile err e
| isDoesNotExistError e = return $ Left err
| otherwise = throw e

printFile :: IO (Either MissingError String)
printFile = do
eitherFilePath <- getEnv' "FOLDER" (MissingEnv "FOLDER")
case eitherFilePath of
Left err -> return $ Left err
Right path -> readFile' path (MissingFile path)









share|improve this question
















I'm using the following scenario as an example to learn how to handle errors in a simple way. The scenario is basically read a file path from an environment variable, then read and print the file with the file path.



The following code works, but I don't like the printFile because it has nested case of, a bit hard to read. I wonder if there is a clean way to get rid of it and keep the printFile function flat without using lookupEnv?



How would you simplify this error handling flow?



module Main where

import Control.Exception (IOException, handle, throw)
import System.Environment (getEnv)
import System.IO.Error (isDoesNotExistError)

data MissingError
= MissingEnv String
| MissingFile String
deriving (Show)

main :: IO ()
main = do
eitherFile <- printFile
either print print eitherFile

getEnv' :: String -> MissingError -> IO (Either MissingError String)
getEnv' env err = handle (missingEnv err) $ Right <$> (getEnv env)

readFile' :: FilePath -> MissingError -> IO (Either MissingError String)
readFile' path err = handle (missingFile err) $ Right <$> (readFile path)

missingEnv :: MissingError -> IOException -> IO (Either MissingError String)
missingEnv err = const $ return $ Left err

missingFile :: MissingError -> IOException -> IO (Either MissingError String)
missingFile err e
| isDoesNotExistError e = return $ Left err
| otherwise = throw e

printFile :: IO (Either MissingError String)
printFile = do
eitherFilePath <- getEnv' "FOLDER" (MissingEnv "FOLDER")
case eitherFilePath of
Left err -> return $ Left err
Right path -> readFile' path (MissingFile path)






haskell






share|improve this question















share|improve this question













share|improve this question




share|improve this question








edited Nov 22 '18 at 9:21









Mark Seemann

184k33326564




184k33326564










asked Nov 22 '18 at 8:14









Leo ZhangLeo Zhang

1,26211323




1,26211323













  • Take a look to monad transformers. EitherT is what you are looking for.

    – Luis Morillo
    Nov 22 '18 at 8:30






  • 2





    @LuisMorillo There's no EitherT in the transformers package; it's called ExceptT. See e.g. reddit.com/r/haskell/comments/3ded39/…

    – Mark Seemann
    Nov 22 '18 at 8:46











  • @MarkSeemann my fault. I searched for EitherT and turns out that exists in Control.Monad.Trans.Either . Don't know if it has the same functionality

    – Luis Morillo
    Nov 22 '18 at 9:02



















  • Take a look to monad transformers. EitherT is what you are looking for.

    – Luis Morillo
    Nov 22 '18 at 8:30






  • 2





    @LuisMorillo There's no EitherT in the transformers package; it's called ExceptT. See e.g. reddit.com/r/haskell/comments/3ded39/…

    – Mark Seemann
    Nov 22 '18 at 8:46











  • @MarkSeemann my fault. I searched for EitherT and turns out that exists in Control.Monad.Trans.Either . Don't know if it has the same functionality

    – Luis Morillo
    Nov 22 '18 at 9:02

















Take a look to monad transformers. EitherT is what you are looking for.

– Luis Morillo
Nov 22 '18 at 8:30





Take a look to monad transformers. EitherT is what you are looking for.

– Luis Morillo
Nov 22 '18 at 8:30




2




2





@LuisMorillo There's no EitherT in the transformers package; it's called ExceptT. See e.g. reddit.com/r/haskell/comments/3ded39/…

– Mark Seemann
Nov 22 '18 at 8:46





@LuisMorillo There's no EitherT in the transformers package; it's called ExceptT. See e.g. reddit.com/r/haskell/comments/3ded39/…

– Mark Seemann
Nov 22 '18 at 8:46













@MarkSeemann my fault. I searched for EitherT and turns out that exists in Control.Monad.Trans.Either . Don't know if it has the same functionality

– Luis Morillo
Nov 22 '18 at 9:02





@MarkSeemann my fault. I searched for EitherT and turns out that exists in Control.Monad.Trans.Either . Don't know if it has the same functionality

– Luis Morillo
Nov 22 '18 at 9:02












2 Answers
2






active

oldest

votes


















5














You can use the ExceptT monad transformer for this. I haven't tried to run the following proposed changes, but it compiles, so I hope it works.



First, import the module that contains ExceptT:



import Control.Monad.Trans.Except


Next, change the printFile function:



printFile :: IO (Either MissingError String)
printFile = runExceptT $ do
path <- ExceptT $ getEnv' "FOLDER" (MissingEnv "FOLDER")
ExceptT $ readFile' path (MissingFile path)


You have functions that return IO (Either MissingError String), so wrapping them in ExceptT gives you do notation that enables you to access the String embedded in what's effectively ExcepT MissingError IO String.



Then unwrap the ExceptT return value with runExceptT.






share|improve this answer































    3














    The suggestion to use ExceptT is of course a good one but IMHO the proposed answer is still somewhat verbose and you can go a bit farther by simply "staying" in the ExceptT monad throughout your code. Also I would not recommend handling IO exceptions all over the place. Even with a small code base you would lose oversight of your code quickly. tryIOError is useful in this regard. And finally rethinking the definition of your errors would also yield easier to understand and a more solid solution. The end result would look something like this:



    module Main where

    import Data.Bifunctor (first)
    import Control.Monad.Except (ExceptT(..), runExceptT)
    import System.Environment (getEnv)
    import System.IO.Error (tryIOError, isDoesNotExistError)

    data MyError = MissingError String
    | SomeIOError IOError
    deriving (Show)

    main :: IO ()
    main = do
    result <- runExceptT printFile
    print result

    getEnv' :: String -> ExceptT MyError IO String
    getEnv' env = mapIOError ("getting env var " ++ env) $ getEnv env

    readFile' :: FilePath -> ExceptT MyError IO String
    readFile' path = mapIOError ("reading file " ++ path) $ readFile path

    printFile :: ExceptT MyError IO String
    printFile = do
    path <- getEnv' "FOLDER"
    readFile' path

    mapIOError :: String -> IO a -> ExceptT MyError IO a
    mapIOError msg = ExceptT . fmap (first mapError) . tryIOError
    where mapError err | isDoesNotExistError err = MissingError msg
    mapError err = SomeIOError err





    share|improve this answer























      Your Answer






      StackExchange.ifUsing("editor", function () {
      StackExchange.using("externalEditor", function () {
      StackExchange.using("snippets", function () {
      StackExchange.snippets.init();
      });
      });
      }, "code-snippets");

      StackExchange.ready(function() {
      var channelOptions = {
      tags: "".split(" "),
      id: "1"
      };
      initTagRenderer("".split(" "), "".split(" "), channelOptions);

      StackExchange.using("externalEditor", function() {
      // Have to fire editor after snippets, if snippets enabled
      if (StackExchange.settings.snippets.snippetsEnabled) {
      StackExchange.using("snippets", function() {
      createEditor();
      });
      }
      else {
      createEditor();
      }
      });

      function createEditor() {
      StackExchange.prepareEditor({
      heartbeatType: 'answer',
      autoActivateHeartbeat: false,
      convertImagesToLinks: true,
      noModals: true,
      showLowRepImageUploadWarning: true,
      reputationToPostImages: 10,
      bindNavPrevention: true,
      postfix: "",
      imageUploader: {
      brandingHtml: "Powered by u003ca class="icon-imgur-white" href="https://imgur.com/"u003eu003c/au003e",
      contentPolicyHtml: "User contributions licensed under u003ca href="https://creativecommons.org/licenses/by-sa/3.0/"u003ecc by-sa 3.0 with attribution requiredu003c/au003e u003ca href="https://stackoverflow.com/legal/content-policy"u003e(content policy)u003c/au003e",
      allowUrls: true
      },
      onDemand: true,
      discardSelector: ".discard-answer"
      ,immediatelyShowMarkdownHelp:true
      });


      }
      });














      draft saved

      draft discarded


















      StackExchange.ready(
      function () {
      StackExchange.openid.initPostLogin('.new-post-login', 'https%3a%2f%2fstackoverflow.com%2fquestions%2f53426475%2fhow-to-simplify-the-error-handling-in-io-either-a-b%23new-answer', 'question_page');
      }
      );

      Post as a guest















      Required, but never shown

























      2 Answers
      2






      active

      oldest

      votes








      2 Answers
      2






      active

      oldest

      votes









      active

      oldest

      votes






      active

      oldest

      votes









      5














      You can use the ExceptT monad transformer for this. I haven't tried to run the following proposed changes, but it compiles, so I hope it works.



      First, import the module that contains ExceptT:



      import Control.Monad.Trans.Except


      Next, change the printFile function:



      printFile :: IO (Either MissingError String)
      printFile = runExceptT $ do
      path <- ExceptT $ getEnv' "FOLDER" (MissingEnv "FOLDER")
      ExceptT $ readFile' path (MissingFile path)


      You have functions that return IO (Either MissingError String), so wrapping them in ExceptT gives you do notation that enables you to access the String embedded in what's effectively ExcepT MissingError IO String.



      Then unwrap the ExceptT return value with runExceptT.






      share|improve this answer




























        5














        You can use the ExceptT monad transformer for this. I haven't tried to run the following proposed changes, but it compiles, so I hope it works.



        First, import the module that contains ExceptT:



        import Control.Monad.Trans.Except


        Next, change the printFile function:



        printFile :: IO (Either MissingError String)
        printFile = runExceptT $ do
        path <- ExceptT $ getEnv' "FOLDER" (MissingEnv "FOLDER")
        ExceptT $ readFile' path (MissingFile path)


        You have functions that return IO (Either MissingError String), so wrapping them in ExceptT gives you do notation that enables you to access the String embedded in what's effectively ExcepT MissingError IO String.



        Then unwrap the ExceptT return value with runExceptT.






        share|improve this answer


























          5












          5








          5







          You can use the ExceptT monad transformer for this. I haven't tried to run the following proposed changes, but it compiles, so I hope it works.



          First, import the module that contains ExceptT:



          import Control.Monad.Trans.Except


          Next, change the printFile function:



          printFile :: IO (Either MissingError String)
          printFile = runExceptT $ do
          path <- ExceptT $ getEnv' "FOLDER" (MissingEnv "FOLDER")
          ExceptT $ readFile' path (MissingFile path)


          You have functions that return IO (Either MissingError String), so wrapping them in ExceptT gives you do notation that enables you to access the String embedded in what's effectively ExcepT MissingError IO String.



          Then unwrap the ExceptT return value with runExceptT.






          share|improve this answer













          You can use the ExceptT monad transformer for this. I haven't tried to run the following proposed changes, but it compiles, so I hope it works.



          First, import the module that contains ExceptT:



          import Control.Monad.Trans.Except


          Next, change the printFile function:



          printFile :: IO (Either MissingError String)
          printFile = runExceptT $ do
          path <- ExceptT $ getEnv' "FOLDER" (MissingEnv "FOLDER")
          ExceptT $ readFile' path (MissingFile path)


          You have functions that return IO (Either MissingError String), so wrapping them in ExceptT gives you do notation that enables you to access the String embedded in what's effectively ExcepT MissingError IO String.



          Then unwrap the ExceptT return value with runExceptT.







          share|improve this answer












          share|improve this answer



          share|improve this answer










          answered Nov 22 '18 at 9:21









          Mark SeemannMark Seemann

          184k33326564




          184k33326564

























              3














              The suggestion to use ExceptT is of course a good one but IMHO the proposed answer is still somewhat verbose and you can go a bit farther by simply "staying" in the ExceptT monad throughout your code. Also I would not recommend handling IO exceptions all over the place. Even with a small code base you would lose oversight of your code quickly. tryIOError is useful in this regard. And finally rethinking the definition of your errors would also yield easier to understand and a more solid solution. The end result would look something like this:



              module Main where

              import Data.Bifunctor (first)
              import Control.Monad.Except (ExceptT(..), runExceptT)
              import System.Environment (getEnv)
              import System.IO.Error (tryIOError, isDoesNotExistError)

              data MyError = MissingError String
              | SomeIOError IOError
              deriving (Show)

              main :: IO ()
              main = do
              result <- runExceptT printFile
              print result

              getEnv' :: String -> ExceptT MyError IO String
              getEnv' env = mapIOError ("getting env var " ++ env) $ getEnv env

              readFile' :: FilePath -> ExceptT MyError IO String
              readFile' path = mapIOError ("reading file " ++ path) $ readFile path

              printFile :: ExceptT MyError IO String
              printFile = do
              path <- getEnv' "FOLDER"
              readFile' path

              mapIOError :: String -> IO a -> ExceptT MyError IO a
              mapIOError msg = ExceptT . fmap (first mapError) . tryIOError
              where mapError err | isDoesNotExistError err = MissingError msg
              mapError err = SomeIOError err





              share|improve this answer




























                3














                The suggestion to use ExceptT is of course a good one but IMHO the proposed answer is still somewhat verbose and you can go a bit farther by simply "staying" in the ExceptT monad throughout your code. Also I would not recommend handling IO exceptions all over the place. Even with a small code base you would lose oversight of your code quickly. tryIOError is useful in this regard. And finally rethinking the definition of your errors would also yield easier to understand and a more solid solution. The end result would look something like this:



                module Main where

                import Data.Bifunctor (first)
                import Control.Monad.Except (ExceptT(..), runExceptT)
                import System.Environment (getEnv)
                import System.IO.Error (tryIOError, isDoesNotExistError)

                data MyError = MissingError String
                | SomeIOError IOError
                deriving (Show)

                main :: IO ()
                main = do
                result <- runExceptT printFile
                print result

                getEnv' :: String -> ExceptT MyError IO String
                getEnv' env = mapIOError ("getting env var " ++ env) $ getEnv env

                readFile' :: FilePath -> ExceptT MyError IO String
                readFile' path = mapIOError ("reading file " ++ path) $ readFile path

                printFile :: ExceptT MyError IO String
                printFile = do
                path <- getEnv' "FOLDER"
                readFile' path

                mapIOError :: String -> IO a -> ExceptT MyError IO a
                mapIOError msg = ExceptT . fmap (first mapError) . tryIOError
                where mapError err | isDoesNotExistError err = MissingError msg
                mapError err = SomeIOError err





                share|improve this answer


























                  3












                  3








                  3







                  The suggestion to use ExceptT is of course a good one but IMHO the proposed answer is still somewhat verbose and you can go a bit farther by simply "staying" in the ExceptT monad throughout your code. Also I would not recommend handling IO exceptions all over the place. Even with a small code base you would lose oversight of your code quickly. tryIOError is useful in this regard. And finally rethinking the definition of your errors would also yield easier to understand and a more solid solution. The end result would look something like this:



                  module Main where

                  import Data.Bifunctor (first)
                  import Control.Monad.Except (ExceptT(..), runExceptT)
                  import System.Environment (getEnv)
                  import System.IO.Error (tryIOError, isDoesNotExistError)

                  data MyError = MissingError String
                  | SomeIOError IOError
                  deriving (Show)

                  main :: IO ()
                  main = do
                  result <- runExceptT printFile
                  print result

                  getEnv' :: String -> ExceptT MyError IO String
                  getEnv' env = mapIOError ("getting env var " ++ env) $ getEnv env

                  readFile' :: FilePath -> ExceptT MyError IO String
                  readFile' path = mapIOError ("reading file " ++ path) $ readFile path

                  printFile :: ExceptT MyError IO String
                  printFile = do
                  path <- getEnv' "FOLDER"
                  readFile' path

                  mapIOError :: String -> IO a -> ExceptT MyError IO a
                  mapIOError msg = ExceptT . fmap (first mapError) . tryIOError
                  where mapError err | isDoesNotExistError err = MissingError msg
                  mapError err = SomeIOError err





                  share|improve this answer













                  The suggestion to use ExceptT is of course a good one but IMHO the proposed answer is still somewhat verbose and you can go a bit farther by simply "staying" in the ExceptT monad throughout your code. Also I would not recommend handling IO exceptions all over the place. Even with a small code base you would lose oversight of your code quickly. tryIOError is useful in this regard. And finally rethinking the definition of your errors would also yield easier to understand and a more solid solution. The end result would look something like this:



                  module Main where

                  import Data.Bifunctor (first)
                  import Control.Monad.Except (ExceptT(..), runExceptT)
                  import System.Environment (getEnv)
                  import System.IO.Error (tryIOError, isDoesNotExistError)

                  data MyError = MissingError String
                  | SomeIOError IOError
                  deriving (Show)

                  main :: IO ()
                  main = do
                  result <- runExceptT printFile
                  print result

                  getEnv' :: String -> ExceptT MyError IO String
                  getEnv' env = mapIOError ("getting env var " ++ env) $ getEnv env

                  readFile' :: FilePath -> ExceptT MyError IO String
                  readFile' path = mapIOError ("reading file " ++ path) $ readFile path

                  printFile :: ExceptT MyError IO String
                  printFile = do
                  path <- getEnv' "FOLDER"
                  readFile' path

                  mapIOError :: String -> IO a -> ExceptT MyError IO a
                  mapIOError msg = ExceptT . fmap (first mapError) . tryIOError
                  where mapError err | isDoesNotExistError err = MissingError msg
                  mapError err = SomeIOError err






                  share|improve this answer












                  share|improve this answer



                  share|improve this answer










                  answered Nov 22 '18 at 10:37









                  Erick GonzalezErick Gonzalez

                  1544




                  1544






























                      draft saved

                      draft discarded




















































                      Thanks for contributing an answer to Stack Overflow!


                      • Please be sure to answer the question. Provide details and share your research!

                      But avoid



                      • Asking for help, clarification, or responding to other answers.

                      • Making statements based on opinion; back them up with references or personal experience.


                      To learn more, see our tips on writing great answers.




                      draft saved


                      draft discarded














                      StackExchange.ready(
                      function () {
                      StackExchange.openid.initPostLogin('.new-post-login', 'https%3a%2f%2fstackoverflow.com%2fquestions%2f53426475%2fhow-to-simplify-the-error-handling-in-io-either-a-b%23new-answer', 'question_page');
                      }
                      );

                      Post as a guest















                      Required, but never shown





















































                      Required, but never shown














                      Required, but never shown












                      Required, but never shown







                      Required, but never shown

































                      Required, but never shown














                      Required, but never shown












                      Required, but never shown







                      Required, but never shown







                      Popular posts from this blog

                      MongoDB - Not Authorized To Execute Command

                      How to fix TextFormField cause rebuild widget in Flutter

                      Npm cannot find a required file even through it is in the searched directory