Copyright | (c) 2013 Tom Hawkins & Lee Pike |
---|---|
Safe Haskell | None |
Language | Haskell98 |
Language.Atom.Elaboration
Description
- data Atom a
- data AtomDB = AtomDB {
- atomId :: Int
- atomName :: Name
- atomNames :: [Name]
- atomEnable :: Hash
- atomSubs :: [AtomDB]
- atomPeriod :: Int
- atomPhase :: Phase
- atomAssigns :: [(MUV, Hash)]
- atomActions :: [([String] -> String, [Hash])]
- atomAsserts :: [(Name, Hash)]
- atomCovers :: [(Name, Hash)]
- data Global = Global {}
- data Rule
- = Rule {
- ruleId :: Int
- ruleName :: Name
- ruleEnable :: Hash
- ruleAssigns :: [(MUV, Hash)]
- ruleActions :: [([String] -> String, [Hash])]
- rulePeriod :: Int
- rulePhase :: Phase
- | Assert {
- ruleName :: Name
- ruleEnable :: Hash
- ruleAssert :: Hash
- | Cover { }
- = Rule {
- data StateHierarchy
- buildAtom :: UeMap -> Global -> Name -> Atom a -> IO (a, AtomSt)
- type UID = Int
- type Name = String
- data Phase
- = MinPhase Int
- | ExactPhase Int
- type Path = [Name]
- elaborate :: UeMap -> Name -> Atom () -> IO (Maybe (UeMap, (StateHierarchy, [Rule], [Name], [Name], [(Name, Type)])))
- var :: Expr a => Name -> a -> Atom (V a)
- var' :: Name -> Type -> V a
- array :: Expr a => Name -> [a] -> Atom (A a)
- array' :: Expr a => Name -> Type -> A a
- addName :: Name -> Atom Name
- get :: Atom AtomSt
- put :: AtomSt -> Atom ()
- allUVs :: UeMap -> [Rule] -> Hash -> [MUV]
- allUEs :: Rule -> [Hash]
Atom monad and container.
The Atom monad holds variable and rule declarations.
Constructors
AtomDB | |
Fields
|
Constructors
Rule | |
Fields
| |
Assert | |
Fields
| |
Cover | |
data StateHierarchy Source
Constructors
StateHierarchy Name [StateHierarchy] | |
StateVariable Name Const | |
StateArray Name [Const] |
Type Aliases and Utilities
A phase is either the minimum phase or the exact phase.
Constructors
MinPhase Int | |
ExactPhase Int |
elaborate :: UeMap -> Name -> Atom () -> IO (Maybe (UeMap, (StateHierarchy, [Rule], [Name], [Name], [(Name, Type)]))) Source
A Relation is used for relative performance constraints between Action
s.
data Relation = Higher UID | Lower UID deriving (Show, Eq)
Given a top level name and design, elaborates design and returns a design database.