From andrew.lelechenko at gmail.com Wed Oct 2 14:10:02 2019 From: andrew.lelechenko at gmail.com (andrew.lelechenko at gmail.com) Date: Wed, 2 Oct 2019 15:10:02 +0100 Subject: Publicly exported pattern synonym for Ratios? In-Reply-To: References: Message-ID: <6F31BA2F-9369-48E4-A2E8-81483FC8206D@gmail.com> Hi, Could you please explain, why numerator and denominator add an extra layer of laziness? Best regards, Andrew > 17 сент. 2019 г., в 15:54, Zemyla написал(а): > >  > Using the numerator and denominator functions in Data.Ratio adds an extra layer of laziness to functions that have to work with Ratios (especially Rationals). I think it'd be convenient if there were a pattern synonym exported from the safe Data.Ratio: > > pattern n :% d <- (n GHC.Ratio.:% d) where > n :% d = n % d > > This way, destructuring is as fast as if you were to import GHC.Ratio directly, but it can't be used to create invalid Ratios. > > The only disadvantage is that using the :% to destructure it requires an Integral constraint on the value, but 99% of the time, the value will be Integer anyway, and even in the remaining 1% you still can't construct a Ratio a without an Integral a constraint in safe code anyway, so it shouldn't matter. > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries From ndospark320 at gmail.com Tue Oct 8 09:08:48 2019 From: ndospark320 at gmail.com (Dannyu NDos) Date: Tue, 8 Oct 2019 18:08:48 +0900 Subject: Add instance Storable Ordering Message-ID: I don't know exact sementics of Storable, but it's addable anyway. instance Storable Ordering where sizeOf _ = sizeOf (undefined ::HTYPE_INT) alignment _ = alignment (undefined ::HTYPE_INT) peekElemOff p i = liftM (`compare` (1::HTYPE_INT)) $ peekElemOff (castPtr p) i pokeElemOff p i x = pokeElemOff (castPtr p ) i (fromIntegral (fromEnum x )::HTYPE_INT) -------------- next part -------------- An HTML attachment was scrubbed... URL: From vamchale at gmail.com Tue Oct 8 14:40:27 2019 From: vamchale at gmail.com (Vanessa McHale) Date: Tue, 8 Oct 2019 09:40:27 -0500 Subject: Add instance Storable Ordering In-Reply-To: References: Message-ID: I would appreciate this too On 10/8/19 4:08 AM, Dannyu NDos wrote: > I don't know exact sementics of Storable, but it's addable anyway. > > instance Storable Ordering where > sizeOf _ = sizeOf (undefined ::HTYPE_INT) > alignment _ = alignment (undefined ::HTYPE_INT) > peekElemOff p i = liftM (`compare` (1::HTYPE_INT)) $ peekElemOff (castPtr p) i > pokeElemOff p i x = pokeElemOff (castPtr p ) i (fromIntegral (fromEnum x > )::HTYPE_INT) > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries -------------- next part -------------- An HTML attachment was scrubbed... URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 659 bytes Desc: OpenPGP digital signature URL: From simon.jakobi at googlemail.com Tue Oct 8 14:56:42 2019 From: simon.jakobi at googlemail.com (Simon Jakobi) Date: Tue, 8 Oct 2019 16:56:42 +0200 Subject: Add instance Storable Ordering In-Reply-To: References: Message-ID: That seems like a good idea! Can you make a feature request at https://gitlab.haskell.org/ghc/ghc/issues and maybe even an merge request? Cheers, Simonx Am Di., 8. Okt. 2019 um 11:09 Uhr schrieb Dannyu NDos : > I don't know exact sementics of Storable, but it's addable anyway. > > instance Storable Ordering where sizeOf _ = sizeOf (undefined ::HTYPE_INT) alignment _ = alignment (undefined ::HTYPE_INT) peekElemOff p i = liftM (`compare` (1::HTYPE_INT)) $ peekElemOff (castPtr p) i pokeElemOff p i x = pokeElemOff (castPtr p ) i (fromIntegral (fromEnum x )::HTYPE_INT) > > _______________________________________________ > 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 svenpanne at gmail.com Tue Oct 8 15:33:28 2019 From: svenpanne at gmail.com (Sven Panne) Date: Tue, 8 Oct 2019 17:33:28 +0200 Subject: Add instance Storable Ordering In-Reply-To: References: Message-ID: Am Di., 8. Okt. 2019 um 16:57 Uhr schrieb Simon Jakobi via Libraries < libraries at haskell.org>: > That seems like a good idea! [...] > Looks OK, but let's use toEnum in peekElemOff: instance Storable Ordering where sizeOf _ = sizeOf (undefined :: CInt) alignment _ = alignment (undefined :: CInt) peekElemOff p i = toEnum . fromIntegral <$> peekElemOff (castPtr p :: Ptr CInt) i pokeElemOff p i = pokeElemOff (castPtr p :: Ptr CInt) i . fromIntegral . fromEnum This is more symmetrical with pokeElemOff and less obfuscated. Note that the instance works for every Enum, so if there are more cases like Ordering, it might be worth to abstract that out. -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Tue Oct 8 15:38:45 2019 From: david.feuer at gmail.com (David Feuer) Date: Tue, 8 Oct 2019 11:38:45 -0400 Subject: Add instance Storable Ordering In-Reply-To: References: Message-ID: newtype WrappedEnum a = WrappedEnum a instance Enum a => Storable (WrappedEnum a) where ... deriving via (WrappedEnum Ordering) instance Storable Ordering On Tue, Oct 8, 2019, 11:34 AM Sven Panne wrote: > Am Di., 8. Okt. 2019 um 16:57 Uhr schrieb Simon Jakobi via Libraries < > libraries at haskell.org>: > >> That seems like a good idea! [...] >> > > Looks OK, but let's use toEnum in peekElemOff: > > instance Storable Ordering where > sizeOf _ = sizeOf (undefined :: CInt) > alignment _ = alignment (undefined :: CInt) > peekElemOff p i = toEnum . fromIntegral <$> peekElemOff (castPtr p :: > Ptr CInt) i > pokeElemOff p i = pokeElemOff (castPtr p :: Ptr CInt) i . fromIntegral > . fromEnum > > This is more symmetrical with pokeElemOff and less obfuscated. Note that > the instance works for every Enum, so if there are more cases like > Ordering, it might be worth to abstract that out. > _______________________________________________ > 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 sylvain at haskus.fr Tue Oct 8 15:42:06 2019 From: sylvain at haskus.fr (Sylvain Henry) Date: Tue, 8 Oct 2019 17:42:06 +0200 Subject: Add instance Storable Ordering In-Reply-To: References: Message-ID: <35c6728f-8152-5b95-a260-11c9d4fb1622@haskus.fr> A `Word8` would be enough instead of 4 or 8 bytes for `CInt`. On 08/10/2019 17:33, Sven Panne wrote: > Am Di., 8. Okt. 2019 um 16:57 Uhr schrieb Simon Jakobi via Libraries > >: > > That seems like a good idea! [...] > > > Looks OK, but let's use toEnum in peekElemOff: > >   instance Storable Ordering where >     sizeOf _ = sizeOf (undefined :: CInt) >     alignment _ = alignment (undefined :: CInt) >     peekElemOff p i = toEnum . fromIntegral <$> peekElemOff (castPtr p > :: Ptr CInt) i >     pokeElemOff p i = pokeElemOff (castPtr p :: Ptr CInt) i . > fromIntegral . fromEnum > > This is more symmetrical with pokeElemOff and less obfuscated. Note > that the instance works for every Enum, so if there are more cases > like Ordering, it might be worth to abstract that out. > > _______________________________________________ > 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 Tue Oct 8 15:42:38 2019 From: david.feuer at gmail.com (David Feuer) Date: Tue, 8 Oct 2019 11:42:38 -0400 Subject: Add instance Storable Ordering In-Reply-To: References: Message-ID: But shouldn't Ordering have the alignment and size of Int8 rather than that of Int? At least in principle? On Tue, Oct 8, 2019, 11:38 AM David Feuer wrote: > newtype WrappedEnum a = WrappedEnum a > > instance Enum a => Storable (WrappedEnum a) where > ... > > deriving via (WrappedEnum Ordering) > instance Storable Ordering > > On Tue, Oct 8, 2019, 11:34 AM Sven Panne wrote: > >> Am Di., 8. Okt. 2019 um 16:57 Uhr schrieb Simon Jakobi via Libraries < >> libraries at haskell.org>: >> >>> That seems like a good idea! [...] >>> >> >> Looks OK, but let's use toEnum in peekElemOff: >> >> instance Storable Ordering where >> sizeOf _ = sizeOf (undefined :: CInt) >> alignment _ = alignment (undefined :: CInt) >> peekElemOff p i = toEnum . fromIntegral <$> peekElemOff (castPtr p :: >> Ptr CInt) i >> pokeElemOff p i = pokeElemOff (castPtr p :: Ptr CInt) i . >> fromIntegral . fromEnum >> >> This is more symmetrical with pokeElemOff and less obfuscated. Note that >> the instance works for every Enum, so if there are more cases like >> Ordering, it might be worth to abstract that out. >> _______________________________________________ >> 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 lemming at henning-thielemann.de Tue Oct 8 15:49:04 2019 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Tue, 8 Oct 2019 17:49:04 +0200 (CEST) Subject: Add instance Storable Ordering In-Reply-To: References: Message-ID: On Tue, 8 Oct 2019, David Feuer wrote: > newtype WrappedEnum a = WrappedEnum a > instance Enum a => Storable (WrappedEnum a) where >   ... That's almost what I recently defined in a custom package: https://hub.darcs.net/thielema/storable-enum/browse/src/Data/Enum/Storable.hs But I also let the user choose the underlying machine type. From david.feuer at gmail.com Tue Oct 8 16:12:17 2019 From: david.feuer at gmail.com (David Feuer) Date: Tue, 8 Oct 2019 12:12:17 -0400 Subject: Add instance Storable Ordering In-Reply-To: References: Message-ID: Yes, yours is better, but I'd go with Enum on both ends rather than relying on rewrite rules to make sure fromIntegral isn't slow. On Tue, Oct 8, 2019, 11:49 AM Henning Thielemann < lemming at henning-thielemann.de> wrote: > > On Tue, 8 Oct 2019, David Feuer wrote: > > > newtype WrappedEnum a = WrappedEnum a > > instance Enum a => Storable (WrappedEnum a) where > > ... > > That's almost what I recently defined in a custom package: > > https://hub.darcs.net/thielema/storable-enum/browse/src/Data/Enum/Storable.hs > > But I also let the user choose the underlying machine type. -------------- next part -------------- An HTML attachment was scrubbed... URL: From ndospark320 at gmail.com Mon Oct 14 04:55:19 2019 From: ndospark320 at gmail.com (Dannyu NDos) Date: Mon, 14 Oct 2019 13:55:19 +0900 Subject: Is join useful for every monad? Message-ID: join is surely useful for Maybe and []. But IO (IO a)? ReadPrec (ReadPrec a)? ST s (ST s a)? When the heck could I encounter such types? -------------- next part -------------- An HTML attachment was scrubbed... URL: From kovanikov at gmail.com Mon Oct 14 05:41:59 2019 From: kovanikov at gmail.com (Dmitrii Kovanikov) Date: Mon, 14 Oct 2019 08:41:59 +0300 Subject: Is join useful for every monad? In-Reply-To: References: Message-ID: Data types like `IO (IO a)` are useful and their usage is described in the following blog post: * http://www.haskellforall.com/2018/02/the-wizard-monoid.html One function from the example uses `join` directly: runWizard :: IO (IO a) -> IO a runWizard = join On Mon, Oct 14, 2019 at 7:55 AM Dannyu NDos wrote: > join is surely useful for Maybe and []. > > But IO (IO a)? ReadPrec (ReadPrec a)? ST s (ST s a)? When the heck could I > encounter such types? > _______________________________________________ > 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 godzbanebane at gmail.com Mon Oct 14 06:46:40 2019 From: godzbanebane at gmail.com (Georgi Lyubenov) Date: Mon, 14 Oct 2019 09:46:40 +0300 Subject: Is join useful for every monad? In-Reply-To: References: Message-ID: Often you encounter functions that look weird at a first glance but turn out to be *exactly* what you need to implement something intuitively "more useful". Apart from Dmitrii's example showing some direct usage, I think this is such one case, as it allows you to implement (>>=) ma f = join (fmap f ma) Other examples (subjectively of course) of such things are (<*>) which allows you to implement liftA{2,3,..} and mfix, which allows you to have recursive bindings in a do block. ======= Georgi -------------- next part -------------- An HTML attachment was scrubbed... URL: From lemming at henning-thielemann.de Mon Oct 14 06:58:27 2019 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Mon, 14 Oct 2019 08:58:27 +0200 (CEST) Subject: Is join useful for every monad? In-Reply-To: References: Message-ID: On Mon, 14 Oct 2019, Georgi Lyubenov wrote: > Other examples (subjectively of course) of such things are (<*>) which > allows you to implement liftA{2,3,..} and mfix, which allows you to have > recursive bindings in a do block. Other example: We have liftM2 :: (a -> b -> c) -> m a -> m b -> m c but what can we do, if we need: liftM2' :: (a -> b -> m c) -> m a -> m b -> m c ? We could just do: join $ liftM2 f ma mb From ndospark320 at gmail.com Mon Oct 14 08:15:27 2019 From: ndospark320 at gmail.com (Dannyu NDos) Date: Mon, 14 Oct 2019 17:15:27 +0900 Subject: Is join useful for every monad? In-Reply-To: References: Message-ID: Welp. So IO (IO a) is a thing. Will I ever encounter ReadPrec (ReadPrec a)? 2019년 10월 14일 (월) 14:42, Dmitrii Kovanikov 님이 작성: > Data types like `IO (IO a)` are useful and their usage is described in the > following blog post: > > * http://www.haskellforall.com/2018/02/the-wizard-monoid.html > > One function from the example uses `join` directly: > > runWizard :: IO (IO a) -> IO a > runWizard = join > > On Mon, Oct 14, 2019 at 7:55 AM Dannyu NDos wrote: > >> join is surely useful for Maybe and []. >> >> But IO (IO a)? ReadPrec (ReadPrec a)? ST s (ST s a)? When the heck could >> I encounter such types? >> _______________________________________________ >> 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 godzbanebane at gmail.com Mon Oct 14 08:36:46 2019 From: godzbanebane at gmail.com (Georgi Lyubenov) Date: Mon, 14 Oct 2019 11:36:46 +0300 Subject: Is join useful for every monad? In-Reply-To: References: Message-ID: In general, if you want to *dynamically generate* actions depending on the result of an earlier action you will always encounter join/(>>=). For example (with ReadPrec/Parser): I want to first parse a character, and then parse the same character two more times. numberAndThenThatManyAs = join (fmap (\c -> satisfy (==c) *> satisfy (==c)) char) Of note: * The example is contrived for simplicity's sake, but you do really need a Monad (and hence join) to perform stuff like this in general. A more practical example would be parsing command-line options that depend on previous options. * Obviously it's way more humane to write this with do-syntax. (or (>>=) or something) - do { c <- char; satisfy (==c); satisfy (==c) } * I'm not actually sure whether you need a Monad in this situation, maybe you could get away with just selectives ======= Georgi -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Mon Oct 14 19:45:42 2019 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Mon, 14 Oct 2019 15:45:42 -0400 Subject: Is join useful for every monad? In-Reply-To: References: Message-ID: Join actually also comes up in compiler engineering! Most normalized compiler reps: notably anf and cps, have a sort of flatness condition where you can’t have nested subexpressions (aka in many cases in strict languages this is where evaluation order becomes explicit ) and the join operation corresponds to a step in the flattening process for nested expression syntax when you do compiler transformations in this setting. This is in fact exactly why it’s pretty brutal to write the monad for an anf or cps syntax , you’re essentially specifying subexpression evaluation order for all pairs of syntax constructors! And while join is not at the moment in the Monad typeclass because of newtype stuff, writing these monad instances is way saner in terms of the join operators rather than in terms of bind. At least in my biased perspective ;) On Mon, Oct 14, 2019 at 4:37 AM Georgi Lyubenov wrote: > In general, if you want to *dynamically generate* actions depending on > the result of an earlier action you will always encounter join/(>>=). > For example (with ReadPrec/Parser): > I want to first parse a character, and then parse the same character two > more times. > numberAndThenThatManyAs = join (fmap (\c -> satisfy (==c) *> satisfy > (==c)) char) > > Of note: > * The example is contrived for simplicity's sake, but you do really need a > Monad (and hence join) to perform stuff like this in general. A more > practical example would be parsing command-line options that depend on > previous options. > * Obviously it's way more humane to write this with do-syntax. (or (>>=) > or something) - do { c <- char; satisfy (==c); satisfy (==c) } > * I'm not actually sure whether you need a Monad in this situation, maybe > you could get away with just selectives > > > ======= > > Georgi > _______________________________________________ > 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 Oct 14 21:07:00 2019 From: ekmett at gmail.com (Edward Kmett) Date: Mon, 14 Oct 2019 14:07:00 -0700 Subject: Is join useful for every monad? In-Reply-To: References: Message-ID: I use join a fair bit in IO! Consider something where you to dig in an IORef, and compute what to do next. join $ atomicModifyIORef someRef $ \case Foo y -> (Bar, doSomethingWith y) x -> (x, return ()) I can't run IO actions inside the atomicModifyIORef but I can give one back as the "extra" result from atomicModifyIORef, and do something I precomputed. With the join there this collapses into one line, and I can often avoid a pair of redundant case statements. Other patterns are for common patterns that _almost_ look like applicative usage, like do x <- foo y <- bar baz x y which can be expressed via join $ baz <$> foo <*> bar without naming all the intermediaries, whether this is good or not depends on how much you like giving transient names to things. -Edward On Mon, Oct 14, 2019 at 12:46 PM Carter Schonwald < carter.schonwald at gmail.com> wrote: > Join actually also comes up in compiler engineering! > > Most normalized compiler reps: notably anf and cps, have a sort of > flatness condition where you can’t have nested subexpressions (aka in many > cases in strict languages this is where evaluation order becomes explicit ) > and the join operation corresponds to a step in the flattening process for > nested expression syntax when you do compiler transformations in this > setting. > > This is in fact exactly why it’s pretty brutal to write the monad for an > anf or cps syntax , you’re essentially specifying subexpression evaluation > order for all pairs of syntax constructors! > > And while join is not at the moment in the Monad typeclass because of > newtype stuff, writing these monad instances is way saner in terms of the > join operators rather than in terms of bind. At least in my biased > perspective ;) > > On Mon, Oct 14, 2019 at 4:37 AM Georgi Lyubenov > wrote: > >> In general, if you want to *dynamically generate* actions depending on >> the result of an earlier action you will always encounter join/(>>=). >> For example (with ReadPrec/Parser): >> I want to first parse a character, and then parse the same character two >> more times. >> numberAndThenThatManyAs = join (fmap (\c -> satisfy (==c) *> satisfy >> (==c)) char) >> >> Of note: >> * The example is contrived for simplicity's sake, but you do really need >> a Monad (and hence join) to perform stuff like this in general. A more >> practical example would be parsing command-line options that depend on >> previous options. >> * Obviously it's way more humane to write this with do-syntax. (or (>>=) >> or something) - do { c <- char; satisfy (==c); satisfy (==c) } >> * I'm not actually sure whether you need a Monad in this situation, maybe >> you could get away with just selectives >> >> >> ======= >> >> Georgi >> _______________________________________________ >> 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 vamchale at gmail.com Mon Oct 14 21:24:08 2019 From: vamchale at gmail.com (Vanessa McHale) Date: Mon, 14 Oct 2019 16:24:08 -0500 Subject: Is join useful for every monad? In-Reply-To: References: Message-ID: <36ff3ed4-cd0f-57b1-541c-496688763c8c@gmail.com> You can use the (-> c) instance in fun ways both :: (a -> b) -> (a, a) -> (b, b) both = join (***) dup :: a -> (a, a) dup = join (,) between `join` (char '"') On 10/13/19 11:55 PM, Dannyu NDos wrote: > join is surely useful for Maybe and []. > > But IO (IO a)? ReadPrec (ReadPrec a)? ST s (ST s a)? When the heck > could I encounter such types? > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries -------------- next part -------------- An HTML attachment was scrubbed... URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 659 bytes Desc: OpenPGP digital signature URL: From oleg.grenrus at iki.fi Thu Oct 17 14:42:54 2019 From: oleg.grenrus at iki.fi (Oleg Grenrus) Date: Thu, 17 Oct 2019 17:42:54 +0300 Subject: Add Data.Foldable1 to base Message-ID: <431b2ab2-d7df-d7f2-602d-15bcebdd36ed@iki.fi> I propose adding `Foldable1` type-class into `base1`. Add Foldable1 ============= Motivation ---------- It's regularly asked whether `Foldable1` could be added to `base` (e.g. on reddit[^ref1], there're also GHC issue[^ref2] and old phabricator diff[^ref3]) Also there's work towards non-empty maps and sets[^ref4], which would benefit from `Foldable1`. As commented on reddit, `Foldable1` could be added without any pain to the `base` as it's pure addition - no modifications needed in existing modules. [^ref1]: https://www.reddit.com/r/haskell/comments/6d0vgt/could_we_have_foldable1_and_traversable1_in_base/ [^ref2]: https://gitlab.haskell.org/ghc/ghc/issues/13573 [^ref3]: https://phabricator.haskell.org/D4812 [^ref4]: https://github.com/haskell/containers/pull/616 Change ------ The change exist as merge request[^ref4] on gitlab.haskell.org. Importantly, this change **doesn't change** anything in other modules of `base`, except of adding a `Foldable` instance to `Data.Complex`. In particular, `foldl1` and `foldr1` in `Data.Foldable` remain partial, etc. My version of `Foldable1` class is big, so I'll comment the motivation for each member ```haskell class Foldable t => Foldable1 t where     {-# MINIMAL foldMap1 | toNonEmpty | foldr1map #-}     -- the defining member, like foldMap but only asking for Semigroup     foldMap1 :: Semigroup m => (a -> m) -> t a -> m     fold1 :: Semigroup m => t m -> m#     -- strict foldMap1, cf foldMap'     foldMap1' :: Semigroup m => (a -> m) -> t a -> m     -- analogue of toList     toNonEmpty :: t a -> NonEmpty a     -- left&right, strict&non-strict folds     foldr1  :: (a -> a -> a) -> t a -> a     foldr1' :: (a -> a -> a) -> t a -> a     foldl1  :: (a -> a -> a) -> t a -> a     foldl1' :: (a -> a -> a) -> t a -> a     -- these can have efficient implementation for NonEmptySet     maximum1 :: forall a. Ord a => t a -> a     minimum1 :: forall a. Ord a => t a -> a     -- head1 have efficient implementation for NonEmpty and Tree     -- last1 for symmetry     head1 :: t a -> a     last1 :: t a -> a     -- fold variants with premap.     -- Without this map, we cannot implement foldl using foldr etc.     foldr1map  :: (a -> b) -> (b -> b -> b) -> t a -> b     foldl1'map :: (a -> b) -> (b -> b -> b) -> t a -> b     foldl1map  :: (a -> b) -> (b -> b -> b) -> t a -> b     foldr1'map :: (a -> b) -> (b -> b -> b) -> t a -> b ``` The merge request also adds instances for everything non-empty in `base`. I propose the `Data.Foldable1` as the module name. `semigroupoids`[^ref6] uses `Data.Semigroup.Foldable`, but it's confusing; and using different name could help migration. The module contains five top-level functions, which should be self-explanatory: ```haskell intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a ``` This is less than in `Data.Semigroup.Foldable`[^ref9], as without `Apply` they don't make sense. For example: ```haskell -- needs Apply, not in Data.Foldable1 traverse1_ :: (Foldable1 t, Apply f) => (a -> f b) -> t a -> f () ``` And if we relax `Apply` to `Applicative`, we get `traverse_`.   [^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 [^ref9]: https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-Foldable-Class.html [^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 Compatibility & migration ------------------------- I drafted a compatibility package `foldable1` (github[^ref6], haddocks[^ref7]), which I hope could be maintained under github.com/haskell organization. I can act as a maintainer, with a hope that there won't be a lot of changes happening in `Data.Foldable1`. To my surprise, there's already a package with this name on Hackage[^ref8] by M Farkas-Dyck (cc'd). I hope they would donate the name to Haskell.org / CLC; the package won't have any other good use when `Data.Foldable1` is in `base`, then act as a compat package. `Data.Foldable1` contains also instances for `Lift`, `Backwards` and `Reverse` data types from `transformers`. Perfectly, the `transformers` bundled with GHC with this change would implement the instances as well. This change should propage to `transformers-compat` too. Similarly, `containers` would have an instance for `Tree` (and non-empty `Set` and `Map` when they are added). `semigroupoids` would need a bit of work, to depend on `foldable1`, yet the public changes can be kept quite minimal. I don't think that anything in reverse dependencies of `lens` will be broken by this change, if "new" `Foldable1` is re-exported from `semigroupoids`' `Data.Semigroup.Foldable`[^ref9] Other "compat" packages -- like `tagged`, `bifunctors` -- have to be dealt with case by case. For example whether they should depend on `foldable1` or other way around. [^ref6]: https://github.com/phadej/foldable1 [^ref7]: https://oleg.fi/haddocks/foldable1/ [^ref8]: https://hackage.haskell.org/package/foldable1 [^ref9]: https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-Foldable-Class.html Unresolved questions -------------------- - Should we add `Bifoldable1` too. That should be trivial. - GHC-8.10 freeze is quite soon, is targeting GHC-8.12/base-4.15 more realistic? -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 833 bytes Desc: OpenPGP digital signature URL: From kovanikov at gmail.com Thu Oct 17 16:26:27 2019 From: kovanikov at gmail.com (Dmitrii Kovanikov) Date: Thu, 17 Oct 2019 19:26:27 +0300 Subject: Add Data.Foldable1 to base In-Reply-To: <431b2ab2-d7df-d7f2-602d-15bcebdd36ed@iki.fi> References: <431b2ab2-d7df-d7f2-602d-15bcebdd36ed@iki.fi> Message-ID: I support this change and I would love to have `Foldable1` in the `base` as well. I find it so useful that we even have it in our alternative prelude called `relude`: * https://github.com/kowainik/relude/blob/45e112677c6e23759e4742cb695eed20a2cb964a/src/Relude/Extra/Foldable1.hs I would love to reexport this typeclass by default from `base` instead of maintaining one more `Extra.*` module in `relude`. However, at this point, I like the implementation in `relude` more because: 1. It has usage examples tested with `doctest`. 2. Implements (almost) each function manually and uses {-# INLINE #-} pragmas for better performance. 3. In the next release, we're also going to add custom type errors of `Foldable1` instances for data types like ordinary lists to improve UX. These improvements don't rely on anything `relude`-specific and can be done in `base` as well. On Thu, Oct 17, 2019 at 5:43 PM Oleg Grenrus wrote: > I propose adding `Foldable1` type-class into `base1`. > > Add Foldable1 > ============= > > > Motivation > ---------- > > It's regularly asked whether `Foldable1` could be added to `base` > (e.g. on reddit[^ref1], there're also GHC issue[^ref2] and old > phabricator diff[^ref3]) > Also there's work towards non-empty maps and sets[^ref4], > which would benefit from `Foldable1`. > > As commented on reddit, `Foldable1` could be added without any pain > to the `base` as it's pure addition - no modifications needed in > existing modules. > > [^ref1]: > > https://www.reddit.com/r/haskell/comments/6d0vgt/could_we_have_foldable1_and_traversable1_in_base/ > [^ref2]: https://gitlab.haskell.org/ghc/ghc/issues/13573 > [^ref3]: https://phabricator.haskell.org/D4812 > [^ref4]: https://github.com/haskell/containers/pull/616 > > Change > ------ > > The change exist as merge request[^ref4] on gitlab.haskell.org. > > Importantly, this change **doesn't change** anything in other modules > of `base`, except of adding a `Foldable` instance to `Data.Complex`. > In particular, `foldl1` and `foldr1` in `Data.Foldable` remain partial, > etc. > > My version of `Foldable1` class is big, so I'll comment the motivation > for each member > > ```haskell > class Foldable t => Foldable1 t where > {-# MINIMAL foldMap1 | toNonEmpty | foldr1map #-} > > -- the defining member, like foldMap but only asking for Semigroup > foldMap1 :: Semigroup m => (a -> m) -> t a -> m > > fold1 :: Semigroup m => t m -> m# > > -- strict foldMap1, cf foldMap' > foldMap1' :: Semigroup m => (a -> m) -> t a -> m > > -- analogue of toList > toNonEmpty :: t a -> NonEmpty a > > -- left&right, strict&non-strict folds > foldr1 :: (a -> a -> a) -> t a -> a > foldr1' :: (a -> a -> a) -> t a -> a > foldl1 :: (a -> a -> a) -> t a -> a > foldl1' :: (a -> a -> a) -> t a -> a > > -- these can have efficient implementation for NonEmptySet > maximum1 :: forall a. Ord a => t a -> a > minimum1 :: forall a. Ord a => t a -> a > > -- head1 have efficient implementation for NonEmpty and Tree > -- last1 for symmetry > head1 :: t a -> a > last1 :: t a -> a > > -- fold variants with premap. > -- Without this map, we cannot implement foldl using foldr etc. > foldr1map :: (a -> b) -> (b -> b -> b) -> t a -> b > foldl1'map :: (a -> b) -> (b -> b -> b) -> t a -> b > foldl1map :: (a -> b) -> (b -> b -> b) -> t a -> b > foldr1'map :: (a -> b) -> (b -> b -> b) -> t a -> b > ``` > > The merge request also adds instances for everything non-empty in `base`. > > I propose the `Data.Foldable1` as the module name. > `semigroupoids`[^ref6] uses `Data.Semigroup.Foldable`, > but it's confusing; and using different name could help migration. > > The module contains five top-level functions, which should > be self-explanatory: > > ```haskell > intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m > > foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a > foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a > > maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a > minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a > ``` > > This is less than in `Data.Semigroup.Foldable`[^ref9], > as without `Apply` they don't make sense. > For example: > > ```haskell > -- needs Apply, not in Data.Foldable1 > traverse1_ :: (Foldable1 t, Apply f) => (a -> f b) -> t a -> f () > ``` > > And if we relax `Apply` to `Applicative`, we get `traverse_`. > > [^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 > [^ref9]: > > https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-Foldable-Class.html > > [^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 > > Compatibility & migration > ------------------------- > > I drafted a compatibility package `foldable1` (github[^ref6], > haddocks[^ref7]), > which I hope could be maintained under github.com/haskell organization. > I can act as a maintainer, with a hope that there won't be a lot > of changes happening in `Data.Foldable1`. > > To my surprise, there's already a package with this name on > Hackage[^ref8] by > M Farkas-Dyck (cc'd). I hope they would donate the name to Haskell.org / > CLC; > the package won't have any other good use when `Data.Foldable1` is in > `base`, > then act as a compat package. > > `Data.Foldable1` contains also instances for `Lift`, `Backwards` and > `Reverse` > data types from `transformers`. Perfectly, the `transformers` bundled > with GHC with this change would implement the instances as well. > This change should propage to `transformers-compat` too. > > Similarly, `containers` would have an instance for `Tree` (and non-empty > `Set` and `Map` when they are added). > > `semigroupoids` would need a bit of work, to depend on `foldable1`, > yet the public changes can be kept quite minimal. > I don't think that anything in reverse dependencies of `lens` will be > broken by > this change, if "new" `Foldable1` is re-exported from `semigroupoids`' > `Data.Semigroup.Foldable`[^ref9] > > Other "compat" packages -- like `tagged`, `bifunctors` -- have to be > dealt with > case by case. For example whether they should depend on `foldable1` or > other way around. > > [^ref6]: https://github.com/phadej/foldable1 > [^ref7]: https://oleg.fi/haddocks/foldable1/ > [^ref8]: https://hackage.haskell.org/package/foldable1 > [^ref9]: > > https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-Foldable-Class.html > > Unresolved questions > -------------------- > > - Should we add `Bifoldable1` too. That should be trivial. > - GHC-8.10 freeze is quite soon, is targeting GHC-8.12/base-4.15 more > realistic? > > > _______________________________________________ > 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 oleg.grenrus at iki.fi Thu Oct 17 17:32:32 2019 From: oleg.grenrus at iki.fi (Oleg Grenrus) Date: Thu, 17 Oct 2019 20:32:32 +0300 Subject: Add Data.Foldable1 to base In-Reply-To: References: <431b2ab2-d7df-d7f2-602d-15bcebdd36ed@iki.fi> Message-ID: <8584c3da-075a-b61a-cbd5-737bd0658755@iki.fi> Thanks for the support and comments Dmitrii. 1. I can add usage examples, that's no brainer. 2. Yes, implementing selected members manually can help, that's the point of having a lot of members, and not bare foldMap1.    - Yet I hope that is not a blocker    - This may be motivated by GHC.Generics, but I don't see instances in `relude`?    -  Non trivial manual implementations should be backed up by some benchmark that shows it's worth having more code (which one have test, that it's coherent!).        - That said, I'll add more manual members when I have test setup ready. E.g. `head1 :: Compose f g a -> a`, and for `Product` (and Generics variants).    - {-# INLINE #-} everywhere doesn't imply more performance.    - The `foldable1` package is simple enough playground to add benchmarks, there are some already. 3. There is no prior art of disallowing instances with TypeErrors in `base`, so I'm wont consider it here either.    - That's worth an own separate library proposal - Oleg On 17.10.2019 19.26, Dmitrii Kovanikov wrote: > I support this change and I would love to have `Foldable1` in the > `base` as well. I find it so useful that we even have it in our > alternative prelude called `relude`: > > * > https://github.com/kowainik/relude/blob/45e112677c6e23759e4742cb695eed20a2cb964a/src/Relude/Extra/Foldable1.hs > > I would love to reexport this typeclass by default from `base` instead > of maintaining one more `Extra.*` module in `relude`. However, at this > point, I like the implementation in `relude` more because: > > 1. It has usage examples tested with `doctest`. > 2. Implements (almost) each function manually and uses {-# INLINE #-} > pragmas for better performance. > 3. In the next release, we're also going to add custom type errors of > `Foldable1` instances for data types like ordinary lists to improve UX. > > These improvements don't rely on anything `relude`-specific and can be > done in `base` as well. > > On Thu, Oct 17, 2019 at 5:43 PM Oleg Grenrus > wrote: > > I propose adding `Foldable1` type-class into `base1`. > > Add Foldable1 > ============= > > > Motivation > ---------- > > It's regularly asked whether `Foldable1` could be added to `base` > (e.g. on reddit[^ref1], there're also GHC issue[^ref2] and old > phabricator diff[^ref3]) > Also there's work towards non-empty maps and sets[^ref4], > which would benefit from `Foldable1`. > > As commented on reddit, `Foldable1` could be added without any pain > to the `base` as it's pure addition - no modifications needed in > existing modules. > > [^ref1]: > https://www.reddit.com/r/haskell/comments/6d0vgt/could_we_have_foldable1_and_traversable1_in_base/ > [^ref2]: https://gitlab.haskell.org/ghc/ghc/issues/13573 > [^ref3]: https://phabricator.haskell.org/D4812 > [^ref4]: https://github.com/haskell/containers/pull/616 > > Change > ------ > > The change exist as merge request[^ref4] on gitlab.haskell.org > . > > Importantly, this change **doesn't change** anything in other modules > of `base`, except of adding a `Foldable` instance to `Data.Complex`. > In particular, `foldl1` and `foldr1` in `Data.Foldable` remain > partial, etc. > > My version of `Foldable1` class is big, so I'll comment the motivation > for each member > > ```haskell > class Foldable t => Foldable1 t where >     {-# MINIMAL foldMap1 | toNonEmpty | foldr1map #-} > >     -- the defining member, like foldMap but only asking for Semigroup >     foldMap1 :: Semigroup m => (a -> m) -> t a -> m > >     fold1 :: Semigroup m => t m -> m# > >     -- strict foldMap1, cf foldMap' >     foldMap1' :: Semigroup m => (a -> m) -> t a -> m > >     -- analogue of toList >     toNonEmpty :: t a -> NonEmpty a > >     -- left&right, strict&non-strict folds >     foldr1  :: (a -> a -> a) -> t a -> a >     foldr1' :: (a -> a -> a) -> t a -> a >     foldl1  :: (a -> a -> a) -> t a -> a >     foldl1' :: (a -> a -> a) -> t a -> a > >     -- these can have efficient implementation for NonEmptySet >     maximum1 :: forall a. Ord a => t a -> a >     minimum1 :: forall a. Ord a => t a -> a > >     -- head1 have efficient implementation for NonEmpty and Tree >     -- last1 for symmetry >     head1 :: t a -> a >     last1 :: t a -> a > >     -- fold variants with premap. >     -- Without this map, we cannot implement foldl using foldr etc. >     foldr1map  :: (a -> b) -> (b -> b -> b) -> t a -> b >     foldl1'map :: (a -> b) -> (b -> b -> b) -> t a -> b >     foldl1map  :: (a -> b) -> (b -> b -> b) -> t a -> b >     foldr1'map :: (a -> b) -> (b -> b -> b) -> t a -> b > ``` > > The merge request also adds instances for everything non-empty in > `base`. > > I propose the `Data.Foldable1` as the module name. > `semigroupoids`[^ref6] uses `Data.Semigroup.Foldable`, > but it's confusing; and using different name could help migration. > > The module contains five top-level functions, which should > be self-explanatory: > > ```haskell > intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m > > foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a > foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a > > maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a > minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a > ``` > > This is less than in `Data.Semigroup.Foldable`[^ref9], > as without `Apply` they don't make sense. > For example: > > ```haskell > -- needs Apply, not in Data.Foldable1 > traverse1_ :: (Foldable1 t, Apply f) => (a -> f b) -> t a -> f () > ``` > > And if we relax `Apply` to `Applicative`, we get `traverse_`. > > [^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 > [^ref9]: > https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-Foldable-Class.html > > [^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 > > Compatibility & migration > ------------------------- > > I drafted a compatibility package `foldable1` (github[^ref6], > haddocks[^ref7]), > which I hope could be maintained under github.com/haskell > organization. > I can act as a maintainer, with a hope that there won't be a lot > of changes happening in `Data.Foldable1`. > > To my surprise, there's already a package with this name on > Hackage[^ref8] by > M Farkas-Dyck (cc'd). I hope they would donate the name to > Haskell.org / > CLC; > the package won't have any other good use when `Data.Foldable1` is in > `base`, > then act as a compat package. > > `Data.Foldable1` contains also instances for `Lift`, `Backwards` and > `Reverse` > data types from `transformers`. Perfectly, the `transformers` bundled > with GHC with this change would implement the instances as well. > This change should propage to `transformers-compat` too. > > Similarly, `containers` would have an instance for `Tree` (and > non-empty > `Set` and `Map` when they are added). > > `semigroupoids` would need a bit of work, to depend on `foldable1`, > yet the public changes can be kept quite minimal. > I don't think that anything in reverse dependencies of `lens` will be > broken by > this change, if "new" `Foldable1` is re-exported from `semigroupoids`' > `Data.Semigroup.Foldable`[^ref9] > > Other "compat" packages -- like `tagged`, `bifunctors` -- have to be > dealt with > case by case. For example whether they should depend on `foldable1` or > other way around. > > [^ref6]: https://github.com/phadej/foldable1 > [^ref7]: https://oleg.fi/haddocks/foldable1/ > [^ref8]: https://hackage.haskell.org/package/foldable1 > [^ref9]: > https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-Foldable-Class.html > > Unresolved questions > -------------------- > > - Should we add `Bifoldable1` too. That should be trivial. > - GHC-8.10 freeze is quite soon, is targeting GHC-8.12/base-4.15 more > realistic? > > > _______________________________________________ > 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 strake888 at gmail.com Thu Oct 17 21:29:52 2019 From: strake888 at gmail.com (Matthew Farkas-Dyck) Date: Thu, 17 Oct 2019 13:29:52 -0800 Subject: Add Data.Foldable1 to base In-Reply-To: <431b2ab2-d7df-d7f2-602d-15bcebdd36ed@iki.fi> References: <431b2ab2-d7df-d7f2-602d-15bcebdd36ed@iki.fi> Message-ID: Yes, i am willing to donate the name "foldable1" once `Foldable1` is in "base". From andrew.thaddeus at gmail.com Fri Oct 18 00:03:21 2019 From: andrew.thaddeus at gmail.com (Andrew Martin) Date: Thu, 17 Oct 2019 20:03:21 -0400 Subject: Add Data.Foldable1 to base In-Reply-To: <431b2ab2-d7df-d7f2-602d-15bcebdd36ed@iki.fi> References: <431b2ab2-d7df-d7f2-602d-15bcebdd36ed@iki.fi> Message-ID: While I want this abstraction in base, I don’t want it there yet. There is an open issue on semigroupoids about renaming everything: https://github.com/ekmett/semigroupoids/issues/26 This needs to be handled before the abstraction is brought into base. Also, foldr1 is awful in common situations. See https://github.com/ekmett/semigroupoids/issues/77 The problem is that refinements of this abstraction seem to have stalled in semigroupoids, but these are desperately needed before the abstraction is brought into base. Sent from my iPhone > On Oct 17, 2019, at 10:42 AM, Oleg Grenrus wrote: > > I propose adding `Foldable1` type-class into `base1`. > > Add Foldable1 > ============= > > > Motivation > ---------- > > It's regularly asked whether `Foldable1` could be added to `base` > (e.g. on reddit[^ref1], there're also GHC issue[^ref2] and old > phabricator diff[^ref3]) > Also there's work towards non-empty maps and sets[^ref4], > which would benefit from `Foldable1`. > > As commented on reddit, `Foldable1` could be added without any pain > to the `base` as it's pure addition - no modifications needed in > existing modules. > > [^ref1]: > https://www.reddit.com/r/haskell/comments/6d0vgt/could_we_have_foldable1_and_traversable1_in_base/ > [^ref2]: https://gitlab.haskell.org/ghc/ghc/issues/13573 > [^ref3]: https://phabricator.haskell.org/D4812 > [^ref4]: https://github.com/haskell/containers/pull/616 > > Change > ------ > > The change exist as merge request[^ref4] on gitlab.haskell.org. > > Importantly, this change **doesn't change** anything in other modules > of `base`, except of adding a `Foldable` instance to `Data.Complex`. > In particular, `foldl1` and `foldr1` in `Data.Foldable` remain partial, etc. > > My version of `Foldable1` class is big, so I'll comment the motivation > for each member > > ```haskell > class Foldable t => Foldable1 t where > {-# MINIMAL foldMap1 | toNonEmpty | foldr1map #-} > > -- the defining member, like foldMap but only asking for Semigroup > foldMap1 :: Semigroup m => (a -> m) -> t a -> m > > fold1 :: Semigroup m => t m -> m# > > -- strict foldMap1, cf foldMap' > foldMap1' :: Semigroup m => (a -> m) -> t a -> m > > -- analogue of toList > toNonEmpty :: t a -> NonEmpty a > > -- left&right, strict&non-strict folds > foldr1 :: (a -> a -> a) -> t a -> a > foldr1' :: (a -> a -> a) -> t a -> a > foldl1 :: (a -> a -> a) -> t a -> a > foldl1' :: (a -> a -> a) -> t a -> a > > -- these can have efficient implementation for NonEmptySet > maximum1 :: forall a. Ord a => t a -> a > minimum1 :: forall a. Ord a => t a -> a > > -- head1 have efficient implementation for NonEmpty and Tree > -- last1 for symmetry > head1 :: t a -> a > last1 :: t a -> a > > -- fold variants with premap. > -- Without this map, we cannot implement foldl using foldr etc. > foldr1map :: (a -> b) -> (b -> b -> b) -> t a -> b > foldl1'map :: (a -> b) -> (b -> b -> b) -> t a -> b > foldl1map :: (a -> b) -> (b -> b -> b) -> t a -> b > foldr1'map :: (a -> b) -> (b -> b -> b) -> t a -> b > ``` > > The merge request also adds instances for everything non-empty in `base`. > > I propose the `Data.Foldable1` as the module name. > `semigroupoids`[^ref6] uses `Data.Semigroup.Foldable`, > but it's confusing; and using different name could help migration. > > The module contains five top-level functions, which should > be self-explanatory: > > ```haskell > intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m > > foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a > foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a > > maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a > minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a > ``` > > This is less than in `Data.Semigroup.Foldable`[^ref9], > as without `Apply` they don't make sense. > For example: > > ```haskell > -- needs Apply, not in Data.Foldable1 > traverse1_ :: (Foldable1 t, Apply f) => (a -> f b) -> t a -> f () > ``` > > And if we relax `Apply` to `Applicative`, we get `traverse_`. > > [^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 > [^ref9]: > https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-Foldable-Class.html > > [^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 > > Compatibility & migration > ------------------------- > > I drafted a compatibility package `foldable1` (github[^ref6], > haddocks[^ref7]), > which I hope could be maintained under github.com/haskell organization. > I can act as a maintainer, with a hope that there won't be a lot > of changes happening in `Data.Foldable1`. > > To my surprise, there's already a package with this name on > Hackage[^ref8] by > M Farkas-Dyck (cc'd). I hope they would donate the name to Haskell.org / > CLC; > the package won't have any other good use when `Data.Foldable1` is in > `base`, > then act as a compat package. > > `Data.Foldable1` contains also instances for `Lift`, `Backwards` and > `Reverse` > data types from `transformers`. Perfectly, the `transformers` bundled > with GHC with this change would implement the instances as well. > This change should propage to `transformers-compat` too. > > Similarly, `containers` would have an instance for `Tree` (and non-empty > `Set` and `Map` when they are added). > > `semigroupoids` would need a bit of work, to depend on `foldable1`, > yet the public changes can be kept quite minimal. > I don't think that anything in reverse dependencies of `lens` will be > broken by > this change, if "new" `Foldable1` is re-exported from `semigroupoids`' > `Data.Semigroup.Foldable`[^ref9] > > Other "compat" packages -- like `tagged`, `bifunctors` -- have to be > dealt with > case by case. For example whether they should depend on `foldable1` or > other way around. > > [^ref6]: https://github.com/phadej/foldable1 > [^ref7]: https://oleg.fi/haddocks/foldable1/ > [^ref8]: https://hackage.haskell.org/package/foldable1 > [^ref9]: > https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-Foldable-Class.html > > Unresolved questions > -------------------- > > - Should we add `Bifoldable1` too. That should be trivial. > - GHC-8.10 freeze is quite soon, is targeting GHC-8.12/base-4.15 more > realistic? > > > _______________________________________________ > 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 Fri Oct 18 00:06:24 2019 From: ekmett at gmail.com (Edward Kmett) Date: Thu, 17 Oct 2019 17:06:24 -0700 Subject: Add Data.Foldable1 to base In-Reply-To: References: Message-ID: <6AA55099-65ED-46B9-B035-88EF6114C6CC@gmail.com> I’m happy to take patches to move things along in semigroupoids. My focus has been elsewhere, I admit. -Edward > On Oct 17, 2019, at 5:03 PM, Andrew Martin wrote: > > While I want this abstraction in base, I don’t want it there yet. There is an open issue on semigroupoids about renaming everything: https://github.com/ekmett/semigroupoids/issues/26 > > This needs to be handled before the abstraction is brought into base. Also, foldr1 is awful in common situations. See https://github.com/ekmett/semigroupoids/issues/77 > > The problem is that refinements of this abstraction seem to have stalled in semigroupoids, but these are desperately needed before the abstraction is brought into base. > > Sent from my iPhone > >> On Oct 17, 2019, at 10:42 AM, Oleg Grenrus wrote: >> >> I propose adding `Foldable1` type-class into `base1`. >> >> Add Foldable1 >> ============= >> >> >> Motivation >> ---------- >> >> It's regularly asked whether `Foldable1` could be added to `base` >> (e.g. on reddit[^ref1], there're also GHC issue[^ref2] and old >> phabricator diff[^ref3]) >> Also there's work towards non-empty maps and sets[^ref4], >> which would benefit from `Foldable1`. >> >> As commented on reddit, `Foldable1` could be added without any pain >> to the `base` as it's pure addition - no modifications needed in >> existing modules. >> >> [^ref1]: >> https://www.reddit.com/r/haskell/comments/6d0vgt/could_we_have_foldable1_and_traversable1_in_base/ >> [^ref2]: https://gitlab.haskell.org/ghc/ghc/issues/13573 >> [^ref3]: https://phabricator.haskell.org/D4812 >> [^ref4]: https://github.com/haskell/containers/pull/616 >> >> Change >> ------ >> >> The change exist as merge request[^ref4] on gitlab.haskell.org. >> >> Importantly, this change **doesn't change** anything in other modules >> of `base`, except of adding a `Foldable` instance to `Data.Complex`. >> In particular, `foldl1` and `foldr1` in `Data.Foldable` remain partial, etc. >> >> My version of `Foldable1` class is big, so I'll comment the motivation >> for each member >> >> ```haskell >> class Foldable t => Foldable1 t where >> {-# MINIMAL foldMap1 | toNonEmpty | foldr1map #-} >> >> -- the defining member, like foldMap but only asking for Semigroup >> foldMap1 :: Semigroup m => (a -> m) -> t a -> m >> >> fold1 :: Semigroup m => t m -> m# >> >> -- strict foldMap1, cf foldMap' >> foldMap1' :: Semigroup m => (a -> m) -> t a -> m >> >> -- analogue of toList >> toNonEmpty :: t a -> NonEmpty a >> >> -- left&right, strict&non-strict folds >> foldr1 :: (a -> a -> a) -> t a -> a >> foldr1' :: (a -> a -> a) -> t a -> a >> foldl1 :: (a -> a -> a) -> t a -> a >> foldl1' :: (a -> a -> a) -> t a -> a >> >> -- these can have efficient implementation for NonEmptySet >> maximum1 :: forall a. Ord a => t a -> a >> minimum1 :: forall a. Ord a => t a -> a >> >> -- head1 have efficient implementation for NonEmpty and Tree >> -- last1 for symmetry >> head1 :: t a -> a >> last1 :: t a -> a >> >> -- fold variants with premap. >> -- Without this map, we cannot implement foldl using foldr etc. >> foldr1map :: (a -> b) -> (b -> b -> b) -> t a -> b >> foldl1'map :: (a -> b) -> (b -> b -> b) -> t a -> b >> foldl1map :: (a -> b) -> (b -> b -> b) -> t a -> b >> foldr1'map :: (a -> b) -> (b -> b -> b) -> t a -> b >> ``` >> >> The merge request also adds instances for everything non-empty in `base`. >> >> I propose the `Data.Foldable1` as the module name. >> `semigroupoids`[^ref6] uses `Data.Semigroup.Foldable`, >> but it's confusing; and using different name could help migration. >> >> The module contains five top-level functions, which should >> be self-explanatory: >> >> ```haskell >> intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m >> >> foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a >> foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a >> >> maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a >> minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a >> ``` >> >> This is less than in `Data.Semigroup.Foldable`[^ref9], >> as without `Apply` they don't make sense. >> For example: >> >> ```haskell >> -- needs Apply, not in Data.Foldable1 >> traverse1_ :: (Foldable1 t, Apply f) => (a -> f b) -> t a -> f () >> ``` >> >> And if we relax `Apply` to `Applicative`, we get `traverse_`. >> >> [^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 >> [^ref9]: >> https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-Foldable-Class.html >> >> [^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 >> >> Compatibility & migration >> ------------------------- >> >> I drafted a compatibility package `foldable1` (github[^ref6], >> haddocks[^ref7]), >> which I hope could be maintained under github.com/haskell organization. >> I can act as a maintainer, with a hope that there won't be a lot >> of changes happening in `Data.Foldable1`. >> >> To my surprise, there's already a package with this name on >> Hackage[^ref8] by >> M Farkas-Dyck (cc'd). I hope they would donate the name to Haskell.org / >> CLC; >> the package won't have any other good use when `Data.Foldable1` is in >> `base`, >> then act as a compat package. >> >> `Data.Foldable1` contains also instances for `Lift`, `Backwards` and >> `Reverse` >> data types from `transformers`. Perfectly, the `transformers` bundled >> with GHC with this change would implement the instances as well. >> This change should propage to `transformers-compat` too. >> >> Similarly, `containers` would have an instance for `Tree` (and non-empty >> `Set` and `Map` when they are added). >> >> `semigroupoids` would need a bit of work, to depend on `foldable1`, >> yet the public changes can be kept quite minimal. >> I don't think that anything in reverse dependencies of `lens` will be >> broken by >> this change, if "new" `Foldable1` is re-exported from `semigroupoids`' >> `Data.Semigroup.Foldable`[^ref9] >> >> Other "compat" packages -- like `tagged`, `bifunctors` -- have to be >> dealt with >> case by case. For example whether they should depend on `foldable1` or >> other way around. >> >> [^ref6]: https://github.com/phadej/foldable1 >> [^ref7]: https://oleg.fi/haddocks/foldable1/ >> [^ref8]: https://hackage.haskell.org/package/foldable1 >> [^ref9]: >> https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-Foldable-Class.html >> >> Unresolved questions >> -------------------- >> >> - Should we add `Bifoldable1` too. That should be trivial. >> - GHC-8.10 freeze is quite soon, is targeting GHC-8.12/base-4.15 more >> realistic? >> >> >> _______________________________________________ >> 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 oleg.grenrus at iki.fi Fri Oct 18 01:12:37 2019 From: oleg.grenrus at iki.fi (Oleg Grenrus) Date: Fri, 18 Oct 2019 04:12:37 +0300 Subject: Add Data.Foldable1 to base In-Reply-To: <6AA55099-65ED-46B9-B035-88EF6114C6CC@gmail.com> References: <6AA55099-65ED-46B9-B035-88EF6114C6CC@gmail.com> Message-ID: What is the proposed change in semigroupoids, I don't see any decisive conclusion comment. To get this going, I suggest limiting discussion to the Foldable1 only and if after this proposal is accepted, extrapolate for the rest of `semigroupoids`. So if someone can propose a concrete list how to rename symbols in https://oleg.fi/haddocks/foldable1/Data-Foldable1.html , I'll make a separate branch & haddock page. Is the wanted renaming s/1//; s/^/semi/: - Foldable1    -> Semifoldable - fold1        -> semifold - foldMap1     -> semifoldMap - foldr1       -> semifoldr - foldr1map    -> semifoldr1map - toNonEmpty   -> toNonEmpty - ... - head1        -> semihead - last1        -> semilast - minimum1     -> semiminimum - maximum1     -> semimaximum - intercalate1 -> semiintercalate - foldl1M      -> semifoldl - ... - maximum1By   -> semimaximumBy - ... I'm fine with this. The head1/semihead are both silly, but the suffix was there to avoid name clash, so prefix is fine for that purpose too. --- The synopsis of current state of proposed Data.Foldable1 module Data.Foldable1where class Foldable t => Foldable1 t   fold1      :: (Foldable1 t, Semigroup m) => t m -> m   foldMap1   :: (Foldable1 t, Semigroup m) => (a -> m) -> t a -> m   foldMap1'  :: (Foldable1 t, Semigroup m) => (a -> m) -> t a -> m   foldr1     :: Foldable1 t => (a -> a -> a) -> t a -> a   foldr1'    :: Foldable1 t => (a -> a -> a) -> t a -> a   foldl1     :: Foldable1 t => (a -> a -> a) -> t a -> a   foldl1'    :: Foldable1 t => (a -> a -> a) -> t a -> a   toNonEmpty :: Foldable1 t => t a -> NonEmpty a   maximum1   :: forall a. (Foldable1 t, Ord a) => t a -> a   minimum1   :: forall a. (Foldable1 t, Ord a) => t a -> a   head1      :: Foldable1 t => t a -> a   last1      :: Foldable1 t => t a -> a   foldr1map  :: Foldable1 t => (a -> b) -> (b -> b -> b) -> t a -> b   foldl1'map :: Foldable1 t => (a -> b) -> (b -> b -> b) -> t a -> b   foldl1map  :: Foldable1 t => (a -> b) -> (b -> b -> b) -> t a -> b   foldr1'map :: Foldable1 t => (a -> b) -> (b -> b -> b) -> t a -> b intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m foldrM1      :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1      :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a maximum1By   :: Foldable1 t => (a -> a -> Ordering) -> t a -> a minimum1By   :: Foldable1 t => (a -> a -> Ordering) -> t a -> a - Oleg On 18.10.2019 3.06, Edward Kmett wrote: > I’m happy to take patches to move things along in semigroupoids. My > focus has been elsewhere, I admit. > > -Edward > >> On Oct 17, 2019, at 5:03 PM, Andrew Martin >> wrote: >> >>  While I want this abstraction in base, I don’t want it there yet. >> There is an open issue on semigroupoids about renaming everything: >> https://github.com/ekmett/semigroupoids/issues/26 >> >> This needs to be handled before the abstraction is brought into base. >> Also, foldr1 is awful in common situations. See >> https://github.com/ekmett/semigroupoids/issues/77 >> >> The problem is that refinements of this abstraction seem to have >> stalled in semigroupoids, but these are desperately needed before the >> abstraction is brought into base. >> >> Sent from my iPhone >> >> On Oct 17, 2019, at 10:42 AM, Oleg Grenrus > > wrote: >> >>> I propose adding `Foldable1` type-class into `base1`. >>> >>> Add Foldable1 >>> ============= >>> >>> >>> Motivation >>> ---------- >>> >>> It's regularly asked whether `Foldable1` could be added to `base` >>> (e.g. on reddit[^ref1], there're also GHC issue[^ref2] and old >>> phabricator diff[^ref3]) >>> Also there's work towards non-empty maps and sets[^ref4], >>> which would benefit from `Foldable1`. >>> >>> As commented on reddit, `Foldable1` could be added without any pain >>> to the `base` as it's pure addition - no modifications needed in >>> existing modules. >>> >>> [^ref1]: >>> https://www.reddit.com/r/haskell/comments/6d0vgt/could_we_have_foldable1_and_traversable1_in_base/ >>> [^ref2]: https://gitlab.haskell.org/ghc/ghc/issues/13573 >>> [^ref3]: https://phabricator.haskell.org/D4812 >>> [^ref4]: https://github.com/haskell/containers/pull/616 >>> >>> Change >>> ------ >>> >>> The change exist as merge request[^ref4] on gitlab.haskell.org >>> . >>> >>> Importantly, this change **doesn't change** anything in other modules >>> of `base`, except of adding a `Foldable` instance to `Data.Complex`. >>> In particular, `foldl1` and `foldr1` in `Data.Foldable` remain >>> partial, etc. >>> >>> My version of `Foldable1` class is big, so I'll comment the motivation >>> for each member >>> >>> ```haskell >>> class Foldable t => Foldable1 t where >>>     {-# MINIMAL foldMap1 | toNonEmpty | foldr1map #-} >>> >>>     -- the defining member, like foldMap but only asking for Semigroup >>>     foldMap1 :: Semigroup m => (a -> m) -> t a -> m >>> >>>     fold1 :: Semigroup m => t m -> m# >>> >>>     -- strict foldMap1, cf foldMap' >>>     foldMap1' :: Semigroup m => (a -> m) -> t a -> m >>> >>>     -- analogue of toList >>>     toNonEmpty :: t a -> NonEmpty a >>> >>>     -- left&right, strict&non-strict folds >>>     foldr1  :: (a -> a -> a) -> t a -> a >>>     foldr1' :: (a -> a -> a) -> t a -> a >>>     foldl1  :: (a -> a -> a) -> t a -> a >>>     foldl1' :: (a -> a -> a) -> t a -> a >>> >>>     -- these can have efficient implementation for NonEmptySet >>>     maximum1 :: forall a. Ord a => t a -> a >>>     minimum1 :: forall a. Ord a => t a -> a >>> >>>     -- head1 have efficient implementation for NonEmpty and Tree >>>     -- last1 for symmetry >>>     head1 :: t a -> a >>>     last1 :: t a -> a >>> >>>     -- fold variants with premap. >>>     -- Without this map, we cannot implement foldl using foldr etc. >>>     foldr1map  :: (a -> b) -> (b -> b -> b) -> t a -> b >>>     foldl1'map :: (a -> b) -> (b -> b -> b) -> t a -> b >>>     foldl1map  :: (a -> b) -> (b -> b -> b) -> t a -> b >>>     foldr1'map :: (a -> b) -> (b -> b -> b) -> t a -> b >>> ``` >>> >>> The merge request also adds instances for everything non-empty in >>> `base`. >>> >>> I propose the `Data.Foldable1` as the module name. >>> `semigroupoids`[^ref6] uses `Data.Semigroup.Foldable`, >>> but it's confusing; and using different name could help migration. >>> >>> The module contains five top-level functions, which should >>> be self-explanatory: >>> >>> ```haskell >>> intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m >>> >>> foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a >>> foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a >>> >>> maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a >>> minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a >>> ``` >>> >>> This is less than in `Data.Semigroup.Foldable`[^ref9], >>> as without `Apply` they don't make sense. >>> For example: >>> >>> ```haskell >>> -- needs Apply, not in Data.Foldable1 >>> traverse1_ :: (Foldable1 t, Apply f) => (a -> f b) -> t a -> f () >>> ``` >>> >>> And if we relax `Apply` to `Applicative`, we get `traverse_`. >>> >>> [^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 >>> [^ref9]: >>> https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-Foldable-Class.html >>> >>> [^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 >>> >>> Compatibility & migration >>> ------------------------- >>> >>> I drafted a compatibility package `foldable1` (github[^ref6], >>> haddocks[^ref7]), >>> which I hope could be maintained under github.com/haskell >>> organization. >>> I can act as a maintainer, with a hope that there won't be a lot >>> of changes happening in `Data.Foldable1`. >>> >>> To my surprise, there's already a package with this name on >>> Hackage[^ref8] by >>> M Farkas-Dyck (cc'd). I hope they would donate the name to >>> Haskell.org / >>> CLC; >>> the package won't have any other good use when `Data.Foldable1` is in >>> `base`, >>> then act as a compat package. >>> >>> `Data.Foldable1` contains also instances for `Lift`, `Backwards` and >>> `Reverse` >>> data types from `transformers`. Perfectly, the `transformers` bundled >>> with GHC with this change would implement the instances as well. >>> This change should propage to `transformers-compat` too. >>> >>> Similarly, `containers` would have an instance for `Tree` (and non-empty >>> `Set` and `Map` when they are added). >>> >>> `semigroupoids` would need a bit of work, to depend on `foldable1`, >>> yet the public changes can be kept quite minimal. >>> I don't think that anything in reverse dependencies of `lens` will be >>> broken by >>> this change, if "new" `Foldable1` is re-exported from `semigroupoids`' >>> `Data.Semigroup.Foldable`[^ref9] >>> >>> Other "compat" packages -- like `tagged`, `bifunctors` -- have to be >>> dealt with >>> case by case. For example whether they should depend on `foldable1` or >>> other way around. >>> >>> [^ref6]: https://github.com/phadej/foldable1 >>> [^ref7]: https://oleg.fi/haddocks/foldable1/ >>> [^ref8]: https://hackage.haskell.org/package/foldable1 >>> [^ref9]: >>> https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-Foldable-Class.html >>> >>> Unresolved questions >>> -------------------- >>> >>> - Should we add `Bifoldable1` too. That should be trivial. >>> - GHC-8.10 freeze is quite soon, is targeting GHC-8.12/base-4.15 more >>> realistic? >>> >>> >>> _______________________________________________ >>> 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 tmorris at tmorris.net Fri Oct 18 07:26:30 2019 From: tmorris at tmorris.net (Tony Morris) Date: Fri, 18 Oct 2019 17:26:30 +1000 Subject: Add Data.Foldable1 to base In-Reply-To: References: <6AA55099-65ED-46B9-B035-88EF6114C6CC@gmail.com> Message-ID: I agree Foldable1 in base would be great, but I think the most bang for buck would be to include several others; at least also Traversable1 and possibly even Apply,Bind,Alt I second the comment about the issue related to addressing the names, etc in semigroupoids, in preparation for inclusion to base. On Fri, Oct 18, 2019 at 11:12 AM Oleg Grenrus wrote: > What is the proposed change in semigroupoids, I don't see any decisive > conclusion comment. To get this going, I suggest limiting discussion to the > Foldable1 only > and if after this proposal is accepted, extrapolate for the rest of > `semigroupoids`. > > So if someone can propose a concrete list how to rename symbols in > https://oleg.fi/haddocks/foldable1/Data-Foldable1.html > , I'll make a > separate branch & haddock page. > > Is the wanted renaming s/1//; s/^/semi/: > > - Foldable1 -> Semifoldable > - fold1 -> semifold > - foldMap1 -> semifoldMap > - foldr1 -> semifoldr > - foldr1map -> semifoldr1map > - toNonEmpty -> toNonEmpty > - ... > - head1 -> semihead > - last1 -> semilast > - minimum1 -> semiminimum > - maximum1 -> semimaximum > > - intercalate1 -> semiintercalate > - foldl1M -> semifoldl > - ... > - maximum1By -> semimaximumBy > - ... > > I'm fine with this. > The head1/semihead are both silly, but the suffix was there to avoid name > clash, so prefix is fine for that purpose too. > > --- > > The synopsis of current state of proposed Data.Foldable1 > > module Data.Foldable1 where > > class Foldable t => Foldable1 t > fold1 :: (Foldable1 t, Semigroup m) => t m -> m > foldMap1 :: (Foldable1 t, Semigroup m) => (a -> m) -> t a -> m > foldMap1' :: (Foldable1 t, Semigroup m) => (a -> m) -> t a -> m > foldr1 :: Foldable1 t => (a -> a -> a) -> t a -> a > foldr1' :: Foldable1 t => (a -> a -> a) -> t a -> a > foldl1 :: Foldable1 t => (a -> a -> a) -> t a -> a > foldl1' :: Foldable1 t => (a -> a -> a) -> t a -> a > toNonEmpty :: Foldable1 t => t a -> NonEmpty a > maximum1 :: forall a. (Foldable1 t, Ord a) => t a -> a > minimum1 :: forall a. (Foldable1 t, Ord a) => t a -> a > head1 :: Foldable1 t => t a -> a > last1 :: Foldable1 t => t a -> a > foldr1map :: Foldable1 t => (a -> b) -> (b -> b -> b) -> t a -> b > foldl1'map :: Foldable1 t => (a -> b) -> (b -> b -> b) -> t a -> b > foldl1map :: Foldable1 t => (a -> b) -> (b -> b -> b) -> t a -> b > foldr1'map :: Foldable1 t => (a -> b) -> (b -> b -> b) -> t a -> b > > intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m > foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a > foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a > maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a > minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a > > - Oleg > On 18.10.2019 3.06, Edward Kmett wrote: > > I’m happy to take patches to move things along in semigroupoids. My focus > has been elsewhere, I admit. > > -Edward > > On Oct 17, 2019, at 5:03 PM, Andrew Martin > wrote: > >  While I want this abstraction in base, I don’t want it there yet. There > is an open issue on semigroupoids about renaming everything: > https://github.com/ekmett/semigroupoids/issues/26 > > This needs to be handled before the abstraction is brought into base. > Also, foldr1 is awful in common situations. See > https://github.com/ekmett/semigroupoids/issues/77 > > The problem is that refinements of this abstraction seem to have stalled > in semigroupoids, but these are desperately needed before the abstraction > is brought into base. > > Sent from my iPhone > > On Oct 17, 2019, at 10:42 AM, Oleg Grenrus wrote: > > I propose adding `Foldable1` type-class into `base1`. > > Add Foldable1 > ============= > > > Motivation > ---------- > > It's regularly asked whether `Foldable1` could be added to `base` > (e.g. on reddit[^ref1], there're also GHC issue[^ref2] and old > phabricator diff[^ref3]) > Also there's work towards non-empty maps and sets[^ref4], > which would benefit from `Foldable1`. > > As commented on reddit, `Foldable1` could be added without any pain > to the `base` as it's pure addition - no modifications needed in > existing modules. > > [^ref1]: > > https://www.reddit.com/r/haskell/comments/6d0vgt/could_we_have_foldable1_and_traversable1_in_base/ > [^ref2]: https://gitlab.haskell.org/ghc/ghc/issues/13573 > [^ref3]: https://phabricator.haskell.org/D4812 > [^ref4]: https://github.com/haskell/containers/pull/616 > > Change > ------ > > The change exist as merge request[^ref4] on gitlab.haskell.org. > > Importantly, this change **doesn't change** anything in other modules > of `base`, except of adding a `Foldable` instance to `Data.Complex`. > In particular, `foldl1` and `foldr1` in `Data.Foldable` remain partial, > etc. > > My version of `Foldable1` class is big, so I'll comment the motivation > for each member > > ```haskell > class Foldable t => Foldable1 t where > {-# MINIMAL foldMap1 | toNonEmpty | foldr1map #-} > > -- the defining member, like foldMap but only asking for Semigroup > foldMap1 :: Semigroup m => (a -> m) -> t a -> m > > fold1 :: Semigroup m => t m -> m# > > -- strict foldMap1, cf foldMap' > foldMap1' :: Semigroup m => (a -> m) -> t a -> m > > -- analogue of toList > toNonEmpty :: t a -> NonEmpty a > > -- left&right, strict&non-strict folds > foldr1 :: (a -> a -> a) -> t a -> a > foldr1' :: (a -> a -> a) -> t a -> a > foldl1 :: (a -> a -> a) -> t a -> a > foldl1' :: (a -> a -> a) -> t a -> a > > -- these can have efficient implementation for NonEmptySet > maximum1 :: forall a. Ord a => t a -> a > minimum1 :: forall a. Ord a => t a -> a > > -- head1 have efficient implementation for NonEmpty and Tree > -- last1 for symmetry > head1 :: t a -> a > last1 :: t a -> a > > -- fold variants with premap. > -- Without this map, we cannot implement foldl using foldr etc. > foldr1map :: (a -> b) -> (b -> b -> b) -> t a -> b > foldl1'map :: (a -> b) -> (b -> b -> b) -> t a -> b > foldl1map :: (a -> b) -> (b -> b -> b) -> t a -> b > foldr1'map :: (a -> b) -> (b -> b -> b) -> t a -> b > ``` > > The merge request also adds instances for everything non-empty in `base`. > > I propose the `Data.Foldable1` as the module name. > `semigroupoids`[^ref6] uses `Data.Semigroup.Foldable`, > but it's confusing; and using different name could help migration. > > The module contains five top-level functions, which should > be self-explanatory: > > ```haskell > intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m > > foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a > foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a > > maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a > minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a > ``` > > This is less than in `Data.Semigroup.Foldable`[^ref9], > as without `Apply` they don't make sense. > For example: > > ```haskell > -- needs Apply, not in Data.Foldable1 > traverse1_ :: (Foldable1 t, Apply f) => (a -> f b) -> t a -> f () > ``` > > And if we relax `Apply` to `Applicative`, we get `traverse_`. > > [^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 > [^ref9]: > > https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-Foldable-Class.html > > [^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 > > Compatibility & migration > ------------------------- > > I drafted a compatibility package `foldable1` (github[^ref6], > haddocks[^ref7]), > which I hope could be maintained under github.com/haskell organization. > I can act as a maintainer, with a hope that there won't be a lot > of changes happening in `Data.Foldable1`. > > To my surprise, there's already a package with this name on > Hackage[^ref8] by > M Farkas-Dyck (cc'd). I hope they would donate the name to Haskell.org / > CLC; > the package won't have any other good use when `Data.Foldable1` is in > `base`, > then act as a compat package. > > `Data.Foldable1` contains also instances for `Lift`, `Backwards` and > `Reverse` > data types from `transformers`. Perfectly, the `transformers` bundled > with GHC with this change would implement the instances as well. > This change should propage to `transformers-compat` too. > > Similarly, `containers` would have an instance for `Tree` (and non-empty > `Set` and `Map` when they are added). > > `semigroupoids` would need a bit of work, to depend on `foldable1`, > yet the public changes can be kept quite minimal. > I don't think that anything in reverse dependencies of `lens` will be > broken by > this change, if "new" `Foldable1` is re-exported from `semigroupoids`' > `Data.Semigroup.Foldable`[^ref9] > > Other "compat" packages -- like `tagged`, `bifunctors` -- have to be > dealt with > case by case. For example whether they should depend on `foldable1` or > other way around. > > [^ref6]: https://github.com/phadej/foldable1 > [^ref7]: https://oleg.fi/haddocks/foldable1/ > [^ref8]: https://hackage.haskell.org/package/foldable1 > [^ref9]: > > https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-Foldable-Class.html > > Unresolved questions > -------------------- > > - Should we add `Bifoldable1` too. That should be trivial. > - GHC-8.10 freeze is quite soon, is targeting GHC-8.12/base-4.15 more > realistic? > > > _______________________________________________ > 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 oleg.grenrus at iki.fi Fri Oct 18 07:56:23 2019 From: oleg.grenrus at iki.fi (Oleg Grenrus) Date: Fri, 18 Oct 2019 10:56:23 +0300 Subject: Add Data.Foldable1 to base In-Reply-To: References: <6AA55099-65ED-46B9-B035-88EF6114C6CC@gmail.com> Message-ID: <36c36812-ede4-b87b-9718-c373b854f85b@iki.fi> I won't try to include Traversable1, nor Apply, Bind, Alt; not yet. It would extend the scope of a patch way too much, and rise AMP-like questions, which I don't have answers to. Foldable1 is something which "could move into base without pain" [1], so let's do that first. - Oleg [1]: https://www.reddit.com/r/haskell/comments/6d0vgt/could_we_have_foldable1_and_traversable1_in_base/dhz42ie/ On 18.10.2019 10.26, Tony Morris wrote: > I agree Foldable1 in base would be great, but I think the most bang > for buck would be to include several others; at least also > Traversable1 and possibly even Apply,Bind,Alt > > I second the comment about the issue related to addressing the names, > etc in semigroupoids, in preparation for inclusion to base. > > On Fri, Oct 18, 2019 at 11:12 AM Oleg Grenrus > wrote: > > What is the proposed change in semigroupoids, I don't see any > decisive conclusion comment. To get this going, I suggest limiting > discussion to the Foldable1 only > and if after this proposal is accepted, extrapolate for the rest > of `semigroupoids`. > > So if someone can propose a concrete list how to rename symbols in > https://oleg.fi/haddocks/foldable1/Data-Foldable1.html > , I'll make > a separate branch & haddock page. > > Is the wanted renaming s/1//; s/^/semi/: > > - Foldable1    -> Semifoldable > - fold1        -> semifold > - foldMap1     -> semifoldMap > - foldr1       -> semifoldr > - foldr1map    -> semifoldr1map > - toNonEmpty   -> toNonEmpty > - ... > - head1        -> semihead > - last1        -> semilast > - minimum1     -> semiminimum > - maximum1     -> semimaximum > > - intercalate1 -> semiintercalate > - foldl1M      -> semifoldl > - ... > - maximum1By   -> semimaximumBy > - ... > > I'm fine with this. > The head1/semihead are both silly, but the suffix was there to > avoid name clash, so prefix is fine for that purpose too. > > --- > > The synopsis of current state of proposed Data.Foldable1 > > module Data.Foldable1where > > class Foldable t => Foldable1 t >   fold1      :: (Foldable1 t, Semigroup m) => t m -> m >   foldMap1   :: (Foldable1 t, Semigroup m) => (a -> m) -> t a -> m >   foldMap1'  :: (Foldable1 t, Semigroup m) => (a -> m) -> t a -> m >   foldr1     :: Foldable1 t => (a -> a -> a) -> t a -> a >   foldr1'    :: Foldable1 t => (a -> a -> a) -> t a -> a >   foldl1     :: Foldable1 t => (a -> a -> a) -> t a -> a >   foldl1'    :: Foldable1 t => (a -> a -> a) -> t a -> a >   toNonEmpty :: Foldable1 t => t a -> NonEmpty a >   maximum1   :: forall a. (Foldable1 t, Ord a) => t a -> a >   minimum1   :: forall a. (Foldable1 t, Ord a) => t a -> a >   head1      :: Foldable1 t => t a -> a >   last1      :: Foldable1 t => t a -> a >   foldr1map  :: Foldable1 t => (a -> b) -> (b -> b -> b) -> t a -> b >   foldl1'map :: Foldable1 t => (a -> b) -> (b -> b -> b) -> t a -> b >   foldl1map  :: Foldable1 t => (a -> b) -> (b -> b -> b) -> t a -> b >   foldr1'map :: Foldable1 t => (a -> b) -> (b -> b -> b) -> t a -> b > > intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m > foldrM1      :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a > -> m a > foldlM1      :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a > -> m a > maximum1By   :: Foldable1 t => (a -> a -> Ordering) -> t a -> a > minimum1By   :: Foldable1 t => (a -> a -> Ordering) -> t a -> a > > - Oleg > > On 18.10.2019 3.06, Edward Kmett wrote: >> I’m happy to take patches to move things along in semigroupoids. >> My focus has been elsewhere, I admit. >> >> -Edward >> >>> On Oct 17, 2019, at 5:03 PM, Andrew Martin >>> >>> wrote: >>> >>>  While I want this abstraction in base, I don’t want it there >>> yet. There is an open issue on semigroupoids about renaming >>> everything: https://github.com/ekmett/semigroupoids/issues/26 >>> >>> This needs to be handled before the abstraction is brought into >>> base. Also, foldr1 is awful in common situations. See >>> https://github.com/ekmett/semigroupoids/issues/77 >>> >>> The problem is that refinements of this abstraction seem to have >>> stalled in semigroupoids, but these are desperately needed >>> before the abstraction is brought into base. >>> >>> Sent from my iPhone >>> >>> On Oct 17, 2019, at 10:42 AM, Oleg Grenrus >> > wrote: >>> >>>> I propose adding `Foldable1` type-class into `base1`. >>>> >>>> Add Foldable1 >>>> ============= >>>> >>>> >>>> Motivation >>>> ---------- >>>> >>>> It's regularly asked whether `Foldable1` could be added to `base` >>>> (e.g. on reddit[^ref1], there're also GHC issue[^ref2] and old >>>> phabricator diff[^ref3]) >>>> Also there's work towards non-empty maps and sets[^ref4], >>>> which would benefit from `Foldable1`. >>>> >>>> As commented on reddit, `Foldable1` could be added without any pain >>>> to the `base` as it's pure addition - no modifications needed in >>>> existing modules. >>>> >>>> [^ref1]: >>>> https://www.reddit.com/r/haskell/comments/6d0vgt/could_we_have_foldable1_and_traversable1_in_base/ >>>> [^ref2]: https://gitlab.haskell.org/ghc/ghc/issues/13573 >>>> [^ref3]: https://phabricator.haskell.org/D4812 >>>> [^ref4]: https://github.com/haskell/containers/pull/616 >>>> >>>> Change >>>> ------ >>>> >>>> The change exist as merge request[^ref4] on gitlab.haskell.org >>>> . >>>> >>>> Importantly, this change **doesn't change** anything in other >>>> modules >>>> of `base`, except of adding a `Foldable` instance to >>>> `Data.Complex`. >>>> In particular, `foldl1` and `foldr1` in `Data.Foldable` remain >>>> partial, etc. >>>> >>>> My version of `Foldable1` class is big, so I'll comment the >>>> motivation >>>> for each member >>>> >>>> ```haskell >>>> class Foldable t => Foldable1 t where >>>>     {-# MINIMAL foldMap1 | toNonEmpty | foldr1map #-} >>>> >>>>     -- the defining member, like foldMap but only asking for >>>> Semigroup >>>>     foldMap1 :: Semigroup m => (a -> m) -> t a -> m >>>> >>>>     fold1 :: Semigroup m => t m -> m# >>>> >>>>     -- strict foldMap1, cf foldMap' >>>>     foldMap1' :: Semigroup m => (a -> m) -> t a -> m >>>> >>>>     -- analogue of toList >>>>     toNonEmpty :: t a -> NonEmpty a >>>> >>>>     -- left&right, strict&non-strict folds >>>>     foldr1  :: (a -> a -> a) -> t a -> a >>>>     foldr1' :: (a -> a -> a) -> t a -> a >>>>     foldl1  :: (a -> a -> a) -> t a -> a >>>>     foldl1' :: (a -> a -> a) -> t a -> a >>>> >>>>     -- these can have efficient implementation for NonEmptySet >>>>     maximum1 :: forall a. Ord a => t a -> a >>>>     minimum1 :: forall a. Ord a => t a -> a >>>> >>>>     -- head1 have efficient implementation for NonEmpty and Tree >>>>     -- last1 for symmetry >>>>     head1 :: t a -> a >>>>     last1 :: t a -> a >>>> >>>>     -- fold variants with premap. >>>>     -- Without this map, we cannot implement foldl using foldr etc. >>>>     foldr1map  :: (a -> b) -> (b -> b -> b) -> t a -> b >>>>     foldl1'map :: (a -> b) -> (b -> b -> b) -> t a -> b >>>>     foldl1map  :: (a -> b) -> (b -> b -> b) -> t a -> b >>>>     foldr1'map :: (a -> b) -> (b -> b -> b) -> t a -> b >>>> ``` >>>> >>>> The merge request also adds instances for everything non-empty >>>> in `base`. >>>> >>>> I propose the `Data.Foldable1` as the module name. >>>> `semigroupoids`[^ref6] uses `Data.Semigroup.Foldable`, >>>> but it's confusing; and using different name could help migration. >>>> >>>> The module contains five top-level functions, which should >>>> be self-explanatory: >>>> >>>> ```haskell >>>> intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m >>>> >>>> foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a >>>> foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a >>>> >>>> maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a >>>> minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a >>>> ``` >>>> >>>> This is less than in `Data.Semigroup.Foldable`[^ref9], >>>> as without `Apply` they don't make sense. >>>> For example: >>>> >>>> ```haskell >>>> -- needs Apply, not in Data.Foldable1 >>>> traverse1_ :: (Foldable1 t, Apply f) => (a -> f b) -> t a -> f () >>>> ``` >>>> >>>> And if we relax `Apply` to `Applicative`, we get `traverse_`. >>>> >>>> [^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 >>>> [^ref9]: >>>> https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-Foldable-Class.html >>>> >>>> [^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 >>>> >>>> Compatibility & migration >>>> ------------------------- >>>> >>>> I drafted a compatibility package `foldable1` (github[^ref6], >>>> haddocks[^ref7]), >>>> which I hope could be maintained under github.com/haskell >>>> organization. >>>> I can act as a maintainer, with a hope that there won't be a lot >>>> of changes happening in `Data.Foldable1`. >>>> >>>> To my surprise, there's already a package with this name on >>>> Hackage[^ref8] by >>>> M Farkas-Dyck (cc'd). I hope they would donate the name to >>>> Haskell.org / >>>> CLC; >>>> the package won't have any other good use when `Data.Foldable1` >>>> is in >>>> `base`, >>>> then act as a compat package. >>>> >>>> `Data.Foldable1` contains also instances for `Lift`, >>>> `Backwards` and >>>> `Reverse` >>>> data types from `transformers`. Perfectly, the `transformers` >>>> bundled >>>> with GHC with this change would implement the instances as well. >>>> This change should propage to `transformers-compat` too. >>>> >>>> Similarly, `containers` would have an instance for `Tree` (and >>>> non-empty >>>> `Set` and `Map` when they are added). >>>> >>>> `semigroupoids` would need a bit of work, to depend on `foldable1`, >>>> yet the public changes can be kept quite minimal. >>>> I don't think that anything in reverse dependencies of `lens` >>>> will be >>>> broken by >>>> this change, if "new" `Foldable1` is re-exported from >>>> `semigroupoids`' >>>> `Data.Semigroup.Foldable`[^ref9] >>>> >>>> Other "compat" packages -- like `tagged`, `bifunctors` -- have >>>> to be >>>> dealt with >>>> case by case. For example whether they should depend on >>>> `foldable1` or >>>> other way around. >>>> >>>> [^ref6]: https://github.com/phadej/foldable1 >>>> [^ref7]: https://oleg.fi/haddocks/foldable1/ >>>> [^ref8]: https://hackage.haskell.org/package/foldable1 >>>> [^ref9]: >>>> https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-Foldable-Class.html >>>> >>>> Unresolved questions >>>> -------------------- >>>> >>>> - Should we add `Bifoldable1` too. That should be trivial. >>>> - GHC-8.10 freeze is quite soon, is targeting >>>> GHC-8.12/base-4.15 more >>>> realistic? >>>> >>>> >>>> _______________________________________________ >>>> 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 oleg.grenrus at iki.fi Fri Oct 18 14:13:51 2019 From: oleg.grenrus at iki.fi (Oleg Grenrus) Date: Fri, 18 Oct 2019 17:13:51 +0300 Subject: Add NonEmptyMap and NonEmptySet to containers In-Reply-To: References: <505415F3-D529-4A16-AB78-B514DF6316EA@kent.ac.uk> Message-ID: <443cd353-781d-1ed4-1d56-639a477a19da@iki.fi> Relating to Foldable1/NonEmptyFoldable, based in another discussion (in my foldable1 to base proposal), it looks like it might be called Semifoldable See https://mail.haskell.org/pipermail/libraries/2019-October/030030.html Yet, Semiset is different thing (based on wikipedia: https://en.wikipedia.org/wiki/Semiset). NonEmptySet is a good name, it doesn't need explanation. If someone feels that it's too long, they can introduce `type NESet = NonEmptySet` alias in their development. - Oleg On 20.9.2019 4.56, Ruben Astudillo wrote: > On 19-09-19 22:17, Alexandre Esteves wrote: >> I do like the sound of `instance Foldable1 Set1` more than I do >> `instance NonEmptyFoldable NonEmptySet` >> > I prefer it too, I just wish (future) documentation included a little > explanation on why the suffix 1 was put. > From keith.wygant at gmail.com Fri Oct 18 15:40:02 2019 From: keith.wygant at gmail.com (Keith) Date: Fri, 18 Oct 2019 15:40:02 +0000 Subject: Add NonEmptyMap and NonEmptySet to containers In-Reply-To: <443cd353-781d-1ed4-1d56-639a477a19da@iki.fi> References: <505415F3-D529-4A16-AB78-B514DF6316EA@kent.ac.uk> <443cd353-781d-1ed4-1d56-639a477a19da@iki.fi> Message-ID: <59031523-7353-4000-ABF5-B9BF68B0CF4B@gmail.com> Sorry about bikeshedding. However, 'semifoldable' would be super confusing. If somebody saw 'semifoldMap' in the wild what would they think? Probably not that it can fold _more_ things than 'foldMap'. 'NonemptyFoldable', 'Semigroup.Foldable', 'SemigroupFoldable', and 'Foldable1', with 'sfoldMap', 'sgFoldMap', 'nonemptyFoldMap', or 'Semigroup.foldMap' may be long or meaningless to most, but at least they aren't actively misleading. –Keith On October 18, 2019 2:13:51 PM UTC, Oleg Grenrus wrote: >Relating to Foldable1/NonEmptyFoldable, based in another discussion (in > >my foldable1 to base proposal), it looks like it might be called >Semifoldable > >See >https://mail.haskell.org/pipermail/libraries/2019-October/030030.html > >Yet, Semiset is different thing (based on wikipedia: >https://en.wikipedia.org/wiki/Semiset). NonEmptySet is a good name, it >doesn't need explanation. If someone feels that it's too long, they can > >introduce `type NESet = NonEmptySet` alias in their development. > >- Oleg > >On 20.9.2019 4.56, Ruben Astudillo wrote: >> On 19-09-19 22:17, Alexandre Esteves wrote: >>> I do like the sound of `instance Foldable1 Set1` more than I do >>> `instance NonEmptyFoldable NonEmptySet` >>> > >> I prefer it too, I just wish (future) documentation included a little >> explanation on why the suffix 1 was put. >> >_______________________________________________ >Libraries mailing list >Libraries at haskell.org >http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries -- Sent from my phone with K-9 Mail. -------------- next part -------------- An HTML attachment was scrubbed... URL: From oleg.grenrus at iki.fi Fri Oct 18 16:10:42 2019 From: oleg.grenrus at iki.fi (Oleg Grenrus) Date: Fri, 18 Oct 2019 19:10:42 +0300 Subject: Add NonEmptyMap and NonEmptySet to containers In-Reply-To: <59031523-7353-4000-ABF5-B9BF68B0CF4B@gmail.com> References: <505415F3-D529-4A16-AB78-B514DF6316EA@kent.ac.uk> <443cd353-781d-1ed4-1d56-639a477a19da@iki.fi> <59031523-7353-4000-ABF5-B9BF68B0CF4B@gmail.com> Message-ID: Please reply to the "Add Data.Foldable1 to base" -thread to keep the discussion in one place. Otherwise this opinion will most likely be ignored. - Oleg P.S. That said, foldMap1/semifoldMap/... can fold over *less* things. It can fold over NonEmpty (list) but not over ordinary []. On 18.10.2019 18.40, Keith wrote: > Sorry about bikeshedding. However, 'semifoldable' would be super > confusing. > > If somebody saw 'semifoldMap' in the wild what would they think? > Probably not that it can fold _more_ things than 'foldMap'. > > 'NonemptyFoldable', 'Semigroup.Foldable', 'SemigroupFoldable', and > 'Foldable1', with 'sfoldMap', 'sgFoldMap', 'nonemptyFoldMap', or > 'Semigroup.foldMap' may be long or meaningless to most, but at least > they aren't actively misleading. > > –Keith > > On October 18, 2019 2:13:51 PM UTC, Oleg Grenrus > wrote: > > Relating to Foldable1/NonEmptyFoldable, based in another discussion (in > my foldable1 to base proposal), it looks like it might be called > Semifoldable > > Seehttps://mail.haskell.org/pipermail/libraries/2019-October/030030.html > > Yet, Semiset is different thing (based on wikipedia: > https://en.wikipedia.org/wiki/Semiset). NonEmptySet is a good name, it > doesn't need explanation. If someone feels that it's too long, they can > introduce `type NESet = NonEmptySet` alias in their development. > > - Oleg > > On 20.9.2019 4.56, Ruben Astudillo wrote: > > On 19-09-19 22:17, Alexandre Esteves wrote: > > I do like the sound of `instance Foldable1 Set1` more than > I do `instance NonEmptyFoldable NonEmptySet` > > > > I prefer it too, I just wish (future) documentation included a > little explanation on why the suffix 1 was put. > > ------------------------------------------------------------------------ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > > -- > Sent from my phone with K-9 Mail. > > _______________________________________________ > 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 lysxia at gmail.com Sun Oct 20 19:25:24 2019 From: lysxia at gmail.com (Li-yao Xia) Date: Sun, 20 Oct 2019 15:25:24 -0400 Subject: Proposal: Laws for mtl classes Message-ID: <7393a1ef-9347-b369-990e-9892acced0ad@gmail.com> Hello Libraries, Some time ago I proposed some laws for the most common mtl classes (State, Reader, Error): https://mail.haskell.org/pipermail/libraries/2019-April/029549.html To address some concerns about completeness I reorganized the laws into groups describing more high-level properties, and formalized them in Coq to ensure the laws are strong enough to lift themselves through common transformers (StateT, ExceptT, ContT; ReaderT and WriterT are similar to StateT, but formalizing that relationship also makes the laws interact in interesting ways). I'm open to suggestions for better ways to verify the "completeness" of the laws. However, as long there aren't any objections to the existing laws themselves, it still seems worth having some documentation earlier rather than never. In the end the actual changes to the initial proposal were quite minor. Feel free to weigh in on the following pull requests: https://github.com/haskell/mtl/pull/61 (MonadReader, MonadState) https://github.com/haskell/mtl/pull/62 (MonadError) --- # Changes 1. Three laws were added, In MonadReader, > local id = id to complete the property that local is a monoid homomorphism (rather than only semigroup); thanks to Andreas Abel for pointing out its absence in the initial proposal. > local f u = ask >>= \s -> local (\_ -> f s) u This law was necessary to verify ContT's MonadReader instance. ContT is not actually lawful, but a certain subset of it seems to be (the elements of ContT that satisfy the commutativity of ask). I did not manage to find out whether it's implied by the other laws. In MonadError, a naturality law > fmap f (catchError u h) = catchError (fmap f u) (fmap f . h) whose need arose when describing the relationship between StateT's and ReaderT's instances. 2. Another finding is the fact that, much like the laws of MonadState are equivalent to saying that 'state' is a monad morphism, the 'ask' fragment of MonadReader (which to many *is* MonadReader) can also be characterized by a monad morphism, which cannot be 'reader', as it only yields two of the 'ask' laws. 3. There were two mistakes in the original proposal. One MonadError law was too strong: > catchError (m >>= k) h = tryError m >>= either h k -- broken by StateT And local should flip the order of composition > local g . local f = local (g . f) -- wrong > local g . local f = local (f . g) -- right --- # Updated proposal ## MonadState > get >>= put = pure () > put s >> get = put s >> pure s > put s1 >> put s2 = put s2 Those three laws imply the following equations expressing that get has no side effects: > get >> m = m > get >>= \s1 -> get >>= \s2 -> k s1 s2 = get >>= \s -> k s s state must be equivalent to its default definition in terms of get and put, and conversely. Under that last condition, a property which is equivalent to the laws above is that state must be a monad morphism, from State s to m. --- ## MonadReader ask has no side effects, and produces the same result at any time. > ask >> m = m > ask >>= \s1 -> ask >>= \s2 -> k s1 s2 = ask >>= \s -> k s s > > m <*> ask = ask <**> m local f applies f to the environment produced by ask. > local f ask = f <$> ask > local f u = ask >>= \s -> local (\_ -> f s) u local is a monoid morphism from (r -> r) to (reversed) (m a -> m a) (i.e., (Endo r -> Dual (Endo (m a)))). > local id = id > local g . local f = local (f . g) local is a monad morphism from m to m. > local f (pure x) = pure x > local f (a >>= k) = local f a >>= \x -> local f (k x) reader must be equivalent to its default definition in terms of ask, and conversely. Under that last condition, a property which is equivalent to the first two laws is that reader must be a monad morphism from Reader r to m. Another property equivalent to the first three laws is that there is a monad morphism phi :: forall a. ReaderT r m a -> m a such that phi ask = ask and phi . lift = id. --- ## MonadError See also Exceptionally Monadic Error Handling, by Jan Malakhovski: https://arxiv.org/abs/1810.13430 catchError and throwError form a monad, with (>>=) interpreted as catchError and pure as throwError. > catchError (throwError e) h = h e > catchError m throwError = m > catchError (catchError m k) h = catchError m (\e -> catchError (k e) h) pure and throwError are left zeros for catchError and (>>=) respectively. > catchError (pure a) h = pure a > throwError e >>= k = throwError e catchError commutes with fmap (it is a natual transformation). > fmap f (catchError u h) = catchError (fmap f u) (fmap f . h) --- Li-yao Xia From lysxia at gmail.com Sun Oct 20 19:27:07 2019 From: lysxia at gmail.com (Li-yao Xia) Date: Sun, 20 Oct 2019 15:27:07 -0400 Subject: Proposal: Laws for mtl classes In-Reply-To: <7393a1ef-9347-b369-990e-9892acced0ad@gmail.com> References: <7393a1ef-9347-b369-990e-9892acced0ad@gmail.com> Message-ID: And I forgot to link to the Coq development for the curious ones: https://github.com/Lysxia/coq-mtl On 10/20/19 3:25 PM, Li-yao Xia wrote: > Hello Libraries, > > Some time ago I proposed some laws for the most common mtl classes > (State, Reader, Error): > https://mail.haskell.org/pipermail/libraries/2019-April/029549.html > > To address some concerns about completeness I reorganized the laws into > groups describing more high-level properties, and formalized them in Coq > to ensure the laws are strong enough to lift themselves through common > transformers (StateT, ExceptT, ContT; ReaderT and WriterT are similar to > StateT, but formalizing that relationship also makes the laws interact > in interesting ways). > > I'm open to suggestions for better ways to verify the "completeness" of > the laws. However, as long there aren't any objections to the existing > laws themselves, it still seems worth having some documentation earlier > rather than never. > > In the end the actual changes to the initial proposal were quite minor. > Feel free to weigh in on the following pull requests: > > https://github.com/haskell/mtl/pull/61 (MonadReader, MonadState) > https://github.com/haskell/mtl/pull/62 (MonadError) > > --- > > # Changes > > 1. Three laws were added, > > In MonadReader, > > > local id = id > > to complete the property that local is a monoid homomorphism (rather > than only semigroup); thanks to Andreas Abel for pointing out its > absence in the initial proposal. > > > > local f u     =   ask >>= \s -> local (\_ -> f s) u > > This law was necessary to verify ContT's MonadReader instance. ContT is > not actually lawful, but a certain subset of it seems to be (the > elements of ContT that satisfy the commutativity of ask). > > I did not manage to find out whether it's implied by the other laws. > > > In MonadError, a naturality law > > > fmap f (catchError u h) = catchError (fmap f u) (fmap f . h) > > whose need arose when describing the relationship between StateT's and > ReaderT's instances. > > > 2. Another finding is the fact that, much like the laws of MonadState > are equivalent to saying that 'state' is a monad morphism, the 'ask' > fragment of MonadReader (which to many *is* MonadReader) can also be > characterized by a monad morphism, which cannot be 'reader', as it only > yields two of the 'ask' laws. > > > 3. There were two mistakes in the original proposal. > > One MonadError law was too strong: > > > catchError (m >>= k) h = tryError m >>= either h k   -- broken by StateT > > And local should flip the order of composition > > > local g . local f = local (g . f)  -- wrong > > local g . local f = local (f . g)  -- right > > --- > > # Updated proposal > > ## MonadState > > > get    >>= put    = pure () > > put s  >>  get    = put s >> pure s > > put s1 >>  put s2 = put s2 > > Those three laws imply the following equations expressing that get has > no side effects: > > > get >> m   =   m > > get >>= \s1 -> get >>= \s2 -> k s1 s2   =   get >>= \s -> k s s > > state must be equivalent to its default definition in terms of get and > put, and conversely. Under that last condition, a property which is > equivalent to the laws above is that state must be a monad morphism, > from State s to m. > > --- > > ## MonadReader > > ask has no side effects, and produces the same result at any time. > > > ask >> m    =   m > > ask >>= \s1 -> ask >>= \s2 -> k s1 s2   =   ask >>= \s -> k s s > > > > m <*> ask   =   ask <**> m > > local f applies f to the environment produced by ask. > > > local f ask   =   f <$> ask > > local f u     =   ask >>= \s -> local (\_ -> f s) u > > local is a monoid morphism from (r -> r) to (reversed) (m a -> m a) > (i.e., (Endo r -> Dual (Endo (m a)))). > > > local id          = id > > local g . local f = local (f . g) > > local is a monad morphism from m to m. > > > local f (pure x)   =  pure x > > local f (a >>= k)  =  local f a >>= \x -> local f (k x) > > reader must be equivalent to its default definition in terms of ask, and > conversely. > > Under that last condition, a property which is equivalent to the first > two laws is that reader must be a monad morphism from Reader r to m. > > Another property equivalent to the first three laws is that there is a > monad morphism phi :: forall a. ReaderT r m a -> m a such that phi ask = > ask and phi . lift = id. > > --- > > ## MonadError > > See also Exceptionally Monadic Error Handling, by Jan Malakhovski: > https://arxiv.org/abs/1810.13430 > > catchError and throwError form a monad, with (>>=) interpreted as > catchError and pure as throwError. > > > catchError (throwError e) h   = h e > > catchError m throwError       = m > > catchError (catchError m k) h = catchError m (\e -> catchError (k e) h) > > pure and throwError are left zeros for catchError and (>>=) respectively. > > > catchError (pure a) h         = pure a > > throwError e >>= k            = throwError e > > catchError commutes with fmap (it is a natual transformation). > > > fmap f (catchError u h)       = catchError (fmap f u) (fmap f . h) > > > --- > > Li-yao Xia From oleg.grenrus at iki.fi Sun Oct 20 21:31:56 2019 From: oleg.grenrus at iki.fi (Oleg Grenrus) Date: Mon, 21 Oct 2019 00:31:56 +0300 Subject: Add Data.Foldable1 to base In-Reply-To: <431b2ab2-d7df-d7f2-602d-15bcebdd36ed@iki.fi> References: <431b2ab2-d7df-d7f2-602d-15bcebdd36ed@iki.fi> Message-ID: <8f9f14e8-72ea-836d-0a79-97563a308529@iki.fi> This is second revision of proposal. Thanks to all commented so far. The changes from the first revision are - Remove `toNonEmpty` from MINIMAL pragma (implementation driven, it seems to be a bad idea to go via toNonEmpty) - Add `Semifoldable` naming-scheme alternative (see sections at the end) - Discuss `Bifoldable1` - Discuss `foldr1` inefficiency - Migration plan for `tagged` and `bifunctors` - PoC patch to `semigroupoids` - `foldable1` package has doctest examples, and a test-suite - more members are manually implemented (and tested) - haddocks regenerated to reflect current state of `foldable1`-package I set the deadline for discussion in two weeks, ending Monday 2019-11-04. - Oleg Add Foldable1 to base ===================== Motivation ---------- It's regularly asked whether `Foldable1` could be added to `base` (e.g. on reddit[^ref1], there're also GHC issue[^ref2] and old phabricator diff[^ref3]) Also there's work towards non-empty maps and sets[^ref4], which would benefit from `Foldable1`. Recently `nonempty-vector` was upload to Hackage as well[^refV]. As commented on reddit, `Foldable1` could be added without any pain to the `base` as it's pure addition - no modifications needed in existing modules. [^ref1]: https://www.reddit.com/r/haskell/comments/6d0vgt/could_we_have_foldable1_and_traversable1_in_base/ [^ref2]: https://gitlab.haskell.org/ghc/ghc/issues/13573 [^ref3]: https://phabricator.haskell.org/D4812 [^ref4]: https://github.com/haskell/containers/pull/616 [^refV]: https://hackage.haskell.org/package/nonempty-vector Changelog --------- - Remove `toNonEmpty` from MINIMAL pragma - Add `Semifoldable` naming-scheme alternative (see sections at the end) - Discuss `Bifoldable1` - Discuss `foldr1` inefficiency - Migration plan for `tagged` and `bifunctors` - PoC patch to `semigroupoids` - `foldable1` package has doctest examples, and a test-suite - more members are manually implemented (and tested) - haddocks regenerated to reflect current state of `foldable1`-package Change: Foldable1 ----------------- The change exist as merge request[^ghcMR] on gitlab.haskell.org. However the more up to date version of a proposed module is visible from haddocks on     https://oleg.fi/haddocks/foldable1/Data-Foldable1.html or     http://oleg.fi/haddocks/semifoldable/Data-Semifoldable.html Importantly, this change **doesn't change** anything in other modules of `base`, except of adding a `Foldable` instance to `Data.Complex`. In particular, `foldl1` and `foldr1` in `Data.Foldable` remain partial, etc. My version of `Foldable1` class is big, so I'll comment the motivation for each member ```haskell class Foldable t => Foldable1 t where     {-# MINIMAL foldMap1 | foldr1map #-}     fold1 :: Semigroup m => t m -> m     -- the defining member, like foldMap but only asking for Semigroup     foldMap1 :: Semigroup m => (a -> m) -> t a -> m     -- strict foldMap1, cf foldMap'     foldMap1' :: Semigroup m => (a -> m) -> t a -> m     -- analogue of toList     toNonEmpty :: t a -> NonEmpty a     -- left&right, strict&non-strict folds     foldr1  :: (a -> a -> a) -> t a -> a     foldr1' :: (a -> a -> a) -> t a -> a     foldl1  :: (a -> a -> a) -> t a -> a     foldl1' :: (a -> a -> a) -> t a -> a     -- these can have efficient implementation for NonEmptySet     maximum1 :: forall a. Ord a => t a -> a     minimum1 :: forall a. Ord a => t a -> a     -- head1 have efficient implementation for NonEmpty and Tree     -- last1 for symmetry     head1 :: t a -> a     last1 :: t a -> a     -- fold variants with premap.     -- Without this map, we cannot implement foldl using foldr etc.     -- These will probably change, see foldr1 inefficiency section     foldr1Map  :: (a -> b) -> (b -> b -> b) -> t a -> b     foldl1'Map :: (a -> b) -> (b -> b -> b) -> t a -> b     foldl1Map  :: (a -> b) -> (b -> b -> b) -> t a -> b     foldr1'Map :: (a -> b) -> (b -> b -> b) -> t a -> b ``` The merge request also adds instances for everything non-empty in `base`. I propose the `Data.Foldable1` as the module name (an alternative `Data.Semifoldable`). `semigroupoids`[^semigroupoids] uses `Data.Semigroup.Foldable`, but it's confusing; and using different name could help migration. Additionally, the `Data.Foldable1` module contains five top-level functions, which should be self-explanatory: ```haskell intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a ``` This is less than in `Data.Semigroup.Foldable`[^d.s.foldable], as other top-level definitions doesn't make sense without bringing in the `Apply` type-class.  For example: ```haskell -- needs Apply, not in Data.Foldable1 traverse1_ :: (Foldable1 t, Apply f) => (a -> f b) -> t a -> f () ``` And if we relax `Apply` to `Applicative`, we get `traverse_`. Bringing `Apply` into `base` is out-of-scope of this proposal. [^ghcMR]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 [^semigroupoids]: https://hackage.haskell.org/package/semigroupoids [^d.s.foldable]: https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-Foldable-Class.html Bifoldable1 ----------- `Bifoldable` class have `Bifoldable1` subclass in `semigroupoids`. We could move that class into `base` as well, but it's not strictly necessary, as it can be done later too. However, `Bifoldable1` should migrate to `bifunctors` package. This is discussed in "Compatibility & migration" section. Name controversy ---------------- Adding `Foldable1` is considered controversial. Library submissions guidelines say: > Adding a new, useful function under a clear name is probably not controversial Yet in this case, there doesn't seem to be clear names. The alternative naming scheme is discussed on `semigroupoids` issue tracker[^naming-issue]. In a comment nickname chessai list a table of possible renamings, essentially dropping `1`-suffix and adding `semi`- prefix.[^refComment1] Following comments brainstorm more ideas like: - all the functions that aren't actual typeclass methods could possibly just   keep the `1` suffix - i'm struggling against consistency here, because some functions sound great   with `semi`- as their prefix, and some sound bad The bad sounding names are `semihead`, `semilast`, `semimaximum` and `semiminimum`. In theory they could be prefixless and suffixless, i.e. plain `head`, `last`, `maximum`, and `minimum`. However, I consider that naming more controversial, as it clashes with `Prelude` names, even one can argue that `Semifoldable` members should eventually replace them. Luckily, the names can be changed, if they are on the way into `Prelude`. A variation of this, is to use bare `s` as prefix to the members, i.e. `sfoldMap`, `sfoldr`. It's shorter, but maybe too subtle? One justification to not use 1-suffix name is[^refComment2] > The 1 is still in conflict, but requires more Eq1, etc like classes to > define. e.g. Monoid1 for taking a monoid to a monoid, then Foldable1 > consistently in that nomenclature would let you reduce through a Monoid1. Also using qualified imports would prevent `Foldable1` class to be ever imported unqualified[^refComment3]: > The haddocks for Semi.Monad being a superclass of Monad someday in the far > flung future would be frankly pretty awful to read, and would ensure that > they could never move into Prelude, forever dooming them to a second class > existence. And finally, trying to unify `Foldable` with `Foldable1` into single class using type families / some hackery requires `QuantifiedConstraints` at the very least. That's not a realistic option to current, essentially a Haskell98 formulation. [^naming-issue]: https://github.com/ekmett/semigroupoids/issues/26 [^refComment1]: https://github.com/ekmett/semigroupoids/issues/26#issuecomment-395565772 [^refComment2]: https://github.com/ekmett/semigroupoids/issues/26#issuecomment-395950042 [^refComment3]: https://github.com/ekmett/semigroupoids/issues/26#issuecomment-398117218 Inefficiency of foldr1 ---------------------- In another `semigroupoids` issue[^foldr1-issue], the inefficiency of `foldr1` is highlighted. My original proposal included functions of the type: ```haskell foldr1Map :: (a -> b) -> (b -> b -> b) -> t a -> b ``` Yet, Andrew Martin points out, another better type: ```haskell foldr1Map :: (a -> b) -> (a -> b -> b) -> t a -> b ``` This helps differentiate between foldr and foldl variants, and also simplifies some implementation bits (to my surprise). I'm in favour of this change. The order of function arguments is chosen so: ```haskell foldr1 = foldr1Map id ``` This variant is implemented in a PR in my repository[^foldrPR]. But not yet incorporated into this proposal. [^foldr1-issue]: https://github.com/ekmett/semigroupoids/issues/77 [^foldrPR]: https://github.com/phadej/foldable1/pull/7 Compatibility & migration ------------------------- I drafted a compatibility package `foldable1`: - GitHub repository:    https://github.com/phadej/foldable1 - haddocks:             https://oleg.fi/haddocks/foldable1/ - Semifoldable variant: https://github.com/phadej/foldable1/pull/5 - its haddocks:         https://oleg.fi/haddocks/semifoldable/ which I hope could be maintained under github.com/haskell organization. I can act as a maintainer, with a hope that there won't be a lot of changes happening in `Data.Foldable1`. To my surprise, there's already a package with this name on Hackage[^hackageFoldable] by M Farkas-Dyck (cc'd). He kindly offered to donate the name if this proposal is accepted (with foldable1 name).[^refDonate] `Data.Foldable1` contains also instances for `Lift`, `Backwards` and `Reverse`, and other data types from `transformers`. Perfectly, the `transformers` bundled with GHC with this change would implement the instances as well. This change should propage to `transformers-compat` too. Similarly, `containers` would have an instance for `Tree` (and non-empty `Set` and `Map` when they are added). Other packages would be compat'd as follows: - `foldable1` would provide instances for `Tagged` from `tagged` - `Bifoldable1` class would migrate to `bifunctors` This is because current dependencies are: ``` semigroups <- tagged <- bifunctors <- semigroupoids ``` and `foldable1` would be more natural between `tagged` and `bifunctors`: ``` semigroups <- tagged <- foldable1 <- bifunctors <- semigroupoids ``` `foldable` have to be before `bifunctors` in the dependency tree, as `Bifoldable1` instances of some `Bifunctor`s need `Foldable1` class. I also drafted a PR for compatibility patch to `semigroupoids`[^semigroupoidsPatch] including `Foldable1` part; but doesn't include migrating `Bifoldable, nor other proposed renaming. The rest of renamings is straight-forward should be straight-forward to do. Migration `Bifoldable` would be a lot easier, when the `foldable1` package interface is stabilized. [^hackageFoldable]: https://hackage.haskell.org/package/foldable1 [^refDonate]: https://mail.haskell.org/pipermail/libraries/2019-October/030029.html [^semigroupoidsPatch]: https://github.com/ekmett/semigroupoids/pull/87 Unresolved questions -------------------- - The names? Foldable1 or Semifoldable, members?     - Bifoldable1 or Bisemifoldable (or Semibifoldable)?     - Members: `semifoldMap` or just `sfoldMap`?   See following Foldable1 and Semifoldable sections for synopsis - Which type signature `foldr1Map` / `semifoldr1Map` should have (`a -> b -> b` is IMO better) - GHC-8.10 freeze is quite soon, is targeting GHC-8.12/base-4.15 more realistic.   Note: this technically is a non-breaking change in `base`,   so could be bundled with GHC-8.10.2, but I think sticking to major would be   preferable by GHC HQ. Appendix: Foldable1 synopsis ---------------------------- https://oleg.fi/haddocks/foldable1/Data-Foldable1.html ```haskell class Foldable t => Foldable1 t where   fold1      :: Semigroup m => t m -> m   foldMap1   :: Semigroup m => (a -> m) -> t a -> m   foldMap1'  :: Semigroup m => (a -> m) -> t a -> m   foldr1     :: (a -> a -> a) -> t a -> a   foldr1'    :: (a -> a -> a) -> t a -> a   foldl1     :: (a -> a -> a) -> t a -> a   foldl1'    :: (a -> a -> a) -> t a -> a   toNonEmpty :: t a -> NonEmpty a   maximum1   :: forall a. Ord a => t a -> a   minimum1   :: forall a. Ord a => t a -> a   head1      :: t a -> a   last1      :: t a -> a   foldr1Map  :: (a -> b) -> (b -> b -> b) -> t a -> b   foldl1'Map :: (a -> b) -> (b -> b -> b) -> t a -> b   foldl1Map  :: (a -> b) -> (b -> b -> b) -> t a -> b   foldr1'Map :: (a -> b) -> (b -> b -> b) -> t a -> b intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m foldrM1      :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1      :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a maximum1By   :: Foldable1 t => (a -> a -> Ordering) -> t a -> a minimum1By   :: Foldable1 t => (a -> a -> Ordering) -> t a -> a ``` Appendix: Semifoldable synopsis ------------------------------- https://oleg.fi/haddocks/semifoldable/ ```haskell class Foldable t => Semifoldable t where   semifold      :: Semigroup m => t m -> m   semifoldMap   :: Semigroup m => (a -> m) -> t a -> m   semifoldMap'  :: Semigroup m => (a -> m) -> t a -> m   semifoldr     :: (a -> a -> a) -> t a -> a   semifoldr'    :: (a -> a -> a) -> t a -> a   semifoldl     :: (a -> a -> a) -> t a -> a   semifoldl'    :: (a -> a -> a) -> t a -> a   toNonEmpty    :: t a -> NonEmpty a   semimaximum   :: forall a. Ord a => t a -> a   semiminimum   :: forall a. Ord a => t a -> a   semihead      :: t a -> a   semilast      :: t a -> a   semifoldrMap  :: (a -> b) -> (b -> b -> b) -> t a -> b   semifoldl'Map :: (a -> b) -> (b -> b -> b) -> t a -> b   semifoldlMap  :: (a -> b) -> (b -> b -> b) -> t a -> b   semifoldr'Map :: (a -> b) -> (b -> b -> b) -> t a -> b intercalate1  :: (Semifoldable t, Semigroup m) => m -> t m -> m foldrM1       :: (Semifoldable t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1       :: (Semifoldable t, Monad m) => (a -> a -> m a) -> t a -> m a semimaximumBy :: Semifoldable t => (a -> a -> Ordering) -> t a -> a semiminimumBy :: Semifoldable t => (a -> a -> Ordering) -> t a -> a -- or alternatively semiintercalate semifoldrM semifoldlM ``` Appendix: Alternative foldr1Map ------------------------------- ```haskell class Foldable t => Foldable1 t where   fold1      :: Semigroup m => t m -> m   foldMap1   :: Semigroup m => (a -> m) -> t a -> m   foldMap1'  :: Semigroup m => (a -> m) -> t a -> m   foldr1     :: (a -> a -> a) -> t a -> a   foldr1'    :: (a -> a -> a) -> t a -> a   foldl1     :: (a -> a -> a) -> t a -> a   foldl1'    :: (a -> a -> a) -> t a -> a   toNonEmpty :: t a -> NonEmpty a   maximum1   :: forall a. Ord a => t a -> a   minimum1   :: forall a. Ord a => t a -> a   head1      :: t a -> a   last1      :: t a -> a   -- These four are changed compared to Foldable1 synopsis   foldr1Map  :: (a -> b) -> (a -> b -> b) -> t a -> b   foldl1'Map :: (a -> b) -> (b -> a -> b) -> t a -> b   foldl1Map  :: (a -> b) -> (b -> a -> b) -> t a -> b   foldr1'Map :: (a -> b) -> (a -> b -> b) -> t a -> b intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m foldrM1      :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1      :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a maximum1By   :: Foldable1 t => (a -> a -> Ordering) -> t a -> a minimum1By   :: Foldable1 t => (a -> a -> Ordering) -> t a -> a ``` > _______________________________________________ > 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 Oct 20 21:35:13 2019 From: zemyla at gmail.com (Zemyla) Date: Sun, 20 Oct 2019 16:35:13 -0500 Subject: Proposal: Laws for mtl classes In-Reply-To: References: <7393a1ef-9347-b369-990e-9892acced0ad@gmail.com> Message-ID: There should be at least some laws for callCC. Obvious ones: * callCC (const m) = m This one says callCC itself has no side effects other than passing the continuation to the provided function. * callCC f = callCC (f . fmap absurd) This says that the return type of the continuation is effectively m Void, so it will never actually "return". * callCC ($ a) = pure a The continuation given returns the value passed to it, and not a different one. It could also probably be expanded to: * callCC ((>>=) m) = m One I'm not as sure about: * callCC (\k -> f k >>= (\a -> k a >>= g)) = callCC (\k -> f (fmap absurd . k) >>= (fmap absurd . k)) A more precise and probably more checkable way of saying that the continuation given doesn't actually return (in other words, it's a left zero for (>>=)), but I'm not sure if it always holds. I'm pretty sure it does, though, because if f uses k at any point, then it would have already returned, by induction on f and the ((>>=) m), ($ a), and (const m) base cases. Incidentally, if you have the MonadCont, MonadReader, MonadState, or MonadWriter operations with a type that only is a Bind (from semigroupoids), then you can prove it's an Applicative and Monad as well: * callCC ($ a) = pure a * a <$ ask = pure a * a <$ get = pure a * a <$ tell mempty = pure a But I don't see how you can with MonadError, though. On Sun, Oct 20, 2019, 14:27 Li-yao Xia wrote: > And I forgot to link to the Coq development for the curious ones: > https://github.com/Lysxia/coq-mtl > > On 10/20/19 3:25 PM, Li-yao Xia wrote: > > Hello Libraries, > > > > Some time ago I proposed some laws for the most common mtl classes > > (State, Reader, Error): > > https://mail.haskell.org/pipermail/libraries/2019-April/029549.html > > > > To address some concerns about completeness I reorganized the laws into > > groups describing more high-level properties, and formalized them in Coq > > to ensure the laws are strong enough to lift themselves through common > > transformers (StateT, ExceptT, ContT; ReaderT and WriterT are similar to > > StateT, but formalizing that relationship also makes the laws interact > > in interesting ways). > > > > I'm open to suggestions for better ways to verify the "completeness" of > > the laws. However, as long there aren't any objections to the existing > > laws themselves, it still seems worth having some documentation earlier > > rather than never. > > > > In the end the actual changes to the initial proposal were quite minor. > > Feel free to weigh in on the following pull requests: > > > > https://github.com/haskell/mtl/pull/61 (MonadReader, MonadState) > > https://github.com/haskell/mtl/pull/62 (MonadError) > > > > --- > > > > # Changes > > > > 1. Three laws were added, > > > > In MonadReader, > > > > > local id = id > > > > to complete the property that local is a monoid homomorphism (rather > > than only semigroup); thanks to Andreas Abel for pointing out its > > absence in the initial proposal. > > > > > > > local f u = ask >>= \s -> local (\_ -> f s) u > > > > This law was necessary to verify ContT's MonadReader instance. ContT is > > not actually lawful, but a certain subset of it seems to be (the > > elements of ContT that satisfy the commutativity of ask). > > > > I did not manage to find out whether it's implied by the other laws. > > > > > > In MonadError, a naturality law > > > > > fmap f (catchError u h) = catchError (fmap f u) (fmap f . h) > > > > whose need arose when describing the relationship between StateT's and > > ReaderT's instances. > > > > > > 2. Another finding is the fact that, much like the laws of MonadState > > are equivalent to saying that 'state' is a monad morphism, the 'ask' > > fragment of MonadReader (which to many *is* MonadReader) can also be > > characterized by a monad morphism, which cannot be 'reader', as it only > > yields two of the 'ask' laws. > > > > > > 3. There were two mistakes in the original proposal. > > > > One MonadError law was too strong: > > > > > catchError (m >>= k) h = tryError m >>= either h k -- broken by > StateT > > > > And local should flip the order of composition > > > > > local g . local f = local (g . f) -- wrong > > > local g . local f = local (f . g) -- right > > > > --- > > > > # Updated proposal > > > > ## MonadState > > > > > get >>= put = pure () > > > put s >> get = put s >> pure s > > > put s1 >> put s2 = put s2 > > > > Those three laws imply the following equations expressing that get has > > no side effects: > > > > > get >> m = m > > > get >>= \s1 -> get >>= \s2 -> k s1 s2 = get >>= \s -> k s s > > > > state must be equivalent to its default definition in terms of get and > > put, and conversely. Under that last condition, a property which is > > equivalent to the laws above is that state must be a monad morphism, > > from State s to m. > > > > --- > > > > ## MonadReader > > > > ask has no side effects, and produces the same result at any time. > > > > > ask >> m = m > > > ask >>= \s1 -> ask >>= \s2 -> k s1 s2 = ask >>= \s -> k s s > > > > > > m <*> ask = ask <**> m > > > > local f applies f to the environment produced by ask. > > > > > local f ask = f <$> ask > > > local f u = ask >>= \s -> local (\_ -> f s) u > > > > local is a monoid morphism from (r -> r) to (reversed) (m a -> m a) > > (i.e., (Endo r -> Dual (Endo (m a)))). > > > > > local id = id > > > local g . local f = local (f . g) > > > > local is a monad morphism from m to m. > > > > > local f (pure x) = pure x > > > local f (a >>= k) = local f a >>= \x -> local f (k x) > > > > reader must be equivalent to its default definition in terms of ask, and > > conversely. > > > > Under that last condition, a property which is equivalent to the first > > two laws is that reader must be a monad morphism from Reader r to m. > > > > Another property equivalent to the first three laws is that there is a > > monad morphism phi :: forall a. ReaderT r m a -> m a such that phi ask = > > ask and phi . lift = id. > > > > --- > > > > ## MonadError > > > > See also Exceptionally Monadic Error Handling, by Jan Malakhovski: > > https://arxiv.org/abs/1810.13430 > > > > catchError and throwError form a monad, with (>>=) interpreted as > > catchError and pure as throwError. > > > > > catchError (throwError e) h = h e > > > catchError m throwError = m > > > catchError (catchError m k) h = catchError m (\e -> catchError (k e) > h) > > > > pure and throwError are left zeros for catchError and (>>=) respectively. > > > > > catchError (pure a) h = pure a > > > throwError e >>= k = throwError e > > > > catchError commutes with fmap (it is a natual transformation). > > > > > fmap f (catchError u h) = catchError (fmap f u) (fmap f . h) > > > > > > --- > > > > Li-yao Xia > _______________________________________________ > 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 John.Ericson at Obsidian.Systems Tue Oct 22 14:51:09 2019 From: John.Ericson at Obsidian.Systems (John Cotton Ericson) Date: Tue, 22 Oct 2019 10:51:09 -0400 Subject: Add Data.Foldable1 to base In-Reply-To: References: <505415F3-D529-4A16-AB78-B514DF6316EA@kent.ac.uk> <443cd353-781d-1ed4-1d56-639a477a19da@iki.fi> <59031523-7353-4000-ABF5-B9BF68B0CF4B@gmail.com> Message-ID: Echoing Keith's point, "semi" to me means a weaker algebra; i.e. a super-class. Foldable => Semifoldable is thus totally wrong, "Semifoldable" is the sub-class. In particular. The Monoid and Semigroup constraints on their respective methods further show that the fold class hierarchy is *contravariant* with respect to the binary operator class hierarchy. Putting semi-* with semi-* only makes sense for something covariant (e.g. the if methods *returned* `Dict (Semigroup a)` etc). Semimonad and Semiapplicative are fine with me (I don't really care, not worth fighting one way or the other) but strong -1 on Semifoldable. John On 10/18/19 12:10 PM, Oleg Grenrus wrote: > Please reply to the "Add Data.Foldable1 to base" -thread to keep the > discussion in one place. > Otherwise this opinion will most likely be ignored. > > - Oleg > > P.S. That said, foldMap1/semifoldMap/... can fold over *less* things. > It can fold over NonEmpty (list) but not over ordinary []. > > On 18.10.2019 18.40, Keith wrote: >> Sorry about bikeshedding. However, 'semifoldable' would be super >> confusing. >> >> If somebody saw 'semifoldMap' in the wild what would they think? >> Probably not that it can fold _more_ things than 'foldMap'. >> >> 'NonemptyFoldable', 'Semigroup.Foldable', 'SemigroupFoldable', and >> 'Foldable1', with 'sfoldMap', 'sgFoldMap', 'nonemptyFoldMap', or >> 'Semigroup.foldMap' may be long or meaningless to most, but at least >> they aren't actively misleading. >> >> –Keith >> >> On October 18, 2019 2:13:51 PM UTC, Oleg Grenrus >> wrote: >> >> Relating to Foldable1/NonEmptyFoldable, based in another discussion (in >> my foldable1 to base proposal), it looks like it might be called >> Semifoldable >> >> Seehttps://mail.haskell.org/pipermail/libraries/2019-October/030030.html >> >> Yet, Semiset is different thing (based on wikipedia: >> https://en.wikipedia.org/wiki/Semiset). NonEmptySet is a good name, it >> doesn't need explanation. If someone feels that it's too long, they can >> introduce `type NESet = NonEmptySet` alias in their development. >> >> - Oleg >> >> On 20.9.2019 4.56, Ruben Astudillo wrote: >> >> On 19-09-19 22:17, Alexandre Esteves wrote: >> >> I do like the sound of `instance Foldable1 Set1` more >> than I do `instance NonEmptyFoldable NonEmptySet` >> >> >> >> I prefer it too, I just wish (future) documentation included >> a little explanation on why the suffix 1 was put. >> >> ------------------------------------------------------------------------ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> >> >> -- >> Sent from my phone with K-9 Mail. >> >> _______________________________________________ >> 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 oleg.grenrus at iki.fi Tue Oct 22 17:07:03 2019 From: oleg.grenrus at iki.fi (Oleg Grenrus) Date: Tue, 22 Oct 2019 20:07:03 +0300 Subject: Add Data.Foldable1 to base In-Reply-To: <8f9f14e8-72ea-836d-0a79-97563a308529@iki.fi> References: <431b2ab2-d7df-d7f2-602d-15bcebdd36ed@iki.fi> <8f9f14e8-72ea-836d-0a79-97563a308529@iki.fi> Message-ID: <620b13a9-a34a-8e4d-6fe2-1a479543f122@iki.fi> To keep committee well equipped to make final decision - Show support or disapproval for both proposed naming schemes (Foldable1 and Semifoldable) - If you don't like either, propose new ones Otherwise these proposal will linger forever "because naming is hard". We can do better. To be explicit, I myself is fine with both naming schemes, and either using semi- or just single s- prefix (e.g. sfoldMap). I encourage everyone to brainstorm the names. The proposal mentions some reasons why Foldable1 is not considered good choice. So if you think Semifoldable is not optimal either, now is good opportunity to make history, by inventing a "contravariant" variant of Semi- prefix. - Oleg On 22.10.2019 17.51, John Cotton Ericson wrote: > > Echoing Keith's point, "semi" to me means a weaker algebra; i.e. a > super-class. Foldable => Semifoldable is thus totally wrong, > "Semifoldable" is the sub-class. In particular. The Monoid and > Semigroup constraints on their respective methods further show that > the fold class hierarchy is *contravariant* with respect to the binary > operator class hierarchy. Putting semi-* with semi-* only makes sense > for something covariant (e.g. the if methods *returned* `Dict > (Semigroup a)` etc). > > Semimonad and Semiapplicative are fine with me (I don't really care, > not worth fighting one way or the other) but strong -1 on Semifoldable. > > John On 21.10.2019 0.31, Oleg Grenrus wrote: > > This is second revision of proposal. Thanks to all commented so far. > > The changes from the first revision are > > - Remove `toNonEmpty` from MINIMAL pragma (implementation driven, it > seems to be a bad idea to go via toNonEmpty) > - Add `Semifoldable` naming-scheme alternative (see sections at the end) > - Discuss `Bifoldable1` > - Discuss `foldr1` inefficiency > - Migration plan for `tagged` and `bifunctors` > - PoC patch to `semigroupoids` > - `foldable1` package has doctest examples, and a test-suite > - more members are manually implemented (and tested) > - haddocks regenerated to reflect current state of `foldable1`-package > > I set the deadline for discussion in two weeks, ending Monday 2019-11-04. > > - Oleg > > > Add Foldable1 to base > ===================== > > Motivation > ---------- > > It's regularly asked whether `Foldable1` could be added to `base` > (e.g. on reddit[^ref1], there're also GHC issue[^ref2] and old > phabricator diff[^ref3]) > Also there's work towards non-empty maps and sets[^ref4], > which would benefit from `Foldable1`. > Recently `nonempty-vector` was upload to Hackage as well[^refV]. > > As commented on reddit, `Foldable1` could be added without any pain > to the `base` as it's pure addition - no modifications needed in > existing modules. > > [^ref1]: > https://www.reddit.com/r/haskell/comments/6d0vgt/could_we_have_foldable1_and_traversable1_in_base/ > [^ref2]: https://gitlab.haskell.org/ghc/ghc/issues/13573 > [^ref3]: https://phabricator.haskell.org/D4812 > [^ref4]: https://github.com/haskell/containers/pull/616 > [^refV]: https://hackage.haskell.org/package/nonempty-vector > > Changelog > --------- > > - Remove `toNonEmpty` from MINIMAL pragma > - Add `Semifoldable` naming-scheme alternative (see sections at the end) > - Discuss `Bifoldable1` > - Discuss `foldr1` inefficiency > - Migration plan for `tagged` and `bifunctors` > - PoC patch to `semigroupoids` > - `foldable1` package has doctest examples, and a test-suite > - more members are manually implemented (and tested) > - haddocks regenerated to reflect current state of `foldable1`-package > > Change: Foldable1 > ----------------- > > The change exist as merge request[^ghcMR] on gitlab.haskell.org. > However the more up to date version of a proposed module is visible from > haddocks on > > https://oleg.fi/haddocks/foldable1/Data-Foldable1.html > > or > > http://oleg.fi/haddocks/semifoldable/Data-Semifoldable.html > > Importantly, this change **doesn't change** anything in other modules > of `base`, except of adding a `Foldable` instance to `Data.Complex`. > In particular, `foldl1` and `foldr1` in `Data.Foldable` remain > partial, etc. > > My version of `Foldable1` class is big, so I'll comment the motivation > for each member > > ```haskell > class Foldable t => Foldable1 t where >     {-# MINIMAL foldMap1 | foldr1map #-} > >     fold1 :: Semigroup m => t m -> m > >     -- the defining member, like foldMap but only asking for Semigroup >     foldMap1 :: Semigroup m => (a -> m) -> t a -> m > >     -- strict foldMap1, cf foldMap' >     foldMap1' :: Semigroup m => (a -> m) -> t a -> m > >     -- analogue of toList >     toNonEmpty :: t a -> NonEmpty a > >     -- left&right, strict&non-strict folds >     foldr1  :: (a -> a -> a) -> t a -> a >     foldr1' :: (a -> a -> a) -> t a -> a >     foldl1  :: (a -> a -> a) -> t a -> a >     foldl1' :: (a -> a -> a) -> t a -> a > >     -- these can have efficient implementation for NonEmptySet >     maximum1 :: forall a. Ord a => t a -> a >     minimum1 :: forall a. Ord a => t a -> a > >     -- head1 have efficient implementation for NonEmpty and Tree >     -- last1 for symmetry >     head1 :: t a -> a >     last1 :: t a -> a > >     -- fold variants with premap. >     -- Without this map, we cannot implement foldl using foldr etc. >     -- These will probably change, see foldr1 inefficiency section >     foldr1Map  :: (a -> b) -> (b -> b -> b) -> t a -> b >     foldl1'Map :: (a -> b) -> (b -> b -> b) -> t a -> b >     foldl1Map  :: (a -> b) -> (b -> b -> b) -> t a -> b >     foldr1'Map :: (a -> b) -> (b -> b -> b) -> t a -> b > ``` > > The merge request also adds instances for everything non-empty in `base`. > > I propose the `Data.Foldable1` as the module name (an alternative > `Data.Semifoldable`). > `semigroupoids`[^semigroupoids] uses `Data.Semigroup.Foldable`, > but it's confusing; and using different name could help migration. > > Additionally, the `Data.Foldable1` module contains five top-level > functions, > which should be self-explanatory: > > ```haskell > intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m > > foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a > foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a > > maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a > minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a > ``` > > This is less than in `Data.Semigroup.Foldable`[^d.s.foldable], as other > top-level definitions doesn't make sense without bringing in the `Apply` > type-class.  For example: > > ```haskell > -- needs Apply, not in Data.Foldable1 > traverse1_ :: (Foldable1 t, Apply f) => (a -> f b) -> t a -> f () > ``` > > And if we relax `Apply` to `Applicative`, we get `traverse_`. > Bringing `Apply` into `base` is out-of-scope of this proposal. > > [^ghcMR]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 > [^semigroupoids]: https://hackage.haskell.org/package/semigroupoids > [^d.s.foldable]: > https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-Foldable-Class.html > > Bifoldable1 > ----------- > > `Bifoldable` class have `Bifoldable1` subclass in `semigroupoids`. > We could move that class into `base` as well, but it's not strictly > necessary, > as it can be done later too. > > However, `Bifoldable1` should migrate to `bifunctors` package. > This is discussed in "Compatibility & migration" section. > > Name controversy > ---------------- > > Adding `Foldable1` is considered controversial. > Library submissions guidelines say: > > > Adding a new, useful function under a clear name is probably not > controversial > > Yet in this case, there doesn't seem to be clear names. > The alternative naming scheme is discussed on `semigroupoids` issue > tracker[^naming-issue]. > > In a comment nickname chessai list a table of possible renamings, > essentially dropping `1`-suffix and adding `semi`- prefix.[^refComment1] > Following comments brainstorm more ideas like: > > - all the functions that aren't actual typeclass methods could > possibly just >   keep the `1` suffix > - i'm struggling against consistency here, because some functions > sound great >   with `semi`- as their prefix, and some sound bad > > The bad sounding names are `semihead`, `semilast`, `semimaximum` and > `semiminimum`. In theory they could be prefixless and suffixless, > i.e. plain `head`, `last`, `maximum`, and `minimum`. However, > I consider that naming more controversial, as it clashes with `Prelude` > names, even one can argue that `Semifoldable` members should > eventually replace them. Luckily, the names can be changed, > if they are on the way into `Prelude`. > > A variation of this, is to use bare `s` as prefix to the members, i.e. > `sfoldMap`, `sfoldr`. It's shorter, but maybe too subtle? > > One justification to not use 1-suffix name is[^refComment2] > > > The 1 is still in conflict, but requires more Eq1, etc like classes to > > define. e.g. Monoid1 for taking a monoid to a monoid, then Foldable1 > > consistently in that nomenclature would let you reduce through a > Monoid1. > > Also using qualified imports would prevent `Foldable1` class to be ever > imported unqualified[^refComment3]: > > > The haddocks for Semi.Monad being a superclass of Monad someday in > the far > > flung future would be frankly pretty awful to read, and would ensure > that > > they could never move into Prelude, forever dooming them to a second > class > > existence. > > And finally, trying to unify `Foldable` with `Foldable1` into single class > using type families / some hackery requires `QuantifiedConstraints` at the > very least. That's not a realistic option to current, essentially a > Haskell98 > formulation. > > [^naming-issue]: https://github.com/ekmett/semigroupoids/issues/26 > [^refComment1]: > https://github.com/ekmett/semigroupoids/issues/26#issuecomment-395565772 > [^refComment2]: > https://github.com/ekmett/semigroupoids/issues/26#issuecomment-395950042 > [^refComment3]: > https://github.com/ekmett/semigroupoids/issues/26#issuecomment-398117218 > > Inefficiency of foldr1 > ---------------------- > > In another `semigroupoids` issue[^foldr1-issue], > the inefficiency of `foldr1` is highlighted. > > My original proposal included functions of the type: > > ```haskell > foldr1Map :: (a -> b) -> (b -> b -> b) -> t a -> b > ``` > > Yet, Andrew Martin points out, another better type: > > ```haskell > foldr1Map :: (a -> b) -> (a -> b -> b) -> t a -> b > ``` > > This helps differentiate between foldr and foldl variants, > and also simplifies some implementation bits (to my surprise). > I'm in favour of this change. > > The order of function arguments is chosen so: > > ```haskell > foldr1 = foldr1Map id > ``` > > This variant is implemented in a PR in my repository[^foldrPR]. > But not yet incorporated into this proposal. > > [^foldr1-issue]: https://github.com/ekmett/semigroupoids/issues/77 > [^foldrPR]: https://github.com/phadej/foldable1/pull/7 > > Compatibility & migration > ------------------------- > > I drafted a compatibility package `foldable1`: > > - GitHub repository: https://github.com/phadej/foldable1 > - haddocks: https://oleg.fi/haddocks/foldable1/ > - Semifoldable variant: https://github.com/phadej/foldable1/pull/5 > - its haddocks: https://oleg.fi/haddocks/semifoldable/ > > which I hope could be maintained under github.com/haskell organization. > I can act as a maintainer, with a hope that there won't be a lot > of changes happening in `Data.Foldable1`. > > To my surprise, there's already a package with this name on > Hackage[^hackageFoldable] by > M Farkas-Dyck (cc'd). He kindly offered to donate the name if > this proposal is accepted (with foldable1 name).[^refDonate] > > `Data.Foldable1` contains also instances for `Lift`, `Backwards` and > `Reverse`, > and other data types from `transformers`. Perfectly, the > `transformers` bundled > with GHC with this change would implement the instances as well.  This > change > should propage to `transformers-compat` too. > > Similarly, `containers` would have an instance for `Tree` (and non-empty > `Set` and `Map` when they are added). > > > Other packages would be compat'd as follows: > - `foldable1` would provide instances for `Tagged` from `tagged` > - `Bifoldable1` class would migrate to `bifunctors` > > This is because current dependencies are: > > ``` > semigroups <- tagged <- bifunctors <- semigroupoids > ``` > > and `foldable1` would be more natural between `tagged` and `bifunctors`: > > ``` > semigroups <- tagged <- foldable1 <- bifunctors <- semigroupoids > ``` > > `foldable` have to be before `bifunctors` in the dependency tree, > as `Bifoldable1` instances of some `Bifunctor`s need `Foldable1` class. > > I also drafted a PR for compatibility patch to > `semigroupoids`[^semigroupoidsPatch] > including `Foldable1` part; but doesn't include > migrating `Bifoldable, nor other proposed renaming. > > The rest of renamings is straight-forward should be straight-forward > to do. > Migration `Bifoldable` would be a lot easier, when the `foldable1` package > interface is stabilized. > > [^hackageFoldable]: https://hackage.haskell.org/package/foldable1 > [^refDonate]: > https://mail.haskell.org/pipermail/libraries/2019-October/030029.html > [^semigroupoidsPatch]: https://github.com/ekmett/semigroupoids/pull/87 > > Unresolved questions > -------------------- > > - The names? Foldable1 or Semifoldable, members? >     - Bifoldable1 or Bisemifoldable (or Semibifoldable)? >     - Members: `semifoldMap` or just `sfoldMap`? >   See following Foldable1 and Semifoldable sections for synopsis > - Which type signature `foldr1Map` / `semifoldr1Map` should have (`a > -> b -> b` is IMO better) > - GHC-8.10 freeze is quite soon, is targeting GHC-8.12/base-4.15 more > realistic. >   Note: this technically is a non-breaking change in `base`, >   so could be bundled with GHC-8.10.2, but I think sticking to major > would be >   preferable by GHC HQ. > > Appendix: Foldable1 synopsis > ---------------------------- > > https://oleg.fi/haddocks/foldable1/Data-Foldable1.html > > ```haskell > class Foldable t => Foldable1 t where >   fold1      :: Semigroup m => t m -> m >   foldMap1   :: Semigroup m => (a -> m) -> t a -> m >   foldMap1'  :: Semigroup m => (a -> m) -> t a -> m > >   foldr1     :: (a -> a -> a) -> t a -> a >   foldr1'    :: (a -> a -> a) -> t a -> a >   foldl1     :: (a -> a -> a) -> t a -> a >   foldl1'    :: (a -> a -> a) -> t a -> a > >   toNonEmpty :: t a -> NonEmpty a > >   maximum1   :: forall a. Ord a => t a -> a >   minimum1   :: forall a. Ord a => t a -> a >   head1      :: t a -> a >   last1      :: t a -> a > >   foldr1Map  :: (a -> b) -> (b -> b -> b) -> t a -> b >   foldl1'Map :: (a -> b) -> (b -> b -> b) -> t a -> b >   foldl1Map  :: (a -> b) -> (b -> b -> b) -> t a -> b >   foldr1'Map :: (a -> b) -> (b -> b -> b) -> t a -> b > > intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m > foldrM1      :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a > foldlM1      :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a > maximum1By   :: Foldable1 t => (a -> a -> Ordering) -> t a -> a > minimum1By   :: Foldable1 t => (a -> a -> Ordering) -> t a -> a > ``` > > Appendix: Semifoldable synopsis > ------------------------------- > > https://oleg.fi/haddocks/semifoldable/ > > ```haskell > class Foldable t => Semifoldable t where >   semifold      :: Semigroup m => t m -> m >   semifoldMap   :: Semigroup m => (a -> m) -> t a -> m >   semifoldMap'  :: Semigroup m => (a -> m) -> t a -> m > >   semifoldr     :: (a -> a -> a) -> t a -> a >   semifoldr'    :: (a -> a -> a) -> t a -> a >   semifoldl     :: (a -> a -> a) -> t a -> a >   semifoldl'    :: (a -> a -> a) -> t a -> a > >   toNonEmpty    :: t a -> NonEmpty a > >   semimaximum   :: forall a. Ord a => t a -> a >   semiminimum   :: forall a. Ord a => t a -> a >   semihead      :: t a -> a >   semilast      :: t a -> a > >   semifoldrMap  :: (a -> b) -> (b -> b -> b) -> t a -> b >   semifoldl'Map :: (a -> b) -> (b -> b -> b) -> t a -> b >   semifoldlMap  :: (a -> b) -> (b -> b -> b) -> t a -> b >   semifoldr'Map :: (a -> b) -> (b -> b -> b) -> t a -> b > > intercalate1  :: (Semifoldable t, Semigroup m) => m -> t m -> m > foldrM1       :: (Semifoldable t, Monad m) => (a -> a -> m a) -> t a > -> m a > foldlM1       :: (Semifoldable t, Monad m) => (a -> a -> m a) -> t a > -> m a > semimaximumBy :: Semifoldable t => (a -> a -> Ordering) -> t a -> a > semiminimumBy :: Semifoldable t => (a -> a -> Ordering) -> t a -> a > > -- or alternatively > semiintercalate > semifoldrM > semifoldlM > ``` > > Appendix: Alternative foldr1Map > ------------------------------- > > ```haskell > class Foldable t => Foldable1 t where >   fold1      :: Semigroup m => t m -> m >   foldMap1   :: Semigroup m => (a -> m) -> t a -> m >   foldMap1'  :: Semigroup m => (a -> m) -> t a -> m > >   foldr1     :: (a -> a -> a) -> t a -> a >   foldr1'    :: (a -> a -> a) -> t a -> a >   foldl1     :: (a -> a -> a) -> t a -> a >   foldl1'    :: (a -> a -> a) -> t a -> a > >   toNonEmpty :: t a -> NonEmpty a > >   maximum1   :: forall a. Ord a => t a -> a >   minimum1   :: forall a. Ord a => t a -> a >   head1      :: t a -> a >   last1      :: t a -> a > >   -- These four are changed compared to Foldable1 synopsis >   foldr1Map  :: (a -> b) -> (a -> b -> b) -> t a -> b >   foldl1'Map :: (a -> b) -> (b -> a -> b) -> t a -> b >   foldl1Map  :: (a -> b) -> (b -> a -> b) -> t a -> b >   foldr1'Map :: (a -> b) -> (a -> b -> b) -> t a -> b > > intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m > foldrM1      :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a > foldlM1      :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a > maximum1By   :: Foldable1 t => (a -> a -> Ordering) -> t a -> a > minimum1By   :: Foldable1 t => (a -> a -> Ordering) -> t a -> a > ``` > >> _______________________________________________ >> 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 lemming at henning-thielemann.de Tue Oct 22 18:34:17 2019 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Tue, 22 Oct 2019 20:34:17 +0200 (CEST) Subject: Add Data.Foldable1 to base In-Reply-To: References: <505415F3-D529-4A16-AB78-B514DF6316EA@kent.ac.uk> <443cd353-781d-1ed4-1d56-639a477a19da@iki.fi> <59031523-7353-4000-ABF5-B9BF68B0CF4B@gmail.com> Message-ID: On Tue, 22 Oct 2019, John Cotton Ericson wrote: > Echoing Keith's point, "semi" to me means a weaker algebra; i.e. a > super-class. Foldable => Semifoldable is thus totally wrong, > "Semifoldable" is the sub-class. me too From godzbanebane at gmail.com Tue Oct 22 19:30:46 2019 From: godzbanebane at gmail.com (Georgi Lyubenov) Date: Tue, 22 Oct 2019 22:30:46 +0300 Subject: Add Data.Foldable1 to base In-Reply-To: References: <505415F3-D529-4A16-AB78-B514DF6316EA@kent.ac.uk> <443cd353-781d-1ed4-1d56-639a477a19da@iki.fi> <59031523-7353-4000-ABF5-B9BF68B0CF4B@gmail.com> Message-ID: +1 for the "not calling it Semifoldable" On Tue, Oct 22, 2019 at 9:34 PM Henning Thielemann < lemming at henning-thielemann.de> wrote: > > On Tue, 22 Oct 2019, John Cotton Ericson wrote: > > > Echoing Keith's point, "semi" to me means a weaker algebra; i.e. a > > super-class. Foldable => Semifoldable is thus totally wrong, > > "Semifoldable" is the sub-class. > > me too > _______________________________________________ > 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 Oct 27 13:47:09 2019 From: zemyla at gmail.com (Zemyla) Date: Sun, 27 Oct 2019 08:47:09 -0500 Subject: Exposed # kinded variables + polykinded Prelude classes? Message-ID: I'm wondering if there would be a benefit, if not to the average programmer, then to the ones working on deeper/faster code, to allow some of the # kinded types (mostly Int#, Word#, Char#, Float#, Double#) to be used in Safe code, and to have typeclasses able to work with them. For instance, the definition of Show would become: class Show (a :: TYPE r) where show :: a -> String default show :: (r ~ 'LiftedRep) => a -> String show x = showsPrec 0 x "" showsPrec :: Int -> a -> ShowS default showsPrec :: (r ~ 'LiftedRep) => Int -> a -> ShowS showsPrec _ x s = show x ++ s showList :: (r ~ 'LiftedRep) => [a] -> ShowS showList ls s = showList__ shows ls s The fact that the defaults only work when the type is a LiftedRep is a nonissue, because there's only a finite number of non-lifted types we'd be defining it for. You could do the same with Eq, Ord, Num, Real, Integral, Fractional, Floating, RealFrac, RealFloat, Semigroup, Monoid, Bits, FiniteBits, and probably several others I can't think of right now. However, with the functions that return pairs, you'd need a version that returns an unboxed pair instead. Assuming you changed ReadPrec, you could even do the same with Read: newtype ReadP (a :: RuntimeRep r) = ReadP (forall b. (a -> R b) -> R b) newtype ReadPrec (a :: RuntimeRep r) = ReadPrec (Int -> ReadP a) IO, ST, and STM could be made polykinded the same way, and would open up Storable. However, how to do a definition for Monad that works for polykinded monads is an issue. I do know that RebindableSyntax handles it easily when there's just one monad that can operate on multiple kinds, though. As for which # types could be exposed, I'm thinking that Char#, Int#, Word#, Float#, Double#, and Proxy# wouldn't be able to break out of Safe code. Int64# and Word64# would work as well, and for 64-bit machines would just be type aliases for Int# and Word# respectively. For types which have functions with undefined behavior for some arguments, you can just make wrappers that check the arguments and error out for the bad values. MutVar#, MVar#, TVar#, and StableName# don't open up any functions that would be unsuitable for safe code, either. I'm pretty sure that Array# and MutableArray# would also be safe, as long as all functions were length-checked and threw errors instead of having undefined behavior. As for why this would be a desirable thing? Mostly for the sake of convenience and generality, I think. I find myself working with unboxed values from time to time, and it's a pain to always remember to use (+#) for Int# and plusWord# for Word#. In addition, having typeclasses that can return unboxed values (like a hypothetical sized# :: Sized a => a -> Int# vs sized :: Sized a => a -> Int) can improve the generated code when the code using the typeclass doesn't get specialized. The module to import these would have to explain the differences between # kinded types and * kinded ones: # values aren't lazy; they can't be top-level definitions; you can't use unboxed tuples or sums with GHCi; and with a few exceptions, you can't place them in containers (you can't have an [Int#], for instance). -------------- next part -------------- An HTML attachment was scrubbed... URL: From chessai1996 at gmail.com Sun Oct 27 20:22:34 2019 From: chessai1996 at gmail.com (chessai .) Date: Sun, 27 Oct 2019 16:22:34 -0400 Subject: Exposed # kinded variables + polykinded Prelude classes? In-Reply-To: References: Message-ID: Just realised i hit reply and not reply all. Here was my email: See https://github.com/chessai/levity and http://hackage.haskell.org/package/unlifted-list. There are a few annoyances due to binder restrictions (see [1]). For example, it is not possible to write polymorphic `bindUnliftedToLifted`: ``` bindUnliftedToLifted :: forall (a :: TYPE r) (b :: TYPE 'LiftedRep). ST s a -> (a -> ST s b) -> ST s b ``` This function is frequently useful when working with monads which have levity-polymorphic parameters, but you cannot write it when a is levity-polymorphic, since it will occur in a binding position. What ends up happening is that you write monomorphic versions of this function for each one you need. Clearly not desirable. The other thing is that levity-polymorphic kinds are (almost?) never inferred. For example, if I have: ``` class Show (a :: TYPE r) where show :: a -> String addNewline :: Show a => a -> String addNewline x = show x ++ "\n" ``` GHC will infer the kind of `a` in `addNewline` to be `TYPE 'LiftedRep`, even though it very well could be `forall (r :: RuntimeRep). TYPE r`. In other words, users will have to constantly kind-annotate because of (over-?)restrictive inference. This becomes annoying rather quickly, and the type errors don't always immediately make it clear what's happening when you miss an annotation. Another thing which is annoying, you can't write things like Monoid or Bounded in the same way! (See also [1]) ``` class Monoid (a :: TYPE r) where mempty :: a ``` GHC will complain about mempty here. You have to instead make it ``` class Monoid (a :: TYPE r) where mempty :: () -> a ``` which just becomes cluttering, your code gets filled with a lot of `mempty ()`. Another thing is that default implementations will not work. You state that it's fine because the number of inhabitants of unlifted kinds is small and finite. This will not be the case in GHC 8.10, when UnliftedNewtypes lands. Then the number of inhabitants becomes non-finite. The ways to use levity-polymorhism which result in the best UX are: 1) CPS, 2) backpack, and 3) resolving [1]. (1) is the easiest to most users right now (see [2] for an example) With all of these drawbacks I'm against having the API of base or any core library really be a place for levity-polymorphic code, especially when talking about core typeclasses/types. Probably best for this to be in userspace. [1]: https://gitlab.haskell.org/ghc/ghc/issues/14917 [2]: http://hackage.haskell.org/package/bytesmith-0.3.0.0/docs/src/Data.Bytes.Parser.Internal.html#Parser On Sun, Oct 27, 2019, 9:47 AM Zemyla wrote: > I'm wondering if there would be a benefit, if not to the average > programmer, then to the ones working on deeper/faster code, to allow some > of the # kinded types (mostly Int#, Word#, Char#, Float#, Double#) to be > used in Safe code, and to have typeclasses able to work with them. > > For instance, the definition of Show would become: > > class Show (a :: TYPE r) where > show :: a -> String > default show :: (r ~ 'LiftedRep) => a -> String > show x = showsPrec 0 x "" > > showsPrec :: Int -> a -> ShowS > default showsPrec :: (r ~ 'LiftedRep) => Int -> a -> ShowS > showsPrec _ x s = show x ++ s > > showList :: (r ~ 'LiftedRep) => [a] -> ShowS > showList ls s = showList__ shows ls s > > The fact that the defaults only work when the type is a LiftedRep is a > nonissue, because there's only a finite number of non-lifted types we'd be > defining it for. > > You could do the same with Eq, Ord, Num, Real, Integral, Fractional, > Floating, RealFrac, RealFloat, Semigroup, Monoid, Bits, FiniteBits, and > probably several others I can't think of right now. However, with the > functions that return pairs, you'd need a version that returns an unboxed > pair instead. Assuming you changed ReadPrec, you could even do the same > with Read: > > newtype ReadP (a :: RuntimeRep r) = ReadP (forall b. (a -> R b) -> R b) > newtype ReadPrec (a :: RuntimeRep r) = ReadPrec (Int -> ReadP a) > > IO, ST, and STM could be made polykinded the same way, and would open up > Storable. However, how to do a definition for Monad that works for > polykinded monads is an issue. I do know that RebindableSyntax handles it > easily when there's just one monad that can operate on multiple kinds, > though. > > As for which # types could be exposed, I'm thinking that Char#, Int#, > Word#, Float#, Double#, and Proxy# wouldn't be able to break out of Safe > code. Int64# and Word64# would work as well, and for 64-bit machines would > just be type aliases for Int# and Word# respectively. For types which have > functions with undefined behavior for some arguments, you can just make > wrappers that check the arguments and error out for the bad values. > MutVar#, MVar#, TVar#, and StableName# don't open up any functions that > would be unsuitable for safe code, either. I'm pretty sure that Array# and > MutableArray# would also be safe, as long as all functions were > length-checked and threw errors instead of having undefined behavior. > > As for why this would be a desirable thing? Mostly for the sake of > convenience and generality, I think. I find myself working with unboxed > values from time to time, and it's a pain to always remember to use (+#) > for Int# and plusWord# for Word#. In addition, having typeclasses that can > return unboxed values (like a hypothetical sized# :: Sized a => a -> Int# > vs sized :: Sized a => a -> Int) can improve the generated code when the > code using the typeclass doesn't get specialized. > > The module to import these would have to explain the differences between # > kinded types and * kinded ones: # values aren't lazy; they can't be > top-level definitions; you can't use unboxed tuples or sums with GHCi; and > with a few exceptions, you can't place them in containers (you can't have > an [Int#], for instance). > _______________________________________________ > 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 Sun Oct 27 21:47:25 2019 From: chessai1996 at gmail.com (chessai .) Date: Sun, 27 Oct 2019 17:47:25 -0400 Subject: Exposed # kinded variables + polykinded Prelude classes? In-Reply-To: References: Message-ID: Regarding UnliftedNewtypes: apparently GND can solve this issue for you. There are som cases where, because of the desugaring, a GND clause will fail, but moving the clause out to a StandaloneDeriving one can fix the issue. But defaults still become annoying for things like Foldable, where most users rely pretty heavily on defaults. On Sun, Oct 27, 2019, 4:22 PM chessai . wrote: > Just realised i hit reply and not reply all. Here was my email: > > See https://github.com/chessai/levity and > http://hackage.haskell.org/package/unlifted-list. > > There are a few annoyances due to binder restrictions (see [1]). > > For example, it is not possible to write polymorphic > `bindUnliftedToLifted`: > > ``` > bindUnliftedToLifted :: forall (a :: TYPE r) (b :: TYPE 'LiftedRep). ST s > a -> (a -> ST s b) -> ST s b > ``` > > This function is frequently useful when working with monads which have > levity-polymorphic parameters, but you cannot write it when a is > levity-polymorphic, since it will occur in a binding position. What ends up > happening is that you write monomorphic versions of this function for each > one you need. Clearly not desirable. > > The other thing is that levity-polymorphic kinds are (almost?) never > inferred. For example, if I have: > > ``` > class Show (a :: TYPE r) where > show :: a -> String > > addNewline :: Show a => a -> String > addNewline x = show x ++ "\n" > ``` > > GHC will infer the kind of `a` in `addNewline` to be `TYPE 'LiftedRep`, > even though it very well could be `forall (r :: RuntimeRep). TYPE r`. In > other words, users will have to constantly kind-annotate because of > (over-?)restrictive inference. This becomes annoying rather quickly, and > the type errors don't always immediately make it clear what's happening > when you miss an annotation. > > Another thing which is annoying, you can't write things like Monoid or > Bounded in the same way! (See also [1]) > > ``` > class Monoid (a :: TYPE r) where > mempty :: a > ``` > > GHC will complain about mempty here. You have to instead make it > > ``` > class Monoid (a :: TYPE r) where > mempty :: () -> a > ``` > > which just becomes cluttering, your code gets filled with a lot of `mempty > ()`. > > Another thing is that default implementations will not work. You state > that it's fine because the number of inhabitants of unlifted kinds is small > and finite. This will not be the case in GHC 8.10, when UnliftedNewtypes > lands. Then the number of inhabitants becomes non-finite. > > The ways to use levity-polymorhism which result in the best UX are: 1) > CPS, 2) backpack, and 3) resolving [1]. (1) is the easiest to most users > right now (see [2] for an example) > > With all of these drawbacks I'm against having the API of base or any core > library really be a place for levity-polymorphic code, especially when > talking about core typeclasses/types. Probably best for this to be in > userspace. > > [1]: https://gitlab.haskell.org/ghc/ghc/issues/14917 > [2]: > http://hackage.haskell.org/package/bytesmith-0.3.0.0/docs/src/Data.Bytes.Parser.Internal.html#Parser > > On Sun, Oct 27, 2019, 9:47 AM Zemyla wrote: > >> I'm wondering if there would be a benefit, if not to the average >> programmer, then to the ones working on deeper/faster code, to allow some >> of the # kinded types (mostly Int#, Word#, Char#, Float#, Double#) to be >> used in Safe code, and to have typeclasses able to work with them. >> >> For instance, the definition of Show would become: >> >> class Show (a :: TYPE r) where >> show :: a -> String >> default show :: (r ~ 'LiftedRep) => a -> String >> show x = showsPrec 0 x "" >> >> showsPrec :: Int -> a -> ShowS >> default showsPrec :: (r ~ 'LiftedRep) => Int -> a -> ShowS >> showsPrec _ x s = show x ++ s >> >> showList :: (r ~ 'LiftedRep) => [a] -> ShowS >> showList ls s = showList__ shows ls s >> >> The fact that the defaults only work when the type is a LiftedRep is a >> nonissue, because there's only a finite number of non-lifted types we'd be >> defining it for. >> >> You could do the same with Eq, Ord, Num, Real, Integral, Fractional, >> Floating, RealFrac, RealFloat, Semigroup, Monoid, Bits, FiniteBits, and >> probably several others I can't think of right now. However, with the >> functions that return pairs, you'd need a version that returns an unboxed >> pair instead. Assuming you changed ReadPrec, you could even do the same >> with Read: >> >> newtype ReadP (a :: RuntimeRep r) = ReadP (forall b. (a -> R b) -> R b) >> newtype ReadPrec (a :: RuntimeRep r) = ReadPrec (Int -> ReadP a) >> >> IO, ST, and STM could be made polykinded the same way, and would open up >> Storable. However, how to do a definition for Monad that works for >> polykinded monads is an issue. I do know that RebindableSyntax handles it >> easily when there's just one monad that can operate on multiple kinds, >> though. >> >> As for which # types could be exposed, I'm thinking that Char#, Int#, >> Word#, Float#, Double#, and Proxy# wouldn't be able to break out of Safe >> code. Int64# and Word64# would work as well, and for 64-bit machines would >> just be type aliases for Int# and Word# respectively. For types which have >> functions with undefined behavior for some arguments, you can just make >> wrappers that check the arguments and error out for the bad values. >> MutVar#, MVar#, TVar#, and StableName# don't open up any functions that >> would be unsuitable for safe code, either. I'm pretty sure that Array# and >> MutableArray# would also be safe, as long as all functions were >> length-checked and threw errors instead of having undefined behavior. >> >> As for why this would be a desirable thing? Mostly for the sake of >> convenience and generality, I think. I find myself working with unboxed >> values from time to time, and it's a pain to always remember to use (+#) >> for Int# and plusWord# for Word#. In addition, having typeclasses that can >> return unboxed values (like a hypothetical sized# :: Sized a => a -> Int# >> vs sized :: Sized a => a -> Int) can improve the generated code when the >> code using the typeclass doesn't get specialized. >> >> The module to import these would have to explain the differences between >> # kinded types and * kinded ones: # values aren't lazy; they can't be >> top-level definitions; you can't use unboxed tuples or sums with GHCi; and >> with a few exceptions, you can't place them in containers (you can't have >> an [Int#], for instance). >> _______________________________________________ >> 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 rae at richarde.dev Mon Oct 28 11:01:43 2019 From: rae at richarde.dev (Richard Eisenberg) Date: Mon, 28 Oct 2019 11:01:43 +0000 Subject: Exposed # kinded variables + polykinded Prelude classes? In-Reply-To: References: Message-ID: <544B3425-292E-4759-9E25-4BF1DDC4D020@richarde.dev> There are two things at play here: 1) Safe Haskell, and 2) levity-polymorphic classes. I think (1) is straightforward. I can't think of any lack of safety or loss of abstraction from levity polymorphism, and now that the issue has been raised, I think the lack of Safe Haskell support for levity polymorphism is a bug. Would you want to file a ticket? I think (2) is quite possible, but with design issues (of course). This has actually been discussed before: https://github.com/ghc-proposals/ghc-proposals/pull/30 Note that the proposal withered on the vine due to lack of love, but it had some support -- it was not rejected. As I've posted previously, I think the right way to get this is to make an alternative, levity-plymorphic prelude, just to see how it all works out. But I do like this direction of travel. Richard > On Oct 27, 2019, at 9:47 PM, chessai . wrote: > > Regarding UnliftedNewtypes: apparently GND can solve this issue for you. There are som cases where, because of the desugaring, a GND clause will fail, but moving the clause out to a StandaloneDeriving one can fix the issue. > > But defaults still become annoying for things like Foldable, where most users rely pretty heavily on defaults. > > On Sun, Oct 27, 2019, 4:22 PM chessai . > wrote: > Just realised i hit reply and not reply all. Here was my email: > > See https://github.com/chessai/levity and http://hackage.haskell.org/package/unlifted-list . > > There are a few annoyances due to binder restrictions (see [1]). > > For example, it is not possible to write polymorphic `bindUnliftedToLifted`: > > ``` > bindUnliftedToLifted :: forall (a :: TYPE r) (b :: TYPE 'LiftedRep). ST s a -> (a -> ST s b) -> ST s b > ``` > > This function is frequently useful when working with monads which have levity-polymorphic parameters, but you cannot write it when a is levity-polymorphic, since it will occur in a binding position. What ends up happening is that you write monomorphic versions of this function for each one you need. Clearly not desirable. > > The other thing is that levity-polymorphic kinds are (almost?) never inferred. For example, if I have: > > ``` > class Show (a :: TYPE r) where > show :: a -> String > > addNewline :: Show a => a -> String > addNewline x = show x ++ "\n" > ``` > > GHC will infer the kind of `a` in `addNewline` to be `TYPE 'LiftedRep`, even though it very well could be `forall (r :: RuntimeRep). TYPE r`. In other words, users will have to constantly kind-annotate because of (over-?)restrictive inference. This becomes annoying rather quickly, and the type errors don't always immediately make it clear what's happening when you miss an annotation. > > Another thing which is annoying, you can't write things like Monoid or Bounded in the same way! (See also [1]) > > ``` > class Monoid (a :: TYPE r) where > mempty :: a > ``` > > GHC will complain about mempty here. You have to instead make it > > ``` > class Monoid (a :: TYPE r) where > mempty :: () -> a > ``` > > which just becomes cluttering, your code gets filled with a lot of `mempty ()`. > > Another thing is that default implementations will not work. You state that it's fine because the number of inhabitants of unlifted kinds is small and finite. This will not be the case in GHC 8.10, when UnliftedNewtypes lands. Then the number of inhabitants becomes non-finite. > > The ways to use levity-polymorhism which result in the best UX are: 1) CPS, 2) backpack, and 3) resolving [1]. (1) is the easiest to most users right now (see [2] for an example) > > With all of these drawbacks I'm against having the API of base or any core library really be a place for levity-polymorphic code, especially when talking about core typeclasses/types. Probably best for this to be in userspace. > > [1]: https://gitlab.haskell.org/ghc/ghc/issues/14917 > [2]: http://hackage.haskell.org/package/bytesmith-0.3.0.0/docs/src/Data.Bytes.Parser.Internal.html#Parser > On Sun, Oct 27, 2019, 9:47 AM Zemyla > wrote: > I'm wondering if there would be a benefit, if not to the average programmer, then to the ones working on deeper/faster code, to allow some of the # kinded types (mostly Int#, Word#, Char#, Float#, Double#) to be used in Safe code, and to have typeclasses able to work with them. > > For instance, the definition of Show would become: > > class Show (a :: TYPE r) where > show :: a -> String > default show :: (r ~ 'LiftedRep) => a -> String > show x = showsPrec 0 x "" > > showsPrec :: Int -> a -> ShowS > default showsPrec :: (r ~ 'LiftedRep) => Int -> a -> ShowS > showsPrec _ x s = show x ++ s > > showList :: (r ~ 'LiftedRep) => [a] -> ShowS > showList ls s = showList__ shows ls s > > The fact that the defaults only work when the type is a LiftedRep is a nonissue, because there's only a finite number of non-lifted types we'd be defining it for. > > You could do the same with Eq, Ord, Num, Real, Integral, Fractional, Floating, RealFrac, RealFloat, Semigroup, Monoid, Bits, FiniteBits, and probably several others I can't think of right now. However, with the functions that return pairs, you'd need a version that returns an unboxed pair instead. Assuming you changed ReadPrec, you could even do the same with Read: > > newtype ReadP (a :: RuntimeRep r) = ReadP (forall b. (a -> R b) -> R b) > newtype ReadPrec (a :: RuntimeRep r) = ReadPrec (Int -> ReadP a) > > IO, ST, and STM could be made polykinded the same way, and would open up Storable. However, how to do a definition for Monad that works for polykinded monads is an issue. I do know that RebindableSyntax handles it easily when there's just one monad that can operate on multiple kinds, though. > > As for which # types could be exposed, I'm thinking that Char#, Int#, Word#, Float#, Double#, and Proxy# wouldn't be able to break out of Safe code. Int64# and Word64# would work as well, and for 64-bit machines would just be type aliases for Int# and Word# respectively. For types which have functions with undefined behavior for some arguments, you can just make wrappers that check the arguments and error out for the bad values. MutVar#, MVar#, TVar#, and StableName# don't open up any functions that would be unsuitable for safe code, either. I'm pretty sure that Array# and MutableArray# would also be safe, as long as all functions were length-checked and threw errors instead of having undefined behavior. > > As for why this would be a desirable thing? Mostly for the sake of convenience and generality, I think. I find myself working with unboxed values from time to time, and it's a pain to always remember to use (+#) for Int# and plusWord# for Word#. In addition, having typeclasses that can return unboxed values (like a hypothetical sized# :: Sized a => a -> Int# vs sized :: Sized a => a -> Int) can improve the generated code when the code using the typeclass doesn't get specialized. > > The module to import these would have to explain the differences between # kinded types and * kinded ones: # values aren't lazy; they can't be top-level definitions; you can't use unboxed tuples or sums with GHCi; and with a few exceptions, you can't place them in containers (you can't have an [Int#], for instance). > > _______________________________________________ > 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: