From alexandre.fmp.esteves at gmail.com Sun Mar 7 03:25:16 2021 From: alexandre.fmp.esteves at gmail.com (Alexandre Esteves) Date: Sun, 7 Mar 2021 03:25:16 +0000 Subject: Proposal: add replay function to Control.Monad.Cont.Class Message-ID: I'd like to propose adding the following function (method?) to Control.Monad.Cont.Class, possibly with another name: replay :: MonadCont m => m (m a) replay = callCC $ pure . fix Using this in a do-notation block allows one to bind a name to the sub-block that starts immediately after. I reached for continuations to try to get this behavior for use with recursive flows without disrupting the reading of the main forward flow and found how to do it in https://jsdw.me/posts/haskell-cont-monad/ under the name "goto". While "goto" is as familiar as a name can be, I feel "replay" more accurately conveys, that you can only 'go back', by stating what actually is happening - that a sub-block we're currently evaluating is replayed from its beginning. As a motivating example, here's the same recursive IO flow written in 3 ways - one with replay, one with fix, and one with where clauses. {-# LANGUAGE LambdaCase #-} import Control.Monad.Cont.Class (MonadCont(callCC)) import Control.Monad.IO.Class (MonadIO, liftIO) import Control.Monad.Trans.Cont (evalContT) import Data.Function (fix) import Text.Read (readMaybe) replay :: MonadCont m => m (m a) replay = callCC $ pure . fix prompt :: MonadIO m => String -> m String prompt t = liftIO $ do putStrLn t putStr "> " getLine flowContT :: IO () flowContT = evalContT $ do liftIO $ putStrLn "Welcome to the totally not contrived game" numberPromptStep <- replay readMaybe <$> prompt "Pick a number" >>= \case Nothing -> liftIO (putStrLn "Not a number") *> numberPromptStep Just n -> liftIO $ putStrLn $ "You picked " <> show (n :: Int) exitPromptStep <- replay prompt "Stop? y/n" >>= \case "y" -> pure () "n" -> numberPromptStep _ -> liftIO (putStrLn "Invalid choice") *> exitPromptStep flowFix :: IO () flowFix = do putStrLn "Welcome to the totally not contrived game" fix $ \numberPromptStep -> do readMaybe <$> prompt "Pick a number" >>= \case Nothing -> liftIO (putStrLn "Not a number") *> numberPromptStep Just n -> liftIO $ putStrLn $ "You picked " <> show (n :: Int) fix $ \exitPromptStep -> do prompt "Stop? y/n" >>= \case "y" -> pure () "n" -> numberPromptStep _ -> liftIO (putStrLn "Invalid choice") *> exitPromptStep flowWhere :: IO () flowWhere = do putStrLn "Welcome to the totally not contrived game" numberPromptStep where numberPromptStep = do readMaybe <$> prompt "Pick a number" >>= \case Nothing -> liftIO (putStrLn "Not a number") *> numberPromptStep Just n -> do liftIO $ putStrLn $ "You picked " <> show (n :: Int) exitPromptStep exitPromptStep = do prompt "Stop? y/n" >>= \case "y" -> pure () "n" -> numberPromptStep _ -> liftIO (putStrLn "Invalid choice") *> exitPromptStep -------------- next part -------------- An HTML attachment was scrubbed... URL: From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Sun Mar 7 09:25:18 2021 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Sun, 7 Mar 2021 09:25:18 +0000 Subject: Proposal: add replay function to Control.Monad.Cont.Class In-Reply-To: References: Message-ID: <20210307092518.GD5518@cloudinit-builder> On Sun, Mar 07, 2021 at 03:25:16AM +0000, Alexandre Esteves wrote: > replay :: MonadCont m => m (m a) > replay = callCC $ pure . fix > > Using this in a do-notation block allows one to bind a name to the > sub-block that starts immediately after. > I reached for continuations to try to get this behavior for use with > recursive flows without disrupting the reading of the main forward flow and > found how to do it in https://jsdw.me/posts/haskell-cont-monad/ under the > name "goto". > > While "goto" is as familiar as a name can be, I feel "replay" more > accurately conveys, that you can only 'go back', by stating what actually > is happening - that a sub-block we're currently evaluating is replayed from > its beginning. Looks like a "label" more than a "goto" to me. Would "label" be a good name? From ekmett at gmail.com Sun Mar 7 17:16:27 2021 From: ekmett at gmail.com (Edward Kmett) Date: Sun, 7 Mar 2021 09:16:27 -0800 Subject: Proposal: add replay function to Control.Monad.Cont.Class In-Reply-To: <20210307092518.GD5518@cloudinit-builder> References: <20210307092518.GD5518@cloudinit-builder> Message-ID: I rather like label. +1 from me. On Sun, Mar 7, 2021 at 1:25 AM Tom Ellis < tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk> wrote: > On Sun, Mar 07, 2021 at 03:25:16AM +0000, Alexandre Esteves wrote: > > replay :: MonadCont m => m (m a) > > replay = callCC $ pure . fix > > > > Using this in a do-notation block allows one to bind a name to the > > sub-block that starts immediately after. > > I reached for continuations to try to get this behavior for use with > > recursive flows without disrupting the reading of the main forward flow > and > > found how to do it in https://jsdw.me/posts/haskell-cont-monad/ under > the > > name "goto". > > > > While "goto" is as familiar as a name can be, I feel "replay" more > > accurately conveys, that you can only 'go back', by stating what actually > > is happening - that a sub-block we're currently evaluating is replayed > from > > its beginning. > > Looks like a "label" more than a "goto" to me. Would "label" be a > good name? > _______________________________________________ > 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 carter.schonwald at gmail.com Sun Mar 7 17:35:45 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sun, 7 Mar 2021 12:35:45 -0500 Subject: Proposal: add replay function to Control.Monad.Cont.Class In-Reply-To: References: <20210307092518.GD5518@cloudinit-builder> Message-ID: Yeah On Sun, Mar 7, 2021 at 12:16 PM Edward Kmett wrote: > I rather like label. +1 from me. > > On Sun, Mar 7, 2021 at 1:25 AM Tom Ellis < > tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk> wrote: > >> On Sun, Mar 07, 2021 at 03:25:16AM +0000, Alexandre Esteves wrote: >> > replay :: MonadCont m => m (m a) >> > replay = callCC $ pure . fix >> > >> > Using this in a do-notation block allows one to bind a name to the >> > sub-block that starts immediately after. >> > I reached for continuations to try to get this behavior for use with >> > recursive flows without disrupting the reading of the main forward flow >> and >> > found how to do it in https://jsdw.me/posts/haskell-cont-monad/ under >> the >> > name "goto". >> > >> > While "goto" is as familiar as a name can be, I feel "replay" more >> > accurately conveys, that you can only 'go back', by stating what >> actually >> > is happening - that a sub-block we're currently evaluating is replayed >> from >> > its beginning. >> >> Looks like a "label" more than a "goto" to me. Would "label" be a >> good name? >> _______________________________________________ >> 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 zemyla at gmail.com Sun Mar 7 18:35:21 2021 From: zemyla at gmail.com (Zemyla) Date: Sun, 7 Mar 2021 12:35:21 -0600 Subject: Proposal: add replay function to Control.Monad.Cont.Class In-Reply-To: References: <20210307092518.GD5518@cloudinit-builder> Message-ID: I kind of don't like it, because the continuation doesn't return anything but itself. I'd prefer something that works more like the setjmp function in C, taking a value and returning the value plus a function that lets it return the new value: setJump :: MonadCont m => a -> m (a -> m b, a) setJump a = callCC $ \k -> let go b = k (go, b) in pure (go, a) On Sun, Mar 7, 2021, 11:36 Carter Schonwald wrote: > Yeah > > On Sun, Mar 7, 2021 at 12:16 PM Edward Kmett wrote: > >> I rather like label. +1 from me. >> >> On Sun, Mar 7, 2021 at 1:25 AM Tom Ellis < >> tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk> wrote: >> >>> On Sun, Mar 07, 2021 at 03:25:16AM +0000, Alexandre Esteves wrote: >>> > replay :: MonadCont m => m (m a) >>> > replay = callCC $ pure . fix >>> > >>> > Using this in a do-notation block allows one to bind a name to the >>> > sub-block that starts immediately after. >>> > I reached for continuations to try to get this behavior for use with >>> > recursive flows without disrupting the reading of the main forward >>> flow and >>> > found how to do it in https://jsdw.me/posts/haskell-cont-monad/ under >>> the >>> > name "goto". >>> > >>> > While "goto" is as familiar as a name can be, I feel "replay" more >>> > accurately conveys, that you can only 'go back', by stating what >>> actually >>> > is happening - that a sub-block we're currently evaluating is replayed >>> from >>> > its beginning. >>> >>> Looks like a "label" more than a "goto" to me. Would "label" be a >>> good name? >>> _______________________________________________ >>> 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 > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Sun Mar 7 19:10:51 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sun, 7 Mar 2021 14:10:51 -0500 Subject: Proposal: add replay function to Control.Monad.Cont.Class In-Reply-To: References: <20210307092518.GD5518@cloudinit-builder> Message-ID: This does sound more useful! What are some simple expressivity examples for the two? On Sun, Mar 7, 2021 at 1:36 PM Zemyla wrote: > I kind of don't like it, because the continuation doesn't return anything > but itself. I'd prefer something that works more like the setjmp function > in C, taking a value and returning the value plus a function that lets it > return the new value: > > setJump :: MonadCont m => a -> m (a -> m b, a) > setJump a = callCC $ \k -> let > go b = k (go, b) > in pure (go, a) > > On Sun, Mar 7, 2021, 11:36 Carter Schonwald > wrote: > >> Yeah >> >> On Sun, Mar 7, 2021 at 12:16 PM Edward Kmett wrote: >> >>> I rather like label. +1 from me. >>> >>> On Sun, Mar 7, 2021 at 1:25 AM Tom Ellis < >>> tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk> wrote: >>> >>>> On Sun, Mar 07, 2021 at 03:25:16AM +0000, Alexandre Esteves wrote: >>>> > replay :: MonadCont m => m (m a) >>>> > replay = callCC $ pure . fix >>>> > >>>> > Using this in a do-notation block allows one to bind a name to the >>>> > sub-block that starts immediately after. >>>> > I reached for continuations to try to get this behavior for use with >>>> > recursive flows without disrupting the reading of the main forward >>>> flow and >>>> > found how to do it in https://jsdw.me/posts/haskell-cont-monad/ >>>> under the >>>> > name "goto". >>>> > >>>> > While "goto" is as familiar as a name can be, I feel "replay" more >>>> > accurately conveys, that you can only 'go back', by stating what >>>> actually >>>> > is happening - that a sub-block we're currently evaluating is >>>> replayed from >>>> > its beginning. >>>> >>>> Looks like a "label" more than a "goto" to me. Would "label" be a >>>> good name? >>>> _______________________________________________ >>>> 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 >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Sun Mar 7 19:33:10 2021 From: david.feuer at gmail.com (David Feuer) Date: Sun, 7 Mar 2021 14:33:10 -0500 Subject: Proposal: add replay function to Control.Monad.Cont.Class In-Reply-To: References: <20210307092518.GD5518@cloudinit-builder> Message-ID: Why not both? On Sun, Mar 7, 2021, 1:36 PM Zemyla wrote: > I kind of don't like it, because the continuation doesn't return anything > but itself. I'd prefer something that works more like the setjmp function > in C, taking a value and returning the value plus a function that lets it > return the new value: > > setJump :: MonadCont m => a -> m (a -> m b, a) > setJump a = callCC $ \k -> let > go b = k (go, b) > in pure (go, a) > > On Sun, Mar 7, 2021, 11:36 Carter Schonwald > wrote: > >> Yeah >> >> On Sun, Mar 7, 2021 at 12:16 PM Edward Kmett wrote: >> >>> I rather like label. +1 from me. >>> >>> On Sun, Mar 7, 2021 at 1:25 AM Tom Ellis < >>> tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk> wrote: >>> >>>> On Sun, Mar 07, 2021 at 03:25:16AM +0000, Alexandre Esteves wrote: >>>> > replay :: MonadCont m => m (m a) >>>> > replay = callCC $ pure . fix >>>> > >>>> > Using this in a do-notation block allows one to bind a name to the >>>> > sub-block that starts immediately after. >>>> > I reached for continuations to try to get this behavior for use with >>>> > recursive flows without disrupting the reading of the main forward >>>> flow and >>>> > found how to do it in https://jsdw.me/posts/haskell-cont-monad/ >>>> under the >>>> > name "goto". >>>> > >>>> > While "goto" is as familiar as a name can be, I feel "replay" more >>>> > accurately conveys, that you can only 'go back', by stating what >>>> actually >>>> > is happening - that a sub-block we're currently evaluating is >>>> replayed from >>>> > its beginning. >>>> >>>> Looks like a "label" more than a "goto" to me. Would "label" be a >>>> good name? >>>> _______________________________________________ >>>> 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 > -------------- next part -------------- An HTML attachment was scrubbed... URL: From alexandre.fmp.esteves at gmail.com Sat Mar 13 16:41:08 2021 From: alexandre.fmp.esteves at gmail.com (Alexandre Esteves) Date: Sat, 13 Mar 2021 16:41:08 +0000 Subject: Proposal: add replay function to Control.Monad.Cont.Class In-Reply-To: References: <20210307092518.GD5518@cloudinit-builder> Message-ID: Agreed that 'label' is a better name than goto/replay. It didn't even hit me until I saw setJump that `m (m a)` doesn't allow representing recursive functions with arguments, so `a -> m(a -> m b, a)` does seem much more expressive to me Starting with my original examples, introducing the recursive binding when there are arguments would look like `(numberPromptStep, (x,y)) <- setJump (x0, y0)` `fix $ \numberPromptStep x y -> do` `numberPromptStep x y = do` It is slightly annoying that the later 2 can simply add an argument while setJump requires using the uncurried version but I don't see a way around that since >>= itself works that way `m (m a)` is essentially the 0-tuple version of `a -> m(a -> m b, a)` which makes me wonder if it's even worth having. Sure, it's convenient not to have these unit/() around, but maybe the same argument (heh) could be made for 2-argument and 3-argument versions. do numberPromptStep <- setJump (..) numberPromptStep do (numberPromptStep, x, y) <- setJump2 x0 y0 (..) numberPromptStep x' y' Given that, I think `a -> m (a -> m b, a)` is the important one be it called label or setJump and maybe there can be a specialized 0-tuple version (e.g. label_ / setJump_) offering the `m (m a)` special case. I don't feel strongly about it though, since unlike `for_` it wouldn't actually relax constraints, only have a simpler signature. On Sun, Mar 7, 2021 at 7:33 PM David Feuer wrote: > Why not both? > > On Sun, Mar 7, 2021, 1:36 PM Zemyla wrote: > >> I kind of don't like it, because the continuation doesn't return anything >> but itself. I'd prefer something that works more like the setjmp function >> in C, taking a value and returning the value plus a function that lets it >> return the new value: >> >> setJump :: MonadCont m => a -> m (a -> m b, a) >> setJump a = callCC $ \k -> let >> go b = k (go, b) >> in pure (go, a) >> >> On Sun, Mar 7, 2021, 11:36 Carter Schonwald >> wrote: >> >>> Yeah >>> >>> On Sun, Mar 7, 2021 at 12:16 PM Edward Kmett wrote: >>> >>>> I rather like label. +1 from me. >>>> >>>> On Sun, Mar 7, 2021 at 1:25 AM Tom Ellis < >>>> tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk> wrote: >>>> >>>>> On Sun, Mar 07, 2021 at 03:25:16AM +0000, Alexandre Esteves wrote: >>>>> > replay :: MonadCont m => m (m a) >>>>> > replay = callCC $ pure . fix >>>>> > >>>>> > Using this in a do-notation block allows one to bind a name to the >>>>> > sub-block that starts immediately after. >>>>> > I reached for continuations to try to get this behavior for use with >>>>> > recursive flows without disrupting the reading of the main forward >>>>> flow and >>>>> > found how to do it in https://jsdw.me/posts/haskell-cont-monad/ >>>>> under the >>>>> > name "goto". >>>>> > >>>>> > While "goto" is as familiar as a name can be, I feel "replay" more >>>>> > accurately conveys, that you can only 'go back', by stating what >>>>> actually >>>>> > is happening - that a sub-block we're currently evaluating is >>>>> replayed from >>>>> > its beginning. >>>>> >>>>> Looks like a "label" more than a "goto" to me. Would "label" be a >>>>> good name? >>>>> _______________________________________________ >>>>> 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 > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simon.jakobi at googlemail.com Tue Mar 16 23:13:43 2021 From: simon.jakobi at googlemail.com (Simon Jakobi) Date: Wed, 17 Mar 2021 00:13:43 +0100 Subject: Proposal: export more Data.Sequence internals In-Reply-To: References: Message-ID: Hi David, and apologies for the late response! I don't have much to add to this discussion since I'm rather unfamiliar with the Data.Sequence internals and fingertrees in general. Since this code is pretty stable AFAIK, I don't see a problem with exposing it under the PVP. My only suggestion would be to find a slightly better name than Data.Sequence.StableInternal. Something like Data.Sequence.Core perhaps?! Cheers! Simon Am Fr., 5. Feb. 2021 um 22:22 Uhr schrieb David Feuer : > > I'd like containers to export more Data.Sequence internals, and to do > so in a way that allows external users to rely on them. I propose the > following: > > 1. Add a module, Data.FingerTree.IntPlus, abstractly exporting the > finger trees used to represent sequences. These can also be used for > other finger trees with measurements in the (Int, +) monoid. This > would include various basic operations for cons, snoc, and splitting, > with most names the same as for sequences. > 2. Add a module, Data.FingerTree.IntPlus.Unsafe, exporting efficient > mapping/traversing functions that rely on specific preconditions to > maintain the internal fingertree annotation invariant. > 3. Add a module, Data.Sequence.StableInternal, exporting the internal > structure of sequences and also some internal functions that may be > useful elsewhere (I'm particularly interested in the `splitMap` > function and future variants thereof). Unlike the `.Internal` module, > this module would be subject to the package version policy, and would > therefore be more suitable for use by other packages. > > I am very open to suggestions for modifications to the module names. > One option might be to put all the FingerTree.IntPlus stuff in the > Data.Sequence.StableInternal hierarchy, if folks think it should be > buried a bit. > > David From travis.cardwell at extrema.is Sat Mar 27 23:13:26 2021 From: travis.cardwell at extrema.is (Travis Cardwell) Date: Sun, 28 Mar 2021 08:13:26 +0900 Subject: template-haskell 2.17.0.0 not on Hackage Message-ID: Hi, I noticed that template-haskell 2.17.0.0 has not been released to Hackage. One consequence of this is that the Hackage Dependency Monitor does not notify package maintainers of the major release. Releasing the new version on Hackage may prompt more package maintainers to update typed Template Haskell API code so that it works with GHC 9. Regards, Travis From taylor at fausak.me Sun Mar 28 12:12:48 2021 From: taylor at fausak.me (Taylor Fausak) Date: Sun, 28 Mar 2021 08:12:48 -0400 Subject: template-haskell 2.17.0.0 not on Hackage In-Reply-To: References: Message-ID: <51ff9750-ee8a-418a-a0c5-59a744944a2c@www.fastmail.com> This happens all the time: https://github.com/haskell-infra/hackage-trustees/issues/276 On Sat, Mar 27, 2021, at 7:13 PM, Travis Cardwell via Libraries wrote: > Hi, > > I noticed that template-haskell 2.17.0.0 has not been released to > Hackage. One consequence of this is that the Hackage Dependency Monitor > does not notify package maintainers of the major release. Releasing the > new version on Hackage may prompt more package maintainers to update > typed Template Haskell API code so that it works with GHC 9. > > Regards, > > Travis > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > From ekmett at gmail.com Sun Mar 28 14:42:30 2021 From: ekmett at gmail.com (Edward Kmett) Date: Sun, 28 Mar 2021 07:42:30 -0700 Subject: template-haskell 2.17.0.0 not on Hackage In-Reply-To: References: Message-ID: The same situation exists with `base-4.15` and any of the other libraries shipped with ghc 9.0.1. Well, base 4.15 _just_ got put up by Ben, but hasn't had a documentation upload yet. In the past it was always Herbert who did these uploads, IIRC. -Edward On Sat, Mar 27, 2021 at 4:17 PM Travis Cardwell via Libraries < libraries at haskell.org> wrote: > Hi, > > I noticed that template-haskell 2.17.0.0 has not been released to > Hackage. One consequence of this is that the Hackage Dependency Monitor > does not notify package maintainers of the major release. Releasing the > new version on Hackage may prompt more package maintainers to update > typed Template Haskell API code so that it works with GHC 9. > > Regards, > > Travis > _______________________________________________ > 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 carter.schonwald at gmail.com Sun Mar 28 16:17:17 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sun, 28 Mar 2021 12:17:17 -0400 Subject: template-haskell 2.17.0.0 not on Hackage In-Reply-To: References: Message-ID: There’s some work in flight I believe to address this problem going forward but I’ll let those working on it opine On Sun, Mar 28, 2021 at 10:42 AM Edward Kmett wrote: > The same situation exists with `base-4.15` and any of the other libraries > shipped with ghc 9.0.1. > > Well, base 4.15 _just_ got put up by Ben, but hasn't had a documentation > upload yet. > > In the past it was always Herbert who did these uploads, IIRC. > > -Edward > > On Sat, Mar 27, 2021 at 4:17 PM Travis Cardwell via Libraries < > libraries at haskell.org> wrote: > >> Hi, >> >> I noticed that template-haskell 2.17.0.0 has not been released to >> Hackage. One consequence of this is that the Hackage Dependency Monitor >> does not notify package maintainers of the major release. Releasing the >> new version on Hackage may prompt more package maintainers to update >> typed Template Haskell API code so that it works with GHC 9. >> >> Regards, >> >> Travis >> _______________________________________________ >> 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 andreas.abel at ifi.lmu.de Mon Mar 29 06:19:32 2021 From: andreas.abel at ifi.lmu.de (Andreas Abel) Date: Mon, 29 Mar 2021 08:19:32 +0200 Subject: template-haskell 2.17.0.0 not on Hackage In-Reply-To: References: Message-ID: > In the past it was always Herbert who did these uploads, IIRC. Why doesn't the GHC team upload the boot libraries to hackage? Seems like this would naturally be a part of making a GHC release... On 2021-03-28 18:17, Carter Schonwald wrote: > There’s some work in flight I believe to address this problem going > forward but I’ll let those working on it opine > > On Sun, Mar 28, 2021 at 10:42 AM Edward Kmett > wrote: > > The same situation exists with `base-4.15` and any of the other > libraries shipped with ghc 9.0.1. > > Well, base 4.15 _just_ got put up by Ben, but hasn't had a > documentation upload yet. > > In the past it was always Herbert who did these uploads, IIRC. > > -Edward > > On Sat, Mar 27, 2021 at 4:17 PM Travis Cardwell via Libraries > > wrote: > > Hi, > > I noticed that template-haskell 2.17.0.0 has not been released to > Hackage.  One consequence of this is that the Hackage Dependency > Monitor > does not notify package maintainers of the major release. > Releasing the > new version on Hackage may prompt more package maintainers to update > typed Template Haskell API code so that it works with GHC 9. > > Regards, > > Travis > _______________________________________________ > 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 > From simon.jakobi at googlemail.com Mon Mar 29 10:57:43 2021 From: simon.jakobi at googlemail.com (Simon Jakobi) Date: Mon, 29 Mar 2021 12:57:43 +0200 Subject: template-haskell 2.17.0.0 not on Hackage In-Reply-To: References: Message-ID: Am Mo., 29. März 2021 um 08:20 Uhr schrieb Andreas Abel : > Why doesn't the GHC team upload the boot libraries to hackage? > Seems like this would naturally be a part of making a GHC release... Apparently Ben Gamari has integrated the libraries and docs upload into the GHC release process now: https://gitlab.haskell.org/ghc/ghc/-/issues/18216#note_342415 From andreas.abel at ifi.lmu.de Mon Mar 29 15:00:23 2021 From: andreas.abel at ifi.lmu.de (Andreas Abel) Date: Mon, 29 Mar 2021 17:00:23 +0200 Subject: template-haskell 2.17.0.0 not on Hackage In-Reply-To: References: Message-ID: Great! On 2021-03-29 12:57, Simon Jakobi wrote: > Am Mo., 29. März 2021 um 08:20 Uhr schrieb Andreas Abel > : > >> Why doesn't the GHC team upload the boot libraries to hackage? >> Seems like this would naturally be a part of making a GHC release... > > Apparently Ben Gamari has integrated the libraries and docs upload > into the GHC release process now: > https://gitlab.haskell.org/ghc/ghc/-/issues/18216#note_342415 >