From aaronngray.lists at gmail.com Fri Apr 2 09:29:35 2021 From: aaronngray.lists at gmail.com (Aaron Gray) Date: Fri, 2 Apr 2021 10:29:35 +0100 Subject: [Haskell-cafe] Hackage dependencies In-Reply-To: <587a637c-cf57-33bd-cdb6-9a95f773d5be@henning-thielemann.de> References: <587a637c-cf57-33bd-cdb6-9a95f773d5be@henning-thielemann.de> Message-ID: Many thanks ! On Tue, 30 Mar 2021 at 15:39, Henning Thielemann wrote: > > > 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 -- Aaron Gray Independent Open Source Software Engineer, Computer Language Researcher, Information Theorist, and amateur computer scientist. From Juan.Casanova at ed.ac.uk Fri Apr 2 12:54:37 2021 From: Juan.Casanova at ed.ac.uk (CASANOVA Juan) Date: Fri, 2 Apr 2021 12:54:37 +0000 Subject: [Haskell-cafe] Existential type variables in constraints Message-ID: Hello again, Here with more type class issues. As usual, assume all extensions required. But here I am going to be explicit, because UndecidableInstances is definitely required for this and I know it's a problematic one. These may be excessive, but with these extensions this should work: {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE QuantifiedConstraints #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE LiberalTypeSynonyms #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE ConstraintKinds #-} My "problem" is I want (almost need) existentially quantified types in constraints. The reason is that I have lots, lots and lots of constraints over up to 10 type variables (multi-parameter type classes in most cases, with complex functional dependencies), which are trickled down over multiple layers of functions over multiple modules. So what I do is I define some global type synonyms that combine families of these constraints, usually the ones that are used in a specific module. Something like: type ModuleAConstraints a b c d = (Ord a, Ord b , Ord c, Class1 a b, Class2 a [c], Class3 [(c,a)] (a -> d [b])) (the specific constraints are made up, mine are much more and more complicated, but you get the idea of the liberality of the constraints) Now, what happens is that in one of the highest-level modules, some of the type variables begin to disappear because they are only used internally in the lower-level modules. The functional dependencies ensure that, once I instantiate the remaining type variables, those type variables will have only one possible result, for which I will have an implemented instance. But my type synonyms include them, and I need them to use the lower-level functions. No problem, you can have existentially quantified variables in constraints. For example, this works: class Class1 a where fun1 :: a -> a -> Bool instance (Ord a, forall b. Ord b) => Class1 a where fun1 = (<) You can also do this with type synonyms and group constraints into pairs. For example, the two following equivalent alternatives work (same definition of Class1): 1: instance (Ord a, forall b c. (Ord b, Ord c)) => Class1 a where fun1 = (<) 2: type CType b c = (Ord b, Ord c) instance (Ord a, forall b c. CType b c) => Class1 a where fun1 = (<) But, it seems, any constraints under the existentially quantifier that only utilize non-quantified variables seems to be completely overlooked by the compiler. As such, the following two equivalent alternatives both fail to type check, telling me that it cannot deduce (Ord a): 3: instance (forall b. (Ord a, Ord b)) => Class1 a where fun1 = (<) 4: type CType a b = (Ord a, Ord b) instance (forall b. CType a b) => Class1 a where fun1 = (<) Is there a good reason for this? It could be a good reason in the sense of: The deduction would be incorrect; or a good reason in the sense of: The compiler would need to do undecidable things to be able to deduce that in general. But right now I cannot see a reason. I honestly cannot see how it could be hard for the compiler to realize that instance (Ord a, forall b. Ord b) => Class1 a where fun1 = (<) and instance (forall b. (Ord a, Ord b)) => Class1 a where fun1 = (<) are equivalent. But it doesn't. Also, is there any way I can make this work? Right now, the only option I can see is to manually re-enumerate all of the constraints that do not include the quantified variable and use that. I guess I can do that and it would only take around an hour... but what a boring and tedious hour, and to be fair I was going to stop for today anyway so I thought I'd throw the question on Haskell Cafe. I hope that's okay 🙂. Thanks in advance as usual. Juan Casanova. 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 Juan.Casanova at ed.ac.uk Fri Apr 2 13:01:06 2021 From: Juan.Casanova at ed.ac.uk (CASANOVA Juan) Date: Fri, 2 Apr 2021 13:01:06 +0000 Subject: [Haskell-cafe] Existential type variables in constraints In-Reply-To: References: Message-ID: Just for the record, the question still remains, but as usual, after I sent the question I realized the general ballpark in which the answer may end up being. When doing: instance (forall b. (Ord a, Ord b)) => Class1 a where fun1 = (<) While in this case there are no functional dependencies, it is possible in principle that (Ord a, Ord b) produces a functional dependency between a and b, which would make the specific "a" a function of whatever "b" is, and since "b" is existentially quantified, then "a" would also be dependent on the specific type it ended up being instantiated to. Is this what's going on? In order to do this, undecidable things like exploring all the possible combinations of functional dependencies would need to be explored by the compiler? Even if this was exactly the problem, I would still be very happy to hear ideas on how to deal with this without having to manually write down all of the constraints that do not include a specific type variable. Thanks again. ________________________________ From: CASANOVA Juan Sent: 02 April 2021 13:54 To: YueCompl via Haskell-Cafe Subject: Existential type variables in constraints Hello again, Here with more type class issues. As usual, assume all extensions required. But here I am going to be explicit, because UndecidableInstances is definitely required for this and I know it's a problematic one. These may be excessive, but with these extensions this should work: {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE QuantifiedConstraints #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE LiberalTypeSynonyms #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE ConstraintKinds #-} My "problem" is I want (almost need) existentially quantified types in constraints. The reason is that I have lots, lots and lots of constraints over up to 10 type variables (multi-parameter type classes in most cases, with complex functional dependencies), which are trickled down over multiple layers of functions over multiple modules. So what I do is I define some global type synonyms that combine families of these constraints, usually the ones that are used in a specific module. Something like: type ModuleAConstraints a b c d = (Ord a, Ord b , Ord c, Class1 a b, Class2 a [c], Class3 [(c,a)] (a -> d [b])) (the specific constraints are made up, mine are much more and more complicated, but you get the idea of the liberality of the constraints) Now, what happens is that in one of the highest-level modules, some of the type variables begin to disappear because they are only used internally in the lower-level modules. The functional dependencies ensure that, once I instantiate the remaining type variables, those type variables will have only one possible result, for which I will have an implemented instance. But my type synonyms include them, and I need them to use the lower-level functions. No problem, you can have existentially quantified variables in constraints. For example, this works: class Class1 a where fun1 :: a -> a -> Bool instance (Ord a, forall b. Ord b) => Class1 a where fun1 = (<) You can also do this with type synonyms and group constraints into pairs. For example, the two following equivalent alternatives work (same definition of Class1): 1: instance (Ord a, forall b c. (Ord b, Ord c)) => Class1 a where fun1 = (<) 2: type CType b c = (Ord b, Ord c) instance (Ord a, forall b c. CType b c) => Class1 a where fun1 = (<) But, it seems, any constraints under the existentially quantifier that only utilize non-quantified variables seems to be completely overlooked by the compiler. As such, the following two equivalent alternatives both fail to type check, telling me that it cannot deduce (Ord a): 3: instance (forall b. (Ord a, Ord b)) => Class1 a where fun1 = (<) 4: type CType a b = (Ord a, Ord b) instance (forall b. CType a b) => Class1 a where fun1 = (<) Is there a good reason for this? It could be a good reason in the sense of: The deduction would be incorrect; or a good reason in the sense of: The compiler would need to do undecidable things to be able to deduce that in general. But right now I cannot see a reason. I honestly cannot see how it could be hard for the compiler to realize that instance (Ord a, forall b. Ord b) => Class1 a where fun1 = (<) and instance (forall b. (Ord a, Ord b)) => Class1 a where fun1 = (<) are equivalent. But it doesn't. Also, is there any way I can make this work? Right now, the only option I can see is to manually re-enumerate all of the constraints that do not include the quantified variable and use that. I guess I can do that and it would only take around an hour... but what a boring and tedious hour, and to be fair I was going to stop for today anyway so I thought I'd throw the question on Haskell Cafe. I hope that's okay 🙂. Thanks in advance as usual. Juan Casanova. 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 borgauf at gmail.com Fri Apr 2 15:37:07 2021 From: borgauf at gmail.com (Galaxy Being) Date: Fri, 2 Apr 2021 10:37:07 -0500 Subject: [Haskell-cafe] Eq source code? Message-ID: While learning about type classes, I tried to find the actual source code for Eq. In my beginner books this much is typically given class Eq a where (==), (/=) :: a -> a -> Bool -- Minimal completion definition: x /= y = not (x == y) x == y = not (x /= y) I then found this at hackage.haskell.org, but the "source" links are dead. On this page is a section of what I can't tell is either source code or just commentary on all the different mathematical ideas about equality, i.e., Reflexivity x == x = True Symmetry x == y = y == x Transitivity if x == y && y == z = True, then x == z = True Substitutivity if x == y = True and f is a "public" function whose return type is an instance of Eq, then f x == f y = True Negation x /= y = not (x == y) I would like to know if this is indeed in the source code or if it's just a sort of commentary. It looks important. Where can I find the actual source for all these basic type classes? LB -------------- next part -------------- An HTML attachment was scrubbed... URL: From liam.wall+haskell at gmail.com Fri Apr 2 15:46:26 2021 From: liam.wall+haskell at gmail.com (Liam Wall) Date: Fri, 2 Apr 2021 16:46:26 +0100 Subject: [Haskell-cafe] Eq source code? In-Reply-To: References: Message-ID: That's description on what any instance is expected to adhere to, not source. You can check source links on stackable too: https://www.stackage.org/haddock/lts-17.8/base-4.14.1.0/Data-Eq.html On Fri, 2 Apr 2021, 16:38 Galaxy Being, wrote: > While learning about type classes, I tried to find the actual source code > for Eq. In my beginner books this much is typically given > > class Eq a where > (==), (/=) :: a -> a -> Bool > > -- Minimal completion definition: > x /= y = not (x == y) > x == y = not (x /= y) > > I then found this > at > hackage.haskell.org, but the "source" links are dead. On this page is a > section of what I can't tell is either source code or just commentary on > all the different mathematical ideas about equality, i.e., > > Reflexivity > x == x = True > Symmetry > x == y = y == x > Transitivity > if x == y && y == z = True, then x == z = True > Substitutivity > if x == y = True and f is a "public" function whose return type is an > instance of Eq, then f x == f y = True > Negation > x /= y = not (x == y) > > I would like to know if this is indeed in the source code or if it's just > a sort of commentary. It looks important. Where can I find the actual > source for all these basic type classes? > > 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 Apr 2 15:54:22 2021 From: bob at redivi.com (Bob Ippolito) Date: Fri, 2 Apr 2021 08:54:22 -0700 Subject: [Haskell-cafe] Eq source code? In-Reply-To: References: Message-ID: The equations you've posted are laws that the instances of the Eq typeclass must satisfy. If someone creates an instance that does not satisfy all of the laws then the behavior is undefined. Laws are generally not present in the source code outside of the comments, and they typically can not be proved in standard Haskell. I don't know why the documentation links are broken (bug in hackage?) but you can find the source links here: https://hackage.haskell.org/package/ghc-prim-0.7.0/docs/GHC-Classes.html Many instances are automatically derived by the compiler (which is usually what you would do for your own data types) or are otherwise dependent on built-in primitives (e.g. eqInt, eqWord, etc.). On Fri, Apr 2, 2021 at 8:38 AM Galaxy Being wrote: > While learning about type classes, I tried to find the actual source code > for Eq. In my beginner books this much is typically given > > class Eq a where > (==), (/=) :: a -> a -> Bool > > -- Minimal completion definition: > x /= y = not (x == y) > x == y = not (x /= y) > > I then found this > at > hackage.haskell.org, but the "source" links are dead. On this page is a > section of what I can't tell is either source code or just commentary on > all the different mathematical ideas about equality, i.e., > > Reflexivity > x == x = True > Symmetry > x == y = y == x > Transitivity > if x == y && y == z = True, then x == z = True > Substitutivity > if x == y = True and f is a "public" function whose return type is an > instance of Eq, then f x == f y = True > Negation > x /= y = not (x == y) > > I would like to know if this is indeed in the source code or if it's just > a sort of commentary. It looks important. Where can I find the actual > source for all these basic type classes? > > 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 Apr 2 15:58:27 2021 From: borgauf at gmail.com (Galaxy Being) Date: Fri, 2 Apr 2021 10:58:27 -0500 Subject: [Haskell-cafe] Eq source code? In-Reply-To: References: Message-ID: Good, so it is a sort of commentary. Thanks. On Fri, Apr 2, 2021 at 10:46 AM Liam Wall wrote: > That's description on what any instance is expected to adhere to, not > source. > > You can check source links on stackable too: > > https://www.stackage.org/haddock/lts-17.8/base-4.14.1.0/Data-Eq.html > > On Fri, 2 Apr 2021, 16:38 Galaxy Being, wrote: > >> While learning about type classes, I tried to find the actual source code >> for Eq. In my beginner books this much is typically given >> >> class Eq a where >> (==), (/=) :: a -> a -> Bool >> >> -- Minimal completion definition: >> x /= y = not (x == y) >> x == y = not (x /= y) >> >> I then found this >> at >> hackage.haskell.org, but the "source" links are dead. On this page is a >> section of what I can't tell is either source code or just commentary on >> all the different mathematical ideas about equality, i.e., >> >> Reflexivity >> x == x = True >> Symmetry >> x == y = y == x >> Transitivity >> if x == y && y == z = True, then x == z = True >> Substitutivity >> if x == y = True and f is a "public" function whose return type is an >> instance of Eq, then f x == f y = True >> Negation >> x /= y = not (x == y) >> >> I would like to know if this is indeed in the source code or if it's just >> a sort of commentary. It looks important. Where can I find the actual >> source for all these basic type classes? >> >> 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 anthony_clayden at clear.net.nz Sat Apr 3 01:18:49 2021 From: anthony_clayden at clear.net.nz (Anthony Clayden) Date: Sat, 3 Apr 2021 14:18:49 +1300 Subject: [Haskell-cafe] Existential type variables in constraints Message-ID: > because UndecidableInstances is definitely required for this and I know it's a problematic one. Hi Juan, I'll knock that on the head at once. `UndecidableInstances` is not "problematic" (or at least it's far less problematic than others you list). Although we're lacking a proof that it can't lead to incoherence/type unsafety, nobody's demonstrated unsafety due to `UndecidableInstances` alone -- that is, providing the program compiles (i.e. instance resolution terminates). OTOH `FlexibleInstances` can give `OverlappingInstances` -- maybe overlapping with those in some other module, thus giving the dreaded Orphan instances problems. I'd be much more concerned about them. > instance (Ord a, forall b c. (Ord b, Ord c)) => Class1 a where > fun1 = (<) Why does that even mention `b` or `c`? There's no FunDep from `a`, to get a FunDep there'd be a constraint `D a b c` or something. They seem totally redundant. > completely overlooked by the compiler Yes. Quite. What do you expect the compiler to do? Even if the class decl gave a signature for `fun1` mentioning `b`, `c`, those would be _distinct_ tyvars, because they're not scoped in the class head. > is there any way I can make this work? Sorry, I don't know what you want to "work". Please at least show a class decl with a FunDep. From your second message: > it is possible in principle that (Ord a, Ord b) produces a functional dependency between a and b No it isn't possible, even in principle: `(..., ...)` is a tuple constructor, not a class; therefore no FunDep could apply. AntC -------------- next part -------------- An HTML attachment was scrubbed... URL: From rae at richarde.dev Sat Apr 3 02:54:05 2021 From: rae at richarde.dev (Richard Eisenberg) Date: Sat, 3 Apr 2021 02:54:05 +0000 Subject: [Haskell-cafe] Existential type variables in constraints In-Reply-To: References: Message-ID: <010f017895a6e24d-99cedddd-a3da-4e4e-8c4d-dd8d896c3f90-000000@us-east-2.amazonses.com> > On Apr 2, 2021, at 8:54 AM, CASANOVA Juan wrote: > > I honestly cannot see how it could be hard for the compiler to realize that > > instance (Ord a, forall b. Ord b) => Class1 a where > fun1 = (<) > > and > > instance (forall b. (Ord a, Ord b)) => Class1 a where > fun1 = (<) > > are equivalent. But it doesn't. Just on this one small point: GHC understands a forall-type as a function, so that (in your second example above) we can produce Ord a and Ord b only once a b has been chosen. Because nothing forces the choice of b, GHC cannot proceed and extract the Ord a constraint. More generally, I don't think there is a good answer for what you want to do, short of using type families instead of functional dependencies. With type families, you can name the new type in terms of the type variables you have in scope. I hope this is helpful! Richard -------------- next part -------------- An HTML attachment was scrubbed... URL: From anka.213 at gmail.com Sat Apr 3 06:59:15 2021 From: anka.213 at gmail.com (=?utf-8?Q?Andreas_K=C3=A4llberg?=) Date: Sat, 3 Apr 2021 14:59:15 +0800 Subject: [Haskell-cafe] Get proof of injectivity for an injective type family Message-ID: Is there any way to get hold of a proof of injectivity for an injective type family? In other words, given this type family type family F a = b | b -> a can I get the term fInj :: F a ~ F b => (a ~ b => r) -> r in any way (without using unsafeCoerce)? -------------- next part -------------- A non-text attachment was scrubbed... Name: smime.p7s Type: application/pkcs7-signature Size: 1394 bytes Desc: not available URL: From Juan.Casanova at ed.ac.uk Sat Apr 3 07:20:44 2021 From: Juan.Casanova at ed.ac.uk (CASANOVA Juan) Date: Sat, 3 Apr 2021 07:20:44 +0000 Subject: [Haskell-cafe] Existential type variables in constraints In-Reply-To: References: Message-ID: Richard's answer sounds like pretty much what I thought on my follow-up message, and I guess I'll have to go the route of re-writing all the constraints that do not contain the type variable no longer there. Anthony, I won't argue with the discussion on which extensions are problematic. The reason I thought people saw UndecidableInstances as problematic is that, precisely because of the undecidability (semidecidability?), you can write incorrect programs that do not terminate to compile, and it can be hard to debug. I do know that whenever the program is correct then it works fine. But we don't always write correct programs, and debugging is an essential thing as well. That said, I have ran into the overlapping instances issues myself plenty of times so I'm not disagreeing, I just had this impression I think from reading people talk about UndecidableInstances. On your discussion of my particular example, I think I did not make it clear enough why I want to do things like that. I did try to explain it, but it seems it did not click with you. Also, I think one of the statements you made is flat out incorrect, but maybe I'm mistaken. One thing at a time. > instance (Ord a, forall b c. (Ord b, Ord c)) => Class1 a where > fun1 = (<) Why does that even mention `b` or `c`? There's no FunDep from `a`, to get a FunDep there'd be a constraint `D a b c` or something. They seem totally redundant. This example is just to corner the problem in one example. The reality of what I would do would be more like this: > type CType b c = (Ord b, Ord c) > instance (Ord a, forall b c. CType b c) => Class1 a where > fun1 = (<) Why do I do this? Because, as I tried to explain, my CType in practice is much larger, and it includes many more type variables. I do it to avoid having 5-line constraints on every function I write. Maybe if I show you the actual example it'll click with you. Here's some of the examples: type ESMGUConstraints t pd fn v sov = (Ord sov, SimpleTerm t, Eq fn, HasArity fn, HasArity sov, ChangeArity sov, Functor (t (SOTerm fn sov)), Functor (t fn), Bifunctor t, Traversable (t (GroundSOT fn)), Unifiable (t (SOTerm fn sov)), Variabilizable v, Variable v, Variabilizable sov, Variable sov, Ord v, Functor (t (GroundSOT fn)), Eq (t fn (Fix (t fn))), Show sov, Show fn, Show v, Show (t (SOTerm fn sov) (UTerm (t (SOTerm fn sov)) v)), Show (t (GroundSOT fn) (UTerm (t (GroundSOT fn)) v)), Ord fn, Ord (t (SOTerm fn sov) (UTerm (t (SOTerm fn sov)) v))) type ESMGUConstraintsU t pd fn v sov uv = (ESMGUConstraints t pd fn v sov, Show uv, Ord uv, Variable uv, Variabilizable uv) type ESMGUConstraintsPdPmv pd pmv = (Ord pd, Ord pmv, Eq pd, Eq pmv, Show pmv, Show pd, HasArity pd, HasArity pmv, Variable pmv, Variabilizable pmv, ChangeArity pmv) type ESMGUConstraintsUPmv t pd fn v pmv fmv uv = (ESMGUConstraintsU t pd fn v fmv uv, ESMGUConstraintsPdPmv pd pmv) type ESMGUConstraintsA a = (SimpleTerm a) type ESMGUConstraintsAMpd a mpd = (ESMGUConstraintsA a, Functor (a mpd), Eq mpd, Ord mpd) type ESMGUConstraintsSS ss = (Functor ss, Unifiable ss) type ESMGUConstraintsAMpdSs a t ss mpd pd fn v pmv fmv = (ESMGUConstraints t pd fn v fmv, ESMGUConstraintsSS ss, ESMGUConstraintsAMpd a mpd, Eq (a mpd (ss (SOAtom pd fn pmv fmv))), Eq (a (SOAtom pd fn pmv fmv) (SOMetawrap t fn v fmv)), ESMGUConstraintsPdPmv pd pmv) type ESMGUConstraintsALL a t ss mpd pd fn v pmv fmv uv = (ESMGUConstraintsU t pd fn v fmv uv, ESMGUConstraintsAMpdSs a t ss mpd pd fn v pmv fmv) I think you can see why I would want to avoid having to write all of this on every function that I write. In fact you can see I already have it partially split, but not in all the ways I may want to use it. In particular, there are others in other modules that build on these and add a few others, and I want those except I no longer have the "uv" type variable on one of the functions I have, but I internally use functions that use the constraints that include it, and functional dependencies should ensure that it is instantiated to one particular class. But this leads to your second point, the one in which I think you said something incorrect, or maybe you didn't see how my example was simplified on purpose. You said: No it isn't possible, even in principle: `(..., ...)` is a tuple constructor, not a class; therefore no FunDep could apply. What about the following code then: class Class1 a b | b -> a where fun1 :: b -> a type CType a b = (Ord a, Class1 a b) fun2 :: (forall b. CType a b) => a -> a -> Bool fun2 = (>) Now, fun2 in particular can be made to work because it only makes use of (Ord a) and not (Class1 a b), but the tuple constraint type (CType a b) does have a functional dependency from b to a, so I can see why a is not an entirely separable variable in the forall-quantified constraint, which is why I think ultimately GHC works the way Richard mentioned and why I can't do what I want, even if the specific (Ord a) constraint can be used. Of course the issue, I see, is that this could produce (and does, in my case) chains of functional dependencies that, when existentially quantified, become difficult/problematic. For example: class Class1 a b | b -> a where fun1 :: b -> a type CType a b c = (Class1 a b, Class1 b c) fun2 :: (forall c. CType a b c) => b -> a fun2 = fun1 fun1 does not depend on c, but the type b does, through the functional dependency in (Class1 b c). I don't even know if it would make sense for this to work or not. You can separate (Class1 a b) like you could with (Ord a), but now it's not completely independent of the rest. of (CType a b c). In other words, I'm not sure if the semantics of (forall c. CType a b c) are the same as the semantics of (Class1 a b, forall c. Class1 b c). Now, my actual situation in practice is more something like this: class Class1 a b | b -> a where fun1 :: b -> a type CType a b c = (Class1 a b, Class1 b c) fun2 :: (forall b. CType a b c) => c -> a fun2 c = fun1 (fun1 c) This makes sense conceptually. fun2 does not specify which b we are talking about, but for every c, there should be only one b that works. That, of course, ultimately means that fun2 will not work for any a and c, but only for those for which there is a b linking them. It seems as if GHC does not have the ability to do this. Actually at this point I'm not sure if I can do what I want without instantiating the type variables. Juan. ________________________________ From: Haskell-Cafe on behalf of Anthony Clayden Sent: 03 April 2021 02:18 To: The Haskell Cafe Subject: Re: [Haskell-cafe] Existential type variables in constraints 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. > because UndecidableInstances is definitely required for this and I know it's a problematic one. Hi Juan, I'll knock that on the head at once. `UndecidableInstances` is not "problematic" (or at least it's far less problematic than others you list). Although we're lacking a proof that it can't lead to incoherence/type unsafety, nobody's demonstrated unsafety due to `UndecidableInstances` alone -- that is, providing the program compiles (i.e. instance resolution terminates). OTOH `FlexibleInstances` can give `OverlappingInstances` -- maybe overlapping with those in some other module, thus giving the dreaded Orphan instances problems. I'd be much more concerned about them. > instance (Ord a, forall b c. (Ord b, Ord c)) => Class1 a where > fun1 = (<) Why does that even mention `b` or `c`? There's no FunDep from `a`, to get a FunDep there'd be a constraint `D a b c` or something. They seem totally redundant. > completely overlooked by the compiler Yes. Quite. What do you expect the compiler to do? Even if the class decl gave a signature for `fun1` mentioning `b`, `c`, those would be _distinct_ tyvars, because they're not scoped in the class head. > is there any way I can make this work? Sorry, I don't know what you want to "work". Please at least show a class decl with a FunDep. From your second message: > it is possible in principle that (Ord a, Ord b) produces a functional dependency between a and b No it isn't possible, even in principle: `(..., ...)` is a tuple constructor, not a class; therefore no FunDep could apply. AntC 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 Juan.Casanova at ed.ac.uk Sat Apr 3 12:52:54 2021 From: Juan.Casanova at ed.ac.uk (CASANOVA Juan) Date: Sat, 3 Apr 2021 12:52:54 +0000 Subject: [Haskell-cafe] Existential type variables in constraints In-Reply-To: References: , Message-ID: Sorry for too many long messages as usual, but I think I found out the best way to proceed for my case. Indeed, I had been sort of avoiding type families for too long, and I figured this was the way to go. In general, using type families from the start instead of functional dependencies on type classes seems to work better. Now, I don't wanna go and re-do thousands of lines of code to adapt to this either. But, I found out you can actually wrap a type class with functional dependencies into a type class with type families in a non-intrusive way to use it properly. Going back to the example I offered before: class Class1 a b | b -> a where fun1 :: b -> a I can wrap this with another class that uses a type family instead of a functional dependency: class Class1 (Class1FamRes b) b => Class1Fam b where type Class1FamRes b fun1fam :: b -> Class1FamRes b fun1fam = fun1 And then I can define my fun2 properly: fun2 :: (Class1Fam a, Class1Fam (Class1FamRes a)) => a -> Class1FamRes (Class1FamRes a) fun2 = fun1 . fun1 And then when instantiating the type variables, assuming I already had the functional dep instances implemented: instance Class1 Int String where fun1 x = 5 instance Class1 Bool Int where fun1 x = True It's trivial to wrap them in Class1Fam instances: instance Class1Fam String where type Class1FamRes String = Int instance Class1Fam Int where type Class1FamRes Int = Bool And I can use fun2 properly. So I think I know how to properly deal with my big program's problem without having to rewrite too much code, and I also think I'll be using type families way more instead of functional dependencies moving forward. Any additional comments anyone might have would be very welcome. Sorry for the sort of monologue. Do let me know if there's a feeling I'm misusing the list. Thanks again, Juan Casanova. ________________________________ From: Haskell-Cafe on behalf of CASANOVA Juan Sent: 03 April 2021 08:20 To: The Haskell Cafe Subject: Re: [Haskell-cafe] Existential type variables in constraints Richard's answer sounds like pretty much what I thought on my follow-up message, and I guess I'll have to go the route of re-writing all the constraints that do not contain the type variable no longer there. Anthony, I won't argue with the discussion on which extensions are problematic. The reason I thought people saw UndecidableInstances as problematic is that, precisely because of the undecidability (semidecidability?), you can write incorrect programs that do not terminate to compile, and it can be hard to debug. I do know that whenever the program is correct then it works fine. But we don't always write correct programs, and debugging is an essential thing as well. That said, I have ran into the overlapping instances issues myself plenty of times so I'm not disagreeing, I just had this impression I think from reading people talk about UndecidableInstances. On your discussion of my particular example, I think I did not make it clear enough why I want to do things like that. I did try to explain it, but it seems it did not click with you. Also, I think one of the statements you made is flat out incorrect, but maybe I'm mistaken. One thing at a time. > instance (Ord a, forall b c. (Ord b, Ord c)) => Class1 a where > fun1 = (<) Why does that even mention `b` or `c`? There's no FunDep from `a`, to get a FunDep there'd be a constraint `D a b c` or something. They seem totally redundant. This example is just to corner the problem in one example. The reality of what I would do would be more like this: > type CType b c = (Ord b, Ord c) > instance (Ord a, forall b c. CType b c) => Class1 a where > fun1 = (<) Why do I do this? Because, as I tried to explain, my CType in practice is much larger, and it includes many more type variables. I do it to avoid having 5-line constraints on every function I write. Maybe if I show you the actual example it'll click with you. Here's some of the examples: type ESMGUConstraints t pd fn v sov = (Ord sov, SimpleTerm t, Eq fn, HasArity fn, HasArity sov, ChangeArity sov, Functor (t (SOTerm fn sov)), Functor (t fn), Bifunctor t, Traversable (t (GroundSOT fn)), Unifiable (t (SOTerm fn sov)), Variabilizable v, Variable v, Variabilizable sov, Variable sov, Ord v, Functor (t (GroundSOT fn)), Eq (t fn (Fix (t fn))), Show sov, Show fn, Show v, Show (t (SOTerm fn sov) (UTerm (t (SOTerm fn sov)) v)), Show (t (GroundSOT fn) (UTerm (t (GroundSOT fn)) v)), Ord fn, Ord (t (SOTerm fn sov) (UTerm (t (SOTerm fn sov)) v))) type ESMGUConstraintsU t pd fn v sov uv = (ESMGUConstraints t pd fn v sov, Show uv, Ord uv, Variable uv, Variabilizable uv) type ESMGUConstraintsPdPmv pd pmv = (Ord pd, Ord pmv, Eq pd, Eq pmv, Show pmv, Show pd, HasArity pd, HasArity pmv, Variable pmv, Variabilizable pmv, ChangeArity pmv) type ESMGUConstraintsUPmv t pd fn v pmv fmv uv = (ESMGUConstraintsU t pd fn v fmv uv, ESMGUConstraintsPdPmv pd pmv) type ESMGUConstraintsA a = (SimpleTerm a) type ESMGUConstraintsAMpd a mpd = (ESMGUConstraintsA a, Functor (a mpd), Eq mpd, Ord mpd) type ESMGUConstraintsSS ss = (Functor ss, Unifiable ss) type ESMGUConstraintsAMpdSs a t ss mpd pd fn v pmv fmv = (ESMGUConstraints t pd fn v fmv, ESMGUConstraintsSS ss, ESMGUConstraintsAMpd a mpd, Eq (a mpd (ss (SOAtom pd fn pmv fmv))), Eq (a (SOAtom pd fn pmv fmv) (SOMetawrap t fn v fmv)), ESMGUConstraintsPdPmv pd pmv) type ESMGUConstraintsALL a t ss mpd pd fn v pmv fmv uv = (ESMGUConstraintsU t pd fn v fmv uv, ESMGUConstraintsAMpdSs a t ss mpd pd fn v pmv fmv) I think you can see why I would want to avoid having to write all of this on every function that I write. In fact you can see I already have it partially split, but not in all the ways I may want to use it. In particular, there are others in other modules that build on these and add a few others, and I want those except I no longer have the "uv" type variable on one of the functions I have, but I internally use functions that use the constraints that include it, and functional dependencies should ensure that it is instantiated to one particular class. But this leads to your second point, the one in which I think you said something incorrect, or maybe you didn't see how my example was simplified on purpose. You said: No it isn't possible, even in principle: `(..., ...)` is a tuple constructor, not a class; therefore no FunDep could apply. What about the following code then: class Class1 a b | b -> a where fun1 :: b -> a type CType a b = (Ord a, Class1 a b) fun2 :: (forall b. CType a b) => a -> a -> Bool fun2 = (>) Now, fun2 in particular can be made to work because it only makes use of (Ord a) and not (Class1 a b), but the tuple constraint type (CType a b) does have a functional dependency from b to a, so I can see why a is not an entirely separable variable in the forall-quantified constraint, which is why I think ultimately GHC works the way Richard mentioned and why I can't do what I want, even if the specific (Ord a) constraint can be used. Of course the issue, I see, is that this could produce (and does, in my case) chains of functional dependencies that, when existentially quantified, become difficult/problematic. For example: class Class1 a b | b -> a where fun1 :: b -> a type CType a b c = (Class1 a b, Class1 b c) fun2 :: (forall c. CType a b c) => b -> a fun2 = fun1 fun1 does not depend on c, but the type b does, through the functional dependency in (Class1 b c). I don't even know if it would make sense for this to work or not. You can separate (Class1 a b) like you could with (Ord a), but now it's not completely independent of the rest. of (CType a b c). In other words, I'm not sure if the semantics of (forall c. CType a b c) are the same as the semantics of (Class1 a b, forall c. Class1 b c). Now, my actual situation in practice is more something like this: class Class1 a b | b -> a where fun1 :: b -> a type CType a b c = (Class1 a b, Class1 b c) fun2 :: (forall b. CType a b c) => c -> a fun2 c = fun1 (fun1 c) This makes sense conceptually. fun2 does not specify which b we are talking about, but for every c, there should be only one b that works. That, of course, ultimately means that fun2 will not work for any a and c, but only for those for which there is a b linking them. It seems as if GHC does not have the ability to do this. Actually at this point I'm not sure if I can do what I want without instantiating the type variables. Juan. ________________________________ From: Haskell-Cafe on behalf of Anthony Clayden Sent: 03 April 2021 02:18 To: The Haskell Cafe Subject: Re: [Haskell-cafe] Existential type variables in constraints 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. > because UndecidableInstances is definitely required for this and I know it's a problematic one. Hi Juan, I'll knock that on the head at once. `UndecidableInstances` is not "problematic" (or at least it's far less problematic than others you list). Although we're lacking a proof that it can't lead to incoherence/type unsafety, nobody's demonstrated unsafety due to `UndecidableInstances` alone -- that is, providing the program compiles (i.e. instance resolution terminates). OTOH `FlexibleInstances` can give `OverlappingInstances` -- maybe overlapping with those in some other module, thus giving the dreaded Orphan instances problems. I'd be much more concerned about them. > instance (Ord a, forall b c. (Ord b, Ord c)) => Class1 a where > fun1 = (<) Why does that even mention `b` or `c`? There's no FunDep from `a`, to get a FunDep there'd be a constraint `D a b c` or something. They seem totally redundant. > completely overlooked by the compiler Yes. Quite. What do you expect the compiler to do? Even if the class decl gave a signature for `fun1` mentioning `b`, `c`, those would be _distinct_ tyvars, because they're not scoped in the class head. > is there any way I can make this work? Sorry, I don't know what you want to "work". Please at least show a class decl with a FunDep. From your second message: > it is possible in principle that (Ord a, Ord b) produces a functional dependency between a and b No it isn't possible, even in principle: `(..., ...)` is a tuple constructor, not a class; therefore no FunDep could apply. AntC 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 ekmett at gmail.com Sun Apr 4 22:35:41 2021 From: ekmett at gmail.com (Edward Kmett) Date: Sun, 4 Apr 2021 15:35:41 -0700 Subject: [Haskell-cafe] Existential type variables in constraints In-Reply-To: References: Message-ID: There's a lot here. I'm just going to laser lock on the starting impossible part that AntC also tried to address. On Sat, Apr 3, 2021 at 12:26 AM CASANOVA Juan wrote: > > This example is just to corner the problem in one example. The reality of > what I would do would be more like this: > > > type CType b c = (Ord b, Ord c) > > instance (Ord a, forall b c. CType b c) => Class1 a where > > This doesn't say what you seem to think it says. It says: When you go to look for an instance for Class1, every such instance is formed as follows: * First go resolve an Ord instance for a. (So far so good). * Next you need to show that for every single pair of types in the universe b and c, Ord b and Ord c hold independently. (Which makes the comparatively narrow ask for an Ord for a seem pretty redundant!) That is an impassable bar. Full stop. It is equivalent to instance (forall x. Ord x) => Class1 a The existence of any type anywhere without an Ord instance that can be uniformly constructed without caring at all about any structure on 'a' stops you cold. That forall isn't denoting existential there, it really is denoting a universal quantifier. If you want 'b' and 'c' to be some function of a, you can use a type family for each to pick them out or a multi-parameter typeclass that includes them in the signature, but that is simply not what you wrote down. -Edward Juan. > ------------------------------ > *From:* Haskell-Cafe on behalf of > Anthony Clayden > *Sent:* 03 April 2021 02:18 > *To:* The Haskell Cafe > *Subject:* Re: [Haskell-cafe] Existential type variables in constraints > > 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. > > because UndecidableInstances is definitely required for this and I know > it's a problematic one. > > Hi Juan, I'll knock that on the head at once. `UndecidableInstances` is > not "problematic" (or at least it's far less problematic than others you > list). Although we're lacking a proof that it can't lead to > incoherence/type unsafety, nobody's demonstrated unsafety due to > `UndecidableInstances` alone -- that is, providing the program compiles > (i.e. instance resolution terminates). > > OTOH `FlexibleInstances` can give `OverlappingInstances` -- maybe > overlapping with those in some other module, thus giving the dreaded Orphan > instances problems. I'd be much more concerned about them. > > > instance (Ord a, forall b c. (Ord b, Ord c)) => Class1 a where > > fun1 = (<) > > > Why does that even mention `b` or `c`? There's no FunDep from `a`, to get a FunDep there'd be a constraint `D a b c` or something. They seem totally redundant. > > > > completely overlooked by the compiler > > > Yes. Quite. What do you expect the compiler to do? Even if the class decl gave a signature for `fun1` mentioning `b`, `c`, those would be _distinct_ tyvars, because they're not scoped in the class head. > > > > is there any way I can make this work? > > > Sorry, I don't know what you want to "work". Please at least show a class decl with a FunDep. From your second message: > > > > it is possible in principle that (Ord a, Ord b) produces a functional dependency between a and b > > > No it isn't possible, even in principle: `(..., ...)` is a tuple constructor, not a class; therefore no FunDep could apply. > > > AntC > > > 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. > _______________________________________________ > 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 Apr 5 05:17:23 2021 From: borgauf at gmail.com (Galaxy Being) Date: Mon, 5 Apr 2021 00:17:23 -0500 Subject: [Haskell-cafe] A functor for two Peano systems Message-ID: I'm just not understanding the concept of a functor in this context: I have this plus :: Int -> Int -> Int plus n m = if (n == 0) then m else sCessor (plus (pCessor n) m) where sCessor x = x + 1 pCessor x = if (x == 0) then error "too small" else (x - 1) and this data MyNum = MNZero | OneMoreThan MyNum deriving (Show,Eq,Ord) plus2 :: MyNum -> MyNum -> MyNum plus2 n m = if (n == MNZero) then m else sCessor (plus2 (pCessor n) m) where sCessor x = (OneMoreThan x) pCessor x = if (x == MNZero) then (error "too small") else (oneLess x) oneLess MNZero = MNZero oneLess (OneMoreThan myn) = myn It seems there should be just one plus, function that would handle both an Int-based Peano and the MyNum-based Peano, not two. But in this definition fmap :: (a -> b) -> f a -> f b The (a -> b) should be "lifted" over the f a -> f b But I can't conceive of how this should all fit together, i.e., to create just one generic plus that would handle both the plus :: Int -> Int -> Int and the plus2 :: MyNum -> MyNum -> MyNum. Trying to get started, I would assume I need some sort of instance Functor MyNum describing, yeah, what? Or am I barking up the completely wrong tree here, i.e., this isn't a functor issue? LB -------------- next part -------------- An HTML attachment was scrubbed... URL: From tanuki at gmail.com Mon Apr 5 05:58:15 2021 From: tanuki at gmail.com (Akhra Gannon) Date: Sun, 4 Apr 2021 22:58:15 -0700 Subject: [Haskell-cafe] A functor for two Peano systems In-Reply-To: References: Message-ID: I think your last guess is correct... what you're trying to build appears to be a semigroup (or monoid), not a functor. On Sun, Apr 4, 2021, 10:18 PM Galaxy Being wrote: > I'm just not understanding the concept of a functor in this context: I > have this > > plus :: Int -> Int -> Int > plus n m = if (n == 0) > then m > else sCessor (plus (pCessor n) m) > where sCessor x = x + 1 > pCessor x = if (x == 0) > then error "too small" > else (x - 1) > > and this > > data MyNum = MNZero | OneMoreThan MyNum deriving (Show,Eq,Ord) > > plus2 :: MyNum -> MyNum -> MyNum > plus2 n m = if (n == MNZero) > then m > else sCessor (plus2 (pCessor n) m) > where sCessor x = (OneMoreThan x) > pCessor x = if (x == MNZero) > then (error "too small") > else (oneLess x) > oneLess MNZero = MNZero > oneLess (OneMoreThan myn) = myn > > It seems there should be just one plus, function that would handle both > an Int-based Peano and the MyNum-based Peano, not two. But in this > definition > > fmap :: (a -> b) -> f a -> f b > > The (a -> b) should be "lifted" over the f a -> f b But I can't conceive > of how this should all fit together, i.e., to create just one generic plus > that would handle both the plus :: Int -> Int -> Int and the plus2 :: > MyNum -> MyNum -> MyNum. Trying to get started, I would assume I need > some sort of instance Functor MyNum describing, yeah, what? Or am I > barking up the completely wrong tree here, i.e., this isn't a functor issue? > > 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 Apr 5 09:07:18 2021 From: Juan.Casanova at ed.ac.uk (CASANOVA Juan) Date: Mon, 5 Apr 2021 09:07:18 +0000 Subject: [Haskell-cafe] Existential type variables in constraints In-Reply-To: References: , Message-ID: Edward, > That forall isn't denoting existential there, it really is denoting a universal quantifier. Huh! You seem to be completely right. I think I had thought it would have an existential meaning like when you use constraints in data definitions, like: data Foo = forall a. Ord a => Foo a But I guess here the existential meaning comes from reading it as a universal quantifier on the co-variant argument: "For every a that is an Ord, we can build a Foo with the constructor Foo", which when used the other way around becomes: "If you have a foo, then you have some type with Ord". This definitely does explain the entire problem with the behaviour I am expecting. > If you want 'b' and 'c' to be some function of a, you can use a type family for each to pick them out or a multi-parameter typeclass that includes them in the signature, but that is simply not what you wrote down. Yes, this definitely seems to be the way to go (type families), though I still don't think what I'm trying to do is possible without type families, while keeping the genericity of the type parameters. Thanks for confirming this, and for clarifying my fundamental misunderstanding with quantified constraints. Juan. ________________________________ From: Edward Kmett Sent: 04 April 2021 23:35 To: CASANOVA Juan Cc: The Haskell Cafe Subject: Re: [Haskell-cafe] Existential type variables in constraints 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. There's a lot here. I'm just going to laser lock on the starting impossible part that AntC also tried to address. On Sat, Apr 3, 2021 at 12:26 AM CASANOVA Juan > wrote: This example is just to corner the problem in one example. The reality of what I would do would be more like this: > type CType b c = (Ord b, Ord c) > instance (Ord a, forall b c. CType b c) => Class1 a where This doesn't say what you seem to think it says. It says: When you go to look for an instance for Class1, every such instance is formed as follows: * First go resolve an Ord instance for a. (So far so good). * Next you need to show that for every single pair of types in the universe b and c, Ord b and Ord c hold independently. (Which makes the comparatively narrow ask for an Ord for a seem pretty redundant!) That is an impassable bar. Full stop. It is equivalent to instance (forall x. Ord x) => Class1 a The existence of any type anywhere without an Ord instance that can be uniformly constructed without caring at all about any structure on 'a' stops you cold. That forall isn't denoting existential there, it really is denoting a universal quantifier. If you want 'b' and 'c' to be some function of a, you can use a type family for each to pick them out or a multi-parameter typeclass that includes them in the signature, but that is simply not what you wrote down. -Edward Juan. ________________________________ From: Haskell-Cafe > on behalf of Anthony Clayden > Sent: 03 April 2021 02:18 To: The Haskell Cafe > Subject: Re: [Haskell-cafe] Existential type variables in constraints 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. > because UndecidableInstances is definitely required for this and I know it's a problematic one. Hi Juan, I'll knock that on the head at once. `UndecidableInstances` is not "problematic" (or at least it's far less problematic than others you list). Although we're lacking a proof that it can't lead to incoherence/type unsafety, nobody's demonstrated unsafety due to `UndecidableInstances` alone -- that is, providing the program compiles (i.e. instance resolution terminates). OTOH `FlexibleInstances` can give `OverlappingInstances` -- maybe overlapping with those in some other module, thus giving the dreaded Orphan instances problems. I'd be much more concerned about them. > instance (Ord a, forall b c. (Ord b, Ord c)) => Class1 a where > fun1 = (<) Why does that even mention `b` or `c`? There's no FunDep from `a`, to get a FunDep there'd be a constraint `D a b c` or something. They seem totally redundant. > completely overlooked by the compiler Yes. Quite. What do you expect the compiler to do? Even if the class decl gave a signature for `fun1` mentioning `b`, `c`, those would be _distinct_ tyvars, because they're not scoped in the class head. > is there any way I can make this work? Sorry, I don't know what you want to "work". Please at least show a class decl with a FunDep. From your second message: > it is possible in principle that (Ord a, Ord b) produces a functional dependency between a and b No it isn't possible, even in principle: `(..., ...)` is a tuple constructor, not a class; therefore no FunDep could apply. AntC 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. _______________________________________________ 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 anthony_clayden at clear.net.nz Mon Apr 5 11:49:34 2021 From: anthony_clayden at clear.net.nz (Anthony Clayden) Date: Mon, 5 Apr 2021 23:49:34 +1200 Subject: [Haskell-cafe] A functor for two Peano systems Message-ID: > Or am I barking up the completely wrong tree here, i.e., this isn't a functor issue? Yes you are barking up the wrong tree/no this isn't a Functor issue. > create just one generic plus that would handle both the plus :: Int -> Int -> Int and the plus2 :: MyNum -> MyNum -> MyNum. A Functor would need to be of the form of a parameterised type. That is, the `f` in `f a`. Neither `Int` nor `MyNum` are parameterised. You want a plus-like method that's polymorphic/generic across different Peano-like numeric representations. IOW you want an overloading. That's what typeclasses are for: > class PolyPlus a where polyPlus :: a -> a -> a > > instance PolyPlus Int where polyPlus = plus > > instance PolyPlus MyNum where polyPlus = plus2 (In those instances you could just put the definitions for those functions/no need to define them separately. BTW both those definitions are truly horrible non-idiomatic Haskell. Why are you trying to write C code in Haskell?) AntC -------------- next part -------------- An HTML attachment was scrubbed... URL: From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Mon Apr 5 12:03:27 2021 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Mon, 5 Apr 2021 13:03:27 +0100 Subject: [Haskell-cafe] Designing a "living will" for my packages on Hackage Message-ID: <20210405120327.GA9751@cloudinit-builder> # Introduction Over the past few weeks I've seen several instances of difficulty caused by unavailable or unknown package maintainers. I want to minimise the risk that difficulties arise for users of my packages should I ever become unavailable or uncontactable. I'd like to brainstorm policies for achieving this. My immediate goal is to find a suitable policy to apply to my own packages but I also have an indirect goal that the policy be suitable and appealing for others to apply to their packages on a voluntary basis. # What already exists? ## My packages already have backup maintainers I am already fortunate enough to have backup maintainers who have agreed to make bugfixes and dependency version bumps should I become unreachable: https://github.com/tomjaguarpaw/haskell-opaleye#backup-maintainers Two caveats: * Bugfixes and dependency version bumps are really the absolute minimum needed to ensure continuity of service. Much more is needed for the general health and reliability of a package. * It has been a long time since I contacted these maintainers and asked for their help in this matter. Perhaps if they were called upon now they would no longer have the time to fulfil this role. Perhaps I should ask the backup maintainers every 12 months whether they are willing to continue in the role. If not then that would give me the impetus to find other backup maintainers. ## Do established policies like this already exist? Perhaps effective backup maintainer policies already exist in the Haskell community or in other language communities? Does anyone know? I would be grateful to find out. # A simple proposal I'd like to propose something simple that avoids anything too legalistic or requires multilateral cooperation. For example, if I had three backup X, Y and Z, I could do the following: * Add these paragraphs to the README In the event that the maintainer has been unavailable and uncontactable for _three months_ then X is entitled to claim ownership of the package. In the event that the maintainer has been unavailable and uncontactable for _four months_ then Y is entitled to claim ownership of the package. In the event that the maintainer has been unavailable and uncontactable for _five months_ then Z is entitled to claim ownership of the package. "The maintainer has been unavailable and uncontactable" means that the maintainer has not made any commits to the repository nor has been contactable by email [or precise other conditions to be determined]. [Once a backup maintainer has claimed ownership they are entitled to do essentially whatever they like with the package, though I would choose them responsibly so that they continue maintaining the package in a sensible way!] * Give the backup maintainers write access to the package git repository and to the package Hackage entry, effective immediately I would choose the backup maintainers carefully so that I trust them not to take drastic actions with the package unless and until the conditions stated in the README are met. * Clarify with the backup maintainers every year that they are still willing to step in in case I become unavailable. If not I'll find replacements. ## Questions about the simple proposal * "Isn't this just the standard practice of having multiple maintainers?" Basically yes, but with the added benefit that the inheritance and ownership procedure is defined clearly. Hopefully that reassures users and developers about the future of the package. * "After 4 months have elapsed what stops X and Y trying to claim ownership at the same time?" Well, not really anything. The first to claim it gets it. But after three months have elapsed I suggest that X take ownership and change the policy, replacing her name with mine. I hope she also deems Y and Z to be good backup maintainers and keeps them in place! * "How many backup maintainers should there be?" I suppose that depends on the package. For my packages I'd probably like two or three. Having only one backup maintainer doesn't set my mind at ease. Four seems a bit too much! * "How long should elapse before claiming ownership is permitted?" Again that depends on the package. For my packages three months of my absence seems reasonable, plus one month per additional backup maintainer to give each a reasonable time to claim the package. ## What do you think? What do people think? Will this simple policy achieve my goal of achieving a smooth transfer of maintainership if I become available? Are there any caveats that make the policy unworkable or undesirable? Is there something about it that would make others averse to apply it to their packages? Is there some easy way to make it better? Cheers, Tom From borgauf at gmail.com Mon Apr 5 17:12:38 2021 From: borgauf at gmail.com (Galaxy Being) Date: Mon, 5 Apr 2021 12:12:38 -0500 Subject: [Haskell-cafe] A functor for two Peano systems In-Reply-To: References: Message-ID: Not sure what you mean by "Why are you trying to write C code in Haskell?" Please explain. This whole exercise is my attempt to translate *The Littler MLer* and its last chapter where they go into functors. The authors are old Scheme men. Maybe that's the problem? On Mon, Apr 5, 2021 at 6:53 AM Anthony Clayden wrote: > > Or am I barking up the completely wrong tree here, i.e., this isn't a > functor issue? > > Yes you are barking up the wrong tree/no this isn't a Functor issue. > > > create just one generic plus that would handle both the plus :: Int -> > Int -> Int and the plus2 :: MyNum -> MyNum -> MyNum. > > A Functor would need to be of the form of a parameterised type. That is, > the `f` in `f a`. Neither `Int` nor `MyNum` are parameterised. > > You want a plus-like method that's polymorphic/generic across different > Peano-like numeric representations. IOW you want an overloading. That's > what typeclasses are for: > > > class PolyPlus a where polyPlus :: a -> a -> a > > > > instance PolyPlus Int where polyPlus = plus > > > > instance PolyPlus MyNum where polyPlus = plus2 > > (In those instances you could just put the definitions for those > functions/no need to define them separately. BTW both those definitions are > truly horrible non-idiomatic Haskell. Why are you trying to write C code in > Haskell?) > > > AntC > > _______________________________________________ > 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 tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Mon Apr 5 17:35:19 2021 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Mon, 5 Apr 2021 18:35:19 +0100 Subject: [Haskell-cafe] A functor for two Peano systems In-Reply-To: References: Message-ID: <20210405173519.GE9751@cloudinit-builder> On Mon, Apr 05, 2021 at 12:17:23AM -0500, Galaxy Being wrote: > I'm just not understanding the concept of a functor in this context: I have > this [...] > It seems there should be just one plus, function that would handle both an > Int-based Peano and the MyNum-based Peano, not two. But in this definition > > fmap :: (a -> b) -> f a -> f b > > The (a -> b) should be "lifted" over the f a -> f b But I can't conceive of > how this should all fit together Are you perhaps confusing the ML notion of "functor" with the Haskell notion of "Functor" (which is just a particular typeclass)? In fact, Haskell's type classes as a whole are probably closer to ML's "functors" than Haskell's "Functor"s are! Tom From bob at redivi.com Mon Apr 5 17:36:07 2021 From: bob at redivi.com (Bob Ippolito) Date: Mon, 5 Apr 2021 10:36:07 -0700 Subject: [Haskell-cafe] A functor for two Peano systems In-Reply-To: References: Message-ID: I think the confusion here is that the word "functor" in ML means something very different than the word "functor" in Haskell. The concept of an ML-style functor exists in modern GHC as Backpack < https://gitlab.haskell.org/ghc/ghc/-/wikis/backpack> but it's not very commonly used (yet?) and it would probably be counterproductive to try and learn how to use that while also learning the basics of Haskell. Typeclasses are often used in Haskell in places where you'd use a Functor in ML, but they are not quite the same thing. On Mon, Apr 5, 2021 at 10:13 AM Galaxy Being wrote: > Not sure what you mean by "Why are you trying to write C code in Haskell?" > Please explain. This whole exercise is my attempt to translate *The > Littler MLer* and its last chapter where they go into functors. The > authors are old Scheme men. Maybe that's the problem? > > On Mon, Apr 5, 2021 at 6:53 AM Anthony Clayden < > anthony_clayden at clear.net.nz> wrote: > >> > Or am I barking up the completely wrong tree here, i.e., this isn't a >> functor issue? >> >> Yes you are barking up the wrong tree/no this isn't a Functor issue. >> >> > create just one generic plus that would handle both the plus :: Int -> >> Int -> Int and the plus2 :: MyNum -> MyNum -> MyNum. >> >> A Functor would need to be of the form of a parameterised type. That is, >> the `f` in `f a`. Neither `Int` nor `MyNum` are parameterised. >> >> You want a plus-like method that's polymorphic/generic across different >> Peano-like numeric representations. IOW you want an overloading. That's >> what typeclasses are for: >> >> > class PolyPlus a where polyPlus :: a -> a -> a >> > >> > instance PolyPlus Int where polyPlus = plus >> > >> > instance PolyPlus MyNum where polyPlus = plus2 >> >> (In those instances you could just put the definitions for those >> functions/no need to define them separately. BTW both those definitions are >> truly horrible non-idiomatic Haskell. Why are you trying to write C code in >> Haskell?) >> >> >> AntC >> >> _______________________________________________ >> 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 Mon Apr 5 19:41:29 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Mon, 5 Apr 2021 15:41:29 -0400 Subject: [Haskell-cafe] Designing a "living will" for my packages on Hackage In-Reply-To: <20210405120327.GA9751@cloudinit-builder> References: <20210405120327.GA9751@cloudinit-builder> Message-ID: I think having your personal policy, however phrased, in the readme or a linked document about maintainership / nmu bug fix stance life cycle is a great idea. I should note that this is actually articulating the *governance* of your project and there can’t really be a one size fit all template. Like, no commits for n months may be fine for a research effort or a stable lib that has no bugs, but is very different when long standing bugs that are reproducible and have real user impact around correctness / performance / new compiler compat. Note that what I mean is that ultimately: you are the current owner of your project. Governance here actually means you are explicitly publishing a pseudo (in that we arent lawyers here mostly ) legal document articulating a) what conditions you pre authorize an non maintainer update and or b) under what conditions you either designate certain folks should become designated co maintainers with various fall backs c) under what conditions you transfer associated intellectual property to a new entity or human for stewardship of your project This can get pretty thorny or nuanced , hence why various large enough prjects get a foundation organized around them often, but is never a bad thing to think about if you’re concerned. And def something we as a community should respect any such documents at least when they’re valid (, like having Alan Turing as your successor maintainer wouldn’t make sense or similar manner of stuff ) On Mon, Apr 5, 2021 at 8:05 AM Tom Ellis < tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk> wrote: > # Introduction > > Over the past few weeks I've seen several instances of difficulty > caused by unavailable or unknown package maintainers. I want to > minimise the risk that difficulties arise for users of my packages > should I ever become unavailable or uncontactable. > > I'd like to brainstorm policies for achieving this. My immediate goal > is to find a suitable policy to apply to my own packages but I also > have an indirect goal that the policy be suitable and appealing for > others to apply to their packages on a voluntary basis. > > > # What already exists? > > ## My packages already have backup maintainers > > I am already fortunate enough to have backup maintainers who have > agreed to make bugfixes and dependency version bumps should I become > unreachable: > > https://github.com/tomjaguarpaw/haskell-opaleye#backup-maintainers > > Two caveats: > > * Bugfixes and dependency version bumps are really the absolute > minimum needed to ensure continuity of service. Much more is > needed for the general health and reliability of a package. > > * It has been a long time since I contacted these maintainers and > asked for their help in this matter. Perhaps if they were called > upon now they would no longer have the time to fulfil this role. > Perhaps I should ask the backup maintainers every 12 months whether > they are willing to continue in the role. If not then that would > give me the impetus to find other backup maintainers. > > > ## Do established policies like this already exist? > > Perhaps effective backup maintainer policies already exist in the > Haskell community or in other language communities? Does anyone know? > I would be grateful to find out. > > > # A simple proposal > > I'd like to propose something simple that avoids anything too > legalistic or requires multilateral cooperation. For example, if I > had three backup X, Y and Z, I could do the following: > > > * Add these paragraphs to the README > > In the event that the maintainer has been unavailable and > uncontactable for _three months_ then X is entitled to claim > ownership of the package. > > In the event that the maintainer has been unavailable and > uncontactable for _four months_ then Y is entitled to claim > ownership of the package. > > In the event that the maintainer has been unavailable and > uncontactable for _five months_ then Z is entitled to claim > ownership of the package. > > "The maintainer has been unavailable and uncontactable" means that > the maintainer has not made any commits to the repository nor has > been contactable by email [or precise other conditions to be > determined]. > > [Once a backup maintainer has claimed ownership they are entitled to > do essentially whatever they like with the package, though I would > choose them responsibly so that they continue maintaining the > package in a sensible way!] > > * Give the backup maintainers write access to the package git > repository and to the package Hackage entry, effective immediately > > I would choose the backup maintainers carefully so that I trust them > not to take drastic actions with the package unless and until the > conditions stated in the README are met. > > * Clarify with the backup maintainers every year that they are still > willing to step in in case I become unavailable. > > If not I'll find replacements. > > > ## Questions about the simple proposal > > * "Isn't this just the standard practice of having multiple > maintainers?" > > Basically yes, but with the added benefit that the inheritance and > ownership procedure is defined clearly. Hopefully that reassures > users and developers about the future of the package. > > * "After 4 months have elapsed what stops X and Y trying to claim > ownership at the same time?" > > Well, not really anything. The first to claim it gets it. But after > three months have elapsed I suggest that X take ownership and change > the policy, replacing her name with mine. I hope she also deems Y > and Z to be good backup maintainers and keeps them in place! > > * "How many backup maintainers should there be?" > > I suppose that depends on the package. For my packages I'd probably > like two or three. Having only one backup maintainer doesn't set my > mind at ease. Four seems a bit too much! > > * "How long should elapse before claiming ownership is permitted?" > > Again that depends on the package. For my packages three months of > my absence seems reasonable, plus one month per additional backup > maintainer to give each a reasonable time to claim the package. > > > ## What do you think? > > What do people think? Will this simple policy achieve my goal of > achieving a smooth transfer of maintainership if I become available? > Are there any caveats that make the policy unworkable or undesirable? > Is there something about it that would make others averse to apply it > to their packages? Is there some easy way to make it better? > > > 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 olf at aatal-apotheke.de Mon Apr 5 19:57:23 2021 From: olf at aatal-apotheke.de (Olaf Klinke) Date: Mon, 5 Apr 2021 21:57:23 +0200 (CEST) Subject: [Haskell-cafe] A functor for two Peano systems Message-ID: You should try to 1. destill which basic operations are necessary on the types Int, MyNum to make your algorithms work, 2. write a type class for these operations, 3. write type class instances for Int and MyNum, 4. write a generic algorithm that works for all members your class, which ideally looks almost identical to the specific code you already have. I dare say this is a common way of reducing boilerplate code in Haskell. BTW, you should consider Numeric.Natural instead of Int for Peano addition. Cheers Olaf From rae at richarde.dev Mon Apr 5 22:04:27 2021 From: rae at richarde.dev (Richard Eisenberg) Date: Mon, 5 Apr 2021 22:04:27 +0000 Subject: [Haskell-cafe] Designing a "living will" for my packages on Hackage In-Reply-To: <20210405120327.GA9751@cloudinit-builder> References: <20210405120327.GA9751@cloudinit-builder> Message-ID: <010f0178a410cc02-6325a516-5b9c-433c-903d-359e7afd8f32-000000@us-east-2.amazonses.com> I think this is a fine framework for specifying what should happen with a package. Even better would be if e.g. Hackage had a field where you could specify this, so that it could be easily found by the Hackage maintainers. But maybe you don't need to interact with the Hackage maintainers because your backup maintainers already have commit rights? A truly wonderful solution would include a feature where e.g. Hackage emailed all backup maintainers for all packages once per year asking them to reconfirm their willingness to serve. And having this as a field in Hackage would help to encourage all packages to follow suit and would be a loud signal to potential adopters that you have anticipated their needs into the future. But it's best to maybe start small. Here's a possible way to get more widespread adoption: - Put this in your own packages' repos, perhaps in a living-will.md - Create a little badge icon, and display it in your README with a link to living-will.md. - Convince a few friends to do the same. Make sure they display the badge. - We programmers like badges. Others will want the badge, too. They will follow suit. - Demand for this feature on Hackage will grow. Hackage will implement. - Sleep well, knowing you have bettered the world. Richard > On Apr 5, 2021, at 8:03 AM, Tom Ellis wrote: > > # Introduction > > Over the past few weeks I've seen several instances of difficulty > caused by unavailable or unknown package maintainers. I want to > minimise the risk that difficulties arise for users of my packages > should I ever become unavailable or uncontactable. > > I'd like to brainstorm policies for achieving this. My immediate goal > is to find a suitable policy to apply to my own packages but I also > have an indirect goal that the policy be suitable and appealing for > others to apply to their packages on a voluntary basis. > > > # What already exists? > > ## My packages already have backup maintainers > > I am already fortunate enough to have backup maintainers who have > agreed to make bugfixes and dependency version bumps should I become > unreachable: > > https://github.com/tomjaguarpaw/haskell-opaleye#backup-maintainers > > Two caveats: > > * Bugfixes and dependency version bumps are really the absolute > minimum needed to ensure continuity of service. Much more is > needed for the general health and reliability of a package. > > * It has been a long time since I contacted these maintainers and > asked for their help in this matter. Perhaps if they were called > upon now they would no longer have the time to fulfil this role. > Perhaps I should ask the backup maintainers every 12 months whether > they are willing to continue in the role. If not then that would > give me the impetus to find other backup maintainers. > > > ## Do established policies like this already exist? > > Perhaps effective backup maintainer policies already exist in the > Haskell community or in other language communities? Does anyone know? > I would be grateful to find out. > > > # A simple proposal > > I'd like to propose something simple that avoids anything too > legalistic or requires multilateral cooperation. For example, if I > had three backup X, Y and Z, I could do the following: > > > * Add these paragraphs to the README > > In the event that the maintainer has been unavailable and > uncontactable for _three months_ then X is entitled to claim > ownership of the package. > > In the event that the maintainer has been unavailable and > uncontactable for _four months_ then Y is entitled to claim > ownership of the package. > > In the event that the maintainer has been unavailable and > uncontactable for _five months_ then Z is entitled to claim > ownership of the package. > > "The maintainer has been unavailable and uncontactable" means that > the maintainer has not made any commits to the repository nor has > been contactable by email [or precise other conditions to be > determined]. > > [Once a backup maintainer has claimed ownership they are entitled to > do essentially whatever they like with the package, though I would > choose them responsibly so that they continue maintaining the > package in a sensible way!] > > * Give the backup maintainers write access to the package git > repository and to the package Hackage entry, effective immediately > > I would choose the backup maintainers carefully so that I trust them > not to take drastic actions with the package unless and until the > conditions stated in the README are met. > > * Clarify with the backup maintainers every year that they are still > willing to step in in case I become unavailable. > > If not I'll find replacements. > > > ## Questions about the simple proposal > > * "Isn't this just the standard practice of having multiple > maintainers?" > > Basically yes, but with the added benefit that the inheritance and > ownership procedure is defined clearly. Hopefully that reassures > users and developers about the future of the package. > > * "After 4 months have elapsed what stops X and Y trying to claim > ownership at the same time?" > > Well, not really anything. The first to claim it gets it. But after > three months have elapsed I suggest that X take ownership and change > the policy, replacing her name with mine. I hope she also deems Y > and Z to be good backup maintainers and keeps them in place! > > * "How many backup maintainers should there be?" > > I suppose that depends on the package. For my packages I'd probably > like two or three. Having only one backup maintainer doesn't set my > mind at ease. Four seems a bit too much! > > * "How long should elapse before claiming ownership is permitted?" > > Again that depends on the package. For my packages three months of > my absence seems reasonable, plus one month per additional backup > maintainer to give each a reasonable time to claim the package. > > > ## What do you think? > > What do people think? Will this simple policy achieve my goal of > achieving a smooth transfer of maintainership if I become available? > Are there any caveats that make the policy unworkable or undesirable? > Is there something about it that would make others averse to apply it > to their packages? Is there some easy way to make it better? > > > 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. From anthony_clayden at clear.net.nz Mon Apr 5 23:13:49 2021 From: anthony_clayden at clear.net.nz (Anthony Clayden) Date: Tue, 6 Apr 2021 11:13:49 +1200 Subject: [Haskell-cafe] A functor for two Peano systems Message-ID: > This whole exercise is my attempt to translate *The Littler MLer* and its last chapter where they go into functors. That approach isn't working for you, and it's trying the patience of the cafe. (These are sub-beginner level q's, please use the Beginners' forum. And I'd forgotten that's what you're doing. Your first post in this thread should have said you're talking about ML functors. https://stackoverflow.com/questions/2030863/in-functional-programming-what-is-a-functor#:~:text=In%20the%20ML%20family%20of,programmers%20have%20difficulty%20with%20it. says "most beginning programmers have difficulty with [functors]".) I suggest you first go through a Haskell tutorial, and get your knowledge secure of idiomatic Haskell. Even so, I just don't believe you're coming from idiomatic ML. Unless 'The Little MLer' is giving it as obfuscated code, and the objective is to de-obfuscate it. I'd code your `plus2` with pattern-matching: > plus2 :: MyNum -> MyNum -> MyNum > plus2 MNZero m = m > plus2 (OneMoreThan n') m = OneMoreThan $ plus2 n' m Your test for `(x == MNZero)` inside helper function `pCessor` is useless: flow-of-control doesn't take the outer `else` branch unless `x` (i.e. `n`) is _not_ equal `MNZero`. Similar redundant code in the case for `Int`. But that has bigger problems, as Olaf points out: `Int`s can be negative. So if `plus` is called with a negative `n`, it'll call `pCessor` repeatedly until stack overflow (or numeric underflow). AntC -------------- next part -------------- An HTML attachment was scrubbed... URL: From gruen0aermel at gmail.com Mon Apr 5 23:36:41 2021 From: gruen0aermel at gmail.com (Aaron VonderHaar) Date: Mon, 5 Apr 2021 16:36:41 -0700 Subject: [Haskell-cafe] A functor for two Peano systems In-Reply-To: References: Message-ID: > That approach isn't working for you, and it's trying the patience of the cafe. (These are sub-beginner level q's, please use the Beginners' forum....) According to https://www.haskell.org/mailing-lists/ , the purpose of haskell-cafe is "General Haskell questions; extended discussions. Forum in which it’s acceptable to ask anything, no matter how naive, and get polite replies." The OP's questions and efforts are more than appropriate here, and they should expect no less than polite, if not helpful, responses here. AntC, your replies are not at all polite, and you seem to be misinformed of the purpose of this mailing list. Please help us maintain a more appropriate environment here in the future, and I would ask the haskell-cafe moderators to assist in this as well. If you want to direct someone to a different forum, please do so politely and without insulting them. --Aaron V. On Mon, Apr 5, 2021 at 4:19 PM Anthony Clayden wrote: > > This whole exercise is my attempt to translate *The Littler MLer* and > its last chapter where they go into functors. > > That approach isn't working for you, and it's trying the patience of the > cafe. (These are sub-beginner level q's, please use the Beginners' forum. > And I'd forgotten that's what you're doing. Your first post in this thread > should have said you're talking about ML functors. > https://stackoverflow.com/questions/2030863/in-functional-programming-what-is-a-functor#:~:text=In%20the%20ML%20family%20of,programmers%20have%20difficulty%20with%20it. says > "most beginning programmers have difficulty with [functors]".) > > I suggest you first go through a Haskell tutorial, and get your knowledge > secure of idiomatic Haskell. Even so, I just don't believe you're coming > from idiomatic ML. Unless 'The Little MLer' is giving it as obfuscated > code, and the objective is to de-obfuscate it. > > I'd code your `plus2` with pattern-matching: > > > plus2 :: MyNum -> MyNum -> MyNum > > plus2 MNZero m = m > > plus2 (OneMoreThan n') m = OneMoreThan $ plus2 n' m > > Your test for `(x == MNZero)` inside helper function `pCessor` is useless: > flow-of-control doesn't take the outer `else` branch unless `x` (i.e. `n`) > is _not_ equal `MNZero`. > > Similar redundant code in the case for `Int`. But that has bigger > problems, as Olaf points out: `Int`s can be negative. So if `plus` is > called with a negative `n`, it'll call `pCessor` repeatedly until stack > overflow (or numeric underflow). > > AntC > _______________________________________________ > 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 igormoreno at gmail.com Tue Apr 6 00:32:59 2021 From: igormoreno at gmail.com (Igor Moreno Santos) Date: Tue, 6 Apr 2021 02:32:59 +0200 Subject: [Haskell-cafe] Looking for a toy imperative language implementation in Haskell for research Message-ID: Hi, I'm looking for a toy imperative language implementation in Haskell for research purposes. I imagine something like the language of arithmetic expressions from TAPL ch. 3 augmented with - while-loop (so the CFG has loops) - blocks (sequence of statements to put inside loops and conditionals) - assignment (otherwise we can't show any effects from sequences) I think there's probably nothing exactly like that so we might end up doing it ourselves but maybe there's already something out there. Thank you in advance. Regards, Igor Moreno -------------- next part -------------- An HTML attachment was scrubbed... URL: From jclites at mac.com Tue Apr 6 01:54:36 2021 From: jclites at mac.com (Jeff Clites) Date: Mon, 5 Apr 2021 18:54:36 -0700 Subject: [Haskell-cafe] Looking for a toy imperative language implementation in Haskell for research In-Reply-To: References: Message-ID: <3C94198A-0CDE-450F-A31C-FE120D0375B7@mac.com> I wonder if something from The Programming Languages Zoo would be helpful: https://plzoo.andrej.com/ It’s in OCaml but might be a good starting point. Jeff > On Apr 5, 2021, at 5:32 PM, Igor Moreno Santos wrote: > > Hi, > > I'm looking for a toy imperative language implementation in Haskell for research purposes. I imagine something like the language of arithmetic expressions from TAPL ch. 3 augmented with > - while-loop (so the CFG has loops) > - blocks (sequence of statements to put inside loops and conditionals) > - assignment (otherwise we can't show any effects from sequences) > > I think there's probably nothing exactly like that so we might end up doing it ourselves but maybe there's already something out there. > > Thank you in advance. > > Regards, > Igor Moreno > > > _______________________________________________ > 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 byorgey at gmail.com Tue Apr 6 02:27:48 2021 From: byorgey at gmail.com (Brent Yorgey) Date: Mon, 5 Apr 2021 21:27:48 -0500 Subject: [Haskell-cafe] Looking for a toy imperative language implementation in Haskell for research In-Reply-To: References: Message-ID: I have an implementation of a language that has all the features you mention (ints + booleans, assignment, arithmetic and logic operators, if statements, while and repeat loops, blocks), which I have used in my Programming Languages class. It also has a typechecker. It is interpreted --- not sure if that is OK or if you are looking for something with a compiler. I would be happy to send it to you privately off-list if it sounds like it might fit the bill. -Brent On Mon, Apr 5, 2021 at 7:34 PM Igor Moreno Santos wrote: > Hi, > > I'm looking for a toy imperative language implementation in Haskell for > research purposes. I imagine something like the language of arithmetic > expressions from TAPL ch. 3 augmented with > - while-loop (so the CFG has loops) > - blocks (sequence of statements to put inside loops and conditionals) > - assignment (otherwise we can't show any effects from sequences) > > I think there's probably nothing exactly like that so we might end up > doing it ourselves but maybe there's already something out there. > > Thank you in advance. > > Regards, > Igor Moreno > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From rae at richarde.dev Tue Apr 6 02:30:43 2021 From: rae at richarde.dev (Richard Eisenberg) Date: Tue, 6 Apr 2021 02:30:43 +0000 Subject: [Haskell-cafe] Get proof of injectivity for an injective type family In-Reply-To: References: Message-ID: <010f0178a50493fa-8e7e17de-ba91-4a62-a89f-05c10e9fe263-000000@us-east-2.amazonses.com> No. Injective type families are solely a type-inference mechanism. There are no proofs or other evidence. Figuring out how to get this right would be a significant research project, I'm afraid. Richard > On Apr 3, 2021, at 2:59 AM, Andreas Källberg wrote: > > Is there any way to get hold of a proof of injectivity for an injective type family? > In other words, given this type family > > type family F a = b | b -> a > > can I get the term > > fInj :: F a ~ F b => (a ~ b => r) -> r > > in any way (without using unsafeCoerce)?_______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. From compl.yue at icloud.com Tue Apr 6 05:10:52 2021 From: compl.yue at icloud.com (Compl Yue) Date: Tue, 06 Apr 2021 13:10:52 +0800 Subject: [Haskell-cafe] Looking for a toy imperative language implementationin Haskell for research In-Reply-To: References: Message-ID: <1617685433423.nvtgtfa1ql4lgq52cp3bbuzh@android.mail.163.com> https://github.com/e-wrks/edh It's dynamically typed, not sure you want that, and maybe overkill wrt features. Pending 0.3 release, which has a lot changed since 0.1 and 0.2. The latest branch may appear a bit more stable than the 0.3 branch, yet unrelease anyway. On 04/06/2021 08:32, Igor Moreno Santos wrote: Hi, I'm looking for a toy imperative language implementation in Haskell for research purposes. I imagine something like the language of arithmetic expressions from TAPL ch. 3 augmented with - while-loop (so the CFG has loops) - blocks (sequence of statements to put inside loops and conditionals) - assignment (otherwise we can't show any effects from sequences) I think there's probably nothing exactly like that so we might end up doing it ourselves but maybe there's already something out there. Thank you in advance. Regards, Igor Moreno _______________________________________________ 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 godzbanebane at gmail.com Tue Apr 6 07:08:31 2021 From: godzbanebane at gmail.com (Georgi Lyubenov) Date: Tue, 6 Apr 2021 10:08:31 +0300 Subject: [Haskell-cafe] A functor for two Peano systems In-Reply-To: References: Message-ID: Adding to what Aaron said, I would also request that you not speak for others (or at least not for me): > it's trying the patience of the cafe would be better rephrased as > it's trying my patience ======= Georgi -------------- next part -------------- An HTML attachment was scrubbed... URL: From tanuki at gmail.com Tue Apr 6 07:49:55 2021 From: tanuki at gmail.com (Akhra Gannon) Date: Tue, 6 Apr 2021 00:49:55 -0700 Subject: [Haskell-cafe] A functor for two Peano systems In-Reply-To: References: Message-ID: Emphatically co-signed, and I would like to add that this is far from the first time I've seen this sort of aggressive, dismissive, adversarial behavior from AntC. Usually it's in discussion of core libraries and extensions and I've held my tongue because there are committees in charge of such things; if they find his input outweighs his tone, so be it. But this is entry-level community gatekeeping. Responding to innocent questions with derision will drive many new and curious Haskellers away. Worse, the ones who stay are more likely to echo that abuse down the line. This is how communities become and remain toxic. So I feel a duty to step up and say, this is thoroughly unacceptable here. On Tue, Apr 6, 2021, 12:09 AM Georgi Lyubenov wrote: > Adding to what Aaron said, I would also request that you not speak for > others (or at least not for me): > > > it's trying the patience of the cafe would be better rephrased as > it's > trying my patience > ======= > Georgi > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From matteo at confscience.com Tue Apr 6 09:25:25 2021 From: matteo at confscience.com (matteo at confscience.com) Date: Tue, 6 Apr 2021 11:25:25 +0200 Subject: [Haskell-cafe] International Conference on Recent Theories and Applications in Transportation and Mobility - (RTATM 2021) Prague Message-ID: <004101d72ac6$c6d04c70$5470e550$@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/ 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 20, 2021 (extended) - 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 compl.yue at icloud.com Tue Apr 6 11:12:51 2021 From: compl.yue at icloud.com (YueCompl) Date: Tue, 6 Apr 2021 19:12:51 +0800 Subject: [Haskell-cafe] How to ensure optimization for large immutable vectors to be shared w.r.t. Referential Transparency Message-ID: <32447B11-A587-41D3-8617-30132561AF7F@icloud.com> Hello Cafe and respected GHC Devs, I would like to ensure some immutable vectors (can be quite large) are always shared instead of copied, and I think that should be straight forward w.r.t. referential transparency we enjoy. In an attempt to determine whether two immutable vectors can be treated as the same one to enable specific optimizations for that case, I tried to use ST to determine their respective backing foreign ptrs for comparison. But appears it can be copied when wrapped in a newtype, I wonder why it is the case, and how to avoid the copy? Here's my minimum reproducible snippet: ```hs λ> :set -XBangPatterns λ> λ> :set -package vector package flags have changed, resetting and loading new packages... λ> λ> import Prelude λ> λ> import Control.Monad.ST λ> import qualified Data.Vector.Storable as VS λ> λ> :{ λ| λ| newtype SomeVector = SomeVector (VS.Vector Int) λ| λ| isSameVector :: SomeVector -> SomeVector -> Bool λ| isSameVector (SomeVector !x) (SomeVector !y) = runST $ do λ| mx@(VS.MVector !x'offset !x'fp) <- VS.unsafeThaw x λ| my@(VS.MVector !y'offset !y'fp) <- VS.unsafeThaw y λ| _ <- VS.unsafeFreeze mx λ| _ <- VS.unsafeFreeze my λ| return $ x'offset == y'offset && x'fp == y'fp λ| λ| :} λ> λ> let !v = VS.fromList [3,2,5] in isSameVector (SomeVector v) (SomeVector v) False λ> λ> let !v = SomeVector (VS.fromList [3,2,5]) in isSameVector v v True λ> ``` Thanks with best regards, Compl -------------- next part -------------- An HTML attachment was scrubbed... URL: From lemming at henning-thielemann.de Tue Apr 6 12:00:07 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Tue, 6 Apr 2021 14:00:07 +0200 (CEST) Subject: [Haskell-cafe] How to ensure optimization for large immutable vectors to be shared w.r.t. Referential Transparency In-Reply-To: <32447B11-A587-41D3-8617-30132561AF7F@icloud.com> References: <32447B11-A587-41D3-8617-30132561AF7F@icloud.com> Message-ID: On Tue, 6 Apr 2021, YueCompl via Haskell-Cafe wrote: > In an attempt to determine whether two immutable vectors can be treated > as the same one to enable specific optimizations for that case, I tried > to use ST to determine their respective backing foreign ptrs for > comparison. But appears it can be copied when wrapped in a newtype, I > wonder why it is the case, and how to avoid the copy? You compare the ForeignPtrs of the mutable vectors. What about comparing the ForeignPtrs of the original immutable vectors? From compl.yue at icloud.com Tue Apr 6 12:29:19 2021 From: compl.yue at icloud.com (YueCompl) Date: Tue, 6 Apr 2021 20:29:19 +0800 Subject: [Haskell-cafe] How to ensure optimization for large immutable vectors to be shared w.r.t. Referential Transparency In-Reply-To: References: <32447B11-A587-41D3-8617-30132561AF7F@icloud.com> Message-ID: <56867838-1078-4D85-BEA2-DAC193196C43@icloud.com> Thanks, it's a good idea. Unfortunately the result remains, making me even more curious. ```hs λ> :set -XBangPatterns λ> λ> :set -package vector package flags have changed, resetting and loading new packages... λ> λ> import Prelude λ> λ> import Control.Monad.ST λ> import qualified Data.Vector.Storable as VS λ> λ> :{ λ| λ| newtype SomeVector = SomeVector (VS.Vector Int) λ| λ| isSameVector :: SomeVector -> SomeVector -> Bool λ| isSameVector (SomeVector !x) (SomeVector !y) = λ| x'offset == y'offset && x'fp == y'fp λ| where λ| (x'fp, x'offset, _x'len) = VS.unsafeToForeignPtr x λ| (y'fp, y'offset, _y'len) = VS.unsafeToForeignPtr y λ| :} λ> λ> let !v = VS.fromList [5..200000] in isSameVector (SomeVector v) (SomeVector v) False λ> λ> let !v = SomeVector (VS.fromList [3,2,5]) in isSameVector v v True λ> ``` > On 2021-04-06, at 20:00, Henning Thielemann wrote: > > > On Tue, 6 Apr 2021, YueCompl via Haskell-Cafe wrote: > >> In an attempt to determine whether two immutable vectors can be treated as the same one to enable specific optimizations for that case, I tried to use ST to determine their respective backing foreign ptrs for comparison. But appears it can be copied when wrapped in a newtype, I wonder why it is the case, and how to avoid the copy? > > You compare the ForeignPtrs of the mutable vectors. What about comparing the ForeignPtrs of the original immutable vectors? -------------- next part -------------- An HTML attachment was scrubbed... URL: From lemming at henning-thielemann.de Tue Apr 6 12:34:25 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Tue, 6 Apr 2021 14:34:25 +0200 (CEST) Subject: [Haskell-cafe] How to ensure optimization for large immutable vectors to be shared w.r.t. Referential Transparency In-Reply-To: <56867838-1078-4D85-BEA2-DAC193196C43@icloud.com> References: <32447B11-A587-41D3-8617-30132561AF7F@icloud.com> <56867838-1078-4D85-BEA2-DAC193196C43@icloud.com> Message-ID: <8955c0f6-c6ac-8c9-22c5-56b47c933b1@henning-thielemann.de> On Tue, 6 Apr 2021, YueCompl wrote: > Thanks, it's a good idea. Unfortunately the result remains, making me even more curious. > ```hs > λ> :set -XBangPatterns > λ>  > λ> :set -package vector > package flags have changed, resetting and loading new packages... > λ>  > λ> import Prelude > λ>  > λ> import Control.Monad.ST > λ> import qualified Data.Vector.Storable as VS > λ>  > λ> :{ > λ|  > λ| newtype SomeVector = SomeVector (VS.Vector Int) > λ|  > λ| isSameVector :: SomeVector -> SomeVector -> Bool > λ| isSameVector (SomeVector !x) (SomeVector !y) =  > λ|   x'offset == y'offset && x'fp == y'fp > λ|  where > λ|   (x'fp, x'offset, _x'len) = VS.unsafeToForeignPtr x > λ|   (y'fp, y'offset, _y'len) = VS.unsafeToForeignPtr y > λ| :} > λ>  > λ> let !v = VS.fromList [5..200000] in isSameVector (SomeVector v) (SomeVector v) > False What happens for [3,2,5]? > λ>  > λ> let !v = SomeVector (VS.fromList [3,2,5]) in isSameVector v v > True > λ>  > ``` From compl.yue at icloud.com Tue Apr 6 12:41:33 2021 From: compl.yue at icloud.com (YueCompl) Date: Tue, 6 Apr 2021 20:41:33 +0800 Subject: [Haskell-cafe] How to ensure optimization for large immutable vectors to be shared w.r.t. Referential Transparency In-Reply-To: <8955c0f6-c6ac-8c9-22c5-56b47c933b1@henning-thielemann.de> References: <32447B11-A587-41D3-8617-30132561AF7F@icloud.com> <56867838-1078-4D85-BEA2-DAC193196C43@icloud.com> <8955c0f6-c6ac-8c9-22c5-56b47c933b1@henning-thielemann.de> Message-ID: ```hs λ> let !v = VS.fromList [3,2,5] in isSameVector (SomeVector v) (SomeVector v) False λ> λ> let !v = SomeVector (VS.fromList [3,2,5]) in isSameVector v v True λ> ``` > On 2021-04-06, at 20:34, Henning Thielemann wrote: > > > On Tue, 6 Apr 2021, YueCompl wrote: > >> Thanks, it's a good idea. Unfortunately the result remains, making me even more curious. >> ```hs >> λ> :set -XBangPatterns >> λ> >> λ> :set -package vector >> package flags have changed, resetting and loading new packages... >> λ> >> λ> import Prelude >> λ> >> λ> import Control.Monad.ST >> λ> import qualified Data.Vector.Storable as VS >> λ> >> λ> :{ >> λ| >> λ| newtype SomeVector = SomeVector (VS.Vector Int) >> λ| >> λ| isSameVector :: SomeVector -> SomeVector -> Bool >> λ| isSameVector (SomeVector !x) (SomeVector !y) = >> λ| x'offset == y'offset && x'fp == y'fp >> λ| where >> λ| (x'fp, x'offset, _x'len) = VS.unsafeToForeignPtr x >> λ| (y'fp, y'offset, _y'len) = VS.unsafeToForeignPtr y >> λ| :} >> λ> >> λ> let !v = VS.fromList [5..200000] in isSameVector (SomeVector v) (SomeVector v) >> False > > What happens for [3,2,5]? > > >> λ> >> λ> let !v = SomeVector (VS.fromList [3,2,5]) in isSameVector v v >> True >> λ> >> ``` -------------- next part -------------- An HTML attachment was scrubbed... URL: From lemming at henning-thielemann.de Tue Apr 6 12:50:20 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Tue, 6 Apr 2021 14:50:20 +0200 (CEST) Subject: [Haskell-cafe] How to ensure optimization for large immutable vectors to be shared w.r.t. Referential Transparency In-Reply-To: References: <32447B11-A587-41D3-8617-30132561AF7F@icloud.com> <56867838-1078-4D85-BEA2-DAC193196C43@icloud.com> <8955c0f6-c6ac-8c9-22c5-56b47c933b1@henning-thielemann.de> Message-ID: <3d6175-7b8e-5779-5b69-6def28ed8ba@henning-thielemann.de> On Tue, 6 Apr 2021, YueCompl wrote: > ```hsλ> let !v = VS.fromList [3,2,5] in isSameVector (SomeVector v) (SomeVector v) > False > λ>  > λ> let !v = SomeVector (VS.fromList [3,2,5]) in isSameVector v v > True > λ>  > ``` Then I have no idea. Maybe ghc-heap-view/ghc-vis can reveal the mystery. https://github.com/nomeata/haskell-bytes-bobkonf2021 From ietf-dane at dukhovni.org Tue Apr 6 13:51:30 2021 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Tue, 6 Apr 2021 09:51:30 -0400 Subject: [Haskell-cafe] How to ensure optimization for large immutable vectors to be shared w.r.t. Referential Transparency In-Reply-To: <32447B11-A587-41D3-8617-30132561AF7F@icloud.com> References: <32447B11-A587-41D3-8617-30132561AF7F@icloud.com> Message-ID: On Tue, Apr 06, 2021 at 07:12:51PM +0800, YueCompl via ghc-devs wrote: > λ> import Control.Monad.ST > λ> import qualified Data.Vector.Storable as VS > λ> > λ> :{ > λ| > λ| newtype SomeVector = SomeVector (VS.Vector Int) > λ| > λ| isSameVector :: SomeVector -> SomeVector -> Bool > λ| isSameVector (SomeVector !x) (SomeVector !y) = runST $ do > λ| mx@(VS.MVector !x'offset !x'fp) <- VS.unsafeThaw x > λ| my@(VS.MVector !y'offset !y'fp) <- VS.unsafeThaw y > λ| _ <- VS.unsafeFreeze mx > λ| _ <- VS.unsafeFreeze my > λ| return $ x'offset == y'offset && x'fp == y'fp > λ| > λ| :} > λ> > λ> let !v = VS.fromList [3,2,5] in isSameVector (SomeVector v) (SomeVector v) > False > λ> > λ> let !v = SomeVector (VS.fromList [3,2,5]) in isSameVector v v > True In GHCi, but not in compiled programs, by default the `NoMonomorphismRestriction` extension is enabled. If I compile your code with that restriction, I can reproduce your results (the values are not shared). If I either skip the extension, or add an explicit type annotation to for the vector, then the values are shared. {-# LANGUAGE BangPatterns #-} {-# LANGUAGE NoMonomorphismRestriction #-} import Control.Monad.ST import qualified Data.Vector.Storable as VS newtype SomeVector = SomeVector (VS.Vector Int) isSameVector :: SomeVector -> SomeVector -> Bool isSameVector (SomeVector !x) (SomeVector !y) = runST $ do mx@(VS.MVector !x'offset !x'fp) <- VS.unsafeThaw x my@(VS.MVector !y'offset !y'fp) <- VS.unsafeThaw y _ <- VS.unsafeFreeze mx _ <- VS.unsafeFreeze my return $ x'offset == y'offset && x'fp == y'fp main :: IO () main = let !v = VS.fromList [0..1023] -- :: VS.Vector Int in print $ isSameVector (SomeVector v) (SomeVector v) Since newtypes are always strict in their argument, I don't think the BangPattern does what you'd like it to do, it just makes "main" strict in v. As defined with `NoMonomorphismRestriction` v is a polymorphic function, and I guess it is specialised at the call site. -- Viktor. From compl.yue at icloud.com Tue Apr 6 13:51:29 2021 From: compl.yue at icloud.com (YueCompl) Date: Tue, 6 Apr 2021 21:51:29 +0800 Subject: [Haskell-cafe] How to ensure optimization for large immutable vectors to be shared w.r.t. Referential Transparency In-Reply-To: <3d6175-7b8e-5779-5b69-6def28ed8ba@henning-thielemann.de> References: <32447B11-A587-41D3-8617-30132561AF7F@icloud.com> <56867838-1078-4D85-BEA2-DAC193196C43@icloud.com> <8955c0f6-c6ac-8c9-22c5-56b47c933b1@henning-thielemann.de> <3d6175-7b8e-5779-5b69-6def28ed8ba@henning-thielemann.de> Message-ID: Appears it'd work as expected when the immutable vector is originally created from foreign ptr, I think it'll work for my cases. (Though it's still strangely unexpected for ad hoc immutable vectors unshared when wrapped.) ```hs λ> :set -XBangPatterns λ> λ> :set -package vector package flags have changed, resetting and loading new packages... λ> λ> import Prelude λ> λ> import Foreign.Marshal.Alloc λ> import Foreign.Storable λ> import Foreign.ForeignPtr λ> λ> import qualified Data.Vector.Storable as VS λ> λ> :{ λ| λ| data SomeVector = SomeVector (VS.Vector Int) λ| λ| isSameVector :: Storable a => VS.Vector a -> VS.Vector a -> Bool λ| isSameVector !x !y = λ| x'offset == y'offset && x'fp == y'fp λ| where λ| (x'fp, x'offset, _x'len) = VS.unsafeToForeignPtr x λ| (y'fp, y'offset, _y'len) = VS.unsafeToForeignPtr y λ| λ| isSame :: SomeVector -> SomeVector -> Bool λ| isSame (SomeVector !x) (SomeVector !y) = isSameVector x y λ| λ| :} λ> λ> let !v = VS.fromList [3,2,5] in isSame (SomeVector v) (SomeVector v) False λ> λ> let !v = SomeVector (VS.fromList [3,2,5]) in isSame v v True λ> λ> λ> (fp :: ForeignPtr Int) <- mallocBytes 256 >>= newForeignPtr_ λ> let !v = VS.unsafeFromForeignPtr fp 0 32 λ| λ> isSame (SomeVector v) (SomeVector v) True λ> ``` > On 2021-04-06, at 20:50, Henning Thielemann wrote: > > > On Tue, 6 Apr 2021, YueCompl wrote: > >> ```hsλ> let !v = VS.fromList [3,2,5] in isSameVector (SomeVector v) (SomeVector v) >> False >> λ> >> λ> let !v = SomeVector (VS.fromList [3,2,5]) in isSameVector v v >> True >> λ> >> ``` > > Then I have no idea. > > Maybe ghc-heap-view/ghc-vis can reveal the mystery. > > https://github.com/nomeata/haskell-bytes-bobkonf2021 -------------- next part -------------- An HTML attachment was scrubbed... URL: From ietf-dane at dukhovni.org Tue Apr 6 14:00:33 2021 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Tue, 6 Apr 2021 10:00:33 -0400 Subject: [Haskell-cafe] How to ensure optimization for large immutable vectors to be shared w.r.t. Referential Transparency In-Reply-To: References: <32447B11-A587-41D3-8617-30132561AF7F@icloud.com> Message-ID: On Tue, Apr 06, 2021 at 09:51:30AM -0400, Viktor Dukhovni wrote: > Since newtypes are always strict in their argument, I don't think the > BangPattern does what you'd like it to do, it just makes "main" strict > in v. As defined with `NoMonomorphismRestriction` v is a polymorphic > function, and I guess it is specialised at the call site. The below variant makes the issue even more clear for me: {-# LANGUAGE BangPatterns #-} {-# LANGUAGE NoMonomorphismRestriction #-} import Control.Monad.ST import qualified Data.Vector.Storable as VS newtype SomeVector = SomeVector (VS.Vector Int) isSameVector :: SomeVector -> SomeVector -> Bool isSameVector (SomeVector !x) (SomeVector !y) = runST $ do mx@(VS.MVector !x'offset !x'fp) <- VS.unsafeThaw x my@(VS.MVector !y'offset !y'fp) <- VS.unsafeThaw y _ <- VS.unsafeFreeze mx _ <- VS.unsafeFreeze my return $ x'offset == y'offset && x'fp == y'fp -- makev :: VS.Vector Int makev = VS.fromList [0..1023] main :: IO () main = let v = makev in print $ v `seq` isSameVector (SomeVector v) (SomeVector v) With `NoMonomorphismRestriction` it fails to compile: /tmp/vec.hs:22:17: error: • Ambiguous type variable ‘a0’ arising from a use of ‘v’ prevents the constraint ‘(VS.Storable a0)’ from being solved. Probable fix: use a type annotation to specify what ‘a0’ should be. These potential instances exist: instance VS.Storable () -- Defined in ‘Foreign.Storable’ instance VS.Storable Bool -- Defined in ‘Foreign.Storable’ instance VS.Storable Char -- Defined in ‘Foreign.Storable’ ...plus four others ...plus 13 instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In the first argument of ‘seq’, namely ‘v’ In the second argument of ‘($)’, namely ‘v `seq` isSameVector (SomeVector v) (SomeVector v)’ In the expression: print $ v `seq` isSameVector (SomeVector v) (SomeVector v) | 22 | in print $ v `seq` isSameVector (SomeVector v) (SomeVector v) | ^ With the default `MonomorphismRestriction`, it compiles and reports that the vectors are shared. -- Viktor. From compl.yue at icloud.com Tue Apr 6 14:19:34 2021 From: compl.yue at icloud.com (YueCompl) Date: Tue, 6 Apr 2021 22:19:34 +0800 Subject: [Haskell-cafe] How to ensure optimization for large immutable vectors to be shared w.r.t. Referential Transparency In-Reply-To: References: <32447B11-A587-41D3-8617-30132561AF7F@icloud.com> Message-ID: <0F37F11D-D3D1-4EB3-935C-89CDA1816B1D@icloud.com> Thanks very much for the diagnostic and explanation! I was wrong in assuming the `in isSameVector (SomeVector v) (SomeVector v)` part is enough to have type of v in `let !v = VS.fromList [3,2,5]` inferred as monomorphic, totally unaware about "NoMonomorphismRestriction" before, I've learned it today :D > On 2021-04-06, at 21:51, Viktor Dukhovni wrote: > > On Tue, Apr 06, 2021 at 07:12:51PM +0800, YueCompl via ghc-devs wrote: > >> λ> import Control.Monad.ST >> λ> import qualified Data.Vector.Storable as VS >> λ> >> λ> :{ >> λ| >> λ| newtype SomeVector = SomeVector (VS.Vector Int) >> λ| >> λ| isSameVector :: SomeVector -> SomeVector -> Bool >> λ| isSameVector (SomeVector !x) (SomeVector !y) = runST $ do >> λ| mx@(VS.MVector !x'offset !x'fp) <- VS.unsafeThaw x >> λ| my@(VS.MVector !y'offset !y'fp) <- VS.unsafeThaw y >> λ| _ <- VS.unsafeFreeze mx >> λ| _ <- VS.unsafeFreeze my >> λ| return $ x'offset == y'offset && x'fp == y'fp >> λ| >> λ| :} >> λ> >> λ> let !v = VS.fromList [3,2,5] in isSameVector (SomeVector v) (SomeVector v) >> False >> λ> >> λ> let !v = SomeVector (VS.fromList [3,2,5]) in isSameVector v v >> True > > In GHCi, but not in compiled programs, by default the > `NoMonomorphismRestriction` extension is enabled. If I compile your > code with that restriction, I can reproduce your results (the values are > not shared). > > If I either skip the extension, or add an explicit type annotation to > for the vector, then the values are shared. > > {-# LANGUAGE BangPatterns #-} > {-# LANGUAGE NoMonomorphismRestriction #-} > import Control.Monad.ST > import qualified Data.Vector.Storable as VS > > newtype SomeVector = SomeVector (VS.Vector Int) > > isSameVector :: SomeVector -> SomeVector -> Bool > isSameVector (SomeVector !x) (SomeVector !y) = runST $ do > mx@(VS.MVector !x'offset !x'fp) <- VS.unsafeThaw x > my@(VS.MVector !y'offset !y'fp) <- VS.unsafeThaw y > _ <- VS.unsafeFreeze mx > _ <- VS.unsafeFreeze my > return $ x'offset == y'offset && x'fp == y'fp > > main :: IO () > main = > let !v = VS.fromList [0..1023] -- :: VS.Vector Int > in print $ isSameVector (SomeVector v) (SomeVector v) > > Since newtypes are always strict in their argument, I don't think the > BangPattern does what you'd like it to do, it just makes "main" strict > in v. As defined with `NoMonomorphismRestriction` v is a polymorphic > function, and I guess it is specialised at the call site. > > -- > Viktor. > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From compl.yue at icloud.com Tue Apr 6 14:58:20 2021 From: compl.yue at icloud.com (YueCompl) Date: Tue, 6 Apr 2021 22:58:20 +0800 Subject: [Haskell-cafe] How to ensure optimization for large immutable vectors to be shared w.r.t. Referential Transparency In-Reply-To: <0F37F11D-D3D1-4EB3-935C-89CDA1816B1D@icloud.com> References: <32447B11-A587-41D3-8617-30132561AF7F@icloud.com> <0F37F11D-D3D1-4EB3-935C-89CDA1816B1D@icloud.com> Message-ID: <333AB632-4025-4B5D-9DB2-6A1CBFA842C8@icloud.com> On a second thought, maybe GHCi's silence is a bad thing here? Maybe it should complain loudly as GHC does? ```hs λ> :set -package vector package flags have changed, resetting and loading new packages... λ> λ> import Prelude λ> λ> import qualified Data.Vector.Storable as VS λ> λ> :{ λ| λ| newtype SomeVector = SomeVector (VS.Vector Int) λ| λ| isSameVector :: SomeVector -> SomeVector -> Bool λ| isSameVector (SomeVector x) (SomeVector y) = λ| x'offset == y'offset && x'fp == y'fp λ| where λ| (x'fp, x'offset, _x'len) = VS.unsafeToForeignPtr x λ| (y'fp, y'offset, _y'len) = VS.unsafeToForeignPtr y λ| λ| :} λ> λ> let (v :: VS.Vector Int) = VS.fromList [3,2,5] in isSameVector (SomeVector v) (SomeVector v) True λ> λ> λ> :set -XMonomorphismRestriction λ> λ> let v = VS.fromList [3,2,5] in isSameVector (SomeVector v) (SomeVector v) True λ> λ> :set -XNoMonomorphismRestriction λ> λ> let v = VS.fromList [3,2,5] in isSameVector (SomeVector v) (SomeVector v) False λ> ``` Further more, my intuition about GHC's type inference here is proved wrong by it, right. But I still think that with a single piece of `let-in` construct, types are better to be inferred as specific as possible, then the result would not be affected by some extension's semantics modification. Here v's type can obviously be inferred to `VS.Vector Int` according to its usage in the `SomeVector` data constructor, I wonder why GHC is not doing this? > On 2021-04-06, at 22:19, YueCompl via ghc-devs wrote: > > Thanks very much for the diagnostic and explanation! > > I was wrong in assuming the `in isSameVector (SomeVector v) (SomeVector v)` part is enough to have type of v in `let !v = VS.fromList [3,2,5]` inferred as monomorphic, totally unaware about "NoMonomorphismRestriction" before, I've learned it today :D > >> On 2021-04-06, at 21:51, Viktor Dukhovni wrote: >> >> On Tue, Apr 06, 2021 at 07:12:51PM +0800, YueCompl via ghc-devs wrote: >> >>> λ> import Control.Monad.ST >>> λ> import qualified Data.Vector.Storable as VS >>> λ> >>> λ> :{ >>> λ| >>> λ| newtype SomeVector = SomeVector (VS.Vector Int) >>> λ| >>> λ| isSameVector :: SomeVector -> SomeVector -> Bool >>> λ| isSameVector (SomeVector !x) (SomeVector !y) = runST $ do >>> λ| mx@(VS.MVector !x'offset !x'fp) <- VS.unsafeThaw x >>> λ| my@(VS.MVector !y'offset !y'fp) <- VS.unsafeThaw y >>> λ| _ <- VS.unsafeFreeze mx >>> λ| _ <- VS.unsafeFreeze my >>> λ| return $ x'offset == y'offset && x'fp == y'fp >>> λ| >>> λ| :} >>> λ> >>> λ> let !v = VS.fromList [3,2,5] in isSameVector (SomeVector v) (SomeVector v) >>> False >>> λ> >>> λ> let !v = SomeVector (VS.fromList [3,2,5]) in isSameVector v v >>> True >> >> In GHCi, but not in compiled programs, by default the >> `NoMonomorphismRestriction` extension is enabled. If I compile your >> code with that restriction, I can reproduce your results (the values are >> not shared). >> >> If I either skip the extension, or add an explicit type annotation to >> for the vector, then the values are shared. >> >> {-# LANGUAGE BangPatterns #-} >> {-# LANGUAGE NoMonomorphismRestriction #-} >> import Control.Monad.ST >> import qualified Data.Vector.Storable as VS >> >> newtype SomeVector = SomeVector (VS.Vector Int) >> >> isSameVector :: SomeVector -> SomeVector -> Bool >> isSameVector (SomeVector !x) (SomeVector !y) = runST $ do >> mx@(VS.MVector !x'offset !x'fp) <- VS.unsafeThaw x >> my@(VS.MVector !y'offset !y'fp) <- VS.unsafeThaw y >> _ <- VS.unsafeFreeze mx >> _ <- VS.unsafeFreeze my >> return $ x'offset == y'offset && x'fp == y'fp >> >> main :: IO () >> main = >> let !v = VS.fromList [0..1023] -- :: VS.Vector Int >> in print $ isSameVector (SomeVector v) (SomeVector v) >> >> Since newtypes are always strict in their argument, I don't think the >> BangPattern does what you'd like it to do, it just makes "main" strict >> in v. As defined with `NoMonomorphismRestriction` v is a polymorphic >> function, and I guess it is specialised at the call site. >> >> -- >> Viktor. >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs -------------- next part -------------- An HTML attachment was scrubbed... URL: From borgauf at gmail.com Tue Apr 6 18:32:40 2021 From: borgauf at gmail.com (Galaxy Being) Date: Tue, 6 Apr 2021 13:32:40 -0500 Subject: [Haskell-cafe] A functor for two Peano systems In-Reply-To: <20210405173519.GE9751@cloudinit-builder> References: <20210405173519.GE9751@cloudinit-builder> Message-ID: That must be my problem. Thanks for the info. On Mon, Apr 5, 2021 at 12:36 PM Tom Ellis < tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk> wrote: > On Mon, Apr 05, 2021 at 12:17:23AM -0500, Galaxy Being wrote: > > I'm just not understanding the concept of a functor in this context: I > have > > this > [...] > > It seems there should be just one plus, function that would handle both > an > > Int-based Peano and the MyNum-based Peano, not two. But in this > definition > > > > fmap :: (a -> b) -> f a -> f b > > > > The (a -> b) should be "lifted" over the f a -> f b But I can't conceive > of > > how this should all fit together > > Are you perhaps confusing the ML notion of "functor" with the Haskell > notion of "Functor" (which is just a particular typeclass)? > > In fact, Haskell's type classes as a whole are probably closer to ML's > "functors" than Haskell's "Functor"s are! > > 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 vamchale at gmail.com Tue Apr 6 21:42:25 2021 From: vamchale at gmail.com (Vanessa McHale) Date: Tue, 6 Apr 2021 16:42:25 -0500 Subject: [Haskell-cafe] Looking for a toy imperative language implementation in Haskell for research In-Reply-To: References: Message-ID: I have kempe - the backend is the interesting part I guess http://hackage.haskell.org/package/kempe It has blocks, it's effectful, it has no loops (just recursion) though. - Vanessa McHale On 4/5/21 7:32 PM, Igor Moreno Santos wrote: > Hi, > > I'm looking for a toy imperative language implementation in Haskell > for research purposes. I imagine something like the language of > arithmetic expressions from TAPL ch. 3 augmented with > - while-loop (so the CFG has loops) > - blocks (sequence of statements to put inside loops and conditionals) > - assignment (otherwise we can't show any effects from sequences) > > I think there's probably nothing exactly like that so we might end up > doing it ourselves but maybe there's already something out there. > > Thank you in advance. > > Regards, > Igor Moreno > > > > _______________________________________________ > 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 siddu.druid at gmail.com Tue Apr 6 22:26:07 2021 From: siddu.druid at gmail.com (Siddharth Bhat) Date: Wed, 7 Apr 2021 03:56:07 +0530 Subject: [Haskell-cafe] Looking for a toy imperative language implementation in Haskell for research In-Reply-To: References: Message-ID: I have https://github.com/bollu/tiny-optimising-compiler which implements a tiny compiler for SSA. It has everything you ask for. It generates MIPS asm, so it performs register allocation as well. On Wed, Apr 7, 2021 at 3:13 AM Vanessa McHale wrote: > I have kempe - the backend is the interesting part I guess > http://hackage.haskell.org/package/kempe > > It has blocks, it's effectful, it has no loops (just recursion) though. > > - Vanessa McHale > On 4/5/21 7:32 PM, Igor Moreno Santos wrote: > > Hi, > > I'm looking for a toy imperative language implementation in Haskell for > research purposes. I imagine something like the language of arithmetic > expressions from TAPL ch. 3 augmented with > - while-loop (so the CFG has loops) > - blocks (sequence of statements to put inside loops and conditionals) > - assignment (otherwise we can't show any effects from sequences) > > I think there's probably nothing exactly like that so we might end up > doing it ourselves but maybe there's already something out there. > > Thank you in advance. > > Regards, > Igor Moreno > > > > _______________________________________________ > 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. -- https://bollu.github.io/ -------------- next part -------------- An HTML attachment was scrubbed... URL: From lanablack at amok.cc Tue Apr 6 22:36:15 2021 From: lanablack at amok.cc (Lana Black) Date: Tue, 06 Apr 2021 22:36:15 +0000 Subject: [Haskell-cafe] Looking for a toy imperative language implementation in Haskell for research In-Reply-To: References: Message-ID: <2681879.mvXUDI8C0e@glow> On Tuesday, 6 April 2021 00:32:59 UTC Igor Moreno Santos wrote: > Hi, > > I'm looking for a toy imperative language implementation in Haskell for > research purposes. I imagine something like the language of arithmetic > expressions from TAPL ch. 3 augmented with > - while-loop (so the CFG has loops) > - blocks (sequence of statements to put inside loops and conditionals) > - assignment (otherwise we can't show any effects from sequences) > > I think there's probably nothing exactly like that so we might end up doing > it ourselves but maybe there's already something out there. > > Thank you in advance. > > Regards, > Igor Moreno Hello Igor, There is an implementation of a subset of Tcl in Haskell. Not sure if this is what you need, but I tried playing with it some years ago and found it interesting. https://hackage.haskell.org/package/hiccup From jack.kelly at bellroy.com Wed Apr 7 00:36:41 2021 From: jack.kelly at bellroy.com (Jack Kelly) Date: Wed, 7 Apr 2021 10:36:41 +1000 Subject: [Haskell-cafe] [ANN] aws-arn-0.1.0.0 - Library and optics for munging Amazon Resource Names (ARNs) Message-ID: I have just pushed an initial release of aws-arn[1] to Hackage. This library provides a type representing Amazon Resource Names (ARNs)[2], and parsing/unparsing functions for them. The provided optics make it very convenient to rewrite parts of ARNs. An example, from the documentation: API Gateway Lambda Authorizers are given the ARN of the requested endpoint and method, and are expected to respond with an IAM Policy Document. It is sometimes useful to manipulate the given ARN when describing which resources to authorize: -- Returns "arn:aws:execute-api:us-east-1:123456789012:my-spiffy-api/stage/*" let authorizerSampleARN = "arn:aws:execute-api:us-east-1:123456789012:my-spiffy-api/stage/GET/some/deep/path" in over (_ARN . arnResource . slashes) (\parts -> take 2 parts ++ ["*"]) authorizerSampleARN The code is available on GitHub[3]; bug reports and pull requests are welcome. There is some additional support for parsing specific resource types -- PRs to support more resource types are especially welcome. Best, -- Jack [1]: https://hackage.haskell.org/package/aws-arn-0.1.0.0 [2]: https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html [3]: https://github.com/bellroy/aws-arn From winterland1989 at gmail.com Wed Apr 7 04:13:32 2021 From: winterland1989 at gmail.com (Dong Han) Date: Wed, 7 Apr 2021 12:13:32 +0800 Subject: [Haskell-cafe] Z.Haskell project announced Message-ID: Dear Haskellers: After having a discussion with HF guys, I decide to announce [Z.Haskell]( http://z.haskell.world/) project, It's available on Hackage and very much usable now, the document is also pretty adequate. To recap the document from Z.Haskell, Z.Haskell provides: + Array, vector(array slice), sorting, searching + Text based UTF-8, basic Unicode manipulating, regex + FFI utilities + Fast parsing and building monad + JSON encoding and decoding + IO resource management, resource pool + File system operations + Network: DNS, TCP, UDP and IPC + Buffered input and output + Process management + Environment settings + High performance logger + High performance low-resolution timer The project's goal is not to compete with the base, but to provide an alternative engineering toolkit, which is more suitable for writing practical network/storage services. Similar to [netty](https://netty.io/) for java or [nodejs](https://nodejs.org/) for javascript. Welcome to join Z.Haskell if you have a similar use case. Currently, we're heading with the following roadmap: + Crypto library based on [botan](https://github.com/ZHaskell/z-botan). + TLS network stack. + HTTP framework. + Distributed system algorithms. Happy hacking! Z.Haskell Contributors -------------- next part -------------- An HTML attachment was scrubbed... URL: From compl.yue at icloud.com Wed Apr 7 06:58:14 2021 From: compl.yue at icloud.com (YueCompl) Date: Wed, 7 Apr 2021 14:58:14 +0800 Subject: [Haskell-cafe] Z.Haskell project announced In-Reply-To: References: Message-ID: Congratulations and thanks for the public release! Wish Z a fast growth and wide adoption. At a glance I'm especially curious how > M GHC lightweight threads scale on N event loops is achieved, does it touch the internals of GHC RTS scheduler? Seems libuv would have to be deeply integrated, how is that done? Sincerely, Compl > On 2021-04-07, at 12:13, Dong Han wrote: > > Dear Haskellers: > > After having a discussion with HF guys, I decide to announce [Z.Haskell](http://z.haskell.world/ ) project, It's available on Hackage and very much usable now, the document is also pretty adequate. > > To recap the document from Z.Haskell, Z.Haskell provides: > > + Array, vector(array slice), sorting, searching > + Text based UTF-8, basic Unicode manipulating, regex > + FFI utilities > + Fast parsing and building monad > + JSON encoding and decoding > + IO resource management, resource pool > + File system operations > + Network: DNS, TCP, UDP and IPC > + Buffered input and output > + Process management > + Environment settings > + High performance logger > + High performance low-resolution timer > > The project's goal is not to compete with the base, but to provide an alternative engineering toolkit, which is more suitable for writing practical network/storage services. Similar to [netty](https://netty.io/ ) for java or [nodejs](https://nodejs.org/ ) for javascript. Welcome to join Z.Haskell if you have a similar use case. Currently, we're heading with the following roadmap: > > + Crypto library based on [botan](https://github.com/ZHaskell/z-botan ). > + TLS network stack. > + HTTP framework. > + Distributed system algorithms. > > Happy hacking! > Z.Haskell Contributors > _______________________________________________ > 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 adam at well-typed.com Wed Apr 7 08:01:03 2021 From: adam at well-typed.com (Adam Gundry) Date: Wed, 7 Apr 2021 09:01:03 +0100 Subject: [Haskell-cafe] Get proof of injectivity for an injective type family In-Reply-To: <010f0178a50493fa-8e7e17de-ba91-4a62-a89f-05c10e9fe263-000000@us-east-2.amazonses.com> References: <010f0178a50493fa-8e7e17de-ba91-4a62-a89f-05c10e9fe263-000000@us-east-2.amazonses.com> Message-ID: [Apologies for the duplicate!] On 06/04/2021 03:30, Richard Eisenberg wrote: > No. Injective type families are solely a type-inference mechanism. There are no proofs or other evidence. Figuring out how to get this right would be a significant research project, I'm afraid. This is quite true, but... >> On Apr 3, 2021, at 2:59 AM, Andreas Källberg wrote: >> >> Is there any way to get hold of a proof of injectivity for an injective type family? >> In other words, given this type family >> >> type family F a = b | b -> a >> >> can I get the term >> >> fInj :: F a ~ F b => (a ~ b => r) -> r >> >> in any way (without using unsafeCoerce)? ...while injective type families don't themselves carry evidence, it is sometimes helpful to encode it by writing the inverse family explicitly and adding constraints that require it to be an inverse: type family FInv b = a | a -> b type Good a = FInv (F a) ~ a fInj :: (F a ~ F b, Good a, Good b) => (a ~ b => r) -> r fInj x = x Of course this may not be enough, because the extra constraints may get in the way. Hope this helps, Adam -- Adam Gundry, Haskell Consultant Well-Typed LLP, https://www.well-typed.com/ Registered in England & Wales, OC335890 118 Wymering Mansions, Wymering Road, London W9 2NF, England From winterland1989 at gmail.com Wed Apr 7 08:45:44 2021 From: winterland1989 at gmail.com (Dong Han) Date: Wed, 7 Apr 2021 16:45:44 +0800 Subject: [Haskell-cafe] Z.Haskell project announced In-Reply-To: References: Message-ID: Hi Compl, Thanks for your blessing, and we're happy to answer your questions. We have published a paper about how did we combine libuv's event loop with GHC lightweight threads, it's on the old [repo]( https://github.com/ZHaskell/stdio/blob/master/docs/A%20High-Performance%20Multicore%20IO%20Manager%20Based%20on%20libuv%20(Experience%20Report).pdf), which is somehow a little bit outdated, but the design is mainly the same. > does it touch the internals of GHC RTS scheduler? No, the concurrency primitives in base(`MVar`, `forkIO`, `yield`, etc) are enough. > Seems libuv would have to be deeply integrated, how is that done? Basically, it consists of three parts: 1. Start an IO manager thread per capability, which is responsible for polling libuv's eventloop. 2. Write bindings to libuv's async functions and wait for the IO manager. 3. Manage memory allocations and how data passing across FFI. Cheers~ Dong On Wed, Apr 7, 2021 at 2:58 PM YueCompl wrote: > Congratulations and thanks for the public release! > > Wish Z a fast growth and wide adoption. > > At a glance I'm especially curious how > > > *M* GHC lightweight threads scale on *N* event loops > > is achieved, does it touch the internals of GHC RTS scheduler? Seems libuv > would have to be deeply integrated, how is that done? > > Sincerely, > Compl > > On 2021-04-07, at 12:13, Dong Han wrote: > > Dear Haskellers: > > After having a discussion with HF guys, I decide to announce [Z.Haskell]( > http://z.haskell.world/) project, It's available on Hackage and very much > usable now, the document is also pretty adequate. > > To recap the document from Z.Haskell, Z.Haskell provides: > > + Array, vector(array slice), sorting, searching > + Text based UTF-8, basic Unicode manipulating, regex > + FFI utilities > + Fast parsing and building monad > + JSON encoding and decoding > + IO resource management, resource pool > + File system operations > + Network: DNS, TCP, UDP and IPC > + Buffered input and output > + Process management > + Environment settings > + High performance logger > + High performance low-resolution timer > > The project's goal is not to compete with the base, but to provide an > alternative engineering toolkit, which is more suitable for writing > practical network/storage services. Similar to [netty](https://netty.io/) > for java or [nodejs](https://nodejs.org/) for javascript. Welcome to join > Z.Haskell if you have a similar use case. Currently, we're heading with the > following roadmap: > > + Crypto library based on [botan](https://github.com/ZHaskell/z-botan). > + TLS network stack. > + HTTP framework. > + Distributed system algorithms. > > Happy hacking! > Z.Haskell Contributors > _______________________________________________ > 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 petite.abeille at gmail.com Fri Apr 9 15:24:14 2021 From: petite.abeille at gmail.com (Petite Abeille) Date: Fri, 9 Apr 2021 17:24:14 +0200 Subject: [Haskell-cafe] haskell text://protocol client? Message-ID: Hello, Would you know of any haskell text://protocol clients? Or servers? [1][2][3] Thanks in advance. [1] https://textprotocol.org [2] https://github.com/textprotocol/public [3] https://github.com/textprotocol/publictext From nick.rudnick at gmail.com Fri Apr 9 15:49:00 2021 From: nick.rudnick at gmail.com (Nick Rudnick) Date: Fri, 9 Apr 2021 17:49:00 +0200 Subject: [Haskell-cafe] Haskell Joke of the Year 2020 Message-ID: Dear all, recently, I was confronted with a question what the Haskell joke of the year 2020 is – for anybody else, whose attention, like mine, this slipped completely, here it is, since it really is quite a bit funny, Haskellers don't make money… :-/ If anybody knows jokes of the other years, I'd be happy to know those, too! Cheers, and thanks in advance, Nick -------------- next part -------------- An HTML attachment was scrubbed... URL: From monkleyon at gmail.com Fri Apr 9 16:27:46 2021 From: monkleyon at gmail.com (MarLinn) Date: Fri, 9 Apr 2021 18:27:46 +0200 Subject: [Haskell-cafe] haskell text://protocol client? In-Reply-To: References: Message-ID: > Would you know of any haskell text://protocol clients? Or servers? [1][2][3] I may be wrong, but it appear so me that * This is a newly developed idea * And by "newly" I mean none of the git repositories you shared is more than about a month old, including the one containing the website * All appears to be done by a single, anonymous enthusiast * None of the resources explain the "why", or a use case, or seem to contain much beyond example/filler content So I don't see a reason why there would already be a Haskell server and/or client, as the single developer seems to follow a different route right now. In fact if you told us you're actually the one behind this idea, posting the question as kind of guerilla marketing, I wouldn't be surprised. Not insinuating you are though, or that that would invalidate the idea. (If nothing else, invalidate :: value → value; the value of this protocol is neither obvious nor explained, and applying a relative value-changing function like invalidate to undefined input must necessarily also return undefined. ;) ) In other words if you're enthusiastic about this there's a good chance you can be the first! ;) -------------- next part -------------- An HTML attachment was scrubbed... URL: From alan.zimm at gmail.com Fri Apr 9 16:45:39 2021 From: alan.zimm at gmail.com (Alan & Kim Zimmerman) Date: Fri, 9 Apr 2021 17:45:39 +0100 Subject: [Haskell-cafe] haskell text://protocol client? In-Reply-To: References: Message-ID: Is that the gemini protocol? If so there are some packages for it on hackage already. Alan On Fri, 9 Apr 2021 at 17:29, MarLinn wrote: > > Would you know of any haskell text://protocol clients? Or servers? [1][2][3] > > > I may be wrong, but it appear so me that > > - This is a newly developed idea > - And by "newly" I mean none of the git repositories you shared is > more than about a month old, including the one containing the website > - All appears to be done by a single, anonymous enthusiast > - None of the resources explain the "why", or a use case, or seem to > contain much beyond example/filler content > > So I don't see a reason why there would already be a Haskell server and/or > client, as the single developer seems to follow a different route right now. > > In fact if you told us you're actually the one behind this idea, posting > the question as kind of guerilla marketing, I wouldn't be surprised. Not > insinuating you are though, or that that would invalidate the idea. (If > nothing else, invalidate :: value → value; the value of this protocol is > neither obvious nor explained, and applying a relative value-changing > function like invalidate to undefined input must necessarily also return > undefined. ;) ) > > In other words if you're enthusiastic about this there's a good chance you > can be the first! ;) > _______________________________________________ > 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 petite.abeille at gmail.com Fri Apr 9 18:25:29 2021 From: petite.abeille at gmail.com (Petite Abeille) Date: Fri, 9 Apr 2021 20:25:29 +0200 Subject: [Haskell-cafe] haskell text://protocol client? In-Reply-To: References: Message-ID: <13BFFF9F-77BA-49BB-BE3A-95210E07607C@gmail.com> > On Apr 9, 2021, at 18:45, Alan & Kim Zimmerman wrote: > > Is that the gemini protocol? More akin to Mercury by the look of it: https://web.archive.org/web/20210302123932/https://portal.mozz.us/gemini/gemini.circumlunar.space/users/solderpunk/gemlog/the-mercury-protocol.gmi From petite.abeille at gmail.com Fri Apr 9 18:37:42 2021 From: petite.abeille at gmail.com (Petite Abeille) Date: Fri, 9 Apr 2021 20:37:42 +0200 Subject: [Haskell-cafe] haskell text://protocol client? In-Reply-To: References: Message-ID: <7F4C5F77-CDD6-4AD1-90E1-98BE703653FA@gmail.com> > On Apr 9, 2021, at 18:27, MarLinn wrote: > > • All appears to be done by a single, anonymous enthusiast Perhaps of the canine variety :D https://en.wikipedia.org/wiki/On_the_Internet,_nobody_knows_you%27re_a_dog ±0¢ From jonathan.protzenko at gmail.com Fri Apr 9 19:48:04 2021 From: jonathan.protzenko at gmail.com (Jonathan Protzenko) Date: Fri, 9 Apr 2021 12:48:04 -0700 Subject: [Haskell-cafe] ML Family Workshop 2021: first call for short abstracts and presentations Message-ID: <5b8a9645-94c3-bb41-9b86-575209a07c76@gmail.com> (tl;dr) The ML family workshop is back, and will be held virtually along with ICFP 2021. The workshop does not have proceedings, making it the perfect venue to run some ideas with the community or present some work in progress within a friendly environment. The PC has a broad expertise and submissions are 3 pages long: when in doubt, just submit! (long version) We are happy to announce that the ML Family Workshop is back for its 2021 edition, which we will be held online on Thursday August 26th, in conjunction with ICFP 2021. The ML family workshop warmly welcomes submission touching on the programming languages traditionally seen as part of the "ML family" (Standard ML, OCaml, F#, CakeML, SML#, Manticore, MetaOCaml, etc.). The scope of the workshop includes all aspects of the design, semantics, theory, application, implementation, and teaching of the members of the ML family. We also encourage presentations from related languages (such as Haskell, Scala, Rust, Nemerle, Links, Koka, F*, Eff, ATS, etc), to exchange experience of further developing ML ideas. ## Submission details Submissions must be at most three pages long; see the full call for papers for details. Submission site: https://ml21.hotcrp.com/ ## Important dates Thu, May 27th 2021 (AoE): submission deadline Thu, Jun 17th 2021 (AoE): author notification Thu, Aug 26th: workshop (time slots TBD) ## Program committee Danel Ahman (University of Ljubljana) Robert Atkey (University of Strathclyde) Frédéric Bour (Tarides) Ezgi Çiçek (Facebook London) Youyou Cong (Tokyo Institute of Technology) Richard A. Eisenberg (Tweag I/O) Martin Elsman (University of Copenhagen, Denmark) Ohad Kammar (University of Edinburgh) Naoki Kobayashi (University of Tokyo, Japan) Benoît Montagu (Inria) Jonathan Protzenko (Microsoft Research) (Chair) Kristina Sojakova (INRIA Paris) Don Syme (Microsoft) Matías Toro (University of Chile) Katsuhiro Ueno (Tohoku University) From bruno.bernardo at tutanota.com Sat Apr 10 10:50:06 2021 From: bruno.bernardo at tutanota.com (Bruno Bernardo) Date: Sat, 10 Apr 2021 12:50:06 +0200 (CEST) Subject: [Haskell-cafe] FMBC 2021 - 2nd Call for Papers Message-ID: [ Please distribute, apologies for multiple postings. ] ======================================================================== 3rd International Workshop on Formal Methods for Blockchains (FMBC) - Second 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 -------------------------------- David Dill, Lead Researcher, Blockchain, Novi/Facebook, USA https://research.fb.com/people/dill-david/ -------------------------------- -------------------------------- 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 * Wolfgang Ahrendt (Chalmers University of Technology, Sweden) * Lacramioara Astefanoei (Nomadic Labs, France) * Massimo Bartoletti (University of Cagliari, Italy) * Joachim Breitner (Dfinity Foundation, Germany) * Achim Brucker (University of Exeter, UK) * Zaynah Dargaye (Nomadic Labs, France) * Jérémie Decouchant (TU Delft, Netherlands) * Dana Drachsler Cohen (Technion, Israel) * Ansgar Fehnker (University of Twente, Netherlands) * Maurice Herlihy (Brown University, USA) * Lars Hupel (INNOQ, Germany) * Florian Kammueller (Middlesex University London, UK) * Igor Konnov (Informal Systems, Austria) * Andreas Lochbihler (Digital Asset, Switzerland) * Simão Melo de Sousa (Universidade da Beira Interior, Portugal) * Karl Palmskog (KTH, Sweden) * Maria Potop-Butucaru (Sorbonne Université, France) * Andreas Rossberg (Dfinity Foundation, Germany) * César Sanchez (Imdea, Spain) * Clara Schneidewind (TU Wien, Austria) * Ilya Sergey (Yale-NUS College/NUS, Singapore) * Mark Staples (CSIRO Data61, Australia) * Meng Sun (Peking University, China) * Simon Thompson (University of Kent, UK) * Josef Widder (Informal Systems, Austria) From m.rolsdorph+cafe at gmail.com Sat Apr 10 12:24:38 2021 From: m.rolsdorph+cafe at gmail.com (Mads Rolsdorph) Date: Sat, 10 Apr 2021 14:24:38 +0200 Subject: [Haskell-cafe] [ANN] network-packet-linux 0.1.1.0 Message-ID: Dear Cafe, The network package [0] provides an extensible API for working with sockets. I'm pleased to announce network-packet-linux [1], a small helper package containing the types needed to use the network package with Linux packet sockets [2]. The documentation [3] provides a short example of using network and network-packet-linux for a simple packet sniffer. Have a great weekend! Mads [0] https://hackage.haskell.org/package/network [1] https://hackage.haskell.org/package/network-packet-linux [2] https://man7.org/linux/man-pages/man7/packet.7.html [3] https://hackage.haskell.org/package/network-packet-linux-0.1.1.0/docs/Network-Socket-Linux.html -------------- next part -------------- An HTML attachment was scrubbed... URL: From pip88nl at gmail.com Sat Apr 10 12:44:25 2021 From: pip88nl at gmail.com (Pippijn van Steenhoven) Date: Sat, 10 Apr 2021 13:44:25 +0100 Subject: [Haskell-cafe] Taking over scenegraph Message-ID: Hi all, I've revived http://hackage.haskell.org/package/scenegraph: https://github.com/homectl/lambdaray/tree/main/scenegraph. I'd like to take over maintenance of that package. I can't reach the original author (email address no longer exists). Also, I'm looking for people who would like to join me in working on it and a 3D rendering pipeline based on GPipe. Currently hanging out in #implicitcad on freenode. Cheers, Pippijn -------------- next part -------------- An HTML attachment was scrubbed... URL: From simon.jakobi at googlemail.com Sat Apr 10 15:15:15 2021 From: simon.jakobi at googlemail.com (Simon Jakobi) Date: Sat, 10 Apr 2021 17:15:15 +0200 Subject: [Haskell-cafe] Taking over scenegraph In-Reply-To: References: Message-ID: CC'ing Mark with an email address used in some papers linked at https://www.cl.cam.ac.uk/~mpew2/. Am Sa., 10. Apr. 2021 um 14:45 Uhr schrieb Pippijn van Steenhoven : > > Hi all, > > I've revived http://hackage.haskell.org/package/scenegraph: https://github.com/homectl/lambdaray/tree/main/scenegraph. I'd like to take over maintenance of that package. I can't reach the original author (email address no longer exists). Also, I'm looking for people who would like to join me in working on it and a 3D rendering pipeline based on GPipe. Currently hanging out in #implicitcad on freenode. > > Cheers, > Pippijn > _______________________________________________ > 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 Sun Apr 11 19:41:54 2021 From: andrew.lelechenko at gmail.com (Andrew Lelechenko) Date: Sun, 11 Apr 2021 20:41:54 +0100 Subject: [Haskell-cafe] [ANN] tasty-bench-0.2.5: featherlight benchmark framework Message-ID: I'm happy to announce a release of tasty-bench-0.2.5. It is a featherlight benchmark framework with API mimicking criterion and gauge. https://github.com/Bodigrim/tasty-bench#readme https://hackage.haskell.org/package/tasty-bench-0.2.5 * It supports GHCs from 7.0 to 9.2 alpha. Running benchmarks on a bleeding edge GHC is important to identify potential performance degradation before a compiler is released. * A build on a clean machine is 16 times faster than criterion and 4 times faster than gauge. A build without dependencies is 6 times faster than criterion and 8 times faster than gauge. One can build benchmarks on CI without wasting excessive resources. * Benchmarks can be written together with tests, and can itself be turned into a performance regression test suite. In fact our benchmarks are just regular tasty tests. * Comparisons between benchmarks are readily available out of the box: no external tools (like criterion-compare or bench-show) are required. One can compare results between runs and between individual benchmarks instead of squinting at absolute numbers. Best regards, Andrew From compl.yue at icloud.com Mon Apr 12 11:34:19 2021 From: compl.yue at icloud.com (YueCompl) Date: Mon, 12 Apr 2021 19:34:19 +0800 Subject: [Haskell-cafe] What's the modern way to apply a polymorphic function to a Dynamic value in GHC 8.8 and onwards? Message-ID: <043B9A36-2014-4E02-9951-CBEC216C3CCA@icloud.com> Dear Cafe and GHC devs, There used to be a "principled way with pattern match on the constructor": ```hs data Dynamic where Dynamic :: Typeable a => a -> Dynamic apD :: Typeable f => (forall a. a -> f a) -> Dynamic -> Dynamic apD f (Dynamic a) = Dynamic $ f a ``` Source: https://www.reddit.com/r/haskell/comments/2kdcca/q_how_to_apply_a_polymorphic_function_to_a/ But now with GHC 8.8 as in my case, `Dynamic` constructor has changed its signature to: ```hs Dynamic :: forall a. TypeRep a -> a -> Dynamic ``` Which renders the `apD` not working anymore. And it seems missing dependencies now for an older solution Edward KMETT provides: ```hs apD :: forall f. Typeable1 f => (forall a. a -> f a) -> Dynamic -> Dynamic apD f a = dynApp df a where t = dynTypeRep a df = reify (mkFunTy t (typeOf1 (undefined :: f ()) `mkAppTy` t)) $ \(_ :: Proxy s) -> toDyn (WithRep f :: WithRep s (() -> f ())) ``` Source: https://stackoverflow.com/questions/10889682/how-to-apply-a-polymorphic-function-to-a-dynamic-value So, how can I do that nowadays? Thanks, Compl From jaro.reinders at gmail.com Mon Apr 12 14:04:54 2021 From: jaro.reinders at gmail.com (Jaro Reinders) Date: Mon, 12 Apr 2021 16:04:54 +0200 Subject: [Haskell-cafe] What's the modern way to apply a polymorphic function to a Dynamic value in GHC 8.8 and onwards? In-Reply-To: <043B9A36-2014-4E02-9951-CBEC216C3CCA@icloud.com> References: <043B9A36-2014-4E02-9951-CBEC216C3CCA@icloud.com> Message-ID: <8ca115eb-d9ac-b1e0-c4f3-0b1cb835adc2@gmail.com> I have no experience in this area, but this compiles: ``` {-# LANGUAGE RankNTypes, ScopedTypeVariables #-} import Type.Reflection import Data.Dynamic appD :: forall f. Typeable f => (forall a. a -> f a) -> Dynamic -> Dynamic appD f (Dynamic rep (x :: a)) = withTypeable rep (toDyn (f x)) ``` Cheers, Jaro On 12-04-2021 13:34, YueCompl via Haskell-Cafe wrote: > Dear Cafe and GHC devs, > > > There used to be a "principled way with pattern match on the constructor": > > ```hs > data Dynamic where > Dynamic :: Typeable a => a -> Dynamic > > apD :: Typeable f => (forall a. a -> f a) -> Dynamic -> Dynamic > apD f (Dynamic a) = Dynamic $ f a > ``` > Source: https://www.reddit.com/r/haskell/comments/2kdcca/q_how_to_apply_a_polymorphic_function_to_a/ > > > But now with GHC 8.8 as in my case, `Dynamic` constructor has changed its signature to: > > ```hs > Dynamic :: forall a. TypeRep a -> a -> Dynamic > ``` > > Which renders the `apD` not working anymore. > > > And it seems missing dependencies now for an older solution Edward KMETT provides: > > ```hs > apD :: forall f. Typeable1 f => (forall a. a -> f a) -> Dynamic -> Dynamic > apD f a = dynApp df a > where t = dynTypeRep a > df = reify (mkFunTy t (typeOf1 (undefined :: f ()) `mkAppTy` t)) $ > \(_ :: Proxy s) -> toDyn (WithRep f :: WithRep s (() -> f ())) > ``` > Source: https://stackoverflow.com/questions/10889682/how-to-apply-a-polymorphic-function-to-a-dynamic-value > > > So, how can I do that nowadays? > > Thanks, > Compl > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > From compl.yue at icloud.com Mon Apr 12 14:13:46 2021 From: compl.yue at icloud.com (YueCompl) Date: Mon, 12 Apr 2021 22:13:46 +0800 Subject: [Haskell-cafe] What's the modern way to apply a polymorphic function to a Dynamic value in GHC 8.8 and onwards? In-Reply-To: <7F106DE5-7E92-4D21-BB0A-E7FC4EEE4484@serokell.io> References: <043B9A36-2014-4E02-9951-CBEC216C3CCA@icloud.com> <7F106DE5-7E92-4D21-BB0A-E7FC4EEE4484@serokell.io> Message-ID: <68E8C92A-9BB2-46FF-8747-C3DD07DA1084@icloud.com> Thanks to Vlad and Jaro, your solution of `apD` compiles, I think it should work. But unfortunately my real case is a little different / more complex, a MWE appears like this: ```hs holdEvent :: Dynamic -> Dynamic holdEvent (Dynamic t evs') = withTypeable t $ Dynamic typeRep (hcHoldEvent evs') where hcHoldEvent :: forall a. EventSink a -> IO (TimeSeries a) hcHoldEvent !evs = do !holder <- newIORef Nothing listenEvents evs $ writeIORef holder . Just return $ TimeSeries $ readIORef holder data EventSink a = EventSink { listenEvents :: (a -> IO ()) -> IO (), closeStream :: IO () } instance Functor EventSink where fmap = undefined newtype TimeSeries a = TimeSeries {readTimeSeries :: IO (Maybe a)} instance Functor TimeSeries where fmap = undefined ``` Now I'm clueless how to use the `withTypeable` trick to apply my polymorphic `hcHoldEvent` to `Dynamic`, naively written as in above, the error is: ```log src/PoC/DynPoly.hs:20:49: error: • Couldn't match expected type ‘EventSink a0’ with actual type ‘a’ ‘a’ is a rigid type variable bound by a pattern with constructor: Dynamic :: forall a. base-4.13.0.0:Data.Typeable.Internal.TypeRep a -> a -> Dynamic, in an equation for ‘holdEvent’ at src/PoC/DynPoly.hs:19:12-25 • In the first argument of ‘hcHoldEvent’, namely ‘evs'’ In the second argument of ‘Dynamic’, namely ‘(hcHoldEvent evs')’ In the second argument of ‘($)’, namely ‘Dynamic typeRep (hcHoldEvent evs')’ • Relevant bindings include evs' :: a (bound at src/PoC/DynPoly.hs:19:22) t :: base-4.13.0.0:Data.Typeable.Internal.TypeRep a (bound at src/PoC/DynPoly.hs:19:20) | 20 | withTypeable t $ Dynamic typeRep (hcHoldEvent evs') | ^^^^ ``` Thanks with best regards, Compl > On 2021-04-12, at 22:04, Jaro Reinders wrote: > > I have no experience in this area, but this compiles: > > ``` > {-# LANGUAGE RankNTypes, ScopedTypeVariables #-} > import Type.Reflection > import Data.Dynamic > > appD :: forall f. Typeable f => (forall a. a -> f a) -> Dynamic -> Dynamic > appD f (Dynamic rep (x :: a)) = withTypeable rep (toDyn (f x)) > ``` > > Cheers, > > Jaro > On 2021-04-12, at 21:06, Vladislav Zavialov wrote: > > Would something like this work for you? > > import Type.Reflection > import Data.Dynamic > > apD :: Typeable f => (forall a. a -> f a) -> Dynamic -> Dynamic > apD f (Dynamic t a) = withTypeable t $ Dynamic typeRep (f a) > > - Vlad > >> On 12 Apr 2021, at 14:34, YueCompl via ghc-devs wrote: >> >> Dear Cafe and GHC devs, >> >> >> There used to be a "principled way with pattern match on the constructor": >> >> ```hs >> data Dynamic where >> Dynamic :: Typeable a => a -> Dynamic >> >> apD :: Typeable f => (forall a. a -> f a) -> Dynamic -> Dynamic >> apD f (Dynamic a) = Dynamic $ f a >> ``` >> Source: https://www.reddit.com/r/haskell/comments/2kdcca/q_how_to_apply_a_polymorphic_function_to_a/ >> >> >> But now with GHC 8.8 as in my case, `Dynamic` constructor has changed its signature to: >> >> ```hs >> Dynamic :: forall a. TypeRep a -> a -> Dynamic >> ``` >> >> Which renders the `apD` not working anymore. >> >> >> And it seems missing dependencies now for an older solution Edward KMETT provides: >> >> ```hs >> apD :: forall f. Typeable1 f => (forall a. a -> f a) -> Dynamic -> Dynamic >> apD f a = dynApp df a >> where t = dynTypeRep a >> df = reify (mkFunTy t (typeOf1 (undefined :: f ()) `mkAppTy` t)) $ >> \(_ :: Proxy s) -> toDyn (WithRep f :: WithRep s (() -> f ())) >> ``` >> Source: https://stackoverflow.com/questions/10889682/how-to-apply-a-polymorphic-function-to-a-dynamic-value >> >> >> So, how can I do that nowadays? >> >> Thanks, >> Compl >> >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From hesselink at gmail.com Mon Apr 12 14:50:14 2021 From: hesselink at gmail.com (Erik Hesselink) Date: Mon, 12 Apr 2021 16:50:14 +0200 Subject: [Haskell-cafe] What's the modern way to apply a polymorphic function to a Dynamic value in GHC 8.8 and onwards? In-Reply-To: <68E8C92A-9BB2-46FF-8747-C3DD07DA1084@icloud.com> References: <043B9A36-2014-4E02-9951-CBEC216C3CCA@icloud.com> <7F106DE5-7E92-4D21-BB0A-E7FC4EEE4484@serokell.io> <68E8C92A-9BB2-46FF-8747-C3DD07DA1084@icloud.com> Message-ID: Your function is not `forall a. a -> f a`, as in your initial example, but requires its argument to be an `EventSink`. The value you unwrap from the `Dynamic` is any existential type, not necessarily an `EventSink`. You'll have to compare the TypeReps (with something like `eqTypeRep`[1], or wrap your function in a `Dynamic` and use `dynApply` [2], which does the comparison for you. Cheers, Erik [1] https://hackage.haskell.org/package/base-4.15.0.0/docs/Type-Reflection.html#v:eqTypeRep [2] https://hackage.haskell.org/package/base-4.15.0.0/docs/Data-Dynamic.html#v:dynApply On Mon, 12 Apr 2021 at 16:15, YueCompl via ghc-devs wrote: > Thanks to Vlad and Jaro, your solution of `apD` compiles, I think it > should work. > > But unfortunately my real case is a little different / more complex, a MWE > appears like this: > > ```hs > holdEvent :: Dynamic -> Dynamic > holdEvent (Dynamic t evs') = > withTypeable t $ Dynamic typeRep (hcHoldEvent evs') > where > hcHoldEvent :: forall a. EventSink a -> IO (TimeSeries a) > hcHoldEvent !evs = do > !holder <- newIORef Nothing > listenEvents evs $ writeIORef holder . Just > return $ TimeSeries $ readIORef holder > > data EventSink a = EventSink > { listenEvents :: (a -> IO ()) -> IO (), > closeStream :: IO () > } > > instance Functor EventSink where > fmap = undefined > > newtype TimeSeries a = TimeSeries {readTimeSeries :: IO (Maybe a)} > > instance Functor TimeSeries where > fmap = undefined > > ``` > > Now I'm clueless how to use the `withTypeable` trick to apply my > polymorphic `hcHoldEvent` to `Dynamic`, naively written as in above, the > error is: > > ```log > *src/PoC/DynPoly.hs:20:49: **error:* > • Couldn't match expected type ‘EventSink a0’ with actual type ‘a’ > ‘a’ is a rigid type variable bound by > a pattern with constructor: > Dynamic :: forall a. > base-4.13.0.0:Data.Typeable.Internal.TypeRep a -> a > -> Dynamic, > in an equation for ‘holdEvent’ > at src/PoC/DynPoly.hs:19:12-25 > • In the first argument of ‘hcHoldEvent’, namely ‘evs'’ > In the second argument of ‘Dynamic’, namely ‘(hcHoldEvent evs')’ > In the second argument of ‘($)’, namely > ‘Dynamic typeRep (hcHoldEvent evs')’ > • Relevant bindings include > evs' :: a (bound at src/PoC/DynPoly.hs:19:22) > t :: base-4.13.0.0:Data.Typeable.Internal.TypeRep a > (bound at src/PoC/DynPoly.hs:19:20) > * |* > *20 |* withTypeable t $ Dynamic typeRep (hcHoldEvent *evs'*) > * |** ^^^^* > > ``` > > Thanks with best regards, > Compl > > > On 2021-04-12, at 22:04, Jaro Reinders wrote: > > I have no experience in this area, but this compiles: > > ``` > {-# LANGUAGE RankNTypes, ScopedTypeVariables #-} > import Type.Reflection > import Data.Dynamic > > appD :: forall f. Typeable f => (forall a. a -> f a) -> Dynamic -> Dynamic > appD f (Dynamic rep (x :: a)) = withTypeable rep (toDyn (f x)) > ``` > > Cheers, > > Jaro > > > > On 2021-04-12, at 21:06, Vladislav Zavialov wrote: > > Would something like this work for you? > > import Type.Reflection > import Data.Dynamic > > apD :: Typeable f => (forall a. a -> f a) -> Dynamic -> Dynamic > apD f (Dynamic t a) = withTypeable t $ Dynamic typeRep (f a) > > - Vlad > > On 12 Apr 2021, at 14:34, YueCompl via ghc-devs > wrote: > > Dear Cafe and GHC devs, > > > There used to be a "principled way with pattern match on the constructor": > > ```hs > data Dynamic where > Dynamic :: Typeable a => a -> Dynamic > > apD :: Typeable f => (forall a. a -> f a) -> Dynamic -> Dynamic > apD f (Dynamic a) = Dynamic $ f a > ``` > Source: > https://www.reddit.com/r/haskell/comments/2kdcca/q_how_to_apply_a_polymorphic_function_to_a/ > > > But now with GHC 8.8 as in my case, `Dynamic` constructor has changed its > signature to: > > ```hs > Dynamic :: forall a. TypeRep a -> a -> Dynamic > ``` > > Which renders the `apD` not working anymore. > > > And it seems missing dependencies now for an older solution Edward KMETT > provides: > > ```hs > apD :: forall f. Typeable1 f => (forall a. a -> f a) -> Dynamic -> Dynamic > apD f a = dynApp df a > where t = dynTypeRep a > df = reify (mkFunTy t (typeOf1 (undefined :: f ()) `mkAppTy` t)) $ > \(_ :: Proxy s) -> toDyn (WithRep f :: WithRep s (() -> f > ())) > ``` > Source: > https://stackoverflow.com/questions/10889682/how-to-apply-a-polymorphic-function-to-a-dynamic-value > > > So, how can I do that nowadays? > > Thanks, > Compl > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From compl.yue at icloud.com Mon Apr 12 16:27:01 2021 From: compl.yue at icloud.com (YueCompl) Date: Tue, 13 Apr 2021 00:27:01 +0800 Subject: [Haskell-cafe] What's the modern way to apply a polymorphic function to a Dynamic value in GHC 8.8 and onwards? In-Reply-To: References: <043B9A36-2014-4E02-9951-CBEC216C3CCA@icloud.com> <7F106DE5-7E92-4D21-BB0A-E7FC4EEE4484@serokell.io> <68E8C92A-9BB2-46FF-8747-C3DD07DA1084@icloud.com> Message-ID: <34A44F73-E4D0-4F1D-BBC1-08A539FAC76A@icloud.com> Thanks Erik, With the help from Iceland_jack via /r/haskell , I end up with a working solution like this: ```hs data TypeableInstance a where -- data TypeableInstance :: forall k. k -> Type where TypeableInstance :: Typeable a => TypeableInstance a typeableInstance :: forall (k :: Type) (a :: k). TypeRep a -> TypeableInstance a typeableInstance typeRep' = withTypeable typeRep' TypeableInstance pattern TypeRep :: forall k (a :: k). () => Typeable a => TypeRep a pattern TypeRep <- (typeableInstance -> TypeableInstance) where TypeRep = typeRep holdEvent :: Dynamic -> Dynamic holdEvent !devs = case devs of Dynamic (App eventSink TypeRep) evs' -> case eqTypeRep (typeRep @EventSink) eventSink of Just HRefl -> Dynamic TypeRep (hcHoldEvent evs') Nothing -> error "not an EventSink" -- to be handled properly _ -> error "even not a poly-type" -- to be handled properly where hcHoldEvent :: forall a. EventSink a -> IO (TimeSeries a) hcHoldEvent !evs = do !holder <- newIORef Nothing listenEvents evs $ writeIORef holder . Just return $ TimeSeries $ readIORef holder data EventSink a = EventSink { listenEvents :: (a -> IO ()) -> IO (), closeStream :: IO () } instance Functor EventSink where fmap = undefined newtype TimeSeries a = TimeSeries {readTimeSeries :: IO (Maybe a)} instance Functor TimeSeries where fmap = undefined ``` I'm still wrapping my head around it, for how the `pattern TypeRep` works in this case. Or you think there exists a solution without using such a pattern? My function (hcHoldEvent) is polymorphic so not eligible to be wrapped as a Dynamic in the first place, or there also some way to specialize it at runtime? That'll be another interesting tool. Thanks with regards, Compl > On 2021-04-12, at 22:50, Erik Hesselink wrote: > > Your function is not `forall a. a -> f a`, as in your initial example, but requires its argument to be an `EventSink`. The value you unwrap from the `Dynamic` is any existential type, not necessarily an `EventSink`. You'll have to compare the TypeReps (with something like `eqTypeRep`[1], or wrap your function in a `Dynamic` and use `dynApply` [2], which does the comparison for you. > > Cheers, > > Erik > > [1] https://hackage.haskell.org/package/base-4.15.0.0/docs/Type-Reflection.html#v:eqTypeRep > [2] https://hackage.haskell.org/package/base-4.15.0.0/docs/Data-Dynamic.html#v:dynApply > On Mon, 12 Apr 2021 at 16:15, YueCompl via ghc-devs > wrote: > Thanks to Vlad and Jaro, your solution of `apD` compiles, I think it should work. > > But unfortunately my real case is a little different / more complex, a MWE appears like this: > > ```hs > holdEvent :: Dynamic -> Dynamic > holdEvent (Dynamic t evs') = > withTypeable t $ Dynamic typeRep (hcHoldEvent evs') > where > hcHoldEvent :: forall a. EventSink a -> IO (TimeSeries a) > hcHoldEvent !evs = do > !holder <- newIORef Nothing > listenEvents evs $ writeIORef holder . Just > return $ TimeSeries $ readIORef holder > > data EventSink a = EventSink > { listenEvents :: (a -> IO ()) -> IO (), > closeStream :: IO () > } > > instance Functor EventSink where > fmap = undefined > > newtype TimeSeries a = TimeSeries {readTimeSeries :: IO (Maybe a)} > > instance Functor TimeSeries where > fmap = undefined > > ``` > > Now I'm clueless how to use the `withTypeable` trick to apply my polymorphic `hcHoldEvent` to `Dynamic`, naively written as in above, the error is: > > ```log > src/PoC/DynPoly.hs:20:49: error: > • Couldn't match expected type ‘EventSink a0’ with actual type ‘a’ > ‘a’ is a rigid type variable bound by > a pattern with constructor: > Dynamic :: forall a. > base-4.13.0.0:Data.Typeable.Internal.TypeRep a -> a -> Dynamic, > in an equation for ‘holdEvent’ > at src/PoC/DynPoly.hs:19:12-25 > • In the first argument of ‘hcHoldEvent’, namely ‘evs'’ > In the second argument of ‘Dynamic’, namely ‘(hcHoldEvent evs')’ > In the second argument of ‘($)’, namely > ‘Dynamic typeRep (hcHoldEvent evs')’ > • Relevant bindings include > evs' :: a (bound at src/PoC/DynPoly.hs:19:22) > t :: base-4.13.0.0:Data.Typeable.Internal.TypeRep a > (bound at src/PoC/DynPoly.hs:19:20) > | > 20 | withTypeable t $ Dynamic typeRep (hcHoldEvent evs') > | ^^^^ > > ``` > > Thanks with best regards, > Compl > > >> On 2021-04-12, at 22:04, Jaro Reinders > wrote: >> >> I have no experience in this area, but this compiles: >> >> ``` >> {-# LANGUAGE RankNTypes, ScopedTypeVariables #-} >> import Type.Reflection >> import Data.Dynamic >> >> appD :: forall f. Typeable f => (forall a. a -> f a) -> Dynamic -> Dynamic >> appD f (Dynamic rep (x :: a)) = withTypeable rep (toDyn (f x)) >> ``` >> >> Cheers, >> >> Jaro > > >> On 2021-04-12, at 21:06, Vladislav Zavialov > wrote: >> >> Would something like this work for you? >> >> import Type.Reflection >> import Data.Dynamic >> >> apD :: Typeable f => (forall a. a -> f a) -> Dynamic -> Dynamic >> apD f (Dynamic t a) = withTypeable t $ Dynamic typeRep (f a) >> >> - Vlad >> >>> On 12 Apr 2021, at 14:34, YueCompl via ghc-devs > wrote: >>> >>> Dear Cafe and GHC devs, >>> >>> >>> There used to be a "principled way with pattern match on the constructor": >>> >>> ```hs >>> data Dynamic where >>> Dynamic :: Typeable a => a -> Dynamic >>> >>> apD :: Typeable f => (forall a. a -> f a) -> Dynamic -> Dynamic >>> apD f (Dynamic a) = Dynamic $ f a >>> ``` >>> Source: https://www.reddit.com/r/haskell/comments/2kdcca/q_how_to_apply_a_polymorphic_function_to_a/ >>> >>> >>> But now with GHC 8.8 as in my case, `Dynamic` constructor has changed its signature to: >>> >>> ```hs >>> Dynamic :: forall a. TypeRep a -> a -> Dynamic >>> ``` >>> >>> Which renders the `apD` not working anymore. >>> >>> >>> And it seems missing dependencies now for an older solution Edward KMETT provides: >>> >>> ```hs >>> apD :: forall f. Typeable1 f => (forall a. a -> f a) -> Dynamic -> Dynamic >>> apD f a = dynApp df a >>> where t = dynTypeRep a >>> df = reify (mkFunTy t (typeOf1 (undefined :: f ()) `mkAppTy` t)) $ >>> \(_ :: Proxy s) -> toDyn (WithRep f :: WithRep s (() -> f ())) >>> ``` >>> Source: https://stackoverflow.com/questions/10889682/how-to-apply-a-polymorphic-function-to-a-dynamic-value >>> >>> >>> So, how can I do that nowadays? >>> >>> Thanks, >>> Compl >>> >>> _______________________________________________ >>> ghc-devs mailing list >>> ghc-devs at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >> > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs -------------- next part -------------- An HTML attachment was scrubbed... URL: From compl.yue at icloud.com Mon Apr 12 16:58:03 2021 From: compl.yue at icloud.com (YueCompl) Date: Tue, 13 Apr 2021 00:58:03 +0800 Subject: [Haskell-cafe] What's the modern way to apply a polymorphic function to a Dynamic value in GHC 8.8 and onwards? In-Reply-To: <34A44F73-E4D0-4F1D-BBC1-08A539FAC76A@icloud.com> References: <043B9A36-2014-4E02-9951-CBEC216C3CCA@icloud.com> <7F106DE5-7E92-4D21-BB0A-E7FC4EEE4484@serokell.io> <68E8C92A-9BB2-46FF-8747-C3DD07DA1084@icloud.com> <34A44F73-E4D0-4F1D-BBC1-08A539FAC76A@icloud.com> Message-ID: <15DE054A-5B61-4011-8D1D-9C344072F964@icloud.com> Oh, forgot to mention that there is a warning I also don't understand by far: ```log src/PoC/DynPoly.hs:40:3: warning: [-Woverlapping-patterns] Pattern match has inaccessible right hand side In a case alternative: Dynamic (App eventSink TypeRep) evs' -> ... | 40 | Dynamic (App eventSink TypeRep) evs' -> | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^... ``` I need to work out some extra stuff to test the solution in real case, meanwhile this warning seems worrying ... > On 2021-04-13, at 00:27, YueCompl via ghc-devs wrote: > > Thanks Erik, > > With the help from Iceland_jack via /r/haskell , I end up with a working solution like this: > > ```hs > data TypeableInstance a where > -- data TypeableInstance :: forall k. k -> Type where > TypeableInstance :: Typeable a => TypeableInstance a > > typeableInstance :: forall (k :: Type) (a :: k). TypeRep a -> TypeableInstance a > typeableInstance typeRep' = withTypeable typeRep' TypeableInstance > > pattern TypeRep :: forall k (a :: k). () => Typeable a => TypeRep a > pattern TypeRep <- > (typeableInstance -> TypeableInstance) > where > TypeRep = typeRep > > holdEvent :: Dynamic -> Dynamic > holdEvent !devs = case devs of > Dynamic (App eventSink TypeRep) evs' -> > case eqTypeRep (typeRep @EventSink) eventSink of > Just HRefl -> Dynamic TypeRep (hcHoldEvent evs') > Nothing -> error "not an EventSink" -- to be handled properly > _ -> error "even not a poly-type" -- to be handled properly > where > hcHoldEvent :: forall a. EventSink a -> IO (TimeSeries a) > hcHoldEvent !evs = do > !holder <- newIORef Nothing > listenEvents evs $ writeIORef holder . Just > return $ TimeSeries $ readIORef holder > > data EventSink a = EventSink > { listenEvents :: (a -> IO ()) -> IO (), > closeStream :: IO () > } > > instance Functor EventSink where > fmap = undefined > > newtype TimeSeries a = TimeSeries {readTimeSeries :: IO (Maybe a)} > > instance Functor TimeSeries where > fmap = undefined > > ``` > > I'm still wrapping my head around it, for how the `pattern TypeRep` works in this case. > > Or you think there exists a solution without using such a pattern? > > My function (hcHoldEvent) is polymorphic so not eligible to be wrapped as a Dynamic in the first place, or there also some way to specialize it at runtime? That'll be another interesting tool. > > Thanks with regards, > Compl > >> On 2021-04-12, at 22:50, Erik Hesselink > wrote: >> >> Your function is not `forall a. a -> f a`, as in your initial example, but requires its argument to be an `EventSink`. The value you unwrap from the `Dynamic` is any existential type, not necessarily an `EventSink`. You'll have to compare the TypeReps (with something like `eqTypeRep`[1], or wrap your function in a `Dynamic` and use `dynApply` [2], which does the comparison for you. >> >> Cheers, >> >> Erik >> >> [1] https://hackage.haskell.org/package/base-4.15.0.0/docs/Type-Reflection.html#v:eqTypeRep >> [2] https://hackage.haskell.org/package/base-4.15.0.0/docs/Data-Dynamic.html#v:dynApply >> On Mon, 12 Apr 2021 at 16:15, YueCompl via ghc-devs > wrote: >> Thanks to Vlad and Jaro, your solution of `apD` compiles, I think it should work. >> >> But unfortunately my real case is a little different / more complex, a MWE appears like this: >> >> ```hs >> holdEvent :: Dynamic -> Dynamic >> holdEvent (Dynamic t evs') = >> withTypeable t $ Dynamic typeRep (hcHoldEvent evs') >> where >> hcHoldEvent :: forall a. EventSink a -> IO (TimeSeries a) >> hcHoldEvent !evs = do >> !holder <- newIORef Nothing >> listenEvents evs $ writeIORef holder . Just >> return $ TimeSeries $ readIORef holder >> >> data EventSink a = EventSink >> { listenEvents :: (a -> IO ()) -> IO (), >> closeStream :: IO () >> } >> >> instance Functor EventSink where >> fmap = undefined >> >> newtype TimeSeries a = TimeSeries {readTimeSeries :: IO (Maybe a)} >> >> instance Functor TimeSeries where >> fmap = undefined >> >> ``` >> >> Now I'm clueless how to use the `withTypeable` trick to apply my polymorphic `hcHoldEvent` to `Dynamic`, naively written as in above, the error is: >> >> ```log >> src/PoC/DynPoly.hs:20:49: error: >> • Couldn't match expected type ‘EventSink a0’ with actual type ‘a’ >> ‘a’ is a rigid type variable bound by >> a pattern with constructor: >> Dynamic :: forall a. >> base-4.13.0.0:Data.Typeable.Internal.TypeRep a -> a -> Dynamic, >> in an equation for ‘holdEvent’ >> at src/PoC/DynPoly.hs:19:12-25 >> • In the first argument of ‘hcHoldEvent’, namely ‘evs'’ >> In the second argument of ‘Dynamic’, namely ‘(hcHoldEvent evs')’ >> In the second argument of ‘($)’, namely >> ‘Dynamic typeRep (hcHoldEvent evs')’ >> • Relevant bindings include >> evs' :: a (bound at src/PoC/DynPoly.hs:19:22) >> t :: base-4.13.0.0:Data.Typeable.Internal.TypeRep a >> (bound at src/PoC/DynPoly.hs:19:20) >> | >> 20 | withTypeable t $ Dynamic typeRep (hcHoldEvent evs') >> | ^^^^ >> >> ``` >> >> Thanks with best regards, >> Compl >> >> >>> On 2021-04-12, at 22:04, Jaro Reinders > wrote: >>> >>> I have no experience in this area, but this compiles: >>> >>> ``` >>> {-# LANGUAGE RankNTypes, ScopedTypeVariables #-} >>> import Type.Reflection >>> import Data.Dynamic >>> >>> appD :: forall f. Typeable f => (forall a. a -> f a) -> Dynamic -> Dynamic >>> appD f (Dynamic rep (x :: a)) = withTypeable rep (toDyn (f x)) >>> ``` >>> >>> Cheers, >>> >>> Jaro >> >> >>> On 2021-04-12, at 21:06, Vladislav Zavialov > wrote: >>> >>> Would something like this work for you? >>> >>> import Type.Reflection >>> import Data.Dynamic >>> >>> apD :: Typeable f => (forall a. a -> f a) -> Dynamic -> Dynamic >>> apD f (Dynamic t a) = withTypeable t $ Dynamic typeRep (f a) >>> >>> - Vlad >>> >>>> On 12 Apr 2021, at 14:34, YueCompl via ghc-devs > wrote: >>>> >>>> Dear Cafe and GHC devs, >>>> >>>> >>>> There used to be a "principled way with pattern match on the constructor": >>>> >>>> ```hs >>>> data Dynamic where >>>> Dynamic :: Typeable a => a -> Dynamic >>>> >>>> apD :: Typeable f => (forall a. a -> f a) -> Dynamic -> Dynamic >>>> apD f (Dynamic a) = Dynamic $ f a >>>> ``` >>>> Source: https://www.reddit.com/r/haskell/comments/2kdcca/q_how_to_apply_a_polymorphic_function_to_a/ >>>> >>>> >>>> But now with GHC 8.8 as in my case, `Dynamic` constructor has changed its signature to: >>>> >>>> ```hs >>>> Dynamic :: forall a. TypeRep a -> a -> Dynamic >>>> ``` >>>> >>>> Which renders the `apD` not working anymore. >>>> >>>> >>>> And it seems missing dependencies now for an older solution Edward KMETT provides: >>>> >>>> ```hs >>>> apD :: forall f. Typeable1 f => (forall a. a -> f a) -> Dynamic -> Dynamic >>>> apD f a = dynApp df a >>>> where t = dynTypeRep a >>>> df = reify (mkFunTy t (typeOf1 (undefined :: f ()) `mkAppTy` t)) $ >>>> \(_ :: Proxy s) -> toDyn (WithRep f :: WithRep s (() -> f ())) >>>> ``` >>>> Source: https://stackoverflow.com/questions/10889682/how-to-apply-a-polymorphic-function-to-a-dynamic-value >>>> >>>> >>>> So, how can I do that nowadays? >>>> >>>> Thanks, >>>> Compl >>>> >>>> _______________________________________________ >>>> ghc-devs mailing list >>>> ghc-devs at haskell.org >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >>> >> >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs -------------- next part -------------- An HTML attachment was scrubbed... URL: From hesselink at gmail.com Mon Apr 12 18:50:11 2021 From: hesselink at gmail.com (Erik Hesselink) Date: Mon, 12 Apr 2021 20:50:11 +0200 Subject: [Haskell-cafe] What's the modern way to apply a polymorphic function to a Dynamic value in GHC 8.8 and onwards? In-Reply-To: <15DE054A-5B61-4011-8D1D-9C344072F964@icloud.com> References: <043B9A36-2014-4E02-9951-CBEC216C3CCA@icloud.com> <7F106DE5-7E92-4D21-BB0A-E7FC4EEE4484@serokell.io> <68E8C92A-9BB2-46FF-8747-C3DD07DA1084@icloud.com> <34A44F73-E4D0-4F1D-BBC1-08A539FAC76A@icloud.com> <15DE054A-5B61-4011-8D1D-9C344072F964@icloud.com> Message-ID: That is a lot, I'm not sure I understand that pattern synonym. Using `withTypeable` instead works for me: holdEvent :: Dynamic -> Dynamic holdEvent (Dynamic tr x) = case tr of App ft at -> case ft `eqTypeRep` typeRep @EventSink of Just HRefl -> withTypeable at $ toDyn (hcHoldEvent x) Nothing -> error "to handle" _ -> error "to handle" Cheers, Erik On Mon, 12 Apr 2021 at 18:58, YueCompl wrote: > Oh, forgot to mention that there is a warning I also don't understand by > far: > > ```log > *src/PoC/DynPoly.hs:40:3: **warning:** [**-Woverlapping-patterns**]* > Pattern match has inaccessible right hand side > In a case alternative: Dynamic (App eventSink TypeRep) evs' -> ... > * |* > *40 |* *Dynamic (App eventSink TypeRep) evs' ->* > * |** ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...* > ``` > I need to work out some extra stuff to test the solution in real case, > meanwhile this warning seems worrying ... > > On 2021-04-13, at 00:27, YueCompl via ghc-devs > wrote: > > Thanks Erik, > > With the help from Iceland_jack > via /r/haskell , I end up with a > working solution like this: > > ```hs > data TypeableInstance a where > -- data TypeableInstance :: forall k. k -> Type where > TypeableInstance :: Typeable a => TypeableInstance a > > typeableInstance :: forall (k :: Type) (a :: k). TypeRep a -> > TypeableInstance a > typeableInstance typeRep' = withTypeable typeRep' TypeableInstance > > pattern TypeRep :: forall k (a :: k). () => Typeable a => TypeRep a > pattern TypeRep <- > (typeableInstance -> TypeableInstance) > where > TypeRep = typeRep > > holdEvent :: Dynamic -> Dynamic > holdEvent !devs = case devs of > Dynamic (App eventSink TypeRep) evs' -> > case eqTypeRep (typeRep @EventSink) eventSink of > Just HRefl -> Dynamic TypeRep (hcHoldEvent evs') > Nothing -> error "not an EventSink" -- to be handled properly > _ -> error "even not a poly-type" -- to be handled properly > where > hcHoldEvent :: forall a. EventSink a -> IO (TimeSeries a) > hcHoldEvent !evs = do > !holder <- newIORef Nothing > listenEvents evs $ writeIORef holder . Just > return $ TimeSeries $ readIORef holder > > data EventSink a = EventSink > { listenEvents :: (a -> IO ()) -> IO (), > closeStream :: IO () > } > > instance Functor EventSink where > fmap = undefined > > newtype TimeSeries a = TimeSeries {readTimeSeries :: IO (Maybe a)} > > instance Functor TimeSeries where > fmap = undefined > > ``` > > I'm still wrapping my head around it, for how the `pattern TypeRep` works > in this case. > > Or you think there exists a solution without using such a pattern? > > My function (hcHoldEvent) is polymorphic so not eligible to be wrapped as > a Dynamic in the first place, or there also some way to specialize it at > runtime? That'll be another interesting tool. > > Thanks with regards, > Compl > > On 2021-04-12, at 22:50, Erik Hesselink wrote: > > Your function is not `forall a. a -> f a`, as in your initial example, but > requires its argument to be an `EventSink`. The value you unwrap from the > `Dynamic` is any existential type, not necessarily an `EventSink`. You'll > have to compare the TypeReps (with something like `eqTypeRep`[1], or wrap > your function in a `Dynamic` and use `dynApply` [2], which does the > comparison for you. > > Cheers, > > Erik > > [1] > https://hackage.haskell.org/package/base-4.15.0.0/docs/Type-Reflection.html#v:eqTypeRep > [2] > https://hackage.haskell.org/package/base-4.15.0.0/docs/Data-Dynamic.html#v:dynApply > > On Mon, 12 Apr 2021 at 16:15, YueCompl via ghc-devs > wrote: > >> Thanks to Vlad and Jaro, your solution of `apD` compiles, I think it >> should work. >> >> But unfortunately my real case is a little different / more complex, a >> MWE appears like this: >> >> ```hs >> holdEvent :: Dynamic -> Dynamic >> holdEvent (Dynamic t evs') = >> withTypeable t $ Dynamic typeRep (hcHoldEvent evs') >> where >> hcHoldEvent :: forall a. EventSink a -> IO (TimeSeries a) >> hcHoldEvent !evs = do >> !holder <- newIORef Nothing >> listenEvents evs $ writeIORef holder . Just >> return $ TimeSeries $ readIORef holder >> >> data EventSink a = EventSink >> { listenEvents :: (a -> IO ()) -> IO (), >> closeStream :: IO () >> } >> >> instance Functor EventSink where >> fmap = undefined >> >> newtype TimeSeries a = TimeSeries {readTimeSeries :: IO (Maybe a)} >> >> instance Functor TimeSeries where >> fmap = undefined >> >> ``` >> >> Now I'm clueless how to use the `withTypeable` trick to apply my >> polymorphic `hcHoldEvent` to `Dynamic`, naively written as in above, the >> error is: >> >> ```log >> *src/PoC/DynPoly.hs:20:49: **error:* >> • Couldn't match expected type ‘EventSink a0’ with actual type ‘a’ >> ‘a’ is a rigid type variable bound by >> a pattern with constructor: >> Dynamic :: forall a. >> base-4.13.0.0:Data.Typeable.Internal.TypeRep a -> a >> -> Dynamic, >> in an equation for ‘holdEvent’ >> at src/PoC/DynPoly.hs:19:12-25 >> • In the first argument of ‘hcHoldEvent’, namely ‘evs'’ >> In the second argument of ‘Dynamic’, namely ‘(hcHoldEvent evs')’ >> In the second argument of ‘($)’, namely >> ‘Dynamic typeRep (hcHoldEvent evs')’ >> • Relevant bindings include >> evs' :: a (bound at src/PoC/DynPoly.hs:19:22) >> t :: base-4.13.0.0:Data.Typeable.Internal.TypeRep a >> (bound at src/PoC/DynPoly.hs:19:20) >> * |* >> *20 |* withTypeable t $ Dynamic typeRep (hcHoldEvent *evs'*) >> * |** ^^^^* >> >> ``` >> >> Thanks with best regards, >> Compl >> >> >> On 2021-04-12, at 22:04, Jaro Reinders wrote: >> >> I have no experience in this area, but this compiles: >> >> ``` >> {-# LANGUAGE RankNTypes, ScopedTypeVariables #-} >> import Type.Reflection >> import Data.Dynamic >> >> appD :: forall f. Typeable f => (forall a. a -> f a) -> Dynamic -> Dynamic >> appD f (Dynamic rep (x :: a)) = withTypeable rep (toDyn (f x)) >> ``` >> >> Cheers, >> >> Jaro >> >> >> >> On 2021-04-12, at 21:06, Vladislav Zavialov >> wrote: >> >> Would something like this work for you? >> >> import Type.Reflection >> import Data.Dynamic >> >> apD :: Typeable f => (forall a. a -> f a) -> Dynamic -> Dynamic >> apD f (Dynamic t a) = withTypeable t $ Dynamic typeRep (f a) >> >> - Vlad >> >> On 12 Apr 2021, at 14:34, YueCompl via ghc-devs >> wrote: >> >> Dear Cafe and GHC devs, >> >> >> There used to be a "principled way with pattern match on the constructor": >> >> ```hs >> data Dynamic where >> Dynamic :: Typeable a => a -> Dynamic >> >> apD :: Typeable f => (forall a. a -> f a) -> Dynamic -> Dynamic >> apD f (Dynamic a) = Dynamic $ f a >> ``` >> Source: >> https://www.reddit.com/r/haskell/comments/2kdcca/q_how_to_apply_a_polymorphic_function_to_a/ >> >> >> But now with GHC 8.8 as in my case, `Dynamic` constructor has changed its >> signature to: >> >> ```hs >> Dynamic :: forall a. TypeRep a -> a -> Dynamic >> ``` >> >> Which renders the `apD` not working anymore. >> >> >> And it seems missing dependencies now for an older solution Edward KMETT >> provides: >> >> ```hs >> apD :: forall f. Typeable1 f => (forall a. a -> f a) -> Dynamic -> Dynamic >> apD f a = dynApp df a >> where t = dynTypeRep a >> df = reify (mkFunTy t (typeOf1 (undefined :: f ()) `mkAppTy` t)) $ >> \(_ :: Proxy s) -> toDyn (WithRep f :: WithRep s (() -> f >> ())) >> ``` >> Source: >> https://stackoverflow.com/questions/10889682/how-to-apply-a-polymorphic-function-to-a-dynamic-value >> >> >> So, how can I do that nowadays? >> >> Thanks, >> Compl >> >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >> >> >> >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >> > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From eric at seidel.io Tue Apr 13 00:54:37 2021 From: eric at seidel.io (Eric Seidel) Date: Mon, 12 Apr 2021 20:54:37 -0400 Subject: [Haskell-cafe] =?utf-8?q?Generalized=2C_named=2C_and_exportable_d?= =?utf-8?q?efault_declarations_=28GHC_Proposal=29?= Message-ID: <8e10d563-e2d6-4d1b-a9a5-f4b0c485bb23@www.fastmail.com> Hi Cafe, The GHC Steering Committee is considering a proposal that would expand the typeclass defaulting mechanism to support arbitrary (single-parameter) classes, and enable exporting defaulting rules. It's received very little input from the community so far, which is a shame because it's trying to address a common complaint about Haskell's String situation. Under the proposal Data.Text could export a rule defaulting IsString to Text. Client modules would automatically import defaulting rules just like class instances, which would make ambiguous string literals automatically default to Text. Please take a look at the proposal and leave your feedback, even if it's just "Yes, this would make my life meaningfully better" (reaction emoji are great for this level of feedback). Gauging the amount of pain caused by problems like this, and weighing that against the cost of new features, is one of the harder parts of being on the Committee. PR: https://github.com/ghc-proposals/ghc-proposals/pull/409 Rendered: https://github.com/blamario/ghc-proposals/blob/exportable-named-default/proposals/0000-exportable-named-default.rst From rae at richarde.dev Tue Apr 13 02:58:16 2021 From: rae at richarde.dev (Richard Eisenberg) Date: Tue, 13 Apr 2021 02:58:16 +0000 Subject: [Haskell-cafe] Generalized, named, and exportable default declarations (GHC Proposal) In-Reply-To: <8e10d563-e2d6-4d1b-a9a5-f4b0c485bb23@www.fastmail.com> References: <8e10d563-e2d6-4d1b-a9a5-f4b0c485bb23@www.fastmail.com> Message-ID: <010f0178c92a4f1c-36309e8f-b0cf-4fbb-9b11-01adba810e31-000000@us-east-2.amazonses.com> Hi all, Thanks, Eric, for posting this here. I thought it would also be helpful to link to https://github.com/ghc-proposals/ghc-proposals/pull/396 . That proposal describes how a plugin might be designed to help handle defaulting. The proposal was labeled "out of scope" because plugin design is not part of the committee process, but I think it's a good counterpoint to the proposal Eric brought up. There is apparently an implementation of the default plugin scheme and I've encouraged the author to submit it for inclusion in GHC. Thanks, Richard > On Apr 12, 2021, at 8:54 PM, Eric Seidel wrote: > > Hi Cafe, > > The GHC Steering Committee is considering a proposal that would expand the typeclass defaulting mechanism to support arbitrary (single-parameter) classes, and enable exporting defaulting rules. > > It's received very little input from the community so far, which is a shame because it's trying to address a common complaint about Haskell's String situation. Under the proposal Data.Text could export a rule defaulting IsString to Text. Client modules would automatically import defaulting rules just like class instances, which would make ambiguous string literals automatically default to Text. > > Please take a look at the proposal and leave your feedback, even if it's just "Yes, this would make my life meaningfully better" (reaction emoji are great for this level of feedback). Gauging the amount of pain caused by problems like this, and weighing that against the cost of new features, is one of the harder parts of being on the Committee. > > PR: https://github.com/ghc-proposals/ghc-proposals/pull/409 > Rendered: https://github.com/blamario/ghc-proposals/blob/exportable-named-default/proposals/0000-exportable-named-default.rst > _______________________________________________ > 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 Apr 13 09:20:39 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Tue, 13 Apr 2021 11:20:39 +0200 (CEST) Subject: [Haskell-cafe] serialized data structures (Was: Generalized, named, and exportable default declarations) In-Reply-To: <8e10d563-e2d6-4d1b-a9a5-f4b0c485bb23@www.fastmail.com> References: <8e10d563-e2d6-4d1b-a9a5-f4b0c485bb23@www.fastmail.com> Message-ID: We have seen a lot of effort of better integrating Text into Haskell programming. The only purpose of doing so is to replace String by something more space and time efficient. What would happen if we invest equally much time into making String as efficient as Text? At ICFP 2019 I attended a talk about Gibbon: https://github.com/iu-parfunc/gibbon The idea of the project is to serialize (Haskell's) tree data structures in memory as much as possible. Wouldn't this enable us to use String instead of Text, again, maybe even lists instead of Vectors? No more Text integration efforts, no more external library with GHC-specific manual optimizations. Unfortunately, the project is still in an early stage. So far, it only supports strict data structures. What if we would not complicate the language and generalize syntactic sugar for Text, but instead improve data layout for all Haskell types and eventually make a custom Text type unnecessary? From compl.yue at icloud.com Tue Apr 13 14:07:32 2021 From: compl.yue at icloud.com (YueCompl) Date: Tue, 13 Apr 2021 22:07:32 +0800 Subject: [Haskell-cafe] What's the modern way to apply a polymorphic function to a Dynamic value in GHC 8.8 and onwards? In-Reply-To: References: <043B9A36-2014-4E02-9951-CBEC216C3CCA@icloud.com> <7F106DE5-7E92-4D21-BB0A-E7FC4EEE4484@serokell.io> <68E8C92A-9BB2-46FF-8747-C3DD07DA1084@icloud.com> <34A44F73-E4D0-4F1D-BBC1-08A539FAC76A@icloud.com> <15DE054A-5B61-4011-8D1D-9C344072F964@icloud.com> Message-ID: After struggled this far, I decide that I can neither trivially understand `pattern TypeRep`, nor the `withTypeable` at core. But this is what really amazing with Haskell, GHC and the community here - I can get my job done even without full understanding of what's going on under the hood, so long as the compiler says it's okay! The warning has gone due to unknown reason after I refactored the code a bit, surprisingly but well, I feel safe and comfort to use it now. Thanks to Erik, Vlad and Jaro again for your help. u/Iceland_jack made a ticket to [add pattern TypeRep to Type.Reflection](https://gitlab.haskell.org/ghc/ghc/-/issues/19691) and appears it's very welcomed. Though I don't expect it get shipped very soon or even could be back ported to GHC 8.8, so I end up with this shim: (there `PolyKinds` appears some unusual to be put into my `.cabal` due to its syntax change can break some of my existing code) ```hs {-# LANGUAGE PolyKinds #-} module Dyn.Shim ( pattern TypeRep, dynPerformIO, dynPerformSTM, dynContSTM, ) where import Control.Concurrent.STM (STM) import Data.Dynamic (Dynamic (..), Typeable) import Type.Reflection ( TypeRep, eqTypeRep, typeRep, withTypeable, pattern App, type (:~~:) (HRefl), ) import Prelude data TypeableInstance a where TypeableInstance :: Typeable a => TypeableInstance a typeableInstance :: TypeRep a -> TypeableInstance a typeableInstance tr = withTypeable tr TypeableInstance {- ORMOLU_DISABLE -} -- | Shim for the proposed one at: -- https://gitlab.haskell.org/ghc/ghc/-/issues/19691 pattern TypeRep :: forall k (a :: k). () => Typeable a => TypeRep a pattern TypeRep <- (typeableInstance -> TypeableInstance) where TypeRep = typeRep {- ORMOLU_ENABLE -} -- | Perform a polymorphic IO action which is wrapped in a 'Dynamic' -- -- The specified 'naAlt' action will be performed instead, if the wrapped -- computation is not applicable, i.e. not really an IO action. dynPerformIO :: IO Dynamic -> Dynamic -> IO Dynamic dynPerformIO naAlt (Dynamic trAct monotypedAct) = case trAct of App io TypeRep -> case io `eqTypeRep` typeRep @IO of Just HRefl -> Dynamic TypeRep <$> monotypedAct Nothing -> naAlt -- not an IO action _ -> naAlt -- not even a poly-type -- | Perform a polymorphic STM action which is wrapped in a 'Dynamic' -- -- The specified 'naAlt' action will be performed instead, if the wrapped -- computation is not applicable, i.e. not really an STM action. dynPerformSTM :: STM Dynamic -> Dynamic -> STM Dynamic dynPerformSTM naAlt (Dynamic trAct monotypedAct) = case trAct of App io TypeRep -> case io `eqTypeRep` typeRep @STM of Just HRefl -> Dynamic TypeRep <$> monotypedAct Nothing -> naAlt -- not an STM action _ -> naAlt -- not even a poly-type -- | Perform a polymorphic STM action which is wrapped in a 'Dynamic' -- -- The specified 'naAlt' action will be performed instead, if the wrapped -- computation is not applicable, i.e. not really an STM action. dynContSTM :: STM () -> Dynamic -> (Dynamic -> STM ()) -> STM () dynContSTM naAlt (Dynamic trAct monotypedAct) !exit = case trAct of App io TypeRep -> case io `eqTypeRep` typeRep @STM of Just HRefl -> exit . Dynamic TypeRep =<< monotypedAct Nothing -> naAlt -- not an STM action _ -> naAlt -- not even a poly-type ``` And my test case being a little more complex than the very first example, might be easier for others to grasp the usage, it runs like this: ```console λ> import PoC.DynPoly λ> testDynHold First got Nothing Then got Just 3 λ> ``` With the code: ```hs module PoC.DynPoly where import Control.Monad (void) import Data.Dynamic (Dynamic (..), fromDynamic, toDyn) import Data.IORef (modifyIORef', newIORef, readIORef, writeIORef) import Dyn.Shim import Type.Reflection (eqTypeRep, typeRep, pattern App, type (:~~:) (HRefl)) import Prelude dynHoldEvent :: Dynamic -> Dynamic dynHoldEvent (Dynamic trEvs monotypedEvs) = case trEvs of App trEs TypeRep -> case trEs `eqTypeRep` typeRep @EventSink of Just HRefl -> Dynamic TypeRep (holdEvent monotypedEvs) Nothing -> error "not an EventSink" -- to be handled properly _ -> error "even not a poly-type" -- to be handled properly where holdEvent :: forall a. EventSink a -> IO (TimeSeries a) holdEvent !evs = do !holder <- newIORef Nothing listenEvents evs $ writeIORef holder . Just return $ TimeSeries $ readIORef holder data EventSink a = EventSink { listenEvents :: (a -> IO ()) -> IO (), publishEvent :: a -> IO () } newtype TimeSeries a = TimeSeries {readTimeSeries :: IO (Maybe a)} newEventSink :: forall a. IO (EventSink a) newEventSink = do !listeners <- newIORef [] let listen listener = modifyIORef' listeners (listener :) publish a = readIORef listeners >>= void . mapM ($ a) return $ EventSink listen publish testDynHold :: IO () testDynHold = do (evs :: EventSink Int) <- newEventSink let !dynEvs = toDyn evs !dynHold = dynHoldEvent dynEvs !dynTs <- dynPerformIO (error "bug: dyn type mismatch?") dynHold case fromDynamic dynTs of Nothing -> error "bug: unexpected dyn result type" Just (ts :: TimeSeries Int) -> do v0 <- readTimeSeries ts putStrLn $ "First got " <> show v0 publishEvent evs 3 v1 <- readTimeSeries ts putStrLn $ "Then got " <> show v1 ``` Thanks with best regards, Compl > On 2021-04-13, at 02:50, Erik Hesselink wrote: > > That is a lot, I'm not sure I understand that pattern synonym. Using `withTypeable` instead works for me: > > holdEvent :: Dynamic -> Dynamic > holdEvent (Dynamic tr x) = > case tr of > App ft at -> > case ft `eqTypeRep` typeRep @EventSink of > Just HRefl -> withTypeable at $ toDyn (hcHoldEvent x) > Nothing -> error "to handle" > _ -> error "to handle" > > Cheers, > > Erik -------------- next part -------------- An HTML attachment was scrubbed... URL: From compl.yue at icloud.com Tue Apr 13 14:48:40 2021 From: compl.yue at icloud.com (YueCompl) Date: Tue, 13 Apr 2021 22:48:40 +0800 Subject: [Haskell-cafe] What's the modern way to apply a polymorphic function to a Dynamic value in GHC 8.8 and onwards? In-Reply-To: References: <043B9A36-2014-4E02-9951-CBEC216C3CCA@icloud.com> <7F106DE5-7E92-4D21-BB0A-E7FC4EEE4484@serokell.io> <68E8C92A-9BB2-46FF-8747-C3DD07DA1084@icloud.com> <34A44F73-E4D0-4F1D-BBC1-08A539FAC76A@icloud.com> <15DE054A-5B61-4011-8D1D-9C344072F964@icloud.com> Message-ID: <1CF43226-1D48-4411-8EC1-D0A6AC690CA4@icloud.com> A followup wish I have: ```hs case io `eqTypeRep` typeRep @IO of Just HRefl -> Dynamic TypeRep <$> monotypedAct Nothing -> naAlt -- not an IO action ``` The `Just HRefl` part as in above remains hard to understand for me, I had glanced it in doc of the 'Type.Reflection' module earlier, but had no chance to figure out the usage of `eqTypeRep` to be like this, at least on my own. The community is very helpful in this regards, in leading me to it. But may there can be better surface syntax / usage hints that more intuitive, i.e. costing less effort to reach the solution? I anticipate improvements but apparently lack expertise for progress, I tried `Just {}` and it won't compile already... I mean, things are already great as far, well, maybe the learning experience can be made even better. Best, Compl > On 2021-04-13, at 22:07, YueCompl via ghc-devs wrote: > > After struggled this far, I decide that I can neither trivially understand `pattern TypeRep`, nor the `withTypeable` at core. But this is what really amazing with Haskell, GHC and the community here - I can get my job done even without full understanding of what's going on under the hood, so long as the compiler says it's okay! The warning has gone due to unknown reason after I refactored the code a bit, surprisingly but well, I feel safe and comfort to use it now. > > Thanks to Erik, Vlad and Jaro again for your help. > > u/Iceland_jack made a ticket to [add pattern TypeRep to Type.Reflection](https://gitlab.haskell.org/ghc/ghc/-/issues/19691 ) and appears it's very welcomed. Though I don't expect it get shipped very soon or even could be back ported to GHC 8.8, so I end up with this shim: > > (there `PolyKinds` appears some unusual to be put into my `.cabal` due to its syntax change can break some of my existing code) > > ```hs > {-# LANGUAGE PolyKinds #-} > > module Dyn.Shim > ( pattern TypeRep, > dynPerformIO, > dynPerformSTM, > dynContSTM, > ) > where > > import Control.Concurrent.STM (STM) > import Data.Dynamic (Dynamic (..), Typeable) > import Type.Reflection > ( TypeRep, > eqTypeRep, > typeRep, > withTypeable, > pattern App, > type (:~~:) (HRefl), > ) > import Prelude > > data TypeableInstance a where > TypeableInstance :: Typeable a => TypeableInstance a > > typeableInstance :: TypeRep a -> TypeableInstance a > typeableInstance tr = withTypeable tr TypeableInstance > > {- ORMOLU_DISABLE -} > > -- | Shim for the proposed one at: > -- https://gitlab.haskell.org/ghc/ghc/-/issues/19691 > pattern TypeRep :: forall k (a :: k). () => Typeable a => TypeRep a > pattern TypeRep <- (typeableInstance -> TypeableInstance) > where TypeRep = typeRep > > {- ORMOLU_ENABLE -} > > -- | Perform a polymorphic IO action which is wrapped in a 'Dynamic' > -- > -- The specified 'naAlt' action will be performed instead, if the wrapped > -- computation is not applicable, i.e. not really an IO action. > dynPerformIO :: IO Dynamic -> Dynamic -> IO Dynamic > dynPerformIO naAlt (Dynamic trAct monotypedAct) = case trAct of > App io TypeRep -> > case io `eqTypeRep` typeRep @IO of > Just HRefl -> Dynamic TypeRep <$> monotypedAct > Nothing -> naAlt -- not an IO action > _ -> naAlt -- not even a poly-type > > -- | Perform a polymorphic STM action which is wrapped in a 'Dynamic' > -- > -- The specified 'naAlt' action will be performed instead, if the wrapped > -- computation is not applicable, i.e. not really an STM action. > dynPerformSTM :: STM Dynamic -> Dynamic -> STM Dynamic > dynPerformSTM naAlt (Dynamic trAct monotypedAct) = case trAct of > App io TypeRep -> > case io `eqTypeRep` typeRep @STM of > Just HRefl -> Dynamic TypeRep <$> monotypedAct > Nothing -> naAlt -- not an STM action > _ -> naAlt -- not even a poly-type > > -- | Perform a polymorphic STM action which is wrapped in a 'Dynamic' > -- > -- The specified 'naAlt' action will be performed instead, if the wrapped > -- computation is not applicable, i.e. not really an STM action. > dynContSTM :: STM () -> Dynamic -> (Dynamic -> STM ()) -> STM () > dynContSTM naAlt (Dynamic trAct monotypedAct) !exit = case trAct of > App io TypeRep -> > case io `eqTypeRep` typeRep @STM of > Just HRefl -> exit . Dynamic TypeRep =<< monotypedAct > Nothing -> naAlt -- not an STM action > _ -> naAlt -- not even a poly-type > > ``` > > And my test case being a little more complex than the very first example, might be easier for others to grasp the usage, it runs like this: > > ```console > λ> import PoC.DynPoly > λ> testDynHold > First got Nothing > Then got Just 3 > λ> > ``` > > With the code: > > ```hs > module PoC.DynPoly where > > import Control.Monad (void) > import Data.Dynamic (Dynamic (..), fromDynamic, toDyn) > import Data.IORef (modifyIORef', newIORef, readIORef, writeIORef) > import Dyn.Shim > import Type.Reflection (eqTypeRep, typeRep, pattern App, type (:~~:) (HRefl)) > import Prelude > > dynHoldEvent :: Dynamic -> Dynamic > dynHoldEvent (Dynamic trEvs monotypedEvs) = > case trEvs of > App trEs TypeRep -> > case trEs `eqTypeRep` typeRep @EventSink of > Just HRefl -> Dynamic TypeRep (holdEvent monotypedEvs) > Nothing -> error "not an EventSink" -- to be handled properly > _ -> error "even not a poly-type" -- to be handled properly > where > holdEvent :: forall a. EventSink a -> IO (TimeSeries a) > holdEvent !evs = do > !holder <- newIORef Nothing > listenEvents evs $ writeIORef holder . Just > return $ TimeSeries $ readIORef holder > > data EventSink a = EventSink > { listenEvents :: (a -> IO ()) -> IO (), > publishEvent :: a -> IO () > } > > newtype TimeSeries a = TimeSeries {readTimeSeries :: IO (Maybe a)} > > newEventSink :: forall a. IO (EventSink a) > newEventSink = do > !listeners <- newIORef [] > let listen listener = modifyIORef' listeners (listener :) > publish a = readIORef listeners >>= void . mapM ($ a) > return $ EventSink listen publish > > testDynHold :: IO () > testDynHold = do > (evs :: EventSink Int) <- newEventSink > let !dynEvs = toDyn evs > !dynHold = dynHoldEvent dynEvs > !dynTs <- dynPerformIO (error "bug: dyn type mismatch?") dynHold > case fromDynamic dynTs of > Nothing -> error "bug: unexpected dyn result type" > Just (ts :: TimeSeries Int) -> do > v0 <- readTimeSeries ts > putStrLn $ "First got " <> show v0 > publishEvent evs 3 > v1 <- readTimeSeries ts > putStrLn $ "Then got " <> show v1 > ``` > > Thanks with best regards, > Compl > > >> On 2021-04-13, at 02:50, Erik Hesselink > wrote: >> >> That is a lot, I'm not sure I understand that pattern synonym. Using `withTypeable` instead works for me: >> >> holdEvent :: Dynamic -> Dynamic >> holdEvent (Dynamic tr x) = >> case tr of >> App ft at -> >> case ft `eqTypeRep` typeRep @EventSink of >> Just HRefl -> withTypeable at $ toDyn (hcHoldEvent x) >> Nothing -> error "to handle" >> _ -> error "to handle" >> >> Cheers, >> >> Erik > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs -------------- next part -------------- An HTML attachment was scrubbed... URL: From blamario at rogers.com Tue Apr 13 14:58:33 2021 From: blamario at rogers.com (Mario) Date: Tue, 13 Apr 2021 10:58:33 -0400 Subject: [Haskell-cafe] serialized data structures (Was: Generalized, named, and exportable default declarations) In-Reply-To: References: <8e10d563-e2d6-4d1b-a9a5-f4b0c485bb23@www.fastmail.com> Message-ID: <00bda0ab-24fb-85de-0d72-26fb4b2528e9@rogers.com> On 2021-04-13 5:20 a.m., Henning Thielemann wrote: > > We have seen a lot of effort of better integrating Text into Haskell > programming. The only purpose of doing so is to replace String by > something more space and time efficient. What would happen if we > invest equally much time into making String as efficient as Text? At > ICFP 2019 I attended a talk about Gibbon: > >    https://github.com/iu-parfunc/gibbon > > The idea of the project is to serialize (Haskell's) tree data > structures in memory as much as possible. Wouldn't this enable us to > use String instead of Text, again, maybe even lists instead of > Vectors? No more Text integration efforts, no more external library > with GHC-specific manual optimizations. Unfortunately, the project is > still in an early stage. So far, it only supports strict data structures. I don't want to be unfair to the project without investigating it closer, but my feeling is that it goes against the spirit of the times. There's been some disillusionment with the shortcut fusion, rule-based rewriting, and similar advanced techniques. It's probably been inevitable that, as GHC slowly shifts from research and teaching to industrial use, the community would get jaded with amazing but flukey research results and put more value on boring predictability instead. Unless Gibbon can make String perform *consistently* as efficient as Text, I don't see the project gaining adoption. From borgauf at gmail.com Tue Apr 13 16:30:10 2021 From: borgauf at gmail.com (Galaxy Being) Date: Tue, 13 Apr 2021 11:30:10 -0500 Subject: [Haskell-cafe] Haskell function composition commutivity? Message-ID: I'm in chapter 4 of Bird's very interesting *Thinking Functionally with Haskell *and he has a problem at the end of the chapter where he lists these equations map f . take n = take n . map f map f . reverse = reverse . map f map f . sort = sort . map f map f . filter p = map fst . filter snd . map (fork (f,p)) filter (p . g) = map (invertg) . filter p . map g reverse . concat = concat . reverse . map reverse filter p . concat = concat . map (filter p) adding this caveat for the 3rd equation iff x <= y <=> f x <= f y and this for the 4th equation fork (f,g) x = (f x, g x) and for the 5th invertg satisfies invertg . g = id My confusion is over the commutative-ness of most of this but only anecdotally. With the particularly dense map f . filter p = map fst . filter snd . map (fork (f,p)) We have > :t (map myF . filter myP) Integral b => [b] -> [b] > :t (map fst . filter snd . map (myFork (myF,myP))) Integral b => [b] -> [b] Is there anything universal to be drawn from these anecdotal examples of seeming commutativity? My breakdown of the third equation shows the same type definition for both sides. Is this a way to find equality? All in all, Bird doesn't indicate that there are any underlying truths, just "almost" commutativity. LB -------------- next part -------------- An HTML attachment was scrubbed... URL: From ietf-dane at dukhovni.org Tue Apr 13 17:06:41 2021 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Tue, 13 Apr 2021 13:06:41 -0400 Subject: [Haskell-cafe] Haskell function composition commutivity? In-Reply-To: References: Message-ID: On Tue, Apr 13, 2021 at 11:30:10AM -0500, Galaxy Being wrote: > Is there anything universal to be drawn from these anecdotal examples of > seeming commutativity? My breakdown of the third equation shows the same > type definition for both sides. Is this a way to find equality? All in all, > Bird doesn't indicate that there are any underlying truths, just "almost" > commutativity. Yes, but the answer is likely some combination of parametricity and the Yoneda Lemma. - Parametricity: Given two fuctors f and g and some function `foo` with type signature: foo :: forall a. f a -> g a we can conclude that `foo` is a "natural transformation", which means that for all functions `bar`, we have: foo . fmap bar = fmap bar . foo - Yoneda Lemma: Given a functor f and some function `foo` with signature: foo :: forall a. (a -> b) -> f b we can conclude that for all `bar :: a -> b`: foo bar = fmap bar (foo id) It is interesting that you used the word "universal", because that's the right word to describe some of the underlying category theory notions. -- Viktor. From ietf-dane at dukhovni.org Tue Apr 13 17:29:58 2021 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Tue, 13 Apr 2021 13:29:58 -0400 Subject: [Haskell-cafe] Haskell function composition commutivity? In-Reply-To: References: Message-ID: On Tue, Apr 13, 2021 at 01:06:41PM -0400, Viktor Dukhovni wrote: > - Yoneda Lemma: Given a functor f and some function `foo` > with signature: > > foo :: forall a. (a -> b) -> f b Sorry, typo, should be: foo :: forall b. (a -> b) -> f b -- Viktor. From x at tomsmeding.com Tue Apr 13 18:02:06 2021 From: x at tomsmeding.com (Tom Smeding) Date: Tue, 13 Apr 2021 18:02:06 +0000 Subject: [Haskell-cafe] Haskell function composition commutivity? In-Reply-To: References: Message-ID: <9e5bf04c-3adc-4634-c9b6-b7571cb01127@tomsmeding.com> (Viktor: sorry for the duplicate...) Does it make a difference? To me the following function type signatures mean exactly the same thing: foo :: (a -> b) -> f b foo :: forall a. (a -> b) -> f b foo :: forall b. (a -> b) -> f b foo :: forall a b. (a -> b) -> f b This of course changes when the `forall` is put inside the parentheses (though I don't think you meant that -- but I'm not a category theorist), or if ScopedTypeVariables is used nontrivially, or... etc. Although, because of the fact that you omitted 'Functor f =>' and instead chose to write the constraint in prose beforehand, I get the feeling that you may be speaking mathematically, not about Haskell as compiled by GHC. - Tom On 13/04/2021 19:29, Viktor Dukhovni wrote: > > On Tue, Apr 13, 2021 at 01:06:41PM -0400, Viktor Dukhovni wrote: > >> - Yoneda Lemma: Given a functor f and some function `foo` >> with signature: >> >> foo :: forall a. (a -> b) -> f b > > Sorry, typo, should be: > > foo :: forall b. (a -> b) -> f b > > -- > 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 ietf-dane at dukhovni.org Tue Apr 13 18:14:48 2021 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Tue, 13 Apr 2021 14:14:48 -0400 Subject: [Haskell-cafe] Haskell function composition commutivity? In-Reply-To: <9e5bf04c-3adc-4634-c9b6-b7571cb01127@tomsmeding.com> References: <9e5bf04c-3adc-4634-c9b6-b7571cb01127@tomsmeding.com> Message-ID: <721ACCDE-5656-4307-86CF-5F47057475CD@dukhovni.org> > On Apr 13, 2021, at 2:02 PM, Tom Smeding wrote: > > Although, because of the fact that you omitted 'Functor f =>' and > instead chose to write the constraint in prose beforehand, I get the > feeling that you may be speaking mathematically, not about Haskell as > compiled by GHC. Yes, mathematically, with Haskell-like syntax. Also the functors in question were intended to stand for specific functors, rather than be universally quantified. So perhaps better: Yoneda (with A some type and F some functor): foo :: forall b. (A -> b) -> F b <=> foo bar = fmap bar (foo (id @A) -- Viktor. From borgauf at gmail.com Tue Apr 13 19:19:46 2021 From: borgauf at gmail.com (Galaxy Being) Date: Tue, 13 Apr 2021 14:19:46 -0500 Subject: [Haskell-cafe] Haskell function composition commutivity? In-Reply-To: <721ACCDE-5656-4307-86CF-5F47057475CD@dukhovni.org> References: <9e5bf04c-3adc-4634-c9b6-b7571cb01127@tomsmeding.com> <721ACCDE-5656-4307-86CF-5F47057475CD@dukhovni.org> Message-ID: Your answers seem to originate outside of normal Haskell tutorials. Where can I start with this higher superset theory? On Tue, Apr 13, 2021 at 1:19 PM Viktor Dukhovni wrote: > > On Apr 13, 2021, at 2:02 PM, Tom Smeding wrote: > > > > Although, because of the fact that you omitted 'Functor f =>' and > > instead chose to write the constraint in prose beforehand, I get the > > feeling that you may be speaking mathematically, not about Haskell as > > compiled by GHC. > > Yes, mathematically, with Haskell-like syntax. Also the > functors in question were intended to stand for specific > functors, rather than be universally quantified. > > So perhaps better: > > Yoneda (with A some type and F some functor): > > foo :: forall b. (A -> b) -> F b > > <=> foo bar = fmap bar (foo (id @A) > > -- > Viktor. > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From olf at aatal-apotheke.de Tue Apr 13 19:36:35 2021 From: olf at aatal-apotheke.de (Olaf Klinke) Date: Tue, 13 Apr 2021 21:36:35 +0200 Subject: [Haskell-cafe] serialized data structures (Was: Generalized, named, and exportable default declarations) Message-ID: <8681bead28e44d9a52c9247e25c5eaf88f2c66f1.camel@aatal-apotheke.de> > We have seen a lot of effort of better integrating Text into Haskell > programming. The only purpose of doing so is to replace String by > something more space and time efficient. What would happen if we invest > equally much time into making String as efficient as Text? At ICFP 2019 I > attended a talk about Gibbon: > > https://github.com/iu-parfunc/gibbon > > The idea of the project is to serialize (Haskell's) tree data structures > in memory as much as possible. Wouldn't this enable us to use String > instead of Text, again, maybe even lists instead of Vectors? No more Text > integration efforts, no more external library with GHC-specific manual > optimizations. Unfortunately, the project is still in an early stage. So > far, it only supports strict data structures. > > What if we would not complicate the language and generalize syntactic > sugar for Text, but instead improve data layout for all Haskell types and > eventually make a custom Text type unnecessary? So essentially Gibbon's aim is to make String work like Text under the hood, without me having to worry about it? +1 for that! Probably I should not comment on this, because I know too little about compilers and serialization. But having to expect something like OverloadedStrings for arbitrary type classes, plus which effect import statements have on this, puts extra cognitive load on the programmer. In contrast, the direction taken by Gibbon removes worries, namely: How much memory penalty do I pay by using this easy-to-understand algebraic data type instead of a more low-level compact representation? I love GHC specifically for its ability to perform many optimizations that Icould not have come up with. Indeed the GHC devs should strive to make the default [*] types work better, as this aligns with the mission of the Haskell Foundation to promote and widen adoption of Haskell. Olaf [*] "default" as dictated by the language report. From lemming at henning-thielemann.de Tue Apr 13 20:23:06 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Tue, 13 Apr 2021 22:23:06 +0200 (CEST) Subject: [Haskell-cafe] serialized data structures (Was: Generalized, named, and exportable default declarations) In-Reply-To: <8681bead28e44d9a52c9247e25c5eaf88f2c66f1.camel@aatal-apotheke.de> References: <8681bead28e44d9a52c9247e25c5eaf88f2c66f1.camel@aatal-apotheke.de> Message-ID: <6a55b3ec-7854-5b41-623-6d3f8376a697@henning-thielemann.de> On Tue, 13 Apr 2021, Olaf Klinke wrote: >> What if we would not complicate the language and generalize syntactic >> sugar for Text, but instead improve data layout for all Haskell types and >> eventually make a custom Text type unnecessary? > > So essentially Gibbon's aim is to make String work like Text under the > hood, without me having to worry about it? +1 for that! In principle yes. I think the idea is the following: Linked data structures were invented decades ago in order to easily perform in-place updates, e.g. insert and remove elements from lists and trees. However, in Haskell we do not allow in-place modifications and copying a data structure is not much more expensive than traversing it. But if we copy the whole tree anyway why do we still need pointers? We have to acknowledge that linked lists come with some costs. A linked list with elements spread across memory have cache-unfriendly access patterns. In contrast to that a serialized tree is compact in memory and very cache friendly. You can still access a subtree without copying. Yet, linked data structures allow sharing of sub-trees or common list tails. For this case we still need pointers. But maybe not as many as today. Gibbon solves this by using two alternative internal identifiers for every data constructor: One for an embedded subtree and one for a pointer to a subtree. This way a list or a String could be hold in one memory chunk or it could be effectively a linked list of chunks or a linked list of single characters if required. From compl.yue at icloud.com Tue Apr 13 20:27:21 2021 From: compl.yue at icloud.com (YueCompl) Date: Wed, 14 Apr 2021 04:27:21 +0800 Subject: [Haskell-cafe] serialized data structures (Was: Generalized, named, and exportable default declarations) In-Reply-To: <00bda0ab-24fb-85de-0d72-26fb4b2528e9@rogers.com> References: <8e10d563-e2d6-4d1b-a9a5-f4b0c485bb23@www.fastmail.com> <00bda0ab-24fb-85de-0d72-26fb4b2528e9@rogers.com> Message-ID: <1EFF8F8E-1E22-4E7C-BCDE-F762A27F3B55@icloud.com> I suggest it won't need to be as efficient as Text, just reasonable efficient will suffice. C++'s mantra of “you don’t pay for what you don’t use” is overly emphasizing on the machine aspect on today's stand point, as machine price (hardware purchase, energy consumption for the run, time to result) descending and human price (programmer / analyst / management mental overhead, time to production deployment, bug tracking & resolution, maintenance & service) ascending, more and more orgs will be willing to pay reasonably more on machines to save the cost on humans. GHC / Haskell's unique trade off w.r.t. optimization may be the new sweet spot in coming years as I feel it. > On 2021-04-13, at 22:58, Mario wrote: > > On 2021-04-13 5:20 a.m., Henning Thielemann wrote: >> >> We have seen a lot of effort of better integrating Text into Haskell programming. The only purpose of doing so is to replace String by something more space and time efficient. What would happen if we invest equally much time into making String as efficient as Text? At ICFP 2019 I attended a talk about Gibbon: >> >> https://github.com/iu-parfunc/gibbon >> >> The idea of the project is to serialize (Haskell's) tree data structures in memory as much as possible. Wouldn't this enable us to use String instead of Text, again, maybe even lists instead of Vectors? No more Text integration efforts, no more external library with GHC-specific manual optimizations. Unfortunately, the project is still in an early stage. So far, it only supports strict data structures. > > > I don't want to be unfair to the project without investigating it closer, but my feeling is that it goes against the spirit of the times. There's been some disillusionment with the shortcut fusion, rule-based rewriting, and similar advanced techniques. It's probably been inevitable that, as GHC slowly shifts from research and teaching to industrial use, the community would get jaded with amazing but flukey research results and put more value on boring predictability instead. Unless Gibbon can make String perform *consistently* as efficient as Text, I don't see the project gaining adoption. > > > _______________________________________________ > 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 Tue Apr 13 21:37:54 2021 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Tue, 13 Apr 2021 17:37:54 -0400 Subject: [Haskell-cafe] Haskell function composition commutivity? In-Reply-To: References: <9e5bf04c-3adc-4634-c9b6-b7571cb01127@tomsmeding.com> <721ACCDE-5656-4307-86CF-5F47057475CD@dukhovni.org> Message-ID: On Tue, Apr 13, 2021 at 02:19:46PM -0500, Galaxy Being wrote: > Your answers seem to originate outside of normal Haskell tutorials. Where > can I start with this higher superset theory? There's a reason why the tutorials don't cover this, the categorical foundations of Haskell types are not beginner material. It is perhaps best to defer going down this rabbit hole until you're more comfortable with the Haskell generally. You could start with: https://bartoszmilewski.com/2014/10/28/category-theory-for-programmers-the-preface/ https://bartoszmilewski.com/2015/04/07/natural-transformations/ For the Yoneda Lemma specifically, I'd recommend: http://blog.sigfpe.com/2006/11/yoneda-lemma.html Parametricity is covered in "Theorems for free": https://www2.cs.sfu.ca/CourseCentral/831/burton/Notes/July14/free.pdf but it is by no means elementary, though skimming it for the essential facts and skipping the gory details is not too difficult. You could also read "Categories for the Working Mathematician" by Saunders Mac Lane. -- Viktor. From carter.schonwald at gmail.com Tue Apr 13 22:45:23 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Tue, 13 Apr 2021 18:45:23 -0400 Subject: [Haskell-cafe] serialized data structures (Was: Generalized, named, and exportable default declarations) In-Reply-To: <1EFF8F8E-1E22-4E7C-BCDE-F762A27F3B55@icloud.com> References: <8e10d563-e2d6-4d1b-a9a5-f4b0c485bb23@www.fastmail.com> <00bda0ab-24fb-85de-0d72-26fb4b2528e9@rogers.com> <1EFF8F8E-1E22-4E7C-BCDE-F762A27F3B55@icloud.com> Message-ID: Indeed. I think there’s a few viable directions folks are exploring on the string front. As for rules based optimization, I think that there’s room for more robust systems, eg can any of the ideas in for example the egraphs good paper from popl 2021 or the associated egg library be adapted to allow for more robust optimization in ghc or similar language for fusion? I suspect yes, but with some serious work around cost model and how unfolding is done (we shouldn’t need to inline to allow fusion that results in choosing to inline!) On Tue, Apr 13, 2021 at 4:30 PM YueCompl via Haskell-Cafe < haskell-cafe at haskell.org> wrote: > I suggest it won't need to be as efficient as Text, just reasonable > efficient will suffice. > > C++'s mantra of “you don’t pay for what you don’t use” is overly > emphasizing on the machine aspect on today's stand point, as machine price > (hardware purchase, energy consumption for the run, time to result) > descending and human price (programmer / analyst / management mental > overhead, time to production deployment, bug tracking & resolution, > maintenance & service) ascending, more and more orgs will be willing to pay > reasonably more on machines to save the cost on humans. > > GHC / Haskell's unique trade off w.r.t. optimization may be the new sweet > spot in coming years as I feel it. > > > On 2021-04-13, at 22:58, Mario wrote: > > > > On 2021-04-13 5:20 a.m., Henning Thielemann wrote: > >> > >> We have seen a lot of effort of better integrating Text into Haskell > programming. The only purpose of doing so is to replace String by something > more space and time efficient. What would happen if we invest equally much > time into making String as efficient as Text? At ICFP 2019 I attended a > talk about Gibbon: > >> > >> https://github.com/iu-parfunc/gibbon > >> > >> The idea of the project is to serialize (Haskell's) tree data > structures in memory as much as possible. Wouldn't this enable us to use > String instead of Text, again, maybe even lists instead of Vectors? No more > Text integration efforts, no more external library with GHC-specific manual > optimizations. Unfortunately, the project is still in an early stage. So > far, it only supports strict data structures. > > > > > > I don't want to be unfair to the project without investigating it > closer, but my feeling is that it goes against the spirit of the times. > There's been some disillusionment with the shortcut fusion, rule-based > rewriting, and similar advanced techniques. It's probably been inevitable > that, as GHC slowly shifts from research and teaching to industrial use, > the community would get jaded with amazing but flukey research results and > put more value on boring predictability instead. Unless Gibbon can make > String perform *consistently* as efficient as Text, I don't see the project > gaining adoption. > > > > > > _______________________________________________ > > Haskell-Cafe mailing list > > To (un)subscribe, modify options or view archives go to: > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > Only members subscribed via the mailman list are allowed to post. > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From compl.yue at icloud.com Wed Apr 14 07:41:04 2021 From: compl.yue at icloud.com (YueCompl) Date: Wed, 14 Apr 2021 15:41:04 +0800 Subject: [Haskell-cafe] serialized data structures (Was: Generalized, named, and exportable default declarations) In-Reply-To: References: <8e10d563-e2d6-4d1b-a9a5-f4b0c485bb23@www.fastmail.com> <00bda0ab-24fb-85de-0d72-26fb4b2528e9@rogers.com> <1EFF8F8E-1E22-4E7C-BCDE-F762A27F3B55@icloud.com> Message-ID: As for text handling: [There Ain’t No Such Thing As Plain Text.](https://www.joelonsoftware.com/2003/10/08/the-absolute-minimum-every-software-developer-absolutely-positively-must-know-about-unicode-and-character-sets-no-excuses) [What Every Programmer Absolutely, Positively Needs To Know About Encodings And Character Sets To Work With Text](https://kunststube.net/encoding) Just some random hits from google search, thanks to globalization, variable-byte-width and even variable-byte-order is the norm today, I see package text hasn't catchup yet: http://hackage.haskell.org/package/text > Currently the text library uses UTF-16 as its internal representation which is neither a fixed-width nor always the most dense representation for Unicode text. We're currently investigating the feasibility of changing Text's internal representation to UTF-8 and if you need such a Text type right now you might be interested in using the spin-off packages text-utf8 and text-short. I do think Haskell can excel at managing compact annotative data structures around raw utf-8 bytes as the major payload, and foster sophisticated manipulation APIs beyond counting and slicing with the out-dated fixed-width character assumption. > On 2021-04-14, at 06:45, Carter Schonwald wrote: > > Indeed. > > I think there’s a few viable directions folks are exploring on the string front. > > As for rules based optimization, I think that there’s room for more robust systems, eg can any of the ideas in for example the egraphs good paper from popl 2021 or the associated egg library be adapted to allow for more robust optimization in ghc or similar language for fusion? I suspect yes, but with some serious work around cost model and how unfolding is done (we shouldn’t need to inline to allow fusion that results in choosing to inline!) > > On Tue, Apr 13, 2021 at 4:30 PM YueCompl via Haskell-Cafe wrote: > I suggest it won't need to be as efficient as Text, just reasonable efficient will suffice. > > C++'s mantra of “you don’t pay for what you don’t use” is overly emphasizing on the machine aspect on today's stand point, as machine price (hardware purchase, energy consumption for the run, time to result) descending and human price (programmer / analyst / management mental overhead, time to production deployment, bug tracking & resolution, maintenance & service) ascending, more and more orgs will be willing to pay reasonably more on machines to save the cost on humans. > > GHC / Haskell's unique trade off w.r.t. optimization may be the new sweet spot in coming years as I feel it. > > > On 2021-04-13, at 22:58, Mario wrote: > > > > On 2021-04-13 5:20 a.m., Henning Thielemann wrote: > >> > >> We have seen a lot of effort of better integrating Text into Haskell programming. The only purpose of doing so is to replace String by something more space and time efficient. What would happen if we invest equally much time into making String as efficient as Text? At ICFP 2019 I attended a talk about Gibbon: > >> > >> https://github.com/iu-parfunc/gibbon > >> > >> The idea of the project is to serialize (Haskell's) tree data structures in memory as much as possible. Wouldn't this enable us to use String instead of Text, again, maybe even lists instead of Vectors? No more Text integration efforts, no more external library with GHC-specific manual optimizations. Unfortunately, the project is still in an early stage. So far, it only supports strict data structures. > > > > > > I don't want to be unfair to the project without investigating it closer, but my feeling is that it goes against the spirit of the times. There's been some disillusionment with the shortcut fusion, rule-based rewriting, and similar advanced techniques. It's probably been inevitable that, as GHC slowly shifts from research and teaching to industrial use, the community would get jaded with amazing but flukey research results and put more value on boring predictability instead. Unless Gibbon can make String perform *consistently* as efficient as Text, I don't see the project gaining adoption. > > > > > > _______________________________________________ > > 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 olf at aatal-apotheke.de Wed Apr 14 12:01:43 2021 From: olf at aatal-apotheke.de (Olaf Klinke) Date: Wed, 14 Apr 2021 14:01:43 +0200 Subject: [Haskell-cafe] serialized data structures (Was: Generalized, named, and exportable default declarations) In-Reply-To: <6a55b3ec-7854-5b41-623-6d3f8376a697@henning-thielemann.de> References: <8681bead28e44d9a52c9247e25c5eaf88f2c66f1.camel@aatal-apotheke.de> <6a55b3ec-7854-5b41-623-6d3f8376a697@henning-thielemann.de> Message-ID: <2e373f6bf45827da6b05c24cce4d055d6dde1ee6.camel@aatal-apotheke.de> On Tue, 2021-04-13 at 22:23 +0200, Henning Thielemann wrote: > On Tue, 13 Apr 2021, Olaf Klinke wrote: > > > > What if we would not complicate the language and generalize syntactic > > > sugar for Text, but instead improve data layout for all Haskell types and > > > eventually make a custom Text type unnecessary? > > > > So essentially Gibbon's aim is to make String work like Text under the > > hood, without me having to worry about it? +1 for that! > > In principle yes. > > I think the idea is the following: Linked data structures were invented > decades ago in order to easily perform in-place updates, e.g. insert and > remove elements from lists and trees. However, in Haskell we do not allow > in-place modifications and copying a data structure is not much more > expensive than traversing it. But if we copy the whole tree anyway why do > we still need pointers? We have to acknowledge that linked lists come with > some costs. A linked list with elements spread across memory have > cache-unfriendly access patterns. In contrast to that a serialized tree is > compact in memory and very cache friendly. You can still access a subtree > without copying. > > Yet, linked data structures allow sharing of sub-trees or common list > tails. For this case we still need pointers. But maybe not as many as > today. Gibbon solves this by using two alternative internal identifiers > for every data constructor: One for an embedded subtree and one for a > pointer to a subtree. > > This way a list or a String could be hold in one memory chunk or it could > be effectively a linked list of chunks or a linked list of single > characters if required. Aha. So when I bind ys = tail xs where xs is compactly represented in memory, then the memory representation of xs is broken up into (head xs : ys) where ys is still compactly represented? I'm thinking procedurally here, which is probably not the way the compliler handles things. How does this relate to "compact regions"? I remember an announcement to this list not so long ago. Olaf From dominic at steinitz.org Wed Apr 14 12:42:18 2021 From: dominic at steinitz.org (Dominic Steinitz) Date: Wed, 14 Apr 2021 13:42:18 +0100 Subject: [Haskell-cafe] Haskell function composition commutivity? In-Reply-To: References: Message-ID: <219DA72A-8CDD-4100-8819-BB5F75328AF3@steinitz.org> I’d recommend *not* reading Categories for the Working Mathematician unless you are a mathematician (lots of background assumed) and even then it’s a bit of a dull read. Dominic Steinitz dominic at steinitz.org http://idontgetoutmuch.org Twitter: @idontgetoutmuch > From: Viktor Dukhovni > To: haskell-cafe at haskell.org > Subject: Re: [Haskell-cafe] Haskell function composition commutivity? > Message-ID: > Content-Type: text/plain; charset=us-ascii > > On Tue, Apr 13, 2021 at 02:19:46PM -0500, Galaxy Being wrote: > >> Your answers seem to originate outside of normal Haskell tutorials. Where >> can I start with this higher superset theory? > > There's a reason why the tutorials don't cover this, the categorical > foundations of Haskell types are not beginner material. It is perhaps > best to defer going down this rabbit hole until you're more comfortable > with the Haskell generally. > > You could start with: > > https://bartoszmilewski.com/2014/10/28/category-theory-for-programmers-the-preface/ > https://bartoszmilewski.com/2015/04/07/natural-transformations/ > > For the Yoneda Lemma specifically, I'd recommend: > > http://blog.sigfpe.com/2006/11/yoneda-lemma.html > > Parametricity is covered in "Theorems for free": > > https://www2.cs.sfu.ca/CourseCentral/831/burton/Notes/July14/free.pdf > > but it is by no means elementary, though skimming it for the essential > facts and skipping the gory details is not too difficult. > > You could also read "Categories for the Working Mathematician" by > Saunders Mac Lane. -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Wed Apr 14 19:11:52 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Wed, 14 Apr 2021 15:11:52 -0400 Subject: [Haskell-cafe] Haskell function composition commutivity? In-Reply-To: <219DA72A-8CDD-4100-8819-BB5F75328AF3@steinitz.org> References: <219DA72A-8CDD-4100-8819-BB5F75328AF3@steinitz.org> Message-ID: Agreed! I’ve actually never met somone who suggests it as either a starter or advanced reference e On Wed, Apr 14, 2021 at 8:43 AM Dominic Steinitz wrote: > I’d recommend *not* reading Categories for the Working Mathematician > unless you are a mathematician (lots of background assumed) and even then > it’s a bit of a dull read. > > Dominic Steinitz > dominic at steinitz.org > http://idontgetoutmuch.org > Twitter: @idontgetoutmuch > > From: Viktor Dukhovni > To: haskell-cafe at haskell.org > Subject: Re: [Haskell-cafe] Haskell function composition commutivity? > Message-ID: > Content-Type: text/plain; charset=us-ascii > > On Tue, Apr 13, 2021 at 02:19:46PM -0500, Galaxy Being wrote: > > Your answers seem to originate outside of normal Haskell tutorials. Where > can I start with this higher superset theory? > > > There's a reason why the tutorials don't cover this, the categorical > foundations of Haskell types are not beginner material. It is perhaps > best to defer going down this rabbit hole until you're more comfortable > with the Haskell generally. > > You could start with: > > > https://bartoszmilewski.com/2014/10/28/category-theory-for-programmers-the-preface/ > https://bartoszmilewski.com/2015/04/07/natural-transformations/ > > For the Yoneda Lemma specifically, I'd recommend: > > http://blog.sigfpe.com/2006/11/yoneda-lemma.html > > Parametricity is covered in "Theorems for free": > > https://www2.cs.sfu.ca/CourseCentral/831/burton/Notes/July14/free.pdf > > but it is by no means elementary, though skimming it for the essential > facts and skipping the gory details is not too difficult. > > You could also read "Categories for the Working Mathematician" by > Saunders Mac Lane. > > > _______________________________________________ > 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 joshchia at gmail.com Thu Apr 15 04:32:16 2021 From: joshchia at gmail.com (=?UTF-8?B?4piCSm9zaCBDaGlhICjorJ3ku7vkuK0p?=) Date: Thu, 15 Apr 2021 12:32:16 +0800 Subject: [Haskell-cafe] How to move files? Message-ID: I'm trying to write to a temp file in /tmp and then move it to another location that may be in /tmp. If I use System.Directory.renameFile and the final location is in another filesystem, I'll get an error "renameFile:renamePath:rename: unsupported operation (Invalid cross-device link)". If I copy to the new location and then remove the temp file, but the new location is also in /tmp, I am doing an unnecessary copy (instead of mv), which is inefficient. I don't know how to detect whether two filepaths are in the same filesystem. What's the best way to move the file if possible but copy-and-delete if necessary? Josh -------------- next part -------------- An HTML attachment was scrubbed... URL: From kane at kane.cx Thu Apr 15 04:40:36 2021 From: kane at kane.cx (David Kraeutmann) Date: Thu, 15 Apr 2021 00:40:36 -0400 Subject: [Haskell-cafe] How to move files? In-Reply-To: References: Message-ID: <7fa25329-edb3-d42b-ee89-405101c9cd33@kane.cx> The source code to mv.c might be useful: https://github.com/coreutils/coreutils/blob/master/src/mv.c On 4/15/21 12:32 AM, ☂Josh Chia (謝任中) wrote: > I'm trying to write to a temp file in /tmp and then move it to another > location that may be in /tmp. > > If I use System.Directory.renameFile and the final location is in > another filesystem, I'll get an error "renameFile:renamePath:rename: > unsupported operation (Invalid cross-device link)". > > If I copy to the new location and then remove the temp file, but the > new location is also in /tmp, I am doing an unnecessary copy (instead > of mv), which is inefficient. > > I don't know how to detect whether two filepaths are in the same > filesystem. > > What's the best way to move the file if possible but copy-and-delete > if necessary? > > Josh > > _______________________________________________ > 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 jack.kelly at bellroy.com Thu Apr 15 04:57:47 2021 From: jack.kelly at bellroy.com (Jack Kelly) Date: Thu, 15 Apr 2021 14:57:47 +1000 Subject: [Haskell-cafe] [ANN] wai-handler-hal-0.1.0.0 - Wrap a WAI Application to run on AWS Lambda Message-ID: I have just pushed an initial release of wai-handler-hal[1] to Hackage. This library lets you run `wai` `Application`s on AWS Lambda, using the proxy integration features of an API Gateway REST API. This allows you to write your APIs using tools like `servant`, test them locally using `warp`, and then build deployment binaries using `hal`. There's an especially nice payoff when you use `servant`: it's very easy to test the entire API locally using `warp`, but then split endpoints into individual Lambda binaries. This means you can assign minimal IAM policies to each Lambda when you deploy to AWS. The library code, an example API, example deployment code (in AWS CDK[2]), and extensive documentation are all available on GitHub[3]; bug reports and pull requests are welcome. Best, -- Jack [1]: https://hackage.haskell.org/package/wai-handler-hal-0.1.0.0 [2]: https://aws.amazon.com/cdk/ [3]: https://github.com/bellroy/wai-handler-hal From donn at avvanta.com Thu Apr 15 05:08:20 2021 From: donn at avvanta.com (Donn Cave) Date: Wed, 14 Apr 2021 22:08:20 -0700 (PDT) Subject: [Haskell-cafe] How to move files? In-Reply-To: <7fa25329-edb3-d42b-ee89-405101c9cd33@kane.cx> References: <7fa25329-edb3-d42b-ee89-405101c9cd33@kane.cx> Message-ID: <20210415050820.B7CAF276D64@mail.avvanta.com> >> I don't know how to detect whether two filepaths are in the same >> filesystem. Yes you do! >> If I use System.Directory.renameFile and the final location is in >> another filesystem, I'll get an error "renameFile:renamePath:rename: >> unsupported operation (Invalid cross-device link)". And it follows that if you get no error, the two filepaths are in the same filesystem >> What's the best way to move the file if possible but copy-and-delete >> if necessary? Catch that error, and copy-and-delete. Donn From compl.yue at icloud.com Thu Apr 15 07:46:51 2021 From: compl.yue at icloud.com (YueCompl) Date: Thu, 15 Apr 2021 15:46:51 +0800 Subject: [Haskell-cafe] How to move files? In-Reply-To: <20210415050820.B7CAF276D64@mail.avvanta.com> References: <7fa25329-edb3-d42b-ee89-405101c9cd33@kane.cx> <20210415050820.B7CAF276D64@mail.avvanta.com> Message-ID: > Catch that error, and copy-and-delete. I suggest this is typical EAFP (Easier to ask for forgiveness than permission) coding style from Zen of Python http://docs.python.org//glossary.html#term-eafp I'm very curious to know how Haskellers think and do about it? Is there something close to Zen of Haskell? > On 2021-04-15, at 13:08, Donn Cave wrote: > >>> I don't know how to detect whether two filepaths are in the same >>> filesystem. > > Yes you do! > >>> If I use System.Directory.renameFile and the final location is in >>> another filesystem, I'll get an error "renameFile:renamePath:rename: >>> unsupported operation (Invalid cross-device link)". > > And it follows that if you get no error, the two filepaths are in the > same filesystem > >>> What's the best way to move the file if possible but copy-and-delete >>> if necessary? > > Catch that error, and copy-and-delete. > > Donn > _______________________________________________ > 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 daniel.trstenjak at gmail.com Thu Apr 15 08:23:34 2021 From: daniel.trstenjak at gmail.com (Daniel Trstenjak) Date: Thu, 15 Apr 2021 10:23:34 +0200 Subject: [Haskell-cafe] How to move files? In-Reply-To: References: Message-ID: <20210415082334.GA4585@octa> Hi Josh, the fastest and safest way is to create the temporary file in the directory of the final location and then move the file to its final name. This way you ensure that the temporary file is always on the same device or partition as the final file and therefore a move is always possible. And it's the safest, because a move is an atomic operation - which copy isn't - and therefore other processes will never see a partially updated file. Greetings, Daniel From svenpanne at gmail.com Thu Apr 15 09:05:25 2021 From: svenpanne at gmail.com (Sven Panne) Date: Thu, 15 Apr 2021 11:05:25 +0200 Subject: [Haskell-cafe] How to move files? In-Reply-To: <20210415082334.GA4585@octa> References: <20210415082334.GA4585@octa> Message-ID: Am Do., 15. Apr. 2021 um 10:24 Uhr schrieb Daniel Trstenjak < daniel.trstenjak at gmail.com>: > And it's the safest, because a move is an atomic operation [...] ... unless you are on Windows. ;-) -------------- next part -------------- An HTML attachment was scrubbed... URL: From compl.yue at icloud.com Thu Apr 15 09:27:16 2021 From: compl.yue at icloud.com (YueCompl) Date: Thu, 15 Apr 2021 17:27:16 +0800 Subject: [Haskell-cafe] How to move files? In-Reply-To: References: <20210415082334.GA4585@octa> Message-ID: <2FA7ECE4-0542-4EB5-B7A7-6054FEFA4AC4@icloud.com> I'm not sure you need this, but on shared filesystem (nfs e.g.), to implement generate-on-demand fashioned data production with parallelism, a trick is to create a temporary directory that exclusively named by your particular run of the critical section of the code. Expect failure from the os in creation of a generated name in location where your final file would go, to ensure same filesystem, and decorate it (with the value from a local counter e.g.) to not appear as the ultimately desired path/name - if failed, try another name; otherwise you succeeded, you are sure this dir is exclusive per your current execution thread, then generate the data (which would take time) and put the payload into a file inside this dir, then fsync to make sure the storage is permanent, then rename it to the ultimate file path/name you'd like it to be. Maybe another parallel process did the same thing and race to overwrite your production, that'll be fine as long as the file data generation algorithm holds some invariant, you'll never have a corrupted/incomplete file on the expected path/name this way. I suggest this is never a Haskell thing but os tricks per se. > On 2021-04-15, at 17:05, Sven Panne wrote: > > Am Do., 15. Apr. 2021 um 10:24 Uhr schrieb Daniel Trstenjak >: > And it's the safest, because a move is an atomic operation [...] > > ... unless you are on Windows. ;-) > _______________________________________________ > 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 joshchia at gmail.com Thu Apr 15 09:27:57 2021 From: joshchia at gmail.com (=?UTF-8?B?4piCSm9zaCBDaGlhICjorJ3ku7vkuK0p?=) Date: Thu, 15 Apr 2021 17:27:57 +0800 Subject: [Haskell-cafe] How to move files? In-Reply-To: <20210415082334.GA4585@octa> References: <20210415082334.GA4585@octa> Message-ID: That would work but may not be the most efficient in all cases. On many systems, /tmp is a tmpfs, which being memory-backed is more efficient than a file on a physical disk or network, so writing to /tmp has performance advantages. On Thu, Apr 15, 2021 at 4:23 PM Daniel Trstenjak wrote: > Hi Josh, > > the fastest and safest way is to create the temporary file in the > directory of the final location and then move the file to its final name. > > This way you ensure that the temporary file is always on the same device > or partition as the final file and therefore a move is always possible. > > And it's the safest, because a move is an atomic operation - which copy > isn't - and therefore other processes will never see a partially updated > file. > > Greetings, > Daniel > -------------- next part -------------- An HTML attachment was scrubbed... URL: From sven.bartscher at weltraumschlangen.de Thu Apr 15 09:58:17 2021 From: sven.bartscher at weltraumschlangen.de (Sven Bartscher) Date: Thu, 15 Apr 2021 11:58:17 +0200 Subject: [Haskell-cafe] How to move files? In-Reply-To: References: <20210415082334.GA4585@octa> Message-ID: Hi, Am 15.04.21 um 11:27 schrieb ☂Josh Chia (謝任中): > That would work but may not be the most efficient in all cases. On many > systems, /tmp is a tmpfs, which being memory-backed is more efficient > than a file on a physical disk or network, so writing to /tmp has > performance advantages. This isn't necessarily relevant in the case the OP describes. In the case where the target directory is also on tmpfs, writing there directly is just as fast as writing to /tmp first. In the case where the target directory is on a slower medium it is not more efficient to write to /tmp first, because you will still have the performance penalty once you copy from /tmp to the target directory. The latter case might be slower if you first write something to the file and later overwrite parts of it with other content or if you decide that you don't need the file at all and just delete it instead of copying it. But you can prevent even those performance penalties by not calling fsync (or close) on the open file before the file contains exactly the data you ultimately want. That way the written content will not actually be written to the medium before fsync is called and you get pretty much the same performance as writing on tmpfs. Though controlling when fsync is called might be tricky if the file is not produced by your own code. I'm also not sure if Haskell calls fsync implicitly in some cases other than closing the file descriptor. Regards Sven -------------- next part -------------- A non-text attachment was scrubbed... Name: OpenPGP_signature Type: application/pgp-signature Size: 833 bytes Desc: OpenPGP digital signature URL: From daniel.trstenjak at gmail.com Thu Apr 15 11:00:23 2021 From: daniel.trstenjak at gmail.com (Daniel Trstenjak) Date: Thu, 15 Apr 2021 13:00:23 +0200 Subject: [Haskell-cafe] How to move files? In-Reply-To: References: <20210415082334.GA4585@octa> Message-ID: <20210415110023.GA23797@octa> On Thu, Apr 15, 2021 at 11:05:25AM +0200, Sven Panne wrote: > Am Do., 15. Apr. 2021 um 10:24 Uhr schrieb Daniel Trstenjak : > > And it's the safest, because a move is an atomic operation [...] > > > ... unless you are on Windows. ;-) I thought it is if you ensure that the move is done on the same device or partition. Greetings, Daniel From compl.yue at icloud.com Thu Apr 15 12:54:20 2021 From: compl.yue at icloud.com (YueCompl) Date: Thu, 15 Apr 2021 20:54:20 +0800 Subject: [Haskell-cafe] Trick to have existential type work in this case? Message-ID: <679DF502-F8BF-42DE-8DFA-AA7226208A31@icloud.com> Dear Cafe, I believe there should exist some trick that I haven't learned, to have this compile: module PoC.Existential where import Data.Dynamic import qualified Data.Vector.Storable as VS import Foreign import Prelude -- * Necessary artifacts data Series a = Series { seriesLen :: IO Int, readSeries :: Int -> IO a } data SomeArray = forall a. (Typeable a, VS.Storable a) => SomeArray { arrayCap :: Int, arrayPtr :: ForeignPtr a } class ManagedArray t where arrayAtTheMoment :: t -> IO SomeArray data SomeManagedArray = forall t. (Typeable t, ManagedArray t) => SomeManagedArray t In following, I can confirm it works with the nested `do` block flattened (as shown later), but I really need it in the more complex real case, so please bear with me. -- * Things not working managedArrayAsSeries :: SomeManagedArray -> IO Dynamic managedArrayAsSeries (SomeManagedArray ma) = do vec <- do SomeArray cap fp <- arrayAtTheMoment ma return $ VS.unsafeFromForeignPtr0 fp cap let len = return $ VS.length vec rs i = return $ vec VS.! i return $ toDyn $ Series len rs The error: src/PoC/Existential.hs:36:5: error: • Couldn't match type ‘a’ with ‘a0’ ‘a’ is a rigid type variable bound by a pattern with constructor: SomeArray :: forall a. (Typeable a, Storable a) => Int -> ForeignPtr a -> SomeArray, in a pattern binding in a 'do' block at src/PoC/Existential.hs:35:5-20 Expected type: IO (VS.Vector a0) Actual type: IO (VS.Vector a) • In a stmt of a 'do' block: return $ VS.unsafeFromForeignPtr0 fp cap In a stmt of a 'do' block: vec <- do SomeArray cap fp <- arrayAtTheMoment ma return $ VS.unsafeFromForeignPtr0 fp cap In the expression: do vec <- do SomeArray cap fp <- arrayAtTheMoment ma return $ VS.unsafeFromForeignPtr0 fp cap let len = return $ VS.length vec rs i = return $ vec VS.! i return $ toDyn $ Series len rs • Relevant bindings include fp :: ForeignPtr a (bound at src/PoC/Existential.hs:35:19) | 36 | return $ VS.unsafeFromForeignPtr0 fp cap | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ While these more trivial things work as expected: -- * Things working managedArrayAsSeries' :: SomeManagedArray -> IO Dynamic managedArrayAsSeries' (SomeManagedArray ma) = do SomeArray cap fp <- arrayAtTheMoment ma let vec = VS.unsafeFromForeignPtr0 fp cap let len = return $ VS.length vec rs i = return $ vec VS.! i return $ toDyn $ Series len rs arrayAsSeries :: SomeArray -> Dynamic arrayAsSeries (SomeArray cap fp) = colAsSeries $ SomeColumn $ VS.unsafeFromForeignPtr0 fp cap arrayAsSeries' :: SomeArray -> Dynamic arrayAsSeries' (SomeArray cap fp) = do let vec = VS.unsafeFromForeignPtr0 fp cap len = return $ VS.length vec rs i = return $ vec VS.! i toDyn $ Series len rs data SomeColumn = forall a. (Typeable a, VS.Storable a) => SomeColumn (VS.Vector a) colAsSeries :: SomeColumn -> Dynamic colAsSeries (SomeColumn colVec) = toDyn $ Series len rs where len = return $ VS.length colVec rs i = return $ colVec VS.! i Please teach me the trick! Thanks with regards, Compl -------------- next part -------------- An HTML attachment was scrubbed... URL: From benjamin.redelings at gmail.com Thu Apr 15 14:10:56 2021 From: benjamin.redelings at gmail.com (Benjamin Redelings) Date: Thu, 15 Apr 2021 10:10:56 -0400 Subject: [Haskell-cafe] GLR parser for Haskell? Message-ID: Hi, I've been looking at the Haskell parser in ghc/compiler/GHC/Parser.y.  It relies on post-processing pretty heavily, both to determine the type of parsed expressions (i.e. is "(x,y)" a pattern or expression?) and to reject invalid syntax (i.e. field declarations are parsed as a type, but this is rejected during postprocessing I think, except in constructor declarations). This makes the grammar rather hard to read.  To quote [1]: > Insteadof describingthe languageto be parsed,thegrammardescribes > theprocessused to parseit; it'smore like a hand-crafted parsing > program,butcrammed into Backus-Naur Form. Does anybody know if there is another version of the parser generator uses grammar rules that are closer to the grammar rules in the 2010 report?  Maybe a GLR grammar? Also, I see that Happy is able to generate GLR parsers.  I'm curious if GLR parsers aren't being used just because they are slow, or if there is some other reason they are hard to use.  I am not an expert on parsing or grammars, so any insight would be appreciated. Thanks! -BenRI [1] https://escholarship.org/uc/item/8559j464 -------------- next part -------------- An HTML attachment was scrubbed... URL: From svenpanne at gmail.com Thu Apr 15 14:14:20 2021 From: svenpanne at gmail.com (Sven Panne) Date: Thu, 15 Apr 2021 16:14:20 +0200 Subject: [Haskell-cafe] How to move files? In-Reply-To: <20210415110023.GA23797@octa> References: <20210415082334.GA4585@octa> <20210415110023.GA23797@octa> Message-ID: Am Do., 15. Apr. 2021 um 13:00 Uhr schrieb Daniel Trstenjak < daniel.trstenjak at gmail.com>: > On Thu, Apr 15, 2021 at 11:05:25AM +0200, Sven Panne wrote: > > Am Do., 15. Apr. 2021 um 10:24 Uhr schrieb Daniel Trstenjak < > daniel.trstenjak at gmail.com>: > > > > And it's the safest, because a move is an atomic operation [...] > > > > > > ... unless you are on Windows. ;-) > > I thought it is if you ensure that the move is done on the same device > or partition. > Which "move" do you mean? ReplaceFileA's return code exposes various levels of non-atomicity ( https://docs.microsoft.com/en-us/windows/win32/api/winbase/nf-winbase-replacefilea) and Transactional NTFS (e.g. MoveFileTransactedA) has already been deprecated ( https://docs.microsoft.com/en-us/windows/win32/fileio/deprecation-of-txf). Perhaps there are other, even more arcane variations on this conceptually simple operation on Windows, but I don't know... Supporting this madness in a cross-platform way is even more interesting. -------------- next part -------------- An HTML attachment was scrubbed... URL: From lemming at henning-thielemann.de Thu Apr 15 14:20:33 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Thu, 15 Apr 2021 16:20:33 +0200 (CEST) Subject: [Haskell-cafe] How to move files? In-Reply-To: References: <7fa25329-edb3-d42b-ee89-405101c9cd33@kane.cx> <20210415050820.B7CAF276D64@mail.avvanta.com> Message-ID: On Thu, 15 Apr 2021, YueCompl via Haskell-Cafe wrote: > > Catch that error, and copy-and-delete. > I suggest this is typical EAFP (Easier to ask for forgiveness than permission) coding style from Zen of Python > http://docs.python.org//glossary.html#term-eafp > > I'm very curious to know how Haskellers think and do about it? I think this is independent from the language. With regard to file operations you must use the exception-catching style, because if you check first and operate then, it might be that in the short time between someone alters the files or directories. From donn at avvanta.com Thu Apr 15 15:21:38 2021 From: donn at avvanta.com (Donn Cave) Date: Thu, 15 Apr 2021 08:21:38 -0700 (PDT) Subject: [Haskell-cafe] How to move files? In-Reply-To: References: <7fa25329-edb3-d42b-ee89-405101c9cd33@kane.cx><20210415050820.B7CAF276D64@mail.avvanta.com> Message-ID: <20210415152138.5DA48276C48@mail.avvanta.com> quoth YueCompl > > Catch that error, and copy-and-delete. > > I suggest this is typical EAFP (Easier to ask for forgiveness than permission) coding style from Zen of Python > http://docs.python.org//glossary.html#term-eafp > > I'm very curious to know how Haskellers think and do about it? > > Is there something close to Zen of Haskell? For another example, I quote from my man page for access(2), which can be used to determine if the caller has the necessary privilege etc. - " The result of access() should not be used to make an actual access control decision, since its response, even if correct at the moment it is formed, may be outdated at the time you act on it. access() results should only be used to pre-flight, such as when configuring user interface elements or for optimization purposes. The actual access control decision should be made by attempting to execute the relevant system call while holding the applicable credentials, and properly handling any resulting errors; and this must be done even though access() may have predicted success." That particular consideration doesn't apply so much to this case, that I can see anyway, but as a model for how to deal with situations like this it seems sound to me, as long as the operation can be trusted to either work or fail inexpensively and without side effects. You make the intended functionality the main program path; you handle failures as you see fit. However, I have to say, it appears to be less of a Haskell option than in most computer programming languages I'm familiar with. main = catchIOError (rename oldFile newFile) (\ e -> print (ioeGetErrorType e)) ... all I get out of that is "unsupported operation". I see no way to get to the POSIX error value, EXDEV, which isn't one of the few common errors that has a documented Haskell test. In OCaml for example, the well known errors are all enumerated (including EXDEV), but if you need to handle one that isn't, there's EUNKNOWNERR with a value. A casual look at the documentation suggests that while I can catch this error, Haskell doesn't give me the means to identify it. To make the most of my appearance here on haskell-cafe ... I find the notion of a "Zen" of this or that language kind of awkward. I suppose it's one of those usages that has taken on its own diluted popular meaning that has few traces of the original (goes back to "Zen in the Art of Archery"? I don't know.) But as little as the term may intend to refer the actual religious practice, that religious practice is a real thing with many adherents, a complicated doctrine with various schools, a lot of priests - and one where I find it very hard to recognize the appication to computer programming. Donn From godzbanebane at gmail.com Thu Apr 15 15:55:56 2021 From: godzbanebane at gmail.com (Georgi Lyubenov) Date: Thu, 15 Apr 2021 18:55:56 +0300 Subject: [Haskell-cafe] GLR parser for Haskell? In-Reply-To: References: Message-ID: Hi! I think the updated tree sitter grammar might be relevant to you - https://github.com/tree-sitter/tree-sitter-haskell Cheers, ====== Georgi -------------- next part -------------- An HTML attachment was scrubbed... URL: From ietf-dane at dukhovni.org Thu Apr 15 16:42:06 2021 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Thu, 15 Apr 2021 12:42:06 -0400 Subject: [Haskell-cafe] How to move files? In-Reply-To: References: Message-ID: On Thu, Apr 15, 2021 at 12:32:16PM +0800, ☂Josh Chia (謝任中) wrote: > What's the best way to move the file if possible but copy-and-delete if > necessary? The `conduit` package has `sinkFileCautious` that creates a temporary file in the target directory, deletes it if an exception is thrown, but otherwise renames the temp file to the requested name on success. https://hackage.haskell.org/package/conduit-1.3.4.1/docs/Conduit.html#v:sinkFileCautious There are fancier things one can do on Linux systems with unnamed temporary files created via openat(2), that can be linked into the target directory only when ready via linkat(2), but this is not particularly portable, and not even supported by all Linux filesystems. AFAIK there is not possible to avoid a narrow window during which the temporary file exists under a transient name, because linkat(2) does not provide a way to atomically replace the target if it exists. So the calling sequence is (with appropriate error checks, not shown): fd = openat(dirfd, ...|O_TMPFILE, mode); write(fd, ...); ... write(fd, ...); (void) unlink("file.tmp"); linkat(fd, "", dirfd, "file.tmp", AT_EMPTY_PATH); renameat(dirfd, "file.tmp", dirfd, "file"); -- Viktor. From trebla at vex.net Thu Apr 15 18:27:18 2021 From: trebla at vex.net (Albert Y. C. Lai) Date: Thu, 15 Apr 2021 14:27:18 -0400 Subject: [Haskell-cafe] Trick to have existential type work in this case? In-Reply-To: <679DF502-F8BF-42DE-8DFA-AA7226208A31@icloud.com> References: <679DF502-F8BF-42DE-8DFA-AA7226208A31@icloud.com> Message-ID: <30722cde-7fe0-659c-3fa6-d3ebb397f269@vex.net> On 2021-04-15 8:54 a.m., YueCompl via Haskell-Cafe wrote: > -- * Things not working > managedArrayAsSeries::SomeManagedArray->IODynamic > managedArrayAsSeries (SomeManagedArrayma)=do > vec <-do > SomeArraycap fp <-arrayAtTheMoment ma > return $VS.unsafeFromForeignPtr0 fp cap > letlen =return $VS.length vec > rs i =return $vec VS.!i > return $toDyn $Serieslen rs That means you have this code fragment: arrayAtTheMoment ma >>= \(SomeArray cap fp) -> return $ VS.unsafeFromForeignPtr0 fp cap That means you have this function: \(SomeArray cap fp) -> return $ VS.unsafeFromForeignPtr0 fp cap Now you are violating the 1st restriction at https://downloads.haskell.org/ghc/latest/docs/html/users_guide/exts/existential_quantification.html#restrictions There are two solutions. 1st solution: One more existential type. data Vec = forall a. (Typeable a, VS.Storable a) => Vec (VS.Vector a) Vec vec <- do SomeArray cap fp <- arrayAtTheMoment ma return (Vec (VS.unsafeFromForeignPtr0 fp cap)) 2nd solution: CPS transform. {-# language RankNTypes #-} {-# language BlockArguments #-} withSomeArray :: SomeArray -> (forall a. (Typeable a, VS.Storable a) => Int -> ForeignPtr a -> r) -> r withSomeArray (SomeArray i p) f = f i p sa <- arrayAtTheMoment ma withSomeArray sa \cap fp -> do let vec = VS.unsafeFromForeignPtr0 fp cap -- or if you prefer: vec <- return (VS.unsafeFromForeignPtr0 fp cap) len = return (VS.length vec) rs i = return (vec VS.! i) etc. -------------- next part -------------- An HTML attachment was scrubbed... URL: From rae at richarde.dev Fri Apr 16 19:02:47 2021 From: rae at richarde.dev (Richard Eisenberg) Date: Fri, 16 Apr 2021 19:02:47 +0000 Subject: [Haskell-cafe] Safe Haskell? Message-ID: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> Hi café, Do you use Safe Haskell? Do you know someone who does? If you do, which of Safe Haskell's guarantees do you rely on? Here, a user of Safe Haskell is someone who relies on any guarantees that Safe Haskell provides, not someone who makes sure to have the right pragmas, etc., in your library so that users can import it Safely. Context: Safe Haskell is not lightweight to support within GHC and the ecosystem. Despite being a formidable research project with a (in my opinion) quite worthwhile goal, it's unclear which of Safe Haskell's purported guarantees are actually guaranteed by GHC. (The lack of unsafeCoerce is not actually guaranteed: https://gitlab.haskell.org/ghc/ghc/-/issues/9562 .) Recent design questions about what should be Safe and what shouldn't be (somehow cannot find the discussion after a few minutes of searching; perhaps fill this in) have been answered only by stabs in the dark. The status quo is causing pain: https://gitlab.haskell.org/ghc/ghc/-/issues/19590 . There are hundreds (maybe thousands) of lines of delicate logic within GHC to support Safe Haskell. These parts of GHC have to be read, understood, and maintained by people with limited time. I thus wonder about deprecating and eventually removing Safe Haskell. I don't have a concrete plan for how to do this yet, but I'm confident we could come up with a migration strategy. The set of people who would win by removing Safe Haskell is easy enough to discover. But this email is intended to discover who would be harmed by doing so. If you know, speak up. Otherwise, I expect I will write up a GHC proposal to remove the feature. Thanks, Richard -------------- next part -------------- An HTML attachment was scrubbed... URL: From cdsmith at gmail.com Fri Apr 16 19:31:20 2021 From: cdsmith at gmail.com (Chris Smith) Date: Fri, 16 Apr 2021 15:31:20 -0400 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> Message-ID: I do not object! I did use SafeHaskell long ago, to provide a server that executed student code in a class. It lasted for a year or so, and caused me great anxiety because I was never entirely sure that it was really safe. At a minimum, it required a bunch of extra logic at build time, careful monitoring of resource usage, etc. I now believe that this use case is far better served by virtualization, which is now a quite well-supported feature across all major operating systems. It would be a big mistake for someone today to try to accomplish with SafeHaskell what is better accomplished with a virtual machine. On Fri, Apr 16, 2021 at 3:07 PM Richard Eisenberg wrote: > Hi café, > > Do you use Safe Haskell? Do you know someone who does? If you do, which of > Safe Haskell's guarantees do you rely on? > > Here, a user of Safe Haskell is someone who relies on any guarantees that > Safe Haskell provides, not someone who makes sure to have the right > pragmas, etc., in your library so that users can import it Safely. > > Context: Safe Haskell is not lightweight to support within GHC and the > ecosystem. Despite being a formidable research project with a (in my > opinion) quite worthwhile goal, it's unclear which of Safe Haskell's > purported guarantees are actually guaranteed by GHC. (The lack of > unsafeCoerce is not actually guaranteed: > https://gitlab.haskell.org/ghc/ghc/-/issues/9562.) Recent design > questions about what should be Safe and what shouldn't be (somehow cannot > find the discussion after a few minutes of searching; perhaps fill this in) > have been answered only by stabs in the dark. The status quo is causing > pain: https://gitlab.haskell.org/ghc/ghc/-/issues/19590. There are > hundreds (maybe thousands) of lines of delicate logic within GHC to support > Safe Haskell. These parts of GHC have to be read, understood, and > maintained by people with limited time. > > I thus wonder about deprecating and eventually removing Safe Haskell. I > don't have a concrete plan for how to do this yet, but I'm confident we > could come up with a migration strategy. > > The set of people who would win by removing Safe Haskell is easy enough to > discover. But this email is intended to discover who would be harmed by > doing so. If you know, speak up. Otherwise, I expect I will write up a GHC > proposal to remove the feature. > > Thanks, > Richard > _______________________________________________ > 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 tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Fri Apr 16 19:38:04 2021 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Fri, 16 Apr 2021 20:38:04 +0100 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> Message-ID: <20210416193804.GN968@cloudinit-builder> On Fri, Apr 16, 2021 at 03:31:20PM -0400, Chris Smith wrote: > I did use SafeHaskell long ago, to provide a server that executed > student code in a class ... I now believe that this use case is far > better served by virtualization, which is now a quite well-supported > feature across all major operating systems. Tangentially I'd like to plug an excellent resource for this that I recently discovered: > NsJail is a process isolation tool for Linux. It utilizes Linux > namespace subsystem, resource limits, and the seccomp-bpf syscall > filters of the Linux kernel. https://github.com/google/nsjail/#overview It's an extremely impressive program! It allows isolation of system resources at a very fine-grained level. Tom From bertram.felgenhauer at googlemail.com Sat Apr 17 13:03:26 2021 From: bertram.felgenhauer at googlemail.com (Bertram Felgenhauer) Date: Sat, 17 Apr 2021 15:03:26 +0200 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> Message-ID: Richard Eisenberg wrote: > Hi café, > > Do you use Safe Haskell? Do you know someone who does? If you do, which > of Safe Haskell's guarantees do you rely on? Yes. lambdabot's evaluation mechanism is essentially designed around Safe Haskell: expressions being evaluated are wrapped in `show`, so there's nothing triggering IO actions from outside. Safe Haskell (barring bugs or evil libraries) ensures that there's no unsafePerformIO nor unsafeCoerce to break the type system, so there's no way to perform arbitrary IO actions inside pure code. The libraries are curated, so evil libraries have not been an issue. As for bugs, there have been holes in Typeable in the past, but currently I believe they're closed, except for the use of MD5 as a hash function (but that may require ~2^64 hash operations to exploit because it's hashing UTF-16 data, rendering the existing differential path collision attacks useless... as far as I know, nobody has done this yet). Preventing the use of Template Haskell is another aspect that lambdabot relies on. Nowadays, lambdabot (as deployed on Freenode) also uses a sandbox for evaluation, but I'm thinking of that as a second line of defense rather than the primary mechanism for keeping things safe. So I'd be sad to see SafeHaskell go away. Cheers, Bertram From rae at richarde.dev Sat Apr 17 14:55:04 2021 From: rae at richarde.dev (Richard Eisenberg) Date: Sat, 17 Apr 2021 14:55:04 +0000 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> Message-ID: <010f0178e053fd66-c174480a-f10a-4a41-9827-3ad6b4be6023-000000@us-east-2.amazonses.com> Hi Bertram, Thanks for speaking up here. I feel like I'm missing something I should know, but how does Safe help you? Looking at the lambdabot docs, users cannot import their own modules, and you describe the libraries as curated. So, presumably, that's enough to keep unsafeCoerce and unsafePerformIO from being in scope. Along similar lines, I don't see a way in lambdabot to enable extensions, so Template Haskell is not an issue for you (I believe). Maybe the role of Safe is in helping you curate your libraries? That is, you can use the Safety of a module in determining whether or not it should be imported. That is indeed helpful. Is that it, though? Does enabling -XSafe when compiling user-supplied code catch some scenarios that would be uncaught otherwise? Thanks for educating me about this -- it's important to know how the feature is being used if we are going to maintain it. Richard > On Apr 17, 2021, at 9:03 AM, Bertram Felgenhauer via Haskell-Cafe wrote: > > Richard Eisenberg wrote: >> Hi café, >> >> Do you use Safe Haskell? Do you know someone who does? If you do, which >> of Safe Haskell's guarantees do you rely on? > > Yes. lambdabot's evaluation mechanism is essentially designed around > Safe Haskell: expressions being evaluated are wrapped in `show`, so > there's nothing triggering IO actions from outside. > > Safe Haskell (barring bugs or evil libraries) ensures that there's no > unsafePerformIO nor unsafeCoerce to break the type system, so there's > no way to perform arbitrary IO actions inside pure code. > > The libraries are curated, so evil libraries have not been an issue. > > As for bugs, there have been holes in Typeable in the past, but > currently I believe they're closed, except for the use of MD5 as a > hash function (but that may require ~2^64 hash operations to exploit > because it's hashing UTF-16 data, rendering the existing differential > path collision attacks useless... as far as I know, nobody has done > this yet). > > Preventing the use of Template Haskell is another aspect that > lambdabot relies on. > > Nowadays, lambdabot (as deployed on Freenode) also uses a sandbox for > evaluation, but I'm thinking of that as a second line of defense > rather than the primary mechanism for keeping things safe. > > So I'd be sad to see SafeHaskell go away. > > 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. From david.feuer at gmail.com Sat Apr 17 15:56:28 2021 From: david.feuer at gmail.com (David Feuer) Date: Sat, 17 Apr 2021 11:56:28 -0400 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> Message-ID: There's really only one situation where I've personally felt I needed something like Safe Haskell—and Safe Haskell doesn't deliver it. Specifically, it's very hard to know whether it's safe to use a particular class method at a particular type. On Fri, Apr 16, 2021, 3:03 PM Richard Eisenberg wrote: > Hi café, > > Do you use Safe Haskell? Do you know someone who does? If you do, which of > Safe Haskell's guarantees do you rely on? > > Here, a user of Safe Haskell is someone who relies on any guarantees that > Safe Haskell provides, not someone who makes sure to have the right > pragmas, etc., in your library so that users can import it Safely. > > Context: Safe Haskell is not lightweight to support within GHC and the > ecosystem. Despite being a formidable research project with a (in my > opinion) quite worthwhile goal, it's unclear which of Safe Haskell's > purported guarantees are actually guaranteed by GHC. (The lack of > unsafeCoerce is not actually guaranteed: > https://gitlab.haskell.org/ghc/ghc/-/issues/9562.) Recent design > questions about what should be Safe and what shouldn't be (somehow cannot > find the discussion after a few minutes of searching; perhaps fill this in) > have been answered only by stabs in the dark. The status quo is causing > pain: https://gitlab.haskell.org/ghc/ghc/-/issues/19590. There are > hundreds (maybe thousands) of lines of delicate logic within GHC to support > Safe Haskell. These parts of GHC have to be read, understood, and > maintained by people with limited time. > > I thus wonder about deprecating and eventually removing Safe Haskell. I > don't have a concrete plan for how to do this yet, but I'm confident we > could come up with a migration strategy. > > The set of people who would win by removing Safe Haskell is easy enough to > discover. But this email is intended to discover who would be harmed by > doing so. If you know, speak up. Otherwise, I expect I will write up a GHC > proposal to remove the feature. > > Thanks, > Richard > _______________________________________________ > 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 bertram.felgenhauer at googlemail.com Sat Apr 17 16:08:44 2021 From: bertram.felgenhauer at googlemail.com (Bertram Felgenhauer) Date: Sat, 17 Apr 2021 18:08:44 +0200 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: <010f0178e053fd66-c174480a-f10a-4a41-9827-3ad6b4be6023-000000@us-east-2.amazonses.com> References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> <010f0178e053fd66-c174480a-f10a-4a41-9827-3ad6b4be6023-000000@us-east-2.amazonses.com> Message-ID: Dear Richard, > Thanks for speaking up here. I feel like I'm missing something I > should know, but how does Safe help you? Looking at the lambdabot > docs, users cannot import their own modules, and you describe the > libraries as curated. So, presumably, that's enough to keep > unsafeCoerce and unsafePerformIO from being in scope. Along similar > lines, I don't see a way in lambdabot to enable extensions, so > Template Haskell is not an issue for you (I believe). Lambdabot maintains a Haskell source file (the pristine version can be seen here, for example): https://silicon.int-e.eu/lambdabot/State/Pristine.hs There's an @let command that can add to that source file, and while the name suggests that it is for adding definitions, it can also add imports. So one can try @let import System.IO.Unsafe which is currently blocked by SafeHaskell: .L.hs:140:1: error: System.IO.Unsafe: Can't be safely imported! The use of @let for importing modulues probably not documented anywhere, but it is occasionally demonstrated on the #haskell IRC channel. You're right about Template Haskell though. @let doesn't allow adding new language pragmas. > Maybe the role of Safe is in helping you curate your libraries? That > is, you can use the Safety of a module in determining whether or not > it should be imported. That is indeed helpful. Is that it, though? > Does enabling -XSafe when compiling user-supplied code catch some > scenarios that would be uncaught otherwise? There are two ways in which Safe Haskell helps with curation. First, the import restriction that helps @let also helps with adding new permanent imports to Pristine.hs in pretty much the same way; a module that can be safely imported should not break the type system or allow "pure" functions that do arbitrary IO. But Safe Haskell also helps on a package level, since we have two tiers of trust: - for untrusted packages, modules are only regarded as safe if their safety is inferred, and the inference mechanism is strong enough to propagate the two safety criteria lambdabot cares about (type safety, and lack of arbitrary IO ala unsafePerformIO). So just installing a package without trusting it requires little review (one can still worry about all the things a package can do during installation, through configure, Setup.hs or Template Haskell...) For trivial packages this can be good enough. (Sometimes it isn't for stupid reasons like IsList only being available through the Unsafe GHC.Exts module.) - for trusted packages, at least one can focus ones attention to modules marked Trustworthy. How much this helps depends very much on the package; all imports of a Trustworthy package may have to be reviewed as well. Because of this, the real curation happens at the level of packages to be trusted; adding an untrusted package requires far less attention. Cheers, Bertram From carter.schonwald at gmail.com Sat Apr 17 16:11:19 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sat, 17 Apr 2021 12:11:19 -0400 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: <010f0178e053fd66-c174480a-f10a-4a41-9827-3ad6b4be6023-000000@us-east-2.amazonses.com> References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> <010f0178e053fd66-c174480a-f10a-4a41-9827-3ad6b4be6023-000000@us-east-2.amazonses.com> Message-ID: I think safe Haskell is largely meant for exactly stuff like lambda bot. One gotcha that I’ve seen come up when people use it ... safe Haskell modules disable all rewrite rules (trustworthy doesn’t). And I’ve seen folks mark a module in their benchmarks as safe... and I suppose they didn’t understand the implications of that. On Sat, Apr 17, 2021 at 10:59 AM Richard Eisenberg wrote: > Hi Bertram, > > Thanks for speaking up here. I feel like I'm missing something I should > know, but how does Safe help you? Looking at the lambdabot docs, users > cannot import their own modules, and you describe the libraries as curated. > So, presumably, that's enough to keep unsafeCoerce and unsafePerformIO from > being in scope. Along similar lines, I don't see a way in lambdabot to > enable extensions, so Template Haskell is not an issue for you (I believe). > > Maybe the role of Safe is in helping you curate your libraries? That is, > you can use the Safety of a module in determining whether or not it should > be imported. That is indeed helpful. Is that it, though? Does enabling > -XSafe when compiling user-supplied code catch some scenarios that would be > uncaught otherwise? > > Thanks for educating me about this -- it's important to know how the > feature is being used if we are going to maintain it. > > Richard > > > On Apr 17, 2021, at 9:03 AM, Bertram Felgenhauer via Haskell-Cafe < > haskell-cafe at haskell.org> wrote: > > > > Richard Eisenberg wrote: > >> Hi café, > >> > >> Do you use Safe Haskell? Do you know someone who does? If you do, which > >> of Safe Haskell's guarantees do you rely on? > > > > Yes. lambdabot's evaluation mechanism is essentially designed around > > Safe Haskell: expressions being evaluated are wrapped in `show`, so > > there's nothing triggering IO actions from outside. > > > > Safe Haskell (barring bugs or evil libraries) ensures that there's no > > unsafePerformIO nor unsafeCoerce to break the type system, so there's > > no way to perform arbitrary IO actions inside pure code. > > > > The libraries are curated, so evil libraries have not been an issue. > > > > As for bugs, there have been holes in Typeable in the past, but > > currently I believe they're closed, except for the use of MD5 as a > > hash function (but that may require ~2^64 hash operations to exploit > > because it's hashing UTF-16 data, rendering the existing differential > > path collision attacks useless... as far as I know, nobody has done > > this yet). > > > > Preventing the use of Template Haskell is another aspect that > > lambdabot relies on. > > > > Nowadays, lambdabot (as deployed on Freenode) also uses a sandbox for > > evaluation, but I'm thinking of that as a second line of defense > > rather than the primary mechanism for keeping things safe. > > > > So I'd be sad to see SafeHaskell go away. > > > > 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. -------------- next part -------------- An HTML attachment was scrubbed... URL: From anka.213 at gmail.com Sun Apr 18 09:43:47 2021 From: anka.213 at gmail.com (=?utf-8?Q?Andreas_K=C3=A4llberg?=) Date: Sun, 18 Apr 2021 17:43:47 +0800 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> Message-ID: <0AE91DE3-29A1-4DDE-A046-C3AD1D5E30C7@gmail.com> I've been considering using it for safety-critical software to prevent things similar to the event-stream fiasco from happening, where someone took over maintenance of an npm library that was a transitive dependency of a bitcoin wallet application and injected malware that stole the users' secret keys and money. https://blog.npmjs.org/post/180565383195/details-about-the-event-stream-incident Would Safe Haskell be effective against those kinds of attacks? It should allow using a large amount of transitive dependencies, without having to manually verify the safety of anything but the core trusted packages, right? > On 17 Apr 2021, at 03:02, Richard Eisenberg wrote: > > Hi café, > > Do you use Safe Haskell? Do you know someone who does? If you do, which of Safe Haskell's guarantees do you rely on? > > Here, a user of Safe Haskell is someone who relies on any guarantees that Safe Haskell provides, not someone who makes sure to have the right pragmas, etc., in your library so that users can import it Safely. > > Context: Safe Haskell is not lightweight to support within GHC and the ecosystem. Despite being a formidable research project with a (in my opinion) quite worthwhile goal, it's unclear which of Safe Haskell's purported guarantees are actually guaranteed by GHC. (The lack of unsafeCoerce is not actually guaranteed: https://gitlab.haskell.org/ghc/ghc/-/issues/9562 .) Recent design questions about what should be Safe and what shouldn't be (somehow cannot find the discussion after a few minutes of searching; perhaps fill this in) have been answered only by stabs in the dark. The status quo is causing pain: https://gitlab.haskell.org/ghc/ghc/-/issues/19590 . There are hundreds (maybe thousands) of lines of delicate logic within GHC to support Safe Haskell. These parts of GHC have to be read, understood, and maintained by people with limited time. > > I thus wonder about deprecating and eventually removing Safe Haskell. I don't have a concrete plan for how to do this yet, but I'm confident we could come up with a migration strategy. > > The set of people who would win by removing Safe Haskell is easy enough to discover. But this email is intended to discover who would be harmed by doing so. If you know, speak up. Otherwise, I expect I will write up a GHC proposal to remove the feature. > > Thanks, > Richard > _______________________________________________ > 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 tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Sun Apr 18 10:38:28 2021 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Sun, 18 Apr 2021 11:38:28 +0100 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: <0AE91DE3-29A1-4DDE-A046-C3AD1D5E30C7@gmail.com> References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> <0AE91DE3-29A1-4DDE-A046-C3AD1D5E30C7@gmail.com> Message-ID: <20210418103828.GT968@cloudinit-builder> On Sun, Apr 18, 2021 at 05:43:47PM +0800, Andreas Källberg wrote: > I've been considering using it for safety-critical software to > prevent things similar to the event-stream fiasco from happening, > where someone took over maintenance of an npm library that was a > transitive dependency of a bitcoin wallet application and injected > malware that stole the users' secret keys and money. > https://blog.npmjs.org/post/180565383195/details-about-the-event-stream-incident > > Would Safe Haskell be effective against those kinds of attacks? It > should allow using a large amount of transitive dependencies, > without having to manually verify the safety of anything but the > core trusted packages, right? Sounds unlikely unless you're willing to never run an IO action: > It does not ensure code inferred safe but in IO cannot perform > arbitrary IO. https://wiki.haskell.org/Safe_Haskell Tom From t_gass at gmx.de Sun Apr 18 10:49:11 2021 From: t_gass at gmx.de (Tilmann) Date: Sun, 18 Apr 2021 11:49:11 +0100 Subject: [Haskell-cafe] Some Love for wxHaskell Message-ID: Hi cafe, I think wxHaskell needs some love :) Over the years I've written a small client for FICS (Free Internet Chess Server) and wxHaskell has served me really well. Also, wxWidgets seems solid and alive.. but today, wxHaskell is lagging behind updates and seems *sniff* dead. Is someone working on wxHaskell atm? I'd love to connect and help. If not, is there some interest to rejuvenate wxHaskell? Who is also depending on wxHaskell and wants to keep it going? Or, is it time to move on to gtk or reflex? Very much looking forward to your replies! Best, Tilmann From lemming at henning-thielemann.de Sun Apr 18 11:04:55 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Sun, 18 Apr 2021 13:04:55 +0200 (CEST) Subject: [Haskell-cafe] Some Love for wxHaskell In-Reply-To: References: Message-ID: On Sun, 18 Apr 2021, Tilmann wrote: > I think wxHaskell needs some love :) Over the years I've written a small > client for FICS (Free Internet Chess Server) and wxHaskell has served me > really well. Also, wxWidgets seems solid and alive.. but today, > wxHaskell is lagging behind updates and seems *sniff* dead. Is someone > working on wxHaskell atm? I'd love to connect and help. If not, is there > some interest to rejuvenate wxHaskell? Who is also depending on > wxHaskell and wants to keep it going? Or, is it time to move on to gtk > or reflex? I use wxHaskell for http://hackage.haskell.org/package/live-sequencer http://hackage.haskell.org/package/midimory http://hackage.haskell.org/package/alsa-gui I find the idea of a platform-agnostic GUI compelling, but I have not actually tried to run somewhere else than Linux/GTK. People have reported that the portability is not as good as promised. From lemming at henning-thielemann.de Sun Apr 18 11:07:38 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Sun, 18 Apr 2021 13:07:38 +0200 (CEST) Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: <20210418103828.GT968@cloudinit-builder> References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> <0AE91DE3-29A1-4DDE-A046-C3AD1D5E30C7@gmail.com> <20210418103828.GT968@cloudinit-builder> Message-ID: <7793ad33-c6d4-c8f-3253-82f9db9ccc56@henning-thielemann.de> On Sun, 18 Apr 2021, Tom Ellis wrote: > On Sun, Apr 18, 2021 at 05:43:47PM +0800, Andreas Källberg wrote: >> I've been considering using it for safety-critical software to >> prevent things similar to the event-stream fiasco from happening, >> where someone took over maintenance of an npm library that was a >> transitive dependency of a bitcoin wallet application and injected >> malware that stole the users' secret keys and money. >> https://blog.npmjs.org/post/180565383195/details-about-the-event-stream-incident >> >> Would Safe Haskell be effective against those kinds of attacks? It >> should allow using a large amount of transitive dependencies, >> without having to manually verify the safety of anything but the >> core trusted packages, right? > > Sounds unlikely unless you're willing to never run an IO action: In safety critical code you might not use bare IO but a wrapper or a type class with a trusted set of primitive methods. From bertram.felgenhauer at googlemail.com Sun Apr 18 11:31:08 2021 From: bertram.felgenhauer at googlemail.com (Bertram Felgenhauer) Date: Sun, 18 Apr 2021 13:31:08 +0200 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> Message-ID: Hi again, I wrote: > So I'd be sad to see SafeHaskell go away. I've slept on this. The above is still true, but only because I happen to have a use case that fits SafeHaskell pretty much perfectly. The bigger picture is bleaker, and SafeHaskell may well be holding back safe Haskell from reaching its full potential. Its main drawbacks are: 1) SafeHaskell imposes a single notion of safety upon the whole world. First, safety is expressed through language pragmas, which are Booleans attached to source code; basically whatever interpretation the base library gives to safety is the one that everyone has to use. On top of that, library maintainers are supposed to do the work of declaring safety of their code, even if they do not care about SafeHaskell at all. Secondly, the mechanism for inferring safety is baked into the compiler, but different notions of safety may require different inference mechanisms. Unless the use case for which SafeHaskell was designed is common (and the replies here indicate that it's not), this is hard to justify. 2) Since SafeHaskell is integrated in GHC, it's hard to improve, and SafeHaskell is lacking in some regards. For example, safety is declared at the module level, rather than the level of exported symbols. This is unfortunate, because the real cost is not in adding annotations to files, but in reviewing individual definitions; the more definitions can be inferred as safe the better, and a finer granularity would help there. In principle, most of SafeHaskell's functionality could be covered by external tools, including managing lists of safe/trusted/unsafe modules (or exports) and tracking safety dependencies for inferred safety or unsafety. There could be a standard file format for such lists, so they can be shared easily. (The information could even be expressed in source code pragmas and be extracted from there, so there doesn't need to be any loss compared to the existing SafeHaskell.) The parts that require compiler support are inference of safety, and checking language extensions and imports against a whitelist. For these things, compiler plugins should work [*]. Maybe a set of utility functions or even an abstraction layer from the GHC API can be found to support these tasks. Ideally, we could have a nice suite of tools for code auditing (define a desired property, chase it through a code base) that supports checking functions automatically through compiler plugins. And if enough people care about a particular property and trust each other's analysis, results could be shared. And of course, the original SafeHaskell use case ala lambdabot would still be covered, since it boils down to only allowing code whose safety can be inferred automatically. There would inevitably be a mess of different safety notions. But that is already the case now. The difference is that currently, only one notion is blessed and supported by GHC and all the others are not. Cheers, Bertram [*] I'm a bit worried that I'm being too naive there. Why is SafeHaskell such a burden within GHC? Is it because it touches many parts, from language pragmas to interface files to actually checking imports? Or am I forgetting something about SafeHaskell that requires deep integration, say, into the type checker? From ivanperezdominguez at gmail.com Sun Apr 18 12:53:10 2021 From: ivanperezdominguez at gmail.com (Ivan Perez) Date: Sun, 18 Apr 2021 08:53:10 -0400 Subject: [Haskell-cafe] Some Love for wxHaskell In-Reply-To: References: Message-ID: I'd be happy to see some love being given to wxHaskell. When it installed correctly, I found it very easy to use and the result was visually more compelling to Windows users than GTK (which also worked fine, btw). I built a reactive framework a few years ago [1] and wxHaskell was one of the supported backends. I wrote an email 2 years ago asking for a fix for mac that I needed for work and never got a response. Maybe it's time to pass maintenance on to others? Ivan [1] https://github.com/keera-studios/keera-hails On Sun, 18 Apr 2021 at 07:10, Henning Thielemann < lemming at henning-thielemann.de> wrote: > > On Sun, 18 Apr 2021, Tilmann wrote: > > > I think wxHaskell needs some love :) Over the years I've written a small > > client for FICS (Free Internet Chess Server) and wxHaskell has served me > > really well. Also, wxWidgets seems solid and alive.. but today, > > wxHaskell is lagging behind updates and seems *sniff* dead. Is someone > > working on wxHaskell atm? I'd love to connect and help. If not, is there > > some interest to rejuvenate wxHaskell? Who is also depending on > > wxHaskell and wants to keep it going? Or, is it time to move on to gtk > > or reflex? > > I use wxHaskell for > http://hackage.haskell.org/package/live-sequencer > http://hackage.haskell.org/package/midimory > http://hackage.haskell.org/package/alsa-gui > > I find the idea of a platform-agnostic GUI compelling, but I have not > actually tried to run somewhere else than Linux/GTK. People have reported > that the portability is not as good as promised. > _______________________________________________ > 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 tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Sun Apr 18 14:21:56 2021 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Sun, 18 Apr 2021 15:21:56 +0100 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> Message-ID: <20210418142156.GU968@cloudinit-builder> On Sun, Apr 18, 2021 at 01:31:08PM +0200, Bertram Felgenhauer via Haskell-Cafe wrote: > In principle, most of SafeHaskell's functionality could be covered by > external tools, including managing lists of safe/trusted/unsafe > modules (or exports) and tracking safety dependencies for inferred > safety or unsafety. [...] > [*] I'm a bit worried that I'm being too naive there. Why is > SafeHaskell such a burden within GHC? Is it because it touches many > parts, from language pragmas to interface files to actually checking > imports? Or am I forgetting something about SafeHaskell that requires > deep integration, say, into the type checker? To this point, I think it's worth noting what aspect of SafeHaskell is difficult to maintain in GHC yet would be easy to maintain outside of GHC, if anything. From compl.yue at icloud.com Mon Apr 19 08:23:16 2021 From: compl.yue at icloud.com (YueCompl) Date: Mon, 19 Apr 2021 16:23:16 +0800 Subject: [Haskell-cafe] Trick to have existential type work in this case? In-Reply-To: <30722cde-7fe0-659c-3fa6-d3ebb397f269@vex.net> References: <679DF502-F8BF-42DE-8DFA-AA7226208A31@icloud.com> <30722cde-7fe0-659c-3fa6-d3ebb397f269@vex.net> Message-ID: <5AAC8F40-98B4-4A1D-822C-8ED292AA6BE8@icloud.com> What a concise explanation and practical solutions! Thanks! With the hint from https://www.reddit.com/user/bss03/ I've figured out the [1st solution](https://www.reddit.com/r/haskell/comments/mre9ha/trick_to_have_existential_type_work_in_this_case/guw5y80/?context=3 ). And your 2nd solution really updated my knowledge about CPS, I used to assume some "continuation" always has to be passed around in CPS, now I know it can be used for nesting of scopes, and to have it naturally "return" back to outer scope. Thanks with best regards! > On 2021-04-16, at 02:27, Albert Y. C. Lai wrote: > > On 2021-04-15 8:54 a.m., YueCompl via Haskell-Cafe wrote: >> >> -- * Things not working >> >> managedArrayAsSeries :: SomeManagedArray -> IO Dynamic >> managedArrayAsSeries (SomeManagedArray ma) = do >> vec <- do >> SomeArray cap fp <- arrayAtTheMoment ma >> return $ VS.unsafeFromForeignPtr0 fp cap >> >> let len = return $ VS.length vec >> rs i = return $ vec VS.! i >> return $ toDyn $ Series len rs >> > That means you have this code fragment: > > arrayAtTheMoment ma > >>= > \(SomeArray cap fp) -> return $ VS.unsafeFromForeignPtr0 fp cap > That means you have this function: > > \(SomeArray cap fp) -> return $ VS.unsafeFromForeignPtr0 fp cap > Now you are violating the 1st restriction at > https://downloads.haskell.org/ghc/latest/docs/html/users_guide/exts/existential_quantification.html#restrictions > There are two solutions. > > 1st solution: One more existential type. > > data Vec = forall a. (Typeable a, VS.Storable a) => Vec (VS.Vector a) > > Vec vec <- do > SomeArray cap fp <- arrayAtTheMoment ma > return (Vec (VS.unsafeFromForeignPtr0 fp cap)) > 2nd solution: CPS transform. > > {-# language RankNTypes #-} > {-# language BlockArguments #-} > > withSomeArray :: SomeArray > -> (forall a. (Typeable a, VS.Storable a) => Int -> ForeignPtr a -> r) > -> r > withSomeArray (SomeArray i p) f = f i p > > sa <- arrayAtTheMoment ma > withSomeArray sa \cap fp -> do > let vec = VS.unsafeFromForeignPtr0 fp cap > -- or if you prefer: vec <- return (VS.unsafeFromForeignPtr0 fp cap) > len = return (VS.length vec) > rs i = return (vec VS.! i) > etc. > _______________________________________________ > 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 t_gass at gmx.de Mon Apr 19 09:27:19 2021 From: t_gass at gmx.de (Tilmann) Date: Mon, 19 Apr 2021 10:27:19 +0100 Subject: [Haskell-cafe] Some Love for wxHaskell In-Reply-To: References: Message-ID: <9dcdd12a-9b9a-a6f1-65c8-24f912130daa@gmx.de> Thank you all for sharing, this was really helpful for me to clear my mind Am 18.04.21 um 11:49 schrieb Tilmann: > Hi cafe, > > I think wxHaskell needs some love :) Over the years I've written a small > client for FICS (Free Internet Chess Server) and wxHaskell has served me > really well. Also, wxWidgets seems solid and alive.. but today, > wxHaskell is lagging behind updates and seems *sniff* dead. Is someone > working on wxHaskell atm? I'd love to connect and help. If not, is there > some interest to rejuvenate wxHaskell? Who is also depending on > wxHaskell and wants to keep it going? Or, is it time to move on to gtk > or reflex? > > Very much looking forward to your replies! > > Best, > > Tilmann > > _______________________________________________ > 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 matteo at confscience.com Tue Apr 20 06:49:12 2021 From: matteo at confscience.com (matteo at confscience.com) Date: Tue, 20 Apr 2021 08:49:12 +0200 Subject: [Haskell-cafe] International Conference on Recent Theories and Applications in Transportation and Mobility - (RTATM 2021) Prague Message-ID: <00ed01d735b1$46051260$d20f3720$@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/ 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 20, 2021 (extended) - 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 benjamin.redelings at gmail.com Tue Apr 20 10:56:13 2021 From: benjamin.redelings at gmail.com (Benjamin Redelings) Date: Tue, 20 Apr 2021 06:56:13 -0400 Subject: [Haskell-cafe] GLR parser for Haskell? In-Reply-To: References: Message-ID: <262a1a03-af2c-cd9f-973d-cc2ebe5c5036@gmail.com> Thanks, that is interesting.  I see this is a different type of grammar than in Parser.y, in that (for example) it does not have any actions on the rules. I'm still curious about why the GHC parser does not use a grammar that is closer to the language grammar.  Is this mostly for historical reasons?  Are GLR parsers too slow?  I don't know what fraction of the compilation time is spent in parsing, but would suspect it is not that much. -BenRI On 4/15/21 11:55 AM, Georgi Lyubenov wrote: > Hi! > > I think the updated tree sitter grammar might be relevant to you -� > https://github.com/tree-sitter/tree-sitter-haskell > > > Cheers, > > ====== > Georgi From allbery.b at gmail.com Tue Apr 20 11:10:26 2021 From: allbery.b at gmail.com (Brandon Allbery) Date: Tue, 20 Apr 2021 07:10:26 -0400 Subject: [Haskell-cafe] GLR parser for Haskell? In-Reply-To: <262a1a03-af2c-cd9f-973d-cc2ebe5c5036@gmail.com> References: <262a1a03-af2c-cd9f-973d-cc2ebe5c5036@gmail.com> Message-ID: GLR support in happy is much younger than ghc is, it'd probably be a massive amount of work to change now. On Tue, Apr 20, 2021 at 6:57 AM Benjamin Redelings < benjamin.redelings at gmail.com> wrote: > Thanks, that is interesting. I see this is a different type of grammar > than in Parser.y, in that (for example) it does not have any actions on > the rules. > > I'm still curious about why the GHC parser does not use a grammar that > is closer to the language grammar. Is this mostly for historical > reasons? Are GLR parsers too slow? I don't know what fraction of the > compilation time is spent in parsing, but would suspect it is not that > much. > > -BenRI > > On 4/15/21 11:55 AM, Georgi Lyubenov wrote: > > Hi! > > > > I think the updated tree sitter grammar might be relevant to you -Â > > https://github.com/tree-sitter/tree-sitter-haskell > > > > > > Cheers, > > > > ====== > > Georgi > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -- brandon s allbery kf8nh allbery.b at gmail.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From svenpanne at gmail.com Tue Apr 20 11:12:15 2021 From: svenpanne at gmail.com (Sven Panne) Date: Tue, 20 Apr 2021 13:12:15 +0200 Subject: [Haskell-cafe] GLR parser for Haskell? In-Reply-To: <262a1a03-af2c-cd9f-973d-cc2ebe5c5036@gmail.com> References: <262a1a03-af2c-cd9f-973d-cc2ebe5c5036@gmail.com> Message-ID: Am Di., 20. Apr. 2021 um 12:57 Uhr schrieb Benjamin Redelings < benjamin.redelings at gmail.com>: > [...] I'm still curious about why the GHC parser does not use a grammar > that > is closer to the language grammar. Is this mostly for historical > reasons? Are GLR parsers too slow? I don't know what fraction of the > compilation time is spent in parsing, but would suspect it is not that > much. > I think there are various aspects: * Tool support (i.e. historic reasons): Happy is a LALR parser generator. * Quality of error reporting: I don't have a clue how good GLR parsers are in this area. Often more powerful parsing methods have horrible reporting, at least that's my impression. * Does the GLR parser generator detect ambiguities and report them to the grammar writer? To me, ambiguities (like the shift/reduce & reduce/reduce conflicts in LALR parsing) are a big red flag and a sign of a questionable language/grammar: Even if the generator/parser is able to figure things out correctly, humans have a much harder time. Cheers, S. -------------- next part -------------- An HTML attachment was scrubbed... URL: From svenpanne at gmail.com Tue Apr 20 11:15:01 2021 From: svenpanne at gmail.com (Sven Panne) Date: Tue, 20 Apr 2021 13:15:01 +0200 Subject: [Haskell-cafe] GLR parser for Haskell? In-Reply-To: References: <262a1a03-af2c-cd9f-973d-cc2ebe5c5036@gmail.com> Message-ID: Am Di., 20. Apr. 2021 um 13:12 Uhr schrieb Brandon Allbery < allbery.b at gmail.com>: > GLR support in happy is much younger than ghc is [...] > I must have missed the addition of GLR parsing to Happy... o_O -------------- next part -------------- An HTML attachment was scrubbed... URL: From bertram.felgenhauer at googlemail.com Tue Apr 20 13:19:44 2021 From: bertram.felgenhauer at googlemail.com (Bertram Felgenhauer) Date: Tue, 20 Apr 2021 15:19:44 +0200 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> Message-ID: Bertram Felgenhauer via Haskell-Cafe wrote: > Unless the use case for which SafeHaskell was designed is common > (and the replies here indicate that it's not), this is hard to > justify. The feedback here is not wholly representative. There's a reddit thread [1] where djdlc points out https://uniprocess.org/effects.html This is interesting because it demonstrates that the notion of safety can be *refined* from its use by the `base` library in the context of DSLs, because one can express which notion of safety applies through types, and confine the code that is ultimately executed through the type system. Obviously this will still break down when the type system is subverted as in https://gitlab.haskell.org/ghc/ghc/-/issues/9562 which Richard pointed out, or https://gitlab.haskell.org/ghc/ghc/-/issues/19287 which wz1000 demonstrated on IRC. But these are terrible bugs anyway; it's just that SafeHaskell boosts their implact from code that people shouldn't write to a potential security issue. Is anybody maintaining a list of these type system unsoundness issues? Apparently some people also enjoy the extra code discipline that producing Safe code requires (link by gentauro (=djdlc) on Freenode): http://blog.stermon.com/articles/2019/02/21/the-main-reason-i-use-safe-haskell-is-restriction.html Cheers, Bertram [1] https://reddit.com/r/haskell/comments/msa3oq/safe_haskell/ or https://teddit.net/r/haskell/comments/msa3oq/safe_haskell/ From meng.wang at bristol.ac.uk Tue Apr 20 17:37:48 2021 From: meng.wang at bristol.ac.uk (Meng Wang) Date: Tue, 20 Apr 2021 17:37:48 +0000 Subject: [Haskell-cafe] Bx 2021 - FINAL CALL FOR PAPERS In-Reply-To: <908db5145342471bb3a4784f18ae9cb4@hpi.de> References: <908db5145342471bb3a4784f18ae9cb4@hpi.de> Message-ID: <2BB64CBC-06DE-477A-B228-5436A2E4C978@bristol.ac.uk> Dear Haskellers, Lenses is Bx and our own Edward Kmett will be giving the keynote! Please consider submitting. Best regards, Meng Bx 2021 - FINAL CALL FOR PAPERS ********************************************************************************** 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. KEYNOTE ========================================= We are happy to announce our keynote speaker: Edward Kmett. 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 (having between 5-9 standard pages, 1 standard page = 2500 characters), whereas full research papers will be mapped to the regular paper category in CEUR (having at least 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 ========================================= _____________________________________ Leen Lambers Senior Researcher at System Analysis and Modeling Group https://hpi.de/giese/personen/dr-leen-lambers.html _____________________________________ Hasso-Plattner-Institut für Digital Engineering gGmbH Universität Potsdam Prof.-Dr.-Helmert-Str. 2-3 D-14482 Potsdam, Germany _____________________________________ Amtsgericht Potsdam, HRB 12184 Geschäftsführung: Prof. Dr. Christoph Meinel _____________________________________ _______________________________________________ Bx mailing list Bx at inf.ed.ac.uk http://lists.inf.ed.ac.uk/mailman/listinfo/bx From jo at durchholz.org Tue Apr 20 19:15:43 2021 From: jo at durchholz.org (Joachim Durchholz) Date: Tue, 20 Apr 2021 21:15:43 +0200 Subject: [Haskell-cafe] GLR parser for Haskell? In-Reply-To: References: <262a1a03-af2c-cd9f-973d-cc2ebe5c5036@gmail.com> Message-ID: Am 20.04.21 um 13:12 schrieb Sven Panne: >    * Does the GLR parser generator detect ambiguities and report them > to the grammar writer? That would be a solution to the decision problem. It could try heuristics though, but I have no idea whether this particular parser does. > To me, ambiguities (like the shift/reduce & > reduce/reduce conflicts in LALR parsing) are a big red flag and a sign > of a questionable language/grammar: Even if the generator/parser is able > to figure things out correctly, humans have a much harder time. Some conflicts indicate language design problems, others do not. If you are after an algorithm that has less unnecessary conflicts, try ILALR (Sönke Kannapinn's PdD thesis - well-written and easy to understand if you can deal with German; see http://webdoc.sub.gwdg.de/ebook/diss/2003/tu-berlin/diss/2001/kannapinn_soenke.htm ; my own analysis, years ago, concluded that ILALR should have its conflicts exactly where a human would have difficulties parsing, but I never progressed to a proof of concept). Note that ILALR does does not help with conflict resolution; a user would likely have less unexpected conflicts, but the remaining ones wouldn't be easier to solve than with LALR. But I may be wrong. As I said, I never used anything like that in anger. Regards, Jo From rae at richarde.dev Tue Apr 20 20:50:30 2021 From: rae at richarde.dev (Richard Eisenberg) Date: Tue, 20 Apr 2021 20:50:30 +0000 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> Message-ID: <010f0178f10c7cc8-a26f8a4c-b402-4132-b1a0-deccb5f1b26d-000000@us-east-2.amazonses.com> After keeping up with this thread, the reddit thread, and a Twitter thread, I started to write a GHC proposal to remove Safe Haskell. However, a conversation with Krzysztof Gogolewski (aka monoidal) and a post on reddit made me change my mind: we need to renovate Safe Haskell, not remove it. And doing so only really makes sense in the context of a larger security overhaul. We are as a loose encampment in an open field with a few night sentries. Safe Haskell is a slightly-crumbling earthen rampart along two sides of the encampment. As such, it's really just an obstacle, and does little (but not nothing) to protect us. I was thinking to clear away the obstacle. But of course the better solution is to reinforce the rampart, build two more sides of it, and create a proper defensive position. This will be hard, and I do not propose to take charge of such an act now. But I recognize that the existing structure naturally forms part of this greater whole. See also https://www.reddit.com/r/haskell/comments/msa3oq/safe_haskell/gv8vph9/ , where I make similar, if not as evocative, comments. Thanks much for the input here! Richard > On Apr 20, 2021, at 9:19 AM, Bertram Felgenhauer via Haskell-Cafe wrote: > > Bertram Felgenhauer via Haskell-Cafe wrote: >> Unless the use case for which SafeHaskell was designed is common >> (and the replies here indicate that it's not), this is hard to >> justify. > > The feedback here is not wholly representative. > > There's a reddit thread [1] where djdlc points out > > https://uniprocess.org/effects.html > > This is interesting because it demonstrates that the notion of safety > can be *refined* from its use by the `base` library in the context of > DSLs, because one can express which notion of safety applies through > types, and confine the code that is ultimately executed through the > type system. > > Obviously this will still break down when the type system is subverted > as in > > https://gitlab.haskell.org/ghc/ghc/-/issues/9562 > > which Richard pointed out, or > > https://gitlab.haskell.org/ghc/ghc/-/issues/19287 > > which wz1000 demonstrated on IRC. But these are terrible bugs anyway; > it's just that SafeHaskell boosts their implact from code that people > shouldn't write to a potential security issue. Is anybody maintaining > a list of these type system unsoundness issues? > > Apparently some people also enjoy the extra code discipline that > producing Safe code requires (link by gentauro (=djdlc) on Freenode): > > http://blog.stermon.com/articles/2019/02/21/the-main-reason-i-use-safe-haskell-is-restriction.html > > Cheers, > > Bertram > > > [1] https://reddit.com/r/haskell/comments/msa3oq/safe_haskell/ > or https://teddit.net/r/haskell/comments/msa3oq/safe_haskell/ > _______________________________________________ > 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 clintonmead at gmail.com Wed Apr 21 04:55:08 2021 From: clintonmead at gmail.com (Clinton Mead) Date: Wed, 21 Apr 2021 14:55:08 +1000 Subject: [Haskell-cafe] Richard Eisenberg inspired dependent type hacking and some questions Message-ID: My apologies for the (kind of) cross post, I originally put a similar question on the Haskell Reddit I'm never sure the best place to post these sorts of things. Inspired by some of the code from one of Richard Eisenberg's weekly videos (which I always eagerly await!) I made some adjustments to his code here . Basically the attempt is to be able to deal with compile time known length lists and runtime only known length lists as uniformly as possible, as the logic is the same in both cases. In addition, allowing us to do things like `safeHead (x : xs)` regardless whether we know the length of `xs` at runtime or compile time, because it should never fail. My attempt makes things a bit messier, adding an extra constructor in the runtime case, and then naturally this means all the functions have to be extended to specifically pattern matched on this constructor. I'm trying to wrap my head around dependent types, and I did buy the ebook version of "Type-Driven Development in Idris", but I've never used Idris before so perhaps I'm having some trouble making these examples more concrete. The vague idea I've seemed to have heard is that dependent types blurs the distinction between "values" and "types", so in Idris my thought was as a result we get rid of this messy hacky distinction between the two that's required in Haskell. Can we actually do this and how? And indeed, can we do this in Haskell as well? Does the current GHC type system give us tools to allow what I've designed without bloating all the functions by having to deal with this extra constructor match? Thanks, Clinton -------------- next part -------------- An HTML attachment was scrubbed... URL: From clintonmead at gmail.com Wed Apr 21 06:51:48 2021 From: clintonmead at gmail.com (Clinton Mead) Date: Wed, 21 Apr 2021 16:51:48 +1000 Subject: [Haskell-cafe] Richard Eisenberg inspired dependent type hacking and some questions In-Reply-To: References: Message-ID: I've just figured that even the approach I used doesn't work very well. Consider: > conditionalAdd :: Bool -> a -> Vec m a -> Vec Unknown a > conditionalAdd b x xs = case b of > True -> Runtime (x :> xs) > False -> Runtime xs > > z = init (conditionalAdd False False (True :> Nil)) 'z' should be type correct, but here it's not, and there's no clear way to do so. I guess I'd have to have a compile time type "at least of length n" but again, I feel like this would be much cleaner with dependent types (and perhaps a more direct translation to Haskell). On Wed, Apr 21, 2021 at 2:55 PM Clinton Mead wrote: > My apologies for the (kind of) cross post, I originally put a similar > question on the Haskell > > Reddit > > I'm never sure the best place to post these sorts of things. > > Inspired by some of the code > > from one of Richard Eisenberg's weekly videos > (which I always eagerly > await!) I made some adjustments to his code here > . > > Basically the attempt is to be able to deal with compile time known length > lists and runtime only known length lists as uniformly as possible, as the > logic is the same in both cases. In addition, allowing us to do things like > `safeHead (x : xs)` regardless whether we know the length of `xs` at > runtime or compile time, because it should never fail. > > My attempt makes things a bit messier, adding an extra constructor in the > runtime case, and then naturally this means all the functions have to be > extended to specifically pattern matched on this constructor. > > I'm trying to wrap my head around dependent types, and I did buy the ebook > version of "Type-Driven Development in Idris", but I've never used Idris > before so perhaps I'm having some trouble making these examples more > concrete. > > The vague idea I've seemed to have heard is that dependent types blurs the > distinction between "values" and "types", so in Idris my thought was as a > result we get rid of this messy hacky distinction between the two that's > required in Haskell. Can we actually do this and how? > > And indeed, can we do this in Haskell as well? Does the current GHC type > system give us tools to allow what I've designed without bloating all the > functions by having to deal with this extra constructor match? > > Thanks, > Clinton > -------------- next part -------------- An HTML attachment was scrubbed... URL: From guthrie at miu.edu Wed Apr 21 12:41:47 2021 From: guthrie at miu.edu (Gregory Guthrie) Date: Wed, 21 Apr 2021 12:41:47 +0000 Subject: [Haskell-cafe] IntelliJ Haskell plugins? Message-ID: Does anyone have experience with and a recommendation for the best Haskell for the IntelliJ IDE? -------------- next part -------------- An HTML attachment was scrubbed... URL: From blamario at rogers.com Wed Apr 21 12:45:03 2021 From: blamario at rogers.com (Mario) Date: Wed, 21 Apr 2021 08:45:03 -0400 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: <010f0178f10c7cc8-a26f8a4c-b402-4132-b1a0-deccb5f1b26d-000000@us-east-2.amazonses.com> References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> <010f0178f10c7cc8-a26f8a4c-b402-4132-b1a0-deccb5f1b26d-000000@us-east-2.amazonses.com> Message-ID: <61fc03aa-2345-5303-76e5-bf75b17a4f07@rogers.com> On 2021-04-20 4:50 p.m., Richard Eisenberg wrote: > We are as a loose encampment in an open field with a few night > sentries. Safe Haskell is a slightly-crumbling earthen rampart along > two sides of the encampment. As such, it's really just an obstacle, > and does little (but not nothing) to protect us. I was thinking to > clear away the obstacle. But of course the better solution is to > reinforce the rampart, build two more sides of it, and create a proper > defensive position. This will be hard, and I do not propose to take > charge of such an act now. But I recognize that the existing structure > naturally forms part of this greater whole. If your main goal is a defensive position you shouldn't be in an open field to begin with. You should encamp on a high ground, with plenty of nearby lumber to build ramparts, and a secure source of fresh water to withstand a siege. That kind of position limits your maneuverability, admittedly, but it's much easier to protect. Sorry, I couldn't resist your analogy. I'm glad that Safe Haskell continues to be maintained, but if you start with the goal of security Haskell is really not the right place to start from. No general-purpose language (open field) is. You want to design from scratch, starting with a secure core language (high ground). You can use Haskell as an inspiration; Marlowe and probably some other blockchain languages do. From develop7 at develop7.info Wed Apr 21 13:00:28 2021 From: develop7 at develop7.info (Andrei Dziahel) Date: Wed, 21 Apr 2021 15:00:28 +0200 Subject: [Haskell-cafe] IntelliJ Haskell plugins? In-Reply-To: References: Message-ID: Hands down Intellij-haskell[1] — it saw good progress these two years despite being essentially a one-man effort (shout out to my man Rik van der Kleij!). There's also HaskForce[2] which is pretty much in a maintenance mode nowadays. 1: https://plugins.jetbrains.com/plugin/8258-intellij-haskell 2: https://plugins.jetbrains.com/plugin/7602-haskforce On Wed, Apr 21, 2021 at 2:48 PM Gregory Guthrie wrote: > > Does anyone have experience with and a recommendation for the best Haskell for the IntelliJ IDE? > > > > > > > > _______________________________________________ > 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. -- Regards, Andrei Dziahel From guthrie at miu.edu Wed Apr 21 13:08:36 2021 From: guthrie at miu.edu (Gregory Guthrie) Date: Wed, 21 Apr 2021 13:08:36 +0000 Subject: [Haskell-cafe] IntelliJ Haskell plugins? In-Reply-To: References: Message-ID: Thanks. Haskforce fails with newer version o f IDE, but before I had found it to be simple and effective. The IntelliJ version seems to require one to use stack for setup and creation of projects, and then use the IDE? -----Original Message----- From: Andrei Dziahel Sent: Wednesday, April 21, 2021 8:00 AM To: Gregory Guthrie Cc: haskell-cafe at haskell.org Subject: Re: [Haskell-cafe] IntelliJ Haskell plugins? Hands down Intellij-haskell[1] — it saw good progress these two years despite being essentially a one-man effort (shout out to my man Rik van der Kleij!). There's also HaskForce[2] which is pretty much in a maintenance mode nowadays. 1: https://plugins.jetbrains.com/plugin/8258-intellij-haskell 2: https://plugins.jetbrains.com/plugin/7602-haskforce On Wed, Apr 21, 2021 at 2:48 PM Gregory Guthrie wrote: > > Does anyone have experience with and a recommendation for the best Haskell for the IntelliJ IDE? > > > > > > > > _______________________________________________ > 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. -- Regards, Andrei Dziahel From svenpanne at gmail.com Wed Apr 21 13:36:22 2021 From: svenpanne at gmail.com (Sven Panne) Date: Wed, 21 Apr 2021 15:36:22 +0200 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: <61fc03aa-2345-5303-76e5-bf75b17a4f07@rogers.com> References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> <010f0178f10c7cc8-a26f8a4c-b402-4132-b1a0-deccb5f1b26d-000000@us-east-2.amazonses.com> <61fc03aa-2345-5303-76e5-bf75b17a4f07@rogers.com> Message-ID: Am Mi., 21. Apr. 2021 um 14:55 Uhr schrieb Mario : > [...] No general-purpose language (open field) is. You want to design from > scratch, starting with > a secure core language (high ground). You can use Haskell as an > inspiration; Marlowe and probably some other blockchain languages do. > That's not totally correct: You can use anything you like when you have a sandbox while executing it. This is even much more safe than relying on a language (which can have conceptual and/or implementation bugs) alone. The attack surface of any non-trivial language, its implementation and its runtime is just too big for anything serious. Sandboxes are complex, too, but less so, and you implement them once and you can use them for many things. Having said that, my personal view is that Safe Haskell has almost no valid use case anymore, given the various sandboxing technologies available today. But that's just my 2c... Cheers, S. -------------- next part -------------- An HTML attachment was scrubbed... URL: From develop7 at develop7.info Wed Apr 21 13:47:16 2021 From: develop7 at develop7.info (Andrei Dziahel) Date: Wed, 21 Apr 2021 15:47:16 +0200 Subject: [Haskell-cafe] IntelliJ Haskell plugins? In-Reply-To: References: Message-ID: It can create projects with the "new project" wizard as well, but does require stack for now. On Wed, Apr 21, 2021 at 3:08 PM Gregory Guthrie wrote: > > Thanks. Haskforce fails with newer version o f IDE, but before I had found it to be simple and effective. > The IntelliJ version seems to require one to use stack for setup and creation of projects, and then use the IDE? > > > > -----Original Message----- > From: Andrei Dziahel > Sent: Wednesday, April 21, 2021 8:00 AM > To: Gregory Guthrie > Cc: haskell-cafe at haskell.org > Subject: Re: [Haskell-cafe] IntelliJ Haskell plugins? > > Hands down Intellij-haskell[1] — it saw good progress these two years despite being essentially a one-man effort (shout out to my man Rik van der Kleij!). There's also HaskForce[2] which is pretty much in a maintenance mode nowadays. > > 1: https://plugins.jetbrains.com/plugin/8258-intellij-haskell > 2: https://plugins.jetbrains.com/plugin/7602-haskforce > > > On Wed, Apr 21, 2021 at 2:48 PM Gregory Guthrie wrote: > > > > Does anyone have experience with and a recommendation for the best Haskell for the IntelliJ IDE? > > > > > > > > > > > > > > > > _______________________________________________ > > 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. > > > > -- > Regards, > Andrei Dziahel -- Regards, Andrei Dziahel From jo at durchholz.org Wed Apr 21 13:52:20 2021 From: jo at durchholz.org (Joachim Durchholz) Date: Wed, 21 Apr 2021 15:52:20 +0200 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> <010f0178f10c7cc8-a26f8a4c-b402-4132-b1a0-deccb5f1b26d-000000@us-east-2.amazonses.com> <61fc03aa-2345-5303-76e5-bf75b17a4f07@rogers.com> Message-ID: <32e32632-395d-5a4f-2c1b-9def91d12aaa@durchholz.org> Am 21.04.21 um 15:36 schrieb Sven Panne: > That's not totally correct: You can use anything you like when you have > a sandbox while executing it. This is even much more safe than relying > on a language (which can have conceptual and/or implementation bugs) > alone. Actually Sandboxes have a just as complicated attack surface as languages. I also believe they are different domains. Secure languages deal with making guarantees about what a program does and, more importantly, what it does not do. So you can control things like IO effects, Capabilities, and the language can even make these guarantees statically. A sandbox deals more with API objects. This is a much more complicated surface because today's APIs tend to be large, complex, and interact in unexpected fashions; on the other hand, it is much nearer to the actual objects being protected. I.e. I believe the two approaches, while they have some overlap, they serve different purposes and need to complement each other. > The attack surface of any non-trivial language, > its implementation and its runtime is just too big for anything serious. > Sandboxes are complex, too, but less so, I believe the opposite is true. APIs change over time. Languages do that, too, but to a much lesser extent, and type system guarantees tend to hold for decades. Even filesystem APIs are less stable than that (think NFS, or filesystem-dependent ACLs). Regards, Jo From rae at richarde.dev Wed Apr 21 14:01:58 2021 From: rae at richarde.dev (Richard Eisenberg) Date: Wed, 21 Apr 2021 14:01:58 +0000 Subject: [Haskell-cafe] Richard Eisenberg inspired dependent type hacking and some questions In-Reply-To: References: Message-ID: <010f0178f4bcd245-fffe0f50-01cb-4226-a127-29393d175c0d-000000@us-east-2.amazonses.com> There are good responses accruing on Reddit, so I won't repeat them here. See, in particular, /u/sccrstud92's well-explained answer at https://www.reddit.com/r/haskell/comments/mv6m5s/hacking_richard_eisenbergs_haskell_dependently/ There are few new points you've raised here, though: > On Apr 21, 2021, at 12:55 AM, Clinton Mead wrote: > > The vague idea I've seemed to have heard is that dependent types blurs the distinction between "values" and "types", so in Idris my thought was as a result we get rid of this messy hacky distinction between the two that's required in Haskell. Can we actually do this and how? Having dependent types means that we don't need singletons, because e.g. the `n` in `SNat n` would be available both at runtime and at compile time. Really, when we say that dependent types blur values and types, we really mean that it allows the same data to be available at runtime (sometimes called "values") and compile-time (sometimes called "types"). > > And indeed, can we do this in Haskell as well? Does the current GHC type system give us tools to allow what I've designed without bloating all the functions by having to deal with this extra constructor match? Existentials are the way to do this. Haskell's support for existentials is similar to that in Idris -- the issue there isn't really about dependent types, per se. I hope this helps! Richard -------------- next part -------------- An HTML attachment was scrubbed... URL: From blamario at rogers.com Wed Apr 21 14:29:55 2021 From: blamario at rogers.com (Mario) Date: Wed, 21 Apr 2021 10:29:55 -0400 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> <010f0178f10c7cc8-a26f8a4c-b402-4132-b1a0-deccb5f1b26d-000000@us-east-2.amazonses.com> <61fc03aa-2345-5303-76e5-bf75b17a4f07@rogers.com> Message-ID: <24a7e2f8-f34e-fa03-b467-3adbdc7fb439@rogers.com> On 2021-04-21 9:36 a.m., Sven Panne wrote: > Am Mi., 21. Apr. 2021 um 14:55 Uhr schrieb Mario >: > > [...] No general-purpose language (open field) is. You want to > design from scratch, starting with > a secure core language (high ground). You can use Haskell as an > inspiration; Marlowe and probably some other blockchain languages do. > > > That's not totally correct: You can use anything you like when you > have a sandbox while executing it. This is even much more safe than > relying on a language (which can have conceptual and/or implementation > bugs) alone. The attack surface of any non-trivial language, > its implementation and its runtime is just too big for anything > serious. Sandboxes are complex, too, but less so, and you implement > them once and you can use them for many things. Having said that, my > personal view is that Safe Haskell has almost no valid use case > anymore, given the various sandboxing technologies available today. > But that's just my 2c... I'm disappointed you haven't continued the encampment analogy. That's especially unforgivable because it actually does provide an insight in this case. Allow me to analogize your argument: Instead of worrying about digging ditches and raising ramparts, why don't we just march into this friendly fort nearby, surrounded by a moat with a drawbridge? Let's just frolic inside. To which the age-old answer is: why not both? Sure, use the ready fortifications if you can find them. But that doesn't mean you can just drop your guard, because enemy could infiltrate any outer defense. Even assuming the fortifications are impenetrable, you'll have to open your gates and lower the drawbridge occasionally. So you still want to keep patrols, guards, inner security, etc. Defense in depth. Analogy over, no sandbox will protect you from attacks like SQL injections or application-layer denial-of-service attacks. A type system designed for the purpose can protect you from both. From svenpanne at gmail.com Wed Apr 21 16:39:58 2021 From: svenpanne at gmail.com (Sven Panne) Date: Wed, 21 Apr 2021 18:39:58 +0200 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: <32e32632-395d-5a4f-2c1b-9def91d12aaa@durchholz.org> References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> <010f0178f10c7cc8-a26f8a4c-b402-4132-b1a0-deccb5f1b26d-000000@us-east-2.amazonses.com> <61fc03aa-2345-5303-76e5-bf75b17a4f07@rogers.com> <32e32632-395d-5a4f-2c1b-9def91d12aaa@durchholz.org> Message-ID: Am Mi., 21. Apr. 2021 um 15:57 Uhr schrieb Joachim Durchholz < jo at durchholz.org>: > Actually Sandboxes have a just as complicated attack surface as languages. > Perhaps we are talking about different kinds of sandboxes: I'm talking about sandboxes at the syscall level. Compared to higher level stuff they are relatively simple. They are not small (tons of syscalls exist nowadays), but each syscall is relatively simple compared to stuff built upon it. Size != complexity. And the SW engineering point is: You program your sandbox SW once and can use it for every language/program, without any need to follow the latest and greatest hype in languages, compilers, type systems etc. This means a *much* higher ROI compared to a language-specific solution. Of course you won't get a PhD for a syscall sandbox... > I also believe they are different domains. > Secure languages deal with making guarantees about what a program does > and, more importantly, what it does not do. So you can control things > like IO effects, Capabilities, and the language can even make these > guarantees statically. > Only if you trust your language itself, your implementation and its RTS. And given the complexity of each of these aspects, basically any language has security holes (see e.g. the recent discussion here about various GHC bugs). A sandbox has a much easier job, it can e.g. always err on the safe side. > A sandbox deals more with API objects. This is a much more complicated > surface because today's APIs tend to be large, complex, and interact in > unexpected fashions; on the other hand, it is much nearer to the actual > objects being protected. > I.e. I believe the two approaches, while they have some overlap, they > serve different purposes and need to complement each other. > A syscall sandbox needs no help whatsoever from a language. > I believe the opposite is true.APIs change over time. The syscall interface is extremely stable, at least compared to the rest of all APIs in existence. > Languages do that, too, but to a much lesser > extent, and type system guarantees tend to hold for decades. > There is no such thing as a type system in the machine code actually running, so you can't trust any higher-level guarantees. > Even filesystem APIs are less stable than that (think NFS, or > filesystem-dependent ACLs). > Do you really see the filesystem implementation on the syscall level? Unless you're doing serious fcntl()/ioctl()-Kung-Fu or stuff like that, I don't think so, but that's just a guess. -------------- next part -------------- An HTML attachment was scrubbed... URL: From fryguybob at gmail.com Wed Apr 21 17:27:15 2021 From: fryguybob at gmail.com (Ryan Yates) Date: Wed, 21 Apr 2021 13:27:15 -0400 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: <010f0178f10c7cc8-a26f8a4c-b402-4132-b1a0-deccb5f1b26d-000000@us-east-2.amazonses.com> References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> <010f0178f10c7cc8-a26f8a4c-b402-4132-b1a0-deccb5f1b26d-000000@us-east-2.amazonses.com> Message-ID: Hi Richard, To add another place I think Safe Haskell is useful: GHC's STM performs lazy validation which means it allows execution of "zombie" or "doomed" transactions, an executing transaction that has observed inconsistent reads from `TVar`s, but has not yet detected it. Given this, unsafe operations can introduce failures when executing a transaction that would not happen executing sequentially. I argued in my thesis that Safe Haskell is sufficient to prevent this. That is, libraries that are safe are safe to use in transactions. Thanks for your work getting this discussion rolling, Ryan On Tue, Apr 20, 2021 at 4:54 PM Richard Eisenberg wrote: > After keeping up with this thread, the reddit thread, and a Twitter > thread, I started to write a GHC proposal to remove Safe Haskell. However, > a conversation with Krzysztof Gogolewski (aka monoidal) and a post on > reddit made me change my mind: we need to renovate Safe Haskell, not remove > it. And doing so only really makes sense in the context of a larger > security overhaul. > > We are as a loose encampment in an open field with a few night sentries. > Safe Haskell is a slightly-crumbling earthen rampart along two sides of the > encampment. As such, it's really just an obstacle, and does little (but not > nothing) to protect us. I was thinking to clear away the obstacle. But of > course the better solution is to reinforce the rampart, build two more > sides of it, and create a proper defensive position. This will be hard, and > I do not propose to take charge of such an act now. But I recognize that > the existing structure naturally forms part of this greater whole. > > See also > https://www.reddit.com/r/haskell/comments/msa3oq/safe_haskell/gv8vph9/, > where I make similar, if not as evocative, comments. > > Thanks much for the input here! > Richard > > On Apr 20, 2021, at 9:19 AM, Bertram Felgenhauer via Haskell-Cafe < > haskell-cafe at haskell.org> wrote: > > Bertram Felgenhauer via Haskell-Cafe wrote: > > Unless the use case for which SafeHaskell was designed is common > (and the replies here indicate that it's not), this is hard to > justify. > > > The feedback here is not wholly representative. > > There's a reddit thread [1] where djdlc points out > > https://uniprocess.org/effects.html > > This is interesting because it demonstrates that the notion of safety > can be *refined* from its use by the `base` library in the context of > DSLs, because one can express which notion of safety applies through > types, and confine the code that is ultimately executed through the > type system. > > Obviously this will still break down when the type system is subverted > as in > > https://gitlab.haskell.org/ghc/ghc/-/issues/9562 > > which Richard pointed out, or > > https://gitlab.haskell.org/ghc/ghc/-/issues/19287 > > which wz1000 demonstrated on IRC. But these are terrible bugs anyway; > it's just that SafeHaskell boosts their implact from code that people > shouldn't write to a potential security issue. Is anybody maintaining > a list of these type system unsoundness issues? > > Apparently some people also enjoy the extra code discipline that > producing Safe code requires (link by gentauro (=djdlc) on Freenode): > > > http://blog.stermon.com/articles/2019/02/21/the-main-reason-i-use-safe-haskell-is-restriction.html > > Cheers, > > Bertram > > > [1] https://reddit.com/r/haskell/comments/msa3oq/safe_haskell/ > or https://teddit.net/r/haskell/comments/msa3oq/safe_haskell/ > _______________________________________________ > 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 ietf-dane at dukhovni.org Wed Apr 21 18:24:29 2021 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Wed, 21 Apr 2021 14:24:29 -0400 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: <61fc03aa-2345-5303-76e5-bf75b17a4f07@rogers.com> References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> <010f0178f10c7cc8-a26f8a4c-b402-4132-b1a0-deccb5f1b26d-000000@us-east-2.amazonses.com> <61fc03aa-2345-5303-76e5-bf75b17a4f07@rogers.com> Message-ID: On Wed, Apr 21, 2021 at 08:45:03AM -0400, Mario wrote: > If your main goal is a defensive position you shouldn't be in an open > field to begin with. You should encamp on a high ground, with plenty of > nearby lumber to build ramparts, and a secure source of fresh water to > withstand a siege. That kind of position limits your maneuverability, > admittedly, but it's much easier to protect. On the topic of whether safety can/should be in the language or be implemented via containerisation, much depends on the details of how the language goes about sandboxing. Some decades back I've used Safe Tcl to limit what untrusted scripts can execute in a server process. With Safe Tcl one populates the untrusted interpreted with a very limited set of verbs and optional aliases into wrapper verbs that run in a separate trusted interpreter. The wrapper verbs can inspect the arguments of restricted commands and allow only appropriate access. Similar features are likely available by embedding Lua or another similar interpreter where it is possible to explicitly expose only a specific language dialect. Such designs tend to be robust. On the other hand, I've always been sceptical of the sandboxing in Java, it was much too complex to be obviously correct, and the long history of bugs in Java applet sandboxing justified the scepticism. Fortunately we longer use Java applets, though JavaScript security in browsers continues to be challenging. So it should not be surprising that I'd also be sceptical of any strong safety claims from Safe Haskell. It seems unlikely to be simple enough to be "obviously correct". This does not mean that it can't be a useful element of defense in depth, but it is difficult to envision how it would be sufficient on its own. The challenge with Safe Haskell, unlike with safe Tcl, is that there is no hard separation between the untrusted and trusted components of the program, they're only separated by static analysis, not separation into distinct execution engines with a controlled communication channel as with Safe Tcl and slave interpreters. For Safe Haskell to be safe, I'd want to see internal virtualisation, with untrusted code using a stripped down RTS that is incapable of supporting external I/O, and all unsafe operations proxied into a separate trusted RTS running separately compiled code. All unsafe operations in the untrusted RTS would then need to be RPC calls into the trusted RTS. The difficulty is though that unlike the case with Tcl, many basic Haskell libraries that export safe pure interfaces, internally use unsafe interfaces (e.g. raw memory access) for performance reasons. So it is rather unclear how to expose a usable untrusted subset of the language except through static analysis (type level guarantess) of the sort that I'm reluctant to trust as a result of high complexity. So while I take no position on whether Safe Haskell should or should not be abandoned, I agree that it is a valid question because the problem is rather non-trivial, and it is not clear whether it is actually possible to implement a sufficiently robust design. -- Viktor. From compl.yue at icloud.com Thu Apr 22 09:19:44 2021 From: compl.yue at icloud.com (YueCompl) Date: Thu, 22 Apr 2021 17:19:44 +0800 Subject: [Haskell-cafe] Smooth developer experience with Cloud IDE for modern Haskell now Message-ID: Dear Cafe, I'd like to share that I find that, we can have rather smooth developer experience for Haskell, on cloud, now. Gitpod (https://gitpod.io ) recently supported VSCode in addition to Eclipse Theia, making the UX much more smoother, with proper Gitpod workspace setup, now it's much easier for Haskell beginners, as well as chromeOS and Windows users to painlessly onboard modern Haskell. Github codespaces (https://github.com/features/codespaces ) is up coming too, there sure will be industry strength cloud infrastructures for serious Haskell development soon. And the setup can be fully automated, a full fledged Cloud IDE for modern Haskell development, is only a click away, see my demo: https://github.com/complyue/GHCiCode#readme I also expect more beginner-friendly tutorials can be written this way, especially for Windows users, they'll be able to touch & feel the mass without going through painful setup procedures. Sincerely, Compl -------------- next part -------------- An HTML attachment was scrubbed... URL: From compl.yue at icloud.com Thu Apr 22 10:04:14 2021 From: compl.yue at icloud.com (YueCompl) Date: Thu, 22 Apr 2021 18:04:14 +0800 Subject: [Haskell-cafe] Smooth developer experience with Cloud IDE for modern Haskell now In-Reply-To: References: Message-ID: <21E2E1EF-A4FB-43FF-B06C-CAF25FD7CB18@icloud.com> Also FYI, I had had bad experience on Replit (https://replit.com/ ), which can also run GHC/Cabal on the cloud, it is overly restrictive on RAM occupation in GHC's cases, the compiler process can be killed halfway compiling sufficiently large projects. While Gitpod workspace provisions ideal hardware resources for GHC to live in. > On 2021-04-22, at 17:19, YueCompl via Haskell-Cafe wrote: > > Dear Cafe, > > I'd like to share that I find that, we can have rather smooth developer experience for Haskell, on cloud, now. > > Gitpod (https://gitpod.io ) recently supported VSCode in addition to Eclipse Theia, making the UX much more smoother, with proper Gitpod workspace setup, now it's much easier for Haskell beginners, as well as chromeOS and Windows users to painlessly onboard modern Haskell. > > Github codespaces (https://github.com/features/codespaces ) is up coming too, there sure will be industry strength cloud infrastructures for serious Haskell development soon. > > And the setup can be fully automated, a full fledged Cloud IDE for modern Haskell development, is only a click away, see my demo: > > https://github.com/complyue/GHCiCode#readme > > I also expect more beginner-friendly tutorials can be written this way, especially for Windows users, they'll be able to touch & feel the mass without going through painful setup procedures. > > Sincerely, > Compl > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From jo at durchholz.org Thu Apr 22 19:23:56 2021 From: jo at durchholz.org (Joachim Durchholz) Date: Thu, 22 Apr 2021 21:23:56 +0200 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> <010f0178f10c7cc8-a26f8a4c-b402-4132-b1a0-deccb5f1b26d-000000@us-east-2.amazonses.com> <61fc03aa-2345-5303-76e5-bf75b17a4f07@rogers.com> <32e32632-395d-5a4f-2c1b-9def91d12aaa@durchholz.org> Message-ID: Am 21.04.21 um 18:39 schrieb Sven Panne: > Am Mi., 21. Apr. 2021 um 15:57 Uhr schrieb Joachim Durchholz > >: > > Actually Sandboxes have a just as complicated attack surface as > languages. > > > Perhaps we are talking about different kinds of sandboxes: I'm talking > about sandboxes at the syscall level. Compared to higher level stuff > they are relatively simple. They are not small (tons of syscalls exist > nowadays), but each syscall is relatively simple compared to stuff built > upon it. Size != complexity. True, but the semantics behind each syscall can be horrendously complex. The syscall for opening a file is straightforward, but its semantics depends on a ton of factors, like whether it's in /proc, on a ramdisk, a remote file system, and the semantics of whatever filesystem is plugged behind. That's why you can have a sandbox and this still doesn't protect you from symlink timing attacks on /tmp, for example (wait for a system process to create a temporary file, delete the file and insert a symlink to a file of your choice - will work with a low probability if there's a window between file creation and file opening, that's why mktemp and friends were built to make this atomic, and we hope(!) that all security-relevant programs have been updated to use that instead of creating a temp file to open it later). > And the SW engineering point is: You > program your sandbox SW once and can use it for every language/program, > without any need to follow the latest and greatest hype in languages, > compilers, type systems etc. Instead you have to make sure that all software uses mktemp instead of doing nonatomic file creation&opening. Which isn't secure by design, you still have to double-check all software. > This means a *much* higher ROI compared to > a language-specific solution. Of course you won't get a PhD for a > syscall sandbox... Except that there is no such thing as an inherently safe syscall interface, there are unsafe ways to use it. And that's where language-based safety can help. > I also believe they are different domains. > Secure languages deal with making guarantees about what a program does > and, more importantly, what it does not do. So you can control things > like IO effects, Capabilities, and the language can even make these > guarantees statically. > > Only if you trust your language itself, your implementation and its RTS. Again, trusting an operating system isn't a smaller surface. After all, you need to trust the OS as a whole, namely that all the syscalls do what they're supposed to do. Not a win, actually. Operating systems are vastly more complex than language runtimes. It's even stronger. The compiler code to emit useful error messages is complex, because it needs to infer the programmer's intentions. The compiler code for type inference is pretty complex as well - it ranges from pretty easy for pure Hindley-Milner typing to arbitrary complexity for dependent types and other things. However, the code that checks if the program type checks after all type inference has been applied - that's actually trivial. It's the moral equivalent of a proof checker for first-order predicate logic, and that's something that you can do at university (I actually did such a thing for my Diploma); *finding* a proof is hard but *checking* one is trivial, and that translates to type systems and things like Secure Haskell. There's still another challenge: Set up a system of axioms, i.e. security properties and how they apply when going through the various primitives, and find a set that's (a) interesting and (b) understandable for programmers. This is pretty hard to do for syscalls, because their semantics was never designed to be easily provable. It's easier to languages if you restrict syscall use to a safe subset (for whatever definition of "safe" resp. for what set of security-relevant properties you're interested in). Such a restriction is good for an easy first prototype, but it falls flat as soon has you allow arbitrary syscalls, or linking arbitrary libraries. So for system security regardless of what programming language people are using, you probably need something at the syscall level - sandboxes, jails, cgroups, whatever else. None of these are perfect - kernel bugs still exist, and some syscalls have well-known security issues - so you *still* need defense in depth. > And given the complexity of each of these aspects, basically any > language has security holes (see e.g. the recent discussion here about > various GHC bugs). A sandbox has a much easier job, it can e.g. always > err on the safe side. No sandbox does that. Well, the new ones do. Then people start demanding additional features, and off you go with new features, new bugs, and new unforeseen interactions. I'm speaking from experience with the JVM sandboxes, which is an in-language mechanism but the problems I saw there could happen regardless of whether the sandboxing is done inside a runtime or at the syscall level. > A sandbox deals more with API objects. This is a much more complicated > surface because today's APIs tend to be large, complex, and interact in > unexpected fashions; on the other hand, it is much nearer to the actual > objects being protected. > I.e. I believe the two approaches, while they have some overlap, they > serve different purposes and need to complement each other. > > > A syscall sandbox needs no help whatsoever from a language. Well, I hope I just argued why a syscall sandbox is never going to be complete. An additional argument: syscall sandboxes can't prevent data exfiltration. There are just too many channels. And in-language security check could prevent exfiltration of user passwords (with the right axioms and inference rules). > I believe the opposite is true.APIs change over time. > > The syscall interface is extremely stable, at least compared to the rest > of all APIs in existence. But first-order predicate logic is immutable, and that's all you need for a checker. (The axioms and inference rules can depend on the API, but that's just the same as with syscalls.) BTW syscalls aren't immutable. They're backwards-compatible. That's irrelevant for a programmer, but it is a world of difference for security - a programmer is interested in what can be done, security is interested in what can *not* be done, and this changes the picture completely. > Languages do that, too, but to a much lesser > extent, and type system guarantees tend to hold for decades. > > There is no such thing as a type system in the machine code actually > running, so you can't trust any higher-level guarantees. You can't trust the compiler, you can't trust the runtime, and you can't trust the kernel. There's really no big difference there. You just happen to know the ghc loopholes better than the syscall loopholes (for me it's the other way round). > Even filesystem APIs are less stable than that (think NFS, or > filesystem-dependent ACLs). > > > Do you really see the filesystem implementation on the syscall level? > Unless you're doing serious fcntl()/ioctl()-Kung-Fu or stuff like that, > I don't think so, but that's just a guess. No, it's much worse. Some syscalls are atomic on a local filesystem and nonatomic on NFS. So if you're writing security-relevant code, you have to know whether you're on NFS or not, and I'm not even sure if you can reliably detect if the file you're trying to create&open is local or NFS. Then there's tons of interesting games you can play with symlinks and hardlinks, further complicated by questions like what happens if a symlink is cross-filesystem (it may well be that all atomicity guarantees go out of the window). Do you even write your code in a way that you detect if a physical file was turned into a symlink behind your back? Even if your code is running inside a VM and might be subject to suspend/resume? (Cloud management software like OpenShift does things like suspend your VM, move it do a different hardware, and resume; filesystem boundaries can indeed change, and it's easy to confuse OpenShift enough to trigger that "oh we need to relocate to another hardware" reaction). Quite a while ago, attacks have started shifting from exploiting operating system bugs to exploiting application programmer expectations and making these fail. And a syscall will do nothing to stop that. A language-based security framework cannot fully stop that, but it can catch another class of errors. So I still stand by my assessment that the approaches don't replace each other, they're complementing each other and you should pursue both. That's my 5 cents - YMMV. Regards, Jo From jo at durchholz.org Thu Apr 22 19:35:07 2021 From: jo at durchholz.org (Joachim Durchholz) Date: Thu, 22 Apr 2021 21:35:07 +0200 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> <010f0178f10c7cc8-a26f8a4c-b402-4132-b1a0-deccb5f1b26d-000000@us-east-2.amazonses.com> <61fc03aa-2345-5303-76e5-bf75b17a4f07@rogers.com> Message-ID: <54438319-dd49-cc71-d4fc-deb70a107f69@durchholz.org> Am 21.04.21 um 20:24 schrieb Viktor Dukhovni: > On the other hand, I've always been sceptical of the sandboxing in Java, > it was much too complex to be obviously correct, and the long history of > bugs in Java applet sandboxing justified the scepticism. Fortunately we > longer use Java applets, though JavaScript security in browsers > continues to be challenging. Same here. > So it should not be surprising that I'd also be sceptical of any > strong safety claims from Safe Haskell. It seems unlikely to be > simple enough to be "obviously correct". This does not mean that it > can't be a useful element of defense in depth, but it is difficult to > envision how it would be sufficient on its own. > > The challenge with Safe Haskell, unlike with safe Tcl, is that there > is no hard separation between the untrusted and trusted components of > the program, they're only separated by static analysis, not > separation into distinct execution engines with a controlled > communication channel as with Safe Tcl and slave interpreters. For Safe Haskell, the substrate language is much easier to reason about - there's no way for static analysis to work well with Java (aliasing alone will preven that), but such a thing *is* possible with Haskell. Heck, ghc is doing deforestation and similar things, no such thing would be even remotely thinkable for any imperative language! So while I agree in principle, I believe Safe Haskell could be safer than the experience with sandboxing in an imperative language would be. The other thing is that the Java sandbox pretty obviously spent more time on writing enabling code than on validating that a new feature doesn't influence existing ones, and you need the opposite approach when doing sandboxes. I.e. I believe the Java sandbox failed not just because it's inherently more difficult, but also because the budget was too limited. > Haskell libraries that export safe pure interfaces, internally use > unsafe interfaces (e.g. raw memory access) for performance reasons. > So it is rather unclear how to expose a usable untrusted subset of the > language except through static analysis (type level guarantess) of the > sort that I'm reluctant to trust as a result of high complexity. Validating that an inference chain is correct is much easier. You need to have pretty simple axioms to make sure you don't get an inconsistent system, or one that doesn't prove the things you believe it proves. (This did indeed happen, IIRC the $ operator turned out to be much less safe than originally believed sometime around 2000.) > So while I take no position on whether Safe Haskell should or should not > be abandoned, I agree that it is a valid question because the problem is > rather non-trivial, and it is not clear whether it is actually possible to > implement a sufficiently robust design. Fully agreed. Not because the inference engine cannot be trusted, but because it's hard to set up a good set of axioms if you have things like unsafe operations and still want to prove that their use in a particular piece of is safe under Haskell's semantics. OTOH this is one of the things that I would have liked to see happen two decades ago and it didn't materialze; quite the opposite, the attempts at putting up a formal semantics for Haskell, while promising initially, were given up because it would be too much work, and that means any inference engine is walking on shifting ground. I do not feel very confident in *that* regard, I have to say. Still, it could be more trustworthy than syscall sandboxing, if Safe Haskell is usefully strict enough about its inferencing. I just don't have enough insight into Safe Haskell so make any predictions there :-) Regards, Jo From svenpanne at gmail.com Thu Apr 22 20:36:29 2021 From: svenpanne at gmail.com (Sven Panne) Date: Thu, 22 Apr 2021 22:36:29 +0200 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> <010f0178f10c7cc8-a26f8a4c-b402-4132-b1a0-deccb5f1b26d-000000@us-east-2.amazonses.com> <61fc03aa-2345-5303-76e5-bf75b17a4f07@rogers.com> <32e32632-395d-5a4f-2c1b-9def91d12aaa@durchholz.org> Message-ID: Am Do., 22. Apr. 2021 um 21:29 Uhr schrieb Joachim Durchholz < jo at durchholz.org>: > True, but the semantics behind each syscall can be horrendously complex. > [...] > That's correct, but a sandbox doesn't need to implement all of it. Checking that e.g. only something below a given directory can be opened (perhaps e.g. only for reading) is relatively easy, prohibiting creation of sockets, limiting the amount of memory which can be mmapped (and how), etc. etc. I can hardly imagine what could be considered "safe" for a program which can use all of e.g. POSIX. > That's why you can have a sandbox and this still doesn't protect you > from symlink timing attacks on /tmp [...] Well, if it is *your* sandbox and some processes from outside the sandbox can change its contents arbitrarily, then you have more security issues than simple symlink attacks. > Instead you have to make sure that all software uses mktemp instead of > doing nonatomic file creation&opening. [...] > Nope, one has just to make sure that the sandboxes are isolated. This is relatively easy on the syscall level (e.g. simulating "your" own /tmp etc.). Except that there is no such thing as an inherently safe syscall > interface, there are unsafe ways to use it. > And that's exactly the reason why you don't give the full power of all syscalls to a sandboxed program. > And that's where language-based safety can help. [...] > Only if *all* of your program is written in that single language, which is hardly the case for every non-toy program: Sooner or later you call out to a C library, and then all bets are off. In general: I think all security-related discussions are futile unless one precisely defines what is considered a threat and what is considered to be safe. And I think we agree to disagree here. :-) -------------- next part -------------- An HTML attachment was scrubbed... URL: From J.Hage at uu.nl Fri Apr 23 06:52:24 2021 From: J.Hage at uu.nl (Hage, J. (Jurriaan)) Date: Fri, 23 Apr 2021 06:52:24 +0000 Subject: [Haskell-cafe] Final Call for the early round of Papers for the Haskell Symposium 2021 Message-ID: <3D3A4DA7-5E98-4A95-B266-61305F92E412@uu.nl> Dear all, This is the first call for the *regular* round of papers for the upcoming Haskell Symposium. Please forward to anyone that you believe might be interested. The deadline for this round is May 21. 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 ================== 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 --------- 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 J.Hage at uu.nl Fri Apr 23 06:56:07 2021 From: J.Hage at uu.nl (Hage, J. (Jurriaan)) Date: Fri, 23 Apr 2021 06:56:07 +0000 Subject: [Haskell-cafe] First call for the *regular* round of Papers for the Haskell Symposium 2021 Message-ID: <07D062FE-FF88-4E4F-88E0-8E1A3D23F80E@uu.nl> Dear all, * Please ignore the message I sent a few minutes ago. It had the wrong subject. Sorry for that. * This is the first call for the *regular* round of papers for the upcoming Haskell Symposium. Please forward to anyone that you believe might be interested. The deadline for this round is May 21. 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 ================== 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 --------- 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 lemming at henning-thielemann.de Fri Apr 23 15:04:53 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Fri, 23 Apr 2021 17:04:53 +0200 (CEST) Subject: [Haskell-cafe] [Haskell] [ANNOUNCE] GHC 9.2.1-alpha2 released In-Reply-To: <874kfxps7i.fsf@smart-cactus.org> References: <874kfxps7i.fsf@smart-cactus.org> Message-ID: <60b99977-b1bf-56d3-c7d7-bfb1e1b7370@henning-thielemann.de> On Thu, 22 Apr 2021, Ben Gamari wrote: > The GHC developers are very happy to announce the availability of the > second alpha release in the 9.2.1 series. Binary distributions, source > distributions, and documentation are available at > > https://downloads.haskell.org/ghc/9.2.1-alpha2 When I try a GHC installed from the Debian tarball I get a permission error on the package.cache because of $ ll /usr/local/ghc-9.2.0.20210422/lib/ghc-9.2.0.20210422/package.conf.d/package.cache -rw------- 1 root root 188641 23. Apr 16:56 /usr/local/ghc-9.2.0.20210422/lib/ghc-9.2.0.20210422/package.conf.d/package.cache I can solve the problem with $ sudo chmod a+r /usr/local/ghc-9.2.0.20210422/lib/ghc-9.2.0.20210422/package.conf.d/package.cache From jo at durchholz.org Fri Apr 23 15:50:37 2021 From: jo at durchholz.org (Joachim Durchholz) Date: Fri, 23 Apr 2021 17:50:37 +0200 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> <010f0178f10c7cc8-a26f8a4c-b402-4132-b1a0-deccb5f1b26d-000000@us-east-2.amazonses.com> <61fc03aa-2345-5303-76e5-bf75b17a4f07@rogers.com> <32e32632-395d-5a4f-2c1b-9def91d12aaa@durchholz.org> Message-ID: <36057043-77f5-f52b-152e-d1488c49b446@durchholz.org> Am 22.04.21 um 22:36 schrieb Sven Panne: > Am Do., 22. Apr. 2021 um 21:29 Uhr schrieb Joachim Durchholz > >: > > True, but the semantics behind each syscall can be horrendously > complex. [...] > > > That's correct, but a sandbox doesn't need to implement all of it. > Checking that e.g. only something below a given directory can be opened > (perhaps e.g. only for reading) is relatively easy, That's exactly what I mean: the API is deceptively simple, but the actual semantics is pretty complicated, even open-ended. Things you can have that complicate the picture: - Symlinks - mount -o remount /dir - Prohibiting a subdirectory on NFS but it happens to live on the local machine so you have to remember to prohibit both paths - NFS in general can allow mapping - then there's also VFS, which offers even more mapping options > prohibiting creation > of sockets, limiting the amount of memory which can be mmapped (and > how), etc. etc. These things can indeed be managed at the OS level. Though in practice it's surprisingly hard to close all loopholes. And attackers think in terms of loopholes. > I can hardly imagine what could be considered "safe" for a program which > can use all of e.g. POSIX. Well, that's exactly my point: sandboxes live at the Posix level (actually, at the level of the operating system), and that's a huge and complicated surface to harden. > That's why you can have a sandbox and this still doesn't protect you > from symlink timing attacks on /tmp [...] > > Well, if it is *your* sandbox and some processes from outside the > sandbox can change its contents arbitrarily, then you have more security > issues than simple symlink attacks. I'm not sure what you mean. The sandbox can run such a symlink attack on its own - assuming it officially has access to /tmp. Of course, sandbox makers have been made aware of this attack and are hardening their sandboxes against it. The point isn't this particular attack, it's that seemingly simple APIs can offer very unexpected loopholes, just by not providing atomicity. I simply don't believe it's possible to build a reliable sandbox. 20 years of Javascript hardening attempts and proved that it's possible to make attacks harder, but we still see pown2own successes. > Except that there is no such thing as an inherently safe syscall > interface, there are unsafe ways to use it. > > And that's exactly the reason why you don't give the full power of all > syscalls to a sandboxed program. Which is exactly the point at which sandbox makers get pressured into adding yet another feature to work around a restriction, on the grounds that "but THIS way of doing it is safe" - which it often enough isn't. The semantics is too complex, it's riddled with aliasing and atomicity problems. > And that's where language-based safety can help. [...] > > Only if *all* of your program is written in that single language, which > is hardly the case for every non-toy program: Sooner or later you call > out to a C library, and then all bets are off. That's why the approaches are complementary. They can't replace each other. > In general: I think all security-related discussions are futile unless > one precisely defines what is considered a threat and what is considered > to be safe. And I think we agree to disagree here. :-) Actually I agree with that. I just disagree with the idea that making syscall-level sandboxes has a better ROI than making language checkers. From borgauf at gmail.com Fri Apr 23 16:31:46 2021 From: borgauf at gmail.com (Galaxy Being) Date: Fri, 23 Apr 2021 11:31:46 -0500 Subject: [Haskell-cafe] repeat confusion Message-ID: I'm in Bird's *Thinking Functionally with Haskell *and he has this code to transpose a matrix based on a list of row lists transpose :: [[a]] -> [[a]] transpose [xs] = [[x] | x <- xs] transpose (xs:xss) = zipWith (:) xs (transpose xss) then he says transpose can be rewritten with this pattern transpose [] = ... what could be the rest of it? The answer he gives is transpose2 :: [[a]] -> [[a]] transpose2 [] = repeat [] transpose2 (xs:xss) = zipWith (:) xs (transpose2 xss) where repeat [] gives an infinite list of repetitions. And, he says, note that transpose [xs] = zipWith (;) xs (repeat []) = [[x] | x <- xs] I suppose I get this last equation, but I don't understand repeat in transpose2. Can someone explain this to me? LB -------------- next part -------------- An HTML attachment was scrubbed... URL: From lemming at henning-thielemann.de Fri Apr 23 16:37:57 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Fri, 23 Apr 2021 18:37:57 +0200 (CEST) Subject: [Haskell-cafe] repeat confusion In-Reply-To: References: Message-ID: <1f4a29bf-26f1-d61d-4819-19552ac6832@henning-thielemann.de> On Fri, 23 Apr 2021, Galaxy Being wrote: > I'm in Bird's Thinking Functionally with Haskell and he has this code to transpose a matrix based on a list of row lists > transpose :: [[a]] -> [[a]] > transpose [xs] = [[x] | x <- xs] > transpose (xs:xss) = zipWith (:) xs (transpose xss) > > then he says transpose can be rewritten with this pattern > > transpose [] = ... > > what could be the rest of it? The answer he gives is > > transpose2 :: [[a]] -> [[a]] > transpose2 [] = repeat []   > transpose2 (xs:xss) = zipWith (:) xs (transpose2 xss) > > where repeat [] gives an infinite list of repetitions. And, he says, note that > > transpose [xs] =  zipWith (;) xs (repeat []) = [[x] | x <- xs] > > I suppose I get this last equation, but I don't understand repeat in transpose2. Can someone explain this to me? With, say transpose [] = [], the (zipWith (:)) would be shortened to the empty list. In contrast to that, (repeat []) provides as many list ends as needed. From jclites at mac.com Fri Apr 23 16:57:52 2021 From: jclites at mac.com (Jeff Clites) Date: Fri, 23 Apr 2021 09:57:52 -0700 Subject: [Haskell-cafe] repeat confusion In-Reply-To: References: Message-ID: <37DCB71C-2AE4-4AE0-A761-13D4AC320F0D@mac.com> With transpose, you get a pattern match failure if you try to transpose an empty list, and with transpose2 you get an infinite list (of empty lists). Those are in a sense two ways of representing failure, if you take an empty list to not be a valid matrix. But the second definition “works” because zip (or zipWith) of two lists stops when either list runs out (so you can zip an infinite list with a finite one to get a finite result). I guess the point is to observe that the “transpose [xs]” case is just a specialization of the “transpose (xs:xss)” if you choose “transpose []” carefully. I’m not sure if that’s deeply significant, though it’s a good thing to watch for (special cases that don’t need to be separate cases). In this situation it does make the failure case exotic though. Jeff > On Apr 23, 2021, at 9:31 AM, Galaxy Being wrote: > > I'm in Bird's Thinking Functionally with Haskell and he has this code to transpose a matrix based on a list of row lists > > transpose :: [[a]] -> [[a]] > transpose [xs] = [[x] | x <- xs] > transpose (xs:xss) = zipWith (:) xs (transpose xss) > > then he says transpose can be rewritten with this pattern > > transpose [] = ... > > what could be the rest of it? The answer he gives is > > transpose2 :: [[a]] -> [[a]] > transpose2 [] = repeat [] > transpose2 (xs:xss) = zipWith (:) xs (transpose2 xss) > > where repeat [] gives an infinite list of repetitions. And, he says, note that > > transpose [xs] = zipWith (;) xs (repeat []) = [[x] | x <- xs] > > I suppose I get this last equation, but I don't understand repeat in transpose2. Can someone explain this to me? > > 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 maydwell at gmail.com Fri Apr 23 22:26:55 2021 From: maydwell at gmail.com (Lyndon Maydwell) Date: Sat, 24 Apr 2021 08:26:55 +1000 Subject: [Haskell-cafe] repeat confusion In-Reply-To: References: Message-ID: Think about it like this: [image: image.png] The current elements are zipped with the tails (which are created with transpose). This has to bottom out with empty tails (repeat []). On Sat, Apr 24, 2021 at 2:32 AM Galaxy Being wrote: > I'm in Bird's *Thinking Functionally with Haskell *and he has this code > to transpose a matrix based on a list of row lists > > transpose :: [[a]] -> [[a]] > transpose [xs] = [[x] | x <- xs] > transpose (xs:xss) = zipWith (:) xs (transpose xss) > > then he says transpose can be rewritten with this pattern > > transpose [] = ... > > what could be the rest of it? The answer he gives is > > transpose2 :: [[a]] -> [[a]] > transpose2 [] = repeat [] > transpose2 (xs:xss) = zipWith (:) xs (transpose2 xss) > > where repeat [] gives an infinite list of repetitions. And, he says, note > that > > transpose [xs] = zipWith (;) xs (repeat []) = [[x] | x <- xs] > > I suppose I get this last equation, but I don't understand repeat in > transpose2. Can someone explain this to me? > > 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: -------------- next part -------------- A non-text attachment was scrubbed... Name: image.png Type: image/png Size: 30405 bytes Desc: not available URL: From eborsboom at fpcomplete.com Sat Apr 24 16:38:41 2021 From: eborsboom at fpcomplete.com (Emanuel Borsboom) Date: Sat, 24 Apr 2021 16:38:41 +0000 Subject: [Haskell-cafe] ANN: first release candidate for stack-2.7 Message-ID: You can download binaries for this pre-release from here: https://github.com/commercialhaskell/stack/releases/tag/rc%2Fv2.7.0.1 **Changes since v2.5.1.1:** Behavior changes: * `stack repl` now always warns about GHCi problems with loading multiple packages. It also sets now proper working directory when invoked with one package. See [#5421](https://github.com/commercialhaskell/stack/issues/5421) * `custom-setup` dependencies are now properly initialized for `stack dist`. This makes `explicit-setup-deps` no longer required and that option was removed. See [#4006](https://github.com/commercialhaskell/stack/issues/4006) Other enhancements: * Nix integration now passes `ghcVersion` (in addition to existing `ghc`) to `shell-file` as an identifier that can be looked up in a compiler attribute set. * Nix integration now allows Nix integration if the user is ready in nix-shell. This gets rid of "In Nix shell but reExecL is False" error. * `stack list` is a new command to list package versions in a snapshot. See [#5431](https://github.com/commercialhaskell/stack/pull/5431) * Consider GHC 9.0 a tested compiler and remove warnings. * `custom-preprocessor-extensions` is a new configuration option for allowing stack to be aware of any custom preprocessors you have added to `Setup.hs`. See [#3491](https://github.com/commercialhaskell/stack/issues/3491) * Added `--candidate` flag to `upload` command to upload a package candidate rather than publishing the package. * Error output using `--no-interleaved-output` no longer prepends indentating whitespace. This allows emacs compilation-mode and vim quickfix to locate and track errors. See [#5523](https://github.com/commercialhaskell/stack/pull/5523) Bug fixes: * `stack new` now suppports branches other than `master` as default for GitHub repositories. See [#5422](https://github.com/commercialhaskell/stack/issues/5422) * Ignore all errors from `hi-file-parser`. See [#5445](https://github.com/commercialhaskell/stack/issues/5445) and [#5486](https://github.com/commercialhaskell/stack/issues/5486). * Support basic auth in package-indices. See [#5509](https://github.com/commercialhaskell/stack/issues/5509). * Add support for parsing `.hi`. files from GHC 8.10 and 9.0. See [hi-file-parser#2](https://github.com/commercialhaskell/hi-file-parser/pull/2). -------------- next part -------------- An HTML attachment was scrubbed... URL: From genaim at gmail.com Sun Apr 25 13:19:41 2021 From: genaim at gmail.com (Samir Genaim) Date: Sun, 25 Apr 2021 15:19:41 +0200 Subject: [Haskell-cafe] WST 2021: deadline extension (9 May, 2021) 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 submission deadline was extended to May 9, 2021].* 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: May 9, 2021* (extended) * notification: June 6, 2021 * final version due: June 20, 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 rae at richarde.dev Mon Apr 26 15:12:31 2021 From: rae at richarde.dev (Richard Eisenberg) Date: Mon, 26 Apr 2021 15:12:31 +0000 Subject: [Haskell-cafe] Smooth developer experience with Cloud IDE for modern Haskell now In-Reply-To: References: Message-ID: <010f01790ebd3574-95da4209-5a0d-4f08-b3df-7c3448469a8e-000000@us-east-2.amazonses.com> Hi Compl, Thanks for building this! Having a proper web-based IDE would indeed be a boon for Haskell. Just in case others try this: I had a hard time figuring out how to start. Eventually, I found the `ghci-code` folder in the panel at the left, and then some Haskell files in there. I went into the `tutor` directory and opened up `Tutor1.hs`, which has "Run cell" widgets. Clicking one launched GHCi. Then I could get my way toward loading the files I wanted. I'm sure there's a better way, but I have no experience with VSCode, never mind gitpod.io . Still, in just a few minutes of tinkering, I found this to be a far better online experience than I had previously encountered. It still would be nice to have an even lighter-weight "here's a .hs file and you can load it in GHCi", but this is great for serious development (it seems). Thanks! Richard > On Apr 22, 2021, at 5:19 AM, YueCompl via Haskell-Cafe wrote: > > Dear Cafe, > > I'd like to share that I find that, we can have rather smooth developer experience for Haskell, on cloud, now. > > Gitpod (https://gitpod.io ) recently supported VSCode in addition to Eclipse Theia, making the UX much more smoother, with proper Gitpod workspace setup, now it's much easier for Haskell beginners, as well as chromeOS and Windows users to painlessly onboard modern Haskell. > > Github codespaces (https://github.com/features/codespaces ) is up coming too, there sure will be industry strength cloud infrastructures for serious Haskell development soon. > > And the setup can be fully automated, a full fledged Cloud IDE for modern Haskell development, is only a click away, see my demo: > > https://github.com/complyue/GHCiCode#readme > > I also expect more beginner-friendly tutorials can be written this way, especially for Windows users, they'll be able to touch & feel the mass without going through painful setup procedures. > > Sincerely, > Compl > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From compl.yue at icloud.com Mon Apr 26 16:01:02 2021 From: compl.yue at icloud.com (YueCompl) Date: Tue, 27 Apr 2021 00:01:02 +0800 Subject: [Haskell-cafe] Smooth developer experience with Cloud IDE for modern Haskell now In-Reply-To: <010f01790ebd3574-95da4209-5a0d-4f08-b3df-7c3448469a8e-000000@us-east-2.amazonses.com> References: <010f01790ebd3574-95da4209-5a0d-4f08-b3df-7c3448469a8e-000000@us-east-2.amazonses.com> Message-ID: Hi Richard, Glad you enjoy it this far! It's strange that didn't work for you, as I had put a Gitpod start task to automatically open `Tutor1.hs` on startup: https://github.com/complyue/GHCiCode/blob/712cec080fd60b99d0ecb2467c980075b1c94c1a/.gitpod.yml#L46-L63 ```yaml # Note this has to be the last task to make its terminal session shown # initially, it can reduce the chance for the IDE to hang up on open - name: Open Welcome File(s) command: | # We have to wait IDE ready anyway, a perfect moment to refresh stack # package index now stack update # Note `gp open` will fail until the IDE is up and ready, VSCode takes # more time than Theia as time being, keep attempting until success WelcomeFile='/workspace/GHCiCode/README.md' # gp open won't work until the IDE GUI is ready until gp open ${WelcomeFile}; do echo "Waiting IDE activated ..." sleep 1 done echo "Showing tutorial(s) ..." # Safe to open more files from now on gp open '/workspace/GHCiCode/ghci-code/tutor/Tutor1.hs' ``` Seems Gitpod is still some clunky, may related to their recent support of VSCode. Gitpod used to support Eclipse Theia only, Theia should be more stable w.r.t. Gitpod features, but on the other hand VSCode is much more featureful & stable than Eclipse Theia w.r.t. IDE features. Anyway the manual operations you've found should just work, thanks for sharing! Btw, I recently played with VSCode's Remote SSH feature, it's quite usable with my own Linux servers. Say only if you have a private Linux server/station reachable over SSH, you can connect VSCode IDE via SSH, the IDE UI can run on macOS, Windows and etc. (ChromeBooks or even Android tablets are said to work too but I haven't used one), so you can get native IDE UI with your favorite device, and the compilers and other toolings (cabal, stack, els e.g.) run on the server. I'm surprised to see a long running `stack build` task in the IDE's terminal view will not be killed after I disconnect the IDE, later I reopen the same folder over SSH, it's still there and running. This means now you can have good experience with a portable low-profile laptop or tablet anywhere with SSH connection to any Linux server to do software development. Cheers, Compl > On 2021-04-26, at 23:12, Richard Eisenberg wrote: > > Hi Compl, > > Thanks for building this! Having a proper web-based IDE would indeed be a boon for Haskell. > > Just in case others try this: I had a hard time figuring out how to start. Eventually, I found the `ghci-code` folder in the panel at the left, and then some Haskell files in there. I went into the `tutor` directory and opened up `Tutor1.hs`, which has "Run cell" widgets. Clicking one launched GHCi. Then I could get my way toward loading the files I wanted. I'm sure there's a better way, but I have no experience with VSCode, never mind gitpod.io . > > Still, in just a few minutes of tinkering, I found this to be a far better online experience than I had previously encountered. It still would be nice to have an even lighter-weight "here's a .hs file and you can load it in GHCi", but this is great for serious development (it seems). > > Thanks! > Richard > >> On Apr 22, 2021, at 5:19 AM, YueCompl via Haskell-Cafe > wrote: >> >> Dear Cafe, >> >> I'd like to share that I find that, we can have rather smooth developer experience for Haskell, on cloud, now. >> >> Gitpod (https://gitpod.io ) recently supported VSCode in addition to Eclipse Theia, making the UX much more smoother, with proper Gitpod workspace setup, now it's much easier for Haskell beginners, as well as chromeOS and Windows users to painlessly onboard modern Haskell. >> >> Github codespaces (https://github.com/features/codespaces ) is up coming too, there sure will be industry strength cloud infrastructures for serious Haskell development soon. >> >> And the setup can be fully automated, a full fledged Cloud IDE for modern Haskell development, is only a click away, see my demo: >> >> https://github.com/complyue/GHCiCode#readme >> >> I also expect more beginner-friendly tutorials can be written this way, especially for Windows users, they'll be able to touch & feel the mass without going through painful setup procedures. >> >> Sincerely, >> Compl >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben at well-typed.com Mon Apr 26 17:40:21 2021 From: ben at well-typed.com (Ben Gamari) Date: Mon, 26 Apr 2021 13:40:21 -0400 Subject: [Haskell-cafe] [Haskell] [ANNOUNCE] GHC 9.2.1-alpha2 released In-Reply-To: <60b99977-b1bf-56d3-c7d7-bfb1e1b7370@henning-thielemann.de> References: <874kfxps7i.fsf@smart-cactus.org> <60b99977-b1bf-56d3-c7d7-bfb1e1b7370@henning-thielemann.de> Message-ID: <87r1ixndvf.fsf@smart-cactus.org> Henning Thielemann writes: > On Thu, 22 Apr 2021, Ben Gamari wrote: > >> The GHC developers are very happy to announce the availability of the >> second alpha release in the 9.2.1 series. Binary distributions, source >> distributions, and documentation are available at >> >> https://downloads.haskell.org/ghc/9.2.1-alpha2 > > When I try a GHC installed from the Debian tarball I get a permission > error on the package.cache because of > > $ ll /usr/local/ghc-9.2.0.20210422/lib/ghc-9.2.0.20210422/package.conf.d/package.cache > -rw------- 1 root root 188641 23. Apr 16:56 /usr/local/ghc-9.2.0.20210422/lib/ghc-9.2.0.20210422/package.conf.d/package.cache > > > I can solve the problem with > > $ sudo chmod a+r /usr/local/ghc-9.2.0.20210422/lib/ghc-9.2.0.20210422/package.conf.d/package.cache Hmm, this is quite concerning. Could you open a ticket, Henning? Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 487 bytes Desc: not available URL: From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Mon Apr 26 18:01:02 2021 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Mon, 26 Apr 2021 19:01:02 +0100 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: <36057043-77f5-f52b-152e-d1488c49b446@durchholz.org> References: <010f0178f10c7cc8-a26f8a4c-b402-4132-b1a0-deccb5f1b26d-000000@us-east-2.amazonses.com> <61fc03aa-2345-5303-76e5-bf75b17a4f07@rogers.com> <32e32632-395d-5a4f-2c1b-9def91d12aaa@durchholz.org> <36057043-77f5-f52b-152e-d1488c49b446@durchholz.org> Message-ID: <20210426180102.GD29737@cloudinit-builder> On Fri, Apr 23, 2021 at 05:50:37PM +0200, Joachim Durchholz wrote: > I just disagree with the idea that making syscall-level sandboxes has a > better ROI than making language checkers. I'm curious whether there's anyone in this thread who takes a different point of view, in absolute terms. The point of contention for me (and I would guess for others too) is whether meagre resources at our disposal should be put towards SafeHaskell and other Haskell-based language checkers, or we should just use what the (comparatively) large and experienced Linux, *BSD, etc.. developers are already providing and many users are already using for hardening efforts. Tom From lemming at henning-thielemann.de Mon Apr 26 18:23:53 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Mon, 26 Apr 2021 20:23:53 +0200 (CEST) Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: <20210426180102.GD29737@cloudinit-builder> References: <010f0178f10c7cc8-a26f8a4c-b402-4132-b1a0-deccb5f1b26d-000000@us-east-2.amazonses.com> <61fc03aa-2345-5303-76e5-bf75b17a4f07@rogers.com> <32e32632-395d-5a4f-2c1b-9def91d12aaa@durchholz.org> <36057043-77f5-f52b-152e-d1488c49b446@durchholz.org> <20210426180102.GD29737@cloudinit-builder> Message-ID: <3ecac18f-6110-8c4-585c-422bf4cb13a8@henning-thielemann.de> On Mon, 26 Apr 2021, Tom Ellis wrote: > I'm curious whether there's anyone in this thread who takes a different > point of view, in absolute terms. > > The point of contention for me (and I would guess for others too) is > whether meagre resources at our disposal should be put towards > SafeHaskell and other Haskell-based language checkers, or we should just > use what the (comparatively) large and experienced Linux, *BSD, etc.. > developers are already providing and many users are already using for > hardening efforts. When SafeHaskell came out I found it a good way to mark modules as Safe in order to be warned by GHC if they are actually unsafe. Unfortunately I did not mark many modules this way. If GHC features are too complex to give such safeness warranties then I think this is a problem on its own. How would we evaluate code of other authors? Today, I would add Safe to all modules of a critical package and watch where that fails and why. This use case cannot be managed by any sandboxing, container or virtualization technique. From safinaskar at mail.ru Mon Apr 26 19:37:04 2021 From: safinaskar at mail.ru (=?UTF-8?B?QXNrYXIgU2FmaW4=?=) Date: Mon, 26 Apr 2021 22:37:04 +0300 Subject: [Haskell-cafe] =?utf-8?q?Safe_Haskell=3F?= In-Reply-To: <010f0178e053fd66-c174480a-f10a-4a41-9827-3ad6b4be6023-000000@us-east-2.amazonses.com> References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> <010f0178e053fd66-c174480a-f10a-4a41-9827-3ad6b4be6023-000000@us-east-2.amazonses.com> Message-ID: <1619465824.267612961@f721.i.mail.ru> Hi. Let me describe two hypothetical use cases for safe Haskell. 1. Isabelle ( http://isabelle.in.tum.de ) is written in SML. Input for Isabelle (theory files) are allowed to contain embedded SML source code for extending Isabelle. If someone sends you Isabelle theory and you open it in your Isabelle IDE, this embedded code starts to automatically execute. I don't know whether Isabelle authors put some restrictions to deny arbitrary code execution. So, as you probably guessed, I think this is possible to write similar prover in Haskell. Its theory files will be allowed to contain embedded Haskell code to extend prover. And SafeHaskell will be used to deny arbitrary code execution. 2. Imagine OS entirely written in Haskell. Both kernel and user space programs. In such OS we don't need any hardware methods of restriction of user programs, i. e. we don't need MMU, context switches, separation of ring 0 and ring 3. Security will be achieved by using SafeHaskell. User will be allowed to run code in user space only if it is compiled using trusted Haskell compiler with SafeHaskell enabled. After compilation the code is loaded directly into kernel address space and executed in ring 0. It will be very easy to implement capability-based security. Benefits of such model: a) We don't have MMU and context switch overhead. System call is just function call b) User space programs will not be able to read/write memory directly, so they will not be able to exploit Spectre/Meltdown, so there is no need in costly mitigations for this vulnerabilities (I'm not sure in b)) c) Programs live in one address space, so they can just pass each other data directly. IPC is just function call d) Speed up caused by a), b) and c) can be so huge that it will be bigger than slow down caused by using Haskell instead of C, so usual arguments "Haskell is too slow" will go away == Askar Safin https://github.com/safinaskar From svenpanne at gmail.com Mon Apr 26 20:27:20 2021 From: svenpanne at gmail.com (Sven Panne) Date: Mon, 26 Apr 2021 22:27:20 +0200 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: <20210426180102.GD29737@cloudinit-builder> References: <010f0178f10c7cc8-a26f8a4c-b402-4132-b1a0-deccb5f1b26d-000000@us-east-2.amazonses.com> <61fc03aa-2345-5303-76e5-bf75b17a4f07@rogers.com> <32e32632-395d-5a4f-2c1b-9def91d12aaa@durchholz.org> <36057043-77f5-f52b-152e-d1488c49b446@durchholz.org> <20210426180102.GD29737@cloudinit-builder> Message-ID: Am Mo., 26. Apr. 2021 um 20:02 Uhr schrieb Tom Ellis < tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk>: > [...] The point of contention for me (and I would guess for others too) is > whether meagre resources at our disposal should be put towards > SafeHaskell and other Haskell-based language checkers, or we should > just use what the (comparatively) large and experienced Linux, *BSD, > etc.. developers are already providing and many users are already > using for hardening efforts. > I think my POV is clear by now. ;-) The current Haskell ecosystem is a bit obscure: There is already a GHC 9.2 alpha, while stack has just an alpha supporting 9.0, and Stackage & Haskell Language Server are still stuck at 8.10.4, so effectively only GHC <= 8.10.4 is usable for quite a few people, I guess. Setting up an up-to-date Haskell development environment is still a difficult process, involving various non-trivial and only lightly documented steps (Example: Given a fully working Spacemacs, but no Haskell SW at all: Try to set up your system for a stack-based workflow with GHC-9.0, including a formatter/linter/code completion/...) . In the meantime, people are discussing more and more esoteric type system extensions for the next GHC release and the advantages of relatively niche features like SafeHaskell. I'm totally aware of the fact that there are different people working on the different parts, nevertheless the overall emphasis is a bit... strange. :-/ -------------- next part -------------- An HTML attachment was scrubbed... URL: From bruno.bernardo at tutanota.com Tue Apr 27 07:21:39 2021 From: bruno.bernardo at tutanota.com (Bruno Bernardo) Date: Tue, 27 Apr 2021 09:21:39 +0200 (CEST) Subject: [Haskell-cafe] FMBC 2021 - 3rd Call for Papers (Deadline extensions) Message-ID: [ Please distribute, apologies for multiple postings. ] ======================================================================== 3rd International Workshop on Formal Methods for Blockchains (FMBC) - Third Call https://fmbc.gitlab.io/2021 July 18 or 19 (TBA), 2021, *online* Co-located with the 33nd International Conference on Computer-Aided Verification (CAV 2021) http://i-cav.org/2021/ ------------------------------------------------------------- IMPORTANT DATES -------------------------------- Abstract submission: May 6, 2021 (extended) Paper submission: May 13, 2021 (extended) Notification: June 24, 2021 (extended) 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 -------------------------------- David Dill, Lead Researcher, Blockchain, Novi/Facebook, USA https://research.fb.com/people/dill-david/ -------------------------------- -------------------------------- 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 * Wolfgang Ahrendt (Chalmers University of Technology, Sweden) * Lacramioara Astefanoei (Nomadic Labs, France) * Massimo Bartoletti (University of Cagliari, Italy) * Joachim Breitner (Dfinity Foundation, Germany) * Achim Brucker (University of Exeter, UK) * Zaynah Dargaye (Nomadic Labs, France) * Jérémie Decouchant (TU Delft, Netherlands) * Dana Drachsler Cohen (Technion, Israel) * Ansgar Fehnker (University of Twente, Netherlands) * Maurice Herlihy (Brown University, USA) * Lars Hupel (INNOQ, Germany) * Florian Kammueller (Middlesex University London, UK) * Igor Konnov (Informal Systems, Austria) * Andreas Lochbihler (Digital Asset, Switzerland) * Simão Melo de Sousa (Universidade da Beira Interior, Portugal) * Karl Palmskog (KTH, Sweden) * Maria Potop-Butucaru (Sorbonne Université, France) * Andreas Rossberg (Dfinity Foundation, Germany) * Albert Rubio (Complutense University of Madrid, Spain) * César Sanchez (Imdea, Spain) * Clara Schneidewind (TU Wien, Austria) * Ilya Sergey (Yale-NUS College/NUS, Singapore) * Mark Staples (CSIRO Data61, Australia) * Meng Sun (Peking University, China) * Simon Thompson (University of Kent, UK) * Josef Widder (Informal Systems, Austria) From jon.fairbairn at cl.cam.ac.uk Tue Apr 27 08:29:48 2021 From: jon.fairbairn at cl.cam.ac.uk (Jon Fairbairn) Date: Tue, 27 Apr 2021 09:29:48 +0100 Subject: [Haskell-cafe] Safe Haskell? References: <010f0178f10c7cc8-a26f8a4c-b402-4132-b1a0-deccb5f1b26d-000000@us-east-2.amazonses.com> <61fc03aa-2345-5303-76e5-bf75b17a4f07@rogers.com> <32e32632-395d-5a4f-2c1b-9def91d12aaa@durchholz.org> <36057043-77f5-f52b-152e-d1488c49b446@durchholz.org> <20210426180102.GD29737@cloudinit-builder> Message-ID: Tom Ellis writes: > On Fri, Apr 23, 2021 at 05:50:37PM +0200, Joachim Durchholz wrote: >> I just disagree with the idea that making syscall-level sandboxes has a >> better ROI than making language checkers. > > I'm curious whether there's anyone in this thread who takes a > different point of view, in absolute terms. > > The point of contention for me (and I would guess for others too) is > whether meagre resources at our disposal should be put towards > SafeHaskell and other Haskell-based language checkers, or we should > just use what the (comparatively) large and experienced Linux, *BSD, > etc.. developers are already providing and many users are already > using for hardening efforts. Surely the whole point of Haskell is that it does things differently from other languages. Right from the beginning static checks were valued over runtime ones, and I’m sad to see that this aspect of the language seems to be undervalued these days. -- Jón Fairbairn Jon.Fairbairn at cl.cam.ac.uk From kolar at fit.vut.cz Tue Apr 27 11:29:45 2021 From: kolar at fit.vut.cz (=?utf-8?B?RHXFoWFuIEtvbMOhxZk=?=) Date: Tue, 27 Apr 2021 13:29:45 +0200 Subject: [Haskell-cafe] Haskell translation and transformation Message-ID: <15282618.KH2fdtmOgW@pckolar> Dear Café, I've tried to make my code more compact and faster in runtime and I tried to use primitive types, e.g. Int#. To omit all influences, I ended with Ackermann function: acker :: Int# -> Int# -> Int# acker 0# n = n +# 1# acker m 0# = acker (m -# 1#) 1# acker m n = acker (m -# 1#) (acker m (n -# 1#)) I was quite surprised, that the result was the same as for function without primitive types when it was compiled with -XStrict option. Both memory and time consumption was the same (small difference under 0.5%). Of course, -O2 option was used. :-) I compared with the same C implementation: int acker(int m, int n) { if (m==0) return n+1; if (n==0) return acker(m-1, 1); return acker(m-1, acker(m,n-1)); } with -O2 option used for gcc, the C code is 7 times faster, for no -O options provided both for ghc and gcc, the C code is also 7 times faster. Thus, no difference. My question is: does the ghc use primitive types automatically when possible? Otherwise, I cannot explain the same times... Or, to my big surprise, using primitives does not save memory and computation time, really? And the other question is about reasoning during translation and code generation, what is the reason the code is so slow? I would guess that forcing primitive types and strict evaluation would produce a code with comparable time to C code... The difference seems to be like the one between compiled code to executable and to low level virtual machine code, which is interpreted then. Versions I used: ghc: 8.10.3 gcc: 10.2.0 Dušan P.S. I definitely don't want to make someone upset with the content, I'm simply wondering... D. -------------- next part -------------- An HTML attachment was scrubbed... URL: From jaro.reinders at gmail.com Tue Apr 27 12:57:58 2021 From: jaro.reinders at gmail.com (Jaro Reinders) Date: Tue, 27 Apr 2021 14:57:58 +0200 Subject: [Haskell-cafe] Haskell translation and transformation In-Reply-To: <15282618.KH2fdtmOgW@pckolar> References: <15282618.KH2fdtmOgW@pckolar> Message-ID: > My question is: does the ghc use primitive types automatically when possible? > Otherwise, I cannot explain the same times... Or, to my big surprise, using primitives > does not save memory and computation time, really? GHC mainly uses inlining to transform high level code into code that uses primitive types. Given a piece of code like: acker :: Int -> Int -> Int acker 0 n = n + 1 acker m 0 = acker (m - 1) 1 acker m n = acker (m - 1) (acker m (n - 1)) GHC will inline (+) and (-). The definition of these functions is: (I# x) + (I# y) = I# (x +# y) (I# x) - (I# y) = I# (x -# y) So it transforms to something like: acker 0 (I# n) = I# (n +# 1#) acker (I# m) 0 = acker (I# (m -# 1#)) 1 acker (I# m) (I# n) = acker (I# (m -# 1#)) (acker (I# m) (I# (n -# 1#))) And what I think is called the worker wrapper transformation can transform it into something like: acker (I# m) (I# n) = acker# m n acker# 0# n = n +# 1# acker# m 0# = acker# (m -# 1#) 1# acker# m n = acker# (m -# 1#) (acker# m (n -# 1#)) Which completely eliminates the boxing and unboxing (the I#s) in the tight loop. > And the other question is about reasoning during translation and code generation, > what is the reason the code is so slow? I would guess that forcing primitive types > and strict evaluation would produce a code with comparable time to C code... The > difference seems to be like the one between compiled code to executable and to > low level virtual machine code, which is interpreted then. I think it is mainly that in small tight loops like your ackermann function, low level optimizations become much more important. On godbolt you can easily compare the produced assembly: Haskell https://godbolt.org/z/nejqWsq9z (acker is Main_$wacker_info) C https://godbolt.org/z/WKW7vcvfb (GCC 9.3 is easier to read than 10.2) The main hot code path blocks like: c4pc_info: movq 8(%rbp),%rax decq %rax addq $16,%rbp movq %rbx,%rsi movq %rax,%r14 And movq $c4pc_info,-16(%rbp) decq %rsi movq %r14,%rax movq %rax,-8(%rbp) addq $-16,%rbp jmp Main_$wacker_info Just seem very awkward when compared to to the GCC assembly. But I'm not knowledgeable enough about GHC's internals to know why this awkward code is generated. Cheers, Jaro From kai.prott at hotmail.de Tue Apr 27 14:06:27 2021 From: kai.prott at hotmail.de (Kai-Oliver Prott) Date: Tue, 27 Apr 2021 16:06:27 +0200 Subject: [Haskell-cafe] Template Haskell question Message-ID: Dear Cafe, what is the reasoning behind the behavior of the following two Haskell expressions: ghci> :set -XTemplateHaskell ghci> let f x ($([p| x |])) = x in f 1 2 2 ghci> let f ($([p| x |])) x = x in f 1 2 2 I'd have guessed that they should both fail compilation with "Conflicting definitions for ‘x’" like the following expression. ghci> let f x x = x in f 1 2 error: ... Moreover, it seems odd that the "x" on the right side always refers to the rightmost pattern variable "x" (regardless if quoted or not). Cheers, Kai From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Tue Apr 27 14:28:45 2021 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Tue, 27 Apr 2021 15:28:45 +0100 Subject: [Haskell-cafe] Template Haskell question In-Reply-To: References: Message-ID: <20210427142845.GG29737@cloudinit-builder> On Tue, Apr 27, 2021 at 04:06:27PM +0200, Kai-Oliver Prott wrote: > Moreover, it seems odd that the "x" on the right side always > refers to the rightmost pattern variable "x" (regardless if > quoted or not). I guess this comes from the translation f x x = -> f = \x -> \x -> I'm not familiar enough with TH to say whether one should expect a warning though. Tom From fte at informatik.uni-kiel.de Tue Apr 27 14:38:33 2021 From: fte at informatik.uni-kiel.de (Finn Teegen) Date: Tue, 27 Apr 2021 16:38:33 +0200 Subject: [Haskell-cafe] Template Haskell question In-Reply-To: <20210427142845.GG29737@cloudinit-builder> References: <20210427142845.GG29737@cloudinit-builder> Message-ID: <9fa8a863-7074-78fd-c3e2-6b5b4d83d2ee@informatik.uni-kiel.de> I have tried the examples as well and, indeed, I get a shadowing warning for the first example (along with an unused warning). ghci> :set -XTemplateHaskell -Wall ghci> let f x $([p| x |]) = x in f 1 2 warning: This binding for 'x' shadows... warning: Defined but not used: 'x' However, for the second example I only get the unused warning. ghci> let f $([p| x |]) x = x in f 1 2 warning: Defined but not used: 'x' This still seems to be a bit inconsistent (not mentioning that I would also expect both examples to fail because of non-linear occurrences of 'x'). Cheers, Finn On 27/04/2021 16:28, Tom Ellis wrote: > On Tue, Apr 27, 2021 at 04:06:27PM +0200, Kai-Oliver Prott wrote: >> Moreover, it seems odd that the "x" on the right side always >> refers to the rightmost pattern variable "x" (regardless if >> quoted or not). > > I guess this comes from the translation > > f x x = > > -> > > f = \x -> \x -> > > > I'm not familiar enough with TH to say whether one should expect a > warning though. > > 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 viercc at gmail.com Tue Apr 27 16:00:39 2021 From: viercc at gmail.com (=?UTF-8?B?5a6u6YeM5rS45Y+4?=) Date: Wed, 28 Apr 2021 01:00:39 +0900 Subject: [Haskell-cafe] Template Haskell question In-Reply-To: <9fa8a863-7074-78fd-c3e2-6b5b4d83d2ee@informatik.uni-kiel.de> References: <20210427142845.GG29737@cloudinit-builder> <9fa8a863-7074-78fd-c3e2-6b5b4d83d2ee@informatik.uni-kiel.de> Message-ID: I have tried too, and can provide a few points to raise. See the following gist: https://gist.github.com/viercc/9d22ea0c740183ba0e4b5b00d654dcd3 * This happens with "normal" non-interactive compilation by GHC * Confirmed with both GHC 8.10.4 and GHC 9.0.1 * This happens with duplicate definitions in let let {x = 1; $([p| x |] :: PatQ) = 2 } in x * There's another inconsistent behavior with pattern splices nested inside another quote \x $([p| x |] :: PatQ) -> x -- compiles to \_ x -> x [| \x $([p| x |] :: PatQ) -> x |] -- compiles to [| \x x1 -> x |] -- /* Koji Miyazato */ From viercc at gmail.com Wed Apr 28 08:42:42 2021 From: viercc at gmail.com (=?UTF-8?B?5a6u6YeM5rS45Y+4?=) Date: Wed, 28 Apr 2021 17:42:42 +0900 Subject: [Haskell-cafe] Template Haskell question In-Reply-To: References: <20210427142845.GG29737@cloudinit-builder> <9fa8a863-7074-78fd-c3e2-6b5b4d83d2ee@informatik.uni-kiel.de> Message-ID: I've been digging through GHC source code to understand the reasons behind these behaviors. 1. There are use-cases of TemplateHaskell which do not want duplicate variables in patterns to be error. See a note in source code: https://gitlab.haskell.org/ghc/ghc/-/blob/d04a758296afdfd12300b0466967a42276a2c5a8/compiler/GHC/ThToHs.hs#L1981 Quoting the linked note, > Consider this TH term construction: > do { x1 <- TH.newName "x" -- newName :: String -> Q TH.Name > ; x2 <- TH.newName "x" -- Builds a NameU > ; x3 <- TH.newName "x" > > ; let x = mkName "x" -- mkName :: String -> TH.Name > -- Builds a NameS > > ; return (LamE (..pattern [x1,x2]..) $ > LamE (VarPat x3) $ > ..tuple (x1,x2,x3,x)) } > > It represents the term \[x1,x2]. \x3. (x1,x2,x3,x) > > a) We don't want to complain about "x" being bound twice in > the pattern [x1,x2] > b) We don't want x3 to shadow the x1,x2 > c) We *do* want 'x' (dynamically bound with mkName) to bind > to the innermost binding of "x", namely x3. > d) When pretty printing, we want to print a unique with x1,x2 > etc, else they'll all print as "x" which isn't very helpful To do this, a variable name has one of these two flavors: "system" flavor for names generated by `newName`, and "normal" flavor for names made by `mkName`. Duplicate variable name error is not checked for "system" flavored names. Actually, using `mkName` works in an intended way (cause error) ghci> (\x $(varP (mkName "x")) -> x) 1 2 :10:3: error: • Conflicting definitions for ‘x’ Bound at: :10:3 :10:7-23 • In a lambda abstraction 2. Quoting brackets ([| ... |], [p| ... |]) are translated to TemplateHaskell code (in Q Monad) by desugarar. The desugarar represents *every* bound variable name by names generated by TH.newName. For example, the desugared code of [| \x y -> x y y |] looks like below: do { x <- newName "x"; y <- newName "y"; return $ (LamE [VarP x, VarP y] (...) ) } And [p| x |] is translated in this manner too, causing the discussed behavior. -- /* Koji Miyazato */ From simonpj at microsoft.com Wed Apr 28 08:48:18 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Wed, 28 Apr 2021 08:48:18 +0000 Subject: [Haskell-cafe] Template Haskell question In-Reply-To: References: <20210427142845.GG29737@cloudinit-builder> <9fa8a863-7074-78fd-c3e2-6b5b4d83d2ee@informatik.uni-kiel.de> Message-ID: If you think there's a bug, you may want to file a GHC ticket about this, and include the results of your digging: https://gitlab.haskell.org/ghc/ghc/-/issues Thanks, Simon | -----Original Message----- | From: Haskell-Cafe On Behalf Of | ???? | Sent: 28 April 2021 09:43 | To: Haskell Cafe | Subject: Re: [Haskell-cafe] Template Haskell question | | I've been digging through GHC source code to understand the reasons | behind these behaviors. | | 1. There are use-cases of TemplateHaskell which do not want duplicate | variables in patterns to be error. See a note in source code: | | https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgitl | ab.haskell.org%2Fghc%2Fghc%2F- | %2Fblob%2Fd04a758296afdfd12300b0466967a42276a2c5a8%2Fcompiler%2FGHC%2F | ThToHs.hs%23L1981&data=04%7C01%7Csimonpj%40microsoft.com%7C2132096 | ac75c4d963e1708d90a21baef%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7 | C637551962278898308%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIj | oiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000&sdata=%2FKJpA8A7Pr | d6iPc14c1Nw6DA7Ktl3axSTwTDmTd2VX4%3D&reserved=0 | | Quoting the linked note, | | > Consider this TH term construction: | > do { x1 <- TH.newName "x" -- newName :: String -> Q TH.Name | > ; x2 <- TH.newName "x" -- Builds a NameU | > ; x3 <- TH.newName "x" | > | > ; let x = mkName "x" -- mkName :: String -> TH.Name | > -- Builds a NameS | > | > ; return (LamE (..pattern [x1,x2]..) $ | > LamE (VarPat x3) $ | > ..tuple (x1,x2,x3,x)) } | > | > It represents the term \[x1,x2]. \x3. (x1,x2,x3,x) | > | > a) We don't want to complain about "x" being bound twice in | > the pattern [x1,x2] | > b) We don't want x3 to shadow the x1,x2 | > c) We *do* want 'x' (dynamically bound with mkName) to bind | > to the innermost binding of "x", namely x3. | > d) When pretty printing, we want to print a unique with x1,x2 | > etc, else they'll all print as "x" which isn't very helpful | | To do this, a variable name has one of these two flavors: | "system" flavor for names generated by `newName`, and "normal" flavor | for names made by `mkName`. Duplicate variable name error is not | checked for "system" flavored names. | | Actually, using `mkName` works in an intended way (cause error) | | ghci> (\x $(varP (mkName "x")) -> x) 1 2 | | :10:3: error: | • Conflicting definitions for ‘x’ | Bound at: :10:3 | :10:7-23 | • In a lambda abstraction | | 2. Quoting brackets ([| ... |], [p| ... |]) are translated to | TemplateHaskell code (in Q Monad) by desugarar. The desugarar | represents *every* bound variable name by names generated by | TH.newName. For example, the desugared code of [| \x y -> x y y |] | looks like below: | | do { x <- newName "x"; y <- newName "y"; | return $ (LamE [VarP x, VarP y] (...) ) } | | And [p| x |] is translated in this manner too, causing the discussed | behavior. | | -- | /* Koji Miyazato */ | _______________________________________________ | Haskell-Cafe mailing list | To (un)subscribe, modify options or view archives go to: | https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail. | haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fhaskell- | cafe&data=04%7C01%7Csimonpj%40microsoft.com%7C2132096ac75c4d963e17 | 08d90a21baef%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637551962278 | 908298%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJ | BTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000&sdata=%2FB%2BKDrSZ%2FNG2O3lzqtB | OmPqO64raW5V0cygOLKZ%2FbxQ%3D&reserved=0 | Only members subscribed via the mailman list are allowed to post. From kindaro at gmail.com Wed Apr 28 14:16:33 2021 From: kindaro at gmail.com (Ignat Insarov) Date: Wed, 28 Apr 2021 19:16:33 +0500 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> Message-ID: Maybe the problem is really that Safe Haskell is not taken to be a default good practice? For example, it is easy to know that I should be setting `-Wall`, but hard to know that I should also enable some other warnings not included in `-Wall`. I know the latter because I read some blog posts somewhere and figured there is a consensus that these additional warnings are good, so I enable them by default. For Safe Haskell, I have not read any such blog posts and I have no idea whether it is a good practice to enable it. This feature is not discoverable. This may be a marketing problem. I have a template for my Haskell projects that enables a bunch of extra warnings, language extensions that I like to have enabled by default, dependencies that I wish were in `base`, and so on. Should Safe Haskell go into that template? From oleg.grenrus at iki.fi Wed Apr 28 15:51:51 2021 From: oleg.grenrus at iki.fi (Oleg Grenrus) Date: Wed, 28 Apr 2021 18:51:51 +0300 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> Message-ID: I don't think adding {-# LANGUAGE Safe #-} (as we do with -Wall) is a good idea. The culprit is Safe-inference. While authors of the original Safe Haskell paper argue that it makes more modules Safe without package maintainer knowing about Safe Haskell, problems on Hackage have shown that it is not the case. We simply cannot rely on Safe-inferred modules (continue) being Safe when new versions are released, or worse, when their transitive dependencies change. There are various examples, I had made such mistakes ([1] is most recent one). ([5] is an example of "dependency" change, luckily caught by explicit pragmas). I have implemented -Winferred-safe-imports [2] to warn about such cases.  And also -Wmissing-safe-haskell-mode [3], and used them successfully to cleanup some Safe Haskell mess in Edward Kmett's packages [4].  (If you rely on older versions of the listed packages to be Safe: don't, you are asking for troubles). Another alternative, which IIRC Edward used previously, is to just stamp {-# LANGUAGE Trustworthy #-} everywhere.  But that undermines the whole idea in my opinion. It's almost as bad as saying nothing, every Trustworthy module have to be audited. Yet, you have to use Trustworthy if your package uses Data.Coerce or depends on vector-package or... So while I and others put many hours into making more of ecosystem Safe Haskell, I feel it is work with very bad ROI.  (I wouldn't have done scan like [4] if there weren't also another reason to do it). So while people may freely discuss whether Safe-Haskell or sandboxes are better setup for running untrusted code, Safe Haskell have been around for almost a decade.  If lambdabot is really the only application people can publicly talk about, I just don't feel it's good enough motivation to keep the language feature and add extra burden for the package maintainers. It is one more thing to know about, as if Haskell package authoring and  maintenance weren't complicated enough already. As I mentioned, Safe-inferred just doesn't work in practice, so package maintainers have to be aware of it.  (Compare to the good practice of having type signatures for top-level bindings, Safety is a part of module signature). TL;DR Safe Haskell requires buy-in from every maintainer, but there are barely any users. For how much longer we need to run this "academic experiment"? - Oleg [1]: https://github.com/ekmett/free/pull/204 [2]: https://downloads.haskell.org/ghc/latest/docs/html/users_guide/exts/safe_haskell.html#ghc-flag--Winferred-safe-imports [3]: https://downloads.haskell.org/ghc/latest/docs/html/users_guide/exts/safe_haskell.html#ghc-flag--Wmissing-safe-haskell-mode [4]: https://github.com/ekmett/lens/issues/959 [5]: https://github.com/haskell/time/compare/1.11.1...1.11.1.1 On 28.4.2021 17.16, Ignat Insarov wrote: > Maybe the problem is really that Safe Haskell is not taken to be a > default good practice? > > For example, it is easy to know that I should be setting `-Wall`, but > hard to know that I should also enable some other warnings not > included in `-Wall`. I know the latter because I read some blog posts > somewhere and figured there is a consensus that these additional > warnings are good, so I enable them by default. > > For Safe Haskell, I have not read any such blog posts and I have no > idea whether it is a good practice to enable it. This feature is not > discoverable. This may be a marketing problem. > > I have a template for my Haskell projects that enables a bunch of > extra warnings, language extensions that I like to have enabled by > default, dependencies that I wish were in `base`, and so on. Should > Safe Haskell go into that template? > _______________________________________________ > 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 rae at richarde.dev Wed Apr 28 18:07:26 2021 From: rae at richarde.dev (Richard Eisenberg) Date: Wed, 28 Apr 2021 18:07:26 +0000 Subject: [Haskell-cafe] Safe Haskell? In-Reply-To: References: <010f0178dc106f34-c2d5b25f-00ce-40bb-bb5c-684bcaa3a765-000000@us-east-2.amazonses.com> Message-ID: <010f017919aa12b1-e075ad42-3c3e-486a-97f7-e45a1e53d31d-000000@us-east-2.amazonses.com> > On Apr 28, 2021, at 11:51 AM, Oleg Grenrus wrote: > > TL;DR Safe Haskell requires buy-in from every maintainer, but there are > barely > any users. For how much longer we need to run this "academic experiment"? This is a good way to put it. The reason I've swung around in favor of keeping what we have is that I think *some* structure like Safe Haskell is needed for proper security. The idea is that an author should have to trust only a few packages (like `bytestring`), and these packages can advertise their wide level of trust in a central location, like Hackage. This trust system exists now, but it's not widely advertised. If we were to remove Safe Haskell, this trust system would disappear, only (likely) to be replaced by a very similar trust system required by the successor to Safe Haskell. So, given the real costs associated with discussing how best to remove the feature, then removing it, then having libraries remove it, seem not quite worth it. On the other hand, perhaps you've implicitly suggested something: just disable Safe-inference. That is, every module starts off Unsafe. This could easily be overridden at the package level with default-extensions: Safe in a cabal file. If we had no safe-inference, would that solve the library-level problems? It would certainly remove a good deal of the complexity within GHC! Richard -------------- next part -------------- An HTML attachment was scrubbed... URL: From leah at vuxu.org Wed Apr 28 18:15:57 2021 From: leah at vuxu.org (Leah Neukirchen) Date: Wed, 28 Apr 2021 20:15:57 +0200 Subject: [Haskell-cafe] Munich Virtual Haskell Meeting, 2021-04-29 @ 19:30 Message-ID: <87pmyecm1u.fsf@vuxu.org> Dear all, This week, our monthly Munich Haskell Meeting will take place again tomorrow(!) Thursday, April 29 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 kyrab at mail.ru Thu Apr 29 05:09:19 2021 From: kyrab at mail.ru (kyra) Date: Thu, 29 Apr 2021 08:09:19 +0300 Subject: [Haskell-cafe] [ANNOUNCE] Experimental Windows GHC 8.10.5 binary release. Supports Haskell DLLs. Message-ID: <7d8270dd-bf09-12c9-0180-dcdd8f6c3908@mail.ru> An experimental Windows GHC 8.10.5 64-bit Visual C/Native Windows SDK binary compatible distribution is released. Features: Supports Haskell DLLs. Both static and dynamic compilers are shipped. Uses LLVM tools exclusively, hence linking is blazing fast compared to the stock distro. Is position-independent (can be loaded to any address, not only the lower 2GBs) and generates position-independent code. Based on and targets Microsoft Visual C runtime and native Windows SDK. The "full" variant of distro contains 438 extra prebuilt packages and a set utilities, including not only the mandatory cabal, stack, Happy and Alex, but also linters, formatters, preprocessors, and even beasts like pandoc, haskell-language-server and even Agda compiler. Distribution site: https://awson.github.io/ghc-nw/. Cheers, K. Briantsev (aka awson) From Graham.Hutton at nottingham.ac.uk Fri Apr 30 08:26:32 2021 From: Graham.Hutton at nottingham.ac.uk (Graham Hutton) Date: Fri, 30 Apr 2021 08:26:32 +0000 Subject: [Haskell-cafe] Free online intro/advanced Haskell courses [YouTube] Message-ID: Hi all, For the last few months, I've been preparing YouTube videos for the introductory and advanced Haskell courses that I teach to students at the University of Nottingham. The courses have now finished, and the full sets of videos are now available: Intro course: http://www.tinyurl.com/haskell-notts Advanced course: http://www.tinyurl.com/haskell-notts2 There’s also a 25% discount for the textbook on which both of the courses are based, Programming in Haskell: Discount link: http://tinyurl.com/25pct-off Best wishes, Graham — Professor Graham Hutton School of Computer Science University of Nottingham, UK http://www.cs.nott.ac.uk/~pszgmh This message and any attachment are intended solely for the addressee and may contain confidential information. If you have received this message in error, please contact the sender and delete the email and attachment. Any views or opinions expressed by the author of this email do not necessarily reflect the views of the University of Nottingham. Email communications with the University of Nottingham may be monitored where permitted by law. From mariojlhm at gmail.com Fri Apr 30 16:22:56 2021 From: mariojlhm at gmail.com (Mario J. Hesles) Date: Fri, 30 Apr 2021 11:22:56 -0500 Subject: [Haskell-cafe] Free online intro/advanced Haskell courses [YouTube] In-Reply-To: References: Message-ID: Hi Graham, When I first purchased and read through the first edition of your book, I recall feeling a tad envious of the students who'd had the opportunity to go through the material in a lecture-based setting. These videos will be an excellent resource to point to. Thank you very much for preparing and releasing them. Sincerely, Mario J. Hesles On Fri, Apr 30, 2021 at 3:31 AM Graham Hutton < Graham.Hutton at nottingham.ac.uk> wrote: > Hi all, > > For the last few months, I've been preparing YouTube videos for > the introductory and advanced Haskell courses that I teach to > students at the University of Nottingham. The courses have now > finished, and the full sets of videos are now available: > > Intro course: http://www.tinyurl.com/haskell-notts > > Advanced course: http://www.tinyurl.com/haskell-notts2 > > There’s also a 25% discount for the textbook on which both of > the courses are based, Programming in Haskell: > > Discount link: http://tinyurl.com/25pct-off > > Best wishes, > > Graham > > — > Professor Graham Hutton > School of Computer Science > University of Nottingham, UK > http://www.cs.nott.ac.uk/~pszgmh > > > > > This message and any attachment are intended solely for the addressee > and may contain confidential information. If you have received this > message in error, please contact the sender and delete the email and > attachment. > > Any views or opinions expressed by the author of this email do not > necessarily reflect the views of the University of Nottingham. Email > communications with the University of Nottingham may be monitored > where permitted by law. > > > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From eborsboom at fpcomplete.com Fri Apr 30 20:38:59 2021 From: eborsboom at fpcomplete.com (Emanuel Borsboom) Date: Fri, 30 Apr 2021 20:38:59 +0000 Subject: [Haskell-cafe] ANN: second release candidate for stack-2.7 Message-ID: You can download binaries for this pre-release from https://github.com/commercialhaskell/stack/releases/tag/rc%2Fv2.7.0.3 Please test it and let us know if you run into any trouble. If all goes well, we expect to release the final version in X weeks. Release notes: * Stack's bindists are now built with GHC 8.10.4, and our `stack.yaml` has moved to lts-17.10. This means Stack can now be built on macOS 11.0 (Big Sur) without ugly workarounds. GHC 8.8 is now the minimum GHC version supported for building Stack itself (but this does not effect _users_ of Stack, which still supports using much older GHC versions). **Changes since v2.7.0.1:** (no changes)