[Haskell-cafe] Monad transformers [Stacking monads]

Andrew Coppin andrewcoppin at btinternet.com
Mon Oct 6 16:48:51 EDT 2008


Andrew Coppin wrote:
> I have some longwinded code that works, but I'm still thinking about 
> how to do this more elegantly. It looks like what I really need is 
> something like
>
>  type M = StateT State (ResultSetT (ErrorT ErrorType Identity))
>
> Is that the correct ordering?
>
> If so, I guess that means I have to somehow construct ResultSetT. Is 
> there an easy way to do that, given that I already have ResultSet? For 
> example, if I put ResultSet into Traversable, would that let me do it?

...and again I'm talking to myself... :-/

So after much experimentation, I have managed to piece together the 
following facts:

- It appears that the outer-most monad transformer represents the 
inner-most monad. So "StateT Foo ListT" means a list of stateful 
computations, while "ListT (StateT Foo)" means a stateful list of 
computations.

- Each transformer seems to be defined as a newtype such that we have 
ListT :: m [x] -> ListT m x and runListT :: ListT m x -> m [x].

- By some magical process that I do not yet understand, I can wrap a 
StateT in 17 other transformers, and yet "get" and "put" do not require 
any lifting. (God only knows what happens if you were to use two StateTs 
in the same monad stack...)

What I haven't figured out yet is how to turn ResultSet into ResultSetT. 
I seem to just spend most of my time being frustrated by the type 
checker. A useful trick is to say things like

  :t lift (undefined :: ListT Int)

to figure out what type the various parts of a complex multi-monad 
expression have. (By now I'm seeing things like "return . return . 
return", which is just far out.) But sometimes I find myself desperately 
wanting to take some block of code and say "what type does *this* part 
of the expression have?" or "if I do x >>= y when y has *this* type, 
what type must x have?" It can be very hard to work this out mentally, 
and unfortunately there isn't any tool I'm aware of that will help you 
in this matter.

After much testing, it appears that the utopian type definition at the 
very top of this message is in fact the thing I need. So if I can just 
figure out how to construct ResultSetT than I'm done. It looks like 
trying to build it from ResultSet is actually harder than just 
implementing it directly, so I'm going to try a direct transformer 
implementation instead. But it's seriously hard work!

For reference, I humbly present ResultSet.hs:



module Orphi.Kernel.ResultSet (ResultSet (), from_list, to_list, build, 
limit, cost, union) where

data ResultSet x = Pack {unpack :: [[x]]} deriving (Eq)

instance (Show x) => Show (ResultSet x) where
  show (Pack xss) = "from_list " ++ show xss

instance Monad ResultSet where
  fail msg = Pack []
  return x = Pack [[x]]
  (Pack xss) >>= f = Pack $ raw_bind xss (unpack . f)

raw_bind :: [[x]] -> (x -> [[y]]) -> [[y]]
raw_bind = work []
  where
    work out []       _ = out
    work out (xs:xss) f =
      let yss = foldr raw_union out (map f xs)
      in  if null yss
            then []       : work []         xss f
            else head yss : work (tail yss) xss f

raw_union :: [[x]] -> [[x]] -> [[x]]
raw_union []       yss      = yss
raw_union xss      []       = xss
raw_union (xs:xss) (ys:yss) = (xs ++ ys) : raw_union xss yss



from_list :: [[x]] -> ResultSet x
from_list = Pack

to_list :: ResultSet x -> [[x]]
to_list = unpack

build :: [x] -> ResultSet x
build = from_list . map return

limit :: Int -> ResultSet x -> ResultSet x
limit n (Pack xss) = Pack (take n xss)

cost :: ResultSet x -> ResultSet x
cost (Pack xss) = Pack ([]:xss)

union :: ResultSet x -> ResultSet x -> ResultSet x
union (Pack xss) (Pack yss) = Pack (raw_union xss yss)



More information about the Haskell-Cafe mailing list