ajhc-0.8.0.8: Haskell compiler that produce binary through C language

Safe HaskellNone

E.Type

Description

The definitions related to jhc core

Synopsis

Documentation

data Comb Source

Constructors

Comb 

Fields

combHead :: TVr
 
combBody :: E
 
combRules :: [Rule]
 

combBody_u :: (E -> E) -> Comb -> CombSource

combRules_u :: ([Rule] -> [Rule]) -> Comb -> CombSource

data Rule Source

Constructors

Rule 

Instances

Eq Rule 
Show Rule 
Binary Rule 
FreeVars Rule IdSet

we delete the free variables of the heads of a rule from the rule's free variables. the reason for doing this is that the rule cannot fire if all its heads are in scope, and if it were not done then many functions seem recursive when they arn't actually.

FreeVars Rule [Id] 

data ARules Source

Constructors

ARules 

Instances

Show ARules

ARules contains a set of rules for a single id, optimized for fast application

invarients for ARules sorted by number of arguments rule takes all hidden rule fields filled in free variables are up to date

Monoid ARules 
Binary ARules 
FreeVars ARules IdSet 

data Lit e t Source

Constructors

LitInt 

Fields

litNumber :: Number
 
litType :: t
 
LitCons 

Fields

litName :: Name
 
litArgs :: [e]
 
litType :: t
 
litAliasFor :: Maybe E
 

Instances

PPrint String (Lit E E) 
Functor (Lit e) 
Foldable (Lit e) 
Traversable (Lit e) 
(Eq e, Eq t) => Eq (Lit e t) 
(Ord e, Ord t) => Ord (Lit e t) 
(Show e, Show t) => Show (Lit e t) 
(Binary e, Binary t) => Binary (Lit e t) 
ConNames (Lit E E) 
CanType (Lit x t) 
FreeVars E x => FreeVars (Lit TVr E) x 

data ESort Source

Constructors

EStar

the sort of boxed lazy types

EBang

the sort of boxed strict types

EHash

the sort of unboxed types

ETuple

the sort of unboxed tuples

EHashHash

the supersort of unboxed types

EStarStar

the supersort of boxed types

ESortNamed Name

user defined sorts

data TVr' e Source

Constructors

TVr 

Fields

tvrIdent :: !Id
 
tvrType :: e
 
tvrInfo :: Info
 

tvrInfo_u :: (Info -> Info) -> TVr' e -> TVr' eSource

tvrType_u :: (t -> e) -> TVr' t -> TVr' eSource

tvrType_s :: e -> TVr' t -> TVr' eSource

data Alt e Source

Constructors

Alt (Lit TVr e) e 

Instances

Eq e => Eq (Alt e) 
Ord e => Ord (Alt e) 
Show e => Show (Alt e) 
Binary e => Binary (Alt e) 
CanType e => CanType (Alt e) 
FreeVars (Alt E) IdSet 
FreeVars (Alt E) (IdMap TVr) 

altHead :: Alt E -> Lit () ()Source

litHead :: Lit a b -> Lit () ()Source

litBinds :: Lit t t1 -> [t]Source

fromAp :: E -> (E, [E])Source

extract out EAp nodes a value and the arguments it is applied to.

fromPi :: E -> (E, [TVr])Source

deconstruct EPi terms, getting function argument types.

fromLam :: E -> (E, [TVr])Source

deconstruct ELam term.

tVr :: Id -> e -> TVr' eSource

isLitCons :: forall e_1629244139 t_1629244140. Lit e_1629244139 t_1629244140 -> BoolSource

isLitInt :: forall e_1629244139 t_1629244140. Lit e_1629244139 t_1629244140 -> BoolSource

fromEPrim :: E -> (Prim, [E], E)Source

fromELetRec :: E -> ([(TVr' E, E)], E)Source

fromEAp :: E -> (E, E)Source