From johannes.waldmann at htwk-leipzig.de Thu Oct 1 15:47:23 2020 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Thu, 1 Oct 2020 17:47:23 +0200 Subject: [Haskell-cafe] ghc-9 strictness annotations change? Message-ID: <175e74ca-bf3f-9da1-61e0-80b468d6a1ee@htwk-leipzig.de> Dear Cafe, did something change w.r.t. placement of the bang? GHCi, version 9.0.0.20200925: https://www.haskell.org/ghc/ :? for help Prelude> data T = T { foo :: ! Int } :1:21: error: Operator applied to too few arguments: ! Prelude> data T = T { foo :: !Int } Prelude> - J.W. From godzbanebane at gmail.com Thu Oct 1 15:53:32 2020 From: godzbanebane at gmail.com (Georgi Lyubenov) Date: Thu, 1 Oct 2020 18:53:32 +0300 Subject: [Haskell-cafe] ghc-9 strictness annotations change? In-Reply-To: <175e74ca-bf3f-9da1-61e0-80b468d6a1ee@htwk-leipzig.de> References: <175e74ca-bf3f-9da1-61e0-80b468d6a1ee@htwk-leipzig.de> Message-ID: Hi! I believe this is what you're looking for - https://github.com/ghc-proposals/ghc-proposals/pull/229 But I'm not sure if it was implemented in 9.0 or earlier. ====== Georgi -------------- next part -------------- An HTML attachment was scrubbed... URL: From johannes.waldmann at htwk-leipzig.de Thu Oct 1 16:19:01 2020 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Thu, 1 Oct 2020 18:19:01 +0200 Subject: [Haskell-cafe] ghc-9 needs type declaration where ghc-8 didn't (with RankNTypes) Message-ID: Dear Cafe, and thanks, Georgi, for answering my previous question here's another difference I noticed (based on real code, but reduced to a minimal test case) GHCi, version 9.0.0.20200925: https://www.haskell.org/ghc/ :? for help Prelude> :set -XRankNTypes Prelude> let f :: (forall a . a -> ()) -> () ; f = g ; g x = undefined :2:43: error: • Couldn't match type ‘p0’ with ‘forall a. a -> ()’ Expected: (forall a. a -> ()) -> () Actual: p0 -> () Cannot instantiate unification variable ‘p0’ with a type involving polytypes: forall a. a -> () • In the expression: g In an equation for ‘f’: f = g The declaration is accepted by ghc-8. For ghc-9, I have to give a type signature for g (copy that of f), or replace `f = g` with `f x = g x`. - J.W. From vamchale at gmail.com Thu Oct 1 16:18:59 2020 From: vamchale at gmail.com (Vanessa McHale) Date: Thu, 1 Oct 2020 11:18:59 -0500 Subject: [Haskell-cafe] Novel error triggered building aeson on Mac Message-ID: Hi all, I recently ran into the following interesting bug (reproducible on Mac; I used ghcup to install GHC and cabal-install): cabal unpack aeson-1.2.1.0 cabal build -w ghc-8.0.2 (yields this error log) Configuring library for aeson-1.2.1.0.. Preprocessing library for aeson-1.2.1.0.. Building library for aeson-1.2.1.0.. [ 1 of 23] Compiling Data.Attoparsec.Time.Internal ( attoparsec-iso8601/Data/Attoparsec/Time/Internal.hs, dist/build/Data/Attoparsec/Time/Internal.o ) [ 2 of 23] Compiling Data.Attoparsec.Time ( attoparsec-iso8601/Data/Attoparsec/Time.hs, dist/build/Data/Attoparsec/Time.o ) [ 3 of 23] Compiling Data.Aeson.Types.Internal ( Data/Aeson/Types/Internal.hs, dist/build/Data/Aeson/Types/Internal.o ) [ 4 of 23] Compiling Data.Aeson.Types.Generic ( Data/Aeson/Types/Generic.hs, dist/build/Data/Aeson/Types/Generic.o ) [ 5 of 23] Compiling Data.Aeson.Parser.UnescapePure ( pure/Data/Aeson/Parser/UnescapePure.hs, dist/build/Data/Aeson/Parser/UnescapePure.o ) [ 6 of 23] Compiling Data.Aeson.Parser.Unescape ( Data/Aeson/Parser/Unescape.hs, dist/build/Data/Aeson/Parser/Unescape.o ) [ 7 of 23] Compiling Data.Aeson.Parser.Time ( Data/Aeson/Parser/Time.hs, dist/build/Data/Aeson/Parser/Time.o ) [ 8 of 23] Compiling Data.Aeson.Parser.Internal ( Data/Aeson/Parser/Internal.hs, dist/build/Data/Aeson/Parser/Internal.o ) : can't load .so/.DLL for: /Users/vmchale/.cabal/store/ghc-8.0.2/lib/libHStm-lcl-cmpt-0.1.1.5-83154f89-ghc8.0.2.dylib (dlopen(/Users/vmchale/.cabal/store/ghc-8.0.2/lib/libHStm-lcl-cmpt-0.1.1.5-83154f89-ghc8.0.2.dylib, 5): REBASE_OPCODE_SET_SEGMENT_AND_OFFSET_ULEB has segment 2 which is not a writable segment (__LINKEDIT) in /Users/vmchale/.cabal/store/ghc-8.0.2/lib/libHStm-lcl-cmpt-0.1.1.5-83154f89-ghc8.0.2.dylib) Seems to be new; I guess the past libraries didn’t trigger it? I can’t tell if it’s a cabal-install bug, GHC bug, mac novelty… Cheers, Vanessa McHale From dburke.gw at gmail.com Thu Oct 1 16:26:49 2020 From: dburke.gw at gmail.com (Doug Burke) Date: Thu, 1 Oct 2020 12:26:49 -0400 Subject: [Haskell-cafe] ghc-9 needs type declaration where ghc-8 didn't (with RankNTypes) In-Reply-To: References: Message-ID: The 9.0 upgrade may help: https://gitlab.haskell.org/ghc/ghc/-/wikis/migration/9.0 On Thu, Oct 1, 2020 at 12:20 PM Johannes Waldmann < johannes.waldmann at htwk-leipzig.de> wrote: > Dear Cafe, > > and thanks, Georgi, for answering my previous question > > here's another difference I noticed > (based on real code, but reduced to a minimal test case) > > GHCi, version 9.0.0.20200925: https://www.haskell.org/ghc/ :? for help > Prelude> :set -XRankNTypes > Prelude> let f :: (forall a . a -> ()) -> () ; f = g ; g x = undefined > > :2:43: error: > • Couldn't match type ‘p0’ with ‘forall a. a -> ()’ > Expected: (forall a. a -> ()) -> () > Actual: p0 -> () > Cannot instantiate unification variable ‘p0’ > with a type involving polytypes: forall a. a -> () > • In the expression: g > In an equation for ‘f’: f = g > > The declaration is accepted by ghc-8. > For ghc-9, I have to give a type signature for g (copy that of f), > or replace `f = g` with `f x = g x`. > > - J.W. > _______________________________________________ > 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. -------------- next part -------------- An HTML attachment was scrubbed... URL: From johannes.waldmann at htwk-leipzig.de Thu Oct 1 16:37:54 2020 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Thu, 1 Oct 2020 18:37:54 +0200 Subject: [Haskell-cafe] ghc-9 needs type declaration where ghc-8 didn't (with RankNTypes) In-Reply-To: References: Message-ID: <6a393efa-3d48-5c74-5288-ae5d4b57fff2@htwk-leipzig.de> > The 9.0 upgrade may help: > https://gitlab.haskell.org/ghc/ghc/-/wikis/migration/9.0 Thanks for that pointer! So, what I observed is an effect of https://gitlab.haskell.org/ghc/ghc/-/wikis/migration/9.0#simplified-subsumption ? I was browsing that, but could not make the connection. "nested foralls" are mentioned only together with GADT/instance/deriving, none of which is in my example. - J. From evincarofautumn at gmail.com Thu Oct 1 18:43:03 2020 From: evincarofautumn at gmail.com (Jon Purdy) Date: Thu, 1 Oct 2020 11:43:03 -0700 Subject: [Haskell-cafe] ghc-9 needs type declaration where ghc-8 didn't (with RankNTypes) In-Reply-To: <6a393efa-3d48-5c74-5288-ae5d4b57fff2@htwk-leipzig.de> References: <6a393efa-3d48-5c74-5288-ae5d4b57fff2@htwk-leipzig.de> Message-ID: I think this is a consequence of the fact that function types are now invariant in their domain, rather than contravariant. If anyone’s more familiar with GHC’s typechecker, please correct me if I’m mistaken here, but I’ll try to explain what I think is happening. The rule for checking a definition against a signature is a subtyping relation, “is at least as polymorphic as”, which matches the intuition that a signature can constrain the inferred type, but can’t promise more than the inferred type can offer. Previously, the inferred type of ‘g’, ∀p a. p → a, would be checked as a subtype of the declared type of ‘f’, (∀a′. a′ → ()) → (). According to the old rules, I₁ → O₁ ≤: I₂ → O₂ if O₁ ≤: O₂ (covariant) and I₂ ≤: I₁ (contravariant), and when polytypes are involved, you eta-expand to juggle the foralls around. So this would judge a ≤: () covariantly, i.e., a type variable is more polymorphic than a type, and (∀a′. a′ → ()) ≤: p contravariantly, because a polytype is more polymorphic than a type variable. Note the reversed order! This was handled in GHC.Tc.Utils.Unify.tc_sub_type_ds. Whereas now this is rejected by the simplified subsumption check, which only unifies using type equality. Can we unify a = ()? Yes, with the substitution a = (). Can we unify p = ∀a′. a′ → ()? No, this would require implicit polymorphic instantiation, which isn’t allowed. I believe the eta-expanded version typechecks in this case because we end up checking a lambda λx. g x against (∀a′. a′ → ()) → (), which causes the typechecker to first assume that x has the polymorphic type ∀a′. a′ → () and then check the application g x in that context. It accepts this because p can be explicitly filled with a polytype just fine in an application (and RankNTypes allows this impredicative instantiation, for the (→) constructor only). I hope this helps (and that I haven’t completely botched the explanation haha) On Thu, Oct 1, 2020 at 9:38 AM Johannes Waldmann < johannes.waldmann at htwk-leipzig.de> wrote: > > > The 9.0 upgrade may help: > > https://gitlab.haskell.org/ghc/ghc/-/wikis/migration/9.0 > > Thanks for that pointer! > > So, what I observed is an effect of > > https://gitlab.haskell.org/ghc/ghc/-/wikis/migration/9.0#simplified-subsumption > ? > I was browsing that, but could not make the connection. > "nested foralls" are mentioned only together with > GADT/instance/deriving, none of which is in my example. > > - J. > _______________________________________________ > 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. -------------- next part -------------- An HTML attachment was scrubbed... URL: From rae at richarde.dev Fri Oct 2 18:35:55 2020 From: rae at richarde.dev (Richard Eisenberg) Date: Fri, 2 Oct 2020 18:35:55 +0000 Subject: [Haskell-cafe] ghc-9 needs type declaration where ghc-8 didn't (with RankNTypes) In-Reply-To: References: <6a393efa-3d48-5c74-5288-ae5d4b57fff2@htwk-leipzig.de> Message-ID: <010f0174ea996331-f192584e-c3bd-4367-8853-d0121b972476-000000@us-east-2.amazonses.com> Hi all, This problem definitely is caused by the change to subsumption in GHC 9.0 (which is a precursor to, but separate from, the new -XImpredicativeTypes). Jon's explanation below gets close to the mark, but I have a different way of explaining a few details. As Jon points out, a key aspect of this is the contravariance of the first argument of the (->) constructor. That is, for A -> B to be more general than C -> D (written (A -> B) <: (C -> D)), then we must have C <: A and B <: D. Note that the order in the first relation is reversed. Why? If E <: F, that means that we can use an E wherever we need an F -- this is really the definition of <: (and suggests, correctly, that G <: G for all G -- in other words, <: is reflexive). When can one function type be used in place of another? In other words, when can a function f of type A -> B be used instead of C -> D? Well, f must be able to accept things of type C, because the context expecting something of type C -> D will pass f something of type C. So, we must be able to supply a C instead of an A -- in other words, we must have C <: A. And then, the context expecting something of type C -> D will want a D, so B must suffice instead of D -- in other words, we must have B <: D. And thus we get the sub-typing rule for (->). This rule is relaxed in GHC 9.0 not because it is unsound -- it's perfectly sound and continues to be -- but because its particular implementation in GHC causes perhaps-unexpected runtime changes around divergent expressions (bottoms) and interferes with type inference in places. See https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0287-simplify-subsumption.rst for more details. Previous to GHC 9.0, we had this: > f :: (forall a. a -> ()) -> () > f = g > > g x = undefined We'll first get a type for g, completely unaffected by f. g's type is, unsurprisingly, forall b c. b -> c, as there's nothing to constrain either its input nor its result. Now, how can we accept f = g? At the appearance of g, we first choose two unification variables (that is, stand-ins for as-yet-unknown types) for the type variables b and c. (This is where my explanation diverges from Jon's.) This is the same as we do for all polymorphic functions, and it's how GHC accepts e.g. show True, by instantiating the variable `a` in show's type. Let's call these unification variables beta and gamma; we thus say g :: beta -> gamma, for some types beta and gamma. Now we must determine whether (beta -> gamma) <: ((forall a. a -> ()) -> ()) holds. Using the rule for <: and (->) we developed above, we must show (forall a. a -> ()) <: beta and gamma <: (). GHC is clever, and will choose beta to be (Any -> ()) and gamma to be (). So we must show (forall a. a -> ()) <: Any -> () and () <: (). The second is known by the reflexivity of <:. For the first, we realize that we are free to choose the `a` in forall a. a -> (). (This bit is subtle. See Section 4.4 of https://www.microsoft.com/en-us/research/wp-content/uploads/2016/02/putting.pdf for more details.) So we create a new unification variable alpha; we now must check (alpha -> ()) <: (Any -> ()). But this is easy: just choose alpha to be Any, and we're all set. In GHC 9.0, we can't do this, because we don't have any rule that allows us to "look under" (->) when checking (beta -> gamma) <: ((forall a. a -> ()) -> ()). The only way for this to work out in GHC 9.0 is for beta to become (forall a. a -> ()) and for gamma to become (). Yet this requires setting beta to be a polytype (a type with a forall), and GHC won't do that -- unless -XImpredicativeTypes is on. In the new implementation of -XImpredicativeTypes, available in GHC HEAD, this indeed works, simply by enabling the extension. I hope this is helpful! Richard > On Oct 1, 2020, at 2:43 PM, Jon Purdy wrote: > > I think this is a consequence of the fact that function types are now invariant in their domain, rather than contravariant. > > If anyone’s more familiar with GHC’s typechecker, please correct me if I’m mistaken here, but I’ll try to explain what I think is happening. > > The rule for checking a definition against a signature is a subtyping relation, “is at least as polymorphic as”, which matches the intuition that a signature can constrain the inferred type, but can’t promise more than the inferred type can offer. > > Previously, the inferred type of ‘g’, ∀p a. p → a, would be checked as a subtype of the declared type of ‘f’, (∀a′. a′ → ()) → (). According to the old rules, I₁ → O₁ ≤: I₂ → O₂ if O₁ ≤: O₂ (covariant) and I₂ ≤: I₁ (contravariant), and when polytypes are involved, you eta-expand to juggle the foralls around. So this would judge a ≤: () covariantly, i.e., a type variable is more polymorphic than a type, and (∀a′. a′ → ()) ≤: p contravariantly, because a polytype is more polymorphic than a type variable. Note the reversed order! This was handled in GHC.Tc.Utils.Unify.tc_sub_type_ds. > > Whereas now this is rejected by the simplified subsumption check, which only unifies using type equality. Can we unify a = ()? Yes, with the substitution a = (). Can we unify p = ∀a′. a′ → ()? No, this would require implicit polymorphic instantiation, which isn’t allowed. > > I believe the eta-expanded version typechecks in this case because we end up checking a lambda λx. g x against (∀a′. a′ → ()) → (), which causes the typechecker to first assume that x has the polymorphic type ∀a′. a′ → () and then check the application g x in that context. It accepts this because p can be explicitly filled with a polytype just fine in an application (and RankNTypes allows this impredicative instantiation, for the (→) constructor only). > > I hope this helps (and that I haven’t completely botched the explanation haha) > > On Thu, Oct 1, 2020 at 9:38 AM Johannes Waldmann > wrote: > > > The 9.0 upgrade may help: > > https://gitlab.haskell.org/ghc/ghc/-/wikis/migration/9.0 > > Thanks for that pointer! > > So, what I observed is an effect of > https://gitlab.haskell.org/ghc/ghc/-/wikis/migration/9.0#simplified-subsumption > ? > I was browsing that, but could not make the connection. > "nested foralls" are mentioned only together with > GADT/instance/deriving, none of which is in my example. > > - J. > _______________________________________________ > 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. -------------- next part -------------- An HTML attachment was scrubbed... URL: From luc.duponcheel at gmail.com Sun Oct 4 22:24:41 2020 From: luc.duponcheel at gmail.com (Luc Duponcheel) Date: Mon, 5 Oct 2020 00:24:41 +0200 Subject: [Haskell-cafe] showing execution steps Message-ID: Hi, Is there a way to let ghci (or executable code generated by ghc) show all intermediate rewrite results when an expression is evaluated to its final result? Luc -- __~O -\ <, (*)/ (*) reality goes far beyond imagination -------------- next part -------------- An HTML attachment was scrubbed... URL: From lemming at henning-thielemann.de Sun Oct 4 22:34:22 2020 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Mon, 5 Oct 2020 00:34:22 +0200 (CEST) Subject: [Haskell-cafe] showing execution steps In-Reply-To: References: Message-ID: On Mon, 5 Oct 2020, Luc Duponcheel wrote: > Is there a way to let ghci (or executable code generated by ghc) > show all intermediate rewrite results when an expression  > is evaluated to its final result? I don't know the answer for GHCi - but for an extremely simple subset of Haskell that is non-strict but lacks sharing, you may try our live-sequencer: https://www.youtube.com/watch?v=0EQCgi5qa3E https://hackage.haskell.org/package/live-sequencer https://sim.mathematik.uni-halle.de/henning/flatpak/bundle/live-sequencer-0.0.6.2.x86_64.flatpak From fa-ml at ariis.it Sun Oct 4 22:41:56 2020 From: fa-ml at ariis.it (Francesco Ariis) Date: Mon, 5 Oct 2020 00:41:56 +0200 Subject: [Haskell-cafe] showing execution steps In-Reply-To: References: Message-ID: <20201004224156.GA27551@extensa> Hello Luc, Il 05 ottobre 2020 alle 00:24 Luc Duponcheel ha scritto: > Is there a way to let ghci (or executable code generated by ghc) > show all intermediate rewrite results when an expression > is evaluated to its final result? Do you mean the «rewrite rules» [1]? If so, -ddump-rules. If you instead mean how expressions are evaluated step by :step and :list can be used inside ghci [2] Even better in my opinion is the `debug` [3] package which gives you a nice and interactive HTML page with all the steps. [1] https://downloads.haskell.org/~ghc/7.0.3/docs/html/users_guide/rewrite-rules.html [2] https://downloads.haskell.org/~ghc/7.0.3/docs/html/users_guide/ghci-debugger.html [3] https://github.com/ndmitchell/debug/ From diaz.carrete at gmail.com Fri Oct 9 12:49:49 2020 From: diaz.carrete at gmail.com (=?UTF-8?B?RGFuaWVsIETDrWF6?=) Date: Fri, 9 Oct 2020 14:49:49 +0200 Subject: [Haskell-cafe] Overlapping instances: are functions and typeclass methods treated differently? In-Reply-To: References: Message-ID: On Thu, Oct 8, 2020 at 2:12 PM Henning Thielemann < lemming at henning-thielemann.de> wrote: > > On Thu, 8 Oct 2020, Daniel Díaz wrote: > > > But now consider this instance: > > > > > newtype Wrapper a = Wrapper (Maybe a) > > > instance Show a => Show (Wrapper a) where > > > show (Wrapper x) = show x > > > > This compiles just fine, despite—to my mind—suffering from the exact > same problem that the "foo" function had. > > Why does it work? > > There is an instance Show (Maybe a) in Prelude, but no instance Show > (Wrapper a), so no overlapping. Sorry, I wasn't very clear there. The problem is not with the "Show (Wrapper a)" instance itself, but with its implementation of "show". It depends (just as the function "foo" did) on "Show (Maybe a)", for which there are overlapping instances. And yet "foo" compiles without problem, while the typeclass method doesn't. -------------- next part -------------- An HTML attachment was scrubbed... URL: From norc.foobar at gmail.com Tue Oct 13 00:27:31 2020 From: norc.foobar at gmail.com (norc foobar) Date: Tue, 13 Oct 2020 02:27:31 +0200 Subject: [Haskell-cafe] Overlapping instances: are functions and typeclass methods treated differently? In-Reply-To: References: Message-ID: Hi Daniel, The constraint on an instance declaration is, perhaps counterintuitively, discharged at the usage site rather than the definition site. foo :: Show a => Wrapper a -> String foo (Wrapper a) = show a will produce the aforementioned diagnostic. --- Victor On Fri, Oct 9, 2020 at 2:51 PM Daniel Díaz wrote: > On Thu, Oct 8, 2020 at 2:12 PM Henning Thielemann < > lemming at henning-thielemann.de> wrote: > >> >> On Thu, 8 Oct 2020, Daniel Díaz wrote: >> >> > But now consider this instance: >> > >> > > newtype Wrapper a = Wrapper (Maybe a) >> > > instance Show a => Show (Wrapper a) where >> > > show (Wrapper x) = show x >> > >> > This compiles just fine, despite—to my mind—suffering from the exact >> same problem that the "foo" function had. >> > Why does it work? >> >> There is an instance Show (Maybe a) in Prelude, but no instance Show >> (Wrapper a), so no overlapping. > > > Sorry, I wasn't very clear there. > > The problem is not with the "Show (Wrapper a)" instance itself, but with > its implementation of "show". It depends (just as the function "foo" did) > on "Show (Maybe a)", for which there are overlapping instances. > > And yet "foo" compiles without problem, while the typeclass method > doesn't. > > _______________________________________________ > 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. -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Tue Oct 13 00:31:13 2020 From: david.feuer at gmail.com (David Feuer) Date: Mon, 12 Oct 2020 20:31:13 -0400 Subject: [Haskell-cafe] Overlapping instances: are functions and typeclass methods treated differently? In-Reply-To: References: Message-ID: That's not the same, because you show what's under the wrapper, rather than the wrapped value. On Mon, Oct 12, 2020, 8:28 PM norc foobar wrote: > Hi Daniel, > > The constraint on an instance declaration is, perhaps counterintuitively, > discharged at the usage site rather than the definition site. > > foo :: Show a => Wrapper a -> String > foo (Wrapper a) = show a > > will produce the aforementioned diagnostic. > > --- > Victor > > On Fri, Oct 9, 2020 at 2:51 PM Daniel Díaz wrote: > >> On Thu, Oct 8, 2020 at 2:12 PM Henning Thielemann < >> lemming at henning-thielemann.de> wrote: >> >>> >>> On Thu, 8 Oct 2020, Daniel Díaz wrote: >>> >>> > But now consider this instance: >>> > >>> > > newtype Wrapper a = Wrapper (Maybe a) >>> > > instance Show a => Show (Wrapper a) where >>> > > show (Wrapper x) = show x >>> > >>> > This compiles just fine, despite—to my mind—suffering from the exact >>> same problem that the "foo" function had. >>> > Why does it work? >>> >>> There is an instance Show (Maybe a) in Prelude, but no instance Show >>> (Wrapper a), so no overlapping. >> >> >> Sorry, I wasn't very clear there. >> >> The problem is not with the "Show (Wrapper a)" instance itself, but with >> its implementation of "show". It depends (just as the function "foo" did) >> on "Show (Maybe a)", for which there are overlapping instances. >> >> And yet "foo" compiles without problem, while the typeclass method >> doesn't. >> >> _______________________________________________ >> 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. -------------- next part -------------- An HTML attachment was scrubbed... URL: From eborsboom at fpcomplete.com Thu Oct 15 16:33:40 2020 From: eborsboom at fpcomplete.com (Emanuel Borsboom) Date: Thu, 15 Oct 2020 16:33:40 +0000 Subject: [Haskell-cafe] ANN: stack-2.5.1 Message-ID: <99E27FC4-C054-40A1-BAE2-ED20A31EF125@fpcomplete.com> See https://haskellstack.org/ for installation and upgrade instructions. **Changes since v2.3.3** Major changes: * Add the `snapshot-location-base` yaml configuration option, which allows to override the default location of snapshot configuration files. This option affects how snapshot synonyms (LTS/Nightly) are expanded to URLs by the `pantry` library. * `docker-network` configuration key added to override docker `--net` arg Behavior changes: * File watching now takes into account specified targets, old behavior could be restored using the new flag `--watch-all` [#5310](https://github.com/commercialhaskell/stack/issues/5310) Other enhancements: * `stack ls dependencies json` now includes fields `sha256` and `size` for dependencies of `type` `archive` in `location`. [#5280](https://github.com/commercialhaskell/stack/issues/5280) * Build failures now show a hint to scroll up to the corresponding section [#5279](https://github.com/commercialhaskell/stack/issues/5279) * Customisable output styles (see `stack --help` and the `--stack-colors` option, and `stack ls stack-colors --help`) now include `info`, `debug`, `other-level`, `secondary` and `highlight`, used with verbose output. Bug fixes: * Fix `stack test --coverage` when using Cabal 3 * `stack new` now generates PascalCase'd module name correctly. [#5376](https://github.com/commercialhaskell/stack/issues/5376) * Connection issues to Casa server no longer cause builds to failure. Casa acts only as an optimizing cache layer, not a critical piece of infrastructure. * Fix modified time busting caches by always calculating sha256 digest during the build process. [#5125](https://github.com/commercialhaskell/stack/issues/5125) **Thanks to all our contributors for this release:** * Andrea Condoluci * Andreas Herrmann * Andres Schmois * Ariel D. Moya Sequeira * Brandon Chinn * Cheah Jer Fei * DerpyCrabs * Emanuel Borsboom * Felix Yan * Jannik Theiß * Jens Petersen * Junji Hashimoto * Kirill Zaborsky * Michael Snoyman * Mihai Maruseac * Mike Pilgrem * Niklas Hambüchen * Ondřej Slámečka * Piper McCorkle * Thomas Lopatic * tomjaguarpaw -------------- next part -------------- A non-text attachment was scrubbed... Name: image001.png Type: image/png Size: 7431 bytes Desc: image001.png URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: image002.png Type: image/png Size: 7480 bytes Desc: image002.png URL: From 6yearold at gmail.com Thu Oct 15 18:37:07 2020 From: 6yearold at gmail.com (Gleb Popov) Date: Thu, 15 Oct 2020 22:37:07 +0400 Subject: [Haskell-cafe] ANN: stack-2.5.1 In-Reply-To: <99E27FC4-C054-40A1-BAE2-ED20A31EF125@fpcomplete.com> References: <99E27FC4-C054-40A1-BAE2-ED20A31EF125@fpcomplete.com> Message-ID: On Thu, Oct 15, 2020 at 8:35 PM Emanuel Borsboom wrote: > See https://haskellstack.org/ for installation and upgrade instructions. > > **Changes since v2.3.3** > > Major changes: > * Add the `snapshot-location-base` yaml configuration option, which allows > to > override the default location of snapshot configuration files. This > option > affects how snapshot synonyms (LTS/Nightly) are expanded to URLs by the > `pantry` library. > * `docker-network` configuration key added to override docker `--net` arg > > Behavior changes: > > * File watching now takes into account specified targets, old behavior > could > be restored using the new flag `--watch-all` > [#5310](https://github.com/commercialhaskell/stack/issues/5310) > > Other enhancements: > > * `stack ls dependencies json` now includes fields `sha256` and `size` for > dependencies of `type` `archive` in `location`. > [#5280](https://github.com/commercialhaskell/stack/issues/5280) > * Build failures now show a hint to scroll up to the corresponding section > [#5279](https://github.com/commercialhaskell/stack/issues/5279) > * Customisable output styles (see `stack --help` and the `--stack-colors` > option, and `stack ls stack-colors --help`) now include `info`, `debug`, > `other-level`, `secondary` and `highlight`, used with verbose output. > > Bug fixes: > > * Fix `stack test --coverage` when using Cabal 3 > * `stack new` now generates PascalCase'd module name correctly. > [#5376](https://github.com/commercialhaskell/stack/issues/5376) > * Connection issues to Casa server no longer cause builds to failure. Casa > acts > only as an optimizing cache layer, not a critical piece of > infrastructure. > * Fix modified time busting caches by always calculating sha256 digest > during > the build process. > [#5125](https://github.com/commercialhaskell/stack/issues/5125) > > **Thanks to all our contributors for this release:** > > * Andrea Condoluci > * Andreas Herrmann > * Andres Schmois > * Ariel D. Moya Sequeira > * Brandon Chinn > * Cheah Jer Fei > * DerpyCrabs > * Emanuel Borsboom > * Felix Yan > * Jannik Theiß > * Jens Petersen > * Junji Hashimoto > * Kirill Zaborsky > * Michael Snoyman > * Mihai Maruseac > * Mike Pilgrem > * Niklas Hambüchen > * Ondřej Slámečka > * Piper McCorkle > * Thomas Lopatic > * tomjaguarpaw > > _______________________________________________ > 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. Doesn't compile for me GHC 8.10.2 when building using cabal: Building library for casa-types-0.0.1.. [1 of 2] Compiling Casa.Types ( src/Casa/Types.hs, dist/build/Casa/Types.o, dist/build/Casa/Types.dyn_o ) src/Casa/Types.hs:52:14: error: * Couldn't match expected type `Either String ByteString' with actual type `(ByteString, ByteString)' * In the pattern: (result, wrong) In a case alternative: (result, wrong) | S.null wrong -> pure result In a stmt of a 'do' block: case Hex.decode (T.encodeUtf8 bytes) of (result, wrong) | S.null wrong -> pure result _ -> fail "Invalid hex key." | 52 | (result, wrong) | S.null wrong -> pure result | ^^^^^^^^^^^^^^^ cabal: Failed to build casa-types-0.0.1 (which is required by pantry-0.5.1.3). See the build log above for details. -------------- next part -------------- An HTML attachment was scrubbed... URL: From johannes.waldmann at htwk-leipzig.de Sat Oct 17 13:10:02 2020 From: johannes.waldmann at htwk-leipzig.de (waldmann) Date: Sat, 17 Oct 2020 15:10:02 +0200 Subject: [Haskell-cafe] ANN: stack-2.5.1 Message-ID: > Doesn't compile for me GHC 8.10.2 when building using cabal [...] for stack-2.5.0.1, this worked: cabal install --constraint 'base16-bytestring==0.1.1.7' --constraint 'optparse-applicative==0.15.1.0' https://github.com/commercialhaskell/stack/issues/5298#issuecomment-702338716 NB : seems to me there's a whole recent-social-history-of-haskell essay waiting to be written around that question (build 'stack' with 'cabal'). - J.W. From tech at jimtyrerrobotics.ca Sat Oct 17 20:22:03 2020 From: tech at jimtyrerrobotics.ca (tech at jimtyrerrobotics.ca) Date: Sat, 17 Oct 2020 16:22:03 -0400 Subject: [Haskell-cafe] Need help to get started Message-ID: <1b73473d60b20fdcd619faeb9ec8f07b@jimtyrerrobotics.ca> hello, I'm an industrial robot tech and the code I write seems to be composed of 99% side-effects ;-) That's the big dumb ones bolted to the floor that make cars and stuff. Decades of imperative sequence coding seem to have fossilized something in my brain. Trying to teach myself Haskell and going nowhere very slowly. Spent the last 8 weeks slowly plodding through "Real World Haskell" and "Learn you a Haskell" with the intention of re-writing a bash script in Haskell. I've normally learned programming by writing something I need instead of tutorials with which I seem to have an attention deficit problem. I use Linux for work and have written a bash script that uses bc and heredocs to write an .adoc file and then calls asciidoctor-pdf to generate an invoice. It's about 90 lines so I am not a scripting pro either. So typing './invoice Wk38' rolls a file called Wk38-of-2020-Invoice.pdf to send to clients. It was while writing this script that I stumbled upon pandoc and then Haskell. And that's where the trouble started. Tha abstraction and macro-approach of Haskell could provide a whole bag of tools for maintaining code (text files) on lines of multiple robots. About the existing script: I write plain text files on my phone that look like this: 14 Sep 0745 1600 Foo y 15 Sep 0815 1500 Foo y 16 Sep 0745 1400 Foo y 17 Sep 0745 1430 Foo y 18 Sep 0745 1400 Foo y and this one is called Wk38 and the fields are: |Date|Time In|Time Out|Proj|Lunch. Then I email it to myself and run the script. So I would be very grateful if someone could write some code for me and put my bootstraps in my fumbling hands: Get the name of the Wkxx file from the command line when running a Haskell standalone executable. fileName <- getArgs Load the lines of the file into a list of list of String[[]]. (or a better way?) lines <- fmap Text.lines (Text.readFile fileName) Recurse through each line of the list(s) and: *: Construct a date::String from the first two fields. (just a string, does not need a real "Date") *: Calc dailyElapsedTime::Double from difference between fields 4 and 3. *: Subtract 0.5hr lunch from dailyElapsedTime if field 6 == "y" *: Add dailyElapsedTime to accumlatedWeekTime::Double. *: Charge = If accumlatedWeekTime < 40hrs then multiply by rate1 *: elseif accumlatedWeekTime > 40hrs then multiply by rate2 *: Append |Date|Time In|Time Out|Charge|Project| to adoc file. If I could load it into ghci and step through it the lights may come on. Thanks very much Noodles From jack at jackkelly.name Sat Oct 17 21:01:24 2020 From: jack at jackkelly.name (jack at jackkelly.name) Date: Sat, 17 Oct 2020 21:01:24 +0000 Subject: [Haskell-cafe] Need help to get started In-Reply-To: <1b73473d60b20fdcd619faeb9ec8f07b@jimtyrerrobotics.ca> References: <1b73473d60b20fdcd619faeb9ec8f07b@jimtyrerrobotics.ca> Message-ID: <51bb1a962e678e1343adab552dfb62c6@jackkelly.name> October 18, 2020 6:20 AM, tech at jimtyrerrobotics.ca wrote: > About the existing script: > I write plain text files on my phone that look like this: > > 14 Sep 0745 1600 Foo y > > and this one is called Wk38 and the fields are: |Date|Time In|Time > Out|Proj|Lunch. > Then I email it to myself and run the script. > > So I would be very grateful if someone could write some code for me and > put my bootstraps in my fumbling hands: > > Get the name of the Wkxx file from the command line when running a > Haskell standalone executable. > fileName <- getArgs > Load the lines of the file into a list of list of String[[]]. (or a > better way?) > lines <- fmap Text.lines (Text.readFile fileName) > Recurse through each line of the list(s) and: > *: Construct a date::String from the first two fields. (just a string, > does not need a real "Date") > *: Calc dailyElapsedTime::Double from difference between fields 4 and > 3. > *: Subtract 0.5hr lunch from dailyElapsedTime if field 6 == "y" > *: Add dailyElapsedTime to accumlatedWeekTime::Double. > *: Charge = If accumlatedWeekTime < 40hrs then multiply by rate1 > *: elseif accumlatedWeekTime > 40hrs then multiply by rate2 > *: Append |Date|Time In|Time Out|Charge|Project| to adoc file. I would break this apart with a couple of additional types: data Entry = Entry { eDay :: Int , eMonth :: Int , eStart :: TimeOfDay , eEnd :: TimeOfDay , eProject :: Text , eLunched :: Bool } deriving (Eq, Show) data Charge = Charge { cDay :: Int , cMonth :: Int , cStart :: TimeOfDay , cEnd :: TimeOfDay , cHoursCharged :: Double , cProject :: Text } deriving (Eq, Show) Then the problem breaks down into: 1. Get filename 2. Read text from file 3. Parse text into [Entry] 4. Convert [Entry] into [Charge] 5. Write [Charge] to other file Maybe a sketch will unstick you: 1. You want `[fileName] <- getArgs` here, as `getArgs :: IO [String]` returns a list of arguments. Your program will fail unless you invoke it with exactly one argument but that's fine for initial testing. 2. lines <- fmap Text.lines (Text.readFile fileName) will give you access to `lines :: [Text]`, which you can pass into other functions. This means you're not trying to do everything inside `main`, and won't have values of type `IO whatever` flying around the rest of your program. 3. At this stage, we have a parsing problem. We want a function like `parseEntry :: Text -> Either Text Entry`, where the `Left` side would be an error message (if that line fails to parse), or the `Entry` describing that line. I can see a couple of ways to attack this: a) Use Text.words and continue with ad-hoc parsing. You may find yourself reinventing wheels that are in the library ecosystem, but for learning that might be fine? b) Use a library like megaparsec and write a full-blown parser. You will get more for free, but the learning curve may be steeper. I am inclined to recommend option (a), so try writing out a bunch of functions: - parseDay :: Text -> Either Text Int - parseMonth :: Text -> Either Text Int - parseTimeOfDay :: Text -> Either Text TimeOfDay - parseYN :: Text -> Either Text Bool - etc. Once you have applied each word from the input line to one of these functions, you will have a lot of `Either Text somePart` values. To combine them into an `Entry`, you'll want to use the `Applicative` typeclass, specifically the `(<$>)` and `(<*>)` operators. `Either e` has an `Applicative` instance for any `e`, so we can get: - Entry :: Int -> Int -> TimeOfDay -> TimeOfDay -> Text -> Bool -> Entry - (<$>) :: Functor f => (a -> b) -> f a -> f b -- Infix alias for fmap (every `Applicative` is a `Functor`) - We use it here with the types `f ~ Either Text`, `a ~ Int`, `b ~ Int -> TimeOfDay -> TimeOfDay -> Text -> Bool -> Entry`: - Entry <$> parseDay dayText :: Either Text (Int -> TimeOfDay -> TimeOfDay -> Text -> Bool -> Entry) - (<*>) :: Applicative f => f (a -> b) -> f a -> f b - With the types `f ~ Either Text`, `a ~ Int`, `b ~ TimeOfDay -> TimeOfDay -> Text -> Bool -> Entry`: - Entry <$> parseDay dayText <*> parseMonth monthText :: Either Text (TimeOfDay -> TimeOfDay -> Text -> Bool -> Entry) - And so on, toward Entry <$> parseDay dayText <*> parseMonth monthText <*> ...etc... <*> parseYN lunchText That gives you `parseEntry`, which parses one line into one `Entry`. We need to apply it over every line in the input list, and `traverse` is the tool for that: traverse :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b) As before, we'll use `Either Text` as our `Applicative`. Lists (i.e. the type constructor `[]`) have a `Traversable` instance, so we can specialise this to: traverse :: (Text -> Either Text Entry) -> [Text] -> Either Text [Entry] This runs the parser on each line, and "combines" the results. Because we're using `Either Text` for our `Applicative`, the effect is to stop on the first parse error and report it. You can then case-match on the result to see whether you have an error, or have parsed a [Entry] which you'll now convert into [Charge]. 4. A function `calculateCharge :: Entry -> Charge` shouldn't be too difficult to write, and then you can lift it to work over lists using `map`. If you lean into the date/time types a bit more, you might find the `Data.Time.LocalTime.diffLocalTime` function (from the `time` package) helpful. 5. Appending `[Charge]` to the other file: There's an `appendFile :: FilePath -> Text -> IO ()` which should get you started. I'd look at writing a function `renderCharge :: Charge -> Text`, making it work over the entire list using `map`, and collapsing the `[Text]` using `Text.unlines`. ***** Parsing looks like the gnarliest part, so I'd leave that to the end. Start at the outside and work your way in. Declare `parseLine` but replace its implementation with something silly: parseLine :: Text -> Either Text Entry parseLine _ = Right $ Entry 1 4 (TimeOfDay 9 0 0) (TimeOfDay 17 0 0) "Dummy" False And see if you can get the rest of the program's skeleton in place. Then you can test that it does something, then replace `parseLine` with a real parser. HTH, -- Jack From lemming at henning-thielemann.de Sat Oct 17 22:18:31 2020 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Sun, 18 Oct 2020 00:18:31 +0200 (CEST) Subject: [Haskell-cafe] Need help to get started In-Reply-To: <51bb1a962e678e1343adab552dfb62c6@jackkelly.name> References: <1b73473d60b20fdcd619faeb9ec8f07b@jimtyrerrobotics.ca> <51bb1a962e678e1343adab552dfb62c6@jackkelly.name> Message-ID: On Sat, 17 Oct 2020, Jack Kelly via Haskell-Cafe wrote: > 3. At this stage, we have a parsing problem. We want a function like `parseEntry :: Text -> Either Text Entry`, where the `Left` side would be an error message (if that line fails to parse), or the `Entry` describing that line. I can see a couple of ways to attack this: > > a) Use Text.words and continue with ad-hoc parsing. You may find yourself reinventing wheels that are in the library ecosystem, but for learning that might be fine? > b) Use a library like megaparsec and write a full-blown parser. You will get more for free, but the learning curve may be steeper. The text file looks like space-separated values. Thus, the cassava library may help parsing stuff into the data type. From tech at jimtyrerrobotics.ca Sun Oct 18 15:40:51 2020 From: tech at jimtyrerrobotics.ca (Jim Tyrer) Date: Sun, 18 Oct 2020 11:40:51 -0400 Subject: [Haskell-cafe] Need help to get started In-Reply-To: References: <1b73473d60b20fdcd619faeb9ec8f07b@jimtyrerrobotics.ca> <51bb1a962e678e1343adab552dfb62c6@jackkelly.name> Message-ID: <2e938c44-b422-af8b-588f-769fbfb0505c@jimtyrerrobotics.ca> Thanks for all the input. Honestly I was expecting to be curtly told to go and RTFM. So very pleasantly surprised thank you. On 2020-10-17 6:18 p.m., Henning Thielemann wrote: > > On Sat, 17 Oct 2020, Jack Kelly via Haskell-Cafe wrote: > >> 3. At this stage, we have a parsing problem. We want a function like >> `parseEntry :: Text -> Either Text Entry`, where the `Left` side would >> be an error message (if that line fails to parse), or the `Entry` >> describing that line. I can see a couple of ways to attack this: >> >>   a) Use Text.words and continue with ad-hoc parsing. You may find >> yourself reinventing wheels that are in the library ecosystem, but for >> learning that might be fine? >>   b) Use a library like megaparsec and write a full-blown parser. You >> will get more for free, but the learning curve may be steeper. > > The text file looks like space-separated values. Thus, the cassava > library may help parsing stuff into the data type. From liuxinyu95 at gmail.com Mon Oct 19 08:12:10 2020 From: liuxinyu95 at gmail.com (Xinyu LIU) Date: Mon, 19 Oct 2020 16:12:10 +0800 Subject: [Haskell-cafe] Release a book about math and programming in Haskell Message-ID: Hi, I recently released a book about mathematics and programming in github: https://github.com/liuxinyu95/unplugged I mainly provide examples, and code snippets in Haskell. The PDF can be downloaded under GNU FDL license. There are 7 chapters together with 108 problems as exercise. I also included all the answers in the appendix. Here are the table of content: Preface - A story about isomorphism. Chapter 1, Natural numbers. Peano Axiom, list and folding; Chapter 2, Recursion. Euclidean algorithm, Lambda calculus, and Y-combinator; Chapter 3, Symmetry. Group, Ring, and Field. Galois Theory; Chapter 4, Category theory and type system; Chapter 5, Deforest. Build-fold fusion law, optimization, and algorithm deduction; Chapter 6, Infinity. Set theory, Infinity and stream; Chapter 7, Logic paradox, Gödel's incompleteness theorems, and Turing halting problem. Answers to the exercise. Xinyu LIU https://github.com/liuxinyu95/unplugged *e*^(*π*i)+1 = 0 -------------- next part -------------- An HTML attachment was scrubbed... URL: From andrei.paskevich at lri.fr Mon Oct 19 16:17:42 2020 From: andrei.paskevich at lri.fr (Andrei Paskevich) Date: Mon, 19 Oct 2020 18:17:42 +0200 Subject: [Haskell-cafe] F-IDE 2021 - Call for Papers Message-ID: <20201019161742.GA1319081@tikki.lri.fr> An embedded and charset-unspecified text was scrubbed... Name: not available URL: From immanuel.litzroth at gmail.com Tue Oct 20 10:43:06 2020 From: immanuel.litzroth at gmail.com (Immanuel Litzroth) Date: Tue, 20 Oct 2020 12:43:06 +0200 Subject: [Haskell-cafe] Clarification on uniWhite lexical definition Message-ID: The haskell report says: uniWhite → any Unicode character defined as whitespace it's not clear to me whether this means that the unicode character should have "Zs" as it's general category ;; Zs Space_Separator a space character (of various non-zero widths) or whether it should be defined as whitespace as in https://www.unicode.org/Public/UCD/latest/ucd/PropList.txt Any clarification appreciated, Immanuel -- -- Researching the dual problem of finding the function that has a given point as fixpoint. From blamario at rogers.com Tue Oct 20 11:59:03 2020 From: blamario at rogers.com (Mario) Date: Tue, 20 Oct 2020 07:59:03 -0400 Subject: [Haskell-cafe] Clarification on uniWhite lexical definition In-Reply-To: References: Message-ID: <1b2a9560-2eb6-5045-2999-035d68bb59fe@rogers.com> On 2020-10-20 6:43 a.m., Immanuel Litzroth wrote: > The haskell report says: > uniWhite → any Unicode character defined as whitespace > > it's not clear to me whether this means that the unicode character should > have "Zs" as it's general category > ;; Zs Space_Separator a space character (of various non-zero widths) > or whether it should be defined as whitespace as in > https://www.unicode.org/Public/UCD/latest/ucd/PropList.txt     Recall that this production dates from 1998, which was the early days of Unicode. You should be looking approximately at the Unicode 2.1.8 standard, not the latest one. And once you look there, you'll find it was much simpler: > Property dump for: 0x10000004 (White space) > > 0009..000D (5 chars) > 0020 > 00A0 > 2000..200B (12 chars) > 2028..2029 (2 chars) > 3000         So there was no ambiguity at the time. Now if you're trying to extrapolate the intent to the present standard... well I have no more authority than you in the matter, but I'd go with the more inclusive definition. From ietf-dane at dukhovni.org Tue Oct 20 20:08:59 2020 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Tue, 20 Oct 2020 16:08:59 -0400 Subject: [Haskell-cafe] Clarification on uniWhite lexical definition In-Reply-To: References: Message-ID: <20201020200859.GJ34643@straasha.imrryr.org> On Tue, Oct 20, 2020 at 12:43:06PM +0200, Immanuel Litzroth wrote: > The haskell report says: > uniWhite → any Unicode character defined as whitespace > > it's not clear to me whether this means that the unicode character should > have "Zs" as it's general category > ;; Zs Space_Separator a space character (of various non-zero widths) > or whether it should be defined as whitespace as in > https://www.unicode.org/Public/UCD/latest/ucd/PropList.txt > > Any clarification appreciated, FWIW, GHC uses "Zs": https://gitlab.haskell.org/ghc/ghc/-/blob/master/compiler/GHC/Parser/Lexer.x#L124-128 https://gitlab.haskell.org/ghc/ghc/-/blob/master/compiler/GHC/Parser/Lexer.x#L2387-2452 https://gitlab.haskell.org/ghc/ghc/-/blob/master/compiler/GHC/Parser/Lexer.x#L2428 https://gitlab.haskell.org/ghc/ghc/-/blob/master/compiler/GHC/Parser/Lexer.x#L2451 with the definition of generalCategory "Space" at: https://gitlab.haskell.org/ghc/ghc/-/blob/master/libraries/base/GHC/Unicode.hs#L133 -- Viktor. From damien.mattei at gmail.com Wed Oct 21 07:45:40 2020 From: damien.mattei at gmail.com (Damien Mattei) Date: Wed, 21 Oct 2020 09:45:40 +0200 Subject: [Haskell-cafe] Release a book about math and programming in Haskell In-Reply-To: References: Message-ID: Hello, as i say it in a private message this is really a great book! the only thing i noticed parcouring (? french word) it is that there should be a lot more programming examples to be both a Math (already) and Programming book. Regards, Damien On Mon, Oct 19, 2020 at 10:13 AM Xinyu LIU wrote: > Hi, > > I recently released a book about mathematics and programming in github: > https://github.com/liuxinyu95/unplugged > > I mainly provide examples, and code snippets in Haskell. The PDF can be > downloaded under GNU FDL license. > > There are 7 chapters together with 108 problems as exercise. I also > included all the answers in the appendix. Here are the table of content: > > Preface - A story about isomorphism. > Chapter 1, Natural numbers. Peano Axiom, list and folding; > Chapter 2, Recursion. Euclidean algorithm, Lambda calculus, and > Y-combinator; > Chapter 3, Symmetry. Group, Ring, and Field. Galois Theory; > Chapter 4, Category theory and type system; > Chapter 5, Deforest. Build-fold fusion law, optimization, and algorithm > deduction; > Chapter 6, Infinity. Set theory, Infinity and stream; > Chapter 7, Logic paradox, Gödel's incompleteness theorems, and Turing > halting problem. > Answers to the exercise. > > Xinyu LIU > https://github.com/liuxinyu95/unplugged > > *e*^(*π*i)+1 = 0 > _______________________________________________ > 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. -------------- next part -------------- An HTML attachment was scrubbed... URL: From tobias.grosser at ed.ac.uk Wed Oct 21 10:08:42 2020 From: tobias.grosser at ed.ac.uk (Tobias Grosser) Date: Wed, 21 Oct 2020 11:08:42 +0100 Subject: [Haskell-cafe] =?utf-8?q?CFP=3A_TCAD_Special_Issue_on_Compiler_Fr?= =?utf-8?q?ameworks_and_Co-design_Methodologies_for_Heterogeneous_Systems-?= =?utf-8?q?on-Chip?= In-Reply-To: References: Message-ID: <5bfa77d0-e64e-4ca9-8fa4-ae692ee3cc3c@www.fastmail.com> We are pleased to inform you about a Special Issue titled "Compiler Frameworks and Co-design Methodologies for Heterogeneous Systems-on-Chip" that will appear in the IEEE Transactions on Computer-Aided Design of Integrated Circuits and Systems (TCAD). We encourage you and your collaborators to submit new significant research-based technical contributions within the scope of this journal. SCOPE AND TOPICS ---------------------------------------------------------------------------- Nowadays, heterogeneous architectures are employed to limit the cost per function and boost energy efficiency in several computing domains, from high-performance computing (HPC) to embedded systems. Advanced heterogeneous systems-on-chip combine diverse processing elements, such as general-purpose processors (GPP), graphics processor units (GPU), digital signal processors (DSP), field-programmable gate arrays (FPGA), and many application-specific hardware accelerators. To fully exploit the power of these platforms and overcome the limits of conventional architectures, system and application designers need new tools and methodologies to address the increasing hardware/software complexity and achieve high productivity. This special issue aims to provide the targeted readers with the new advances and challenges in the area of compiler frameworks, hardware/software methodologies, and related tools to aid the design of complex heterogeneous systems. Relevant topics include, but are not limited to, the following: * Compiler frameworks and co-design workflows for heterogeneous hardware * End-to-end frameworks targeting heterogeneous specialized units * Application-specific co-design methodologies for heterogeneous platforms * Synergistic HW/SW techniques to promote parallelism in heterogeneous computing * Novel programming paradigms to promote heterogeneous design * Source-to-source translation and (semi-)automatic code generation for heterogeneous architectures * Methodologies to improve software portability across heterogeneous targets MANUSCRIPT PREPARATION AND SUBMISSION --------------------------------------------------------------------------- Submissions to this Special Issue must represent original material that has been neither submitted to, nor published in, any other journal. All submitted manuscripts must follow the TCAD guidelines: https://ieee-ceda.org/publication/tcad-publication/tcad-paper-submission Please submit your manuscript in electronic form through Manuscript Central website: https://mc.manuscriptcentral.com/tcad On the first page of the submission form, select this special issue in the "Type" field choosing this option: "SI on Compiler Frameworks and Co-design Methodologies" GUEST EDITORS --------------------------------------------------------------------------- * Luca Benini, Full Professor, Università di Bologna / ETH Zürich (lbenini at iis.ee.ethz.ch) * Luca Carloni, Full Professor, Columbia University (luca at cs.columbia.edu) * Giuseppe Tagliavini, Assistant Professor, University of Bologna (giuseppe.tagliavini at unibo.it) * Tobias Grosser, Associate Professor, University of Edinburgh (tobias.grosser at ed.ac.uk) TIMELINE --------------------------------------------------------------------------- * Submission Deadline: November 15, 2020 * Reviews Completed: January 15, 2021 * Major Revisions Due: February 15, 2021 * Reviews of Revisions Completed: March 15, 2021 * Notification of Final Acceptance: March 31, 2021 * Publication Materials for Final Manuscripts Due: April 10, 2021 * Publication: May 2021 -- The University of Edinburgh is a charitable body, registered in Scotland, with registration number SC005336. From dennis.raddle at gmail.com Sun Oct 25 01:03:59 2020 From: dennis.raddle at gmail.com (Dennis Raddle) Date: Sat, 24 Oct 2020 18:03:59 -0700 Subject: [Haskell-cafe] error when running stack Message-ID: I get this error when running stack: Downloading lts- xxxx building plan aesonException "Error in $['system-info']: key \"os\" not present" running "stack update" didn't help. I'm very confused because I don't remember what I did that provoked this error. Anyone know what's going on? Dennis -------------- next part -------------- An HTML attachment was scrubbed... URL: From lemming at henning-thielemann.de Sun Oct 25 01:09:54 2020 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Sun, 25 Oct 2020 02:09:54 +0100 (CET) Subject: [Haskell-cafe] error when running stack In-Reply-To: References: Message-ID: On Sat, 24 Oct 2020, Dennis Raddle wrote: > I get this error when running stack: > > Downloading lts- xxxx building plan > aesonException "Error in $['system-info']: key \"os\" not present" > > running "stack update" didn't help. > I'm very confused because I don't remember what I did that provoked this error. > Anyone know what's going on? aesonException and the error message suggest an error in a JSON file ... From dennis.raddle at gmail.com Sun Oct 25 01:33:39 2020 From: dennis.raddle at gmail.com (Dennis Raddle) Date: Sat, 24 Oct 2020 18:33:39 -0700 Subject: [Haskell-cafe] error when running stack In-Reply-To: References: Message-ID: What part of stack uses JSON? And why would this appear in a previously functioning stack installation? One clue is that I might have installed ghcup just before this. Not sure if that's related. Not sure how to uninstall ghcup. I'm on a Mac. Mike On Sat, Oct 24, 2020 at 6:09 PM Henning Thielemann < lemming at henning-thielemann.de> wrote: > > On Sat, 24 Oct 2020, Dennis Raddle wrote: > > > I get this error when running stack: > > > > Downloading lts- xxxx building plan > > aesonException "Error in $['system-info']: key \"os\" not present" > > > > running "stack update" didn't help. > > I'm very confused because I don't remember what I did that provoked this > error. > > Anyone know what's going on? > > aesonException and the error message suggest an error in a JSON file ... > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ietf-dane at dukhovni.org Sun Oct 25 07:20:24 2020 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Sun, 25 Oct 2020 03:20:24 -0400 Subject: [Haskell-cafe] error when running stack In-Reply-To: References: Message-ID: <20201025072024.GY34643@straasha.imrryr.org> On Sat, Oct 24, 2020 at 06:03:59PM -0700, Dennis Raddle wrote: > I get this error when running stack: > > Downloading lts- xxxx building plan > aesonException "Error in $['system-info']: key \"os\" not present" The files in question are the build plan files, e.g. ~/.stack/build-plan/lts-13.10.yaml Older versions of stack used to look for an "os" field under "system-info" in these files: ... system-info: core-packages: ghc: 8.6.3 bytestring: 0.10.8.2 unix: 2.7.2.2 base: 4.12.0.0 time: 1.8.0.2 hpc: 0.6.0.3 filepath: 1.4.2.1 process: 1.6.3.0 array: 0.5.3.0 integer-gmp: 1.0.2.0 containers: 0.6.0.1 ghc-boot: 8.6.3 binary: 0.8.6.0 ghc-prim: 0.5.3 ghc-heap: 8.6.3 ghci: 8.6.3 rts: '1.0' terminfo: 0.4.1.2 transformers: 0.5.5.0 deepseq: 1.4.4.0 ghc-boot-th: 8.6.3 pretty: 1.1.3.6 template-haskell: 2.14.0.0 directory: 1.3.3.0 ghc-version: 8.6.3 os: linux ... That code was dropped from stack some time back (between v1.5.1 and v1.6.1), and new build plans likely don't include the no longer needed information. Perhaps you're trying to use a very old stack executable (older than 1.6.1?) to process a new build plan (LTS snapshot). commit 624165387b77df09108888a8c4ec3b0b512e5096 Author: Michael Snoyman Date: Mon Jun 26 08:35:31 2017 +0300 Remove a bunch of unneeded info from BuildPlan > running "stack update" didn't help. > I'm very confused because I don't remember what I did that provoked this > error. Simplest is probably to reinstall stack from scratch, perhaps you're missing too many intermediate versions to perform a direct upgrade. -- Viktor. From compl.yue at icloud.com Sun Oct 25 10:27:45 2020 From: compl.yue at icloud.com (YueCompl) Date: Sun, 25 Oct 2020 18:27:45 +0800 Subject: [Haskell-cafe] Reason about a Megaparsec error Message-ID: <25B66A20-E422-4D48-9DDE-F1BF6229E055@icloud.com> Dear Cafe, I find myself unable to reason about an error that `optional` in a parser err out instead of return Nothing, I asked the question at StackOverflow, and would like to seek your help here as well. https://stackoverflow.com/questions/64522568/why-optional-in-a-parser-can-err-out https://github.com/complyue/dcp is a minimum working example to reprod this error $ cabal run dcp:dcp < samples/basic.txt Up to date dcp: 10:1: | 10 | method doXXX() pass | ^ unexpected 'm' expecting ';' CallStack (from HasCallStack): error, called at src/Parser.hs:149:14 in main:Parser $ I believe it's optionalSemicolon causing the failure: https://github.com/complyue/dcp/blob/1df7ad590d78d4fa9a017eb53f9f265e291bdfa7/src/Parser.hs#L50-L54 findIt = do -- ignore leading whitespaces and an optional semicolon in between nbsc >> optionalSemicolon >> nbsc -- try get a doc comment block getIt >>= \case And it's defined like this: https://github.com/complyue/dcp/blob/1df7ad590d78d4fa9a017eb53f9f265e291bdfa7/src/Parser.hs#L31-L32 optionalSemicolon :: Parser Bool optionalSemicolon = fromMaybe False <$> optional (True <$ symbol ";") I can't reason about why it can fail like this. Best regards, Compl -------------- next part -------------- An HTML attachment was scrubbed... URL: From jaro.reinders at gmail.com Sun Oct 25 10:53:49 2020 From: jaro.reinders at gmail.com (Jaro Reinders) Date: Sun, 25 Oct 2020 11:53:49 +0100 Subject: [Haskell-cafe] Reason about a Megaparsec error In-Reply-To: <25B66A20-E422-4D48-9DDE-F1BF6229E055@icloud.com> References: <25B66A20-E422-4D48-9DDE-F1BF6229E055@icloud.com> Message-ID: I think you have to insert a 'try' manually inside the optional, because megaparsec doesn't do backtracking by default. On 10/25/20 11:27 AM, YueCompl via Haskell-Cafe wrote: > Dear Cafe, > > I find myself unable to reason about an error that `optional` in a parser err out instead of return Nothing, I asked the question at StackOverflow, and would like to seek your help here as well. > > https://stackoverflow.com/questions/64522568/why-optional-in-a-parser-can-err-out > > https://github.com/complyue/dcp is a minimum working example to reprod this error > $ cabal run dcp:dcp < samples/basic.txt > Up to date > dcp: 10:1: > | > 10 | method doXXX() pass > | ^ > unexpected 'm' > expecting ';' > > CallStack (from HasCallStack): > error, called at src/Parser.hs:149:14 in main:Parser > $ > I believe it's optionalSemicolon causing the failure: > https://github.com/complyue/dcp/blob/1df7ad590d78d4fa9a017eb53f9f265e291bdfa7/src/Parser.hs#L50-L54 > findIt = do > -- ignore leading whitespaces and an optional semicolon in between > nbsc >> optionalSemicolon >> nbsc > -- try get a doc comment block > getIt >>= \case > And it's defined like this: https://github.com/complyue/dcp/blob/1df7ad590d78d4fa9a017eb53f9f265e291bdfa7/src/Parser.hs#L31-L32 > optionalSemicolon :: Parser Bool > optionalSemicolon = fromMaybe False <$> optional (True <$ symbol ";") > I can't reason about why it can fail like this. > > Best regards, > Compl > > > > _______________________________________________ > 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. > From compl.yue at icloud.com Sun Oct 25 11:00:49 2020 From: compl.yue at icloud.com (YueCompl) Date: Sun, 25 Oct 2020 19:00:49 +0800 Subject: [Haskell-cafe] Reason about a Megaparsec error In-Reply-To: References: <25B66A20-E422-4D48-9DDE-F1BF6229E055@icloud.com> Message-ID: During the parsing of doc comments, backtracking is off on purpose, as it won't consume syntactic contents, merely whitespaces (while doc comment is a special form of block comment), the desired result is `Nothing` or `Just docCmt` without backtracking of whitespaces. > On 2020-10-25, at 18:53, Jaro Reinders wrote: > > I think you have to insert a 'try' manually inside the optional, because megaparsec doesn't do backtracking by default. > > On 10/25/20 11:27 AM, YueCompl via Haskell-Cafe wrote: >> Dear Cafe, >> I find myself unable to reason about an error that `optional` in a parser err out instead of return Nothing, I asked the question at StackOverflow, and would like to seek your help here as well. >> https://stackoverflow.com/questions/64522568/why-optional-in-a-parser-can-err-out >> https://github.com/complyue/dcp is a minimum working example to reprod this error >> $ cabal run dcp:dcp < samples/basic.txt >> Up to date >> dcp: 10:1: >> | >> 10 | method doXXX() pass >> | ^ >> unexpected 'm' >> expecting ';' >> CallStack (from HasCallStack): >> error, called at src/Parser.hs:149:14 in main:Parser >> $ >> I believe it's optionalSemicolon causing the failure: >> https://github.com/complyue/dcp/blob/1df7ad590d78d4fa9a017eb53f9f265e291bdfa7/src/Parser.hs#L50-L54 >> findIt = do >> -- ignore leading whitespaces and an optional semicolon in between >> nbsc >> optionalSemicolon >> nbsc >> -- try get a doc comment block >> getIt >>= \case >> And it's defined like this: https://github.com/complyue/dcp/blob/1df7ad590d78d4fa9a017eb53f9f265e291bdfa7/src/Parser.hs#L31-L32 >> optionalSemicolon :: Parser Bool >> optionalSemicolon = fromMaybe False <$> optional (True <$ symbol ";") >> I can't reason about why it can fail like this. >> Best regards, >> Compl >> _______________________________________________ >> 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. From jaro.reinders at gmail.com Sun Oct 25 11:07:23 2020 From: jaro.reinders at gmail.com (Jaro Reinders) Date: Sun, 25 Oct 2020 12:07:23 +0100 Subject: [Haskell-cafe] Reason about a Megaparsec error In-Reply-To: References: <25B66A20-E422-4D48-9DDE-F1BF6229E055@icloud.com> Message-ID: <52d2fcd5-3bce-cd9f-9749-c0510663eccb@gmail.com> But in the basic.txt example, won't the first nbsc consume everything up to 'method doXXX() pass'. Then the semicolon parser consumes the 'm' character, and that will never backtrack. So that 'm' character is lost. On 10/25/20 12:00 PM, YueCompl wrote: > During the parsing of doc comments, backtracking is off on purpose, as it won't consume syntactic contents, merely whitespaces (while doc comment is a special form of block comment), the desired result is `Nothing` or `Just docCmt` without backtracking of whitespaces. > >> On 2020-10-25, at 18:53, Jaro Reinders wrote: >> >> I think you have to insert a 'try' manually inside the optional, because megaparsec doesn't do backtracking by default. >> >> On 10/25/20 11:27 AM, YueCompl via Haskell-Cafe wrote: >>> Dear Cafe, >>> I find myself unable to reason about an error that `optional` in a parser err out instead of return Nothing, I asked the question at StackOverflow, and would like to seek your help here as well. >>> https://stackoverflow.com/questions/64522568/why-optional-in-a-parser-can-err-out >>> https://github.com/complyue/dcp is a minimum working example to reprod this error >>> $ cabal run dcp:dcp < samples/basic.txt >>> Up to date >>> dcp: 10:1: >>> | >>> 10 | method doXXX() pass >>> | ^ >>> unexpected 'm' >>> expecting ';' >>> CallStack (from HasCallStack): >>> error, called at src/Parser.hs:149:14 in main:Parser >>> $ >>> I believe it's optionalSemicolon causing the failure: >>> https://github.com/complyue/dcp/blob/1df7ad590d78d4fa9a017eb53f9f265e291bdfa7/src/Parser.hs#L50-L54 >>> findIt = do >>> -- ignore leading whitespaces and an optional semicolon in between >>> nbsc >> optionalSemicolon >> nbsc >>> -- try get a doc comment block >>> getIt >>= \case >>> And it's defined like this: https://github.com/complyue/dcp/blob/1df7ad590d78d4fa9a017eb53f9f265e291bdfa7/src/Parser.hs#L31-L32 >>> optionalSemicolon :: Parser Bool >>> optionalSemicolon = fromMaybe False <$> optional (True <$ symbol ";") >>> I can't reason about why it can fail like this. >>> Best regards, >>> Compl >>> _______________________________________________ >>> 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. > From compl.yue at icloud.com Sun Oct 25 11:10:30 2020 From: compl.yue at icloud.com (YueCompl) Date: Sun, 25 Oct 2020 19:10:30 +0800 Subject: [Haskell-cafe] Reason about a Megaparsec error In-Reply-To: <52d2fcd5-3bce-cd9f-9749-c0510663eccb@gmail.com> References: <25B66A20-E422-4D48-9DDE-F1BF6229E055@icloud.com> <52d2fcd5-3bce-cd9f-9749-c0510663eccb@gmail.com> Message-ID: Unlike `sc`, `nbsc` won't consume block comments, as it's defined as `L.space space1 (L.skipLineComment "#") empty` > On 2020-10-25, at 19:07, Jaro Reinders wrote: > > But in the basic.txt example, won't the first nbsc consume everything up to 'method doXXX() pass'. Then the semicolon parser consumes the 'm' character, and that will never backtrack. So that 'm' character is lost. > > On 10/25/20 12:00 PM, YueCompl wrote: >> During the parsing of doc comments, backtracking is off on purpose, as it won't consume syntactic contents, merely whitespaces (while doc comment is a special form of block comment), the desired result is `Nothing` or `Just docCmt` without backtracking of whitespaces. >>> On 2020-10-25, at 18:53, Jaro Reinders wrote: >>> >>> I think you have to insert a 'try' manually inside the optional, because megaparsec doesn't do backtracking by default. >>> >>> On 10/25/20 11:27 AM, YueCompl via Haskell-Cafe wrote: >>>> Dear Cafe, >>>> I find myself unable to reason about an error that `optional` in a parser err out instead of return Nothing, I asked the question at StackOverflow, and would like to seek your help here as well. >>>> https://stackoverflow.com/questions/64522568/why-optional-in-a-parser-can-err-out >>>> https://github.com/complyue/dcp is a minimum working example to reprod this error >>>> $ cabal run dcp:dcp < samples/basic.txt >>>> Up to date >>>> dcp: 10:1: >>>> | >>>> 10 | method doXXX() pass >>>> | ^ >>>> unexpected 'm' >>>> expecting ';' >>>> CallStack (from HasCallStack): >>>> error, called at src/Parser.hs:149:14 in main:Parser >>>> $ >>>> I believe it's optionalSemicolon causing the failure: >>>> https://github.com/complyue/dcp/blob/1df7ad590d78d4fa9a017eb53f9f265e291bdfa7/src/Parser.hs#L50-L54 >>>> findIt = do >>>> -- ignore leading whitespaces and an optional semicolon in between >>>> nbsc >> optionalSemicolon >> nbsc >>>> -- try get a doc comment block >>>> getIt >>= \case >>>> And it's defined like this: https://github.com/complyue/dcp/blob/1df7ad590d78d4fa9a017eb53f9f265e291bdfa7/src/Parser.hs#L31-L32 >>>> optionalSemicolon :: Parser Bool >>>> optionalSemicolon = fromMaybe False <$> optional (True <$ symbol ";") >>>> I can't reason about why it can fail like this. >>>> Best regards, >>>> Compl >>>> _______________________________________________ >>>> 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. -------------- next part -------------- An HTML attachment was scrubbed... URL: From jaro.reinders at gmail.com Sun Oct 25 11:16:11 2020 From: jaro.reinders at gmail.com (Jaro Reinders) Date: Sun, 25 Oct 2020 12:16:11 +0100 Subject: [Haskell-cafe] Reason about a Megaparsec error In-Reply-To: References: <25B66A20-E422-4D48-9DDE-F1BF6229E055@icloud.com> <52d2fcd5-3bce-cd9f-9749-c0510663eccb@gmail.com> Message-ID: <8b6c43be-c367-8dcb-ac15-ef33e40982a2@gmail.com> But the 'findIt' parser will be rerun after every block comment right? On 10/25/20 12:10 PM, YueCompl wrote: > Unlike `sc`, `nbsc` won't consume block comments, as it's defined as `L.space space1 (L.skipLineComment "#") empty` > >> On 2020-10-25, at 19:07, Jaro Reinders wrote: >> >> But in the basic.txt example, won't the first nbsc consume everything up to 'method doXXX() pass'. Then the semicolon parser consumes the 'm' character, and that will never backtrack. So that 'm' character is lost. >> >> On 10/25/20 12:00 PM, YueCompl wrote: >>> During the parsing of doc comments, backtracking is off on purpose, as it won't consume syntactic contents, merely whitespaces (while doc comment is a special form of block comment), the desired result is `Nothing` or `Just docCmt` without backtracking of whitespaces. >>>> On 2020-10-25, at 18:53, Jaro Reinders wrote: >>>> >>>> I think you have to insert a 'try' manually inside the optional, because megaparsec doesn't do backtracking by default. >>>> >>>> On 10/25/20 11:27 AM, YueCompl via Haskell-Cafe wrote: >>>>> Dear Cafe, >>>>> I find myself unable to reason about an error that `optional` in a parser err out instead of return Nothing, I asked the question at StackOverflow, and would like to seek your help here as well. >>>>> https://stackoverflow.com/questions/64522568/why-optional-in-a-parser-can-err-out >>>>> https://github.com/complyue/dcp is a minimum working example to reprod this error >>>>> $ cabal run dcp:dcp < samples/basic.txt >>>>> Up to date >>>>> dcp: 10:1: >>>>> | >>>>> 10 | method doXXX() pass >>>>> | ^ >>>>> unexpected 'm' >>>>> expecting ';' >>>>> CallStack (from HasCallStack): >>>>> error, called at src/Parser.hs:149:14 in main:Parser >>>>> $ >>>>> I believe it's optionalSemicolon causing the failure: >>>>> https://github.com/complyue/dcp/blob/1df7ad590d78d4fa9a017eb53f9f265e291bdfa7/src/Parser.hs#L50-L54 >>>>> findIt = do >>>>> -- ignore leading whitespaces and an optional semicolon in between >>>>> nbsc >> optionalSemicolon >> nbsc >>>>> -- try get a doc comment block >>>>> getIt >>= \case >>>>> And it's defined like this: https://github.com/complyue/dcp/blob/1df7ad590d78d4fa9a017eb53f9f265e291bdfa7/src/Parser.hs#L31-L32 >>>>> optionalSemicolon :: Parser Bool >>>>> optionalSemicolon = fromMaybe False <$> optional (True <$ symbol ";") >>>>> I can't reason about why it can fail like this. >>>>> Best regards, >>>>> Compl >>>>> _______________________________________________ >>>>> 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. > > From compl.yue at icloud.com Sun Oct 25 11:21:13 2020 From: compl.yue at icloud.com (YueCompl) Date: Sun, 25 Oct 2020 19:21:13 +0800 Subject: [Haskell-cafe] Reason about a Megaparsec error In-Reply-To: <8b6c43be-c367-8dcb-ac15-ef33e40982a2@gmail.com> References: <25B66A20-E422-4D48-9DDE-F1BF6229E055@icloud.com> <52d2fcd5-3bce-cd9f-9749-c0510663eccb@gmail.com> <8b6c43be-c367-8dcb-ac15-ef33e40982a2@gmail.com> Message-ID: The rerun is guarded behind an optional `L.skipBlockCommentNested "{#" "#}"` got a `Just{}` result, and only after `getIt` got a `Nothing` result. > On 2020-10-25, at 19:16, Jaro Reinders wrote: > > But the 'findIt' parser will be rerun after every block comment right? > > On 10/25/20 12:10 PM, YueCompl wrote: >> Unlike `sc`, `nbsc` won't consume block comments, as it's defined as `L.space space1 (L.skipLineComment "#") empty` >>> On 2020-10-25, at 19:07, Jaro Reinders wrote: >>> >>> But in the basic.txt example, won't the first nbsc consume everything up to 'method doXXX() pass'. Then the semicolon parser consumes the 'm' character, and that will never backtrack. So that 'm' character is lost. >>> >>> On 10/25/20 12:00 PM, YueCompl wrote: >>>> During the parsing of doc comments, backtracking is off on purpose, as it won't consume syntactic contents, merely whitespaces (while doc comment is a special form of block comment), the desired result is `Nothing` or `Just docCmt` without backtracking of whitespaces. >>>>> On 2020-10-25, at 18:53, Jaro Reinders wrote: >>>>> >>>>> I think you have to insert a 'try' manually inside the optional, because megaparsec doesn't do backtracking by default. >>>>> >>>>> On 10/25/20 11:27 AM, YueCompl via Haskell-Cafe wrote: >>>>>> Dear Cafe, >>>>>> I find myself unable to reason about an error that `optional` in a parser err out instead of return Nothing, I asked the question at StackOverflow, and would like to seek your help here as well. >>>>>> https://stackoverflow.com/questions/64522568/why-optional-in-a-parser-can-err-out >>>>>> https://github.com/complyue/dcp is a minimum working example to reprod this error >>>>>> $ cabal run dcp:dcp < samples/basic.txt >>>>>> Up to date >>>>>> dcp: 10:1: >>>>>> | >>>>>> 10 | method doXXX() pass >>>>>> | ^ >>>>>> unexpected 'm' >>>>>> expecting ';' >>>>>> CallStack (from HasCallStack): >>>>>> error, called at src/Parser.hs:149:14 in main:Parser >>>>>> $ >>>>>> I believe it's optionalSemicolon causing the failure: >>>>>> https://github.com/complyue/dcp/blob/1df7ad590d78d4fa9a017eb53f9f265e291bdfa7/src/Parser.hs#L50-L54 >>>>>> findIt = do >>>>>> -- ignore leading whitespaces and an optional semicolon in between >>>>>> nbsc >> optionalSemicolon >> nbsc >>>>>> -- try get a doc comment block >>>>>> getIt >>= \case >>>>>> And it's defined like this: https://github.com/complyue/dcp/blob/1df7ad590d78d4fa9a017eb53f9f265e291bdfa7/src/Parser.hs#L31-L32 >>>>>> optionalSemicolon :: Parser Bool >>>>>> optionalSemicolon = fromMaybe False <$> optional (True <$ symbol ";") >>>>>> I can't reason about why it can fail like this. >>>>>> Best regards, >>>>>> Compl >>>>>> _______________________________________________ >>>>>> 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. -------------- next part -------------- An HTML attachment was scrubbed... URL: From jaro.reinders at gmail.com Sun Oct 25 11:26:54 2020 From: jaro.reinders at gmail.com (Jaro Reinders) Date: Sun, 25 Oct 2020 12:26:54 +0100 Subject: [Haskell-cafe] Reason about a Megaparsec error In-Reply-To: References: <25B66A20-E422-4D48-9DDE-F1BF6229E055@icloud.com> <52d2fcd5-3bce-cd9f-9749-c0510663eccb@gmail.com> <8b6c43be-c367-8dcb-ac15-ef33e40982a2@gmail.com> Message-ID: I think the optionalSemicolon will consume the '{' of the first comment and then the 'getIt' will produce Nothing because the input doesn't start with '{##' anymore, and then it will go on like that until the optionalSemicolon consumes that 'm'. On 10/25/20 12:21 PM, YueCompl wrote: > The rerun is guarded behind an optional `L.skipBlockCommentNested "{#" "#}"` got a `Just{}` result, and only after `getIt` got a `Nothing` result. > >> On 2020-10-25, at 19:16, Jaro Reinders wrote: >> >> But the 'findIt' parser will be rerun after every block comment right? >> >> On 10/25/20 12:10 PM, YueCompl wrote: >>> Unlike `sc`, `nbsc` won't consume block comments, as it's defined as `L.space space1 (L.skipLineComment "#") empty` >>>> On 2020-10-25, at 19:07, Jaro Reinders wrote: >>>> >>>> But in the basic.txt example, won't the first nbsc consume everything up to 'method doXXX() pass'. Then the semicolon parser consumes the 'm' character, and that will never backtrack. So that 'm' character is lost. >>>> >>>> On 10/25/20 12:00 PM, YueCompl wrote: >>>>> During the parsing of doc comments, backtracking is off on purpose, as it won't consume syntactic contents, merely whitespaces (while doc comment is a special form of block comment), the desired result is `Nothing` or `Just docCmt` without backtracking of whitespaces. >>>>>> On 2020-10-25, at 18:53, Jaro Reinders wrote: >>>>>> >>>>>> I think you have to insert a 'try' manually inside the optional, because megaparsec doesn't do backtracking by default. >>>>>> >>>>>> On 10/25/20 11:27 AM, YueCompl via Haskell-Cafe wrote: >>>>>>> Dear Cafe, >>>>>>> I find myself unable to reason about an error that `optional` in a parser err out instead of return Nothing, I asked the question at StackOverflow, and would like to seek your help here as well. >>>>>>> https://stackoverflow.com/questions/64522568/why-optional-in-a-parser-can-err-out >>>>>>> https://github.com/complyue/dcp is a minimum working example to reprod this error >>>>>>> $ cabal run dcp:dcp < samples/basic.txt >>>>>>> Up to date >>>>>>> dcp: 10:1: >>>>>>> | >>>>>>> 10 | method doXXX() pass >>>>>>> | ^ >>>>>>> unexpected 'm' >>>>>>> expecting ';' >>>>>>> CallStack (from HasCallStack): >>>>>>> error, called at src/Parser.hs:149:14 in main:Parser >>>>>>> $ >>>>>>> I believe it's optionalSemicolon causing the failure: >>>>>>> https://github.com/complyue/dcp/blob/1df7ad590d78d4fa9a017eb53f9f265e291bdfa7/src/Parser.hs#L50-L54 >>>>>>> findIt = do >>>>>>> -- ignore leading whitespaces and an optional semicolon in between >>>>>>> nbsc >> optionalSemicolon >> nbsc >>>>>>> -- try get a doc comment block >>>>>>> getIt >>= \case >>>>>>> And it's defined like this: https://github.com/complyue/dcp/blob/1df7ad590d78d4fa9a017eb53f9f265e291bdfa7/src/Parser.hs#L31-L32 >>>>>>> optionalSemicolon :: Parser Bool >>>>>>> optionalSemicolon = fromMaybe False <$> optional (True <$ symbol ";") >>>>>>> I can't reason about why it can fail like this. >>>>>>> Best regards, >>>>>>> Compl >>>>>>> _______________________________________________ >>>>>>> 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. > > From compl.yue at icloud.com Sun Oct 25 11:36:54 2020 From: compl.yue at icloud.com (YueCompl) Date: Sun, 25 Oct 2020 19:36:54 +0800 Subject: [Haskell-cafe] Reason about a Megaparsec error In-Reply-To: References: <25B66A20-E422-4D48-9DDE-F1BF6229E055@icloud.com> <52d2fcd5-3bce-cd9f-9749-c0510663eccb@gmail.com> <8b6c43be-c367-8dcb-ac15-ef33e40982a2@gmail.com> Message-ID: Tried this: ```hs findIt = do -- ignore leading whitespaces and an optional semicolon in between nbsc ii0 <- getInput trace ("**about*to*match*semicolon*[" <> T.unpack ii0 <> "]") $ pure () optionalSemicolon trace ("**after*semicolon*attempt**") $ pure () nbsc -- try get a doc comment block getIt >>= \case ``` ```console $ cabal run dcp < samples/basic.txt Up to date **about*to*match*semicolon*[{## # this is the module's doc comment #} # this is regular line comment to be dropped in parsing {## # this is the doc comment for `doXXX()` #} method doXXX() pass {# # this is regular block comment to be dropped in parsing #} {## # this is the doc comment for `doYYY()` #} method doYYY() pass ] dcp: 10:1: | 10 | method doXXX() pass | ^ unexpected 'm' expecting ';' CallStack (from HasCallStack): error, called at src/Parser.hs:154:14 in main:Parser ``` So it seems the very first optionalSemicolon failed without consuming anything ... And actually I totally have no clue how the content before `method doXXX` is consumed. > On 2020-10-25, at 19:26, Jaro Reinders wrote: > > I think the optionalSemicolon will consume the '{' of the first comment and then the 'getIt' will produce Nothing because the input doesn't start with '{##' anymore, and then it will go on like that until the optionalSemicolon consumes that 'm'. > > On 10/25/20 12:21 PM, YueCompl wrote: >> The rerun is guarded behind an optional `L.skipBlockCommentNested "{#" "#}"` got a `Just{}` result, and only after `getIt` got a `Nothing` result. >>> On 2020-10-25, at 19:16, Jaro Reinders wrote: >>> >>> But the 'findIt' parser will be rerun after every block comment right? >>> >>> On 10/25/20 12:10 PM, YueCompl wrote: >>>> Unlike `sc`, `nbsc` won't consume block comments, as it's defined as `L.space space1 (L.skipLineComment "#") empty` >>>>> On 2020-10-25, at 19:07, Jaro Reinders wrote: >>>>> >>>>> But in the basic.txt example, won't the first nbsc consume everything up to 'method doXXX() pass'. Then the semicolon parser consumes the 'm' character, and that will never backtrack. So that 'm' character is lost. >>>>> >>>>> On 10/25/20 12:00 PM, YueCompl wrote: >>>>>> During the parsing of doc comments, backtracking is off on purpose, as it won't consume syntactic contents, merely whitespaces (while doc comment is a special form of block comment), the desired result is `Nothing` or `Just docCmt` without backtracking of whitespaces. >>>>>>> On 2020-10-25, at 18:53, Jaro Reinders wrote: >>>>>>> >>>>>>> I think you have to insert a 'try' manually inside the optional, because megaparsec doesn't do backtracking by default. >>>>>>> >>>>>>> On 10/25/20 11:27 AM, YueCompl via Haskell-Cafe wrote: >>>>>>>> Dear Cafe, >>>>>>>> I find myself unable to reason about an error that `optional` in a parser err out instead of return Nothing, I asked the question at StackOverflow, and would like to seek your help here as well. >>>>>>>> https://stackoverflow.com/questions/64522568/why-optional-in-a-parser-can-err-out >>>>>>>> https://github.com/complyue/dcp is a minimum working example to reprod this error >>>>>>>> $ cabal run dcp:dcp < samples/basic.txt >>>>>>>> Up to date >>>>>>>> dcp: 10:1: >>>>>>>> | >>>>>>>> 10 | method doXXX() pass >>>>>>>> | ^ >>>>>>>> unexpected 'm' >>>>>>>> expecting ';' >>>>>>>> CallStack (from HasCallStack): >>>>>>>> error, called at src/Parser.hs:149:14 in main:Parser >>>>>>>> $ >>>>>>>> I believe it's optionalSemicolon causing the failure: >>>>>>>> https://github.com/complyue/dcp/blob/1df7ad590d78d4fa9a017eb53f9f265e291bdfa7/src/Parser.hs#L50-L54 >>>>>>>> findIt = do >>>>>>>> -- ignore leading whitespaces and an optional semicolon in between >>>>>>>> nbsc >> optionalSemicolon >> nbsc >>>>>>>> -- try get a doc comment block >>>>>>>> getIt >>= \case >>>>>>>> And it's defined like this: https://github.com/complyue/dcp/blob/1df7ad590d78d4fa9a017eb53f9f265e291bdfa7/src/Parser.hs#L31-L32 >>>>>>>> optionalSemicolon :: Parser Bool >>>>>>>> optionalSemicolon = fromMaybe False <$> optional (True <$ symbol ";") >>>>>>>> I can't reason about why it can fail like this. >>>>>>>> Best regards, >>>>>>>> Compl >>>>>>>> _______________________________________________ >>>>>>>> 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. -------------- next part -------------- An HTML attachment was scrubbed... URL: From jaro.reinders at gmail.com Sun Oct 25 11:42:36 2020 From: jaro.reinders at gmail.com (Jaro Reinders) Date: Sun, 25 Oct 2020 12:42:36 +0100 Subject: [Haskell-cafe] Reason about a Megaparsec error In-Reply-To: References: <25B66A20-E422-4D48-9DDE-F1BF6229E055@icloud.com> <52d2fcd5-3bce-cd9f-9749-c0510663eccb@gmail.com> <8b6c43be-c367-8dcb-ac15-ef33e40982a2@gmail.com> Message-ID: Aha, I think it is the 'lexeme' function that causes these problems. 'symbol = lexeme . string', but lexeme first skips over all the comments (even the multiline comments). On 10/25/20 12:36 PM, YueCompl wrote: > Tried this: > > ```hs > findIt = do > -- ignore leading whitespaces and an optional semicolon in between > nbsc > ii0 <- getInput > trace ("**about*to*match*semicolon*[" <> T.unpack ii0 <> "]") $ pure () > optionalSemicolon > trace ("**after*semicolon*attempt**") $ pure () > nbsc > -- try get a doc comment block > getIt >>= \case > ``` > > ```console > $ cabal run dcp < samples/basic.txt > Up to date > **about*to*match*semicolon*[{## > # this is the module's doc comment > #} > > # this is regular line comment to be dropped in parsing > > {## > # this is the doc comment for `doXXX()` > #} > method doXXX() pass > > {# > # this is regular block comment to be dropped in parsing > #} > > {## > # this is the doc comment for `doYYY()` > #} > method doYYY() pass > ] > dcp: 10:1: > | > 10 | method doXXX() pass > | ^ > unexpected 'm' > expecting ';' > > CallStack (from HasCallStack): > error, called at src/Parser.hs:154:14 in main:Parser > ``` > > So it seems the very first optionalSemicolon failed without consuming anything ... > > And actually I totally have no clue how the content before `method doXXX` is consumed. > >> On 2020-10-25, at 19:26, Jaro Reinders wrote: >> >> I think the optionalSemicolon will consume the '{' of the first comment and then the 'getIt' will produce Nothing because the input doesn't start with '{##' anymore, and then it will go on like that until the optionalSemicolon consumes that 'm'. >> >> On 10/25/20 12:21 PM, YueCompl wrote: >>> The rerun is guarded behind an optional `L.skipBlockCommentNested "{#" "#}"` got a `Just{}` result, and only after `getIt` got a `Nothing` result. >>>> On 2020-10-25, at 19:16, Jaro Reinders wrote: >>>> >>>> But the 'findIt' parser will be rerun after every block comment right? >>>> >>>> On 10/25/20 12:10 PM, YueCompl wrote: >>>>> Unlike `sc`, `nbsc` won't consume block comments, as it's defined as `L.space space1 (L.skipLineComment "#") empty` >>>>>> On 2020-10-25, at 19:07, Jaro Reinders wrote: >>>>>> >>>>>> But in the basic.txt example, won't the first nbsc consume everything up to 'method doXXX() pass'. Then the semicolon parser consumes the 'm' character, and that will never backtrack. So that 'm' character is lost. >>>>>> >>>>>> On 10/25/20 12:00 PM, YueCompl wrote: >>>>>>> During the parsing of doc comments, backtracking is off on purpose, as it won't consume syntactic contents, merely whitespaces (while doc comment is a special form of block comment), the desired result is `Nothing` or `Just docCmt` without backtracking of whitespaces. >>>>>>>> On 2020-10-25, at 18:53, Jaro Reinders wrote: >>>>>>>> >>>>>>>> I think you have to insert a 'try' manually inside the optional, because megaparsec doesn't do backtracking by default. >>>>>>>> >>>>>>>> On 10/25/20 11:27 AM, YueCompl via Haskell-Cafe wrote: >>>>>>>>> Dear Cafe, >>>>>>>>> I find myself unable to reason about an error that `optional` in a parser err out instead of return Nothing, I asked the question at StackOverflow, and would like to seek your help here as well. >>>>>>>>> https://stackoverflow.com/questions/64522568/why-optional-in-a-parser-can-err-out >>>>>>>>> https://github.com/complyue/dcp is a minimum working example to reprod this error >>>>>>>>> $ cabal run dcp:dcp < samples/basic.txt >>>>>>>>> Up to date >>>>>>>>> dcp: 10:1: >>>>>>>>> | >>>>>>>>> 10 | method doXXX() pass >>>>>>>>> | ^ >>>>>>>>> unexpected 'm' >>>>>>>>> expecting ';' >>>>>>>>> CallStack (from HasCallStack): >>>>>>>>> error, called at src/Parser.hs:149:14 in main:Parser >>>>>>>>> $ >>>>>>>>> I believe it's optionalSemicolon causing the failure: >>>>>>>>> https://github.com/complyue/dcp/blob/1df7ad590d78d4fa9a017eb53f9f265e291bdfa7/src/Parser.hs#L50-L54 >>>>>>>>> findIt = do >>>>>>>>> -- ignore leading whitespaces and an optional semicolon in between >>>>>>>>> nbsc >> optionalSemicolon >> nbsc >>>>>>>>> -- try get a doc comment block >>>>>>>>> getIt >>= \case >>>>>>>>> And it's defined like this: https://github.com/complyue/dcp/blob/1df7ad590d78d4fa9a017eb53f9f265e291bdfa7/src/Parser.hs#L31-L32 >>>>>>>>> optionalSemicolon :: Parser Bool >>>>>>>>> optionalSemicolon = fromMaybe False <$> optional (True <$ symbol ";") >>>>>>>>> I can't reason about why it can fail like this. >>>>>>>>> Best regards, >>>>>>>>> Compl >>>>>>>>> _______________________________________________ >>>>>>>>> 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. > > From compl.yue at icloud.com Sun Oct 25 12:22:36 2020 From: compl.yue at icloud.com (YueCompl) Date: Sun, 25 Oct 2020 20:22:36 +0800 Subject: [Haskell-cafe] Reason about a Megaparsec error In-Reply-To: References: <25B66A20-E422-4D48-9DDE-F1BF6229E055@icloud.com> <52d2fcd5-3bce-cd9f-9749-c0510663eccb@gmail.com> <8b6c43be-c367-8dcb-ac15-ef33e40982a2@gmail.com> Message-ID: <3BCA36D4-DC62-4FA3-9D1B-BF195D231598@icloud.com> Yeah, you are so right! It's working now: ```console $ cabal run dcp < samples/basic.txt Up to date * Module parsed as: (Just ["this is the module's doc comment"],[(Just ["this is the doc comment for `doXXX()`"],"method doXXX() pass\n\n"),(Just ["this is the doc comment for `doYYY()`"],"method doYYY() pass\n")]) ``` https://github.com/complyue/dcp/commit/fd2df02f7218e59db2a732d5de74acedfefefaa2 ```diff optionalComma :: Parser Bool -optionalComma = fromMaybe False <$> optional (True <$ symbol ",") +optionalComma = fromMaybe False <$> optional (True <$ string ",") optionalSemicolon :: Parser Bool -optionalSemicolon = fromMaybe False <$> optional (True <$ symbol ";") +optionalSemicolon = fromMaybe False <$> optional (True <$ string ";") ``` Thanks! > On 2020-10-25, at 19:42, Jaro Reinders wrote: > > Aha, I think it is the 'lexeme' function that causes these problems. 'symbol = lexeme . string', but lexeme first skips over all the comments (even the multiline comments). > > On 10/25/20 12:36 PM, YueCompl wrote: >> Tried this: >> ```hs >> findIt = do >> -- ignore leading whitespaces and an optional semicolon in between >> nbsc >> ii0 <- getInput >> trace ("**about*to*match*semicolon*[" <> T.unpack ii0 <> "]") $ pure () >> optionalSemicolon >> trace ("**after*semicolon*attempt**") $ pure () >> nbsc >> -- try get a doc comment block >> getIt >>= \case >> ``` >> ```console >> $ cabal run dcp < samples/basic.txt >> Up to date >> **about*to*match*semicolon*[{## >> # this is the module's doc comment >> #} >> # this is regular line comment to be dropped in parsing >> {## >> # this is the doc comment for `doXXX()` >> #} >> method doXXX() pass >> {# >> # this is regular block comment to be dropped in parsing >> #} >> {## >> # this is the doc comment for `doYYY()` >> #} >> method doYYY() pass >> ] >> dcp: 10:1: >> | >> 10 | method doXXX() pass >> | ^ >> unexpected 'm' >> expecting ';' >> CallStack (from HasCallStack): >> error, called at src/Parser.hs:154:14 in main:Parser >> ``` >> So it seems the very first optionalSemicolon failed without consuming anything ... >> And actually I totally have no clue how the content before `method doXXX` is consumed. >>> On 2020-10-25, at 19:26, Jaro Reinders wrote: >>> >>> I think the optionalSemicolon will consume the '{' of the first comment and then the 'getIt' will produce Nothing because the input doesn't start with '{##' anymore, and then it will go on like that until the optionalSemicolon consumes that 'm'. >>> >>> On 10/25/20 12:21 PM, YueCompl wrote: >>>> The rerun is guarded behind an optional `L.skipBlockCommentNested "{#" "#}"` got a `Just{}` result, and only after `getIt` got a `Nothing` result. >>>>> On 2020-10-25, at 19:16, Jaro Reinders wrote: >>>>> >>>>> But the 'findIt' parser will be rerun after every block comment right? >>>>> >>>>> On 10/25/20 12:10 PM, YueCompl wrote: >>>>>> Unlike `sc`, `nbsc` won't consume block comments, as it's defined as `L.space space1 (L.skipLineComment "#") empty` >>>>>>> On 2020-10-25, at 19:07, Jaro Reinders wrote: >>>>>>> >>>>>>> But in the basic.txt example, won't the first nbsc consume everything up to 'method doXXX() pass'. Then the semicolon parser consumes the 'm' character, and that will never backtrack. So that 'm' character is lost. >>>>>>> >>>>>>> On 10/25/20 12:00 PM, YueCompl wrote: >>>>>>>> During the parsing of doc comments, backtracking is off on purpose, as it won't consume syntactic contents, merely whitespaces (while doc comment is a special form of block comment), the desired result is `Nothing` or `Just docCmt` without backtracking of whitespaces. >>>>>>>>> On 2020-10-25, at 18:53, Jaro Reinders wrote: >>>>>>>>> >>>>>>>>> I think you have to insert a 'try' manually inside the optional, because megaparsec doesn't do backtracking by default. >>>>>>>>> >>>>>>>>> On 10/25/20 11:27 AM, YueCompl via Haskell-Cafe wrote: >>>>>>>>>> Dear Cafe, >>>>>>>>>> I find myself unable to reason about an error that `optional` in a parser err out instead of return Nothing, I asked the question at StackOverflow, and would like to seek your help here as well. >>>>>>>>>> https://stackoverflow.com/questions/64522568/why-optional-in-a-parser-can-err-out >>>>>>>>>> https://github.com/complyue/dcp is a minimum working example to reprod this error >>>>>>>>>> $ cabal run dcp:dcp < samples/basic.txt >>>>>>>>>> Up to date >>>>>>>>>> dcp: 10:1: >>>>>>>>>> | >>>>>>>>>> 10 | method doXXX() pass >>>>>>>>>> | ^ >>>>>>>>>> unexpected 'm' >>>>>>>>>> expecting ';' >>>>>>>>>> CallStack (from HasCallStack): >>>>>>>>>> error, called at src/Parser.hs:149:14 in main:Parser >>>>>>>>>> $ >>>>>>>>>> I believe it's optionalSemicolon causing the failure: >>>>>>>>>> https://github.com/complyue/dcp/blob/1df7ad590d78d4fa9a017eb53f9f265e291bdfa7/src/Parser.hs#L50-L54 >>>>>>>>>> findIt = do >>>>>>>>>> -- ignore leading whitespaces and an optional semicolon in between >>>>>>>>>> nbsc >> optionalSemicolon >> nbsc >>>>>>>>>> -- try get a doc comment block >>>>>>>>>> getIt >>= \case >>>>>>>>>> And it's defined like this: https://github.com/complyue/dcp/blob/1df7ad590d78d4fa9a017eb53f9f265e291bdfa7/src/Parser.hs#L31-L32 >>>>>>>>>> optionalSemicolon :: Parser Bool >>>>>>>>>> optionalSemicolon = fromMaybe False <$> optional (True <$ symbol ";") >>>>>>>>>> I can't reason about why it can fail like this. >>>>>>>>>> Best regards, >>>>>>>>>> Compl >>>>>>>>>> _______________________________________________ >>>>>>>>>> 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. -------------- next part -------------- An HTML attachment was scrubbed... URL: From compl.yue at icloud.com Sun Oct 25 13:55:23 2020 From: compl.yue at icloud.com (YueCompl) Date: Sun, 25 Oct 2020 21:55:23 +0800 Subject: [Haskell-cafe] How to encode *NoMatch* after consumed some input in a parser Message-ID: <4A9D0921-C444-4726-B0F9-2556A8BA4DF5@icloud.com> Dear Cafe, This is a followup question to my previous one. Also asked as a Megaparsec question issue at https://github.com/mrkkrp/megaparsec/issues/429 As I observed (have no idea where a canonical definition could live for this) that for the contract of parser combinators: fail with no input consumed will have next alternative to be tried with possible success fail with some input consumed will err out immediately regardless rest alternatives Am I right about these rules? Where is the official specification of such rules? Then I guess that empty result of a parser could mean NoMatch even after consumed some input, and want to leverage this semantic, but encountered error with current implementation https://github.com/complyue/dcp/blob/5be688396b7e2bda00ea80fd99d2a7b3ec5c788d/src/Parser.hs#L138-L146 artifactDecl :: Parser ArtDecl artifactDecl = do artCmt <- immediateDocComments (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) $ cabal run dcp < samples/full.txt Up to date dcp: 73:1: | 73 | | ^ expecting "{#", "{##", or artifact body CallStack (from HasCallStack): error, called at src/Parser.hs:151:14 in main:Parser So how can I achieve that? Background is I'm trying to prototype an implementation of doc comment parsing as described at #428 Best regards, Compl -------------- next part -------------- An HTML attachment was scrubbed... URL: From compl.yue at icloud.com Sun Oct 25 23:28:49 2020 From: compl.yue at icloud.com (Compl Yue) Date: Mon, 26 Oct 2020 07:28:49 +0800 Subject: [Haskell-cafe] Does it violate the laws of Alternative/Monoid to implement empty/mempty with mzero from MonadPlus? Message-ID: <34AABC73-FAC8-4126-8356-62E7FE0DA273@getmailspring.com> Dear Cafe, Regarding the Alternative instance of ParsecT from Megaparsec here: https://github.com/mrkkrp/megaparsec/blob/ccf314b0b940bdbfec3820b18f42d241e6920b61/Text/Megaparsec/Internal.hs#L202-L205 (https://link.getmailspring.com/link/34AABC73-FAC8-4126-8356-62E7FE0DA273 at getmailspring.com/0?redirect=https%3A%2F%2Fgithub.com%2Fmrkkrp%2Fmegaparsec%2Fblob%2Fccf314b0b940bdbfec3820b18f42d241e6920b61%2FText%2FMegaparsec%2FInternal.hs%23L202-L205&recipient=aGFza2VsbC1jYWZlQGhhc2tlbGwub3Jn) -- | 'empty' is a parser that __fails__ without consuming input. instance (Ord e, Stream s) => Alternative (ParsecT e s m) where empty = mzero (<|>) = mplus I come to this question, does it violate the laws of Alternative/Monoid to implement empty/mempty with mzero from MonadPlus? First of all, can I somehow regard Alternative as a repurposed Monoid? So this question applies similarly to Monoid as well? Then I think the lack of failure semantic in Alternative/Monoid might have two different interpretations: 1) It must NOT fail 2) Whether it can fail or not is not cared Which one is correct? I feel 1) is in spirit of purism, that pure code should not fail, but it's a monad, then 2) may in monad's spirit to be effectful and composable with other effects including failing. I'd think it violates the law when interpretation 1) is taken. Background about my confusion: https://github.com/mrkkrp/megaparsec/issues/429#issuecomment-716170935 (https://link.getmailspring.com/link/34AABC73-FAC8-4126-8356-62E7FE0DA273 at getmailspring.com/1?redirect=https%3A%2F%2Fgithub.com%2Fmrkkrp%2Fmegaparsec%2Fissues%2F429%23issuecomment-716170935&recipient=aGFza2VsbC1jYWZlQGhhc2tlbGwub3Jn) The parsing of whitespaces is so handled in Megaparsec's idiom that every lexeme should consume (discard) all whitespaces following it. But after tinkered around with some related issues, I by now would think a silent, joinable empty / mempty might be more sense making for each whitespace block to be parsed individually, i.e. without association with any lexeme while neither will fail the overall parsing. The demand comes in that I'd like the doc comment parser to evaulate to empty and contribute nothing to an enclosing many , in case all following it is whtespaces till eof; while in case it's followed by some artifact definition, the doc comment parser should evaluate to a syntactic doc node assoicated with that artifact. empty seems an ideal device for that purpose, but in the fact it is implemented with mzero, the overall parsing will fail, which makes it infeasible. Best regards, Compl -------------- next part -------------- An HTML attachment was scrubbed... URL: From dennis.raddle at gmail.com Mon Oct 26 06:16:45 2020 From: dennis.raddle at gmail.com (Dennis Raddle) Date: Sun, 25 Oct 2020 23:16:45 -0700 Subject: [Haskell-cafe] error when running stack In-Reply-To: <20201025072024.GY34643@straasha.imrryr.org> References: <20201025072024.GY34643@straasha.imrryr.org> Message-ID: It seems to be related to ghc-up. I think installing ghc-up changed my path. Perhaps it's bundled with an old version of stack. Changing the paths back fixed the problem. So I must be running the version of stack now that I've been using all this time, that's been working all this time. So.. ghcup seems to have an old version of stack, or puts an old version on the path? Just thinking out loud here. Dennis On Sun, Oct 25, 2020 at 12:21 AM Viktor Dukhovni wrote: > On Sat, Oct 24, 2020 at 06:03:59PM -0700, Dennis Raddle wrote: > > > I get this error when running stack: > > > > Downloading lts- xxxx building plan > > aesonException "Error in $['system-info']: key \"os\" not present" > > The files in question are the build plan files, e.g. > > ~/.stack/build-plan/lts-13.10.yaml > > Older versions of stack used to look for an "os" field > under "system-info" in these files: > > ... > system-info: > core-packages: > ghc: 8.6.3 > bytestring: 0.10.8.2 > unix: 2.7.2.2 > base: 4.12.0.0 > time: 1.8.0.2 > hpc: 0.6.0.3 > filepath: 1.4.2.1 > process: 1.6.3.0 > array: 0.5.3.0 > integer-gmp: 1.0.2.0 > containers: 0.6.0.1 > ghc-boot: 8.6.3 > binary: 0.8.6.0 > ghc-prim: 0.5.3 > ghc-heap: 8.6.3 > ghci: 8.6.3 > rts: '1.0' > terminfo: 0.4.1.2 > transformers: 0.5.5.0 > deepseq: 1.4.4.0 > ghc-boot-th: 8.6.3 > pretty: 1.1.3.6 > template-haskell: 2.14.0.0 > directory: 1.3.3.0 > ghc-version: 8.6.3 > os: linux > ... > > That code was dropped from stack some time back (between v1.5.1 and > v1.6.1), and new build plans likely don't include the no longer needed > information. Perhaps you're trying to use a very old stack executable > (older than 1.6.1?) to process a new build plan (LTS snapshot). > > commit 624165387b77df09108888a8c4ec3b0b512e5096 > Author: Michael Snoyman > Date: Mon Jun 26 08:35:31 2017 +0300 > > Remove a bunch of unneeded info from BuildPlan > > > running "stack update" didn't help. > > I'm very confused because I don't remember what I did that provoked this > > error. > > Simplest is probably to reinstall stack from scratch, perhaps you're > missing too many intermediate versions to perform a direct upgrade. > > -- > Viktor. > _______________________________________________ > 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. -------------- next part -------------- An HTML attachment was scrubbed... URL: From olf at aatal-apotheke.de Mon Oct 26 20:18:29 2020 From: olf at aatal-apotheke.de (Olaf Klinke) Date: Mon, 26 Oct 2020 21:18:29 +0100 Subject: [Haskell-cafe] Does it violate the laws of Alternative/Monoid to implement empty/mempty with mzero from MonadPlus? Message-ID: 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 From ramin.honary at cross-compass.com Tue Oct 27 01:05:01 2020 From: ramin.honary at cross-compass.com (Ramin Honary) Date: Tue, 27 Oct 2020 10:05:01 +0900 Subject: [Haskell-cafe] [Job] Cross Compass is hiring Haskell developers Message-ID: Cross Compass ( https://www.cross-compass.com/ ) is a data science and machine learning consultancy located in Tokyo, Japan. We are hiring Haskellers to work on a machine learning platform. We are mainly looking for people skilled in either web programming, machine learning, or embedded development. Technical skills used on our team ================================= Our machine learning platform has quite a few moving parts: - two web frontends (one written in PureScript, and one written in TypeScript) - two backends (one written in Haskell, and one written in Ruby) - a deep learning engine (written in Haskell, calling out to Caffe2) - a library for running models on embedded devices (written in C, C++ and CUDA calling out to oneDNN and cuDNN) Given these various parts, we end up touching a lot of different technologies: - Haskell, including the following libraries: - conduit - JuicyPixels - lens - servant - PureScript, including the following libraries: - affjax - argonaut - protobuf - react-basic - Nix (and a little Docker) - Ruby - TypeScript - C (and a little C++ and CUDA) - machine learning (we are currently mostly focused on deep learning) We have long-term plans to move away from Ruby and TypeScript (and towards Haskell and PureScript), but no concrete time-frame for when this will happen. What sort of developers are we looking for? =========================================== In the short term, we are planning on hiring two developers. We want to hire developers who know some combination of the above technologies, or would be interested in learning. We imagine hiring one developer who is familiar with Ruby, TypeScript, and Haskell. Machine learning experience wouldn't be necessary, but helpful. They would start out with web development in Ruby and Typescript, along with some Haskell work. Over time they would probably move more towards doing web development in Haskell and PureScript. We imagine hiring one other developer who is familiar with machine learning, Haskell, and possibly embedded development. They would help with the Haskell deep learning engine, as well as the C-based embedded library. They would probably also have the chance to help with the Haskel web backend and PureScript web frontend. We are also interested in any other candidates that have unique combinations of the above skills, or interesting backgrounds. Please don't hesitate to apply based on your background or skills. Previous working experience with Haskell or any of the other technologies listed above is not a requirement. Non-technical requirements ========================== We would prefer to hire developers that can work locally from Tokyo. We sponsor visas for developers who want to move to Japan. If we don't find anyone who is willing to relocate to Japan, we will considering hiring remote-only candidates. Most of our meetings take place in the afternoon in JST (UTC+9), which is around 5 AM UTC. Although we are flexible on this point. https://www.timeanddate.com/worldclock/converter.html?iso=20201104T050000&p1=248 We prefer to hire developers who want to work full time (40 hours per week). Pay ==================== The salary range for this position is 6 to 8 million yen (about USD $57,000 to $75,000). Application and hiring process ============================== If this sounds interesting, please feel free to email us at recruit at cross-compass.com . We are not too big on standard resumes, but you are welcome to send us any information that you think would catch our attention, including things like: - relevant work history (e.g. work somewhere before using Haskell? Or maybe doing frontend development with TypeScript?) - relevant education history (e.g. took a class on machine learning?) - open-source software links (e.g. author any interesting libraries? have a cool machine learning project?) - papers, articles, blog posts, social media, or anything else which reflects well on you We'd also like to know your situation regarding on-premise work vs. remote, including whether or not you would be interested in moving to Japan. There will be one interview to learn more about you and for you to ask us questions. We will invite promising candidates to a part-time, one-month paid trial period. During this trial period we see what it is like working with you, and you get to see how we work as a team. Ideally, you'd be able to work at least a couple hours a week (so we both have an idea what is it like to work with each other when the month is over), but we are flexible with the details here. We would make you an offer after the trial-period. Haskellers at Cross Compass =========================== There are already a few Haskellers at Cross Compass. You may have interacted with us online or at various meetups and conferences. - Viktor Kronvall ( https://github.com/considerate ) - Jonas Carpay ( https://github.com/jonascarpay ) - Ramin Honary ( https://github.com/RaminHAL9001 ) - James Brock ( https://github.com/jamesdbrock ) - Dennis Gosnell ( https://functor.tokyo/ ) Other Considerations ==================== - We would consider hiring someone part-time with a lot of experience, although we would probably only do this if we don't find someone willing to work full time. - Being able to speak Japanese is not a requirement. - HR will often help employees new to Japan with things like finding an apartment, opening a bank account, getting a cell phone, etc. - We don't particularly have any requirements regarding years of experience. Coronavirus =========== - It is currently possible for people to get a work visa and come to Japan. (At one point foreigners weren't able to enter Japan, but this restriction has been relaxed and now people can enter with a work visa.) - Over the last few months, there are on average a couple hundred cases per day in Tokyo. - Most people in Cross Compass have been working remotely since Coronavirus became a problem in Tokyo. Some people go in to the office once or twice a week. I imagine this will continue until cases of Coronavirus start to drop. I don't know what the plans for what the remote working situation will be like when Coronavirus is no longer a problem. If you're concerned about this, please make sure to ask about this in your application email. From compl.yue at icloud.com Tue Oct 27 09:26:27 2020 From: compl.yue at icloud.com (YueCompl) Date: Tue, 27 Oct 2020 17:26:27 +0800 Subject: [Haskell-cafe] Does it violate the laws of Alternative/Monoid to implement empty/mempty with mzero from MonadPlus? In-Reply-To: References: Message-ID: 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 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 > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From compl.yue at icloud.com Tue Oct 27 09:44:15 2020 From: compl.yue at icloud.com (YueCompl) Date: Tue, 27 Oct 2020 17:44:15 +0800 Subject: [Haskell-cafe] Does it violate the laws of Alternative/Monoid to implement empty/mempty with mzero from MonadPlus? In-Reply-To: References: Message-ID: On second thought, my parser's ability to conditionally evaluate to `empty` is also suspicious, maybe a parser can only statically being `empty` or not? But technically a parser can evaluate to `empty` or otherwise dynamically, which seems very confusing to me. > On 2020-10-27, at 17:26, 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 > 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. -------------- next part -------------- An HTML attachment was scrubbed... URL: From jaro.reinders at gmail.com Tue Oct 27 09:47:01 2020 From: jaro.reinders at gmail.com (Jaro Reinders) Date: Tue, 27 Oct 2020 10:47:01 +0100 Subject: [Haskell-cafe] Does it violate the laws of Alternative/Monoid to implement empty/mempty with mzero from MonadPlus? In-Reply-To: References: Message-ID: <52e99112-5ef3-4a4b-5de9-88eadba35e39@gmail.com> 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 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. > From compl.yue at icloud.com Tue Oct 27 10:15:22 2020 From: compl.yue at icloud.com (YueCompl) Date: Tue, 27 Oct 2020 18:15:22 +0800 Subject: [Haskell-cafe] Does it violate the laws of Alternative/Monoid to implement empty/mempty with mzero from MonadPlus? In-Reply-To: <52e99112-5ef3-4a4b-5de9-88eadba35e39@gmail.com> References: <52e99112-5ef3-4a4b-5de9-88eadba35e39@gmail.com> Message-ID: <4EFE4DA1-3C7D-46CB-B9C4-DD7D22C22C48@icloud.com> 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 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 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. -------------- next part -------------- An HTML attachment was scrubbed... URL: From jaro.reinders at gmail.com Tue Oct 27 10:33:26 2020 From: jaro.reinders at gmail.com (Jaro Reinders) Date: Tue, 27 Oct 2020 11:33:26 +0100 Subject: [Haskell-cafe] Does it violate the laws of Alternative/Monoid to implement empty/mempty with mzero from MonadPlus? In-Reply-To: <4EFE4DA1-3C7D-46CB-B9C4-DD7D22C22C48@icloud.com> References: <52e99112-5ef3-4a4b-5de9-88eadba35e39@gmail.com> <4EFE4DA1-3C7D-46CB-B9C4-DD7D22C22C48@icloud.com> Message-ID: <38fa67ec-f4f7-d118-9662-1b1908105ad7@gmail.com> 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 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 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. > > From lysxia at gmail.com Tue Oct 27 15:22:00 2020 From: lysxia at gmail.com (Li-yao Xia) Date: Tue, 27 Oct 2020 11:22:00 -0400 Subject: [Haskell-cafe] Does it violate the laws of Alternative/Monoid to implement empty/mempty with mzero from MonadPlus? In-Reply-To: <38fa67ec-f4f7-d118-9662-1b1908105ad7@gmail.com> References: <52e99112-5ef3-4a4b-5de9-88eadba35e39@gmail.com> <4EFE4DA1-3C7D-46CB-B9C4-DD7D22C22C48@icloud.com> <38fa67ec-f4f7-d118-9662-1b1908105ad7@gmail.com> Message-ID: <8432d210-18bf-d47b-96ec-0f830c7beceb@gmail.com> 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 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 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. From compl.yue at icloud.com Tue Oct 27 15:38:24 2020 From: compl.yue at icloud.com (YueCompl) Date: Tue, 27 Oct 2020 23:38:24 +0800 Subject: [Haskell-cafe] Does it violate the laws of Alternative/Monoid to implement empty/mempty with mzero from MonadPlus? In-Reply-To: <8432d210-18bf-d47b-96ec-0f830c7beceb@gmail.com> References: <52e99112-5ef3-4a4b-5de9-88eadba35e39@gmail.com> <4EFE4DA1-3C7D-46CB-B9C4-DD7D22C22C48@icloud.com> <38fa67ec-f4f7-d118-9662-1b1908105ad7@gmail.com> <8432d210-18bf-d47b-96ec-0f830c7beceb@gmail.com> Message-ID: <24DB5AD8-EC14-4775-9CF7-44007ADFC225@icloud.com> 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 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. >> 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 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 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. > _______________________________________________ > 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. From lysxia at gmail.com Tue Oct 27 15:57:50 2020 From: lysxia at gmail.com (Li-yao Xia) Date: Tue, 27 Oct 2020 11:57:50 -0400 Subject: [Haskell-cafe] Does it violate the laws of Alternative/Monoid to implement empty/mempty with mzero from MonadPlus? In-Reply-To: <24DB5AD8-EC14-4775-9CF7-44007ADFC225@icloud.com> References: <52e99112-5ef3-4a4b-5de9-88eadba35e39@gmail.com> <4EFE4DA1-3C7D-46CB-B9C4-DD7D22C22C48@icloud.com> <38fa67ec-f4f7-d118-9662-1b1908105ad7@gmail.com> <8432d210-18bf-d47b-96ec-0f830c7beceb@gmail.com> <24DB5AD8-EC14-4775-9CF7-44007ADFC225@icloud.com> Message-ID: <2b607875-775b-1102-7cfc-f183dbd7411b@gmail.com> 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 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. >>> 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 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 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. >> _______________________________________________ >> 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. > From compl.yue at icloud.com Tue Oct 27 16:42:16 2020 From: compl.yue at icloud.com (YueCompl) Date: Wed, 28 Oct 2020 00:42:16 +0800 Subject: [Haskell-cafe] Does it violate the laws of Alternative/Monoid to implement empty/mempty with mzero from MonadPlus? In-Reply-To: <2b607875-775b-1102-7cfc-f183dbd7411b@gmail.com> References: <52e99112-5ef3-4a4b-5de9-88eadba35e39@gmail.com> <4EFE4DA1-3C7D-46CB-B9C4-DD7D22C22C48@icloud.com> <38fa67ec-f4f7-d118-9662-1b1908105ad7@gmail.com> <8432d210-18bf-d47b-96ec-0f830c7beceb@gmail.com> <24DB5AD8-EC14-4775-9CF7-44007ADFC225@icloud.com> <2b607875-775b-1102-7cfc-f183dbd7411b@gmail.com> Message-ID: <471B26C7-B66C-4F33-B227-E67E839C49F2@icloud.com> `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 ```hs arts <- manyTill (scWithSemiColons >> artifactDecl) eof ``` And the artifact parser 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 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 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. >>>> 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 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 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. >>> _______________________________________________ >>> 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. -------------- next part -------------- An HTML attachment was scrubbed... URL: From compl.yue at icloud.com Tue Oct 27 16:44:50 2020 From: compl.yue at icloud.com (YueCompl) Date: Wed, 28 Oct 2020 00:44:50 +0800 Subject: [Haskell-cafe] Does it violate the laws of Alternative/Monoid to implement empty/mempty with mzero from MonadPlus? In-Reply-To: <471B26C7-B66C-4F33-B227-E67E839C49F2@icloud.com> References: <52e99112-5ef3-4a4b-5de9-88eadba35e39@gmail.com> <4EFE4DA1-3C7D-46CB-B9C4-DD7D22C22C48@icloud.com> <38fa67ec-f4f7-d118-9662-1b1908105ad7@gmail.com> <8432d210-18bf-d47b-96ec-0f830c7beceb@gmail.com> <24DB5AD8-EC14-4775-9CF7-44007ADFC225@icloud.com> <2b607875-775b-1102-7cfc-f183dbd7411b@gmail.com> <471B26C7-B66C-4F33-B227-E67E839C49F2@icloud.com> Message-ID: <5EDB0D46-08FF-4812-8E51-0A9C30C01D06@icloud.com> 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 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 > > ```hs > arts <- manyTill (scWithSemiColons >> artifactDecl) eof > ``` > > And the artifact parser 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 > 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 > 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 . >>>>> 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 > 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 > 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. >>>> _______________________________________________ >>>> 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. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From compl.yue at gmail.com Wed Oct 28 09:10:45 2020 From: compl.yue at gmail.com (Compl Yue) Date: Wed, 28 Oct 2020 17:10:45 +0800 Subject: [Haskell-cafe] Consider adding recoverability to the vocabulary of parser combinators Message-ID: Dear Cafe, I'm still not fully clear about the confusion regarding megaparsec's behavior that I posted lately here. But now comes to my mind that it may have some problem rooted in the lacking of recoverability semantic with respect to parser combinators, some quoting from http://hackage.haskell.org/package/parser-combinators/docs/Control-Applicative-Combinators.html The *A note on backtracking* section > Combinators in this module are defined in terms Applicative and Alternative operations. And `empty`'s doc: > This parser fails unconditionally without providing any information about the cause of the failure. Clearly `empty` is used to express failure, but there is seemingly no device to explicitly express whether a failure is recoverable. Then I observed megaparsec's implicit rule as currently implemented is like: *) a failure with no input consumed can be recovered by rest parsers *) a failure with some input consumed can not be recovered by rest parsers This works to great extent, but I would think the expressiveness can be further extended for a parser from the application, to tell the library that some input induces recoverable failure. I have no expertise to suggest whether `MonadPlus` and/or `MonadFail` are suitable devices to be considered, but as megaparsec has implemented instances for them, I do feel some tweaks would be possible and meaningful. Best regards, Compl -------------- next part -------------- An HTML attachment was scrubbed... URL: From compl.yue at gmail.com Wed Oct 28 09:18:23 2020 From: compl.yue at gmail.com (Compl Yue) Date: Wed, 28 Oct 2020 17:18:23 +0800 Subject: [Haskell-cafe] Consider adding recoverability to the vocabulary of parser combinators Message-ID: (sorry for repost, seems GMail's html processing on my last email has rendered it barely readable, so again with plain text here) Dear Cafe, I'm still not fully clear about the confusion regarding megaparsec's behavior that I posted lately here. But now comes to my mind that it may have some problem rooted in the lacking of recoverability semantic with respect to parser combinators, some quoting from http://hackage.haskell.org/package/parser-combinators/docs/Control-Applicative-Combinators.html The *A note on backtracking* section > Combinators in this module are defined in terms Applicative and Alternative operations. And `empty`'s doc: > This parser fails unconditionally without providing any information about the cause of the failure. Clearly `empty` is used to express failure, but there is seemingly no device to explicitly express whether a failure is recoverable. Then I observed megaparsec's implicit rule as currently implemented is like: *) a failure with no input consumed can be recovered by rest parsers *) a failure with some input consumed can not be recovered by rest parsers This works to great extent, but I would think the expressiveness can be further extended for a parser from the application, to tell the library that some input induces recoverable failure. I have no expertise to suggest whether `MonadPlus` and/or `MonadFail` are suitable devices to be considered, but as megaparsec has implemented instances for them, I do feel some tweaks would be possible and meaningful. Best regards, Compl -------------- next part -------------- An HTML attachment was scrubbed... URL: From lysxia at gmail.com Wed Oct 28 12:19:52 2020 From: lysxia at gmail.com (Li-yao Xia) Date: Wed, 28 Oct 2020 08:19:52 -0400 Subject: [Haskell-cafe] Consider adding recoverability to the vocabulary of parser combinators In-Reply-To: References: Message-ID: Hi Compl, At least, for the example you gave on this list, it can be fixed by returning Nothing instead of using the facility for failure baked into (mega)parsec. (Proposed diff for reference: https://github.com/complyue/dcp/pull/3) "Returning Nothing" can be seen as adding a new channel for errors, turning the Parser monad into `MaybeT Parser`. Then `return Nothing` is how `empty` is defined by `MaybeT`, allowing that error to be caught and recovered from at the point where it was thrown, no backtracking. (And the original failure mode of Parser becomes `lift empty`.) Does that address your problem? Cheers, Li-yao On 10/28/2020 5:18 AM, Compl Yue wrote: > (sorry for repost, seems GMail's html processing on my last email has > rendered it barely readable, so again with plain text here) > > Dear Cafe, > > I'm still not fully clear about the confusion regarding megaparsec's > behavior that I posted lately here. But now comes to my mind that it may > have some problem rooted in the lacking of recoverability semantic with > respect to parser combinators, some quoting from > http://hackage.haskell.org/package/parser-combinators/docs/Control-Applicative-Combinators.html > > The  *A note on backtracking* section > > > Combinators in this module are defined in terms Applicative and > Alternative operations. > > And `empty`'s doc: > > > This parser fails unconditionally without providing any information > about the cause of the failure. > > Clearly `empty` is used to express failure, but there is seemingly no > device to explicitly express whether a failure is recoverable. Then I > observed megaparsec's implicit rule as currently implemented is like: > > *) a failure with no input consumed can be recovered by rest parsers > *) a failure with some input consumed can not be recovered by rest parsers > > This works to great extent, but I would think the expressiveness can be > further extended for a parser from the application, to tell the library > that some input induces recoverable failure. > > I have no expertise to suggest whether `MonadPlus` and/or `MonadFail` > are suitable devices to be considered, but as megaparsec has implemented > instances for them, I do feel some tweaks would be possible and meaningful. > > Best regards, > Compl > > > _______________________________________________ > 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. > From compl.yue at gmail.com Wed Oct 28 13:37:11 2020 From: compl.yue at gmail.com (Compl Yue) Date: Wed, 28 Oct 2020 21:37:11 +0800 Subject: [Haskell-cafe] Consider adding recoverability to the vocabulary of parser combinators In-Reply-To: References: Message-ID: Hi Li-yao, I appreciate your help especially the PR as a working fix. But personally I don't like the overall method of your solution, I can see Monad Transformers are powerful enough to tackle similar problems, but I'm not satisfied by the ergonomics in composing monads with transformers. `ParsecT` had already caused me much pain to get started in the beginning, and I'm still not fluent (comfortable) in transforming monads, especially I'm afraid I will have to transform much of the standard combinator functions, in order to get the real case parser working, as its resulting AST is much more complex. I still have faith in the improvement of megaparsec as a well known parser combinator library (I regard it as the best for engineering needs among other libraries), and I must admit megaparsec already elegantly works 99% out of my current use cases, and the very issue we are talking about is a nice-to-have rather than must-to-have, so I would think we still have time to anticipate more options to come out. And I particularly like to see parser combinators have this issue addressed in its own design space. Thanks again with best regards, Compl On Wed, Oct 28, 2020 at 8:19 PM Li-yao Xia wrote: > Hi Compl, > > At least, for the example you gave on this list, it can be fixed by > returning Nothing instead of using the facility for failure baked into > (mega)parsec. (Proposed diff for reference: > https://github.com/complyue/dcp/pull/3) > > "Returning Nothing" can be seen as adding a new channel for errors, > turning the Parser monad into `MaybeT Parser`. Then `return Nothing` is > how `empty` is defined by `MaybeT`, allowing that error to be caught and > recovered from at the point where it was thrown, no backtracking. (And > the original failure mode of Parser becomes `lift empty`.) > > Does that address your problem? > > Cheers, > Li-yao > > On 10/28/2020 5:18 AM, Compl Yue wrote: > > (sorry for repost, seems GMail's html processing on my last email has > > rendered it barely readable, so again with plain text here) > > > > Dear Cafe, > > > > I'm still not fully clear about the confusion regarding megaparsec's > > behavior that I posted lately here. But now comes to my mind that it may > > have some problem rooted in the lacking of recoverability semantic with > > respect to parser combinators, some quoting from > > > http://hackage.haskell.org/package/parser-combinators/docs/Control-Applicative-Combinators.html > > > > The *A note on backtracking* section > > > > > Combinators in this module are defined in terms Applicative and > > Alternative operations. > > > > And `empty`'s doc: > > > > > This parser fails unconditionally without providing any information > > about the cause of the failure. > > > > Clearly `empty` is used to express failure, but there is seemingly no > > device to explicitly express whether a failure is recoverable. Then I > > observed megaparsec's implicit rule as currently implemented is like: > > > > *) a failure with no input consumed can be recovered by rest parsers > > *) a failure with some input consumed can not be recovered by rest > parsers > > > > This works to great extent, but I would think the expressiveness can be > > further extended for a parser from the application, to tell the library > > that some input induces recoverable failure. > > > > I have no expertise to suggest whether `MonadPlus` and/or `MonadFail` > > are suitable devices to be considered, but as megaparsec has implemented > > instances for them, I do feel some tweaks would be possible and > meaningful. > > > > Best regards, > > Compl > > > > > > _______________________________________________ > > 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. > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From compl.yue at gmail.com Wed Oct 28 13:48:37 2020 From: compl.yue at gmail.com (Compl Yue) Date: Wed, 28 Oct 2020 21:48:37 +0800 Subject: [Haskell-cafe] Consider adding recoverability to the vocabulary of parser combinators In-Reply-To: References: Message-ID: (sorry I forgot the text color again, maybe https://darkreader.org is to blame, anyway plain text mode I should use) Hi Li-yao, I appreciate your help especially the PR as a working fix. But personally I don't like the overall method of your solution, I can see Monad Transformers are powerful enough to tackle similar problems, but I'm not satisfied by the ergonomics in composing monads with transformers. `ParsecT` had already caused me much pain to get started in the beginning, and I'm still not fluent (comfortable) in transforming monads, especially I'm afraid I will have to transform much of the standard combinator functions, in order to get the real case parser working, as its resulting AST is much more complex. I still have faith in the improvement of megaparsec as a well known parser combinator library (I regard it as the best for engineering needs among other libraries), and I must admit megaparsec already elegantly works 99% out of my current use cases, and the very issue we are talking about is a nice-to-have rather than must-to-have, so I would think we still have time to anticipate more options to come out. And I particularly like to see parser combinators have this issue addressed in its own design space. Thanks again with best regards, Compl On Wed, Oct 28, 2020 at 8:19 PM Li-yao Xia wrote: > > Hi Compl, > > At least, for the example you gave on this list, it can be fixed by > returning Nothing instead of using the facility for failure baked into > (mega)parsec. (Proposed diff for reference: > https://github.com/complyue/dcp/pull/3) > > "Returning Nothing" can be seen as adding a new channel for errors, > turning the Parser monad into `MaybeT Parser`. Then `return Nothing` is > how `empty` is defined by `MaybeT`, allowing that error to be caught and > recovered from at the point where it was thrown, no backtracking. (And > the original failure mode of Parser becomes `lift empty`.) > > Does that address your problem? > > Cheers, > Li-yao > > On 10/28/2020 5:18 AM, Compl Yue wrote: > > (sorry for repost, seems GMail's html processing on my last email has > > rendered it barely readable, so again with plain text here) > > > > Dear Cafe, > > > > I'm still not fully clear about the confusion regarding megaparsec's > > behavior that I posted lately here. But now comes to my mind that it may > > have some problem rooted in the lacking of recoverability semantic with > > respect to parser combinators, some quoting from > > http://hackage.haskell.org/package/parser-combinators/docs/Control-Applicative-Combinators.html > > > > The *A note on backtracking* section > > > > > Combinators in this module are defined in terms Applicative and > > Alternative operations. > > > > And `empty`'s doc: > > > > > This parser fails unconditionally without providing any information > > about the cause of the failure. > > > > Clearly `empty` is used to express failure, but there is seemingly no > > device to explicitly express whether a failure is recoverable. Then I > > observed megaparsec's implicit rule as currently implemented is like: > > > > *) a failure with no input consumed can be recovered by rest parsers > > *) a failure with some input consumed can not be recovered by rest parsers > > > > This works to great extent, but I would think the expressiveness can be > > further extended for a parser from the application, to tell the library > > that some input induces recoverable failure. > > > > I have no expertise to suggest whether `MonadPlus` and/or `MonadFail` > > are suitable devices to be considered, but as megaparsec has implemented > > instances for them, I do feel some tweaks would be possible and meaningful. > > > > Best regards, > > Compl > > > > > > _______________________________________________ > > 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. > > From mgajda at mimuw.edu.pl Thu Oct 29 14:46:10 2020 From: mgajda at mimuw.edu.pl (Michal J Gajda) Date: Thu, 29 Oct 2020 15:46:10 +0100 Subject: [Haskell-cafe] Haskell-Cafe Digest, Vol 206, Issue 17 In-Reply-To: References: Message-ID: Hi Ly-Xia, Compl, I would argue that `Maybe` does not scale well to debugging issues in big files. When parsing a large dataset you want: 1. Get precise coordinates and description of each fault so you can fix it. 1. Be able to parse it as far as possible to get overview of entire dataset before it can be handled in error-free way. Because of this I suggest adding resilience at the level of collections: 1. Each list of declarations, record fields etc, can be parsed with resilient version of `listOf` or `sepBy` combinators and return valid entries. In context where it replaces `forM` or `mapM` I named it `forData`: 2. Invalid entries should be put into logging monad (`WriterT [Error]` that keeps a list of errors and their coordinates). This approach can be used in monad that processes a list of records, as well as in the parser: ``` forData :: (a -> m (Either Error b)) -> WriterT [Error] m [b] type Parser e -- error type m -- monad a -- result = WriterT [e] m b parseList :: (a -> Parser m b) -> Parser m [b] ``` Argument is expanded in my Haskell.Love presentation: https://www.youtube.com/watch?v=KY27LsV11Rg&t=1281s When you want to gradually expand information on errors you can also use contravariant logging operator: ``` withErrorInfo :: (e -> f) -> Parser e m a -> Parser f m a data InFile e = InFile FilePath e parseFile filename = do addErrorInfo (InFile filename) $ do input <- liftIO (readFile filename) parseFile input ``` This gradual enrichment of error messages is frequently seen in IOHK project's state machines if you enjoy reading their source code. (If you want to make it more efficient by immediately processing errors instead of tagging them along in alist, please look at contravariant logging, But I usually recommend error aggregation as a last stage of processing to discover the most serious issues.) -- Cheers Michał ________________________________ Hi Compl, At least, for the example you gave on this list, it can be fixed by returning Nothing instead of using the facility for failure baked into (mega)parsec. (Proposed diff for reference: https://github.com/complyue/dcp/pull/3) "Returning Nothing" can be seen as adding a new channel for errors, turning the Parser monad into `MaybeT Parser`. Then `return Nothing` is how `empty` is defined by `MaybeT`, allowing that error to be caught and recovered from at the point where it was thrown, no backtracking. (And the original failure mode of Parser becomes `lift empty`.) Does that address your problem? Cheers, Li-yao On 10/28/2020 5:18 AM, Compl Yue wrote: > > I'm still not fully clear about the confusion regarding megaparsec's > behavior that I posted lately here. But now comes to my mind that it may > have some problem rooted in the lacking of recoverability semantic with > respect to parser combinators, some quoting from > http://hackage.haskell.org/package/parser-combinators/docs/Control-Applicative-Combinators.html > > The *A note on backtracking* section > > > Combinators in this module are defined in terms Applicative and > Alternative operations. > > And `empty`'s doc: > > > This parser fails unconditionally without providing any information > about the cause of the failure. > > Clearly `empty` is used to express failure, but there is seemingly no > device to explicitly express whether a failure is recoverable. Then I > observed megaparsec's implicit rule as currently implemented is like: > > *) a failure with no input consumed can be recovered by rest parsers > *) a failure with some input consumed can not be recovered by rest parsers > > This works to great extent, but I would think the expressiveness can be > further extended for a parser from the application, to tell the library > that some input induces recoverable failure. > > I have no expertise to suggest whether `MonadPlus` and/or `MonadFail` > are suitable devices to be considered, but as megaparsec has implemented > instances for them, I do feel some tweaks would be possible and meaningful. On Thu, Oct 29, 2020 at 1:01 PM wrote: > > Send Haskell-Cafe mailing list submissions to > haskell-cafe at haskell.org > > To subscribe or unsubscribe via the World Wide Web, visit > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > or, via email, send a message with subject or body 'help' to > haskell-cafe-request at haskell.org > > You can reach the person managing the list at > haskell-cafe-owner at haskell.org > > When replying, please edit your Subject line so it is more specific > than "Re: Contents of Haskell-Cafe digest..." > Today's Topics: > > 1. Re: Consider adding recoverability to the vocabulary of > parser combinators (Li-yao Xia) > 2. Re: Consider adding recoverability to the vocabulary of > parser combinators (Compl Yue) > 3. Re: Consider adding recoverability to the vocabulary of > parser combinators (Compl Yue) > > > > ---------- Forwarded message ---------- > From: Li-yao Xia > To: Compl Yue > Cc: "Haskell Café" > Bcc: > Date: Wed, 28 Oct 2020 08:19:52 -0400 > Subject: Re: [Haskell-cafe] Consider adding recoverability to the vocabulary of parser combinators > Hi Compl, > > At least, for the example you gave on this list, it can be fixed by > returning Nothing instead of using the facility for failure baked into > (mega)parsec. (Proposed diff for reference: > https://github.com/complyue/dcp/pull/3) > > "Returning Nothing" can be seen as adding a new channel for errors, > turning the Parser monad into `MaybeT Parser`. Then `return Nothing` is > how `empty` is defined by `MaybeT`, allowing that error to be caught and > recovered from at the point where it was thrown, no backtracking. (And > the original failure mode of Parser becomes `lift empty`.) > > Does that address your problem? > > Cheers, > Li-yao > > On 10/28/2020 5:18 AM, Compl Yue wrote: > > (sorry for repost, seems GMail's html processing on my last email has > > rendered it barely readable, so again with plain text here) > > > > Dear Cafe, > > > > I'm still not fully clear about the confusion regarding megaparsec's > > behavior that I posted lately here. But now comes to my mind that it may > > have some problem rooted in the lacking of recoverability semantic with > > respect to parser combinators, some quoting from > > http://hackage.haskell.org/package/parser-combinators/docs/Control-Applicative-Combinators.html > > > > The *A note on backtracking* section > > > > > Combinators in this module are defined in terms Applicative and > > Alternative operations. > > > > And `empty`'s doc: > > > > > This parser fails unconditionally without providing any information > > about the cause of the failure. > > > > Clearly `empty` is used to express failure, but there is seemingly no > > device to explicitly express whether a failure is recoverable. Then I > > observed megaparsec's implicit rule as currently implemented is like: > > > > *) a failure with no input consumed can be recovered by rest parsers > > *) a failure with some input consumed can not be recovered by rest parsers > > > > This works to great extent, but I would think the expressiveness can be > > further extended for a parser from the application, to tell the library > > that some input induces recoverable failure. > > > > I have no expertise to suggest whether `MonadPlus` and/or `MonadFail` > > are suitable devices to be considered, but as megaparsec has implemented > > instances for them, I do feel some tweaks would be possible and meaningful. > > > > Best regards, > > Compl > > > > > > _______________________________________________ > > 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. > > > > > > > ---------- Forwarded message ---------- > From: Compl Yue > To: Li-yao Xia > Cc: "Haskell Café" > Bcc: > Date: Wed, 28 Oct 2020 21:37:11 +0800 > Subject: Re: [Haskell-cafe] Consider adding recoverability to the vocabulary of parser combinators > Hi Li-yao, > > I appreciate your help especially the PR as a working fix. > > But personally I don't like the overall method of your solution, I can see Monad Transformers are powerful enough to tackle similar problems, but I'm not satisfied by the ergonomics in composing monads with transformers. `ParsecT` had already caused me much pain to get started in the beginning, and I'm still not fluent (comfortable) in transforming monads, especially I'm afraid I will have to transform much of the standard combinator functions, in order to get the real case parser working, as its resulting AST is much more complex. > > I still have faith in the improvement of megaparsec as a well known parser combinator library (I regard it as the best for engineering needs among other libraries), and I must admit megaparsec already elegantly works 99% out of my current use cases, and the very issue we are talking about is a nice-to-have rather than must-to-have, so I would think we still have time to anticipate more options to come out. > > And I particularly like to see parser combinators have this issue addressed in its own design space. > > Thanks again with best regards, > Compl > > > On Wed, Oct 28, 2020 at 8:19 PM Li-yao Xia wrote: >> >> Hi Compl, >> >> At least, for the example you gave on this list, it can be fixed by >> returning Nothing instead of using the facility for failure baked into >> (mega)parsec. (Proposed diff for reference: >> https://github.com/complyue/dcp/pull/3) >> >> "Returning Nothing" can be seen as adding a new channel for errors, >> turning the Parser monad into `MaybeT Parser`. Then `return Nothing` is >> how `empty` is defined by `MaybeT`, allowing that error to be caught and >> recovered from at the point where it was thrown, no backtracking. (And >> the original failure mode of Parser becomes `lift empty`.) >> >> Does that address your problem? >> >> Cheers, >> Li-yao >> >> On 10/28/2020 5:18 AM, Compl Yue wrote: >> > (sorry for repost, seems GMail's html processing on my last email has >> > rendered it barely readable, so again with plain text here) >> > >> > Dear Cafe, >> > >> > I'm still not fully clear about the confusion regarding megaparsec's >> > behavior that I posted lately here. But now comes to my mind that it may >> > have some problem rooted in the lacking of recoverability semantic with >> > respect to parser combinators, some quoting from >> > http://hackage.haskell.org/package/parser-combinators/docs/Control-Applicative-Combinators.html >> > >> > The *A note on backtracking* section >> > >> > > Combinators in this module are defined in terms Applicative and >> > Alternative operations. >> > >> > And `empty`'s doc: >> > >> > > This parser fails unconditionally without providing any information >> > about the cause of the failure. >> > >> > Clearly `empty` is used to express failure, but there is seemingly no >> > device to explicitly express whether a failure is recoverable. Then I >> > observed megaparsec's implicit rule as currently implemented is like: >> > >> > *) a failure with no input consumed can be recovered by rest parsers >> > *) a failure with some input consumed can not be recovered by rest parsers >> > >> > This works to great extent, but I would think the expressiveness can be >> > further extended for a parser from the application, to tell the library >> > that some input induces recoverable failure. >> > >> > I have no expertise to suggest whether `MonadPlus` and/or `MonadFail` >> > are suitable devices to be considered, but as megaparsec has implemented >> > instances for them, I do feel some tweaks would be possible and meaningful. >> > >> > Best regards, >> > Compl >> > >> > >> > _______________________________________________ >> > 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. >> > > > > > > ---------- Forwarded message ---------- > From: Compl Yue > To: Li-yao Xia > Cc: "Haskell Café" > Bcc: > Date: Wed, 28 Oct 2020 21:48:37 +0800 > Subject: Re: [Haskell-cafe] Consider adding recoverability to the vocabulary of parser combinators > (sorry I forgot the text color again, maybe https://darkreader.org is > to blame, anyway plain text mode I should use) > > Hi Li-yao, > > I appreciate your help especially the PR as a working fix. > > But personally I don't like the overall method of your solution, I can > see Monad Transformers are powerful enough to tackle similar problems, > but I'm not satisfied by the ergonomics in composing monads with > transformers. `ParsecT` had already caused me much pain to get started > in the beginning, and I'm still not fluent (comfortable) in > transforming monads, especially I'm afraid I will have to transform > much of the standard combinator functions, in order to get the real > case parser working, as its resulting AST is much more complex. > > I still have faith in the improvement of megaparsec as a well known > parser combinator library (I regard it as the best for engineering > needs among other libraries), and I must admit megaparsec already > elegantly works 99% out of my current use cases, and the very issue we > are talking about is a nice-to-have rather than must-to-have, so I > would think we still have time to anticipate more options to come out. > > And I particularly like to see parser combinators have this issue > addressed in its own design space. > > Thanks again with best regards, > Compl > > On Wed, Oct 28, 2020 at 8:19 PM Li-yao Xia wrote: > > > > Hi Compl, > > > > At least, for the example you gave on this list, it can be fixed by > > returning Nothing instead of using the facility for failure baked into > > (mega)parsec. (Proposed diff for reference: > > https://github.com/complyue/dcp/pull/3) > > > > "Returning Nothing" can be seen as adding a new channel for errors, > > turning the Parser monad into `MaybeT Parser`. Then `return Nothing` is > > how `empty` is defined by `MaybeT`, allowing that error to be caught and > > recovered from at the point where it was thrown, no backtracking. (And > > the original failure mode of Parser becomes `lift empty`.) > > > > Does that address your problem? > > > > Cheers, > > Li-yao > > > > On 10/28/2020 5:18 AM, Compl Yue wrote: > > > (sorry for repost, seems GMail's html processing on my last email has > > > rendered it barely readable, so again with plain text here) > > > > > > Dear Cafe, > > > > > > I'm still not fully clear about the confusion regarding megaparsec's > > > behavior that I posted lately here. But now comes to my mind that it may > > > have some problem rooted in the lacking of recoverability semantic with > > > respect to parser combinators, some quoting from > > > http://hackage.haskell.org/package/parser-combinators/docs/Control-Applicative-Combinators.html > > > > > > The *A note on backtracking* section > > > > > > > Combinators in this module are defined in terms Applicative and > > > Alternative operations. > > > > > > And `empty`'s doc: > > > > > > > This parser fails unconditionally without providing any information > > > about the cause of the failure. > > > > > > Clearly `empty` is used to express failure, but there is seemingly no > > > device to explicitly express whether a failure is recoverable. Then I > > > observed megaparsec's implicit rule as currently implemented is like: > > > > > > *) a failure with no input consumed can be recovered by rest parsers > > > *) a failure with some input consumed can not be recovered by rest parsers > > > > > > This works to great extent, but I would think the expressiveness can be > > > further extended for a parser from the application, to tell the library > > > that some input induces recoverable failure. > > > > > > I have no expertise to suggest whether `MonadPlus` and/or `MonadFail` > > > are suitable devices to be considered, but as megaparsec has implemented > > > instances for them, I do feel some tweaks would be possible and meaningful. > > > > > > Best regards, > > > Compl > > > > > > > > > _______________________________________________ > > > 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 > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe -- Pozdrawiam Michał From godzbanebane at gmail.com Thu Oct 29 15:05:16 2020 From: godzbanebane at gmail.com (Georgi Lyubenov) Date: Thu, 29 Oct 2020 17:05:16 +0200 Subject: [Haskell-cafe] Haskell-Cafe Digest, Vol 206, Issue 17 In-Reply-To: References: Message-ID: Hi Michal, Just noting that perhaps https://hackage.haskell.org/package/validation or https://hackage.haskell.org/package/monad-validate could also be of use for these purposes. Cheers, ====== Georgi -------------- next part -------------- An HTML attachment was scrubbed... URL: From compl.yue at icloud.com Thu Oct 29 16:50:14 2020 From: compl.yue at icloud.com (YueCompl) Date: Fri, 30 Oct 2020 00:50:14 +0800 Subject: [Haskell-cafe] Haskell-Cafe Digest, Vol 206, Issue 17 In-Reply-To: References: Message-ID: <4F374A05-690F-4250-ABC2-4665DB3DAC0B@icloud.com> Thanks Michal and Georgi, And actually I'm also pondering with ideas to start a fault tolerant parser implementation, filed a question issue at https://github.com/mrkkrp/megaparsec/issues/431 so far. I'll definitely take IOHK's approaches for reference, I think I'll benefit a lot from those battle tested, production ready codebase. Thanks with best regards, Compl > On 2020-10-29, at 23:05, Georgi Lyubenov wrote: > > Hi Michal, > > Just noting that perhaps https://hackage.haskell.org/package/validation or https://hackage.haskell.org/package/monad-validate could also be of use for these purposes. > > Cheers, > > ====== > Georgi > _______________________________________________ > 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. -------------- next part -------------- An HTML attachment was scrubbed... URL: From corentin.dupont at gmail.com Thu Oct 29 17:55:04 2020 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Thu, 29 Oct 2020 18:55:04 +0100 Subject: [Haskell-cafe] [ANN] Keycloak-hs V2 In-Reply-To: References: Message-ID: Hello, I'm very proud to announce the second version of Keycloak-hs, a library to access Keycloak: http://hackage.haskell.org/package/keycloak-hs. Keycloak (www.keycloak.org) is a tool allowing you to authenticate and manage users, and protect your API resources. This version has a much better interface to Keycloak, and more documentation. With this library you can: - Manage and verify Auth tokens - Manage Users in Keycloak - Manage Resources to be protected with Keycloak - Evaluate permissions and policies Comments are welcome! Cheers! Corentin -------------- next part -------------- An HTML attachment was scrubbed... URL: From jaro.reinders at gmail.com Thu Oct 29 18:16:11 2020 From: jaro.reinders at gmail.com (Jaro Reinders) Date: Thu, 29 Oct 2020 19:16:11 +0100 Subject: [Haskell-cafe] Haskell-Cafe Digest, Vol 206, Issue 17 In-Reply-To: <4F374A05-690F-4250-ABC2-4665DB3DAC0B@icloud.com> References: <4F374A05-690F-4250-ABC2-4665DB3DAC0B@icloud.com> Message-ID: <58cdfa57-1512-047a-8100-2da58af905fe@gmail.com> uu-parsinglib [1] is an error correcting parser combinator library. There is a "short" tutorial that explains some of the ideas behind that library [2]. The error correcting is covered in section 7. I should also mention that it is already a bit old and not maintained anymore, so there might be some rough edges. [1] http://hackage.haskell.org/package/uu-parsinglib [2] http://www.cs.tufts.edu/~nr/cs257/archive/doaitse-swierstra/combinator-parsing-tutorial.pdf On 10/29/20 5:50 PM, YueCompl via Haskell-Cafe wrote: > Thanks Michal and Georgi, > > And actually I'm also pondering with ideas to start a fault tolerant parser implementation, filed a question issue at https://github.com/mrkkrp/megaparsec/issues/431 so far. > > I'll definitely take IOHK's approaches for reference, I think I'll benefit a lot from those battle tested, production ready codebase. > > Thanks with best regards, > Compl > > >> On 2020-10-29, at 23:05, Georgi Lyubenov wrote: >> >> Hi Michal, >> >> Just noting that perhaps https://hackage.haskell.org/package/validation or https://hackage.haskell.org/package/monad-validate could also be of use for these purposes. >> >> Cheers, >> >> ====== >> Georgi >> _______________________________________________ >> 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. > From elan-mentholer at orange.fr Thu Oct 29 18:31:19 2020 From: elan-mentholer at orange.fr (Elan-Mentholer) Date: Thu, 29 Oct 2020 19:31:19 +0100 (CET) Subject: [Haskell-cafe] UNSUBSCRIBE Message-ID: <1946474409.7432.1603996279343.JavaMail.www@wwinf1j04> UNSUBSCRIBE -------------- next part -------------- An HTML attachment was scrubbed... URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: montagne.jpg Type: image/jpg Size: 15723 bytes Desc: not available URL: From mlang at blind.guru Thu Oct 29 22:47:29 2020 From: mlang at blind.guru (Mario Lang) Date: Thu, 29 Oct 2020 23:47:29 +0100 Subject: [Haskell-cafe] Panmusic? Message-ID: <87d010odj2.fsf@blind.guru> Hi. With all this recent talk of parsing, and me being in the process of redoing my homepage with Hakyll (read, Pandoc) I can not help but think of a long-term project of mine. I've written two different programs to handle braille music code. FreeDots[1] (Java) which converts MusicXML to Braille Music Code, and BMC[2] (C++) which converts Braille Music Code to LilyPond and MusicXML. Combining the insight that Haskell is perfect for writing compilers, and Pandoc being one of the most successful Haskell applications, I can not help but wonder: Maybe I am after Panmusic? Before another wasted attempt of stupidly reinventing the wheel, I need to ask: Is anyone working on the universal music notation converter in Haskell? If not yet, would you be interested to? The colest thing I know to a versatile format converter right now is music21[3]. However, I'd much rather see this job done in Haskell then in any other language. [1] https://github.com/mlang/freedots [2] https://github.com/mlang/bmc [3] https://github.com/cuthbertLab/music21 -- CYa, ⡍⠁⠗⠊⠕ From mlists at devalot.com Thu Oct 29 22:58:32 2020 From: mlists at devalot.com (Peter J. Jones) Date: Thu, 29 Oct 2020 15:58:32 -0700 Subject: [Haskell-cafe] Intention to take over the pipes-text package Message-ID: <87v9esk5bb.fsf@devalot.com> (This is a re-post from October 6, 2020 since the original did not make it into the archive.) The pipes-text [1] package on Hackage hasn't been updated in about 4 years and doesn't currently build due to outdated `build-depends'. Patches have been supplied to the GitHub [2] repository but none have been merged. The last commit was on Dec 2, 2016. I have attempted to reach out to the author (Michael Thompson) to offer assistance and have not received any response. As per the instructions on the Haskell Wiki, I'm posting this message to signal my intent to take over the pipes-text package as a maintainer. I have a working fork here [3]. Michael, if you prefer to keep the package under your control I'm more than happy to help you manage the GitHub project and get some patches merged. Otherwise I'll reach out to the Hackage administrators after a reasonable amount of time has passed. [1]: https://hackage.haskell.org/package/pipes-text [2]: https://github.com/michaelt/text-pipes [3]: https://github.com/pjones/pipes-text -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 487 bytes Desc: not available URL: From mgajda at mimuw.edu.pl Fri Oct 30 04:11:13 2020 From: mgajda at mimuw.edu.pl (Michal J Gajda) Date: Fri, 30 Oct 2020 05:11:13 +0100 Subject: [Haskell-cafe] Haskell-Cafe Digest, Vol 206, Issue 17 In-Reply-To: <4F374A05-690F-4250-ABC2-4665DB3DAC0B@icloud.com> References: <4F374A05-690F-4250-ABC2-4665DB3DAC0B@icloud.com> Message-ID: Best of luck Yue! I think you may want to also share it with https://datahaskell.org and their Gitter channel: https://gitter.im/dataHaskell/Lobby Since this project may benefit from collaboration - please release early, release often, discuss on Gitter :-) -- Cheers Michał On Thu, Oct 29, 2020 at 5:50 PM YueCompl wrote: > > Thanks Michal and Georgi, > > And actually I'm also pondering with ideas to start a fault tolerant parser implementation, filed a question issue at https://github.com/mrkkrp/megaparsec/issues/431 so far. > > I'll definitely take IOHK's approaches for reference, I think I'll benefit a lot from those battle tested, production ready codebase. > > Thanks with best regards, > Compl > > > On 2020-10-29, at 23:05, Georgi Lyubenov wrote: > > Hi Michal, > > Just noting that perhaps https://hackage.haskell.org/package/validation or https://hackage.haskell.org/package/monad-validate could also be of use for these purposes. > > Cheers, > > ====== > Georgi > _______________________________________________ > 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. > > -- Pozdrawiam Michał From johannes.waldmann at htwk-leipzig.de Fri Oct 30 08:17:29 2020 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Fri, 30 Oct 2020 09:17:29 +0100 Subject: [Haskell-cafe] Panmusic? Message-ID: <690a5254-8cd4-2b73-dd70-99725afc6943@htwk-leipzig.de> > Is anyone working on the universal music notation > converter in Haskell? https://github.com/music-suite/music-suite http://music-suite.github.io/docs/ref/ I think this intends to be "the pandoc of music". I was looking into lilypond parsing for that, see my fork https://github.com/jwaldmann/lilypond-parse#goals but I'm currently stalled on this, for lack of time - and for the thorough mess that lilypond makes of mixing lexing, parsing, and semantics. It's as bad as TeX ... - J. From stefan.wehr at gmail.com Fri Oct 30 11:08:53 2020 From: stefan.wehr at gmail.com (Stefan Wehr) Date: Fri, 30 Oct 2020 12:08:53 +0100 Subject: [Haskell-cafe] 2nd Call for Contributions: BOB 2021 [Feb 26, Deadline Nov 13] Message-ID: BOB Conference 2021 "What happens when we use what's best for a change?" http://bobkonf.de/2021/cfc.html Berlin, February 26 Call for Contributions Deadline: November 13, 2020 You are actively engaged in advanced software engineering methods, implement ambitious architectures and are open to cutting-edge innovation? Attend this conference, meet people that share your goals, and get to know the best software tools and technologies available today. We strive to offer a day full of new experiences and impressions that you can use to immediately improve your daily life as a software developer. If you share our vision and want to contribute, submit a proposal for a talk or tutorial! NOTE: The conference fee will be waived for presenters. Travel expenses will not be covered (for exceptions see "Speaker Grants"). Online or Onsite We do know yet whether BOB will happen onsite in Berlin or as an online event. Should BOB happen online, we will likely ask for pre-recorded talks to make room for questions and social interactions during the actual conference day. (Of course, we'll provide assistance making those recordings.) Tutorials will likely happen as a live-session. Speaker Grants -------------- BOB has Speaker Grants available to support speakers from groups under-represented in technology. We specifically seek women speakers, speakers of color, and speakers who are not be able to attend the conference for financial reasons. Shepherding ----------- The program committee offers shepherding to all speakers. Shepherding provides speakers assistance with preparing their sessions. Specifically: - advice on structure and presentation - review of talk slides - assistance with recording - review of recording, if applicable Topics ------ We are looking for talks about best-of-breed software technology, e.g.: - functional programming - persistent data structures and databases - event-based modelling and architecture - types - formal methods for correctness and robustness - abstractions for concurrency and parallelism - metaprogramming - probabilistic programming - math and programming - controlled side effects - beyond REST and SOAP - effective abstractions for data analytics - … everything really that isn’t mainstream, but you think should be. Presenters should provide the audience with information that is practically useful for software developers. We're especially interested in experience reports. Other topics are also relevant, e.g.: - introductory talks on technical background - overviews of a given field - demos and how-tos Requirements ------------ We accept proposals for presentations of 45 minutes (40 minutes talk + 5 minutes questions), as well as 90 minute tutorials for beginners. The language of presentation should be either English or German. Your proposal should include (in your presentation language of choice): - An abstract of max. 1500 characters. - A short bio/cv - Contact information (including at least email address) - A list of 3-5 concrete ideas of how your work can be applied in a developer's daily life - additional material (websites, blogs, slides, videos of past presentations, …) - Don't be confused: The system calls a submission event. Organisation ------------ - Direct questions to contact at bobkonf dot de - Proposal deadline: November 13, 2020 - Notification: November 27, 2020 - Program: December 6, 2020 Submit here: https://bobcfc.active-group.de/en/bob2021/cfp Program Committee ----------------- (more information here: https://bobkonf.de/2020/programmkomitee.html) - Matthias Fischmann, Wire - Matthias Neubauer, SICK AG - Nicole Rauch, Softwareentwicklung und Entwicklungscoaching - Michael Sperber, Active Group - Stefan Wehr, Hochschule Offenburg Scientific Advisory Board - Annette Bieniusa, TU Kaiserslautern - Torsten Grust, Uni Tübingen - Peter Thiemann, Uni Freiburg -------------- next part -------------- An HTML attachment was scrubbed... URL: From lysxia at gmail.com Fri Oct 30 13:48:10 2020 From: lysxia at gmail.com (Li-yao Xia) Date: Fri, 30 Oct 2020 09:48:10 -0400 Subject: [Haskell-cafe] Split the IsList class for OverloadedLists Message-ID: Hello Café, Right now the IsList class used by the OverloadedLists extension requires both fromList, to construct something using list syntax, and toList, to pattern-match on something using list syntax. So types implementing that class are expected to be isomorphic to lists. This is a very strong restriction. In particular, this gets in the way of implementing IsList for aeson's Value type[1], since there's no sensible total implementation of toList. [1]: That is a recently proposed idea https://github.com/bos/aeson/issues/813 Proposal: split toList and fromList in two separate classes. (And modify the OverloadedLists extension accordingly.) Since they rely on an associated type family Item, it would be made a standalone family. type family Item (l :: Type) :: Type class ToList l where toList :: l -> [Item l] class FromList l where fromList :: [Item l] -> l fromListN :: Int -> [Item l] -> l (Note: we can't just replace ToList with Foldable, because these classes have different kinds.) - Any objections? An obvious concern is backwards compatibility. Is that a deal breaker? Are there other issues with this idea? - Should that be a GHC proposal[2]? - Has this been discussed before? [2]: https://github.com/ghc-proposals/ghc-proposals One alternative is to use RebindableSyntax, which already allows users to redefine toList and fromList however they want. The issue is it might also mess with all other kinds of syntactic sugar just enough that the unpleasantness is not worth the trouble. For example, if you wanted to use multiple list-like types in one module, you would want an overloaded version of fromList/fromListN. You either roll your own or find a suitable dependency. Either way it's overhead you might not be willing to pay for, as opposed to something that's already in base and Just Works. So even with some existing workarounds in mind, the above proposal seems a net improvement over the status quo. Maybe some day we'll also get to take fromInteger out of Num. Regards, Li-yao From mlang at blind.guru Fri Oct 30 15:40:30 2020 From: mlang at blind.guru (Mario Lang) Date: Fri, 30 Oct 2020 16:40:30 +0100 Subject: [Haskell-cafe] Panmusic? In-Reply-To: <690a5254-8cd4-2b73-dd70-99725afc6943@htwk-leipzig.de> (Johannes Waldmann's message of "Fri, 30 Oct 2020 09:17:29 +0100") References: <690a5254-8cd4-2b73-dd70-99725afc6943@htwk-leipzig.de> Message-ID: <87y2jnyb69.fsf@blind.guru> Johannes Waldmann writes: >> Is anyone working on the universal music notation >> converter in Haskell? > > https://github.com/music-suite/music-suite > http://music-suite.github.io/docs/ref/ > > I think this intends to be "the pandoc of music". Thanks for the pointer! This looks very interesting. > I was looking into lilypond parsing for that, see my fork > https://github.com/jwaldmann/lilypond-parse#goals > but I'm currently stalled on this, for lack of time - > and for the thorough mess that lilypond makes > of mixing lexing, parsing, and semantics. Yeah, a good LilyPond parser needs to have a Scheme interpreter built-in. > It's as bad as TeX ... That is intetional I guess. LilyPond is modeled after TeX. -- CYa, ⡍⠁⠗⠊⠕ From johannes.waldmann at htwk-leipzig.de Fri Oct 30 17:06:28 2020 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Fri, 30 Oct 2020 18:06:28 +0100 Subject: [Haskell-cafe] Panmusic? In-Reply-To: <87y2jnyb69.fsf@blind.guru> References: <690a5254-8cd4-2b73-dd70-99725afc6943@htwk-leipzig.de> <87y2jnyb69.fsf@blind.guru> Message-ID: <1bc3f813-dca3-4d46-0908-f1db5c18d39b@htwk-leipzig.de> Hi >> [lilypond]'s as bad as TeX ... > > That is intetional I guess. LilyPond is modeled after TeX. Sure. I should have added: .. and as brilliant as well. Horrible language, with beautiful output. > Yeah, a good LilyPond parser .. the lexer, even? > .. needs to have a Scheme interpreter built-in. So, do you have such a parser? - J. From duke.j.david at gmail.com Sat Oct 31 18:35:25 2020 From: duke.j.david at gmail.com (David Duke) Date: Sat, 31 Oct 2020 18:35:25 +0000 Subject: [Haskell-cafe] GHC-8.6.3 question. Message-ID: Dear colleagues I'm in the process of having to reinstall ghc-8.6.3 in order to use a library (gtk) where the last successful build is 8.6.3. I was able to do that on linux. However I'm now trying to repeat this under OSX. I couldn't find a binary version, so I've been trying to build from source- but i'm hitting an issue on 'make install': stage2/build/libHSghc-8.6.3_p.a: copyFile: does not exist (No such file or directory) I'm not seeing a stage2 directory in my build area, but I'm not seeing any earlier error messages so I'm unclear why the build is failing. If someone familiar with this release and/or th build process could suggest any causes or fixes that would be helpful. thanks, David Duke -------------- next part -------------- An HTML attachment was scrubbed... URL: From mgajda at mimuw.edu.pl Sat Oct 31 18:38:41 2020 From: mgajda at mimuw.edu.pl (mgajda at mimuw.edu.pl) Date: Sat, 31 Oct 2020 18:38:41 UTC Subject: [Haskell-cafe] [CFP]Agile and Functional Data Pipelines workshop Message-ID: <20201031183841.e3d4b019304dd3be@migamake.com> Dear Friends, The emerging interest in the rigorous and agile data science and functional ETL pipelines has driven the developments of many new libraries, frameworks and methodologies. We invite industry practitioners and academics to present their latest work on agile functional data pipelines as a workshop at the EDI'2021 conference. Call for papers =============== The following would be accepted: - Exposures of methodologies for building agile functional data pipelines - Presentations of frameworks used for data pipelines in industry and academia - Experience reports from building of data pipelines in industry and academia - Benchmarks and optimization of agile data pipeline frameworks - Solutions to data integration and exchange problems within ETL pipelines. In particular, we encourage: - Agile functional data methodologists - Authors of ETL frameworks, streaming libraries and databases, reactive streaming, streaming benchmarks, high-performance workflow engines - Position papers on the use of agile and functional data methodologies - Descriptions of environments for interactive and live programming with data - Benchmarks of state-of-the-art solutions for agile functional data pipelines. Details at https://afdp.github.io Important dates =============== Abstract registration deadline : December 15th, 2020 Submission deadline : December 22nd, 2020 Acceptance notification : January 12th 2021 Final manuscripts : January 23rd, 2021 Presentation at the conference : March 23rd-26th 2021 Submission instructions ======================= Original, unpublished papers are solicited for presentation at the AFDP workshop. Prospective authors are invited to submit papers (electronically, PDF only) that are no longer than 6 pages for full papers, including all figures and references. For work-in-progress, we also solicit extended abstracts for presentations. The submitted paper must be formatted according to the guidelines of Procedia Computer Science. All accepted papers will be published in Procedia Computer Science. Location ======== This workshop will be held as a part of [The 4th International Conference on Emerging Data and Industry 4.0 (EDI40)](http://cs-conferences.acadiau.ca/EDI40-21/) held on March 23 - 26, 2021 in Warsaw, Poland. -- Best regards MichaB From jaro.reinders at gmail.com Sat Oct 31 18:45:58 2020 From: jaro.reinders at gmail.com (Jaro Reinders) Date: Sat, 31 Oct 2020 19:45:58 +0100 Subject: [Haskell-cafe] GHC-8.6.3 question. In-Reply-To: References: Message-ID: I can't help with compiling GHC from source, but gtk-0.15.5 builds fine with GHC 8.8.4 On 10/31/20 7:35 PM, David Duke wrote: > Dear colleagues > > I'm in the process of having to reinstall ghc-8.6.3 in order to use a > library (gtk) where the last successful build is 8.6.3. I was able to do > that on linux. However I'm now trying to repeat this under OSX. I couldn't > find a binary version, so I've been trying to build from source- but i'm > hitting an issue on 'make install': > > stage2/build/libHSghc-8.6.3_p.a: copyFile: does not exist (No such file or > directory) > > I'm not seeing a stage2 directory in my build area, but I'm not seeing any > earlier error messages so I'm unclear why the build is failing. > > If someone familiar with this release and/or th build process could suggest > any causes or fixes that would be helpful. > > thanks, > David Duke > > > _______________________________________________ > 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. > From olf at aatal-apotheke.de Sat Oct 31 19:43:40 2020 From: olf at aatal-apotheke.de (Olaf Klinke) Date: Sat, 31 Oct 2020 20:43:40 +0100 Subject: [Haskell-cafe] Split the IsList class for OverloadedLists Message-ID: > Hello Café, > > Right now the IsList class used by the OverloadedLists extension > requires both fromList, to construct something using list syntax, > and > toList, to pattern-match on something using list syntax. > > So types implementing that class are expected to be isomorphic to > lists. > This is a very strong restriction. In particular, this gets in the > way > of implementing IsList for aeson's Value type[1], since there's no > sensible total implementation of toList. > > [1]: That is a recently proposed idea > https://github.com/bos/aeson/issues/813 For constructing values from list syntax, I can understand that only fromList is used and Aeson's Value indeed contains lists. But if both fromList and toList are required, I would expect that fromList.toList=id and I can not see how that can ever be achieved with Aeson Values. Maybe a lightweight quasi-quoter can be syntactically almost as convenient for construction? MonoFoldable and MonoTraversable instances for Value might also be helpful: MonoFoldable gives you a toList function. > > > Proposal: split toList and fromList in two separate classes. > > (And modify the OverloadedLists extension accordingly.) > > Since they rely on an associated type family Item, it would be made > a > standalone family. > > > type family Item (l :: Type) :: Type > > class ToList l where > toList :: l -> [Item l] > > class FromList l where > fromList :: [Item l] -> l > fromListN :: Int -> [Item l] -> l > > > (Note: we can't just replace ToList with Foldable, because these > classes > have different kinds.) > > > - Any objections? An obvious concern is backwards compatibility. Is > that > a deal breaker? Are there other issues with this idea? You would lose the pattern matching functionality, it seems. It reminds me very much of OverloadedStrings and that is not always as convenient as you might think. The issue is that a previously monomorphic piece of syntax suddenly is polymorphic, so in some places with OveroadedStrings one must provide type annotations. And that destroys the brevity one was after. > > - Should that be a GHC proposal[2]? > > - Has this been discussed before? > > [2]: https://github.com/ghc-proposals/ghc-proposals > > > One alternative is to use RebindableSyntax, which already allows > users > to redefine toList and fromList however they want. The issue is it > might > also mess with all other kinds of syntactic sugar just enough that > the > unpleasantness is not worth the trouble. > > For example, if you wanted to use multiple list-like types in one > module, you would want an overloaded version of fromList/fromListN. > You > either roll your own or find a suitable dependency. Either way it's > overhead you might not be willing to pay for, as opposed to > something > that's already in base and Just Works. > > So even with some existing workarounds in mind, the above proposal > seems > a net improvement over the status quo. > > Maybe some day we'll also get to take fromInteger out of Num. > > Regards, > Li-yao > From lemming at henning-thielemann.de Sat Oct 31 19:55:02 2020 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Sat, 31 Oct 2020 20:55:02 +0100 (CET) Subject: [Haskell-cafe] Split the IsList class for OverloadedLists In-Reply-To: References: Message-ID: On Sat, 31 Oct 2020, Olaf Klinke wrote: >> (Note: we can't just replace ToList with Foldable, because these >> classes have different kinds.) >> >> >> - Any objections? An obvious concern is backwards compatibility. Is >> that a deal breaker? Are there other issues with this idea? > You would lose the pattern matching functionality, it seems. > It reminds me very much of OverloadedStrings and that is not always as > convenient as you might think. The issue is that a previously > monomorphic piece of syntax suddenly is polymorphic, so in some places > with OveroadedStrings one must provide type annotations. And that > destroys the brevity one was after. That's the problem. Instead of extending syntactic sugar you can resort to plain functional programming. Constructing a list: l :: [a] -> YourList a Use like: l[1,2,3]. Matching a list using continuation passing: withList :: ([a] -> b) -> YourList a -> b Use like in: func m = withList $ \(x:y:_) n -> ... From jack at jackkelly.name Sat Oct 31 20:38:31 2020 From: jack at jackkelly.name (jack at jackkelly.name) Date: Sat, 31 Oct 2020 20:38:31 +0000 Subject: [Haskell-cafe] GHC-8.6.3 question. In-Reply-To: References: Message-ID: <3cfda95bdc841d977c6300580628a82a@jackkelly.name> Hello David, November 1, 2020 4:35 AM, "David Duke" wrote: > I'm in the process of having to reinstall ghc-8.6.3 in order to use a library (gtk) where the last > successful build is 8.6.3. I was able to do that on linux. However I'm now trying to repeat this > under OSX. I don't use macOS so I can't answer your build question directly, but do you use ghcup ( https://www.haskell.org/ghcup/ ) to manage your GHC versions? It looks like ghcup has been told about 8.6.3 on darwin: https://gitlab.haskell.org/haskell/ghcup/-/blob/8f4705a50eefafd92ceef32094eec7140885b3d5/.download-urls#L99 HTH, -- Jack