It depends on definition of equivalence for your Functor. When proving Alternative laws for artoparsec's Parser all errors are treated as equivalent: so no problem. Also attoparsec concentrates on the speed, not error reporting:




Sent from my iPhone
On 11 Jun 2016, at 10:15, Юрий Сыровецкий (Yuriy Syrovetskiy) <cblp@cblp.su> wrote:

So should we consider it a bug in attoparsec? And should somebody fix it?

On 11 Jun 2016 10:04, "Erik Hesselink" <hesselink@gmail.com> wrote:
OK, so you're using attoparsec (through aeson). That's valuable
information would have been useful to include in your initial email.

After a bit of experimenting and reading the docs, I think the problem
is that attoparsec's Alternative instance isn't completely correct.
From the docs, Alternative is supposed to be "a monoid on applicative
functors". The Monoid laws say, among other things, that `mappend x
mempty = x`. For Applicative, this would mean `x <|> empty = x`.
However, in attoparsec:

    λ parse (fail "boom" <|> empty) "hello"
    Fail "hello" [] "Failed reading: empty"

In parsec, on the other hand:

    λ parse (fail "boom" <|> empty) "" "hello"
    Left (line 1, column 1):
    boom

So I don't think changing Applicative or asum is the way to go here.

Erik

On 11 June 2016 at 07:15, Юрий Сыровецкий (Yuriy Syrovetskiy)
<cblp@cblp.su> wrote:
> λ> :show imports
> import Prelude -- implicit
> import Data.Aeson.Types
> import Data.Foldable
> import Control.Applicative
> λ> parse (\v -> withObject "Object" (\_ -> pure "OK") v <|> fail
> "Expected object") Null
> Error "Expected object"
> λ> parse (\v -> asum [withObject "Object" (\_ -> pure "OK") v, fail
> "Expected object"]) Null
> Error "empty"
>
> Maybe instance Alternative Parser should be changed to ignore "empty"?
>
> 2016-06-10 20:01 GMT+03:00 Oleg Grenrus <oleg.grenrus@iki.fi>:
>> If you aren’t scared of the dependencies: semigroupoids has asum1 (yet it’s easy to write yourself)
>>
>> https://s3.amazonaws.com/haddock.stackage.org/lts-6.2/semigroupoids-5.0.1/Data-Semigroup-Foldable.html#v:asum1
>>
>> λ Prelude Data.Semigroup.Foldable Data.List.NonEmpty > asum1 ([Right 1, Right 2, Left "error"] :: NonEmpty (Either String Int))
>> Right 1
>> λ Prelude Data.Semigroup.Foldable Data.List.NonEmpty > asum1 ([Left "error"] :: NonEmpty (Either String Int))
>> Left "error"
>>
>> - Oleg
>>
>>> On 10 Jun 2016, at 17:37, Юрий Сыровецкий (Yuriy Syrovetskiy) <cblp@cblp.su> wrote:
>>>
>>> Hello
>>>
>>> I want to define some parser such way:
>>>
>>>    myParser = tryA <|> tryB <|> fail "input must be either A or B"
>>>
>>> It works. But then I want to rewrite it with asum:
>>>
>>>    myParser = asum [tryA, tryB, fail "must be A or B"]
>>>
>>> It works, but the wrong way. Instead of my error it writes "empty".
>>> Just "empty".
>>>
>>> It is so because in base library
>>>
>>>    asum = foldr (<|>) empty
>>>
>>> What if it was defined
>>>
>>>    asum [] = empty
>>>    asum [x:xs] = x <|> asum xs
>>>
>>> It would help me with my parser. But what can this break? Why isn't
>>> this done yet?
>>>
>>> --
>>> Yuriy Syrovetskiy, http://cblp.su
>>> _______________________________________________
>>> Haskell-Cafe mailing list
>>> Haskell-Cafe@haskell.org
>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>>>
>>
>
>
>
> --
> Yuriy Syrovetskiy, http://cblp.su
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe