hypertypes-0.2.2: Typed ASTs
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hyper.Type.Prune

Documentation

data Prune h Source #

Constructors

Pruned 
Unpruned (h :# Prune) 

Instances

Instances details
HApply Prune Source # 
Instance details

Defined in Hyper.Type.Prune

Methods

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

HContext Prune Source # 
Instance details

Defined in Hyper.Type.Prune

Methods

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

HFoldable Prune Source # 
Instance details

Defined in Hyper.Type.Prune

Methods

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

HFunctor Prune Source # 
Instance details

Defined in Hyper.Type.Prune

Methods

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

HNodes Prune Source # 
Instance details

Defined in Hyper.Type.Prune

Methods

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

HPointed Prune Source # 
Instance details

Defined in Hyper.Type.Prune

Methods

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

RNodes Prune Source # 
Instance details

Defined in Hyper.Type.Prune

RTraversable Prune Source # 
Instance details

Defined in Hyper.Type.Prune

HTraversable Prune Source # 
Instance details

Defined in Hyper.Type.Prune

Methods

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

ZipMatch Prune Source # 
Instance details

Defined in Hyper.Type.Prune

Methods

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

c Prune => Recursively c Prune Source # 
Instance details

Defined in Hyper.Type.Prune

(Infer m t, HPointed (InferOf t), HTraversable (InferOf t), HNodesConstraint t (HComposeConstraint1 (Infer m) Prune)) => Infer m (HCompose Prune t) Source # 
Instance details

Defined in Hyper.Type.Prune

(Blame m t, HNodesConstraint t (HComposeConstraint1 (Infer m) Prune), HNodesConstraint t (HComposeConstraint1 (Blame m) Prune), HNodesConstraint t (HComposeConstraint1 RNodes Prune), HNodesConstraint t (HComposeConstraint1 (Recursively HFunctor) Prune), HNodesConstraint t (HComposeConstraint1 (Recursively HFoldable) Prune), HNodesConstraint t (HComposeConstraint1 RTraversable Prune)) => Blame m (HCompose Prune t) Source # 
Instance details

Defined in Hyper.Type.Prune

Generic (Prune h) Source # 
Instance details

Defined in Hyper.Type.Prune

Associated Types

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

Methods

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

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

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

Defined in Hyper.Type.Prune

Methods

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

show :: Prune h -> String #

showList :: [Prune h] -> ShowS #

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

Defined in Hyper.Type.Prune

Methods

put :: Prune h -> Put #

get :: Get (Prune h) #

putList :: [Prune h] -> Put #

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

Defined in Hyper.Type.Prune

Methods

rnf :: Prune h -> () #

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

Defined in Hyper.Type.Prune

Methods

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

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

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

Defined in Hyper.Type.Prune

Methods

compare :: Prune h -> Prune h -> Ordering #

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

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

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

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

max :: Prune h -> Prune h -> Prune h #

min :: Prune h -> Prune h -> Prune h #

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

Defined in Hyper.Type.Prune

type HWitnessType Prune Source # 
Instance details

Defined in Hyper.Type.Prune

type HNodesConstraint Prune constraint Source # 
Instance details

Defined in Hyper.Type.Prune

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

Defined in Hyper.Type.Prune

type Rep (Prune h) = D1 ('MetaData "Prune" "Hyper.Type.Prune" "hypertypes-0.2.2-9g9pX7Hb2mGI4yyssTDpOd" 'False) (C1 ('MetaCons "Pruned" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unpruned" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (h :# Prune))))
type InferOf (HCompose Prune t) Source # 
Instance details

Defined in Hyper.Type.Prune

data W_Prune node where Source #

Constructors

W_Prune_Prune :: W_Prune Prune 

_Pruned :: forall h. Prism' (Prune h) () Source #

_Unpruned :: forall h h. Prism (Prune h) (Prune h) ((:#) h Prune) ((:#) h Prune) Source #