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

Language.Atom.Language

Contents

Description

The Atom language.

Synopsis

Documentation

Primary Language Containers

type Atom = AtomSource

The Atom monad captures variable and transition rule declarations.

Hierarchical Rule Declarations

atom :: Name -> Atom a -> Atom aSource

Creates a hierarchical node, where each node could be a atomic rule.

period :: Int -> Atom a -> Atom aSource

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.

getPeriod :: Atom IntSource

Returns the execution period of the current scope.

phase :: Int -> Atom a -> Atom aSource

Defines the earliest phase within the period at which the rule should execute. The phase must be at least zero and less than the current period.

getPhase :: Atom IntSource

Returns the phase of the current scope.

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.

incr :: (Assign a, NumE a) => V a -> Atom ()Source

Increments a NumE V.

decr :: (Assign a, NumE a) => V a -> Atom ()Source

Decrements a NumE V.

Variable Declarations

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.

bool :: Name -> Bool -> Atom (V Bool)Source

Local boolean variable declaration.

bool' :: Name -> V BoolSource

External boolean variable declaration.

int8 :: Name -> Int8 -> Atom (V Int8)Source

Local int8 variable declaration.

int8' :: Name -> V Int8Source

External int8 variable declaration.

int16 :: Name -> Int16 -> Atom (V Int16)Source

Local int16 variable declaration.

int16' :: Name -> V Int16Source

External int16 variable declaration.

int32 :: Name -> Int32 -> Atom (V Int32)Source

Local int32 variable declaration.

int32' :: Name -> V Int32Source

External int32 variable declaration.

int64 :: Name -> Int64 -> Atom (V Int64)Source

Local int64 variable declaration.

int64' :: Name -> V Int64Source

External int64 variable declaration.

word8 :: Name -> Word8 -> Atom (V Word8)Source

Local word8 variable declaration.

word8' :: Name -> V Word8Source

External word8 variable declaration.

word16 :: Name -> Word16 -> Atom (V Word16)Source

Local word16 variable declaration.

word16' :: Name -> V Word16Source

External word16 variable declaration.

word32 :: Name -> Word32 -> Atom (V Word32)Source

Local word32 variable declaration.

word32' :: Name -> V Word32Source

External word32 variable declaration.

word64 :: Name -> Word64 -> Atom (V Word64)Source

Local word64 variable declaration.

word64' :: Name -> V Word64Source

External word64 variable declaration.

float :: Name -> Float -> Atom (V Float)Source

Local float variable declaration.

float' :: Name -> V FloatSource

External float variable declaration.

double :: Name -> Double -> Atom (V Double)Source

Local double variable declaration.

double' :: Name -> V DoubleSource

External double variable declaration.

Custom Actions

action :: ([String] -> String) -> [UE] -> Atom ()Source

Declares an action.

call :: Name -> Atom ()Source

Calls an external C function of type 'void f(void)'.

Probing

probe :: Expr a => Name -> E a -> Atom ()Source

Declares a probe.

probes :: Atom [(String, UE)]Source

Fetches all declared probes to current design point.

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.

Utilities

type Name = StringSource

A name.

liftIO :: MonadIO m => forall a. IO a -> m a

path :: Atom StringSource

Returns the current atom hierarchical path.

clock :: E Word64Source

Reference to the 64-bit free running clock.

Code Coverage

nextCoverage :: Atom (E Word32, E Word32)Source

Rule coverage information. (current coverage index, coverage data)