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

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

Language.Atom

Contents

Description

Atom is a Haskell DSL for designing hard realtime embedded software.

Based on guarded atomic actions (similar to STM), Atom enables highly concurrent programming without the need for mutex locking. In addition, Atom performs compile-time task scheduling and generates code with deterministic execution time and constant memory use, simplifying the process of timing verification and memory consumption in hard realtime applications. Without mutex locking and run-time task scheduling, Atom eliminates the need and overhead of RTOSes for many embedded applications.

Synopsis

Code

data Config Source

C code configuration parameters.

Constructors

Config 

Fields

cFuncName :: String

Alternative primary function name. If this is empty, then it will default to the name passed to compile.

cStateName :: String

Name of state variable structure. Default: state

cCode :: [Name] -> [Name] -> [(Name, Type)] -> (String, String)

Custom C code to insert above and below the functions, given assertion names, coverage names, and probe names and types.

hCode :: [Name] -> [Name] -> [(Name, Type)] -> (String, String)

Custom C code to insert above and below the state definition in the header file, given assertion names, coverage names, and probe names and types.

cRuleCoverage :: Bool

Enable rule coverage tracking.

cAssert :: Bool

Enable assertions and functional coverage.

cAssertName :: String

Name of assertion function. Prototype: void assert(int, bool, uint64_t);

cCoverName :: String

Name of coverage function. Prototype: void cover(int, bool, uint64_t);

hardwareClock :: Maybe Clock

Hardware counter to schedule rules, or Nothing (the default).

defaults :: Config Source

Default C code configuration parameters (default function name, no pre/post code, ANSI C types).

data Clock Source

Data associated with sampling a hardware clock. For the clock to work correctly, you MUST assign __global_clock the current time (according to clockName) the first time you enter the main Atom-generated function calling your rules.

Constructors

Clock 

Fields

clockName :: String

C function to sample the clock. The function is assumed to have the prototype: clockType clockName(void).

clockType :: Type

Clock type. Assumed to be one of Word8, Word16, Word32, or Word64. It is permissible for the clock to roll over.

delta :: Integer

Number of ticks in a phase. Must be greater than 0.

delay :: String

C function to delay/sleep. The function is assumed to have the prototype: void delay(clockType i), where i is the duration of delay/sleep.

err :: Maybe String

Nothing, or a user-defined error-reporting function if the period duration is violated, e.g., the execution time was greater than delta. Assumed to have prototype: void err(void).

defaultClock :: Clock Source

Default hardware clock parameters (name "clk", Word64, delta 1, delay function is "delay", no error function).

cType :: Type -> String Source

C99 type naming rules.

Compilation

compile :: Name -> Config -> Atom () -> IO (Schedule, RuleCoverage, [Name], [Name], [(Name, Type)]) Source

Compiles an atom description to C.

reportSchedule :: Schedule -> String Source

Generate a rule scheduling report for the given schedule.

type Schedule = (UeMap, [(Int, Int, [Rule])]) Source

Schedule expressed as a UeMap and a list of (period, phase, rules).

Common

data Timer Source

A Timer.

timer :: Name -> Atom Timer Source

Creates a new timer.

startTimer Source

Arguments

:: Timer

Timer to start

-> E Word64

Number of clock ticks the timer shall run

-> Atom () 

Starts a Timer. A timer can be restarted at any time.

startTimerIf Source

Arguments

:: Timer

Timer to start conditionally

-> E Bool

Condition for starting the timer

-> E Word64

Number of ticks the timer shall run

-> Atom () 

Conditionally start a Timer.

timerDone :: Timer -> E Bool Source

True when a timer has completed. Note that this remains True until the timer is restarted.

oneShotRise :: E Bool -> Atom (E Bool) Source

One-shot on a rising transition.

oneShotFall :: E Bool -> Atom (E Bool) Source

One-shot on a falling transition.

debounce Source

Arguments

:: Name

Name of the resulting atom

-> E Word64

On time in ticks

-> E Word64

Off time in ticks

-> Bool

Initial value

-> E Bool

The boolean to debounce

-> Atom (E Bool)

Resulting debounced boolean

Debounces a boolean given an on and off time (ticks) and an initial state.

lookupTable Source

Arguments

:: FloatingE a 
=> [(E a, E a)]

(x, y) lookup table

-> E a

Input x value

-> E a

Output y value

1-D lookup table. x values out of table range are clipped at end y values. Input table must be monotonically increasing in x.

linear Source

Arguments

:: FloatingE a 
=> (E a, E a)

First point, (x1, y1)

-> (E a, E a)

Second point, (x2, y2)

-> E a

Input x value

-> E a

Interpolated/extrapolated y value

Linear extrapolation and interpolation on a line with 2 points. The two x points must be different to prevent a divide-by-zero.

hysteresis Source

Arguments

:: OrdE a 
=> E a

min

-> E a

max

-> E a

Input

-> Atom (E Bool) 

Hysteresis returns True when the input exceeds max and False when the input is less than min. The state is held when the input is between min and max.

data Channel a Source

A channel is a uni-directional communication link that ensures one read for every write.

Constructors

Channel a (V Bool) 

channel :: a -> Atom (Channel a) Source

Creates a new channel, with a given name and data.

writeChannel :: Channel a -> Atom () Source

Write data to a Channel. A write will only suceed if the Channel is empty.

readChannel :: Channel a -> Atom a Source

Read data from a Channel. A read will only suceed if the Channel has data to be read.

Signal fading

data Fader Source

Fader object.

data FaderInit Source

Fader initalization.

Constructors

OnA

Start at signal A

OnB

Start at signal B

OnCenter

Start at average of A and B

fader Source

Arguments

:: Name

Name

-> Double

Fade rate

-> FaderInit

Initialization

-> E Double

Signal A

-> E Double

Signal B

-> Atom (Fader, E Double) 

Fader construction

fadeToA :: Fader -> Atom () Source

Fade to signal A.

fadeToB :: Fader -> Atom () Source

Fade to signal B.

fadeToCenter :: Fader -> Atom () Source

Fade to center, i.e. average of signal A and B.

Thresholds

boolThreshold :: Name -> Int32 -> Bool -> E Bool -> Atom (E Bool) Source

Boolean thresholding over time. Output is set when internal counter hits limit, and cleared when counter is 0.

doubleThreshold :: Name -> Double -> E Double -> Atom (E Bool) Source

Integrating threshold. Output is set with integral reaches limit, and cleared when integral reaches 0.

Valid/Invalid data

data ValidData a Source

ValidData captures the data and its validity condition. ValidData is abstract to prevent rules from using invalid data.

validData :: a -> E Bool -> ValidData a Source

Create ValidData given the data and validity condition.

getValidData :: ValidData a -> Atom a Source

Get a valid data. Action is disabled if data is invalid.

whenValid :: ValidData a -> Atom () Source

Action enabled if ValidData is valid.

whenInvalid :: ValidData a -> Atom () Source

Action enabled if ValidData is not valid.

Language & EDSL

type Atom = Atom Source

The Atom monad captures variable and transition 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.

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.

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.

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)'.

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.

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.

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.

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

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

Expressions

data E a where Source

A typed expression.

Constructors

VRef :: V a -> E a 
Const :: a -> E a 
Cast :: (NumE a, NumE b) => E a -> E b 
Add :: NumE a => E a -> E a -> E a 
Sub :: NumE a => E a -> E a -> E a 
Mul :: NumE a => E a -> E a -> E a 
Div :: NumE a => E a -> E a -> E a 
Mod :: IntegralE a => E a -> E a -> E a 
Not :: E Bool -> E Bool 
And :: E Bool -> E Bool -> E Bool 
BWNot :: IntegralE a => E a -> E a 
BWAnd :: IntegralE a => E a -> E a -> E a 
BWOr :: IntegralE a => E a -> E a -> E a 
BWXor :: IntegralE a => E a -> E a -> E a 
BWShiftL :: (IntegralE a, IntegralE b) => E a -> E b -> E a 
BWShiftR :: (IntegralE a, IntegralE b) => E a -> E b -> E a 
Eq :: EqE a => E a -> E a -> E Bool 
Lt :: OrdE a => E a -> E a -> E Bool 
Mux :: E Bool -> E a -> E a -> E a 
F2B :: E Float -> E Word32 
D2B :: E Double -> E Word64 
B2F :: E Word32 -> E Float 
B2D :: E Word64 -> E Double 
Retype :: UE -> E a 
Pi :: FloatingE a => E a 
Exp :: FloatingE a => E a -> E a 
Log :: FloatingE a => E a -> E a 
Sqrt :: FloatingE a => E a -> E a 
Pow :: FloatingE a => E a -> E a -> E a 
Sin :: FloatingE a => E a -> E a 
Asin :: FloatingE a => E a -> E a 
Cos :: FloatingE a => E a -> E a 
Acos :: FloatingE a => E a -> E a 
Sinh :: FloatingE a => E a -> E a 
Cosh :: FloatingE a => E a -> E a 
Asinh :: FloatingE a => E a -> E a 
Acosh :: FloatingE a => E a -> E a 
Atan :: FloatingE a => E a -> E a 
Atanh :: FloatingE a => E a -> E a 

Instances

Expr a => Eq (E a) 
(Num a, Fractional a, Floating a, FloatingE a) => Floating (E a) 
(OrdE a, NumE a, Num a, Fractional a) => Fractional (E a) 
(Num a, NumE a, OrdE a) => Num (E a) 
Show (E a) 
(Expr a, OrdE a, EqE a, IntegralE a, Bits a) => Bits (E a) 
Expr a => TypeOf (E a) 
Expr a => Width (E a) 

data V a Source

Variables updated by state transition rules.

Constructors

V UV 

Instances

Eq (V a) 
TypeOf (V a) 
Expr a => Width (V a) 

data UV Source

Untyped variables.

Instances

data A a Source

A typed array.

Constructors

A UA 

Instances

Eq (A a) 
TypeOf (A a) 

data UA Source

An untyped array.

Constructors

UA Int String [Const] 
UAExtern String Type 

Instances

data Variable Source

Typed variable

Instances

data Type Source

The type of a E.

class Width a where Source

Types with a defined width in bits

Methods

width :: a -> Int Source

The width of a type, in number of bits

Instances

Width UE 
Width UV 
Width Const 
Width Type 
Expr a => Width (E a) 
Expr a => Width (V a) 

class TypeOf a where Source

Types which have a defined Type

Methods

typeOf :: a -> Type Source

The corresponding Type of the given object

Instances

bytes :: Width a => a -> Int Source

The number of bytes that an object occupies

ue :: Expr a => E a -> UE Source

Converts an typed expression (E a) to an untyped expression (UE).

uv :: V a -> UV Source

Convert a typed variable to an untyped one

class (Num a, Expr a, EqE a, OrdE a) => NumE a Source

Expression of numerical type

class (NumE a, Integral a) => IntegralE a Source

Expression of integral type

Minimal complete definition

signed

class (RealFloat a, NumE a, OrdE a) => FloatingE a Source

Floating-point typed expression

class (Eq a, Expr a) => EqE a Source

Expressions which can be compared for equality

class (Eq a, Ord a, EqE a) => OrdE a Source

Expressions which can be ordered

true :: E Bool Source

True term.

false :: E Bool Source

False term.

value :: V a -> E a Source

Returns the value of a V.

not_ :: E Bool -> E Bool Source

Logical negation.

(&&.) :: E Bool -> E Bool -> E Bool infixl 3 Source

Logical AND.

(||.) :: E Bool -> E Bool -> E Bool infixl 2 Source

Logical OR.

and_ :: [E Bool] -> E Bool Source

The conjunction of a E Bool list.

or_ :: [E Bool] -> E Bool Source

The disjunction of a E Bool list.

any_ :: (a -> E Bool) -> [a] -> E Bool Source

True iff the predicate is true for any element.

all_ :: (a -> E Bool) -> [a] -> E Bool Source

True iff the predicate is true for all elements.

imply Source

Arguments

:: E Bool

a

-> E Bool

b

-> E Bool 

Logical implication (if a then b).

(.&.) :: Bits a => a -> a -> a

Bitwise "and"

complement :: Bits a => a -> a

Reverse all the bits in the argument

(.|.) :: Bits a => a -> a -> a

Bitwise "or"

xor :: Bits a => a -> a -> a

Bitwise "xor"

(.<<.) :: (Bits a, IntegralE a, IntegralE n) => E a -> E n -> E a Source

Bitwise left-shifting.

(.>>.) :: (Bits a, IntegralE a, IntegralE n) => E a -> E n -> E a Source

Bitwise right-shifting.

rol :: (IntegralE a, IntegralE n, Bits a) => E a -> E n -> E a Source

Bitwise left-rotation.

ror :: (IntegralE a, IntegralE n, Bits a) => E a -> E n -> E a Source

Bitwise right-rotation.

bitSize :: Bits a => a -> Int

Return the number of bits in the type of the argument. The actual value of the argument is ignored. The function bitSize is undefined for types that do not have a fixed bitsize, like Integer.

isSigned :: Bits a => a -> Bool

Return True if the argument is a signed type. The actual value of the argument is ignored

(==.) :: EqE a => E a -> E a -> E Bool infix 4 Source

Equal.

(/=.) :: EqE a => E a -> E a -> E Bool infix 4 Source

Not equal.

(<.) :: OrdE a => E a -> E a -> E Bool infix 4 Source

Less than.

(<=.) :: OrdE a => E a -> E a -> E Bool infix 4 Source

Less than or equal.

(>.) :: OrdE a => E a -> E a -> E Bool infix 4 Source

Greater than.

(>=.) :: OrdE a => E a -> E a -> E Bool infix 4 Source

Greater than or equal.

min_ :: OrdE a => E a -> E a -> E a Source

Returns the minimum of two numbers.

minimum_ :: OrdE a => [E a] -> E a Source

Returns the minimum of a list of numbers.

max_ :: OrdE a => E a -> E a -> E a Source

Returns the maximum of two numbers.

maximum_ :: OrdE a => [E a] -> E a Source

Returns the maximum of a list of numbers.

limit :: OrdE a => E a -> E a -> E a -> E a Source

Limits between min and max.

div_ :: IntegralE a => E a -> E a -> E a Source

Division. If both the dividend and divisor are constants, a compile-time check is made for divide-by-zero. Otherwise, if the divisor ever evaluates to 0, a runtime exception will occur, even if the division occurs within the scope of a cond or mux that tests for 0 (because Atom generates deterministic-time code, every branch of a cond or mux is executed).

div0_ :: IntegralE a => E a -> E a -> a -> E a Source

Division, where the C code is instrumented with a runtime check to ensure the divisor does not equal 0. If it is equal to 0, the 3rd argument is a user-supplied non-zero divsor.

mod_ :: IntegralE a => E a -> E a -> E a Source

Modulo. If both the dividend and modulus are constants, a compile-time check is made for divide-by-zero. Otherwise, if the modulus ever evaluates to 0, a runtime exception will occur, even if the division occurs within the scope of a cond or mux that tests for 0 (because Atom generates deterministic-time code, every branch of a cond or mux is executed).

mod0_ :: IntegralE a => E a -> E a -> a -> E a Source

Modulus, where the C code is instrumented with a runtime check to ensure the modulus does not equal 0. If it is equal to 0, the 3rd argument is a user-supplied non-zero divsor.

mux :: Expr a => E Bool -> E a -> E a -> E a Source

Conditional expression. Note, both branches are evaluated!

mux test onTrue onFalse

(!) :: (Expr a, IntegralE b) => A a -> E b -> V a infixl 9 Source

Array index to variable.

(!.) :: (Expr a, IntegralE b) => A a -> E b -> E a infixl 9 Source

Array index to expression.

ubool :: Bool -> UE Source

Produced an untyped expression from a constant Bool

unot :: UE -> UE Source

Logical NOT of an untyped expression

uand :: UE -> UE -> UE Source

Logical AND of two untyped expressions

uor :: UE -> UE -> UE Source

Logical OR of two untyped expressions

ueq :: UE -> UE -> UE Source

Check equality on two untyped expressions

umux Source

Arguments

:: UE

Selector

-> UE

Input 1

-> UE

Input 2

-> UE 

2-to-1 multiplexer. If selector is true, this returns input 1; if selector is false, this returns input 2.

Testing

data Test Source

Parameters for a test simulation

Constructors

Test 

Fields

name :: String

Name for test (used in log file, state name, and output)

cycles :: Int

Number of simulation cycles to run

testbench :: Atom ()

Atom specification to test

modules :: [FilePath]

Other C files to build in

includes :: [FilePath]

Other C headers to include

declCode :: String

C declarations and definitions inserted prior to the main function

initCode :: String

C code executed inside the main function, prior to loopCode

loopCode :: String

C code executed inside the loop running the test

endCode :: String

C code executed after that loop, but still in main

defaultTest :: Test Source

Default test parameters

runTests Source

Arguments

:: Int

Random seed

-> [IO Test]

List of tests to run

-> IO () 

Run a list of tests, output a report on test passes and coverage.

printStrLn :: String -> Atom () Source

Print a string in C using printf, appending a newline.

printIntegralE Source

Arguments

:: IntegralE a 
=> String

Prefix for printed value

-> E a

Integral value to print

-> Atom () 

Print an integral value in C using printf.

printFloatingE Source

Arguments

:: FloatingE a 
=> String

Prefix for printed value

-> E a

Floating point value to print

-> Atom () 

Print a floating point value in C using printf.

printProbe :: (String, UE) -> Atom () Source

Print the value of a probe to the console (along with its name).