[Haskell-cafe] Does it violate the laws of Alternative/Monoid to implement empty/mempty with mzero from MonadPlus?

YueCompl compl.yue at icloud.com
Tue Oct 27 16:44:50 UTC 2020


That's to say, `try`'s *backtracking* effect is not desirable here, do we already a version of `try` that without backtracking?

> On 2020-10-28, at 00:42, YueCompl <compl.yue at icloud.com> wrote:
> 
> `try` won't work for me, as the next alternative would be `eof`, if the non-essential parts of input are not consumed, `eof` won't match.
> 
> The line for the MWE at https://github.com/complyue/dcp/blob/91616496e43d153ca8ae92c0d030b3cdc351fb6c/src/Parser.hs#L136 <https://github.com/complyue/dcp/blob/91616496e43d153ca8ae92c0d030b3cdc351fb6c/src/Parser.hs#L136>
> 
> ```hs
>   arts    <- manyTill (scWithSemiColons >> artifactDecl) eof
> ```
> 
> And the artifact parser https://github.com/complyue/dcp/blob/91616496e43d153ca8ae92c0d030b3cdc351fb6c/src/Parser.hs#L139-L147 <https://github.com/complyue/dcp/blob/91616496e43d153ca8ae92c0d030b3cdc351fb6c/src/Parser.hs#L139-L147>
> 
> ```hs
> artifactDecl :: Parser ArtDecl
> artifactDecl = lexeme $ do
>   artCmt <- optional immediateDocComment
>   (eof >> empty) <|> do
>     artBody <- takeWhileP (Just "artifact body")
>                           (not . flip elem (";{" :: [Char]))
>     if T.null $ T.strip artBody
>       then empty -- this is not possible in real cases
>       else return (artCmt, artBody)
> 
> ```
> 
> The `eof >> empty` in above will cause the parsing to err out overall, because the line before it `optional immediateDocComment` has consumed some input.
> 
> 
>> On 2020-10-27, at 23:57, Li-yao Xia <lysxia at gmail.com <mailto:lysxia at gmail.com>> wrote:
>> 
>> That sounds like a use case for "try". Is it not?
>> 
>> Li-yao
>> 
>> On 10/27/2020 11:38 AM, YueCompl wrote:
>>> Li-yao, the issue my parser faces is unable to express an recoverable *error*, that though it consumed some whitespaces, it doesn't want to raise an unrecoverable error, `empty` is supposed to do that in my intuition, but Megaparsec considers it an unrecoverable error in this case.
>>> Best regards,
>>> Compl
>>>> On 2020-10-27, at 23:22, Li-yao Xia <lysxia at gmail.com <mailto:lysxia at gmail.com>> wrote:
>>>> 
>>>> 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 <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 <mailto: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 <mailto: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 <https://en.wikibooks.org/wiki/Haskell/Alternative_and_MonadPlus>
>>>>>>>>> [2] https://wiki.haskell.org/MonadPlus <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 <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 <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 <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 <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 <http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe>
>> Only members subscribed via the mailman list are allowed to post.
> 

-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20201028/b4e21d56/attachment.html>


More information about the Haskell-Cafe mailing list