Sunday, January 24, 2010

Pure, extensible exceptions and self-returning functions

> {-# LANGUAGE MultiParamTypeClasses
> , FunctionalDependencies
> , FlexibleInstances
> , FlexibleContexts
> , UndecidableInstances
> , OverlappingInstances
> , TypeFamilies
> , TypeSynonymInstances
> , ScopedTypeVariables
> , NoMonomorphismRestriction
> #-}



I'm sorry, it's rude to enable type system extensions, before introducing yourself, so: Hi, my name is Bartek and I'm an addict. I started doing Haskell 3 years ago, because everyone else in my programming class did so. I know, that peer pressure is the oldest excuse in the book, but that's the way it is. In the beginning, everything was great - it felt wonderful. Finally, I was able to write programs without the usual, imperative problems (such as off-by-one errors), thanks to regular functional programming features - recursion and pattern matching. Creating programs, that worked the first time they compiled, was exhilarating. And purity, the most noble thing any piece of code can achieve. Pure programs are never gonna make you cry, never gonna say goodbye, never gonna tell a lie and hurt you.

But it wasn't all fun and games. The types. At first, they helped me to write programs, then it turned into an obsession. Compulsive need to turn every possible programming error into statically checked type error, consumed my soul. Soon, it was impossible for me to code anymore - inability to express the proper solution in types and constant strive for perfection rendered me unable to accept inferior solutions.
Would I stop myself, three years ago, from writing the first fold? Of course not, I choose to believe what I was programmed to believe.

OK, enough of that, it probably wasn't funny anyway.


So... exceptions. They always fascinated me, since I understood the Either monad:


> instance Monad (Either e) where
> fail s = error$"The 90's called, they want their 'fail' back. also: " ++ s
> return = Right
> Left e >>= _ = Left e
> Right x >>= f = f x

No more magic explanations about walking the stack, just a simple, direct implementation of exception semantic.

But, there was a problem - there were many ways to report errors - haskell-8-ways-to-report-errors but even using the most advanced one (I obviously don't consider anything IO-related), MonadError with ErrorT monad transformer was still too weak to use comfortably with different types of errors, because it wasn't extensible.

I couldn't accept, that such an inferior language as Java had such a great exception system, whereas we, god's chosen people of Haskell, were destined to live in shame of using dynamically typed and imperative hacks to use extensible exception mechanism. The very thing, that we grew up in opposition to, became the foundation of our libraries. What is worse, it didn't stop people from lying with straight face to others, about virtues of purity and the power of type system of Haskell.

It took me 2 years of studying teachings of Oleg Kiselyov (who was raised among types, where he learned to speak their language), but finally, I have the solution. It's so simple, that you're probably wondering why it took me 2 years. Well, I've wasted a lot of time, that's my specialty.

I'm about to release a library - pure-exception (repository is available. needs some more polishing of haddock docs and cabal stuff) that provides means to use computations with checked, extensible and hierarchical exceptions. If you're wondering why do we need another exception library (especially after control-monad-exception), we don't. It has some practical advantages over control-monad-exception:

  • absolutely no boilerplate needed
  • better API (similar to MonadError, which is already familiar to many haskellers)
  • better error messages (for minimal amount of boilerplate - 4 tokens per exception type)

But, I suspect control-monad-exception could evolve into something similar.

The biggest difference, and the main reason behind pure-exception, is implementation - it's not based on Control.Exception from extensible-exceptions package. Some properties:

  • the exception mechanism is pure - no unsafePerformIO inside
  • all functions are total - there are no missing cases and not a single 'undefined' token is used.
  • it's statically typed - no unsafeCoerce, cast or Typeable.

Pure, total and statically typed - the way god intended programs to be written.

It relies on type-level programming, thus uses type system extensions. Which ones? Short answer - all of them. Better answer:

  • MultiParamTypeClasses
  • FunctionalDependencies
  • OverlappingInstances
  • IncoherentInstances - needed to provide extra functionality, not required for core functionality
  • GADTs - not really required, they make implementation nicer (type-level code should also be pretty!)
  • UndecidableInstances
  • TypeFamilies - TypeFamilies are only used for equality constraints, there are no actual type families used. Equality constraints could be substituted with TypeCast from HList
  • 'lazy instance selection' - not an extension, but type-checker property. This means, that the solution is ghc-only.

You're probably thinking, that it's not practical to use these extensions, that such code belongs on Oleg's website and we would be better off with Dynamics. Here's a fun fact: I've tried reimplementing exception mechanism described in the paper behind extensible-exceptions library, I've written some code that type-checked but didn't work and it took me a lot of time to find the bug. That's not the Haskell way. But maybe it's because I'm stupid, right? Well according to the footnote on page 4 of that paper, even Simon Marlow introduced a bug, that was spotted by someone else. It's hard to be smarter than Simon Marlow (*), so it's clearly the wrong way of programming.

(*) - unless you are Simon Marlow

On the other hand, when I was writing my code, with all those extensions (that supposedly lead to problems) and multiple redesigns, I didn't find a single bug in a code that type-checked. Not even some stupid mistake that's spotted 5 seconds after compilation. That's the way I want to code.


If you have objections to checked exceptions, then riddle me this: you like Haskell (otherwise why are you reading this?), you love when your programs work on the first try, because purity and rich types help creating correct programs, right? Don't you think, that there's a coincidence between that and the fact, that you cannot implement in Haskell unchecked exceptions, without using unsafePerformIO? "But, checked exceptions force me to" - great! Every time some application crashes for me with NullPointerException, I'd love to force something into some body part of some developer. My shoe of course.


OK, so let's see some code. Here's a simple, partial (escape function is partial) monad (not transformer) for computations with extensible exceptions.

But first, a warm-up. Self-returning functions. What's a self-returning function? It's a function that (sometimes, no point if it always does) satisfies the equation:
foo x = foo

Some of you probably think "it's not possible... Hindley-Milner...", well, have you considered switching to SML?

Others know, that it's possible to sprinkle it with newtypes, Ins, outs and it would work.

No! We'll ram it down ghc's throat and it better like it.

> class Foo x y | x -> y where
> foo :: x -> y

instance Foo x y => Foo z (x->y) where

foo x = foo


Unfortunately, with only one instance and functional dependency, ghc will try to simplify the type of foo to:

z1 -> z2 -> z3 -> ....

and it results in a loop.

To stop it from simplifying, we have to add another instance, so the type stays polymorphic, with an explicit Foo context. It also makes sense, for foo to only sometimes return itself, otherwise it's useless.

> instance Foo String String where
> foo = id

Now, the previous instance cannot be added, because functional dependencies don't play along with overlapping instances. There is the usual solution of TypeCasts.

But it's also possible to use equality constraints:

> instance (b ~ (x->y), Foo x y) => Foo a b where
> foo x = foo

*Main> :t foo
foo :: (Foo x y) => x -> y
*Main> :t foo ()
foo () :: (Foo x y) => x -> y
*Main> :t foo () 'h'
foo () 'h' :: (Foo x y) => x -> y
*Main> foo () 'h' "Hello World!"
"Hello World!"


Let's evolve Foo. First modification is for foo to carry a String in its closure, and use it in the end:

> class Foo2 x y | x -> y where
> foo2 :: String -> x -> y

> instance Foo2 String String where
> foo2 s = (s++)

> instance (b ~ (x->y), Foo2 x y) => Foo2 a b where
> foo2 s _ = foo2 s

*Main> :t foo2 "Hello"
foo2 "Hello" :: (Foo2 x y) => x -> y
*Main> :t foo2 "Hello" ()
foo2 "Hello" () :: (Foo2 x y) => x -> y
*Main> foo2 "Hello" () " World!"
"Hello World!"


Second modification will invert the thing a little - the 'base' case will accept a function, and apply to it the String it carries:
> class Foo3 x y | x -> y where
> foo3 :: String -> x -> y

> instance Foo3 (String->v) v where
> foo3 s f = f s

> instance (b ~ (x->y), Foo3 x y) => Foo3 a b where
> foo3 s _ = foo3 s

*Main> :t foo3 "!dlroW olleH"
foo3 "!dlroW olleH" :: (Foo3 x y) => x -> y
*Main> :t foo3 "!dlroW olleH" ()
foo3 "!dlroW olleH" () :: (Foo3 x y) => x -> y
*Main> foo3 "!dlroW olleH" () (\(s::String) -> reverse s)
"Hello World!"


The type of the final function has to be ground/monomorphic.

Next modification is to parametrize over Strings:

> class Foo4 e x y | x -> y where
> foo4 :: e -> x -> y

> instance Foo4 e (e->v) v where
> foo4 e f = f e

> instance (b ~ (x->y), Foo4 e x y) => Foo4 e a b where
> foo4 s _ = foo4 s

*Main> foo4 "!dlroW olleH" () (\(s::String) -> reverse s)
"Hello World!"
*Main> foo4 'c' () Char.toUpper
'C'


But what does it have to with exceptions? Well, here's the final modification: the case that ignores its argument and returns itself, now will return itself wrapped in Left. The name of the class also changes:

> class Throws e x y | x -> y where
> throws :: e -> x -> y

> instance Throws e (e->v) v where
> throws e f = f e

> instance (b ~ Either (x->y) z, Throws e x y) => Throws e a b where
> throws s _ = Left $ throws s

Whatever this is, it sure is extensible:

*Main> :t throws ()
throws () :: (Throws () x y) => x -> y
*Main> :t throws ""
throws "" :: (Throws [Char] x y) => x -> y
*Main> :t if True then throws "" else throws ()
if True then throws "" else throws ()
:: (Throws [Char] x y, Throws () x y) => x -> y

What about the following functions?

> raise = Left . throws

> Left  e `handle` h = e h
> Right x `handle` _ = Right x

> runEither (Right x) = x

*Main> :t raise ()
raise () :: (Throws () x y) => Either (x -> y) z
*Main> :t raise ""
raise "" :: (Throws [Char] x y) => Either (x -> y) z
*Main> :t if True then raise "" else raise ()
if True then raise "" else raise ()
:: (Throws [Char] x y, Throws () x y) => Either (x -> y) z


Now this becomes possible (types are inferred automatically):

> data Expr = Const Int | Div Expr Expr deriving (Show, Read)
> data ParseError = ParseError
> data DivByZero = DivByZero

> parse :: (Read a, Throws ParseError x y) => String -> Either (x -> y) a
> parse s = case reads s of
> [(e,"")] -> return e
> _ -> raise ParseError

> evalExpr :: (Throws DivByZero x y) => Expr -> Either (x -> y) Int
> evalExpr (Const n) = return n
> evalExpr (Div e1 e2) = do
> v1 <- evalExpr e1
> v2 <- evalExpr e2
> if v2 == 0 then
> raise DivByZero
> else
> return $ v1 `div` v2

> calc :: (Throws ParseError x y, Throws DivByZero x y) => String -> Either (x -> y) Int
> calc s = parse s >>= evalExpr

It's not possible to run a computation, without handling all exceptions:

*Main> runEither $ calc "Div (Const 2) (Const 0)"

:1:12:
Overlapping instances for Throws ParseError x y
...

:1:12:
Overlapping instances for Throws DivByZero x y

*Main> runEither $ calc "Div (Const 2) (Const 0)" `handle` (\ParseError -> return 0)

:1:12:
Overlapping instances for Throws DivByZero x y


And finally:

> main = getLine >>= print . calc'
> where calc' s = runEither $ calc s `handle` (\ParseError -> return 0) `handle` \DivByZero -> return (-1)


If you like the idea, please take a look at pure-exception library, it has much better API than this, and it's more powerful. There are plenty of examples at patch-tag

Suggestions are very welcome. Both regarding library and my blog. I know my english is broken (but, what would you expect from someone, who learned the language by watching Family Guy and reading dirty stories on the internet).