hypertypes-0.2.2: Typed ASTs
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hyper.Type.Functor

Description

Lift Functors to HyperTypes

Synopsis

Documentation

newtype F f h Source #

Lift a Functor, or type constructor of kind Type -> Type to a HyperType.

  • F Maybe can be used to encode structures with missing values
  • F (Either Text) can be used to encode results of parsing where structure components may fail to parse.

Constructors

F (f (h :# F f)) 

Instances

Instances details
c (F f) => Recursively c (F f) Source # 
Instance details

Defined in Hyper.Type.Functor

Methods

recursively :: proxy (c (F f)) -> Dict (c (F f), HNodesConstraint (F f) (Recursively c)) Source #

Applicative f => HApply (F f) Source # 
Instance details

Defined in Hyper.Type.Functor

Methods

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

Foldable f => HFoldable (F f) Source # 
Instance details

Defined in Hyper.Type.Functor

Methods

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

Functor f => HFunctor (F f) Source # 
Instance details

Defined in Hyper.Type.Functor

Methods

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

Monad f => HMonad (F f) Source # 
Instance details

Defined in Hyper.Type.Functor

Methods

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

HNodes (F f) Source # 
Instance details

Defined in Hyper.Type.Functor

Associated Types

type HNodesConstraint (F f) c Source #

type HWitnessType (F f) :: HyperType -> Type Source #

Methods

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

Applicative f => HPointed (F f) Source # 
Instance details

Defined in Hyper.Type.Functor

Methods

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

RNodes (F f) Source # 
Instance details

Defined in Hyper.Type.Functor

Traversable f => RTraversable (F f) Source # 
Instance details

Defined in Hyper.Type.Functor

Traversable f => HTraversable (F f) Source # 
Instance details

Defined in Hyper.Type.Functor

Methods

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

Generic (F f h) Source # 
Instance details

Defined in Hyper.Type.Functor

Associated Types

type Rep (F f h) :: Type -> Type #

Methods

from :: F f h -> Rep (F f h) x #

to :: Rep (F f h) x -> F f h #

Constraints (F f h) Show => Show (F f h) Source # 
Instance details

Defined in Hyper.Type.Functor

Methods

showsPrec :: Int -> F f h -> ShowS #

show :: F f h -> String #

showList :: [F f h] -> ShowS #

Constraints (F f h) Binary => Binary (F f h) Source # 
Instance details

Defined in Hyper.Type.Functor

Methods

put :: F f h -> Put #

get :: Get (F f h) #

putList :: [F f h] -> Put #

Constraints (F f h) NFData => NFData (F f h) Source # 
Instance details

Defined in Hyper.Type.Functor

Methods

rnf :: F f h -> () #

Constraints (F f h) Eq => Eq (F f h) Source # 
Instance details

Defined in Hyper.Type.Functor

Methods

(==) :: F f h -> F f h -> Bool #

(/=) :: F f h -> F f h -> Bool #

Constraints (F f h) Ord => Ord (F f h) Source # 
Instance details

Defined in Hyper.Type.Functor

Methods

compare :: F f h -> F f h -> Ordering #

(<) :: F f h -> F f h -> Bool #

(<=) :: F f h -> F f h -> Bool #

(>) :: F f h -> F f h -> Bool #

(>=) :: F f h -> F f h -> Bool #

max :: F f h -> F f h -> F f h #

min :: F f h -> F f h -> F f h #

type HWitnessType (F f) Source # 
Instance details

Defined in Hyper.Type.Functor

type HWitnessType (F f) = W_F f
type HNodesConstraint (F f) constraint Source # 
Instance details

Defined in Hyper.Type.Functor

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

Defined in Hyper.Type.Functor

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

_F :: Iso (F f0 # k0) (F f1 # k1) (f0 (k0 # F f0)) (f1 (k1 # F f1)) Source #

An Iso from F to its content.

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

data W_F (f :: Type -> Type) node where Source #

Constructors

W_F_F_f :: W_F f (F f)