summaryrefslogtreecommitdiff
path: root/libraries/base/Data/Functor
diff options
context:
space:
mode:
Diffstat (limited to 'libraries/base/Data/Functor')
-rw-r--r--libraries/base/Data/Functor/Compose.hs7
-rw-r--r--libraries/base/Data/Functor/Const.hs5
-rw-r--r--libraries/base/Data/Functor/Product.hs6
-rw-r--r--libraries/base/Data/Functor/Sum.hs6
4 files changed, 1 insertions, 23 deletions
diff --git a/libraries/base/Data/Functor/Compose.hs b/libraries/base/Data/Functor/Compose.hs
index 225d16283b..d8369ebc05 100644
--- a/libraries/base/Data/Functor/Compose.hs
+++ b/libraries/base/Data/Functor/Compose.hs
@@ -3,7 +3,6 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE TypeOperators #-}
-----------------------------------------------------------------------------
@@ -27,7 +26,6 @@ module Data.Functor.Compose (
import Data.Functor.Classes
-import Data.Kind (Type)
import Control.Applicative
import Data.Coerce (coerce)
import Data.Data (Data)
@@ -40,9 +38,6 @@ infixr 9 `Compose`
-- | Right-to-left composition of functors.
-- The composition of applicative functors is always applicative,
-- but the composition of monads is not always a monad.
---
--- Kinds `k2` and `k1` explicitly quantified since 4.15.0.0.
-type Compose :: forall k2 k1. (k2 -> Type) -> (k1 -> k2) -> (k1 -> Type)
newtype Compose f g a = Compose { getCompose :: f (g a) }
deriving ( Data -- ^ @since 4.9.0.0
, Generic -- ^ @since 4.9.0.0
@@ -131,7 +126,7 @@ instance (Alternative f, Applicative g) => Alternative (Compose f g) where
-- | The deduction (via generativity) that if @g x :~: g y@ then @x :~: y@.
--
-- @since 4.14.0.0
-instance TestEquality f => TestEquality (Compose f g) where
+instance (TestEquality f) => TestEquality (Compose f g) where
testEquality (Compose x) (Compose y) =
case testEquality x y of -- :: Maybe (g x :~: g y)
Just Refl -> Just Refl -- :: Maybe (x :~: y)
diff --git a/libraries/base/Data/Functor/Const.hs b/libraries/base/Data/Functor/Const.hs
index dd1880e30b..651041f15b 100644
--- a/libraries/base/Data/Functor/Const.hs
+++ b/libraries/base/Data/Functor/Const.hs
@@ -2,9 +2,7 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE PolyKinds #-}
-{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE Trustworthy #-}
-----------------------------------------------------------------------------
@@ -38,9 +36,6 @@ import GHC.Read (Read(readsPrec), readParen, lex)
import GHC.Show (Show(showsPrec), showParen, showString)
-- | The 'Const' functor.
---
--- Kind `k` explicitly quantified since 4.15.0.0.
-type Const :: forall k. Type -> k -> Type
newtype Const a b = Const { getConst :: a }
deriving ( Bits -- ^ @since 4.9.0.0
, Bounded -- ^ @since 4.9.0.0
diff --git a/libraries/base/Data/Functor/Product.hs b/libraries/base/Data/Functor/Product.hs
index 266a72d75e..a3678e910e 100644
--- a/libraries/base/Data/Functor/Product.hs
+++ b/libraries/base/Data/Functor/Product.hs
@@ -1,9 +1,7 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE PolyKinds #-}
-{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE Safe #-}
-{-# LANGUAGE StandaloneKindSignatures #-}
-----------------------------------------------------------------------------
-- |
-- Module : Data.Functor.Product
@@ -28,15 +26,11 @@ import Control.Monad (MonadPlus(..))
import Control.Monad.Fix (MonadFix(..))
import Control.Monad.Zip (MonadZip(mzipWith))
import Data.Data (Data)
-import Data.Kind (Type)
import Data.Functor.Classes
import GHC.Generics (Generic, Generic1)
import Text.Read (Read(..), readListDefault, readListPrecDefault)
-- | Lifted product of functors.
---
--- Kind `k` explicitly quantified since 4.15.0.0.
-type Product :: forall k. (k -> Type) -> (k -> Type) -> (k -> Type)
data Product f g a = Pair (f a) (g a)
deriving ( Data -- ^ @since 4.9.0.0
, Generic -- ^ @since 4.9.0.0
diff --git a/libraries/base/Data/Functor/Sum.hs b/libraries/base/Data/Functor/Sum.hs
index cca541fe5e..f7d6178a2b 100644
--- a/libraries/base/Data/Functor/Sum.hs
+++ b/libraries/base/Data/Functor/Sum.hs
@@ -1,9 +1,7 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE PolyKinds #-}
-{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE Safe #-}
-{-# LANGUAGE StandaloneKindSignatures #-}
-----------------------------------------------------------------------------
-- |
-- Module : Data.Functor.Sum
@@ -25,15 +23,11 @@ module Data.Functor.Sum (
import Control.Applicative ((<|>))
import Data.Data (Data)
-import Data.Kind (Type)
import Data.Functor.Classes
import GHC.Generics (Generic, Generic1)
import Text.Read (Read(..), readListDefault, readListPrecDefault)
-- | Lifted sum of functors.
---
--- Kind `k` explicitly quantified since 4.15.0.0.
-type Sum :: forall k. (k -> Type) -> (k -> Type) -> (k -> Type)
data Sum f g a = InL (f a) | InR (g a)
deriving ( Data -- ^ @since 4.9.0.0
, Generic -- ^ @since 4.9.0.0