Skip to content

Instantly share code, notes, and snippets.

@gelisam
Last active February 21, 2022 13:16
Show Gist options
  • Star 5 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save gelisam/137effb33d2777328d366dcb563d8d13 to your computer and use it in GitHub Desktop.
Save gelisam/137effb33d2777328d366dcb563d8d13 to your computer and use it in GitHub Desktop.
Keeping track of which errors have and haven't been handled
-- in response to https://www.parsonsmatt.org/2018/11/03/trouble_with_typed_errors.html
{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses #-}
module CouldBe where
import Control.Monad
import Data.Void
-- Here is an alternate, much simpler solution to the problem of keeping track of which errors have
-- and haven't been handled. It doesn't use prisms nor generics, it simply uses the monad
-- transformers trick under a different guise.
-- 'makePrisms' is fine, but since I only need 'review', we can use a much simpler typeclass.
class CouldBe a e where
inject :: a -> e
-- As in the original article, we use one type per error and we take advantage of the fact that
-- constraints are unordered to automatically combine the set of errors which can be thrown by
-- different parts of a computation.
throw :: CouldBe a e
=> a -> Either e r
throw = Left . inject
data E1 = E1
data E2 = E2
data E3 = E3
head1 :: CouldBe E1 e
=> [a] -> Either e a
head1 [] = throw E1
head1 (x:_) = pure x
head2 :: CouldBe E2 e
=> [a] -> Either e a
head2 [] = throw E2
head2 (x:_) = pure x
head3 :: CouldBe E3 e
=> [a] -> Either e a
head3 [] = throw E3
head3 (x:_) = pure x
throwalot :: (CouldBe E1 e, CouldBe E2 e, CouldBe E3 e)
=> [[[[a]]]] -> Either e a
throwalot = head1 >=> head2 >=> head3 >=> head1
-- Also as in the original article, we specialize @forall e. (CouldBe E1 e, CouldBe E2 e) => e@ to
-- @_ => Either E1 e'@ in order to handle the @E1@ case. Unlike the original article, the remaining
-- constraint is not a mess of generics stuff, but rather another nice list of 'CouldBe'
-- constraints: @forall e'. CouldBe E2 e' => Either E1 e'@.
handle :: (a -> r)
-> Either (Either a e) r
-> Either e r
handle _ (Right r) = Right r
handle handler (Left (Left a)) = Right (handler a)
handle _ (Left (Right e)) = Left e
handleSome :: CouldBe E2 e
=> a -> a -> [[[[a]]]] -> Either e a
handleSome a1 a3 = handle (\E1 -> a1)
. handle (\E3 -> a3)
. throwalot
-- In particular, once all the 'CouldBe' constraints are handled, the remaining set of constraints
-- is empty, so we can specialize @forall e. e@ to 'Void' and get rid of the 'Either'.
handled :: Either Void r -> r
handled = either absurd id
handleAll :: a -> a -> a -> [[[[a]]]] -> a
handleAll a1 a2 a3 = handled
. handle (\E2 -> a2)
. handleSome a1 a3
-- All right, time to reveal the magic. Notice that if we had defined a 'MonadExcept' variant for
-- each exception type, 'MonadExceptE1', 'MonadExceptE2', etc., we would also have a working
-- solution:
-- 'throwalot' would have had the constraint @(MonadExceptE1 m, MonadExceptE2 m, MonadExceptE2 m)@,
-- 'handleSome' would partially specialize the monad stack to @MonadExceptE2 m' => ExceptE1T (ExceptE3T m') a@,
-- and so on. This is the strategy I rely on in my on-error package (https://github.com/Simspace/on-error).
--
-- If we boil down the above monad transformers solution to its bare essentials, we realize that it
-- is the O(n^2) instances which monad transformers are infamous for which do all the work. So we
-- can write down O(n^2) 'CouldBe' instances explaining how each pair of error types interact with
-- each other:
instance CouldBe E1 e => CouldBe E1 (Either Void e) where inject = Right . inject
instance CouldBe E2 e => CouldBe E2 (Either Void e) where inject = Right . inject
instance CouldBe E3 e => CouldBe E3 (Either Void e) where inject = Right . inject
instance CouldBe E1 (Either E1 e) where inject = Left
instance CouldBe E2 e => CouldBe E2 (Either E1 e) where inject = Right . inject
instance CouldBe E3 e => CouldBe E3 (Either E1 e) where inject = Right . inject
-- ...and so on. And, like with the real monad transformers, we can reduce the O(n^2) requirement to
-- O(n) if we're willing to use overlapping instances:
instance CouldBe E2 (Either E2 e) where inject = Left
instance {-# OVERLAPPABLE #-} CouldBe a e => CouldBe a (Either E2 e) where inject = Right . inject
instance CouldBe E3 (Either E3 e) where inject = Left
instance {-# OVERLAPPABLE #-} CouldBe a e => CouldBe a (Either E3 e) where inject = Right . inject
-- That's it! Now when we use 'handle' on an 'E1' handler and on a body of type
-- @forall e'. (CouldBe E1 e', CouldBe E2 e', CouldBe E3 e') => Either e' r@, that @e'@ gets
-- specialized to @Either E1 e@. Ghc then finds and discharges the three 'CouldBe' instances for
-- this type:
--
-- instance CouldBe E1 (Either E1 e)
-- instance CouldBe E2 e => CouldBe E2 (Either E1 e)
-- instance CouldBe E3 e => CouldBe E3 (Either E1 e)
--
-- Which is how we end up with the clean residual constraint @(CouldBe E2 e, CouldBe E3 e)@.
@gelisam
Copy link
Author

gelisam commented Nov 9, 2018

Here is a version which throws and tracks exceptions instead of Lefts: https://gist.github.com/gelisam/187f54494da03855890698ed96c65bef

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment