Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Compose/bind "Except"s with varying error types by common error type class

Tags:

haskell

I have some functions returning Except types (from transformers package) with varying error types but all implementing the class Show. In case of an error I just want to print the message.

What's the best way to compose/bind them?

I could convert the error types for every fun* before (=<<), or write a (=<<) wrapper that takes all showable types and converts them to Strings (RankNTypes?), but that feels ugly. Is there a better way, using the type system, that handles all that automatically?

Example code:

module Main where

import           Control.Monad.Trans.Except
import qualified Data.Text as T

type StrError = String
type TxtError = T.Text

funA :: String -> Except StrError String
funA = return

funB :: String -> Except TxtError T.Text
funB = return . T.pack

fun :: String -> IO ()
fun s = case runExcept (funB =<< funA s) of
            Left e  -> putStrLn $ show e
            Right _ -> return ()

main :: IO ()
main = fun "foo"
like image 250
snøreven Avatar asked Jan 27 '26 15:01

snøreven


1 Answers

The simplest way would be to create a new Exception type (but this does require -XExistentialQuantification) of exceptions that can be shown.

data Exception = forall e . Show e => Exception e

Then, all that needs to be changed to make your code compile is the type signatures.

funA :: String -> Except Exception String
funB :: String -> Except Exception T.Text

Additionally, whenever you create an exception (of which there are no examples in your code above) you now need to wrap it in the Exception constructor.

throwsA :: String -> Except Exception String
throwsA = throwE . Exception

throwsB :: T.Text -> Except Exception T.Text
throwsB = throwE . Exception

EDIT I would encourage you to make new types for your exceptions (with appropriate Show) then derive Exception from Control.Exception. That is more overhead, but it may benefit you afterwards if you ever need to switch back and forth between heterogeneous exception types. This is the way I would do it.

{-# LANGUAGE DeriveDataTypeable #-}
module Main where

import Data.Typeable
import Control.Exception
import Control.Monad.Trans.Except
import qualified Data.Text as T
import Control.Monad

newtype StrError = StrError String deriving (Show,Typeable)
newtype TxtError = TxtError T.Text deriving (Show,Typeable)

instance Exception StrError
instance Exception TxtError

toErr :: Exception e => Except e a -> Except SomeException a
toErr = mapExcept (either (Left . toException) Right)


funA :: String -> Except StrError String
funA = return

funB :: String -> Except TxtError T.Text
funB = return . T.pack

throwsA :: String -> Except StrError String
throwsA = throwE . StrError

throwsB :: T.Text -> Except TxtError T.Text
throwsB = throwE . TxtError


fun :: String -> IO ()
fun s = case runExcept $ (toErr . funA >=> toErr . funB) s of
            Left e  -> putStrLn $ displayException e
            Right _ -> return ()

main :: IO ()
main = fun "foo"
like image 89
Alec Avatar answered Jan 30 '26 06:01

Alec