From vlad.z.4096 at gmail.com Fri Jun 2 13:04:38 2017 From: vlad.z.4096 at gmail.com (Vladislav Zavialov) Date: Fri, 2 Jun 2017 16:04:38 +0300 Subject: Deprecate KProxy Message-ID: Now that we have -XTypeInType, there's no need for KProxy anymore. The deprecation warning can advise to use regular Proxy instead. From david.feuer at gmail.com Fri Jun 2 16:30:17 2017 From: david.feuer at gmail.com (David Feuer) Date: Fri, 2 Jun 2017 12:30:17 -0400 Subject: Deprecate KProxy In-Reply-To: References: Message-ID: +1, eventually. The big question is when. TypeInType wasn't particularly stable in 8.0. I believe it's improved considerably in 8.2. I'd suggest documenting now (8.2) that it's going to be deprecated and why, but waiting till 8.4 or even 8.6/9.0 to actually do the deed. On Fri, Jun 2, 2017 at 9:04 AM, Vladislav Zavialov wrote: > Now that we have -XTypeInType, there's no need for KProxy anymore. The > deprecation warning can advise to use regular Proxy instead. > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries From ekmett at gmail.com Fri Jun 2 18:02:33 2017 From: ekmett at gmail.com (Edward Kmett) Date: Fri, 2 Jun 2017 14:02:33 -0400 Subject: Deprecate KProxy In-Reply-To: References: Message-ID: I'd say pull the plug on it in 8.4. There are vanishingly few users of this type and they are the type who roll with such punches well. -Edward > On Jun 2, 2017, at 12:30 PM, David Feuer wrote: > > +1, eventually. The big question is when. TypeInType wasn't > particularly stable in 8.0. I believe it's improved considerably in > 8.2. I'd suggest documenting now (8.2) that it's going to be > deprecated and why, but waiting till 8.4 or even 8.6/9.0 to actually > do the deed. > > On Fri, Jun 2, 2017 at 9:04 AM, Vladislav Zavialov > wrote: >> Now that we have -XTypeInType, there's no need for KProxy anymore. The >> deprecation warning can advise to use regular Proxy instead. >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries From drkoster at qq.com Mon Jun 5 07:58:19 2017 From: drkoster at qq.com (=?ISO-8859-1?B?RHIuS29zdGVy?=) Date: Mon, 5 Jun 2017 15:58:19 +0800 Subject: Add DList to base Message-ID: Currently GHC already defined DList for internal use in serveral places. This data type is a nature choice when you need CPS your append, which is a common need. I think base should provide it. Cheers~ Winter -------------- next part -------------- An HTML attachment was scrubbed... URL: From ivan.miljenovic at gmail.com Mon Jun 5 10:21:55 2017 From: ivan.miljenovic at gmail.com (Ivan Lazar Miljenovic) Date: Mon, 5 Jun 2017 20:21:55 +1000 Subject: Add DList to base In-Reply-To: References: Message-ID: On 5 June 2017 at 17:58, Dr.Koster wrote: > Currently GHC already defined DList for internal use in serveral places. > This data type is a nature choice when you need CPS your append, which is a > common need. I think base should provide it. It depends if GHC defines DList for use with base or not; if it's something that's required to use base that _may_ be a semi-valid use case. In general though, as annoying as it is to have to add yet another dependency, build, reload ghci, etc. I prefer to have base to be smaller and packages split up and the dlist package serves admirably. If nothing else, it can iterate faster if a new function needs to be added. Call this a weak +0.1(only because of GHC defining it). -- Ivan Lazar Miljenovic Ivan.Miljenovic at gmail.com http://IvanMiljenovic.wordpress.com From drkoster at qq.com Tue Jun 6 02:21:49 2017 From: drkoster at qq.com (=?gb18030?B?RHIuS29zdGVy?=) Date: Tue, 6 Jun 2017 10:21:49 +0800 Subject: =?gb18030?B?u9i4tKO6IEFkZCBETGlzdCB0byBiYXNl?= In-Reply-To: References: Message-ID: Here's a example of Dlist in base: https://github.com/ghc/ghc/blob/master/libraries/base/GHC/Event/PSQ.hs#L468 And here is in GHC module: https://github.com/ghc/ghc/blob/ba597c1dd1daf9643b72dc7aeace8d6b3fce84eb/utils/mkUserGuidePart/DList.hs It's so simple that people often define it with the code it's used, adding it to base can save these key stokes. ------------------ 原始邮件 ------------------ 发件人: "Ivan Lazar Miljenovic";; 发送时间: 2017年6月5日(星期一) 晚上6:21 收件人: "Dr.Koster"; 抄送: "libraries"; 主题: Re: Add DList to base On 5 June 2017 at 17:58, Dr.Koster wrote: > Currently GHC already defined DList for internal use in serveral places. > This data type is a nature choice when you need CPS your append, which is a > common need. I think base should provide it. It depends if GHC defines DList for use with base or not; if it's something that's required to use base that _may_ be a semi-valid use case. In general though, as annoying as it is to have to add yet another dependency, build, reload ghci, etc. I prefer to have base to be smaller and packages split up and the dlist package serves admirably. If nothing else, it can iterate faster if a new function needs to be added. Call this a weak +0.1(only because of GHC defining it). -- Ivan Lazar Miljenovic Ivan.Miljenovic at gmail.com http://IvanMiljenovic.wordpress.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Tue Jun 6 03:09:27 2017 From: david.feuer at gmail.com (David Feuer) Date: Mon, 5 Jun 2017 23:09:27 -0400 Subject: Add DList to base In-Reply-To: References: Message-ID: I'm -1 on this. For an abstract DList-style list builder, there's the dlist package, which you shouldn't fear depending on (its only dependencies are base and deepseq, both of which are GHC boot packages). The dlist package defines a DList that's an instance of MonadPlus, Traversable, IsList, Ord, Read, Show, IsString, Monoid, and NFData, and provides a variety of functions for working with them. Many of the instances and functions are, inherently, absurdly inefficient. This is because there's basically *nothing* you can do to a DList directly except build one up with `.` and tear one down with `apply`. DLists are extremely efficient precisely when GHC is able to optimize them away altogether. As soon as that is not the case, they're mediocre at best. Now suppose you want a non-abstract DList type (with the constructor exposed). newtype DList a = DL { unDL :: [a] -> [a] } What can that offer in the way of instances? Well, it's clearly not a Functor, so it's certainly not Applicative, Monad, MonadPlus, or Traversable. Ouch. There's no way to write matching Read and Show instances, so you're stuck picking just one. Similarly, IsList and IsString aren't guaranteed to round-trip properly. NFData is utterly absurd, of course. So what's left? Foldable, Monoid, and either Read or Show. The Foldable instance doesn't even interact nicely with the Monoid instance: there's no guarantee that foldMap f xs <> foldMap f ys = foldMap f (xs <> ys). So there's pretty much *nothing going on here*. DList x just doesn't have much more to offer than Endo [x]. We already have Endo; ergo, we don't need DList. On Mon, Jun 5, 2017 at 3:58 AM, Dr.Koster wrote: > Currently GHC already defined DList for internal use in serveral places. > This data type is a nature choice when you need CPS your append, which is a > common need. I think base should provide it. > > Cheers~ > Winter > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > From lemming at henning-thielemann.de Tue Jun 6 06:24:29 2017 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Tue, 6 Jun 2017 08:24:29 +0200 (CEST) Subject: Add DList to base In-Reply-To: References: Message-ID: On Mon, 5 Jun 2017, David Feuer wrote: > DList x just doesn't have much more to offer than Endo [x]. We already > have Endo; ergo, we don't need DList. I admit that I already used Endo as a quickly available DList replacement. From vagarenko at gmail.com Tue Jun 6 23:32:57 2017 From: vagarenko at gmail.com (Alexey Vagarenko) Date: Wed, 7 Jun 2017 04:32:57 +0500 Subject: Proposal: add integer division to GHC.TypeLits Message-ID: I'd like to propose adding Div, Mod and DivMod type families to GHC.TypeLits, which would be promoted versions of methods of Integral class. type family Div :: Nat -> Nat -> Nat type family Mod :: Nat -> Nat -> Nat type family DivMod :: Nat -> Nat -> (Nat, Nat) I've made trac ticket for this https://ghc.haskell.org/trac/ghc/ticket/13652 some time ago, but it hasn't got much attention. -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Wed Jun 7 00:17:59 2017 From: david.feuer at gmail.com (David Feuer) Date: Tue, 6 Jun 2017 20:17:59 -0400 Subject: Proposal: add integer division to GHC.TypeLits In-Reply-To: References: Message-ID: Yes please! +1 On Jun 6, 2017 7:33 PM, "Alexey Vagarenko" wrote: I'd like to propose adding Div, Mod and DivMod type families to GHC.TypeLits, which would be promoted versions of methods of Integral class. type family Div :: Nat -> Nat -> Nat type family Mod :: Nat -> Nat -> Nat type family DivMod :: Nat -> Nat -> (Nat, Nat) I've made trac ticket for this https://ghc.haskell.org/trac/ghc/ticket/13652 some time ago, but it hasn't got much attention. _______________________________________________ Libraries mailing list Libraries at haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries -------------- next part -------------- An HTML attachment was scrubbed... URL: From ryan.gl.scott at gmail.com Wed Jun 7 15:38:41 2017 From: ryan.gl.scott at gmail.com (Ryan Scott) Date: Wed, 7 Jun 2017 08:38:41 -0700 Subject: Proposal: add integer division to GHC.TypeLits Message-ID: +1 from me as well. Ryan S. -------------- next part -------------- An HTML attachment was scrubbed... URL: From oleg.grenrus at iki.fi Wed Jun 7 21:20:10 2017 From: oleg.grenrus at iki.fi (Oleg Grenrus) Date: Thu, 8 Jun 2017 00:20:10 +0300 Subject: Proposal: add integer division to GHC.TypeLits In-Reply-To: References: Message-ID: <9e5aae65-f24e-18d2-3b5c-c59a67da53bc@iki.fi> What would be the semantics, especially what Div n 0 would reduce to: `TypeError` or be irreducible i.e. be stuck? I'm quite neutral about adding `Div` and `Mod` (after all, I added `AppendSymbol` :), -1 for `DivMod` (we need `Fst` and `Snd`in `base` too). Yet, how about the rest of families in `Data.Constraint.Nat` [1] ? 1. Note: If we add them, let's only add them to GHC.TypeNats. 2. Note: current type families form decidable system, which `ghc-typelits-natnormalize` [2] can solve. Adding division complicates that story. Cheers, Oleg. [1]: http://hackage.haskell.org/package/constraints-0.9.1/docs/Data-Constraint-Nat.html [2]: https://hackage.haskell.org/package/ghc-typelits-natnormalise On 07.06.2017 02:32, Alexey Vagarenko wrote: > I'd like to propose adding Div, Mod and DivMod type families to > GHC.TypeLits, > which would be promoted versions of methods of Integral class. > > type family Div :: Nat -> Nat -> Nat > type family Mod :: Nat -> Nat -> Nat > type family DivMod :: Nat -> Nat -> (Nat, Nat) > > I've made trac ticket for this > https://ghc.haskell.org/trac/ghc/ticket/13652 > some time ago, but it hasn't got much attention. > > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: OpenPGP digital signature URL: From ryan.gl.scott at gmail.com Thu Jun 8 15:36:45 2017 From: ryan.gl.scott at gmail.com (Ryan Scott) Date: Thu, 8 Jun 2017 08:36:45 -0700 Subject: Proposal: add integer division to GHC.TypeLits Message-ID: To be clear, I don't think Alexey is proposing that we implement inductive definitions of Div/Mod/DivMod to base (which, as you note, would require implementing type-level Fst and Snd as well). One of the motivations for this proposal is that we _did_ implement and inductive DivMod in the singletons library [1], and it is horribly slow. What I believe Alexey wants is a built-in type family that leverages machine instructions to perform the div/mod calculations behind the hood, much like we currently do for other type-level arithmetic operators, such as (+), (-), and (*). > Yet, how about the rest of families in `Data.Constraint.Nat` Obviously, adding more built-in type families is perhaps not an ideal solution, and there are certainly many more things we _could_ add. But I think integer division is a common-enough use case that it makes sense to support it in base. We need not bog down this proposal with whataboutism. > Note: If we add them, let's only add them to GHC.TypeNats. Agreed. > Note: current type families form decidable system, which > `ghc-typelits-natnormalize` can solve. Adding division complicates > that story. Sure, but then again, there are many type families that you could throw into this system that this particular GHC plugin couldn't reason about. I don't see how Div/Mod are unique in that regard. > What would be the semantics, especially what > > Div n 0 > > would reduce to: `TypeError` or be irreducible i.e. be stuck? I would propose that it would be stuck. There is precedent for this already: (2 - 3) is a stuck type, for instance. This is also the approach that the ghc-typelits-extra plugin takes. Ryan S. ----- [1] https://github.com/goldfirere/singletons/blob/75dae57bbe06b21b3adbb82158c4767ebd695d14/src/Data/Singletons/Prelude/Show.hs#L201-L214 [2] http://hackage.haskell.org/package/ghc-typelits-extra From tmorris at tmorris.net Thu Jun 8 23:41:06 2017 From: tmorris at tmorris.net (Tony Morris) Date: Fri, 9 Jun 2017 09:41:06 +1000 Subject: Add DList to base In-Reply-To: References: Message-ID: Are there any DList specific functions, that are not provided by existing type-classes (such as Foldable), that are typically used? I can think of a few, but they are all in lens. On Tue, Jun 6, 2017 at 4:24 PM, Henning Thielemann < lemming at henning-thielemann.de> wrote: > > On Mon, 5 Jun 2017, David Feuer wrote: > > DList x just doesn't have much more to offer than Endo [x]. We already >> have Endo; ergo, we don't need DList. >> > > I admit that I already used Endo as a quickly available DList replacement. > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ivan.miljenovic at gmail.com Fri Jun 9 00:30:00 2017 From: ivan.miljenovic at gmail.com (Ivan Lazar Miljenovic) Date: Fri, 9 Jun 2017 10:30:00 +1000 Subject: Add DList to base In-Reply-To: References: Message-ID: On 9 June 2017 at 09:41, Tony Morris wrote: > Are there any DList specific functions, that are not provided by existing > type-classes (such as Foldable), that are typically used? I can think of a > few, but they are all in lens. singleton, cons, snoc Though if you have singleton (which can be obtained from either Endo or GHC.Ext.IsList.fromList and `(:[])`; alternatively you could use pure/return but that is less pleasant IMO than the singleton function for code legibility purposes) and mappend you can do cons and snoc. > > On Tue, Jun 6, 2017 at 4:24 PM, Henning Thielemann > wrote: >> >> >> On Mon, 5 Jun 2017, David Feuer wrote: >> >>> DList x just doesn't have much more to offer than Endo [x]. We already >>> have Endo; ergo, we don't need DList. >> >> >> I admit that I already used Endo as a quickly available DList replacement. >> >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -- Ivan Lazar Miljenovic Ivan.Miljenovic at gmail.com http://IvanMiljenovic.wordpress.com From tmorris at tmorris.net Fri Jun 9 04:15:51 2017 From: tmorris at tmorris.net (Tony Morris) Date: Fri, 9 Jun 2017 14:15:51 +1000 Subject: Add DList to base In-Reply-To: References: Message-ID: Yeah, those are in lens, so I am less concerned that they don't appear in base. Specifically, if DList were not to exist in base, and I use the typeclasses that we all know as well as lens, what am I missing out on? On Fri, Jun 9, 2017 at 10:30 AM, Ivan Lazar Miljenovic < ivan.miljenovic at gmail.com> wrote: > On 9 June 2017 at 09:41, Tony Morris wrote: > > Are there any DList specific functions, that are not provided by existing > > type-classes (such as Foldable), that are typically used? I can think of > a > > few, but they are all in lens. > > singleton, cons, snoc > > Though if you have singleton (which can be obtained from either Endo > or GHC.Ext.IsList.fromList and `(:[])`; alternatively you could use > pure/return but that is less pleasant IMO than the singleton function > for code legibility purposes) and mappend you can do cons and snoc. > > > > > On Tue, Jun 6, 2017 at 4:24 PM, Henning Thielemann > > wrote: > >> > >> > >> On Mon, 5 Jun 2017, David Feuer wrote: > >> > >>> DList x just doesn't have much more to offer than Endo [x]. We already > >>> have Endo; ergo, we don't need DList. > >> > >> > >> I admit that I already used Endo as a quickly available DList > replacement. > >> > >> _______________________________________________ > >> Libraries mailing list > >> Libraries at haskell.org > >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > > > > > > > _______________________________________________ > > Libraries mailing list > > Libraries at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > > > > > -- > Ivan Lazar Miljenovic > Ivan.Miljenovic at gmail.com > http://IvanMiljenovic.wordpress.com > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ivan.miljenovic at gmail.com Fri Jun 9 04:58:24 2017 From: ivan.miljenovic at gmail.com (Ivan Lazar Miljenovic) Date: Fri, 9 Jun 2017 14:58:24 +1000 Subject: Add DList to base In-Reply-To: References: Message-ID: On 9 June 2017 at 14:15, Tony Morris wrote: > Yeah, those are in lens, so I am less concerned that they don't appear in > base. Specifically, if DList were not to exist in base, and I use the > typeclasses that we all know as well as lens, what am I missing out on? >From a brief skim through the DList module documentation, those are the only functions defined that do not have direct analogues in existing typeclasses in base. > > On Fri, Jun 9, 2017 at 10:30 AM, Ivan Lazar Miljenovic > wrote: >> >> On 9 June 2017 at 09:41, Tony Morris wrote: >> > Are there any DList specific functions, that are not provided by >> > existing >> > type-classes (such as Foldable), that are typically used? I can think of >> > a >> > few, but they are all in lens. >> >> singleton, cons, snoc >> >> Though if you have singleton (which can be obtained from either Endo >> or GHC.Ext.IsList.fromList and `(:[])`; alternatively you could use >> pure/return but that is less pleasant IMO than the singleton function >> for code legibility purposes) and mappend you can do cons and snoc. >> >> > >> > On Tue, Jun 6, 2017 at 4:24 PM, Henning Thielemann >> > wrote: >> >> >> >> >> >> On Mon, 5 Jun 2017, David Feuer wrote: >> >> >> >>> DList x just doesn't have much more to offer than Endo [x]. We already >> >>> have Endo; ergo, we don't need DList. >> >> >> >> >> >> I admit that I already used Endo as a quickly available DList >> >> replacement. >> >> >> >> _______________________________________________ >> >> Libraries mailing list >> >> Libraries at haskell.org >> >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> > >> > >> > >> > _______________________________________________ >> > Libraries mailing list >> > Libraries at haskell.org >> > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> > >> >> >> >> -- >> Ivan Lazar Miljenovic >> Ivan.Miljenovic at gmail.com >> http://IvanMiljenovic.wordpress.com > > -- Ivan Lazar Miljenovic Ivan.Miljenovic at gmail.com http://IvanMiljenovic.wordpress.com From drkoster at qq.com Wed Jun 14 03:26:06 2017 From: drkoster at qq.com (=?gb18030?B?RHIuS29zdGVy?=) Date: Wed, 14 Jun 2017 11:26:06 +0800 Subject: =?gb18030?B?u9i4tKO6IEFkZCBETGlzdCB0byBiYXNl?= In-Reply-To: References: Message-ID: > What can that offer in the way of instances? Well, it's clearly not a > Functor, so it's certainly not Applicative, Monad, MonadPlus, or > Traversable. Ouch. There's no way to write matching Read and Show > instances, so you're stuck picking just one. Similarly, IsList and > IsString aren't guaranteed to round-trip properly. NFData is utterly > absurd, of course. So what's left? Foldable, Monoid, and either Read > or Show. The Foldable instance doesn't even interact nicely with the > Monoid instance: there's no guarantee that foldMap f xs <> foldMap f > ys = foldMap f (xs <> ys). So there's pretty much *nothing going on > here*. DList x just doesn't have much more to offer than Endo [x]. We > already have Endo; ergo, we don't need DList. I think that's OK: 1) If we're concerning those inefficient instances(My understanding is those defined using `toList`, such as `Foldable` and `Functor`), we can just don't add them. 2) Even `type DList a = Endo [a]` is OK, what i'm asking is CPSed operations (such as cons, replicate...) working on this type, not those instances. BTW. Isn't current `NFData`instance in dlist package problematic? We should directly `seq` the function IMHO. ------------------ 原始邮件 ------------------ 发件人: "David Feuer";; 发送时间: 2017年6月6日(星期二) 中午11:09 收件人: "Dr.Koster"; 抄送: "libraries"; 主题: Re: Add DList to base I'm -1 on this. For an abstract DList-style list builder, there's the dlist package, which you shouldn't fear depending on (its only dependencies are base and deepseq, both of which are GHC boot packages). The dlist package defines a DList that's an instance of MonadPlus, Traversable, IsList, Ord, Read, Show, IsString, Monoid, and NFData, and provides a variety of functions for working with them. Many of the instances and functions are, inherently, absurdly inefficient. This is because there's basically *nothing* you can do to a DList directly except build one up with `.` and tear one down with `apply`. DLists are extremely efficient precisely when GHC is able to optimize them away altogether. As soon as that is not the case, they're mediocre at best. Now suppose you want a non-abstract DList type (with the constructor exposed). newtype DList a = DL { unDL :: [a] -> [a] } What can that offer in the way of instances? Well, it's clearly not a Functor, so it's certainly not Applicative, Monad, MonadPlus, or Traversable. Ouch. There's no way to write matching Read and Show instances, so you're stuck picking just one. Similarly, IsList and IsString aren't guaranteed to round-trip properly. NFData is utterly absurd, of course. So what's left? Foldable, Monoid, and either Read or Show. The Foldable instance doesn't even interact nicely with the Monoid instance: there's no guarantee that foldMap f xs <> foldMap f ys = foldMap f (xs <> ys). So there's pretty much *nothing going on here*. DList x just doesn't have much more to offer than Endo [x]. We already have Endo; ergo, we don't need DList. On Mon, Jun 5, 2017 at 3:58 AM, Dr.Koster wrote: > Currently GHC already defined DList for internal use in serveral places. > This data type is a nature choice when you need CPS your append, which is a > common need. I think base should provide it. > > Cheers~ > Winter > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Wed Jun 14 05:58:03 2017 From: david.feuer at gmail.com (David Feuer) Date: Wed, 14 Jun 2017 01:58:03 -0400 Subject: =?UTF-8?B?UmU6IOWbnuWkje+8miBBZGQgRExpc3QgdG8gYmFzZQ==?= In-Reply-To: References: Message-ID: The current NFData instance in dlist is the best you can do. seq on a function (very) rarely does what you want. The instance the package defines guarantees that the DList represents a list that can be reduced to normal form. The semantics are right. Efficiency-wise, it's lousy, but there's no way to fix it (without changing the underlying representation). On Jun 13, 2017 11:26 PM, "Dr.Koster" wrote: > What can that offer in the way of instances? Well, it's clearly not a > Functor, so it's certainly not Applicative, Monad, MonadPlus, or > Traversable. Ouch. There's no way to write matching Read and Show > instances, so you're stuck picking just one. Similarly, IsList and > IsString aren't guaranteed to round-trip properly. NFData is utterly > absurd, of course. So what's left? Foldable, Monoid, and either Read > or Show. The Foldable instance doesn't even interact nicely with the > Monoid instance: there's no guarantee that foldMap f xs <> foldMap f > ys = foldMap f (xs <> ys). So there's pretty much *nothing going on > here*. DList x just doesn't have much more to offer than Endo [x]. We > already have Endo; ergo, we don't need DList. I think that's OK: 1) If we're concerning those inefficient instances(My understanding is those defined using `toList`, such as `Foldable` and `Functor`), we can just don't add them. 2) Even `type DList a = Endo [a]` is OK, what i'm asking is CPSed operations (such as cons, replicate...) working on this type, not those instances. BTW. Isn't current `NFData`instance in dlist package problematic? We should directly `seq` the function IMHO. ------------------ 原始邮件 ------------------ *发件人:* "David Feuer";; *发送时间:* 2017年6月6日(星期二) 中午11:09 *收件人:* "Dr.Koster"; *抄送:* "libraries"; *主题:* Re: Add DList to base I'm -1 on this. For an abstract DList-style list builder, there's the dlist package, which you shouldn't fear depending on (its only dependencies are base and deepseq, both of which are GHC boot packages). The dlist package defines a DList that's an instance of MonadPlus, Traversable, IsList, Ord, Read, Show, IsString, Monoid, and NFData, and provides a variety of functions for working with them. Many of the instances and functions are, inherently, absurdly inefficient. This is because there's basically *nothing* you can do to a DList directly except build one up with `.` and tear one down with `apply`. DLists are extremely efficient precisely when GHC is able to optimize them away altogether. As soon as that is not the case, they're mediocre at best. Now suppose you want a non-abstract DList type (with the constructor exposed). newtype DList a = DL { unDL :: [a] -> [a] } What can that offer in the way of instances? Well, it's clearly not a Functor, so it's certainly not Applicative, Monad, MonadPlus, or Traversable. Ouch. There's no way to write matching Read and Show instances, so you're stuck picking just one. Similarly, IsList and IsString aren't guaranteed to round-trip properly. NFData is utterly absurd, of course. So what's left? Foldable, Monoid, and either Read or Show. The Foldable instance doesn't even interact nicely with the Monoid instance: there's no guarantee that foldMap f xs <> foldMap f ys = foldMap f (xs <> ys). So there's pretty much *nothing going on here*. DList x just doesn't have much more to offer than Endo [x]. We already have Endo; ergo, we don't need DList. On Mon, Jun 5, 2017 at 3:58 AM, Dr.Koster wrote: > Currently GHC already defined DList for internal use in serveral places. > This data type is a nature choice when you need CPS your append, which is a > common need. I think base should provide it. > > Cheers~ > Winter > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -------------- next part -------------- An HTML attachment was scrubbed... URL: From andrew.thaddeus at gmail.com Sun Jun 18 14:24:09 2017 From: andrew.thaddeus at gmail.com (Andrew Martin) Date: Sun, 18 Jun 2017 10:24:09 -0400 Subject: Compact Normal Form and ST Message-ID: <20170618142409.GA7507@thadasaurus> In the primops file where the compact normal form functions are documented (https://github.com/ghc/ghc/blob/adcd1c62b6d372f100ccf1d5d7cd94f79aaac194/compiler/prelude/primops.txt.pp#L2487), I noticed that all of the functions have type signatures that constrain them to only being used in IO. For example: compactAdd# :: Compact# -> a -> State# RealWorld -> (# State# RealWorld, a #) I would like to know if generalizing these to allow them to work in ST would be sound. That is, changing the type signature to: compactAdd# :: Compact# -> a -> State# s -> (# State# s, a #) I'm not requesting that this change actually be made. I only want to know if using unsafeCoerce to create the second function for my own project would actually be sound. For those interested in knowing why I want this, it's because there are situation where I'm interested in building up a giant structure in a compact region, but in a way that doesn't actually require IO. I think it's a pity to have to use a type signature with IO and then call unsafePerformIO at the end instead of using the more constrained ST, and runST, which makes it clear that I'm not doing anything observable form the outside. As a minor bonus, the ST version of the Compact data type shouldn't need the lock that the IO version does, since concurrent calls to compactAdd are not possible. -Andrew Martin From ezyang at mit.edu Mon Jun 19 03:49:10 2017 From: ezyang at mit.edu (Edward Z. Yang) Date: Sun, 18 Jun 2017 23:49:10 -0400 Subject: Compact Normal Form and ST In-Reply-To: <20170618142409.GA7507@thadasaurus> References: <20170618142409.GA7507@thadasaurus> Message-ID: <1497843947-sup-6951@sabre> There are two senses of referential transparency here which should be considered. First is whether or not you will get the same value results if you use the compact functionality in ST. Here, the answer is yes. Compact normal form has very trivial semantics in this domain, and it would have been OK even to make compact normal forms be pure functions. Second is whether or not the performance characteristics are preserved. Here, the situation is different. Most notably, pure expressions and invocations of the same runST block may be commoned up (via an optimization pass like CSE.) In that case, what was previously two separate compact blocks may be commoned up into a single one. This could be disaster if you were planning to use these blocks as separate allocation buffers for subsequent modifications. This motivated specializing compact to IO. It won't segfault if you put it in ST, but the performance characteristics might change. Edward Excerpts from Andrew Martin's message of 2017-06-18 10:24:09 -0400: > In the primops file where the compact normal form functions are > documented (https://github.com/ghc/ghc/blob/adcd1c62b6d372f100ccf1d5d7cd94f79aaac194/compiler/prelude/primops.txt.pp#L2487), > I noticed that all of the functions have type signatures that constrain > them to only being used in IO. For example: > > compactAdd# :: Compact# -> a -> State# RealWorld -> (# State# RealWorld, a #) > > I would like to know if generalizing these to allow them to work in ST would > be sound. That is, changing the type signature to: > > compactAdd# :: Compact# -> a -> State# s -> (# State# s, a #) > > I'm not requesting that this change actually be made. I only want to > know if using unsafeCoerce to create the second function for my own > project would actually be sound. > > For those interested in knowing why I want this, it's because there are > situation where I'm interested in building up a giant structure in a > compact region, but in a way that doesn't actually require IO. I think > it's a pity to have to use a type signature with IO and then call > unsafePerformIO at the end instead of using the more constrained ST, > and runST, which makes it clear that I'm not doing anything observable > form the outside. > > As a minor bonus, the ST version of the Compact data type shouldn't need > the lock that the IO version does, since concurrent calls to compactAdd > are not possible. > > -Andrew Martin > From david.feuer at gmail.com Mon Jun 19 08:41:52 2017 From: david.feuer at gmail.com (David Feuer) Date: Mon, 19 Jun 2017 04:41:52 -0400 Subject: Compact Normal Form and ST In-Reply-To: References: <20170618142409.GA7507@thadasaurus> <1497843947-sup-6951@sabre> Message-ID: Can you explain how things could go wrong in ST, perhaps with an example? It's hard to see the potential problem. On Jun 18, 2017 11:49 PM, "Edward Z. Yang" wrote: There are two senses of referential transparency here which should be considered. First is whether or not you will get the same value results if you use the compact functionality in ST. Here, the answer is yes. Compact normal form has very trivial semantics in this domain, and it would have been OK even to make compact normal forms be pure functions. Second is whether or not the performance characteristics are preserved. Here, the situation is different. Most notably, pure expressions and invocations of the same runST block may be commoned up (via an optimization pass like CSE.) In that case, what was previously two separate compact blocks may be commoned up into a single one. This could be disaster if you were planning to use these blocks as separate allocation buffers for subsequent modifications. This motivated specializing compact to IO. It won't segfault if you put it in ST, but the performance characteristics might change. Edward Excerpts from Andrew Martin's message of 2017-06-18 10:24:09 -0400: > In the primops file where the compact normal form functions are > documented (https://github.com/ghc/ghc/blob/adcd1c62b6d372f100ccf1d5d7cd94 f79aaac194/compiler/prelude/primops.txt.pp#L2487), > I noticed that all of the functions have type signatures that constrain > them to only being used in IO. For example: > > compactAdd# :: Compact# -> a -> State# RealWorld -> (# State# RealWorld, a #) > > I would like to know if generalizing these to allow them to work in ST would > be sound. That is, changing the type signature to: > > compactAdd# :: Compact# -> a -> State# s -> (# State# s, a #) > > I'm not requesting that this change actually be made. I only want to > know if using unsafeCoerce to create the second function for my own > project would actually be sound. > > For those interested in knowing why I want this, it's because there are > situation where I'm interested in building up a giant structure in a > compact region, but in a way that doesn't actually require IO. I think > it's a pity to have to use a type signature with IO and then call > unsafePerformIO at the end instead of using the more constrained ST, > and runST, which makes it clear that I'm not doing anything observable > form the outside. > > As a minor bonus, the ST version of the Compact data type shouldn't need > the lock that the IO version does, since concurrent calls to compactAdd > are not possible. > > -Andrew Martin > _______________________________________________ Libraries mailing list Libraries at haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries -------------- next part -------------- An HTML attachment was scrubbed... URL: From andrew.thaddeus at gmail.com Mon Jun 19 13:06:39 2017 From: andrew.thaddeus at gmail.com (Andrew Martin) Date: Mon, 19 Jun 2017 09:06:39 -0400 Subject: Compact Normal Form and ST In-Reply-To: References: <20170618142409.GA7507@thadasaurus> <1497843947-sup-6951@sabre> Message-ID: I too am struggling to find a scenario in which this causes something to go wrong. Ending up with only one block instead of two copies of it seems like it could only be a problem, as Edward says, "if you were planning to use these blocks as separate allocation buffers for subsequent modifications". But, mutable byte arrays allocated by newByteArray# cannot escape runST, so I don't see how this could happen. Well, I guess if you returned a frozen array, and then you thawed it for subsequent modification outside of runST, that would be problematic, but CSE already makes that unsafe, even without involving compact regions. It's good to know that, for my purposes, I'm in the clear, but I would also like to hear from Edward clarifying the original statement. -Andrew Martin On Mon, Jun 19, 2017 at 4:41 AM, David Feuer wrote: > Can you explain how things could go wrong in ST, perhaps with an example? > It's hard to see the potential problem. > > On Jun 18, 2017 11:49 PM, "Edward Z. Yang" wrote: > > There are two senses of referential transparency here which should be > considered. First is whether or not you will get the same value results > if you use the compact functionality in ST. Here, the answer is yes. > Compact normal form has very trivial semantics in this domain, and > it would have been OK even to make compact normal forms be pure > functions. > > Second is whether or not the performance characteristics are preserved. > Here, the situation is different. Most notably, pure expressions and > invocations of the same runST block may be commoned up (via an > optimization pass like CSE.) In that case, what was previously two > separate compact blocks may be commoned up into a single one. This > could be disaster if you were planning to use these blocks as separate > allocation buffers for subsequent modifications. > > This motivated specializing compact to IO. It won't segfault if you > put it in ST, but the performance characteristics might change. > > Edward > > Excerpts from Andrew Martin's message of 2017-06-18 10:24:09 -0400: > > In the primops file where the compact normal form functions are > > documented (https://github.com/ghc/ghc/blob/adcd1c62b6d372f100ccf1d5d7c > d94f79aaac194/compiler/prelude/primops.txt.pp#L2487), > > I noticed that all of the functions have type signatures that constrain > > them to only being used in IO. For example: > > > > compactAdd# :: Compact# -> a -> State# RealWorld -> (# State# > RealWorld, a #) > > > > I would like to know if generalizing these to allow them to work in ST > would > > be sound. That is, changing the type signature to: > > > > compactAdd# :: Compact# -> a -> State# s -> (# State# s, a #) > > > > I'm not requesting that this change actually be made. I only want to > > know if using unsafeCoerce to create the second function for my own > > project would actually be sound. > > > > For those interested in knowing why I want this, it's because there are > > situation where I'm interested in building up a giant structure in a > > compact region, but in a way that doesn't actually require IO. I think > > it's a pity to have to use a type signature with IO and then call > > unsafePerformIO at the end instead of using the more constrained ST, > > and runST, which makes it clear that I'm not doing anything observable > > form the outside. > > > > As a minor bonus, the ST version of the Compact data type shouldn't need > > the lock that the IO version does, since concurrent calls to compactAdd > > are not possible. > > > > -Andrew Martin > > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > > -- -Andrew Thaddeus Martin -------------- next part -------------- An HTML attachment was scrubbed... URL: From ezyang at mit.edu Mon Jun 19 17:58:47 2017 From: ezyang at mit.edu (Edward Z. Yang) Date: Mon, 19 Jun 2017 13:58:47 -0400 Subject: Compact Normal Form and ST In-Reply-To: References: <20170618142409.GA7507@thadasaurus> <1497843947-sup-6951@sabre> Message-ID: <1497894245-sup-2975@sabre> Actually, this is more interesting than I thought! Let me explain. Let's take the compact API and make a hypothetical ST style interface. Here's one possibility: data Compact s a compact :: a -> ST s (Compact s a) getCompact :: Compact a -> a runST :: (forall s. ST s a) -> a Let's consider the following code: let x1 = runST (fmap getCompact (compact big_value)) x2 = runST (fmap getCompact (compact big_value)) GHC may CSE x1 and x2 into a single expression, which means that what was previously two compact expressions turns into a single one. "But Edward", you may say, "That's fine, I only cared about the compact region being distinct within a single ST block. If you really wanted x1 and x2 to be distinct, you should have written it this way:" let (x1, x2) = runST $ do x1 <- fmap getCompact (compact big_value) x2 <- fmap getCompact (compact big_value) return (x1, x2) which is indeed true! So I suppose it depends on what your expectations are. Edward Excerpts from Andrew Martin's message of 2017-06-19 09:06:39 -0400: > I too am struggling to find a scenario in which this causes something to > go wrong. Ending up with only one block instead of two copies of it > seems like it could only be a problem, as Edward says, "if you were > planning to use these blocks as separate allocation buffers for > subsequent modifications". But, mutable byte arrays allocated by > newByteArray# cannot escape runST, so I don't see how this could happen. > Well, I guess if you returned a frozen array, and then you thawed it > for subsequent modification outside of runST, that would be problematic, > but CSE already makes that unsafe, even without involving compact > regions. It's good to know that, for my purposes, I'm in the clear, but > I would also like to hear from Edward clarifying the original statement. > > -Andrew Martin > > On Mon, Jun 19, 2017 at 4:41 AM, David Feuer wrote: > > > Can you explain how things could go wrong in ST, perhaps with an example? > > It's hard to see the potential problem. > > > > On Jun 18, 2017 11:49 PM, "Edward Z. Yang" wrote: > > > > There are two senses of referential transparency here which should be > > considered. First is whether or not you will get the same value results > > if you use the compact functionality in ST. Here, the answer is yes. > > Compact normal form has very trivial semantics in this domain, and > > it would have been OK even to make compact normal forms be pure > > functions. > > > > Second is whether or not the performance characteristics are preserved. > > Here, the situation is different. Most notably, pure expressions and > > invocations of the same runST block may be commoned up (via an > > optimization pass like CSE.) In that case, what was previously two > > separate compact blocks may be commoned up into a single one. This > > could be disaster if you were planning to use these blocks as separate > > allocation buffers for subsequent modifications. > > > > This motivated specializing compact to IO. It won't segfault if you > > put it in ST, but the performance characteristics might change. > > > > Edward > > > > Excerpts from Andrew Martin's message of 2017-06-18 10:24:09 -0400: > > > In the primops file where the compact normal form functions are > > > documented (https://github.com/ghc/ghc/blob/adcd1c62b6d372f100ccf1d5d7c > > d94f79aaac194/compiler/prelude/primops.txt.pp#L2487), > > > I noticed that all of the functions have type signatures that constrain > > > them to only being used in IO. For example: > > > > > > compactAdd# :: Compact# -> a -> State# RealWorld -> (# State# > > RealWorld, a #) > > > > > > I would like to know if generalizing these to allow them to work in ST > > would > > > be sound. That is, changing the type signature to: > > > > > > compactAdd# :: Compact# -> a -> State# s -> (# State# s, a #) > > > > > > I'm not requesting that this change actually be made. I only want to > > > know if using unsafeCoerce to create the second function for my own > > > project would actually be sound. > > > > > > For those interested in knowing why I want this, it's because there are > > > situation where I'm interested in building up a giant structure in a > > > compact region, but in a way that doesn't actually require IO. I think > > > it's a pity to have to use a type signature with IO and then call > > > unsafePerformIO at the end instead of using the more constrained ST, > > > and runST, which makes it clear that I'm not doing anything observable > > > form the outside. > > > > > > As a minor bonus, the ST version of the Compact data type shouldn't need > > > the lock that the IO version does, since concurrent calls to compactAdd > > > are not possible. > > > > > > -Andrew Martin > > > > > _______________________________________________ > > Libraries mailing list > > Libraries at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > > > > > > From merijn at inconsistent.nl Fri Jun 23 08:46:29 2017 From: merijn at inconsistent.nl (Merijn Verstraaten) Date: Fri, 23 Jun 2017 10:46:29 +0200 Subject: File operations in base and fork+exec Message-ID: <8C13B528-BC4F-4438-9A29-1CD6DD5502CF@inconsistent.nl> Hi! So I realise proposing backwards incompatible changes to base is tilting at windmills, but I just noticed that most (all?) file operations in base don't open files with O_CLOEXEC, which basically means that every open Handle/file descriptor gets leaked to every single subprocess you fork+exec from Haskell. This seems highly undesirable. For POSIX there appears to be an operation in base that disables this, but it doesn't seem to easily exported. I would like to propose that all operations in base open files with O_CLOEXEC by default and exposing an easy method to mark specific file descriptors to be preserved across exec (This can be achieved by using fcntl to remove the CLOEXEC bit from a specific fd). I'm not sure to what extent Windows behaviour is similar to POSIX, but in principle it should behave the same, I think. Cheers, Merijn From jwlato at gmail.com Fri Jun 23 10:58:33 2017 From: jwlato at gmail.com (John Lato) Date: Fri, 23 Jun 2017 10:58:33 +0000 Subject: File operations in base and fork+exec In-Reply-To: <8C13B528-BC4F-4438-9A29-1CD6DD5502CF@inconsistent.nl> References: <8C13B528-BC4F-4438-9A29-1CD6DD5502CF@inconsistent.nl> Message-ID: Big +1. I got bitten by this a few years ago and was going to do some work on the Unix package to make it easier to do this properly but never got around to it. On Fri, Jun 23, 2017, 10:46 Merijn Verstraaten wrote: > Hi! > > So I realise proposing backwards incompatible changes to base is tilting > at windmills, but I just noticed that most (all?) file operations in base > don't open files with O_CLOEXEC, which basically means that every open > Handle/file descriptor gets leaked to every single subprocess you fork+exec > from Haskell. This seems highly undesirable. For POSIX there appears to be > an operation in base that disables this, but it doesn't seem to easily > exported. > > I would like to propose that all operations in base open files with > O_CLOEXEC by default and exposing an easy method to mark specific file > descriptors to be preserved across exec (This can be achieved by using > fcntl to remove the CLOEXEC bit from a specific fd). > > I'm not sure to what extent Windows behaviour is similar to POSIX, but in > principle it should behave the same, I think. > > Cheers, > Merijn > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -------------- next part -------------- An HTML attachment was scrubbed... URL: From mail at nh2.me Fri Jun 23 11:33:21 2017 From: mail at nh2.me (=?UTF-8?Q?Niklas_Hamb=c3=bcchen?=) Date: Fri, 23 Jun 2017 13:33:21 +0200 Subject: File operations in base and fork+exec In-Reply-To: <8C13B528-BC4F-4438-9A29-1CD6DD5502CF@inconsistent.nl> References: <8C13B528-BC4F-4438-9A29-1CD6DD5502CF@inconsistent.nl> Message-ID: Hi Merijn, I have proposed the same 2 years ago: https://mail.haskell.org/pipermail/haskell-cafe/2015-July/120523.html I am very much in support of that. As mentioned, Python shows that one can pull that kind of change cleanly. Niklas On 23/06/17 10:46, Merijn Verstraaten wrote: > I would like to propose that all operations in base open files with O_CLOEXEC by default and exposing an easy method to mark specific file descriptors to be preserved across exec From hesselink at gmail.com Fri Jun 23 11:35:16 2017 From: hesselink at gmail.com (Erik Hesselink) Date: Fri, 23 Jun 2017 13:35:16 +0200 Subject: File operations in base and fork+exec In-Reply-To: References: <8C13B528-BC4F-4438-9A29-1CD6DD5502CF@inconsistent.nl> Message-ID: +1. Would be good to get this default in 'network' as well, I ran into it with sockets in the past. Relevant ticket: https://github.com/haskell/network/issues/119 Erik On 23 June 2017 at 13:33, Niklas Hambüchen wrote: > Hi Merijn, > > I have proposed the same 2 years ago: > https://mail.haskell.org/pipermail/haskell-cafe/2015-July/120523.html > > I am very much in support of that. > > As mentioned, Python shows that one can pull that kind of change cleanly. > > Niklas > > On 23/06/17 10:46, Merijn Verstraaten wrote: > > I would like to propose that all operations in base open files with > O_CLOEXEC by default and exposing an easy method to mark specific file > descriptors to be preserved across exec > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -------------- next part -------------- An HTML attachment was scrubbed... URL: From spam at scientician.net Fri Jun 23 11:49:08 2017 From: spam at scientician.net (Bardur Arantsson) Date: Fri, 23 Jun 2017 13:49:08 +0200 Subject: File operations in base and fork+exec In-Reply-To: <8C13B528-BC4F-4438-9A29-1CD6DD5502CF@inconsistent.nl> References: <8C13B528-BC4F-4438-9A29-1CD6DD5502CF@inconsistent.nl> Message-ID: On 2017-06-23 10:46, Merijn Verstraaten wrote: > Hi! > > So I realise proposing backwards incompatible changes to base is tilting at windmills, but I just noticed that most (all?) file operations in base don't open files with O_CLOEXEC, which basically means that every open Handle/file descriptor gets leaked to every single subprocess you fork+exec from Haskell. This seems highly undesirable. For POSIX there appears to be an operation in base that disables this, but it doesn't seem to easily exported. > > I would like to propose that all operations in base open files with O_CLOEXEC by default and exposing an easy method to mark specific file descriptors to be preserved across exec (This can be achieved by using fcntl to remove the CLOEXEC bit from a specific fd). > > I'm not sure to what extent Windows behaviour is similar to POSIX, but in principle it should behave the same, I think. > +1. Current behavior is suboptimal for *almost* every use case and also highly surprising. Regards, From ekmett at gmail.com Fri Jun 23 12:41:17 2017 From: ekmett at gmail.com (Edward Kmett) Date: Fri, 23 Jun 2017 14:41:17 +0200 Subject: File operations in base and fork+exec In-Reply-To: References: <8C13B528-BC4F-4438-9A29-1CD6DD5502CF@inconsistent.nl> Message-ID: I'd like to jump on the "this has bitten me before" bandwagon. +1 -Edward On Fri, Jun 23, 2017 at 1:49 PM, Bardur Arantsson wrote: > On 2017-06-23 10:46, Merijn Verstraaten wrote: > > Hi! > > > > So I realise proposing backwards incompatible changes to base is tilting > at windmills, but I just noticed that most (all?) file operations in base > don't open files with O_CLOEXEC, which basically means that every open > Handle/file descriptor gets leaked to every single subprocess you fork+exec > from Haskell. This seems highly undesirable. For POSIX there appears to be > an operation in base that disables this, but it doesn't seem to easily > exported. > > > > I would like to propose that all operations in base open files with > O_CLOEXEC by default and exposing an easy method to mark specific file > descriptors to be preserved across exec (This can be achieved by using > fcntl to remove the CLOEXEC bit from a specific fd). > > > > I'm not sure to what extent Windows behaviour is similar to POSIX, but > in principle it should behave the same, I think. > > > > +1. Current behavior is suboptimal for *almost* every use case and also > highly surprising. > > Regards, > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -------------- next part -------------- An HTML attachment was scrubbed... URL: From qdunkan at gmail.com Fri Jun 23 21:53:40 2017 From: qdunkan at gmail.com (Evan Laforge) Date: Fri, 23 Jun 2017 14:53:40 -0700 Subject: File operations in base and fork+exec In-Reply-To: References: <8C13B528-BC4F-4438-9A29-1CD6DD5502CF@inconsistent.nl> Message-ID: Same here. Very confusing bug and hard to track down. On Fri, Jun 23, 2017 at 5:41 AM, Edward Kmett wrote: > I'd like to jump on the "this has bitten me before" bandwagon. +1 > > -Edward > > On Fri, Jun 23, 2017 at 1:49 PM, Bardur Arantsson > wrote: >> >> On 2017-06-23 10:46, Merijn Verstraaten wrote: >> > Hi! >> > >> > So I realise proposing backwards incompatible changes to base is tilting >> > at windmills, but I just noticed that most (all?) file operations in base >> > don't open files with O_CLOEXEC, which basically means that every open >> > Handle/file descriptor gets leaked to every single subprocess you fork+exec >> > from Haskell. This seems highly undesirable. For POSIX there appears to be >> > an operation in base that disables this, but it doesn't seem to easily >> > exported. >> > >> > I would like to propose that all operations in base open files with >> > O_CLOEXEC by default and exposing an easy method to mark specific file >> > descriptors to be preserved across exec (This can be achieved by using fcntl >> > to remove the CLOEXEC bit from a specific fd). >> > >> > I'm not sure to what extent Windows behaviour is similar to POSIX, but >> > in principle it should behave the same, I think. >> > >> >> +1. Current behavior is suboptimal for *almost* every use case and also >> highly surprising. >> >> Regards, >> >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >