hypertypes-0.2.2: Typed ASTs
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hyper.Type.Pure

Description

A HyperType to express the simplest plain form of a nested higher-kinded data structure.

The value level hyperfunctions equivalent of Pure is called self in Hyperfunctions papers.

Synopsis

Documentation

newtype Pure h Source #

A HyperType to express the simplest plain form of a nested higher-kinded data structure

Constructors

Pure (h :# Pure) 

Instances

Instances details
HApply Pure Source # 
Instance details

Defined in Hyper.Type.Pure

Methods

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

HContext Pure Source # 
Instance details

Defined in Hyper.Class.Context

Methods

hcontext :: forall (p :: HyperType). (Pure # p) -> Pure # (HFunc p (Const (Pure # p)) :*: p) Source #

HFoldable Pure Source # 
Instance details

Defined in Hyper.Type.Pure

Methods

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

HFunctor Pure Source # 
Instance details

Defined in Hyper.Type.Pure

Methods

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

HMonad Pure Source # 
Instance details

Defined in Hyper.Class.Monad

Methods

hjoin :: forall (p :: HyperType). Recursively HFunctor p => (HCompose Pure Pure # p) -> Pure # p Source #

HNodes Pure Source # 
Instance details

Defined in Hyper.Type.Pure

Associated Types

type HNodesConstraint Pure c Source #

type HWitnessType Pure :: HyperType -> Type Source #

Methods

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

HPointed Pure Source # 
Instance details

Defined in Hyper.Type.Pure

Methods

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

RNodes Pure Source # 
Instance details

Defined in Hyper.Class.Recursive

RTraversable Pure Source # 
Instance details

Defined in Hyper.Class.Recursive

HTraversable Pure Source # 
Instance details

Defined in Hyper.Type.Pure

Methods

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

ZipMatch Pure Source # 
Instance details

Defined in Hyper.Class.ZipMatch

Methods

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

c Pure => Recursively c Pure Source # 
Instance details

Defined in Hyper.Class.Recursive

Generic (Pure h) Source # 
Instance details

Defined in Hyper.Type.Pure

Associated Types

type Rep (Pure h) :: Type -> Type #

Methods

from :: Pure h -> Rep (Pure h) x #

to :: Rep (Pure h) x -> Pure h #

Constraints (Pure h) Show => Show (Pure h) Source # 
Instance details

Defined in Hyper.Type.Pure

Methods

showsPrec :: Int -> Pure h -> ShowS #

show :: Pure h -> String #

showList :: [Pure h] -> ShowS #

Constraints (Pure h) Binary => Binary (Pure h) Source # 
Instance details

Defined in Hyper.Type.Pure

Methods

put :: Pure h -> Put #

get :: Get (Pure h) #

putList :: [Pure h] -> Put #

Constraints (Pure h) NFData => NFData (Pure h) Source # 
Instance details

Defined in Hyper.Type.Pure

Methods

rnf :: Pure h -> () #

Constraints (Pure h) Eq => Eq (Pure h) Source # 
Instance details

Defined in Hyper.Type.Pure

Methods

(==) :: Pure h -> Pure h -> Bool #

(/=) :: Pure h -> Pure h -> Bool #

Constraints (Pure h) Ord => Ord (Pure h) Source # 
Instance details

Defined in Hyper.Type.Pure

Methods

compare :: Pure h -> Pure h -> Ordering #

(<) :: Pure h -> Pure h -> Bool #

(<=) :: Pure h -> Pure h -> Bool #

(>) :: Pure h -> Pure h -> Bool #

(>=) :: Pure h -> Pure h -> Bool #

max :: Pure h -> Pure h -> Pure h #

min :: Pure h -> Pure h -> Pure h #

Pretty (h :# Pure) => Pretty (Pure h) Source # 
Instance details

Defined in Hyper.Type.Pure

Methods

pPrintPrec :: PrettyLevel -> Rational -> Pure h -> Doc #

pPrint :: Pure h -> Doc #

pPrintList :: PrettyLevel -> [Pure h] -> Doc #

type HWitnessType Pure Source # 
Instance details

Defined in Hyper.Type.Pure

type HNodesConstraint Pure constraint Source # 
Instance details

Defined in Hyper.Type.Pure

type HNodesConstraint Pure constraint = constraint Pure
type Rep (Pure h) Source # 
Instance details

Defined in Hyper.Type.Pure

type Rep (Pure h) = D1 ('MetaData "Pure" "Hyper.Type.Pure" "hypertypes-0.2.2-9g9pX7Hb2mGI4yyssTDpOd" 'True) (C1 ('MetaCons "Pure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (h :# Pure))))

_Pure :: Iso (Pure # h) (Pure # j) (h # Pure) (j # Pure) Source #

An Iso from Pure to its content.

Using _Pure rather than the Pure data constructor is recommended, because it helps the type inference know that Pure is parameterized with a HyperType.

data W_Pure node where Source #

Constructors

W_Pure_Pure :: W_Pure Pure