hkd-0.1: "higher-kinded data"

Copyright(c) 2019 Edward Kmett 2019 Oleg Grenrus
LicenseBSD-2-Clause OR Apache-2.0
MaintainerOleg Grenrus <oleg.grenrus@iki.fi>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.HKD

Contents

Description

"Higher-Kinded Data" such as it is

Synopsis

Natural transformation

type (~>) f g = forall a. f a -> g a Source #

Functor

class FFunctor (t :: (k -> Type) -> Type) where Source #

Methods

ffmap :: (f ~> g) -> t f -> t g Source #

Instances
FFunctor (Some :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffmap :: (f ~> g) -> Some f -> Some g Source #

FFunctor (Some :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffmap :: (f ~> g) -> Some f -> Some g Source #

FFunctor (Some :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffmap :: (f ~> g) -> Some f -> Some g Source #

FFunctor (V1 :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffmap :: (f ~> g) -> V1 f -> V1 g Source #

FFunctor (U1 :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffmap :: (f ~> g) -> U1 f -> U1 g Source #

FFunctor (Proxy :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffmap :: (f ~> g) -> Proxy f -> Proxy g Source #

FFunctor (Limit :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffmap :: (f ~> g) -> Limit f -> Limit g Source #

FFunctor (Const a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffmap :: (f ~> g) -> Const a f -> Const a g Source #

FFunctor (Element a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffmap :: (f ~> g) -> Element a f -> Element a g Source #

FFunctor (NT f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffmap :: (f0 ~> g) -> NT f f0 -> NT f g Source #

(FFunctor f, FFunctor g) => FFunctor (f :+: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffmap :: (f0 ~> g0) -> (f :+: g) f0 -> (f :+: g) g0 Source #

(FFunctor f, FFunctor g) => FFunctor (f :*: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffmap :: (f0 ~> g0) -> (f :*: g) f0 -> (f :*: g) g0 Source #

FFunctor (K1 i a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffmap :: (f ~> g) -> K1 i a f -> K1 i a g Source #

(FFunctor f, FFunctor g) => FFunctor (Sum f g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffmap :: (f0 ~> g0) -> Sum f g f0 -> Sum f g g0 Source #

(FFunctor f, FFunctor g) => FFunctor (Product f g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffmap :: (f0 ~> g0) -> Product f g f0 -> Product f g g0 Source #

(Functor f, FFunctor g) => FFunctor (f :.: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffmap :: (f0 ~> g0) -> (f :.: g) f0 -> (f :.: g) g0 Source #

(Functor f, FFunctor g) => FFunctor (Compose f g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffmap :: (f0 ~> g0) -> Compose f g f0 -> Compose f g g0 Source #

FFunctor (Tab a :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffmap :: (f ~> g) -> Tab a f -> Tab a g Source #

Contravariant

class FContravariant (t :: (k -> Type) -> Type) where Source #

Methods

fcontramap :: (f ~> g) -> t g -> t f Source #

Instances
FContravariant (V1 :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

fcontramap :: (f ~> g) -> V1 g -> V1 f Source #

FContravariant (U1 :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

fcontramap :: (f ~> g) -> U1 g -> U1 f Source #

FContravariant (Proxy :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

fcontramap :: (f ~> g) -> Proxy g -> Proxy f Source #

FContravariant (Const a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

fcontramap :: (f ~> g) -> Const a g -> Const a f Source #

(FContravariant f, FContravariant g) => FContravariant (f :+: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

fcontramap :: (f0 ~> g0) -> (f :+: g) g0 -> (f :+: g) f0 Source #

(FContravariant f, FContravariant g) => FContravariant (f :*: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

fcontramap :: (f0 ~> g0) -> (f :*: g) g0 -> (f :*: g) f0 Source #

FContravariant (K1 i a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

fcontramap :: (f ~> g) -> K1 i a g -> K1 i a f Source #

(FContravariant f, FContravariant g) => FContravariant (Sum f g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

fcontramap :: (f0 ~> g0) -> Sum f g g0 -> Sum f g f0 Source #

(FContravariant f, FContravariant g) => FContravariant (Product f g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

fcontramap :: (f0 ~> g0) -> Product f g g0 -> Product f g f0 Source #

(Functor f, FContravariant g) => FContravariant (f :.: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

fcontramap :: (f0 ~> g0) -> (f :.: g) g0 -> (f :.: g) f0 Source #

(Functor f, FContravariant g) => FContravariant (Compose f g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

fcontramap :: (f0 ~> g0) -> Compose f g g0 -> Compose f g f0 Source #

FContravariant Logarithm Source # 
Instance details

Defined in Data.HKD

Methods

fcontramap :: (f ~> g) -> Logarithm g -> Logarithm f Source #

Foldable

class FFoldable (t :: (k -> Type) -> Type) where Source #

Minimal complete definition

ffoldMap

Methods

ffoldMap :: Monoid m => (forall a. f a -> m) -> t f -> m Source #

flengthAcc :: Int -> t f -> Int Source #

Instances
FFoldable (Some :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffoldMap :: Monoid m => (forall (a :: k0). f a -> m) -> Some f -> m Source #

flengthAcc :: Int -> Some f -> Int Source #

FFoldable (Some :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffoldMap :: Monoid m => (forall (a :: k0). f a -> m) -> Some f -> m Source #

flengthAcc :: Int -> Some f -> Int Source #

FFoldable (Some :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffoldMap :: Monoid m => (forall (a :: k0). f a -> m) -> Some f -> m Source #

flengthAcc :: Int -> Some f -> Int Source #

FFoldable (U1 :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffoldMap :: Monoid m => (forall (a :: k0). f a -> m) -> U1 f -> m Source #

flengthAcc :: Int -> U1 f -> Int Source #

FFoldable (V1 :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffoldMap :: Monoid m => (forall (a :: k0). f a -> m) -> V1 f -> m Source #

flengthAcc :: Int -> V1 f -> Int Source #

FFoldable (Proxy :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffoldMap :: Monoid m => (forall (a :: k0). f a -> m) -> Proxy f -> m Source #

flengthAcc :: Int -> Proxy f -> Int Source #

FFoldable (Limit :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffoldMap :: Monoid m => (forall (a :: k0). f a -> m) -> Limit f -> m Source #

flengthAcc :: Int -> Limit f -> Int Source #

FFoldable (Const a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffoldMap :: Monoid m => (forall (a0 :: k0). f a0 -> m) -> Const a f -> m Source #

flengthAcc :: Int -> Const a f -> Int Source #

FFoldable (Element a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffoldMap :: Monoid m => (forall (a0 :: k0). f a0 -> m) -> Element a f -> m Source #

flengthAcc :: Int -> Element a f -> Int Source #

(FFoldable f, FFoldable g) => FFoldable (f :+: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffoldMap :: Monoid m => (forall (a :: k0). f0 a -> m) -> (f :+: g) f0 -> m Source #

flengthAcc :: Int -> (f :+: g) f0 -> Int Source #

(FFoldable f, FFoldable g) => FFoldable (f :*: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffoldMap :: Monoid m => (forall (a :: k0). f0 a -> m) -> (f :*: g) f0 -> m Source #

flengthAcc :: Int -> (f :*: g) f0 -> Int Source #

FFoldable (K1 i a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffoldMap :: Monoid m => (forall (a0 :: k0). f a0 -> m) -> K1 i a f -> m Source #

flengthAcc :: Int -> K1 i a f -> Int Source #

(FFoldable f, FFoldable g) => FFoldable (Sum f g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffoldMap :: Monoid m => (forall (a :: k0). f0 a -> m) -> Sum f g f0 -> m Source #

flengthAcc :: Int -> Sum f g f0 -> Int Source #

(FFoldable f, FFoldable g) => FFoldable (Product f g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffoldMap :: Monoid m => (forall (a :: k0). f0 a -> m) -> Product f g f0 -> m Source #

flengthAcc :: Int -> Product f g f0 -> Int Source #

(Foldable f, FFoldable g) => FFoldable (f :.: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffoldMap :: Monoid m => (forall (a :: k0). f0 a -> m) -> (f :.: g) f0 -> m Source #

flengthAcc :: Int -> (f :.: g) f0 -> Int Source #

(Foldable f, FFoldable g) => FFoldable (Compose f g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffoldMap :: Monoid m => (forall (a :: k0). f0 a -> m) -> Compose f g f0 -> m Source #

flengthAcc :: Int -> Compose f g f0 -> Int Source #

flength :: FFoldable t => t f -> Int Source #

ftraverse_ :: (FFoldable t, Applicative m) => (forall a. f a -> m b) -> t f -> m () Source #

ffor_ :: (FFoldable t, Applicative m) => t f -> (forall a. f a -> m b) -> m () Source #

Traversable

class (FFoldable t, FFunctor t) => FTraversable (t :: (k -> Type) -> Type) where Source #

Methods

ftraverse :: Applicative m => (forall a. f a -> m (g a)) -> t f -> m (t g) Source #

Instances
FTraversable (Some :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ftraverse :: Applicative m => (forall (a :: k0). f a -> m (g a)) -> Some f -> m (Some g) Source #

FTraversable (Some :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ftraverse :: Applicative m => (forall (a :: k0). f a -> m (g a)) -> Some f -> m (Some g) Source #

FTraversable (Some :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ftraverse :: Applicative m => (forall (a :: k0). f a -> m (g a)) -> Some f -> m (Some g) Source #

FTraversable (V1 :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ftraverse :: Applicative m => (forall (a :: k0). f a -> m (g a)) -> V1 f -> m (V1 g) Source #

FTraversable (U1 :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ftraverse :: Applicative m => (forall (a :: k0). f a -> m (g a)) -> U1 f -> m (U1 g) Source #

FTraversable (Proxy :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ftraverse :: Applicative m => (forall (a :: k0). f a -> m (g a)) -> Proxy f -> m (Proxy g) Source #

FTraversable (Const a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ftraverse :: Applicative m => (forall (a0 :: k0). f a0 -> m (g a0)) -> Const a f -> m (Const a g) Source #

FTraversable (Element a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ftraverse :: Applicative m => (forall (a0 :: k0). f a0 -> m (g a0)) -> Element a f -> m (Element a g) Source #

(FTraversable f, FTraversable g) => FTraversable (f :+: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ftraverse :: Applicative m => (forall (a :: k0). f0 a -> m (g0 a)) -> (f :+: g) f0 -> m ((f :+: g) g0) Source #

(FTraversable f, FTraversable g) => FTraversable (f :*: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ftraverse :: Applicative m => (forall (a :: k0). f0 a -> m (g0 a)) -> (f :*: g) f0 -> m ((f :*: g) g0) Source #

FTraversable (K1 i a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ftraverse :: Applicative m => (forall (a0 :: k0). f a0 -> m (g a0)) -> K1 i a f -> m (K1 i a g) Source #

(FTraversable f, FTraversable g) => FTraversable (Sum f g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ftraverse :: Applicative m => (forall (a :: k0). f0 a -> m (g0 a)) -> Sum f g f0 -> m (Sum f g g0) Source #

(FTraversable f, FTraversable g) => FTraversable (Product f g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ftraverse :: Applicative m => (forall (a :: k0). f0 a -> m (g0 a)) -> Product f g f0 -> m (Product f g g0) Source #

(Traversable f, FTraversable g) => FTraversable (f :.: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ftraverse :: Applicative m => (forall (a :: k0). f0 a -> m (g0 a)) -> (f :.: g) f0 -> m ((f :.: g) g0) Source #

(Traversable f, FTraversable g) => FTraversable (Compose f g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ftraverse :: Applicative m => (forall (a :: k0). f0 a -> m (g0 a)) -> Compose f g f0 -> m (Compose f g g0) Source #

ffmapDefault :: FTraversable t => (f ~> g) -> t f -> t g Source #

ffoldMapDefault :: (FTraversable t, Monoid m) => (forall a. f a -> m) -> t f -> m Source #

ffor :: (FTraversable t, Applicative m) => t f -> (forall a. f a -> m (g a)) -> m (t g) Source #

Generic derivation

gftraverse :: forall t (f :: Type -> Type) (g :: Type -> Type) m. (Applicative m, Generic (t f), Generic (t g), GFTraversable (Curried (Yoneda m)) f g (Rep (t f)) (Rep (t g))) => (forall a. f a -> m (g a)) -> t f -> m (t g) Source #

Generically derive ftraverse.

Simple usage:

data Record f = Record
    { fieldInt    :: f Int
    , fieldString :: f String
    , fieldSome   :: Some f
    }
  deriving (Generic)

instance FFunctor     Record where ffmap     = ffmapDefault
instance FFoldable    Record where ffoldMap  = ffoldMapDefault
instance FTraversable Record where ftraverse = gftraverse

Zip & Repeat

class FFunctor t => FZip t where Source #

Methods

fzipWith :: (forall x. f x -> g x -> h x) -> t f -> t g -> t h Source #

Instances
FZip (V1 :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

fzipWith :: (forall (x :: k0). f x -> g x -> h x) -> V1 f -> V1 g -> V1 h Source #

FZip (U1 :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

fzipWith :: (forall (x :: k0). f x -> g x -> h x) -> U1 f -> U1 g -> U1 h Source #

FZip (Proxy :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

fzipWith :: (forall (x :: k0). f x -> g x -> h x) -> Proxy f -> Proxy g -> Proxy h Source #

FZip (Limit :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

fzipWith :: (forall (x :: k0). f x -> g x -> h x) -> Limit f -> Limit g -> Limit h Source #

Semigroup a => FZip (Const a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

fzipWith :: (forall (x :: k0). f x -> g x -> h x) -> Const a f -> Const a g -> Const a h Source #

FZip (Element a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

fzipWith :: (forall (x :: k0). f x -> g x -> h x) -> Element a f -> Element a g -> Element a h Source #

FZip (NT f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

fzipWith :: (forall (x :: k0). f0 x -> g x -> h x) -> NT f f0 -> NT f g -> NT f h Source #

(FZip f, FZip g) => FZip (f :*: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

fzipWith :: (forall (x :: k0). f0 x -> g0 x -> h x) -> (f :*: g) f0 -> (f :*: g) g0 -> (f :*: g) h Source #

Semigroup a => FZip (K1 i a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

fzipWith :: (forall (x :: k0). f x -> g x -> h x) -> K1 i a f -> K1 i a g -> K1 i a h Source #

(FZip f, FZip g) => FZip (Product f g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

fzipWith :: (forall (x :: k0). f0 x -> g0 x -> h x) -> Product f g f0 -> Product f g g0 -> Product f g h Source #

(Applicative f, FZip g) => FZip (f :.: g :: (k -> Type) -> Type) Source #

We only need an Apply part of an Applicative.

Instance details

Defined in Data.HKD

Methods

fzipWith :: (forall (x :: k0). f0 x -> g0 x -> h x) -> (f :.: g) f0 -> (f :.: g) g0 -> (f :.: g) h Source #

(Applicative f, FZip g) => FZip (Compose f g :: (k -> Type) -> Type) Source #

We only need an Apply part of an Applicative.

Instance details

Defined in Data.HKD

Methods

fzipWith :: (forall (x :: k0). f0 x -> g0 x -> h x) -> Compose f g f0 -> Compose f g g0 -> Compose f g h Source #

class FZip t => FRepeat t where Source #

Methods

frepeat :: (forall x. f x) -> t f Source #

Instances
FRepeat (U1 :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

frepeat :: (forall (x :: k0). f x) -> U1 f Source #

FRepeat (Proxy :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

frepeat :: (forall (x :: k0). f x) -> Proxy f Source #

FRepeat (Limit :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

frepeat :: (forall (x :: k0). f x) -> Limit f Source #

(Monoid a, Semigroup a) => FRepeat (Const a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

frepeat :: (forall (x :: k0). f x) -> Const a f Source #

FRepeat (Element a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

frepeat :: (forall (x :: k0). f x) -> Element a f Source #

FRepeat (NT a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

frepeat :: (forall (x :: k0). f x) -> NT a f Source #

(FRepeat f, FRepeat g) => FRepeat (f :*: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

frepeat :: (forall (x :: k0). f0 x) -> (f :*: g) f0 Source #

(Monoid a, Semigroup a) => FRepeat (K1 i a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

frepeat :: (forall (x :: k0). f x) -> K1 i a f Source #

(FRepeat f, FRepeat g) => FRepeat (Product f g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

frepeat :: (forall (x :: k0). f0 x) -> Product f g f0 Source #

(Applicative f, FRepeat g) => FRepeat (f :.: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

frepeat :: (forall (x :: k0). f0 x) -> (f :.: g) f0 Source #

(Applicative f, FRepeat g) => FRepeat (Compose f g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

frepeat :: (forall (x :: k0). f0 x) -> Compose f g f0 Source #

Generic derivation

gfzipWith :: forall t (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). (Generic (t f), Generic (t g), Generic (t h), GFZip f g h (Rep (t f)) (Rep (t g)) (Rep (t h))) => (forall a. f a -> g a -> h a) -> t f -> t g -> t h Source #

Generically derive fzipWith.

Simple usage:

data Record f = Record
    { fieldInt    :: f Int
    , fieldString :: f String
    }
  deriving (Generic)

instance FZip    Record where fzipWith = gfzipWith
instance FRepeat Record where frepeat  = gfrepeat

gfrepeat :: forall t (f :: Type -> Type). (Generic (t f), GFRepeat f (Rep (t f))) => (forall x. f x) -> t f Source #

Higher kinded data

See also Data.Some in some package. hkd provides instances for it.

newtype Logarithm f Source #

A logarithm.

Recall that function arrow, -> is an exponential object. If we take f = (->) r, then

Logarithm ((->) r) ≅ forall a. (r -> a) -> a ≅ r

and this works for all Distributive / Representable functors.

Constructors

Logarithm 

Fields

Instances
FContravariant Logarithm Source # 
Instance details

Defined in Data.HKD

Methods

fcontramap :: (f ~> g) -> Logarithm g -> Logarithm f Source #

newtype Tab a f Source #

Tabulation.

Constructors

Tab 

Fields

Instances
FFunctor (Tab a :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffmap :: (f ~> g) -> Tab a f -> Tab a g Source #

indexLogarithm :: f a -> Logarithm f -> a Source #

newtype Element a f Source #

Element in f

Constructors

Element 

Fields

Instances
FRepeat (Element a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

frepeat :: (forall (x :: k0). f x) -> Element a f Source #

FZip (Element a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

fzipWith :: (forall (x :: k0). f x -> g x -> h x) -> Element a f -> Element a g -> Element a h Source #

FTraversable (Element a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ftraverse :: Applicative m => (forall (a0 :: k0). f a0 -> m (g a0)) -> Element a f -> m (Element a g) Source #

FFoldable (Element a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffoldMap :: Monoid m => (forall (a0 :: k0). f a0 -> m) -> Element a f -> m Source #

flengthAcc :: Int -> Element a f -> Int Source #

FFunctor (Element a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffmap :: (f ~> g) -> Element a f -> Element a g Source #

newtype NT f g Source #

Newtyped "natural" transformation

Constructors

NT 

Fields

Instances
FRepeat (NT a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

frepeat :: (forall (x :: k0). f x) -> NT a f Source #

FZip (NT f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

fzipWith :: (forall (x :: k0). f0 x -> g x -> h x) -> NT f f0 -> NT f g -> NT f h Source #

FFunctor (NT f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffmap :: (f0 ~> g) -> NT f f0 -> NT f g Source #

newtype Limit f Source #

Constructors

Limit 

Fields

Instances
FRepeat (Limit :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

frepeat :: (forall (x :: k0). f x) -> Limit f Source #

FZip (Limit :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

fzipWith :: (forall (x :: k0). f x -> g x -> h x) -> Limit f -> Limit g -> Limit h Source #

FFoldable (Limit :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffoldMap :: Monoid m => (forall (a :: k0). f a -> m) -> Limit f -> m Source #

flengthAcc :: Int -> Limit f -> Int Source #

FFunctor (Limit :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.HKD

Methods

ffmap :: (f ~> g) -> Limit f -> Limit g Source #