From anthony_clayden at clear.net.nz Mon Mar 1 05:26:16 2021 From: anthony_clayden at clear.net.nz (Anthony Clayden) Date: Mon, 1 Mar 2021 18:26:16 +1300 Subject: [Haskell-cafe] Not too extensible records? Message-ID: Hi Ignat, as an example of what an extensible records system might look like in Haskell, you could play with Hugs.Trex -- https://www.haskell.org/hugs/pages/hugsman/exts.html#sect7.2 To match a few of its features to your post: > suppose I have two functions: one is a layout algorithm that assigns to nodes some spatial positions, and the second is a topological algorithm that discerns roots and leaves. These two functions are conceptually independent and ... r1 = (label = blah1) r2 = (topology = blah2 | r1) r3 = (v2 = blah3 :: Double | r2) The `( ... | r1)` means extend `r1` with some extra field or fields comma-separated. This is an 'extensible' 'anonymous' records system -- 'anonymous' in that you don't pre-declare your record types via `data`. You can name your record types, either with a `type` decl or with a `newtype` that provides a constructor for known-in-advance types. > may be applied in any order, Yes you can extend an existing record with arbitrary fields, the result is always a 'flat' tuple with the labels-value pairs forming a set: two records are same type providing they have the same set of labels and the same field types at each label, irrespective of how the labels got added. > I would like to make sure their fields are not mixed. > I need to be able to add more and more fields to labels, but in such a way that it is impossible to assign an unsuitable field. There's a so-called 'lacks' constraint you can put on record operations (written with backslash): foo :: r1\topology => Rec r1 -> a -> Rec (edges :: a | r1) is the type of a function that will extend record type `r1` lacking label 'topology' with a field `edges` at type `a`. You can put record types with lacks constraints on instances: instance (r2\v2) => Foo (Rec (label :: String | r2)) (Rec (v2 :: Double, label :: String | r2)) where ... holds for any record that includes label `label` at `String`, and possibly other labels in `r2`, but lacks `v2`. (I'm presuming there's a FunDep on Foo so the second instance parameter is the return type.) > a huge number of `HasThis` and `HasThat` instances That instance head is in effect a `Has` `label` constraint. There's also a shorthand `#label` that generates a function to extract the value at `label` **from any record with a `label`** -- that is, Hugs infers the `Has` constraint for you. > it seems to me that some smart technology is needed to make this manageable. I'm not seeing Trex as 'smart'. It follows conventional relational algebra semantics; was developed ~1996; last release of Hugs was 2006. I'd have thought GHC would come up with something comparable by now. As Olaf's and Henning's replies show, you could fake it with "a lot of boilerplate" and/or some dubious type trickery. AntC -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben.franksen at online.de Mon Mar 1 11:36:47 2021 From: ben.franksen at online.de (Ben Franksen) Date: Mon, 1 Mar 2021 12:36:47 +0100 Subject: [Haskell-cafe] DatatypeContexts / alternative In-Reply-To: <010f0177ea02fd16-74356e30-dd0b-4a49-818a-404ee8e8437c-000000@us-east-2.amazonses.com> References: <20210223182947.GB6186@cloudinit-builder> <010f0177d04a01ec-cdcf65f0-b70d-4344-ad2b-8ccc0de7b29f-000000@us-east-2.amazonses.com> <010f0177ea02fd16-74356e30-dd0b-4a49-818a-404ee8e8437c-000000@us-east-2.amazonses.com> Message-ID: Am 28.02.21 um 20:00 schrieb Richard Eisenberg: >> On Feb 28, 2021, at 3:25 AM, Ben Franksen >> wrote: >> >> What are these other GHC features? Does the paper explain this? >> Otherwise where can I read more about it? > > I think it was data families. But, perhaps more troublesome is the > fact that the paper assumes a dependently-typed internal language. > Maybe it's possible to do this without dependent types in the > internal language, but I'm not sure how to begin to think about that > problem. I see. So this cannot be expressed in, say, System Fc? I wonder... is it possible to pinpoint where System Fc is not sufficiently expressive? Perhaps trying to do so exposes a way to extend System Fc that allows to implement this scheme, ideally as step towards a dependently typed IL w/o going the full way. Sorry if these questions are completely naive! I am not versed enough in type theory to full grasp the formulas in these papers in all detail. > I was about to write that it might be helpful to have a GHC proposal > to implement this paper, which would depend on (and provide further > motivation for) having dependent types... but I'm not actually sure > that would be productive at this point. Yes, this seems to be of relevance only in the very long run. Cheers Ben From johannes.waldmann at htwk-leipzig.de Mon Mar 1 16:45:07 2021 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Mon, 1 Mar 2021 17:45:07 +0100 Subject: [Haskell-cafe] naturally, length :: a -> Int Message-ID: Dear Cafe - let's fight Int. In a lot of code I write (for research, teaching, production), a lot of numbers are in fact natural numbers - because I am counting (e.g., number of elements in a collection) or pointing into what I just counted (e.g., Data.Set.elemAt). But Haskell's "most natural" type is - Int. At least that's my impression from current usage in libraries and teaching examples (see functions length, replicate, ... ). I've developed a horror of reading and writing "length something :: Int". As I will be teaching an introductory class on FP soon, I am looking for ways to handle this. One option is presented in Bird/Gibbons: Algorithm Design with Haskell, which has "type Nat = Int" on page 6. Actually, that's the very first code example that appears in the book! The footnote there refers to a remark in Data.Word that has since been dropped? Now there is Numeric.Natural, (cf. https://mail.haskell.org/pipermail/libraries/2014-November/024203.html ) and numeric literals are already overloaded, so we can just use that? Well, yes and no - we still have to write a type conversion each time we use some library function that insists on Int, or, write cumbersome "genericLength". Also (but that is the lesser concern), Numeric.Natural is for arbitrary-length numbers (corresponding to Integer), while I might sometimes know that numbers are representable in a machine word, and I don't want to pay for the implied pattern match (data Natural = NatS Word | NatJ BigNat). I am willing to pay for underflow checks (on subtraction), and for overflow checks (if there's an upper bound). If I want to live risky (no checks) I could use Data.Word. So, what do you do? (Yes, Peano numerals ...) Or, how do we convince ourselves (and our students) of keeping the current status? NB: here is another practical argument for Natural (from production code, an auto-grading system for student homework) We use datatype-generic parsers heavily. For data Foo = Foo { ... :: Nat ... }, bad input will be rejected by the parser already, and I need no extra checks later on. Less code! I sometimes even use "Pos(itive)". That's all fine and dandy - until I call some library function... - J.W. From lemming at henning-thielemann.de Mon Mar 1 17:11:20 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Mon, 1 Mar 2021 18:11:20 +0100 (CET) Subject: [Haskell-cafe] naturally, length :: a -> Int In-Reply-To: References: Message-ID: On Mon, 1 Mar 2021, Johannes Waldmann wrote: > So, what do you do? (Yes, Peano numerals ...) > Or, how do we convince ourselves (and our students) > of keeping the current status? A poor man's definition of peano numbers is: type Peano = [()] 'length xs' becomes: map (const ()) xs or () <$ xs or void xs (+) becomes (++) (*) becomes liftA2 const (-) becomes \xs ys -> foldl (flip drop) ys (1<$xs) My experience with Word is that it makes things even worse. It is neither compatible with Int nor has it bound checks. It happens pretty easily that in an intermediate result is negative although the whole expression of type Word is always non-negative. I would prefer to use Liquid Haskell and restrict Int to non-negative numbers. This would solve both problems. From ietf-dane at dukhovni.org Mon Mar 1 18:14:38 2021 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Mon, 1 Mar 2021 13:14:38 -0500 Subject: [Haskell-cafe] naturally, length :: a -> Int In-Reply-To: References: Message-ID: On Mon, Mar 01, 2021 at 05:45:07PM +0100, Johannes Waldmann wrote: > I've developed a horror > of reading and writing "length something :: Int". If you're willing to tolerate the small overhead of Natural: $ ghci λ> import Data.Foldable (Foldable, foldl') λ> import GHC.Natural λ> len :: Foldable t => t a -> Natural; len = foldl' (\a _ -> a + 1) 0 λ> let x = len [1,2,3] λ> :t x x :: Natural λ> x 3 otherwise, note that `succ`, unlike (+), does bounds checks: λ> let x = maxBound :: Int λ> succ x *** Exception: Prelude.Enum.succ{Int}: tried to take `succ' of maxBound and so: λ> import Data.Foldable (Foldable, foldl') λ> len :: Foldable t => t a -> Int; len = foldl' (\a _ -> succ a) 0 λ> let x = len [1,2,3] λ> :t x x :: Int λ> x 3 on a 64-bit machine, testing to make sure the bounds check actually works would take too long, but we can cheat: λ> len :: Foldable t => t a -> Int; len = foldl' (\a _ -> succ a) (maxBound :: Int) λ> len [] 9223372036854775807 λ> len [1] *** Exception: Prelude.Enum.succ{Int}: tried to take `succ' of maxBound -- Viktor. From ietf-dane at dukhovni.org Tue Mar 2 07:44:01 2021 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Tue, 2 Mar 2021 05:44:01 -0200 Subject: [Haskell-cafe] Puzzling instance method definitions in Data.Sequence.Internal Message-ID: In `containers`, Data.Sequence.Internal defines a Foldable instance for `Seq` with method definitions for `length` and `null` that I'm struggling to understand: https://github.com/haskell/containers/blob/master/containers/src/Data/Sequence/Internal.hs#L410-L415 #if MIN_VERSION_base(4,8,0) length = length {-# INLINE length #-} null = null {-# INLINE null #-} #endif further down the file there are also explicit top-level definitions for these functions: https://github.com/haskell/containers/blob/master/containers/src/Data/Sequence/Internal.hs#L2161-L2168 -- | \( O(1) \). Is this the empty sequence? null :: Seq a -> Bool null (Seq EmptyT) = True null _ = False -- | \( O(1) \). The number of elements in the sequence. length :: Seq a -> Int length (Seq xs) = size xs So the intent seems clear, but I don't understand how the instance method definitions are valid. The imports of Both Prelude and Data.Foldable don't include `length` or `null`: https://github.com/haskell/containers/blob/master/containers/src/Data/Sequence/Internal.hs#L194-L213 So the RHS definitions should plausibly resolve to the top-level functions, but when I try to define a similar type class instance GHC tells me: ‘method’ is not a (visible) method of class ‘Class’ and in any case I'd expect `length = length` to yield an infinite loop, regardless of any other bindings in the outer scope. How is Data.Sequence.Internal getting away with this??? -- Viktor. From lemming at henning-thielemann.de Tue Mar 2 08:08:30 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Tue, 2 Mar 2021 09:08:30 +0100 (CET) Subject: [Haskell-cafe] Puzzling instance method definitions in Data.Sequence.Internal In-Reply-To: References: Message-ID: <7b55dedc-2aa5-d4a8-e08f-f99ee71d92f7@henning-thielemann.de> On Tue, 2 Mar 2021, Viktor Dukhovni wrote: > So the intent seems clear, but I don't understand how the instance method > definitions are valid. The imports of Both Prelude and Data.Foldable don't > include `length` or `null`: > > https://github.com/haskell/containers/blob/master/containers/src/Data/Sequence/Internal.hs#L194-L213 It is enough if the method name is imported with qualification. Surprising and maybe inconsistent but that's the state of affairs. GHC even forbids qualification on the left-hand side of a method definition. This at least is consistent with all function definitions. From ietf-dane at dukhovni.org Tue Mar 2 08:16:04 2021 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Tue, 2 Mar 2021 06:16:04 -0200 Subject: [Haskell-cafe] Puzzling instance method definitions in Data.Sequence.Internal In-Reply-To: <7b55dedc-2aa5-d4a8-e08f-f99ee71d92f7@henning-thielemann.de> References: <7b55dedc-2aa5-d4a8-e08f-f99ee71d92f7@henning-thielemann.de> Message-ID: > On Mar 2, 2021, at 6:08 AM, Henning Thielemann wrote: > > On Tue, 2 Mar 2021, Viktor Dukhovni wrote: > >> So the intent seems clear, but I don't understand how the instance method >> definitions are valid. The imports of Both Prelude and Data.Foldable don't >> include `length` or `null`: >> >> https://github.com/haskell/containers/blob/master/containers/src/Data/Sequence/Internal.hs#L194-L213 > > It is enough if the method name is imported with qualification. Surprising and maybe inconsistent but that's the state of affairs. GHC even forbids qualification on the left-hand side of a method definition. This at least is consistent with all function definitions. Thanks, that explains it. By far from obvious, but handy to know. Indeed the module also has (one more line than I took into account): https://github.com/haskell/containers/blob/master/containers/src/Data/Sequence/Internal.hs#L214 import qualified Data.Foldable as F Much appreciated. -- Viktor. From ben.franksen at online.de Tue Mar 2 12:52:56 2021 From: ben.franksen at online.de (Ben Franksen) Date: Tue, 2 Mar 2021 13:52:56 +0100 Subject: [Haskell-cafe] naturally, length :: a -> Int In-Reply-To: References: Message-ID: Am 01.03.21 um 17:45 schrieb Johannes Waldmann: > let's fight Int. I'm in. > In a lot of code I write (for research, teaching, production), > a lot of numbers are in fact natural numbers - > because I am counting (e.g., number of elements in a collection) > or pointing into what I just counted (e.g., Data.Set.elemAt). > > But Haskell's "most natural" type is - Int. > At least that's my impression from current usage in libraries > and teaching examples (see functions length, replicate, ... ). > > I've developed a horror > of reading and writing "length something :: Int". Same here. > If I want to live risky (no checks) I could use Data.Word. I think Data.Word is not so bad. Does it come with a guarantee that maxBound=2^n-1 and all operations being treated module 2^n, for some natural number n? That would be fine for most applications I guess. It would be nice if one could change the semantics of under- or overflow for Data.Word with a compiler flag, e.g. so that it throws an exception. > That's all fine and dandy - until I call some library function... I would support a move Int->Word in all libraries where that makes sense. But I doubt it will happen. Cheers Ben From polux2001 at gmail.com Tue Mar 2 14:16:23 2021 From: polux2001 at gmail.com (Paul Brauner) Date: Tue, 2 Mar 2021 15:16:23 +0100 Subject: [Haskell-cafe] data kinds and exhaustiveness of typeclass instances Message-ID: Hello, the following program doesn't typecheck in GHC 9: data Tag = A | B data Foo (a :: Tag) = Foo class C a where f :: a -> Int instance C (Foo A) where f x = 1 instance C (Foo B) where f x = 2 g :: Foo a -> Int g = f Yet one could argue that for all a :: Tag, C (Foo a) holds because a :: Tag can only take two values: A or B, and C (Foo A) and C (Foo B) hold. Is there a way to somehow convince GHC of that fact so that g typechecks? Cheers, Paul -------------- next part -------------- An HTML attachment was scrubbed... URL: From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Tue Mar 2 14:41:22 2021 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Tue, 2 Mar 2021 14:41:22 +0000 Subject: [Haskell-cafe] data kinds and exhaustiveness of typeclass instances In-Reply-To: References: Message-ID: <20210302144122.GI17096@cloudinit-builder> On Tue, Mar 02, 2021 at 03:16:23PM +0100, Paul Brauner wrote: > the following program doesn't typecheck in GHC 9: > > data Tag = A | B > data Foo (a :: Tag) = Foo > > class C a where > f :: a -> Int > > instance C (Foo A) where > f x = 1 > > instance C (Foo B) where > f x = 2 > > g :: Foo a -> Int > g = f > > Yet one could argue that for all a :: Tag, C (Foo a) holds because a :: Tag > can only take two values: A or B, and C (Foo A) and C (Foo B) hold. Is > there a way to somehow convince GHC of that fact so that g typechecks? What would you expect the type of 'g Foo' to be? From johannes.waldmann at htwk-leipzig.de Tue Mar 2 14:53:34 2021 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Tue, 2 Mar 2021 15:53:34 +0100 Subject: [Haskell-cafe] naturally, length :: a -> Int In-Reply-To: References: Message-ID: Dear Cafe, thanks for ideas and arguments. > [Ben Franksen] I would support a move Int->Word in all libraries > where that makes sense. I find it hard to think of a library where that does NOT make sense... The following is somewhat related but actually orthogonal: I mentioned that numbers often arise as cardinalities (so they are natural, by definition) and serve as pointers. The next step is then: pointer type safety. Vincent Hanquez' Foundation https://hackage.haskell.org/package/foundation-0.0.25 defines class (IsList c, Item c ~ Element c) => Collection c where length :: c -> CountOf (Element c) class ( ... Collection c) => Sequential c where take :: CountOf (Element c) -> c -> c with newtype CountOf ty (and there's also newtype Offset ty) I tend to agree. The phantom type argument for CountOf would catch errors like adding the number of students to the number of exercises (in my application). (Well and the next step after that would be to have the size of the collection in the (dependent) type as well.) Current implementation is newtype CountOf ty = CountOf Int and the author adds (and that was also the point I was making) "Int is a terrible backing type which is hard to get away from, considering that GHC/Haskell are mostly using this for [counting and] offset. Trying to bring some sanity by a lightweight wrapping." NB: I found out about this from Michael Snoyman's (very much entertaining, and too much true) https://www.snoyman.com/blog/2020/12/haskell-bad-parts-3/ Best regards, J.W. From rae at richarde.dev Tue Mar 2 15:00:55 2021 From: rae at richarde.dev (Richard Eisenberg) Date: Tue, 2 Mar 2021 15:00:55 +0000 Subject: [Haskell-cafe] data kinds and exhaustiveness of typeclass instances In-Reply-To: References: Message-ID: <010f0177f374d32c-ace56c66-4b74-40d4-9e18-bf138f5d5e20-000000@us-east-2.amazonses.com> > Is there a way to somehow convince GHC of that fact so that g typechecks? No. First, it would actually be unsound to do so, because of the possibility of exotic types, built with pathological combinations of type and data families: https://gitlab.haskell.org/ghc/ghc/-/issues/14420 But, actually, the bigger problem is that we need a class constraint in order to allow a function to compute at runtime. The function f actually takes two arguments at runtime: a representation of the instance which carries f's implementation (this is sometimes called a dictionary), and the normal argument of type a. `g`, on the other hand, has no access to the dictionary needed at runtime, and so it's unclear how it should compute. Put another way: a value of type Foo carries no information (beyond the fact that it terminates), because Foo has only one data constructor. So there's no way that g :: Foo a -> Int could be anything but a constant function. You need the class constraint to change this fact. Hope this helps! Richard > On Mar 2, 2021, at 9:16 AM, Paul Brauner wrote: > > Hello, > > the following program doesn't typecheck in GHC 9: > > data Tag = A | B > data Foo (a :: Tag) = Foo > > class C a where > f :: a -> Int > > instance C (Foo A) where > f x = 1 > > instance C (Foo B) where > f x = 2 > > g :: Foo a -> Int > g = f > > Yet one could argue that for all a :: Tag, C (Foo a) holds because a :: Tag can only take two values: A or B, and C (Foo A) and C (Foo B) hold. Is there a way to somehow convince GHC of that fact so that g typechecks? > > Cheers, > Paul > _______________________________________________ > 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 seph at codex.scot Tue Mar 2 15:28:27 2021 From: seph at codex.scot (Seph Shewell Brockway) Date: Tue, 2 Mar 2021 15:28:27 +0000 Subject: [Haskell-cafe] data kinds and exhaustiveness of typeclass instances In-Reply-To: <010f0177f374d32c-ace56c66-4b74-40d4-9e18-bf138f5d5e20-000000@us-east-2.amazonses.com> References: <010f0177f374d32c-ace56c66-4b74-40d4-9e18-bf138f5d5e20-000000@us-east-2.amazonses.com> Message-ID: <20210302152827.awzctp5tay5sehoc@leviathan> On Tue, Mar 02, 2021 at 03:00:55PM +0000, Richard Eisenberg wrote: > > Is there a way to somehow convince GHC of that fact so that g typechecks? > > No. > > First, it would actually be unsound to do so, because of the possibility of exotic types, built with pathological combinations of type and data families: https://gitlab.haskell.org/ghc/ghc/-/issues/14420 > > But, actually, the bigger problem is that we need a class constraint in order to allow a function to compute at runtime. The function f actually takes two arguments at runtime: a representation of the instance which carries f's implementation (this is sometimes called a dictionary), and the normal argument of type a. `g`, on the other hand, has no access to the dictionary needed at runtime, and so it's unclear how it should compute. > > Put another way: a value of type Foo carries no information (beyond the fact that it terminates), because Foo has only one data constructor. So there's no way that g :: Foo a -> Int could be anything but a constant function. You need the class constraint to change this fact. > > Hope this helps! > Richard To elaborate a little on Richard’s answer, this is the reason for GHC.TypeLits’ KnownNat class, so that we have natVal :: KnownNat n => proxy n -> Integer You’d have to supplement your program with a class KnownTag, like so: data Tag = A | B data Foo (a :: Tag) = Foo class KnownTag (a :: Tag) where tagVal :: proxy a -> Tag instance KnownTag A where tagVal _ = A instance KnownTag B where tagVal _ = B class C a where f :: a -> Int instance KnownTag a => C (Foo a) where f _ = case tagVal (Proxy :: Proxy a) of A -> 1; B -> 2 g :: KnownTag a => Foo a -> Int g = f Regards, Seph -- Seph Shewell Brockway, BSc MSc (Glas.) Pronouns: she/her From sylvain at haskus.fr Tue Mar 2 16:02:23 2021 From: sylvain at haskus.fr (Sylvain Henry) Date: Tue, 2 Mar 2021 17:02:23 +0100 Subject: [Haskell-cafe] naturally, length :: a -> Int In-Reply-To: References: Message-ID: On 01/03/2021 17:45, Johannes Waldmann wrote: > Dear Cafe - > > > let's fight Int. I'm in too. One first step would be to use `Word#` instead of `Int#` in ghc primops where it makes sense. This could be done as it should be transparent to most users. The natural next step would be to modify functions and classes in `base` to use appropriate types too. I don't think it's going to happen as it would require modifying the Haskell report and breaking almost every existing code/books/etc. So an alternative path would be to extract every wired-in things from `base` and to put them into a `ghc-base` package that `base`, `foundation` and other alternative preludes would depend on. This way we could write codes that don't depend on `base` and the legacy stuff it contains at all (even transitively). Could you open a ticket on GHC's bug tracker about this? Cheers, Sylvain From david.feuer at gmail.com Tue Mar 2 16:17:32 2021 From: david.feuer at gmail.com (David Feuer) Date: Tue, 2 Mar 2021 11:17:32 -0500 Subject: [Haskell-cafe] naturally, length :: a -> Int In-Reply-To: References: Message-ID: I think non-wrapping Word should be a different type or two. I'm quite fond of the ring laws myself. For many practical purposes, Word64 can stand in for Natural. A non-wrapping variant (newtype, perhaps?) might be useful. Another occasionally useful one is Word63, which is good for bounds-checked operations. On Tue, Mar 2, 2021, 7:53 AM Ben Franksen wrote: > Am 01.03.21 um 17:45 schrieb Johannes Waldmann: > > let's fight Int. > > I'm in. > > > In a lot of code I write (for research, teaching, production), > > a lot of numbers are in fact natural numbers - > > because I am counting (e.g., number of elements in a collection) > > or pointing into what I just counted (e.g., Data.Set.elemAt). > > > > But Haskell's "most natural" type is - Int. > > At least that's my impression from current usage in libraries > > and teaching examples (see functions length, replicate, ... ). > > > > I've developed a horror > > of reading and writing "length something :: Int". > > Same here. > > > If I want to live risky (no checks) I could use Data.Word. > > I think Data.Word is not so bad. Does it come with a guarantee that > maxBound=2^n-1 and all operations being treated module 2^n, for some > natural number n? That would be fine for most applications I guess. > > It would be nice if one could change the semantics of under- or overflow > for Data.Word with a compiler flag, e.g. so that it throws an exception. > > > That's all fine and dandy - until I call some library function... > > I would support a move Int->Word in all libraries where that makes sense. > > But I doubt it will happen. > > Cheers > Ben > > _______________________________________________ > 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 Mar 2 16:48:11 2021 From: jaro.reinders at gmail.com (Jaro Reinders) Date: Tue, 2 Mar 2021 17:48:11 +0100 Subject: [Haskell-cafe] naturally, length :: a -> Int In-Reply-To: References: Message-ID: <8f2d19f5-dff1-955a-5314-f623e9b3496b@gmail.com> There was a great talk about this at PWLConf 2019 by José Manuel Calderón Trilla: "What about the Natural Numbers?" There is a recording on YouTube: https://www.youtube.com/watch?v=jFk1qpr1ytk I think we should not be so quick to give up theoretical elegance and simplicity for the sake of performance (especially not in a language like Haskell). If we would make a change then I would prefer using the lazy and possibly infinite natural numbers with pattern synonyms for successor and zero. Like the existing Integer but then lazy, so more programs will terminate, for example a program that checks if the length of a finite list is smaller than the length of an infinite list. And if we make the change we will probably also need something like Linear.Affine from the linear package with an instance for these natural numbers where the difference between two naturals is an Integer. That would hopefully make it reasonably easy to convert naturals to and from integers. I hope that some of the performance concerns can be tackled by compiler optimizations, for example, detecting when naturals are used in tight loops which can be safely replaced by machine words, similar to strictness analysis and unboxing. And of course programmers can choose to use the old unsafe machine words/ints manually. From duke.j.david at gmail.com Tue Mar 2 17:21:05 2021 From: duke.j.david at gmail.com (David Duke) Date: Tue, 2 Mar 2021 17:21:05 +0000 Subject: [Haskell-cafe] naturally, length :: a -> Int In-Reply-To: References: Message-ID: You might want to revisit the following paper by Colin Runciman -: author = {Colin Runciman}, title = {What About the Natural Numbers}, journal = {Computer Languages}, year = {1989}, volume = {14}, pages = {181--191} It makes similar points and fills out details ... http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.56.3442 regards David On Tue, Mar 2, 2021 at 2:56 PM Johannes Waldmann < johannes.waldmann at htwk-leipzig.de> wrote: > Dear Cafe, > > > thanks for ideas and arguments. > > > > [Ben Franksen] I would support a move Int->Word in all libraries > > where that makes sense. > > I find it hard to think of a library where that does NOT make sense... > > > The following is somewhat related but actually orthogonal: > I mentioned that numbers often arise as cardinalities > (so they are natural, by definition) and serve as pointers. > The next step is then: pointer type safety. Vincent Hanquez' Foundation > https://hackage.haskell.org/package/foundation-0.0.25 defines > > class (IsList c, Item c ~ Element c) => Collection c where > length :: c -> CountOf (Element c) > class ( ... Collection c) => Sequential c where > take :: CountOf (Element c) -> c -> c > > with newtype CountOf ty (and there's also newtype Offset ty) > > I tend to agree. The phantom type argument for CountOf > would catch errors like adding the number of students > to the number of exercises (in my application). > > (Well and the next step after that would be to have > the size of the collection in the (dependent) type as well.) > > Current implementation is newtype CountOf ty = CountOf Int > and the author adds (and that was also the point I was making) > "Int is a terrible backing type which is hard to get away from, > considering that GHC/Haskell are mostly using this for [counting > and] offset. Trying to bring some sanity by a lightweight wrapping." > > > NB: I found out about this from Michael Snoyman's > (very much entertaining, and too much true) > https://www.snoyman.com/blog/2020/12/haskell-bad-parts-3/ > > > Best regards, 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. -- David Duke Emeritus Professor of Computer Science School of Computing University of Leeds UK E:duke.j.david at gmail.com W:https://engineering.leeds.ac.uk/staff/334/Professor_David_Duke -------------- next part -------------- An HTML attachment was scrubbed... URL: From polux2001 at gmail.com Tue Mar 2 19:23:21 2021 From: polux2001 at gmail.com (Paul Brauner) Date: Tue, 2 Mar 2021 20:23:21 +0100 Subject: [Haskell-cafe] data kinds and exhaustiveness of typeclass instances In-Reply-To: <20210302152827.awzctp5tay5sehoc@leviathan> References: <010f0177f374d32c-ace56c66-4b74-40d4-9e18-bf138f5d5e20-000000@us-east-2.amazonses.com> <20210302152827.awzctp5tay5sehoc@leviathan> Message-ID: Thanks all, this all makes sense! On Tue, Mar 2, 2021 at 4:34 PM Seph Shewell Brockway wrote: > On Tue, Mar 02, 2021 at 03:00:55PM +0000, Richard Eisenberg wrote: > > > Is there a way to somehow convince GHC of that fact so that g > typechecks? > > > > No. > > > > First, it would actually be unsound to do so, because of the possibility > of exotic types, built with pathological combinations of type and data > families: https://gitlab.haskell.org/ghc/ghc/-/issues/14420 < > https://gitlab.haskell.org/ghc/ghc/-/issues/14420> > > > > But, actually, the bigger problem is that we need a class constraint in > order to allow a function to compute at runtime. The function f actually > takes two arguments at runtime: a representation of the instance which > carries f's implementation (this is sometimes called a dictionary), and the > normal argument of type a. `g`, on the other hand, has no access to the > dictionary needed at runtime, and so it's unclear how it should compute. > > > > Put another way: a value of type Foo carries no information (beyond the > fact that it terminates), because Foo has only one data constructor. So > there's no way that g :: Foo a -> Int could be anything but a constant > function. You need the class constraint to change this fact. > > > > Hope this helps! > > Richard > > To elaborate a little on Richard’s answer, this is the reason for > GHC.TypeLits’ KnownNat class, so that we have > > natVal :: KnownNat n => proxy n -> Integer > > You’d have to supplement your program with a class KnownTag, like so: > > data Tag = A | B > data Foo (a :: Tag) = Foo > > class KnownTag (a :: Tag) where > tagVal :: proxy a -> Tag > > instance KnownTag A where > tagVal _ = A > > instance KnownTag B where > tagVal _ = B > > class C a where > f :: a -> Int > > instance KnownTag a => C (Foo a) where > f _ = case tagVal (Proxy :: Proxy a) of A -> 1; B -> 2 > > g :: KnownTag a => Foo a -> Int > g = f > > Regards, > > Seph > > -- > Seph Shewell Brockway, BSc MSc (Glas.) > Pronouns: she/her > -------------- next part -------------- An HTML attachment was scrubbed... URL: From polux2001 at gmail.com Tue Mar 2 19:35:04 2021 From: polux2001 at gmail.com (Paul Brauner) Date: Tue, 2 Mar 2021 20:35:04 +0100 Subject: [Haskell-cafe] data kinds and exhaustiveness of typeclass instances In-Reply-To: References: <010f0177f374d32c-ace56c66-4b74-40d4-9e18-bf138f5d5e20-000000@us-east-2.amazonses.com> <20210302152827.awzctp5tay5sehoc@leviathan> Message-ID: Another way of putting it, please correct me if I'm wrong. In coq we could prove forall a, C (Foo a) by case analysis on a. Then we could use that proof to recover the f by applying it to p inside g. It can't work in Haskell because p has no runtime representation. In Haskell the proxy plays the role of p, KnownTag plays the role of the proof that p can be eliminated, and "instance KnownTag a => C (Foo a)" plays the role of the theorem. On Tue, Mar 2, 2021 at 8:23 PM Paul Brauner wrote: > Thanks all, this all makes sense! > > On Tue, Mar 2, 2021 at 4:34 PM Seph Shewell Brockway > wrote: > >> On Tue, Mar 02, 2021 at 03:00:55PM +0000, Richard Eisenberg wrote: >> > > Is there a way to somehow convince GHC of that fact so that g >> typechecks? >> > >> > No. >> > >> > First, it would actually be unsound to do so, because of the >> possibility of exotic types, built with pathological combinations of type >> and data families: https://gitlab.haskell.org/ghc/ghc/-/issues/14420 < >> https://gitlab.haskell.org/ghc/ghc/-/issues/14420> >> > >> > But, actually, the bigger problem is that we need a class constraint in >> order to allow a function to compute at runtime. The function f actually >> takes two arguments at runtime: a representation of the instance which >> carries f's implementation (this is sometimes called a dictionary), and the >> normal argument of type a. `g`, on the other hand, has no access to the >> dictionary needed at runtime, and so it's unclear how it should compute. >> > >> > Put another way: a value of type Foo carries no information (beyond the >> fact that it terminates), because Foo has only one data constructor. So >> there's no way that g :: Foo a -> Int could be anything but a constant >> function. You need the class constraint to change this fact. >> > >> > Hope this helps! >> > Richard >> >> To elaborate a little on Richard’s answer, this is the reason for >> GHC.TypeLits’ KnownNat class, so that we have >> >> natVal :: KnownNat n => proxy n -> Integer >> >> You’d have to supplement your program with a class KnownTag, like so: >> >> data Tag = A | B >> data Foo (a :: Tag) = Foo >> >> class KnownTag (a :: Tag) where >> tagVal :: proxy a -> Tag >> >> instance KnownTag A where >> tagVal _ = A >> >> instance KnownTag B where >> tagVal _ = B >> >> class C a where >> f :: a -> Int >> >> instance KnownTag a => C (Foo a) where >> f _ = case tagVal (Proxy :: Proxy a) of A -> 1; B -> 2 >> >> g :: KnownTag a => Foo a -> Int >> g = f >> >> Regards, >> >> Seph >> >> -- >> Seph Shewell Brockway, BSc MSc (Glas.) >> Pronouns: she/her >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From godzbanebane at gmail.com Wed Mar 3 07:14:47 2021 From: godzbanebane at gmail.com (Georgi Lyubenov) Date: Wed, 3 Mar 2021 09:14:47 +0200 Subject: [Haskell-cafe] data kinds and exhaustiveness of typeclass instances In-Reply-To: References: <010f0177f374d32c-ace56c66-4b74-40d4-9e18-bf138f5d5e20-000000@us-east-2.amazonses.com> <20210302152827.awzctp5tay5sehoc@leviathan> Message-ID: To "more directly" do the same thing as in coq, you can also take the singletons approach, and either explicitly use a "proof providing" function: withC :: STag t -> (C (Foo t) => r) -> r withC tag k = case tag of SA -> k SB -> k (so if you call `withC tag body` you now have the required constraint in `body` or you could use the implicit singleton carrying type class: instance STagI t => C (Foo t) where f = case tagSing of SA -> f SB -> f and the remaining boilerplate code required: data STag t where SA :: STag A SB :: STag B class STagI t where tagSing :: STag t instance STag A where tagSing = SA instance STag B where tagSing = SB -------------- next part -------------- An HTML attachment was scrubbed... URL: From matteo at confscience.com Wed Mar 3 10:20:48 2021 From: matteo at confscience.com (matteo at confscience.com) Date: Wed, 3 Mar 2021 11:20:48 +0100 Subject: [Haskell-cafe] International Conference on Informatics Revolution for Smarter Healthcare (IRSH 2021) Prague Message-ID: <005a01d71016$e170f400$a452dc00$@confscience.com> Call for papers ************************************************* International Conference on Informatics Revolution for Smarter Healthcare (IRSH 2021) Prague- Czech Republic, October 14-15, 2021 https://confscience.com/irsh/ Submission deadline: April 1, 2021 All papers accepted in IRSH 2021 will be published in Springer CCIS (Communications in Computer and Information Science). CCIS is abstracted/indexed in Scopus, SCImago, EI-Compendex, Mathematical Reviews, DBLP, Google Scholar, and Thomson Reuters Conference Proceedings Citation (Former ISI Proceedings) *************************************************************************** IMPORTANT DATES: - Paper Submission: April 1, 2021 - Acceptance Notification: July 1, 2021 - Final Manuscript Due: September 1, 2021 *************************************************************************** The IRSH 2021 conference will be held in Conjunction with: International Conference on Applied Data Science and Intelligence (ADSI 2021) International Conference on Recent Theories and Applications in Transportation and Mobility - (RTATM 2021) *************************************************************************** TOPICS: Authors are invited to submit their original papers to address the topics of the conference, including but not limited to: FUNDAMENTALS AND THEORIES - Interoperability and Data Integration - Confidentiality and Data Security - Data protection - Data Sharing - Security, Privacy, and Trust - Emergent healthcare standards - Emergent healthcare architectures - ICT, Ageing and Disability - Physiological and behavioural modelling - Pandemic and disease modeling - Usability and user experience of medical devices - Human behaviour - Clinical investigation regulatory frameworks - Integrated healthcare approaches - eHealth data standards and interoperability (e.g. HL7/FHIR) - Databases and data warehousing - Big Data and Open Data for healthcare - Design and Development of Methodologies for Healthcare - Emergent Communication Technologies - Real-time interaction theories - Emergent Technologies for Ambient Assisted Living - User Interface Design for healthcare - Sustainability - New approaches for accuracy and effectiveness - Data mining and bioinformatics - Enhanced living environments - Analysis and evaluation of healthcare systems INTELLIGENT HEALTHCARE - Pattern recognition and Machine - Learning for healthcare - Cognitive Informatics - Big Data in Healthcare - Wellbeing Informatics - Data Mining and Data Analytics - Data Visualization - Smart environments - Smart Ambient Assisted Living - Intelligent healthcare solutions - Agent-based solutions for healthcare - Collaboration systems - Intelligent Electronic Health Records - Internet of Things for healthcare - Cyber-Physical Systems for healthcare - Ambient Computing and Reasoning - Context Awareness - Smart devices for eldercare - Autonomy and active ageing - Emergent technologies for intelligent Computer Vision - Service production and delivery - Gamification - Multi-modal interaction - Computer-aided detection and diagnosis - Crowdsourcing for smarted healthcare SERVICES, SYSTEMS, AND INFRASTRUCTURES - Emergent healthcare services - Pervasive health systems and services - Remote healthcare management - Emergent healthcare infrastructure - Industry Revolution 4.0 for healthcare - eHealth - Electronic health records - Assistive technologies - Disease surveillance and patient monitoring systems - Prevention and detection systems - Home monitoring - Healthcare management systems - ICT-based therapeutic systems - ICT-based rehabilitation technologies - Wearable health informatics - Emergent technologies for data analytics - Ambient Assisted Leaving (AAL) - Decision Support Systems - Emergent Technologies for Remote AAL Monitoring - Emergent Technologies and Accessibility - 5G for healthcare - Healthcare supply chain and logistics - Wireless Body Networks - Telemedicine and mobile telemedicine - Mobile Systems - Software Defined infrastructures - Patient empowerment systems - Smart technology for remote patient visits - Biosensors - Medical devices APPLICATIONS - eHealth applications - Application of health informatics in clinical cases - Mobile technologies for healthcare applications - Software Systems in healthcare - Social networking and healthcare - Case Studies - Personalization and patient experience - AR and VR applications - Patient billing - Accounting systems - Personnel and payroll - Materials management - Voice recognition systems - Asset management solutions - Disease management - Feedback integration - Clinical software - Crowd-computing applications - Future directions - Drone-based solutions - Software Defined Networks for healthcare *************************************************************************** OUTSTANDING PAPERS: Based on the peer review scores as well as the presentations at the conference, the authors of outstanding papers will be invited to extend their works for a potential publication in journals special issues with high impact factors. *************************************************************************** PAPER SUBMISSION: Papers must be submitted electronically as PDF files via easychair (https://easychair.org/conferences/?conf=irsh2021). All papers will be peer reviewed. Length of Full papers: 12-15 pages long (written in the LNCS/CCIS one-column page format, 400 words per page) Length of Short papers: less than 12 pages For more information, please refer to the conference website: https://confscience.com/irsh/ *************************************************************************** CONTACT For more information, please send an email to info-irsh at confscience.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Wed Mar 3 10:29:24 2021 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Wed, 3 Mar 2021 10:29:24 +0000 Subject: [Haskell-cafe] International Conference on Applied Data Science and Intelligence - (ADSI 2021) Prague In-Reply-To: References: <004c01d7086e$dabe7a60$903b6f20$@confscience.com> Message-ID: <20210303102924.GL17096@cloudinit-builder> On Mon, Feb 22, 2021 at 09:57:12AM +0100, Ben Franksen wrote: > I would like to renew my request to block this fake conference spammer. > This sort of business is disgusting and offensive. Seconded. There have been seven spam posts from this poster in the last 5 weeks. From lemming at henning-thielemann.de Wed Mar 3 10:36:26 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Wed, 3 Mar 2021 11:36:26 +0100 (CET) Subject: [Haskell-cafe] International Conference on Applied Data Science and Intelligence - (ADSI 2021) Prague In-Reply-To: <20210303102924.GL17096@cloudinit-builder> References: <004c01d7086e$dabe7a60$903b6f20$@confscience.com> <20210303102924.GL17096@cloudinit-builder> Message-ID: <99b26f86-5670-96c4-7f44-96c6dc30156@henning-thielemann.de> On Wed, 3 Mar 2021, Tom Ellis wrote: > On Mon, Feb 22, 2021 at 09:57:12AM +0100, Ben Franksen wrote: > >> I would like to renew my request to block this fake conference spammer. >> This sort of business is disgusting and offensive. > > Seconded. There have been seven spam posts from this poster in the > last 5 weeks. But then we enter the discussion who considers what conferences as fake. I have added a filter rule to my private spam filter. If you think that the announcements are constantly off-topic, you might ask the sender to unsubscribe from the mailing list. From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Wed Mar 3 10:42:38 2021 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Wed, 3 Mar 2021 10:42:38 +0000 Subject: [Haskell-cafe] International Conference on Applied Data Science and Intelligence - (ADSI 2021) Prague In-Reply-To: <99b26f86-5670-96c4-7f44-96c6dc30156@henning-thielemann.de> References: <004c01d7086e$dabe7a60$903b6f20$@confscience.com> <20210303102924.GL17096@cloudinit-builder> <99b26f86-5670-96c4-7f44-96c6dc30156@henning-thielemann.de> Message-ID: <20210303104238.GM17096@cloudinit-builder> On Wed, Mar 03, 2021 at 11:36:26AM +0100, Henning Thielemann wrote: > On Wed, 3 Mar 2021, Tom Ellis wrote: > > On Mon, Feb 22, 2021 at 09:57:12AM +0100, Ben Franksen wrote: > > > > > I would like to renew my request to block this fake conference spammer. > > > This sort of business is disgusting and offensive. > > > > Seconded. There have been seven spam posts from this poster in the > > last 5 weeks. > > But then we enter the discussion who considers what conferences as fake. I don't think we need to do that. We can just observe that since 28th January the poster has posted seven messages to Haskell Cafe on the subjects of * International Conference on Recent Theories and Applications in Transportation * International Conference on Applied Data Science and Intelligence * International Conference on Informatics Revolution for Smarter Healthcare none of which have anything to do with Haskell. > If you think that the announcements are constantly off-topic, you might ask > the sender to unsubscribe from the mailing list. My experience dealing with internet spam makes me think this course of action is less likely to lead to a desired outcome than asking the moderators to block the account! Tom From migmit at gmail.com Wed Mar 3 10:47:40 2021 From: migmit at gmail.com (MigMit) Date: Wed, 3 Mar 2021 11:47:40 +0100 Subject: [Haskell-cafe] International Conference on Applied Data Science and Intelligence - (ADSI 2021) Prague In-Reply-To: <20210303104238.GM17096@cloudinit-builder> References: <004c01d7086e$dabe7a60$903b6f20$@confscience.com> <20210303102924.GL17096@cloudinit-builder> <99b26f86-5670-96c4-7f44-96c6dc30156@henning-thielemann.de> <20210303104238.GM17096@cloudinit-builder> Message-ID: <12794E5B-259E-4926-83C3-4B9FCC91742E@gmail.com> Agreed. Doesn't even matter if the conferences are fake or real; they are clearly off-topic, and that poster does not post anything else, so, blocking the account is quite reasonable. > On 3 Mar 2021, at 11:42, Tom Ellis wrote: > > On Wed, Mar 03, 2021 at 11:36:26AM +0100, Henning Thielemann wrote: >> On Wed, 3 Mar 2021, Tom Ellis wrote: >>> On Mon, Feb 22, 2021 at 09:57:12AM +0100, Ben Franksen wrote: >>> >>>> I would like to renew my request to block this fake conference spammer. >>>> This sort of business is disgusting and offensive. >>> >>> Seconded. There have been seven spam posts from this poster in the >>> last 5 weeks. >> >> But then we enter the discussion who considers what conferences as fake. > > I don't think we need to do that. We can just observe that since 28th > January the poster has posted seven messages to Haskell Cafe on the > subjects of > > * International Conference on Recent Theories and Applications in Transportation > * International Conference on Applied Data Science and Intelligence > * International Conference on Informatics Revolution for Smarter Healthcare > > none of which have anything to do with Haskell. > >> If you think that the announcements are constantly off-topic, you might ask >> the sender to unsubscribe from the mailing list. > > My experience dealing with internet spam makes me think this course of > action is less likely to lead to a desired outcome than asking the > moderators to block the account! > > Tom > > > _______________________________________________ > 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 carter.schonwald at gmail.com Wed Mar 3 13:45:34 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Wed, 3 Mar 2021 08:45:34 -0500 Subject: [Haskell-cafe] naturally, length :: a -> Int In-Reply-To: References: Message-ID: I think we’d also wanna add compiler suport for ints and words and signal on over/underflow using cpu machinery . Most other approachs have pretty fun changes in memory rep On Tue, Mar 2, 2021 at 11:10 AM Sylvain Henry wrote: > On 01/03/2021 17:45, Johannes Waldmann wrote: > > Dear Cafe - > > > > > > let's fight Int. > > I'm in too. > > One first step would be to use `Word#` instead of `Int#` in ghc primops > where it makes sense. This could be done as it should be transparent to > most users. > > The natural next step would be to modify functions and classes in `base` > to use appropriate types too. I don't think it's going to happen as it > would require modifying the Haskell report and breaking almost every > existing code/books/etc. > > So an alternative path would be to extract every wired-in things from > `base` and to put them into a `ghc-base` package that `base`, > `foundation` and other alternative preludes would depend on. This way we > could write codes that don't depend on `base` and the legacy stuff it > contains at all (even transitively). > > Could you open a ticket on GHC's bug tracker about this? > > Cheers, > Sylvain > > _______________________________________________ > 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 Wed Mar 3 15:17:02 2021 From: olf at aatal-apotheke.de (Olaf Klinke) Date: Wed, 03 Mar 2021 16:17:02 +0100 Subject: [Haskell-cafe] naturally, length :: a -> Int Message-ID: Which bugs can be caught at compile-time by having length return natural numbers? Regarding space, Int instead of Word only wastes the sign bit, doesn't it? I like the idea that Johannes Waldmann and Jaro Reinders brought up: Why is length :: Foldable a => a -> Int so convenient? Short answer: Because of "affine" things like `availableSpace - length xs'. There are indeed two types involved here, as the foundation package points out: relative offsets (like a tangent space?) and absolute counts. Think of NominalDiffTime versus UTCTime, or the two interpretations of vectors as points/movements in space. In this light one could regard the current length as "the relative offset of the end of the list" which can readily be subtracted from another relative offset. In mathematical terms: Int the free group over the monoid of cardinal lengths. While we're at it: Can there be a Fractional type permitting only positive numbers, as the positive real numbers are closed under division? Can there be a type of rationals between 0 and 1 (which is closed under multiplication) where (/x) is the right adjoint to (*x)? Olaf From olf at aatal-apotheke.de Wed Mar 3 15:27:46 2021 From: olf at aatal-apotheke.de (Olaf Klinke) Date: Wed, 03 Mar 2021 16:27:46 +0100 Subject: [Haskell-cafe] aeson: instance FromJSON IntMap Message-ID: <8d8326808c01d2983de1653b6a3a8ef41af08cba.camel@aatal-apotheke.de> Dear Cafe, why is Aeson's instance FromJSON IntMap so different from the instance of Map? Apparently the Map instance expects an Object (the dictionary) while the IntMap instance [1] is implemented using IntMap.fromList, so it expects an array. I can of course decode the JSON as (Map Int) and then use IntMap.fromAscList . Map.assocs but how efficient is that? And it also relies on Map.assocs producing the list in the order expected by fromAscList which (unlikely) could be broken in a future version of containers. Thanks Olaf [1] https://hackage.haskell.org/package/aeson-1.5.6.0/docs/src/Data.Aeson.Types.FromJSON.html#line-1891 From oleg.grenrus at iki.fi Wed Mar 3 16:16:03 2021 From: oleg.grenrus at iki.fi (Oleg Grenrus) Date: Wed, 3 Mar 2021 18:16:03 +0200 Subject: [Haskell-cafe] aeson: instance FromJSON IntMap In-Reply-To: <8d8326808c01d2983de1653b6a3a8ef41af08cba.camel@aatal-apotheke.de> References: <8d8326808c01d2983de1653b6a3a8ef41af08cba.camel@aatal-apotheke.de> Message-ID: History digging points to a commit from 2013: https://github.com/haskell/aeson/commit/260a7e839bfda660bb7e0b715567b35d76cc4693  I'm too lazy to dig further, but I'd expect that the answer "that instance have always been that way". Back then there weren't machinery to parse keys of maps (we had e.g. `FromJSON (Map Text a)`). Now we have. I'm open to change (and have other small-ish yet breaking changes in mind for aeson), please open an issue, so we can discuss it there. Cheers, Oleg On 3.3.2021 17.27, Olaf Klinke wrote: > Dear Cafe, > > why is Aeson's instance FromJSON IntMap so different from the instance > of Map? Apparently the Map instance expects an Object (the dictionary) > while the IntMap instance [1] is implemented using IntMap.fromList, so > it expects an array. > I can of course decode the JSON as (Map Int) and then use > IntMap.fromAscList . Map.assocs > but how efficient is that? And it also relies on Map.assocs producing > the list in the order expected by fromAscList which (unlikely) could be > broken in a future version of containers. > > Thanks > Olaf > > [1] > https://hackage.haskell.org/package/aeson-1.5.6.0/docs/src/Data.Aeson.Types.FromJSON.html#line-1891 > > _______________________________________________ > 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 jgbailey at gmail.com Wed Mar 3 19:06:37 2021 From: jgbailey at gmail.com (Justin Bailey) Date: Wed, 3 Mar 2021 11:06:37 -0800 Subject: [Haskell-cafe] aeson: instance FromJSON IntMap In-Reply-To: References: <8d8326808c01d2983de1653b6a3a8ef41af08cba.camel@aatal-apotheke.de> Message-ID: I recently ran into a similar issue, where the `parseJason` instance for a map with custom keys (not Text but a sum type) was expected to be a JSON array rather than an object. I just ended up writing my own instance, assuming the built-in one would be too hard to change (breaking backwards compatibility). On Wed, Mar 3, 2021 at 8:17 AM Oleg Grenrus wrote: > > History digging points to a commit from 2013: > https://github.com/haskell/aeson/commit/260a7e839bfda660bb7e0b715567b35d76cc4693 > I'm too lazy to dig further, but I'd expect that the answer "that > instance have always been that way". > > Back then there weren't machinery to parse keys of maps (we had e.g. > `FromJSON (Map Text a)`). Now we have. I'm open to change (and have > other small-ish yet breaking changes in mind for aeson), please open an > issue, so we can discuss it there. > > Cheers, Oleg > > On 3.3.2021 17.27, Olaf Klinke wrote: > > Dear Cafe, > > > > why is Aeson's instance FromJSON IntMap so different from the instance > > of Map? Apparently the Map instance expects an Object (the dictionary) > > while the IntMap instance [1] is implemented using IntMap.fromList, so > > it expects an array. > > I can of course decode the JSON as (Map Int) and then use > > IntMap.fromAscList . Map.assocs > > but how efficient is that? And it also relies on Map.assocs producing > > the list in the order expected by fromAscList which (unlikely) could be > > broken in a future version of containers. > > > > Thanks > > Olaf > > > > [1] > > https://hackage.haskell.org/package/aeson-1.5.6.0/docs/src/Data.Aeson.Types.FromJSON.html#line-1891 > > > > _______________________________________________ > > 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 ben.franksen at online.de Thu Mar 4 10:17:51 2021 From: ben.franksen at online.de (Ben Franksen) Date: Thu, 4 Mar 2021 11:17:51 +0100 Subject: [Haskell-cafe] naturally, length :: a -> Int In-Reply-To: <8f2d19f5-dff1-955a-5314-f623e9b3496b@gmail.com> References: <8f2d19f5-dff1-955a-5314-f623e9b3496b@gmail.com> Message-ID: Am 02.03.21 um 17:48 schrieb Jaro Reinders: > There was a great talk about this at PWLConf 2019 by José Manuel > Calderón Trilla: "What about the Natural Numbers?" > There is a recording on YouTube: > https://www.youtube.com/watch?v=jFk1qpr1ytk Thanks for the link. I read Colin's paper long ago and forgot most about it. IMO the correspondence with take and drop for lists isn't too convincing. Lists are boring, and for data structures with more interesting invariants (like Sets) size/length is no longer a monoid homomorphism. The talk is also missing out on the opportunity to hold an extended discussion about arithmetic laws like cancellation. For instance, we have (a - b) + b == a for unsigned (Data.Word, assuming operations modulo 2^bitsize), but (a .-. b) + b == a does not hold in general. Due to primary school "indoctrination" we all intuitively expect such laws to hold for the standard arithmetic operators, which is why I think they should be either modulo 2^wordsize as in C or raise an exception. And I would really like to be able to chose which of those I get. None of this preclude the addition of non-standard arithmetic operators, of course. These may be useful in certain simple situations like when dealing with lists. Cheers Ben From ben.franksen at online.de Thu Mar 4 10:36:14 2021 From: ben.franksen at online.de (Ben Franksen) Date: Thu, 4 Mar 2021 11:36:14 +0100 Subject: [Haskell-cafe] naturally, length :: a -> Int In-Reply-To: References: Message-ID: Am 03.03.21 um 16:17 schrieb Olaf Klinke: > Which bugs can be caught at compile-time by having length return > natural numbers? Regarding space, Int instead of Word only wastes the > sign bit, doesn't it? > > I like the idea that Johannes Waldmann and Jaro Reinders brought up: > Why is length :: Foldable a => a -> Int so convenient? Short answer: > Because of "affine" things like `availableSpace - length xs'. > > There are indeed two types involved here, as the foundation package > points out: relative offsets (like a tangent space?) and absolute > counts. Think of NominalDiffTime versus UTCTime, or the two > interpretations of vectors as points/movements in space. > > In this light one could regard the current length as > "the relative offset of the end of the list" which can readily be > subtracted from another relative offset. In mathematical terms: Int the > free group over the monoid of cardinal lengths. Hm, interesting point. If we do embrace that viewpoint, then I'd say we should go all the way and interpret indices modulo (non-negative) structure size! This makes (safe) indexing total (for non-empty structures) and allows things like xs !! (-1) == last xs as in Perl and some other languages. Unsafe indexing (as in the vector package) could remain as is for performance critical code. Cheers Ben From olf at aatal-apotheke.de Thu Mar 4 13:17:40 2021 From: olf at aatal-apotheke.de (Olaf Klinke) Date: Thu, 04 Mar 2021 14:17:40 +0100 Subject: [Haskell-cafe] naturally, length :: a -> Int Message-ID: <7bfbe3810273539af73e79c31244cf364e5f73c3.camel@aatal-apotheke.de> > Date: Thu, 4 Mar 2021 11:36:14 +0100 > From: Ben Franksen > To: haskell-cafe at haskell.org > Subject: Re: [Haskell-cafe] naturally, length :: a -> Int > Message-ID: > Content-Type: text/plain; charset=utf-8 > > Am 03.03.21 um 16:17 schrieb Olaf Klinke: > > Which bugs can be caught at compile-time by having length return > > natural numbers? Regarding space, Int instead of Word only wastes the > > sign bit, doesn't it? > > > > I like the idea that Johannes Waldmann and Jaro Reinders brought up: > > Why is length :: Foldable a => a -> Int so convenient? Short answer: > > Because of "affine" things like `availableSpace - length xs'. > > > > There are indeed two types involved here, as the foundation package > > points out: relative offsets (like a tangent space?) and absolute > > counts. Think of NominalDiffTime versus UTCTime, or the two > > interpretations of vectors as points/movements in space. > > > > In this light one could regard the current length as > > "the relative offset of the end of the list" which can readily be > > subtracted from another relative offset. In mathematical terms: Int the > > free group over the monoid of cardinal lengths. > > Hm, interesting point. > > If we do embrace that viewpoint, then I'd say we should go all the way > and interpret indices modulo (non-negative) structure size! This makes > (safe) indexing total (for non-empty structures) and allows things like > xs !! (-1) == last xs as in Perl and some other languages. Unsafe > indexing (as in the vector package) could remain as is for performance > critical code. > > Cheers > Ben I like Haskell particularly for not being like Matlab, where virtually any well-bracketed indexing syntax does produce a result, but not necessarily what you intended or expected. Besides, for some structures length is expensive but index is not so much, so I wonder whether one can modulo-index into a lazy container without evaluating its entire spine. I just wanted to understand/justify why Int is so convenient, and the Time-DiffTime analogy sprang to mind. Following the free group route, one immediately sees that there is an embedding from cardinalities to offsets, but no inverse. We could, of course, bring other categories into the picture such as ordered sets. Then there is an embedding-projection pair between Int and Natural, where all Ints < 0 are mapped to 0. The base functions such as take and drop adhere to this interpretation. Olaf From sylvain at haskus.fr Thu Mar 4 21:24:37 2021 From: sylvain at haskus.fr (Sylvain Henry) Date: Thu, 4 Mar 2021 22:24:37 +0100 Subject: [Haskell-cafe] Serious bug with Natural in GHC 9.0.1 Message-ID: Hi Café, I've made a mistake while implementing constant folding for Natural numbers in GHC 9.0.1 that hasn't been caught before the release. It's a rather serious bug as any number converted into `Natural` with `fromIntegral` can be truncated to Word range if a bogus rule is triggered (see #19345 and #19411 for more details). It is already fixed in HEAD and the fix will be present in GHC 9.0.2 which should be released soon. In the meantime you can check if the rule is triggered with `-ddump-rule-firings`. If it shows that the following rule has fired, then your code may be badly modified: |Rule fired: fromIntegral/Int->Natural (GHC.Real)| (the issue is that despite its name the rule isn't correctly constrained to convert Ints into Natural, but any numeric type...). Sorry about that! Sylvain #19345: https://gitlab.haskell.org/ghc/ghc/-/issues/19345 #19411: https://gitlab.haskell.org/ghc/ghc/-/issues/19411 -------------- next part -------------- An HTML attachment was scrubbed... URL: From emilypi at cohomolo.gy Fri Mar 5 04:55:20 2021 From: emilypi at cohomolo.gy (Emily Pillmore) Date: Fri, 05 Mar 2021 04:55:20 +0000 Subject: [Haskell-cafe] Serious bug with Natural in GHC 9.0.1 In-Reply-To: References: Message-ID: No worries Sylvain, Mistakes will be made while improving things, and we caught it, so that's great. Thanks for the head's up and good luck with your ongoing improvements! Cheers, Emily On Thu, Mar 04, 2021 at 4:24 PM, Sylvain Henry < sylvain at haskus.fr > wrote: > > > > Hi Café, > > > > I've made a mistake while implementing constant folding for Natural > numbers in GHC 9.0.1 that hasn't been caught before the release. It's a > rather serious bug as any number converted into `Natural` with > `fromIntegral` can be truncated to Word range if a bogus rule is triggered > (see #19345 and #19411 for more details). > > > > It is already fixed in HEAD and the fix will be present in GHC 9.0.2 which > should be released soon. > > > > In the meantime you can check if the rule is triggered with > `-ddump-rule-firings`. If it shows that the following rule has fired, then > your code may be badly modified: > > > > Rule fired: fromIntegral/Int->Natural (GHC.Real) > > > > (the issue is that despite its name the rule isn't correctly constrained > to convert Ints into Natural, but any numeric type...). > > Sorry about that! > Sylvain > > #19345: https:/ / gitlab. haskell. org/ ghc/ ghc/ -/ issues/ 19345 ( > https://gitlab.haskell.org/ghc/ghc/-/issues/19345 ) > #19411: https:/ / gitlab. haskell. org/ ghc/ ghc/ -/ issues/ 19411 ( > https://gitlab.haskell.org/ghc/ghc/-/issues/19411 ) > > > > > > > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: http:/ / mail. haskell. > org/ cgi-bin/ mailman/ listinfo/ haskell-cafe ( > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe ) Only > members subscribed via the mailman list are allowed to post. > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben.franksen at online.de Fri Mar 5 13:50:00 2021 From: ben.franksen at online.de (Ben Franksen) Date: Fri, 5 Mar 2021 14:50:00 +0100 Subject: [Haskell-cafe] naturally, length :: a -> Int In-Reply-To: <7bfbe3810273539af73e79c31244cf364e5f73c3.camel@aatal-apotheke.de> References: <7bfbe3810273539af73e79c31244cf364e5f73c3.camel@aatal-apotheke.de> Message-ID: Am 04.03.21 um 14:17 schrieb Olaf Klinke: >> Am 03.03.21 um 16:17 schrieb Olaf Klinke: >>> I like the idea that Johannes Waldmann and Jaro Reinders brought up: >>> Why is length :: Foldable a => a -> Int so convenient? Short answer: >>> Because of "affine" things like `availableSpace - length xs'. >>> >>> There are indeed two types involved here, as the foundation package >>> points out: relative offsets (like a tangent space?) and absolute >>> counts. Think of NominalDiffTime versus UTCTime, or the two >>> interpretations of vectors as points/movements in space. >>> >>> In this light one could regard the current length as >>> "the relative offset of the end of the list" which can readily be >>> subtracted from another relative offset. In mathematical terms: Int the >>> free group over the monoid of cardinal lengths. >> >> Hm, interesting point. >> >> If we do embrace that viewpoint, then I'd say we should go all the way >> and interpret indices modulo (non-negative) structure size! This makes >> (safe) indexing total (for non-empty structures) and allows things like >> xs !! (-1) == last xs as in Perl and some other languages. Unsafe >> indexing (as in the vector package) could remain as is for performance >> critical code. >> >> Cheers >> Ben > > I like Haskell particularly for not being like Matlab, where virtually > any well-bracketed indexing syntax does produce a result, but not > necessarily what you intended or expected. Okay, so you expect the result of list !! (-1) vector ! (-1) to be bottom a.k.a. "error: index out of range". Whether a non-result like that corresponds closer to what you expected or intended depends pretty much on your expectations and intentions. Indexing modulo size/length is well-defined, logically sound, easy to understand and remember, and therefore (IMHO) very practical. Of course YMMV. > Besides, for some structures > length is expensive but index is not so much, so I wonder whether one > can modulo-index into a lazy container without evaluating its entire > spine. One cannot, naturally, index into a list with a negative index or with one that is greater than or equal to the length w/o evaluating its entire spine. So what? If you write "abc" !! 3 this will throw an error nowadays, but only after traversing the full spine. Now you may argue that [0..] !! (-1) at least crashes immediately, whereas with my proposal it would first eat up all your memory. Okay, not so nice. However, note that replacing Int with Word for size/length/indexing has exactly the same disadvantage, e.g. with [0..] !! (0 - 1) Cheers Ben From rebecca at rebeccaskinner.net Fri Mar 5 16:00:07 2021 From: rebecca at rebeccaskinner.net (Rebecca Skinner) Date: Fri, 5 Mar 2021 10:00:07 -0600 Subject: [Haskell-cafe] Haskell.org Call For Nominations Message-ID: Dear Haskellers, As you may know, Emily Pillmore has recently stepped down from her role on the Haskell.org committee as she focuses full time on her new role as the CTO of the Haskell Foundation. We are currently seeking nominations for anyone interested in filling her vacated seat on the committee. The term for this seat will end in October of 2021, so it will be a good opportunity for anyone who is interested in serving for a short time, perhaps to get a better idea of whether they would like to be re-nominated for a full term at the end of the year. The role is about setting policy, providing direction/guidance for Haskell.org infrastructure, planning for the long term, and being fiscally responsible with the Haskell.org funds and donations. As overseers for policy regarding the open source side of Haskell, committee members must also be able to set aside personal or business related bias and make decisions with the good of the open source Haskell community in mind. For more information about the haskell committee please visit https://www.haskell.org/haskell-org-committee/ To nominate yourself, please send an email to committee at haskell.org no later than 12 March 2021. Q: If selected for this role, will I serve a normal 3-year term? A: No, you will serve the remainder of the term for the seat, which will end in October of 2021. Q: If I was nominated for a seat during the 2021 election and was not selected, am I eligible for re-nomination? A: We had a number of great candidates for the recent election and we would welcome anyone who was not selected to re-nominate themselves for this seat. Q: If selected, am I eligible for re-nomination at the end of the year? A: Yes, if you are selected and serve you may be re-nominated for a full 2022-2025 term. Q: Who can be nominated to serve on the committee? A: Anyone who has something to contribute. Committee members do not need to be deep technical Haskell experts. Instead we look for enthusiasm towards improving the Haskell community. We aim to represent the different facets of the community. We aim to be diverse in terms of industry or research, and in terms of gender, race and location. Q: What should I include in my nomination? A: Tell us a bit about who you are, and how you think you can help. Feel free to include anything that you think will help us make a better decision. Q: What is involved in membership? A: Being a member of the committee does not necessarily require a significant amount of time, but committee members should aim to be responsive during discussions when the committee is called upon to make a decision. For more information, or any other questions, please reach out to the committee by email. - Rebecca Skinner on behalf of the Haskell.org Committee -------------- next part -------------- An HTML attachment was scrubbed... URL: From maurer.benjamin at gmail.com Fri Mar 5 16:01:02 2021 From: maurer.benjamin at gmail.com (Benjamin Maurer) Date: Fri, 5 Mar 2021 17:01:02 +0100 Subject: [Haskell-cafe] Profiling analyzing ghc compilation In-Reply-To: <010f0177b69bb8e1-8c19d5f1-22ed-4b67-9364-4c11a86de524-000000@us-east-2.amazonses.com> References: <010f0177b69bb8e1-8c19d5f1-22ed-4b67-9364-4c11a86de524-000000@us-east-2.amazonses.com> Message-ID: <269beeb9-7e92-aba5-e806-bb83fb9959cb@gmail.com> There is also `|-ddump-timings| ` (see https://downloads.haskell.org/~ghc/9.0.1/docs/html/users_guide/flags.html#compiler-debugging-options), which seems to print a subset of what `-dshow-passes` prints? If I ever have time, I'd love to make something like Clang's `time-trace` functionality, i.e., printing per-file pass timings in Chrome tracing profiling format, so that one can get pretty flame graphs. (https://aras-p.info/blog/2019/01/16/time-trace-timeline-flame-chart-profiler-for-Clang/) The data already seems to be there. Maybe someone else gets to it before me =) Cheers, Ben -------------- next part -------------- An HTML attachment was scrubbed... URL: From lemming at henning-thielemann.de Fri Mar 5 22:22:55 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Fri, 5 Mar 2021 23:22:55 +0100 (CET) Subject: [Haskell-cafe] naturally, length :: a -> Int In-Reply-To: References: Message-ID: On Wed, 3 Mar 2021, Olaf Klinke wrote: > While we're at it: Can there be a Fractional type permitting only > positive numbers, as the positive real numbers are closed under > division? Can there be a type of rationals between 0 and 1 (which is > closed under multiplication) where (/x) is the right adjoint to (*x)? Once I defined a wrapper for numbers that (morally) restricts the value range to non-negative values: http://hackage.haskell.org/package/non-negative However, it turned out to be impractical. It is incompatible with its base number type. If you have even more variants for positive numbers, for numbers in the range [0,1] you will do more conversions than computations. I found the LiquidHaskell approach convincing: You have a base type and add constraints on the value range. You could assign a [0,1]-value to a non-negative value without conversion, because LiquidHaskell would ask Z3 and Z3 would confirm that a [0,1]-value is always non-negative. From zemyla at gmail.com Sat Mar 6 02:03:54 2021 From: zemyla at gmail.com (Zemyla) Date: Fri, 5 Mar 2021 20:03:54 -0600 Subject: [Haskell-cafe] naturally, length :: a -> Int In-Reply-To: References: Message-ID: You're looking for Ratio Natural. On Wed, Mar 3, 2021, 09:20 Olaf Klinke wrote: > While we're at it: Can there be a Fractional type permitting only > positive numbers, as the positive real numbers are closed under > division? > -------------- next part -------------- An HTML attachment was scrubbed... URL: From lemming at henning-thielemann.de Sat Mar 6 13:41:22 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Sat, 6 Mar 2021 14:41:22 +0100 (CET) Subject: [Haskell-cafe] naturally, length :: a -> Int In-Reply-To: References: Message-ID: On Fri, 5 Mar 2021, Zemyla wrote: > You're looking for Ratio Natural. It's more like Ratio PositiveNatural. From raichoo at googlemail.com Mon Mar 8 12:51:11 2021 From: raichoo at googlemail.com (raichoo) Date: Mon, 8 Mar 2021 13:51:11 +0100 Subject: [Haskell-cafe] Announcing `passveil` 0.0.1.0 Message-ID: Hi everyone, My company antei (https://antei.de) has developed a password manager for our internal usage and we have decided to open source it. We drew a lot of inspiration from the well established `password-store`. It's build in Haskell and uses `darcs` for versioning the password store. We have chosen `darcs` because of its powerful merging capabilities which turned out to be useful for our use case. Apart from that, we have implemented a trust system, that can be used to transfer knowledge of a password to other people having access to the store, so we do not have to rely on transmitting sensitive data via insecure channels (https://sysadminotaur.devolutions.net/30-vault). Please note that `passveil` is in an early state and has only been tested and used internally. We strongly believe in open source and making our tools available to others and are constantly working on improving our code and want share our progress with everyone. Check out: https://passveil.antei.de for more information. Kind regards, raichoo -------------- next part -------------- An HTML attachment was scrubbed... URL: From J.Hage at uu.nl Mon Mar 8 14:09:28 2021 From: J.Hage at uu.nl (Hage, J. (Jurriaan)) Date: Mon, 8 Mar 2021 14:09:28 +0000 Subject: [Haskell-cafe] Second Call for Papers for the Haskell Symposium 2021 Message-ID: <4D71E45D-E4EE-4CF4-9FF6-06EB813B8A2A@uu.nl> Dear all, This is the second call for papers for the upcoming Haskell Symposium. The deadline of the first round is approaching fast. Please forward to anyone that you believe might be interested. Apologies for receiving multiple copies of this announcement. Best regards, Jurriaan Hage Chair ================================================================================ ACM SIGPLAN CALL FOR SUBMISSIONS Haskell Symposium 2021 ** virtual ** Thu 26 -- Fri 27 August, 2021 http://www.haskell.org/haskell-symposium/2021/ ================================================================================ The ACM SIGPLAN Haskell Symposium 2021 will be co-located with the 2021 International Conference on Functional Programming (ICFP). Due to COVID-19 it will take place **virtually** this year. Like last year, we will be using a lightweight double-blind reviewing process. See further information below. Different from last year is that we offer a new submission category: the tutorial. Details can be found below. The Haskell Symposium presents original research on Haskell, discusses practical experience and future development of the language, and promotes other forms of declarative programming. Topics of interest include: * Language design, with a focus on possible extensions and modifications of Haskell as well as critical discussions of the status quo; * Theory, such as formal semantics of the present language or future extensions, type systems, effects, metatheory, and foundations for program analysis and transformation; * Implementations, including program analysis and transformation, static and dynamic compilation for sequential, parallel, and distributed architectures, memory management, as well as foreign function and component interfaces; * Libraries, that demonstrate new ideas or techniques for functional programming in Haskell; * Tools, such as profilers, tracers, debuggers, preprocessors, and testing tools; * Applications, to scientific and symbolic computing, databases, multimedia, telecommunication, the web, and so forth; * Functional Pearls, being elegant and instructive programming examples; * Experience Reports, to document general practice and experience in education, industry, or other contexts; * Tutorials, to document how to use a particular language feature, programming technique, tool or library within the Haskell ecosystem; * System Demonstrations, based on running software rather than novel research results. Regular papers should explain their research contributions in both general and technical terms, identifying what has been accomplished, explaining why it is significant, and relating it to previous work, and to other languages where appropriate. Experience reports and functional pearls need not necessarily report original academic research results. For example, they may instead report reusable programming idioms, elegant ways to approach a problem, or practical experience that will be useful to other users, implementers, or researchers. The key criterion for such a paper is that it makes a contribution from which other Haskellers can benefit. It is not enough simply to describe a standard solution to a standard programming problem, or report on experience where you used Haskell in the standard way and achieved the result you were expecting. A new submission category for this year's Haskell Symposium is the tutorial. Like with the experience report and the functional pearl, the key criterion for such a paper is that it makes a contribution from which other Haskellers can benefit. What distinguishes a tutorial is that its focus is on explaining an aspect of the Haskell language and/or ecosystem in a way that is generally useful to a Haskell audience. Tutorials for many such topics can be found online; the distinction here is that by writing it up for formal review it will be vetted by experts and formally published. System demonstrations should summarize the system capabilities that would be demonstrated. The proposals will be judged on whether the ensuing session is likely to be important and interesting to the Haskell community at large, whether on grounds academic or industrial, theoretical or practical, technical, social or artistic. Please contact the program chair with any questions about the relevance of a proposal. If your contribution is not a research paper, please mark the title of your experience report, functional pearl, tutorial or system demonstration as such, by supplying a subtitle (Experience Report, Functional Pearl, Tutorial Paper, System Demonstration). Submission Details ================== Early and Regular Track ----------------------- The Haskell Symposium uses a two-track submission process so that some papers can gain early feedback. Strong papers submitted to the early track are accepted outright, and the others will be given their reviews and invited to resubmit to the regular track. Papers accepted via the early and regular tracks are considered of equal value and will not be distinguished in the proceedings. Although all papers may be submitted to the early track, authors of functional pearls and experience reports are particularly encouraged to use this mechanism. The success of these papers depends heavily on the way they are presented, and submitting early will give the program committee a chance to provide feedback and help draw out the key ideas. Formatting ---------- Submitted papers should be in portable document format (PDF), formatted using the ACM SIGPLAN style guidelines. Authors should use the `acmart` format, with the `sigplan` sub-format for ACM proceedings. For details, see: http://www.sigplan.org/Resources/Author/#acmart-format It is recommended to use the `review` option when submitting a paper; this option enables line numbers for easy reference in reviews. Functional pearls, experience reports, tutorials and demo proposals should be labelled clearly as such. Lightweight Double-blind Reviewing ---------------------------------- Haskell Symposium 2021 will use a lightweight double-blind reviewing process. To facilitate this, submitted papers must adhere to two rules: 1. Author names and institutions must be omitted, and 2. References to authors' own related work should be in the third person (e.g., not "We build on our previous work" but rather "We build on the work of "). The purpose of this process is to help the reviewers come to an initial judgment about the paper without bias, not to make it impossible for them to discover the authors if they were to try. Nothing should be done in the name of anonymity that weakens the submission or makes the job of reviewing the paper more difficult (e.g., important background references should not be omitted or anonymized). In addition, authors should feel free to disseminate their ideas or draft versions of their paper as they normally would. For instance, authors may post drafts of their papers on the web or give talks on their research ideas. A reviewer will learn the identity of the author(s) of a paper after a review is submitted. Page Limits ----------- The length of submissions should not exceed the following limits: Regular paper: 12 pages Functional pearl: 12 pages Tutorial: 12 pages Experience report: 6 pages Demo proposal: 2 pages There is no requirement that all pages are used. For example, a functional pearl may be much shorter than 12 pages. In all cases, the list of references is not counted against these page limits. Deadlines --------- Early track: Submission deadline: 19 March 2021 (Fri) Notification: 23 April 2021 (Fri) Regular track and demos: Submission deadline: 21 May 2021 (Fri) Notification: 23 June 2021 (Wed) Deadlines are valid anywhere on Earth. Submission ---------- Submissions must adhere to SIGPLAN's republication policy (http://sigplan.org/Resources/Policies/Republication/), and authors should be aware of ACM's policies on plagiarism (https://www.acm.org/publications/policies/plagiarism). Program Committee members are allowed to submit papers, but their papers will be held to a higher standard. The paper submission deadline and length limitations are firm. There will be no extensions, and papers violating the length limitations will be summarily rejected. Papers should be submitted through HotCRP at: https://haskell21.hotcrp.com/ Improved versions of a paper may be submitted at any point before the submission deadline using the same web interface. Supplementary material: Authors have the option to attach supplementary material to a submission, on the understanding that reviewers may choose not to look at it. This supplementary material should not be submitted as part of the main document; instead, it should be uploaded as a separate PDF document or tarball. Supplementary material should be uploaded at submission time, not by providing a URL in the paper that points to an external repository. Authors can distinguish between anonymized and non-anonymized supplementary material. Anonymized supplementary material will be visible to reviewers immediately; non-anonymized supplementary material will be revealed to reviewers only after they have submitted their review of the paper and learned the identity of the author(s). Resubmitted Papers: authors who submit a revised version of a paper that has previously been rejected by another conference have the option to attach an annotated copy of the reviews of their previous submission(s), explaining how they have addressed these previous reviews in the present submission. If a reviewer identifies him/herself as a reviewer of this previous submission and wishes to see how his/her comments have been addressed, the conference chair will communicate to this reviewer the annotated copy of his/her previous review. Otherwise, no reviewer will read the annotated copies of the previous reviews. Proceedings =========== Accepted papers will be included in the ACM Digital Library. Their authors will be required to choose one of the following options: - Author retains copyright of the work and grants ACM a non-exclusive permission-to-publish license (and, optionally, licenses the work with a Creative Commons license); - Author retains copyright of the work and grants ACM an exclusive permission-to-publish license; - Author transfers copyright of the work to ACM. For more information, please see ACM Copyright Policy (http://www.acm.org/publications/policies/copyright-policy) and ACM Author Rights (http://authors.acm.org/main.html). Accepted proposals for system demonstrations will be posted on the symposium website but not formally published in the proceedings. Publication date: The official publication date of accepted papers is the date the proceedings are made available in the ACM Digital Library. This date may be up to two weeks prior to the first day of the conference. The official publication date affects the deadline for any patent filings related to published work. Artifacts ========= Authors of accepted papers are encouraged to make auxiliary material (artifacts like source code, test data, etc.) available with their paper. They can opt to have these artifacts published alongside their paper in the ACM Digital Library (copyright of artifacts remains with the authors). If an accepted paper's artifacts are made permanently available for retrieval in a publicly accessible archival repository like the ACM Digital Library, that paper qualifies for an Artifacts Available badge (https://www.acm.org/publications/policies/artifact-review-badging#available). Applications for such a badge can be made after paper acceptance and will be reviewed by the PC chair. Program Committee ================= Edwin Brady University of St Andrews Koen Claessen Chalmers University of Technology Dominique Devriese Vrije Universiteit Brussel Andy Gill University of Kansas Jurriaan Hage (chair) Universiteit Utrecht Zhenjiang Hu Peking University Ranjit Jhala University of California Patricia Johann Appalachian State University Yukiyoshi Kameyama University of Tsukuba George Karachalias Tweag Ralf Laemmel University of Koblenz-Landau Daan Leijen Microsoft Research Ben Lippmeier Ghost Locomotion Neil Mitchell Facebook Alberto Pardo Universidad de la Republica, Uruguay Matt Roberts Macquarie University Janis Voigtlaender University of Duisburg-Essen Nicolas Wu Imperial College London If you have questions, please contact the chair at: j.hage at uu.nl ================================================================================ From frank at dedden.net Mon Mar 8 19:23:44 2021 From: frank at dedden.net (Frank Dedden) Date: Mon, 8 Mar 2021 20:23:44 +0100 Subject: [Haskell-cafe] [ANN] Copilot 3.2.1 - hard realtime C runtime verification Message-ID: Dear all, We are very pleased to announce the release of Copilot 3.2.1, a stream-based DSL for writing and monitoring embedded C programs, with an emphasis on correctness and hard realtime requirements. Copilot is typically used as a high-level runtime verification framework, and supports temporal logic (LTL, PTLTL and MTL), clocks and voting algorithms. Among others, Copilot has been used at the Safety Critical Avionics Systems Branch of NASA Langley Research Center for monitoring test flights of drones. In collaboration with the development team at Galois, Inc., the new release introduces a backend to their What4 solver frontend. With this addition, it is now possible to prove properties of Copilot specifications using What4 [4]. We thank Galois for their help and their contribution. The second big focus of this release was the documentation: the public API documentation has been improved and completed. Additionally, several small improvements and fixes are made in the C99 code generator. The newest release is available on hackage [1]. For more information, including documentation, examples and links to the source code, please visit the webpage [2]. Current emphasis is on facilitating the use with other systems, and improving the codebase in terms of stability and test coverage. Users are encouraged to participate by opening issues and asking questions via our github repo [3]. Kind regards, The Copilot developers: - Frank Dedden - Alwyn Goodloe - Ivan Perez [1] http://hackage.haskell.org/package/copilot [2] https://copilot-language.github.io [3] https://github.com/Copilot-Language/copilot [4] https://github.com/GaloisInc/what4 From bruno.bernardo at tutanota.com Mon Mar 8 21:34:13 2021 From: bruno.bernardo at tutanota.com (Bruno Bernardo) Date: Mon, 8 Mar 2021 22:34:13 +0100 (CET) Subject: [Haskell-cafe] FMBC 2021 - 1st CFP Message-ID: [ Please distribute, apologies for multiple postings. ]========================================================================3rd International Workshop on Formal Methods for Blockchains (FMBC) 2021 - First Callhttps://fmbc.gitlab.io/2021July 18 or 19 (TBA), 2021Co-located with the 33nd International Conference on Computer-Aided Verification (CAV 2021)http://i-cav.org/2021/-------------------------------------------------------------IMPORTANT DATES--------------------------------Abstract submission: April 22, 2021Full paper submission: April 29, 2021Notification: June 10, 2021Camera-ready: July 8, 2021Workshop: July 18 or 19 (TBA), 2021Deadlines are Anywhere on Earth:https://en.wikipedia.org/wiki/Anywhere_on_Earth----------------------------------------------------------------TOPICS OF INTEREST--------------------------------Blockchains are decentralized transactional ledgers that rely oncryptographic hash functions for guaranteeing the integrity of thestored data. Participants on the network reach agreement on what validtransactions are through consensus algorithms.Blockchains may also provide support for Smart Contracts. SmartContracts are scripts of an ad-hoc programming language that arestored in the Blockchain and that run on the network. They caninteract with the ledger’s data and update its state. These scriptscan express the logic of possibly complex contracts between users ofthe Blockchain. Thus, Smart Contracts can facilitate the economicactivity of Blockchain participants.With the emergence and increasing popularity of cryptocurrencies suchas Bitcoin and Ethereum, it is now of utmost importance to have strongguarantees of the behavior of Blockchain software.These guarantees can be brought by using Formal Methods. Indeed,Blockchain software encompasses many topics of computer science whereusing Formal Methods techniques and tools are relevant: consensusalgorithms to ensure the liveness and the security of the data on thechain, programming languages specifically designed to write SmartContracts, cryptographic protocols, such as zero-knowledge proofs,used to ensure privacy, etc.This workshop is a forum to identify theoretical and practicalapproaches of formal methods for Blockchain technology. Topicsinclude, but are not limited to:* Formal models of Blockchain applications or concepts* Formal methods for consensus protocols* Formal methods for Blockchain-specific cryptographic primitives or protocols* Design and implementation of Smart Contract languages* Verification of Smart Contracts----------------------------------------------------------------SUBMISSION--------------------------------Submit original manuscripts (not published or considered elsewhere)with a page limit of 12 pages for full papers and 6 pages for shortpapers (excluding bibliography and short appendix of up to 5additional pages).Alternatively you may also submit an extended abstract of up to 3pages (including bibliography) summarizing your ongoing work in thearea of formal methods and blockchain. Authors of selectedextended-abstracts are invited to give a short lightning talk.Submission link: https://easychair.org/conferences/?conf=fmbc2021Authors are encouraged to use LaTeX and prepare their submissionsaccording to the instructions and styling guides for OASIcs providedby Dagstuhl.Instructions for authors: https://submission.dagstuhl.de/documentation/authors#oasicsAt least one author of an accepted paper is expected to present thepaper at the workshop as a registered participant.----------------------------------------------------------------PROCEEDINGS--------------------------------All submissions will be peer-reviewed by at least three members of theprogram committee for quality and relevance. Accepted regular papers(full and short papers) will be included in the workshop proceedings,published as a volume of the OpenAccess Series in Informatics (OASIcs)by Dagstuhl.----------------------------------------------------------------INVITED SPEAKER--------------------------------To be confirmed----------------------------------------------------------------PROGRAM COMMITTEE--------------------------------PC CO-CHAIRS* Bruno Bernardo (Nomadic Labs, France) (bruno at nomadic-labs.com)* Diego Marmsoler (University of Exeter, UK) (D.Marmsoler at exeter.ac.uk)PC MEMBERSTo be confirmed From bruno.bernardo at tutanota.com Mon Mar 8 22:07:43 2021 From: bruno.bernardo at tutanota.com (Bruno Bernardo) Date: Mon, 8 Mar 2021 23:07:43 +0100 (CET) Subject: [Haskell-cafe] FMBC 2021 - 1st CFP In-Reply-To: References: Message-ID: Apologies for the poor formatting of my previous message. You'll find below a hopefully more readable version.Sorry again for the noise. ==================================== [ Please distribute, apologies for multiple postings. ] ======================================================================== 3rd International Workshop on Formal Methods for Blockchains (FMBC) 2021 - First Call https://fmbc.gitlab.io/2021 July 18 or 19 (TBA), 2021 Co-located with the 33nd International Conference on Computer-Aided Verification (CAV 2021) http://i-cav.org/2021/ ------------------------------------------------------------- IMPORTANT DATES -------------------------------- Abstract submission: April 22, 2021 Full paper submission: April 29, 2021 Notification: June 10, 2021 Camera-ready: July 8, 2021 Workshop: July 18 or 19 (TBA), 2021 Deadlines are Anywhere on Earth: https://en.wikipedia.org/wiki/Anywhere_on_Earth -------------------------------- -------------------------------- TOPICS OF INTEREST -------------------------------- Blockchains are decentralized transactional ledgers that rely on cryptographic hash functions for guaranteeing the integrity of the stored data. Participants on the network reach agreement on what valid transactions are through consensus algorithms. Blockchains may also provide support for Smart Contracts. Smart Contracts are scripts of an ad-hoc programming language that are stored in the Blockchain and that run on the network. They can interact with the ledger’s data and update its state. These scripts can express the logic of possibly complex contracts between users of the Blockchain. Thus, Smart Contracts can facilitate the economic activity of Blockchain participants. With the emergence and increasing popularity of cryptocurrencies such as Bitcoin and Ethereum, it is now of utmost importance to have strong guarantees of the behavior of Blockchain software. These guarantees can be brought by using Formal Methods. Indeed, Blockchain software encompasses many topics of computer science where using Formal Methods techniques and tools are relevant: consensus algorithms to ensure the liveness and the security of the data on the chain, programming languages specifically designed to write Smart Contracts, cryptographic protocols, such as zero-knowledge proofs, used to ensure privacy, etc. This workshop is a forum to identify theoretical and practical approaches of formal methods for Blockchain technology. Topics include, but are not limited to: * Formal models of Blockchain applications or concepts * Formal methods for consensus protocols * Formal methods for Blockchain-specific cryptographic primitives or protocols * Design and implementation of Smart Contract languages * Verification of Smart Contracts -------------------------------- -------------------------------- SUBMISSION -------------------------------- Submit original manuscripts (not published or considered elsewhere) with a page limit of 12 pages for full papers and 6 pages for short papers (excluding bibliography and short appendix of up to 5 additional pages). Alternatively you may also submit an extended abstract of up to 3 pages (including bibliography) summarizing your ongoing work in the area of formal methods and blockchain. Authors of selected extended-abstracts are invited to give a short lightning talk. Submission link: https://easychair.org/conferences/?conf=fmbc2021 Authors are encouraged to use LaTeX and prepare their submissions according to the instructions and styling guides for OASIcs provided by Dagstuhl. Instructions for authors: https://submission.dagstuhl.de/documentation/authors#oasics At least one author of an accepted paper is expected to present the paper at the workshop as a registered participant. -------------------------------- -------------------------------- PROCEEDINGS -------------------------------- All submissions will be peer-reviewed by at least three members of the program committee for quality and relevance. Accepted regular papers (full and short papers) will be included in the workshop proceedings, published as a volume of the OpenAccess Series in Informatics (OASIcs) by Dagstuhl. -------------------------------- -------------------------------- INVITED SPEAKER -------------------------------- To be confirmed -------------------------------- -------------------------------- PROGRAM COMMITTEE -------------------------------- PC CO-CHAIRS * Bruno Bernardo (Nomadic Labs, France) (bruno at nomadic-labs.com) * Diego Marmsoler (University of Exeter, UK) (D.Marmsoler at exeter.ac.uk) PC MEMBERS To be confirmed From me at aidy.dev Tue Mar 9 00:51:34 2021 From: me at aidy.dev (Adriaan Leijnse) Date: Tue, 9 Mar 2021 01:51:34 +0100 (CET) Subject: [Haskell-cafe] Multitier Haskell? In-Reply-To: References: Message-ID: Dear Café, Are there any techniques for compiling a single client-server program such that clients are not distributed any server code? I'm currently looking at implementing an FRP library with a type system like Gavial's [0]. The types will make it clear on which side code belongs. My current thinking is to have Client and Server instances of a ClientServer type class which can safely implement the functions of the other side as no-ops/bottom, but I imagine that would at leastrequire a dead code elimination step after compilation to get the desired effect? Adriaan [0] https://arxiv.org/pdf/2002.06188.pdf -------------- next part -------------- An HTML attachment was scrubbed... URL: From simon at joyful.com Wed Mar 10 20:00:10 2021 From: simon at joyful.com (Simon Michael) Date: Wed, 10 Mar 2021 12:00:10 -0800 Subject: [Haskell-cafe] ANN: hledger-1.21 Message-ID: <2F51A50D-AA37-4003-9EB2-B04765C128C2@joyful.com> I'm very pleased to announce hledger 1.21 ! http://hledger.org/release-notes.html#hledger-1-21 describes the user-visible changes. Highlights include: - About 10% faster/more space-efficient, and much more in some cases - Jump to any topic in the manuals from the command line - More polish for valuation and balance reports, and a new value change report - Improvements to check, print and other commands. Thank you to the following release contributors this time around: Dmitry Astapov, Arnout Engelen, Damien Cassou, aragaer, Doug Goldstein, Caleb Maclennan, Felix Van der Jeugt, heavy first time contributor Vladimir Zhelezov, and especially Stephen Morgan. hledger (http://hledger.org) is a robust, cross-platform, plain text accounting tool, with command-line, terminal and web UIs. It is an actively maintained, largely compatible reimplementation of Ledger CLI with many improvements. You can use it to track money, time, investments, cryptocurrencies, inventory and more. See also the Plain Text Accounting site (http://plaintextaccounting.org). http://hledger.org/download shows all the ways to install hledger on mac, windows or unix (stack, cabal, brew, nix, CI binaries, your package manager..). Or, run this bash script to install or upgrade to the latest release: $ curl -sO https://raw.githubusercontent.com/simonmichael/hledger/master/hledger-install/hledger-install.sh $ less hledger-install.sh # security review $ bash hledger-install.sh New users, check out https://hledger.org/quickstart. To get help, see http://hledger.org#help-feedback, and join our chat channel via Freenode (#hledger, http://irc.hledger.org) or Matrix (#freenode_#hledger:matrix.org, http://matrix.hledger.org). Beginners and experts, contributors, sponsors, and all feedback are most welcome! Wishing you health and prosperity, -Simon From chikitosan at gmail.com Thu Mar 11 22:12:02 2021 From: chikitosan at gmail.com (Antonio) Date: Thu, 11 Mar 2021 23:12:02 +0100 Subject: [Haskell-cafe] Some questions about Fudgets library Message-ID: <20210311221202.GA3955@saruman> I wonder why there is no Fudgets package in Hackage. I found this, but the fudgets link is broken: http://hackage.haskell.org/user/ThomasHallgren Nevertheless, there is a cabalized package in the Fudgets homepage, so it's strange it's not in Hackage. Also, is there an arrowized version of Fudgets? If not, why? Is there some fundamental reason that makes it impossible to port it to the arrows framework or simply nobody cared to port it? (Also, the license seems to not allow modifications.) I'm trying to write a bittorrent client in Haskell. I decided to use arrows for it and took a look at Fudgets and Yampa. I haven't decided yet which one to use. Fudgets seems more suitable and I like it more, but the fact that it doesn't use the arrow notation and classes is a bit annoying. I read that Fruit is more or less a mix of Fudgets and Yampa that uses arrows. Sadly, it's unmaintained, the web doesn't exist and it's not in Hackage. Is there any other Fudgets-like option? Greetings. From ivanperezdominguez at gmail.com Thu Mar 11 22:20:57 2021 From: ivanperezdominguez at gmail.com (Ivan Perez) Date: Thu, 11 Mar 2021 17:20:57 -0500 Subject: [Haskell-cafe] Some questions about Fudgets library In-Reply-To: <20210311221202.GA3955@saruman> References: <20210311221202.GA3955@saruman> Message-ID: Hi Antonio, I've long envisioned a reimplementation of Fudgets using Monadic Stream Functions [1]. MSFs are like Yampa's SFs but with constrained side effects and without the mandatory continuous time (but you can put it back). I don't think there is a fundamental limitation other than finding the time to do it. Sometimes there's issues with implementing arr in these kinds of systems (because it lifts a pure function and so it creates a widget with uninitialized state), but it can be worked out. Ping me up if you want to talk about this. I was going to do something along these lines by the end of my PhD, so I thought a bit about how to do it. I also did some experiments for application debugging that used similar ideas. All the best, Ivan [1] https://github.com/ivanperez-keera/dunai/ On Thu, 11 Mar 2021 at 17:13, Antonio wrote: > I wonder why there is no Fudgets package in Hackage. > > I found this, but the fudgets link is broken: > > http://hackage.haskell.org/user/ThomasHallgren > > Nevertheless, there is a cabalized package in the Fudgets homepage, so > it's strange it's not in Hackage. > > Also, is there an arrowized version of Fudgets? If not, why? Is there some > fundamental reason that makes it impossible to port it to the arrows > framework or simply nobody cared to port it? (Also, the license seems to > not allow modifications.) > > I'm trying to write a bittorrent client in Haskell. I decided to use > arrows for it and took a look at Fudgets and Yampa. I haven't decided yet > which one to use. Fudgets seems more suitable and I like it more, but the > fact that it doesn't use the arrow notation and classes is a bit annoying. > > I read that Fruit is more or less a mix of Fudgets and Yampa that uses > arrows. Sadly, it's unmaintained, the web doesn't exist and it's not in > Hackage. Is there any other Fudgets-like option? > > Greetings. > _______________________________________________ > 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 chikitosan at gmail.com Thu Mar 11 22:29:50 2021 From: chikitosan at gmail.com (Antonio) Date: Thu, 11 Mar 2021 23:29:50 +0100 Subject: [Haskell-cafe] Some questions about Fudgets library In-Reply-To: References: <20210311221202.GA3955@saruman> Message-ID: <20210311222950.GA4057@saruman> Thanks! Will take a look at it. Greetings, Antonio El Thu, Mar 11, 2021 at 05:20:57PM -0500, Ivan Perez escribió: > Hi Antonio, > > I've long envisioned a reimplementation of Fudgets using Monadic Stream > Functions [1]. > > MSFs are like Yampa's SFs but with constrained side effects and without the > mandatory continuous time (but you can put it back). > > I don't think there is a fundamental limitation other than finding the time > to do it. Sometimes there's issues with implementing arr in these kinds of > systems (because it lifts a pure function and so it creates a widget with > uninitialized state), but it can be worked out. > Ping me up if you want to talk about this. I was going to do something > along these lines by the end of my PhD, so I thought a bit about how to do > it. I also did some experiments for application debugging that used similar > ideas. > > All the best, > > Ivan > > [1] https://github.com/ivanperez-keera/dunai/ > > On Thu, 11 Mar 2021 at 17:13, Antonio wrote: > > > I wonder why there is no Fudgets package in Hackage. > > > > I found this, but the fudgets link is broken: > > > > http://hackage.haskell.org/user/ThomasHallgren > > > > Nevertheless, there is a cabalized package in the Fudgets homepage, so > > it's strange it's not in Hackage. > > > > Also, is there an arrowized version of Fudgets? If not, why? Is there some > > fundamental reason that makes it impossible to port it to the arrows > > framework or simply nobody cared to port it? (Also, the license seems to > > not allow modifications.) > > > > I'm trying to write a bittorrent client in Haskell. I decided to use > > arrows for it and took a look at Fudgets and Yampa. I haven't decided yet > > which one to use. Fudgets seems more suitable and I like it more, but the > > fact that it doesn't use the arrow notation and classes is a bit annoying. > > > > I read that Fruit is more or less a mix of Fudgets and Yampa that uses > > arrows. Sadly, it's unmaintained, the web doesn't exist and it's not in > > Hackage. Is there any other Fudgets-like option? > > > > Greetings. > > _______________________________________________ > > 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 emilypi at cohomolo.gy Fri Mar 12 02:13:12 2021 From: emilypi at cohomolo.gy (Emily Pillmore) Date: Fri, 12 Mar 2021 02:13:12 +0000 Subject: [Haskell-cafe] Package Takeover: `toml` Message-ID: To whom it may concern, I'd like to take over maintenance of the package `toml`.  I have a burning need. I tried to contact Spiros  a year ago, but no response has come. The last release was 2017, and it's safe to say the package is totally abandoned.  My hackage user is topos. Cheers, E -------------- next part -------------- An HTML attachment was scrubbed... URL: From javran.c at gmail.com Fri Mar 12 02:31:30 2021 From: javran.c at gmail.com (Javran Cheng) Date: Thu, 11 Mar 2021 18:31:30 -0800 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: Message-ID: Hi Emily, Just in case you are a stack user, you can create a fork (or just modify it locally), and specify your modified version in extra-deps of package.yaml - see examples in the doc, "location: " can also be specified if the package is only locally modified. Cheers, Javran On Thu, Mar 11, 2021 at 6:14 PM Emily Pillmore wrote: > To whom it may concern, > > I'd like to take over maintenance of the package `toml`. I have a burning > need. I tried to contact Spiros a year ago, but no response has come. The > last release was 2017, and it's safe to say the package is totally > abandoned. My hackage user is topos. > > Cheers, > E > > _______________________________________________ > 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. -- Javran (Fang) Cheng -------------- next part -------------- An HTML attachment was scrubbed... URL: From amindfv at mailbox.org Fri Mar 12 03:04:16 2021 From: amindfv at mailbox.org (amindfv at mailbox.org) Date: Thu, 11 Mar 2021 20:04:16 -0700 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: Message-ID: <20210312030416.GA29223@painter.painter> On Fri, Mar 12, 2021 at 02:13:12AM +0000, Emily Pillmore wrote: > To whom it may concern, > > I'd like to take over maintenance of the package `toml`.  I have a burning need. I tried to contact Spiros  a year ago, but no response has come. The last release was 2017, and it's safe to say the package is totally abandoned.  My hackage user is topos. Hi, I'm a maintainer of `toml`. What do you need? Tom From carter.schonwald at gmail.com Fri Mar 12 03:36:27 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 11 Mar 2021 22:36:27 -0500 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: <20210312030416.GA29223@painter.painter> References: <20210312030416.GA29223@painter.painter> Message-ID: If you’re the maintainer of https://hackage.haskell.org/package/toml could you give emily maintainer / upload perms ? It really needs a new lead :) 2014 is a long time ago (I co wrote the email to spiros way back when. Any progress on this would be great) On Thu, Mar 11, 2021 at 10:05 PM amindfv--- via Haskell-Cafe < haskell-cafe at haskell.org> wrote: > On Fri, Mar 12, 2021 at 02:13:12AM +0000, Emily Pillmore wrote: > > To whom it may concern, > > > > I'd like to take over maintenance of the package `toml`. I have a > burning need. I tried to contact Spiros a year ago, but no response has > come. The last release was 2017, and it's safe to say the package is > totally abandoned. My hackage user is topos. > > Hi, I'm a maintainer of `toml`. What do you need? > > Tom > > _______________________________________________ > 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 amindfv at mailbox.org Fri Mar 12 04:15:28 2021 From: amindfv at mailbox.org (amindfv at mailbox.org) Date: Thu, 11 Mar 2021 21:15:28 -0700 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312030416.GA29223@painter.painter> Message-ID: <20210312041528.GA32250@painter.painter> I'm in the middle of a package overhaul. If there's a burning need for fixes please get in touch (off-list?) and let me know what you need. Thanks, Tom On Thu, Mar 11, 2021 at 10:36:27PM -0500, Carter Schonwald wrote: > If you’re the maintainer of > https://hackage.haskell.org/package/toml could you give emily maintainer / > upload perms ? It really needs a new lead :) 2014 is a long time ago > > (I co wrote the email to spiros way back when. Any progress on this would > be great) > > On Thu, Mar 11, 2021 at 10:05 PM amindfv--- via Haskell-Cafe < > haskell-cafe at haskell.org> wrote: > > > On Fri, Mar 12, 2021 at 02:13:12AM +0000, Emily Pillmore wrote: > > > To whom it may concern, > > > > > > I'd like to take over maintenance of the package `toml`. I have a > > burning need. I tried to contact Spiros a year ago, but no response has > > come. The last release was 2017, and it's safe to say the package is > > totally abandoned. My hackage user is topos. > > > > Hi, I'm a maintainer of `toml`. What do you need? > > > > Tom > > > > _______________________________________________ > > 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 carter.schonwald at gmail.com Fri Mar 12 04:43:14 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 11 Mar 2021 23:43:14 -0500 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: <20210312041528.GA32250@painter.painter> References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> Message-ID: Are you talking about tomland ?? There’s no GitHub url on the toml package from 2014 ... I think the main priority here is having a canonically good toml lib for the community, in a good name space, That meets our needs robustly (I think emily has some interesting AND WORTHY uses in mind). Can you share the dev repo? To be clear: this is in the context hackage is a public commons and its name space is a resource. Do you have any immediate plans/needs for that specific package name? If not, we promise to give some excellent code a great home in the toml name space if you hand it over. Everyone will be happy and joyous at the resulting work that emily will facilitate. And dogs will dance in the streets and children will smile. If you still have any residual concerns, emily and I are happy to hop on a video chat to solve worries therof. Cheers! -Carter On Thu, Mar 11, 2021 at 11:15 PM amindfv at mailbox.org wrote: > I'm in the middle of a package overhaul. If there's a burning need for > fixes please get in touch (off-list?) and let me know what you need. > > Thanks, > Tom > > On Thu, Mar 11, 2021 at 10:36:27PM -0500, Carter Schonwald wrote: > > If you’re the maintainer of > > https://hackage.haskell.org/package/toml could you give emily > maintainer / > > upload perms ? It really needs a new lead :) 2014 is a long time ago > > > > (I co wrote the email to spiros way back when. Any progress on this would > > be great) > > > > On Thu, Mar 11, 2021 at 10:05 PM amindfv--- via Haskell-Cafe < > > haskell-cafe at haskell.org> wrote: > > > > > On Fri, Mar 12, 2021 at 02:13:12AM +0000, Emily Pillmore wrote: > > > > To whom it may concern, > > > > > > > > I'd like to take over maintenance of the package `toml`. I have a > > > burning need. I tried to contact Spiros a year ago, but no response > has > > > come. The last release was 2017, and it's safe to say the package is > > > totally abandoned. My hackage user is topos. > > > > > > Hi, I'm a maintainer of `toml`. What do you need? > > > > > > Tom > > > > > > _______________________________________________ > > > 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 amindfv at mailbox.org Fri Mar 12 05:09:51 2021 From: amindfv at mailbox.org (amindfv at mailbox.org) Date: Thu, 11 Mar 2021 22:09:51 -0700 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> Message-ID: <20210312050951.GA2730@painter.painter> On Thu, Mar 11, 2021 at 11:43:14PM -0500, Carter Schonwald wrote: > Are you talking about tomland ?? > No, I'm talking about https://hackage.haskell.org/package/toml . > There’s no GitHub url on the toml package from 2014 ... > > I think the main priority here is having a canonically good toml lib for > the community, in a good name space, That meets our needs robustly (I think > emily has some interesting AND WORTHY uses in mind). > > Can you share the dev repo? > > To be clear: this is in the context hackage is a public commons and its > name space is a resource. Do you have any immediate plans/needs for that > specific package name? > > If not, we promise to give some excellent code a great home in the toml > name space if you hand it over. Everyone will be happy and joyous at the > resulting work that emily will facilitate. And dogs will dance in the > streets and children will smile. Respectfully, this conversation started because of the claim "I have a burning need." I actually cancelled a plan I had tonight because I wanted to be sure I could be responsive if there was some system going down because of e.g. an outdated set of dependencies. Now the discussion is about how "toml" is a nice name and there are interesting ideas for as-yet unwritten code. If there really is a burning need, I'm still around. Otherwise I'm feeling a bit duped. Tom > > If you still have any residual concerns, emily and I are happy to hop on a > video chat to solve worries therof. > > Cheers! > > -Carter > > > On Thu, Mar 11, 2021 at 11:15 PM amindfv at mailbox.org > wrote: > > > I'm in the middle of a package overhaul. If there's a burning need for > > fixes please get in touch (off-list?) and let me know what you need. > > > > Thanks, > > Tom > > > > On Thu, Mar 11, 2021 at 10:36:27PM -0500, Carter Schonwald wrote: > > > If you’re the maintainer of > > > https://hackage.haskell.org/package/toml could you give emily > > maintainer / > > > upload perms ? It really needs a new lead :) 2014 is a long time ago > > > > > > (I co wrote the email to spiros way back when. Any progress on this would > > > be great) > > > > > > On Thu, Mar 11, 2021 at 10:05 PM amindfv--- via Haskell-Cafe < > > > haskell-cafe at haskell.org> wrote: > > > > > > > On Fri, Mar 12, 2021 at 02:13:12AM +0000, Emily Pillmore wrote: > > > > > To whom it may concern, > > > > > > > > > > I'd like to take over maintenance of the package `toml`. I have a > > > > burning need. I tried to contact Spiros a year ago, but no response > > has > > > > come. The last release was 2017, and it's safe to say the package is > > > > totally abandoned. My hackage user is topos. > > > > > > > > Hi, I'm a maintainer of `toml`. What do you need? > > > > > > > > Tom > > > > > > > > _______________________________________________ > > > > 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 emilypi at cohomolo.gy Fri Mar 12 05:27:57 2021 From: emilypi at cohomolo.gy (Emily Pillmore) Date: Fri, 12 Mar 2021 05:27:57 +0000 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: <20210312050951.GA2730@painter.painter> References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> Message-ID: Tom, I have been eyeing a remake of this package for a long time for some of my projects. To be clear: there is no fire that needs to be put out, but I do have a need. The package has been out of commission for 7 years, and there are certainly no relevant downstream dependencies at this point. Do you have a source repository or existing code that I could see or make use of in the interim period between now and a release? I'm genuinely surprised there was someone else made maintainer of the package without a public takeover. When/how did this happen? Did I miss the takeover announcement? Carter and I were looking into this in February of last year, and the need arose again, so I brought it up today. Thanks, E On Fri, Mar 12, 2021 at 12:09 AM, < amindfv at mailbox.org > wrote: > > > > On Thu, Mar 11, 2021 at 11:43:14PM -0500, Carter Schonwald wrote: > > >> >> >> Are you talking about tomland ?? >> >> > > > > No, I'm talking about https:/ / hackage. haskell. org/ package/ toml ( > https://hackage.haskell.org/package/toml ). > > >> >> >> There’s no GitHub url on the toml package from 2014 ... >> >> >> >> I think the main priority here is having a canonically good toml lib for >> the community, in a good name space, That meets our needs robustly (I >> think emily has some interesting AND WORTHY uses in mind). >> >> >> >> Can you share the dev repo? >> >> >> >> To be clear: this is in the context hackage is a public commons and its >> name space is a resource. Do you have any immediate plans/needs for that >> specific package name? >> >> >> >> If not, we promise to give some excellent code a great home in the toml >> name space if you hand it over. Everyone will be happy and joyous at the >> resulting work that emily will facilitate. And dogs will dance in the >> streets and children will smile. >> >> > > > > Respectfully, this conversation started because of the claim "I have a > burning need." I actually cancelled a plan I had tonight because I wanted > to be sure I could be responsive if there was some system going down > because of e.g. an outdated set of dependencies. Now the discussion is > about how "toml" is a nice name and there are interesting ideas for as-yet > unwritten code. > > > > If there really is a burning need, I'm still around. Otherwise I'm feeling > a bit duped. > > > > Tom > > >> >> >> If you still have any residual concerns, emily and I are happy to hop on a >> video chat to solve worries therof. >> >> >> >> Cheers! >> >> >> >> -Carter >> >> >> >> On Thu, Mar 11 , 2021 at 11:15 PM amindfv@ mailbox. org ( >> amindfv at mailbox.org ) < amindfv@ mailbox. org ( amindfv at mailbox.org ) > >> wrote: >> >> >>> >>> >>> I'm in the middle of a package overhaul. If there's a burning need for >>> fixes please get in touch (off-list?) and let me know what you need. >>> >>> >>> >>> Thanks, >>> Tom >>> >>> >>> >>> On Thu, Mar 11, 2021 at 10:36:27PM -0500, Carter Schonwald wrote: >>> >>> >>>> >>>> >>>> If you’re the maintainer of >>>> https:/ / hackage. haskell. org/ package/ toml ( >>>> https://hackage.haskell.org/package/toml ) could you give emily >>>> >>>> >>> >>> >>> >>> maintainer / >>> >>> >>>> >>>> >>>> upload perms ? It really needs a new lead :) 2014 is a long time ago >>>> >>>> >>>> >>>> (I co wrote the email to spiros way back when. Any progress on this would >>>> be great) >>>> >>>> >>>> >>>> On Thu, Mar 11 , 2021 at 10:05 PM amindfv--- via Haskell-Cafe < haskell-cafe@ >>>> haskell. org ( haskell-cafe at haskell.org ) > wrote: >>>> >>>> >>>>> >>>>> >>>>> On Fri, Mar 12, 2021 at 02:13:12AM +0000, Emily Pillmore wrote: >>>>> >>>>> >>>>>> >>>>>> >>>>>> To whom it may concern, >>>>>> >>>>>> >>>>>> >>>>>> I'd like to take over maintenance of the package `toml`. I have a >>>>>> >>>>>> >>>>> >>>>> >>>>> >>>>> burning need. I tried to contact Spiros a year ago, but no response >>>>> >>>>> >>>> >>>> >>> >>> >>> >>> has >>> >>> >>>> >>>>> >>>>> >>>>> come. The last release was 2017, and it's safe to say the package is >>>>> totally abandoned. My hackage user is topos. >>>>> >>>>> >>>>> >>>>> Hi, I'm a maintainer of `toml`. What do you need? >>>>> >>>>> >>>>> >>>>> Tom >>>>> >>>>> >>>>> >>>>> _______________________________________________ >>>>> Haskell-Cafe mailing list >>>>> To (un)subscribe, modify options or view archives go to: http:/ / mail. haskell. >>>>> org/ cgi-bin/ mailman/ listinfo/ haskell-cafe ( >>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe ) Only >>>>> members subscribed via the mailman list are allowed to post. >>>>> >>>>> >>>> >>>> >>> >>> >> >> > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From amindfv at mailbox.org Fri Mar 12 05:56:06 2021 From: amindfv at mailbox.org (amindfv at mailbox.org) Date: Thu, 11 Mar 2021 22:56:06 -0700 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> Message-ID: <20210312055606.GA6517@painter.painter> On Fri, Mar 12, 2021 at 05:27:57AM +0000, Emily Pillmore wrote: > Tom, > > I have been eyeing a remake of this package for a long time for some of my projects. To be clear: there is no fire that needs to be put out, but I do have a need. The package has been out of commission for 7 years, and there are certainly no relevant downstream dependencies at this point. Do you have a source repository or existing code that I could see or make use of in the interim period between now and a release? Again, trying to be respectful here, but "burning" kinda does imply "fire," and "need" certainly does imply "need." It's now seeming more just like a desire for the package name. If you're looking for a modern TOML parser asap, I'd recommend one of these popular ones: https://hackage.haskell.org/package/htoml https://hackage.haskell.org/package/tomland https://hackage.haskell.org/package/toml-parser The last one is probably most similar to the `toml` package. It's great. `htoml` was also based on `toml`. If none of these fits the bill, there are more on Hackage. Tom > > I'm genuinely surprised there was someone else made maintainer of the package without a public takeover. When/how did this happen? Did I miss the takeover announcement? Carter and I were looking into this in February of last year, and the need arose again, so I brought it up today. > > Thanks, > > E > > On Fri, Mar 12, 2021 at 12:09 AM, < amindfv at mailbox.org > wrote: > > > > > > > > > On Thu, Mar 11, 2021 at 11:43:14PM -0500, Carter Schonwald wrote: > > > > > >> > >> > >> Are you talking about tomland ?? > >> > >> > > > > > > > > No, I'm talking about https:/ / hackage. haskell. org/ package/ toml ( > > https://hackage.haskell.org/package/toml ). > > > > > >> > >> > >> There’s no GitHub url on the toml package from 2014 ... > >> > >> > >> > >> I think the main priority here is having a canonically good toml lib for > >> the community, in a good name space, That meets our needs robustly (I > >> think emily has some interesting AND WORTHY uses in mind). > >> > >> > >> > >> Can you share the dev repo? > >> > >> > >> > >> To be clear: this is in the context hackage is a public commons and its > >> name space is a resource. Do you have any immediate plans/needs for that > >> specific package name? > >> > >> > >> > >> If not, we promise to give some excellent code a great home in the toml > >> name space if you hand it over. Everyone will be happy and joyous at the > >> resulting work that emily will facilitate. And dogs will dance in the > >> streets and children will smile. > >> > >> > > > > > > > > Respectfully, this conversation started because of the claim "I have a > > burning need." I actually cancelled a plan I had tonight because I wanted > > to be sure I could be responsive if there was some system going down > > because of e.g. an outdated set of dependencies. Now the discussion is > > about how "toml" is a nice name and there are interesting ideas for as-yet > > unwritten code. > > > > > > > > If there really is a burning need, I'm still around. Otherwise I'm feeling > > a bit duped. > > > > > > > > Tom > > > > > >> > >> > >> If you still have any residual concerns, emily and I are happy to hop on a > >> video chat to solve worries therof. > >> > >> > >> > >> Cheers! > >> > >> > >> > >> -Carter > >> > >> > >> > >> On Thu, Mar 11 , 2021 at 11:15 PM amindfv@ mailbox. org ( > >> amindfv at mailbox.org ) < amindfv@ mailbox. org ( amindfv at mailbox.org ) > > >> wrote: > >> > >> > >>> > >>> > >>> I'm in the middle of a package overhaul. If there's a burning need for > >>> fixes please get in touch (off-list?) and let me know what you need. > >>> > >>> > >>> > >>> Thanks, > >>> Tom > >>> > >>> > >>> > >>> On Thu, Mar 11, 2021 at 10:36:27PM -0500, Carter Schonwald wrote: > >>> > >>> > >>>> > >>>> > >>>> If you’re the maintainer of > >>>> https:/ / hackage. haskell. org/ package/ toml ( > >>>> https://hackage.haskell.org/package/toml ) could you give emily > >>>> > >>>> > >>> > >>> > >>> > >>> maintainer / > >>> > >>> > >>>> > >>>> > >>>> upload perms ? It really needs a new lead :) 2014 is a long time ago > >>>> > >>>> > >>>> > >>>> (I co wrote the email to spiros way back when. Any progress on this would > >>>> be great) > >>>> > >>>> > >>>> > >>>> On Thu, Mar 11 , 2021 at 10:05 PM amindfv--- via Haskell-Cafe < haskell-cafe@ > >>>> haskell. org ( haskell-cafe at haskell.org ) > wrote: > >>>> > >>>> > >>>>> > >>>>> > >>>>> On Fri, Mar 12, 2021 at 02:13:12AM +0000, Emily Pillmore wrote: > >>>>> > >>>>> > >>>>>> > >>>>>> > >>>>>> To whom it may concern, > >>>>>> > >>>>>> > >>>>>> > >>>>>> I'd like to take over maintenance of the package `toml`. I have a > >>>>>> > >>>>>> > >>>>> > >>>>> > >>>>> > >>>>> burning need. I tried to contact Spiros a year ago, but no response > >>>>> > >>>>> > >>>> > >>>> > >>> > >>> > >>> > >>> has > >>> > >>> > >>>> > >>>>> > >>>>> > >>>>> come. The last release was 2017, and it's safe to say the package is > >>>>> totally abandoned. My hackage user is topos. > >>>>> > >>>>> > >>>>> > >>>>> Hi, I'm a maintainer of `toml`. What do you need? > >>>>> > >>>>> > >>>>> > >>>>> Tom > >>>>> > >>>>> > >>>>> > >>>>> _______________________________________________ > >>>>> Haskell-Cafe mailing list > >>>>> To (un)subscribe, modify options or view archives go to: http:/ / mail. haskell. > >>>>> org/ cgi-bin/ mailman/ listinfo/ haskell-cafe ( > >>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe ) Only > >>>>> members subscribed via the mailman list are allowed to post. > >>>>> > >>>>> > >>>> > >>>> > >>> > >>> > >> > >> > > > > > > From emilypi at cohomolo.gy Fri Mar 12 06:28:44 2021 From: emilypi at cohomolo.gy (Emily Pillmore) Date: Fri, 12 Mar 2021 06:28:44 +0000 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: <20210312055606.GA6517@painter.painter> References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> Message-ID: Tom, Look, I don't want to debate syntax and semantics here, but "burning need/desire/ambition" etc ( https://idioms.thefreedictionary.com/burning+desire ) is an extremely common colloquialism that doesn't imply an emergency, just a strongly felt urge.  I can't apologize for my wording, but I'm sorry for the situation nonetheless. > > It's now seeming more just like a desire for the package name. > > I'm going to look at `toml-parser` in the meantime, but no toml library does what I have in mind (namely a full fledged implementation of the spec, streaming, deriving etc.), nor do many of them provide bidirectional serialization save `tomland`. To reiterate Carter's point, hackage names are a community resource, and they deserve to be thought through carefully, so yes, the package name is part of the request. I do alot of community service to make sure things that take up precious Hackage real-estate are treated well, which is why `toml` posed an opportunity. To that point, anything you put out is something I am interested in investing time and effort into making a standard. Do you have any code currently, or is this a TODO on your list? Going through your hackage libraries, I see no source repository listings, issue trackers, or even an email to reach you by. - E On Fri, Mar 12, 2021 at 12:56 AM, < amindfv at mailbox.org > wrote: > > > > On Fri, Mar 12, 2021 at 05:27:57AM +0000, Emily Pillmore wrote: > > >> >> >> Tom, >> >> >> >> I have been eyeing a remake of this package for a long time for some of my >> projects. To be clear: there is no fire that needs to be put out, but I do >> have a need. The package has been out of commission for 7 years, and there >> are certainly no relevant downstream dependencies at this point. Do you >> have a source repository or existing code that I could see or make use of >> in the interim period between now and a release? >> >> > > > > Again, trying to be respectful here, but "burning" kinda does imply > "fire," and "need" certainly does imply "need." It's now seeming more just > like a desire for the package name. > > > > If you're looking for a modern TOML parser asap, I'd recommend one of > these popular ones: > > > > https:/ / hackage. haskell. org/ package/ htoml ( > https://hackage.haskell.org/package/htoml ) > https:/ / hackage. haskell. org/ package/ tomland ( > https://hackage.haskell.org/package/tomland ) > https:/ / hackage. haskell. org/ package/ toml-parser ( > https://hackage.haskell.org/package/toml-parser ) > > > > The last one is probably most similar to the `toml` package. It's great. > `htoml` was also based on `toml`. > > > > If none of these fits the bill, there are more on Hackage. > > > > Tom > > >> >> >> I'm genuinely surprised there was someone else made maintainer of the >> package without a public takeover. When/how did this happen? Did I miss >> the takeover announcement? Carter and I were looking into this in February >> of last year, and the need arose again, so I brought it up today. >> >> >> >> Thanks, >> >> >> >> E >> >> >> >> On Fri, Mar 12, 2021 at 12:09 AM, < amindfv@ mailbox. org ( >> amindfv at mailbox.org ) > wrote: >> >> >>> >>> >>> On Thu, Mar 11, 2021 at 11:43:14PM -0500, Carter Schonwald wrote: >>> >>> >>>> >>>> >>>> Are you talking about tomland ?? >>>> >>>> >>> >>> >>> >>> No, I'm talking about https:/ / hackage. haskell. org/ package/ toml ( https:/ >>> / hackage. haskell. org/ package/ toml ( >>> https://hackage.haskell.org/package/toml ) ). >>> >>> >>>> >>>> >>>> There’s no GitHub url on the toml package from 2014 ... >>>> >>>> >>>> >>>> I think the main priority here is having a canonically good toml lib for >>>> the community, in a good name space, That meets our needs robustly (I >>>> think emily has some interesting AND WORTHY uses in mind). >>>> >>>> >>>> >>>> Can you share the dev repo? >>>> >>>> >>>> >>>> To be clear: this is in the context hackage is a public commons and its >>>> name space is a resource. Do you have any immediate plans/needs for that >>>> specific package name? >>>> >>>> >>>> >>>> If not, we promise to give some excellent code a great home in the toml >>>> name space if you hand it over. Everyone will be happy and joyous at the >>>> resulting work that emily will facilitate. And dogs will dance in the >>>> streets and children will smile. >>>> >>>> >>> >>> >>> >>> Respectfully, this conversation started because of the claim "I have a >>> burning need." I actually cancelled a plan I had tonight because I wanted >>> to be sure I could be responsive if there was some system going down >>> because of e.g. an outdated set of dependencies. Now the discussion is >>> about how "toml" is a nice name and there are interesting ideas for as-yet >>> unwritten code. >>> >>> >>> >>> If there really is a burning need, I'm still around. Otherwise I'm feeling >>> a bit duped. >>> >>> >>> >>> Tom >>> >>> >>>> >>>> >>>> If you still have any residual concerns, emily and I are happy to hop on a >>>> video chat to solve worries therof. >>>> >>>> >>>> >>>> Cheers! >>>> >>>> >>>> >>>> -Carter >>>> >>>> >>>> >>>> On Thu, Mar 11 , 2021 at 11:15 PM amindfv@ mailbox. org ( amindfv@ mailbox. >>>> org ( amindfv at mailbox.org ) ) < amindfv@ mailbox. org ( amindfv@ mailbox. org >>>> ( amindfv at mailbox.org ) ) > wrote: >>>> >>>> >>>>> >>>>> >>>>> I'm in the middle of a package overhaul. If there's a burning need for >>>>> fixes please get in touch (off-list?) and let me know what you need. >>>>> >>>>> >>>>> >>>>> Thanks, >>>>> Tom >>>>> >>>>> >>>>> >>>>> On Thu, Mar 11, 2021 at 10:36:27PM -0500, Carter Schonwald wrote: >>>>> >>>>> >>>>>> >>>>>> >>>>>> If you’re the maintainer of >>>>>> https:/ / hackage. haskell. org/ package/ toml ( >>>>>> https:/ / hackage. haskell. org/ package/ toml ( >>>>>> https://hackage.haskell.org/package/toml ) ) could you give emily >>>>>> >>>>>> >>>>> >>>>> >>>>> >>>>> maintainer / >>>>> >>>>> >>>>>> >>>>>> >>>>>> upload perms ? It really needs a new lead :) 2014 is a long time ago >>>>>> >>>>>> >>>>>> >>>>>> (I co wrote the email to spiros way back when. Any progress on this would >>>>>> be great) >>>>>> >>>>>> >>>>>> >>>>>> On Thu, Mar 11 , 2021 at 10:05 PM amindfv--- via Haskell-Cafe < >>>>>> haskell-cafe@ haskell. org ( haskell-cafe@ haskell. org ( >>>>>> haskell-cafe at haskell.org ) ) > wrote: >>>>>> >>>>>> >>>>>>> >>>>>>> >>>>>>> On Fri, Mar 12, 2021 at 02:13:12AM +0000, Emily Pillmore wrote: >>>>>>> >>>>>>> >>>>>>>> >>>>>>>> >>>>>>>> To whom it may concern, >>>>>>>> >>>>>>>> >>>>>>>> >>>>>>>> I'd like to take over maintenance of the package `toml`. I have a >>>>>>>> >>>>>>>> >>>>>>> >>>>>>> >>>>>>> >>>>>>> burning need. I tried to contact Spiros a year ago, but no response >>>>>>> >>>>>>> >>>>>> >>>>>> >>>>> >>>>> >>>>> >>>>> has >>>>> >>>>> >>>>>> >>>>>>> >>>>>>> >>>>>>> come. The last release was 2017, and it's safe to say the package is >>>>>>> totally abandoned. My hackage user is topos. >>>>>>> >>>>>>> >>>>>>> >>>>>>> Hi, I'm a maintainer of `toml`. What do you need? >>>>>>> >>>>>>> >>>>>>> >>>>>>> Tom >>>>>>> >>>>>>> >>>>>>> >>>>>>> _______________________________________________ >>>>>>> Haskell-Cafe mailing list >>>>>>> To (un)subscribe, modify options or view archives go to: http:/ / mail. >>>>>>> haskell. org/ cgi-bin/ mailman/ listinfo/ haskell-cafe ( >>>>>>> http:/ / mail. haskell. org/ cgi-bin/ mailman/ listinfo/ haskell-cafe ( >>>>>>> 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 amindfv at mailbox.org Fri Mar 12 07:01:30 2021 From: amindfv at mailbox.org (amindfv at mailbox.org) Date: Fri, 12 Mar 2021 00:01:30 -0700 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> Message-ID: <20210312070130.GA9783@painter.painter> On Fri, Mar 12, 2021 at 06:28:44AM +0000, Emily Pillmore wrote: > Tom, > > Look, I don't want to debate syntax and semantics here, but "burning need/desire/ambition" etc ( https://idioms.thefreedictionary.com/burning+desire ) is an extremely common colloquialism that doesn't imply an emergency, just a strongly felt urge.  I can't apologize for my wording, but I'm sorry for the situation nonetheless. I also don't want to debate semantics but I can tell you "I have a burning need" on a Hackage takeover has a different connotation of urgency than "I have a burning desire to write a toml parsing library and to have it be named 'toml'". I still feel duped and now condescended to as well. I do nonetheless appreciate your apology for the situation. > > > > It's now seeming more just like a desire for the package name. > > > > > > I'm going to look at `toml-parser` in the meantime, but no toml library does what I have in mind (namely a full fledged implementation of the spec, streaming, deriving etc.), nor do many of them provide bidirectional serialization save `tomland`. To reiterate Carter's point, hackage names are a community resource, and they deserve to be thought through carefully, so yes, the package name is part of the request. I do alot of community service to make sure things that take up precious Hackage real-estate are treated well, which is why `toml` posed an opportunity. I'm actually open to the idea of using a simple name like "toml" for a best-in-class Haskell library, but I'd want to see proof that it is clearly the best in terms of implementation and adoption. I of course think my plans for toml parsing are the most wonderful, but if a consensus favorite package emerges and it's not mine I will step aside. > > To that point, anything you put out is something I am interested in investing time and effort into making a standard. Do you have any code currently, or is this a TODO on your list? Going through your hackage libraries, I see no source repository listings, issue trackers, or even an email to reach you by. I do have code, yes. As mentioned earlier I'm in the middle of a rewrite. If there's more to discuss maybe we should move this conversation off-list as it's no longer about a package takeover? Tom From hallgren at chalmers.se Fri Mar 12 11:28:07 2021 From: hallgren at chalmers.se (Thomas Hallgren) Date: Fri, 12 Mar 2021 12:28:07 +0100 Subject: [Haskell-cafe] Some questions about Fudgets library In-Reply-To: <20210311221202.GA3955@saruman> References: <20210311221202.GA3955@saruman> Message-ID: Hi Antonio, I have contemplated publishing Fudgets on Hackage, and the reason for the broken link is that I uploaded a package candidate [1]. But Fudgets has remained essentially the same since the mid 90s, and while it still works and is available from the Fudgets home page [2], its age shows in many ways, and that's why I hesitate to publish it on Hackage... Best regards, Thomas H [1] https://hackage.haskell.org/package/fudgets-0.18.2/candidate [2] https://www.altocumulus.org/Fudgets/ On 2021-03-11 23:12, Antonio wrote: > I wonder why there is no Fudgets package in Hackage. > > I found this, but the fudgets link is broken: > > http://hackage.haskell.org/user/ThomasHallgren > > Nevertheless, there is a cabalized package in the Fudgets homepage, so it's strange it's not in Hackage. > > Also, is there an arrowized version of Fudgets? If not, why? Is there some fundamental reason that makes it impossible to port it to the arrows framework or simply nobody cared to port it? (Also, the license seems to not allow modifications.) > > I'm trying to write a bittorrent client in Haskell. I decided to use arrows for it and took a look at Fudgets and Yampa. I haven't decided yet which one to use. Fudgets seems more suitable and I like it more, but the fact that it doesn't use the arrow notation and classes is a bit annoying. > > I read that Fruit is more or less a mix of Fudgets and Yampa that uses arrows. Sadly, it's unmaintained, the web doesn't exist and it's not in Hackage. Is there any other Fudgets-like option? > > Greetings. > _______________________________________________ > 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 lemming at henning-thielemann.de Fri Mar 12 11:36:16 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Fri, 12 Mar 2021 12:36:16 +0100 (CET) Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: <20210312055606.GA6517@painter.painter> References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> Message-ID: <46ca1e58-8d6b-eba0-c330-ca7cfde63cbd@henning-thielemann.de> On Thu, 11 Mar 2021, amindfv--- via Haskell-Cafe wrote: > Again, trying to be respectful here, but "burning" kinda does imply > "fire," and "need" certainly does imply "need." It's now seeming more > just like a desire for the package name. I have nothing to do with 'toml' but the many takeover requests in the recent past make me nervous that if I am away from Haskell programming for some weeks or months brings me in danger of losing my packages. Btw. for some years I was not subscribed to Haskell Cafe because of high traffic and I would have missed such takeover request. I think the preference should be to create a fork. Tom, could you please add a Maintainer field at hackage/toml via the Hackage revision feature? From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Fri Mar 12 11:50:06 2021 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Fri, 12 Mar 2021 11:50:06 +0000 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: <46ca1e58-8d6b-eba0-c330-ca7cfde63cbd@henning-thielemann.de> References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <46ca1e58-8d6b-eba0-c330-ca7cfde63cbd@henning-thielemann.de> Message-ID: <20210312115006.GG15063@cloudinit-builder> On Fri, Mar 12, 2021 at 12:36:16PM +0100, Henning Thielemann wrote: > On Thu, 11 Mar 2021, amindfv--- via Haskell-Cafe wrote: > > Again, trying to be respectful here, but "burning" kinda does imply > > "fire," and "need" certainly does imply "need." It's now seeming more > > just like a desire for the package name. > > I have nothing to do with 'toml' but the many takeover requests in the > recent past make me nervous that if I am away from Haskell programming for > some weeks or months brings me in danger of losing my packages. Btw. for > some years I was not subscribed to Haskell Cafe because of high traffic and > I would have missed such takeover request. I think the preference should be > to create a fork. This raises an interesting question: to whom does the entry in the package namespace belong? There's a tacit assumption that it belongs to the first person who registered it. Arguably though it could be deemed to belong to the community. The more "generic" the name the more water that argument seems to hold. The solution of "create a fork" could equally well be turned around to apply to a package maintainer who returns after a long absence to find that the community has taken over maintenance of her package. I don't think there's any absolute sense in which that is the wrong answer. We won't find a general principle that holds in all cases but I do think it is worth discussing and perhaps coming up with some voluntary principles that maintainers can sign up to. Looking to how other language ecosystems handle this issue may be helpful. Tom From carter.schonwald at gmail.com Fri Mar 12 11:54:36 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 12 Mar 2021 06:54:36 -0500 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: <20210312115006.GG15063@cloudinit-builder> References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <46ca1e58-8d6b-eba0-c330-ca7cfde63cbd@henning-thielemann.de> <20210312115006.GG15063@cloudinit-builder> Message-ID: Agreed. On Fri, Mar 12, 2021 at 6:51 AM Tom Ellis < tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk> wrote: > On Fri, Mar 12, 2021 at 12:36:16PM +0100, Henning Thielemann wrote: > > On Thu, 11 Mar 2021, amindfv--- via Haskell-Cafe wrote: > > > Again, trying to be respectful here, but "burning" kinda does imply > > > "fire," and "need" certainly does imply "need." It's now seeming more > > > just like a desire for the package name. > > > > I have nothing to do with 'toml' but the many takeover requests in the > > recent past make me nervous that if I am away from Haskell programming > for > > some weeks or months brings me in danger of losing my packages. Btw. for > > some years I was not subscribed to Haskell Cafe because of high traffic > and > > I would have missed such takeover request. I think the preference should > be > > to create a fork. > > This raises an interesting question: to whom does the entry in the > package namespace belong? There's a tacit assumption that it belongs > to the first person who registered it. Arguably though it could be > deemed to belong to the community. The more "generic" the name the > more water that argument seems to hold. > > The solution of "create a fork" could equally well be turned around to > apply to a package maintainer who returns after a long absence to find > that the community has taken over maintenance of her package. I don't > think there's any absolute sense in which that is the wrong answer. > > We won't find a general principle that holds in all cases but I do > think it is worth discussing and perhaps coming up with some voluntary > principles that maintainers can sign up to. Looking to how other > language ecosystems handle this issue may be helpful. > > Tom > _______________________________________________ > 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 chikitosan at gmail.com Fri Mar 12 11:56:56 2021 From: chikitosan at gmail.com (Antonio) Date: Fri, 12 Mar 2021 12:56:56 +0100 Subject: [Haskell-cafe] Some questions about Fudgets library In-Reply-To: References: <20210311221202.GA3955@saruman> Message-ID: <20210312115656.GA6164@saruman> Hi Thomas, Oh, I didn't see that candidate. It's nice to have Fudgets in Hackage eventually. I'll try to arrowize it, but it will take quite some time. I'll probably finish my bittorrent client first with Fudgets as it's now, in order to have a good grasp of it, and later I'll take a dive into X11 and Fudgets internals to try to modernize it. Best regards, Antonio El Fri, Mar 12, 2021 at 12:28:07PM +0100, Thomas Hallgren escribió: > Hi Antonio, > > I have contemplated publishing Fudgets on Hackage, and the reason for the broken > link is that I uploaded a package candidate [1]. But Fudgets has remained > essentially the same since the mid 90s, and while it still works and is > available from the Fudgets home page [2], its age shows in many ways, and that's > why I hesitate to publish it on Hackage... > > Best regards, > Thomas H > > [1] https://hackage.haskell.org/package/fudgets-0.18.2/candidate > [2] https://www.altocumulus.org/Fudgets/ > > > On 2021-03-11 23:12, Antonio wrote: > > I wonder why there is no Fudgets package in Hackage. > > > > I found this, but the fudgets link is broken: > > > > http://hackage.haskell.org/user/ThomasHallgren > > > > Nevertheless, there is a cabalized package in the Fudgets homepage, so it's strange it's not in Hackage. > > > > Also, is there an arrowized version of Fudgets? If not, why? Is there some fundamental reason that makes it impossible to port it to the arrows framework or simply nobody cared to port it? (Also, the license seems to not allow modifications.) > > > > I'm trying to write a bittorrent client in Haskell. I decided to use arrows for it and took a look at Fudgets and Yampa. I haven't decided yet which one to use. Fudgets seems more suitable and I like it more, but the fact that it doesn't use the arrow notation and classes is a bit annoying. > > > > I read that Fruit is more or less a mix of Fudgets and Yampa that uses arrows. Sadly, it's unmaintained, the web doesn't exist and it's not in Hackage. Is there any other Fudgets-like option? > > > > Greetings. > > _______________________________________________ > > 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 kovanikov at gmail.com Fri Mar 12 12:04:33 2021 From: kovanikov at gmail.com (Dmitrii Kovanikov) Date: Fri, 12 Mar 2021 12:04:33 +0000 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: <20210312070130.GA9783@painter.painter> References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <20210312070130.GA9783@painter.painter> Message-ID: Hi everyone, I feel extremely sad about this discussion for multiple reasons. But regarding the technical agenda: > I'm going to look at `toml-parser` in the meantime, but no toml library does what I have in mind (namely a full fledged implementation of the spec, streaming, deriving etc.), nor do many of them provide bidirectional serialization save `tomland`. This does sound very disappointing to me and I don't fully understand the needs. Because: * tomland is the official TOML parsing library in Haskell according to the TOML spec wiki * tomland fully supports the spec version 0.5.0, and the latest spec 1.0.0 was published relatively recently. And to my knowledge, it is the only Haskell library that supports the latest spec. * tomland is the most popular TOML parsing library according to reverse dependencies on Hackage * tomland is based on explicit values, but nevertheless it provides deriving via Generics I feel very confused about this situation. And again I feel like people the Haskell committees members are not willing to recognise other's people work and would rather rewrite everything from scratch instead of collaborating with existing projects created by people outside of committees. Even outside the Haskell community (the TOML org), tomland was acknowledged as the official TOML library, but not in the Haskell community itself. At least, the following steps could be taken first: * Why not open issues to tomland (or other libraries) and discuss the features you want? We maintain tomland for multiple years. The latest release was Feb 12 2021 (a month ago!). We constantly improve the implementation, fix parsing issues, improve interface and error-handling. Attempting to rewrite all this from scratch instead of collaborating with existing maintainers feels very unfriendly. * If you want to have the official TOML parsing library under the `toml` namespace on Hackage, again, why not ask the maintainers if they consider moving the library? And only after this discussion act accordingly. * If you are concerned about the lack of people working on the `tomland` library (which I don't fully understand, because in Kowainik we always have at least two people maintaining packages), then why not ask to add as a maintainer, instead of rewriting another library? Or even ask to move to the official `haskell` organization on GitHub, if you want to have more people maintaining the official package. I mean, how am I supposed to feel motivated working on Haskell open-source projects, if my work can be just discarded at any time, the official library will be appointed without even communicating this desire? If I weren't subscribed to this thread, I probably wouldn't even know that something is going behind backs. We've put a lot of effort into tomland. We literally spent years of maintenance, UX improvements, bug fixes, writing tutorials and blog posts about the library and its implementation. And it is still not enough just to be respected and even give the chance to reply to the users needs? That sounds very concerning to me. I don' feel like Haskell tech can move forward if people's (specifically if they are not associated with any Haskell leaders) work is disrespected. Best regards, Dmitrii On Fri, 12 Mar 2021 at 07:02, amindfv--- via Haskell-Cafe < haskell-cafe at haskell.org> wrote: > On Fri, Mar 12, 2021 at 06:28:44AM +0000, Emily Pillmore wrote: > > Tom, > > > > Look, I don't want to debate syntax and semantics here, but "burning > need/desire/ambition" etc ( > https://idioms.thefreedictionary.com/burning+desire ) is an extremely > common colloquialism that doesn't imply an emergency, just a strongly felt > urge. I can't apologize for my wording, but I'm sorry for the situation > nonetheless. > > I also don't want to debate semantics but I can tell you "I have a burning > need" on a Hackage takeover has a different connotation of urgency than "I > have a burning desire to write a toml parsing library and to have it be > named 'toml'". I still feel duped and now condescended to as well. I do > nonetheless appreciate your apology for the situation. > > > > > > > It's now seeming more just like a desire for the package name. > > > > > > > > > > I'm going to look at `toml-parser` in the meantime, but no toml library > does what I have in mind (namely a full fledged implementation of the spec, > streaming, deriving etc.), nor do many of them provide bidirectional > serialization save `tomland`. To reiterate Carter's point, hackage names > are a community resource, and they deserve to be thought through carefully, > so yes, the package name is part of the request. I do alot of community > service to make sure things that take up precious Hackage real-estate are > treated well, which is why `toml` posed an opportunity. > > I'm actually open to the idea of using a simple name like "toml" for a > best-in-class Haskell library, but I'd want to see proof that it is clearly > the best in terms of implementation and adoption. I of course think my > plans for toml parsing are the most wonderful, but if a consensus favorite > package emerges and it's not mine I will step aside. > > > > > To that point, anything you put out is something I am interested in > investing time and effort into making a standard. Do you have any code > currently, or is this a TODO on your list? Going through your hackage > libraries, I see no source repository listings, issue trackers, or even an > email to reach you by. > > I do have code, yes. As mentioned earlier I'm in the middle of a rewrite. > If there's more to discuss maybe we should move this conversation off-list > as it's no longer about a package takeover? > > Tom > > _______________________________________________ > 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 carter.schonwald at gmail.com Fri Mar 12 12:40:45 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 12 Mar 2021 07:40:45 -0500 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <20210312070130.GA9783@painter.painter> Message-ID: Hey Dmitrii, I believe emily has in mind fully incremental streaming support. Which requires a wildly different internal architecture than all the stuff in the aeson inspired design family https://github.com/cartazio/streaming-machine-json Is an example of a constant space json parser with fully incremental consumption and emissions. An predecessor was used in a work prject 5 years ago and it could handle multi gig json monsters like a champ. I never released it to hackage because I want to have a better / more reusable design. Parsing the same 3-10gb json with aeson was impossible on a machine that had hundreds of gigs of ram. :) I believe emily has in mind similar levels of robustness On Fri, Mar 12, 2021 at 7:08 AM Dmitrii Kovanikov wrote: > Hi everyone, > > I feel extremely sad about this discussion for multiple reasons. But > regarding the technical agenda: > > > I'm going to look at `toml-parser` in the meantime, but no toml library > does what I have in mind (namely a full fledged implementation of the spec, > streaming, deriving etc.), nor do many of them provide bidirectional > serialization save `tomland`. > > This does sound very disappointing to me and I don't fully understand > the needs. Because: > > * tomland is the official TOML parsing library in Haskell according to the TOML > spec wiki > * tomland fully supports the spec version 0.5.0, and the latest spec 1.0.0 > was published relatively recently. And to my knowledge, it is the only > Haskell library that supports the latest spec. > * tomland is the most popular TOML parsing library according to reverse > dependencies on Hackage > * tomland is based on explicit values, but nevertheless it provides > deriving via Generics > > I feel very confused about this situation. And again I feel like people > the Haskell committees members are not willing to recognise other's > people work and would rather rewrite everything from scratch instead of > collaborating with existing projects created by people outside of > committees. Even outside the Haskell community (the TOML org), tomland was > acknowledged as the official TOML library, but not in the Haskell community > itself. > > At least, the following steps could be taken first: > > * Why not open issues to tomland (or other libraries) and discuss the > features you want? We maintain tomland for multiple years. The latest > release was Feb 12 2021 (a month ago!). We constantly improve the > implementation, fix parsing issues, improve interface and error-handling. > Attempting to rewrite all this from scratch instead of collaborating with > existing maintainers feels very unfriendly. > * If you want to have the official TOML parsing library under the `toml` > namespace on Hackage, again, why not ask the maintainers if they consider > moving the library? And only after this discussion act accordingly. > * If you are concerned about the lack of people working on the `tomland` > library (which I don't fully understand, because in Kowainik we always have > at least two people maintaining packages), then why not ask to add as a > maintainer, instead of rewriting another library? Or even ask to move to > the official `haskell` organization on GitHub, if you want to have more > people maintaining the official package. > > I mean, how am I supposed to feel motivated working on Haskell open-source > projects, if my work can be just discarded at any time, the official > library will be appointed without even communicating this desire? If I > weren't subscribed to this thread, I probably wouldn't even know that > something is going behind backs. We've put a lot of effort into tomland. We > literally spent years of maintenance, UX improvements, bug fixes, writing > tutorials and blog posts about the library and its implementation. And it > is still not enough just to be respected and even give the chance to reply > to the users needs? > > That sounds very concerning to me. I don' feel like Haskell tech can move > forward if people's (specifically if they are not associated with any > Haskell leaders) work is disrespected. > > Best regards, > Dmitrii > > On Fri, 12 Mar 2021 at 07:02, amindfv--- via Haskell-Cafe < > haskell-cafe at haskell.org> wrote: > >> On Fri, Mar 12, 2021 at 06:28:44AM +0000, Emily Pillmore wrote: >> > Tom, >> > >> > Look, I don't want to debate syntax and semantics here, but "burning >> need/desire/ambition" etc ( >> https://idioms.thefreedictionary.com/burning+desire ) is an extremely >> common colloquialism that doesn't imply an emergency, just a strongly felt >> urge. I can't apologize for my wording, but I'm sorry for the situation >> nonetheless. >> >> I also don't want to debate semantics but I can tell you "I have a >> burning need" on a Hackage takeover has a different connotation of urgency >> than "I have a burning desire to write a toml parsing library and to have >> it be named 'toml'". I still feel duped and now condescended to as well. I >> do nonetheless appreciate your apology for the situation. >> >> > > >> > > It's now seeming more just like a desire for the package name. >> > > >> > > >> > >> > I'm going to look at `toml-parser` in the meantime, but no toml library >> does what I have in mind (namely a full fledged implementation of the spec, >> streaming, deriving etc.), nor do many of them provide bidirectional >> serialization save `tomland`. To reiterate Carter's point, hackage names >> are a community resource, and they deserve to be thought through carefully, >> so yes, the package name is part of the request. I do alot of community >> service to make sure things that take up precious Hackage real-estate are >> treated well, which is why `toml` posed an opportunity. >> >> I'm actually open to the idea of using a simple name like "toml" for a >> best-in-class Haskell library, but I'd want to see proof that it is clearly >> the best in terms of implementation and adoption. I of course think my >> plans for toml parsing are the most wonderful, but if a consensus favorite >> package emerges and it's not mine I will step aside. >> >> > >> > To that point, anything you put out is something I am interested in >> investing time and effort into making a standard. Do you have any code >> currently, or is this a TODO on your list? Going through your hackage >> libraries, I see no source repository listings, issue trackers, or even an >> email to reach you by. >> >> I do have code, yes. As mentioned earlier I'm in the middle of a rewrite. >> If there's more to discuss maybe we should move this conversation off-list >> as it's no longer about a package takeover? >> >> Tom >> >> _______________________________________________ >> 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 kovanikov at gmail.com Fri Mar 12 13:10:57 2021 From: kovanikov at gmail.com (Dmitrii Kovanikov) Date: Fri, 12 Mar 2021 13:10:57 +0000 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <20210312070130.GA9783@painter.painter> Message-ID: The TOML format is optimized for human-readability, not space efficiency. And it has some data redundancy, which makes it great for the application configuration use-case but not so great as a serialization format. If you are using TOML to serialise data or you need to parse 3-10 GB of application configuration, there's a chance that something can be improved without streaming TOML parsing. So streaming TOML parser looks like a very specific use-case that doesn't justify taking someone's package and making it the official TOML parser. Best regards, Dmitrii On Fri, 12 Mar 2021 at 12:40, Carter Schonwald wrote: > Hey Dmitrii, > I believe emily has in mind fully incremental streaming support. Which > requires a wildly different internal architecture than all the stuff in the > aeson inspired design family > > https://github.com/cartazio/streaming-machine-json > Is an example of a constant space json parser with fully incremental > consumption and emissions. > > An predecessor was used in a work prject 5 years ago and it could handle > multi gig json monsters like a champ. I never released it to hackage > because I want to have a better / more reusable design. Parsing the same > 3-10gb json with aeson was impossible on a machine that had hundreds of > gigs of ram. :) > > I believe emily has in mind similar levels of robustness > > On Fri, Mar 12, 2021 at 7:08 AM Dmitrii Kovanikov > wrote: > >> Hi everyone, >> >> I feel extremely sad about this discussion for multiple reasons. But >> regarding the technical agenda: >> >> > I'm going to look at `toml-parser` in the meantime, but no toml library >> does what I have in mind (namely a full fledged implementation of the spec, >> streaming, deriving etc.), nor do many of them provide bidirectional >> serialization save `tomland`. >> >> This does sound very disappointing to me and I don't fully understand >> the needs. Because: >> >> * tomland is the official TOML parsing library in Haskell according to >> the TOML spec wiki >> * tomland fully supports the spec version 0.5.0, and the latest spec >> 1.0.0 was published relatively recently. And to my knowledge, it is the >> only Haskell library that supports the latest spec. >> * tomland is the most popular TOML parsing library according to reverse >> dependencies on Hackage >> * tomland is based on explicit values, but nevertheless it provides >> deriving via Generics >> >> I feel very confused about this situation. And again I feel like people >> the Haskell committees members are not willing to recognise other's >> people work and would rather rewrite everything from scratch instead of >> collaborating with existing projects created by people outside of >> committees. Even outside the Haskell community (the TOML org), tomland was >> acknowledged as the official TOML library, but not in the Haskell community >> itself. >> >> At least, the following steps could be taken first: >> >> * Why not open issues to tomland (or other libraries) and discuss the >> features you want? We maintain tomland for multiple years. The latest >> release was Feb 12 2021 (a month ago!). We constantly improve the >> implementation, fix parsing issues, improve interface and error-handling. >> Attempting to rewrite all this from scratch instead of collaborating with >> existing maintainers feels very unfriendly. >> * If you want to have the official TOML parsing library under the `toml` >> namespace on Hackage, again, why not ask the maintainers if they consider >> moving the library? And only after this discussion act accordingly. >> * If you are concerned about the lack of people working on the `tomland` >> library (which I don't fully understand, because in Kowainik we always have >> at least two people maintaining packages), then why not ask to add as a >> maintainer, instead of rewriting another library? Or even ask to move to >> the official `haskell` organization on GitHub, if you want to have more >> people maintaining the official package. >> >> I mean, how am I supposed to feel motivated working on Haskell >> open-source projects, if my work can be just discarded at any time, the >> official library will be appointed without even communicating this desire? >> If I weren't subscribed to this thread, I probably wouldn't even know that >> something is going behind backs. We've put a lot of effort into tomland. We >> literally spent years of maintenance, UX improvements, bug fixes, writing >> tutorials and blog posts about the library and its implementation. And it >> is still not enough just to be respected and even give the chance to reply >> to the users needs? >> >> That sounds very concerning to me. I don' feel like Haskell tech can move >> forward if people's (specifically if they are not associated with any >> Haskell leaders) work is disrespected. >> >> Best regards, >> Dmitrii >> >> On Fri, 12 Mar 2021 at 07:02, amindfv--- via Haskell-Cafe < >> haskell-cafe at haskell.org> wrote: >> >>> On Fri, Mar 12, 2021 at 06:28:44AM +0000, Emily Pillmore wrote: >>> > Tom, >>> > >>> > Look, I don't want to debate syntax and semantics here, but "burning >>> need/desire/ambition" etc ( >>> https://idioms.thefreedictionary.com/burning+desire ) is an extremely >>> common colloquialism that doesn't imply an emergency, just a strongly felt >>> urge. I can't apologize for my wording, but I'm sorry for the situation >>> nonetheless. >>> >>> I also don't want to debate semantics but I can tell you "I have a >>> burning need" on a Hackage takeover has a different connotation of urgency >>> than "I have a burning desire to write a toml parsing library and to have >>> it be named 'toml'". I still feel duped and now condescended to as well. I >>> do nonetheless appreciate your apology for the situation. >>> >>> > > >>> > > It's now seeming more just like a desire for the package name. >>> > > >>> > > >>> > >>> > I'm going to look at `toml-parser` in the meantime, but no toml >>> library does what I have in mind (namely a full fledged implementation of >>> the spec, streaming, deriving etc.), nor do many of them provide >>> bidirectional serialization save `tomland`. To reiterate Carter's point, >>> hackage names are a community resource, and they deserve to be thought >>> through carefully, so yes, the package name is part of the request. I do >>> alot of community service to make sure things that take up precious Hackage >>> real-estate are treated well, which is why `toml` posed an opportunity. >>> >>> I'm actually open to the idea of using a simple name like "toml" for a >>> best-in-class Haskell library, but I'd want to see proof that it is clearly >>> the best in terms of implementation and adoption. I of course think my >>> plans for toml parsing are the most wonderful, but if a consensus favorite >>> package emerges and it's not mine I will step aside. >>> >>> > >>> > To that point, anything you put out is something I am interested in >>> investing time and effort into making a standard. Do you have any code >>> currently, or is this a TODO on your list? Going through your hackage >>> libraries, I see no source repository listings, issue trackers, or even an >>> email to reach you by. >>> >>> I do have code, yes. As mentioned earlier I'm in the middle of a >>> rewrite. If there's more to discuss maybe we should move this conversation >>> off-list as it's no longer about a package takeover? >>> >>> Tom >>> >>> _______________________________________________ >>> 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 carter.schonwald at gmail.com Fri Mar 12 13:22:19 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 12 Mar 2021 08:22:19 -0500 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <20210312070130.GA9783@painter.painter> Message-ID: hey dimtrii, i'm sure theres other pieces, thats just the one i'm spec robust engineering is for robustness. not for assuming sane users or nonadversarial inputs relatedly/on that topic, you should probably consider using the float parser in the scientific package rather than https://hackage.haskell.org/package/tomland-1.3.2.0/docs/src/Toml.Parser.Value.html#floatP, theres some easy to design malicious inputs otherwise (talking about robustness made me look to see if you were using what for parsing floats! ) On Fri, Mar 12, 2021 at 8:11 AM Dmitrii Kovanikov wrote: > The TOML format is optimized for human-readability, not space efficiency. > And it has some data redundancy, which makes it great for the application > configuration use-case but not so great as a serialization format. If you > are using TOML to serialise data or you need to parse 3-10 GB of > application configuration, there's a chance that something can be improved > without streaming TOML parsing. > > So streaming TOML parser looks like a very specific use-case that doesn't > justify taking someone's package and making it the official TOML parser. > > Best regards, > Dmitrii > > On Fri, 12 Mar 2021 at 12:40, Carter Schonwald > wrote: > >> Hey Dmitrii, >> I believe emily has in mind fully incremental streaming support. Which >> requires a wildly different internal architecture than all the stuff in the >> aeson inspired design family >> >> https://github.com/cartazio/streaming-machine-json >> Is an example of a constant space json parser with fully incremental >> consumption and emissions. >> >> An predecessor was used in a work prject 5 years ago and it could handle >> multi gig json monsters like a champ. I never released it to hackage >> because I want to have a better / more reusable design. Parsing the same >> 3-10gb json with aeson was impossible on a machine that had hundreds of >> gigs of ram. :) >> >> I believe emily has in mind similar levels of robustness >> >> On Fri, Mar 12, 2021 at 7:08 AM Dmitrii Kovanikov >> wrote: >> >>> Hi everyone, >>> >>> I feel extremely sad about this discussion for multiple reasons. But >>> regarding the technical agenda: >>> >>> > I'm going to look at `toml-parser` in the meantime, but no toml >>> library does what I have in mind (namely a full fledged implementation of >>> the spec, streaming, deriving etc.), nor do many of them provide >>> bidirectional serialization save `tomland`. >>> >>> This does sound very disappointing to me and I don't fully understand >>> the needs. Because: >>> >>> * tomland is the official TOML parsing library in Haskell according to >>> the TOML spec wiki >>> * tomland fully supports the spec version 0.5.0, and the latest spec >>> 1.0.0 was published relatively recently. And to my knowledge, it is the >>> only Haskell library that supports the latest spec. >>> * tomland is the most popular TOML parsing library according to reverse >>> dependencies on Hackage >>> * tomland is based on explicit values, but nevertheless it provides >>> deriving via Generics >>> >>> I feel very confused about this situation. And again I feel like people >>> the Haskell committees members are not willing to recognise other's >>> people work and would rather rewrite everything from scratch instead of >>> collaborating with existing projects created by people outside of >>> committees. Even outside the Haskell community (the TOML org), tomland was >>> acknowledged as the official TOML library, but not in the Haskell community >>> itself. >>> >>> At least, the following steps could be taken first: >>> >>> * Why not open issues to tomland (or other libraries) and discuss the >>> features you want? We maintain tomland for multiple years. The latest >>> release was Feb 12 2021 (a month ago!). We constantly improve the >>> implementation, fix parsing issues, improve interface and error-handling. >>> Attempting to rewrite all this from scratch instead of collaborating with >>> existing maintainers feels very unfriendly. >>> * If you want to have the official TOML parsing library under the `toml` >>> namespace on Hackage, again, why not ask the maintainers if they consider >>> moving the library? And only after this discussion act accordingly. >>> * If you are concerned about the lack of people working on the `tomland` >>> library (which I don't fully understand, because in Kowainik we always have >>> at least two people maintaining packages), then why not ask to add as a >>> maintainer, instead of rewriting another library? Or even ask to move to >>> the official `haskell` organization on GitHub, if you want to have more >>> people maintaining the official package. >>> >>> I mean, how am I supposed to feel motivated working on Haskell >>> open-source projects, if my work can be just discarded at any time, the >>> official library will be appointed without even communicating this desire? >>> If I weren't subscribed to this thread, I probably wouldn't even know that >>> something is going behind backs. We've put a lot of effort into tomland. We >>> literally spent years of maintenance, UX improvements, bug fixes, writing >>> tutorials and blog posts about the library and its implementation. And it >>> is still not enough just to be respected and even give the chance to reply >>> to the users needs? >>> >>> That sounds very concerning to me. I don' feel like Haskell tech can >>> move forward if people's (specifically if they are not associated with any >>> Haskell leaders) work is disrespected. >>> >>> Best regards, >>> Dmitrii >>> >>> On Fri, 12 Mar 2021 at 07:02, amindfv--- via Haskell-Cafe < >>> haskell-cafe at haskell.org> wrote: >>> >>>> On Fri, Mar 12, 2021 at 06:28:44AM +0000, Emily Pillmore wrote: >>>> > Tom, >>>> > >>>> > Look, I don't want to debate syntax and semantics here, but "burning >>>> need/desire/ambition" etc ( >>>> https://idioms.thefreedictionary.com/burning+desire ) is an extremely >>>> common colloquialism that doesn't imply an emergency, just a strongly felt >>>> urge. I can't apologize for my wording, but I'm sorry for the situation >>>> nonetheless. >>>> >>>> I also don't want to debate semantics but I can tell you "I have a >>>> burning need" on a Hackage takeover has a different connotation of urgency >>>> than "I have a burning desire to write a toml parsing library and to have >>>> it be named 'toml'". I still feel duped and now condescended to as well. I >>>> do nonetheless appreciate your apology for the situation. >>>> >>>> > > >>>> > > It's now seeming more just like a desire for the package name. >>>> > > >>>> > > >>>> > >>>> > I'm going to look at `toml-parser` in the meantime, but no toml >>>> library does what I have in mind (namely a full fledged implementation of >>>> the spec, streaming, deriving etc.), nor do many of them provide >>>> bidirectional serialization save `tomland`. To reiterate Carter's point, >>>> hackage names are a community resource, and they deserve to be thought >>>> through carefully, so yes, the package name is part of the request. I do >>>> alot of community service to make sure things that take up precious Hackage >>>> real-estate are treated well, which is why `toml` posed an opportunity. >>>> >>>> I'm actually open to the idea of using a simple name like "toml" for a >>>> best-in-class Haskell library, but I'd want to see proof that it is clearly >>>> the best in terms of implementation and adoption. I of course think my >>>> plans for toml parsing are the most wonderful, but if a consensus favorite >>>> package emerges and it's not mine I will step aside. >>>> >>>> > >>>> > To that point, anything you put out is something I am interested in >>>> investing time and effort into making a standard. Do you have any code >>>> currently, or is this a TODO on your list? Going through your hackage >>>> libraries, I see no source repository listings, issue trackers, or even an >>>> email to reach you by. >>>> >>>> I do have code, yes. As mentioned earlier I'm in the middle of a >>>> rewrite. If there's more to discuss maybe we should move this conversation >>>> off-list as it's no longer about a package takeover? >>>> >>>> Tom >>>> >>>> _______________________________________________ >>>> 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 imantc at gmail.com Fri Mar 12 13:26:17 2021 From: imantc at gmail.com (Imants Cekusins) Date: Fri, 12 Mar 2021 15:26:17 +0200 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <20210312070130.GA9783@painter.painter> Message-ID: How about naming all official / recommended / _the_ packages with a prefix / suffix (e.g. base-*) and requiring an approval to create such packages? This way, the required name would always be available when needed. From carter.schonwald at gmail.com Fri Mar 12 13:40:39 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 12 Mar 2021 08:40:39 -0500 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <20210312070130.GA9783@painter.painter> Message-ID: def a good idea to figure out, though that and or any other solution is as much about making sure the anthropology of the culture over time supports the convention as much as anything else, On Fri, Mar 12, 2021 at 8:29 AM Imants Cekusins wrote: > How about naming all official / recommended / _the_ packages with a > prefix / suffix (e.g. base-*) and requiring an approval to create such > packages? > > This way, the required name would always be available when needed. > _______________________________________________ > 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 svenpanne at gmail.com Fri Mar 12 15:31:32 2021 From: svenpanne at gmail.com (Sven Panne) Date: Fri, 12 Mar 2021 16:31:32 +0100 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <20210312070130.GA9783@painter.painter> Message-ID: Am Fr., 12. März 2021 um 14:29 Uhr schrieb Imants Cekusins : > How about naming all official / recommended / _the_ packages with a > prefix / suffix (e.g. base-*) and requiring an approval to create such > packages? > I highly doubt that any finite (let alone: small) group of people has the competence to decide what "the" package for a given task should be, given the vast number of topics packages cover. It is OK for mainstream topics, but even then different people have different needs and views. What happens when people not really competent in a given topic try to standardize things as "the" way to do it can e.g. be seen in C++'s SG13, a completely failed attempt to standardize 2D graphics. Apart from a relatively small, undisputed set of things, let the community decide what "the" way to do things should be, basically using "survival of the fittest". If one library is definitely better than another, then it will be used much more often, at least most of the time. An e.g. well-curated "official" overview of libraries for different topics can help here. I think that discussions about package names are quite irrelevant, it is all about discoverability of a package, and the package name doesn't help there at all most of the time. Googling "haskell toml", you get tomland and htoml as the first 2 hits. I would have never guessed the first name BTW, and I actually don't care that much: Even if it's called "gnlpft" and it is the 1st hit on Google and does its task well: So be it! Typing whatever package name into a .cabal file is the least of your problems when choosing a library. Another good example: "aeson". It's not really the first name coming to your mind when you think about JSON, but people don't have a problem discovering it. A more problematic thing than the package names IMHO is the choice of names for the hierarchical modules within a package: If things somehow clash by accident here, you have bigger problems. There is no process whatsoever (at least I don't know one) how these names are allocated. There were some proposals by Malcolm W. and Simon M. some 10-20 years ago IIRC, but these were only rough sketches. Cheers, S. -------------- next part -------------- An HTML attachment was scrubbed... URL: From ivanperezdominguez at gmail.com Fri Mar 12 15:33:52 2021 From: ivanperezdominguez at gmail.com (Ivan Perez) Date: Fri, 12 Mar 2021 10:33:52 -0500 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <20210312070130.GA9783@painter.painter> Message-ID: This is something I'd strongly vote against. It will likely create yet more fights between people for control of any committee that designates which packages are "recommended". Let the community figure out which packages are best. Let's instead encourage collaboration and agreement at package level, so we work together towards having better packages, as opposed to many not-so-good ones. Ivan On Fri, 12 Mar 2021 at 08:29, Imants Cekusins wrote: > How about naming all official / recommended / _the_ packages with a > prefix / suffix (e.g. base-*) and requiring an approval to create such > packages? > > This way, the required name would always be available when needed. > _______________________________________________ > 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 eraker at gmail.com Fri Mar 12 15:34:32 2021 From: eraker at gmail.com (erik) Date: Fri, 12 Mar 2021 07:34:32 -0800 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <20210312070130.GA9783@painter.painter> Message-ID: Tom wrote: > We won't find a general principle that holds in all cases but I do think > it is worth discussing and perhaps coming up with some voluntary > principles that maintainers can sign up to. Looking to how other language > ecosystems handle this issue may be helpful. I am a bystander in this discussion, but reading it I couldn't help but think about how developers in other languages typically avoid this problem (and I don't think this will come as a surprise to anyone here) by giving libraries non-prosaic names. Relatedly, as a developer selecting dependencies for a project, I want to know "what do most people use to solve this particular problem?" It wouldn't matter to me whether the answer is a package named something whimsical and weird as long as it looks well- (and recently!) maintained and there is information on how to use it. I wouldn't presume to offer this as a recommendation to this group, but I was a little surprised by the antagonistic direction of this conversation. Indeed, if there's a new and better approach to TOML parsing (and if I have that particular problem in the future...), I'd be happy to rely on that new approach (and the efforts of those involved), no matter what the package is called. To be honest, though, it's tough for me to tell if Emily's original request is about forking a codebase or simply taking over the name and producing an entirely new codebase? In any case, the work sounds interesting. On Fri, Mar 12, 2021 at 5:42 AM Carter Schonwald wrote: > def a good idea to figure out, though that and or any other solution is as > much about making sure the anthropology of the culture over time supports > the convention as much as anything else, > > On Fri, Mar 12, 2021 at 8:29 AM Imants Cekusins wrote: > >> How about naming all official / recommended / _the_ packages with a >> prefix / suffix (e.g. base-*) and requiring an approval to create such >> packages? >> >> This way, the required name would always be available when needed. >> _______________________________________________ >> 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. -- Erik Aker -------------- next part -------------- An HTML attachment was scrubbed... URL: From hecate at glitchbra.in Fri Mar 12 15:37:10 2021 From: hecate at glitchbra.in (=?UTF-8?Q?H=c3=a9cate?=) Date: Fri, 12 Mar 2021 16:37:10 +0100 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: <46ca1e58-8d6b-eba0-c330-ca7cfde63cbd@henning-thielemann.de> References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <46ca1e58-8d6b-eba0-c330-ca7cfde63cbd@henning-thielemann.de> Message-ID: I think you shouldn't reasonably fear a takeover demand on the mailing-list if you don't disappear for years without a clear successor. Le 12/03/2021 à 12:36, Henning Thielemann a écrit : > > On Thu, 11 Mar 2021, amindfv--- via Haskell-Cafe wrote: > >> Again, trying to be respectful here, but "burning" kinda does imply >> "fire," and "need" certainly does imply "need." It's now seeming more >> just like a desire for the package name. > > I have nothing to do with 'toml' but the many takeover requests in the > recent past make me nervous that if I am away from Haskell programming > for some weeks or months brings me in danger of losing my packages. > Btw. for some years I was not subscribed to Haskell Cafe because of > high traffic and I would have missed such takeover request. I think > the preference should be to create a fork. > > Tom, could you please add a Maintainer field at hackage/toml via the > Hackage revision feature? > _______________________________________________ > 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. -- Hécate ✨ 🐦: @TechnoEmpress IRC: Uniaika WWW: https://glitchbra.in RUN: BSD From lemming at henning-thielemann.de Fri Mar 12 15:46:07 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Fri, 12 Mar 2021 16:46:07 +0100 (CET) Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <20210312070130.GA9783@painter.painter> Message-ID: On Fri, 12 Mar 2021, Sven Panne wrote: > Even if it's called "gnlpft" and it is the 1st hit on Google I think the correct name must be "gnlpfth", because 'h' stands for the Heart that beats for you night and day. > Another good example: "aeson". It's not really the first name coming to > your mind when you think about JSON, but people don't have a problem > discovering it. This was the first example I also had to think of. > A more problematic thing than the package names IMHO is the choice of > names for the hierarchical modules within a package: If things somehow > clash by accident here, you have bigger problems. There is no process > whatsoever (at least I don't know one) how these names are allocated. > There were some proposals by Malcolm W. and Simon M. some 10-20 years > ago IIRC, but these were only rough sketches. Most module names today end up in the "Data" folder. :-) From carter.schonwald at gmail.com Fri Mar 12 15:46:37 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 12 Mar 2021 10:46:37 -0500 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <46ca1e58-8d6b-eba0-c330-ca7cfde63cbd@henning-thielemann.de> Message-ID: Yeah, especially since a takeover does require actually documenting you’ve made real efforts to reach the maintainer / last person to do a package upload. On Fri, Mar 12, 2021 at 10:41 AM Hécate wrote: > I think you shouldn't reasonably fear a takeover demand on the > mailing-list if you don't disappear for years without a clear successor. > > Le 12/03/2021 à 12:36, Henning Thielemann a écrit : > > > > On Thu, 11 Mar 2021, amindfv--- via Haskell-Cafe wrote: > > > >> Again, trying to be respectful here, but "burning" kinda does imply > >> "fire," and "need" certainly does imply "need." It's now seeming more > >> just like a desire for the package name. > > > > I have nothing to do with 'toml' but the many takeover requests in the > > recent past make me nervous that if I am away from Haskell programming > > for some weeks or months brings me in danger of losing my packages. > > Btw. for some years I was not subscribed to Haskell Cafe because of > > high traffic and I would have missed such takeover request. I think > > the preference should be to create a fork. > > > > Tom, could you please add a Maintainer field at hackage/toml via the > > Hackage revision feature? > > _______________________________________________ > > 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. > > -- > Hécate ✨ > 🐦: @TechnoEmpress > IRC: Uniaika > WWW: https://glitchbra.in > RUN: BSD > > _______________________________________________ > 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 lemming at henning-thielemann.de Fri Mar 12 15:49:18 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Fri, 12 Mar 2021 16:49:18 +0100 (CET) Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <46ca1e58-8d6b-eba0-c330-ca7cfde63cbd@henning-thielemann.de> Message-ID: On Fri, 12 Mar 2021, Hécate wrote: > I think you shouldn't reasonably fear a takeover demand on the > mailing-list if you don't disappear for years without a clear successor. I ask you to defend my packages, if I am unavailable for some time! :-) From hecate at glitchbra.in Fri Mar 12 16:03:37 2021 From: hecate at glitchbra.in (=?UTF-8?Q?H=c3=a9cate?=) Date: Fri, 12 Mar 2021 17:03:37 +0100 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <46ca1e58-8d6b-eba0-c330-ca7cfde63cbd@henning-thielemann.de> Message-ID: <3b848f77-f399-9455-7170-2d9cc92e4094@glitchbra.in> I shall defend them to best of my abilities! Le 12/03/2021 à 16:49, Henning Thielemann a écrit : > > On Fri, 12 Mar 2021, Hécate wrote: > >> I think you shouldn't reasonably fear a takeover demand on the >> mailing-list if you don't disappear for years without a clear successor. > > I ask you to defend my packages, if I am unavailable for some time! :-) -- Hécate ✨ 🐦: @TechnoEmpress IRC: Uniaika WWW: https://glitchbra.in RUN: BSD From b at chreekat.net Fri Mar 12 16:37:17 2021 From: b at chreekat.net (Bryan Richter) Date: Fri, 12 Mar 2021 18:37:17 +0200 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: <3b848f77-f399-9455-7170-2d9cc92e4094@glitchbra.in> References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <46ca1e58-8d6b-eba0-c330-ca7cfde63cbd@henning-thielemann.de> <3b848f77-f399-9455-7170-2d9cc92e4094@glitchbra.in> Message-ID: There's some wringing of hands about dark powers taking over packages in the dead of night that I find uncalled for. Ironically, then, I'm still curious to hear the answer to Emily's question. Was there, in fact, a previous package takeover of toml that wasn't publicly announced? Or is amindfv the original maintainer that everyone didn't know they were looking for? On Fri, 12 Mar 2021, 18.04 Hécate, wrote: > I shall defend them to best of my abilities! > > Le 12/03/2021 à 16:49, Henning Thielemann a écrit : > > > > On Fri, 12 Mar 2021, Hécate wrote: > > > >> I think you shouldn't reasonably fear a takeover demand on the > >> mailing-list if you don't disappear for years without a clear successor. > > > > I ask you to defend my packages, if I am unavailable for some time! :-) > > -- > Hécate ✨ > 🐦: @TechnoEmpress > IRC: Uniaika > WWW: https://glitchbra.in > RUN: BSD > > _______________________________________________ > 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 lemming at henning-thielemann.de Fri Mar 12 16:42:31 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Fri, 12 Mar 2021 17:42:31 +0100 (CET) Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <46ca1e58-8d6b-eba0-c330-ca7cfde63cbd@henning-thielemann.de> <3b848f77-f399-9455-7170-2d9cc92e4094@glitchbra.in> Message-ID: On Fri, 12 Mar 2021, Bryan Richter wrote: > There's some wringing of hands about dark powers taking over packages in > the dead of night that I find uncalled for. Ironically, then, I'm still > curious to hear the answer to Emily's question. Was there, in fact, a > previous package takeover of toml that wasn't publicly announced? I don't think there is any need for a public announcment if a package creator hands over maintainership to another developer. From allbery.b at gmail.com Fri Mar 12 16:55:14 2021 From: allbery.b at gmail.com (Brandon Allbery) Date: Fri, 12 Mar 2021 11:55:14 -0500 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <46ca1e58-8d6b-eba0-c330-ca7cfde63cbd@henning-thielemann.de> <3b848f77-f399-9455-7170-2d9cc92e4094@glitchbra.in> Message-ID: That depends. Can I in fact, were I looking for a maintainer, find out who to contact about the package? Ideally without much digging. On Fri, Mar 12, 2021 at 11:44 AM Henning Thielemann < lemming at henning-thielemann.de> wrote: > > On Fri, 12 Mar 2021, Bryan Richter wrote: > > > There's some wringing of hands about dark powers taking over packages in > > the dead of night that I find uncalled for. Ironically, then, I'm still > > curious to hear the answer to Emily's question. Was there, in fact, a > > previous package takeover of toml that wasn't publicly announced? > > I don't think there is any need for a public announcment if a package > creator hands over maintainership to another developer. > _______________________________________________ > 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. -- brandon s allbery kf8nh allbery.b at gmail.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From ietf-dane at dukhovni.org Fri Mar 12 16:57:57 2021 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Fri, 12 Mar 2021 14:57:57 -0200 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <46ca1e58-8d6b-eba0-c330-ca7cfde63cbd@henning-thielemann.de> <3b848f77-f399-9455-7170-2d9cc92e4094@glitchbra.in> Message-ID: > On Mar 12, 2021, at 2:42 PM, Henning Thielemann wrote: > > I don't think there is any need for a public announcment if a package creator hands over maintainership to another developer. Well, there have been some rather unfortunate transfers of control of widely used packages (in other ecosystems than hackage) to shady operators who made malicious changes. This is more directly a concern for browser plugins, or "apps", but also applies to Python, Ruby, Node and ultimately even Haskell. Supply chain security is a hard problem, and any transparency in changes of control would be great. If release tarballs are digitally signed, and contributors can be expected to not hand over their own keys when transferring control, but rather to arrange for new keys to be authorised to continue to make releases, then such changes of control could be noted on hackage as a change in which key signed a new release. Cautious users might pin the release keys trusted to sign a given dependency, and could then review and approve imports of these if signed by not yet trusted keys. There could even be a role for trusted reviewers (and ideally a means to compensate them for their work). I did mention this is a hard problem... -- Viktor. From imantc at gmail.com Fri Mar 12 16:57:59 2021 From: imantc at gmail.com (Imants Cekusins) Date: Fri, 12 Mar 2021 18:57:59 +0200 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <46ca1e58-8d6b-eba0-c330-ca7cfde63cbd@henning-thielemann.de> <3b848f77-f399-9455-7170-2d9cc92e4094@glitchbra.in> Message-ID: re: maintainer of toml package: https://hackage.haskell.org/packages/search?terms=toml Maintainer: seliopou, TomMurphy https://hackage.haskell.org/package/toml Maintainer: none no repo in https://hackage.haskell.org/package/toml-0.1.3/toml.cabal Let's see how soon the next version is uploaded with maintainer and repo specified. A repo would be nice, wouldn't it? From lemming at henning-thielemann.de Fri Mar 12 16:59:31 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Fri, 12 Mar 2021 17:59:31 +0100 (CET) Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <46ca1e58-8d6b-eba0-c330-ca7cfde63cbd@henning-thielemann.de> <3b848f77-f399-9455-7170-2d9cc92e4094@glitchbra.in> Message-ID: On Fri, 12 Mar 2021, Brandon Allbery wrote: > That depends. Can I in fact, were I looking for a maintainer, find out > who to contact about the package? Ideally without much digging. That's what the Cabal.Maintainer field is for. It is missing in toml, which is bad. From chris at chrisdornan.com Fri Mar 12 17:10:03 2021 From: chris at chrisdornan.com (Chris Dornan) Date: Fri, 12 Mar 2021 17:10:03 +0000 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <46ca1e58-8d6b-eba0-c330-ca7cfde63cbd@henning-thielemann.de> <3b848f77-f399-9455-7170-2d9cc92e4094@glitchbra.in> Message-ID: > > I don't think there is any need for a public announcment if a package creator hands over maintainership to another developer. > Well, there have been some rather unfortunate transfers of control of widely used packages (in other ecosystems than hackage) to shady operators > who made malicious changes. This is more directly a concern for browser plugins, or "apps", but also > applies to Python, Ruby, Node and ultimately even Haskell. Viktor makes some great points, but we do not have any such checks in place at the moment. Currently it is accepted that a package maintainer can get help maintaining a package through whatever means. The original package maintainer can step off at a later time, leaving the new maintainers in charge. At this stage, I think we should stop piling in on Tom -- it does not seem right, at all. Chris On Fri, 12 Mar 2021 at 16:59, Viktor Dukhovni wrote: > > On Mar 12, 2021, at 2:42 PM, Henning Thielemann < > lemming at henning-thielemann.de> wrote: > > > > I don't think there is any need for a public announcment if a package > creator hands over maintainership to another developer. > > Well, there have been some rather unfortunate transfers of control of > widely used packages (in other ecosystems than hackage) to shady operators > who made malicious changes. This is more directly a concern for browser > plugins, or "apps", but also > applies to Python, Ruby, Node and ultimately even Haskell. > > Supply chain security is a hard problem, and any transparency in changes > of control would be great. > > If release tarballs are digitally signed, and contributors can be > expected to not hand over their own keys when transferring control, > but rather to arrange for new keys to be authorised to continue to > make releases, then such changes of control could be noted on hackage > as a change in which key signed a new release. > > Cautious users might pin the release keys trusted to sign a given > dependency, and could then review and approve imports of these > if signed by not yet trusted keys. There could even be a role > for trusted reviewers (and ideally a means to compensate them > for their work). I did mention this is a hard problem... > > -- > 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 emilypi at cohomolo.gy Fri Mar 12 17:13:02 2021 From: emilypi at cohomolo.gy (Emily Pillmore) Date: Fri, 12 Mar 2021 17:13:02 +0000 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <20210312070130.GA9783@painter.painter> Message-ID: Dmiitri, > > This does sound very disappointing to me and I don't fully understand the > needs. > > > > I feel very confused about this situation. And again I feel like people > the Haskell committees members are not willing to recognise other's people > work and would rather rewrite everything from scratch instead of > collaborating with existing projects created by people outside of > committees. > > You're right. You *don't* fully understand my needs! You have not asked, and  just assumed that what I want is exactly what you provide in `tomland`! I am looking at `toml` for a personal side project, not for official business, and I disagree with the existing choices, so I'd like to develop my own and saw a chance to make use of a namespace that was neglected for years on Hackage. This has nothing to do with any technical agenda or anything in my official capacity. In my comments, I said the phrase "develop it into *a* standard" ("standard" as in "good", or of high quality make), not " *the* standard" as in the preferred choice. Multiple standards can exist. I have not said this is official, and I have not said this will be blessed. I have not even mentioned HF or its agendas, or my role in either.  This does not preempt you or your libraries, nor does it make a statement about the quality of your work. > > * Why not open issues to tomland (or other libraries) and discuss the > features you want? We maintain tomland for multiple years. The latest > release was Feb 12 2021 (a month ago!). We constantly improve the > implementation, fix parsing issues, improve interface and error-handling. > Attempting to rewrite all this from scratch instead of collaborating with > existing maintainers feels very unfriendly. > > * If you want to have the official TOML parsing library under the `toml` > namespace on Hackage, again, why not ask the maintainers if they consider > moving the library? And only after this discussion act accordingly. > > * If you are concerned about the lack of people working on the `tomland` > library (which I don't fully understand, because in Kowainik we always > have at least two people maintaining packages), then why not ask to add as > a maintainer, instead of rewriting another library? Or even ask to move to > the official `haskell` organization on GitHub, if you want to have more > people maintaining the official package. > > * Because i have a feature set in mind that seems more appropriate for a new library. * The maintainer (Spiros) has been inactive for 7 years. There is no maintainer listed or source repo available. We messaged Spiros last year, and received no response. I went through the proper channels to check that this was the right thing to do. However, I did not expect Tom Murphy to have been added to the maintainers list, which was a new development, and we'll work with each other to figure out a solution. * This is putting words in my mouth. I have no concerns about the lack of people working on `tomland`. > > I mean, how am I supposed to feel motivated working on Haskell open-source > projects, if my work can be just discarded at any time, the official > library will be appointed without even communicating this desire? If I > weren't subscribed to this thread, I probably wouldn't even know that > something is going behind backs. We've put a lot of effort into tomland. > We literally spent years of maintenance, UX improvements, bug fixes, > writing tutorials and blog posts about the library and its implementation. > And it is still not enough just to be respected and even give the chance > to reply to the users needs? > > This is not an official project, so these points are moot. Instead of jumping to these conclusions, you could have asked me to clarify any points of contention you may have seen. I'm curious as to why you took this tack, and feel disrespected when `tomland` is the go-to TOML library in Haskell, and as you say, has been recognized outside of the community by the TOML org itself. We can take this offline though.I suspect you are bringing a ton of baggage into the conversation that was not a result of this thread. - E On Fri, Mar 12, 2021 at 8:10 AM, Dmitrii Kovanikov < kovanikov at gmail.com > wrote: > > The TOML format is optimized for human-readability, not space efficiency. > And it has some data redundancy, which makes it great for the application > configuration use-case but not so great as a serialization format. If you > are using TOML to serialise data or you need to parse 3-10 GB of > application configuration, there's a chance that something can be improved > without streaming TOML parsing. > > > So streaming TOML parser looks like a very specific use-case that doesn't > justify taking someone's package and making it the official TOML parser. > > > Best regards, > Dmitrii > > On Fri, 12 Mar 2021 at 12:40, Carter Schonwald < carter. schonwald@ gmail. > com ( carter.schonwald at gmail.com ) > wrote: > > >> Hey Dmitrii, >> I believe emily has in mind fully incremental streaming support. Which >> requires a wildly different internal architecture than all the stuff in >> the aeson inspired design family >> >> >> https:/ / github. com/ cartazio/ streaming-machine-json ( >> https://github.com/cartazio/streaming-machine-json ) >> Is an example of a constant space json parser with fully incremental >> consumption and emissions. >> >> >> An predecessor  was used in a work prject 5 years ago and it could handle >> multi gig json monsters like a champ.  I never released it to hackage >> because I want to have a better / more reusable design.  Parsing the same >> 3-10gb json with aeson was impossible on a machine that had hundreds of >> gigs of ram. :) >> >> >> I believe emily has in mind similar levels of robustness >> >> On Fri, Mar 12, 2021 at 7:08 AM Dmitrii Kovanikov < kovanikov@ gmail. com ( >> kovanikov at gmail.com ) > wrote: >> >> >>> Hi everyone, >>> >>> >>> I feel extremely sad about this discussion for multiple reasons. But >>> regarding the technical agenda: >>> >>> >>> > I'm going to look at `toml-parser` in the meantime, but no toml library >>> does what I have in mind (namely a full fledged implementation of the >>> spec, streaming, deriving etc.), nor do many of them provide bidirectional >>> serialization save `tomland`. >>> >>> >>> This does sound very disappointing to me and I don't fully understand the >>> needs. Because: >>> >>> >>> * tomland is the official TOML parsing library in Haskell according to the >>> TOML spec wiki ( https://github.com/toml-lang/toml/wiki ) >>> * tomland fully supports the spec version 0.5.0, and the latest spec 1.0.0 >>> was published relatively recently. And to my knowledge, it is the only >>> Haskell library that supports the latest spec. >>> * tomland is the most popular TOML parsing library according to reverse >>> dependencies ( https://packdeps.haskellers.com/reverse ) on Hackage >>> * tomland is based on explicit values, but nevertheless it provides >>> deriving via Generics >>> >>> >>> I feel very confused about this situation. And again I feel like people >>> the Haskell committees members are not willing to recognise other's people >>> work and would rather rewrite everything from scratch instead of >>> collaborating with existing projects created by people outside of >>> committees. Even outside the Haskell community (the TOML org), tomland was >>> acknowledged as the official TOML library, but not in the Haskell >>> community itself. >>> >>> >>> At least, the following steps could be taken first: >>> >>> >>> * Why not open issues to tomland (or other libraries) and discuss the >>> features you want? We maintain tomland for multiple years. The latest >>> release was Feb 12 2021 (a month ago!). We constantly improve the >>> implementation, fix parsing issues, improve interface and error-handling. >>> Attempting to rewrite all this from scratch instead of collaborating with >>> existing maintainers feels very unfriendly. >>> * If you want to have the official TOML parsing library under the `toml` >>> namespace on Hackage, again, why not ask the maintainers if they consider >>> moving the library? And only after this discussion act accordingly. >>> * If you are concerned about the lack of people working on the `tomland` >>> library (which I don't fully understand, because in Kowainik we always >>> have at least two people maintaining packages), then why not ask to add as >>> a maintainer, instead of rewriting another library? Or even ask to move to >>> the official `haskell` organization on GitHub, if you want to have more >>> people maintaining the official package. >>> >>> >>> I mean, how am I supposed to feel motivated working on Haskell open-source >>> projects, if my work can be just discarded at any time, the official >>> library will be appointed without even communicating this desire? If I >>> weren't subscribed to this thread, I probably wouldn't even know that >>> something is going behind backs. We've put a lot of effort into tomland. >>> We literally spent years of maintenance, UX improvements, bug fixes, >>> writing tutorials and blog posts about the library and its implementation. >>> And it is still not enough just to be respected and even give the chance >>> to reply to the users needs? >>> >>> >>> That sounds very concerning to me. I don' feel like Haskell tech can move >>> forward if people's (specifically if they are not associated with any >>> Haskell leaders) work is disrespected. >>> >>> >>> Best regards, >>> Dmitrii >>> >>> >>> On Fri, 12 Mar 2021 at 07:02, amindfv--- via Haskell-Cafe < haskell-cafe@ haskell. >>> org ( haskell-cafe at haskell.org ) > wrote: >>> >>> >>>> >>> >>> >>> >>>> On Fri, Mar 12, 2021 at 06:28:44AM +0000, Emily Pillmore wrote: >>>> > Tom, >>>> > >>>> > Look, I don't want to debate syntax and semantics here, but "burning >>>> need/desire/ambition" etc ( https:/ / idioms. thefreedictionary. com/ burning+desire >>>> ( https://idioms.thefreedictionary.com/burning+desire ) ) is an extremely >>>> common colloquialism that doesn't imply an emergency, just a strongly felt >>>> urge.  I can't apologize for my wording, but I'm sorry for the situation >>>> nonetheless. >>>> >>>> I also don't want to debate semantics but I can tell you "I have a burning >>>> need" on a Hackage takeover has a different connotation of urgency than "I >>>> have a burning desire to write a toml parsing library and to have it be >>>> named 'toml'". I still feel duped and now condescended to as well. I do >>>> nonetheless appreciate your apology for the situation. >>>> >>>> > > >>>> > > It's now seeming more just like a desire for the package name. >>>> > > >>>> > > >>>> > >>>> > I'm going to look at `toml-parser` in the meantime, but no toml library >>>> does what I have in mind (namely a full fledged implementation of the >>>> spec, streaming, deriving etc.), nor do many of them provide bidirectional >>>> serialization save `tomland`. To reiterate Carter's point, hackage names >>>> are a community resource, and they deserve to be thought through >>>> carefully, so yes, the package name is part of the request. I do alot of >>>> community service to make sure things that take up precious Hackage >>>> real-estate are treated well, which is why `toml` posed an opportunity. >>>> >>>> I'm actually open to the idea of using a simple name like "toml" for a >>>> best-in-class Haskell library, but I'd want to see proof that it is >>>> clearly the best in terms of implementation and adoption. I of course >>>> think my plans for toml parsing are the most wonderful, but if a consensus >>>> favorite package emerges and it's not mine I will step aside. >>>> >>>> > >>>> > To that point, anything you put out is something I am interested in >>>> investing time and effort into making a standard. Do you have any code >>>> currently, or is this a TODO on your list? Going through your hackage >>>> libraries, I see no source repository listings, issue trackers, or even an >>>> email to reach you by. >>>> >>>> I do have code, yes. As mentioned earlier I'm in the middle of a rewrite. >>>> If there's more to discuss maybe we should move this conversation off-list >>>> as it's no longer about a package takeover? >>>> >>>> Tom >>>> >>>> >>> >>> >>> >>>> _______________________________________________ >>>> Haskell-Cafe mailing list >>>> To (un)subscribe, modify options or view archives go to: >>>> http:/ / mail. haskell. org/ cgi-bin/ mailman/ listinfo/ haskell-cafe ( >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe ) >>>> Only members subscribed via the mailman list are allowed to post. >>> >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> To (un)subscribe, modify options or view archives go to: >>> http:/ / mail. haskell. org/ cgi-bin/ mailman/ listinfo/ haskell-cafe ( >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe ) >>> Only members subscribed via the mailman list are allowed to post. >> >> >> > > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: http:/ / mail. haskell. > org/ cgi-bin/ mailman/ listinfo/ haskell-cafe ( > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe ) Only > members subscribed via the mailman list are allowed to post. > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From b at chreekat.net Fri Mar 12 17:15:12 2021 From: b at chreekat.net (Bryan Richter) Date: Fri, 12 Mar 2021 19:15:12 +0200 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <46ca1e58-8d6b-eba0-c330-ca7cfde63cbd@henning-thielemann.de> <3b848f77-f399-9455-7170-2d9cc92e4094@glitchbra.in> Message-ID: Can I suggest to the Hackage Whoever a slight change in policy? I think the shock of seeing a package takeover request for your own package is understandably, uh, shocking, and makes the ensuing discussion tense. I also feel like most takeover requests follow this pattern; rarely does a package end up changing hands. Perhaps it's a problem of tone. Rather than suggesting "State your intention to take over the package in a public forum ", step 2 should lighten up and state, "After trying to reach the maintainer for a reasonable amount of time, reach out to the public to expand your search." https://wiki.haskell.org/Taking_over_a_package On Fri, 12 Mar 2021, 18.59 Henning Thielemann, < lemming at henning-thielemann.de> wrote: > > On Fri, 12 Mar 2021, Brandon Allbery wrote: > > > That depends. Can I in fact, were I looking for a maintainer, find out > > who to contact about the package? Ideally without much digging. > > That's what the Cabal.Maintainer field is for. It is missing in toml, > which is bad. -------------- next part -------------- An HTML attachment was scrubbed... URL: From ryan.gl.scott at gmail.com Fri Mar 12 17:29:24 2021 From: ryan.gl.scott at gmail.com (Ryan Scott) Date: Fri, 12 Mar 2021 12:29:24 -0500 Subject: [Haskell-cafe] [ANN] singletons-3.0, singletons-th-3.0, and singletons-base-3.0 Message-ID: I'm happy to announce the 3.0 release of the singletons library, as well as the debut of its companion libraries, singletons-th and singletons-base. There's been a fair bit of improvements, cleanup, and reorganization since the last release, so I thought it appropriate to give this release a super-major version bump. This announcement will go over some highlights of the new releases, but if you want the full details, you can consult the changelog entries for each library below: * singletons-3.0: http://hackage.haskell.org/package/singletons-3.0/changelog * singletons-th-3.0: http://hackage.haskell.org/package/singletons-th-3.0/changelog * singletons-base-3.0: http://hackage.haskell.org/package/singletons-base-3.0/changelog ########################## ## Why three libraries? ## ########################## Instead of there just being one singletons library, there are now _three_ libraries: * singletons: A small, foundational library that defines basic singleton-related types and definitions. The new singletons library supports GHC 8.0 or later, does not depend on any external libraries, and does not make use of Template Haskell. * singletons-th: A library that defines Template Haskell functionality for promoting term-level functions to type-level equivalents and singling functions to dependently typed equivalents. This library requires bleeding-edge GHC features, and as a result, it only supports GHC 9.0 or later. * singletons-base: A library that uses singletons-th to define promoted and singled functions from the base library, including the Prelude. Similarly to singletons-th, this library only supports GHC 9.0 or later. Previous singletons releases combined all of this functionality into a single library. However, discussions with singletons users revealed that this was a frequent source of pain: * The total time it took to compile the old singletons library dissuaded some from using it, especially for those who only wanted to use a small part of the library. * Some users wished to use singletons in environments where Template Haskell is not an option. * Some users wanted to use core definitions from Data.Singletons, but because the old singletons library only ever supported one GHC at a time, this was impractical. The new package structure in the 3.0 release is an attempt to address some of these pain points. In particular, most of the code which results in extensive compile times is now confined to the singletons-base library. For the full discussion that led up to this, see [1]. ########################### ## Module reorganization ## ########################### Splitting up singletons into smaller packages provided a rare opportunity to clean up the module naming conventions, which were confusing and inconsistent in many places. The 3.0 releases now use the following conventions: * All modules in singletons now begin with Data.Singletons.*. * All modules in singletons-th now begin with Data.Singletons.TH.*. * Most modules in singletons-base now reflect the modules from base from which they take inspiration. For example, the Prelude module now has a Prelude.Singletons counterpart in singletons. Similarly, there are also modules like Control.Monad.Singletons, GHC.TypeLits.Singletons, etc. All other modules that do not correspond to something in base now begin with Data.Singletons.Base.*. The convention now used in singletons-base was inspired by the conventions used in the lens library. The end result is that is now somewhat easier to figure out what parts of singletons-base to import. Because this is a significant departure from previous singletons releases, if you want to continue supporting pre-3.0 releases, you will likely need to put something like this in your .cabal file: flag singletons-3-0 description: Use @singletons-3.0@ or later. default: True library ... if flag(singletons-3-0) build-depends: singletons-base >= 3.0 -- You may also need to depend on singletons >= 3.0 or singletons-th >= 3.0 else build-depends: singletons < 3.0 ################### ## Other changes ## ################### Besides the package and module reorganization mentioned above, singletons-{,th,base}-3.0 feature a variety of new quality-of-life improvements. Here are a handful of the more notable improvements: * The OptionsM type, used for configuring how the Template Haskell machinery in singletons-th works, is now an instance of Quote. This avoids the need to use the Control.Monad.Trans.Class.lift function to lift quoted declarations into OptionsM. [2] * Data.Singletons.TH.Options now defines a promotedDataTypeOrConName option. Overriding this option can be useful in situations where one wishes to promote types such as `Nat`, `Symbol`, or data types built on top of them. [3] * The internals of the ShowSing class have been refactored to allow deriving Show instances for Sing types (e.g., deriving instance ShowSing a => Show (SList (z :: [a]))). [4] * Improve the quality of GHCi's output when using :kind on types defined by singletons-th. [5] If you encounter any issues, feel free to leave a bug report at https://github.com/goldfirere/singletons/issues. Happy (type-level) hacking, Ryan S. ----- [1] https://github.com/goldfirere/singletons/issues/420 [2] https://github.com/goldfirere/singletons/pull/484 [3] https://github.com/goldfirere/singletons/pull/462 [4] https://github.com/goldfirere/singletons/pull/486 [5] https://github.com/goldfirere/singletons/pull/446 From lemming at henning-thielemann.de Fri Mar 12 17:36:56 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Fri, 12 Mar 2021 18:36:56 +0100 (CET) Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <46ca1e58-8d6b-eba0-c330-ca7cfde63cbd@henning-thielemann.de> <3b848f77-f399-9455-7170-2d9cc92e4094@glitchbra.in> Message-ID: On Fri, 12 Mar 2021, Bryan Richter wrote: > Rather than suggesting "State your intention to take over the package in > a public forum ", step 2 should lighten up and state, "After trying to > reach the maintainer for a reasonable amount of time, reach out to the > public to expand your search." Sounds much better to me. > https://wiki.haskell.org/Taking_over_a_package From carter.schonwald at gmail.com Fri Mar 12 17:37:52 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 12 Mar 2021 12:37:52 -0500 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <46ca1e58-8d6b-eba0-c330-ca7cfde63cbd@henning-thielemann.de> <3b848f77-f399-9455-7170-2d9cc92e4094@glitchbra.in> Message-ID: But that’s in fact what happened here! :) On Fri, Mar 12, 2021 at 12:27 PM Bryan Richter wrote: > Can I suggest to the Hackage Whoever a slight change in policy? > > I think the shock of seeing a package takeover request for your own > package is understandably, uh, shocking, and makes the ensuing discussion > tense. I also feel like most takeover requests follow this pattern; rarely > does a package end up changing hands. > > Perhaps it's a problem of tone. > > Rather than suggesting "State your intention to take over the package in a > public forum ", step 2 should lighten up and state, "After trying to reach > the maintainer for a reasonable amount of time, reach out to the public to > expand your search." > > https://wiki.haskell.org/Taking_over_a_package > > On Fri, 12 Mar 2021, 18.59 Henning Thielemann, < > lemming at henning-thielemann.de> wrote: > >> >> On Fri, 12 Mar 2021, Brandon Allbery wrote: >> >> > That depends. Can I in fact, were I looking for a maintainer, find out >> > who to contact about the package? Ideally without much digging. >> >> That's what the Cabal.Maintainer field is for. It is missing in toml, >> which is bad. > > _______________________________________________ > 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 carter.schonwald at gmail.com Fri Mar 12 17:38:27 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 12 Mar 2021 12:38:27 -0500 Subject: [Haskell-cafe] [ANN] singletons-3.0, singletons-th-3.0, and singletons-base-3.0 In-Reply-To: References: Message-ID: This is fantastic! On Fri, Mar 12, 2021 at 12:31 PM Ryan Scott wrote: > I'm happy to announce the 3.0 release of the singletons library, as > well as the debut of its companion libraries, singletons-th and > singletons-base. There's been a fair bit of improvements, cleanup, and > reorganization since the last release, so I thought it appropriate to > give this release a super-major version bump. This announcement will > go over some highlights of the new releases, but if you want the full > details, you can consult the changelog entries for each library below: > > * singletons-3.0: > http://hackage.haskell.org/package/singletons-3.0/changelog > * singletons-th-3.0: > http://hackage.haskell.org/package/singletons-th-3.0/changelog > * singletons-base-3.0: > http://hackage.haskell.org/package/singletons-base-3.0/changelog > > ########################## > ## Why three libraries? ## > ########################## > > Instead of there just being one singletons library, there are now > _three_ libraries: > > * singletons: A small, foundational library that defines basic > singleton-related types and definitions. The new singletons library > supports GHC 8.0 or later, does not depend on any external libraries, > and does not make use of Template Haskell. > * singletons-th: A library that defines Template Haskell functionality > for promoting term-level functions to type-level equivalents and > singling functions to dependently typed equivalents. This library > requires bleeding-edge GHC features, and as a result, it only supports > GHC 9.0 or later. > * singletons-base: A library that uses singletons-th to define > promoted and singled functions from the base library, including the > Prelude. Similarly to singletons-th, this library only supports GHC > 9.0 or later. > > Previous singletons releases combined all of this functionality into a > single library. However, discussions with singletons users revealed > that this was a frequent source of pain: > > * The total time it took to compile the old singletons library > dissuaded some from using it, especially for those who only wanted to > use a small part of the library. > * Some users wished to use singletons in environments where Template > Haskell is not an option. > * Some users wanted to use core definitions from Data.Singletons, but > because the old singletons library only ever supported one GHC at a > time, this was impractical. > > The new package structure in the 3.0 release is an attempt to address > some of these pain points. In particular, most of the code which > results in extensive compile times is now confined to the > singletons-base library. For the full discussion that led up to this, > see [1]. > > ########################### > ## Module reorganization ## > ########################### > > Splitting up singletons into smaller packages provided a rare > opportunity to clean up the module naming conventions, which were > confusing and inconsistent in many places. The 3.0 releases now use > the following conventions: > > * All modules in singletons now begin with Data.Singletons.*. > * All modules in singletons-th now begin with Data.Singletons.TH.*. > * Most modules in singletons-base now reflect the modules from base > from which they take inspiration. For example, the Prelude module now > has a Prelude.Singletons counterpart in singletons. Similarly, there > are also modules like Control.Monad.Singletons, > GHC.TypeLits.Singletons, etc. All other modules that do not correspond > to something in base now begin with Data.Singletons.Base.*. > > The convention now used in singletons-base was inspired by the > conventions used in the lens library. The end result is that is now > somewhat easier to figure out what parts of singletons-base to import. > Because this is a significant departure from previous singletons > releases, if you want to continue supporting pre-3.0 releases, you > will likely need to put something like this in your .cabal file: > > flag singletons-3-0 > description: Use @singletons-3.0@ or later. > default: True > > library > ... > if flag(singletons-3-0) > build-depends: > singletons-base >= 3.0 > -- You may also need to depend on singletons >= 3.0 or > singletons-th >= 3.0 > else > build-depends: > singletons < 3.0 > > ################### > ## Other changes ## > ################### > > Besides the package and module reorganization mentioned above, > singletons-{,th,base}-3.0 feature a variety of new quality-of-life > improvements. Here are a handful of the more notable improvements: > > * The OptionsM type, used for configuring how the Template Haskell > machinery in singletons-th works, is now an instance of Quote. This > avoids the need to use the Control.Monad.Trans.Class.lift function to > lift quoted declarations into OptionsM. [2] > * Data.Singletons.TH.Options now defines a promotedDataTypeOrConName > option. Overriding this option can be useful in situations where one > wishes to promote types such as `Nat`, `Symbol`, or data types built > on top of them. [3] > * The internals of the ShowSing class have been refactored to allow > deriving Show instances for Sing types (e.g., deriving instance > ShowSing a => Show (SList (z :: [a]))). [4] > * Improve the quality of GHCi's output when using :kind on types > defined by singletons-th. [5] > > If you encounter any issues, feel free to leave a bug report at > https://github.com/goldfirere/singletons/issues. > > Happy (type-level) hacking, > > Ryan S. > ----- > [1] https://github.com/goldfirere/singletons/issues/420 > [2] https://github.com/goldfirere/singletons/pull/484 > [3] https://github.com/goldfirere/singletons/pull/462 > [4] https://github.com/goldfirere/singletons/pull/486 > [5] https://github.com/goldfirere/singletons/pull/446 > _______________________________________________ > 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 amindfv at mailbox.org Fri Mar 12 18:02:12 2021 From: amindfv at mailbox.org (amindfv at mailbox.org) Date: Fri, 12 Mar 2021 11:02:12 -0700 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: <20210312115006.GG15063@cloudinit-builder> References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <46ca1e58-8d6b-eba0-c330-ca7cfde63cbd@henning-thielemann.de> <20210312115006.GG15063@cloudinit-builder> Message-ID: <20210312180212.GA19829@painter.painter> On Fri, Mar 12, 2021 at 11:50:06AM +0000, Tom Ellis wrote: > On Fri, Mar 12, 2021 at 12:36:16PM +0100, Henning Thielemann wrote: > > On Thu, 11 Mar 2021, amindfv--- via Haskell-Cafe wrote: > > > Again, trying to be respectful here, but "burning" kinda does imply > > > "fire," and "need" certainly does imply "need." It's now seeming more > > > just like a desire for the package name. > > > > I have nothing to do with 'toml' but the many takeover requests in the > > recent past make me nervous that if I am away from Haskell programming for > > some weeks or months brings me in danger of losing my packages. Btw. for > > some years I was not subscribed to Haskell Cafe because of high traffic and > > I would have missed such takeover request. I think the preference should be > > to create a fork. > > This raises an interesting question: to whom does the entry in the > package namespace belong? There's a tacit assumption that it belongs > to the first person who registered it. Arguably though it could be > deemed to belong to the community. The more "generic" the name the > more water that argument seems to hold. > As I said earlier, I'm open to this line of reasoning if there's a clear winner in terms of mindshare and functionality. As it is there are multiple popular, relatively mature packages, and the request was to give the name to a project which doesn't yet exist except in stub form. "Belonging to the community" is a tricky concept, too - imagine the community speaks and declares tomland the winner, and tomland gets moved to the 'toml' namespace. Then, a couple years down the line, people find they want streaming parsing and in the meantime Carter and Emily have written great code. Do we then kick The Package Formerly Known As Tomland out of the 'toml' spot and put an entirely different project there? That's quite a breaking change for people with 'toml' in their .cabal files. For what it's worth, my rewrite isn't a whole-cloth reimagning but instead is a fairly straightforward modernization of the existing 'toml' code. Tom From amindfv at mailbox.org Fri Mar 12 18:19:07 2021 From: amindfv at mailbox.org (amindfv at mailbox.org) Date: Fri, 12 Mar 2021 11:19:07 -0700 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312055606.GA6517@painter.painter> <46ca1e58-8d6b-eba0-c330-ca7cfde63cbd@henning-thielemann.de> <3b848f77-f399-9455-7170-2d9cc92e4094@glitchbra.in> Message-ID: <20210312181907.GA21481@painter.painter> On Fri, Mar 12, 2021 at 05:59:31PM +0100, Henning Thielemann wrote: > > On Fri, 12 Mar 2021, Brandon Allbery wrote: > > > That depends. Can I in fact, were I looking for a maintainer, find out > > who to contact about the package? Ideally without much digging. > > That's what the Cabal.Maintainer field is for. It is missing in toml, which > is bad. Fixed. > _______________________________________________ > 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 emilypi at cohomolo.gy Fri Mar 12 18:29:15 2021 From: emilypi at cohomolo.gy (Emily Pillmore) Date: Fri, 12 Mar 2021 18:29:15 +0000 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: <20210312180212.GA19829@painter.painter> References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <46ca1e58-8d6b-eba0-c330-ca7cfde63cbd@henning-thielemann.de> <20210312115006.GG15063@cloudinit-builder> <20210312180212.GA19829@painter.painter> Message-ID: Fwiw, I agree with the notion that "belonging to the community" is tricky, and entitled to a certain degree. That being said (and this might be where there is confusion in terms of what everyone believes or doesn't believe surround the subject), I think a diversity of projects that answer a particular need is better than a single monolithic choice. For example, I also work on the `waargonaut` series of libraries which offer an alternative solution to JSON in contrast to `aeson`: a succinct zipper-based approach to parsing which is faster in some cases than the one used in `aeson`, and the controversial stance that deriving JSON schema is an anti-pattern. And despite there being contention in that last point, the succinct-zipper approach has led many to choose it for streaming JSON, and we've been able to POC improvements to the `aeson` parser based on things we've done in `waargonaut`. By no means will `waargonaut` ever be the blessed choice, but it is still useful and valuable just for existing and trying something different. So in my mind, at least, competition is friendly and doesn't dilute any particular market share if it's significantly different. At the very least, I'd like to at least not have `toml` in its current state appear as a viable candidate in the list of hackage packages without being more up to date and presenting a sound choice, if not the most ideal. And i'm perfectly happy with saying "Hey, Tom got here first, c'est la vie" and helping him renovate the library if he's just looking at modernizing the existing code! This doesn't really entail kicking anyone out or blessing any package in particular. It's more janitorial to me. - E On Fri, Mar 12, 2021 at 1:02 PM, amindfv--- < haskell-cafe at haskell.org > wrote: > > > > On Fri, Mar 12, 2021 at 11:50:06AM +0000, Tom Ellis wrote: > > >> >> >> On Fri, Mar 12, 2021 at 12:36:16PM +0100, Henning Thielemann wrote: >> >> >>> >>> >>> On Thu, 11 Mar 2021, amindfv--- via Haskell-Cafe wrote: >>> >>> >>>> >>>> >>>> Again, trying to be respectful here, but "burning" kinda does imply >>>> "fire," and "need" certainly does imply "need." It's now seeming more just >>>> like a desire for the package name. >>>> >>>> >>> >>> >>> >>> I have nothing to do with 'toml' but the many takeover requests in the >>> recent past make me nervous that if I am away from Haskell programming for >>> some weeks or months brings me in danger of losing my packages. Btw. for >>> some years I was not subscribed to Haskell Cafe because of high traffic >>> and I would have missed such takeover request. I think the preference >>> should be to create a fork. >>> >>> >> >> >> >> This raises an interesting question: to whom does the entry in the package >> namespace belong? There's a tacit assumption that it belongs to the first >> person who registered it. Arguably though it could be deemed to belong to >> the community. The more "generic" the name the more water that argument >> seems to hold. >> >> > > > > As I said earlier, I'm open to this line of reasoning if there's a clear > winner in terms of mindshare and functionality. As it is there are > multiple popular, relatively mature packages, and the request was to give > the name to a project which doesn't yet exist except in stub form. > > > > "Belonging to the community" is a tricky concept, too - imagine the > community speaks and declares tomland the winner, and tomland gets moved > to the 'toml' namespace. Then, a couple years down the line, people find > they want streaming parsing and in the meantime Carter and Emily have > written great code. Do we then kick The Package Formerly Known As Tomland > out of the 'toml' spot and put an entirely different project there? That's > quite a breaking change for people with 'toml' in their .cabal files. > > > > For what it's worth, my rewrite isn't a whole-cloth reimagning but instead > is a fairly straightforward modernization of the existing 'toml' code. > > > > Tom > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: http:/ / mail. haskell. > org/ cgi-bin/ mailman/ listinfo/ haskell-cafe ( > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe ) Only > members subscribed via the mailman list are allowed to post. > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From amindfv at mailbox.org Fri Mar 12 18:29:47 2021 From: amindfv at mailbox.org (amindfv at mailbox.org) Date: Fri, 12 Mar 2021 11:29:47 -0700 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312055606.GA6517@painter.painter> <46ca1e58-8d6b-eba0-c330-ca7cfde63cbd@henning-thielemann.de> <3b848f77-f399-9455-7170-2d9cc92e4094@glitchbra.in> Message-ID: <20210312182947.GB21481@painter.painter> On Fri, Mar 12, 2021 at 07:15:12PM +0200, Bryan Richter wrote: > Can I suggest to the Hackage Whoever a slight change in policy? > > I think the shock of seeing a package takeover request for your own package > is understandably, uh, shocking, and makes the ensuing discussion tense. I > also feel like most takeover requests follow this pattern; rarely does a > package end up changing hands. > > Perhaps it's a problem of tone. I wasn't at all shocked at the original request. I figured, correctly, Emily had looked at the package on Hackage and not seen a maintainer listed. Seemed like an easy fix. If you look at the original messages I was ready and willing to help. The shock, if there was any, came from what felt like an unwarranted claim of an urgent need, and a push to take it over even after I materialized. > > Rather than suggesting "State your intention to take over the package in a > public forum ", step 2 should lighten up and state, "After trying to reach > the maintainer for a reasonable amount of time, reach out to the public to > expand your search." I don't have a problem with the original wording but I do like your change. Tom > > https://wiki.haskell.org/Taking_over_a_package > > On Fri, 12 Mar 2021, 18.59 Henning Thielemann, < > lemming at henning-thielemann.de> wrote: > > > > > On Fri, 12 Mar 2021, Brandon Allbery wrote: > > > > > That depends. Can I in fact, were I looking for a maintainer, find out > > > who to contact about the package? Ideally without much digging. > > > > That's what the Cabal.Maintainer field is for. It is missing in toml, > > which is bad. > _______________________________________________ > 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 amindfv at mailbox.org Fri Mar 12 18:38:53 2021 From: amindfv at mailbox.org (amindfv at mailbox.org) Date: Fri, 12 Mar 2021 11:38:53 -0700 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <46ca1e58-8d6b-eba0-c330-ca7cfde63cbd@henning-thielemann.de> <3b848f77-f399-9455-7170-2d9cc92e4094@glitchbra.in> Message-ID: <20210312183853.GC21481@painter.painter> On Fri, Mar 12, 2021 at 06:57:59PM +0200, Imants Cekusins wrote: > Let's see how soon the next version is uploaded with maintainer and > repo specified. A repo would be nice, wouldn't it? Tbh this type of scrutiny is making me less likely to want to publish unfinished code because it would only open me up to criticism (this code doesn't have feature X, I don't think this code is being worked on fast enough, etc.). I've already said I'll give up the package name if there's a clear consensus from the larger community. A WIP repo might be nice for you but I'm not required to publish anything before I feel it's ready. Tom From imantc at gmail.com Fri Mar 12 19:55:08 2021 From: imantc at gmail.com (Imants Cekusins) Date: Fri, 12 Mar 2021 21:55:08 +0200 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: <20210312183853.GC21481@painter.painter> References: <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <46ca1e58-8d6b-eba0-c330-ca7cfde63cbd@henning-thielemann.de> <3b848f77-f399-9455-7170-2d9cc92e4094@glitchbra.in> <20210312183853.GC21481@painter.painter> Message-ID: Well, a repo with history of the published code is often specified in the .cabal file. This allows for overview of changes between versions. Forks and PRs are also convenient. A few repo hosts also include issue tracker which can also be used to communicate with authors / maintainers. Clarity helps. On Fri 12 Mar 2021, 20:38 amindfv at mailbox.org, wrote: > On Fri, Mar 12, 2021 at 06:57:59PM +0200, Imants Cekusins wrote: > > > Let's see how soon the next version is uploaded with maintainer and > > repo specified. A repo would be nice, wouldn't it? > > Tbh this type of scrutiny is making me less likely to want to publish > unfinished code because it would only open me up to criticism (this code > doesn't have feature X, I don't think this code is being worked on fast > enough, etc.). I've already said I'll give up the package name if there's a > clear consensus from the larger community. A WIP repo might be nice for you > but I'm not required to publish anything before I feel it's ready. > > Tom > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From gershomb at gmail.com Fri Mar 12 21:26:24 2021 From: gershomb at gmail.com (Gershom B) Date: Fri, 12 Mar 2021 16:26:24 -0500 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <46ca1e58-8d6b-eba0-c330-ca7cfde63cbd@henning-thielemann.de> <3b848f77-f399-9455-7170-2d9cc92e4094@glitchbra.in> Message-ID: On Mar 12, 2021, 12:27 PM -0500, Bryan Richter , wrote: > Can I suggest to the Hackage Whoever a slight change in policy? > > I think the shock of seeing a package takeover request for your own package is understandably, uh, shocking, and makes the ensuing discussion tense. I also feel like most takeover requests follow this pattern; rarely does a package end up changing hands. > > Perhaps it's a problem of tone. > > Rather than suggesting "State your intention to take over the package in a public forum ", step 2 should lighten up and state, "After trying to reach the maintainer for a reasonable amount of time, reach out to the public to expand your search." > > https://wiki.haskell.org/Taking_over_a_package > The proposed change is not just a tone change. The point of step 2 is that an official request be filed in a public forum and sufficient time then pass that we can be confident the maintainer has been publicly informed of the issue. It’s not about having a heavy tone or the like. This whole fracas is simply the result of confusion and miscommunication — a package appeared unmaintained, but it turned out that there was a maintainer, but it was hard to tell because the maintainer was not listed on the last uploaded package. The correct fix for this is everyone chill out, go for a walk, and then get on with more productive things. By the way, I should mention that there _is_ a hackage audit log of who has been added to maintainer (and trustee and admin) groups, and by whom, since there seemed to be some confusion about that. Best, Gershom -------------- next part -------------- An HTML attachment was scrubbed... URL: From borgauf at gmail.com Fri Mar 12 22:01:18 2021 From: borgauf at gmail.com (Galaxy Being) Date: Fri, 12 Mar 2021 16:01:18 -0600 Subject: [Haskell-cafe] SML vs Haskell types Message-ID: Hello, This is my first post here, and it's an odd one, I'll admit. Basically, I'm trying to translate the material in *The Little MLer *to Haskell, the TLMLer being an excellent types workout. So in SML I have this datatype 'a shish = Bottom of 'a | Onion of 'a shish | Lamb of 'a shish | Tomato of 'a shish and this datatype rod = Dagger | Fork | Sword and then this SML function fun is_veggie (Bottom (x)) = true | is_veggie (Onion (x)) = is_veggie (x) | is_veggie (Lamb (x)) = false | is_veggie (Tomato (x)) = is_veggie (x) which has no problem handling tis is_veggie (Onion(Tomato(Bottom(Dagger)))) Now, in Haskell I've translated this (with minor alterations) to data Shish a = Holder a | Onion a (Shish a) | Lamb a (Shish a) | Tomato a (Shish a) data Rod = Dagger | Fork | Sword However, in Haskell these two expressions are different things entirely meal4 = Tomato Dagger (Onion Fork (Lamb Spear (Holder Fork))) meal5 = (Tomato (Onion (Lamb (Holder Fork)))) Here's my attempt at handling meal4 with a Haskell isVeggie isVeggie (Holder (sh)) = True isVeggie (Onion sh (sk)) = isVeggie sk isVeggie (Tomato sh (sk)) = isVeggie sk isVeggie (Lamb sh (sk)) = False This works for meal4, but not for meal5. And yet in the SML world their is_veggie handles (Onion(Tomato(Bottom(Dagger)))) just fine. TLMLer says Onion (Tomato (Bottom (Dagger))) belongs to the type rod shish, while in Haskell Onion (Tomato (Holder (Dagger))) is a bizarre nested beast due to the fact that the data constructor variable of Onion is Tomato (Holder (Dagger)) etc. etc. Can a single Haskell version of isVeggie handle both meal4 and meal5? No? I thought so. But then how would a separate Haskell version of isVeggie handle meal5 -- or is it just too weird? Also, but not critical, how could the Haskell isVeggie be done with guards, i.e., just like a consed list is matched on (x:xs) in the recursion case? I can see that 1:2:3:[] and Onion (Tomato (Bottom (Dagger))) are both conses, but the latter I don't know how to break out into head and tail for a guard case where the individual food items were not mentioned explicitly. IOW, this doesn't work isVeggieKebab :: Shish -> Bool isVeggieKebab Holder (sk) = True isVeggieKebab (shkb (sk)) | (shkb == Onion) || (shkb == Tomato) = isVeggieKebab sk | otherwise = False I'm feeling some doom and gloom about this project. Right at the start this seems to be an insurmountable difference between SML and Haskell type systems. Or I simply don't understand something fundamental here. LB -------------- next part -------------- An HTML attachment was scrubbed... URL: From tikhon at jelv.is Fri Mar 12 22:08:28 2021 From: tikhon at jelv.is (Tikhon Jelvis) Date: Fri, 12 Mar 2021 14:08:28 -0800 Subject: [Haskell-cafe] SML vs Haskell types In-Reply-To: References: Message-ID: Onion of 'a shish is equivalent to Onion (Shish a) in Haskell rather than Onion a (Shish a). The latter version in Haskell creates a constructor with two arguments, something like Onion of ('a * 'a shish) would in SML. (Or, at least, OCaml—not 100% familiar with SML syntax myself!) On Fri, Mar 12, 2021, 14:03 Galaxy Being wrote: > Hello, > > This is my first post here, and it's an odd one, I'll admit. Basically, > I'm trying to translate the material in *The Little MLer *to Haskell, the > TLMLer being an excellent types workout. So in SML I have this > > datatype 'a shish = Bottom of 'a | Onion of 'a shish | Lamb of 'a shish | > Tomato of 'a shish > > and this > > datatype rod = Dagger | Fork | Sword > > and then this SML function > > fun is_veggie (Bottom (x)) = true > | is_veggie (Onion (x)) = is_veggie (x) > | is_veggie (Lamb (x)) = false > | is_veggie (Tomato (x)) = is_veggie (x) > > which has no problem handling tis > > is_veggie (Onion(Tomato(Bottom(Dagger)))) > > Now, in Haskell I've translated this (with minor alterations) to > > data Shish a = Holder a | Onion a (Shish a) | Lamb a (Shish a) | Tomato a > (Shish a) > data Rod = Dagger | Fork | Sword > > However, in Haskell these two expressions are different things entirely > > meal4 = Tomato Dagger (Onion Fork (Lamb Spear (Holder Fork))) > meal5 = (Tomato (Onion (Lamb (Holder Fork)))) > > Here's my attempt at handling meal4 with a Haskell isVeggie > > isVeggie (Holder (sh)) = True > isVeggie (Onion sh (sk)) = isVeggie sk > isVeggie (Tomato sh (sk)) = isVeggie sk > isVeggie (Lamb sh (sk)) = False > > This works for meal4, but not for meal5. And yet in the SML world their > is_veggie handles (Onion(Tomato(Bottom(Dagger)))) just fine. TLMLer says > > Onion (Tomato (Bottom (Dagger))) > > belongs to the type rod shish, while in Haskell > > Onion (Tomato (Holder (Dagger))) > > is a bizarre nested beast due to the fact that the data constructor > variable of Onion is Tomato (Holder (Dagger)) etc. etc. > > Can a single Haskell version of isVeggie handle both meal4 and meal5? No? > I thought so. But then how would a separate Haskell version of isVeggie > handle meal5 -- or is it just too weird? Also, but not critical, how > could the Haskell isVeggie be done with guards, i.e., just like a consed > list is matched on (x:xs) in the recursion case? I can see that 1:2:3:[] > and Onion (Tomato (Bottom (Dagger))) are both conses, but the latter I > don't know how to break out into head and tail for a guard case where the > individual food items were not mentioned explicitly. IOW, this doesn't work > > isVeggieKebab :: Shish -> Bool > isVeggieKebab Holder (sk) = True > isVeggieKebab (shkb (sk)) | (shkb == Onion) || (shkb == Tomato) = > isVeggieKebab sk > | otherwise = False > > I'm feeling some doom and gloom about this project. Right at the start > this seems to be an insurmountable difference between SML and Haskell type > systems. Or I simply don't understand something fundamental here. > > LB > > > _______________________________________________ > 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 borgauf at gmail.com Fri Mar 12 22:21:35 2021 From: borgauf at gmail.com (Galaxy Being) Date: Fri, 12 Mar 2021 16:21:35 -0600 Subject: [Haskell-cafe] SML vs Haskell types In-Reply-To: References: Message-ID: So are you saying data Shish2 a = Holder2 a | Onion (Shish a) | Lamb (Shish a) | Tomato (Shish a) but then I'm having trouble with meal6 = (Onion (Tomato (Lamb (Holder2 (Fork))))) Couldn't match expected type `Shish a1' with actual type `Shish2 a0' * In the first argument of `Tomato', namely `(Lamb (Holder2 (Fork)))' In the first argument of `Onion', namely `(Tomato (Lamb (Holder2 (Fork))))' In the expression: (Onion (Tomato (Lamb (Holder2 (Fork))) On Fri, Mar 12, 2021 at 4:08 PM Tikhon Jelvis wrote: > Onion of 'a shish is equivalent to Onion (Shish a) in Haskell rather than > Onion a (Shish a). > > The latter version in Haskell creates a constructor with two arguments, > something like Onion of ('a * 'a shish) would in SML. (Or, at least, > OCaml—not 100% familiar with SML syntax myself!) > > On Fri, Mar 12, 2021, 14:03 Galaxy Being wrote: > >> Hello, >> >> This is my first post here, and it's an odd one, I'll admit. Basically, >> I'm trying to translate the material in *The Little MLer *to Haskell, >> the TLMLer being an excellent types workout. So in SML I have this >> >> datatype 'a shish = Bottom of 'a | Onion of 'a shish | Lamb of 'a shish | >> Tomato of 'a shish >> >> and this >> >> datatype rod = Dagger | Fork | Sword >> >> and then this SML function >> >> fun is_veggie (Bottom (x)) = true >> | is_veggie (Onion (x)) = is_veggie (x) >> | is_veggie (Lamb (x)) = false >> | is_veggie (Tomato (x)) = is_veggie (x) >> >> which has no problem handling tis >> >> is_veggie (Onion(Tomato(Bottom(Dagger)))) >> >> Now, in Haskell I've translated this (with minor alterations) to >> >> data Shish a = Holder a | Onion a (Shish a) | Lamb a (Shish a) | Tomato a >> (Shish a) >> data Rod = Dagger | Fork | Sword >> >> However, in Haskell these two expressions are different things entirely >> >> meal4 = Tomato Dagger (Onion Fork (Lamb Spear (Holder Fork))) >> meal5 = (Tomato (Onion (Lamb (Holder Fork)))) >> >> Here's my attempt at handling meal4 with a Haskell isVeggie >> >> isVeggie (Holder (sh)) = True >> isVeggie (Onion sh (sk)) = isVeggie sk >> isVeggie (Tomato sh (sk)) = isVeggie sk >> isVeggie (Lamb sh (sk)) = False >> >> This works for meal4, but not for meal5. And yet in the SML world their >> is_veggie handles (Onion(Tomato(Bottom(Dagger)))) just fine. TLMLer says >> >> Onion (Tomato (Bottom (Dagger))) >> >> belongs to the type rod shish, while in Haskell >> >> Onion (Tomato (Holder (Dagger))) >> >> is a bizarre nested beast due to the fact that the data constructor >> variable of Onion is Tomato (Holder (Dagger)) etc. etc. >> >> Can a single Haskell version of isVeggie handle both meal4 and meal5? >> No? I thought so. But then how would a separate Haskell version of >> isVeggie handle meal5 -- or is it just too weird? Also, but not >> critical, how could the Haskell isVeggie be done with guards, i.e., just >> like a consed list is matched on (x:xs) in the recursion case? I can see >> that 1:2:3:[] and Onion (Tomato (Bottom (Dagger))) are both conses, but >> the latter I don't know how to break out into head and tail for a guard >> case where the individual food items were not mentioned explicitly. IOW, >> this doesn't work >> >> isVeggieKebab :: Shish -> Bool >> isVeggieKebab Holder (sk) = True >> isVeggieKebab (shkb (sk)) | (shkb == Onion) || (shkb == Tomato) = >> isVeggieKebab sk >> | otherwise = False >> >> I'm feeling some doom and gloom about this project. Right at the start >> this seems to be an insurmountable difference between SML and Haskell type >> systems. Or I simply don't understand something fundamental here. >> >> LB >> >> >> _______________________________________________ >> 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 bob at redivi.com Fri Mar 12 22:44:32 2021 From: bob at redivi.com (Bob Ippolito) Date: Fri, 12 Mar 2021 14:44:32 -0800 Subject: [Haskell-cafe] SML vs Haskell types In-Reply-To: References: Message-ID: I think the problem is that you have a typo such that this Shish2 is dependent on some other data type named Shish. If you change the type name to Shish (or change its definition to use Shish2) it works fine. data Shish a = Holder2 a | Onion (Shish a) | Lamb (Shish a) | Tomato (Shish a) deriving Show data Rod = Dagger | Fork | Sword deriving Show meal6 = (Onion (Tomato (Lamb (Holder2 (Fork))))) On Fri, Mar 12, 2021 at 2:23 PM Galaxy Being wrote: > So are you saying > > data Shish2 a = Holder2 a | Onion (Shish a) | Lamb (Shish a) | Tomato > (Shish a) > > but then I'm having trouble with > > meal6 = (Onion (Tomato (Lamb (Holder2 (Fork))))) > > Couldn't match expected type `Shish a1' > with actual type `Shish2 a0' > * In the first argument of `Tomato', namely > `(Lamb (Holder2 (Fork)))' > In the first argument of `Onion', namely > `(Tomato (Lamb (Holder2 (Fork))))' > In the expression: (Onion (Tomato (Lamb (Holder2 (Fork))) > > > > > On Fri, Mar 12, 2021 at 4:08 PM Tikhon Jelvis wrote: > >> Onion of 'a shish is equivalent to Onion (Shish a) in Haskell rather than >> Onion a (Shish a). >> >> The latter version in Haskell creates a constructor with two arguments, >> something like Onion of ('a * 'a shish) would in SML. (Or, at least, >> OCaml—not 100% familiar with SML syntax myself!) >> >> On Fri, Mar 12, 2021, 14:03 Galaxy Being wrote: >> >>> Hello, >>> >>> This is my first post here, and it's an odd one, I'll admit. Basically, >>> I'm trying to translate the material in *The Little MLer *to Haskell, >>> the TLMLer being an excellent types workout. So in SML I have this >>> >>> datatype 'a shish = Bottom of 'a | Onion of 'a shish | Lamb of 'a >>> shish | Tomato of 'a shish >>> >>> and this >>> >>> datatype rod = Dagger | Fork | Sword >>> >>> and then this SML function >>> >>> fun is_veggie (Bottom (x)) = true >>> | is_veggie (Onion (x)) = is_veggie (x) >>> | is_veggie (Lamb (x)) = false >>> | is_veggie (Tomato (x)) = is_veggie (x) >>> >>> which has no problem handling tis >>> >>> is_veggie (Onion(Tomato(Bottom(Dagger)))) >>> >>> Now, in Haskell I've translated this (with minor alterations) to >>> >>> data Shish a = Holder a | Onion a (Shish a) | Lamb a (Shish a) | Tomato >>> a (Shish a) >>> data Rod = Dagger | Fork | Sword >>> >>> However, in Haskell these two expressions are different things entirely >>> >>> meal4 = Tomato Dagger (Onion Fork (Lamb Spear (Holder Fork))) >>> meal5 = (Tomato (Onion (Lamb (Holder Fork)))) >>> >>> Here's my attempt at handling meal4 with a Haskell isVeggie >>> >>> isVeggie (Holder (sh)) = True >>> isVeggie (Onion sh (sk)) = isVeggie sk >>> isVeggie (Tomato sh (sk)) = isVeggie sk >>> isVeggie (Lamb sh (sk)) = False >>> >>> This works for meal4, but not for meal5. And yet in the SML world their >>> is_veggie handles (Onion(Tomato(Bottom(Dagger)))) just fine. TLMLer >>> says >>> >>> Onion (Tomato (Bottom (Dagger))) >>> >>> belongs to the type rod shish, while in Haskell >>> >>> Onion (Tomato (Holder (Dagger))) >>> >>> is a bizarre nested beast due to the fact that the data constructor >>> variable of Onion is Tomato (Holder (Dagger)) etc. etc. >>> >>> Can a single Haskell version of isVeggie handle both meal4 and meal5? >>> No? I thought so. But then how would a separate Haskell version of >>> isVeggie handle meal5 -- or is it just too weird? Also, but not >>> critical, how could the Haskell isVeggie be done with guards, i.e., just >>> like a consed list is matched on (x:xs) in the recursion case? I can see >>> that 1:2:3:[] and Onion (Tomato (Bottom (Dagger))) are both conses, but >>> the latter I don't know how to break out into head and tail for a guard >>> case where the individual food items were not mentioned explicitly. IOW, >>> this doesn't work >>> >>> isVeggieKebab :: Shish -> Bool >>> isVeggieKebab Holder (sk) = True >>> isVeggieKebab (shkb (sk)) | (shkb == Onion) || (shkb == Tomato) = >>> isVeggieKebab sk >>> | otherwise = False >>> >>> I'm feeling some doom and gloom about this project. Right at the start >>> this seems to be an insurmountable difference between SML and Haskell type >>> systems. Or I simply don't understand something fundamental here. >>> >>> LB >>> >>> >>> _______________________________________________ >>> 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 borgauf at gmail.com Sat Mar 13 00:59:52 2021 From: borgauf at gmail.com (Galaxy Being) Date: Fri, 12 Mar 2021 18:59:52 -0600 Subject: [Haskell-cafe] SML vs Haskell types In-Reply-To: References: Message-ID: So embarrassing. Thanks. Anyway, this is what works data Shish2 a = Holder2 a | Onion2 (Shish2 a) | Lamb2 (Shish2 a) | Tomato2 (Shish2 a) whatHolder2 (Holder2 (sh)) = sh whatHolder2 (Onion2 (sk)) = whatHolder2 sk whatHolder2 (Tomato2 (sk)) = whatHolder2 sk whatHolder2 (Lamb2 (sk)) = whatHolder2 sk meal6 = (Onion2 (Tomato2 (Lamb2 (Holder2 (Fork))))) > whatHolder2 meal6 Fork However, I'm still wondering how to have an abstracted (x:xs) - like pattern to collapse all the ingredients, i.e., whatHolder2 (Holder2 (sh)) = sh whatHolder2 (shish2-head (shish2-tail)) = whatHolder2 shish2-tail On Fri, Mar 12, 2021 at 4:44 PM Bob Ippolito wrote: > I think the problem is that you have a typo such that this Shish2 is > dependent on some other data type named Shish. If you change the type name > to Shish (or change its definition to use Shish2) it works fine. > > data Shish a = Holder2 a | Onion (Shish a) | Lamb (Shish a) | Tomato > (Shish a) deriving Show > data Rod = Dagger | Fork | Sword deriving Show > > meal6 = (Onion (Tomato (Lamb (Holder2 (Fork))))) > > > On Fri, Mar 12, 2021 at 2:23 PM Galaxy Being wrote: > >> So are you saying >> >> data Shish2 a = Holder2 a | Onion (Shish a) | Lamb (Shish a) | Tomato >> (Shish a) >> >> but then I'm having trouble with >> >> meal6 = (Onion (Tomato (Lamb (Holder2 (Fork))))) >> >> Couldn't match expected type `Shish a1' >> with actual type `Shish2 a0' >> * In the first argument of `Tomato', namely >> `(Lamb (Holder2 (Fork)))' >> In the first argument of `Onion', namely >> `(Tomato (Lamb (Holder2 (Fork))))' >> In the expression: (Onion (Tomato (Lamb (Holder2 (Fork))) >> >> >> >> >> On Fri, Mar 12, 2021 at 4:08 PM Tikhon Jelvis wrote: >> >>> Onion of 'a shish is equivalent to Onion (Shish a) in Haskell rather >>> than Onion a (Shish a). >>> >>> The latter version in Haskell creates a constructor with two arguments, >>> something like Onion of ('a * 'a shish) would in SML. (Or, at least, >>> OCaml—not 100% familiar with SML syntax myself!) >>> >>> On Fri, Mar 12, 2021, 14:03 Galaxy Being wrote: >>> >>>> Hello, >>>> >>>> This is my first post here, and it's an odd one, I'll admit. Basically, >>>> I'm trying to translate the material in *The Little MLer *to Haskell, >>>> the TLMLer being an excellent types workout. So in SML I have this >>>> >>>> datatype 'a shish = Bottom of 'a | Onion of 'a shish | Lamb of 'a >>>> shish | Tomato of 'a shish >>>> >>>> and this >>>> >>>> datatype rod = Dagger | Fork | Sword >>>> >>>> and then this SML function >>>> >>>> fun is_veggie (Bottom (x)) = true >>>> | is_veggie (Onion (x)) = is_veggie (x) >>>> | is_veggie (Lamb (x)) = false >>>> | is_veggie (Tomato (x)) = is_veggie (x) >>>> >>>> which has no problem handling tis >>>> >>>> is_veggie (Onion(Tomato(Bottom(Dagger)))) >>>> >>>> Now, in Haskell I've translated this (with minor alterations) to >>>> >>>> data Shish a = Holder a | Onion a (Shish a) | Lamb a (Shish a) | Tomato >>>> a (Shish a) >>>> data Rod = Dagger | Fork | Sword >>>> >>>> However, in Haskell these two expressions are different things entirely >>>> >>>> meal4 = Tomato Dagger (Onion Fork (Lamb Spear (Holder Fork))) >>>> meal5 = (Tomato (Onion (Lamb (Holder Fork)))) >>>> >>>> Here's my attempt at handling meal4 with a Haskell isVeggie >>>> >>>> isVeggie (Holder (sh)) = True >>>> isVeggie (Onion sh (sk)) = isVeggie sk >>>> isVeggie (Tomato sh (sk)) = isVeggie sk >>>> isVeggie (Lamb sh (sk)) = False >>>> >>>> This works for meal4, but not for meal5. And yet in the SML world >>>> their is_veggie handles (Onion(Tomato(Bottom(Dagger)))) just fine. >>>> TLMLer says >>>> >>>> Onion (Tomato (Bottom (Dagger))) >>>> >>>> belongs to the type rod shish, while in Haskell >>>> >>>> Onion (Tomato (Holder (Dagger))) >>>> >>>> is a bizarre nested beast due to the fact that the data constructor >>>> variable of Onion is Tomato (Holder (Dagger)) etc. etc. >>>> >>>> Can a single Haskell version of isVeggie handle both meal4 and meal5? >>>> No? I thought so. But then how would a separate Haskell version of >>>> isVeggie handle meal5 -- or is it just too weird? Also, but not >>>> critical, how could the Haskell isVeggie be done with guards, i.e., just >>>> like a consed list is matched on (x:xs) in the recursion case? I can see >>>> that 1:2:3:[] and Onion (Tomato (Bottom (Dagger))) are both conses, >>>> but the latter I don't know how to break out into head and tail for a guard >>>> case where the individual food items were not mentioned explicitly. IOW, >>>> this doesn't work >>>> >>>> isVeggieKebab :: Shish -> Bool >>>> isVeggieKebab Holder (sk) = True >>>> isVeggieKebab (shkb (sk)) | (shkb == Onion) || (shkb == Tomato) = >>>> isVeggieKebab sk >>>> | otherwise = False >>>> >>>> I'm feeling some doom and gloom about this project. Right at the start >>>> this seems to be an insurmountable difference between SML and Haskell type >>>> systems. Or I simply don't understand something fundamental here. >>>> >>>> LB >>>> >>>> >>>> _______________________________________________ >>>> 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 cody at codygman.dev Sat Mar 13 01:09:03 2021 From: cody at codygman.dev (Cody Gman) Date: Sat, 13 Mar 2021 02:09:03 +0100 (CET) Subject: [Haskell-cafe] Is Data.Pool not thread-safe or have I done something silly? Message-ID: <334170386.173268.1615597743472@ichabod.co-bxl> I wrote some code with a Data.Pool that has 1 stripe, 1 max resource, and then basically did `Async.replicateConcurrently_ . withResource $ \res -> f res`. I expect withResource to block in each of those threads until the first thread spawned is done with that Resource and releases. To be clear, I get output like: ```shell /tmp $ stack exec --resolver lts-17.5 --package resource-pool --package stm --package hslogger --package time --package concurrent-output -- ghc -O2 -threaded -fwarn-unused-imports testpool.hs && ./testpool acquire 0 - .81428 acquire 1 - .81431 acquire 2 - .81438 acquire 3 - .81440 acquire 4 - .81448 ThreadId 8: processing 1 - .82460 ThreadId 17: processing 4 - .82461 ThreadId 11: processing 2 - .82464 ThreadId 14: processing 3 - .82464 ThreadId 5: processing 0 - .82465 anything else? release 4 - .14427 release 3 - .14430 release 2 - .14431 release 1 - .14431 release 0 - .14432 anything else? anything else? ``` I expect output like: ```shell /tmp $ stack exec --resolver lts-17.5 --package resource-pool --package stm --package hslogger --package time --package concurrent-output -- ghc -O2 -threaded -fwarn-unused-imports testpool.hs && ./testpool [1 of 1] Compiling Main ( testpool.hs, testpool.o ) Linking testpool ... acquire 0 ThreadId 5: processing 0 - .01129 release 0 acquire 1 -- I thought this would have blocked until 0 was released ThreadId 8: processing 1 - .01120 release 1 acquire 2 ThreadId 11: processing 2 - .01123 release 2 acquire 3 ThreadId 14: processing 3 - .01129 release 3 acquire 4 ThreadId 17: processing 4 - .01129 release 4 anything else? anything else? anything else? ``` Here is the code: ``` #!/usr/bin/env stack -- stack script --resolver lts-17.5 --package resource-pool --package stm --package hslogger --package time --package concurrent-output import Control.Concurrent import Control.Concurrent.Async import Control.Concurrent.STM import Data.Pool import Data.Time import System.Console.Concurrent import System.Clock main :: IO () main = do counter <- newTVarIO 0 let acquire = do k <- atomically $ do k <- readTVar counter writeTVar counter (k + 1) return k now <- getTime Monotonic outputConcurrent ("acquire " ++ show k ++ " - "++ show now ++ "\n") return k release k = do now <- getTime Monotonic outputConcurrent ("acquire " ++ show k ++ " - "++ show now ++ "\n") withConcurrentOutput $ do -- create a pool that only allows 1 resource pool <- createPool acquire release 1 500 1 replicateConcurrently_ 5 $ do useResourceFor (seconds 10) pool -- Why do you need these to see the release messages? putStrLn "anything else?" >> threadDelay (seconds 5) putStrLn "anything else?" >> threadDelay (seconds 5) putStrLn "anything else?" >> threadDelay (seconds 5) useResourceFor waitSeconds pool = withResource pool $ \i -> do threadDelay waitSeconds tid <- myThreadId now <- getTime Monotonic outputConcurrent $ show tid <> ": " <> " processing " <> show i <> " - " <> show now <> "\n" seconds = (* 1000000) ``` I'm hoping someone could help explain what I did wrong or confirm it's a bug. Thanks, Cody From b at chreekat.net Sat Mar 13 06:52:16 2021 From: b at chreekat.net (Bryan Richter) Date: Sat, 13 Mar 2021 08:52:16 +0200 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <46ca1e58-8d6b-eba0-c330-ca7cfde63cbd@henning-thielemann.de> <3b848f77-f399-9455-7170-2d9cc92e4094@glitchbra.in> Message-ID: Fair point: my suggestion was unclear. I agree that explicitly stating a takeover request is important. I meant to suggest widening the search as an intermediate step between direct contact with the maintainer and the takeover announcement, itself. It could be step 1.B.? For the record, I think that Emily, Tom, and others acted reasonably and in good faith in this thread, although my own tone was regrettably snappy. I do think the existing policy works, but I stand by my (clarified) suggestion. Even if the actual maintainer is unruffled by the sudden appearance of a takeover announcement, as in this case, the wider public --- most of whom probably aren't even aware of the policy --- should also be considered. I think it's easier to avoid [confusion] than resist it. If people keep getting confused by the same thing, maybe it's the thing itself that needs clarification. On Fri, 12 Mar 2021, 23.27 Gershom B, wrote: > On Mar 12, 2021, 12:27 PM -0500, Bryan Richter , wrote: > > Can I suggest to the Hackage Whoever a slight change in policy? > > > I think the shock of seeing a package takeover request for your own > package is understandably, uh, shocking, and makes the ensuing discussion > tense. I also feel like most takeover requests follow this pattern; rarely > does a package end up changing hands. > > > Perhaps it's a problem of tone. > > > Rather than suggesting "State your intention to take over the package in a > public forum ", step 2 should lighten up and state, "After trying to reach > the maintainer for a reasonable amount of time, reach out to the public to > expand your search." > > > https://wiki.haskell.org/Taking_over_a_package > > > > The proposed change is not just a tone change. The point of step 2 is that > an official request be filed in a public forum and sufficient time then > pass that we can be confident the maintainer has been publicly informed of > the issue. It’s not about having a heavy tone or the like. > > This whole fracas is simply the result of confusion and miscommunication — > a package appeared unmaintained, but it turned out that there was a > maintainer, but it was hard to tell because the maintainer was not listed > on the last uploaded package. The correct fix for this is everyone chill > out, go for a walk, and then get on with more productive things. > > By the way, I should mention that there _is_ a hackage audit log of who > has been added to maintainer (and trustee and admin) groups, and by whom, > since there seemed to be some confusion about that. > > Best, > Gershom > _______________________________________________ > 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 jo at durchholz.org Sat Mar 13 07:38:37 2021 From: jo at durchholz.org (Joachim Durchholz) Date: Sat, 13 Mar 2021 08:38:37 +0100 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <20210312030416.GA29223@painter.painter> <20210312041528.GA32250@painter.painter> <20210312050951.GA2730@painter.painter> <20210312055606.GA6517@painter.painter> <20210312070130.GA9783@painter.painter> Message-ID: <7863c9dd-8c6e-3a18-807c-cd870f21e9e3@durchholz.org> Am 12.03.21 um 18:13 schrieb Emily Pillmore: > I'm curious as to why you took > this tack, and feel disrespected when `tomland` is the go-to TOML > library in Haskell, and as you say, has been recognized outside of the > community by the TOML org itself. I understand your irritation at Tom derailing your request into a discussion about all kinds of unrelated things. (I'm irritated myself how he's emphasizing his feelings in so many of his messages; it's not an irrelevant topic but he has made his feelings clear enough, and the focus should be on other things as well.) However, since you state that the existing packages do not meet your needs and want to restructure the code, maybe taking over Tom's package(s) isn't a good idea anyway - restructuring tends to affect the public API, and library users would have reason to object to that. You already have the code - nothing prevents you from taking it and adapting it to your needs. And you don't need the name. Either your library is getting enough traction that it will be mentioned, and then search engines will find it regardless of its name; or your library will end being useful mainly for yourself, and then the name doesn't matter. Regards, Jo From kindaro at gmail.com Sat Mar 13 11:39:40 2021 From: kindaro at gmail.com (Ignat Insarov) Date: Sat, 13 Mar 2021 16:39:40 +0500 Subject: [Haskell-cafe] Property checks and PostgreSQL? Message-ID: Note: I posted this [elsewhere] — I hope it is permissible to also post here. There seems to be no single right venue for Haskell questions at this time. [elsewhere]: https://discourse.haskell.org/t/property-checks-and-postgresql/2078 So, I have a three layer stack: PostgreSQL data base, Haskell back end, PureScript front end. And there is a fault somewhere in this stack: sometimes some items present in the data base do not make it to the front end. A small fortune in programmer hours has been spent searching for the fault but there is no progress. No one can figure out even roughly where the fault is. Our last hope is to property check the whole thing, from end to end, verifying that any things put into the data base can be retrieved by the front end. We have in place a fixture that creates a new PostgreSQL cluster, runs the back end on it and makes some scripted HTTP requests. We use it to run unit tests, such like _«if I make this `PUT` request and then that `GET` request to the same end point, I should get back the same thing as I put in»_. In principle it would not be a problem to make a property check out of this property. Practically, tearing down the cluster, building a new pristine one and initializing the data base anew takes seconds, so this way even a trivial property check would take minutes to run. Theoretically, we can carefully reset the data base back to the initial state after each run of the property check. Given that only a small amount of data is modified, it would take imperceptibly little time. But it is hard to know what exactly should be reset, and it is easy to get it wrong if done by hand! One trick we do use is SQL transactions. We take a single connexion, start a transaction, perform a check and then roll the transaction back. Unfortunately, even this is not completely safe: it looks as though sequences used to draw primary keys from are not reset to their previous values! _(Or maybe we are doing something wrong — I am not really a PostgreSQL guru so I am not too sure of myself.)_ But even ignoring this problem _(it is irrelevant to most checks)_, there is another, more severe problem: transactions guarantee that uncommitted data is only visible inside the same connexion. So, there is no way to request it from the HTTP API. This trick is suitable for fuzzing the data base – back end layer, but nothing beyond that. Another thing I heard being done is to selectively drop and re-create exactly the tables affected by a run of a property check. This seems challenging to automate though. How can I know in a general way if a table has been touched? And then, how can I re-create exactly the affected tables given that the data base initialization code is an opaque blob? I wonder if this problem is already solved. In any case, any advice is welcome! From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Sat Mar 13 11:51:36 2021 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Sat, 13 Mar 2021 11:51:36 +0000 Subject: [Haskell-cafe] Property checks and PostgreSQL? In-Reply-To: References: Message-ID: <20210313115136.GA14644@cloudinit-builder> On Sat, Mar 13, 2021 at 04:39:40PM +0500, Ignat Insarov wrote: > So, I have a three layer stack: PostgreSQL data base, Haskell back end, > PureScript front end. And there is a fault somewhere in this stack [...] > Our last hope is to property check the whole thing, from end to > end, verifying that any things put into the data base can be > retrieved by the front end. It's not clear to me why you need to reset anything. Can you attach a unique value to each entry you make and then subsequently check that the unique value is present in the data you read back? From kindaro at gmail.com Sat Mar 13 12:18:39 2021 From: kindaro at gmail.com (Ignat Insarov) Date: Sat, 13 Mar 2021 17:18:39 +0500 Subject: [Haskell-cafe] Property checks and PostgreSQL? In-Reply-To: <20210313115136.GA14644@cloudinit-builder> References: <20210313115136.GA14644@cloudinit-builder> Message-ID: Yes, usually I can ignore extraneous values and this would work. But this is not a local fault. We already check that individual items can always be retrieved. It must be some relation between the items that determines whether an item will be broken. It also depends on the query — any single item can always be retrieved, but some items disappear when a set of items is requested. This is why I want to ensure that the runs of the property check are completely isolated. I am not looking for an example of a single broken item — I am looking for an example of a broken data base as a whole. From bertram.felgenhauer at googlemail.com Sat Mar 13 14:42:30 2021 From: bertram.felgenhauer at googlemail.com (Bertram Felgenhauer) Date: Sat, 13 Mar 2021 15:42:30 +0100 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <46ca1e58-8d6b-eba0-c330-ca7cfde63cbd@henning-thielemann.de> <3b848f77-f399-9455-7170-2d9cc92e4094@glitchbra.in> Message-ID: Gershom B wrote: > By the way, I should mention that there _is_ a hackage audit log of who > has been added to maintainer (and trustee and admin) groups, and by > whom, since there seemed to be some confusion about that. The list of maintainers is public; in this case, https://hackage.haskell.org/package/toml/maintainers/ But that doesn't solve the problem of *contacting* a maintainer; all you get is a name and a list of other packages they maintain. Still, maybe it would help if this feature was more prominent? A direct link from the package description page could work, though it's not obvious where the best place is. An unobtrusive but perhaps too subtle place would be the "package maintainers" phrase under "Maintainer's Corner". The obvious place to look is in the summary box, but that is already very crowded. Cheers, Bertram From bertram.felgenhauer at googlemail.com Sat Mar 13 15:06:30 2021 From: bertram.felgenhauer at googlemail.com (Bertram Felgenhauer) Date: Sat, 13 Mar 2021 16:06:30 +0100 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <3b848f77-f399-9455-7170-2d9cc92e4094@glitchbra.in> Message-ID: I wrote: > https://hackage.haskell.org/package/toml/maintainers/ > > Still, maybe it would help if this feature was more prominent? See also https://github.com/haskell/hackage-server/issues/918 Cheers, Bertram From effectfully at gmail.com Sat Mar 13 16:55:41 2021 From: effectfully at gmail.com (Roman) Date: Sat, 13 Mar 2021 19:55:41 +0300 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <3b848f77-f399-9455-7170-2d9cc92e4094@glitchbra.in> Message-ID: Emily, > Carter and I were looking into this in February of last year, and the need > arose again, so I brought it up today. > > I have been eyeing a remake of this package for a long time for some of my > projects. To be clear: there is no fire that needs to be put out, but I do > have a need. > It's not a "need" (not a technical one at least), it's a desire to control a certain package name. Even if there was no responsive maintainer, I'd argue that if anything that name should be given to Kowainik who already support the de facto standard Haskell library for dealing with TOML, 'cause their package fits your criteria (I absolutely do not agree with that criteria, but that's irrelevant) hackage names are a community resource, and they deserve to be thought > through carefully > much better than your yet-to-be-written library (despite the fact that you'll most certainly produce a great library). If "Hackage real-estate" is that "precious", as you put it, it shouldn't be given away on the basis of a promise to write a standard library, there should be actual code to compare. I'm genuinely surprised there was someone else made maintainer of the > package without a public takeover. When/how did this happen? > I do not feel like the author of a library takes the responsibility to inform the public about giving someone permissions to their own library by uploading it to Hackage. There *should* be some package metadata that specifies a way to contact the maintainer, but that issue is now fixed. сб, 13 мар. 2021 г. в 18:07, Bertram Felgenhauer via Haskell-Cafe < haskell-cafe at haskell.org>: > I wrote: > > https://hackage.haskell.org/package/toml/maintainers/ > > > > Still, maybe it would help if this feature was more prominent? > > See also https://github.com/haskell/hackage-server/issues/918 > > Cheers, > > Bertram > _______________________________________________ > 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 lemming at henning-thielemann.de Sat Mar 13 18:39:38 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Sat, 13 Mar 2021 19:39:38 +0100 (CET) Subject: [Haskell-cafe] data kinds and exhaustiveness of typeclass instances In-Reply-To: References: Message-ID: <7b6b272c-70a-5f91-45f9-8777a7d9faf0@henning-thielemann.de> On Tue, 2 Mar 2021, Paul Brauner wrote: > Hello, > the following program doesn't typecheck in GHC 9: > > data Tag = A | B > data Foo (a :: Tag) = Foo > > class C a where >   f :: a -> Int > > instance C (Foo A) where >   f x = 1 > > instance C (Foo B) where >   f x = 2 > > g :: Foo a -> Int > g = f You need a typecase on Tag's constructors. E.g. class C a where switch :: f A -> f B -> f a instance C A where switch h _ = h instance C B where switch _ h = h newtype G a = G {getG :: Foo a -> Int} g :: (C a) => Foo a -> Int g = getG $ switch (G f) (G f) Or you define a helper GADT: data Choice a where A :: Choice A B :: Choice B class C a where choice :: Choice a instance C A where choice = A instance C B where choice = B choiceFromFoo :: (C a) => Foo a -> Choice a choiceFromFoo Foo = choice g :: (C a) => Foo a -> Int g foo = case choiceFromFoo foo of A -> f foo B -> f foo From amindfv at mailbox.org Sat Mar 13 21:07:52 2021 From: amindfv at mailbox.org (amindfv at mailbox.org) Date: Sat, 13 Mar 2021 14:07:52 -0700 Subject: [Haskell-cafe] Package Takeover: `toml` In-Reply-To: References: <3b848f77-f399-9455-7170-2d9cc92e4094@glitchbra.in> Message-ID: <20210313210752.GA2870@painter.painter> This is being amicably resolved off-list. Tom On Sat, Mar 13, 2021 at 07:55:41PM +0300, Roman wrote: > Emily, > > > > Carter and I were looking into this in February of last year, and the need > > arose again, so I brought it up today. > > > > > > I have been eyeing a remake of this package for a long time for some of my > > projects. To be clear: there is no fire that needs to be put out, but I do > > have a need. > > > > It's not a "need" (not a technical one at least), it's a desire to control > a certain package name. Even if there was no responsive maintainer, I'd > argue that if anything that name should be given to Kowainik who already > support the de facto standard Haskell library for dealing with TOML, 'cause > their package fits your criteria (I absolutely do not agree with that > criteria, but that's irrelevant) > > hackage names are a community resource, and they deserve to be thought > > through carefully > > > > much better than your yet-to-be-written library (despite the fact that > you'll most certainly produce a great library). If "Hackage real-estate" is > that "precious", as you put it, it shouldn't be given away on the basis of > a promise to write a standard library, there should be actual code to > compare. > > I'm genuinely surprised there was someone else made maintainer of the > > package without a public takeover. When/how did this happen? > > > > I do not feel like the author of a library takes the responsibility to > inform the public about giving someone permissions to their own library by > uploading it to Hackage. There *should* be some package metadata that > specifies a way to contact the maintainer, but that issue is now fixed. > > сб, 13 мар. 2021 г. в 18:07, Bertram Felgenhauer via Haskell-Cafe < > haskell-cafe at haskell.org>: > > > I wrote: > > > https://hackage.haskell.org/package/toml/maintainers/ > > > > > > Still, maybe it would help if this feature was more prominent? > > > > See also https://github.com/haskell/hackage-server/issues/918 > > > > Cheers, > > > > Bertram > > _______________________________________________ > > 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 amindfv at mailbox.org Sat Mar 13 21:22:25 2021 From: amindfv at mailbox.org (amindfv at mailbox.org) Date: Sat, 13 Mar 2021 14:22:25 -0700 Subject: [Haskell-cafe] Property checks and PostgreSQL? In-Reply-To: References: Message-ID: <20210313212225.GA3505@painter.painter> On Sat, Mar 13, 2021 at 04:39:40PM +0500, Ignat Insarov wrote: > Note: I posted this [elsewhere] — I hope it is permissible to also post > here. There seems to be no single right venue for Haskell questions at this > time. > > [elsewhere]: https://discourse.haskell.org/t/property-checks-and-postgresql/2078 > > So, I have a three layer stack: PostgreSQL data base, Haskell back end, > PureScript front end. And there is a fault somewhere in this stack: sometimes > some items present in the data base do not make it to the front end. A small > fortune in programmer hours has been spent searching for the fault but there is > no progress. No one can figure out even roughly where the fault is. Our last > hope is to property check the whole thing, from end to end, verifying that any > things put into the data base can be retrieved by the front end. > > We have in place a fixture that creates a new PostgreSQL cluster, runs the back > end on it and makes some scripted HTTP requests. We use it to run unit tests, > such like _«if I make this `PUT` request and then that `GET` request to the same > end point, I should get back the same thing as I put in»_. In principle it would > not be a problem to make a property check out of this property. Practically, > tearing down the cluster, building a new pristine one and initializing the data > base anew takes seconds, so this way even a trivial property check would take > minutes to run. Do you know where the majority of the time is spent? I.e. can you just drop the schema without re-creating the cluster? I'd guess it'd be fast but I don't know your setup. > > Another thing I heard being done is to selectively drop and re-create exactly > the tables affected by a run of a property check. This seems challenging to > automate though. How can I know in a general way if a table has been touched? > And then, how can I re-create exactly the affected tables given that the data > base initialization code is an opaque blob? At $WORK we do this: property tests on PSQL data dropping data between tests, but we know which tables are modified so we can just truncate the affected ones. Tom From amindfv at mailbox.org Sat Mar 13 21:26:40 2021 From: amindfv at mailbox.org (amindfv at mailbox.org) Date: Sat, 13 Mar 2021 14:26:40 -0700 Subject: [Haskell-cafe] Property checks and PostgreSQL? In-Reply-To: <20210313212225.GA3505@painter.painter> References: <20210313212225.GA3505@painter.painter> Message-ID: <20210313212640.GA4248@painter.painter> On Sat, Mar 13, 2021 at 02:22:25PM -0700, amindfv at mailbox.org wrote: > On Sat, Mar 13, 2021 at 04:39:40PM +0500, Ignat Insarov wrote: > > Note: I posted this [elsewhere] — I hope it is permissible to also post > > here. There seems to be no single right venue for Haskell questions at this > > time. > > > > [elsewhere]: https://discourse.haskell.org/t/property-checks-and-postgresql/2078 > > > > So, I have a three layer stack: PostgreSQL data base, Haskell back end, > > PureScript front end. And there is a fault somewhere in this stack: sometimes > > some items present in the data base do not make it to the front end. A small > > fortune in programmer hours has been spent searching for the fault but there is > > no progress. No one can figure out even roughly where the fault is. Our last > > hope is to property check the whole thing, from end to end, verifying that any > > things put into the data base can be retrieved by the front end. > > > > We have in place a fixture that creates a new PostgreSQL cluster, runs the back > > end on it and makes some scripted HTTP requests. We use it to run unit tests, > > such like _«if I make this `PUT` request and then that `GET` request to the same > > end point, I should get back the same thing as I put in»_. In principle it would > > not be a problem to make a property check out of this property. Practically, > > tearing down the cluster, building a new pristine one and initializing the data > > base anew takes seconds, so this way even a trivial property check would take > > minutes to run. > > Do you know where the majority of the time is spent? I.e. can you just drop the schema without re-creating the cluster? I'd guess it'd be fast but I don't know your setup. > > > > > Another thing I heard being done is to selectively drop and re-create exactly > > the tables affected by a run of a property check. This seems challenging to > > automate though. How can I know in a general way if a table has been touched? > > And then, how can I re-create exactly the affected tables given that the data > > base initialization code is an opaque blob? > > At $WORK we do this: property tests on PSQL data dropping data between tests, but we know which tables are modified so we can just truncate the affected ones. I should add, too: it's not always desirable to truncate or start from a pristine database. Sometimes having data lying around that shouldn't affect your tests can be a good way of testing that that data truly doesn't affect the thing being tested. I.e. it's another method of fuzzing. > > Tom > From ietf-dane at dukhovni.org Sat Mar 13 21:42:18 2021 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Sat, 13 Mar 2021 19:42:18 -0200 Subject: [Haskell-cafe] Property checks and PostgreSQL? In-Reply-To: References: Message-ID: <6278B124-DA6D-41A6-AED7-E4606E2F7FF9@dukhovni.org> > On Mar 13, 2021, at 9:39 AM, Ignat Insarov wrote: > > er thing I heard being done is to selectively drop and re-create exactly > the tables affected by a run of a property check. This seems challenging to > automate though. How can I know in a general way if a table has been touched? > And then, how can I re-create exactly the affected tables given that the data > base initialization code is an opaque blob? > > I wonder if this problem is already solved. In any case, any advice is welcome! The template test database should be immutable during the tests. Just clone the template database, and run tests against the clone. When done, drop the clone. https://www.postgresql.org/docs/12/manage-ag-templatedbs.html https://www.postgresql.org/docs/12/manage-ag-dropdb.html https://www.postgresqltutorial.com/postgresql-copy-database/ https://www.postgresqltutorial.com/postgresql-drop-database/ -- Viktor. From kindaro at gmail.com Sat Mar 13 23:06:41 2021 From: kindaro at gmail.com (Ignat Insarov) Date: Sun, 14 Mar 2021 04:06:41 +0500 Subject: [Haskell-cafe] Property checks and PostgreSQL? In-Reply-To: <20210313212225.GA3505@painter.painter> References: <20210313212225.GA3505@painter.painter> Message-ID: > Do you know where the majority of the time is spent? I.e. can you just drop the schema without re-creating the cluster? I'd guess it'd be fast but I don't know your setup. The first step would be to keep the cluster, yes. It takes a few seconds, although we can use a `tmpfs` backed by RAM to cut this down to about one second. But initializing the data base from prepared `*.sql` files also takes a few seconds. > At $WORK we do this: property tests on PSQL data dropping data between tests, but we know which tables are modified so we can just truncate the affected ones. So how exactly do you do that? Like, do you write the SQL statements needed to reset the data base for every check by hand? And what sort of statements do you use? Do you drop the table or delete the rows? It would be ideal if I could somehow detect the tables that were touched and reset them automatically. But I cannot think of a simple way to do that. I cannot simply erase all the data because some data needs to be in place for the application to even start. From kindaro at gmail.com Sat Mar 13 23:13:27 2021 From: kindaro at gmail.com (Ignat Insarov) Date: Sun, 14 Mar 2021 04:13:27 +0500 Subject: [Haskell-cafe] Property checks and PostgreSQL? In-Reply-To: <6278B124-DA6D-41A6-AED7-E4606E2F7FF9@dukhovni.org> References: <6278B124-DA6D-41A6-AED7-E4606E2F7FF9@dukhovni.org> Message-ID: > The template test database should be immutable during the tests. Just > clone the template database, and run tests against the clone. When done, > drop the clone. Is it significantly faster than importing from prepared `*.sql` files? The problem here is that, as I understand, we will have to restart the application every time so that it connects to the new data base. It takes about a second. I was hoping that there is some way to clone a single schema, but I figure it is not possible. So now I have to either drop the schema and import it again from `*.sql`, or drop the data base, clone it from the template and restart the application. It does not seem like a clear win. Note that I need the application to be running so that I may observe the HTTP API. Although perhaps I can factor the API out and write a simple wrapper for it that would start faster. But this is extra work and it would increase the complexity of the project, so I am not sure if I should. From amindfv at mailbox.org Sun Mar 14 02:55:02 2021 From: amindfv at mailbox.org (amindfv at mailbox.org) Date: Sat, 13 Mar 2021 19:55:02 -0700 Subject: [Haskell-cafe] Property checks and PostgreSQL? In-Reply-To: References: <20210313212225.GA3505@painter.painter> Message-ID: <20210314025502.GA19481@painter.painter> On Sun, Mar 14, 2021 at 04:06:41AM +0500, Ignat Insarov wrote: > > Do you know where the majority of the time is spent? I.e. can you just drop the schema without re-creating the cluster? I'd guess it'd be fast but I don't know your setup. > > The first step would be to keep the cluster, yes. It takes a few > seconds, although we can use a `tmpfs` backed by RAM to cut this down > to about one second. But initializing the data base from prepared > `*.sql` files also takes a few seconds. > I don't know your setup but if the problem is not with the creation of your schema it does feel like a waste to tear it down and re-create it from a tmpfs each time. > > At $WORK we do this: property tests on PSQL data dropping data between tests, but we know which tables are modified so we can just truncate the affected ones. > > So how exactly do you do that? Like, do you write the SQL statements > needed to reset the data base for every check by hand? And what sort > of statements do you use? Do you drop the table or delete the rows? > Depends on the test but it's a lot more common to just call "truncate table foo" when necessary. > It would be ideal if I could somehow detect the tables that were > touched and reset them automatically. But I cannot think of a simple > way to do that. I cannot simply erase all the data because some data > needs to be in place for the application to even start. It's possible I'm answering an X/Y question[0] right now, but: - Can you create a function that populates this essential data and only call that function after truncating? - If your data is timestamped you could always delete all "new" rows? Tom [0] https://meta.stackexchange.com/questions/66377/what-is-the-xy-problem From lemming at henning-thielemann.de Sun Mar 14 08:23:04 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Sun, 14 Mar 2021 09:23:04 +0100 (CET) Subject: [Haskell-cafe] Cyclic indexing (Was: naturally, length :: a -> Int) In-Reply-To: References: Message-ID: <149e029-8597-356c-755a-602cede3a89f@henning-thielemann.de> On Thu, 4 Mar 2021, Ben Franksen wrote: > If we do embrace that viewpoint, then I'd say we should go all the way > and interpret indices modulo (non-negative) structure size! This makes > (safe) indexing total (for non-empty structures) and allows things like > xs !! (-1) == last xs as in Perl and some other languages. Unsafe > indexing (as in the vector package) could remain as is for performance > critical code. This seems to be the MatLab way of solving problems: Just don't talk about them anymore. :-) However, I had the idea of adding a Cyclic shape to my array library: http://hackage.haskell.org/package/comfort-array-0.4/docs/Data-Array-Comfort-Shape.html In comfort-array I use distinct types for the array shape and its indices, where the index type is a type function of the shape type. I had the plan to add a Cyclic shape type in order to better support the Discrete Fourier Transform. A DFT actually transforms a cyclic signal to a cyclic frequency spectrum. This means, a Fourier transform library like fftw would still transform an array with indices from 0 to n-1, but you can access the frequency (-1) with index (-1) although it is stored at index (n-1). From jo at durchholz.org Sun Mar 14 09:41:31 2021 From: jo at durchholz.org (Joachim Durchholz) Date: Sun, 14 Mar 2021 10:41:31 +0100 Subject: [Haskell-cafe] Property checks and PostgreSQL? In-Reply-To: References: Message-ID: <6e1a1297-e5c8-ff40-c44d-0ade58465e53@durchholz.org> > So, I have a three layer stack: PostgreSQL data base, Haskell back end, > PureScript front end. And there is a fault somewhere in this stack: sometimes > some items present in the data base do not make it to the front end. A small > fortune in programmer hours has been spent searching for the fault but there is > no progress. No one can figure out even roughly where the fault is. Are you running at the standard isolation level? If yes, your code may be affected by nonrepeatable read, phantom read, or serialization anomaly - in a nutshell, this is what happens if you expect to get the same results if the query is run twice, but the rows that affect this result are somehow not included in the transactions (there are edge cases that can do this, the isolation levels progressively exclude them, at the expense of performance loss). More details are on https://www.postgresql.org/docs/current/transaction-iso.html . > Theoretically, we can carefully reset the data base back to the initial state > after each run of the property check. Given that only a small amount of data is > modified, it would take imperceptibly little time. But it is hard to know what > exactly should be reset, and it is easy to get it wrong if done by hand! Have you tried nested transactions? I have no PSQL experience myself, but it looks like it should do the minimal-effort rollback you're after: Start a transaction, let the unit tests run (including their own transactions, just they're nested now), roll back the overarching initial transaction. > One trick we do use is SQL transactions. We take a single connexion, start a > transaction, perform a check and then roll the transaction back. Unfortunately, > even this is not completely safe: it looks as though sequences used to draw > primary keys from are not reset to their previous values! _(Or maybe we are > doing something wrong — I am not really a PostgreSQL guru so I am not too sure > of myself.)_ No, this is documented (if surprising) behaviour. But TBH if your code is affected by the values you get from a sequence, that's not what sequences are intended for - they're for being unique, not for their numerical properties. See https://www.postgresql.org/message-id/501B1494.9040502 at ringerc.id.au for more details. > But even ignoring this problem _(it is irrelevant to most checks)_, > there is another, more severe problem: transactions guarantee that uncommitted > data is only visible inside the same connexion. So, there is no way to request > it from the HTTP API. This trick is suitable for fuzzing the data base – back > end layer, but nothing beyond that. Yes, Postgresql gives you no way to read dirty data. This is pretty typical of MVCC databases. But even if there were a way, you'd never get a guarantee that you're actually getting the data that another transaction sees. If you wish to see what another transaction sees, you'll have to instrument the code that does the transaction. This should be doable in the backend. > Another thing I heard being done is to selectively drop and re-create exactly > the tables affected by a run of a property check. This seems challenging to > automate though. How can I know in a general way if a table has been touched? > And then, how can I re-create exactly the affected tables given that the data > base initialization code is an opaque blob? > > I wonder if this problem is already solved. In any case, any advice is welcome! I doubt it's a useful way forward. It's just not a use case that database are built for, and you have a high risk of hitting nonfunctional problems (performance, possibly from cold query optimization caches and such) or functional problems (sequencing of dropping/creating DB objects that depend on each other, for example, and you already saw the sequence number issue). Background is that databases are such complex beasts that the developer teams struggle to get the core goals done, nice-to-have goals get dropped pretty quickly. PGSQL is exceptional in that it tries to keep as many nice-to-have goals intact as possible, but I wouldn't count on that. Regards, Jo P.S.: This is concentrating on the database layer, which is unrelated to Haskell. Which might be because your problem is database-related, or because I happen to know more about databases than about Haskell. Or because you described your problems in terms of database issue. If it's really database-related, you may have more concrete advice on a PGQSL-related forum than here. From olf at aatal-apotheke.de Sun Mar 14 12:34:04 2021 From: olf at aatal-apotheke.de (Olaf Klinke) Date: Sun, 14 Mar 2021 13:34:04 +0100 Subject: [Haskell-cafe] naturally, length :: a -> Int In-Reply-To: References: Message-ID: On Fri, 2021-03-05 at 20:03 -0600, Zemyla wrote: > You're looking for Ratio Natural. > > On Wed, Mar 3, 2021, 09:20 Olaf Klinke wrote: > > > While we're at it: Can there be a Fractional type permitting only > > positive numbers, as the positive real numbers are closed under > > division? > > How stupid of me not to think of Ratio Natural. I should have phrased my question more precisely: Are there types that by construction (not only morally) permit only certain subsets of real numbers with reasonably efficient arithmetical operations? A naive way to represent rationals between 0 and 1 would be as newtype Part = Part !Natural !Natural with semantics \(Part a b) -> a % (a+b) Then (*) is easy to implement. \x -> 1-x is O(1) but arithmetic mean is more complicated. I have a proof-of-concept. If there is general interest in Rationals between 0 and 1 I could turn it into a small package, provided no other implementation exists. Olaf From jeroen at chordify.net Sun Mar 14 14:26:53 2021 From: jeroen at chordify.net (Jeroen Bransen) Date: Sun, 14 Mar 2021 15:26:53 +0100 Subject: [Haskell-cafe] Is Data.Pool not thread-safe or have I done something silly? In-Reply-To: <334170386.173268.1615597743472@ichabod.co-bxl> References: <334170386.173268.1615597743472@ichabod.co-bxl> Message-ID: <20d259c7-491f-09a3-0186-e82a5dc1de79@chordify.net> Hi Cody, I think part of your confusion may come from the naming of your functions. Your 'acquire' function is passed as first argument to createPool, and thus is a 'create' function rather than an acquire function. As your pool only ever has a single resource, I would expect that it would be called only once, because once a resource has been created it can be reused  by all threads. With stackage lts-16.15 I get exactly the behaviour I would expect on my machine: acquire 0 - TimeSpec {sec = 221871, nsec = 95964800} ThreadId 6:  processing 0 - TimeSpec {sec = 221881, nsec = 97250800} ThreadId 8:  processing 0 - TimeSpec {sec = 221891, nsec = 98211800} ThreadId 10:  processing 0 - TimeSpec {sec = 221901, nsec = 99347300} ThreadId 12:  processing 0 - TimeSpec {sec = 221911, nsec = 100904500} ThreadId 14:  processing 0 - TimeSpec {sec = 221921, nsec = 102292000} anything else? acquire 0 - TimeSpec {sec = 221921, nsec = 442620100} anything else? anything else? First a resource is created, then every 10 seconds a thread completed, and finally the resource is freed (your logging in release also prints acquire, but the second instance is from release). I can't run GHC 8.10 yet so not sure what happens there. Regards, Jeroen Bransen Op 13-3-2021 om 02:09 schreef Cody Gman: > I wrote some code with a Data.Pool that has 1 stripe, 1 max resource, and then basically did `Async.replicateConcurrently_ . withResource $ \res -> f res`. > > I expect withResource to block in each of those threads until the first thread spawned is done with that Resource and releases. > > To be clear, I get output like: > > ```shell > /tmp $ stack exec --resolver lts-17.5 --package resource-pool --package stm --package hslogger --package time --package concurrent-output -- ghc -O2 -threaded -fwarn-unused-imports testpool.hs && ./testpool > acquire 0 - .81428 > acquire 1 - .81431 > acquire 2 - .81438 > acquire 3 - .81440 > acquire 4 - .81448 > ThreadId 8: processing 1 - .82460 > ThreadId 17: processing 4 - .82461 > ThreadId 11: processing 2 - .82464 > ThreadId 14: processing 3 - .82464 > ThreadId 5: processing 0 - .82465 > anything else? > release 4 - .14427 > release 3 - .14430 > release 2 - .14431 > release 1 - .14431 > release 0 - .14432 > anything else? > anything else? > > ``` > > I expect output like: > > ```shell > /tmp $ stack exec --resolver lts-17.5 --package resource-pool --package stm --package hslogger --package time --package concurrent-output -- ghc -O2 -threaded -fwarn-unused-imports testpool.hs && ./testpool > [1 of 1] Compiling Main ( testpool.hs, testpool.o ) > Linking testpool ... > acquire 0 > ThreadId 5: processing 0 - .01129 > release 0 > acquire 1 -- I thought this would have blocked until 0 was released > ThreadId 8: processing 1 - .01120 > release 1 > acquire 2 > ThreadId 11: processing 2 - .01123 > release 2 > acquire 3 > ThreadId 14: processing 3 - .01129 > release 3 > acquire 4 > ThreadId 17: processing 4 - .01129 > release 4 > anything else? > anything else? > anything else? > ``` > > Here is the code: > > ``` > #!/usr/bin/env stack > -- stack script --resolver lts-17.5 --package resource-pool --package stm --package hslogger --package time --package concurrent-output > > import Control.Concurrent > import Control.Concurrent.Async > import Control.Concurrent.STM > import Data.Pool > import Data.Time > import System.Console.Concurrent > import System.Clock > > main :: IO () > main = do > counter <- newTVarIO 0 > let acquire = do > k <- atomically $ do > k <- readTVar counter > writeTVar counter (k + 1) > return k > now <- getTime Monotonic > outputConcurrent ("acquire " ++ show k ++ " - "++ show now ++ "\n") > return k > release k = do > now <- getTime Monotonic > outputConcurrent ("acquire " ++ show k ++ " - "++ show now ++ "\n") > > withConcurrentOutput $ do > -- create a pool that only allows 1 resource > pool <- createPool acquire release 1 500 1 > replicateConcurrently_ 5 $ do > useResourceFor (seconds 10) pool > > -- Why do you need these to see the release messages? > putStrLn "anything else?" >> threadDelay (seconds 5) > putStrLn "anything else?" >> threadDelay (seconds 5) > putStrLn "anything else?" >> threadDelay (seconds 5) > > useResourceFor waitSeconds pool = withResource pool $ \i -> do > threadDelay waitSeconds > tid <- myThreadId > now <- getTime Monotonic > outputConcurrent $ show tid <> ": " <> " processing " <> show i <> " - " <> show now <> "\n" > > seconds = (* 1000000) > ``` > > I'm hoping someone could help explain what I did wrong or confirm it's a bug. > > Thanks, > > Cody > _______________________________________________ > 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. -- Jeroen Bransen Back-end Developer at Chordify -- From johannes.waldmann at htwk-leipzig.de Sun Mar 14 20:49:29 2021 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Sun, 14 Mar 2021 21:49:29 +0100 Subject: [Haskell-cafe] Let's fight Int, Pt. 2 Message-ID: Dear Cafe, it's bad to use Int where you really mean Nat, because this creates extra work (defensive programming, or mental gymnastics to prove that you don't need it) Another Int anti-feature is arithmetics with silent wrap-around - with respect to an unspecified modulus, as highlighted by a recent example: https://gitlab.haskell.org/ghc/ghc/-/issues/19500 What are the possibilities for a "checked Int"? (also, "checked Nat") A historical precedent is set by Ada http://archive.adaic.com/standards/83lrm/html/lrm-03-05.html#3.5.4 "The exception NUMERIC_ERROR is raised by the execution of an operation ... that cannot deliver the correct result" Another point in the design space is Rust: "Integer operators will panic when they overflow when compiled in debug mode." https://doc.rust-lang.org/reference/expressions/operator-expr.html?highlight=numeric#overflow The Haskell standard https://www.haskell.org/onlinereport/haskell2010/haskellch6.html#x13-1350006.4 says that "The results of exceptional conditions (such as overflow or underflow) on the fixed-precision numeric types are undefined;" so any program that relies on Int's wrap-around, is already broken. GHC's base library specifies "modulo 2^width" semantics for signed (Data.Int) and unsigned (Data.Word) integer types. Finally, about "fighting" - I guess it's more about strategies to cope with the present situation. - J.W. From lemming at henning-thielemann.de Sun Mar 14 21:10:59 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Sun, 14 Mar 2021 22:10:59 +0100 (CET) Subject: [Haskell-cafe] Let's fight Int, Pt. 2 In-Reply-To: References: Message-ID: On Sun, 14 Mar 2021, Johannes Waldmann wrote: > A historical precedent is set by Ada > http://archive.adaic.com/standards/83lrm/html/lrm-03-05.html#3.5.4 > "The exception NUMERIC_ERROR is raised by the execution of an operation > ... that cannot deliver the correct result" Even in C, 'int' has no wrap-around semantics. Chris Lattner, creator of LLVM, blogs about how the LLVM optimizer makes use of that fact: https://blog.llvm.org/2011/05/what-every-c-programmer-should-know.html I guess, if Haskeller's use the LLVM backend and assume wrap-around semantics they will run into the same trouble that Chris describes in his blog posts. From kazu at iij.ad.jp Mon Mar 15 00:13:38 2021 From: kazu at iij.ad.jp (Kazu Yamamoto (=?iso-2022-jp?B?GyRCOzNLXE9CSScbKEI=?=)) Date: Mon, 15 Mar 2021 09:13:38 +0900 (JST) Subject: [Haskell-cafe] Future of package cryptonite In-Reply-To: <033fd5f4-5106-0f21-95e2-9ea06fa8dc33@pwned.gg> References: <033fd5f4-5106-0f21-95e2-9ea06fa8dc33@pwned.gg> Message-ID: <20210315.091338.227613484946451382.kazu@iij.ad.jp> Hello, We should also take care of "memory", "foundation" and "basement". No action is taken for over a month to https://github.com/haskell-foundation/foundation/pull/549 I cannot switch my main GHC version to 9.0 at this moment. --Kazu > Hello Haskell-cafe, > > I'm writing to discuss the future of the package cryptonite, including scenarios where it would be acceptable to take over the package - by me & Kazu (in CC), who already maintains hs-tls, and anyone else who is qualified and willing. > > The current maintainer Vincent (in CC) has been unresponsive to several attempts to contact him by email over the past several months, and is not responsive to PRs [1] on github. He is not entirely dormant, he has made a bugfix release in January, however otherwise he does not communicate. > > Based on [2] and some other hearsay, I understand that Vincent has "quit Haskell". The other maintainer, Oliver Chéron has also explicitly said that he has quit Haskell [3]. > > We have also attempted to contact other members of the haskell-crypto github group, however only one of them responded to say they don't feel they can make decisions for cryptonite. > > Under what time frame does the list think it would be acceptable to take over the package? And additionally, are there any other interested volunteers to co-maintain? (I do not want to be the main maintainer, due to more direct interests in other topics.) > > Best, > Ximin > > [1] https://github.com/haskell-crypto/cryptonite > [2] https://github.com/haskell-crypto/cryptonite/issues/330#issuecomment-670801628 > [3] https://github.com/haskell-crypto/cryptonite/pull/323#issuecomment-701885924 > > -- > GPG: ed25519/56034877E1F87C35 > https://github.com/infinity0/pubkeys.git From anthony_clayden at clear.net.nz Mon Mar 15 01:00:05 2021 From: anthony_clayden at clear.net.nz (Anthony Clayden) Date: Mon, 15 Mar 2021 14:00:05 +1300 Subject: [Haskell-cafe] Property checks and PostgreSQL? Message-ID: > PostgreSQL data base, Haskell back end, PureScript front end. And there is a fault somewhere in this stack: sometimes some items present in the data base do not make it to the front end. A small fortune in programmer hours has been spent ... Speaking purely from a SQL-and-stuff point of view, "programmer hours spent" sounds to me like a problem with nulls. Are any of your columns nullable? Are you sure they should be nullable? In particular are any of the columns in the keys nullable? Or any of the columns on which you're joining tables? (Perhaps a proper value in one table, but a null in the table it's supposed to equal?) How are you mapping between Haskell field values to/from nullable columns in the SQL? Is that mapping fool-proof? Is it consistent across different tables using what should be the same value? And in general: SQL nulls are an abomination; don't do that; do normalise your database schema to avoid nulls. AntC (35 years an SQL programmer, never trusted it) -------------- next part -------------- An HTML attachment was scrubbed... URL: From svenpanne at gmail.com Mon Mar 15 08:05:16 2021 From: svenpanne at gmail.com (Sven Panne) Date: Mon, 15 Mar 2021 09:05:16 +0100 Subject: [Haskell-cafe] Future of package cryptonite In-Reply-To: <20210315.091338.227613484946451382.kazu@iij.ad.jp> References: <033fd5f4-5106-0f21-95e2-9ea06fa8dc33@pwned.gg> <20210315.091338.227613484946451382.kazu@iij.ad.jp> Message-ID: Am Mo., 15. März 2021 um 01:17 Uhr schrieb Kazu Yamamoto : > We should also take care of "memory", "foundation" and "basement". > No action is taken for over a month to > https://github.com/haskell-foundation/foundation/pull/549 Somehow I'm getting more and more allergic to all these hasty unwarranted "I want to take over package XY" requests. The last release of cryptonite was less than 7 weeks ago, a PR for foundation was not merged within 5 weeks, etc. etc. For god's sake: If you are in such a hurry, just fork locally! Or even better: Give the maintainers a huge pile of $$$, most of them are doing their stuff in their spare time, so you can't expect SLAs where you would have to spend 5 digit sums as a company. Or you can fork visibly on e.g. GitHub under a different package name and let other people decide which variant to take. "Taking over" a package can almost be seen as robbery from the point of view of the original author, and it is actively discouraging people to make their code Open Source. We should be much, much more sensitive in the Haskell community, I haven't seen such things in other language ecosystems. Having said that, I think that a few projects are blocked by stack issues before they can support GHC 9.0. It would be great if things would be released more in lock-step, I dream of a world where a new GHC comes out in sync with cabal, stack, Stackage, Haskell language server etc. all supporting the new compiler. Other language ecosystems are lightyears ahead regarding this... :-/ Cheers, S. -------------- next part -------------- An HTML attachment was scrubbed... URL: From lemming at henning-thielemann.de Mon Mar 15 09:02:23 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Mon, 15 Mar 2021 10:02:23 +0100 (CET) Subject: [Haskell-cafe] Future of package cryptonite In-Reply-To: References: <033fd5f4-5106-0f21-95e2-9ea06fa8dc33@pwned.gg> <20210315.091338.227613484946451382.kazu@iij.ad.jp> Message-ID: <334bd863-66cb-e2f9-3ca8-54352739998d@henning-thielemann.de> On Mon, 15 Mar 2021, Sven Panne wrote: > Somehow I'm getting more and more allergic to all these hasty > unwarranted "I want to take over package XY" requests. The last release > of cryptonite was less than 7 weeks ago, a PR for foundation was not > merged within 5 weeks, etc. etc.  For god's sake: If you are in such a > hurry, just fork locally! Or even better: Give the maintainers a huge > pile of $$$, most of them are doing their stuff in their spare time, so > you can't expect SLAs where you would have to spend 5 digit sums as a > company. I like this reasoning! If you cannot solve a problem with money, you can solve it with a lot of money. From simon.jakobi at googlemail.com Mon Mar 15 09:11:14 2021 From: simon.jakobi at googlemail.com (Simon Jakobi) Date: Mon, 15 Mar 2021 10:11:14 +0100 Subject: [Haskell-cafe] Future of package cryptonite In-Reply-To: References: <033fd5f4-5106-0f21-95e2-9ea06fa8dc33@pwned.gg> <20210315.091338.227613484946451382.kazu@iij.ad.jp> Message-ID: With regards to basement, I think it's neither hasty nor unwarranted to push for new maintainers. Vincent has been aware of the compatibility issue with GHC 9.0 for nearly 3 months: https://github.com/haskell-infra/hackage-trustees/issues/284#issuecomment-750738981 Now that GHC 9.0.1 has been out for over 5 weeks, I think it's pretty reasonable to expect that a package as central as basement should get a compatible release. Am Mo., 15. März 2021 um 09:06 Uhr schrieb Sven Panne : > > Am Mo., 15. März 2021 um 01:17 Uhr schrieb Kazu Yamamoto : >> >> We should also take care of "memory", "foundation" and "basement". >> No action is taken for over a month to >> https://github.com/haskell-foundation/foundation/pull/549 > > > Somehow I'm getting more and more allergic to all these hasty unwarranted "I want to take over package XY" requests. The last release of cryptonite was less than 7 weeks ago, a PR for foundation was not merged within 5 weeks, etc. etc. For god's sake: If you are in such a hurry, just fork locally! Or even better: Give the maintainers a huge pile of $$$, most of them are doing their stuff in their spare time, so you can't expect SLAs where you would have to spend 5 digit sums as a company. Or you can fork visibly on e.g. GitHub under a different package name and let other people decide which variant to take. > > "Taking over" a package can almost be seen as robbery from the point of view of the original author, and it is actively discouraging people to make their code Open Source. We should be much, much more sensitive in the Haskell community, I haven't seen such things in other language ecosystems. > > Having said that, I think that a few projects are blocked by stack issues before they can support GHC 9.0. It would be great if things would be released more in lock-step, I dream of a world where a new GHC comes out in sync with cabal, stack, Stackage, Haskell language server etc. all supporting the new compiler. Other language ecosystems are lightyears ahead regarding this... :-/ > > Cheers, > S. > _______________________________________________ > 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 andrew.lelechenko at gmail.com Mon Mar 15 18:33:39 2021 From: andrew.lelechenko at gmail.com (Andrew Lelechenko) Date: Mon, 15 Mar 2021 18:33:39 +0000 Subject: [Haskell-cafe] Future of package cryptonite In-Reply-To: References: Message-ID: > Under what time frame does the list think it would be acceptable to take over the package? And additionally, are there any other interested volunteers to co-maintain? (I do not want to be the main maintainer, due to more direct interests in other topics.) If you do not want to be the main maintainer and do not have much interest in cryptography, then it sounds wrong to initiate a takeover. There is a procedure for non-maintainer uploads via Hackage Trustees, please file an issue at https://github.com/haskell-infra/hackage-trustees/issues , linking a patched repository. > I cannot switch my main GHC version to 9.0 at this moment. It would be nice to audit that `cryptonite` is not vulnerable to https://mail.haskell.org/pipermail/haskell-cafe/2021-March/133540.html Best regards, Andrew -------------- next part -------------- An HTML attachment was scrubbed... URL: From danburton.email at gmail.com Mon Mar 15 21:32:05 2021 From: danburton.email at gmail.com (Dan Burton) Date: Mon, 15 Mar 2021 17:32:05 -0400 Subject: [Haskell-cafe] Future of package cryptonite In-Reply-To: References: <033fd5f4-5106-0f21-95e2-9ea06fa8dc33@pwned.gg> <20210315.091338.227613484946451382.kazu@iij.ad.jp> Message-ID: I'm not sure if these issues affect those particular packages, but the ecosystem should not be in a rush for GHC 9 compatibility, due to a few issues with unsafePerformIO which may be serious blockers. Kindly pump the brakes on this and wait until ghc 9.0.2 at least. See: https://gitlab.haskell.org/ghc/ghc/-/issues/19413 (But I do generally agree that we should push for widely-used projects to have more co-maintainers.) -- Dan Burton On Mon, Mar 15, 2021 at 5:13 AM Simon Jakobi via Haskell-Cafe < haskell-cafe at haskell.org> wrote: > With regards to basement, I think it's neither hasty nor unwarranted > to push for new maintainers. Vincent has been aware of the > compatibility issue with GHC 9.0 for nearly 3 months: > > https://github.com/haskell-infra/hackage-trustees/issues/284#issuecomment-750738981 > > Now that GHC 9.0.1 has been out for over 5 weeks, I think it's pretty > reasonable to expect that a package as central as basement should get > a compatible release. > > Am Mo., 15. März 2021 um 09:06 Uhr schrieb Sven Panne >: > > > > Am Mo., 15. März 2021 um 01:17 Uhr schrieb Kazu Yamamoto >: > >> > >> We should also take care of "memory", "foundation" and "basement". > >> No action is taken for over a month to > >> https://github.com/haskell-foundation/foundation/pull/549 > > > > > > Somehow I'm getting more and more allergic to all these hasty > unwarranted "I want to take over package XY" requests. The last release of > cryptonite was less than 7 weeks ago, a PR for foundation was not merged > within 5 weeks, etc. etc. For god's sake: If you are in such a hurry, just > fork locally! Or even better: Give the maintainers a huge pile of $$$, most > of them are doing their stuff in their spare time, so you can't expect SLAs > where you would have to spend 5 digit sums as a company. Or you can fork > visibly on e.g. GitHub under a different package name and let other people > decide which variant to take. > > > > "Taking over" a package can almost be seen as robbery from the point of > view of the original author, and it is actively discouraging people to make > their code Open Source. We should be much, much more sensitive in the > Haskell community, I haven't seen such things in other language ecosystems. > > > > Having said that, I think that a few projects are blocked by stack > issues before they can support GHC 9.0. It would be great if things would > be released more in lock-step, I dream of a world where a new GHC comes out > in sync with cabal, stack, Stackage, Haskell language server etc. all > supporting the new compiler. Other language ecosystems are lightyears ahead > regarding this... :-/ > > > > Cheers, > > S. > > _______________________________________________ > > 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 javran.c at gmail.com Mon Mar 15 22:42:58 2021 From: javran.c at gmail.com (Javran Cheng) Date: Mon, 15 Mar 2021 15:42:58 -0700 Subject: [Haskell-cafe] Some Alex beginner questions regarding parsing Java Message-ID: Hi Cafe! Firstly, sorry for spamming if you already see this on Stack Overflow, I do feel this is too much for a single SO question. I'm recently playing with Alex + Happy to try parsing Java (for now I'm only working on the lexer / Alex, so whenever you see "parse" below, that means tokenize). My reference is Java SE 15 Spec, the chapter of interest is Chapter 3. Lexical Structure (side note: my timing is a bit interesting as I just realized as of writing this, Java SE 16 spec is out just few days ago, so I might switch to that) and now that I've get my hand dirty a bit, I have few questions and hope if someone can shed some light on them: 1. For now I'm using "monad-bytestring" wrapper for performance, but now I think maybe String-based wrapper is more appropriate, for it allows me to follow 1. and 2. in "3.2. Lexical Translations" properly before passing the input to Alex - namely I can pre-process input stream to (1) do Unicode escaping to turn the raw byte flow into a flow of Chars (2) I can normalize line terminators into just \n. But: 1. Are those two passes (Unicode escape and line terminator normalization) possible within Alex framework? 2. Is there any way that I can stick with a memory-compact string representation? (not sure why Alex doesn't provide any Text-based wrapper, as it did mention in its doc that it internally works on UTF-8 encoded byte sequence) I could probably consider to not use any wrapper, as GHC and Agda did, but that's sort of an undocumented territory so I'm hesitated to do so. 2. The other trouble I have regarding "3.2. Lexical Translations" is the special rules applied to ">"s: "... There is one exception: if lexical translation occurs in a type context (§4.11) ..." - but how in the world am I going to do this? I mean the lexical analysis is not even done how am I going to tell whether it's a type context (and §4.11 is quite long that I won't even try to read it, unless forced)? Maybe I can just tokenize every ">" as an individual operatior, as if ">>", ">>=", ">>>", and ">>>=" don't exist and worry about that later, but that doesn't sound right to me. 3. I realize there's a need for "irrecoverable failure": I have a test case with octal literal "012389", which is supposed to fail, but Alex happily tokenized that into [octal "0123", decimal "89"] - for now my workaround is for every number literal to check whether previous char is a digit and fail if it is indeed so, but I feel this is like ducktaping on a flawed approach and at some point it will fail on some edge cases. an ideal fix IMO would be to have some notion of irrecoverable failure - failing to parse a literal at full should be irrecoverable rather than trying to parse most of it and move on. In addition, as Java spec requires that if a numeric literal doesn't fit in the intended type, it's a compilation error - which can also be encoded as an irrecoverable failure as well. I'm not sure how to do that in Alex though, I can see few ways: 1. encode irrecoverable failure by setting to a special startcode, which does not provide anyway to go back to startcode 0 - so an irrecoverable failure sets that special startcode, and at the start of every action, it checks whether startcode is the special "failure" startcode and fail accordingly 2. this is similar to startcode, but use a wrapper that supports userstate. 3. maybe this is another case that not using a wrapper would give me more control, but I don't have a concrete idea regarding this alternative. Any thoughts on this is appreciated. Thanks! Javran (Fang) Cheng -------------- next part -------------- An HTML attachment was scrubbed... URL: From trebla at vex.net Mon Mar 15 23:48:00 2021 From: trebla at vex.net (Albert Y. C. Lai) Date: Mon, 15 Mar 2021 19:48:00 -0400 Subject: [Haskell-cafe] SML vs Haskell types In-Reply-To: References: Message-ID: You're now looking at the difference between: -- list of booleans but the end has an Int data T1 = End1 Int | Node1 Bool T1 whatInt1 (End1 i) = i whatInt1 (Node1 _ xs) = whatInt1 xs and -- list of booleans but the end has an Int again but different data T2 = End2 Int | FalseNode2 T2 | TrueNode2 T2 whatInt2 (End2 i) = i -- the following two cases are unmergeable -- but there is a mitigation if you find out about "record syntax" whatInt2 (FalseNode2 xs) = whatInt2 xs whatInt2 (TrueNode2 xs) = whatInt2 xs Record syntax can mitigate it: data T3 = End3 Int | FalseNode3 {tail3 :: T3} | TrueNode3 {tail3 :: T3} whatInt3 (End3 i) = i whatInt3 r = whatInt3 (tail3 r) But I say "mitgate", not "solve", because it doesn't generalize to data Q = QI Int | QF {qtail :: Q} | QT {qtail :: Q}  | BF{qleft, qright :: Q} | BT{qleft, qright :: Q} On 2021-03-12 7:59 p.m., Galaxy Being wrote: > However, I'm still wondering how to have an abstracted (x:xs) - like > pattern to collapse all the ingredients, i.e., > > whatHolder2 (Holder2 (sh)) = sh > whatHolder2 (shish2-head (shish2-tail)) = whatHolder2 shish2-tail -------------- next part -------------- An HTML attachment was scrubbed... URL: From kazu at iij.ad.jp Tue Mar 16 00:19:16 2021 From: kazu at iij.ad.jp (Kazu Yamamoto (=?iso-2022-jp?B?GyRCOzNLXE9CSScbKEI=?=)) Date: Tue, 16 Mar 2021 09:19:16 +0900 (JST) Subject: [Haskell-cafe] Future of package cryptonite In-Reply-To: <23d0cadd-d39d-6562-a17e-f4d171fe7467@pwned.gg> References: <20210315.091338.227613484946451382.kazu@iij.ad.jp> <23d0cadd-d39d-6562-a17e-f4d171fe7467@pwned.gg> Message-ID: <20210316.091916.1417169110587003758.kazu@iij.ad.jp> Hi Ximin, Cc: haskell-cafe According to the mail archive[1], your messages are not delivered to haskell-cafe. So, I'm citing your response below. [1] https://mail.haskell.org/pipermail/haskell-cafe/2021-March/ --Kazu From: Ximin Luo Subject: Re: [Haskell-cafe] Future of package cryptonite > Sven Panne: >> Am Mo., 15. März 2021 um 01:17 Uhr schrieb Kazu Yamamoto >: >> >> We should also take care of "memory", "foundation" and "basement". >> No action is taken for over a month to >> https://github.com/haskell-foundation/foundation/pull/549 >> >> >> Somehow I'm getting more and more allergic to all these hasty unwarranted "I want to take over package XY" requests. The last release of cryptonite was less than 7 weeks ago, a PR for foundation was not merged within 5 weeks, etc. etc.  For god's sake: If you are in such a hurry, just fork locally! Or even better: Give the maintainers a huge pile of $$$, most of them are doing their stuff in their spare time, so you can't expect SLAs where you would have to spend 5 digit sums as a company. Or you can fork visibly on e.g. GitHub under a different package name and let other people decide which variant to take. >> > > The cryptonite bugfix release in January is the *only* activity on the package for many months. As I understand from Kazu, Vincent has personally decided to quit, he just has not publicly announced it (nor made any other communications). > > So this bugfix release seems more of a "I guess I should really do the minimum to stop possible harm", rather than performing expected maintainer duties & making progress on the overall Haskell ecosystem. > >> "Taking over" a package can almost be seen as robbery from the point of view of the original author, and it is actively discouraging people to make their code Open Source. We should be much, much more sensitive in the Haskell community, I haven't seen such things in other language ecosystems. >> > > Haskell as an ecosystem is much smaller than other language ecosystems, and maintainers of key libraries like cryptonite going AWOL is unfortunately more common. Given that, it is expected to see more requests like this. > > Implicit in all of these requests is that, if the original maintainer restarts their normal maintainer activities, they can immediately re-exercise their maintainership activities and previous access. > > Package namespaces are a shared resource and its consequences affect everyone, and so "ownership" is not as simple as "who got it first". That is why we have a package takeover process in the first place. [1] One extreme case outside of Haskell would be the left-pad npm example. Nobody is taking away copyrights, licenses, or source code away from anyone; nobody has the power to do that. > > [1] https://wiki.haskell.org/Taking_over_a_package > >> Having said that, I think that a few projects are blocked by stack issues before they can support GHC 9.0. It would be great if things would be released more in lock-step, I dream of a world where a new GHC comes out in sync with cabal, stack, Stackage, Haskell language server etc. all supporting the new compiler. Other language ecosystems are lightyears ahead regarding this... :-/ >> >> Cheers, >>    S. > > -- > GPG: ed25519/56034877E1F87C35 > https://github.com/infinity0/pubkeys.git From J.Hage at uu.nl Tue Mar 16 08:11:30 2021 From: J.Hage at uu.nl (Hage, J. (Jurriaan)) Date: Tue, 16 Mar 2021 08:11:30 +0000 Subject: [Haskell-cafe] Final Call for the early round of Papers for the Haskell Symposium 2021 Message-ID: <8CA0F65D-81EF-4BA7-99E3-31DE83FCA6B6@uu.nl> Dear all, This is the final call for the early round of papers for the upcoming Haskell Symposium. Please forward to anyone that you believe might be interested. The deadline for this early round is March 19. Note that in May there is still the regular round of submissions. Apologies for receiving multiple copies of this announcement. Best regards, Jurriaan Hage Chair ================================================================================ ACM SIGPLAN CALL FOR SUBMISSIONS Haskell Symposium 2021 ** virtual ** Thu 26 -- Fri 27 August, 2021 http://www.haskell.org/haskell-symposium/2021/ ================================================================================ The ACM SIGPLAN Haskell Symposium 2021 will be co-located with the 2021 International Conference on Functional Programming (ICFP). Due to COVID-19 it will take place **virtually** this year. Like last year, we will be using a lightweight double-blind reviewing process. See further information below. Different from last year is that we offer a new submission category: the tutorial. Details can be found below. The Haskell Symposium presents original research on Haskell, discusses practical experience and future development of the language, and promotes other forms of declarative programming. Topics of interest include: * Language design, with a focus on possible extensions and modifications of Haskell as well as critical discussions of the status quo; * Theory, such as formal semantics of the present language or future extensions, type systems, effects, metatheory, and foundations for program analysis and transformation; * Implementations, including program analysis and transformation, static and dynamic compilation for sequential, parallel, and distributed architectures, memory management, as well as foreign function and component interfaces; * Libraries, that demonstrate new ideas or techniques for functional programming in Haskell; * Tools, such as profilers, tracers, debuggers, preprocessors, and testing tools; * Applications, to scientific and symbolic computing, databases, multimedia, telecommunication, the web, and so forth; * Functional Pearls, being elegant and instructive programming examples; * Experience Reports, to document general practice and experience in education, industry, or other contexts; * Tutorials, to document how to use a particular language feature, programming technique, tool or library within the Haskell ecosystem; * System Demonstrations, based on running software rather than novel research results. Regular papers should explain their research contributions in both general and technical terms, identifying what has been accomplished, explaining why it is significant, and relating it to previous work, and to other languages where appropriate. Experience reports and functional pearls need not necessarily report original academic research results. For example, they may instead report reusable programming idioms, elegant ways to approach a problem, or practical experience that will be useful to other users, implementers, or researchers. The key criterion for such a paper is that it makes a contribution from which other Haskellers can benefit. It is not enough simply to describe a standard solution to a standard programming problem, or report on experience where you used Haskell in the standard way and achieved the result you were expecting. A new submission category for this year's Haskell Symposium is the tutorial. Like with the experience report and the functional pearl, the key criterion for such a paper is that it makes a contribution from which other Haskellers can benefit. What distinguishes a tutorial is that its focus is on explaining an aspect of the Haskell language and/or ecosystem in a way that is generally useful to a Haskell audience. Tutorials for many such topics can be found online; the distinction here is that by writing it up for formal review it will be vetted by experts and formally published. System demonstrations should summarize the system capabilities that would be demonstrated. The proposals will be judged on whether the ensuing session is likely to be important and interesting to the Haskell community at large, whether on grounds academic or industrial, theoretical or practical, technical, social or artistic. Please contact the program chair with any questions about the relevance of a proposal. If your contribution is not a research paper, please mark the title of your experience report, functional pearl, tutorial or system demonstration as such, by supplying a subtitle (Experience Report, Functional Pearl, Tutorial Paper, System Demonstration). Submission Details ================== Early and Regular Track ----------------------- The Haskell Symposium uses a two-track submission process so that some papers can gain early feedback. Strong papers submitted to the early track are accepted outright, and the others will be given their reviews and invited to resubmit to the regular track. Papers accepted via the early and regular tracks are considered of equal value and will not be distinguished in the proceedings. Although all papers may be submitted to the early track, authors of functional pearls and experience reports are particularly encouraged to use this mechanism. The success of these papers depends heavily on the way they are presented, and submitting early will give the program committee a chance to provide feedback and help draw out the key ideas. Formatting ---------- Submitted papers should be in portable document format (PDF), formatted using the ACM SIGPLAN style guidelines. Authors should use the `acmart` format, with the `sigplan` sub-format for ACM proceedings. For details, see: http://www.sigplan.org/Resources/Author/#acmart-format It is recommended to use the `review` option when submitting a paper; this option enables line numbers for easy reference in reviews. Functional pearls, experience reports, tutorials and demo proposals should be labelled clearly as such. Lightweight Double-blind Reviewing ---------------------------------- Haskell Symposium 2021 will use a lightweight double-blind reviewing process. To facilitate this, submitted papers must adhere to two rules: 1. Author names and institutions must be omitted, and 2. References to authors' own related work should be in the third person (e.g., not "We build on our previous work" but rather "We build on the work of "). The purpose of this process is to help the reviewers come to an initial judgment about the paper without bias, not to make it impossible for them to discover the authors if they were to try. Nothing should be done in the name of anonymity that weakens the submission or makes the job of reviewing the paper more difficult (e.g., important background references should not be omitted or anonymized). In addition, authors should feel free to disseminate their ideas or draft versions of their paper as they normally would. For instance, authors may post drafts of their papers on the web or give talks on their research ideas. A reviewer will learn the identity of the author(s) of a paper after a review is submitted. Page Limits ----------- The length of submissions should not exceed the following limits: Regular paper: 12 pages Functional pearl: 12 pages Tutorial: 12 pages Experience report: 6 pages Demo proposal: 2 pages There is no requirement that all pages are used. For example, a functional pearl may be much shorter than 12 pages. In all cases, the list of references is not counted against these page limits. Deadlines --------- Early track: Submission deadline: 19 March 2021 (Fri) Notification: 23 April 2021 (Fri) Regular track and demos: Submission deadline: 21 May 2021 (Fri) Notification: 23 June 2021 (Wed) Deadlines are valid anywhere on Earth. Submission ---------- Submissions must adhere to SIGPLAN's republication policy (http://sigplan.org/Resources/Policies/Republication/), and authors should be aware of ACM's policies on plagiarism (https://www.acm.org/publications/policies/plagiarism). Program Committee members are allowed to submit papers, but their papers will be held to a higher standard. The paper submission deadline and length limitations are firm. There will be no extensions, and papers violating the length limitations will be summarily rejected. Papers should be submitted through HotCRP at: https://haskell21.hotcrp.com/ Improved versions of a paper may be submitted at any point before the submission deadline using the same web interface. Supplementary material: Authors have the option to attach supplementary material to a submission, on the understanding that reviewers may choose not to look at it. This supplementary material should not be submitted as part of the main document; instead, it should be uploaded as a separate PDF document or tarball. Supplementary material should be uploaded at submission time, not by providing a URL in the paper that points to an external repository. Authors can distinguish between anonymized and non-anonymized supplementary material. Anonymized supplementary material will be visible to reviewers immediately; non-anonymized supplementary material will be revealed to reviewers only after they have submitted their review of the paper and learned the identity of the author(s). Resubmitted Papers: authors who submit a revised version of a paper that has previously been rejected by another conference have the option to attach an annotated copy of the reviews of their previous submission(s), explaining how they have addressed these previous reviews in the present submission. If a reviewer identifies him/herself as a reviewer of this previous submission and wishes to see how his/her comments have been addressed, the conference chair will communicate to this reviewer the annotated copy of his/her previous review. Otherwise, no reviewer will read the annotated copies of the previous reviews. Proceedings =========== Accepted papers will be included in the ACM Digital Library. Their authors will be required to choose one of the following options: - Author retains copyright of the work and grants ACM a non-exclusive permission-to-publish license (and, optionally, licenses the work with a Creative Commons license); - Author retains copyright of the work and grants ACM an exclusive permission-to-publish license; - Author transfers copyright of the work to ACM. For more information, please see ACM Copyright Policy (http://www.acm.org/publications/policies/copyright-policy) and ACM Author Rights (http://authors.acm.org/main.html). Accepted proposals for system demonstrations will be posted on the symposium website but not formally published in the proceedings. Publication date: The official publication date of accepted papers is the date the proceedings are made available in the ACM Digital Library. This date may be up to two weeks prior to the first day of the conference. The official publication date affects the deadline for any patent filings related to published work. Artifacts ========= Authors of accepted papers are encouraged to make auxiliary material (artifacts like source code, test data, etc.) available with their paper. They can opt to have these artifacts published alongside their paper in the ACM Digital Library (copyright of artifacts remains with the authors). If an accepted paper's artifacts are made permanently available for retrieval in a publicly accessible archival repository like the ACM Digital Library, that paper qualifies for an Artifacts Available badge (https://www.acm.org/publications/policies/artifact-review-badging#available). Applications for such a badge can be made after paper acceptance and will be reviewed by the PC chair. Program Committee ================= Edwin Brady University of St Andrews Koen Claessen Chalmers University of Technology Dominique Devriese Vrije Universiteit Brussel Andy Gill University of Kansas Jurriaan Hage (chair) Universiteit Utrecht Zhenjiang Hu Peking University Ranjit Jhala University of California Patricia Johann Appalachian State University Yukiyoshi Kameyama University of Tsukuba George Karachalias Tweag Ralf Laemmel University of Koblenz-Landau Daan Leijen Microsoft Research Ben Lippmeier Ghost Locomotion Neil Mitchell Facebook Alberto Pardo Universidad de la Republica, Uruguay Matt Roberts Macquarie University Janis Voigtlaender University of Duisburg-Essen Nicolas Wu Imperial College London If you have questions, please contact the chair at: j.hage at uu.nl ================================================================================ From ben.franksen at online.de Tue Mar 16 12:59:09 2021 From: ben.franksen at online.de (Ben Franksen) Date: Tue, 16 Mar 2021 13:59:09 +0100 Subject: [Haskell-cafe] shorter error messages Message-ID: Is there a way to tell ghc to print errors, especially type errors in a more concise way? Ideally one or two lines of text? I hate it when I have to scroll several pages of text just to see the next/previous error location. Cheers Ben -- Niemand hat das Recht zu gehorchen. -- Hannah Arendt From carter.schonwald at gmail.com Tue Mar 16 15:21:56 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Tue, 16 Mar 2021 11:21:56 -0400 Subject: [Haskell-cafe] shorter error messages In-Reply-To: References: Message-ID: I don’t think so! But it’s a great idea perhaps! How do other tools do it? And or is there a bread crumb you could do find next/previous match on the current output for? Or is that missing and the real issue to address? On Tue, Mar 16, 2021 at 9:02 AM Ben Franksen wrote: > Is there a way to tell ghc to print errors, especially type errors in a > more concise way? Ideally one or two lines of text? I hate it when I > have to scroll several pages of text just to see the next/previous error > location. > > Cheers > Ben > -- > Niemand hat das Recht zu gehorchen. -- Hannah Arendt > > _______________________________________________ > 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 lemming at henning-thielemann.de Tue Mar 16 15:37:13 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Tue, 16 Mar 2021 16:37:13 +0100 (CET) Subject: [Haskell-cafe] shorter error messages In-Reply-To: References: Message-ID: On Tue, 16 Mar 2021, Ben Franksen wrote: > Is there a way to tell ghc to print errors, especially type errors in a > more concise way? Ideally one or two lines of text? I hate it when I > have to scroll several pages of text just to see the next/previous error > location. It has become especially worse since undefined identifiers are now sometimes handled by the type checker. A simple "xyz is not defined" can now consume many pages of follow-up type errors. From carter.schonwald at gmail.com Tue Mar 16 15:56:46 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Tue, 16 Mar 2021 11:56:46 -0400 Subject: [Haskell-cafe] shorter error messages In-Reply-To: References: Message-ID: Huh! When does that happen? I thought that’s only with leading underscore for typed hole syntax On Tue, Mar 16, 2021 at 11:40 AM Henning Thielemann < lemming at henning-thielemann.de> wrote: > > On Tue, 16 Mar 2021, Ben Franksen wrote: > > > Is there a way to tell ghc to print errors, especially type errors in a > > more concise way? Ideally one or two lines of text? I hate it when I > > have to scroll several pages of text just to see the next/previous error > > location. > > It has become especially worse since undefined identifiers are now > sometimes handled by the type checker. A simple "xyz is not defined" can > now consume many pages of follow-up type errors. > _______________________________________________ > 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 stuebinm at disroot.org Tue Mar 16 15:58:47 2021 From: stuebinm at disroot.org (stuebinm) Date: Tue, 16 Mar 2021 16:58:47 +0100 Subject: [Haskell-cafe] shorter error messages In-Reply-To: References: Message-ID: <496756c2-00d7-d717-48bc-ae53528a9974@disroot.org> I've found this problem to be largely solved when using the haskell language server with the emacs lsp mode — it just marks whatever call would throw a type error and gives you a (usually) reasonably short hint of what went wrong. So far I've also not seen any false alerts — but then I've only been using it for a week or so, so maybe I just haven't run into them yet. Of course, this doesn't really help if you really want to just use ghc by itself, but perhaps it would be possible to write some minimal client for the language server which just shows you the errors? Barring that, I guess you /could/ do something like $ ghc 2>&1 | grep "Couldn't match" -A 4 to get a list of type errors, but that's rarely actually useful ... stuebinm On 16.03.21 16:21, Carter Schonwald wrote: > I don’t think so! But it’s a great idea perhaps!  How do other tools do > it? And or is there a bread crumb you could do find next/previous match > on the current output for? Or is that missing and the real issue to address? > > On Tue, Mar 16, 2021 at 9:02 AM Ben Franksen > wrote: > > Is there a way to tell ghc to print errors, especially type errors in a > more concise way? Ideally one or two lines of text? I hate it when I > have to scroll several pages of text just to see the next/previous error > location. > > Cheers > Ben > -- > Niemand hat das Recht zu gehorchen. -- Hannah Arendt > > _______________________________________________ > 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 -------------- A non-text attachment was scrubbed... Name: OpenPGP_0x695C841098BECF1D.asc Type: application/pgp-keys Size: 3131 bytes Desc: not available URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: OpenPGP_signature Type: application/pgp-signature Size: 840 bytes Desc: OpenPGP digital signature URL: From lemming at henning-thielemann.de Tue Mar 16 16:00:26 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Tue, 16 Mar 2021 17:00:26 +0100 (CET) Subject: [Haskell-cafe] shorter error messages In-Reply-To: References: Message-ID: <55682fdf-493f-3292-aa91-aa5c326a6a4e@henning-thielemann.de> On Tue, 16 Mar 2021, Carter Schonwald wrote: > Huh! When does that happen? I thought that’s only with leading > underscore for typed hole syntax  I don't know exactly, it happens sometimes but not always. From x at tomsmeding.com Tue Mar 16 16:40:41 2021 From: x at tomsmeding.com (Tom Smeding) Date: Tue, 16 Mar 2021 16:40:41 +0000 Subject: [Haskell-cafe] shorter error messages In-Reply-To: <496756c2-00d7-d717-48bc-ae53528a9974@disroot.org> References: <496756c2-00d7-d717-48bc-ae53528a9974@disroot.org> Message-ID: In any case, the haskell language server just uses GHC internally, so it just shortens the GHC message. But then I believe the same result could be accomplished by some simple text manipulation on GHC's normal output. - Tom ‐‐‐‐‐‐‐ Original Message ‐‐‐‐‐‐‐ On Tuesday, March 16, 2021 4:58 PM, stuebinm via Haskell-Cafe wrote: > I've found this problem to be largely solved when using the haskell > language server with the emacs lsp mode — it just marks whatever call > would throw a type error and gives you a (usually) reasonably short hint > of what went wrong. So far I've also not seen any false alerts — but > then I've only been using it for a week or so, so maybe I just haven't > run into them yet. > > Of course, this doesn't really help if you really want to just use ghc > by itself, but perhaps it would be possible to write some minimal client > for the language server which just shows you the errors? > > Barring that, I guess you /could/ do something like > $ ghc 2>&1 | grep "Couldn't match" -A 4 > to get a list of type errors, but that's rarely actually useful ... > > stuebinm > > On 16.03.21 16:21, Carter Schonwald wrote: > > > I don’t think so! But it’s a great idea perhaps!  How do other tools do > > it? And or is there a bread crumb you could do find next/previous match > > on the current output for? Or is that missing and the real issue to address? > > On Tue, Mar 16, 2021 at 9:02 AM Ben Franksen > mailto:ben.franksen at online.de> wrote: > > > > Is there a way to tell ghc to print errors, especially type errors in a > > more concise way? Ideally one or two lines of text? I hate it when I > > have to scroll several pages of text just to see the next/previous error > > location. > > > > Cheers > > Ben > > -- > > Niemand hat das Recht zu gehorchen. -- Hannah Arendt > > > > _______________________________________________ > > 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 jaro.reinders at gmail.com Tue Mar 16 16:56:59 2021 From: jaro.reinders at gmail.com (Jaro Reinders) Date: Tue, 16 Mar 2021 17:56:59 +0100 Subject: [Haskell-cafe] shorter error messages In-Reply-To: References: <496756c2-00d7-d717-48bc-ae53528a9974@disroot.org> Message-ID: On 16-03-2021 17:40, Tom Smeding wrote: > In any case, the haskell language server just uses GHC internally, so it just shortens the GHC message. But then I believe the same result could be accomplished by some simple text manipulation on GHC's normal output. In fact, you can use -ddump-json to get JSON error messages. I should be easy to convert that to any form you like. But there is no clear specification of that output: https://gitlab.haskell.org/ghc/ghc/-/issues/19278 And I also want to point out that there is a big open issue for better error messages: https://gitlab.haskell.org/ghc/ghc/-/issues/8809 From rae at richarde.dev Tue Mar 16 18:07:41 2021 From: rae at richarde.dev (Richard Eisenberg) Date: Tue, 16 Mar 2021 18:07:41 +0000 Subject: [Haskell-cafe] shorter error messages In-Reply-To: References: <496756c2-00d7-d717-48bc-ae53528a9974@disroot.org> Message-ID: <010f01783c38d626-a685b7fa-ffc9-49cb-bb10-1de9df00b965-000000@us-east-2.amazonses.com> There is no "official" way to accommodate this reasonable request. The ideas up-thread are good ones. I want to pipe in that we're currently going through an internal overhaul of error-message handling that will make such a request much easier to contemplate in the future. This is active work going on right now. So there is hope, possibly for 9.4. Of course, once the internal overhaul is done, we'll need to design any features that actually change the output -- the overhaul just makes it easy to implement such features (which would be very difficult at the moment). Richard > On Mar 16, 2021, at 12:56 PM, Jaro Reinders wrote: > > On 16-03-2021 17:40, Tom Smeding wrote: >> In any case, the haskell language server just uses GHC internally, so it just shortens the GHC message. But then I believe the same result could be accomplished by some simple text manipulation on GHC's normal output. > > In fact, you can use -ddump-json to get JSON error messages. I should be easy to convert that to any form you like. > > But there is no clear specification of that output: > https://gitlab.haskell.org/ghc/ghc/-/issues/19278 > > And I also want to point out that there is a big open issue for better error messages: > https://gitlab.haskell.org/ghc/ghc/-/issues/8809 > _______________________________________________ > 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 ietf-dane at dukhovni.org Wed Mar 17 02:21:09 2021 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Tue, 16 Mar 2021 22:21:09 -0400 Subject: [Haskell-cafe] Can eta-reduction of (\xs -> augment (flip (flip . foldr) xs)) typecheck? Message-ID: With both `augment` and `foldr` from GHC.Base: augment :: (forall b. (a -> b -> b) -> b -> b) -> [a] -> [a] augment g = g (:) foldr :: (a -> b -> b) -> b -> [a] -> b ... The function: \xs -> augment (g xs) where g xs c z = foldr c z xs -- pointfree: g == flip (flip . foldr) typechecks (it is in fact just (++)) λ> let g xs c z = foldr c z xs λ> :t \xs -> augment (g xs) \xs -> augment (g xs) :: [a] -> [a] -> [a] Is it possible to explicitly type annotate some `g'` so that the function: (\xs -> (augment . g') xs) :: [a] -> [a] -> [a] is also just (++). That is, basically `g'` is the same as g, but with an explicit type signature that makes the type checker accept the eta-reduced composition? A completely naive attempt, with no type annotations yields: λ> let g xs c z = foldr c z xs λ> :t g g :: [a] -> (a -> b -> b) -> b -> b λ> :t (augment . g) :1:2: error: • Couldn't match type: forall b. (a1 -> b -> b) -> b -> b with: (a -> b0 -> b0) -> b0 -> b0 Expected: ((a -> b0 -> b0) -> b0 -> b0) -> [a1] -> [a1] Actual: (forall b. (a1 -> b -> b) -> b -> b) -> [a1] -> [a1] • In the first argument of ‘(.)’, namely ‘augment’ In the expression: augment . g I haven't found any variant type signatures for "g" that make this go. I think this may require impredicative polymorphism, and so can't be done until perhaps QuickLook lands (don't know whether that'll be enough). -- Viktor. From andrei.h.popescu at gmail.com Wed Mar 17 11:10:02 2021 From: andrei.h.popescu at gmail.com (Andrei Popescu) Date: Wed, 17 Mar 2021 11:10:02 +0000 Subject: [Haskell-cafe] 21st Midlands Graduate School in the Foundations of Computing Science: Final Call for Participation Message-ID: FINAL CALL FOR PARTICIPATION 21st Midlands Graduate School in the Foundations of Computing Science MGS 21 12-16 April 2021, virtually https://staffwww.dcs.shef.ac.uk/people/G.Struth/mgs21.html OVERVIEW The annual Midlands Graduate School in the Foundations of Computing Science (MGS) offers an intensive programme of lectures on the mathematical foundations of computing. It addresses first of all PhD students in their first or second year, but is open to anyone interested in its topics, from academia to industry and around the world. The MGS has been run since 1999 and is hosted alternately by the Universities of Birmingham, Leicester, Nottingham and Sheffield. MGS 21 is its 21st incarnation. Information about previous events can be found at the MGS web site http://www.cs.nott.ac.uk/MGS PROGRAMME MGS 21 consists of eight courses, each with four or five hours of lectures and a similar number of exercise sessions. Three courses are introductory; one is given by an invited lecturer. These should be attended by all participants. The remaining more advanced courses should be selected based on interest. MGS 21 aims at a mix of livestreamed and prerecorded lectures and livestreamed exercise sessions, with additional social online events. Invited lectures: Monads and Interactions Tarmo Uustalu, Reykjavik Introductory courses: Category Theory Jacopo Emmenegger, Birmingham Type Theory Thorsten Altenkirch, Nottingham Proof Theory Anupam Das, Birmingham Advanced courses: Homotopy Type Theory Nicolai Kraus, Nottingham Inductive and Coinductive Reasoning with Isabelle/HOL Andrei Popescu, Sheffield Effects and Call-by-Push-Value Paul Levy, Birmingham Formal Modelling and Analysis of Concurrent Systems Mohammad Mousavi, Leicester In addition we are organising a session where participants can briefly present and discuss their own research. A call will be made in March. REGISTRATION Participation at MGS 21 is free of charge, but selective. Requests must be submitted online via https://staffwww.dcs.shef.ac.uk/people/G.Struth/mgs21.html Registration deadline is April 1. ORGANISATION Please direct all queries about MGS 21 to Georg Struth. The Sheffield organisers are Harsh Beohar (H.Beohar at sheffield.ac.uk) Andrei Popescu (A.Popescu at sheffield.ac.uk) Georg Struth (G.Struth at sheffield.ac.uk) From matteo at confscience.com Wed Mar 17 11:46:00 2021 From: matteo at confscience.com (matteo at confscience.com) Date: Wed, 17 Mar 2021 12:46:00 +0100 Subject: [Haskell-cafe] International Conference on Applied Data Science and Intelligence - (ADSI 2021) Prague Message-ID: <00f101d71b23$1a752890$4f5f79b0$@confscience.com> Call for papers ************************************************* International Conference on Applied Data Science and Intelligence - (ADSI 2021) Prague- Czech Republic, October 14-15, 2021 https://confscience.com/adsi/ Submission deadline: April 1, 2021 All papers accepted in ADSI 2021 will be published in Springer CCIS (Communications in Computer and Information Science). CCIS is abstracted/indexed in Scopus, SCImago, EI-Compendex, Mathematical Reviews, DBLP, Google Scholar, and Thomson Reuters Conference Proceedings Citation (Former ISI Proceedings) *************************************************************************** IMPORTANT DATES: - Paper Submission: April 1, 2021 - Acceptance Notification: July 1, 2021 - Final Manuscript Due: September 1, 2021 *************************************************************************** The ADSI 2021 conference will be held in Conjunction with: International Conference on Recent Theories and Applications in Transportation and Mobility (RTATM 2021) International Conference on Informatics Revolution for Smarter Healthcare (IRSH 2021) *************************************************************************** TOPICS: Authors are invited to submit their original papers to address the topics of the conference, including but not limited to: FUNDAMENTALS AND THEORIES - Theoretical Models - Spatial and temporal multi-models - Multi-dimensional data - Data acquisition and pre-processing - Data inference - Data Classification and Taxonomy - Data Metrics - New approaches for collaboration and competition - Self-organization, self-healing, fault-tolerance approaches - Spatial reasoning - Context awareness - Intelligent mobility - New approaches to supervised and unsupervised learning - New approaches for security, privacy, trust, and ethics in data science - Real-time data analytics - Multi-Agent Systems for data science - Distributed data analytics - Data authenticity - New theories and approaches for Deep learning - New approaches for Business Intelligence - Fuzzy logic - Decision trees - Support vector machines - Evolutionary computation - Statistical methods - Collaborative filtering - Data engineering - Content mining - Indexing schemes - Information retrieval - Metadata use and management INTELLIGENT DATA PROCESSING AND ANALYTICS - Multi-level data processing - Data analytics optimization - Smart data mining - Machine Learning - Deep Learning - Bio-Inspired Computing - Secure data analytics - Privacy in data analytics - Trust in Big Data - Business intelligence - Visualization Analytics - Intelligence as a Service (IaaS) - Data Science as a Service (DSaaS) - Natural Language Processing - Signal Processing - Simulation and Modeling - Data-Intensive Computing SYSTEMS AND INFRASTRUCTURES - Data storage infrastructure - Data warehouses - Data Query and Indexing Technologies - Software Defined Infrastructures - Software Defined Networks (SDN) - Distributed data systems - Smart grid computing - Intelligent data management - Big Data computing - Smart data networking - Internet of Things - Cyber Physical Systems - Blockchain - Fog and Edge intelligence - Parallel Computing systems - Open Source systems for data science - Embedded intelligence - Embedded data science - In-Memory computing - Intelligent drones - Internet of Drones - Real-time data acquisition systems APPLICATIONS - Intelligent Hazard management - Intelligent data science in healthcare - Intelligent data science in farming - Intelligent data science in Oil and Gas - Smart logistics - Intelligent data science in transportation - Intelligent data science in surveillance - Xtech (Fintech, Agritech, etc.) - Intelligent drones - Digital transformation - Bioinformatics - Marketing - Social Science - E-learning and E-services *************************************************************************** OUTSTANDING PAPERS: Based on the peer review scores as well as the presentations at the conference, the authors of outstanding papers will be invited to extend their works for a potential publication in journals special issues with high impact factors. *************************************************************************** PAPER SUBMISSION: Papers must be submitted electronically as PDF files via easychair (https://easychair.org/conferences/?conf=adsi2021). All papers will be peer reviewed. Length of Full papers: 12-15 pages long (written in the LNCS/CCIS one-column page format, 400 words per page) Length of Short papers: less than 12 pages For more information, please refer to the conference website: https://confscience.com/adsi/ *************************************************************************** CONTACT For more information, please send an email to info-adsi at confscience.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben.franksen at online.de Wed Mar 17 12:08:50 2021 From: ben.franksen at online.de (Ben Franksen) Date: Wed, 17 Mar 2021 13:08:50 +0100 Subject: [Haskell-cafe] shorter error messages In-Reply-To: <010f01783c38d626-a685b7fa-ffc9-49cb-bb10-1de9df00b965-000000@us-east-2.amazonses.com> References: <496756c2-00d7-d717-48bc-ae53528a9974@disroot.org> <010f01783c38d626-a685b7fa-ffc9-49cb-bb10-1de9df00b965-000000@us-east-2.amazonses.com> Message-ID: Am 16.03.21 um 19:07 schrieb Richard Eisenberg: > There is no "official" way to accommodate this reasonable request. > The ideas up-thread are good ones. Thanks everyone for the many suggestions. I am using cabal to build. Vim and emacs and IDEs are not in my toolbox for various reasons. Of course I can do shell hacking to filter the messages, just wanted to ask if there is a more convenient way. > I want to pipe in that we're currently going through an internal > overhaul of error-message handling that will make such a request > much easier to contemplate in the future. This is active work going > on right now. So there is hope, possibly for 9.4. Of course, once > the internal overhaul is done, we'll need to design any features > that actually change the output -- the overhaul just makes it easy > to implement such features (which would be very difficult at the > moment). Looking forward to that! It seems I am not the only one who would, occasionally, prefer to get error messages in a more condensed form. Cheers Ben From rae at richarde.dev Wed Mar 17 13:30:30 2021 From: rae at richarde.dev (Richard Eisenberg) Date: Wed, 17 Mar 2021 13:30:30 +0000 Subject: [Haskell-cafe] shorter error messages In-Reply-To: References: <496756c2-00d7-d717-48bc-ae53528a9974@disroot.org> <010f01783c38d626-a685b7fa-ffc9-49cb-bb10-1de9df00b965-000000@us-east-2.amazonses.com> Message-ID: <010f017840616e06-a3ffec38-bef4-4d6e-99c7-7597c9e32a9a-000000@us-east-2.amazonses.com> In the short-term: I'll take option 3. We've already changed some of the datatypes around there, and the new output reflects the new structure. I did poke around a bit (https://gitlab.haskell.org/ghc/ghc/-/issues/19278) asking if anyone relied on the existing structure, and we were told just to update as we saw fit. In the longer-term: Option 1. The JSON feature is, essentially, undesigned. It just happened. There is no real specification or supported story for what tools are likely to consume the data. After this overhaul, it will be easy to imagine arbitrarily structured and informative JSON output, and so I imagine we'll start a conversation with consumers (i.e. IDEs and similar tools) to design an advertised interface. This interface will need to be somewhat unstable in perpetuity, as GHC improves errors, adds new ones, etc. But my hope is that the stated design encompasses this need for change and specifies what will and will not change over time. Maybe even there will be a way to query GHC for its JSON schema? Not sure. An important detail is that the flag for JSON output is -ddump-json, starting with a `d`; this means it's in the "debugging GHC" section of the manual. I hope that changes someday (where "hope" implies that I will actively support efforts at doing so). Richard > On Mar 16, 2021, at 6:01 PM, Sebastiaan Joosten wrote: > > Hi Richard, > > this raises a question about the upcoming overhaul: is the JSON dump format following -ddump-json most likely to: > 1. change a lot (complete overhaul is likely and/or feature might disappear - say because all datatypes will be changed and the JSON is just some 'deriving Generic' ToJSON dump with default parameters) > 2. stay the same mostly (if/wherever it changes, it is either a bug or deliberate feature) > 3. change in minor ways (stability is not considered important in the overhaul but there are no reasons to believe this part of the code will be affected much) > ? > > What would your guess be? > > Sebastiaan > > PS: feel free to reply to cafe if that seems fitting – my mails there get rejected (issue on my end) > >> On 16 Mar 2021, at 14:07, Richard Eisenberg wrote: >> >> There is no "official" way to accommodate this reasonable request. The ideas up-thread are good ones. >> >> I want to pipe in that we're currently going through an internal overhaul of error-message handling that will make such a request much easier to contemplate in the future. This is active work going on right now. So there is hope, possibly for 9.4. Of course, once the internal overhaul is done, we'll need to design any features that actually change the output -- the overhaul just makes it easy to implement such features (which would be very difficult at the moment). >> >> Richard >> >>> On Mar 16, 2021, at 12:56 PM, Jaro Reinders wrote: >>> >>> On 16-03-2021 17:40, Tom Smeding wrote: >>>> In any case, the haskell language server just uses GHC internally, so it just shortens the GHC message. But then I believe the same result could be accomplished by some simple text manipulation on GHC's normal output. >>> >>> In fact, you can use -ddump-json to get JSON error messages. I should be easy to convert that to any form you like. >>> >>> But there is no clear specification of that output: >>> https://gitlab.haskell.org/ghc/ghc/-/issues/19278 >>> >>> And I also want to point out that there is a big open issue for better error messages: >>> https://gitlab.haskell.org/ghc/ghc/-/issues/8809 >>> _______________________________________________ >>> 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 javran.c at gmail.com Thu Mar 18 01:00:00 2021 From: javran.c at gmail.com (Javran Cheng) Date: Wed, 17 Mar 2021 18:00:00 -0700 Subject: [Haskell-cafe] Some Alex beginner questions regarding parsing Java In-Reply-To: References: Message-ID: Few days after I wrote the OP, I realized I had some misconceptions and now I can answer few of my own questions (I still don't get the second one though): On Mon, Mar 15, 2021 at 3:42 PM Javran Cheng wrote: > Hi Cafe! > > Firstly, sorry for spamming if you already see this on Stack Overflow, I > do feel this is too much for a single SO question. > > I'm recently playing with Alex + Happy to try parsing Java (for now I'm > only working on the lexer / Alex, so whenever you see "parse" below, that > means tokenize). My reference is Java SE 15 Spec, the chapter of interest > is Chapter 3. Lexical Structure > (side > note: my timing is a bit interesting as I just realized as of writing this, > Java SE 16 spec is out just few days ago, so I might switch to that) and > now that I've get my hand dirty a bit, I have few questions and hope if > someone can shed some light on them: > > 1. For now I'm using "monad-bytestring" wrapper for performance, but > now I think maybe String-based wrapper is more appropriate, for it allows > me to follow 1. and 2. in "3.2. Lexical Translations" properly before > passing the input to Alex - namely I can pre-process input stream to (1) do > Unicode escaping to turn the raw byte flow into a flow of Chars (2) I can > normalize line terminators into just \n. But: > 1. Are those two passes (Unicode escape and line terminator > normalization) possible within Alex framework? > 2. Is there any way that I can stick with a memory-compact string > representation? (not sure why Alex doesn't provide any Text-based wrapper, > as it did mention in its doc that it internally works on UTF-8 encoded byte > sequence) I could probably consider to not use any wrapper, as GHC and Agda > did, but that's sort of an undocumented territory so I'm hesitated to do so. > > I'm actually less worried about String-based parsing now - I'm not really keeping a chunk of String and moving it around like data, I'm consuming it, and this is fine as long as backtracking is minimized. And for whatever reason I totally missed "5.2 Basic interface" in Alex's user manual, which answers my "how to use Alex without wrapper" question - I can just run alex command and copy what's necessary from generated source code - now I know I just need the definition of AlexInput, alexGetByte, alexInputPrevChar and whatever transitively required. > > 1. The other trouble I have regarding "3.2. Lexical Translations" is > the special rules applied to ">"s: "... There is one exception: if > lexical translation occurs in a type context (§4.11) ..." - but how in the > world am I going to do this? I mean the lexical analysis is not even done > how am I going to tell whether it's a type context (and §4.11 is quite long > that I won't even try to read it, unless forced)? Maybe I can just tokenize > every ">" as an individual operatior, as if ">>", ">>=", ">>>", and ">>>=" > don't exist and worry about that later, but that doesn't sound right to me. > > This one I still don't get - any help is appreciated. > > 1. I realize there's a need for "irrecoverable failure": I have a test > case with octal literal "012389", which is supposed to fail, but Alex > happily tokenized that into [octal "0123", decimal "89"] - for now my > workaround is for every number literal to check whether previous char is a > digit and fail if it is indeed so, but I feel this is like ducktaping on a > flawed approach and at some point it will fail on some edge cases. an ideal > fix IMO would be to have some notion of irrecoverable failure - failing to > parse a literal at full should be irrecoverable rather than trying to parse > most of it and move on. In addition, as Java spec requires that if a > numeric literal doesn't fit in the intended type, it's a compilation error > - which can also be encoded as an irrecoverable failure as well. I'm not > sure how to do that in Alex though, I can see few ways: > 1. encode irrecoverable failure by setting to a special startcode, > which does not provide anyway to go back to startcode 0 - so an > irrecoverable failure sets that special startcode, and at the start of > every action, it checks whether startcode is the special "failure" > startcode and fail accordingly > 2. this is similar to startcode, but use a wrapper that supports > userstate. > 3. maybe this is another case that not using a wrapper would give > me more control, but I don't have a concrete idea regarding this > alternative. > > This is another thing that I totally misunderstood: I wrote the Alex rule for recognizing octals as "0(0-7)+", of course only "0123" bit of "012389" matches! Instead I should probably just accept a boarder pattern and deal with them in Alex actions (This is similar to just do regex "(\d+\.){3}\d+" and check whether numbers are in 0~255 range for parsing and validating IPv4 address), this way allow me to throw informative errors. And Alex is actually capable of doing "irrecoverable failures", as it's just a newtype around a state function that returns "Either String _". Although I'd like the error type to be finer than String, which now I'm happy to just roll my own without alex wrappers. > Any thoughts on this is appreciated. > > Thanks! > Javran (Fang) Cheng > Cheers, -- Javran (Fang) Cheng -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Thu Mar 18 01:11:50 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Wed, 17 Mar 2021 21:11:50 -0400 Subject: [Haskell-cafe] Some Alex beginner questions regarding parsing Java In-Reply-To: References: Message-ID: On Wed, Mar 17, 2021 at 9:02 PM Javran Cheng wrote: > Few days after I wrote the OP, I realized I had some misconceptions and > now I can answer few of my own questions (I still don't get the second one > though): > > On Mon, Mar 15, 2021 at 3:42 PM Javran Cheng wrote: > >> Hi Cafe! >> >> Firstly, sorry for spamming if you already see this on Stack Overflow, I >> do feel this is too much for a single SO question. >> >> I'm recently playing with Alex + Happy to try parsing Java (for now I'm >> only working on the lexer / Alex, so whenever you see "parse" below, that >> means tokenize). My reference is Java SE 15 Spec, the chapter of interest >> is Chapter 3. Lexical Structure >> (side >> note: my timing is a bit interesting as I just realized as of writing this, >> Java SE 16 spec is out just few days ago, so I might switch to that) and >> now that I've get my hand dirty a bit, I have few questions and hope if >> someone can shed some light on them: >> >> 1. For now I'm using "monad-bytestring" wrapper for performance, but >> now I think maybe String-based wrapper is more appropriate, for it allows >> me to follow 1. and 2. in "3.2. Lexical Translations" properly before >> passing the input to Alex - namely I can pre-process input stream to (1) do >> Unicode escaping to turn the raw byte flow into a flow of Chars (2) I can >> normalize line terminators into just \n. But: >> 1. Are those two passes (Unicode escape and line terminator >> normalization) possible within Alex framework? >> 2. Is there any way that I can stick with a memory-compact string >> representation? (not sure why Alex doesn't provide any Text-based wrapper, >> as it did mention in its doc that it internally works on UTF-8 encoded byte >> sequence) I could probably consider to not use any wrapper, as GHC and Agda >> did, but that's sort of an undocumented territory so I'm hesitated to do so. >> >> I'm actually less worried about String-based parsing now - I'm not really > keeping a chunk of String and moving it around like data, I'm consuming it, > and this is fine as long as backtracking is minimized. > And for whatever reason I totally missed "5.2 Basic interface" in Alex's > user manual, which answers my "how to use Alex without wrapper" question - > I can just run alex command and copy what's necessary from generated source > code - now I know I just need the definition of AlexInput, alexGetByte, > alexInputPrevChar and whatever transitively required. > >> >> 1. The other trouble I have regarding "3.2. Lexical Translations" is >> the special rules applied to ">"s: "... There is one exception: if >> lexical translation occurs in a type context (§4.11) ..." - but how in the >> world am I going to do this? I mean the lexical analysis is not even done >> how am I going to tell whether it's a type context (and §4.11 is quite long >> that I won't even try to read it, unless forced)? Maybe I can just tokenize >> every ">" as an individual operatior, as if ">>", ">>=", ">>>", and ">>>=" >> don't exist and worry about that later, but that doesn't sound right to me. >> >> This one I still don't get - any help is appreciated. > >> >> 1. I realize there's a need for "irrecoverable failure": I have a >> test case with octal literal "012389", which is supposed to fail, but >> Alex happily tokenized that into [octal "0123", decimal "89"] - for >> now my workaround is for every number literal to check whether previous >> char is a digit and fail if it is indeed so, but I feel this is like >> ducktaping on a flawed approach and at some point it will fail on some edge >> cases. an ideal fix IMO would be to have some notion of irrecoverable >> failure - failing to parse a literal at full should be irrecoverable rather >> than trying to parse most of it and move on. In addition, as Java spec >> requires that if a numeric literal doesn't fit in the intended type, it's a >> compilation error - which can also be encoded as an irrecoverable failure >> as well. I'm not sure how to do that in Alex though, I can see few ways: >> 1. encode irrecoverable failure by setting to a special startcode, >> which does not provide anyway to go back to startcode 0 - so an >> irrecoverable failure sets that special startcode, and at the start of >> every action, it checks whether startcode is the special "failure" >> startcode and fail accordingly >> 2. this is similar to startcode, but use a wrapper that supports >> userstate. >> 3. maybe this is another case that not using a wrapper would give >> me more control, but I don't have a concrete idea regarding this >> alternative. >> >> This is another thing that I totally misunderstood: I wrote the Alex rule > for recognizing octals as "0(0-7)+", of course only "0123" bit of "012389" > matches! Instead I should probably just accept a boarder pattern and deal > with them in Alex actions (This is similar to just do regex "(\d+\.){3}\d+" > and check whether numbers are in 0~255 range for parsing and validating > IPv4 address), this way allow me to throw informative errors. And Alex is > actually capable of doing "irrecoverable failures", as it's just a newtype > around a state function that returns "Either String _". Although I'd like > the error type to be finer than String, which now I'm happy to just roll my > own without alex wrappers. > > This sortah rule is akin to something agda does, roughly , which is treat stuff as a single token unless there’s a white space separator. For that matter, agdas parser may be a good example of a pretty fancy use of happy and Alex. Though it itself was originally based on the happy/Alex parsers in ghc. Any thoughts on this is appreciated. >> >> Thanks! >> Javran (Fang) Cheng >> > > Cheers, > -- > Javran (Fang) Cheng > _______________________________________________ > 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 ben.franksen at online.de Thu Mar 18 07:35:52 2021 From: ben.franksen at online.de (Ben Franksen) Date: Thu, 18 Mar 2021 08:35:52 +0100 Subject: [Haskell-cafe] strange cabal error Message-ID: Any idea what I am running into here? ben at home[5]:.../softIOC/home>cabal build Resolving dependencies... TODO: add support for multiple packages in a directory CallStack (from HasCallStack): error, called at ./Distribution/Client/ProjectOrchestration.hs:548:9 in main:Distribution.Client.ProjectOrchestration This appears immediately after I issued a (successful) ben at home[5]:.../softIOC/home>cabal init --minimal --package-name test Cheers Ben -- I would rather have questions that cannot be answered, than answers that cannot be questioned. -- Richard Feynman From ben.franksen at online.de Thu Mar 18 07:54:22 2021 From: ben.franksen at online.de (Ben Franksen) Date: Thu, 18 Mar 2021 08:54:22 +0100 Subject: [Haskell-cafe] strange cabal error In-Reply-To: References: Message-ID: Am 18.03.21 um 08:35 schrieb Ben Franksen: > Any idea what I am running into here? > > ben at home[5]:.../softIOC/home>cabal build > Resolving dependencies... > TODO: add support for multiple packages in a directory > CallStack (from HasCallStack): > error, called at ./Distribution/Client/ProjectOrchestration.hs:548:9 > in main:Distribution.Client.ProjectOrchestration > > This appears immediately after I issued a (successful) > > ben at home[5]:.../softIOC/home>cabal init --minimal --package-name test This was with cabal-install-3.2. Upgrading to -head fixes it. Nevertheless, I'd be interested to know how to avoid that error with 3.2. Cheers Ben -- I would rather have questions that cannot be answered, than answers that cannot be questioned. -- Richard Feynman From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Sun Mar 21 08:14:09 2021 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Sun, 21 Mar 2021 08:14:09 +0000 Subject: [Haskell-cafe] Global Package Install In-Reply-To: References: Message-ID: <20210321081409.GF15119@cloudinit-builder> On Thu, Feb 18, 2021 at 03:35:10PM -0500, Viktor Dukhovni wrote: > On Thu, Feb 18, 2021 at 12:22:52AM -0800, A. Mc. wrote: > You can use "cabal repl -z" to run ghci with the Cabal "user" package > database in scope: I'm confused by this. What is 'the Cabal "user" package database'? The --help text says -z --ignore-project Only include explicitlyspecified packages (and 'base'). I can't see any evidence locally that it brings any packages into scope. Could you please clarify exactly what -z is doing in your example below? Thanks, Tom > $ ghci > GHCi, version 9.0.1: https://www.haskell.org/ghc/ :? for help > λ> :set -package iproute > cannot satisfy -package iproute > (use -v for more information) > λ> > Leaving GHCi. > > $ cabal repl -z > Resolving dependencies... > Build profile: -w ghc-9.0.1 -O1 > In order, the following will be built (use -v for more details): > - fake-package-0 (lib) (first run) > Configuring library for fake-package-0.. > Preprocessing library for fake-package-0.. > Warning: No exposed modules > GHCi, version 9.0.1: https://www.haskell.org/ghc/ :? for help > Loaded GHCi configuration from /tmp/cabal-repl.-87318/setcwd.ghci > λ> :set -XOverloadedStrings > λ> :set -package iproute > package flags have changed, resetting and loading new packages... > λ> import Data.IP > λ> import Numeric > λ> showHex (fromIPv4w "127.0.0.1") "" > "7f000001" From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Sun Mar 21 08:40:39 2021 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Sun, 21 Mar 2021 08:40:39 +0000 Subject: [Haskell-cafe] Global Package Install In-Reply-To: <010f0177b6ffcbb6-6a4d2bc7-a2ba-4e2e-b868-a484b15472eb-000000@us-east-2.amazonses.com> References: <010f0177b6ffcbb6-6a4d2bc7-a2ba-4e2e-b868-a484b15472eb-000000@us-east-2.amazonses.com> Message-ID: <20210321084039.GG15119@cloudinit-builder> On Thu, Feb 18, 2021 at 09:15:53PM +0000, Richard Eisenberg wrote: > > On Feb 18, 2021, at 3:48 PM, Viktor Dukhovni wrote: > > > > $ cabal repl -v0 -z --repl-options -package=iproute --repl-options -XOverloadedStrings > > Yes, but it's so, so much easier just to say `ghci`. And then I can > pass lots of options to `ghci` directly when I want to. And I don't > have to spend time writing and maintaining wrapper scripts. I was reminded of this thread because I just saw yet another post (this time on Haskell Discourse) from a user confused about how the v1-style global package database is supposed to work these days. In this thread we had a few people mention that they prefer the "global package database" style. I'd like to improve my understanding of why people prefer that style. I believe it was only Richard who explained his rationale (above). For me personally, "global package database" style was useful because I could "cabal install" a package and then "ghc" or "ghci" would have it immediately available. However, I have since given up trying to get that style to work and now I use the "--build-depends" or "create a temporary cabal package" approach[0]. So what are the benefits of the "global package database" workflow style? Is it just that cabal -z repl --package QuickCheck --repl-options="whatever" is more of a pain to type than ghci "whatever" and that creating a .cabal file and running "cabal build" is more of a pain than typing "ghc", or is there something fundamental that the "global package database" supports that cabal v2-style does not? Tom [0] http://h2.jaguarpaw.co.uk/posts/how-i-use-cabal/ From genaim at gmail.com Sun Mar 21 08:40:42 2021 From: genaim at gmail.com (Samir Genaim) Date: Sun, 21 Mar 2021 09:40:42 +0100 Subject: [Haskell-cafe] WST 2021 - Call for Papers Message-ID: ====================================================================== WST 2021 - Call for Papers 17th International Workshop on Termination http://costa.fdi.ucm.es/wst2021 July 16, 2021, Pittsburgh, PA, United States Co-located with CADE-28 *** The Workshop will be Virtual *** ====================================================================== The Workshop on Termination (WST) traditionally brings together, in an informal setting, researchers interested in all aspects of termination, whether this interest be practical or theoretical, primary or derived. The workshop also provides a ground for cross-fertilization of ideas from the different communities interested in termination (e.g., working on computational mechanisms, programming languages, software engineering, constraint solving, etc.). The friendly atmosphere enables fruitful exchanges leading to joint research and subsequent publications. IMPORTANT DATES: * submission deadline: April 25, 2021 * notification: May 30, 2021 * final version due: June 13, 2021 * workshop: July 16, 2021 INVITED SPEAKERS: TBA TOPICS: The 17th International Workshop on Termination welcomes contributions on all aspects of termination. In particular, papers investigating applications of termination (for example in complexity analysis, program analysis and transformation, theorem proving, program correctness, modeling computational systems, etc.) are very welcome. Topics of interest include (but are not limited to): * abstraction methods in termination analysis * certification of termination and complexity proofs * challenging termination problems * comparison and classification of termination methods * complexity analysis in any domain * implementation of termination methods * non-termination analysis and loop detection * normalization and infinitary normalization * operational termination of logic-based systems * ordinal notation and subrecursive hierarchies * SAT, SMT, and constraint solving for (non-)termination analysis * scalability and modularity of termination methods * termination analysis in any domain (lambda calculus, declarative programming, rewriting, transition systems, etc.) * well-founded relations and well-quasi-orders SUBMISSION GUIDELINES: Submissions are short papers/extended abstracts which should not exceed 5 pages. There will be no formal reviewing. In particular, we welcome short versions of recently published articles and papers submitted elsewhere. The program committee checks relevance and provides additional feedback for each submission. The accepted papers will be made available electronically before the workshop. Papers should be submitted electronically via the submission page: https://easychair.org/conferences/?conf=wst2021 Please, use LaTeX and the LIPIcs style file http://drops.dagstuhl.de/styles/lipics/lipics-authors.tgz to prepare your submission. PROGRAM COMMITTEE: * Martin Avanzini - INRIA Sophia, Antipolis * Carsten Fuhs - Birkbeck, U. of London * Samir Genaim (chair) - U. Complutense de Madrid * Jürgen Giesl - RWTH Aachen * Matthias Heizmann - U. of Freiburg * Cynthia Kop - Radboud U. Nijmegen * Salvador Lucas - U. Politècnica de València * Étienne Payet - U. de La Réunion * Albert Rubio - U. Complutense de Madrid * René Thiemann - U. of Innsbruck -------------- next part -------------- An HTML attachment was scrubbed... URL: From ietf-dane at dukhovni.org Sun Mar 21 10:01:23 2021 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Sun, 21 Mar 2021 06:01:23 -0400 Subject: [Haskell-cafe] Global Package Install In-Reply-To: <20210321081409.GF15119@cloudinit-builder> References: <20210321081409.GF15119@cloudinit-builder> Message-ID: On Sun, Mar 21, 2021 at 08:14:09AM +0000, Tom Ellis wrote: > On Thu, Feb 18, 2021 at 03:35:10PM -0500, Viktor Dukhovni wrote: > > You can use "cabal repl -z" to run ghci with the Cabal "user" package > > database in scope: > > I'm confused by this. What is 'the Cabal "user" package database'? > The --help text says > > -z --ignore-project Only include explicitlyspecified packages (and 'base'). With the "-z" flag, "cabal repl" stops looking for ".cabal" files in the current directory (sandbox if you like), and just works with whatever is installed in the Cabal package database. Thus, because I've previously compiled optparse-applicative and streaming-bytestring: $ (cd ~/.cabal/store/ghc-8.10.4; ls -d optparse-applicative* streaming-byte*) optparse-applicative-0.16.1.0-eee378057b7539bcf75579d76e9f4ff170b047a9ccc498b6fe1ba5d2dfa9075a streaming-bytestring-0.2.0-8e7f82f7151e104bdca4aac21a045ebe5b332e0490a839f8fba8a3901dfcd58a I can run: $ cabal repl -v0 -z λ> import Data.Either λ> :set -package bytestring λ> import Data.ByteString λ> :set -package streaming-bytestring λ> import Streaming.ByteString λ> :set -package optparse-applicative λ> import Options.Applicative λ> :t strOption strOption :: Data.String.IsString s => Mod OptionFields s -> Parser s λ> :t unconsChunk unconsChunk :: Monad m => ByteStream m r -> m (Either r (Data.ByteString.ByteString, ByteStream m r)) whereas the same does not generally work with just ghci, which does not know about Cabal's package store: $ ghci -v0 λ> :set -package bytestring λ> :set -package streaming-bytestring cannot satisfy -package streaming-bytestring (use -v for more information) λ> :set -package optparse-applicative cannot satisfy -package optparse-applicative (use -v for more information) However, (perhaps dependent on one's Cabal configuration settings) when I use "cabal install --lib some-package" I also end up with a GHC environment file created as a side-effect of the "cabal install". Below I request "base" which is already there, so the only effect is to create the environment file: $ cabal install --lib base Resolving dependencies... Up to date $ cat ~/.ghc/x86_64-freebsd-8.10.4/environments/default clear-package-db global-package-db package-db /home/viktor/.cabal/store/ghc-8.10.4/package.db package-id ghc-8.10.4 package-id bytestring-0.10.12.0 package-id unix-2.7.2.2 package-id base-4.14.1.0 package-id time-1.9.3 package-id hpc-0.6.1.0 package-id filepath-1.4.2.1 package-id process-1.6.9.0 package-id array-0.5.4.0 package-id integer-gmp-1.0.3.0 package-id containers-0.6.4.1 package-id ghc-boot-8.10.4 package-id binary-0.8.8.0 package-id ghc-prim-0.6.1 package-id ghci-8.10.4 package-id rts-1.0.1 package-id terminfo-0.4.1.4 package-id transformers-0.5.6.2 package-id deepseq-1.4.4.0 package-id ghc-boot-th-8.10.4 package-id pretty-1.1.3.6 package-id template-haskell-2.16.0.0 package-id directory-1.3.6.0 package-id text-1.2.4.1 Once the environment file is in place, I can: $ ghci -v0 λ> import Data.Either λ> :set -package optparse-applicative λ> import Options.Applicative λ> :set -package streaming-bytestring λ> import Streaming.ByteString λ> :set -package bytestring λ> import Data.ByteString λ> :t strOption strOption :: Data.String.IsString s => Mod OptionFields s -> Parser s λ> :t unconsChunk unconsChunk :: Monad m => ByteStream m r -> m (Either r (Data.ByteString.ByteString, ByteStream m r)) > I can't see any evidence locally that it brings any packages into > scope. Could you please clarify exactly what -z is doing in your > example below? With "-z" I can load any pre-built library from the Cabal package store, rather than just the dependencies of the current project. -- Viktor. From johannes.waldmann at htwk-leipzig.de Sun Mar 21 17:55:38 2021 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Sun, 21 Mar 2021 18:55:38 +0100 Subject: [Haskell-cafe] Global Package Install Message-ID: <57e93f69-6c31-8831-7123-62b912f341b6@htwk-leipzig.de> > .. a few people mention that they prefer the > "global package database" style. I'd like to improve my understanding > of why people prefer that style. Teaching. Reduce storage, and save students the extra work and distraction. https://github.com/haskell/cabal/issues/7172 same question, with discussion of possible work-around with "shared local" database: https://github.com/haskell/cabal/issues/6515 I will need this in two week's time .. - J.W. From duke.j.david at gmail.com Sun Mar 21 18:13:54 2021 From: duke.j.david at gmail.com (David Duke) Date: Sun, 21 Mar 2021 18:13:54 +0000 Subject: [Haskell-cafe] Global Package Install In-Reply-To: <57e93f69-6c31-8831-7123-62b912f341b6@htwk-leipzig.de> References: <57e93f69-6c31-8831-7123-62b912f341b6@htwk-leipzig.de> Message-ID: > .. a few people mention that they prefer the > "global package database" style. I'd like to improve my understanding > of why people prefer that style. I had/have a strong preference for the global package database. a) teaching. no longer relevant but when it was beyond the points already raised: - simplified helping students when we were clearly using the same codebase - assessment: easier to set and advise when you know exactly what libraries/versions the class will be using. It was also easier to set up by passing code requirements to support staff before term. they would ensure tools and a list of required libraries were installed. b) research, - I often found it helpful to move between ghci and my program text, testing ideas or checking types in ghci then copying and pasting into the file - ghc-pkg plus the Haskell doc provided a usable and helpful foundation for work c) I saw no reason to try an alternative version of working nor any evidence that one would make my life any easier On Sun, Mar 21, 2021 at 5:58 PM Johannes Waldmann < johannes.waldmann at htwk-leipzig.de> wrote: > > .. a few people mention that they prefer the > > "global package database" style. I'd like to improve my understanding > > of why people prefer that style. > > Teaching. > > Reduce storage, and save students the extra work and distraction. > https://github.com/haskell/cabal/issues/7172 > > same question, with discussion of > possible work-around with "shared local" database: > https://github.com/haskell/cabal/issues/6515 > > I will need this in two week's time .. > > - 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. -- David Duke Emeritus Professor of Computer Science School of Computing University of Leeds UK E:duke.j.david at gmail.com W:https://engineering.leeds.ac.uk/staff/334/Professor_David_Duke -------------- next part -------------- An HTML attachment was scrubbed... URL: From power.walross at gmail.com Sun Mar 21 20:04:02 2021 From: power.walross at gmail.com (Fendor) Date: Sun, 21 Mar 2021 21:04:02 +0100 Subject: [Haskell-cafe] Global Package Install In-Reply-To: <57e93f69-6c31-8831-7123-62b912f341b6@htwk-leipzig.de> References: <57e93f69-6c31-8831-7123-62b912f341b6@htwk-leipzig.de> Message-ID: Since I am helping with a university course myself at the moment, I want to add that the work-around described in the second linked cabal issue (#6515), namely setting `store-dir` and `remote-repo-cache` to a global read-only location, works very well in practice. In my opinion, it achieves its goals easily: * Reduce storage (everyone uses the same index and packages) * Easy to synchronize (you can install additional versions for all students) * Easy to maintain (new semester? Just remove the store folder and build every package anew) And for the easier `ghci` workflow, a generated ghci environment file is also really handy and easy to upgrade/change. Best regards, Fendor On 3/21/21 6:55 PM, Johannes Waldmann wrote: >> .. a few people mention that they prefer the >> "global package database" style. I'd like to improve my understanding >> of why people prefer that style. > Teaching. > > Reduce storage, and save students the extra work and distraction. > https://github.com/haskell/cabal/issues/7172 > > same question, with discussion of > possible work-around with "shared local" database: > https://github.com/haskell/cabal/issues/6515 > > I will need this in two week's time .. > > - 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. From johannes.waldmann at htwk-leipzig.de Sun Mar 21 20:33:33 2021 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Sun, 21 Mar 2021 21:33:33 +0100 Subject: [Haskell-cafe] Global Package Install Message-ID: Hi. Interesting discussion. Thanks for data points on using cabal-install for the classroom. > the work-around described in the second linked cabal issue (#6515), > namely setting `store-dir` and `remote-repo-cache` > to a global read-only location, works very well in practice. Good to know. I will look into it. This "setting" has to be done by each student (once)? Well, they have to create/change other configurations as well (e.g., put proper PATH in .bashrc) so it's probably OK. And, students can then not cabal-install extra private packages? (With global package installs, they could. But perhaps it's better that they cannot, for all the reasons mentioned.) > .. helping students when we were clearly using the same codebase this is solved by `stack --resolver=<...>` but that eats space and requires another extra tool (stack) besides ghc(i). > I saw no reason to try an alternative version [to the global install] Well I did, and that reason was "cabal hell", where "global hell" is the worst, as it regularly requires a fresh ghc install. So for my own work of course I do use per-user install, and other forms of isolation. Best regards, Johannes. From javran.c at gmail.com Mon Mar 22 08:44:56 2021 From: javran.c at gmail.com (Javran Cheng) Date: Mon, 22 Mar 2021 01:44:56 -0700 Subject: [Haskell-cafe] ANN unicode-general-category-0.1.0.0 Message-ID: Hi Cafe, I'm happy to announce the release of a new package: unicode-general-category. This package provides the same set of functions related to Unicode general category found in Data.Char, but uses information from Unicode 13.0.0 - in addition a set of tools are offered to turn any modern UnicodeData.txt into such a set of functions. I wrote this as a by-product of my recent adventure into parsing Java (it follows Unicode 13, but Data.Char is dependent on GHC versions), but hope this can also be helpful to others in some way. https://hackage.haskell.org/package/unicode-general-category https://github.com/Javran/unicode-general-category Cheers, Javran (Fang) Cheng -------------- next part -------------- An HTML attachment was scrubbed... URL: From matteo at confscience.com Mon Mar 22 09:48:15 2021 From: matteo at confscience.com (matteo at confscience.com) Date: Mon, 22 Mar 2021 10:48:15 +0100 Subject: [Haskell-cafe] International Conference on Recent Theories and Applications in Transportation and Mobility - (RTATM 2021) Prague Message-ID: <005201d71f00$7b2b8630$71829290$@confscience.com> Call for papers ************************************************* International Conference on Recent Theories and Applications in Transportation and Mobility - (RTATM 2021) Prague - Czech Republic, October 14-15, 2021 https://confscience.com/rtatm/ Submission deadline: April 1, 2021 All papers accepted in RTATM 2021 will be published in Springer CCIS (Communications in Computer and Information Science). CCIS is abstracted/indexed in Scopus, SCImago, EI-Compendex, Mathematical Reviews, DBLP, Google Scholar, and Thomson Reuters Conference Proceedings Citation (Former ISI Proceedings) *************************************************************************** IMPORTANT DATES: - Paper Submission: April 1, 2021 - Acceptance Notification: July 1, 2021 - Final Manuscript Due: September 1, 2021 *************************************************************************** The RTATM 2021 conference will be held in Conjunction with: International Conference on Applied Data Science and Intelligence (ADSI 2021) International Conference on Informatics Revolution for Smarter Healthcare (IRSH 2021) *************************************************************************** TOPICS: Authors are invited to submit their original papers to address the topics of the conference, including but not limited to: FUNDAMENTALS AND THEORIES - Modelling and Simulation Algorithms - Vehicular Wireless Medium Access Control - V2X communications - Routings and Protocols for Connected Vehicles - Mobility Models and Architectures - Distribution Strategies - Traffic Incident Management Systems - Bio-Inspired Approaches - Optimization and Collaboration - Automatic Control in Vehicular Networks - Energy-aware Connected Mobility - Programming Languages - Sustainable Transportation - Multimodal Transportation Networks and Systems - Systemsb Integration - Driver Behavior Models and Simulation - Human Factors and Travel Behaviour - Green Mobility - Regulations and Bylaws for Intelligent - Transportation and Mobility SMART TRANSPORTATION AND LOGISTICS - Mobility Management - Connected Vehicles - VANETs - Predictive Logistics - Spatio-Temporal Event Tracking - Decision Support Systems - Emergency Management - Logistics and E-Commerce - Supply Chain Design and Execution - Supply Chain Management - Advanced Planning Systems - Fleet Management - Multi-Agent Systems - Machine Learning for Smart Logistics - Intelligent Infrastructures - Real-time Analysis of Comprehensive Supply Chain Data - Smart Synchronization of Logistics Processes - New Approaches for Cost Transparency - Big Data for Smart Logistics - Logistics 4.0 - Mobile Networks - Next-Generation Smart Logistics - Performance Management Approaches - Tests and Deployment - Software Defined Networks - Smart Freight Management - Smart Shipment Management - Smart Warehousing - Smart Inventory management DATA AND SERVICES - Real-Time transportation Data Acquisition - Event Detection and Monitoring - Data Warehouses for connected mobility - Data mining and Data analytics - Data Worthiness in Connected Vehicles - Data Trustworthiness for effective transportation and mobility - Road Traffic Data Analytics - Structured and Unstructured Data for Connected Mobility - Volunteered Geographic Information (VGI) - Data Representation for Connected Mobility - Transportation Data Mining - Transportation and mobility Data Visualization - Cognitive and Context-aware Intelligence - Transportation Decision Support Systems - Mobility as a Service (MaaS) - Intelligent Transportation Services - Smart Mobility Services - Big Data and Vehicle Analytics - Massive Data Management - Collective and connected Intelligence - Next Generation Services - Driver Behaviour Analysis - Geo-Spatial Services - Service-Oriented Architecture (SOA) - Web and Mobile Services SAFETY, SECURITY, AND HAZARD MANAGEMENT - Security Issues in Vehicular Communications - Safety Applications of Connected Vehicles - Weather-related Safety solutions - V2V, V2I and I2V Road Safety Applications - Connected Mobility for Hazard Management - Risk Management - Road Traffic Crashes Analytics - Traffic Jam Prediction - Resource Allocation for Hazard Management - Trust and Privacy Issues in Logistics - Management of Exceptional Events - New approaches to Networking Security for Transportation Applications - Failure modes, human factors, software safety - Automated Failure Analysis - Performance and Human Error Analysis - Design and Reliability of Control Systems - Dispersion Modelling Software - Quantification of Risk *************************************************************************** OUTSTANDING PAPERS: Based on the peer review scores as well as the presentations at the conference, the authors of outstanding papers will be invited to extend their works for a potential publication in journals special issues with high impact factors. *************************************************************************** PAPER SUBMISSION: Papers must be submitted electronically as PDF files via easychair (https://easychair.org/conferences/?conf=rtatm2021). All papers will be peer reviewed. Length of Full papers: 12-15 pages long (written in the LNCS/CCIS one-column page format, 400 words per page) Length of Short papers: less than 12 pages For more information, please refer to the conference website: https://confscience.com/rtatm/ *************************************************************************** CONTACT For more information, please send an email to info-rtatm at confscience.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From xnningxie at gmail.com Mon Mar 22 11:52:11 2021 From: xnningxie at gmail.com (Ningning Xie) Date: Mon, 22 Mar 2021 11:52:11 +0000 Subject: [Haskell-cafe] Call for Talks: Haskell Implementors' Workshop Message-ID: Call for Talks ACM SIGPLAN Haskell Implementors' Workshop https://icfp21.sigplan.org/home/hiw-2021 Virtual, 22 Aug, 2021 Co-located with ICFP 2021 https://icfp21.sigplan.org/ Important dates --------------- Deadline: Wednesday, 30 June, 2021 (AoE) Notification: Wednesday, 14 July, 2021 Workshop: Sunday, 22 August, 2021 The 13th Haskell Implementors' Workshop is to be held alongside ICFP 2021 this year virtually. It is a forum for people involved in the design and development of Haskell implementations, tools, libraries, and supporting infrastructure, to share their work and discuss future directions and collaborations with others. Talks and/or demos are proposed by submitting an abstract, and selected by a small program committee. There will be no published proceedings. The workshop will be informal and interactive, with open spaces in the timetable and room for ad-hoc discussion, demos, and lightning short talks. Scope and target audience ------------------------- It is important to distinguish the Haskell Implementors' Workshop from the Haskell Symposium which is also co-located with ICFP 2021. The Haskell Symposium is for the publication of Haskell-related research. In contrast, the Haskell Implementors' Workshop will have no proceedings -- although we will aim to make talk videos, slides and presented data available with the consent of the speakers. The Implementors' Workshop is an ideal place to describe a Haskell extension, describe works-in-progress, demo a new Haskell-related tool, or even propose future lines of Haskell development. Members of the wider Haskell community encouraged to attend the workshop -- we need your feedback to keep the Haskell ecosystem thriving. Students working with Haskell are specially encouraged to share their work. The scope covers any of the following topics. There may be some topics that people feel we've missed, so by all means submit a proposal even if it doesn't fit exactly into one of these buckets: * Compilation techniques * Language features and extensions * Type system implementation * Concurrency and parallelism: language design and implementation * Performance, optimisation and benchmarking * Virtual machines and run-time systems * Libraries and tools for development or deployment Talks ----- We invite proposals from potential speakers for talks and demonstrations. We are aiming for 20-minute talks with 5 minutes for questions and changeovers. We want to hear from people writing compilers, tools, or libraries, people with cool ideas for directions in which we should take the platform, proposals for new features to be implemented, and half-baked crazy ideas. Please submit a talk title and abstract of no more than 300 words. Submissions should be made via HotCRP. The website is: https://icfp-hiw21.hotcrp.com/ We will also have lightning talks session. These have been very well received in recent years, and we aim to increase the time available to them. Lightning talks be ~7mins and are scheduled on the day of the workshop. Suggested topics for lightning talks are to present a single idea, a work-in-progress project, a problem to intrigue and perplex Haskell implementors, or simply to ask for feedback and collaborators. Logistics --------- Due to the on-going COVID-19 situation, ICFP (and, consequently, HIW) will be held remotely this year. However, the organizers are still working hard to provide for a great workshop experience. While we are sad that this year will lack the robust hallway track that is often the highlight of HIW, we believe that this remote workshop presents a unique opportunity to include more of the Haskell community in our discussion and explore new modes of communicating with our colleagues. We hope that you will join us in making this HIW as vibrant as any other. Program Committee ----------------- * Dominique Devriese (Vrije Universiteit Brussel) * Daan Leijen (Microsoft Research) * Andres Löh (Well-Typed LLP) * Julie Moronuki (Typeclass Consulting) * John Wiegley (DFINITY) * Ningning Xie (the University of Hong Kong) * Edward Z. Yang (Facebook AI Research) Contact ------- * Ningning Xie -------------- next part -------------- An HTML attachment was scrubbed... URL: From rae at richarde.dev Mon Mar 22 13:27:29 2021 From: rae at richarde.dev (Richard Eisenberg) Date: Mon, 22 Mar 2021 13:27:29 +0000 Subject: [Haskell-cafe] Global Package Install In-Reply-To: <20210321084039.GG15119@cloudinit-builder> References: <010f0177b6ffcbb6-6a4d2bc7-a2ba-4e2e-b868-a484b15472eb-000000@us-east-2.amazonses.com> <20210321084039.GG15119@cloudinit-builder> Message-ID: <010f01785a1e76af-17151048-bdcc-4697-b0db-0b7d9edf1b2b-000000@us-east-2.amazonses.com> > On Mar 21, 2021, at 4:40 AM, Tom Ellis wrote: > > So what are the benefits of the "global package database" workflow > style? Is it just that > > cabal -z repl --package QuickCheck --repl-options="whatever" > > is more of a pain to type than > > ghci "whatever" > > and that creating a .cabal file and running "cabal build" is more of a > pain than typing "ghc", or is there something fundamental that the > "global package database" supports that cabal v2-style does not? Maybe it's superficial, but this is the big thing for me, yes. I also tend to have long-running ghci sessions, and so I don't always know what packages I'll want before launching. Some of this is also, for me, philosophical: I don't want anything between me and GHC. That is, I want to know exactly what flags are being passed to GHC and to be able to control those flags myself. A tool that installs libraries should do that, and then get out of the way. Richard -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben.franksen at online.de Mon Mar 22 14:06:31 2021 From: ben.franksen at online.de (Ben Franksen) Date: Mon, 22 Mar 2021 15:06:31 +0100 Subject: [Haskell-cafe] Global Package Install In-Reply-To: <010f01785a1e76af-17151048-bdcc-4697-b0db-0b7d9edf1b2b-000000@us-east-2.amazonses.com> References: <010f0177b6ffcbb6-6a4d2bc7-a2ba-4e2e-b868-a484b15472eb-000000@us-east-2.amazonses.com> <20210321084039.GG15119@cloudinit-builder> <010f01785a1e76af-17151048-bdcc-4697-b0db-0b7d9edf1b2b-000000@us-east-2.amazonses.com> Message-ID: >> cabal -z repl --package QuickCheck --repl-options="whatever" >> >> is more of a pain to type than >> >> ghci "whatever" >> >> and that creating a .cabal file and running "cabal build" is more >> of a pain than typing "ghc", or is there something fundamental that >> the "global package database" supports that cabal v2-style does >> not? > > Maybe it's superficial, but this is the big thing for me, yes. I also > tend to have long-running ghci sessions, and so I don't always know > what packages I'll want before launching. > > Some of this is also, for me, philosophical: I don't want anything > between me and GHC. That is, I want to know exactly what flags are > being passed to GHC and to be able to control those flags myself. A > tool that installs libraries should do that, and then get out of the > way. I think this amounts to a call for action to fix `cabal install --lib` (assuming the v2- variant). Indeed when I tried this with cabal-head my cabal store became unusable, which hasn't happened to me for a very long time now. (Deleting ~/.cabal/store/ghc-8.2.2 fixed it.) Cheers Ben -- I would rather have questions that cannot be answered, than answers that cannot be questioned. -- Richard Feynman From jeffbrown.the at gmail.com Tue Mar 23 16:18:42 2021 From: jeffbrown.the at gmail.com (Jeffrey Brown) Date: Tue, 23 Mar 2021 11:18:42 -0500 Subject: [Haskell-cafe] Implementing Dragon, Uber's data-integration tool for property graphs Message-ID: If your interests include any nonempty subset of Haskell, category theory and graphs, you might enjoy this. Online attendance is free. (For all I know in-person attendance is free too, if you live near SF area.) https://www.meetup.com/Category-Theory/events/nnrhgsyccfbhc -- Jeff Brown | Jeffrey Benjamin Brown LinkedIn | Github | Twitter | Facebook | very old Website -------------- next part -------------- An HTML attachment was scrubbed... URL: From olf at aatal-apotheke.de Wed Mar 24 14:47:44 2021 From: olf at aatal-apotheke.de (Olaf Klinke) Date: Wed, 24 Mar 2021 15:47:44 +0100 Subject: [Haskell-cafe] ANN closed-intervals-0.1 Message-ID: Dear Cafe, I am pleased to announce the first release of closed-intervals [1], a package for querying and manipulating collections of closed intervals in totally ordered types. Other packages exist which either deal with a single interval type [2,4] or provide an interval type class [3]. Having both closed, open and half-open intervals makes the interface complicated, however. The focus of closed-intervals is on intervals including both end-points and is intended to be used on records with length or duration information. My use cases are mostly sequences of annotated time intervals [*], parsed from time-stamped data. Against these sequences overlap-, coverage- and intersection queries are run using single intervals as query. The package contains many doctests. Testing builds on Henning Thielemann's doctest-extract [5] and doctest-exitcode-io [6] packages. closed-intervals is, after provenience [7], the second package in an effort to open-source my employer's entire Haskell codebase. We will gradually publish from general to problem-specific. Cheers, Olaf [1] https://hackage.haskell.org/package/closed-intervals [2] https://hackage.haskell.org/package/data-interval [3] https://hackage.haskell.org/package/IntervalMap [4] https://hackage.haskell.org/package/intervals [5] https://hackage.haskell.org/package/doctest-extract [6] https://hackage.haskell.org/package/doctest-exitcode-io [7] https://hackage.haskell.org/package/provenience [*] Since time types are fine-grained and a time point is an idealized concept, the question of end-point inclusion is not that relevant for time intervals. We do distinguish between intersection in end-points and proper intersection, though. From ifl21.publicity at gmail.com Wed Mar 24 15:59:06 2021 From: ifl21.publicity at gmail.com (Pieter Koopman) Date: Wed, 24 Mar 2021 08:59:06 -0700 Subject: [Haskell-cafe] IFL2021 First call for papers Message-ID: ================================================================================ IFL 2021 33rd Symposium on Implementation and Application of Functional Languages venue: online 1 - 3 September 2021 https://ifl21.cs.ru.nl ================================================================================ Scope The goal of the IFL symposia is to bring together researchers actively engaged in the implementation and application of functional and function-based programming languages. IFL 2021 will be a venue for researchers to present and discuss new ideas and concepts, work in progress, and publication-ripe results related to the implementation and application of functional languages and function-based programming. Industrial track and topics of interest This year's edition of IFL explicitly solicits original work concerning *applications* of functional programming in industry and academia. These contributions will be reviewed by experts with an industrial background. Topics of interest to IFL include, but are not limited to: * language concepts * type systems, type checking, type inferencing * compilation techniques * staged compilation * run-time function specialisation * run-time code generation * partial evaluation * (abstract) interpretation * meta-programming * generic programming * automatic program generation * array processing * concurrent/parallel programming * concurrent/parallel program execution * embedded systems * web applications * (embedded) domain-specific languages * security * novel memory management techniques * run-time profiling performance measurements * debugging and tracing * testing and proofing * virtual/abstract machine architectures * validation, verification of functional programs * tools and programming techniques * applications of functional programming in the industry, including ** functional programming techniques for large applications ** successes of the application functional programming ** challenges for functional programming encountered ** any topic related to the application of functional programming that is interesting for the IFL community Post-symposium peer-review Following IFL tradition, IFL 2021 will use a post-symposium review process to produce the formal proceedings. Before the symposium authors submit draft papers. These draft papers will be screened by the program chairs to make sure that they are within the scope of IFL. The draft papers will be made available to all participants at the symposium. Each draft paper is presented by one of the authors at the symposium. After the symposium every presenter is invited to submit a full paper, incorporating feedback from discussions at the symposium. Work submitted to IFL may not be simultaneously submitted to other venues; submissions must adhere to ACM SIGPLAN's republication policy. The program committee will evaluate these submissions according to their correctness, novelty, originality, relevance, significance, and clarity, and will thereby determine whether the paper is accepted or rejected for the formal proceedings. We plan to publish these proceedings in the International Conference Proceedings Series of the ACM Digital Library, as in previous years. Moreover, the proceedings will also be made publicly available as open access. Important dates Submission deadline of draft papers: 17 August 2021 Notification of acceptance for presentation: 19 August 2021 Registration deadline: 30 August 2021 IFL Symposium: 1-3 September 2021 Submission of papers for proceedings: 6 December 2021 Notification of acceptance: 3 February 2022 Camera-ready version: 15 March 2022 ### Submission details All contributions must be written in English. Papers must use the ACM two columns conference format, which can be found at: http://www.acm.org/publications/proceedings-template Peter Landin Prize The Peter Landin Prize is awarded to the best paper presented at the symposium every year. The honoured article is selected by the program committee based on the submissions received for the formal review process. The prize carries a cash award equivalent to 150 Euros. Organisation IFL 2021 Chairs: Pieter Koopman and Peter Achten, Radboud University, The Netherlands IFL Publicity chair: Pieter Koopman, Radboud University, The Netherlands PC (under construction): Peter Achten (co-chair) - Radboud University, Netherlands Thomas van Binsbergen - University of Amsterdam, Netherlands Edwin Brady - University of St. Andrews, Scotland Laura Castro - University of A Coruña, Spain Youyou Cong - Tokyo Institute of Technology, Japan Olaf Chitil - University of Kent, England Andy Gill - University of Kansas, USA Clemens Grelck - University of Amsterdam, Netherlands John Hughes - Chalmers University, Sweden Pieter Koopman (co-chair) - Radboud University, Netherlands Cynthia Kop - Radboud University, Netherlands Jay McCarthey - University of Massachussetts Lowell, USA Neil Mitchell - Facebook, England Jan De Muijnck-Hughes - Glasgow University, Scotland Keiko Nakata - SAP Innovation Center Potsdam, Germany Jurriën Stutterheim - Standard Chartered, Singapore Simon Thompson - University of Kent, England Melinda Tóth - Eötvos Loránd University, Hungary Phil Trinder - Glasgow University, Scotland Meng Wang - University of Bristol, England Viktória Zsók - Eötvos Loránd University, Hungary Virtual symposium Because of the Covid-19 pandemic, this year IFL 2021 will be an online event, consisting of paper presentations, discussions and virtual social gatherings. Registered participants can take part from anywhere in the world. Acknowledgments This call-for-papers is an adaptation and evolution of content from previous instances of IFL. We are grateful to prior organisers for their work, which is reused here. [image: beacon] -------------- next part -------------- An HTML attachment was scrubbed... URL: From shubhammittal588 at gmail.com Thu Mar 25 16:25:40 2021 From: shubhammittal588 at gmail.com (Shubham Mittal) Date: Thu, 25 Mar 2021 21:55:40 +0530 Subject: [Haskell-cafe] Query regarding GSOC Message-ID: Hello I am Shubham from India currently pursuing BTech IT 2nd year. I would like to contribute to Haskell-Cafe as a part of GSOC. Can you please guide me how I can i do so? Thanks and Regards, Shubham Mittal -------------- next part -------------- An HTML attachment was scrubbed... URL: From borgauf at gmail.com Fri Mar 26 04:34:58 2021 From: borgauf at gmail.com (Galaxy Being) Date: Thu, 25 Mar 2021 23:34:58 -0500 Subject: [Haskell-cafe] Does Haskell have this SML syntax? Message-ID: I saw this in *The Little MLer*, a book on SML datatype 'a list = Empty | Cons of 'a * 'a list fun subst_c (pred) = fn (n,Empty) => Empty | (n,Cons(e,t)) => if pred (e) then Cons (n,subst_c (pred) (n,t)) else Cons (e,subst_c (pred) (n,t)) The data type is just a homemade list, and the function subst_c takes a predicate ('a -> Bool) and determines whether an incoming list's elements pass or fail. What is interesting is the fn ... => ... part which takes in more parameters, namely an 'a and an 'a list. Technically this fn... is an anonymous, nameless function, and it seems bizarre to me that it's nested inside the named function but still taking in parameters as if it were at the top level. Here's a previous version showing all three parameters at the top level fun subst_c (pred) (n,Empty) = Empty ... The purpose of the first function was to demonstrate currying. IOW, what the second unnamed function is doing behind the scenes can be broken down to two-stages (currying) of the first with named, then unnamed functions. So my question is, is there anything like this in Haskell where a function inside a function -- named or anonymous -- can take incoming parameters as if it were top level? LB -------------- next part -------------- An HTML attachment was scrubbed... URL: From kindaro at gmail.com Fri Mar 26 05:10:07 2021 From: kindaro at gmail.com (Ignat Insarov) Date: Fri, 26 Mar 2021 10:10:07 +0500 Subject: [Haskell-cafe] Does Haskell have this SML syntax? In-Reply-To: References: Message-ID: Hello Galaxy Being! You can do this: module Y where substitute ∷ (α → Bool) → (α, [α]) → [α] substitute predicate = \ thing → case thing of (_, [ ]) → [ ] (substitution, (x: xs)) → let remainder = substitute predicate (substitution, xs) in if predicate x then substitution: remainder else x: remainder It is even nicer since we can factor out the common part of the `if` block into a `let … in`. You can also enable the `LambdaCase` language extension and it will let you elide the `thing` thing. I am not sure if this is what your question is really about… In principle, of course Haskell has currying. Actually, functions are usually written in curried form in Haskell. Please let me know if I missed the substance of your question! From ietf-dane at dukhovni.org Fri Mar 26 05:21:17 2021 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Fri, 26 Mar 2021 01:21:17 -0400 Subject: [Haskell-cafe] Does Haskell have this SML syntax? In-Reply-To: References: Message-ID: On Thu, Mar 25, 2021 at 11:34:58PM -0500, Galaxy Being wrote: > I saw this in *The Little MLer*, a book on SML > > datatype 'a list = Empty | Cons of 'a * 'a list > > fun subst_c (pred) > = fn (n,Empty) => Empty > | (n,Cons(e,t)) => if pred (e) > then Cons (n,subst_c (pred) (n,t)) > else Cons (e,subst_c (pred) (n,t)) The Haskell version is: {-# LANGUAGE LambdaCase #-} data List a = Empty | Cons a (List a) deriving (Eq, Ord, Show) infixr 5 `Cons` -- | Substitute list elements matching a predicate with a given value. -- subst_c :: (a -> Bool) -- ^ Predicate for elements to replace -> (a, List a) -- ^ (Replacement element, input list) -> List a subst_c pred = \ case (_, Empty) -> Empty (n, Cons e t) | pred e -> Cons n $ subst_c pred (n, t) | otherwise -> Cons e $ subst_c pred (n, t) λ> :load subst_c.hs λ> subst_c odd (42::Int, 1 `Cons` 2 `Cons` 3 `Cons` Empty) Cons 42 (Cons 2 (Cons 42 Empty)) See also the table at: https://github.com/ghc-proposals/ghc-proposals/pull/302#issuecomment-791209499 (my favourite is option 2) which proposes alternatives for new syntax generalising "\ case" (LambdaCase) to allow anonymous functions to pattern match multiple arguments. That new syntax is not yet available, so for now "\ case" requires currying, such as seen in the SML code and the Haskell equivalent above. -- Viktor. From borgauf at gmail.com Fri Mar 26 05:26:47 2021 From: borgauf at gmail.com (Galaxy Being) Date: Fri, 26 Mar 2021 00:26:47 -0500 Subject: [Haskell-cafe] Does Haskell have this SML syntax? In-Reply-To: References: Message-ID: I'm sure you've answered my question, but I'm too much of a beginner to fathom it. If you could explain, that would be great, but I could also go off and try to grok it myself. Again, thanks. On Fri, Mar 26, 2021 at 12:09 AM Ignat Insarov wrote: > Hello Galaxy Being! > > You can do this: > > module Y where > > substitute ∷ (α → Bool) → (α, [α]) → [α] > substitute predicate = \ thing → case thing of > (_, [ ]) → [ ] > (substitution, (x: xs)) → > let remainder = substitute predicate (substitution, xs) in > if predicate x > then substitution: remainder > else x: remainder > > It is even nicer since we can factor out the common part of the `if` > block into a `let … in`. You can also enable the `LambdaCase` language > extension and it will let you elide the `thing` thing. > > I am not sure if this is what your question is really about… In > principle, of course Haskell has currying. Actually, functions are > usually written in curried form in Haskell. Please let me know if I > missed the substance of your question! > -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Fri Mar 26 05:37:01 2021 From: david.feuer at gmail.com (David Feuer) Date: Fri, 26 Mar 2021 01:37:01 -0400 Subject: [Haskell-cafe] Does Haskell have this SML syntax? In-Reply-To: References: Message-ID: Let's start with the basics: lambda expressions. ML says fn x => blah blah Haskell spells that \x -> blah blah Suppose you want to pattern match on the argument. If you only need one pattern, that's cool: \(x,y) -> blah blah But what if you need more than one pattern? Well, standard ("Report") Haskell makes you use a case expression: \mx -> case mx of Just x -> blah Nothing -> etcetera But GHC has a widely used language extension to get something more like ML. If you put -- The "language" is case insensitive. -- The LambdaCase is case sensitive. {-# language LambdaCase #-} at the very tippy top of your .hs file, or pass -XLambdaCase to GHCi, then you can write that last one \case Just x -> blah Nothing -> etcetera There has been some discussion of trying to expand that syntax to support anonymous functions of multiple arguments, but no proposal has been accepted as yet. On Fri, Mar 26, 2021, 1:27 AM Galaxy Being wrote: > I'm sure you've answered my question, but I'm too much of a beginner to > fathom it. If you could explain, that would be great, but I could also go > off and try to grok it myself. Again, thanks. > > On Fri, Mar 26, 2021 at 12:09 AM Ignat Insarov wrote: > >> Hello Galaxy Being! >> >> You can do this: >> >> module Y where >> >> substitute ∷ (α → Bool) → (α, [α]) → [α] >> substitute predicate = \ thing → case thing of >> (_, [ ]) → [ ] >> (substitution, (x: xs)) → >> let remainder = substitute predicate (substitution, xs) in >> if predicate x >> then substitution: remainder >> else x: remainder >> >> It is even nicer since we can factor out the common part of the `if` >> block into a `let … in`. You can also enable the `LambdaCase` language >> extension and it will let you elide the `thing` thing. >> >> I am not sure if this is what your question is really about… In >> principle, of course Haskell has currying. Actually, functions are >> usually written in curried form in Haskell. Please let me know if I >> missed the substance of your question! >> > _______________________________________________ > 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 borgauf at gmail.com Fri Mar 26 20:01:03 2021 From: borgauf at gmail.com (Galaxy Being) Date: Fri, 26 Mar 2021 15:01:03 -0500 Subject: [Haskell-cafe] Does Haskell have this SML syntax? In-Reply-To: References: Message-ID: This has been very helpful. I plugged in the version VD above gave and it works. Now, what might be the purpose of this \ case? In SML the code I gave simply looks like a trick to simulate a curry where the function takes a parameter, then morphs into a new function that takes the next parameter. What would be the main use of this \ case ploy? I can't believe it was dreamt up just to fake currying. What's still strange to me is how the system knows to reach past the pred data MyList a = Empty | Cons a (MyList a) deriving (Eq, Ord, Show) subst_c :: (a -> Bool) -> (a, MyList a) -> MyList a subst_c pred = \ case (_, Empty) -> Empty (n, Cons e t) | pred e -> Cons n $ subst_c pred (n, t) | otherwise -> Cons e $ subst_c pred (n, t) and pattern match on the (a, MyList a) inside the function. So again, how can it do this and why would I want to? On Fri, Mar 26, 2021 at 12:37 AM David Feuer wrote: > Let's start with the basics: lambda expressions. > > ML says > > fn x => blah blah > > Haskell spells that > > \x -> blah blah > > Suppose you want to pattern match on the argument. If you only need one > pattern, that's cool: > > \(x,y) -> blah blah > > But what if you need more than one pattern? Well, standard ("Report") > Haskell makes you use a case expression: > > \mx -> case mx of > Just x -> blah > Nothing -> etcetera > > But GHC has a widely used language extension to get something more like > ML. If you put > > -- The "language" is case insensitive. > -- The LambdaCase is case sensitive. > {-# language LambdaCase #-} > > at the very tippy top of your .hs file, or pass -XLambdaCase to GHCi, then > you can write that last one > > \case > Just x -> blah > Nothing -> etcetera > > There has been some discussion of trying to expand that syntax to support > anonymous functions of multiple arguments, but no proposal has been > accepted as yet. > > On Fri, Mar 26, 2021, 1:27 AM Galaxy Being wrote: > >> I'm sure you've answered my question, but I'm too much of a beginner to >> fathom it. If you could explain, that would be great, but I could also go >> off and try to grok it myself. Again, thanks. >> >> On Fri, Mar 26, 2021 at 12:09 AM Ignat Insarov wrote: >> >>> Hello Galaxy Being! >>> >>> You can do this: >>> >>> module Y where >>> >>> substitute ∷ (α → Bool) → (α, [α]) → [α] >>> substitute predicate = \ thing → case thing of >>> (_, [ ]) → [ ] >>> (substitution, (x: xs)) → >>> let remainder = substitute predicate (substitution, xs) in >>> if predicate x >>> then substitution: remainder >>> else x: remainder >>> >>> It is even nicer since we can factor out the common part of the `if` >>> block into a `let … in`. You can also enable the `LambdaCase` language >>> extension and it will let you elide the `thing` thing. >>> >>> I am not sure if this is what your question is really about… In >>> principle, of course Haskell has currying. Actually, functions are >>> usually written in curried form in Haskell. Please let me know if I >>> missed the substance of your question! >>> >> _______________________________________________ >> 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 ietf-dane at dukhovni.org Fri Mar 26 21:03:30 2021 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Fri, 26 Mar 2021 17:03:30 -0400 Subject: [Haskell-cafe] Does Haskell have this SML syntax? In-Reply-To: References: Message-ID: On Fri, Mar 26, 2021 at 03:01:03PM -0500, Galaxy Being wrote: > Now, what might be the purpose of this \ case? It is just a short-hand: \ case pat1 -> e1 pat2 -> e2 ... is identical to: \ x -> case x of pat1 -> e1 pat2 -> e2 ... In other words, a concise function taking a single argument that is immediately the verbatim subject of some pattern matches. maybe fallback extract = \ case Just av -> extract av Nothing -> fallback > In SML the code I gave simply looks like a trick to simulate a curry > where the function takes a parameter, then morphs into a new function > that takes the next parameter. This is not a trick, it is elementary mathematical logic, In set theory, we have an isomorphism: A x B -> C <---> A -> (B -> C) this was eventually formalised in Churches Lambda Calculus. λ(x,y). mumble <---> λx. (λy. mumble) -- mumble = ..., some formula in x and y > What would be the main use of this \ case ploy? I can't believe it was > dreamt up just to fake currying. I don't understand why you're using words like "fake" and "ploy". This is just a shorthand that avoids having to introduce a superfluous intermediate variable that adds nothing to the clarity of the code. > What's still strange to me is how the system knows to reach past the > pred That's just the same isomorphism, for fixed pred, (subst_c pred) is a function of (a, MyList a). But we can also view the same subst_c as a function of two arguments (pred, (a, MyList a)). The two viewpoints are isomorphic. The notation for anonymous functions allows us to avoid having to name the restriction of `subst_c` to a given value of `pred`. subst_c pred = \ (a, MyList a) -> mumble <---> subst_c pred (a, MyList a) = mumble > data MyList a = Empty | Cons a (MyList a) deriving (Eq, Ord, Show) > subst_c :: (a -> Bool) -> (a, MyList a) -> MyList a > subst_c pred = \ case > (_, Empty) -> Empty > (n, Cons e t) > | pred e -> Cons n $ subst_c pred (n, t) > | otherwise -> Cons e $ subst_c pred (n, t) > > and pattern match on the (a, MyList a) inside the function. Well "closures" that capture a context, are immensely useful in writing reusable software building blocks. You can e.g. name "subst_c pred" specialised for a particular predicate and use it repeatedly, or pass it as a function to be used in some higher-order function. > So again, how can it do this and why would I want to? When working with higher-order functions, the function-valued arguments passed to them are often partially-applied general-purpose "combinators". Functional programming would be much more tediously verbose, if we couldn't write function-valued expressions by partially applying existing functions. Instead of: map (* 2) [1,2,3,4] we'd have to always write: map double [1,2,3,4] where double x = 2 * x or similar. Often the expression is at least as clear as any name you might give it. -- Viktor. From borgauf at gmail.com Sat Mar 27 22:59:59 2021 From: borgauf at gmail.com (Galaxy Being) Date: Sat, 27 Mar 2021 17:59:59 -0500 Subject: [Haskell-cafe] Install on Ubuntu Message-ID: I've found a Haskell setup guide here, but after the stack setup it wants to install cabal curl -sSL https://get.haskellstack.org | sh then stack install cabal-install cabal update Why do I want to install cabal after stack? Any advice welcome on the "definitive setup." Just started a new machine with Ubuntu 20.10 on it. LB -------------- next part -------------- An HTML attachment was scrubbed... URL: From lemming at henning-thielemann.de Sat Mar 27 23:08:11 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Sun, 28 Mar 2021 00:08:11 +0100 (CET) Subject: [Haskell-cafe] Install on Ubuntu In-Reply-To: References: Message-ID: <2fbb2c1-d140-cd5e-7798-2bd136ac186c@henning-thielemann.de> On Sat, 27 Mar 2021, Galaxy Being wrote: > Why do I want to install cabal after stack? Any advice welcome on the > "definitive setup." Just started a new machine with Ubuntu 20.10 on it. On Ubuntu you can just install $ sudo apt install ghc cabal-install or $ sudo apt install haskell-stack You may also add the repository $ sudo apt-add-repository ppa:hvr/ghc in order to get a wider range of versions of ghc and cabal-install. From borgauf at gmail.com Sun Mar 28 00:02:25 2021 From: borgauf at gmail.com (Galaxy Being) Date: Sat, 27 Mar 2021 19:02:25 -0500 Subject: [Haskell-cafe] Install on Ubuntu In-Reply-To: <2fbb2c1-d140-cd5e-7798-2bd136ac186c@henning-thielemann.de> References: <2fbb2c1-d140-cd5e-7798-2bd136ac186c@henning-thielemann.de> Message-ID: Hmm. Already did the first part,i.e., curl -sSL https://get.haskellstack.org | sh Should I do the cabal install now? On Sat, Mar 27, 2021 at 6:08 PM Henning Thielemann < lemming at henning-thielemann.de> wrote: > > On Sat, 27 Mar 2021, Galaxy Being wrote: > > > Why do I want to install cabal after stack? Any advice welcome on the > > "definitive setup." Just started a new machine with Ubuntu 20.10 on it. > > > On Ubuntu you can just install > > $ sudo apt install ghc cabal-install > > or > > $ sudo apt install haskell-stack > > > You may also add the repository > > $ sudo apt-add-repository ppa:hvr/ghc > > in order to get a wider range of versions of ghc and cabal-install. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From lemming at henning-thielemann.de Sun Mar 28 00:31:46 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Sun, 28 Mar 2021 01:31:46 +0100 (CET) Subject: [Haskell-cafe] Install on Ubuntu In-Reply-To: References: <2fbb2c1-d140-cd5e-7798-2bd136ac186c@henning-thielemann.de> Message-ID: <5e165f23-44df-47ea-f896-604791ef2f6@henning-thielemann.de> On Sat, 27 Mar 2021, Galaxy Being wrote: > Hmm. Already did the first part,i.e., curl -sSL https://get.haskellstack.org | sh > Should I do the cabal install now? If you use the Ubuntu packages you do not need to fetch 'stack' using 'curl'. From ivanperezdominguez at gmail.com Sun Mar 28 01:24:52 2021 From: ivanperezdominguez at gmail.com (Ivan Perez) Date: Sat, 27 Mar 2021 21:24:52 -0400 Subject: [Haskell-cafe] Install on Ubuntu In-Reply-To: <5e165f23-44df-47ea-f896-604791ef2f6@henning-thielemann.de> References: <2fbb2c1-d140-cd5e-7798-2bd136ac186c@henning-thielemann.de> <5e165f23-44df-47ea-f896-604791ef2f6@henning-thielemann.de> Message-ID: LB, I'd strongly recommend just going the route of sudo apt-add-repository ppa:hvr/ghc and installing whichever versions of cabal-install and ghc you want. It's simple and keeps your $HOME clean. Ivan On Sat, 27 Mar 2021 at 20:37, Henning Thielemann < lemming at henning-thielemann.de> wrote: > > On Sat, 27 Mar 2021, Galaxy Being wrote: > > > Hmm. Already did the first part,i.e., curl -sSL > https://get.haskellstack.org | sh > > Should I do the cabal install now? > > If you use the Ubuntu packages you do not need to fetch 'stack' using > 'curl'. > _______________________________________________ > 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 chikitosan at gmail.com Sun Mar 28 12:36:57 2021 From: chikitosan at gmail.com (Antonio R G) Date: Sun, 28 Mar 2021 14:36:57 +0200 Subject: [Haskell-cafe] Some questions about Fudgets library In-Reply-To: References: <20210311221202.GA3955@saruman> Message-ID: <20210328123657.GA2894@saruman> Hi, Finally, after much reading and thinking, I decided to not use fudgets for my bittorrent application, so my plan to modernize the Fudget library will be on hold for some time, at least until I finish the application. Anyway, I have now a pretty clear idea of how to modernize it, and will do it eventually (it'll be a quite radical rewriting). Why not use fudgets for bittorrent? Well, I come to the conclusion that fudgets are great for writing client/server applications, where there is bidirectional flow of information but requests only flow in one direction; but, for p2p applications, where both information and requests flow bidirectionally, fudgets are not the most natural way to implement them. So I'll search for a different abstraction or maybe switch to a logic language or functional-logic language. Best regards, Antonio Regidor Garcia From athas at sigkill.dk Sun Mar 28 13:43:59 2021 From: athas at sigkill.dk (Troels Henriksen) Date: Sun, 28 Mar 2021 15:43:59 +0200 Subject: [Haskell-cafe] Pattern matching desugaring regression? Re: Why does my module take so long to compile? In-Reply-To: <87mtw5406p.fsf@sigkill.dk> (Troels Henriksen's message of "Mon, 15 Feb 2021 20:10:06 +0100") References: <87y2fp5pn7.fsf@sigkill.dk> <57fb4de7-d4c6-f08c-d226-18d1572d26b@henning-thielemann.de> <87pn115kmo.fsf@sigkill.dk> <87zh05458o.fsf@sigkill.dk> <87tuqd439x.fsf@sigkill.dk> <87mtw5406p.fsf@sigkill.dk> Message-ID: <87wntr9yw0.fsf@sigkill.dk> Troels Henriksen writes: > It is very likely that issue 17386 is the issue. With > > {-# OPTIONS_GHC -Wno-overlapping-patterns -Wno-incomplete-patterns > -Wno-incomplete-uni-patterns -Wno-incomplete-record-updates #-} > > my module(s) compile very quickly. I'll wait and see if GHC 9 does > better before I try to create a smaller case (and now I at least have a > workaround). I have now tried it with GHC 9, and unfortunately it is still very slow. As time permits, I will see if I can come up with a self-contained module that illustrates the slowdown. I do have an idea for a optimisation: In all of the cases where coverage tracking takes a long time, I have a catch-all case at the bottom. I think that is a fairly common pattern, where a program tries to detect various special cases, before falling back to a general case. Perhaps coverage checking should have a short-circuiting check for whether there is an obvious catch-all case, and if so, not bother looking any closer? -- \ Troels /\ Henriksen From sgraf1337 at gmail.com Sun Mar 28 16:35:07 2021 From: sgraf1337 at gmail.com (Sebastian Graf) Date: Sun, 28 Mar 2021 18:35:07 +0200 Subject: [Haskell-cafe] Pattern matching desugaring regression? Re: Why does my module take so long to compile? In-Reply-To: <87wntr9yw0.fsf@sigkill.dk> References: <87y2fp5pn7.fsf@sigkill.dk> <57fb4de7-d4c6-f08c-d226-18d1572d26b@henning-thielemann.de> <87pn115kmo.fsf@sigkill.dk> <87zh05458o.fsf@sigkill.dk> <87tuqd439x.fsf@sigkill.dk> <87mtw5406p.fsf@sigkill.dk> <87wntr9yw0.fsf@sigkill.dk> Message-ID: Hi Troels, Sorry to hear GHC 9 didn't fix your problems! Yes, please open an issue. Optimising for specific usage patterns might be feasible, although note that most often it's not the exhaustivity check that is causing problems, but the check for overlapping patterns. At the moment the checker doesn't take shortcuts if we have -Wincomplete-patterns, but -Wno-overlapping-patterns. Maybe it could? Let's see what is causing you problems and decide then. Cheers, Sebastian Am So., 28. März 2021 um 15:44 Uhr schrieb Troels Henriksen < athas at sigkill.dk>: > Troels Henriksen writes: > > > It is very likely that issue 17386 is the issue. With > > > > {-# OPTIONS_GHC -Wno-overlapping-patterns -Wno-incomplete-patterns > > -Wno-incomplete-uni-patterns -Wno-incomplete-record-updates #-} > > > > my module(s) compile very quickly. I'll wait and see if GHC 9 does > > better before I try to create a smaller case (and now I at least have a > > workaround). > > I have now tried it with GHC 9, and unfortunately it is still very slow. > > As time permits, I will see if I can come up with a self-contained > module that illustrates the slowdown. > > I do have an idea for a optimisation: In all of the cases where coverage > tracking takes a long time, I have a catch-all case at the bottom. I > think that is a fairly common pattern, where a program tries to detect > various special cases, before falling back to a general case. Perhaps > coverage checking should have a short-circuiting check for whether there > is an obvious catch-all case, and if so, not bother looking any closer? > > -- > \ Troels > /\ Henriksen > -------------- next part -------------- An HTML attachment was scrubbed... URL: From clintonmead at gmail.com Mon Mar 29 00:24:08 2021 From: clintonmead at gmail.com (Clinton Mead) Date: Mon, 29 Mar 2021 11:24:08 +1100 Subject: [Haskell-cafe] Why Haskell? Message-ID: I’m looking for recommendations of videos/articles to show to a software development manager about why one should use Haskell, focused more from a benefits to business perspective. Naturally this may involve some code, this manager isn’t completely clueless when it comes to programming languages, but basically something that explains why I’m raving about this “Haskell” thing all the time and why it’s a good idea. Thanks, Clinton -------------- next part -------------- An HTML attachment was scrubbed... URL: From jack at jackkelly.name Mon Mar 29 00:48:12 2021 From: jack at jackkelly.name (jack at jackkelly.name) Date: Mon, 29 Mar 2021 00:48:12 +0000 Subject: [Haskell-cafe] Why Haskell? In-Reply-To: References: Message-ID: March 29, 2021 10:24 AM, "Clinton Mead" wrote: > I’m looking for recommendations of videos/articles to show to a software development manager about > why one should use Haskell, focused more from a benefits to business perspective. This article is about Elm, but should generalise to other strongly and statically-typed ML-family functional programming languages: http://nonullpointers.com/posts/2019-05-28-side-effects-of-elm-in-production.html (Disclosure: I work for Bellroy, but didn't when the events in this article took place. We are now using Haskell for a small but growing number of backend services.) Key points: * The react build of the checkout took six months and had data loss and error reproduction issues * The react build caused an 8% drop in conversion rate, and nobody could work out why * Some state transitions were missed due to weak typing in redux * The Elm rewrite took three months (1/2 the time, though consider that the devs would have a good handle on the domain at that point) * The Elm version was ~55% the SLOC of the react version * The Elm version had essentially no runtime failures * The Elm version forced the developers to consider all state transitions * The Elm version was much easier to modify, which meant experiments were cheaper to build and run Note: A checkout page seems to be a particularly good fit for Elm because it has a lot of complicated state transitions (so you get a good payoff from adopting types), "getting it wrong" has a large cost (directly translates into missed conversions), and doesn't need to interact with external JS libraries _that_ much (payment SDKs notwithstanding, but that tends to happen at the end of the checkout process). Best, -- Jack From carter.schonwald at gmail.com Mon Mar 29 01:18:56 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sun, 28 Mar 2021 21:18:56 -0400 Subject: [Haskell-cafe] Why Haskell? In-Reply-To: References: Message-ID: For businesses, it all boils down to can you deliver better value sooner, and improve it faster and generally improve the business / product offering in a compelling sustainable way. If you can do that and grow the team to suport that system so there’s no fear of having a single maintainer they can afford, , that’s all you need! Deliver better business value , sooner, and that’s all. ! On Sun, Mar 28, 2021 at 8:25 PM Clinton Mead wrote: > I’m looking for recommendations of videos/articles to show to a software > development manager about why one should use Haskell, focused more from a > benefits to business perspective. > > Naturally this may involve some code, this manager isn’t completely > clueless when it comes to programming languages, but basically something > that explains why I’m raving about this “Haskell” thing all the time and > why it’s a good idea. > > Thanks, > Clinton > _______________________________________________ > 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 borgauf at gmail.com Mon Mar 29 03:12:07 2021 From: borgauf at gmail.com (Galaxy Being) Date: Sun, 28 Mar 2021 22:12:07 -0500 Subject: [Haskell-cafe] Maybe won't let me count Message-ID: I've got this import Data.Maybe data MyList a = Empty | Cons a (MyList a) deriving (Eq,Ord,Show) data BaconOrIndex = Bacon | Indx Int deriving (Eq,Ord,Show) whereIsBM Empty = Nothing whereIsBM (Cons idx lx) = if (idx == Bacon) then Just 1 else (whereIsBM lx) which I would like to tell me where the Bacon is (index), not just if there's Bacon, which is what it does now. That is, I need this to happen > whereIsBM (Cons (Indx 5) (Cons Bacon (Cons (Indx 2) (Cons (Indx 8) Empty)))) Just 2 So I need to traverse a BaconOrIndex list and count how deep I went to find the Bacon variable. I get the above code to evaluate error-free, but obviously I'm only returning a Just 1 when it sees Bacon. What I need is to have the last part be . . . else (1 + whereIsBM lx) work; but it keeps giving the error Non type-variable argument in the constraint: Num (Maybe a) (Use FlexibleContexts to permit this) • When checking the inferred type whereIsBM :: forall a. (Num a, Num (Maybe a)) => MyList BaconOrIndex -> Maybe a I haven't a clue what this means. Eventually, I'll wrap this in something that handles the Nothing and does fromJust on the alternative. This whole effort is because if I didn't use the Maybe strategy, and said whereIsBM Empty = 0 ... it would never give back 0 if it didn't find Bacon, rather, it would simply return the whole countdown to Empty. What can I do to make Maybe work here? LB -------------- next part -------------- An HTML attachment was scrubbed... URL: From evincarofautumn at gmail.com Mon Mar 29 03:37:13 2021 From: evincarofautumn at gmail.com (Jon Purdy) Date: Sun, 28 Mar 2021 20:37:13 -0700 Subject: [Haskell-cafe] Maybe won't let me count In-Reply-To: References: Message-ID: ‘whereIsBM’ returns a Maybe-wrapped value, so applying ‘1 + …’ to it would require ‘Maybe a’ to be in ‘Num’, hence the error message. ‘FlexibleContexts’ (ditto ‘FlexibleInstances’) is a pretty benign extension, but it won’t help here, since it just kicks the error down the road a bit. The basic thing you need to do is match on the Maybe and return ‘Nothing’ if it was ‘Nothing’, or ‘Just (1 + x)’ if it was ‘Just x’ for some x. That can be written quite literally as a ‘case’ expression: case whereIsBM lx of Just x -> Just (1 + x) Nothing -> Nothing Which could also be written with ‘do’: do x <- whereIsBM lx pure (1 + x) But this pattern is very common, so it’s already packaged up and generalised as ‘fmap’, a.k.a. ‘<$>’ fmap (1 +) (whereIsBM lx) -- or (1 +) <$> whereIsBM lx On Sun, Mar 28, 2021, 8:13 PM Galaxy Being wrote: > I've got this > > import Data.Maybe > > data MyList a = Empty | Cons a (MyList a) deriving (Eq,Ord,Show) > data BaconOrIndex = Bacon | Indx Int deriving (Eq,Ord,Show) > > whereIsBM Empty = Nothing > whereIsBM (Cons idx lx) = if (idx == Bacon) then Just 1 else (whereIsBM lx) > > which I would like to tell me where the Bacon is (index), not just if > there's Bacon, which is what it does now. That is, I need this to happen > > > whereIsBM (Cons (Indx 5) (Cons Bacon (Cons (Indx 2) (Cons (Indx 8) > Empty)))) > Just 2 > > So I need to traverse a BaconOrIndex list and count how deep I went to > find the Bacon variable. I get the above code to evaluate error-free, but > obviously I'm only returning a Just 1 when it sees Bacon. What I need is > to have the last part be > > . . . else (1 + whereIsBM lx) > > work; but it keeps giving the error > > Non type-variable argument in the constraint: Num (Maybe a) > (Use FlexibleContexts to permit this) > • When checking the inferred type > whereIsBM :: forall a. > (Num a, Num (Maybe a)) => > MyList BaconOrIndex -> Maybe a > > I haven't a clue what this means. Eventually, I'll wrap this in something > that handles the Nothing and does fromJust on the alternative. This > whole effort is because if I didn't use the Maybe strategy, and said > > whereIsBM Empty = 0 > ... > > it would never give back 0 if it didn't find Bacon, rather, it would > simply return the whole countdown to Empty. What can I do to make Maybe work > here? > > LB > _______________________________________________ > 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 ietf-dane at dukhovni.org Mon Mar 29 04:26:29 2021 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Mon, 29 Mar 2021 00:26:29 -0400 Subject: [Haskell-cafe] Maybe won't let me count In-Reply-To: References: Message-ID: On Sun, Mar 28, 2021 at 08:37:13PM -0700, Jon Purdy wrote: > fmap (1 +) (whereIsBM lx) > -- or > (1 +) <$> whereIsBM lx Or with bounds checks: succ <$> whereIsBM lx but all these variants run out of stack on very long lists due to failure to be tail recursive. A more robust elemIndex implementation would be: elemIndex :: (Integral i, Eq a) => a -> [a] -> Maybe i elemIndex e = go 0 where go !_ [] = Nothing go !acc (x : xs) | x == e = Just acc | otherwise = go (succ acc) xs This is quite pedantic in generalising the index type from `Int` to `Integral`, and then using `succ` rather than (1 +) to ensure that overflow is detected: λ> :set -XBangPatterns λ> import Data.Int (Int8) λ> λ> :{ λ>| elemIndex :: (Integral i, Eq a) => a -> [a] -> Maybe i λ>| elemIndex e = go 0 λ>| where λ>| go !_ [] = Nothing λ>| go !acc (x : xs) | x == e = Just acc λ>| | otherwise = go (succ acc) xs λ>| :} λ> λ> elemIndex 42 [0..] :: Maybe Int8 Just 42 λ> λ> elemIndex 300 [0..] :: Maybe Int8 *** Exception: Enum.succ{Int8}: tried to take `succ' of maxBound More typically/sloppily one would just use "Int" and (+), in the expectation that Ints are 64 bits or more, and no list one could search is longer than 2^63-1 elements. Often that assumption is justified, but the strictly correct implementation is: elemIndex :: Eq a => a -> [a] -> Maybe Integer elemIndex e = go 0 where go !_ [] = Nothing go !acc (x : xs) | x == e = Just acc | otherwise = go (acc + 1) xs and the user would need to check the value for overflow before converting to some narrower integral type. The function is still however /partial/, in that given the infinite list [0..] and a negative target value it would now search forever. Which brings us to the more fundamental observation that if you're using a (linked) list to search through more than a handful of items you're very much in a state of sin. That's simply not the right data structure for the purpose. Linked lists should be used primarily for one shot iteration, rather than indexing, search or repeated traversal. Any appearance of a list index is a strong signal that the wrong data structure is in use. One should probably be using arrays or vectors in these cases, but in `base` we only have `array` in `GHC.Array`, and the interface is not friendly to new users. Thus I applaud Michael Snoyman's quest to address the absense of a basic array type in the `base` library. Perhaps more users would stop abusing lists (memoisable iterators) as an indexed store. -- Viktor. From borgauf at gmail.com Mon Mar 29 04:27:48 2021 From: borgauf at gmail.com (Galaxy Being) Date: Sun, 28 Mar 2021 23:27:48 -0500 Subject: [Haskell-cafe] Maybe won't let me count In-Reply-To: References: Message-ID: I'm not getting past whereIsBM boiList = case boiList of Nothing -> Nothing Just (Cons idx lx) | (idx == Bacon) -> Just 1 | otherwise -> Just (1 + whereIsBM lx) ...and a few other attempts. On Sun, Mar 28, 2021 at 10:37 PM Jon Purdy wrote: > ‘whereIsBM’ returns a Maybe-wrapped value, so applying ‘1 + …’ to it would > require ‘Maybe a’ to be in ‘Num’, hence the error message. > ‘FlexibleContexts’ (ditto ‘FlexibleInstances’) is a pretty benign > extension, but it won’t help here, since it just kicks the error down the > road a bit. > > The basic thing you need to do is match on the Maybe and return ‘Nothing’ > if it was ‘Nothing’, or ‘Just (1 + x)’ if it was ‘Just x’ for some x. That > can be written quite literally as a ‘case’ expression: > > case whereIsBM lx of > Just x -> Just (1 + x) > Nothing -> Nothing > > Which could also be written with ‘do’: > > do > x <- whereIsBM lx > pure (1 + x) > > But this pattern is very common, so it’s already packaged up and > generalised as ‘fmap’, a.k.a. ‘<$>’ > > fmap (1 +) (whereIsBM lx) > -- or > (1 +) <$> whereIsBM lx > > On Sun, Mar 28, 2021, 8:13 PM Galaxy Being wrote: > >> I've got this >> >> import Data.Maybe >> >> data MyList a = Empty | Cons a (MyList a) deriving (Eq,Ord,Show) >> data BaconOrIndex = Bacon | Indx Int deriving (Eq,Ord,Show) >> >> whereIsBM Empty = Nothing >> whereIsBM (Cons idx lx) = if (idx == Bacon) then Just 1 else (whereIsBM >> lx) >> >> which I would like to tell me where the Bacon is (index), not just if >> there's Bacon, which is what it does now. That is, I need this to happen >> >> > whereIsBM (Cons (Indx 5) (Cons Bacon (Cons (Indx 2) (Cons (Indx 8) >> Empty)))) >> Just 2 >> >> So I need to traverse a BaconOrIndex list and count how deep I went to >> find the Bacon variable. I get the above code to evaluate error-free, >> but obviously I'm only returning a Just 1 when it sees Bacon. What I >> need is to have the last part be >> >> . . . else (1 + whereIsBM lx) >> >> work; but it keeps giving the error >> >> Non type-variable argument in the constraint: Num (Maybe a) >> (Use FlexibleContexts to permit this) >> • When checking the inferred type >> whereIsBM :: forall a. >> (Num a, Num (Maybe a)) => >> MyList BaconOrIndex -> Maybe a >> >> I haven't a clue what this means. Eventually, I'll wrap this in something >> that handles the Nothing and does fromJust on the alternative. This >> whole effort is because if I didn't use the Maybe strategy, and said >> >> whereIsBM Empty = 0 >> ... >> >> it would never give back 0 if it didn't find Bacon, rather, it would >> simply return the whole countdown to Empty. What can I do to make Maybe work >> here? >> >> LB >> _______________________________________________ >> 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 Juan.Casanova at ed.ac.uk Mon Mar 29 06:11:36 2021 From: Juan.Casanova at ed.ac.uk (CASANOVA Juan) Date: Mon, 29 Mar 2021 06:11:36 +0000 Subject: [Haskell-cafe] Maybe won't let me count In-Reply-To: References: , Message-ID: As others explained, you still can't do (1 + whereIsBM Ix), you need to unwrap the whereIsBM value or use fmap (<$>). Here, let me give you a small modification on your code that will do it: whereIsBM boiList = case boiList of Nothing -> Nothing Just (Cons idx lx) | (idx == Bacon) -> Just 1 | otherwise -> (1 +) <$> (whereIsBM lx) And as others have explained, what this does is take the result of (whereIsBM Ix), which is a Maybe-wrapped value, and apply the function ((1 +) <$>) (alternatively, (fmap (1 +))), which basically just takes the function (1 +) (add 1 to a number) and applies it to whatever is wrapped inside the Maybe (your numbers), while keeping the Maybe structure. So if the result of (whereIsBM x) is Nothing, then applying ((1 +) <$>) will return Nothing because there's nothing wrapped, whereas if (whereIsBM x) is (Just n), then applying ((1 + ) <$>) to it will return (Just (1 + n)). You could also, as others explained, case match on the result of (whereIsBM Ix), but that would be more verbose and probably just confuse you. But it is, ultimately, what fmap is actually doing. Unwrapping and re-wrapping. ________________________________ From: Haskell-Cafe on behalf of Galaxy Being Sent: 29 March 2021 05:27 To: haskell-cafe Subject: Re: [Haskell-cafe] Maybe won't let me count This email was sent to you by someone outside the University. You should only click on links or attachments if you are certain that the email is genuine and the content is safe. I'm not getting past whereIsBM boiList = case boiList of Nothing -> Nothing Just (Cons idx lx) | (idx == Bacon) -> Just 1 | otherwise -> Just (1 + whereIsBM lx) ...and a few other attempts. On Sun, Mar 28, 2021 at 10:37 PM Jon Purdy > wrote: ‘whereIsBM’ returns a Maybe-wrapped value, so applying ‘1 + …’ to it would require ‘Maybe a’ to be in ‘Num’, hence the error message. ‘FlexibleContexts’ (ditto ‘FlexibleInstances’) is a pretty benign extension, but it won’t help here, since it just kicks the error down the road a bit. The basic thing you need to do is match on the Maybe and return ‘Nothing’ if it was ‘Nothing’, or ‘Just (1 + x)’ if it was ‘Just x’ for some x. That can be written quite literally as a ‘case’ expression: case whereIsBM lx of Just x -> Just (1 + x) Nothing -> Nothing Which could also be written with ‘do’: do x <- whereIsBM lx pure (1 + x) But this pattern is very common, so it’s already packaged up and generalised as ‘fmap’, a.k.a. ‘<$>’ fmap (1 +) (whereIsBM lx) -- or (1 +) <$> whereIsBM lx On Sun, Mar 28, 2021, 8:13 PM Galaxy Being > wrote: I've got this import Data.Maybe data MyList a = Empty | Cons a (MyList a) deriving (Eq,Ord,Show) data BaconOrIndex = Bacon | Indx Int deriving (Eq,Ord,Show) whereIsBM Empty = Nothing whereIsBM (Cons idx lx) = if (idx == Bacon) then Just 1 else (whereIsBM lx) which I would like to tell me where the Bacon is (index), not just if there's Bacon, which is what it does now. That is, I need this to happen > whereIsBM (Cons (Indx 5) (Cons Bacon (Cons (Indx 2) (Cons (Indx 8) Empty)))) Just 2 So I need to traverse a BaconOrIndex list and count how deep I went to find the Bacon variable. I get the above code to evaluate error-free, but obviously I'm only returning a Just 1 when it sees Bacon. What I need is to have the last part be . . . else (1 + whereIsBM lx) work; but it keeps giving the error Non type-variable argument in the constraint: Num (Maybe a) (Use FlexibleContexts to permit this) • When checking the inferred type whereIsBM :: forall a. (Num a, Num (Maybe a)) => MyList BaconOrIndex -> Maybe a I haven't a clue what this means. Eventually, I'll wrap this in something that handles the Nothing and does fromJust on the alternative. This whole effort is because if I didn't use the Maybe strategy, and said whereIsBM Empty = 0 ... it would never give back 0 if it didn't find Bacon, rather, it would simply return the whole countdown to Empty. What can I do to make Maybe work here? LB _______________________________________________ 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. The University of Edinburgh is a charitable body, registered in Scotland, with registration number SC005336. Is e buidheann carthannais a th’ ann an Oilthigh Dhùn Èideann, clàraichte an Alba, àireamh clàraidh SC005336. -------------- next part -------------- An HTML attachment was scrubbed... URL: From chikitosan at gmail.com Mon Mar 29 07:01:58 2021 From: chikitosan at gmail.com (Antonio Regidor Garcia) Date: Mon, 29 Mar 2021 09:01:58 +0200 Subject: [Haskell-cafe] Why Haskell? In-Reply-To: References: Message-ID: <20210329070158.GA10246@saruman> Not bussiness oriented, but these two articles are pretty good at explaining what Haskell and similar languages have to offer: This is brief and centered on Haskell's type system: https://perl.plover.com/yak/typing/notes.html This is longer and more general: http://www.cse.chalmers.se/~rjmh/Papers/whyfp.pdf Best, Antonio El Mon, Mar 29, 2021 at 11:24:08AM +1100, Clinton Mead escribió: > I’m looking for recommendations of videos/articles to show to a software > development manager about why one should use Haskell, focused more from a > benefits to business perspective. > > Naturally this may involve some code, this manager isn’t completely > clueless when it comes to programming languages, but basically something > that explains why I’m raving about this “Haskell” thing all the time and > why it’s a good idea. > > Thanks, > Clinton > _______________________________________________ > 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 Mon Mar 29 07:35:42 2021 From: compl.yue at icloud.com (YueCompl) Date: Mon, 29 Mar 2021 15:35:42 +0800 Subject: [Haskell-cafe] Why Haskell? In-Reply-To: References: Message-ID: <48377971-E4D8-4E75-AC56-6BFADCD21D77@icloud.com> https://www.reddit.com/r/programming/comments/25m291/simon_peyton_jones_haskell_is_useless/ That might be sth you'd like to hide from the manager, but better prepared for himself to discover about. Years have passed though, I'm very curious how situations have changed according to SPJ's criteria. > On 2021-03-29, at 08:24, Clinton Mead wrote: > > I’m looking for recommendations of videos/articles to show to a software development manager about why one should use Haskell, focused more from a benefits to business perspective. > > Naturally this may involve some code, this manager isn’t completely clueless when it comes to programming languages, but basically something that explains why I’m raving about this “Haskell” thing all the time and why it’s a good idea. > > Thanks, > Clinton > _______________________________________________ > 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 chikitosan at gmail.com Mon Mar 29 07:36:16 2021 From: chikitosan at gmail.com (Antonio Regidor Garcia) Date: Mon, 29 Mar 2021 09:36:16 +0200 Subject: [Haskell-cafe] Maybe won't let me count In-Reply-To: References: Message-ID: <20210329073616.GB10246@saruman> A simple solution: data MyList a = Empty | Cons a (MyList a) deriving (Eq,Ord,Show) data BaconOrIndex = Bacon | Indx Int deriving (Eq,Ord,Show) whereIsBM = whereIsBM' 0 whereIsBM' _ Empty = Nothing whereIsBM' !n (Cons Bacon _) = Just n whereIsBM' !n (Cons _ lx) = whereIsBM' (succ n) lx You can omit the ! if you want. The result will be the same, but the computation will use more memory because the program will first construct the unevaluated data structure (called 'thunk') suc (suc (suc (... 0) ...)) and then compute it instead of computing succ 0 to 1, then succ 1 to 2, etc., step by step, in constant memory. succ n is n+1 but faster than the function (+). Best, Antonio Regidor Garcia El Sun, Mar 28, 2021 at 11:27:48PM -0500, Galaxy Being escribió: > I'm not getting past > > whereIsBM boiList = case boiList of > Nothing -> Nothing > Just (Cons idx lx) > | (idx == Bacon) -> Just 1 > | otherwise -> Just (1 + whereIsBM lx) > > ...and a few other attempts. > > On Sun, Mar 28, 2021 at 10:37 PM Jon Purdy > wrote: > > > ‘whereIsBM’ returns a Maybe-wrapped value, so applying ‘1 + …’ to it would > > require ‘Maybe a’ to be in ‘Num’, hence the error message. > > ‘FlexibleContexts’ (ditto ‘FlexibleInstances’) is a pretty benign > > extension, but it won’t help here, since it just kicks the error down the > > road a bit. > > > > The basic thing you need to do is match on the Maybe and return ‘Nothing’ > > if it was ‘Nothing’, or ‘Just (1 + x)’ if it was ‘Just x’ for some x. That > > can be written quite literally as a ‘case’ expression: > > > > case whereIsBM lx of > > Just x -> Just (1 + x) > > Nothing -> Nothing > > > > Which could also be written with ‘do’: > > > > do > > x <- whereIsBM lx > > pure (1 + x) > > > > But this pattern is very common, so it’s already packaged up and > > generalised as ‘fmap’, a.k.a. ‘<$>’ > > > > fmap (1 +) (whereIsBM lx) > > -- or > > (1 +) <$> whereIsBM lx > > > > On Sun, Mar 28, 2021, 8:13 PM Galaxy Being wrote: > > > >> I've got this > >> > >> import Data.Maybe > >> > >> data MyList a = Empty | Cons a (MyList a) deriving (Eq,Ord,Show) > >> data BaconOrIndex = Bacon | Indx Int deriving (Eq,Ord,Show) > >> > >> whereIsBM Empty = Nothing > >> whereIsBM (Cons idx lx) = if (idx == Bacon) then Just 1 else (whereIsBM > >> lx) > >> > >> which I would like to tell me where the Bacon is (index), not just if > >> there's Bacon, which is what it does now. That is, I need this to happen > >> > >> > whereIsBM (Cons (Indx 5) (Cons Bacon (Cons (Indx 2) (Cons (Indx 8) > >> Empty)))) > >> Just 2 > >> > >> So I need to traverse a BaconOrIndex list and count how deep I went to > >> find the Bacon variable. I get the above code to evaluate error-free, > >> but obviously I'm only returning a Just 1 when it sees Bacon. What I > >> need is to have the last part be > >> > >> . . . else (1 + whereIsBM lx) > >> > >> work; but it keeps giving the error > >> > >> Non type-variable argument in the constraint: Num (Maybe a) > >> (Use FlexibleContexts to permit this) > >> • When checking the inferred type > >> whereIsBM :: forall a. > >> (Num a, Num (Maybe a)) => > >> MyList BaconOrIndex -> Maybe a > >> > >> I haven't a clue what this means. Eventually, I'll wrap this in something > >> that handles the Nothing and does fromJust on the alternative. This > >> whole effort is because if I didn't use the Maybe strategy, and said > >> > >> whereIsBM Empty = 0 > >> ... > >> > >> it would never give back 0 if it didn't find Bacon, rather, it would > >> simply return the whole countdown to Empty. What can I do to make Maybe work > >> here? > >> > >> LB > >> _______________________________________________ > >> 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 chikitosan at gmail.com Mon Mar 29 08:12:17 2021 From: chikitosan at gmail.com (Antonio Regidor Garcia) Date: Mon, 29 Mar 2021 10:12:17 +0200 Subject: [Haskell-cafe] Why Haskell? In-Reply-To: <48377971-E4D8-4E75-AC56-6BFADCD21D77@icloud.com> References: <48377971-E4D8-4E75-AC56-6BFADCD21D77@icloud.com> Message-ID: <20210329081217.GA10722@saruman> XD XD XD It seems a sales talk about his STM monad, something like "Haskell is useless but Haskell+STM is in the good direction". So: Haskell 1.2 (stream-based IO): stateless, useless Haskell 1.3+ (monadic IO): statefull, but too coarse-grained, still useless Haskell 98/2010 + STM: more fine-grained statefullness, becoming usefull Best, Antonio El Mon, Mar 29, 2021 at 03:35:42PM +0800, YueCompl via Haskell-Cafe escribió: > https://www.reddit.com/r/programming/comments/25m291/simon_peyton_jones_haskell_is_useless/ > > That might be sth you'd like to hide from the manager, but better prepared for himself to discover about. > > Years have passed though, I'm very curious how situations have changed according to SPJ's criteria. > > > On 2021-03-29, at 08:24, Clinton Mead wrote: > > > > I’m looking for recommendations of videos/articles to show to a software development manager about why one should use Haskell, focused more from a benefits to business perspective. > > > > Naturally this may involve some code, this manager isn’t completely clueless when it comes to programming languages, but basically something that explains why I’m raving about this “Haskell” thing all the time and why it’s a good idea. > > > > Thanks, > > Clinton > > _______________________________________________ > > 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 ietf-dane at dukhovni.org Mon Mar 29 08:22:07 2021 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Mon, 29 Mar 2021 04:22:07 -0400 Subject: [Haskell-cafe] Maybe won't let me count In-Reply-To: <20210329073616.GB10246@saruman> References: <20210329073616.GB10246@saruman> Message-ID: > On Mar 29, 2021, at 3:36 AM, Antonio Regidor Garcia wrote: > > succ n is n+1 but faster than the function (+). Because 'succ' typically does bounds checks, while (+) (for Int) just does the underlying CPU instruction, that's not particularly plausible. Indeed running a test (100 million increments) suggests that (+) is noticeably cheaper: (1 +): MUT time 0.035s ( 0.035s elapsed) (succ): MUT time 0.134s ( 0.134s elapsed) The succ function is however safer against uncaught overflow: λ> succ False True λ> succ True *** Exception: Prelude.Enum.Bool.succ: bad argument If the datatype in question is not bounded (Double, Integer, ...) then succ performance is closer to that of (+). I see identical speeds for Double, but (GHC 8.10 on X86_64) succ seems slightly slower for Integer. -- Viktor. From chikitosan at gmail.com Mon Mar 29 08:38:58 2021 From: chikitosan at gmail.com (Antonio Regidor Garcia) Date: Mon, 29 Mar 2021 10:38:58 +0200 Subject: [Haskell-cafe] Maybe won't let me count In-Reply-To: References: <20210329073616.GB10246@saruman> Message-ID: <20210329083858.GA11471@saruman> Mmm strange... I thought I read somewhere that succ is faster, but now I'm searching for the reference and don't find it. Anyway, good to know! Best, Antonio Regidor Garcia El Mon, Mar 29, 2021 at 04:22:07AM -0400, Viktor Dukhovni escribió: > > On Mar 29, 2021, at 3:36 AM, Antonio Regidor Garcia wrote: > > > > succ n is n+1 but faster than the function (+). > > Because 'succ' typically does bounds checks, while (+) (for Int) just > does the underlying CPU instruction, that's not particularly plausible. > > Indeed running a test (100 million increments) suggests that (+) is > noticeably cheaper: > > (1 +): MUT time 0.035s ( 0.035s elapsed) > (succ): MUT time 0.134s ( 0.134s elapsed) > > The succ function is however safer against uncaught overflow: > > λ> succ False > True > λ> succ True > *** Exception: Prelude.Enum.Bool.succ: bad argument > > If the datatype in question is not bounded (Double, Integer, ...) then > succ performance is closer to that of (+). I see identical speeds for > Double, but (GHC 8.10 on X86_64) succ seems slightly slower for Integer. > > -- > 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. From lemming at henning-thielemann.de Mon Mar 29 08:58:49 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Mon, 29 Mar 2021 10:58:49 +0200 (CEST) Subject: [Haskell-cafe] Maybe won't let me count In-Reply-To: References: Message-ID: <3b8bb257-78a0-3ea1-dafe-26f6c798663@henning-thielemann.de> On Mon, 29 Mar 2021, Viktor Dukhovni wrote: > Thus I applaud Michael Snoyman's quest to address the absense of a basic > array type in the `base` library. Perhaps more users would stop abusing > lists (memoisable iterators) as an indexed store. Data.Array actually _was_ part of base-3. However, I think we should split 'base' in more smaller parts rather than making it bigger. From ietf-dane at dukhovni.org Mon Mar 29 09:12:04 2021 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Mon, 29 Mar 2021 05:12:04 -0400 Subject: [Haskell-cafe] Arrays in base... (was: ... indexing lists) Message-ID: On Mon, Mar 29, 2021 at 10:58:49AM +0200, Henning Thielemann wrote: > On Mon, 29 Mar 2021, Viktor Dukhovni wrote: > > > Thus I applaud Michael Snoyman's quest to address the absense of a basic > > array type in the `base` library. Perhaps more users would stop abusing > > lists (memoisable iterators) as an indexed store. > > Data.Array actually _was_ part of base-3. > > However, I think we should split 'base' in more smaller parts rather than > making it bigger. FWIW, I don't think that splitting base into multiple libraries would achieves much, it would likely raise the cost of coordinating versioning. I do however agree that perhaps separating base from GHC could be a good idea, if GHC could ship a smaller foundational library with primops, ... and `base` evolved somewhat independently. However that too has potential drawbacks, because packages would be more likely to have non-overlapping version bounds on a separately evolving base... Probably manageable, but something to keep in mind. -- Viktor. From leah at vuxu.org Mon Mar 29 09:16:37 2021 From: leah at vuxu.org (Leah Neukirchen) Date: Mon, 29 Mar 2021 11:16:37 +0200 Subject: [Haskell-cafe] Munich Virtual Haskell Meeting, 2021-03-31 @ 19:30 Message-ID: <87h7ku7216.fsf@vuxu.org> Dear all, This week, our monthly Munich Haskell Meeting will take place again on Wednesday, March 31 on Google Meet at 19:30 CEST. **Due to meetup limitations in Bavaria, this meeting will take place online!** For details see here: https://muenchen.haskell.bayern/dates.html A Google Meet link to join the room is provided on the page. Everybody is welcome, especially the Haskellers from Bavaria that do not usually come to our Munich meetings due to travel distance! cu, -- Leah Neukirchen https://leahneukirchen.org/ From lemming at henning-thielemann.de Mon Mar 29 09:24:06 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Mon, 29 Mar 2021 11:24:06 +0200 (CEST) Subject: [Haskell-cafe] Arrays in base... (was: ... indexing lists) In-Reply-To: References: Message-ID: <8d63683f-99d4-77f0-bc9c-cef794e7bd3e@henning-thielemann.de> On Mon, 29 Mar 2021, Viktor Dukhovni wrote: > On Mon, Mar 29, 2021 at 10:58:49AM +0200, Henning Thielemann wrote: > >> Data.Array actually _was_ part of base-3. >> >> However, I think we should split 'base' in more smaller parts rather than >> making it bigger. > > FWIW, I don't think that splitting base into multiple libraries would > achieves much, it would likely raise the cost of coordinating > versioning. It would enable new Haskell compilers to implement some packages but not all. From compl.yue at icloud.com Mon Mar 29 11:11:49 2021 From: compl.yue at icloud.com (YueCompl) Date: Mon, 29 Mar 2021 19:11:49 +0800 Subject: [Haskell-cafe] Why Haskell? In-Reply-To: <20210329081217.GA10722@saruman> References: <48377971-E4D8-4E75-AC56-6BFADCD21D77@icloud.com> <20210329081217.GA10722@saruman> Message-ID: <1CAB6F4E-6DA4-46E4-9F78-BFDA6E020CA5@icloud.com> But AFAICT, STM composes poorly with other monads in today's mtl fashion, and by itself I don't think effects are tracked sufficiently well. I'm not aware of an idiomatic way to properly have STM in a monad stack, or is it there? > On 2021-03-29, at 16:12, Antonio Regidor Garcia wrote: > > XD XD XD It seems a sales talk about his STM monad, something like "Haskell is useless but Haskell+STM is in the good direction". So: > > Haskell 1.2 (stream-based IO): stateless, useless > Haskell 1.3+ (monadic IO): statefull, but too coarse-grained, still useless > Haskell 98/2010 + STM: more fine-grained statefullness, becoming usefull > > Best, > > Antonio > > El Mon, Mar 29, 2021 at 03:35:42PM +0800, YueCompl via Haskell-Cafe escribió: >> https://www.reddit.com/r/programming/comments/25m291/simon_peyton_jones_haskell_is_useless/ > >> >> That might be sth you'd like to hide from the manager, but better prepared for himself to discover about. >> >> Years have passed though, I'm very curious how situations have changed according to SPJ's criteria. >> >>> On 2021-03-29, at 08:24, Clinton Mead wrote: >>> >>> I’m looking for recommendations of videos/articles to show to a software development manager about why one should use Haskell, focused more from a benefits to business perspective. >>> >>> Naturally this may involve some code, this manager isn’t completely clueless when it comes to programming languages, but basically something that explains why I’m raving about this “Haskell” thing all the time and why it’s a good idea. >>> >>> Thanks, >>> Clinton >>> _______________________________________________ >>> 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 chikitosan at gmail.com Mon Mar 29 11:34:05 2021 From: chikitosan at gmail.com (Antonio Regidor Garcia) Date: Mon, 29 Mar 2021 13:34:05 +0200 Subject: [Haskell-cafe] Why Haskell? In-Reply-To: <1CAB6F4E-6DA4-46E4-9F78-BFDA6E020CA5@icloud.com> References: <48377971-E4D8-4E75-AC56-6BFADCD21D77@icloud.com> <20210329081217.GA10722@saruman> <1CAB6F4E-6DA4-46E4-9F78-BFDA6E020CA5@icloud.com> Message-ID: <20210329113405.GA14284@saruman> The STM is stateful (mutable state, thus impure) but it only changes the RAM, contrary to IO, that can change from the screen to missile launchers (so potentially much harmful). So the STM is deliberately separated from IO and similar monads. That's the point of using it. I don't have much experience combining it with non-IO monads, though. El Mon, Mar 29, 2021 at 07:11:49PM +0800, YueCompl escribió: > But AFAICT, STM composes poorly with other monads in today's mtl fashion, and by itself I don't think effects are tracked sufficiently well. > > I'm not aware of an idiomatic way to properly have STM in a monad stack, or is it there? > > > On 2021-03-29, at 16:12, Antonio Regidor Garcia wrote: > > > > XD XD XD It seems a sales talk about his STM monad, something like "Haskell is useless but Haskell+STM is in the good direction". So: > > > > Haskell 1.2 (stream-based IO): stateless, useless > > Haskell 1.3+ (monadic IO): statefull, but too coarse-grained, still useless > > Haskell 98/2010 + STM: more fine-grained statefullness, becoming usefull > > > > Best, > > > > Antonio > > > > El Mon, Mar 29, 2021 at 03:35:42PM +0800, YueCompl via Haskell-Cafe escribió: > >> https://www.reddit.com/r/programming/comments/25m291/simon_peyton_jones_haskell_is_useless/ > > >> > >> That might be sth you'd like to hide from the manager, but better prepared for himself to discover about. > >> > >> Years have passed though, I'm very curious how situations have changed according to SPJ's criteria. > >> > >>> On 2021-03-29, at 08:24, Clinton Mead wrote: > >>> > >>> I’m looking for recommendations of videos/articles to show to a software development manager about why one should use Haskell, focused more from a benefits to business perspective. > >>> > >>> Naturally this may involve some code, this manager isn’t completely clueless when it comes to programming languages, but basically something that explains why I’m raving about this “Haskell” thing all the time and why it’s a good idea. > >>> > >>> Thanks, > >>> Clinton > >>> _______________________________________________ > >>> 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 allbery.b at gmail.com Mon Mar 29 11:43:25 2021 From: allbery.b at gmail.com (Brandon Allbery) Date: Mon, 29 Mar 2021 07:43:25 -0400 Subject: [Haskell-cafe] Arrays in base... (was: ... indexing lists) In-Reply-To: <8d63683f-99d4-77f0-bc9c-cef794e7bd3e@henning-thielemann.de> References: <8d63683f-99d4-77f0-bc9c-cef794e7bd3e@henning-thielemann.de> Message-ID: We're already long past the point where an alternative Haskell compiler needs to implement an ever-expanding list of extensions to work with large and useful parts of Hackage. On Mon, Mar 29, 2021, 05:32 Henning Thielemann < lemming at henning-thielemann.de> wrote: > > On Mon, 29 Mar 2021, Viktor Dukhovni wrote: > > > On Mon, Mar 29, 2021 at 10:58:49AM +0200, Henning Thielemann wrote: > > > >> Data.Array actually _was_ part of base-3. > >> > >> However, I think we should split 'base' in more smaller parts rather > than > >> making it bigger. > > > > FWIW, I don't think that splitting base into multiple libraries would > > achieves much, it would likely raise the cost of coordinating > > versioning. > > It would enable new Haskell compilers to implement some packages but not > all. > _______________________________________________ > 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 ietf-dane at dukhovni.org Mon Mar 29 11:50:59 2021 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Mon, 29 Mar 2021 07:50:59 -0400 Subject: [Haskell-cafe] Why Haskell? In-Reply-To: <1CAB6F4E-6DA4-46E4-9F78-BFDA6E020CA5@icloud.com> References: <48377971-E4D8-4E75-AC56-6BFADCD21D77@icloud.com> <20210329081217.GA10722@saruman> <1CAB6F4E-6DA4-46E4-9F78-BFDA6E020CA5@icloud.com> Message-ID: On Mon, Mar 29, 2021 at 07:11:49PM +0800, YueCompl via Haskell-Cafe wrote: > But AFAICT, STM composes poorly with other monads in today's mtl > fashion, and by itself I don't think effects are tracked sufficiently > well. > > I'm not aware of an idiomatic way to properly have STM in a monad > stack, or is it there? STM is not a monad transformer, but it is a fine base monad, just like Identity, IO or ST. Here's a contrived example of (StateT Int STM Int): import Control.Concurrent.STM import Control.Monad (when) import Control.Monad.Trans.State.Strict import Control.Monad.Trans.Class (lift) -- main :: IO () main = do tv <- newTVarIO 0 y <- atomically $ flip evalStateT 0 $ do x <- get lift $ do modifyTVar tv (\a -> a + x + 1) y <- readTVar tv when (y > 10) retry return y print y So any or all of RWST work with STM, but you typically want to keep your STM transactions small and simple, so this is not a place where one would generally run wild with fancy stacks that do non-trivial additional computation. Indeed Monad Transformers are not Monads, they're always stacked on top of some base monad. The turtles don't go all the way down. A practical example of STM-like Monad's can be found in Hasql, where database operations run in a Monad that ensures that they have no side-effects that would prevent the transaction from being retried on deadlock detection. This is also a base Monad, where if you like you can stack more (pure) transformers. Which reminds me that ExceptT can be useful in such Monads, which avoid throwing impure exceptions. And is used in Hasql, where the operations tend to be more expensive than in STM, and any overhead from layering ExceptT or similar is quite small. -- Viktor. From sylvain at haskus.fr Mon Mar 29 12:18:08 2021 From: sylvain at haskus.fr (Sylvain Henry) Date: Mon, 29 Mar 2021 14:18:08 +0200 Subject: [Haskell-cafe] Why Haskell? In-Reply-To: References: Message-ID: <33b97d1d-0d3c-8952-0651-b833e16f7c71@haskus.fr> This talk from FP Complete's CEO is high-level (targeting management): https://www.youtube.com/watch?v=ybSBCVhVWs8 Cheers, Sylvain On 29/03/2021 02:24, Clinton Mead wrote: > I’m looking for recommendations of videos/articles to show to a > software development manager about why one should use Haskell, focused > more from a benefits to business perspective. > > Naturally this may involve some code, this manager isn’t completely > clueless when it comes to programming languages, but basically > something that explains why I’m raving about this “Haskell” thing all > the time and why it’s a good idea. > > Thanks, > Clinton > > _______________________________________________ > 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 Mon Mar 29 13:19:11 2021 From: compl.yue at icloud.com (YueCompl) Date: Mon, 29 Mar 2021 21:19:11 +0800 Subject: [Haskell-cafe] Why Haskell? In-Reply-To: References: <48377971-E4D8-4E75-AC56-6BFADCD21D77@icloud.com> <20210329081217.GA10722@saruman> <1CAB6F4E-6DA4-46E4-9F78-BFDA6E020CA5@icloud.com> Message-ID: <54998E88-C2A6-43CD-9395-6F83C6DDF7FA@icloud.com> Thanks for the insights, I was not aware of this approach before. But with STM as the base monad, I feel like to have lost the ability to delimit transaction boundaries at will, which is the essential tool STM offers. I can only think of doing that from IO via `atomically`, but that way we are dragged back to write transaction composing code in IO, so will lose effect tracking. I dunno but is there a way to delimit STM transactions without IO? > On 2021-03-29, at 19:50, Viktor Dukhovni wrote: > > STM is not a monad transformer, but it is a fine base monad, just like > Identity, IO or ST. Here's a contrived example of (StateT Int STM Int): > > import Control.Concurrent.STM > import Control.Monad (when) > import Control.Monad.Trans.State.Strict > import Control.Monad.Trans.Class (lift) > > -- > main :: IO () > main = do > tv <- newTVarIO 0 > y <- atomically $ flip evalStateT 0 $ do > x <- get > lift $ do > modifyTVar tv (\a -> a + x + 1) > y <- readTVar tv > when (y > 10) retry > return y > print y > > So any or all of RWST work with STM, but you typically want to keep your > STM transactions small and simple, so this is not a place where one > would generally run wild with fancy stacks that do non-trivial > additional computation. > > Indeed Monad Transformers are not Monads, they're always stacked on top > of some base monad. The turtles don't go all the way down. > > A practical example of STM-like Monad's can be found in Hasql, where > database operations run in a Monad that ensures that they have no > side-effects that would prevent the transaction from being retried on > deadlock detection. This is also a base Monad, where if you like > you can stack more (pure) transformers. > > Which reminds me that ExceptT can be useful in such Monads, which > avoid throwing impure exceptions. And is used in Hasql, where > the operations tend to be more expensive than in STM, and any > overhead from layering ExceptT or similar is quite small. > > -- > 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. From charukiewicz at protonmail.com Mon Mar 29 15:57:12 2021 From: charukiewicz at protonmail.com (Christian Charukiewicz) Date: Mon, 29 Mar 2021 15:57:12 +0000 Subject: [Haskell-cafe] Why Haskell? In-Reply-To: References: Message-ID: Hi Clinton, I've been using Haskell (as well as Elm) in production for several years now, and have found that the language is very conducive to writing reliable and maintainable software while also fostering developer productivity. Earlier this year, I wrote an article titled Why Haskell is our first choice for building production software systems: https://www.foxhound.systems/blog/why-haskell-for-production/. The article is written at someone like a software development manager, who knows how to program but doesn't necessarily know anything about Haskell. You may find that showing this article to your manager may help capture why you're raving about Haskell. If you're interested, I also wrote an experience report about using Elm in production back in 2017, available here: https://charukiewi.cz/posts/elm/ Let me know if you have any questions. Always happy to help someone in your situation, since I think Haskell is a great language and many organizations can benefit from its strengths. Best, Christian ‐‐‐‐‐‐‐ Original Message ‐‐‐‐‐‐‐ On Sunday, March 28th, 2021 at 19:24, Clinton Mead wrote: > I’m looking for recommendations of videos/articles to show to a software development manager about why one should use Haskell, focused more from a benefits to business perspective. > > Naturally this may involve some code, this manager isn’t completely clueless when it comes to programming languages, but basically something that explains why I’m raving about this “Haskell” thing all the time and why it’s a good idea. > > Thanks, > Clinton -------------- next part -------------- An HTML attachment was scrubbed... URL: From borgauf at gmail.com Mon Mar 29 17:12:59 2021 From: borgauf at gmail.com (Galaxy Being) Date: Mon, 29 Mar 2021 12:12:59 -0500 Subject: [Haskell-cafe] Maybe won't let me count In-Reply-To: <3b8bb257-78a0-3ea1-dafe-26f6c798663@henning-thielemann.de> References: <3b8bb257-78a0-3ea1-dafe-26f6c798663@henning-thielemann.de> Message-ID: A bit of post-mortem... I got this data MyList a = Empty | Cons a (MyList a) deriving (Eq,Ord,Show) data BaconOrIndex = Bacon | Indx Int deriving (Eq,Ord,Show) import Data.Maybe whereIsBM = whereIsBM' 1 whereIsBM' _ Empty = Nothing whereIsBM' !n (Cons Bacon _) = Just n whereIsBM' !n (Cons _ lx) = whereIsBM' (succ n) lx > whereIsBM (Cons (Indx 5) (Cons (Indx 13) (Cons (Indx 2) (Cons (Indx 8) Empty)))) Nothing > whereIsBM (Cons (Indx 5) (Cons (Indx 13) (Cons Bacon (Cons (Indx 8) Empty)))) Just 3 to work. Unfortunately, I couldn't get this whereIsBM boiList = go 0 where go !_ Empty = Nothing go !acc (Cons idx lx) | (idx == Bacon) = Just acc | otherwise = go (acc + 1) lx to work. Both are nearly identical, but the latter gives this error > whereIsBM (Cons (Indx 5) (Cons (Indx 13) (Cons (Indx 2) (Cons (Indx 8) Empty)))) No instance for (Show (MyList BaconOrIndex -> Maybe Integer)) : arising from a use of `print' This also failed whereIsBM boiList = case boiList of Nothing -> Nothing Just (Cons idx lx) | (idx == Bacon) -> Just 1 | otherwise -> (1 +) <$> (whereIsBM lx) Couldn't match type `Maybe (MyList BaconOrIndex)' with `MyList BaconOrIndex' Expected type: MyList BaconOrIndex -> Maybe a Actual type: Maybe (MyList BaconOrIndex) -> Maybe a Not sure why this didn't work. Would like to understand the whole fmap idea as applied here, though. On Mon, Mar 29, 2021 at 4:04 AM Henning Thielemann < lemming at henning-thielemann.de> wrote: > > On Mon, 29 Mar 2021, Viktor Dukhovni wrote: > > > Thus I applaud Michael Snoyman's quest to address the absense of a basic > > array type in the `base` library. Perhaps more users would stop abusing > > lists (memoisable iterators) as an indexed store. > > Data.Array actually _was_ part of base-3. > > However, I think we should split 'base' in more smaller parts rather than > making it bigger. > _______________________________________________ > 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 lemming at henning-thielemann.de Mon Mar 29 17:13:45 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Mon, 29 Mar 2021 19:13:45 +0200 (CEST) Subject: [Haskell-cafe] detecting infinite loop with type inference (Was: Why Haskell?) In-Reply-To: <20210329070158.GA10246@saruman> References: <20210329070158.GA10246@saruman> Message-ID: On Mon, 29 Mar 2021, Antonio Regidor Garcia wrote: > Not bussiness oriented, but these two articles are pretty good at explaining what Haskell and similar languages have to offer: > > This is brief and centered on Haskell's type system: > > https://perl.plover.com/yak/typing/notes.html >From slide 29 on he gives the example that type inference can point him to an infinite loop. This would not work in Haskell, would it? From jaro.reinders at gmail.com Mon Mar 29 17:30:41 2021 From: jaro.reinders at gmail.com (Jaro Reinders) Date: Mon, 29 Mar 2021 19:30:41 +0200 Subject: [Haskell-cafe] detecting infinite loop with type inference (Was: Why Haskell?) In-Reply-To: References: <20210329070158.GA10246@saruman> Message-ID: <2a06b4d6-c719-5078-53ac-5a2cef19d201@gmail.com> I get the same strange inferred type for this quickly translated program: split [] = ([], []) split [h] = ([h], []) split (x:y:t) = let (s1, s2) = split t in (x:s1, y:s2) merge :: [Int] -> [Int] -> [Int] merge [] x = x merge x [] = x merge (h1:t1) (h2:t2) = if h1 < h2 then h1:merge t1 (h2:t2) else h2:merge (h1:t1) t2 sort [] = [] sort x = let (p, q) = split x in merge (sort p) (sort q) > :t sort sort :: [a] -> [Int] The reason is that sort always returns the empty list, independently of the input list, so the type of the input list is not constrained. On 29-03-2021 19:13, Henning Thielemann wrote: > > On Mon, 29 Mar 2021, Antonio Regidor Garcia wrote: > >> Not bussiness oriented, but these two articles are pretty good at explaining >> what Haskell and similar languages have to offer: >> >> This is brief and centered on Haskell's type system: >> >> https://perl.plover.com/yak/typing/notes.html > > From slide 29 on he gives the example that type inference can point him to an > infinite loop. > > This would not work in Haskell, would it? > _______________________________________________ > 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 mail at andres-loeh.de Mon Mar 29 17:34:27 2021 From: mail at andres-loeh.de (Andres Loeh) Date: Mon, 29 Mar 2021 19:34:27 +0200 Subject: [Haskell-cafe] Maybe won't let me count In-Reply-To: References: <3b8bb257-78a0-3ea1-dafe-26f6c798663@henning-thielemann.de> Message-ID: Hi. In this version > whereIsBM boiList = go 0 > where > go !_ Empty = Nothing > go !acc (Cons idx lx) | (idx == Bacon) = Just acc > | otherwise = go (acc + 1) lx you abstract from boiList but then don't use it. You should either remove boiList on the left hand side or add it as a second argument to the call of the go function. In this version > whereIsBM boiList = case boiList of > Nothing -> Nothing > Just (Cons idx lx) > | (idx == Bacon) -> Just 1 > | otherwise -> (1 +) <$> (whereIsBM lx) you are pattern matching on boiList with Nothing / Just, as if it is of Maybe type, but judging from the other functions and also the recursive call, you're expecting it to be of type MyList. Cheers, Andres From ietf-dane at dukhovni.org Mon Mar 29 17:51:54 2021 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Mon, 29 Mar 2021 13:51:54 -0400 Subject: [Haskell-cafe] Maybe won't let me count In-Reply-To: References: <3b8bb257-78a0-3ea1-dafe-26f6c798663@henning-thielemann.de> Message-ID: On Mon, Mar 29, 2021 at 12:12:59PM -0500, Galaxy Being wrote: > A bit of post-mortem... Perhaps the Haskell beginners list: https://mail.haskell.org/cgi-bin/mailman/listinfo/beginners will be more helpful, and a tad more appropriate for such questions? -- Viktor. From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Mon Mar 29 19:03:38 2021 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Mon, 29 Mar 2021 20:03:38 +0100 Subject: [Haskell-cafe] detecting infinite loop with type inference (Was: Why Haskell?) In-Reply-To: <2a06b4d6-c719-5078-53ac-5a2cef19d201@gmail.com> References: <20210329070158.GA10246@saruman> <2a06b4d6-c719-5078-53ac-5a2cef19d201@gmail.com> Message-ID: <20210329190338.GA9814@cloudinit-builder> It's even better if you generalise merge to merge :: Ord a => [a] -> [a] -> [a] Then the type of sort is Ord a => [b] -> [a] and it's more obvious that not only is the input unused but the output is always empty. Interestingly I wrote on article about how to improve a particular program Mark Dominus himself wrote featuring exactly this kind of analysis! http://h2.jaguarpaw.co.uk/posts/using-brain-less-refactoring-yahtzee/ Tom On Mon, Mar 29, 2021 at 07:30:41PM +0200, Jaro Reinders wrote: > I get the same strange inferred type for this quickly translated program: > > split [] = ([], []) > split [h] = ([h], []) > split (x:y:t) = let (s1, s2) = split t > in (x:s1, y:s2) > > merge :: [Int] -> [Int] -> [Int] > merge [] x = x > merge x [] = x > merge (h1:t1) (h2:t2) = > if h1 < h2 then h1:merge t1 (h2:t2) > else h2:merge (h1:t1) t2 > > sort [] = [] > sort x = let (p, q) = split x > in merge (sort p) (sort q) > > > > > :t sort > sort :: [a] -> [Int] > > The reason is that sort always returns the empty list, independently of the > input list, so the type of the input list is not constrained. > > On 29-03-2021 19:13, Henning Thielemann wrote: > > > > On Mon, 29 Mar 2021, Antonio Regidor Garcia wrote: > > > > > Not bussiness oriented, but these two articles are pretty good at > > > explaining what Haskell and similar languages have to offer: > > > > > > This is brief and centered on Haskell's type system: > > > > > > https://perl.plover.com/yak/typing/notes.html > > > > From slide 29 on he gives the example that type inference can point him > > to an infinite loop. > > > > This would not work in Haskell, would it? > > _______________________________________________ > > 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 chikitosan at gmail.com Mon Mar 29 20:02:38 2021 From: chikitosan at gmail.com (Antonio Regidor Garcia) Date: Mon, 29 Mar 2021 22:02:38 +0200 Subject: [Haskell-cafe] detecting infinite loop with type inference (Was: Why Haskell?) In-Reply-To: <2a06b4d6-c719-5078-53ac-5a2cef19d201@gmail.com> References: <20210329070158.GA10246@saruman> <2a06b4d6-c719-5078-53ac-5a2cef19d201@gmail.com> Message-ID: <20210329200238.GA2919@saruman> El Mon, Mar 29, 2021 at 07:30:41PM +0200, Jaro Reinders escribió: > The reason is that sort always returns the empty list, independently > of the input list, so the type of the input list is not constrained. Actually, it only returns the empty list for the empty list. For other lists, it never returns. From trebla at vex.net Mon Mar 29 20:08:43 2021 From: trebla at vex.net (Albert Y. C. Lai) Date: Mon, 29 Mar 2021 16:08:43 -0400 Subject: [Haskell-cafe] Why Haskell? In-Reply-To: References: Message-ID: https://docs.google.com/presentation/d/1a4GvI0dbL8sfAlnTUwVxhq4_j-QiDlz02_t0XZJXnzY/preview?slide=id.p (probably more like explaining to you what you should say to management) On 2021-03-28 8:24 p.m., Clinton Mead wrote: > I’m looking for recommendations of videos/articles to show to a software > development manager about why one should use Haskell, focused more from > a benefits to business perspective. > > Naturally this may involve some code, this manager isn’t completely > clueless when it comes to programming languages, but basically something > that explains why I’m raving about this “Haskell” thing all the time and > why it’s a good idea. > > Thanks, > Clinton > > _______________________________________________ > 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 Juan.Casanova at ed.ac.uk Tue Mar 30 05:56:23 2021 From: Juan.Casanova at ed.ac.uk (CASANOVA Juan) Date: Tue, 30 Mar 2021 05:56:23 +0000 Subject: [Haskell-cafe] Maybe won't let me count In-Reply-To: References: <3b8bb257-78a0-3ea1-dafe-26f6c798663@henning-thielemann.de>, Message-ID: For the record, since I suggested this solution (without actually trying it): whereIsBM boiList = case boiList of Nothing -> Nothing Just (Cons idx lx) | (idx == Bacon) -> Just 1 | otherwise -> (1 +) <$> (whereIsBM lx) The problem I did not realize here is that lx is of type BaconOrIndex, not Maybe BaconOrIndex. There are two solutions. What someone suggested of just making whereIsBM receive BaconOrIndex all the way (You're also missing the Empty case, I just realized, which maybe you confused with Nothing, so I add that one): whereIsBM boiList = case boiList of { Empty -> Nothing; Cons idx lx | (idx == Bacon) -> Just 1 | otherwise -> (1 +) <$> (whereIsBM lx) } The other option is to just wrap lx in Just, but that really feels strange and not what you want, plus you'd still need to account for the Empty case. ________________________________ From: Haskell-Cafe on behalf of Galaxy Being Sent: 29 March 2021 18:12 To: haskell-cafe Subject: Re: [Haskell-cafe] Maybe won't let me count This email was sent to you by someone outside the University. You should only click on links or attachments if you are certain that the email is genuine and the content is safe. A bit of post-mortem... I got this data MyList a = Empty | Cons a (MyList a) deriving (Eq,Ord,Show) data BaconOrIndex = Bacon | Indx Int deriving (Eq,Ord,Show) import Data.Maybe whereIsBM = whereIsBM' 1 whereIsBM' _ Empty = Nothing whereIsBM' !n (Cons Bacon _) = Just n whereIsBM' !n (Cons _ lx) = whereIsBM' (succ n) lx > whereIsBM (Cons (Indx 5) (Cons (Indx 13) (Cons (Indx 2) (Cons (Indx 8) Empty)))) Nothing > whereIsBM (Cons (Indx 5) (Cons (Indx 13) (Cons Bacon (Cons (Indx 8) Empty)))) Just 3 to work. Unfortunately, I couldn't get this whereIsBM boiList = go 0 where go !_ Empty = Nothing go !acc (Cons idx lx) | (idx == Bacon) = Just acc | otherwise = go (acc + 1) lx to work. Both are nearly identical, but the latter gives this error > whereIsBM (Cons (Indx 5) (Cons (Indx 13) (Cons (Indx 2) (Cons (Indx 8) Empty)))) No instance for (Show (MyList BaconOrIndex -> Maybe Integer)) : arising from a use of `print' This also failed whereIsBM boiList = case boiList of Nothing -> Nothing Just (Cons idx lx) | (idx == Bacon) -> Just 1 | otherwise -> (1 +) <$> (whereIsBM lx) Couldn't match type `Maybe (MyList BaconOrIndex)' with `MyList BaconOrIndex' Expected type: MyList BaconOrIndex -> Maybe a Actual type: Maybe (MyList BaconOrIndex) -> Maybe a Not sure why this didn't work. Would like to understand the whole fmap idea as applied here, though. On Mon, Mar 29, 2021 at 4:04 AM Henning Thielemann > wrote: On Mon, 29 Mar 2021, Viktor Dukhovni wrote: > Thus I applaud Michael Snoyman's quest to address the absense of a basic > array type in the `base` library. Perhaps more users would stop abusing > lists (memoisable iterators) as an indexed store. Data.Array actually _was_ part of base-3. However, I think we should split 'base' in more smaller parts rather than making it bigger. _______________________________________________ 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. The University of Edinburgh is a charitable body, registered in Scotland, with registration number SC005336. Is e buidheann carthannais a th' ann an Oilthigh Dh?n ?ideann, cl?raichte an Alba, ?ireamh cl?raidh SC005336. -------------- next part -------------- An HTML attachment was scrubbed... URL: From x at tomsmeding.com Tue Mar 30 07:27:11 2021 From: x at tomsmeding.com (Tom Smeding) Date: Tue, 30 Mar 2021 07:27:11 +0000 Subject: [Haskell-cafe] Injective type classes? Message-ID: Hi Cafe, With this class definition with this instance: class C a where instance C b => C (a, b) GHC can of course infer, given 'C b', that 'C (a, b)'. This is nothing more than the meaning of the instance declaration above. However, GHC cannot infer the inverse: {-# LANGUAGE FlexibleContexts #-} foo :: C a => a -> Int foo = undefined bar1 :: C (a, b) => a -> b -> Int bar1 _ = foo This gives an error on the right-hand side of 'bar1': "Could not deduce (C b) arising from a use of ‘foo’; from the context: C (a, b)". The same happens in similar cases: {-# LANGUAGE GADTs #-} bar2 :: (C p, p ~ (a, b)) => a -> b -> Int bar2 _ = foo data Thing a where Tup :: a -> b -> Thing (a, b) bar3 :: C a => Thing a -> Int bar3 (Tup x y) = foo y Both these usages of 'foo' yield the same error. My use-case is 'bar3', where I would like GHC to determine that the call to 'foo' is valid. (I don't actually care directly about bar1 and bar2.) Is there a way to make 'bar3' compile? Note that: - In my actual use case, 'C' is of course not empty. - In my actual use case, my type class instances _are_ in fact injective, even though I do enable FlexibleInstances to be able to write e.g. 'instance C (T a Int)'. - Above, the dictionary for 'C (a, b)' includes a dictionary for 'C b', doesn't it? So if inference can resolve 'C b', then the compilation to Core can find the right dictionary, I think? (Not sure about this part.) Thanks a lot for your help. Cheers, Tom -------------- next part -------------- An HTML attachment was scrubbed... URL: From chikitosan at gmail.com Tue Mar 30 07:58:28 2021 From: chikitosan at gmail.com (Antonio Regidor Garcia) Date: Tue, 30 Mar 2021 09:58:28 +0200 Subject: [Haskell-cafe] Injective type classes? In-Reply-To: References: Message-ID: <20210330075828.GA2655@saruman> El Tue, Mar 30, 2021 at 07:27:11AM +0000, Tom Smeding escribió: > Hi Cafe, > > With this class definition with this instance: > > class C a where > instance C b => C (a, b) > > GHC can of course infer, given 'C b', that 'C (a, b)'. This is nothing more > than the meaning of the instance declaration above. > > However, GHC cannot infer the inverse: Because the inverse doesn't need to hold. A priori, nothing prevents the existence of (a, b) instances where b isn't an instance. For example, if Ord a and Ord b hold, then Ord (a, b) holds, but not the opposite. If, for example, you have Ord a but not Ord b, you can make (a, b) an instance of Ord by simply defining (a1, b1) `compare` (a2, b2) = a1 `compare` a2. Best, Antonio From kai.prott at hotmail.de Tue Mar 30 08:01:20 2021 From: kai.prott at hotmail.de (Kai-Oliver Prott) Date: Tue, 30 Mar 2021 10:01:20 +0200 Subject: [Haskell-cafe] Injective type classes? In-Reply-To: References: Message-ID: Hey Tom, there is a paper "Bidirectional type class instances" [1] about a similar concept. However, the approach is not implemented in GHC. At the moment, the dictionary for 'C (a, b)' does not explicitly include a dictionary for C a and C b. It is only implicitly referenced in the implementation of C's class methods. For it to be explicitly available for further usage, the dictionary data type for classes of C would have to be extended by an argument. This is not trivial and is discussed in the mentioned paper. The discussion at the GHC proposal show some alternative approaches how something like this can be achieved with the current GHC (e.g. [2]). Best, Kai [1] https://dl.acm.org/doi/abs/10.1145/3331545.3342596 [2] https://github.com/ghc-proposals/ghc-proposals/pull/284#issuecomment-542322728 On 30.03.21 09:27, Tom Smeding wrote: > Hi Cafe, > > With this class definition with this instance: > >     class C a where >     instance C b => C (a, b) > > GHC can of course infer, given 'C b', that 'C (a, b)'. This is nothing > more > than the meaning of the instance declaration above. > > However, GHC cannot infer the inverse: > >     {-# LANGUAGE FlexibleContexts #-} > >     foo :: C a => a -> Int >     foo = undefined > >     bar1 :: C (a, b) => a -> b -> Int >     bar1 _ = foo > > This gives an error on the right-hand side of 'bar1': "Could not > deduce (C b) > arising from a use of ‘foo’; from the context: C (a, b)". The same > happens in > similar cases: > >     {-# LANGUAGE GADTs #-} > >     bar2 :: (C p, p ~ (a, b)) => a -> b -> Int >     bar2 _ = foo > >     data Thing a where >         Tup :: a -> b -> Thing (a, b) > >     bar3 :: C a => Thing a -> Int >     bar3 (Tup x y) = foo y > > Both these usages of 'foo' yield the same error. > > My use-case is 'bar3', where I would like GHC to determine that the > call to > 'foo' is valid. (I don't actually care directly about bar1 and bar2.) > > Is there a way to make 'bar3' compile? > > Note that: > - In my actual use case, 'C' is of course not empty. > - In my actual use case, my type class instances _are_ in fact > injective, even >   though I do enable FlexibleInstances to be able to write e.g. >   'instance C (T a Int)'. > - Above, the dictionary for 'C (a, b)' includes a dictionary for 'C > b', doesn't >   it? So if inference can resolve 'C b', then the compilation to Core > can find >   the right dictionary, I think? (Not sure about this part.) > > Thanks a lot for your help. > > Cheers, > Tom > > > _______________________________________________ > 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 aaronngray.lists at gmail.com Tue Mar 30 09:38:13 2021 From: aaronngray.lists at gmail.com (Aaron Gray) Date: Tue, 30 Mar 2021 10:38:13 +0100 Subject: [Haskell-cafe] Hackage dependencies Message-ID: Hi, Is there a tool or web access to give a list off all Hackage packages dependent upon a Hackage package, please ? Regards, Aaron -- Aaron Gray Independent Open Source Software Engineer, Computer Language Researcher, Information Theorist, and Computer Scientist. From ollie at ocharles.org.uk Tue Mar 30 09:43:19 2021 From: ollie at ocharles.org.uk (Oliver Charles) Date: Tue, 30 Mar 2021 10:43:19 +0100 Subject: [Haskell-cafe] Hackage dependencies In-Reply-To: References: Message-ID: On Tue, 30 Mar 2021, at 10:38 AM, Aaron Gray wrote: > Hi, > > Is there a tool or web access to give a list off all Hackage packages > dependent upon a Hackage package, please ? I think you want https://packdeps.haskellers.com/reverse Ollie -------------- next part -------------- An HTML attachment was scrubbed... URL: From x at tomsmeding.com Tue Mar 30 09:51:18 2021 From: x at tomsmeding.com (Tom Smeding) Date: Tue, 30 Mar 2021 09:51:18 +0000 Subject: [Haskell-cafe] Injective type classes? In-Reply-To: References: Message-ID: Hi Kai, Thanks for the links! Your [2] is a workaround that works perfectly for my purposes. I had already considered using an associated type, but that puts the GHC type checker into an infinite loop... Using a separate type family fixes my issue. Cheers, Tom ‐‐‐‐‐‐‐ Original Message ‐‐‐‐‐‐‐ On Tuesday, March 30, 2021 10:01 AM, Kai-Oliver Prott wrote: > Hey Tom, > > there is a paper "Bidirectional type class instances" [1] about a similar concept. > > However, the approach is not implemented in GHC. At the moment, the dictionary for 'C (a, b)' does not explicitly include a dictionary for C a and C b. It is only implicitly referenced in the implementation of C's class methods. > For it to be explicitly available for further usage, the dictionary data type for classes of C would have to be extended by an argument. This is not trivial and is discussed in the mentioned paper. > > The discussion at the GHC proposal show some alternative approaches how something like this can be achieved with the current GHC (e.g. [2]). > > Best, > Kai > > [1] https://dl.acm.org/doi/abs/10.1145/3331545.3342596 > [2] https://github.com/ghc-proposals/ghc-proposals/pull/284#issuecomment-542322728 > > On 30.03.21 09:27, Tom Smeding wrote: > >> Hi Cafe, >> >> With this class definition with this instance: >> >> class C a where >> instance C b => C (a, b) >> >> GHC can of course infer, given 'C b', that 'C (a, b)'. This is nothing more >> than the meaning of the instance declaration above. >> >> However, GHC cannot infer the inverse: >> >> {-# LANGUAGE FlexibleContexts #-} >> >> foo :: C a => a -> Int >> foo = undefined >> >> bar1 :: C (a, b) => a -> b -> Int >> bar1 _ = foo >> >> This gives an error on the right-hand side of 'bar1': "Could not deduce (C b) >> arising from a use of ‘foo’; from the context: C (a, b)". The same happens in >> similar cases: >> >> {-# LANGUAGE GADTs #-} >> >> bar2 :: (C p, p ~ (a, b)) => a -> b -> Int >> bar2 _ = foo >> >> data Thing a where >> Tup :: a -> b -> Thing (a, b) >> >> bar3 :: C a => Thing a -> Int >> bar3 (Tup x y) = foo y >> >> Both these usages of 'foo' yield the same error. >> >> My use-case is 'bar3', where I would like GHC to determine that the call to >> 'foo' is valid. (I don't actually care directly about bar1 and bar2.) >> >> Is there a way to make 'bar3' compile? >> >> Note that: >> - In my actual use case, 'C' is of course not empty. >> - In my actual use case, my type class instances _are_ in fact injective, even >> though I do enable FlexibleInstances to be able to write e.g. >> 'instance C (T a Int)'. >> - Above, the dictionary for 'C (a, b)' includes a dictionary for 'C b', doesn't >> it? So if inference can resolve 'C b', then the compilation to Core can find >> the right dictionary, I think? (Not sure about this part.) >> >> Thanks a lot for your help. >> >> Cheers, >> Tom >> >> _______________________________________________ >> 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 lemming at henning-thielemann.de Tue Mar 30 14:36:57 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Tue, 30 Mar 2021 16:36:57 +0200 (CEST) Subject: [Haskell-cafe] Injective type classes? In-Reply-To: References: Message-ID: <63c47af9-3b6b-2993-7812-a3973ae395ad@henning-thielemann.de> On Tue, 30 Mar 2021, Tom Smeding wrote: > Note that: > - In my actual use case, 'C' is of course not empty. > - In my actual use case, my type class instances _are_ in fact injective, even >   though I do enable FlexibleInstances to be able to write e.g. >   'instance C (T a Int)'. > - Above, the dictionary for 'C (a, b)' includes a dictionary for 'C b', doesn't >   it? So if inference can resolve 'C b', then the compilation to Core can find >   the right dictionary, I think? (Not sure about this part.) How shall GHC find the method implementations for 'b' if it only has the methods for '(a,b)'? From lemming at henning-thielemann.de Tue Mar 30 14:39:02 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Tue, 30 Mar 2021 16:39:02 +0200 (CEST) Subject: [Haskell-cafe] Hackage dependencies In-Reply-To: References: Message-ID: <587a637c-cf57-33bd-cdb6-9a95f773d5be@henning-thielemann.de> On Tue, 30 Mar 2021, Oliver Charles wrote: > On Tue, 30 Mar 2021, at 10:38 AM, Aaron Gray wrote: > Hi, > > Is there a tool or web access to give a list off all Hackage packages > dependent upon a Hackage package, please ? > > > I think you want https://packdeps.haskellers.com/reverse Stackage lists dependencies in both directions, e.g. https://www.stackage.org/package/vector From x at tomsmeding.com Tue Mar 30 14:41:01 2021 From: x at tomsmeding.com (Tom Smeding) Date: Tue, 30 Mar 2021 14:41:01 +0000 Subject: [Haskell-cafe] Injective type classes? In-Reply-To: <63c47af9-3b6b-2993-7812-a3973ae395ad@henning-thielemann.de> References: <63c47af9-3b6b-2993-7812-a3973ae395ad@henning-thielemann.de> Message-ID: On Tuesday, March 30, 2021 4:36 PM, Henning Thielemann wrote: > > > On Tue, 30 Mar 2021, Tom Smeding wrote: > > > Note that: > > > > - In my actual use case, 'C' is of course not empty. > > - In my actual use case, my type class instances are in fact injective, even > >   though I do enable FlexibleInstances to be able to write e.g. > >   'instance C (T a Int)'. > > > > - Above, the dictionary for 'C (a, b)' includes a dictionary for 'C b', doesn't > >   it? So if inference can resolve 'C b', then the compilation to Core can find > >   the right dictionary, I think? (Not sure about this part.) > > > > How shall GHC find the method implementations for 'b' if it only has the > methods for '(a,b)'? Because the instance for '(a,b)' includes a type class constraint for 'b', I expected that the relevant dictionary (which is surely needed for implementing the methods contained in the dictionary for '(a,b)') would be available. However, I understand from a sibling post that this dictionary for 'b' is only contained in the closures for the methods in the dictionary for '(a,b)', and GHC cannot easily access that. In any case, I have a workaround, as I posted in a reply to Kai's email. Nevertheless, thanks for the help! :) Cheers, Tom From meng.wang at bristol.ac.uk Wed Mar 31 10:51:14 2021 From: meng.wang at bristol.ac.uk (Meng Wang) Date: Wed, 31 Mar 2021 10:51:14 +0000 Subject: [Haskell-cafe] Bx 2021 - CALL FOR PAPERS Message-ID: To Haskellers, Bidirectional Transformations (Bx) are also known as lenses! Please consider submitting your Haskell-related papers which are very welcome. Best regards, Meng Meng Wang, PhD (Oxon) University of Bristol Senior Lecturer of Programming Languages Head of PL research group International Director of SCEEM (CS, EEE, EMath) School ********************************************************************************** 9th International Workshop on Bidirectional Transformations (Bx 2021) as part of the STAF conference (June 21, 2021) running virtually, Western Norway University of Applied Sciences, Bergen, Norway http://bx-community.wikidot.com/bx2021:home ********************************************************************************** * Important dates: * Abstract submission: April 27, 2021 * Paper Submission: May 4, 2021 ********************************************************************************** OVERVIEW ========================================= Bidirectional transformations (bx) are a mechanism for maintaining the consistency between two or more related (and heterogeneous) sources of information (i.e., relational databases, software models and code, or any other artefacts following standard or domain-specific formats). The strongest argument in favour of bx is its ability to provide a synchronization mechanism that is guaranteed to be correct by construction. Bx has been attracting a wide range of research areas and communities, with prominent presence at top conferences in several different fields (namely databases, programming languages, software engineering, and graph transformation). Nowadays, the fast-growing complexity of software- or data- intensive systems has forced the industry and the academy to use and investigate different development techniques to manage the many different aspects of the systems. Researchers are actively investigating the use of bidirectional approaches to tackle a diverse set of challenges with various applications including model-driven software development, visualization with direct manipulation, big data, databases, domain-specific languages, serializers, and data transformation, integration and exchange. Bx 2021 is a dedicated venue for bx in all relevant fields and is part of a workshop series that was created in order to promote cross-disciplinary research and awareness in the area. As such, since its beginning in 2012, the workshop has rotated between venues in different fields. TOPICS ========================================= The aim of the workshop is to bring together researchers and practitioners, established and new, interested in bx from different perspectives, including but not limited to: * bidirectional programming languages and frameworks * software development with bx * data and model synchronization * view updating * inter-model consistency analysis and repair * data/schema (or model/metamodel) co-evolution * coupled software/model transformations * inversion of transformations and data exchange mappings * domain-specific languages for bx * analysis and classification of requirements for bx * bridging the gap between formal concepts and application scenarios * analysis of efficiency of transformation algorithms and benchmarks * model-driven and model-based approaches * survey and comparison of bx technologies * case studies and tool support CATEGORIES OF SUBMISSIONS ========================================= Five categories of submissions are considered: * Full Research Papers (13-15 pages) - in-depth presentations of novel concepts and results - applications of bx to new domains - survey papers providing novel comparisons between existing bx technologies and approaches, case studies * Tool Papers (7-8 pages) - guideline papers presenting best practices for employing a specific bx approach (with a specific tool) - presentation of new tools or substantial improvements to existing ones - qualitative and/or quantitative comparisons of applying different bx approaches and tools * Experience Report (7-8 pages) - sharing experiences and lessons learned with bx tools/frameworks/languages - how bx is used in (research/industrial/educational) projects * Short Papers (5 pages) - work in progress - small focused contributions - position papers and research perspectives - critical questions and challenges for bx * Talk Proposals (2 pages) - proposed lectures about topics of interest for bx - existing work representing relevant contributions for bx - promising contributions that are not mature enough to be proposed as papers of the other categories If your submission is not a Full Research Paper, please include the intended submission category in the Title field of EasyChair’s submission form. Tool papers, experience reports and short papers will be mapped to the short paper category in CEUR (5-9 standard pages, 1 standard page = 2500 characters), whereas full research papers will be mapped to the regular paper category in CEUR (min. 10 standard pages). The bibliography is excluded from the page limits. All papers are expected to be self-contained and well-written. Tool papers are not expected to present novel scientific results, but to document artifacts of interest and share bx experience/best practices with the community. Experience papers are expected to report on lessons learnt from applying bx approaches, languages, tools, and theories to practical application case studies. Extended abstracts should primarily provoke interesting discussion at the workshop and will not be held to the same standard of maturity as regular papers; short papers contain focused results, positions or perspectives that can be presented in full in just a few pages, and that correspondingly contain fewer results and that therefore might not be competitive in the full paper category. Talk proposals are expected to present work that is of particular interest to the community and worth a talk slot at the workshop. We strongly encourage authors to ensure that any (variants of) examples are present in the bx example repository at the time of submission, and, for tool papers, to allow for reproducibility with minimal effort, either via a virtual machine (e.g., via Share) or a dedicated website with relevant artifacts and tool access. All submissions will be peer-reviewed by at least three members of the program committee. If a submission is accepted, at least one author is expected to participate in the workshop to present it. Authors of accepted tool paper submissions are also expected to be available to demonstrate their tool at the event. PROCEEDINGS ========================================= The workshop proceedings (in a STAF 2021 joint volume for workshops), including all accepted papers (except talk proposals), shall be submitted after the conference to CEUR-WS.org for online publication. Pre-prints of all papers will be available via the workshop website at the beginning of the conference. Papers must follow the CEUR one column style available at: http://ceur-ws.org/Vol-XXX/CEURART.zip or https://www.overleaf.com/latex/templates/template-for-submissions-to-ceur-workshop-proceedings-ceur-ws-dot-org/hpvjjzhjxzjk and must be submitted via EasyChair: https://easychair.org/conferences/?conf=bx2021 Please also ensure that your submission is legible when printed on a black and white printer. In particular, please check that colors remain distinct and font sizes are legible. Submissions not complying with the above guidelines may be excluded from the reviewing process without further notice. IMPORTANT DATES ========================================= Abstract submission: April 27, 2021 Paper submission: May 4, 2021 Author notification: May 25, 2021 Early registration: May 27, 2021 Workshop: June 21, 2021 PROGRAM CO-CHAIRS ========================================= The workshop is co-organized by Meng Wang (University of Bristol, UK) and Leen Lambers (Hasso Plattner Institute at the University of Potsdam, Germany). In case of questions, please contact the PC chairs at bx2021 at easychair.org . Please find further information w.r.t. the Bx 2021 workshop at: http://bx-community.wikidot.com/bx2021:home and STAF 2021 conference at: https://staf2021.hvl.no/ PROGRAM COMMITTEE ========================================= Ravi Chugh, University of Chicago, USA Anthony Cleve, University of Namur, Belgium Alcino Cunha, University of Minho, Portugal Romina Eramo, University of L'Aquila, Italy Michael Johnson, Macquarie University, Australia Hsiang Shang Ko, Academia Sinica, Taiwan Ralf Lämmel, University of Koblenz-Landau, Germany Kazutaka Matsuda, Tohoku University, Japan Fernando Orejas, Universitat Politècnica de Catalunya, Spain Roly Perera, Alan Turing Institute, UK Perdita Stevens, The University of Edinburgh, UK Tarmo Uustalu, Reykjavik University, Iceland Jens Weber, University of Victoria, Canada Bernhard Westfechtel, University of Bayreuth, Germany ========================================= -------------- next part -------------- An HTML attachment was scrubbed... URL: