Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Basic functors.
Definitions of the type-level equivalents of
const
, id
, and (.
), and a definition of
the lifted function space.
These datatypes are generally useful, but in this
library, they're primarily used as parameters for
the NP
, NS
, POP
, and SOP
types.
We define own variants of Const
,
Identity
and Compose
for
various reasons.
Const
andCompose
become kind polymorphic only inbase-4.9.0.0
(transformers-0.5.0.0
).- Shorter names are convenient, and pattern synonyms aren't (yet) powerful enough, particularly exhaustiveness check doesn't work properly. See https://ghc.haskell.org/trac/ghc/ticket/8779.
Synopsis
- newtype K (a :: *) (b :: k) = K a
- unK :: K a b -> a
- newtype I (a :: *) = I a
- unI :: I a -> a
- newtype ((f :: l -> *) :.: (g :: k -> l)) (p :: k) = Comp (f (g p))
- unComp :: (f :.: g) p -> f (g p)
- mapII :: (a -> b) -> I a -> I b
- mapIK :: (a -> b) -> I a -> K b c
- mapKI :: (a -> b) -> K a c -> I b
- mapKK :: (a -> b) -> K a c -> K b d
- mapIII :: (a -> b -> c) -> I a -> I b -> I c
- mapIIK :: (a -> b -> c) -> I a -> I b -> K c d
- mapIKI :: (a -> b -> c) -> I a -> K b d -> I c
- mapIKK :: (a -> b -> c) -> I a -> K b d -> K c e
- mapKII :: (a -> b -> c) -> K a d -> I b -> I c
- mapKIK :: (a -> b -> c) -> K a d -> I b -> K c e
- mapKKI :: (a -> b -> c) -> K a d -> K b e -> I c
- mapKKK :: (a -> b -> c) -> K a d -> K b e -> K c f
Basic functors
newtype K (a :: *) (b :: k) Source #
The constant type functor.
Like Constant
, but kind-polymorphic
in its second argument and with a shorter name.
K a |
Instances
Eq2 (K :: * -> * -> *) Source # | Since: 0.2.4.0 |
Ord2 (K :: * -> * -> *) Source # | Since: 0.2.4.0 |
Defined in Generics.SOP.BasicFunctors | |
Read2 (K :: * -> * -> *) Source # | Since: 0.2.4.0 |
Defined in Generics.SOP.BasicFunctors liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (K a b) # liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [K a b] # liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (K a b) # liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [K a b] # | |
Show2 (K :: * -> * -> *) Source # | Since: 0.2.4.0 |
NFData2 (K :: * -> * -> *) Source # | Since: 0.2.5.0 |
Defined in Generics.SOP.BasicFunctors | |
Functor (K a :: * -> *) Source # | |
Monoid a => Applicative (K a :: * -> *) Source # | |
Foldable (K a :: * -> *) Source # | |
Defined in Generics.SOP.BasicFunctors fold :: Monoid m => K a m -> m # foldMap :: Monoid m => (a0 -> m) -> K a a0 -> m # foldr :: (a0 -> b -> b) -> b -> K a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> K a a0 -> b # foldl :: (b -> a0 -> b) -> b -> K a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> K a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> K a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> K a a0 -> a0 # elem :: Eq a0 => a0 -> K a a0 -> Bool # maximum :: Ord a0 => K a a0 -> a0 # minimum :: Ord a0 => K a a0 -> a0 # | |
Traversable (K a :: * -> *) Source # | |
Eq a => Eq1 (K a :: * -> *) Source # | Since: 0.2.4.0 |
Ord a => Ord1 (K a :: * -> *) Source # | Since: 0.2.4.0 |
Defined in Generics.SOP.BasicFunctors | |
Read a => Read1 (K a :: * -> *) Source # | Since: 0.2.4.0 |
Defined in Generics.SOP.BasicFunctors | |
Show a => Show1 (K a :: * -> *) Source # | Since: 0.2.4.0 |
NFData a => NFData1 (K a :: * -> *) Source # | Since: 0.2.5.0 |
Defined in Generics.SOP.BasicFunctors | |
Eq a => Eq (K a b) Source # | |
Ord a => Ord (K a b) Source # | |
Read a => Read (K a b) Source # | |
Show a => Show (K a b) Source # | |
Generic (K a b) Source # | |
NFData a => NFData (K a b) Source # | Since: 0.2.5.0 |
Defined in Generics.SOP.BasicFunctors | |
HasDatatypeInfo (K a b) Source # | |
Defined in Generics.SOP.Instances type DatatypeInfoOf (K a b) :: DatatypeInfo Source # datatypeInfo :: proxy (K a b) -> DatatypeInfo (Code (K a b)) Source # | |
Generic (K a b) Source # | |
type Rep (K a b) Source # | |
Defined in Generics.SOP.BasicFunctors | |
type DatatypeInfoOf (K a b) Source # | |
Defined in Generics.SOP.Instances | |
type Code (K a b) Source # | |
Defined in Generics.SOP.Instances |
The identity type functor.
Like Identity
, but with a shorter name.
I a |
Instances
newtype ((f :: l -> *) :.: (g :: k -> l)) (p :: k) infixr 7 Source #
Composition of functors.
Like Compose
, but kind-polymorphic
and with a shorter name.
Comp (f (g p)) |
Instances
(Functor f, Functor g) => Functor (f :.: g) Source # | |
(Applicative f, Applicative g) => Applicative (f :.: g) Source # | Since: 0.2.5.0 |
(Foldable f, Foldable g) => Foldable (f :.: g) Source # | Since: 0.2.5.0 |
Defined in Generics.SOP.BasicFunctors fold :: Monoid m => (f :.: g) m -> m # foldMap :: Monoid m => (a -> m) -> (f :.: g) a -> m # foldr :: (a -> b -> b) -> b -> (f :.: g) a -> b # foldr' :: (a -> b -> b) -> b -> (f :.: g) a -> b # foldl :: (b -> a -> b) -> b -> (f :.: g) a -> b # foldl' :: (b -> a -> b) -> b -> (f :.: g) a -> b # foldr1 :: (a -> a -> a) -> (f :.: g) a -> a # foldl1 :: (a -> a -> a) -> (f :.: g) a -> a # toList :: (f :.: g) a -> [a] # length :: (f :.: g) a -> Int # elem :: Eq a => a -> (f :.: g) a -> Bool # maximum :: Ord a => (f :.: g) a -> a # minimum :: Ord a => (f :.: g) a -> a # | |
(Traversable f, Traversable g) => Traversable (f :.: g) Source # | Since: 0.2.5.0 |
Defined in Generics.SOP.BasicFunctors | |
(Eq1 f, Eq1 g) => Eq1 (f :.: g) Source # | Since: 0.2.4.0 |
(Ord1 f, Ord1 g) => Ord1 (f :.: g) Source # | Since: 0.2.4.0 |
Defined in Generics.SOP.BasicFunctors | |
(Read1 f, Read1 g) => Read1 (f :.: g) Source # | Since: 0.2.4.0 |
Defined in Generics.SOP.BasicFunctors | |
(Show1 f, Show1 g) => Show1 (f :.: g) Source # | Since: 0.2.4.0 |
(NFData1 f, NFData1 g) => NFData1 (f :.: g) Source # | Since: 0.2.5.0 |
Defined in Generics.SOP.BasicFunctors | |
(Eq1 f, Eq1 g, Eq a) => Eq ((f :.: g) a) Source # | |
(Ord1 f, Ord1 g, Ord a) => Ord ((f :.: g) a) Source # | |
Defined in Generics.SOP.BasicFunctors | |
(Read1 f, Read1 g, Read a) => Read ((f :.: g) a) Source # | |
(Show1 f, Show1 g, Show a) => Show ((f :.: g) a) Source # | |
Generic ((f :.: g) p) Source # | |
NFData (f (g a)) => NFData ((f :.: g) a) Source # | Since: 0.2.5.0 |
Defined in Generics.SOP.BasicFunctors | |
HasDatatypeInfo ((f :.: g) p) Source # | |
Defined in Generics.SOP.Instances type DatatypeInfoOf ((f :.: g) p) :: DatatypeInfo Source # datatypeInfo :: proxy ((f :.: g) p) -> DatatypeInfo (Code ((f :.: g) p)) Source # | |
Generic ((f :.: g) p) Source # | |
type Rep ((f :.: g) p) Source # | |
Defined in Generics.SOP.BasicFunctors | |
type DatatypeInfoOf ((f :.: g) p) Source # | |
Defined in Generics.SOP.Instances | |
type Code ((f :.: g) p) Source # | |
Defined in Generics.SOP.Instances |