[Haskell-cafe] Does it violate the laws of Alternative/Monoid to implement empty/mempty with mzero from MonadPlus?
Li-yao Xia
lysxia at gmail.com
Tue Oct 27 15:22:00 UTC 2020
That law (v >> mzero = mzero) is controversial. It's near impossible to
satisfy for slightly sophisticated monads. It's notably broken by
`MaybeT` whose very purpose is to augment a monad with such an extra
Alternative/MonadPlus capability (a concrete counterexample for that law
can be found with `MaybeT (State s)`).
MonadPlus is there mainly for historical reasons, because it predates
Applicative. Then Alternative was added because the operations turned
out to be useful even for Applicatives that were not Monads. The
presence of both seems to sugggest there ought to be a difference, but
IMO they should just be considered the same and we should thus simply
forget about MonadPlus. How would you document that Alternative and
MonadPlus may have different implementations anyway? Imagine if
`Control.Monad.msum` and `Control.Applicative.asum` were not the same,
how confusing that would be.
To add an error that can not be recovered from you can use `Maybe` or
`Either` as the base monad for `ParsecT`: `ParsecT e s Maybe`, so `lift
Nothing` fails with your "unparsable" semantics.
Li-yao
On 10/27/2020 6:33 AM, Jaro Reinders wrote:
> Yeah, it seems Megaparsecs parser violates the MonadPlus laws:
>
> >>> isRight $ parse ((char 'a' >> mzero) `mplus` char 'a') "" "a"
> False
> >>> isRight $ parse (mzero `mplus` char 'a') "" "a"
> True
>
> I've created an issue: https://github.com/mrkkrp/megaparsec/issues/430.
>
> On 10/27/20 11:15 AM, YueCompl wrote:
>> Isn't 'u <*> empty = empty' resembles MonadPlus?
>>
>> mzero >>= f = mzero
>> v >> mzero = mzero
>>
>> Since ParsecT also has a MonadPlus instance, can we have different
>> implementations of `empty` and `mzero` to have these 2 separate
>> semantics expressible:
>>
>> *) parse to ignored result from some input
>> *) un-parsable (input consumed or not is irrelevant as to err out anyway)
>>
>>
>> parse to no significant result
>> unparsable
>> consumed input
>> empty -> throw ??
>> mzero -> throw
>> no input consumed
>> empty -> nothrow
>> mzero -> throw
>>
>> I'd much like the behavior above `empty -> throw ??` changed to `empty
>> -> nothrow`
>>
>>> On 2020-10-27, at 17:47, Jaro Reinders <jaro.reinders at gmail.com> wrote:
>>>
>>> The 'empty' value should always be the unit of <|>, that is specified
>>> in the documentation of the Alternative class. The problem starts
>>> when you build composite parsers. E.g. (char 'a' *> empty) does not
>>> need to be a unit of <|>. I thought of 'fixing' this by adding
>>> another law 'u <*> empty = empty', but that disregards all effects
>>> that u can have.
>>>
>>> On 10/27/20 10:26 AM, YueCompl via Haskell-Cafe wrote:
>>>> In [1], Alternative is said being most commonly considered to form a
>>>> monoid, so that:
>>>> ```hs
>>>> -- empty is a neutral element
>>>> empty <|> u = u
>>>> u <|> empty = u
>>>> ```
>>>> In my particular case wrt Megaparsec, when the artifact parser
>>>> evaluates to `empty` at eof, I suppose the outer `many` should
>>>> evaluate to whatsoever previously parsed, but current implementation
>>>> of Megaparsec makes it conditional:
>>>> *) in case the parser hasn't consumed any input, it works the way as
>>>> expected
>>>> *) incase the parser has consumed some input (whitespaces), the
>>>> outer `many` throws error
>>>> So can I say this is a violation regarding [1]?
>>>> Best regards,
>>>> Compl
>>>>> On 2020-10-27, at 04:18, Olaf Klinke <olf at aatal-apotheke.de> wrote:
>>>>>
>>>>> I used to think that an Alternative is just an Applicative which is
>>>>> also a Monoid but apparently there is no consensus about this [1,2].
>>>>> Actually it kind of makes sense to make the 'empty' parser fail:
>>>>> Consider the parser combinator
>>>>>
>>>>> choice = Data.Foldable.asum = foldr (<|>) empty
>>>>>
>>>>> which folds over a list of Alternatives. Its semantics can be regarded
>>>>> analogous to 'any' for a list of Booleans, and in the latter the empty
>>>>> list evaluates to False.
>>>>> Put differently: The parser (p <|> q) matches at least as many inputs
>>>>> than either p or q. Hence the neutral element for <|> ought to be the
>>>>> parser that matches the least amount of inputs, but a parser that
>>>>> succeeds on the empty string _does_ match some input. It would be the
>>>>> neutral element for the monoid operation that concatenates parsers.
>>>>>
>>>>> Olaf
>>>>>
>>>>> [1] https://en.wikibooks.org/wiki/Haskell/Alternative_and_MonadPlus
>>>>> [2] https://wiki.haskell.org/MonadPlus
>>>>>
>>>>>
>>>> _______________________________________________
>>>> Haskell-Cafe mailing list
>>>> To (un)subscribe, modify options or view archives go to:
>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>>>> Only members subscribed via the mailman list are allowed to post.
>>> _______________________________________________
>>> Haskell-Cafe mailing list
>>> To (un)subscribe, modify options or view archives go to:
>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>>> Only members subscribed via the mailman list are allowed to post.
>>
>>
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.
More information about the Haskell-Cafe
mailing list