atom-1.0.13: An EDSL for embedded hard realtime applications.

Copyright(c) 2013 Tom Hawkins & Lee Pike
Safe HaskellNone
LanguageHaskell98

Language.Atom.Language

Contents

Description

Definitions for the Atom EDSL itself

Synopsis

Documentation

Primary Language Containers

type Atom = Atom Source

The Atom monad captures variable and transition rule declarations.

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.

getPeriod :: Atom Int Source

Returns the execution period of the current scope.

phase :: Int -> Atom a -> Atom a Source

Defines the earliest phase within the period at which the rule should execute; the scheduler attempt to find an optimal phase from 0 <= n < period (thus, the phase must be at least zero and less than the current period.).

exactPhase :: Int -> Atom a -> Atom a Source

Ensures an atom is scheduled only at phase n.

getPhase :: Atom Int Source

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.

class Expr a => Assign a where Source

Minimal complete definition

Nothing

Methods

(<==) :: V a -> E a -> Atom () infixr 1 Source

Assign an E to a V.

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 a Source

Generic external variable declaration.

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

Generic array declaration.

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

Generic external array declaration.

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

Local boolean variable declaration.

bool' :: Name -> V Bool Source

External boolean variable declaration.

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

Local int8 variable declaration.

int8' :: Name -> V Int8 Source

External int8 variable declaration.

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

Local int16 variable declaration.

int16' :: Name -> V Int16 Source

External int16 variable declaration.

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

Local int32 variable declaration.

int32' :: Name -> V Int32 Source

External int32 variable declaration.

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

Local int64 variable declaration.

int64' :: Name -> V Int64 Source

External int64 variable declaration.

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

Local word8 variable declaration.

word8' :: Name -> V Word8 Source

External word8 variable declaration.

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

Local word16 variable declaration.

word16' :: Name -> V Word16 Source

External word16 variable declaration.

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

Local word32 variable declaration.

word32' :: Name -> V Word32 Source

External word32 variable declaration.

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

Local word64 variable declaration.

word64' :: Name -> V Word64 Source

External word64 variable declaration.

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

Local float variable declaration.

float' :: Name -> V Float Source

External float variable declaration.

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

Local double variable declaration.

double' :: Name -> V Double Source

External double variable declaration.

Custom Actions

action Source

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.

call Source

Arguments

:: Name

Function f

-> Atom () 

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

Probing

probe Source

Arguments

:: Expr a 
=> Name

Human-readable probe name

-> E a

Expression to inspect

-> Atom () 

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.

Utilities

type Name = String Source

A name.

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

Lift a computation from the IO monad.

path :: Atom String Source

Returns the current atom hierarchical path.

clock :: E Word64 Source

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)