Copyright | (c) 2013 Tom Hawkins & Lee Pike |
---|---|
Safe Haskell | None |
Language | Haskell98 |
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.
- data Config = Config {}
- defaults :: Config
- data Clock = Clock {}
- defaultClock :: Clock
- writeC :: Name -> Config -> StateHierarchy -> [Rule] -> Schedule -> [Name] -> [Name] -> [(Name, Type)] -> IO RuleCoverage
- cType :: Type -> String
- type RuleCoverage = [(Name, Int, Int)]
- compile :: Name -> Config -> Atom () -> IO (Schedule, RuleCoverage, [Name], [Name], [(Name, Type)])
- reportSchedule :: Schedule -> String
- type Schedule = (UeMap, [(Int, Int, [Rule])])
- data Timer
- timer :: Name -> Atom Timer
- startTimer :: Timer -> E Word64 -> Atom ()
- startTimerIf :: Timer -> E Bool -> E Word64 -> Atom ()
- timerDone :: Timer -> E Bool
- oneShotRise :: E Bool -> Atom (E Bool)
- oneShotFall :: E Bool -> Atom (E Bool)
- debounce :: Name -> E Word64 -> E Word64 -> Bool -> E Bool -> Atom (E Bool)
- lookupTable :: FloatingE a => [(E a, E a)] -> E a -> E a
- linear :: FloatingE a => (E a, E a) -> (E a, E a) -> E a -> E a
- hysteresis :: OrdE a => E a -> E a -> E a -> Atom (E Bool)
- data Channel a = Channel a (V Bool)
- channel :: a -> Atom (Channel a)
- writeChannel :: Channel a -> Atom ()
- readChannel :: Channel a -> Atom a
- data Fader
- data FaderInit
- fader :: Name -> Double -> FaderInit -> E Double -> E Double -> Atom (Fader, E Double)
- fadeToA :: Fader -> Atom ()
- fadeToB :: Fader -> Atom ()
- fadeToCenter :: Fader -> Atom ()
- boolThreshold :: Name -> Int32 -> Bool -> E Bool -> Atom (E Bool)
- doubleThreshold :: Name -> Double -> E Double -> Atom (E Bool)
- data ValidData a
- validData :: a -> E Bool -> ValidData a
- getValidData :: ValidData a -> Atom a
- whenValid :: ValidData a -> Atom ()
- whenInvalid :: ValidData a -> Atom ()
- 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)
- data E a where
- 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
- data V a = V UV
- data UE
- = UVRef UV
- | UConst Const
- | UCast Type UE
- | UAdd UE UE
- | USub UE UE
- | UMul UE UE
- | UDiv UE UE
- | UMod UE UE
- | UNot UE
- | UAnd [UE]
- | UBWNot UE
- | UBWAnd UE UE
- | UBWOr UE UE
- | UBWXor UE UE
- | UBWShiftL UE UE
- | UBWShiftR UE UE
- | UEq UE UE
- | ULt UE UE
- | UMux UE UE UE
- | UF2B UE
- | UD2B UE
- | UB2F UE
- | UB2D UE
- | UPi
- | UExp UE
- | ULog UE
- | USqrt UE
- | UPow UE UE
- | USin UE
- | UAsin UE
- | UCos UE
- | UAcos UE
- | USinh UE
- | UCosh UE
- | UAsinh UE
- | UAcosh UE
- | UAtan UE
- | UAtanh UE
- data UV
- data A a = A UA
- data UA
- class Eq a => Expr a where
- data Expression
- data Variable
- data Type
- data Const
- class Width a where
- class TypeOf a where
- bytes :: Width a => a -> Int
- ue :: Expr a => E a -> UE
- uv :: V a -> UV
- class (Num a, Expr a, EqE a, OrdE a) => NumE a
- class (NumE a, Integral a) => IntegralE a
- class (RealFloat a, NumE a, OrdE a) => FloatingE a
- class (Eq a, Expr a) => EqE a
- class (Eq a, Ord a, EqE a) => OrdE a
- true :: E Bool
- false :: E Bool
- value :: V a -> E a
- not_ :: E Bool -> E Bool
- (&&.) :: E Bool -> E Bool -> E Bool
- (||.) :: E Bool -> E Bool -> E Bool
- and_ :: [E Bool] -> E Bool
- or_ :: [E Bool] -> E Bool
- any_ :: (a -> E Bool) -> [a] -> E Bool
- all_ :: (a -> E Bool) -> [a] -> E Bool
- imply :: E Bool -> E Bool -> E Bool
- (.&.) :: Bits a => a -> a -> a
- complement :: Bits a => a -> a
- (.|.) :: Bits a => a -> a -> a
- xor :: Bits a => a -> a -> a
- (.<<.) :: (Bits a, IntegralE a, IntegralE n) => E a -> E n -> E a
- (.>>.) :: (Bits a, IntegralE a, IntegralE n) => E a -> E n -> E a
- rol :: (IntegralE a, IntegralE n, Bits a) => E a -> E n -> E a
- ror :: (IntegralE a, IntegralE n, Bits a) => E a -> E n -> E a
- bitSize :: Bits a => a -> Int
- isSigned :: Bits a => a -> Bool
- (==.) :: EqE a => E a -> E a -> E Bool
- (/=.) :: EqE a => E a -> E a -> E Bool
- (<.) :: OrdE a => E a -> E a -> E Bool
- (<=.) :: OrdE a => E a -> E a -> E Bool
- (>.) :: OrdE a => E a -> E a -> E Bool
- (>=.) :: OrdE a => E a -> E a -> E Bool
- min_ :: OrdE a => E a -> E a -> E a
- minimum_ :: OrdE a => [E a] -> E a
- max_ :: OrdE a => E a -> E a -> E a
- maximum_ :: OrdE a => [E a] -> E a
- limit :: OrdE a => E a -> E a -> E a -> E a
- div_ :: IntegralE a => E a -> E a -> E a
- div0_ :: IntegralE a => E a -> E a -> a -> E a
- mod_ :: IntegralE a => E a -> E a -> E a
- mod0_ :: IntegralE a => E a -> E a -> a -> E a
- mux :: Expr a => E Bool -> E a -> E a -> E a
- (!) :: (Expr a, IntegralE b) => A a -> E b -> V a
- (!.) :: (Expr a, IntegralE b) => A a -> E b -> E a
- ubool :: Bool -> UE
- unot :: UE -> UE
- uand :: UE -> UE -> UE
- uor :: UE -> UE -> UE
- ueq :: UE -> UE -> UE
- umux :: UE -> UE -> UE -> UE
- data Test = Test {}
- defaultTest :: Test
- class Expr a => Random a where
- runTests :: Int -> [IO Test] -> IO ()
- printStrLn :: String -> Atom ()
- printIntegralE :: IntegralE a => String -> E a -> Atom ()
- printFloatingE :: FloatingE a => String -> E a -> Atom ()
- printProbe :: (String, UE) -> Atom ()
Code
Module: Language.Atom.Code
C code configuration parameters.
Config | |
|
Default C code configuration parameters (default function name, no pre/post code, ANSI C types).
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.
Clock | |
|
Default hardware clock parameters (name "clk
", Word64, delta 1, delay
function is "delay
", no error function).
writeC :: Name -> Config -> StateHierarchy -> [Rule] -> Schedule -> [Name] -> [Name] -> [(Name, Type)] -> IO RuleCoverage Source
type RuleCoverage = [(Name, Int, Int)] Source
Compilation
Module: Language.Atom.Compile
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
Module: Language.Atom.Common
Starts a Timer. A timer can be restarted at any time.
:: 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.
:: 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.
1-D lookup table. x
values out of table range are clipped at end y
values. Input table must be monotonically increasing in x
.
:: FloatingE a | |
=> (E a, E a) | First point, (x1, y1) |
-> (E a, E a) | Second point, (x2, y2) |
-> E a | Input |
-> E a | Interpolated/extrapolated |
Linear extrapolation and interpolation on a line with 2 points.
The two x
points must be different to prevent a divide-by-zero.
A channel is a uni-directional communication link that ensures one read for every write.
writeChannel :: Channel a -> Atom () Source
readChannel :: Channel a -> Atom a Source
Signal fading
Module: Language.Atom.Common.Fader
Fader initalization.
:: Name | Name |
-> Double | Fade rate |
-> FaderInit | Initialization |
-> E Double | Signal A |
-> E Double | Signal B |
-> Atom (Fader, E Double) |
Fader construction
fadeToCenter :: Fader -> Atom () Source
Fade to center, i.e. average of signal A and B.
Thresholds
Module: Language.Atom.Common.Threshold
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
Module: Language.Atom.Common.ValidData
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.
whenInvalid :: ValidData a -> Atom () Source
Action enabled if ValidData
is not valid.
Language & EDSL
Module: Language.Atom.Language
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
.
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.
:: ([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.
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.
nextCoverage :: Atom (E Word32, E Word32) Source
Rule coverage information. (current coverage index, coverage data)
Expressions
Module: Language.Atom.Expressions
A typed expression.
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 |
Variables updated by state transition rules.
An untyped term.
UVRef UV | |
UConst Const | |
UCast Type UE | |
UAdd UE UE | |
USub UE UE | |
UMul UE UE | |
UDiv UE UE | |
UMod UE UE | |
UNot UE | |
UAnd [UE] | |
UBWNot UE | |
UBWAnd UE UE | |
UBWOr UE UE | |
UBWXor UE UE | |
UBWShiftL UE UE | |
UBWShiftR UE UE | |
UEq UE UE | |
ULt UE UE | |
UMux UE UE UE | |
UF2B UE | |
UD2B UE | |
UB2F UE | |
UB2D UE | |
UPi | |
UExp UE | |
ULog UE | |
USqrt UE | |
UPow UE UE | |
USin UE | |
UAsin UE | |
UCos UE | |
UAcos UE | |
USinh UE | |
UCosh UE | |
UAsinh UE | |
UAcosh UE | |
UAtan UE | |
UAtanh UE |
Untyped variables.
An untyped array.
class Eq a => Expr a where Source
Typed expression:
expression :: E a -> Expression Source
data Expression Source
Typed expression
Typed variable
The type of a E
.
Typed constant
Types with a defined width in bits
Types which have a defined Type
complement :: Bits a => a -> a
Reverse all the bits in the argument
isSigned :: Bits a => a -> Bool
Return True
if the argument is a signed type. The actual
value of the argument is ignored
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
2-to-1 multiplexer. If selector is true, this returns input 1; if selector is false, this returns input 2.
Testing
Module: Language.Atom.Unit
Parameters for a test simulation
Test | |
|
Default test parameters
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.
Print an integral value in C using printf
.
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).