Language.Copilot.Language
Contents
- Operators and functions
- Boolean constants
- Arithmetic operators (derived)
- Division
- The next functions are used only to coerce the type of their argument
- The next functions provide easier access to typed external variables.
- The next functions provide easier access to typed external arrays.
- Set of operators from which to choose during the generation of random streams
- Constructs of the copilot language
- The next functions are typed variable declarations to help the type-checker.
- The next functions help typing the send operations
- Typed constant declarations.
Description
- mod :: (Streamable a, IntegralE a) => Spec a -> Spec a -> Spec a
- div :: (Streamable a, IntegralE a) => Spec a -> Spec a -> Spec a
- mod0 :: (Streamable a, IntegralE a) => a -> Spec a -> Spec a -> Spec a
- div0 :: (Streamable a, IntegralE a) => a -> Spec a -> Spec a -> Spec a
- (<) :: (Streamable a, OrdE a) => Spec a -> Spec a -> Spec Bool
- (<=) :: (Streamable a, OrdE a) => Spec a -> Spec a -> Spec Bool
- (==) :: (Streamable a, EqE a) => Spec a -> Spec a -> Spec Bool
- (/=) :: (Streamable a, EqE a) => Spec a -> Spec a -> Spec Bool
- (>=) :: (Streamable a, OrdE a) => Spec a -> Spec a -> Spec Bool
- (>) :: (Streamable a, OrdE a) => Spec a -> Spec a -> Spec Bool
- not :: Spec Bool -> Spec Bool
- (||) :: Spec Bool -> Spec Bool -> Spec Bool
- (&&) :: Spec Bool -> Spec Bool -> Spec Bool
- (^) :: Spec Bool -> Spec Bool -> Spec Bool
- (==>) :: Spec Bool -> Spec Bool -> Spec Bool
- data Bool
- class (Eq a, Show a) => Num a where
- class Num a => Fractional a where
- (/) :: a -> a -> a
- mux :: Streamable a => Spec Bool -> Spec a -> Spec a -> Spec a
- class (Streamable a, Integral a) => CastIntTo a where
- cast :: (Streamable b, IntegralE b) => Spec b -> Spec a
- bool :: Spec Bool -> Spec Bool
- int8 :: Spec Int8 -> Spec Int8
- int16 :: Spec Int16 -> Spec Int16
- int32 :: Spec Int32 -> Spec Int32
- int64 :: Spec Int64 -> Spec Int64
- word8 :: Spec Word8 -> Spec Word8
- word16 :: Spec Word16 -> Spec Word16
- word32 :: Spec Word32 -> Spec Word32
- word64 :: Spec Word64 -> Spec Word64
- float :: Spec Float -> Spec Float
- double :: Spec Double -> Spec Double
- extB :: Var -> Phase -> Spec Bool
- extI8 :: Var -> Phase -> Spec Int8
- extI16 :: Var -> Phase -> Spec Int16
- extI32 :: Var -> Phase -> Spec Int32
- extI64 :: Var -> Phase -> Spec Int64
- extW8 :: Var -> Phase -> Spec Word8
- extW16 :: Var -> Phase -> Spec Word16
- extW32 :: Var -> Phase -> Spec Word32
- extW64 :: Var -> Phase -> Spec Word64
- extF :: Var -> Phase -> Spec Float
- extD :: Var -> Phase -> Spec Double
- extArrB :: (Streamable a, IntegralE a) => (Var, Spec a) -> Phase -> Spec Bool
- extArrI8 :: (Streamable a, IntegralE a) => (Var, Spec a) -> Phase -> Spec Int8
- extArrI16 :: (Streamable a, IntegralE a) => (Var, Spec a) -> Phase -> Spec Int16
- extArrI32 :: (Streamable a, IntegralE a) => (Var, Spec a) -> Phase -> Spec Int32
- extArrI64 :: (Streamable a, IntegralE a) => (Var, Spec a) -> Phase -> Spec Int64
- extArrW8 :: (Streamable a, IntegralE a) => (Var, Spec a) -> Phase -> Spec Word8
- extArrW16 :: (Streamable a, IntegralE a) => (Var, Spec a) -> Phase -> Spec Word16
- extArrW32 :: (Streamable a, IntegralE a) => (Var, Spec a) -> Phase -> Spec Word32
- extArrW64 :: (Streamable a, IntegralE a) => (Var, Spec a) -> Phase -> Spec Word64
- extArrF :: (Streamable a, IntegralE a) => (Var, Spec a) -> Phase -> Spec Float
- extArrD :: (Streamable a, IntegralE a) => (Var, Spec a) -> Phase -> Spec Double
- opsF :: Operators
- opsF2 :: Operators
- opsF3 :: Operators
- var :: Streamable a => Var -> Spec a
- const :: Streamable a => a -> Spec a
- drop :: Streamable a => Int -> Spec a -> Spec a
- (++) :: Streamable a => [a] -> Spec a -> Spec a
- (.=) :: Streamable a => Var -> Spec a -> Streams
- (..|) :: Sendable a => Send a -> Sends -> Sends
- varB :: Var -> Spec Bool
- varI8 :: Var -> Spec Int8
- varI16 :: Var -> Spec Int16
- varI32 :: Var -> Spec Int32
- varI64 :: Var -> Spec Int64
- varW8 :: Var -> Spec Word8
- varW16 :: Var -> Spec Word16
- varW32 :: Var -> Spec Word32
- varW64 :: Var -> Spec Word64
- varF :: Var -> Spec Float
- varD :: Var -> Spec Double
- sendW8 :: Var -> (Phase, Port) -> Send Word8
- constB :: Bool -> Spec Bool
- constI8 :: Int8 -> Spec Int8
- constI16 :: Int16 -> Spec Int16
- constI32 :: Int32 -> Spec Int32
- constI64 :: Int64 -> Spec Int64
- constW8 :: Word8 -> Spec Word8
- constW16 :: Word16 -> Spec Word16
- constW32 :: Word32 -> Spec Word32
- constW64 :: Word64 -> Spec Word64
- constF :: Float -> Spec Float
- constD :: Double -> Spec Double
Operators and functions
div :: (Streamable a, IntegralE a) => Spec a -> Spec a -> Spec aSource
Beware : crash without any possible recovery if a division by 0 happens. Same risk with mod. Use div0 and mod0 if unsure.
div0 :: (Streamable a, IntegralE a) => a -> Spec a -> Spec a -> Spec aSource
As mod and div, except that if the division would be by 0, the first argument is used as a default.
Boolean constants
data Bool
Arithmetic operators (derived)
class (Eq a, Show a) => Num a where
Basic numeric class.
Minimal complete definition: all except negate
or (-)
Methods
(+) :: a -> a -> a
(*) :: a -> a -> a
(-) :: a -> a -> a
negate :: a -> a
Unary negation.
abs :: a -> a
Absolute value.
signum :: a -> a
Sign of a number.
The functions abs
and signum
should satisfy the law:
abs x * signum x == x
For real numbers, the signum
is either -1
(negative), 0
(zero)
or 1
(positive).
fromInteger :: Integer -> a
Conversion from an Integer
.
An integer literal represents the application of the function
fromInteger
to the appropriate value of type Integer
,
so such literals have type (
.
Num
a) => a
Division
class Num a => Fractional a where
Fractional numbers, supporting real division.
Minimal complete definition: fromRational
and (recip
or (
)
/
)
Instances
Fractional Double | |
Fractional Float | |
Integral a => Fractional (Ratio a) | |
(OrdE a, NumE a, Num a, Fractional a) => Fractional (E a) | |
(Streamable a, NumE a, Fractional a) => Fractional (Spec a) |
mux :: Streamable a => Spec Bool -> Spec a -> Spec a -> Spec aSource
Beware : both sides are executed, even if the result of one is later discarded
class (Streamable a, Integral a) => CastIntTo a whereSource
The next functions are used only to coerce the type of their argument
The next functions provide easier access to typed external variables.
The next functions provide easier access to typed external arrays.
Set of operators from which to choose during the generation of random streams
opsF, opsF2 and opsF3 are feeded to Tests.Random.randomStreams. They allows the random generated streams to include lots of operators. If you add a new operator to Copilot, it would be nice to add it to one of those, that way it could be used in the random streams used for testing. opsF holds all the operators of arity 1, opsF2 of arity 2 and opsF3 of arity3 They are StreamableMaps, because operators are sorted based on their return type.
Constructs of the copilot language
var :: Streamable a => Var -> Spec aSource
Stream variable reference
const :: Streamable a => a -> Spec aSource
A constant stream
(++) :: Streamable a => [a] -> Spec a -> Spec aSource
Just a trivial wrapper over the
constructor
Append