| Copyright | (c) 2011 National Institute of Aerospace / Galois Inc. |
|---|---|
| Safe Haskell | Safe |
| Language | Haskell2010 |
Copilot.Core.Operators
Description
Synopsis
- data Op1 a b where
- Not :: Op1 Bool Bool
- Abs :: forall a. Num a => Type a -> Op1 a a
- Sign :: forall a. Num a => Type a -> Op1 a a
- Recip :: forall a. Fractional a => Type a -> Op1 a a
- Exp :: forall a. Floating a => Type a -> Op1 a a
- Sqrt :: forall a. Floating a => Type a -> Op1 a a
- Log :: forall a. Floating a => Type a -> Op1 a a
- Sin :: forall a. Floating a => Type a -> Op1 a a
- Tan :: forall a. Floating a => Type a -> Op1 a a
- Cos :: forall a. Floating a => Type a -> Op1 a a
- Asin :: forall a. Floating a => Type a -> Op1 a a
- Atan :: forall a. Floating a => Type a -> Op1 a a
- Acos :: forall a. Floating a => Type a -> Op1 a a
- Sinh :: forall a. Floating a => Type a -> Op1 a a
- Tanh :: forall a. Floating a => Type a -> Op1 a a
- Cosh :: forall a. Floating a => Type a -> Op1 a a
- Asinh :: forall a. Floating a => Type a -> Op1 a a
- Atanh :: forall a. Floating a => Type a -> Op1 a a
- Acosh :: forall a. Floating a => Type a -> Op1 a a
- Ceiling :: forall a. RealFrac a => Type a -> Op1 a a
- Floor :: forall a. RealFrac a => Type a -> Op1 a a
- BwNot :: forall a. Bits a => Type a -> Op1 a a
- Cast :: forall a b. (Integral a, Num b) => Type a -> Type b -> Op1 a b
- GetField :: forall (s :: Symbol) a b. KnownSymbol s => Type a -> Type b -> (a -> Field s b) -> Op1 a b
- data Op2 a b c where
- And :: Op2 Bool Bool Bool
- Or :: Op2 Bool Bool Bool
- Add :: forall a. Num a => Type a -> Op2 a a a
- Sub :: forall a. Num a => Type a -> Op2 a a a
- Mul :: forall a. Num a => Type a -> Op2 a a a
- Mod :: forall a. Integral a => Type a -> Op2 a a a
- Div :: forall a. Integral a => Type a -> Op2 a a a
- Fdiv :: forall a. Fractional a => Type a -> Op2 a a a
- Pow :: forall a. Floating a => Type a -> Op2 a a a
- Logb :: forall a. Floating a => Type a -> Op2 a a a
- Atan2 :: forall a. RealFloat a => Type a -> Op2 a a a
- Eq :: forall a. Eq a => Type a -> Op2 a a Bool
- Ne :: forall a. Eq a => Type a -> Op2 a a Bool
- Le :: forall a. Ord a => Type a -> Op2 a a Bool
- Ge :: forall a. Ord a => Type a -> Op2 a a Bool
- Lt :: forall a. Ord a => Type a -> Op2 a a Bool
- Gt :: forall a. Ord a => Type a -> Op2 a a Bool
- BwAnd :: forall a. Bits a => Type a -> Op2 a a a
- BwOr :: forall a. Bits a => Type a -> Op2 a a a
- BwXor :: forall a. Bits a => Type a -> Op2 a a a
- BwShiftL :: forall a b. (Bits a, Integral b) => Type a -> Type b -> Op2 a b a
- BwShiftR :: forall a b. (Bits a, Integral b) => Type a -> Type b -> Op2 a b a
- Index :: forall (n :: Nat) c. Type (Array n c) -> Op2 (Array n c) Word32 c
- UpdateField :: forall b (s :: Symbol) a. (Typeable b, KnownSymbol s, Show b) => Type a -> Type b -> (a -> Field s b) -> Op2 a b a
- data Op3 a b c d where
Documentation
Unary operators.
Constructors
| Not :: Op1 Bool Bool | |
| Abs :: forall a. Num a => Type a -> Op1 a a | |
| Sign :: forall a. Num a => Type a -> Op1 a a | |
| Recip :: forall a. Fractional a => Type a -> Op1 a a | |
| Exp :: forall a. Floating a => Type a -> Op1 a a | |
| Sqrt :: forall a. Floating a => Type a -> Op1 a a | |
| Log :: forall a. Floating a => Type a -> Op1 a a | |
| Sin :: forall a. Floating a => Type a -> Op1 a a | |
| Tan :: forall a. Floating a => Type a -> Op1 a a | |
| Cos :: forall a. Floating a => Type a -> Op1 a a | |
| Asin :: forall a. Floating a => Type a -> Op1 a a | |
| Atan :: forall a. Floating a => Type a -> Op1 a a | |
| Acos :: forall a. Floating a => Type a -> Op1 a a | |
| Sinh :: forall a. Floating a => Type a -> Op1 a a | |
| Tanh :: forall a. Floating a => Type a -> Op1 a a | |
| Cosh :: forall a. Floating a => Type a -> Op1 a a | |
| Asinh :: forall a. Floating a => Type a -> Op1 a a | |
| Atanh :: forall a. Floating a => Type a -> Op1 a a | |
| Acosh :: forall a. Floating a => Type a -> Op1 a a | |
| Ceiling :: forall a. RealFrac a => Type a -> Op1 a a | |
| Floor :: forall a. RealFrac a => Type a -> Op1 a a | |
| BwNot :: forall a. Bits a => Type a -> Op1 a a | |
| Cast | |
| GetField | |
Binary operators.
Constructors
| And :: Op2 Bool Bool Bool | |
| Or :: Op2 Bool Bool Bool | |
| Add :: forall a. Num a => Type a -> Op2 a a a | |
| Sub :: forall a. Num a => Type a -> Op2 a a a | |
| Mul :: forall a. Num a => Type a -> Op2 a a a | |
| Mod :: forall a. Integral a => Type a -> Op2 a a a | |
| Div :: forall a. Integral a => Type a -> Op2 a a a | |
| Fdiv :: forall a. Fractional a => Type a -> Op2 a a a | |
| Pow :: forall a. Floating a => Type a -> Op2 a a a | |
| Logb :: forall a. Floating a => Type a -> Op2 a a a | |
| Atan2 :: forall a. RealFloat a => Type a -> Op2 a a a | |
| Eq :: forall a. Eq a => Type a -> Op2 a a Bool | |
| Ne :: forall a. Eq a => Type a -> Op2 a a Bool | |
| Le :: forall a. Ord a => Type a -> Op2 a a Bool | |
| Ge :: forall a. Ord a => Type a -> Op2 a a Bool | |
| Lt :: forall a. Ord a => Type a -> Op2 a a Bool | |
| Gt :: forall a. Ord a => Type a -> Op2 a a Bool | |
| BwAnd :: forall a. Bits a => Type a -> Op2 a a a | |
| BwOr :: forall a. Bits a => Type a -> Op2 a a a | |
| BwXor :: forall a. Bits a => Type a -> Op2 a a a | |
| BwShiftL :: forall a b. (Bits a, Integral b) => Type a -> Type b -> Op2 a b a | |
| BwShiftR :: forall a b. (Bits a, Integral b) => Type a -> Type b -> Op2 a b a | |
| Index | |
| UpdateField | |