Copyright | (c) 2013 Tom Hawkins & Lee Pike |
---|---|
Safe Haskell | None |
Language | Haskell98 |
Definitions for Atom expressions, variables, and types
- 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
Types
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
Constants
Variable Reference and Assignment
Logical Operations
Bit-wise Operations
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
Equality and Comparison
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