atom-1.0.4: A DSL for embedded hard realtime applications.

Language.Atom.Elaboration

Contents

Synopsis

Atom monad and container.

data Atom a Source

The Atom monad holds variable and rule declarations.

Instances

data AtomDB Source

Constructors

AtomDB 

Fields

atomId :: Int
 
atomName :: Name
 
atomNames :: [Name]
 
atomEnable :: UE
 
atomSubs :: [AtomDB]
 
atomPeriod :: Int
 
atomPhase :: Phase
 
atomAssigns :: [(UV, UE)]
 
atomActions :: [([String] -> String, [UE])]
 
atomAsserts :: [(Name, UE)]
 
atomCovers :: [(Name, UE)]
 

Instances

data Global Source

Constructors

Global 

data Rule Source

Constructors

Rule 

Fields

ruleId :: Int
 
ruleName :: Name
 
ruleEnable :: UE
 
ruleAssigns :: [(UV, UE)]
 
ruleActions :: [([String] -> String, [UE])]
 
rulePeriod :: Int
 
rulePhase :: Phase
 
Assert 

Fields

ruleName :: Name
 
ruleEnable :: UE
 
ruleAssert :: UE
 
Cover 

Fields

ruleName :: Name
 
ruleEnable :: UE
 
ruleCover :: UE
 

Instances

Type Aliases and Utilities

type UID = IntSource

type Name = StringSource

A name.

data Phase Source

A phase is either the minimum phase or the exact phase.

Constructors

MinPhase Int 
ExactPhase Int 

type Path = [Name]Source

A hierarchical name.

elaborate :: Name -> Atom () -> IO (Maybe (StateHierarchy, [Rule], [Name], [Name], [(Name, Type)]))Source

A Relation is used for relative performance constraints between Actions. data Relation = Higher UID | Lower UID deriving (Show, Eq)

Given a top level name and design, elaborates design and returns a design database.

var :: Expr a => Name -> a -> Atom (V a)Source

Generic local variable declaration.

var' :: Name -> Type -> V aSource

Generic external variable declaration.

array :: Expr a => Name -> [a] -> Atom (A a)Source

Generic array declaration.

array' :: Expr a => Name -> Type -> A aSource

Generic external array declaration.

allUVs :: [Rule] -> UE -> [UV]Source

All the variables that directly and indirectly control the value of an expression.

allUEs :: Rule -> [UE]Source

All primary expressions used in a rule.