summaryrefslogtreecommitdiff
path: root/libraries/base/Data/Functor/Compose.hs
diff options
context:
space:
mode:
Diffstat (limited to 'libraries/base/Data/Functor/Compose.hs')
-rw-r--r--libraries/base/Data/Functor/Compose.hs7
1 files changed, 6 insertions, 1 deletions
diff --git a/libraries/base/Data/Functor/Compose.hs b/libraries/base/Data/Functor/Compose.hs
index d8369ebc05..225d16283b 100644
--- a/libraries/base/Data/Functor/Compose.hs
+++ b/libraries/base/Data/Functor/Compose.hs
@@ -3,6 +3,7 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE TypeOperators #-}
-----------------------------------------------------------------------------
@@ -26,6 +27,7 @@ module Data.Functor.Compose (
import Data.Functor.Classes
+import Data.Kind (Type)
import Control.Applicative
import Data.Coerce (coerce)
import Data.Data (Data)
@@ -38,6 +40,9 @@ 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
@@ -126,7 +131,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)