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

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

Language.Atom.Expressions

Contents

Description

Definitions for Atom expressions, variables, and types

Synopsis

Types

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

Constants

true :: E Bool Source

True term.

false :: E Bool Source

False term.

Variable Reference and Assignment

value :: V a -> E a Source

Returns the value of a V.

Logical Operations

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

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

Equality and Comparison

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

Arithmetic Operations

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.

Conditional Operator

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

Conditional expression. Note, both branches are evaluated!

mux test onTrue onFalse

Array Indexing

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

Smart constructors for untyped expressions.

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.