Copyright | (c) 2013 Tom Hawkins & Lee Pike |
---|---|
Safe Haskell | None |
Language | Haskell98 |
Language.Atom.Language
Contents
Description
Definitions for the Atom EDSL itself
- module Language.Atom.Expressions
- type Atom = Atom
- atom :: Name -> Atom a -> Atom a
- period :: Int -> Atom a -> Atom a
- getPeriod :: Atom Int
- phase :: Int -> Atom a -> Atom a
- exactPhase :: Int -> Atom a -> Atom a
- getPhase :: Atom Int
- cond :: E Bool -> Atom ()
- class Expr a => Assign a where
- incr :: (Assign a, NumE a) => V a -> Atom ()
- decr :: (Assign a, NumE a) => V a -> Atom ()
- 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
- bool :: Name -> Bool -> Atom (V Bool)
- bool' :: Name -> V Bool
- int8 :: Name -> Int8 -> Atom (V Int8)
- int8' :: Name -> V Int8
- int16 :: Name -> Int16 -> Atom (V Int16)
- int16' :: Name -> V Int16
- int32 :: Name -> Int32 -> Atom (V Int32)
- int32' :: Name -> V Int32
- int64 :: Name -> Int64 -> Atom (V Int64)
- int64' :: Name -> V Int64
- word8 :: Name -> Word8 -> Atom (V Word8)
- word8' :: Name -> V Word8
- word16 :: Name -> Word16 -> Atom (V Word16)
- word16' :: Name -> V Word16
- word32 :: Name -> Word32 -> Atom (V Word32)
- word32' :: Name -> V Word32
- word64 :: Name -> Word64 -> Atom (V Word64)
- word64' :: Name -> V Word64
- float :: Name -> Float -> Atom (V Float)
- float' :: Name -> V Float
- double :: Name -> Double -> Atom (V Double)
- double' :: Name -> V Double
- action :: ([String] -> String) -> [UE] -> Atom ()
- call :: Name -> Atom ()
- probe :: Expr a => Name -> E a -> Atom ()
- probes :: Atom [(String, UE)]
- assert :: Name -> E Bool -> Atom ()
- cover :: Name -> E Bool -> Atom ()
- assertImply :: Name -> E Bool -> E Bool -> Atom ()
- type Name = String
- liftIO :: MonadIO m => forall a. IO a -> m a
- path :: Atom String
- clock :: E Word64
- nextCoverage :: Atom (E Word32, E Word32)
Documentation
module Language.Atom.Expressions
Primary Language Containers
Hierarchical Rule Declarations
atom :: Name -> Atom a -> Atom a Source
Creates a hierarchical node, where each node could be an atomic rule.
period :: Int -> Atom a -> Atom a Source
Defines the period of execution of sub-rules as a factor of the base rate
of the system. Rule period is bound by the closest period assertion. For
example:
> period 10 $ period 2 a -- Rules in a
have a period of 2, not 10.
exactPhase :: Int -> Atom a -> Atom a Source
Ensures an atom is scheduled only at phase n
.
Action Directives
cond :: E Bool -> Atom () Source
Adds an enabling condition to an atom subtree of rules. This condition must be true before any rules in hierarchy are allowed to execute.
Variable Declarations
Custom Actions
Arguments
:: ([String] -> String) | A function which receives a list of C parameters, and returns C code that should be executed. |
-> [UE] | A list of expressions; the supplied functions receive parameters which correspond to these expressions. |
-> Atom () |
Declares an action, which executes C code that is optionally passed some parameters.
Calls an external C function of type 'void f(void)'.
Probing
Declares a probe. A probe allows inspecting any expression, remotely to its context, at any desired rate.
probes :: Atom [(String, UE)] Source
Fetches all declared probes to current design point. The list contained
therein is (probe name, untyped expression).
See printProbe
.
Assertions and Functional Coverage
assert :: Name -> E Bool -> Atom () Source
An assertions checks that an 'E Bool' is true. Assertions are checked between the execution of every rule. Parent enabling conditions can disable assertions, but period and phase constraints do not. Assertion names should be globally unique.
cover :: Name -> E Bool -> Atom () Source
A functional coverage point tracks if an event has occured (true). Coverage points are checked at the same time as assertions. Coverage names should be globally unique.
assertImply :: Name -> E Bool -> E Bool -> Atom () Source
Implication assertions. Creates an implicit coverage point for the precondition.