[Git][ghc/ghc][master] 4 commits: Optimized Foldable methods for Data.Functor.Compose
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Thu Mar 23 13:19:54 UTC 2023
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
8c98deba by Armando Ramirez at 2023-03-23T09:19:32-04:00
Optimized Foldable methods for Data.Functor.Compose
Explicitly define length, elem, etc. in Foldable instance for Data.Functor.Compose
Implementation of https://github.com/haskell/core-libraries-committee/issues/57
- - - - -
bc066108 by Armando Ramirez at 2023-03-23T09:19:32-04:00
Additional optimized versions
- - - - -
80fce576 by Bodigrim at 2023-03-23T09:19:32-04:00
Simplify minimum/maximum in instance Foldable (Compose f g)
- - - - -
8cb88a5a by Bodigrim at 2023-03-23T09:19:32-04:00
Update changelog to mention changes to instance Foldable (Compose f g)
- - - - -
2 changed files:
- libraries/base/Data/Functor/Compose.hs
- libraries/base/changelog.md
Changes:
=====================================
libraries/base/Data/Functor/Compose.hs
=====================================
@@ -31,6 +31,8 @@ import Data.Functor.Classes
import Control.Applicative
import Data.Coerce (coerce)
import Data.Data (Data)
+import Data.Foldable (Foldable(..))
+import Data.Monoid (Sum(..), All(..), Any(..), Product(..))
import Data.Type.Equality (TestEquality(..), (:~:)(..))
import GHC.Generics (Generic, Generic1)
import Text.Read (Read(..), ReadPrec, readListDefault, readListPrecDefault)
@@ -111,7 +113,23 @@ instance (Functor f, Functor g) => Functor (Compose f g) where
-- | @since 4.9.0.0
instance (Foldable f, Foldable g) => Foldable (Compose f g) where
+ fold (Compose t) = foldMap fold t
foldMap f (Compose t) = foldMap (foldMap f) t
+ foldMap' f (Compose t) = foldMap' (foldMap' f) t
+ foldr f b (Compose fga) = foldr (\ga acc -> foldr f acc ga) b fga
+ foldr' f b (Compose fga) = foldr' (\ga acc -> foldr' f acc ga) b fga
+ foldl f b (Compose fga) = foldl (\acc ga -> foldl f acc ga) b fga
+ foldl' f b (Compose fga) = foldl' (\acc ga -> foldl' f acc ga) b fga
+
+ null (Compose t) = null t || getAll (foldMap (All . null) t)
+ length (Compose t) = getSum (foldMap' (Sum . length) t)
+ elem x (Compose t) = getAny (foldMap (Any . elem x) t)
+
+ minimum (Compose fga) = minimum $ map minimum $ filter (not . null) $ toList fga
+ maximum (Compose fga) = maximum $ map maximum $ filter (not . null) $ toList fga
+
+ sum (Compose t) = getSum (foldMap' (Sum . sum) t)
+ product (Compose t) = getProduct (foldMap' (Product . product) t)
-- | @since 4.9.0.0
instance (Traversable f, Traversable g) => Traversable (Compose f g) where
=====================================
libraries/base/changelog.md
=====================================
@@ -12,6 +12,8 @@
* Add `Type.Reflection.decTypeRep`, `Data.Typeable.decT` and `Data.Typeable.hdecT` equality decisions functions.
([CLC proposal #98](https://github.com/haskell/core-libraries-committee/issues/98))
* Add `Data.Functor.unzip` ([CLC proposal #88](https://github.com/haskell/core-libraries-committee/issues/88))
+ * Implement more members of `instance Foldable (Compose f g)` explicitly.
+ ([CLC proposal #57](https://github.com/haskell/core-libraries-committee/issues/57))
## 4.18.0.0 *TBA*
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/30d45e971d94b3c28296a3f20f94275f38bc89d1...8cb88a5ade9427ca2f26e7f2dbf9defb8fb0ed22
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/30d45e971d94b3c28296a3f20f94275f38bc89d1...8cb88a5ade9427ca2f26e7f2dbf9defb8fb0ed22
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230323/d2113ef3/attachment-0001.html>
More information about the ghc-commits
mailing list