Sunday, May 27, 2012

Conduit bugs

I want to preface this by saying that this post is not intended to be mean-spirited and I will offer some insights on how to fix these problems.

I often find that violations of type-class laws almost invariably lead to subtle bugs, which is why I go to so much effort to ground my pipes library in theoretically-derived type-classes and enforce their corresponding laws very strictly. In this post I'm going to illustrate the importance of this for conduit by showing several conduit bugs and demonstrating how they stem directly from type-class law violations. I based these bugs on conduit-0.4.2.


Conduits violate the Monad laws


... specifically, associativity:
printer = NeedInput (\a -> lift (print a) >> printer) (return ())

residue x = Done (Just x) ()
>>> yield 1 $$ printer
1
>>> yield 1 $$ (residue 2 >> residue 3) >> printer
2
1
>>> yield 1 $$ residue 2 >> (residue 3 >> printer)
3
2
1
The left-associative grouping accidentally drops residual input. There are two cases where conduits suffer from data loss, and one of them corresponds to violating the associativity law for monads.

The next example is a bigger problem:
mySink = NeedInput (\_ -> return ())
                   (lift $ putStrLn "Finalize Resource)
>>> yield 1 $$ (yield 1 >> (residue 3 >> mySink)) =$ return ()
-- No output
>>> yield 1 $$ ((yield >> residue 3) >> mySink) =$ return ()
Finalize Resource
The right-associative grouping accidentally drops the finalizer. Conduits don't guarantee deterministic finalization in certain corner cases, again because they violate the monad laws.

More generally, any conduit that sequences two buffered conduits is prone to the above two bugs. The source of both violations is the attempt to "push back" input by attaching residual input to the Done constructor. I can't yet offer a solution for this because I have not yet tackled the parsing problem, however removing this feature will at least prevent the above case of dropped finalizers.


Conduits violate the Category laws


I know that conduits do not advertise being a Category, but I investigated where conduits deviated from a Category and found more bugs in the process.

For example, conduits lack an identity conduit. This is apparent from the type of conduit composition:
(=$=) :: Monad m
 => Pipe a b m () <-- This needs to be fixed
 -> Pipe b c m r
 -> Pipe a c m r
The upstream conduit is constrained to return (), so you immediately lose the ability to return values from upstream like you can with pipes and you cannot form a proper upstream identity pipe. However, we could type-restrict composition to only return () and see if that forms a category, even if not necessarily as powerful as the pipes category:
(=$=) :: Monad m
 => Pipe a b m ()
 -> Pipe b c m ()
 -> Pipe a c m ()
The closest this composition comes to an identity conduit is:
idC = await >>= maybe (return ()) (\a -> yield a >> idC)
Unfortunately, idC does not serve as an identity conduit when you place it upstream of a conduit:
inject x p = case p of
    NeedInput _ p' -> yield x =$= p';
    p' -> p'

print2 = replicateM_ 2 (await >>= lift . print)
>>> yield 1 $$ inject 2 print2
Nothing
Just 2
>>> yield 1 $$ inject 2 (idC $= print2)
Nothing
Nothing
This seemingly innocuous identity law violation actually represents a known subtle bug in conduits where if they are fed a Nothing followed by a Just x they break. Some conduit library code depends on this scenario never happening in order to guarantee safety and correctness. Michael already knows this, because he notes this in the comments of composition:
-- [...] However, it is not
-- recommended to give input to a pipe after it has
-- been told there is no more input. [...]
I find it interesting that despite not attempting to make conduits a category, the invariant Michael requires is precisely the invariant necessary to make the identity law work. This exemplifies how even when we don't program using theoretical constructs, our intuition for correct behavior exactly matches the laws for the theoretically-grounded classes.

The lack of a proper upstream identity is also a source of data loss. When you compose two pipes, the residual input for the downstream pipe is discarded under all circumstances, and there is no way to solve this without introducing a proper upstream identity conduit.

pipes has solved this issue, but the solution is precisely what necessitated the parametrized monad and I can discuss this with Michael if he is interested because I think he would not be as reluctant to use extensions to allow do notation for parametrized monads. The other advantage of switching to the pipes solution is that you gain the ability to finalize upstream early without terminating, which conduit does not presently have.


Conduits violate Monad Transformer laws


This is my fault. The first release of my library violated the monad transformer laws and while I've fixed it in version 2.0, conduit still has the original version found in pipes.

The original version violates both the identity and composition laws of monad transformers. You can see this if you just count the number of PipeM constructors generated:
count' n c = case c of
    Done i _ -> Done i n
    PipeM m h -> PipeM (liftM (count (n + 1)) m) h
    HaveOutput c' h o -> HaveOutput (count n c') h o
    NeedInput f c' -> NeedInput (fmap (count n) f) (count n c')

count = count' 0
-- lift (return x) /= return x
>>> runPipe $ count $ lift $ return (-99)
1
>>> runPipe $ count $ return (-99)
0

-- lift (m1 >> m2) /= lift m1 >> lift m2
>>> runPipe $ count $ lift $ return (-99) >> return (-99)
1
>>> runPipe $ count $ lift (return (-99)) >> lift (return (-99))
2
This is the reason I switched to using an approach based on a free monad transformer (i.e. FreeT), instead of using an ordinary free monad.

This makes the monad bind mandatory at each step, which actually leads to very little degradation of performance, so I had no problem making the switch. More importantly, though, it allows more powerful optimizations using rewrite rules than are currently possible when the monad is optional. For example, the following rewrite rule is safe once you have a correct instance for MonadTrans:
{-# RULES
  "forever alone" forall m.  forever (lift m) = lift (forever m)
  #-}
I will discuss rewrite rules later in a post about optimizing pipes and frames, but one of my big motivations for strictly enforcing all the class laws as strong as possible is that it then permits rewrites so powerful that all the pipe code completely disappears, leaving behind the hand-written loop code (think: stream fusion on steroids).


Other bugs


There are other bugs in conduits that I found in the process, mainly associated with registering finalizers. For example, conduits has a nasty habit of releasing resources multiple times, but this is hidden by the ResourceT machinery which ignores duplicate resource release requests.

However, this is quite easy for conduits to fix. All you do is remove the finalizer field from the PipeM constructor and have pipeClose ignore PipeM actions completely, only associating finalizers with HaveOutput. This fixes the issue of multiple finalizations and also fixes the issue of accidentally drawing one last chunk of data before finalizing if you aren't careful about writing the source.

Even if you fix that, though, there are still other finalization problems. For example, while Michael provides a mechanism for bidirectionally-safe finalization, he never uses it for sources and sinks, meaning that if you elevate them to conduits they won't finalize correctly, however this is easy to fix and he will know how to do it. He also never exposes any utility functions for bidirectionally-safe finalization that is an equivalent to the finallyP in pipes.


Discussion


This post presents some examples where if you are close to a theoretically-grounded type-class but not quite there, the difference is most likely a bug. This means that you can identify bugs in a library rapidly just by examining where it approximates theoretical type-classes and then studying where they fail to observe the corresponding class laws.

Monday, May 21, 2012

pipes 2.0 - Pipe Finalization

I'm happy to announce that pipes-2.0 now includes an elegant and sound way to finalize resources promptly and deterministically. You can find the latest version of the library here.

Before I continue I want to acknowledge Paolo Capriotti, who contributed a lot of instrumental discussion that led to this solution, particularly for how to manage downstream finalization.

The library introduces a new higher order data-type called a Frame complete with its own Category that you can use to solve all your finalization problems. It's layered on top of ordinary Pipes and it has plenty of nice properties that fall out of enforcing the Category laws. However, this post is not documentation, so I encourage you to read the expanded tutorial, starting from the "Frames" section before you continue.

The real topic of this post is a really quick and dirty meta-discussion containing a lot of comments on the release that didn't belong in the documentation. I will also touch upon issues with finalization that I grappled with when working on finalizing pipes while satisfying the Category laws. I'm hoping it will help guide other iteratee libraries which might have different goals but still deal with the same issues. I will discuss these topics in more depth in future posts, but I felt all of these are worth briefly mentioning right now.


Parametrized Monads


The first big issue is that prompt finalization is inherently not a monad, but rather a parametrized monad. By prompt finalization, I mean the finalizing upstream resources before the current pipe is done. What we'd like is some sort of way to write:
do  someCode
    finalizeUpstream
    codeThatCan'tAwait
The problem is that if it's a monad, there is no restriction on the ordering of commands, so nothing prevents the user from calling an await after upstream is finalized. With a parametrized monad (a.k.a. an indexed monad) and GADTs, you can solve this problem by marking the finalization point with a phantom type that marks upstream has been finalized. There are actually more elegant ways to do it, but that's the most straightforward way. To learn more about parametrized monads, I highly recommend Dan Piponi's introduction to them.

However, for the time being I chose to not use parametrized monads and stuck to just splitting it into two separate monads: one for before finalizing upstream and one for after finalizing upstream. The first monad would would return the second one as a return value, so you have something that looks like:
Pipe a b m (Producer b m r)
The second block is forbidden from awaiting anything other than (), so you can safely finalize upstream at the transition between the two monads.

Besides avoiding extensions, there is a more important reason that I haven't released a version of pipes that uses parametrized monads. It turns out you can use them to communicate more complicated session types than just ordinary streams and I wanted more time to experiment that with generalization of pipes before incorporating it into the library.

The choice not to use parametrized monads complicated the underlying type for Frame slightly, but when I do include parametrized monads, it should clean up the type considerably. What that means for now is that there are two types you switch between, one of which is a Monad (the Ensure type), and the other which is a Category (the Frame) type. Once I figure out the most elegant way to do parametrized monads they should become the same type. Fortunately, it's not hard to switch between them and the documentation explains their relationship, especially Control.Pipe.Final, which goes into more depth about the types.

Directionality


Another issue that I grappled with was whether or not bidirectional pipes can possibly form a Category. Bidirectional pipes would have made finalization a lot easier, but unfortunately I could never come up with a solution that formed a proper Category. I can't definitively rule out the possibility of them, but I am reasonably sure that you can't implement them and retain anything that remotely resembles my original Pipe type. That's obviously a vague statement since I can't quantify my notion of what it means to resemble the original Pipe type.

The key breakthrough in designing finalized pipes was to not fight the unidirectionality of pipes at all and to instead just "go with the flow" (literally). This means that I had to use two separate tricks to ensure that finalization worked in both directions. This was disconcerting at first until I noticed a very general dual pattern underlying the two tricks that emerged...


Monoids


So let's imagine for a second that I'm right and pipes really must be unidirectional if you want to form a category. Now let's try to figure out how to finalize pipes correctly if a downstream pipe terminates before them. Well, if pipes are unidirectional, there is absolutely no way to communicate back upstream that the pipe terminated. Instead, we just "go with the flow" and do the reverse: every time a pipe yields it passes its most up-to-date finalizer alongside the yielded value. Downstream pipes are then responsible for calling the finalizers passed to them if they terminate first before awaiting a new value from the pipe that yielded.

What composition does is remember the last finalizer each frame yielded (defaulting to the empty finalizer for pipes that haven't run yet) then it combines the most current finalizer of each pipe with the most current finalizers of every pipe upstream. So if we had three pipes composed like so:
p1 <-< p2 <-< p3
Then you can make a diagram showing how finalizers are combined automatically by composition behind the scenes:
               p1    <-<     p2   <-<   p3
-----------------------------------------------
               f1            f2         f3
               |             |          |
               v             v          v
<-(f3*f2*f1)-< * <-(f3*f2)-< * <-(f3)-< * <-(1)
... where I'm using (*) to denote mappend (i.e. monoid multiplication), and 1 to denote mempty (i.e. monoid unit). f1 would be the most up-to-date finalizer of pipe p1, f2 would be the most up-to-date finalizer of pipe p2, and f3 would be the most up-to-date finalizer of pipe p3. The monoid in this case is just monad sequencing where (*) = (>>) and 1 = return ().

So let's say that pipe p1 were to close its input end. Composition would then take the collected upstream finalizers coming into pipe p1, which in this case is (f3*f2) = f3 >> f2, and call them since it knows it is safe to finalize them.

All of this occurs completely behind the scenes. From the user's perspective, all they do is yield the individual finalizers alongside ordinary output and the process of collecting finalizers and calling them upon termination is completely a black box:
               p1           p2           p3
----------------------------------------------
               f1           f2           f3
               |            |            |
               v            v            v
*******************BLACK**********BOX*********

So the process of collecting upstream finalizers and running them behaves like a monoid under the hood where it folds all the upstream finalizers towards the pipe that is terminating so that it knows exactly what to call to finalize all of them. Where it gets really interesting is that finalizing downstream behaves dually as a comonoid.


Comonoids


Finalizing downstream can use the ordinary metaphor of exception propagation. It's not quite as trivial as it sounds (and it was in fact the harder of the two halves to get correct, surprisingly), but if you understand exceptions you are 90% of the way towards understanding how to finalize downstream pipes.

Once you get this, it's not hard to see how this behavior is inherently comonoidal. All we have to do is reverse all the arrows in our previous diagram:
          p1  >->   p2  >->   p3
-------------------------------------
          e         e         e 
          ^         ^         ^
          |         |         |
e >-(e)-> * >-(e)-> * >-(e)-> * >-> 1
Now, this time (*) is comultiplication and 1 is counit. Comultiplication consists of splitting off the exceptional value for each pipe to handle, which ensures that no pipe accidentally swallows the exception. Counit discards the exception and doesn't bother to handle it.

Again, the user doesn't see any of this propagation or unfolding and is not responsible for rethrowing the exception. All the user sees is that they await input and get an exception instead. The rest is a black box automatically handled by composition:
          p1  >->   p2  >->   p3
------------------------------------
          e         e         e 
          ^         ^         ^
          |         |         |
*************BLACK******BOX*********

Synthesis


There is another way to think of how this monoid/comonoid duality solves the issue of unidirectionality. For the upstream half of finalization, the finalizer is transmitted to the exception (which is the termination in this case). For the downstream half, the exception (i.e. termination) is transmitted to the finalizer.

If you study the source code, you'll notice that I define composition as follows:
p1 <-< p2 = mult (return ()) p1 <~< comult p2
Where mult is what does all the monoidal folding of the finalizers, comult is what does the comonoidal unfolding of the exception. (<~<) just simulates the parametrized monad. But where are unit and counit? If you've read the documentation, the answer is that they are right there under your nose in the form of yieldF (which is unit) and awaitF (which is counit). And if you check out the definition for the identity frame, it is just:
idF = forever $ awaitF >>= yieldF
In other words, idF is both the unit for the monoidal fold and the counit for the comonoidal unfold. Diagramatically, this looks like:
... <-(f)-< * <-(f)-< ...
            ^
            |
            1
-------------------------
...   <-<  idF  <-<   ...
-------------------------
            1
            ^
            |
... <-(e)-< * <-(e)-< ...
... where the top half is the monoid and the bottom half is the comonoid.


Strictness


One important mistake I made in the first release of my library was releasing the Strict category, which wasn't a true category. It's easy to see this because it violates one of the identity laws:
(p >> discard) <+< idP /= p
So that got removed from the library in this release, however one thing I realized from countless failed attempts to fix it is that the category of pipes is inherently lazy. However, when I finally solved the finalization issue, I discovered that you could implement strictness anyway on top of the lazy core in a way that is very elegant and compositional and I describe this in the tutorial.

The "inherent" laziness of pipes/frames is important for another reason, though. You'll notice that I mentioned the capability to finalize upstream promptly but I never mentioned being able to finalize downstream promptly before the pipe is done. It turns out this is not possible and in the same way that pipe/frame composition inherently prefers to be lazy, it also prefers to order finalizers from upstream to downstream because it's lazy.

To see why, just spend a minute thinking about what it would mean to finalize downstream before a frame was done under lazy semantics.


Speed


One big problem is that the finalization machinery now incurs a large overhead. Some naive benchmarks I ran show that for IO the frame overhead takes about as much time as the IO operations it manages. However, I have done absolutely nothing to optimize the implementation at all (i.e. no Codensity transformation, no INLINE pragmas, no rewrite rules), so if you are good at optimizing Haskell code and are interested in contributing to the pipes library then I could really use your help as improving speed is a major goal for the next patch. However, I might split the faster code into a separate library if it complicates the source code considerably, because I would like to keep the main library as a reference implementation that is easier to understand.


Exceptions


The implementation only covers finalization for now, but the same principles and techniques can be adapted to solve the issue of exceptions as well. For example, while the implementation currently uses Nothing to transmit the termination exception, it can be modified to transmit a value of any kind (although not as trivially as it sounds!). Similarly, the finalizers need not be limited to the base monad, nor do they even need to be finalizers (or even monads!). Really, anything that is a monoid or comonoid can be used. I chose to go with the simplest and most practical implementation that demonstrates the basic underlying principle in order to give other people ideas.


FreeT


FreeT is the monad transformer version of the free monad that I use to refactor the implementation of the Pipe type (and it's quite common in iteratee/coroutine libraries, where it appears under various names). I'm working with Ross to include it in the transformers package, but until that happens I'm rolling it into the pipes library for now. Once it is added to transformers I will remove it from pipes and use the transformers version, so don't make pipes a dependency for FreeT.


Other Changes


Also, if you haven't been following the library closely, pipes is now BSD-licensed, so feel free to use it as you please.


Conclusion


Like with the original pipe composition, I verified that frame composition enforces the category laws (and this was an extraordinarily tedious and headache-inducing proof). This alone is probably the most significant contribution of this library as it is the only existing implementation that has a finalization mechanism that is:
  • Safe: Finalizers never get duplicated or dropped.
  • Modular: It completely decouples the finalization code of each frame and lets you to reason about their finalization properties independently of each other.
  • Scalable: It is very easy to build long pipelines with no increase in complexity at all.
  • Easy: No glue code is required to chain together the finalization mechanisms of pipes.
You don't have to take my word for it, though. Try it out!

Wednesday, May 2, 2012

Scrap your type classes

Edit: My opinion on type classes has mellowed since I wrote this post, but I still keep it around as a critique against the excesses of type classes.

What I'm about to propose is that all Haskell type class programming can (and should) be implemented purely at the value level using a simple and ordinary code transformation.

The trick is simple and I will begin by transforming the Monad type-class. Given any class:
class Monad m where
    return :: a -> m a
    (>>=)  :: m a -> (a -> m b) -> m b
You can delete the class and replace it with a corresponding data type:
{-# LANGUAGE Rank2Types #-}

-- MonadI = Monad "I"nstance
data MonadI m = MonadI {
    _return :: forall a . a -> m a,
    _bind   :: forall a b . m a -> (a -> m b) -> m b }
Then, given any instance for that class:
instance Monad Maybe where
    return = Just
    m >>= f = case m of
        Nothing -> Nothing
        Just x  -> f x
... delete that instance and replace it with a value of our data type containing the method definitions:
monad'Maybe :: MonadI Maybe
monad'Maybe = MonadI {
    _return = Just,
    _bind   = \m f -> case m of
        Nothing -> Nothing
        Just x  -> f x }
This value-level representation of a class instance has several important benefits.


No class constraints


Now class constraints transform into ordinary parameters:
-- Before
sequence :: (Monad m) => [m a] -> m [a]

-- After
sequence' :: MonadI m -> [m a] -> m [a]
sequence' i x = case x of
    []   -> return []
    m:ms -> m           >>= \x  ->
            sequence' i ms >>= \xs ->
            return (x:xs)
  where
    return = _return i
    (>>=)  = _bind   i

sequence' monad'Maybe [Just 3, Just 4]
= Just [3, 4]
This means that we can now skip type-level programming and implement everything within lambda calculus at the value level. Things that previously required elaborate extensions now only require ordinary Haskell functions.


No more extension hell


Let's say I wanted to implement an isomorphism type class using traditional type classes:
class Isomorphism a b where
    fw :: a -> b
    bw :: b -> a
The first problem is that I'd need to turn on MultiParamTypeClasses to write a class like this.

Now I try to write this instance:
instance Isomorphism ((), a) a where
    fw = snd
    bw = (,) ()
Oops! Now I need FlexibleInstances for the () in the type. That extension's not as controversial, though.

But what if I then do this:
instance (Isomorphism a b, Isomorphism b c)
 => Isomorphism a c where
    fw = fw . fw
    bw = bw . bw
This is completely unresolvable, even using UndecidableInstances. GHC will just barf and terminate after several rounds of recursion.

On the other hand, had I written it like:
data Isomorphism a b = Isomorphism {
    fw :: a -> b,
    bw :: b -> a }
... then I can trivially combine isomorphisms:
combine :: Isomorphism b c -> Isomorphism a b -> Isomorphism a c
combine (Isomorphism fw1 bw1) (Isomorphism fw2 bw2)
    = Isomorphism (fw1 . fw2) (bw2 . bw1)

Haskell is better at value-level programming


The astute reader will notice that the last definition suggests a category. Let's go all the way and rewrite the Category class at the value level and use it:
data CategoryI cat = CategoryI {
    _compose :: forall a b c . cat b c -> cat a b -> cat a c,
    _id      :: forall a . cat a a }

category'Function :: CategoryI (->)
category'Function = CategoryI {
    _compose = \f g x -> f (g x),
    _id      = \x -> x }

category'Isomorphism :: CategoryI Isomorphism
category'Isomorphism = CategoryI {
    _compose = let (.) = _compose category'Function
                in \(Isomorphism fw1 bw1)
                    (Isomorphism fw2 bw2) ->
                       Isomorphism (fw1 . fw2) (bw1 . bw2),
    _id      = let id = _id category'Function
                in Isomorphism id id }
Now we can just combine isomorphisms using ordinary composition:
iso1 :: Isomorphism ((a, b), c) (a, (b, c))
iso1 = Isomorphism {
    _fw = \((a, b), c) = (a, (b, c)),
    _bw = \(a, (b, c)) = ((a, b), c) }

iso2 :: Isomorphism ((), a) a
    _fw = \((), a) = a,
    _bw = \a -> ((), a) }

(.) = _compose category'Function
iso1 . iso2 :: Isomorphism (((), b), c) (b, c)
... instead of attempting a bunch of type-class hackery that doesn't work. More importantly, we can now use our more featureful value-level programming tools to do what was incredibly difficult to do at the type level.


Class maintenance


One big issue in Haskell is maintaining class APIs. However, when we implement classes at the value level, this problem completely disappears.

For example, let's say that I realize in retrospect that my Monad class needed to be split into two classes, one named Pointed to hold return and one named Monad that has Pointed as a superclass. If people use my Monad class extensively, then I'd have to break all their Monad instances if I split it into two separate classes because now they would have to spin off all of their return implementations into separate instances for Pointed.

Now, had I implemented it as a data type, it wouldn't even matter. I'd just write:
data PointedI m = PointedI { _pure :: forall a . a -> m a }

-- Pointed is a super-class of Monad
pointed'Super'Monad :: MonadI m -> PointedI m
pointed'Super'Monad i = PointedI (_return i}
Similarly, I can translate:
class (Pointed m) => Monad m where ...
... into:
monad'Pointed'Bind ::
    PointedI m -> (m a -> (a -> m b) -> m b) -> MonadI m
monad'Pointed'Bind i b = MonadI (_pure i) b
Now users can automatically derive Pointed instances from their old Monad instances, or they can choose to write a Pointed instance and then build a Monad instance on top of it.


Backwards compatibility


Similarly, let's say that I forgot to make Functor a superclass of Monad. What's incredibly painful for the Haskell community to solve at the type-level is utterly straightforward to fix after-the-fact at the value level:
data FunctorI f = FunctorI {
    _fmap :: forall a b . (a -> b) -> f a -> f b }

functor'Monad :: MonadI m -> FunctorI m
functor'Monad i = FunctorI { _fmap = \f x -> x >>= return . f }
  where
    (.)    = _compose category'Function
    (>>=)  = _bind   i
    return = _return i

No more newtypes


Don't you hate having to wrap things using newtypes to get the correct class instance? Well, now that's unnecessary:
data MonoidI m = MonoidI {
    _mempty  :: m,
    _mappend :: m -> m -> m }

monoidSum :: MonoidI Int
monoidSum = MonoidI {
    _mempty  = 0,
    _mappend = (+) }

monoidProduct :: MonoidI Int
monoidProduct = MonoidI {
    _mempty  = 1,
    _mappend = (*) }

mconcat :: MonoidI a -> [a] -> a
mconcat i = foldr (_mappend i) (_mempty i)

sum     = mconcat monoidSum
product = mconcat monoidProduct
Now we're actually writing in a true functional style where sum and product are true functions of the instance, rather than fake functions of a class constraint using awkward newtypes.


Value-level programming is safer


Type classes are used most often for operator overloading. The dark side to this that your overloaded function will type-check on anything that is an instance of that class, including things you may not have intended it to type-check on.

For example, let's say I'm trying to write the following code using the ever-so-permissive Binary class:
main = encodeFile "test.dat" (2, 3)
... but it's 3:00 in the morning and I make a mistake and instead type:
main = encodeFile "test.dat" (2, [3])
This type-checks and silently fails! However, had I explicitly passed the instance I wished to use, this would have raised a compile-time error:
binPair :: BinaryI a -> BinaryI b -> BinaryI (a, b)
binInt  :: BinaryI Int

-- Won't compile!
main = encodeFile (binPair binInt binInt) "test.dat" (2, [3])
You might say, "Well, I don't want to have to annotate the type I'm using. I want it done automatically." However, this is the exact same argument made for forgiving languages like Perl or PHP were people advocate that in ambiguous situations the language or library should attempt to silently guess what you intended to do in instead of complaining loudly. This is exactly the antithesis of a strongly typed language!

Also, in the above case you would have had to annotate it anyway, because Binary wouldn't have been able to infer the specific type of the numeric literals!
main = encodeFile "test.dat" (2 :: Int, 3, :: Int)
Or what if I wanted to implement two different ways to encode a list, one which was the naive encoding and one which used more efficient arrays for certain types:
-- Naive version
instance Binary a => Binary [a] where ...
-- Efficient array version
instance Binary [Int] where ...
Oops! OverlappingInstances! I'd have to wrap one of them in a newtype, which take just as much effort to do as just passing the value instance:
binList :: BinaryI a -> BinaryI [a]
binInt  :: BinaryI Int

main = encodeFile (binList binInt) "listInt.dat" [1..10]
If I was really clever, I could even write implement both instances using the same binList function and then have it select whether to encode a list or array based on the sub-instance passed to it! That's not even possible using type-classes.


No type annotations


Here's another example of an incredibly awkward use of typeclasses:
class Storable a where
    ...
    sizeOf :: a -> Int
Anybody who has ever had to use this knows how awkward it is when you don't have a value of type a to provide it, which is common. You have to do this:
sizeOf (undefined :: a)
That's just horrible, especially when the solution with value-level instances is so simple in comparison:
data StorableI a = Storable {
    ...
    _sizeOf :: Int }

storable'CInt = StorableI {
    ...
    _sizeOf = 4 }
Now we'd just call:
_sizeOf storable'CInt
... instead of using undefined as a hack.

In fact, with value-level instances, type annotations are never ever necessary. Instead of:
readInt :: String -> Int
readInt = read
... or:
read "4" :: Int
... we'd just use:
read read'Int "4"
In other words, the value-level instance is all the information the function needs, and it's guaranteed to be sound and catch incorrect instance errors at compile-time.


Powerful Approach


I wanted to demonstrate that this is a really industrial-strength replacement to type classes, so I took the mtl's StateT, ReaderT, and Identity and implemented them entirely in value-level instances. The code is provided in the Appendix of this post. This implementation allows you to straightforwardly translate:
test :: (MonadState a m, MonadReader a m) => m ()
test = ask >>= put
... into
test :: MonadStateI a m -> MonadReaderI a m -> m ()
test = \is ir -> let (>>=)   = _bind (_monad'Super'MonadState is)
                  in (_ask ir) >>= (_put is)
You can then instantiate test at the value level using any monad instances that implement the State and Reader capabilities and it generates the correct type and implementation:
example1 :: ReaderT a (StateT a Identity) ()
example1 = test
    (monadState'ReaderT $ monadState'StateT $ monad'Identity)
    (monadReader'ReaderT $ monad'StateT $ monad'Identity)

example2 :: StateT a (ReaderT a Identity) ()
example2 = test
    (monadState'StateT $ monad'ReaderT $ monad'Identity)
    (monadReader'StateT $ monadReader'ReaderT $ monad'Identity)

run1 = runIdentity $ runStateT (runReaderT example1 'A') 'B'
run2 = runIdentity $ runReaderT (runStateT example2 'B') 'A'
-- Both output ((), 'A')
Despite the incredible verbosity, it achieves two amazing things:
  • It's implemented with only a single extension: Rank2Types. No UndecidableInstances required.
  • No type signatures or type annotations are necessary. You can delete every single type signature in the file, which is completely self-contained, and the compiler infers every single type correctly. Try it!


More tricks


This is just scratching the surface. This post doesn't even really cover all the things that are only possible with value-level instances like:
  • Generate lenses for instances (example: Lens (Binary [Int]) (Binary Int))
  • Instances parametrized by run-time values
  • Infinite families of instances (i.e. Stream (MyClassI m))
In other words, what I'm trying to say is that value-level instances are right now above us in the "power spectrum" of Haskell programming and you don't really get a feel for how incredibly useful they are until you actually start using them.


Simplicity


Another feature about value-level instances is the conceptual simplicity and elegance. Before there is a type-class checker and a type-checker. Now there is just a type-checker. You don't really appreciate how great this is until you try it and start getting amazingly clear compiler errors. Programming without type-classes is very intuitive! Really, the hardest part about it is simply naming things!

Also, the fact that it's implementable purely using ordinary functional programming is a very big win. If anything, it would make the GHC compiler writer's jobs much easier by not requiring them to entertain any of the half-baked type-class extensions that people propose. This approach allows you to completely remove type-classes from the language. I'm just putting that out there.

Flaws


On that note, that brings me to the last section, where I will frankly discuss all the huge problems with it. The four biggest problems are:
  • No ecosystem for it. To make effective use of it, you'd need new versions of most Haskell libraries.
  • No do syntactic sugar. This one hurts.
  • Verbosity. Every instance has to be named and passed around.
  • Inertia. Programmers used to overloading will be reluctant to start specifying the instance they want.
The first issue is a huge problem and can only be solved if the community agrees this is actually a good idea. I'm only one person and that's about all my opinion counts for. All I can do is mention that more recent data types are already moving in this direction, with Lens (from data-lens) being the best example. Just imagine how impossible it would have been to implement Lens as a class:
class Lens a b where
    get :: a -> b
    set :: b -> a -> a
It fails horrendously, for the exact same reason the Isomorphism class crashes and burns. When implemented as a data type, it works completely flawlessly at the expense of extra verbosity. So if you liked Lens, chances are you'll like value-level instances in general.

The second issue of syntactic sugar can be solved by something like RebindableSyntax and having do notation use whatever (>>=) is in scope. You would then specify which MonadI instance you use for each do block:
let (>>=) = _bind m
 in do ...
... or you pass the MonadI instance as a parameter to the do block.

This is not ideal, unfortunately and ties into the third issue of verbosity. All I can say is that the only way you can understand that the verbosity is "worth it" is if you try it out and see how much more powerful and easier it is than type-class programming. Also, value-level instances admit the exact same tricks to clean up code as normal parameter passing. For example, you can use Reader (MonadI m) to avoid explicitly passing a monad instance around.

However, this still doesn't solve the problem of just coming up with names for the instances, which is uncomfortable until you get used to it and come up with a systematic nomenclature. This is a case where a more powerful name-spacing system would really help.

The last problem is the most insidious one, in my opinion, which is that we as Haskell programmers have been conditioned to believe that it is correct and normal to have operators change behavior silently when passed different arguments, which completely subverts type-safety. I'm going to conclude by saying that this is absolutely wrong and that the most important reason that you should adopt value-level instances is precisely because they are the type-safe approach to ad-hoc polymorphism.


Appendix


The following code implements StateT, ReaderT, Identity, MonadState, and MonadReader from the mtl, along with some example functions. The code is completely self-contained and can be loaded directly into ghci. Every function is annotated with a comment showing how the mtl implements the exact same class or instance so you have plenty of examples for how you would translate the type-class approach into the value-level instance approach.
{-# LANGUAGE Rank2Types #-}

newtype StateT  s m a = StateT   { runStateT   :: s -> m (a, s) }
newtype ReaderT r m a = ReaderT  { runReaderT  :: r -> m a      }
newtype Identity    a = Identity { runIdentity :: a             }

{- class Monad m where
       return :: a -> m a
       (>>=) :: m a -> (a -> m b) -> m b -}
data MonadI m = MonadI {
    _return :: forall a . a -> m a,
    _bind   :: forall a b . m a -> (a -> m b) -> m b }

{- class MonadTrans t where
       lift :: Monad m => m a -> t m a -}
data MonadTransI t = MonadTransI {
    _lift :: forall a m . MonadI m -> m a -> t m a }

{- class Monad m => MonadState s m | m -> s where
       get :: m s
       put :: s -> m ()
       state :: (s -> (a, s)) -> m a -}
data MonadStateI s m = MonadStateI {
    -- This next line is the secret sauce
    _monad'Super'MonadState :: MonadI m,
    _put :: s -> m (),
    _get :: m s,
    _state :: forall a . (s -> (a, s)) -> m a }

{- class Monad m => Monadreader r m | m -> r where
       ask    :: m r
       local  :: (r -> r) -> m a -> m a
       reader :: (r -> a) -> m a -}
data MonadReaderI r m = MonadReaderI {
    _monad'Super'MonadReader :: MonadI m,
    _ask    :: m r,
    _local  :: forall a . (r -> r) -> m a -> m a,
    _reader :: forall a . (r -> a) -> m a }

{- get :: (Monad m) => StateT s m s
   get = StateT $ \s -> return (s, s) -}
get :: MonadI m -> StateT s m s
get i = StateT $ \s -> (_return i) (s, s)

{- put :: (Monad m) => s -> StateT s m ()
   put s = StateT $ \_ -> return ((), s) -}
put :: MonadI m -> s -> StateT s m ()
put i s = StateT $ \_ -> (_return i) ((), s)

{- state :: (Monad m) => (s -> (a, s)) -> StateT s m a
   state f = StateT (return . f) -}
state :: MonadI m -> (s -> (a, s)) -> StateT s m a
state i f = StateT ((_return i) . f)

{- ask :: (Monad m) => ReaderT r m r
   ask = ReaderT return -}
ask :: MonadI m -> ReaderT r m r
ask i = ReaderT (_return i)

{- local :: (Monad m) =>
       (r -> r) -> ReaderT r m a -> ReaderT r m a
   local f m = ReaderT $ runReaderT m . f -}
local :: MonadI m -> (r -> r) -> ReaderT r m a -> ReaderT r m a
local _ f m = ReaderT $ runReaderT m . f

{- reader :: (Monad m) => (r -> a) -> ReaderT r m a
   reader f = ReaderT (return . f) -}
reader :: MonadI m -> (r -> a) -> ReaderT r m a
reader i f = ReaderT ((_return i) . f)

{- instance Monad (Identity) where
       return = Identity
       m >>= k = k $ runIdentity m -}
monad'Identity :: MonadI Identity
monad'Identity = MonadI {
    _return = Identity,
    _bind = \m k -> k $ runIdentity m }

{- instance (Monad m) => Monad (StateT s m) where
       return a = state $ \s -> (a, s)
       m >>= k  = StateT $ \s -> do
           (a, s') <- runStateT m s
           runStateT (k a) s' -}
monad'StateT :: MonadI m -> MonadI (StateT s m)
monad'StateT i =
    let (>>=) = _bind i
     in MonadI {
            _return = \a -> state i $ \s -> (a, s),
            _bind   = \m k -> StateT $ \s ->
                          runStateT m s >>= \(a, s') ->
                          runStateT (k a) s' }

{- instance (Monad m) => Monad (ReaderT s m) where
       return = lift . return
       m >>= k = ReaderT $ \r -> do
           a <- runReaderT m r
           runReaderT (k a) r -}
monad'ReaderT :: MonadI m -> MonadI (ReaderT s m )
monad'ReaderT i =
    let return = _return i
        (>>=) = _bind i
        lift = _lift monadTrans'ReaderT i
     in MonadI {
            _return = lift . (_return i),
            _bind = \m k -> ReaderT $ \r ->
                runReaderT m r >>= \a ->
                runReaderT (k a) r }

{- instance MonadTrans StateT where
       lift m = StateT $ \s -> do
           a <- m
           return (a, s) -}
monadTrans'StateT :: MonadTransI (StateT s)
monadTrans'StateT = MonadTransI {
    _lift = \i m ->
        let return = _return i
            (>>=)  = _bind   i
         in StateT $ \s ->
                m >>= \a ->
                return (a, s) }

{- instance MonadTrans ReaderT where
       lift m = ReaderT (const m) -}
monadTrans'ReaderT :: MonadTransI (ReaderT r)
monadTrans'ReaderT = MonadTransI {
    _lift = \_ m -> ReaderT (const m) }

{- instance (Monad m) => MonadState s (StateT s m) where
       get = get -- from Control.Monad.Trans.State
       put = put
       state = state -}
monadState'StateT :: MonadI m -> MonadStateI s (StateT s m)
monadState'StateT i = MonadStateI {
    _monad'Super'MonadState = monad'StateT i,
    _get   = get   i,
    _put   = put   i,
    _state = state i }

{- instance (MonadState s m) => MonadState s (ReaderT r m) where
       get   = lift get
       put   = lift . put
       state = lift . state -}
monadState'ReaderT ::
    MonadStateI s m -> MonadStateI s (ReaderT r m)
monadState'ReaderT i =
    let monad'm = _monad'Super'MonadState i
        lift = _lift monadTrans'ReaderT monad'm
     in MonadStateI {
            _monad'Super'MonadState = monad'ReaderT monad'm,
            _get   = lift $ _get   i,
            _put   = lift . _put   i,
            _state = lift . _state i }

{- instance Monad m => MonadReader r (ReaderT r m) where
       ask = ask
       local = local
       reader = reader -}
monadReader'ReaderT :: MonadI m -> MonadReaderI r (ReaderT r m )
monadReader'ReaderT i = MonadReaderI {
    _monad'Super'MonadReader = monad'ReaderT i,
    _ask    = ask    i,
    _local  = local  i,
    _reader = reader i }

{- instance (MonadReader r m) => MonadReader r (StateT s m) where
       ask = lift ask
       local = \f m -> StateT $ local f . runStateT m
       reader = lift . reader -}
monadReader'StateT ::
    MonadReaderI r m -> MonadReaderI r (StateT s m)
monadReader'StateT i =
    let monad'm = _monad'Super'MonadReader i
        lift = _lift monadTrans'StateT monad'm
     in MonadReaderI {
            _monad'Super'MonadReader = monad'StateT monad'm,
            _ask = lift $ _ask i,
            _local = \f m -> StateT $ (_local i f) . runStateT m,
            _reader = lift . (_reader i) }

{- test :: (MonadState a m, MonadReader a m) => m ()
   test = ask >>= put -}
test :: MonadStateI a m -> MonadReaderI a m -> m ()
test = \is ir -> let (>>=)   = _bind (_monad'Super'MonadState is)
                  in (_ask ir) >>= (_put is)

example1 :: ReaderT a (StateT a Identity) ()
example1 = test
    (monadState'ReaderT $ monadState'StateT $ monad'Identity)
    (monadReader'ReaderT $ monad'StateT $ monad'Identity)

example2 :: StateT a (ReaderT a Identity) ()
example2 = test
    (monadState'StateT $ monad'ReaderT $ monad'Identity)
    (monadReader'StateT $ monadReader'ReaderT $ monad'Identity)

run1, run2 :: ((), Char)
run1 = runIdentity $ runStateT (runReaderT example1 'A') 'B'
run2 = runIdentity $ runReaderT (runStateT example2 'B') 'A'