From simon.jakobi at googlemail.com Tue Jul 3 00:53:12 2018 From: simon.jakobi at googlemail.com (Simon Jakobi) Date: Tue, 3 Jul 2018 02:53:12 +0200 Subject: Proposal: Strict variant of foldMap In-Reply-To: References: <76355A8A-559F-40AB-99AA-F61F19C56F22@gmail.com> Message-ID: I have uploaded a patch at https://phabricator.haskell.org/D4924. Am Fr., 29. Juni 2018 um 02:11 Uhr schrieb Andrew Martin : > > I don't see any reason to not do this. Someone just needs to put a differential on phabricator, adding foldMap, a default implementation, and documentation of it. It would be maybe 6 lines total. The default implementation of foldMap' would use foldl' and that would be optimal for everything in base. > > On Thu, Jun 28, 2018 at 6:38 PM, Simon Jakobi via Libraries wrote: >> >> Is there any chance that foldMap' might still make it into base-4.12? >> Am Sa., 9. Juni 2018 um 10:23 Uhr schrieb Edward Kmett : >> > >> > +1 from me. >> > >> > -Edward >> > >> > On Jun 8, 2018, at 9:11 PM, evan at evan-borden.com wrote: >> > >> > +1 We utilize a foldMap' in the freckle codebase. >> > >> > On Fri, Jun 8, 2018 at 1:10 PM, Daniel Cartwright wrote: >> >> >> >> +1 >> >> >> >> On Fri, Jun 8, 2018 at 9:20 AM Andrew Martin wrote: >> >>> >> >>> I propose adding another method to the Foldable typeclass: foldMap' >> >>> >> >>> This has the same behavior as foldMap except that it is strict in the accumulator. This can lead to considerable performance gains when the user knows that monoidal append is strict both arguments. Consider the following example (available as a gist at https://gist.github.com/andrewthad/f79b7022725532baf709514cf08c3955): >> >>> >> >>> {-# LANGUAGE BangPatterns #-} >> >>> {-# OPTIONS_GHC -O2 #-} >> >>> import Gauge >> >>> import Data.Foldable >> >>> import qualified Data.Set as S >> >>> >> >>> foldMap' :: (Monoid m, Foldable f) => (a -> m) -> f a -> m >> >>> foldMap' f = foldl' (\ !acc a -> acc <> f a) mempty >> >>> >> >>> numbers :: [Int] >> >>> numbers = [1..4000] >> >>> >> >>> intToSet :: Int -> S.Set Int >> >>> intToSet i = S.singleton (mod i 10) >> >>> >> >>> main :: IO () >> >>> main = defaultMain >> >>> [ bench "lazy" $ whnf (foldMap intToSet) numbers >> >>> , bench "strict" $ whnf (foldMap' intToSet) numbers >> >>> ] >> >>> >> >>> Here are the results we get from running this: >> >>> >> >>> benchmarked lazy >> >>> time 178.8 μs (176.1 μs .. 183.1 μs) >> >>> 0.996 R² (0.993 R² .. 0.998 R²) >> >>> mean 180.8 μs (179.1 μs .. 183.3 μs) >> >>> std dev 7.242 μs (5.856 μs .. 9.304 μs) >> >>> variance introduced by outliers: 20% (moderately inflated) >> >>> >> >>> benchmarked strict >> >>> time 108.4 μs (106.1 μs .. 111.0 μs) >> >>> 0.997 R² (0.996 R² .. 0.999 R²) >> >>> mean 107.9 μs (107.0 μs .. 109.3 μs) >> >>> std dev 3.672 μs (2.451 μs .. 6.220 μs) >> >>> variance introduced by outliers: 15% (moderately inflated) >> >>> >> >>> These performance gains are considerable. It needs to be a method of Foldable and not just a function written using foldl' for the same reason that the lazy foldMap needs to be a method of Foldable. There are types for which the default implementation can be improved upon. This is a non-breaking change since there is a sensible default implementation. >> >>> >> >>> -- >> >>> -Andrew Thaddeus Martin >> >>> _______________________________________________ >> >>> 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 >> >> >> > >> > >> > >> > -- >> > -- >> > Evan Borden >> > >> > _______________________________________________ >> > 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 >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > > > > -- > -Andrew Thaddeus Martin From mail at joachim-breitner.de Thu Jul 5 15:10:19 2018 From: mail at joachim-breitner.de (Joachim Breitner) Date: Thu, 05 Jul 2018 11:10:19 -0400 Subject: Diagonally in Data.Bimap In-Reply-To: References: Message-ID: <6a62e007b2ed9dffcc2e6782ca8c4810579eb3db.camel@joachim-breitner.de> Hi Am Donnerstag, den 05.07.2018, 15:36 +0200 schrieb Gabor Greif: > Hi! > > Just searched for a `bimap` variant that simultaneously transforms > both components with the same morphism: > > ``` haskell > diag :: Bifunctor p => (a -> b) -> p a a -> p b b > diag f = bimap f f > ``` > > I did not find any. Would it make sense to add it? possibly, I have wanted it too before. Bikeshedding: I’d have expected the name “both”. It also has precedence here: http://hackage.haskell.org/package/extra/docs/Data-Tuple-Extra.html#v:both http://hackage.haskell.org/package/concatenative/docs/Control-Concatenative.html#v:both http://hackage.haskell.org/package/MissingK/docs/Control-Arrow-Extra.html#v:both http://hackage.haskell.org/package/lens-family/docs/Lens-Family2-Stock.html#v:both http://hackage.haskell.org/package/lens/docs/Control-Lens-Traversal.html#v:both Diagonally sounds more like something of type `a -> (a,a)` or similar. > PPS: I would have sent this to libraries at haskell.org but it seem to be > closed group. It should not. Maybe only open to subscribers? (A common crude anti- spam measurement.) Cheers, Joachim -- Joachim Breitner mail at joachim-breitner.de http://www.joachim-breitner.de/ -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 833 bytes Desc: This is a digitally signed message part URL: From neves73 at gmail.com Thu Jul 5 23:39:12 2018 From: neves73 at gmail.com (pedro neves) Date: Thu, 5 Jul 2018 19:39:12 -0400 Subject: Diagonally in Data.Bimap In-Reply-To: <6a62e007b2ed9dffcc2e6782ca8c4810579eb3db.camel@joachim-breitner.de> References: <6a62e007b2ed9dffcc2e6782ca8c4810579eb3db.camel@joachim-breitner.de> Message-ID: Hello All, Can you please remove me from this e-mail string ... I don't know how I got added ... Thank you. On Thu, Jul 5, 2018 at 11:10 AM Joachim Breitner wrote: > Hi > > Am Donnerstag, den 05.07.2018, 15:36 +0200 schrieb Gabor Greif: > > Hi! > > > > Just searched for a `bimap` variant that simultaneously transforms > > both components with the same morphism: > > > > ``` haskell > > diag :: Bifunctor p => (a -> b) -> p a a -> p b b > > diag f = bimap f f > > ``` > > > > I did not find any. Would it make sense to add it? > > possibly, I have wanted it too before. > > Bikeshedding: > I’d have expected the name “both”. It also has precedence here: > http://hackage.haskell.org/package/extra/docs/Data-Tuple-Extra.html#v:both > > http://hackage.haskell.org/package/concatenative/docs/Control-Concatenative.html#v:both > > http://hackage.haskell.org/package/MissingK/docs/Control-Arrow-Extra.html#v:both > > http://hackage.haskell.org/package/lens-family/docs/Lens-Family2-Stock.html#v:both > > http://hackage.haskell.org/package/lens/docs/Control-Lens-Traversal.html#v:both > > Diagonally sounds more like something of type `a -> (a,a)` or similar. > > > PPS: I would have sent this to libraries at haskell.org but it seem to be > > closed group. > > It should not. Maybe only open to subscribers? (A common crude anti- > spam measurement.) > > Cheers, > Joachim > > > -- > Joachim Breitner > mail at joachim-breitner.de > http://www.joachim-breitner.de/ > _______________________________________________ > 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 johnw at newartisans.com Thu Jul 5 23:41:14 2018 From: johnw at newartisans.com (John Wiegley) Date: Thu, 05 Jul 2018 16:41:14 -0700 Subject: Diagonally in Data.Bimap In-Reply-To: References: <6a62e007b2ed9dffcc2e6782ca8c4810579eb3db.camel@joachim-breitner.de> Message-ID: <1530834074.259535.1431495424.33175F9A@webmail.messagingengine.com> You've been unsubscribed from the libraries list. John On Thu, Jul 5, 2018, at 4:39 PM, pedro neves wrote: > Hello All, > > Can you please remove me from this e-mail string ... > > I don't know how I got added ... Thank you. > > On Thu, Jul 5, 2018 at 11:10 AM Joachim Breitner breitner.de> wrote:>> Hi >> >> Am Donnerstag, den 05.07.2018, 15:36 +0200 schrieb Gabor Greif: >> > Hi! >> > >> > Just searched for a `bimap` variant that simultaneously transforms>> > both components with the same morphism: >> > >> > ``` haskell >> > diag :: Bifunctor p => (a -> b) -> p a a -> p b b >> > diag f = bimap f f >> > ``` >> > >> > I did not find any. Would it make sense to add it? >> >> possibly, I have wanted it too before. >> >> Bikeshedding: >> I’d have expected the name “both”. It also has precedence here: >> http://hackage.haskell.org/package/extra/docs/Data-Tuple-Extra.html#v:both>> http://hackage.haskell.org/package/concatenative/docs/Control-Concatenative.html#v:both>> http://hackage.haskell.org/package/MissingK/docs/Control-Arrow-Extra.html#v:both>> http://hackage.haskell.org/package/lens-family/docs/Lens-Family2-Stock.html#v:both>> http://hackage.haskell.org/package/lens/docs/Control-Lens-Traversal.html#v:both>> >> Diagonally sounds more like something of type `a -> (a,a)` or >> similar.>> >> > PPS: I would have sent this to libraries at haskell.org but it seem >> > to be>> > closed group. >> >> It should not. Maybe only open to subscribers? (A common crude anti->> spam measurement.) >> >> Cheers, >> Joachim >> >> >> -- >> Joachim Breitner >> mail at joachim-breitner.de >> http://www.joachim-breitner.de/ >> _______________________________________________ >> 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 -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Sat Jul 7 18:35:24 2018 From: david.feuer at gmail.com (David Feuer) Date: Sat, 7 Jul 2018 14:35:24 -0400 Subject: Discussion: New atomic IORef functions Message-ID: I have proposed[1] the replacement of the atomicModifyMutVar# primop, and the addition of two cheaper but less capable ones. It seems likely that the proposal will succeed, but that the GHC steering committee will leave the question of user interface changes to the libraries list. I would like to open the discussion here. The new primops lead naturally to several thin wrappers: -- Atomically replace the IORef contents -- with the first component of the result of -- applying the function to the old contents. -- Return the old value and the result of -- applying the function, without forcing the latter. -- -- atomicModifyIORef ref f = do -- (_old, ~(_new, res)) <- atomicModifyIORef2Lazy ref f -- return res atomicModifyIORef2Lazy :: IORef a -> (a -> (a, b)) -> IO (a, (a, b)) -- Atomically replace the IORef contents -- with the result of applying the function -- to the old contents. Return the old and -- new contents without forcing the latter. atomicModifyIORefLazy_ :: IORef a -> (a -> a) -> IO (a, a) -- Atomically replace the IORef contents -- with the given value and return the old -- contents. -- -- atomicWriteIORef ref x = void (atomicSwapIORef ref x) atomicSwapIORef :: IORef a -> a -> IO a Based on the code I've read that uses atomicModifyIORef, I believe that the complete laziness of atomicModifyIORef2Lazy and atomicModifyIORefLazy_ is very rarely desirable. I therefore believe we should also (or perhaps instead?) offer stricter versions: atomicModifyIORef2 :: IORef a -> (a -> (a, b)) -> IO (a, (a, b)) atomicModifyIORef2 ref f = do r@(_old, (_new, _res)) <- atomicModifyIORef2Lazy ref f return r atomicModifyIORef_ :: IORef a -> (a -> a) -> IO (a, a) atomicModifyIORef_ ref f = do r@(_old, !_new) <- atomicModifyIORefLazy_ ref f return r The classic atomicModifyIORef also admits a less gratuitously lazy version: atomicModifyIORefNGL :: IORef a -> (a -> (a,b)) -> IO b atomicModifyIORefNGL ref f = do (_old, (_new, res)) <- atomicModifyIORef2 ref f return res Should we add that as well (with a better name)? Should we even consider *replacing* the current atomicModifyIORef with that version? That could theoretically break existing code, but I suspect it would do so very rarely. If we don't change the existing atomicModifyIORef now, I think we should consider deprecating it: it's very easy to accidentally use it too lazily. -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Sat Jul 7 19:09:33 2018 From: david.feuer at gmail.com (David Feuer) Date: Sat, 7 Jul 2018 15:09:33 -0400 Subject: Discussion: New atomic IORef functions In-Reply-To: References: Message-ID: Whoops! I left out the proposal link: https://github.com/ghc-proposals/ghc-proposals/pull/149 Also, what I called atomicModifyIORef_ below should really be called something like atomicModifyIORef'_, since it forces a polymorphic value. Another thing to note: the underlying atomicModifyMutVar2# primop actually supports more than just pairs. It can handle triples, solos, and any other record types whose first components are lifted: atomicModifyIORefSoloLazy :: IORef a -> (a -> Solo a) -> IO (Solo a) atomicModifyIORefSolo :: IORef a -> (a -> Solo a) -> IO a atomicModifyIORef3, atomicModifyIORef3Lazy :: IORef a -> (a -> (a, b, c)) -> IO (a, b, c) etc. Should we add any such? On Sat, Jul 7, 2018, 2:35 PM David Feuer wrote: > I have proposed[1] the replacement of the atomicModifyMutVar# primop, and > the addition of two cheaper but less capable ones. It seems likely that the > proposal will succeed, but that the GHC steering committee will leave the > question of user interface changes to the libraries list. I would like to > open the discussion here. > > The new primops lead naturally to several thin wrappers: > > -- Atomically replace the IORef contents > -- with the first component of the result of > -- applying the function to the old contents. > -- Return the old value and the result of > -- applying the function, without forcing the latter. > -- > -- atomicModifyIORef ref f = do > -- (_old, ~(_new, res)) <- atomicModifyIORef2Lazy ref f > -- return res > atomicModifyIORef2Lazy > :: IORef a -> (a -> (a, b)) -> IO (a, (a, b)) > > -- Atomically replace the IORef contents > -- with the result of applying the function > -- to the old contents. Return the old and > -- new contents without forcing the latter. > atomicModifyIORefLazy_ > :: IORef a -> (a -> a) -> IO (a, a) > > -- Atomically replace the IORef contents > -- with the given value and return the old > -- contents. > -- > -- atomicWriteIORef ref x = void (atomicSwapIORef ref x) > atomicSwapIORef > :: IORef a -> a -> IO a > > Based on the code I've read that uses atomicModifyIORef, I believe that > the complete laziness of atomicModifyIORef2Lazy and atomicModifyIORefLazy_ is > very rarely desirable. I therefore believe we should also (or perhaps > instead?) offer stricter versions: > > atomicModifyIORef2 > :: IORef a -> (a -> (a, b)) -> IO (a, (a, b)) > atomicModifyIORef2 ref f = do > r@(_old, (_new, _res)) <- atomicModifyIORef2Lazy ref f > return r > > atomicModifyIORef_ > :: IORef a -> (a -> a) -> IO (a, a) > atomicModifyIORef_ ref f = do > r@(_old, !_new) <- atomicModifyIORefLazy_ ref f > return r > > The classic atomicModifyIORef also admits a less gratuitously lazy version: > > atomicModifyIORefNGL > :: IORef a -> (a -> (a,b)) -> IO b > atomicModifyIORefNGL ref f = do > (_old, (_new, res)) <- atomicModifyIORef2 ref f > return res > > Should we add that as well (with a better name)? Should we even consider > *replacing* the current atomicModifyIORef with that version? That could > theoretically break existing code, but I suspect it would do so very > rarely. If we don't change the existing atomicModifyIORef now, I think we > should consider deprecating it: it's very easy to accidentally use it too > lazily. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From drkoster at qq.com Sun Jul 8 07:36:06 2018 From: drkoster at qq.com (winter) Date: Sun, 8 Jul 2018 15:36:06 +0800 Subject: Discussion: New atomic IORef functions In-Reply-To: References: Message-ID: <09e17416-8629-6801-0b8b-1ef64d775eaf@qq.com>+A80125156783EBA2 I believe new variations should always be motivated by use-case if there're too many choices, the lazy behavior of old `atomicModifyIORef` is justified by some cases the modifying functions are lazy in its argument, thus a lazy version could win by not forcing previous thunks, we'd want to keep its behavior as how it's documented. As for tuples more than pairs, they're not really needed, user can always squeeze their product into `b` component. IMHO only the addition of `atomicModifyIORef_` is sensible in the context of base, other APIs may go to package like primitives. But if you have a motivated use case with `atomicModifyIORef2`, etc. Please tell me. On 2018年07月08日 03:09, David Feuer wrote: > Whoops! I left out the proposal link: > > https://github.com/ghc-proposals/ghc-proposals/pull/149 > > Also, what I called atomicModifyIORef_ below should really be called > something like atomicModifyIORef'_, since it forces a polymorphic value. > > Another thing to note: the underlying atomicModifyMutVar2# primop > actually supports more than just pairs. It can handle triples, solos, > and any other record types whose first components are lifted: > > atomicModifyIORefSoloLazy >   :: IORef a -> (a -> Solo a) -> IO (Solo a) > > atomicModifyIORefSolo >   :: IORef a -> (a -> Solo a) -> IO a > > atomicModifyIORef3, atomicModifyIORef3Lazy >   :: IORef a -> (a -> (a, b, c)) -> IO (a, b, c) > > etc. > > Should we add any such? > > On Sat, Jul 7, 2018, 2:35 PM David Feuer > wrote: > > I have proposed[1] the replacement of the atomicModifyMutVar# > primop, and the addition of two cheaper but less capable ones. It > seems likely that the proposal will succeed, but that the GHC > steering committee will leave the question of user interface > changes to the libraries list. I would like to open the discussion > here. > > The new primops lead naturally to several thin wrappers: > > -- Atomically replace the IORef contents > -- with the first component of the result of > -- applying the function to the old contents. > -- Return the old value and the result of > -- applying the function, without forcing the latter. > -- > -- atomicModifyIORef ref f = do > --   (_old, ~(_new, res)) <- atomicModifyIORef2Lazy ref f > --   return res > atomicModifyIORef2Lazy >   :: IORef a -> (a -> (a, b)) -> IO (a, (a, b)) > > -- Atomically replace the IORef contents > -- with the result of applying the function > -- to the old contents. Return the old and > -- new contents without forcing the latter. > atomicModifyIORefLazy_ >   :: IORef a -> (a -> a) -> IO (a, a) > > -- Atomically replace the IORef contents > -- with the given value and return the old > -- contents. > -- > -- atomicWriteIORef ref x = void (atomicSwapIORef ref x) > atomicSwapIORef >   :: IORef a -> a -> IO a > > Based on the code I've read that uses atomicModifyIORef, I believe > that the complete laziness of atomicModifyIORef2Lazy and > atomicModifyIORefLazy_ is very rarely desirable. I therefore > believe we should also (or perhaps instead?) offer stricter versions: > > atomicModifyIORef2 >   :: IORef a -> (a -> (a, b)) -> IO (a, (a, b)) > atomicModifyIORef2 ref f = do >   r@(_old, (_new, _res)) <- atomicModifyIORef2Lazy ref f >   return r > > atomicModifyIORef_ >   :: IORef a -> (a -> a) -> IO (a, a) > atomicModifyIORef_ ref f = do >   r@(_old, !_new) <- atomicModifyIORefLazy_ ref f >   return r > > The classic atomicModifyIORef also admits a less gratuitously lazy > version: > > atomicModifyIORefNGL >   :: IORef a -> (a -> (a,b)) -> IO b > atomicModifyIORefNGL ref f = do >   (_old, (_new, res)) <- atomicModifyIORef2 ref f >   return res > > Should we add that as well (with a better name)? Should we even > consider *replacing* the current atomicModifyIORef with that > version? That could theoretically break existing code, but I > suspect it would do so very rarely. If we don't change the > existing atomicModifyIORef now, I think we should consider > deprecating it: it's very easy to accidentally use it too lazily. > > > > _______________________________________________ > 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 Sun Jul 8 16:40:13 2018 From: david.feuer at gmail.com (David Feuer) Date: Sun, 8 Jul 2018 12:40:13 -0400 Subject: fixST lost bottoms Message-ID: I filed a ticket[*] for this, but I think maybe the libraries list should weigh in on whether it is something that should be fixed. In general, fixST f is supposed to bottom out if f forces its argument. However, the lazy way GHC blackholes thunks under evaluation sometimes leads to the computation being run again. In certain contrived situations, this can allow the computation to succeed! The example I give in the ticket: import Control.Monad.ST.Strict import Control.Monad.Fix import Data.STRef foo :: ST s Int foo = do ref <- newSTRef True mfix $ \res -> do x <- readSTRef ref if x then do writeSTRef ref False return $! res + 5 -- force the final result else return 10 main = print $ runST foo Here, the computation writes to an STRef before forcing the final result. Forcing the final result causes the computation to run again, this time taking the other branch. The program prints 15. When compiled with -O -feager-blackholing, however, the expected <> exception occurs. As far as I know, this weirdness never changes the value produced by a non-bottoming computation, and never changes a non-bottoming computation into a bottoming one. The fix (defining fixST the way fixIO is currently defined) would have a slight performance impact. Is it worth it? [*] https://ghc.haskell.org/trac/ghc/ticket/15349 -------------- next part -------------- An HTML attachment was scrubbed... URL: From erkokl at gmail.com Sun Jul 8 21:25:50 2018 From: erkokl at gmail.com (Levent Erkok) Date: Sun, 8 Jul 2018 14:25:50 -0700 Subject: fixST lost bottoms In-Reply-To: References: Message-ID: Hi David, Wonderful example. I'm afraid no-eager-blackholing also breaks the "no spooky action at a distance" rule. Since `x` is not used recursively, we should be able to pull it out of the `mfix` call, transforming the original to: foo :: ST s Int foo = do ref <- newSTRef True x <- readSTRef ref mfix $ \res -> do if x then do writeSTRef ref False return $! res + 5 -- force the final result else return 10 I believe this variant will produce <> with or without eager-blackholing, as it should. By this argument alone, I'd say the no-eager-blackholing breaks mfix axioms for strict-state. This example is also interesting from a pure termination point of view: Moving things "out-of" mfix usually improves termination. In this case, the opposite is happening. Strictly speaking, this is in violation of the mfix-axioms. But I doubt it's worth losing sleep over. I suggest we add this as an example in the value-recursion section on how eager-blackholing can change things. Cheers, -Levent. On Sun, Jul 8, 2018 at 9:40 AM, David Feuer wrote: > I filed a ticket[*] for this, but I think maybe the libraries list should > weigh in on whether it is something that should be fixed. In general, fixST > f is supposed to bottom out if f forces its argument. However, the lazy way > GHC blackholes thunks under evaluation sometimes leads to the computation > being run again. In certain contrived situations, this can allow the > computation to succeed! > > The example I give in the ticket: > > import Control.Monad.ST.Strict > import Control.Monad.Fix > import Data.STRef > > foo :: ST s Int > foo = do > ref <- newSTRef True > mfix $ \res -> do > x <- readSTRef ref > if x > then do > writeSTRef ref False > return $! res + 5 -- force the final result > else return 10 > > main = print $ runST foo > > Here, the computation writes to an STRef before forcing the final result. > Forcing the final result causes the computation to run again, this time > taking the other branch. The program prints 15. When compiled with -O > -feager-blackholing, however, the expected <> exception occurs. > > As far as I know, this weirdness never changes the value produced by a > non-bottoming computation, and never changes a non-bottoming computation > into a bottoming one. The fix (defining fixST the way fixIO is currently > defined) would have a slight performance impact. Is it worth it? > > [*] https://ghc.haskell.org/trac/ghc/ticket/15349 > > _______________________________________________ > 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 arseniy.alekseyev at gmail.com Sun Jul 8 22:51:23 2018 From: arseniy.alekseyev at gmail.com (Arseniy Alekseyev) Date: Sun, 8 Jul 2018 23:51:23 +0100 Subject: fixST lost bottoms In-Reply-To: References: Message-ID: This might be just me expecting too much guarantees from ST monad, but it seems to me that this is a potential violation of memory-safety. Consider the program below. The use of [unsafeWrite] in [silly_function] is guarded by the code above (we know we wrote [sz] so we should read back [sz]). It ought to be safe if you can rely on sequential execution of ST monad with no preemption. However, it does end up preempted due to the use of [mfix] elsewhere in the program, which leads to a segmentation fault. import Data.Array.ST import Data.Array.Base import Control.Monad.ST.Strict import Control.Monad.Fix silly_function :: STArray s Int Int -> Int -> ST s () silly_function arr a = do (0, sz) <- getBounds arr writeArray arr 0 sz let !res = a sz <- readArray arr 0 unsafeWrite arr sz res foo :: ST s Int foo = do arr <- newArray (0, 10) 0 mfix $ \res -> do n <- readArray arr 0 writeArray arr 0 1000000000 if n > 0 then return 666 else do silly_function arr res readArray arr 10 main = print $ runST foo On Sun, 8 Jul 2018 at 22:26, Levent Erkok wrote: > Hi David, > > Wonderful example. I'm afraid no-eager-blackholing also breaks the "no > spooky action at a distance" rule. Since `x` is not used recursively, we > should be able to pull it out of the `mfix` call, transforming the original > to: > > foo :: ST s Int > foo = do > ref <- newSTRef True > x <- readSTRef ref > mfix $ \res -> do > if x > then do > writeSTRef ref False > return $! res + 5 -- force the final result > else return 10 > > I believe this variant will produce <> with or without > eager-blackholing, as it should. By this argument alone, I'd say the > no-eager-blackholing breaks mfix axioms for strict-state. > > This example is also interesting from a pure termination point of view: > Moving things "out-of" mfix usually improves termination. In this case, the > opposite is happening. > > Strictly speaking, this is in violation of the mfix-axioms. But I doubt > it's worth losing sleep over. I suggest we add this as an example in the > value-recursion section on how eager-blackholing can change things. > > Cheers, > > -Levent. > > On Sun, Jul 8, 2018 at 9:40 AM, David Feuer wrote: > >> I filed a ticket[*] for this, but I think maybe the libraries list should >> weigh in on whether it is something that should be fixed. In general, fixST >> f is supposed to bottom out if f forces its argument. However, the lazy way >> GHC blackholes thunks under evaluation sometimes leads to the computation >> being run again. In certain contrived situations, this can allow the >> computation to succeed! >> >> The example I give in the ticket: >> >> import Control.Monad.ST.Strict >> import Control.Monad.Fix >> import Data.STRef >> >> foo :: ST s Int >> foo = do >> ref <- newSTRef True >> mfix $ \res -> do >> x <- readSTRef ref >> if x >> then do >> writeSTRef ref False >> return $! res + 5 -- force the final result >> else return 10 >> >> main = print $ runST foo >> >> Here, the computation writes to an STRef before forcing the final result. >> Forcing the final result causes the computation to run again, this time >> taking the other branch. The program prints 15. When compiled with -O >> -feager-blackholing, however, the expected <> exception occurs. >> >> As far as I know, this weirdness never changes the value produced by a >> non-bottoming computation, and never changes a non-bottoming computation >> into a bottoming one. The fix (defining fixST the way fixIO is currently >> defined) would have a slight performance impact. Is it worth it? >> >> [*] https://ghc.haskell.org/trac/ghc/ticket/15349 >> >> _______________________________________________ >> 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 > -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Mon Jul 9 04:08:03 2018 From: david.feuer at gmail.com (David Feuer) Date: Mon, 9 Jul 2018 00:08:03 -0400 Subject: fixST lost bottoms In-Reply-To: References: Message-ID: That's a very scary, albeit contrived, example. I wonder if there are more realistic functions that are susceptible to this attack from "safe" Haskell. In light of your exploit, I'm leaning toward saying we probably *should* fix this, but I'd like to hear your opinion. On Sun, Jul 8, 2018, 6:51 PM Arseniy Alekseyev wrote: > This might be just me expecting too much guarantees from ST monad, but it > seems to me that this is a potential violation of memory-safety. > Consider the program below. > > The use of [unsafeWrite] in [silly_function] is guarded by the code above > (we know we wrote [sz] so we should read back [sz]). It ought to be safe > if you can rely on sequential execution of ST monad with no preemption. > However, it does end up preempted due to the use of [mfix] elsewhere in > the program, which leads to a segmentation fault. > > import Data.Array.ST > import Data.Array.Base > import Control.Monad.ST.Strict > import Control.Monad.Fix > > silly_function :: STArray s Int Int -> Int -> ST s () > silly_function arr a = do > (0, sz) <- getBounds arr > writeArray arr 0 sz > let !res = a > sz <- readArray arr 0 > unsafeWrite arr sz res > > foo :: ST s Int > foo = do > arr <- newArray (0, 10) 0 > mfix $ \res -> do > n <- readArray arr 0 > writeArray arr 0 1000000000 > if n > 0 > then > return 666 > else do > silly_function arr res > readArray arr 10 > > main = print $ runST foo > > > On Sun, 8 Jul 2018 at 22:26, Levent Erkok wrote: > >> Hi David, >> >> Wonderful example. I'm afraid no-eager-blackholing also breaks the "no >> spooky action at a distance" rule. Since `x` is not used recursively, we >> should be able to pull it out of the `mfix` call, transforming the original >> to: >> >> foo :: ST s Int >> foo = do >> ref <- newSTRef True >> x <- readSTRef ref >> mfix $ \res -> do >> if x >> then do >> writeSTRef ref False >> return $! res + 5 -- force the final result >> else return 10 >> >> I believe this variant will produce <> with or without >> eager-blackholing, as it should. By this argument alone, I'd say the >> no-eager-blackholing breaks mfix axioms for strict-state. >> >> This example is also interesting from a pure termination point of view: >> Moving things "out-of" mfix usually improves termination. In this case, the >> opposite is happening. >> >> Strictly speaking, this is in violation of the mfix-axioms. But I doubt >> it's worth losing sleep over. I suggest we add this as an example in the >> value-recursion section on how eager-blackholing can change things. >> >> Cheers, >> >> -Levent. >> >> On Sun, Jul 8, 2018 at 9:40 AM, David Feuer >> wrote: >> >>> I filed a ticket[*] for this, but I think maybe the libraries list >>> should weigh in on whether it is something that should be fixed. In >>> general, fixST f is supposed to bottom out if f forces its argument. >>> However, the lazy way GHC blackholes thunks under evaluation sometimes >>> leads to the computation being run again. In certain contrived situations, >>> this can allow the computation to succeed! >>> >>> The example I give in the ticket: >>> >>> import Control.Monad.ST.Strict >>> import Control.Monad.Fix >>> import Data.STRef >>> >>> foo :: ST s Int >>> foo = do >>> ref <- newSTRef True >>> mfix $ \res -> do >>> x <- readSTRef ref >>> if x >>> then do >>> writeSTRef ref False >>> return $! res + 5 -- force the final result >>> else return 10 >>> >>> main = print $ runST foo >>> >>> Here, the computation writes to an STRef before forcing the final >>> result. Forcing the final result causes the computation to run again, this >>> time taking the other branch. The program prints 15. When compiled with -O >>> -feager-blackholing, however, the expected <> exception occurs. >>> >>> As far as I know, this weirdness never changes the value produced by a >>> non-bottoming computation, and never changes a non-bottoming computation >>> into a bottoming one. The fix (defining fixST the way fixIO is currently >>> defined) would have a slight performance impact. Is it worth it? >>> >>> [*] https://ghc.haskell.org/trac/ghc/ticket/15349 >>> >>> _______________________________________________ >>> 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 >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From arseniy.alekseyev at gmail.com Mon Jul 9 10:58:29 2018 From: arseniy.alekseyev at gmail.com (Arseniy Alekseyev) Date: Mon, 9 Jul 2018 11:58:29 +0100 Subject: fixST lost bottoms In-Reply-To: References: Message-ID: I do find it scary, but I personally am in no position to express opinion on what should happen (I'm not on any committee and I'm not even a regular Haskell user). On Mon, 9 Jul 2018 at 05:08, David Feuer wrote: > That's a very scary, albeit contrived, example. I wonder if there are more > realistic functions that are susceptible to this attack from "safe" > Haskell. In light of your exploit, I'm leaning toward saying we probably > *should* fix this, but I'd like to hear your opinion. > > On Sun, Jul 8, 2018, 6:51 PM Arseniy Alekseyev < > arseniy.alekseyev at gmail.com> wrote: > >> This might be just me expecting too much guarantees from ST monad, but it >> seems to me that this is a potential violation of memory-safety. >> Consider the program below. >> >> The use of [unsafeWrite] in [silly_function] is guarded by the code >> above (we know we wrote [sz] so we should read back [sz]). It ought to >> be safe if you can rely on sequential execution of ST monad with no >> preemption. >> However, it does end up preempted due to the use of [mfix] elsewhere in >> the program, which leads to a segmentation fault. >> >> import Data.Array.ST >> import Data.Array.Base >> import Control.Monad.ST.Strict >> import Control.Monad.Fix >> >> silly_function :: STArray s Int Int -> Int -> ST s () >> silly_function arr a = do >> (0, sz) <- getBounds arr >> writeArray arr 0 sz >> let !res = a >> sz <- readArray arr 0 >> unsafeWrite arr sz res >> >> foo :: ST s Int >> foo = do >> arr <- newArray (0, 10) 0 >> mfix $ \res -> do >> n <- readArray arr 0 >> writeArray arr 0 1000000000 >> if n > 0 >> then >> return 666 >> else do >> silly_function arr res >> readArray arr 10 >> >> main = print $ runST foo >> >> >> On Sun, 8 Jul 2018 at 22:26, Levent Erkok wrote: >> >>> Hi David, >>> >>> Wonderful example. I'm afraid no-eager-blackholing also breaks the "no >>> spooky action at a distance" rule. Since `x` is not used recursively, we >>> should be able to pull it out of the `mfix` call, transforming the original >>> to: >>> >>> foo :: ST s Int >>> foo = do >>> ref <- newSTRef True >>> x <- readSTRef ref >>> mfix $ \res -> do >>> if x >>> then do >>> writeSTRef ref False >>> return $! res + 5 -- force the final result >>> else return 10 >>> >>> I believe this variant will produce <> with or without >>> eager-blackholing, as it should. By this argument alone, I'd say the >>> no-eager-blackholing breaks mfix axioms for strict-state. >>> >>> This example is also interesting from a pure termination point of view: >>> Moving things "out-of" mfix usually improves termination. In this case, the >>> opposite is happening. >>> >>> Strictly speaking, this is in violation of the mfix-axioms. But I doubt >>> it's worth losing sleep over. I suggest we add this as an example in the >>> value-recursion section on how eager-blackholing can change things. >>> >>> Cheers, >>> >>> -Levent. >>> >>> On Sun, Jul 8, 2018 at 9:40 AM, David Feuer >>> wrote: >>> >>>> I filed a ticket[*] for this, but I think maybe the libraries list >>>> should weigh in on whether it is something that should be fixed. In >>>> general, fixST f is supposed to bottom out if f forces its argument. >>>> However, the lazy way GHC blackholes thunks under evaluation sometimes >>>> leads to the computation being run again. In certain contrived situations, >>>> this can allow the computation to succeed! >>>> >>>> The example I give in the ticket: >>>> >>>> import Control.Monad.ST.Strict >>>> import Control.Monad.Fix >>>> import Data.STRef >>>> >>>> foo :: ST s Int >>>> foo = do >>>> ref <- newSTRef True >>>> mfix $ \res -> do >>>> x <- readSTRef ref >>>> if x >>>> then do >>>> writeSTRef ref False >>>> return $! res + 5 -- force the final result >>>> else return 10 >>>> >>>> main = print $ runST foo >>>> >>>> Here, the computation writes to an STRef before forcing the final >>>> result. Forcing the final result causes the computation to run again, this >>>> time taking the other branch. The program prints 15. When compiled with -O >>>> -feager-blackholing, however, the expected <> exception occurs. >>>> >>>> As far as I know, this weirdness never changes the value produced by a >>>> non-bottoming computation, and never changes a non-bottoming computation >>>> into a bottoming one. The fix (defining fixST the way fixIO is currently >>>> defined) would have a slight performance impact. Is it worth it? >>>> >>>> [*] https://ghc.haskell.org/trac/ghc/ticket/15349 >>>> >>>> _______________________________________________ >>>> 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 >>> >> -------------- next part -------------- An HTML attachment was scrubbed... URL: From ekmett at gmail.com Mon Jul 9 12:13:51 2018 From: ekmett at gmail.com (Edward Kmett) Date: Mon, 9 Jul 2018 08:13:51 -0400 Subject: [core libraries] Re: fixST lost bottoms In-Reply-To: References: Message-ID: Arseniy's example definitely leaves me inclined to say we should fix rather than just document this. -Edward On Sun, Jul 8, 2018 at 6:51 PM Arseniy Alekseyev < arseniy.alekseyev at gmail.com> wrote: > This might be just me expecting too much guarantees from ST monad, but it > seems to me that this is a potential violation of memory-safety. > Consider the program below. > > The use of [unsafeWrite] in [silly_function] is guarded by the code above > (we know we wrote [sz] so we should read back [sz]). It ought to be safe > if you can rely on sequential execution of ST monad with no preemption. > However, it does end up preempted due to the use of [mfix] elsewhere in > the program, which leads to a segmentation fault. > > import Data.Array.ST > import Data.Array.Base > import Control.Monad.ST.Strict > import Control.Monad.Fix > > silly_function :: STArray s Int Int -> Int -> ST s () > silly_function arr a = do > (0, sz) <- getBounds arr > writeArray arr 0 sz > let !res = a > sz <- readArray arr 0 > unsafeWrite arr sz res > > foo :: ST s Int > foo = do > arr <- newArray (0, 10) 0 > mfix $ \res -> do > n <- readArray arr 0 > writeArray arr 0 1000000000 > if n > 0 > then > return 666 > else do > silly_function arr res > readArray arr 10 > > main = print $ runST foo > > > On Sun, 8 Jul 2018 at 22:26, Levent Erkok wrote: > >> Hi David, >> >> Wonderful example. I'm afraid no-eager-blackholing also breaks the "no >> spooky action at a distance" rule. Since `x` is not used recursively, we >> should be able to pull it out of the `mfix` call, transforming the original >> to: >> >> foo :: ST s Int >> foo = do >> ref <- newSTRef True >> x <- readSTRef ref >> mfix $ \res -> do >> if x >> then do >> writeSTRef ref False >> return $! res + 5 -- force the final result >> else return 10 >> >> I believe this variant will produce <> with or without >> eager-blackholing, as it should. By this argument alone, I'd say the >> no-eager-blackholing breaks mfix axioms for strict-state. >> >> This example is also interesting from a pure termination point of view: >> Moving things "out-of" mfix usually improves termination. In this case, the >> opposite is happening. >> >> Strictly speaking, this is in violation of the mfix-axioms. But I doubt >> it's worth losing sleep over. I suggest we add this as an example in the >> value-recursion section on how eager-blackholing can change things. >> >> Cheers, >> >> -Levent. >> >> On Sun, Jul 8, 2018 at 9:40 AM, David Feuer >> wrote: >> >>> I filed a ticket[*] for this, but I think maybe the libraries list >>> should weigh in on whether it is something that should be fixed. In >>> general, fixST f is supposed to bottom out if f forces its argument. >>> However, the lazy way GHC blackholes thunks under evaluation sometimes >>> leads to the computation being run again. In certain contrived situations, >>> this can allow the computation to succeed! >>> >>> The example I give in the ticket: >>> >>> import Control.Monad.ST.Strict >>> import Control.Monad.Fix >>> import Data.STRef >>> >>> foo :: ST s Int >>> foo = do >>> ref <- newSTRef True >>> mfix $ \res -> do >>> x <- readSTRef ref >>> if x >>> then do >>> writeSTRef ref False >>> return $! res + 5 -- force the final result >>> else return 10 >>> >>> main = print $ runST foo >>> >>> Here, the computation writes to an STRef before forcing the final >>> result. Forcing the final result causes the computation to run again, this >>> time taking the other branch. The program prints 15. When compiled with -O >>> -feager-blackholing, however, the expected <> exception occurs. >>> >>> As far as I know, this weirdness never changes the value produced by a >>> non-bottoming computation, and never changes a non-bottoming computation >>> into a bottoming one. The fix (defining fixST the way fixIO is currently >>> defined) would have a slight performance impact. Is it worth it? >>> >>> [*] https://ghc.haskell.org/trac/ghc/ticket/15349 >>> >>> _______________________________________________ >>> 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 >> > -- > You received this message because you are subscribed to the Google Groups > "haskell-core-libraries" group. > To unsubscribe from this group and stop receiving emails from it, send an > email to haskell-core-libraries+unsubscribe at googlegroups.com. > For more options, visit https://groups.google.com/d/optout. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ndospark320 at naver.com Wed Jul 11 06:59:37 2018 From: ndospark320 at naver.com (=?utf-8?B?67CV7Iug7ZmY?=) Date: Wed, 11 Jul 2018 15:59:37 +0900 Subject: =?utf-8?B?QmV0dGVyIGNhc2luZyBmdW5jdGlvbnMgKEdlcm1hbiDDnywgZXRjLik=?= Message-ID: <8bc837677d8efb3109567491a617acb@cweb05.nm.nhnsystem.com> Current Haskell has 'simple' `Char`-to-`Char` casing functions (as specified by Unicode), namely `toUpper`, `toLower` and `toTitle`. So to convert cases of a `String`, Haskell intends `fmap toUpper`, etc. But this has some bugs. Case 1. German ß (Eszett) 'ß' (U+00DF), Latin Small Letter Sharp S, is a lowercase letter itself, but Unicode doesn't specify its 'simple' uppercase counterpart. It's because its uppercase counterpart is not a single character, but two characters, "SS". Case 2. Turkish İ and ı Rather than the common 'I' and 'i' case pair, Turkish language has the 'İ' (U+0130) and 'i' pair and the 'I' and 'ı' (U+0131) pair. Those are, dotted I pair and dotless I pair, respectively. Case 3. Greek Σ (Sigma) Greek 'Σ' (U+03A3) must be lowercase mapped to 'ς' (U+03C2) if followed by a whitespace, rather than normal 'σ' (U+03C3). Case 4. Greek iota subscript (Ypogegrammeni) Greek 'Capital' letters with iota subscripts (for example, 'ᾈ' (U+1F88)), though they are the 'simple' uppercase counterpart of their lowercase counterpart, they themselves are actually treated as titlecase characters. For example, the actual uppercase counterpart of 'ᾀ' (U+1F80) is "ἈΙ" (U+1F08 U+0399). That is, an actual capital iota instead of the iota subscript. Case 5. Precomposed letters without upper/lowercase counterpart For example, ΐ (U+03B0) doesn't have precomposed uppercase counterpart. It must be effectively mapped to "Ϊ́" (U+03AA U+0301). In Summary, we need more elaborated casing functions which are `String`-to-`String`. Bibliography: The Unicode Standard Version 11.0 – Core Specification, Section 5.18. -------------- next part -------------- An HTML attachment was scrubbed... URL: From fa-ml at ariis.it Wed Jul 11 07:35:35 2018 From: fa-ml at ariis.it (Francesco Ariis) Date: Wed, 11 Jul 2018 09:35:35 +0200 Subject: Better casing =?iso-8859-1?Q?functions?= =?iso-8859-1?B?IChHZXJtYW4g3yw=?= etc.) In-Reply-To: <8bc837677d8efb3109567491a617acb@cweb05.nm.nhnsystem.com> References: <8bc837677d8efb3109567491a617acb@cweb05.nm.nhnsystem.com> Message-ID: <20180711073535.se5kud4xkil2tvrc@x60s.casa> Hello 박신환, On Wed, Jul 11, 2018 at 03:59:37PM +0900, 박신환 wrote: > Case 4. Greek iota subscript (Ypogegrammeni) I think not even Data.Text handles this correctly! From blamario at ciktel.net Wed Jul 11 12:33:31 2018 From: blamario at ciktel.net (=?UTF-8?Q?Mario_Bla=c5=beevi=c4=87?=) Date: Wed, 11 Jul 2018 08:33:31 -0400 Subject: =?UTF-8?Q?Re:_Better_casing_functions_=28German_=c3=9f=2c_etc.=29?= In-Reply-To: <8bc837677d8efb3109567491a617acb@cweb05.nm.nhnsystem.com> References: <8bc837677d8efb3109567491a617acb@cweb05.nm.nhnsystem.com> Message-ID: On 2018-07-11 02:59 AM, 박신환 wrote: > > Current Haskell has 'simple' `Char`-to-`Char` casing functions (as > specified by Unicode), namely `toUpper`, `toLower` and `toTitle`. > > So to convert cases of a `String`, Haskell intends `fmap toUpper`, > etc. But this has some bugs. > I've never tested the cases you list, but I believe the text-icu library covers them. See http://hackage.haskell.org/package/text-icu-0.7.0.1/docs/Data-Text-ICU.html#g:4 > Case 1. German ß (Eszett) > > 'ß' (U+00DF), Latin Small Letter Sharp S, is a lowercase letter > itself, but Unicode doesn't specify its 'simple' uppercase counterpart. > > It's because its uppercase counterpart is not a single character, but > two characters, "SS". > > Case 2. Turkish İ and ı > > Rather than the common 'I' and 'i' case pair, Turkish language has the > 'İ' (U+0130) and 'i' pair and the 'I' and 'ı'(U+0131) pair. Those > are, dotted I pair and dotless I pair, respectively. > > Case 3. Greek Σ (Sigma) > > Greek 'Σ' (U+03A3) must be lowercase mapped to 'ς' (U+03C2) if > followed by a whitespace, rather than normal 'σ' (U+03C3). > > Case 4. Greek iota subscript (Ypogegrammeni) > > Greek 'Capital' letters with iota subscripts (for example, 'ᾈ' > (U+1F88)), though they are the 'simple' uppercase counterpart of their > lowercase counterpart, they themselves are actually treated as > titlecase characters. For example, the actual uppercase counterpart of > 'ᾀ' (U+1F80) is "ἈΙ" (U+1F08 U+0399). That is, an actual capital iota > instead of the iota subscript. > > Case 5. Precomposed letters without upper/lowercase counterpart > > For example, ΐ (U+03B0) doesn't have precomposed uppercase > counterpart. It must be effectively mapped to "Ϊ́" (U+03AA U+0301). > > > In Summary, we need more elaborated casing functions which are > `String`-to-`String`. > > > Bibliography: > > /The Unicode Standard Version 11.0 – Core Specification/, Section 5.18. > > > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries From mikhail.glushenkov at gmail.com Wed Jul 11 15:26:50 2018 From: mikhail.glushenkov at gmail.com (Mikhail Glushenkov) Date: Wed, 11 Jul 2018 16:26:50 +0100 Subject: =?UTF-8?Q?Re=3A_Better_casing_functions_=28German_=C3=9F=2C_etc=2E=29?= In-Reply-To: <8bc837677d8efb3109567491a617acb@cweb05.nm.nhnsystem.com> References: <8bc837677d8efb3109567491a617acb@cweb05.nm.nhnsystem.com> Message-ID: Hi, On Wed, 11 Jul 2018, 08:00 박신환, wrote: > > [...] > Case 1. German ß (Eszett) > > > > 'ß' (U+00DF), Latin Small Letter Sharp S, is a lowercase letter itself, but Unicode doesn't specify its 'simple' uppercase counterpart. > > It's because its uppercase counterpart is not a single character, but two characters, "SS". Capital sharp s is now also considered valid: https://medium.com/@typefacts/the-german-capital-letter-eszett-e0936c1388f8 From david.feuer at gmail.com Wed Jul 11 16:51:00 2018 From: david.feuer at gmail.com (David Feuer) Date: Wed, 11 Jul 2018 12:51:00 -0400 Subject: Discussion: New atomic IORef functions In-Reply-To: <5b41befd.1c69fb81.f94b3.914cSMTPIN_ADDED_BROKEN@mx.google.com> References: <5b41befd.1c69fb81.f94b3.914cSMTPIN_ADDED_BROKEN@mx.google.com> Message-ID: All the fundamental functions I've defined can be usefully used in the base library. I think that's one good reason to put them there. Another is that while the basic array operations have traditionally been exposed through array, vector, and primitive, and the basic TVar operations have been exposed through stm, the basic IORef and MVar operations have been exposed through base (except, for some reason, casMutVar#). I see no reason to change that. I never proposed a function that forces the previous value unnecessarily, so I don't know why you're complaining about that. The extra laziness I don't like is in the pair result; none of the uses I've seen thus can far make intentional use of that. That's why I tend to think atomicModifyIORef (as it exists today) is almost never what people actually want. Squeezing into a second component leads to extra allocation in what may be a performance-critical function; that said, I'm willing to hold off on higher tuples for now. On Sun, Jul 8, 2018, 3:36 AM winter wrote: > I believe new variations should always be motivated by use-case if > there're too many choices, the lazy behavior of old `atomicModifyIORef` is > justified by some cases the modifying functions are lazy in its argument, > thus a lazy version could win by not forcing previous thunks, we'd want to > keep its behavior as how it's documented. > > As for tuples more than pairs, they're not really needed, user can always > squeeze their product into `b` component. > > IMHO only the addition of `atomicModifyIORef_` is sensible in the context > of base, other APIs may go to package like primitives. But if you have a > motivated use case with `atomicModifyIORef2`, etc. Please tell me. > > On 2018年07月08日 03:09, David Feuer wrote: > > Whoops! I left out the proposal link: > > https://github.com/ghc-proposals/ghc-proposals/pull/149 > > Also, what I called atomicModifyIORef_ below should really be called > something like atomicModifyIORef'_, since it forces a polymorphic value. > > Another thing to note: the underlying atomicModifyMutVar2# primop actually > supports more than just pairs. It can handle triples, solos, and any other > record types whose first components are lifted: > > atomicModifyIORefSoloLazy > :: IORef a -> (a -> Solo a) -> IO (Solo a) > > atomicModifyIORefSolo > :: IORef a -> (a -> Solo a) -> IO a > > atomicModifyIORef3, atomicModifyIORef3Lazy > :: IORef a -> (a -> (a, b, c)) -> IO (a, b, c) > > etc. > > Should we add any such? > > On Sat, Jul 7, 2018, 2:35 PM David Feuer wrote: > >> I have proposed[1] the replacement of the atomicModifyMutVar# primop, and >> the addition of two cheaper but less capable ones. It seems likely that the >> proposal will succeed, but that the GHC steering committee will leave the >> question of user interface changes to the libraries list. I would like to >> open the discussion here. >> >> The new primops lead naturally to several thin wrappers: >> >> -- Atomically replace the IORef contents >> -- with the first component of the result of >> -- applying the function to the old contents. >> -- Return the old value and the result of >> -- applying the function, without forcing the latter. >> -- >> -- atomicModifyIORef ref f = do >> -- (_old, ~(_new, res)) <- atomicModifyIORef2Lazy ref f >> -- return res >> atomicModifyIORef2Lazy >> :: IORef a -> (a -> (a, b)) -> IO (a, (a, b)) >> >> -- Atomically replace the IORef contents >> -- with the result of applying the function >> -- to the old contents. Return the old and >> -- new contents without forcing the latter. >> atomicModifyIORefLazy_ >> :: IORef a -> (a -> a) -> IO (a, a) >> >> -- Atomically replace the IORef contents >> -- with the given value and return the old >> -- contents. >> -- >> -- atomicWriteIORef ref x = void (atomicSwapIORef ref x) >> atomicSwapIORef >> :: IORef a -> a -> IO a >> >> Based on the code I've read that uses atomicModifyIORef, I believe that >> the complete laziness of atomicModifyIORef2Lazy and >> atomicModifyIORefLazy_ is very rarely desirable. I therefore believe we >> should also (or perhaps instead?) offer stricter versions: >> >> atomicModifyIORef2 >> :: IORef a -> (a -> (a, b)) -> IO (a, (a, b)) >> atomicModifyIORef2 ref f = do >> r@(_old, (_new, _res)) <- atomicModifyIORef2Lazy ref f >> return r >> >> atomicModifyIORef_ >> :: IORef a -> (a -> a) -> IO (a, a) >> atomicModifyIORef_ ref f = do >> r@(_old, !_new) <- atomicModifyIORefLazy_ ref f >> return r >> >> The classic atomicModifyIORef also admits a less gratuitously lazy >> version: >> >> atomicModifyIORefNGL >> :: IORef a -> (a -> (a,b)) -> IO b >> atomicModifyIORefNGL ref f = do >> (_old, (_new, res)) <- atomicModifyIORef2 ref f >> return res >> >> Should we add that as well (with a better name)? Should we even consider >> *replacing* the current atomicModifyIORef with that version? That could >> theoretically break existing code, but I suspect it would do so very >> rarely. If we don't change the existing atomicModifyIORef now, I think we >> should consider deprecating it: it's very easy to accidentally use it too >> lazily. >> > > > _______________________________________________ > Libraries mailing listLibraries at haskell.orghttp://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > > _______________________________________________ > 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 drkoster at qq.com Wed Jul 11 18:22:05 2018 From: drkoster at qq.com (=?gb18030?B?RHIuS29zdGVy?=) Date: Thu, 12 Jul 2018 02:22:05 +0800 Subject: Discussion: New atomic IORef functions Message-ID: But if you force the pair result, you have to evaluate modifying function isn't it? That's sometime unwanted when you have an very expensive f here, let's say a deep binary search which might not depend previous result. I think that is also why current atomicModifyIORef is designed this way, so I'd rather keep it the old way. 发自我的iPhone ------------------ Original ------------------ From: David Feuer Date: Thu,Jul 12,2018 0:51 AM To: winter Cc: Haskell Libraries Subject: Re: Discussion: New atomic IORef functions All the fundamental functions I've defined can be usefully used in the base library. I think that's one good reason to put them there. Another is that while the basic array operations have traditionally been exposed through array, vector, and primitive, and the basic TVar operations have been exposed through stm, the basic IORef and MVar operations have been exposed through base (except, for some reason, casMutVar#). I see no reason to change that. I never proposed a function that forces the previous value unnecessarily, so I don't know why you're complaining about that. The extra laziness I don't like is in the pair result; none of the uses I've seen thus can far make intentional use of that. That's why I tend to think atomicModifyIORef (as it exists today) is almost never what people actually want. Squeezing into a second component leads to extra allocation in what may be a performance-critical function; that said, I'm willing to hold off on higher tuples for now. On Sun, Jul 8, 2018, 3:36 AM winter wrote: I believe new variations should always be motivated by use-case if there're too many choices, the lazy behavior of old `atomicModifyIORef` is justified by some cases the modifying functions are lazy in its argument, thus a lazy version could win by not forcing previous thunks, we'd want to keep its behavior as how it's documented. As for tuples more than pairs, they're not really needed, user can always squeeze their product into `b` component. IMHO only the addition of `atomicModifyIORef_` is sensible in the context of base, other APIs may go to package like primitives. But if you have a motivated use case with `atomicModifyIORef2`, etc. Please tell me. On 2018年07月08日 03:09, David Feuer wrote: Whoops! I left out the proposal link: https://github.com/ghc-proposals/ghc-proposals/pull/149 Also, what I called atomicModifyIORef_ below should really be called something like atomicModifyIORef'_, since it forces a polymorphic value. Another thing to note: the underlying atomicModifyMutVar2# primop actually supports more than just pairs. It can handle triples, solos, and any other record types whose first components are lifted: atomicModifyIORefSoloLazy :: IORef a -> (a -> Solo a) -> IO (Solo a) atomicModifyIORefSolo :: IORef a -> (a -> Solo a) -> IO a atomicModifyIORef3, atomicModifyIORef3Lazy :: IORef a -> (a -> (a, b, c)) -> IO (a, b, c) etc. Should we add any such? On Sat, Jul 7, 2018, 2:35 PM David Feuer wrote: I have proposed[1] the replacement of the atomicModifyMutVar# primop, and the addition of two cheaper but less capable ones. It seems likely that the proposal will succeed, but that the GHC steering committee will leave the question of user interface changes to the libraries list. I would like to open the discussion here. The new primops lead naturally to several thin wrappers: -- Atomically replace the IORef contents -- with the first component of the result of -- applying the function to the old contents. -- Return the old value and the result of -- applying the function, without forcing the latter. -- -- atomicModifyIORef ref f = do -- (_old, ~(_new, res)) <- atomicModifyIORef2Lazy ref f -- return res atomicModifyIORef2Lazy :: IORef a -> (a -> (a, b)) -> IO (a, (a, b)) -- Atomically replace the IORef contents -- with the result of applying the function -- to the old contents. Return the old and -- new contents without forcing the latter. atomicModifyIORefLazy_ :: IORef a -> (a -> a) -> IO (a, a) -- Atomically replace the IORef contents -- with the given value and return the old -- contents. -- -- atomicWriteIORef ref x = void (atomicSwapIORef ref x) atomicSwapIORef :: IORef a -> a -> IO a Based on the code I've read that uses atomicModifyIORef, I believe that the complete laziness of atomicModifyIORef2Lazy and atomicModifyIORefLazy_ is very rarely desirable. I therefore believe we should also (or perhaps instead?) offer stricter versions: atomicModifyIORef2 :: IORef a -> (a -> (a, b)) -> IO (a, (a, b)) atomicModifyIORef2 ref f = do r@(_old, (_new, _res)) <- atomicModifyIORef2Lazy ref f return r atomicModifyIORef_ :: IORef a -> (a -> a) -> IO (a, a) atomicModifyIORef_ ref f = do r@(_old, !_new) <- atomicModifyIORefLazy_ ref f return r The classic atomicModifyIORef also admits a less gratuitously lazy version: atomicModifyIORefNGL :: IORef a -> (a -> (a,b)) -> IO b atomicModifyIORefNGL ref f = do (_old, (_new, res)) <- atomicModifyIORef2 ref f return res Should we add that as well (with a better name)? Should we even consider *replacing* the current atomicModifyIORef with that version? That could theoretically break existing code, but I suspect it would do so very rarely. If we don't change the existing atomicModifyIORef now, I think we should consider deprecating it: it's very easy to accidentally use it too lazily. _______________________________________________ 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 -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Wed Jul 11 18:31:00 2018 From: david.feuer at gmail.com (David Feuer) Date: Wed, 11 Jul 2018 14:31:00 -0400 Subject: Discussion: New atomic IORef functions In-Reply-To: References: Message-ID: I'm not committed to changing atomicModifyIORef. I'm much more interested in adding atomicModifyIORef2, atomicModifyIORef'_, and atomicSwapIORef. I do think it would be helpful to get a pair-strict version of atomicModifyIORef (atomicModifyIORefP?), but I guess it's not horrible if users have to write their own with atomicModifyIORef2. The lazy atomicModifyIORef2Lazy and atomicModifyIORefLazy_ are pretty optional: I see their laziness as more an implementation detail than an essential feature. On Wed, Jul 11, 2018 at 2:22 PM, Dr.Koster wrote: > But if you force the pair result, you have to evaluate modifying function > isn't it? That's sometime unwanted when you have an very expensive f here, > let's say a deep binary search which might not depend previous result. > > I think that is also why current atomicModifyIORef is designed this way, so > I'd rather keep it the old way. > > 发自我的iPhone > > > ------------------ Original ------------------ > From: David Feuer > Date: Thu,Jul 12,2018 0:51 AM > To: winter > Cc: Haskell Libraries > Subject: Re: Discussion: New atomic IORef functions > > All the fundamental functions I've defined can be usefully used in the base > library. I think that's one good reason to put them there. Another is that > while the basic array operations have traditionally been exposed through > array, vector, and primitive, and the basic TVar operations have been > exposed through stm, the basic IORef and MVar operations have been exposed > through base (except, for some reason, casMutVar#). I see no reason to > change that. > > I never proposed a function that forces the previous value unnecessarily, so > I don't know why you're complaining about that. The extra laziness I don't > like is in the pair result; none of the uses I've seen thus can far make > intentional use of that. That's why I tend to think atomicModifyIORef (as it > exists today) is almost never what people actually want. > > Squeezing into a second component leads to extra allocation in what may be a > performance-critical function; that said, I'm willing to hold off on higher > tuples for now. > > On Sun, Jul 8, 2018, 3:36 AM winter wrote: >> >> I believe new variations should always be motivated by use-case if >> there're too many choices, the lazy behavior of old `atomicModifyIORef` is >> justified by some cases the modifying functions are lazy in its argument, >> thus a lazy version could win by not forcing previous thunks, we'd want to >> keep its behavior as how it's documented. >> >> As for tuples more than pairs, they're not really needed, user can always >> squeeze their product into `b` component. >> >> IMHO only the addition of `atomicModifyIORef_` is sensible in the context >> of base, other APIs may go to package like primitives. But if you have a >> motivated use case with `atomicModifyIORef2`, etc. Please tell me. >> >> >> On 2018年07月08日 03:09, David Feuer wrote: >> >> Whoops! I left out the proposal link: >> >> https://github.com/ghc-proposals/ghc-proposals/pull/149 >> >> Also, what I called atomicModifyIORef_ below should really be called >> something like atomicModifyIORef'_, since it forces a polymorphic value. >> >> Another thing to note: the underlying atomicModifyMutVar2# primop actually >> supports more than just pairs. It can handle triples, solos, and any other >> record types whose first components are lifted: >> >> atomicModifyIORefSoloLazy >> :: IORef a -> (a -> Solo a) -> IO (Solo a) >> >> atomicModifyIORefSolo >> :: IORef a -> (a -> Solo a) -> IO a >> >> atomicModifyIORef3, atomicModifyIORef3Lazy >> :: IORef a -> (a -> (a, b, c)) -> IO (a, b, c) >> >> etc. >> >> Should we add any such? >> >> On Sat, Jul 7, 2018, 2:35 PM David Feuer wrote: >>> >>> I have proposed[1] the replacement of the atomicModifyMutVar# primop, and >>> the addition of two cheaper but less capable ones. It seems likely that the >>> proposal will succeed, but that the GHC steering committee will leave the >>> question of user interface changes to the libraries list. I would like to >>> open the discussion here. >>> >>> The new primops lead naturally to several thin wrappers: >>> >>> -- Atomically replace the IORef contents >>> -- with the first component of the result of >>> -- applying the function to the old contents. >>> -- Return the old value and the result of >>> -- applying the function, without forcing the latter. >>> -- >>> -- atomicModifyIORef ref f = do >>> -- (_old, ~(_new, res)) <- atomicModifyIORef2Lazy ref f >>> -- return res >>> atomicModifyIORef2Lazy >>> :: IORef a -> (a -> (a, b)) -> IO (a, (a, b)) >>> >>> -- Atomically replace the IORef contents >>> -- with the result of applying the function >>> -- to the old contents. Return the old and >>> -- new contents without forcing the latter. >>> atomicModifyIORefLazy_ >>> :: IORef a -> (a -> a) -> IO (a, a) >>> >>> -- Atomically replace the IORef contents >>> -- with the given value and return the old >>> -- contents. >>> -- >>> -- atomicWriteIORef ref x = void (atomicSwapIORef ref x) >>> atomicSwapIORef >>> :: IORef a -> a -> IO a >>> >>> Based on the code I've read that uses atomicModifyIORef, I believe that >>> the complete laziness of atomicModifyIORef2Lazy and atomicModifyIORefLazy_ >>> is very rarely desirable. I therefore believe we should also (or perhaps >>> instead?) offer stricter versions: >>> >>> atomicModifyIORef2 >>> :: IORef a -> (a -> (a, b)) -> IO (a, (a, b)) >>> atomicModifyIORef2 ref f = do >>> r@(_old, (_new, _res)) <- atomicModifyIORef2Lazy ref f >>> return r >>> >>> atomicModifyIORef_ >>> :: IORef a -> (a -> a) -> IO (a, a) >>> atomicModifyIORef_ ref f = do >>> r@(_old, !_new) <- atomicModifyIORefLazy_ ref f >>> return r >>> >>> The classic atomicModifyIORef also admits a less gratuitously lazy >>> version: >>> >>> atomicModifyIORefNGL >>> :: IORef a -> (a -> (a,b)) -> IO b >>> atomicModifyIORefNGL ref f = do >>> (_old, (_new, res)) <- atomicModifyIORef2 ref f >>> return res >>> >>> Should we add that as well (with a better name)? Should we even consider >>> *replacing* the current atomicModifyIORef with that version? That could >>> theoretically break existing code, but I suspect it would do so very rarely. >>> If we don't change the existing atomicModifyIORef now, I think we should >>> consider deprecating it: it's very easy to accidentally use it too lazily. >> >> >> >> _______________________________________________ >> 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 Thu Jul 12 03:32:11 2018 From: drkoster at qq.com (winter) Date: Thu, 12 Jul 2018 11:32:11 +0800 Subject: Discussion: New atomic IORef functions In-Reply-To: References: Message-ID: +EDA27D21C45161E0 OK then, here's some subtle things i want to shout out if you're going to make the change ; ) 1. The proposed naming is just not great, how about these: atomicExchangeIORef :: IORef a -> (a -> (a, b)) -> IO (a, (a, b)) atomicExchangeIORef' :: IORef a -> (a -> (a, b)) -> IO (a, (a, b)) atomicApplyIORef :: IORef a -> (a -> a) -> IO (a, a) atomicApplyIORef :: IORef a -> (a -> a) -> IO (a, a) It may not that great but it's more informative IMO. 3. atomicExchangeIORef should not force the tuple, e.g. don't pattern match on the tuple result, instead let users choose to force or not. (May worth adding some document, I'd be happy to help) 4. atomicExchangeIORef' will not only force the tuple, but also force both `a` and `b` part to match atomicModifyIORef' 's semantics. 5. atomicApplyIORef(and atomicApplyIORef') deserve its own primop, since we can skip building selector thunks all together. On 2018年07月12日 02:31, David Feuer wrote: > I'm not committed to changing atomicModifyIORef. I'm much more > interested in adding atomicModifyIORef2, atomicModifyIORef'_, and > atomicSwapIORef. I do think it would be helpful to get a pair-strict > version of atomicModifyIORef (atomicModifyIORefP?), but I guess it's > not horrible if users have to write their own with atomicModifyIORef2. > The lazy atomicModifyIORef2Lazy and atomicModifyIORefLazy_ are pretty > optional: I see their laziness as more an implementation detail than > an essential feature. > > On Wed, Jul 11, 2018 at 2:22 PM, Dr.Koster wrote: >> But if you force the pair result, you have to evaluate modifying function >> isn't it? That's sometime unwanted when you have an very expensive f here, >> let's say a deep binary search which might not depend previous result. >> >> I think that is also why current atomicModifyIORef is designed this way, so >> I'd rather keep it the old way. >> >> 发自我的iPhone >> >> >> ------------------ Original ------------------ >> From: David Feuer >> Date: Thu,Jul 12,2018 0:51 AM >> To: winter >> Cc: Haskell Libraries >> Subject: Re: Discussion: New atomic IORef functions >> >> All the fundamental functions I've defined can be usefully used in the base >> library. I think that's one good reason to put them there. Another is that >> while the basic array operations have traditionally been exposed through >> array, vector, and primitive, and the basic TVar operations have been >> exposed through stm, the basic IORef and MVar operations have been exposed >> through base (except, for some reason, casMutVar#). I see no reason to >> change that. >> >> I never proposed a function that forces the previous value unnecessarily, so >> I don't know why you're complaining about that. The extra laziness I don't >> like is in the pair result; none of the uses I've seen thus can far make >> intentional use of that. That's why I tend to think atomicModifyIORef (as it >> exists today) is almost never what people actually want. >> >> Squeezing into a second component leads to extra allocation in what may be a >> performance-critical function; that said, I'm willing to hold off on higher >> tuples for now. >> >> On Sun, Jul 8, 2018, 3:36 AM winter wrote: >>> I believe new variations should always be motivated by use-case if >>> there're too many choices, the lazy behavior of old `atomicModifyIORef` is >>> justified by some cases the modifying functions are lazy in its argument, >>> thus a lazy version could win by not forcing previous thunks, we'd want to >>> keep its behavior as how it's documented. >>> >>> As for tuples more than pairs, they're not really needed, user can always >>> squeeze their product into `b` component. >>> >>> IMHO only the addition of `atomicModifyIORef_` is sensible in the context >>> of base, other APIs may go to package like primitives. But if you have a >>> motivated use case with `atomicModifyIORef2`, etc. Please tell me. >>> >>> >>> On 2018年07月08日 03:09, David Feuer wrote: >>> >>> Whoops! I left out the proposal link: >>> >>> https://github.com/ghc-proposals/ghc-proposals/pull/149 >>> >>> Also, what I called atomicModifyIORef_ below should really be called >>> something like atomicModifyIORef'_, since it forces a polymorphic value. >>> >>> Another thing to note: the underlying atomicModifyMutVar2# primop actually >>> supports more than just pairs. It can handle triples, solos, and any other >>> record types whose first components are lifted: >>> >>> atomicModifyIORefSoloLazy >>> :: IORef a -> (a -> Solo a) -> IO (Solo a) >>> >>> atomicModifyIORefSolo >>> :: IORef a -> (a -> Solo a) -> IO a >>> >>> atomicModifyIORef3, atomicModifyIORef3Lazy >>> :: IORef a -> (a -> (a, b, c)) -> IO (a, b, c) >>> >>> etc. >>> >>> Should we add any such? >>> >>> On Sat, Jul 7, 2018, 2:35 PM David Feuer wrote: >>>> I have proposed[1] the replacement of the atomicModifyMutVar# primop, and >>>> the addition of two cheaper but less capable ones. It seems likely that the >>>> proposal will succeed, but that the GHC steering committee will leave the >>>> question of user interface changes to the libraries list. I would like to >>>> open the discussion here. >>>> >>>> The new primops lead naturally to several thin wrappers: >>>> >>>> -- Atomically replace the IORef contents >>>> -- with the first component of the result of >>>> -- applying the function to the old contents. >>>> -- Return the old value and the result of >>>> -- applying the function, without forcing the latter. >>>> -- >>>> -- atomicModifyIORef ref f = do >>>> -- (_old, ~(_new, res)) <- atomicModifyIORef2Lazy ref f >>>> -- return res >>>> atomicModifyIORef2Lazy >>>> :: IORef a -> (a -> (a, b)) -> IO (a, (a, b)) >>>> >>>> -- Atomically replace the IORef contents >>>> -- with the result of applying the function >>>> -- to the old contents. Return the old and >>>> -- new contents without forcing the latter. >>>> atomicModifyIORefLazy_ >>>> :: IORef a -> (a -> a) -> IO (a, a) >>>> >>>> -- Atomically replace the IORef contents >>>> -- with the given value and return the old >>>> -- contents. >>>> -- >>>> -- atomicWriteIORef ref x = void (atomicSwapIORef ref x) >>>> atomicSwapIORef >>>> :: IORef a -> a -> IO a >>>> >>>> Based on the code I've read that uses atomicModifyIORef, I believe that >>>> the complete laziness of atomicModifyIORef2Lazy and atomicModifyIORefLazy_ >>>> is very rarely desirable. I therefore believe we should also (or perhaps >>>> instead?) offer stricter versions: >>>> >>>> atomicModifyIORef2 >>>> :: IORef a -> (a -> (a, b)) -> IO (a, (a, b)) >>>> atomicModifyIORef2 ref f = do >>>> r@(_old, (_new, _res)) <- atomicModifyIORef2Lazy ref f >>>> return r >>>> >>>> atomicModifyIORef_ >>>> :: IORef a -> (a -> a) -> IO (a, a) >>>> atomicModifyIORef_ ref f = do >>>> r@(_old, !_new) <- atomicModifyIORefLazy_ ref f >>>> return r >>>> >>>> The classic atomicModifyIORef also admits a less gratuitously lazy >>>> version: >>>> >>>> atomicModifyIORefNGL >>>> :: IORef a -> (a -> (a,b)) -> IO b >>>> atomicModifyIORefNGL ref f = do >>>> (_old, (_new, res)) <- atomicModifyIORef2 ref f >>>> return res >>>> >>>> Should we add that as well (with a better name)? Should we even consider >>>> *replacing* the current atomicModifyIORef with that version? That could >>>> theoretically break existing code, but I suspect it would do so very rarely. >>>> If we don't change the existing atomicModifyIORef now, I think we should >>>> consider deprecating it: it's very easy to accidentally use it too lazily. >>> >>> >>> _______________________________________________ >>> 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 david.feuer at gmail.com Thu Jul 12 05:07:53 2018 From: david.feuer at gmail.com (David Feuer) Date: Thu, 12 Jul 2018 01:07:53 -0400 Subject: Discussion: New atomic IORef functions In-Reply-To: <5b46cbc2.1c69fb81.94e81.aeb4SMTPIN_ADDED_BROKEN@mx.google.com> References: <5b46cbc2.1c69fb81.94e81.aeb4SMTPIN_ADDED_BROKEN@mx.google.com> Message-ID: On Wed, Jul 11, 2018, 11:32 PM winter wrote: > OK then, here's some subtle things i want to shout out if you're going to > make the change ; ) > > 1. The proposed naming is just not great, how about these: > > atomicExchangeIORef :: IORef a -> (a -> (a, b)) -> IO (a, (a, b)) > atomicExchangeIORef' :: IORef a -> (a -> (a, b)) -> IO (a, (a, b)) > > atomicApplyIORef :: IORef a -> (a -> a) -> IO (a, a) > atomicApplyIORef :: IORef a -> (a -> a) -> IO (a, a) > > It may not that great but it's more informative IMO. > I agree that my names aren't great, but I think yours are worse. > 3. atomicExchangeIORef should not force the tuple, e.g. don't pattern > match on the tuple result, instead let users choose to force or not. (May > worth adding some document, I'd be happy to help) > I generally disagree. Being lazy in the tuple is pretty much an invitation to memory leaks. I think the lazy version should ideally also be available (it's what the new primop will provide, after all), but I don't think it should be the obvious thing for people to reach for. > 4. atomicExchangeIORef' will not only force the tuple, but also force both > `a` and `b` part to match atomicModifyIORef' 's semantics. > I don't see the need for this. Users can easily force exactly what they want using atomicModifyIORef2 (or if they really want, atomicModifyIORef2Lazy). > 5. atomicApplyIORef(and atomicApplyIORef') deserve its own primop, since > we can skip building selector thunks all together. > Yes, I've implemented that primop already, and it will be added. I'm still looking for an expert to help implement the simplest of the lot, atomicSwapMutVar#, as efficiently as possible. -------------- next part -------------- An HTML attachment was scrubbed... URL: From drkoster at qq.com Thu Jul 12 06:56:13 2018 From: drkoster at qq.com (winter) Date: Thu, 12 Jul 2018 14:56:13 +0800 Subject: Discussion: New atomic IORef functions In-Reply-To: References: <5b46cbc2.1c69fb81.94e81.aeb4SMTPIN_ADDED_BROKEN@mx.google.com> Message-ID: +F940C2601F3DB085 > I generally disagree. Being lazy in the tuple is pretty much an invitation to memory leaks. I think the lazy version should ideally also be available (it's what the new primop will provide, after all), but I don't think it should be the obvious thing for people to reach for. let's put lazy modifying cases aside(which is not that rare), I'm pretty sure haskell forks will use strict version from time to time, it's not the lack of ' make a funtion more easy to reach, it's really just a matter of document,  why breaking consistency with original atomicModifyIORef/atomicModifyIORef'  ? I expect the old mnemonic still works on new ones. > I don't see the need for this. Users can easily force exactly what they want using atomicModifyIORef2 (or if they really want, atomicModifyIORef2Lazy). Exactly the same reason with above, if people have to force the a and b part to stop leakage, then this strict version is not really doing a good job IMHO, I just don't see the value that you have already forced the modification function, but then stopped at a half place where left a thunk inside the IORef. On 2018年07月12日 13:07, David Feuer wrote: > On Wed, Jul 11, 2018, 11:32 PM winter > wrote: > > OK then, here's some subtle things i want to shout out if you're > going to make the change ; ) > > 1. The proposed naming is just not great, how about these: > > atomicExchangeIORef :: IORef a -> (a -> (a, b)) -> IO (a, (a, b)) > atomicExchangeIORef' :: IORef a -> (a -> (a, b)) -> IO (a, (a, b)) > > atomicApplyIORef :: IORef a -> (a -> a) -> IO (a, a) > atomicApplyIORef :: IORef a -> (a -> a) -> IO (a, a) > > It may not that great but it's more informative IMO. > > > I agree that my names aren't great, but I think yours are worse. > > > 3. atomicExchangeIORef should not force the tuple, e.g. don't > pattern match on the tuple result, instead let users choose to > force or not. (May worth adding some document, I'd be happy to help) > > > I generally disagree. Being lazy in the tuple is pretty much an > invitation to memory leaks. I think the lazy version should ideally > also be available (it's what the new primop will provide, after all), > but I don't think it should be the obvious thing for people to reach for. > > > 4. atomicExchangeIORef' will not only force the tuple, but also > force both `a` and `b` part to match atomicModifyIORef' 's semantics. > > > I don't see the need for this. Users can easily force exactly what > they want using atomicModifyIORef2 (or if they really want, > atomicModifyIORef2Lazy). > > > 5. atomicApplyIORef(and atomicApplyIORef') deserve its own primop, > since we can skip building selector thunks all together. > > > Yes, I've implemented that primop already, and it will be added. I'm > still looking for an expert to help implement the simplest of the lot, > atomicSwapMutVar#, as efficiently as possible. -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Sat Jul 14 01:55:49 2018 From: david.feuer at gmail.com (David Feuer) Date: Fri, 13 Jul 2018 21:55:49 -0400 Subject: atomicModifyIORef' strictness Message-ID: In the process of replacing atomicModifyMutVar#, I noticed that atomicModifyIORef' is just a little bit lazy: atomicModifyIORef' ref (\x -> (x + 1, undefined)) will increment the reference and then throw an exception in the calling thread. We could sometimes avoid creating thunks by changing this, so the above would install undefined in the IORef as well. For example, suppose I write atomicModifyIORef' ref (\x -> (3, x + 5)) This will end up producing a thunk for the second component. That could be avoided using something like atomicModifyIORef' ref (\ !x -> (3, x + 5)) but it seems a little surprising to have to do that in a function that focuses on being strict. I don't really care too much one way or the other, but I figured I should point this out and see what you all think. -------------- next part -------------- An HTML attachment was scrubbed... URL: From zocca.marco at gmail.com Tue Jul 24 13:06:32 2018 From: zocca.marco at gmail.com (Marco Zocca) Date: Tue, 24 Jul 2018 15:06:32 +0200 Subject: Extensions to the module name system in H2020 Message-ID: Hi all, I was wondering if there are plans to extend/revisit/tidy up the module name system (https://wiki.haskell.org/Hierarchical_module_names) in view of Haskell 2020. I'm mostly concerned with scientific/numerical applications, where I find the current state of things to be a bit chaotic (see Numeric/Numerical/Optimisation/Optimization etc.). I would be glad to help out, and gather intelligence from the community as well via e.g. a poll. Best, Marco (github.com/ocramz) From chessai1996 at gmail.com Tue Jul 24 13:12:37 2018 From: chessai1996 at gmail.com (Daniel Cartwright) Date: Tue, 24 Jul 2018 09:12:37 -0400 Subject: Extensions to the module name system in H2020 In-Reply-To: References: Message-ID: I am of the opinion that at least most packages should start module names with their package name. Hackage guarantees uniqueness of package names, so this makes sense. The whole Data/Control/Numeric thing seems arbitrary. I would rather see Base.List, Base.Applicative, etc. This has multiple benefits, such as non-overlapping module names by construction (assuming the use of hackage library code), and knowing where the package came from immediately. On Tue, Jul 24, 2018, 9:06 AM Marco Zocca wrote: > Hi all, > > I was wondering if there are plans to extend/revisit/tidy up the > module name system > (https://wiki.haskell.org/Hierarchical_module_names) in view of > Haskell 2020. > > I'm mostly concerned with scientific/numerical applications, where I > find the current state of things to be a bit chaotic (see > Numeric/Numerical/Optimisation/Optimization etc.). > > I would be glad to help out, and gather intelligence from the > community as well via e.g. a poll. > > Best, > Marco (github.com/ocramz) > _______________________________________________ > 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 ndospark320 at naver.com Sun Jul 29 09:44:33 2018 From: ndospark320 at naver.com (=?utf-8?B?67CV7Iug7ZmY?=) Date: Sun, 29 Jul 2018 18:44:33 +0900 Subject: =?utf-8?B?TWFwLXRvLWludGVnZXIgZm9yIGNpcGhlcnM/?= Message-ID: <933cb2341a6b6246ee51dcf9dceed@cweb29.nm.nhnsystem.com> For use of ciphers (SHA-256, RSA-2048, etc.), a type must be able to be injectively mapped to integers. It seems `Enum` is currently the closest thing that does this. But `Enum` is supposed to be for arithmetic sequences, so it seems better to define a new typeclass. (Here named `Cipherable`) There are some types that aren't members of `Enum`. For example, `Maybe`, `[]`, etc. They seem okay to be Cipherable. Hence: {-# LANGUAGE ScopedTypeVariables #-}  instance Cipherable a => Cipherable (Maybe a) where toEnum 0 = Nothing toEnum n = Just (toEnum n) fromEnum Nothing = 0 fromEnum (Just x) = 1 + fromEnum x instance forall a. (Cipherable a, Bounded a) => Cipherable [a] where toEnum 0 = [] toEnum n = let (q,r) = (n-1) `quotRem` (1 + fromEnum (maxBound :: a)) in toEnum r : toEnum q fromEnum [] = 0 fromEnum (x:xs) = 1 + fromEnum x + (1 + fromEnum (maxBound :: a)) * fromEnum xs instance Cipherable Void where toEnum = errorWithoutStackTrace "Cipher.Cipherable.Void.toEnum" fromEnum = absurd (Besides, it is possible to re-write that of `[]` without ScopedTypeVariables? I see no way...) -------------- next part -------------- An HTML attachment was scrubbed... URL: From ndospark320 at naver.com Sun Jul 29 09:47:52 2018 From: ndospark320 at naver.com (=?utf-8?B?67CV7Iug7ZmY?=) Date: Sun, 29 Jul 2018 18:47:52 +0900 Subject: =?utf-8?B?TWFwLXRvLWludGVnZXIgZm9yIGNpcGhlcnM/IChlZGl0ZWQp?= In-Reply-To: <933cb2341a6b6246ee51dcf9dceed@cweb29.nm.nhnsystem.com> References: <933cb2341a6b6246ee51dcf9dceed@cweb29.nm.nhnsystem.com> Message-ID: For use of ciphers (SHA-256, RSA-2048, etc.), a type must be able to be injectively mapped to integers. It seems `Enum` is currently the closest thing that does this. But `Enum` is supposed to be for arithmetic sequences, so it seems better to define a new typeclass. (Here named `Cipherable`) Here, `Cipherable` has `deCipher :: Natural -> a` and `enCipher :: a -> Natural`. There are some types that aren't members of `Enum`. For example, `Maybe`, `[]`, etc. They seem okay to be Cipherable. Hence: {-# LANGUAGE ScopedTypeVariables #-} instance Cipherable a => Cipherable (Maybe a) where deCipher 0 = Nothing deCipher n = Just (toEnum n) enCipher Nothing = 0 enCipher (Just x) = 1 + fromEnum x instance forall a. (Cipherable a, Bounded a) => Cipherable [a] where deCipher 0 = [] deCipher n = let (q,r) = (n-1) `quotRem` (1 + fromEnum (maxBound :: a)) in toEnum r : toEnum q enCipher [] = 0 enCipher (x:xs) = 1 + fromEnum x + (1 + fromEnum (maxBound :: a)) * fromEnum xs instance Cipherable Void where deCipher = errorWithoutStackTrace "Cipher.Cipherable.Void.deCipher" enCipher = absurd (Besides, it is possible to re-write that of `[]` without ScopedTypeVariables? I see no way...) -------------- next part -------------- An HTML attachment was scrubbed... URL: From ndospark320 at naver.com Sun Jul 29 09:50:24 2018 From: ndospark320 at naver.com (=?utf-8?B?67CV7Iug7ZmY?=) Date: Sun, 29 Jul 2018 18:50:24 +0900 Subject: =?utf-8?B?TWFwLXRvLWludGVnZXIgZm9yIGNpcGhlcnM/IChlZGl0ZWQp?= In-Reply-To: References: <933cb2341a6b6246ee51dcf9dceed@cweb29.nm.nhnsystem.com> Message-ID: For use of ciphers (SHA-256, RSA-2048, etc.), a type must be able to be injectively mapped to integers. It seems `Enum` is currently the closest thing that does this. But `Enum` is supposed to be for arithmetic sequences, so it seems better to define a new typeclass. (Here named `Cipherable`) Here, `Cipherable` has `deCipher :: Natural -> a` and `enCipher :: a -> Natural`. There are some types that aren't members of `Enum`. For example, `Maybe`, `[]`, etc. They seem okay to be Cipherable. Hence: {-# LANGUAGE ScopedTypeVariables #-} instance Cipherable a => Cipherable (Maybe a) where deCipher 0 = Nothing deCipher n = Just (deCipher (n-1)) enCipher Nothing = 0 enCipher (Just x) = 1 + enCipher x instance forall a. (Cipherable a, Bounded a) => Cipherable [a] where deCipher 0 = [] deCipher n = let (q,r) = (n-1) `quotRem` (1 + enCipher (maxBound :: a)) in deCipher r : deCipher q enCipher [] = 0 enCipher (x:xs) = 1 + enCipher x + (1 + enCipher (maxBound :: a)) * fromEnum xs instance Cipherable Void where deCipher = errorWithoutStackTrace "Cipher.Cipherable.Void.deCipher" enCipher = absurd (Besides, it is possible to re-write that of `[]` without ScopedTypeVariables? I see no way...) -------------- next part -------------- An HTML attachment was scrubbed... URL: From lemming at henning-thielemann.de Sun Jul 29 09:53:44 2018 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Sun, 29 Jul 2018 11:53:44 +0200 (CEST) Subject: Map-to-integer for ciphers? (edited) In-Reply-To: References: <933cb2341a6b6246ee51dcf9dceed@cweb29.nm.nhnsystem.com> Message-ID: On Sun, 29 Jul 2018, 박신환 wrote: > instance forall a. (Cipherable a, Bounded a) => Cipherable [a] where >     deCipher 0 = [] >     deCipher n = let >         (q,r) = (n-1) `quotRem` (1 + enCipher (maxBound :: a)) >         in deCipher r : deCipher q let (q,r) = (n-1) `quotRem` (1 + enCipher (maxBound `asTypeOf` rd)) rd = deCipher r in rd : deCipher q >     enCipher []     = 0 >     enCipher (x:xs) = 1 + enCipher x + (1 + enCipher (maxBound :: a)) * fromEnum xs maxBound `asTypeOf` x From wolfgang-it at jeltsch.info Mon Jul 30 10:55:56 2018 From: wolfgang-it at jeltsch.info (Wolfgang Jeltsch) Date: Mon, 30 Jul 2018 13:55:56 +0300 Subject: Extensions to the module name system in H2020 In-Reply-To: References: Message-ID: <1532948156.2639.37.camel@jeltsch.info> Hi! There are also disadvantages in having the module name beginning with the package name. With that system, extending subtrees of the module tree is made impossible. In the incremental-computing package, for example, we add incrementalization to several common data types. We do this by adding modules like Data.Sequence.Incremental. With your approach, we would have to change that name to something like Incremental.Sequence. However, if someone implements some new data type in a package amazing- type and adds incrementalization support right away, the incremental version would be in AmazingType.Incremental. So the order of the type name and the string Incremental would generally depend on whether a type was implemented before or after the incremental-computing package was created. In addition, changing the package structure would result in changing the module names. For example, Edward Kmett once split his category theory package into several small packages; under your system, this would result in massive module name changes and consequently compatibility issues. All in all, I think separating package names from module names is a good idea. The distribution of modules among packages seems more like an implementation detail to me and is a lot dependent on historical accident. It should not pollute module naming. All the best, Wolfgang Am Dienstag, den 24.07.2018, 09:12 -0400 schrieb Daniel Cartwright: > I am of the opinion that at least most packages should start module > names with their package name. Hackage guarantees uniqueness of > package names, so this makes sense. The whole Data/Control/Numeric > thing seems arbitrary. I would rather see Base.List, Base.Applicative, > etc. This has multiple benefits, such as non-overlapping module names > by construction (assuming the use of hackage library code), and > knowing where the package came from immediately. > > On Tue, Jul 24, 2018, 9:06 AM Marco Zocca > wrote: > > Hi all, > > > >  I was wondering if there are plans to extend/revisit/tidy up the > > module name system > > (https://wiki.haskell.org/Hierarchical_module_names) in view of > > Haskell 2020. > > > > I'm mostly concerned with scientific/numerical applications, where I > > find the current state of things to be a bit chaotic (see > > Numeric/Numerical/Optimisation/Optimization etc.). > > > > I would be glad to help out, and gather intelligence from the > > community as well via e.g. a poll. > > > > Best, > > Marco (github.com/ocramz) > > _______________________________________________ > > 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 -------------- next part -------------- An HTML attachment was scrubbed... URL: From m at tweag.io Mon Jul 30 11:03:41 2018 From: m at tweag.io (Boespflug, Mathieu) Date: Mon, 30 Jul 2018 13:03:41 +0200 Subject: Extensions to the module name system in H2020 In-Reply-To: <1532948156.2639.37.camel@jeltsch.info> References: <1532948156.2639.37.camel@jeltsch.info> Message-ID: I agree. I would add that separating function from provenance is a good thing. It's a good thing that I can import Data.Map if I just want a map type, rather than some bespoke AmazingTypes.Map. It's up to my build tool configuration to bring into scope the right package that provides some implementation of a map. And in a post Backpack world, this will be even more useful, because I can check that whatever implementation I choose matches the the type signatures that my code expects. On 30 July 2018 at 12:55, Wolfgang Jeltsch wrote: > Hi! > > There are also disadvantages in having the module name beginning with the > package name. > > With that system, extending subtrees of the module tree is made > impossible. In the *incremental-computing* package, for example, we add > incrementalization to several common data types. We do this by adding > modules like *Data.Sequence.Incremental*. With your approach, we would > have to change that name to something like *Incremental.Sequence*. > However, if someone implements some new data type in a package > *amazing-type* and adds incrementalization support right away, the > incremental version would be in *AmazingType.Incremental*. So the order > of the type name and the string *Incremental* would generally depend on > whether a type was implemented before or after the *incremental-computing* > package was created. > > In addition, changing the package structure would result in changing the > module names. For example, Edward Kmett once split his category theory > package into several small packages; under your system, this would result > in massive module name changes and consequently compatibility issues. > > All in all, I think separating package names from module names is a good > idea. The distribution of modules among packages seems more like an > implementation detail to me and is a lot dependent on historical accident. > It should not pollute module naming. > > All the best, > Wolfgang > > Am Dienstag, den 24.07.2018, 09:12 -0400 schrieb Daniel Cartwright: > > I am of the opinion that at least most packages should start module names > with their package name. Hackage guarantees uniqueness of package names, so > this makes sense. The whole Data/Control/Numeric thing seems arbitrary. I > would rather see Base.List, Base.Applicative, etc. This has multiple > benefits, such as non-overlapping module names by construction (assuming > the use of hackage library code), and knowing where the package came from > immediately. > > On Tue, Jul 24, 2018, 9:06 AM Marco Zocca wrote: > > Hi all, > > I was wondering if there are plans to extend/revisit/tidy up the > module name system > (https://wiki.haskell.org/Hierarchical_module_names) in view of > Haskell 2020. > > I'm mostly concerned with scientific/numerical applications, where I > find the current state of things to be a bit chaotic (see > Numeric/Numerical/Optimisation/Optimization etc.). > > I would be glad to help out, and gather intelligence from the > community as well via e.g. a poll. > > Best, > Marco (github.com/ocramz) > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > _______________________________________________ > Libraries mailing listLibraries at haskell.orghttp://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > > _______________________________________________ > 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 chessai1996 at gmail.com Mon Jul 30 14:22:25 2018 From: chessai1996 at gmail.com (Daniel Cartwright) Date: Mon, 30 Jul 2018 10:22:25 -0400 Subject: Extensions to the module name system in H2020 In-Reply-To: References: <1532948156.2639.37.camel@jeltsch.info> Message-ID: Wolfgang, instead of Incremental.Type, instead you could just extend it to something like Containers.Map.Incremental, but I see your point. At that point, you cannot tell from which package the module came and might even assume at first that it comes from containers. I also see your point about polluting module names/causing compatibility issues for lots of things. Maybe this is another one of those things that would have been better if adopted earlier on, but is much less practical to adopt at this point or going further. On Mon, Jul 30, 2018, 7:04 AM Boespflug, Mathieu wrote: > I agree. > > I would add that separating function from provenance is a good thing. It's > a good thing that I can import Data.Map if I just want a map type, rather > than some bespoke AmazingTypes.Map. It's up to my build tool configuration > to bring into scope the right package that provides some implementation of > a map. And in a post Backpack world, this will be even more useful, because > I can check that whatever implementation I choose matches the the type > signatures that my code expects. > > > On 30 July 2018 at 12:55, Wolfgang Jeltsch > wrote: > >> Hi! >> >> There are also disadvantages in having the module name beginning with the >> package name. >> >> With that system, extending subtrees of the module tree is made >> impossible. In the *incremental-computing* package, for example, we add >> incrementalization to several common data types. We do this by adding >> modules like *Data.Sequence.Incremental*. With your approach, we would >> have to change that name to something like *Incremental.Sequence*. >> However, if someone implements some new data type in a package >> *amazing-type* and adds incrementalization support right away, the >> incremental version would be in *AmazingType.Incremental*. So the order >> of the type name and the string *Incremental* would generally depend on >> whether a type was implemented before or after the >> *incremental-computing* package was created. >> >> In addition, changing the package structure would result in changing the >> module names. For example, Edward Kmett once split his category theory >> package into several small packages; under your system, this would result >> in massive module name changes and consequently compatibility issues. >> >> All in all, I think separating package names from module names is a good >> idea. The distribution of modules among packages seems more like an >> implementation detail to me and is a lot dependent on historical accident. >> It should not pollute module naming. >> >> All the best, >> Wolfgang >> >> Am Dienstag, den 24.07.2018, 09:12 -0400 schrieb Daniel Cartwright: >> >> I am of the opinion that at least most packages should start module names >> with their package name. Hackage guarantees uniqueness of package names, so >> this makes sense. The whole Data/Control/Numeric thing seems arbitrary. I >> would rather see Base.List, Base.Applicative, etc. This has multiple >> benefits, such as non-overlapping module names by construction (assuming >> the use of hackage library code), and knowing where the package came from >> immediately. >> >> On Tue, Jul 24, 2018, 9:06 AM Marco Zocca wrote: >> >> Hi all, >> >> I was wondering if there are plans to extend/revisit/tidy up the >> module name system >> (https://wiki.haskell.org/Hierarchical_module_names) in view of >> Haskell 2020. >> >> I'm mostly concerned with scientific/numerical applications, where I >> find the current state of things to be a bit chaotic (see >> Numeric/Numerical/Optimisation/Optimization etc.). >> >> I would be glad to help out, and gather intelligence from the >> community as well via e.g. a poll. >> >> Best, >> Marco (github.com/ocramz) >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> >> _______________________________________________ >> Libraries mailing listLibraries at haskell.orghttp://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> >> >> _______________________________________________ >> 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 > -------------- next part -------------- An HTML attachment was scrubbed... URL: From dave at zednenem.com Mon Jul 30 19:03:00 2018 From: dave at zednenem.com (David Menendez) Date: Mon, 30 Jul 2018 15:03:00 -0400 Subject: Extensions to the module name system in H2020 In-Reply-To: References: <1532948156.2639.37.camel@jeltsch.info> Message-ID: I think there are several ideas being discussed here, and it may be helpful to distinguish them. 1. Two packages may unintentionally include modules with the same name, making it difficult to use both at once 2. Module names should be organized in some logical manner 3. A package may want to import a module without tying it to a specific package Obviously, 1 and 3 are in tension. You can get around 1 with a GHC extension that lets you import a module from a specific package. I would argue that 2 is useful when organizing a single package, but less so when discussing the universe of all publicly available Haskell libraries. (This is how you end up with stuff like Text.ParserCombinators.Parsec and Text.PrettyPrint.HughesPJ, where the package name is effectively at the end of the name.) I don’t see any particular reason to prefer, say, Data.Sequence.Incremental to Data.Incremental.Sequence. Scenario 3 comes up every time this topic is discussed, but I don’t recall seeing even anecdotal evidence for it. Can anyone name two or more packages that define modules with the same name(s) such that one is a drop-in replacement for the other? That isn’t a rhetorical question. I’d honestly like to know if these exist. Probably the best solution is to separate the internal name of a module (used within its package) from the external name (used by modules in other packages). When including a package, users may assign a prefix to every module’s name and rename individual modules as desired. Packages can specify a suggested prefix that will get picked up by default, unless overridden. This (1) avoids problems from name collisions, (2) allows hierarchical naming for external modules, and (3) enables replacing one module with another from another package (or even the same package). This sort of scheme has been suggested before (I think Simon Marlow proposed something like it a few years ago), but it never seemed pressing enough to do the work. Now that Backpack has taken a big step towards separating internal and external names, I think this is worth investigating. On Mon, Jul 30, 2018 at 10:22 AM, Daniel Cartwright wrote: > Wolfgang, instead of Incremental.Type, instead you could just extend it to > something like > > Containers.Map.Incremental, > > but I see your point. At that point, you cannot tell from which package the > module came and might even assume at first that it comes from containers. > > I also see your point about polluting module names/causing compatibility > issues for lots of things. Maybe this is another one of those things that > would have been better if adopted earlier on, but is much less practical to > adopt at this point or going further. > > > On Mon, Jul 30, 2018, 7:04 AM Boespflug, Mathieu wrote: >> >> I agree. >> >> I would add that separating function from provenance is a good thing. It's >> a good thing that I can import Data.Map if I just want a map type, rather >> than some bespoke AmazingTypes.Map. It's up to my build tool configuration >> to bring into scope the right package that provides some implementation of a >> map. And in a post Backpack world, this will be even more useful, because I >> can check that whatever implementation I choose matches the the type >> signatures that my code expects. >> >> >> On 30 July 2018 at 12:55, Wolfgang Jeltsch >> wrote: >>> >>> Hi! >>> >>> There are also disadvantages in having the module name beginning with the >>> package name. >>> >>> With that system, extending subtrees of the module tree is made >>> impossible. In the incremental-computing package, for example, we add >>> incrementalization to several common data types. We do this by adding >>> modules like Data.Sequence.Incremental. With your approach, we would have to >>> change that name to something like Incremental.Sequence. However, if someone >>> implements some new data type in a package amazing-type and adds >>> incrementalization support right away, the incremental version would be in >>> AmazingType.Incremental. So the order of the type name and the string >>> Incremental would generally depend on whether a type was implemented before >>> or after the incremental-computing package was created. >>> >>> In addition, changing the package structure would result in changing the >>> module names. For example, Edward Kmett once split his category theory >>> package into several small packages; under your system, this would result in >>> massive module name changes and consequently compatibility issues. >>> >>> All in all, I think separating package names from module names is a good >>> idea. The distribution of modules among packages seems more like an >>> implementation detail to me and is a lot dependent on historical accident. >>> It should not pollute module naming. >>> >>> All the best, >>> Wolfgang >>> >>> Am Dienstag, den 24.07.2018, 09:12 -0400 schrieb Daniel Cartwright: >>> >>> I am of the opinion that at least most packages should start module names >>> with their package name. Hackage guarantees uniqueness of package names, so >>> this makes sense. The whole Data/Control/Numeric thing seems arbitrary. I >>> would rather see Base.List, Base.Applicative, etc. This has multiple >>> benefits, such as non-overlapping module names by construction (assuming the >>> use of hackage library code), and knowing where the package came from >>> immediately. >>> >>> On Tue, Jul 24, 2018, 9:06 AM Marco Zocca wrote: >>> >>> Hi all, >>> >>> I was wondering if there are plans to extend/revisit/tidy up the >>> module name system >>> (https://wiki.haskell.org/Hierarchical_module_names) in view of >>> Haskell 2020. >>> >>> I'm mostly concerned with scientific/numerical applications, where I >>> find the current state of things to be a bit chaotic (see >>> Numeric/Numerical/Optimisation/Optimization etc.). >>> >>> I would be glad to help out, and gather intelligence from the >>> community as well via e.g. a poll. >>> >>> Best, >>> Marco (github.com/ocramz) >>> _______________________________________________ >>> 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 >>> >>> >>> _______________________________________________ >>> 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 > > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -- Dave Menendez From lemming at henning-thielemann.de Tue Jul 31 08:24:34 2018 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Tue, 31 Jul 2018 10:24:34 +0200 (CEST) Subject: Extensions to the module name system in H2020 In-Reply-To: References: <1532948156.2639.37.camel@jeltsch.info> Message-ID: On Mon, 30 Jul 2018, David Menendez wrote: > Scenario 3 comes up every time this topic is discussed, but I don’t > recall seeing even anecdotal evidence for it. Can anyone name two or > more packages that define modules with the same name(s) such that one > is a drop-in replacement for the other? That isn’t a rhetorical > question. I’d honestly like to know if these exist. stream-fusion provided a drop-in replacement for Data.List with improved list fusion. My prelude2010 provides a drop-in replacement for Prelude, however the user actually wants to stick to prelude2010 in order to get the old Prelude signatures back. From wolfgang-it at jeltsch.info Tue Jul 31 12:43:54 2018 From: wolfgang-it at jeltsch.info (Wolfgang Jeltsch) Date: Tue, 31 Jul 2018 15:43:54 +0300 Subject: Extensions to the module name system in H2020 In-Reply-To: References: <1532948156.2639.37.camel@jeltsch.info> Message-ID: <1533041034.22651.19.camel@jeltsch.info> Am Montag, den 30.07.2018, 15:03 -0400 schrieb David Menendez: > I think there are several ideas being discussed here, and it may be > helpful to distinguish them. > > 1. Two packages may unintentionally include modules with the same >    name, making it difficult to use both at once > 2. Module names should be organized in some logical manner > 3. A package may want to import a module without tying it to a >    specific package There is also the situation where the package name isn’t essential and shouldn’t get in the way when naming modules. For example, there are a lot of monad transformers in the world. The `transformers` package implements some of them; others are added by other packages. It is good if the module that implements a certain kind of monad transformer has a name of the form `Control.Monad.Trans.⟨type-of-transformer⟩`. Having the package name in the module name would be like revealing an implementation detail. All the best, Wolfgang From chessai1996 at gmail.com Tue Jul 31 12:51:15 2018 From: chessai1996 at gmail.com (Daniel Cartwright) Date: Tue, 31 Jul 2018 08:51:15 -0400 Subject: Extensions to the module name system in H2020 In-Reply-To: <1533041034.22651.19.camel@jeltsch.info> References: <1532948156.2639.37.camel@jeltsch.info> <1533041034.22651.19.camel@jeltsch.info> Message-ID: "There is also the situation where the package name isn’t essential and shouldn’t get in the way when naming modules. For example, there are a lot of monad transformers in the world. The `transformers` package implements some of them; others are added by other packages. It is good if the module that implements a certain kind of monad transformer has a name of the form `Control.Monad.Trans.⟨type-of-transformer⟩`. Having the package name in the module name would be like revealing an implementation detail." Not sure I agree that that is necessarily the case. Transformers.ExceptT Transformers.ReaderT These.ChronicleT This lets me know exactly where these transformers came from, just by reading the module name. On Tue, Jul 31, 2018, 8:44 AM Wolfgang Jeltsch wrote: > Am Montag, den 30.07.2018, 15:03 -0400 schrieb David Menendez: > > I think there are several ideas being discussed here, and it may be > > helpful to distinguish them. > > > > 1. Two packages may unintentionally include modules with the same > > name, making it difficult to use both at once > > 2. Module names should be organized in some logical manner > > 3. A package may want to import a module without tying it to a > > specific package > > There is also the situation where the package name isn’t essential and > shouldn’t get in the way when naming modules. For example, there are a > lot of monad transformers in the world. The `transformers` package > implements some of them; others are added by other packages. It is good > if the module that implements a certain kind of monad transformer has a > name of the form `Control.Monad.Trans.⟨type-of-transformer⟩`. Having the > package name in the module name would be like revealing an > implementation detail. > > All the best, > Wolfgang > _______________________________________________ > 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 wolfgang-it at jeltsch.info Tue Jul 31 13:28:58 2018 From: wolfgang-it at jeltsch.info (Wolfgang Jeltsch) Date: Tue, 31 Jul 2018 16:28:58 +0300 Subject: Extensions to the module name system in H2020 In-Reply-To: References: <1532948156.2639.37.camel@jeltsch.info> <1533041034.22651.19.camel@jeltsch.info> Message-ID: <1533043738.22651.23.camel@jeltsch.info> Am Dienstag, den 31.07.2018, 08:51 -0400 schrieb Daniel Cartwright: > "There is also the situation where the package name isn’t essential > and > shouldn’t get in the way when naming modules. For example, there are a > lot of monad transformers in the world. The `transformers` package > implements some of them; others are added by other packages. It is > good > if the module that implements a certain kind of monad transformer has > a > name of the form `Control.Monad.Trans.⟨type-of-transformer⟩`. Having > the > package name in the module name would be like revealing an > implementation detail." > > Not sure I agree that that is necessarily the case. > > Transformers.ExceptT > Transformers.ReaderT > These.ChronicleT > > This lets me know exactly where these transformers came from, just by > reading the module name. But I don’t want to see where those transformers “came from” but that they are certain monad transformers. The latter is expressed by the cons istent naming Control.Monad.Trans.⟨type-of-transformer⟩. All the best, Wolfgang -------------- next part -------------- An HTML attachment was scrubbed... URL: From chessai1996 at gmail.com Tue Jul 31 13:35:01 2018 From: chessai1996 at gmail.com (Daniel Cartwright) Date: Tue, 31 Jul 2018 09:35:01 -0400 Subject: Extensions to the module name system in H2020 In-Reply-To: <1533043738.22651.23.camel@jeltsch.info> References: <1532948156.2639.37.camel@jeltsch.info> <1533041034.22651.19.camel@jeltsch.info> <1533043738.22651.23.camel@jeltsch.info> Message-ID: As someone who reads documentation, I do want to see where they came from. The source (not code, but origin) of a module is not an implementation detail, it's a place for documentation. This naming scheme is also consistent in its own right. On Tue, Jul 31, 2018, 9:29 AM Wolfgang Jeltsch wrote: > Am Dienstag, den 31.07.2018, 08:51 -0400 schrieb Daniel Cartwright: > > "There is also the situation where the package name isn’t essential and > shouldn’t get in the way when naming modules. For example, there are a > lot of monad transformers in the world. The `transformers` package > implements some of them; others are added by other packages. It is good > if the module that implements a certain kind of monad transformer has a > name of the form `Control.Monad.Trans.⟨type-of-transformer⟩`. Having the > package name in the module name would be like revealing an > implementation detail." > > Not sure I agree that that is necessarily the case. > > Transformers.ExceptT > Transformers.ReaderT > These.ChronicleT > > This lets me know exactly where these transformers came from, just by > reading the module name. > > > But I don’t want to see where those transformers “came from” but that they > are certain monad transformers. The latter is expressed by the > *consistent* naming Control.Monad.Trans.⟨type-of-transformer⟩. > > All the best, > Wolfgang > _______________________________________________ > 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 dave at zednenem.com Tue Jul 31 18:57:47 2018 From: dave at zednenem.com (David Menendez) Date: Tue, 31 Jul 2018 14:57:47 -0400 Subject: Extensions to the module name system in H2020 In-Reply-To: <1533041034.22651.19.camel@jeltsch.info> References: <1532948156.2639.37.camel@jeltsch.info> <1533041034.22651.19.camel@jeltsch.info> Message-ID: On Tue, Jul 31, 2018 at 8:43 AM, Wolfgang Jeltsch wrote: > Am Montag, den 30.07.2018, 15:03 -0400 schrieb David Menendez: >> I think there are several ideas being discussed here, and it may be >> helpful to distinguish them. >> >> 1. Two packages may unintentionally include modules with the same >> name, making it difficult to use both at once >> 2. Module names should be organized in some logical manner >> 3. A package may want to import a module without tying it to a >> specific package > > There is also the situation where the package name isn’t essential and > shouldn’t get in the way when naming modules. For example, there are a > lot of monad transformers in the world. The `transformers` package > implements some of them; others are added by other packages. It is good > if the module that implements a certain kind of monad transformer has a > name of the form `Control.Monad.Trans.⟨type-of-transformer⟩`. Having the > package name in the module name would be like revealing an > implementation detail. How would the package name get in the way? What is it getting in the way of? Having related modules have similar prefixes may be useful from an organizational standpoint, but it has no impact at all on how they are used. This isn’t Java, where I can import Control.Monad.* and bring all the submodules in scope. I agree with the argument that reflecting the provenance of a module in its name is not always desirable, but the idea that it is never desirable is obviously incorrect. Are Parsec, QuickCheck, and pretty all doing it wrong? Again, this is only an issue because we don’t have a convenient way of renaming modules when we declare a dependency on a package. With a small addition to the infrastructure, we can avoid this argument entirely. -- Dave Menendez From wolfgang-it at jeltsch.info Tue Jul 31 22:40:29 2018 From: wolfgang-it at jeltsch.info (Wolfgang Jeltsch) Date: Wed, 01 Aug 2018 01:40:29 +0300 Subject: Extensions to the module name system in H2020 In-Reply-To: References: <1532948156.2639.37.camel@jeltsch.info> <1533041034.22651.19.camel@jeltsch.info> Message-ID: <1533076829.22651.48.camel@jeltsch.info> Am Dienstag, den 31.07.2018, 14:57 -0400 schrieb David Menendez: > I agree with the argument that reflecting the provenance of a module > in its name is not always desirable, but the idea that it is never > desirable is obviously incorrect. Are Parsec, QuickCheck, and pretty > all doing it wrong? I’ve never considered the module names of Parsec, QuickCheck, etc. mentioning the packages the modules come from but mentioning the interfaces the modules provide. So for me “QuickCheck” doesn’t refer to the QuickCheck package but to a certain way of doing tests with a certain interface. All the best, Wolfgang