hypertypes-0.1.0.2: Typed ASTs
Safe HaskellNone
LanguageHaskell2010

Hyper.Combinator.Ann

Synopsis

Documentation

data Ann a h Source #

Constructors

Ann 

Fields

Instances

Instances details
(c (Ann a), Recursively c a) => Recursively c (Ann a) Source # 
Instance details

Defined in Hyper.Combinator.Ann

Methods

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

HNodes a => HNodes (Ann a) Source # 
Instance details

Defined in Hyper.Combinator.Ann

Associated Types

type HNodesConstraint (Ann a) c Source #

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

Methods

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

HPointed a => HPointed (Ann a) Source # 
Instance details

Defined in Hyper.Combinator.Ann

Methods

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

HFunctor a => HFunctor (Ann a) Source # 
Instance details

Defined in Hyper.Combinator.Ann

Methods

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

HFoldable a => HFoldable (Ann a) Source # 
Instance details

Defined in Hyper.Combinator.Ann

Methods

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

HTraversable a => HTraversable (Ann a) Source # 
Instance details

Defined in Hyper.Combinator.Ann

Methods

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

HApply a => HApply (Ann a) Source # 
Instance details

Defined in Hyper.Combinator.Ann

Methods

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

RTraversable a => RTraversable (Ann a) Source # 
Instance details

Defined in Hyper.Combinator.Ann

RNodes a => RNodes (Ann a) Source # 
Instance details

Defined in Hyper.Combinator.Ann

Methods

recursiveHNodes :: proxy (Ann a) -> Dict (HNodesConstraint (Ann a) RNodes) Source #

(HContext a, HFunctor a) => HContext (Ann a) Source # 
Instance details

Defined in Hyper.Class.Context

Methods

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

Constraints (Ann a h) Eq => Eq (Ann a h) Source # 
Instance details

Defined in Hyper.Combinator.Ann

Methods

(==) :: Ann a h -> Ann a h -> Bool #

(/=) :: Ann a h -> Ann a h -> Bool #

Constraints (Ann a h) Ord => Ord (Ann a h) Source # 
Instance details

Defined in Hyper.Combinator.Ann

Methods

compare :: Ann a h -> Ann a h -> Ordering #

(<) :: Ann a h -> Ann a h -> Bool #

(<=) :: Ann a h -> Ann a h -> Bool #

(>) :: Ann a h -> Ann a h -> Bool #

(>=) :: Ann a h -> Ann a h -> Bool #

max :: Ann a h -> Ann a h -> Ann a h #

min :: Ann a h -> Ann a h -> Ann a h #

Constraints (Ann a h) Show => Show (Ann a h) Source # 
Instance details

Defined in Hyper.Combinator.Ann

Methods

showsPrec :: Int -> Ann a h -> ShowS #

show :: Ann a h -> String #

showList :: [Ann a h] -> ShowS #

Generic (Ann a h) Source # 
Instance details

Defined in Hyper.Combinator.Ann

Associated Types

type Rep (Ann a h) :: Type -> Type #

Methods

from :: Ann a h -> Rep (Ann a h) x #

to :: Rep (Ann a h) x -> Ann a h #

Constraints (Ann a h) Binary => Binary (Ann a h) Source # 
Instance details

Defined in Hyper.Combinator.Ann

Methods

put :: Ann a h -> Put #

get :: Get (Ann a h) #

putList :: [Ann a h] -> Put #

Constraints (Ann a h) NFData => NFData (Ann a h) Source # 
Instance details

Defined in Hyper.Combinator.Ann

Methods

rnf :: Ann a h -> () #

RNodes h => HNodes (HFlip Ann h) Source # 
Instance details

Defined in Hyper.Combinator.Ann

Associated Types

type HNodesConstraint (HFlip Ann h) c Source #

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

Methods

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

Recursively HFunctor h => HFunctor (HFlip Ann h) Source # 
Instance details

Defined in Hyper.Combinator.Ann

Methods

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

Recursively HFoldable h => HFoldable (HFlip Ann h) Source # 
Instance details

Defined in Hyper.Combinator.Ann

Methods

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

RTraversable h => HTraversable (HFlip Ann h) Source # 
Instance details

Defined in Hyper.Combinator.Ann

Methods

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

(Recursively HContext h, Recursively HFunctor h) => HContext (HFlip Ann h) Source # 
Instance details

Defined in Hyper.Class.Context

Methods

hcontext :: forall (p :: HyperType). (HFlip Ann h # p) -> HFlip Ann h # (HFunc p (Const (HFlip Ann h # p)) :*: p) Source #

type HWitnessType (Ann a) Source # 
Instance details

Defined in Hyper.Combinator.Ann

type HWitnessType (Ann a)
type HNodesConstraint (Ann a) constraint Source # 
Instance details

Defined in Hyper.Combinator.Ann

type HNodesConstraint (Ann a) constraint = (HNodesConstraint a constraint, constraint (Ann a))
type Rep (Ann a h) Source # 
Instance details

Defined in Hyper.Combinator.Ann

type Rep (Ann a h) = D1 ('MetaData "Ann" "Hyper.Combinator.Ann" "hypertypes-0.1.0.2-GDiSRF0EwgQ6Mkx3yytlTL" 'False) (C1 ('MetaCons "Ann" 'PrefixI 'True) (S1 ('MetaSel ('Just "_hAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a h)) :*: S1 ('MetaSel ('Just "_hVal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (h :# Ann a))))
type HWitnessType (HFlip Ann h) Source # 
Instance details

Defined in Hyper.Combinator.Ann

type HNodesConstraint (HFlip Ann h) c Source # 
Instance details

Defined in Hyper.Combinator.Ann

type HNodesConstraint (HFlip Ann h) c = (Recursive c, c h)

hAnn :: forall a h. Lens' (Ann a h) (a h) Source #

hVal :: forall a h. Lens' (Ann a h) ((:#) h (Ann a)) Source #

type Annotated a = Ann (Const a) Source #

annValue :: Lens (Annotated a # h0) (Annotated a # h1) (h0 # Annotated a) (h1 # Annotated a) Source #

Polymorphic lens to an Annotated value