{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Data.Array.Accelerate.Classes.Num (
Num,
(P.+), (P.-), (P.*), P.negate, P.abs, P.signum, P.fromInteger,
) where
import Data.Array.Accelerate.Sugar.Elt
import Data.Array.Accelerate.Smart
import Data.Array.Accelerate.Type
import Prelude ( (.) )
import qualified Prelude as P
type Num a = (Elt a, P.Num (Exp a))
instance P.Num (Exp Int) where
+ :: Exp Int -> Exp Int -> Exp Int
(+) = Exp Int -> Exp Int -> Exp Int
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkAdd
(-) = Exp Int -> Exp Int -> Exp Int
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkSub
* :: Exp Int -> Exp Int -> Exp Int
(*) = Exp Int -> Exp Int -> Exp Int
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkMul
negate :: Exp Int -> Exp Int
negate = Exp Int -> Exp Int
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkNeg
abs :: Exp Int -> Exp Int
abs = Exp Int -> Exp Int
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkAbs
signum :: Exp Int -> Exp Int
signum = Exp Int -> Exp Int
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkSig
fromInteger :: Integer -> Exp Int
fromInteger = Int -> Exp Int
forall e. (HasCallStack, Elt e) => e -> Exp e
constant (Int -> Exp Int) -> (Integer -> Int) -> Integer -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Int
forall a. Num a => Integer -> a
P.fromInteger
instance P.Num (Exp Int8) where
+ :: Exp Int8 -> Exp Int8 -> Exp Int8
(+) = Exp Int8 -> Exp Int8 -> Exp Int8
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkAdd
(-) = Exp Int8 -> Exp Int8 -> Exp Int8
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkSub
* :: Exp Int8 -> Exp Int8 -> Exp Int8
(*) = Exp Int8 -> Exp Int8 -> Exp Int8
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkMul
negate :: Exp Int8 -> Exp Int8
negate = Exp Int8 -> Exp Int8
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkNeg
abs :: Exp Int8 -> Exp Int8
abs = Exp Int8 -> Exp Int8
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkAbs
signum :: Exp Int8 -> Exp Int8
signum = Exp Int8 -> Exp Int8
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkSig
fromInteger :: Integer -> Exp Int8
fromInteger = Int8 -> Exp Int8
forall e. (HasCallStack, Elt e) => e -> Exp e
constant (Int8 -> Exp Int8) -> (Integer -> Int8) -> Integer -> Exp Int8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Int8
forall a. Num a => Integer -> a
P.fromInteger
instance P.Num (Exp Int16) where
+ :: Exp Int16 -> Exp Int16 -> Exp Int16
(+) = Exp Int16 -> Exp Int16 -> Exp Int16
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkAdd
(-) = Exp Int16 -> Exp Int16 -> Exp Int16
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkSub
* :: Exp Int16 -> Exp Int16 -> Exp Int16
(*) = Exp Int16 -> Exp Int16 -> Exp Int16
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkMul
negate :: Exp Int16 -> Exp Int16
negate = Exp Int16 -> Exp Int16
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkNeg
abs :: Exp Int16 -> Exp Int16
abs = Exp Int16 -> Exp Int16
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkAbs
signum :: Exp Int16 -> Exp Int16
signum = Exp Int16 -> Exp Int16
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkSig
fromInteger :: Integer -> Exp Int16
fromInteger = Int16 -> Exp Int16
forall e. (HasCallStack, Elt e) => e -> Exp e
constant (Int16 -> Exp Int16) -> (Integer -> Int16) -> Integer -> Exp Int16
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Int16
forall a. Num a => Integer -> a
P.fromInteger
instance P.Num (Exp Int32) where
+ :: Exp Int32 -> Exp Int32 -> Exp Int32
(+) = Exp Int32 -> Exp Int32 -> Exp Int32
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkAdd
(-) = Exp Int32 -> Exp Int32 -> Exp Int32
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkSub
* :: Exp Int32 -> Exp Int32 -> Exp Int32
(*) = Exp Int32 -> Exp Int32 -> Exp Int32
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkMul
negate :: Exp Int32 -> Exp Int32
negate = Exp Int32 -> Exp Int32
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkNeg
abs :: Exp Int32 -> Exp Int32
abs = Exp Int32 -> Exp Int32
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkAbs
signum :: Exp Int32 -> Exp Int32
signum = Exp Int32 -> Exp Int32
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkSig
fromInteger :: Integer -> Exp Int32
fromInteger = Int32 -> Exp Int32
forall e. (HasCallStack, Elt e) => e -> Exp e
constant (Int32 -> Exp Int32) -> (Integer -> Int32) -> Integer -> Exp Int32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Int32
forall a. Num a => Integer -> a
P.fromInteger
instance P.Num (Exp Int64) where
+ :: Exp Int64 -> Exp Int64 -> Exp Int64
(+) = Exp Int64 -> Exp Int64 -> Exp Int64
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkAdd
(-) = Exp Int64 -> Exp Int64 -> Exp Int64
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkSub
* :: Exp Int64 -> Exp Int64 -> Exp Int64
(*) = Exp Int64 -> Exp Int64 -> Exp Int64
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkMul
negate :: Exp Int64 -> Exp Int64
negate = Exp Int64 -> Exp Int64
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkNeg
abs :: Exp Int64 -> Exp Int64
abs = Exp Int64 -> Exp Int64
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkAbs
signum :: Exp Int64 -> Exp Int64
signum = Exp Int64 -> Exp Int64
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkSig
fromInteger :: Integer -> Exp Int64
fromInteger = Int64 -> Exp Int64
forall e. (HasCallStack, Elt e) => e -> Exp e
constant (Int64 -> Exp Int64) -> (Integer -> Int64) -> Integer -> Exp Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Int64
forall a. Num a => Integer -> a
P.fromInteger
instance P.Num (Exp Word) where
+ :: Exp Word -> Exp Word -> Exp Word
(+) = Exp Word -> Exp Word -> Exp Word
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkAdd
(-) = Exp Word -> Exp Word -> Exp Word
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkSub
* :: Exp Word -> Exp Word -> Exp Word
(*) = Exp Word -> Exp Word -> Exp Word
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkMul
negate :: Exp Word -> Exp Word
negate = Exp Word -> Exp Word
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkNeg
abs :: Exp Word -> Exp Word
abs = Exp Word -> Exp Word
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkAbs
signum :: Exp Word -> Exp Word
signum = Exp Word -> Exp Word
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkSig
fromInteger :: Integer -> Exp Word
fromInteger = Word -> Exp Word
forall e. (HasCallStack, Elt e) => e -> Exp e
constant (Word -> Exp Word) -> (Integer -> Word) -> Integer -> Exp Word
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Word
forall a. Num a => Integer -> a
P.fromInteger
instance P.Num (Exp Word8) where
+ :: Exp Word8 -> Exp Word8 -> Exp Word8
(+) = Exp Word8 -> Exp Word8 -> Exp Word8
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkAdd
(-) = Exp Word8 -> Exp Word8 -> Exp Word8
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkSub
* :: Exp Word8 -> Exp Word8 -> Exp Word8
(*) = Exp Word8 -> Exp Word8 -> Exp Word8
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkMul
negate :: Exp Word8 -> Exp Word8
negate = Exp Word8 -> Exp Word8
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkNeg
abs :: Exp Word8 -> Exp Word8
abs = Exp Word8 -> Exp Word8
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkAbs
signum :: Exp Word8 -> Exp Word8
signum = Exp Word8 -> Exp Word8
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkSig
fromInteger :: Integer -> Exp Word8
fromInteger = Word8 -> Exp Word8
forall e. (HasCallStack, Elt e) => e -> Exp e
constant (Word8 -> Exp Word8) -> (Integer -> Word8) -> Integer -> Exp Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Word8
forall a. Num a => Integer -> a
P.fromInteger
instance P.Num (Exp Word16) where
+ :: Exp Word16 -> Exp Word16 -> Exp Word16
(+) = Exp Word16 -> Exp Word16 -> Exp Word16
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkAdd
(-) = Exp Word16 -> Exp Word16 -> Exp Word16
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkSub
* :: Exp Word16 -> Exp Word16 -> Exp Word16
(*) = Exp Word16 -> Exp Word16 -> Exp Word16
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkMul
negate :: Exp Word16 -> Exp Word16
negate = Exp Word16 -> Exp Word16
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkNeg
abs :: Exp Word16 -> Exp Word16
abs = Exp Word16 -> Exp Word16
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkAbs
signum :: Exp Word16 -> Exp Word16
signum = Exp Word16 -> Exp Word16
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkSig
fromInteger :: Integer -> Exp Word16
fromInteger = Word16 -> Exp Word16
forall e. (HasCallStack, Elt e) => e -> Exp e
constant (Word16 -> Exp Word16)
-> (Integer -> Word16) -> Integer -> Exp Word16
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Word16
forall a. Num a => Integer -> a
P.fromInteger
instance P.Num (Exp Word32) where
+ :: Exp Word32 -> Exp Word32 -> Exp Word32
(+) = Exp Word32 -> Exp Word32 -> Exp Word32
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkAdd
(-) = Exp Word32 -> Exp Word32 -> Exp Word32
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkSub
* :: Exp Word32 -> Exp Word32 -> Exp Word32
(*) = Exp Word32 -> Exp Word32 -> Exp Word32
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkMul
negate :: Exp Word32 -> Exp Word32
negate = Exp Word32 -> Exp Word32
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkNeg
abs :: Exp Word32 -> Exp Word32
abs = Exp Word32 -> Exp Word32
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkAbs
signum :: Exp Word32 -> Exp Word32
signum = Exp Word32 -> Exp Word32
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkSig
fromInteger :: Integer -> Exp Word32
fromInteger = Word32 -> Exp Word32
forall e. (HasCallStack, Elt e) => e -> Exp e
constant (Word32 -> Exp Word32)
-> (Integer -> Word32) -> Integer -> Exp Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Word32
forall a. Num a => Integer -> a
P.fromInteger
instance P.Num (Exp Word64) where
+ :: Exp Word64 -> Exp Word64 -> Exp Word64
(+) = Exp Word64 -> Exp Word64 -> Exp Word64
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkAdd
(-) = Exp Word64 -> Exp Word64 -> Exp Word64
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkSub
* :: Exp Word64 -> Exp Word64 -> Exp Word64
(*) = Exp Word64 -> Exp Word64 -> Exp Word64
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkMul
negate :: Exp Word64 -> Exp Word64
negate = Exp Word64 -> Exp Word64
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkNeg
abs :: Exp Word64 -> Exp Word64
abs = Exp Word64 -> Exp Word64
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkAbs
signum :: Exp Word64 -> Exp Word64
signum = Exp Word64 -> Exp Word64
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkSig
fromInteger :: Integer -> Exp Word64
fromInteger = Word64 -> Exp Word64
forall e. (HasCallStack, Elt e) => e -> Exp e
constant (Word64 -> Exp Word64)
-> (Integer -> Word64) -> Integer -> Exp Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Word64
forall a. Num a => Integer -> a
P.fromInteger
instance P.Num (Exp CInt) where
+ :: Exp CInt -> Exp CInt -> Exp CInt
(+) = Exp CInt -> Exp CInt -> Exp CInt
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkAdd
(-) = Exp CInt -> Exp CInt -> Exp CInt
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkSub
* :: Exp CInt -> Exp CInt -> Exp CInt
(*) = Exp CInt -> Exp CInt -> Exp CInt
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkMul
negate :: Exp CInt -> Exp CInt
negate = Exp CInt -> Exp CInt
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkNeg
abs :: Exp CInt -> Exp CInt
abs = Exp CInt -> Exp CInt
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkAbs
signum :: Exp CInt -> Exp CInt
signum = Exp CInt -> Exp CInt
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkSig
fromInteger :: Integer -> Exp CInt
fromInteger = CInt -> Exp CInt
forall e. (HasCallStack, Elt e) => e -> Exp e
constant (CInt -> Exp CInt) -> (Integer -> CInt) -> Integer -> Exp CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> CInt
forall a. Num a => Integer -> a
P.fromInteger
instance P.Num (Exp CUInt) where
+ :: Exp CUInt -> Exp CUInt -> Exp CUInt
(+) = Exp CUInt -> Exp CUInt -> Exp CUInt
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkAdd
(-) = Exp CUInt -> Exp CUInt -> Exp CUInt
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkSub
* :: Exp CUInt -> Exp CUInt -> Exp CUInt
(*) = Exp CUInt -> Exp CUInt -> Exp CUInt
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkMul
negate :: Exp CUInt -> Exp CUInt
negate = Exp CUInt -> Exp CUInt
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkNeg
abs :: Exp CUInt -> Exp CUInt
abs = Exp CUInt -> Exp CUInt
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkAbs
signum :: Exp CUInt -> Exp CUInt
signum = Exp CUInt -> Exp CUInt
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkSig
fromInteger :: Integer -> Exp CUInt
fromInteger = CUInt -> Exp CUInt
forall e. (HasCallStack, Elt e) => e -> Exp e
constant (CUInt -> Exp CUInt) -> (Integer -> CUInt) -> Integer -> Exp CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> CUInt
forall a. Num a => Integer -> a
P.fromInteger
instance P.Num (Exp CLong) where
+ :: Exp CLong -> Exp CLong -> Exp CLong
(+) = Exp CLong -> Exp CLong -> Exp CLong
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkAdd
(-) = Exp CLong -> Exp CLong -> Exp CLong
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkSub
* :: Exp CLong -> Exp CLong -> Exp CLong
(*) = Exp CLong -> Exp CLong -> Exp CLong
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkMul
negate :: Exp CLong -> Exp CLong
negate = Exp CLong -> Exp CLong
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkNeg
abs :: Exp CLong -> Exp CLong
abs = Exp CLong -> Exp CLong
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkAbs
signum :: Exp CLong -> Exp CLong
signum = Exp CLong -> Exp CLong
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkSig
fromInteger :: Integer -> Exp CLong
fromInteger = CLong -> Exp CLong
forall e. (HasCallStack, Elt e) => e -> Exp e
constant (CLong -> Exp CLong) -> (Integer -> CLong) -> Integer -> Exp CLong
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> CLong
forall a. Num a => Integer -> a
P.fromInteger
instance P.Num (Exp CULong) where
+ :: Exp CULong -> Exp CULong -> Exp CULong
(+) = Exp CULong -> Exp CULong -> Exp CULong
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkAdd
(-) = Exp CULong -> Exp CULong -> Exp CULong
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkSub
* :: Exp CULong -> Exp CULong -> Exp CULong
(*) = Exp CULong -> Exp CULong -> Exp CULong
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkMul
negate :: Exp CULong -> Exp CULong
negate = Exp CULong -> Exp CULong
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkNeg
abs :: Exp CULong -> Exp CULong
abs = Exp CULong -> Exp CULong
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkAbs
signum :: Exp CULong -> Exp CULong
signum = Exp CULong -> Exp CULong
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkSig
fromInteger :: Integer -> Exp CULong
fromInteger = CULong -> Exp CULong
forall e. (HasCallStack, Elt e) => e -> Exp e
constant (CULong -> Exp CULong)
-> (Integer -> CULong) -> Integer -> Exp CULong
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> CULong
forall a. Num a => Integer -> a
P.fromInteger
instance P.Num (Exp CLLong) where
+ :: Exp CLLong -> Exp CLLong -> Exp CLLong
(+) = Exp CLLong -> Exp CLLong -> Exp CLLong
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkAdd
(-) = Exp CLLong -> Exp CLLong -> Exp CLLong
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkSub
* :: Exp CLLong -> Exp CLLong -> Exp CLLong
(*) = Exp CLLong -> Exp CLLong -> Exp CLLong
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkMul
negate :: Exp CLLong -> Exp CLLong
negate = Exp CLLong -> Exp CLLong
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkNeg
abs :: Exp CLLong -> Exp CLLong
abs = Exp CLLong -> Exp CLLong
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkAbs
signum :: Exp CLLong -> Exp CLLong
signum = Exp CLLong -> Exp CLLong
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkSig
fromInteger :: Integer -> Exp CLLong
fromInteger = CLLong -> Exp CLLong
forall e. (HasCallStack, Elt e) => e -> Exp e
constant (CLLong -> Exp CLLong)
-> (Integer -> CLLong) -> Integer -> Exp CLLong
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> CLLong
forall a. Num a => Integer -> a
P.fromInteger
instance P.Num (Exp CULLong) where
+ :: Exp CULLong -> Exp CULLong -> Exp CULLong
(+) = Exp CULLong -> Exp CULLong -> Exp CULLong
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkAdd
(-) = Exp CULLong -> Exp CULLong -> Exp CULLong
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkSub
* :: Exp CULLong -> Exp CULLong -> Exp CULLong
(*) = Exp CULLong -> Exp CULLong -> Exp CULLong
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkMul
negate :: Exp CULLong -> Exp CULLong
negate = Exp CULLong -> Exp CULLong
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkNeg
abs :: Exp CULLong -> Exp CULLong
abs = Exp CULLong -> Exp CULLong
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkAbs
signum :: Exp CULLong -> Exp CULLong
signum = Exp CULLong -> Exp CULLong
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkSig
fromInteger :: Integer -> Exp CULLong
fromInteger = CULLong -> Exp CULLong
forall e. (HasCallStack, Elt e) => e -> Exp e
constant (CULLong -> Exp CULLong)
-> (Integer -> CULLong) -> Integer -> Exp CULLong
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> CULLong
forall a. Num a => Integer -> a
P.fromInteger
instance P.Num (Exp CShort) where
+ :: Exp CShort -> Exp CShort -> Exp CShort
(+) = Exp CShort -> Exp CShort -> Exp CShort
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkAdd
(-) = Exp CShort -> Exp CShort -> Exp CShort
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkSub
* :: Exp CShort -> Exp CShort -> Exp CShort
(*) = Exp CShort -> Exp CShort -> Exp CShort
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkMul
negate :: Exp CShort -> Exp CShort
negate = Exp CShort -> Exp CShort
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkNeg
abs :: Exp CShort -> Exp CShort
abs = Exp CShort -> Exp CShort
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkAbs
signum :: Exp CShort -> Exp CShort
signum = Exp CShort -> Exp CShort
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkSig
fromInteger :: Integer -> Exp CShort
fromInteger = CShort -> Exp CShort
forall e. (HasCallStack, Elt e) => e -> Exp e
constant (CShort -> Exp CShort)
-> (Integer -> CShort) -> Integer -> Exp CShort
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> CShort
forall a. Num a => Integer -> a
P.fromInteger
instance P.Num (Exp CUShort) where
+ :: Exp CUShort -> Exp CUShort -> Exp CUShort
(+) = Exp CUShort -> Exp CUShort -> Exp CUShort
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkAdd
(-) = Exp CUShort -> Exp CUShort -> Exp CUShort
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkSub
* :: Exp CUShort -> Exp CUShort -> Exp CUShort
(*) = Exp CUShort -> Exp CUShort -> Exp CUShort
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkMul
negate :: Exp CUShort -> Exp CUShort
negate = Exp CUShort -> Exp CUShort
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkNeg
abs :: Exp CUShort -> Exp CUShort
abs = Exp CUShort -> Exp CUShort
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkAbs
signum :: Exp CUShort -> Exp CUShort
signum = Exp CUShort -> Exp CUShort
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkSig
fromInteger :: Integer -> Exp CUShort
fromInteger = CUShort -> Exp CUShort
forall e. (HasCallStack, Elt e) => e -> Exp e
constant (CUShort -> Exp CUShort)
-> (Integer -> CUShort) -> Integer -> Exp CUShort
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> CUShort
forall a. Num a => Integer -> a
P.fromInteger
instance P.Num (Exp Half) where
+ :: Exp Half -> Exp Half -> Exp Half
(+) = Exp Half -> Exp Half -> Exp Half
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkAdd
(-) = Exp Half -> Exp Half -> Exp Half
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkSub
* :: Exp Half -> Exp Half -> Exp Half
(*) = Exp Half -> Exp Half -> Exp Half
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkMul
negate :: Exp Half -> Exp Half
negate = Exp Half -> Exp Half
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkNeg
abs :: Exp Half -> Exp Half
abs = Exp Half -> Exp Half
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkAbs
signum :: Exp Half -> Exp Half
signum = Exp Half -> Exp Half
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkSig
fromInteger :: Integer -> Exp Half
fromInteger = Half -> Exp Half
forall e. (HasCallStack, Elt e) => e -> Exp e
constant (Half -> Exp Half) -> (Integer -> Half) -> Integer -> Exp Half
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Half
forall a. Num a => Integer -> a
P.fromInteger
instance P.Num (Exp Float) where
+ :: Exp Float -> Exp Float -> Exp Float
(+) = Exp Float -> Exp Float -> Exp Float
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkAdd
(-) = Exp Float -> Exp Float -> Exp Float
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkSub
* :: Exp Float -> Exp Float -> Exp Float
(*) = Exp Float -> Exp Float -> Exp Float
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkMul
negate :: Exp Float -> Exp Float
negate = Exp Float -> Exp Float
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkNeg
abs :: Exp Float -> Exp Float
abs = Exp Float -> Exp Float
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkAbs
signum :: Exp Float -> Exp Float
signum = Exp Float -> Exp Float
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkSig
fromInteger :: Integer -> Exp Float
fromInteger = Float -> Exp Float
forall e. (HasCallStack, Elt e) => e -> Exp e
constant (Float -> Exp Float) -> (Integer -> Float) -> Integer -> Exp Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Float
forall a. Num a => Integer -> a
P.fromInteger
instance P.Num (Exp Double) where
+ :: Exp Double -> Exp Double -> Exp Double
(+) = Exp Double -> Exp Double -> Exp Double
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkAdd
(-) = Exp Double -> Exp Double -> Exp Double
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkSub
* :: Exp Double -> Exp Double -> Exp Double
(*) = Exp Double -> Exp Double -> Exp Double
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkMul
negate :: Exp Double -> Exp Double
negate = Exp Double -> Exp Double
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkNeg
abs :: Exp Double -> Exp Double
abs = Exp Double -> Exp Double
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkAbs
signum :: Exp Double -> Exp Double
signum = Exp Double -> Exp Double
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkSig
fromInteger :: Integer -> Exp Double
fromInteger = Double -> Exp Double
forall e. (HasCallStack, Elt e) => e -> Exp e
constant (Double -> Exp Double)
-> (Integer -> Double) -> Integer -> Exp Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Double
forall a. Num a => Integer -> a
P.fromInteger
instance P.Num (Exp CFloat) where
+ :: Exp CFloat -> Exp CFloat -> Exp CFloat
(+) = Exp CFloat -> Exp CFloat -> Exp CFloat
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkAdd
(-) = Exp CFloat -> Exp CFloat -> Exp CFloat
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkSub
* :: Exp CFloat -> Exp CFloat -> Exp CFloat
(*) = Exp CFloat -> Exp CFloat -> Exp CFloat
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkMul
negate :: Exp CFloat -> Exp CFloat
negate = Exp CFloat -> Exp CFloat
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkNeg
abs :: Exp CFloat -> Exp CFloat
abs = Exp CFloat -> Exp CFloat
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkAbs
signum :: Exp CFloat -> Exp CFloat
signum = Exp CFloat -> Exp CFloat
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkSig
fromInteger :: Integer -> Exp CFloat
fromInteger = CFloat -> Exp CFloat
forall e. (HasCallStack, Elt e) => e -> Exp e
constant (CFloat -> Exp CFloat)
-> (Integer -> CFloat) -> Integer -> Exp CFloat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> CFloat
forall a. Num a => Integer -> a
P.fromInteger
instance P.Num (Exp CDouble) where
+ :: Exp CDouble -> Exp CDouble -> Exp CDouble
(+) = Exp CDouble -> Exp CDouble -> Exp CDouble
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkAdd
(-) = Exp CDouble -> Exp CDouble -> Exp CDouble
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkSub
* :: Exp CDouble -> Exp CDouble -> Exp CDouble
(*) = Exp CDouble -> Exp CDouble -> Exp CDouble
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t -> Exp t
mkMul
negate :: Exp CDouble -> Exp CDouble
negate = Exp CDouble -> Exp CDouble
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkNeg
abs :: Exp CDouble -> Exp CDouble
abs = Exp CDouble -> Exp CDouble
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkAbs
signum :: Exp CDouble -> Exp CDouble
signum = Exp CDouble -> Exp CDouble
forall t. (Elt t, IsNum (EltR t)) => Exp t -> Exp t
mkSig
fromInteger :: Integer -> Exp CDouble
fromInteger = CDouble -> Exp CDouble
forall e. (HasCallStack, Elt e) => e -> Exp e
constant (CDouble -> Exp CDouble)
-> (Integer -> CDouble) -> Integer -> Exp CDouble
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> CDouble
forall a. Num a => Integer -> a
P.fromInteger