AspectAG-0.7.0.1: Strongly typed Attribute Grammars implemented using type-level programming.
Copyright(c) Juan García Garland 2018
LicenseLGPL
Maintainerjpgarcia@fing.edu.uy
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Language.Grammars.AspectAG.HList

Description

Implementation of strongly typed heterogeneous lists.

Synopsis

Documentation

data HList (l :: [Type]) :: Type where Source #

Heterogeneous lists are implemented as a GADT

Constructors

HNil :: HList '[] 
HCons :: x -> HList xs -> HList (x ': xs) 

class HMember (t :: Type) (l :: [Type]) where Source #

HMember is a test membership function. Since we are in Haskell the value level function computes with the evidence

Associated Types

type HMemberRes t l :: Bool Source #

Methods

hMember :: Label t -> HList l -> Proxy (HMemberRes t l) Source #

Instances

Instances details
HMember t ('[] :: [Type]) Source # 
Instance details

Defined in Language.Grammars.AspectAG.HList

Associated Types

type HMemberRes t '[] :: Bool Source #

Methods

hMember :: Label t -> HList '[] -> Proxy (HMemberRes t '[]) Source #

HMember t (t' ': ts) Source # 
Instance details

Defined in Language.Grammars.AspectAG.HList

Associated Types

type HMemberRes t (t' ': ts) :: Bool Source #

Methods

hMember :: Label t -> HList (t' ': ts) -> Proxy (HMemberRes t (t' ': ts)) Source #

class HMember' (t :: k) (l :: [k]) where Source #

HMember' is a test membership function. But looking up in a list of Labels

Associated Types

type HMemberRes' t l :: Bool Source #

Methods

hMember' :: f t -> KList l -> Proxy (HMemberRes' t l) Source #

Instances

Instances details
HMember' (t :: k) ('[] :: [k]) Source # 
Instance details

Defined in Language.Grammars.AspectAG.HList

Associated Types

type HMemberRes' t '[] :: Bool Source #

Methods

hMember' :: f t -> KList '[] -> Proxy (HMemberRes' t '[]) Source #

HMember' (t :: k) (t' ': ts :: [k]) Source # 
Instance details

Defined in Language.Grammars.AspectAG.HList

Associated Types

type HMemberRes' t (t' ': ts) :: Bool Source #

Methods

hMember' :: f t -> KList (t' ': ts) -> Proxy (HMemberRes' t (t' ': ts)) Source #

(.:) :: forall x (xs :: [Type]). x -> HList xs -> HList (x ': xs) infixr 2 Source #

No other functionality is needed for AAG

ε :: HList ('[] :: [Type]) Source #

data KList (l :: [k]) :: Type where Source #

a polykinded heteogeneous list

Constructors

KNil :: KList '[] 
KCons :: Label h -> KList l -> KList (h ': l) 

(.:.) :: forall k (h :: k) (l :: [k]). Label h -> KList l -> KList (h ': l) infixr 2 Source #

eL :: KList ('[] :: [k]) Source #