summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--libraries/base/Data/Functor/Classes.hs79
-rw-r--r--libraries/base/Data/Functor/Compose.hs35
-rw-r--r--libraries/base/Data/Functor/Product.hs31
-rw-r--r--libraries/base/Data/Functor/Sum.hs28
-rw-r--r--libraries/base/changelog.md5
m---------utils/haddock0
6 files changed, 111 insertions, 67 deletions
diff --git a/libraries/base/Data/Functor/Classes.hs b/libraries/base/Data/Functor/Classes.hs
index e547dd12ad..92f3f89e1e 100644
--- a/libraries/base/Data/Functor/Classes.hs
+++ b/libraries/base/Data/Functor/Classes.hs
@@ -1,7 +1,10 @@
{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE Safe #-}
+{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
+{-# LANGUAGE QuantifiedConstraints #-}
-----------------------------------------------------------------------------
-- |
-- Module : Data.Functor.Classes
@@ -91,8 +94,18 @@ import Text.Show (showListWith)
-- | Lifting of the 'Eq' class to unary type constructors.
--
+-- Any instance should be subject to the following law that canonicity
+-- is preserved:
+--
+-- @liftEq (==)@ = @(==)@
+--
+-- This class therefore represents the generalization of 'Eq' by
+-- decomposing its main method into a canonical lifting on a canonical
+-- inner method, so that the lifting can be reused for other arguments
+-- than the canonical one.
+--
-- @since 4.9.0.0
-class Eq1 f where
+class (forall a. Eq a => Eq (f a)) => Eq1 f where
-- | Lift an equality test through the type constructor.
--
-- The function will usually be applied to an equality function,
@@ -102,6 +115,10 @@ class Eq1 f where
--
-- @since 4.9.0.0
liftEq :: (a -> b -> Bool) -> f a -> f b -> Bool
+ default liftEq
+ :: (f ~ f' c, Eq2 f', Eq c)
+ => (a -> b -> Bool) -> f a -> f b -> Bool
+ liftEq = liftEq2 (==)
-- | Lift the standard @('==')@ function through the type constructor.
--
@@ -111,8 +128,18 @@ eq1 = liftEq (==)
-- | Lifting of the 'Ord' class to unary type constructors.
--
+-- Any instance should be subject to the following law that canonicity
+-- is preserved:
+--
+-- @liftCompare compare@ = 'compare'
+--
+-- This class therefore represents the generalization of 'Ord' by
+-- decomposing its main method into a canonical lifting on a canonical
+-- inner method, so that the lifting can be reused for other arguments
+-- than the canonical one.
+--
-- @since 4.9.0.0
-class (Eq1 f) => Ord1 f where
+class (Eq1 f, forall a. Ord a => Ord (f a)) => Ord1 f where
-- | Lift a 'compare' function through the type constructor.
--
-- The function will usually be applied to a comparison function,
@@ -122,6 +149,10 @@ class (Eq1 f) => Ord1 f where
--
-- @since 4.9.0.0
liftCompare :: (a -> b -> Ordering) -> f a -> f b -> Ordering
+ default liftCompare
+ :: (f ~ f' c, Ord2 f', Ord c)
+ => (a -> b -> Ordering) -> f a -> f b -> Ordering
+ liftCompare = liftCompare2 compare
-- | Lift the standard 'compare' function through the type constructor.
--
@@ -131,6 +162,22 @@ compare1 = liftCompare compare
-- | Lifting of the 'Read' class to unary type constructors.
--
+-- Any instance should be subject to the following laws that canonicity
+-- is preserved:
+--
+-- @liftReadsPrec readsPrec readList@ = 'readsPrec'
+--
+-- @liftReadList readsPrec readList@ = 'readList'
+--
+-- @liftReadPrec readPrec readListPrec@ = 'readPrec'
+--
+-- @liftReadListPrec readPrec readListPrec@ = 'readListPrec'
+--
+-- This class therefore represents the generalization of 'Read' by
+-- decomposing it's methods into a canonical lifting on a canonical
+-- inner method, so that the lifting can be reused for other arguments
+-- than the canonical one.
+--
-- Both 'liftReadsPrec' and 'liftReadPrec' exist to match the interface
-- provided in the 'Read' type class, but it is recommended to implement
-- 'Read1' instances using 'liftReadPrec' as opposed to 'liftReadsPrec', since
@@ -145,7 +192,7 @@ compare1 = liftCompare compare
-- For more information, refer to the documentation for the 'Read' class.
--
-- @since 4.9.0.0
-class Read1 f where
+class (forall a. Read a => Read (f a)) => Read1 f where
{-# MINIMAL liftReadsPrec | liftReadPrec #-}
-- | 'readsPrec' function for an application of the type constructor
@@ -219,14 +266,30 @@ liftReadListPrecDefault rp rl = list (liftReadPrec rp rl)
-- | Lifting of the 'Show' class to unary type constructors.
--
+-- Any instance should be subject to the following laws that canonicity
+-- is preserved:
+--
+-- @liftShowsPrec showsPrec showList@ = 'showsPrec'
+--
+-- @liftShowList showsPrec showList@ = 'showList'
+--
+-- This class therefore represents the generalization of 'Show' by
+-- decomposing it's methods into a canonical lifting on a canonical
+-- inner method, so that the lifting can be reused for other arguments
+-- than the canonical one.
+--
-- @since 4.9.0.0
-class Show1 f where
+class (forall a. Show a => Show (f a)) => Show1 f where
-- | 'showsPrec' function for an application of the type constructor
-- based on 'showsPrec' and 'showList' functions for the argument type.
--
-- @since 4.9.0.0
liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) ->
Int -> f a -> ShowS
+ default liftShowsPrec
+ :: (f ~ f' b, Show2 f', Show b)
+ => (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
+ liftShowsPrec = liftShowsPrec2 showsPrec showList
-- | 'showList' function for an application of the type constructor
-- based on 'showsPrec' and 'showList' functions for the argument type.
@@ -248,7 +311,7 @@ showsPrec1 = liftShowsPrec showsPrec showList
-- | Lifting of the 'Eq' class to binary type constructors.
--
-- @since 4.9.0.0
-class Eq2 f where
+class (forall a. Eq a => Eq1 (f a)) => Eq2 f where
-- | Lift equality tests through the type constructor.
--
-- The function will usually be applied to equality functions,
@@ -268,7 +331,7 @@ eq2 = liftEq2 (==) (==)
-- | Lifting of the 'Ord' class to binary type constructors.
--
-- @since 4.9.0.0
-class (Eq2 f) => Ord2 f where
+class (Eq2 f, forall a. Ord a => Ord1 (f a)) => Ord2 f where
-- | Lift 'compare' functions through the type constructor.
--
-- The function will usually be applied to comparison functions,
@@ -302,7 +365,7 @@ compare2 = liftCompare2 compare compare
-- For more information, refer to the documentation for the 'Read' class.
--
-- @since 4.9.0.0
-class Read2 f where
+class (forall a. Read a => Read1 (f a)) => Read2 f where
{-# MINIMAL liftReadsPrec2 | liftReadPrec2 #-}
-- | 'readsPrec' function for an application of the type constructor
@@ -385,7 +448,7 @@ liftReadListPrec2Default rp1 rl1 rp2 rl2 = list (liftReadPrec2 rp1 rl1 rp2 rl2)
-- | Lifting of the 'Show' class to binary type constructors.
--
-- @since 4.9.0.0
-class Show2 f where
+class (forall a. Show a => Show1 (f a)) => Show2 f where
-- | 'showsPrec' function for an application of the type constructor
-- based on 'showsPrec' and 'showList' functions for the argument types.
--
diff --git a/libraries/base/Data/Functor/Compose.hs b/libraries/base/Data/Functor/Compose.hs
index 813712f8dd..49955402a6 100644
--- a/libraries/base/Data/Functor/Compose.hs
+++ b/libraries/base/Data/Functor/Compose.hs
@@ -5,6 +5,7 @@
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE Trustworthy #-}
+{-# LANGUAGE StandaloneDeriving #-}
-----------------------------------------------------------------------------
-- |
@@ -32,7 +33,7 @@ import Data.Coerce (coerce)
import Data.Data (Data)
import Data.Type.Equality (TestEquality(..), (:~:)(..))
import GHC.Generics (Generic, Generic1)
-import Text.Read (Read(..), readListDefault, readListPrecDefault)
+import Text.Read ()
infixr 9 `Compose`
@@ -47,6 +48,17 @@ newtype Compose f g a = Compose { getCompose :: f (g a) }
, Monoid -- ^ @since 4.16.0.0
)
+-- Instances of Prelude classes
+
+-- | @since 4.18.0.0
+deriving instance Eq (f (g a)) => Eq (Compose f g a)
+-- | @since 4.18.0.0
+deriving instance Ord (f (g a)) => Ord (Compose f g a)
+-- | @since 4.18.0.0
+deriving instance Read (f (g a)) => Read (Compose f g a)
+-- | @since 4.18.0.0
+deriving instance Show (f (g a)) => Show (Compose f g a)
+
-- Instances of lifted Prelude classes
-- | @since 4.9.0.0
@@ -77,27 +89,6 @@ instance (Show1 f, Show1 g) => Show1 (Compose f g) where
sp' = liftShowsPrec sp sl
sl' = liftShowList sp sl
--- Instances of Prelude classes
-
--- | @since 4.9.0.0
-instance (Eq1 f, Eq1 g, Eq a) => Eq (Compose f g a) where
- (==) = eq1
-
--- | @since 4.9.0.0
-instance (Ord1 f, Ord1 g, Ord a) => Ord (Compose f g a) where
- compare = compare1
-
--- | @since 4.9.0.0
-instance (Read1 f, Read1 g, Read a) => Read (Compose f g a) where
- readPrec = readPrec1
-
- readListPrec = readListPrecDefault
- readList = readListDefault
-
--- | @since 4.9.0.0
-instance (Show1 f, Show1 g, Show a) => Show (Compose f g a) where
- showsPrec = showsPrec1
-
-- Functor instances
-- | @since 4.9.0.0
diff --git a/libraries/base/Data/Functor/Product.hs b/libraries/base/Data/Functor/Product.hs
index 114ad6a699..efa6b9977a 100644
--- a/libraries/base/Data/Functor/Product.hs
+++ b/libraries/base/Data/Functor/Product.hs
@@ -2,6 +2,7 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE Safe #-}
+{-# LANGUAGE StandaloneDeriving #-}
-----------------------------------------------------------------------------
-- |
-- Module : Data.Functor.Product
@@ -28,7 +29,7 @@ import Control.Monad.Zip (MonadZip(mzipWith))
import Data.Data (Data)
import Data.Functor.Classes
import GHC.Generics (Generic, Generic1)
-import Text.Read (Read(..), readListDefault, readListPrecDefault)
+import Text.Read ()
-- | Lifted product of functors.
data Product f g a = Pair (f a) (g a)
@@ -37,6 +38,15 @@ data Product f g a = Pair (f a) (g a)
, Generic1 -- ^ @since 4.9.0.0
)
+-- | @since 4.18.0.0
+deriving instance (Eq (f a), Eq (g a)) => Eq (Product f g a)
+-- | @since 4.18.0.0
+deriving instance (Ord (f a), Ord (g a)) => Ord (Product f g a)
+-- | @since 4.18.0.0
+deriving instance (Read (f a), Read (g a)) => Read (Product f g a)
+-- | @since 4.18.0.0
+deriving instance (Show (f a), Show (g a)) => Show (Product f g a)
+
-- | @since 4.9.0.0
instance (Eq1 f, Eq1 g) => Eq1 (Product f g) where
liftEq eq (Pair x1 y1) (Pair x2 y2) = liftEq eq x1 x2 && liftEq eq y1 y2
@@ -60,25 +70,6 @@ instance (Show1 f, Show1 g) => Show1 (Product f g) where
showsBinaryWith (liftShowsPrec sp sl) (liftShowsPrec sp sl) "Pair" d x y
-- | @since 4.9.0.0
-instance (Eq1 f, Eq1 g, Eq a) => Eq (Product f g a)
- where (==) = eq1
-
--- | @since 4.9.0.0
-instance (Ord1 f, Ord1 g, Ord a) => Ord (Product f g a) where
- compare = compare1
-
--- | @since 4.9.0.0
-instance (Read1 f, Read1 g, Read a) => Read (Product f g a) where
- readPrec = readPrec1
-
- readListPrec = readListPrecDefault
- readList = readListDefault
-
--- | @since 4.9.0.0
-instance (Show1 f, Show1 g, Show a) => Show (Product f g a) where
- showsPrec = showsPrec1
-
--- | @since 4.9.0.0
instance (Functor f, Functor g) => Functor (Product f g) where
fmap f (Pair x y) = Pair (fmap f x) (fmap f y)
a <$ (Pair x y) = Pair (a <$ x) (a <$ y)
diff --git a/libraries/base/Data/Functor/Sum.hs b/libraries/base/Data/Functor/Sum.hs
index affa4e5fc0..2ec25f5588 100644
--- a/libraries/base/Data/Functor/Sum.hs
+++ b/libraries/base/Data/Functor/Sum.hs
@@ -2,6 +2,7 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE Safe #-}
+{-# LANGUAGE StandaloneDeriving #-}
-----------------------------------------------------------------------------
-- |
-- Module : Data.Functor.Sum
@@ -25,7 +26,7 @@ import Control.Applicative ((<|>))
import Data.Data (Data)
import Data.Functor.Classes
import GHC.Generics (Generic, Generic1)
-import Text.Read (Read(..), readListDefault, readListPrecDefault)
+import Text.Read ()
-- | Lifted sum of functors.
data Sum f g a = InL (f a) | InR (g a)
@@ -34,6 +35,15 @@ data Sum f g a = InL (f a) | InR (g a)
, Generic1 -- ^ @since 4.9.0.0
)
+-- | @since 4.18.0.0
+deriving instance (Eq (f a), Eq (g a)) => Eq (Sum f g a)
+-- | @since 4.18.0.0
+deriving instance (Ord (f a), Ord (g a)) => Ord (Sum f g a)
+-- | @since 4.18.0.0
+deriving instance (Read (f a), Read (g a)) => Read (Sum f g a)
+-- | @since 4.18.0.0
+deriving instance (Show (f a), Show (g a)) => Show (Sum f g a)
+
-- | @since 4.9.0.0
instance (Eq1 f, Eq1 g) => Eq1 (Sum f g) where
liftEq eq (InL x1) (InL x2) = liftEq eq x1 x2
@@ -65,22 +75,6 @@ instance (Show1 f, Show1 g) => Show1 (Sum f g) where
showsUnaryWith (liftShowsPrec sp sl) "InR" d y
-- | @since 4.9.0.0
-instance (Eq1 f, Eq1 g, Eq a) => Eq (Sum f g a) where
- (==) = eq1
--- | @since 4.9.0.0
-instance (Ord1 f, Ord1 g, Ord a) => Ord (Sum f g a) where
- compare = compare1
--- | @since 4.9.0.0
-instance (Read1 f, Read1 g, Read a) => Read (Sum f g a) where
- readPrec = readPrec1
-
- readListPrec = readListPrecDefault
- readList = readListDefault
--- | @since 4.9.0.0
-instance (Show1 f, Show1 g, Show a) => Show (Sum f g a) where
- showsPrec = showsPrec1
-
--- | @since 4.9.0.0
instance (Functor f, Functor g) => Functor (Sum f g) where
fmap f (InL x) = InL (fmap f x)
fmap f (InR y) = InR (fmap f y)
diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md
index 515e398798..a11b059000 100644
--- a/libraries/base/changelog.md
+++ b/libraries/base/changelog.md
@@ -31,6 +31,11 @@
as well as [the migration guide](https://github.com/haskell/core-libraries-committee/blob/main/guides/export-lifta2-prelude.md)
* Update to Unicode 15.0.0.
* Add `Eq` and `Ord` instances for `Generically1`.
+ * Relax instances for Functor combinators; put superclass on Class1 and Class2
+ to make non-breaking. See [CLC
+ #10](https://github.com/haskell/core-libraries-committee/issues/10) for the
+ related discussion, as well as [the migration
+ guide](https://github.com/haskell/core-libraries-committee/blob/main/guides/functor-combinator-instances-and-class1s.md).
## 4.17.0.0 *August 2022*
diff --git a/utils/haddock b/utils/haddock
-Subproject b5e40b15228fdca5ce7d4e2f2241156d0b08526
+Subproject 7e4326f999056fb7b0b955ccadf5eab86b755a0