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

Safe HaskellNone

Language.Atom.Expressions

Contents

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

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

class Width a whereSource

Methods

width :: a -> IntSource

Instances

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

class TypeOf a whereSource

Methods

typeOf :: a -> TypeSource

Instances

bytes :: Width a => a -> IntSource

ue :: Expr a => E a -> UESource

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

uv :: V a -> UVSource

Constants

true :: E BoolSource

True term.

false :: E BoolSource

False term.

Variable Reference and Assignment

value :: V a -> E aSource

Returns the value of a V.

Logical Operations

not_ :: E Bool -> E BoolSource

Logical negation.

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

Logical AND.

(||.) :: E Bool -> E Bool -> E BoolSource

Logical OR.

and_ :: [E Bool] -> E BoolSource

The conjunction of a E Bool list.

or_ :: [E Bool] -> E BoolSource

The disjunction of a E Bool list.

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

True iff the predicate is true for any element.

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

True iff the predicate is true for all elements.

Bit-wise Operations

(.&.) :: 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 aSource

Bitwise left-shifting.

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

Bitwise right-shifting.

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

Bitwise left-rotation.

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

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

Equality and Comparison

(==.) :: EqE a => E a -> E a -> E BoolSource

Equal.

(/=.) :: EqE a => E a -> E a -> E BoolSource

Not equal.

(<.) :: OrdE a => E a -> E a -> E BoolSource

Less than.

(<=.) :: OrdE a => E a -> E a -> E BoolSource

Less than or equal.

(>.) :: OrdE a => E a -> E a -> E BoolSource

Greater than.

(>=.) :: OrdE a => E a -> E a -> E BoolSource

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.

uand :: UE -> UE -> UESource

uor :: UE -> UE -> UESource

ueq :: UE -> UE -> UESource

umux :: UE -> UE -> UE -> UESource