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

Language.Atom.Expressions

Synopsis

Types

data E a whereSource

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
Shift :: IntegralE a => E a -> Int -> 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

Instances

Expr a => Eq (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 UE Source

An untyped term.

Constructors

UAnd [UE]

Instances

data UV Source

Untyped variables.

Constructors

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

Instances

class Eq a => Expr a whereSource

Methods

eType :: E a -> Type Source

constant :: a -> Const Source

expression :: E a -> Expression Source

variable :: V a -> Variable Source

rawBits :: E a -> E Word64 Source

Instances

data Expression Source

Constructors

data Variable Source

Constructors

Instances

data Type Source

The type of a E .

Constructors

Instances

data Const Source

Constructors

Instances

class Width a whereSource

Methods

width :: a -> Int Source

Instances

class TypeOf a whereSource

Methods

typeOf :: a -> Type Source

Instances

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

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

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

uv :: V a -> UV Source

ueUpstream :: UE -> [UE]Source

The list of UEs adjacent upstream of a UE.

nearestUVs :: UE -> [UV]Source

The list of all UVs that directly control the value of an expression.

arrayIndices :: UE -> [(UA, UE)]Source

All array indexing subexpressions.

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

Instances

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

Instances

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

Instances

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

Instances

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

Instances

Constants

true :: E Bool Source

True term.

false :: E Bool Source

False term.

Variable Reference and Assignment

value :: V a -> E aSource

Returns the value of a V .

Logical Operations

not_ :: E Bool -> E Bool Source

Logical negation.

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

Logical AND.

(||.) :: E Bool -> E Bool -> E Bool 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 :: E Bool -> E Bool -> E Bool Source

Equality and Comparison

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

Equal.

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

Not equal.

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

Less than.

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

Less than or equal.

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

Greater than.

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

Greater than or equal.

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

Returns the minimum of two numbers.

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

Returns the minimum of a list of numbers.

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

Returns the maximum of two numbers.

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

Returns the maximum of a list of numbers.

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

Limits between min and max.

Arithmetic Operations

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

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 aSource

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 aSource

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 aSource

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.

Conditional Operator

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

Conditional expression. Note, both branches are evaluated!

 mux test onTrue onFalse

Array Indexing

(!) :: (Expr a, IntegralE b) => A a -> E b -> V aSource

Array index to variable.

(!.) :: (Expr a, IntegralE b) => A a -> E b -> E aSource

Array index to expression.

Smart constructors for untyped expressions.

ubool :: Bool -> UE Source

unot :: UE -> UE Source

uand :: UE -> UE -> UE Source

uor :: UE -> UE -> UE Source

ueq :: UE -> UE -> UE Source

umux :: UE -> UE -> UE -> UE Source

AltStyle によって変換されたページ (->オリジナル) /