[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 2 commits: Add laws relating between Foldable/Traversable with their Bi- superclasses

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Mon Nov 6 08:14:17 UTC 2023



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
e3c8f19b by Tobias Haslop at 2023-11-06T03:14:09-05:00
Add laws relating between Foldable/Traversable with their Bi- superclasses

See https://github.com/haskell/core-libraries-committee/issues/205 for
discussion.

This commit also documents that the tuple instances only satisfy the
laws up to lazyness, similar to the documentation added in !9512.

- - - - -
8df66b46 by Tobias Haslop at 2023-11-06T03:14:13-05:00
Elaborate on the quantified superclass of Bifunctor

This was requested in the comment
https://github.com/haskell/core-libraries-committee/issues/93#issuecomment-1597271700
for when Traversable becomes a superclass of Bitraversable, but similarly
applies to Functor/Bifunctor, which already are in a superclass relationship.

- - - - -


3 changed files:

- libraries/base/src/Data/Bifoldable.hs
- libraries/base/src/Data/Bifunctor.hs
- libraries/base/src/Data/Bitraversable.hs


Changes:

=====================================
libraries/base/src/Data/Bifoldable.hs
=====================================
@@ -92,6 +92,15 @@ import GHC.Generics (K1(..))
 -- 'bifoldr' f g z t ≡ 'appEndo' ('bifoldMap' (Endo . f) (Endo . g) t) z
 -- @
 --
+-- If the type is also an instance of 'Foldable', then
+-- it must satisfy (up to laziness):
+--
+-- @
+-- 'bifoldl' 'const' ≡ 'foldl'
+-- 'bifoldr' ('flip' 'const') ≡ 'foldr'
+-- 'bifoldMap' ('const' 'mempty') ≡ 'foldMap'
+-- @
+--
 -- If the type is also a 'Data.Bifunctor.Bifunctor' instance, it should satisfy:
 --
 -- @
@@ -221,7 +230,17 @@ class Bifoldable p where
   bifoldl f g z t = appEndo (getDual (bifoldMap (Dual . Endo . flip f)
                                                 (Dual . Endo . flip g) t)) z
 
--- | @since 4.10.0.0
+-- | Class laws for tuples hold only up to laziness. The
+-- Bifoldable methods are lazier than their Foldable counterparts.
+-- For example the law @'bifoldr' ('flip' 'const') ≡ 'foldr'@ does
+-- not hold for tuples if lazyness is exploited:
+--
+-- >>> bifoldr (flip const) (:) [] (undefined :: (Int, Word)) `seq` ()
+-- ()
+-- >>> foldr (:) [] (undefined :: (Int, Word)) `seq` ()
+-- *** Exception: Prelude.undefined
+--
+-- @since 4.10.0.0
 instance Bifoldable (,) where
   bifoldMap f g ~(a, b) = f a `mappend` g b
 


=====================================
libraries/base/src/Data/Bifunctor.hs
=====================================
@@ -39,12 +39,26 @@ import GHC.Generics ( K1(..) )
 -- Intuitively it is a bifunctor where both the first and second
 -- arguments are covariant.
 --
+-- The class definition of a 'Bifunctor' @p@ uses the
+-- [QuantifiedConstraints](https://downloads.haskell.org/ghc/latest/docs/users_guide/exts/quantified_constraints.html)
+-- language extension to quantify over the first type
+-- argument @a@ in its context. The context requires that @p a@
+-- must be a 'Functor' for all @a at . In other words a partially
+-- applied 'Bifunctor' must be a 'Functor'. This makes 'Functor' a
+-- superclass of 'Bifunctor' such that a function with a
+-- 'Bifunctor' constraint may use 'fmap' in its implementation.
+-- 'Functor' has been a quantified superclass of
+-- 'Bifunctor' since base-4.18.0.0.
+--
 -- You can define a 'Bifunctor' by either defining 'bimap' or by
--- defining both 'first' and 'second'. A partially applied 'Bifunctor'
--- must be a 'Functor' and the 'second' method must agree with 'fmap'.
+-- defining both 'first' and 'second'. The 'second' method must
+-- agree with 'fmap':
+--
+-- @'second' ≡ 'fmap'@
+--
 -- From this it follows that:
 --
--- @'second' 'id' = 'id'@
+-- @'second' 'id' ≡ 'id'@
 --
 -- If you supply 'bimap', you should ensure that:
 --
@@ -69,8 +83,6 @@ import GHC.Generics ( K1(..) )
 -- 'second' (f '.' g) ≡ 'second' f '.' 'second' g
 -- @
 --
--- Since 4.18.0.0 'Functor' is a superclass of 'Bifunctor.
---
 -- @since 4.8.0.0
 class (forall a. Functor (p a)) => Bifunctor p where
     {-# MINIMAL bimap | first, second #-}


=====================================
libraries/base/src/Data/Bitraversable.hs
=====================================
@@ -70,8 +70,8 @@ import GHC.Generics (K1(..))
 -- preserving the 'Applicative' operations:
 --
 -- @
--- t ('pure' x) = 'pure' x
--- t (f '<*>' x) = t f '<*>' t x
+-- t ('pure' x) ≡ 'pure' x
+-- t (f '<*>' x) ≡ t f '<*>' t x
 -- @
 --
 -- and the identity functor 'Identity' and composition functors
@@ -91,11 +91,18 @@ import GHC.Generics (K1(..))
 --
 -- @
 -- 'bimap' f g ≡ 'runIdentity' . 'bitraverse' ('Identity' . f) ('Identity' . g)
--- 'bifoldMap' f g = 'getConst' . 'bitraverse' ('Const' . f) ('Const' . g)
+-- 'bifoldMap' f g ≡ 'getConst' . 'bitraverse' ('Const' . f) ('Const' . g)
 -- @
 --
 -- These are available as 'bimapDefault' and 'bifoldMapDefault' respectively.
 --
+-- If the type is also an instance of 'Traversable', then
+-- it must satisfy (up to laziness):
+--
+-- @
+-- 'traverse' ≡ 'bitraverse' 'pure'
+-- @
+--
 -- @since 4.10.0.0
 class (Bifunctor t, Bifoldable t) => Bitraversable t where
   -- | Evaluates the relevant functions at each element in the structure,
@@ -164,7 +171,17 @@ bimapM = bitraverse
 bisequence :: (Bitraversable t, Applicative f) => t (f a) (f b) -> f (t a b)
 bisequence = bitraverse id id
 
--- | @since 4.10.0.0
+-- | Class laws for tuples hold only up to laziness. The
+-- Bitraversable methods are lazier than their Traversable counterparts.
+-- For example the law @'bitraverse' 'pure' ≡ 'traverse'@ does
+-- not hold for tuples if lazyness is exploited:
+--
+-- >>> (bitraverse pure pure undefined :: IO (Int, Word)) `seq` ()
+-- ()
+-- >>> (traverse pure undefined :: IO (Int, Word)) `seq` ()
+-- *** Exception: Prelude.undefined
+--
+-- @since 4.10.0.0
 instance Bitraversable (,) where
   bitraverse f g ~(a, b) = liftA2 (,) (f a) (g b)
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2da2ef55a012ac7acb961338871c9196e4a48f18...8df66b466ddf507c43c1b5e491a133194aed651a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2da2ef55a012ac7acb961338871c9196e4a48f18...8df66b466ddf507c43c1b5e491a133194aed651a
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/20231106/7c820106/attachment-0001.html>


More information about the ghc-commits mailing list