hypertypes-0.2.2: Typed ASTs
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hyper.Type

Description

A HyperType is a type parameterized by a hypertype.

This infinite definition is expressible using the AHyperType Kind for hypertypes.

For more information see the README.

Synopsis

Documentation

type HyperType = AHyperType -> Type Source #

A hypertype is a type parameterized by a hypertype

newtype AHyperType Source #

Constructors

AHyperType HyperType 

Instances

Instances details
Infer m h => Infer m (Rec1 h) Source # 
Instance details

Defined in Hyper.Class.Infer

Methods

inferBody :: forall (h0 :: AHyperType -> Type). (Rec1 h # InferChild m h0) -> m (Rec1 h # h0, InferOf (Rec1 h) # UVarOf m) Source #

inferContext :: proxy0 m -> proxy1 (Rec1 h) -> Dict (HNodesConstraint (Rec1 h) (Infer m), HNodesConstraint (InferOf (Rec1 h)) (UnifyGen m)) Source #

c (Const a :: AHyperType -> Type) => Recursively c (Const a :: AHyperType -> Type) Source # 
Instance details

Defined in Hyper.Class.Recursive

Methods

recursively :: proxy (c (Const a)) -> Dict (c (Const a), HNodesConstraint (Const a) (Recursively c)) Source #

(InferOf a ~ InferOf b, Infer m a, Infer m b) => Infer m (a :+: b) Source # 
Instance details

Defined in Hyper.Class.Infer

Methods

inferBody :: forall (h :: AHyperType -> Type). ((a :+: b) # InferChild m h) -> m ((a :+: b) # h, InferOf (a :+: b) # UVarOf m) Source #

inferContext :: proxy0 m -> proxy1 (a :+: b) -> Dict (HNodesConstraint (a :+: b) (Infer m), HNodesConstraint (InferOf (a :+: b)) (UnifyGen m)) Source #

Infer m h => Infer m (M1 i c h) Source # 
Instance details

Defined in Hyper.Class.Infer

Methods

inferBody :: forall (h0 :: AHyperType -> Type). (M1 i c h # InferChild m h0) -> m (M1 i c h # h0, InferOf (M1 i c h) # UVarOf m) Source #

inferContext :: proxy0 m -> proxy1 (M1 i c h) -> Dict (HNodesConstraint (M1 i c h) (Infer m), HNodesConstraint (InferOf (M1 i c h)) (UnifyGen m)) Source #

Semigroup a => HApply (Const a :: AHyperType -> Type) Source # 
Instance details

Defined in Hyper.Class.Apply

Methods

hzip :: forall (p :: HyperType) (q :: HyperType). (Const a # p) -> (Const a # q) -> Const a # (p :*: q) Source #

HFoldable (Const a :: AHyperType -> Type) Source # 
Instance details

Defined in Hyper.Class.Foldable

Methods

hfoldMap :: Monoid a0 => (forall (n :: HyperType). HWitness (Const a) n -> (p # n) -> a0) -> (Const a # p) -> a0 Source #

HFoldable h => HFoldable (Rec1 h) Source # 
Instance details

Defined in Hyper.Class.Foldable

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (Rec1 h) n -> (p # n) -> a) -> (Rec1 h # p) -> a Source #

HFunctor (Const a :: AHyperType -> Type) Source # 
Instance details

Defined in Hyper.Class.Functor

Methods

hmap :: (forall (n :: HyperType). HWitness (Const a) n -> (p # n) -> q # n) -> (Const a # p) -> Const a # q Source #

HFunctor h => HFunctor (Rec1 h) Source # 
Instance details

Defined in Hyper.Class.Functor

Methods

hmap :: (forall (n :: HyperType). HWitness (Rec1 h) n -> (p # n) -> q # n) -> (Rec1 h # p) -> Rec1 h # q Source #

HNodes (Const a :: AHyperType -> Type) Source # 
Instance details

Defined in Hyper.Class.Nodes

Associated Types

type HNodesConstraint (Const a) c Source #

type HWitnessType (Const a) :: HyperType -> Type Source #

Methods

hLiftConstraint :: forall c (n :: HyperType) r. HNodesConstraint (Const a) c => HWitness (Const a) n -> Proxy c -> (c n => r) -> r Source #

HNodes h => HNodes (Rec1 h) Source # 
Instance details

Defined in Hyper.Class.Nodes

Associated Types

type HNodesConstraint (Rec1 h) c Source #

type HWitnessType (Rec1 h) :: HyperType -> Type Source #

Methods

hLiftConstraint :: forall c (n :: HyperType) r. HNodesConstraint (Rec1 h) c => HWitness (Rec1 h) n -> Proxy c -> (c n => r) -> r Source #

Monoid a => HPointed (Const a :: AHyperType -> Type) Source # 
Instance details

Defined in Hyper.Class.Pointed

Methods

hpure :: (forall (n :: HyperType). HWitness (Const a) n -> p # n) -> Const a # p Source #

RNodes (Const a :: AHyperType -> Type) Source # 
Instance details

Defined in Hyper.Class.Recursive

RTraversable (Const a :: AHyperType -> Type) Source # 
Instance details

Defined in Hyper.Class.Recursive

HTraversable (Const a :: AHyperType -> Type) Source # 
Instance details

Defined in Hyper.Class.Traversable

Methods

hsequence :: forall f (p :: AHyperType -> Type). Applicative f => (Const a # ContainedH f p) -> f (Const a # p) Source #

HTraversable h => HTraversable (Rec1 h) Source # 
Instance details

Defined in Hyper.Class.Traversable

Methods

hsequence :: forall f (p :: AHyperType -> Type). Applicative f => (Rec1 h # ContainedH f p) -> f (Rec1 h # p) Source #

Eq a => ZipMatch (Const a :: AHyperType -> Type) Source # 
Instance details

Defined in Hyper.Class.ZipMatch

Methods

zipMatch :: forall (p :: HyperType) (q :: HyperType). (Const a # p) -> (Const a # q) -> Maybe (Const a # (p :*: q)) Source #

ZipMatch h => ZipMatch (Rec1 h) Source # 
Instance details

Defined in Hyper.Class.ZipMatch

Methods

zipMatch :: forall (p :: HyperType) (q :: HyperType). (Rec1 h # p) -> (Rec1 h # q) -> Maybe (Rec1 h # (p :*: q)) Source #

(HApply a, HApply b) => HApply (a :*: b) Source # 
Instance details

Defined in Hyper.Class.Apply

Methods

hzip :: forall (p :: HyperType) (q :: HyperType). ((a :*: b) # p) -> ((a :*: b) # q) -> (a :*: b) # (p :*: q) Source #

(HFoldable a, HFoldable b) => HFoldable (a :*: b) Source # 
Instance details

Defined in Hyper.Class.Foldable

Methods

hfoldMap :: Monoid a0 => (forall (n :: HyperType). HWitness (a :*: b) n -> (p # n) -> a0) -> ((a :*: b) # p) -> a0 Source #

(HFoldable a, HFoldable b) => HFoldable (a :+: b) Source # 
Instance details

Defined in Hyper.Class.Foldable

Methods

hfoldMap :: Monoid a0 => (forall (n :: HyperType). HWitness (a :+: b) n -> (p # n) -> a0) -> ((a :+: b) # p) -> a0 Source #

(HFunctor a, HFunctor b) => HFunctor (a :*: b) Source # 
Instance details

Defined in Hyper.Class.Functor

Methods

hmap :: (forall (n :: HyperType). HWitness (a :*: b) n -> (p # n) -> q # n) -> ((a :*: b) # p) -> (a :*: b) # q Source #

(HFunctor a, HFunctor b) => HFunctor (a :+: b) Source # 
Instance details

Defined in Hyper.Class.Functor

Methods

hmap :: (forall (n :: HyperType). HWitness (a :+: b) n -> (p # n) -> q # n) -> ((a :+: b) # p) -> (a :+: b) # q Source #

(HNodes a, HNodes b) => HNodes (a :*: b) Source # 
Instance details

Defined in Hyper.Class.Nodes

Associated Types

type HNodesConstraint (a :*: b) c Source #

type HWitnessType (a :*: b) :: HyperType -> Type Source #

Methods

hLiftConstraint :: forall c (n :: HyperType) r. HNodesConstraint (a :*: b) c => HWitness (a :*: b) n -> Proxy c -> (c n => r) -> r Source #

(HNodes a, HNodes b) => HNodes (a :+: b) Source # 
Instance details

Defined in Hyper.Class.Nodes

Associated Types

type HNodesConstraint (a :+: b) c Source #

type HWitnessType (a :+: b) :: HyperType -> Type Source #

Methods

hLiftConstraint :: forall c (n :: HyperType) r. HNodesConstraint (a :+: b) c => HWitness (a :+: b) n -> Proxy c -> (c n => r) -> r Source #

(HPointed a, HPointed b) => HPointed (a :*: b) Source # 
Instance details

Defined in Hyper.Class.Pointed

Methods

hpure :: (forall (n :: HyperType). HWitness (a :*: b) n -> p # n) -> (a :*: b) # p Source #

(HTraversable a, HTraversable b) => HTraversable (a :*: b) Source # 
Instance details

Defined in Hyper.Class.Traversable

Methods

hsequence :: forall f (p :: AHyperType -> Type). Applicative f => ((a :*: b) # ContainedH f p) -> f ((a :*: b) # p) Source #

(HTraversable a, HTraversable b) => HTraversable (a :+: b) Source # 
Instance details

Defined in Hyper.Class.Traversable

Methods

hsequence :: forall f (p :: AHyperType -> Type). Applicative f => ((a :+: b) # ContainedH f p) -> f ((a :+: b) # p) Source #

(ZipMatch a, ZipMatch b) => ZipMatch (a :*: b) Source # 
Instance details

Defined in Hyper.Class.ZipMatch

Methods

zipMatch :: forall (p :: HyperType) (q :: HyperType). ((a :*: b) # p) -> ((a :*: b) # q) -> Maybe ((a :*: b) # (p :*: q)) Source #

(ZipMatch a, ZipMatch b) => ZipMatch (a :+: b) Source # 
Instance details

Defined in Hyper.Class.ZipMatch

Methods

zipMatch :: forall (p :: HyperType) (q :: HyperType). ((a :+: b) # p) -> ((a :+: b) # q) -> Maybe ((a :+: b) # (p :*: q)) Source #

HFoldable h => HFoldable (M1 i m h) Source # 
Instance details

Defined in Hyper.Class.Foldable

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (M1 i m h) n -> (p # n) -> a) -> (M1 i m h # p) -> a Source #

HFunctor h => HFunctor (M1 i m h) Source # 
Instance details

Defined in Hyper.Class.Functor

Methods

hmap :: (forall (n :: HyperType). HWitness (M1 i m h) n -> (p # n) -> q # n) -> (M1 i m h # p) -> M1 i m h # q Source #

HNodes h => HNodes (M1 i m h) Source # 
Instance details

Defined in Hyper.Class.Nodes

Associated Types

type HNodesConstraint (M1 i m h) c Source #

type HWitnessType (M1 i m h) :: HyperType -> Type Source #

Methods

hLiftConstraint :: forall c (n :: HyperType) r. HNodesConstraint (M1 i m h) c => HWitness (M1 i m h) n -> Proxy c -> (c n => r) -> r Source #

HTraversable h => HTraversable (M1 i m h) Source # 
Instance details

Defined in Hyper.Class.Traversable

Methods

hsequence :: forall f (p :: AHyperType -> Type). Applicative f => (M1 i m h # ContainedH f p) -> f (M1 i m h # p) Source #

ZipMatch h => ZipMatch (M1 i m h) Source # 
Instance details

Defined in Hyper.Class.ZipMatch

Methods

zipMatch :: forall (p :: HyperType) (q :: HyperType). (M1 i m h # p) -> (M1 i m h # q) -> Maybe (M1 i m h # (p :*: q)) Source #

type InferOf (Rec1 h) Source # 
Instance details

Defined in Hyper.Class.Infer

type InferOf (Rec1 h) = InferOf h
type HWitnessType (Const a :: AHyperType -> Type) Source # 
Instance details

Defined in Hyper.Class.Nodes

type HWitnessType (Rec1 h) Source # 
Instance details

Defined in Hyper.Class.Nodes

type HNodesConstraint (Const a :: AHyperType -> Type) _1 Source # 
Instance details

Defined in Hyper.Class.Nodes

type HNodesConstraint (Const a :: AHyperType -> Type) _1 = ()
type HNodesConstraint (Rec1 h) c Source # 
Instance details

Defined in Hyper.Class.Nodes

type InferOf (a :+: _1) Source # 
Instance details

Defined in Hyper.Class.Infer

type InferOf (a :+: _1) = InferOf a
type HWitnessType (a :*: b) Source # 
Instance details

Defined in Hyper.Class.Nodes

type HWitnessType (a :+: b) Source # 
Instance details

Defined in Hyper.Class.Nodes

type HNodesConstraint (a :*: b) x Source # 
Instance details

Defined in Hyper.Class.Nodes

type HNodesConstraint (a :+: b) x Source # 
Instance details

Defined in Hyper.Class.Nodes

type InferOf (M1 _1 _2 h) Source # 
Instance details

Defined in Hyper.Class.Infer

type InferOf (M1 _1 _2 h) = InferOf h
type HWitnessType (M1 i m h) Source # 
Instance details

Defined in Hyper.Class.Nodes

type HWitnessType (M1 i m h) = HWitnessType h
type HNodesConstraint (M1 i m h) c Source # 
Instance details

Defined in Hyper.Class.Nodes

type HNodesConstraint (M1 i m h) c = HNodesConstraint h c

type family GetHyperType h where ... Source #

A type-level getter for the type constructor encoded in AHyperType.

Notes:

  • If DataKinds supported lifting field getters this would had been replaced with the type's getter.
  • GetHyperType is injective, but due to no support for constrained type families, that's not expressible at the moment.
  • Because GetHyperType can't declared as bijective, uses of it may restrict inference. In those cases wrapping terms with the asHyper helper assists Haskell's type inference as if Haskell knew that GetHyperType was bijective.

Equations

GetHyperType ('AHyperType t) = t 

type (#) h p = h ('AHyperType p) :: Type Source #

A type synonym to express nested-HKD structures

type (:#) h p = GetHyperType h # p Source #

A type synonym to express child nodes in nested-HKDs

asHyper :: (h # p) -> h # p Source #

An id variant which tells the type checker that its argument is a hypertype.

See the notes for GetHyperType which expand on why this might be used.

Note that asHyper may often be used during development to assist the inference of incomplete code, but removed once the code is complete.