[Haskell-cafe] Stacking monads
Andrew Coppin
andrewcoppin at btinternet.com
Fri Oct 3 14:01:20 EDT 2008
Andrew Coppin wrote:
> Consider the following beautiful code:
>
> run :: State -> Foo -> ResultSet State
>
> run_and :: State -> Foo -> Foo -> ResultSet State
> run_and s0 x y = do
> s1 <- run s0 x
> s2 <- run s1 y
> return s2
>
> run_or :: State -> Foo -> Foo -> ResultSet State
> run_or s0 x y = merge (run s0 x) (run s0 y)
Right, well, it turns out that if I replace every ResultSet State with
ErrorT ErrorType ResultSet State then the run_and function still
typechecks! (I have no idea whether it still produces the correct
result, but it typechecks.)
The run_or function now becomes highly problematic. The function
runErrorT essentially ends up being
runErrorT :: ErrorT ErrorType ResultSet State -> Either ErrorType
(ResultSet State)
which looks promising. But that means I end up with
runErrorT (run s0 x) :: ResultSet (Either ErrorType State)
which isn't what I want at all. What *I* want is something more like
Either ErrorType (ResultSet State). After much searching (Hoogle rather
failed me here), I discover that if ResultSet happened to be in
Traversable then I'd have a function called "sequence" which performs
the exact type transformation I want. Then, utilising the fact that
Either is itself a kind of error monad, I can do
run_or s0 x y =
let
either_rset1 = sequence $ run s0 x
either_rset2 = sequence $ run s0 y
either_rset3 = do rset1 <- either_rset1; rset2 <- either_rset2;
return (merge rset1 rset2)
However, now I have a problem. I have either_rset3 :: Either ErrorType
(ResultSet State), and I need to somehow get back to ErrorT ErrorType
ResultSet State. Well, the first part is easy:
case either_rset3 of
Left e -> throwError e
Right rset -> uh...
Now I need some function from ResultSet State to ErrorT ErrorType
ResultSet State. It looks like such a function ought to exist, but...
uh... well I had to use Hoogle to find it. After some poking, it found a
function called "lift" from a module I didn't even know about called
Control.Monad.Trans. This has the exact signature I want, so we have
run_or s0 x y =
let
either_rset1 = sequence $ run s0 x
either_rset2 = sequence $ run s0 y
either_rset3 = do rset1 <- either_rset1; rset2 <- either_rset2;
return (merge rset1 rset2)
in case either_rset3 of
Left e -> throwError e
Right rset -> lift rset
Again, this now typechecks. I have *no clue* if it behaves correctly.
(Most specifically, I've only tried using it with dummy types to see if
the type checker will swallow it, so I haven't attempted writing an
instance for Traversable yet. Maybe I'll go look at the list definition
for this to see how it works...)
So, assuming all this stuff does what I *think* it does, it looks like
I've got this working. But _damn_, couldn't they have written down
instructions somewhere? This has taken me all day...! o_O
More information about the Haskell-Cafe
mailing list