[Haskell-beginners] Adding Either around a List monad?

Mario Lang mlang at delysid.org
Mon Oct 5 10:06:14 UTC 2015


Hi.

Consider this structure:

vs :: Rational -> [Input] -> [[Output]]
vs _ []     = return []
vs l (x:xs) = pms l x >>= \pm -> (pm :) <$> vs (l - dur pm) xs

pms :: Rational -> Input -> [Output]
pms l x = [x, x+1, x+2, ...] -- Just an example, not real code.
                             -- in reality, l is used to determine
                             -- the result of pms.

This is basically traverse, but with a state (l) added to it.
So without the state, vs could be written as

vs = traverse pms

Now, I want to add Either e to this, like:

vs :: Rational -> [Input] -> Either e [[Output]]
pms :: Rational -> Input -> Either e [Output]

However, I have no idea how to implement vs.

Interestingly, adding Either e to vs without changing the code lets it
compile, but it gives me the wrong result:

vs :: Rational -> [Input] -> Either e [[Output]]
vs _ []     = return []
vs l (x:xs) = pms l x >>= \pm -> (pm :) <$> vs (l - pm) xs

Since I am in the Either monad now, >>= does not do non-determinism, it
simply unwraps the Either from pms.  I have to admit, I dont fully
understand why this compiles, and what exactly it does wrong.  I only
see from testing that the results can't be right.

On IRC, Gurkenglas suggested to use the State monad, like this:

vs :: Rational -> [Input] -> Either e [[Output]]
vs l = `evalStateT l` . mapM v where
  v x = do l <- get
           pm <- lift $ pms l x
           put (l - dur pm)
           return pm

This compiles, but also yields unexpected results.

I have invested several hours now trying to add Either around this
algorithm, so that I can emit hard failures.  I am sort of frustrated
and out of ideas.  Somehow, I can't figure out what these
transformations actually change in behaviour.  I am being told, by quite
experienced Haskell programmers, that this is supposed to be correct,
but my testing tells me otherwise.  So before I just give up on this,
could someone please have a look and let me know if I have missed
something obvious?

-- 
CYa,
  ⡍⠁⠗⠊⠕


More information about the Beginners mailing list