Safe Haskell | None |
---|---|
Language | Haskell2010 |
Documentation
data ((a :: (Type -> Type) -> Type) :* (b :: (Type -> Type) -> Type)) (f :: Type -> Type) infixr 4 Source #
Infix version of Product
. Allows to combine
higher-kinded types, and keep them partially applied until needed:
data User = User { name :: String, age :: Int } deriving Generic type Config = Nested User :* Single Int configOpt :: Config Opt configOpt = ...
(a f) :* (b f) infixr 4 |
Instances
newtype Tagged (t :: k) (a :: (Type -> Type) -> Type) (f :: Type -> Type) Source #
This type adds a type-level phantom tag to a higher-kinded type.
Its JSON instance allows using :*
with JSONSource
.
Instances
ProductB a => ProductB (Tagged t a :: (Type -> Type) -> Type) Source # | |
TraversableB a => TraversableB (Tagged t a :: (Type -> Type) -> Type) Source # | |
Defined in Options.Harg.Het.Prod btraverse :: Applicative t0 => (forall (a0 :: k). f a0 -> t0 (g a0)) -> Tagged t a f -> t0 (Tagged t a g) # | |
FunctorB a => FunctorB (Tagged t a :: (Type -> Type) -> Type) Source # | |
Defined in Options.Harg.Het.Prod | |
(FromJSON (a Maybe), FromJSON (b Maybe), ProductB a, ProductB b, KnownSymbol ta, KnownSymbol tb) => FromJSON ((Tagged ta a :* Tagged tb b) Maybe) Source # | |
(FromJSON (a Maybe), FromJSON (b' Maybe), ProductB a, ProductB b', KnownSymbol ta, b' ~ (Tagged tb b :* c)) => FromJSON ((Tagged ta a :* (Tagged tb b :* c)) Maybe) Source # | |
Generic (Tagged t a f) Source # | |
FromJSON (a f) => FromJSON (Tagged t a f) Source # | |
type Rep (Tagged t a f) Source # | |
Defined in Options.Harg.Het.Prod |