No subject


Thu Feb 24 17:58:36 CET 2011


safeHeadFailure [] =3D failure "empty list"
safeHeadFailure (x:xs) =3D return x

safeHead' :: [a] -> Maybe a
safeHead' =3D safeHeadFailure

and sure enough, safeHead' works in Maybe. But if I change it to

safeHead' :: [a] -> Either String a

which is more like what will happen in real code I get:

    No instance for (Failure String (Either String))
      arising from a use of `safeHeadFailure'
    Possible fix:
      add an instance declaration for (Failure String (Either String))
    In the expression: safeHeadFailure
    In an equation for `safeHead'': safeHead' =3D safeHeadFailure

Yes, I installed control-monad-failure-mtl and yes I have a 'import
Control.Monad.Error' directive in the module.

This is straight from the article:

safeHeadPair' :: Failure String m =3D> [a] -> [b] -> m (a, b)
safeHeadPair' [] [] =3D failure "both lists empty"
safeHeadPair' [] _ =3D failure "first list empty"
safeHeadPair' _ [] =3D failure "second list empty"
safeHeadPair' (x:xs) (y:ys) =3D return (x, y)

safeHead2 :: [a] -> [b] -> Either String (a, b)
safeHead2 =3D safeHeadPair'

I get the same failure here.

What am I missing?

On Thu May 26 11:24 , Elvio Toccalino  sent:

>Well, there's the 'failure' package. Another package builds on top of
>it, the control-monad-failure (easier to use, maybe).
>I read in the monad reader (don't remember the issue number) about it,
>and have used it ever since. The idea is to let the instanced monad
>decide what a failure means.
>Check it out, and comment back.
>
>Cheers.
>
>On Thu, 2011-05-26 at 11:15 -0700, Sean Perry wrote:
>> This is probably a FAQ of sorts, but I found composing the proper search=
 terms
>> complicated.
>>=20
>> When I write simple parsers and the like I tend to prefer returning usef=
ul error
>> strings instead of simply Nothing from Maybe.
>>=20
>> For example this is a common utility function of mine. Yes, I know with =
the
>> addition of a Read n qualification I can make this more
>> generic but it does not help with the current discussion.
>>=20
>> getNum :: String -> Either String Int
>> getNum n =3D case reads n of [(x, "")] -> Right x
>>                            [(x, cs)] -> Left $ "incomplete parse: " ++ cs
>>                            cs        -> Left $ "invalid number: " ++ cs
>>=20
>> But I would rather write the following so I am not bound to Either. This=
 would
>> even work with Maybe since Nothing just drops the string from fail.
>>=20
>> getNum :: Monad m =3D> String -> m Int
>> getNum n =3D case reads n of [(x, "")] -> return x
>>                            [(x, cs)] -> fail $ "incomplete parse: " ++ cs
>>                            cs        -> fail $ "invalid number: " ++ cs
>>=20
>> Yeah, I know, no one likes the fact that fail raises an exception. What =
I would
>> like to do in my code is define something like
>>=20
>> class (Monad a) =3D> MonadGentle a where
>>     myreturn =3D return
>>     myfail s =3D fails s
>>=20
>> But I can not get an instance of this to compile because it insists myre=
turn and
>> myfail are not visible.
>>=20
>> Since this comes up a lot in the tutorials and books, I am curious why t=
here is
>> not something like MonadGentle in Hackage or the libs. I use mzero occas=
ionally,
>> but as I said I usually prefer some information with my errors since it =
makes for
>> more human usable results.
>>=20
>> Thanks.
>>=20
>>=20
>> _______________________________________________
>> Beginners mailing list
>> Beginners at haskell.org
>> http://www.haskell.org/mailman/listinfo/beginners
>
>





More information about the Beginners mailing list