{-# LANGUAGE LambdaCase #-}
module Language.Futhark.Primitive
(
IntType (..),
allIntTypes,
FloatType (..),
allFloatTypes,
PrimType (..),
allPrimTypes,
module Data.Int,
module Data.Word,
Half,
IntValue (..),
intValue,
intValueType,
valueIntegral,
FloatValue (..),
floatValue,
floatValueType,
PrimValue (..),
primValueType,
blankPrimValue,
onePrimValue,
Overflow (..),
Safety (..),
UnOp (..),
allUnOps,
BinOp (..),
allBinOps,
ConvOp (..),
allConvOps,
CmpOp (..),
allCmpOps,
doUnOp,
doComplement,
doAbs,
doFAbs,
doSSignum,
doUSignum,
doBinOp,
doAdd,
doMul,
doSDiv,
doSMod,
doPow,
doConvOp,
doZExt,
doSExt,
doFPConv,
doFPToUI,
doFPToSI,
doUIToFP,
doSIToFP,
intToInt64,
intToWord64,
flipConvOp,
doCmpOp,
doCmpEq,
doCmpUlt,
doCmpUle,
doCmpSlt,
doCmpSle,
doFCmpLt,
doFCmpLe,
binOpType,
unOpType,
cmpOpType,
convOpType,
primFuns,
zeroIsh,
zeroIshInt,
oneIsh,
oneIshInt,
negativeIsh,
primBitSize,
primByteSize,
intByteSize,
floatByteSize,
commutativeBinOp,
associativeBinOp,
convOpFun,
prettySigned,
)
where
import Control.Category
import Data.Binary.Get qualified as G
import Data.Binary.Put qualified as P
import Data.Bits
( complement,
countLeadingZeros,
countTrailingZeros,
popCount,
shift,
shiftR,
xor,
(.&.),
(.|.),
)
import Data.Fixed (mod')
import Data.Int (Int16, Int32, Int64, Int8)
import Data.Map qualified as M
import Data.Text qualified as T
import Data.Word (Word16, Word32, Word64, Word8)
import Foreign.C.Types (CUShort (..))
import Futhark.Util (convFloat)
import Futhark.Util.CMath
import Futhark.Util.Pretty
import Numeric (log1p)
import Numeric.Half
import Prelude hiding (id, (.))
data IntType
= Int8
| Int16
| Int32
| Int64
deriving (IntType -> IntType -> Bool
(IntType -> IntType -> Bool)
-> (IntType -> IntType -> Bool) -> Eq IntType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IntType -> IntType -> Bool
== :: IntType -> IntType -> Bool
$c/= :: IntType -> IntType -> Bool
/= :: IntType -> IntType -> Bool
Eq, Eq IntType
Eq IntType
-> (IntType -> IntType -> Ordering)
-> (IntType -> IntType -> Bool)
-> (IntType -> IntType -> Bool)
-> (IntType -> IntType -> Bool)
-> (IntType -> IntType -> Bool)
-> (IntType -> IntType -> IntType)
-> (IntType -> IntType -> IntType)
-> Ord IntType
IntType -> IntType -> Bool
IntType -> IntType -> Ordering
IntType -> IntType -> IntType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: IntType -> IntType -> Ordering
compare :: IntType -> IntType -> Ordering
$c< :: IntType -> IntType -> Bool
< :: IntType -> IntType -> Bool
$c<= :: IntType -> IntType -> Bool
<= :: IntType -> IntType -> Bool
$c> :: IntType -> IntType -> Bool
> :: IntType -> IntType -> Bool
$c>= :: IntType -> IntType -> Bool
>= :: IntType -> IntType -> Bool
$cmax :: IntType -> IntType -> IntType
max :: IntType -> IntType -> IntType
$cmin :: IntType -> IntType -> IntType
min :: IntType -> IntType -> IntType
Ord, Int -> IntType -> ShowS
[IntType] -> ShowS
IntType -> String
(Int -> IntType -> ShowS)
-> (IntType -> String) -> ([IntType] -> ShowS) -> Show IntType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IntType -> ShowS
showsPrec :: Int -> IntType -> ShowS
$cshow :: IntType -> String
show :: IntType -> String
$cshowList :: [IntType] -> ShowS
showList :: [IntType] -> ShowS
Show, Int -> IntType
IntType -> Int
IntType -> [IntType]
IntType -> IntType
IntType -> IntType -> [IntType]
IntType -> IntType -> IntType -> [IntType]
(IntType -> IntType)
-> (IntType -> IntType)
-> (Int -> IntType)
-> (IntType -> Int)
-> (IntType -> [IntType])
-> (IntType -> IntType -> [IntType])
-> (IntType -> IntType -> [IntType])
-> (IntType -> IntType -> IntType -> [IntType])
-> Enum IntType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: IntType -> IntType
succ :: IntType -> IntType
$cpred :: IntType -> IntType
pred :: IntType -> IntType
$ctoEnum :: Int -> IntType
toEnum :: Int -> IntType
$cfromEnum :: IntType -> Int
fromEnum :: IntType -> Int
$cenumFrom :: IntType -> [IntType]
enumFrom :: IntType -> [IntType]
$cenumFromThen :: IntType -> IntType -> [IntType]
enumFromThen :: IntType -> IntType -> [IntType]
$cenumFromTo :: IntType -> IntType -> [IntType]
enumFromTo :: IntType -> IntType -> [IntType]
$cenumFromThenTo :: IntType -> IntType -> IntType -> [IntType]
enumFromThenTo :: IntType -> IntType -> IntType -> [IntType]
Enum, IntType
IntType -> IntType -> Bounded IntType
forall a. a -> a -> Bounded a
$cminBound :: IntType
minBound :: IntType
$cmaxBound :: IntType
maxBound :: IntType
Bounded)
instance Pretty IntType where
pretty :: forall ann. IntType -> Doc ann
pretty IntType
Int8 = Doc ann
"i8"
pretty IntType
Int16 = Doc ann
"i16"
pretty IntType
Int32 = Doc ann
"i32"
pretty IntType
Int64 = Doc ann
"i64"
allIntTypes :: [IntType]
allIntTypes :: [IntType]
allIntTypes = [IntType
forall a. Bounded a => a
minBound .. IntType
forall a. Bounded a => a
maxBound]
data FloatType
= Float16
| Float32
| Float64
deriving (FloatType -> FloatType -> Bool
(FloatType -> FloatType -> Bool)
-> (FloatType -> FloatType -> Bool) -> Eq FloatType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FloatType -> FloatType -> Bool
== :: FloatType -> FloatType -> Bool
$c/= :: FloatType -> FloatType -> Bool
/= :: FloatType -> FloatType -> Bool
Eq, Eq FloatType
Eq FloatType
-> (FloatType -> FloatType -> Ordering)
-> (FloatType -> FloatType -> Bool)
-> (FloatType -> FloatType -> Bool)
-> (FloatType -> FloatType -> Bool)
-> (FloatType -> FloatType -> Bool)
-> (FloatType -> FloatType -> FloatType)
-> (FloatType -> FloatType -> FloatType)
-> Ord FloatType
FloatType -> FloatType -> Bool
FloatType -> FloatType -> Ordering
FloatType -> FloatType -> FloatType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FloatType -> FloatType -> Ordering
compare :: FloatType -> FloatType -> Ordering
$c< :: FloatType -> FloatType -> Bool
< :: FloatType -> FloatType -> Bool
$c<= :: FloatType -> FloatType -> Bool
<= :: FloatType -> FloatType -> Bool
$c> :: FloatType -> FloatType -> Bool
> :: FloatType -> FloatType -> Bool
$c>= :: FloatType -> FloatType -> Bool
>= :: FloatType -> FloatType -> Bool
$cmax :: FloatType -> FloatType -> FloatType
max :: FloatType -> FloatType -> FloatType
$cmin :: FloatType -> FloatType -> FloatType
min :: FloatType -> FloatType -> FloatType
Ord, Int -> FloatType -> ShowS
[FloatType] -> ShowS
FloatType -> String
(Int -> FloatType -> ShowS)
-> (FloatType -> String)
-> ([FloatType] -> ShowS)
-> Show FloatType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FloatType -> ShowS
showsPrec :: Int -> FloatType -> ShowS
$cshow :: FloatType -> String
show :: FloatType -> String
$cshowList :: [FloatType] -> ShowS
showList :: [FloatType] -> ShowS
Show, Int -> FloatType
FloatType -> Int
FloatType -> [FloatType]
FloatType -> FloatType
FloatType -> FloatType -> [FloatType]
FloatType -> FloatType -> FloatType -> [FloatType]
(FloatType -> FloatType)
-> (FloatType -> FloatType)
-> (Int -> FloatType)
-> (FloatType -> Int)
-> (FloatType -> [FloatType])
-> (FloatType -> FloatType -> [FloatType])
-> (FloatType -> FloatType -> [FloatType])
-> (FloatType -> FloatType -> FloatType -> [FloatType])
-> Enum FloatType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: FloatType -> FloatType
succ :: FloatType -> FloatType
$cpred :: FloatType -> FloatType
pred :: FloatType -> FloatType
$ctoEnum :: Int -> FloatType
toEnum :: Int -> FloatType
$cfromEnum :: FloatType -> Int
fromEnum :: FloatType -> Int
$cenumFrom :: FloatType -> [FloatType]
enumFrom :: FloatType -> [FloatType]
$cenumFromThen :: FloatType -> FloatType -> [FloatType]
enumFromThen :: FloatType -> FloatType -> [FloatType]
$cenumFromTo :: FloatType -> FloatType -> [FloatType]
enumFromTo :: FloatType -> FloatType -> [FloatType]
$cenumFromThenTo :: FloatType -> FloatType -> FloatType -> [FloatType]
enumFromThenTo :: FloatType -> FloatType -> FloatType -> [FloatType]
Enum, FloatType
FloatType -> FloatType -> Bounded FloatType
forall a. a -> a -> Bounded a
$cminBound :: FloatType
minBound :: FloatType
$cmaxBound :: FloatType
maxBound :: FloatType
Bounded)
instance Pretty FloatType where
pretty :: forall ann. FloatType -> Doc ann
pretty FloatType
Float16 = Doc ann
"f16"
pretty FloatType
Float32 = Doc ann
"f32"
pretty FloatType
Float64 = Doc ann
"f64"
allFloatTypes :: [FloatType]
allFloatTypes :: [FloatType]
allFloatTypes = [FloatType
forall a. Bounded a => a
minBound .. FloatType
forall a. Bounded a => a
maxBound]
data PrimType
= IntType IntType
| FloatType FloatType
| Bool
|
Unit
deriving (PrimType -> PrimType -> Bool
(PrimType -> PrimType -> Bool)
-> (PrimType -> PrimType -> Bool) -> Eq PrimType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PrimType -> PrimType -> Bool
== :: PrimType -> PrimType -> Bool
$c/= :: PrimType -> PrimType -> Bool
/= :: PrimType -> PrimType -> Bool
Eq, Eq PrimType
Eq PrimType
-> (PrimType -> PrimType -> Ordering)
-> (PrimType -> PrimType -> Bool)
-> (PrimType -> PrimType -> Bool)
-> (PrimType -> PrimType -> Bool)
-> (PrimType -> PrimType -> Bool)
-> (PrimType -> PrimType -> PrimType)
-> (PrimType -> PrimType -> PrimType)
-> Ord PrimType
PrimType -> PrimType -> Bool
PrimType -> PrimType -> Ordering
PrimType -> PrimType -> PrimType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: PrimType -> PrimType -> Ordering
compare :: PrimType -> PrimType -> Ordering
$c< :: PrimType -> PrimType -> Bool
< :: PrimType -> PrimType -> Bool
$c<= :: PrimType -> PrimType -> Bool
<= :: PrimType -> PrimType -> Bool
$c> :: PrimType -> PrimType -> Bool
> :: PrimType -> PrimType -> Bool
$c>= :: PrimType -> PrimType -> Bool
>= :: PrimType -> PrimType -> Bool
$cmax :: PrimType -> PrimType -> PrimType
max :: PrimType -> PrimType -> PrimType
$cmin :: PrimType -> PrimType -> PrimType
min :: PrimType -> PrimType -> PrimType
Ord, Int -> PrimType -> ShowS
[PrimType] -> ShowS
PrimType -> String
(Int -> PrimType -> ShowS)
-> (PrimType -> String) -> ([PrimType] -> ShowS) -> Show PrimType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PrimType -> ShowS
showsPrec :: Int -> PrimType -> ShowS
$cshow :: PrimType -> String
show :: PrimType -> String
$cshowList :: [PrimType] -> ShowS
showList :: [PrimType] -> ShowS
Show)
instance Enum PrimType where
toEnum :: Int -> PrimType
toEnum Int
0 = IntType -> PrimType
IntType IntType
Int8
toEnum Int
1 = IntType -> PrimType
IntType IntType
Int16
toEnum Int
2 = IntType -> PrimType
IntType IntType
Int32
toEnum Int
3 = IntType -> PrimType
IntType IntType
Int64
toEnum Int
4 = FloatType -> PrimType
FloatType FloatType
Float16
toEnum Int
5 = FloatType -> PrimType
FloatType FloatType
Float32
toEnum Int
6 = FloatType -> PrimType
FloatType FloatType
Float64
toEnum Int
7 = PrimType
Bool
toEnum Int
_ = PrimType
Unit
fromEnum :: PrimType -> Int
fromEnum (IntType IntType
Int8) = Int
0
fromEnum (IntType IntType
Int16) = Int
1
fromEnum (IntType IntType
Int32) = Int
2
fromEnum (IntType IntType
Int64) = Int
3
fromEnum (FloatType FloatType
Float16) = Int
4
fromEnum (FloatType FloatType
Float32) = Int
5
fromEnum (FloatType FloatType
Float64) = Int
6
fromEnum PrimType
Bool = Int
7
fromEnum PrimType
Unit = Int
8
instance Bounded PrimType where
minBound :: PrimType
minBound = IntType -> PrimType
IntType IntType
Int8
maxBound :: PrimType
maxBound = PrimType
Unit
instance Pretty PrimType where
pretty :: forall ann. PrimType -> Doc ann
pretty (IntType IntType
t) = IntType -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. IntType -> Doc ann
pretty IntType
t
pretty (FloatType FloatType
t) = FloatType -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. FloatType -> Doc ann
pretty FloatType
t
pretty PrimType
Bool = Doc ann
"bool"
pretty PrimType
Unit = Doc ann
"unit"
allPrimTypes :: [PrimType]
allPrimTypes :: [PrimType]
allPrimTypes =
(IntType -> PrimType) -> [IntType] -> [PrimType]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> PrimType
IntType [IntType]
allIntTypes
[PrimType] -> [PrimType] -> [PrimType]
forall a. [a] -> [a] -> [a]
++ (FloatType -> PrimType) -> [FloatType] -> [PrimType]
forall a b. (a -> b) -> [a] -> [b]
map FloatType -> PrimType
FloatType [FloatType]
allFloatTypes
[PrimType] -> [PrimType] -> [PrimType]
forall a. [a] -> [a] -> [a]
++ [PrimType
Bool, PrimType
Unit]
data IntValue
= Int8Value !Int8
| Int16Value !Int16
| Int32Value !Int32
| Int64Value !Int64
deriving (IntValue -> IntValue -> Bool
(IntValue -> IntValue -> Bool)
-> (IntValue -> IntValue -> Bool) -> Eq IntValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IntValue -> IntValue -> Bool
== :: IntValue -> IntValue -> Bool
$c/= :: IntValue -> IntValue -> Bool
/= :: IntValue -> IntValue -> Bool
Eq, Eq IntValue
Eq IntValue
-> (IntValue -> IntValue -> Ordering)
-> (IntValue -> IntValue -> Bool)
-> (IntValue -> IntValue -> Bool)
-> (IntValue -> IntValue -> Bool)
-> (IntValue -> IntValue -> Bool)
-> (IntValue -> IntValue -> IntValue)
-> (IntValue -> IntValue -> IntValue)
-> Ord IntValue
IntValue -> IntValue -> Bool
IntValue -> IntValue -> Ordering
IntValue -> IntValue -> IntValue
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: IntValue -> IntValue -> Ordering
compare :: IntValue -> IntValue -> Ordering
$c< :: IntValue -> IntValue -> Bool
< :: IntValue -> IntValue -> Bool
$c<= :: IntValue -> IntValue -> Bool
<= :: IntValue -> IntValue -> Bool
$c> :: IntValue -> IntValue -> Bool
> :: IntValue -> IntValue -> Bool
$c>= :: IntValue -> IntValue -> Bool
>= :: IntValue -> IntValue -> Bool
$cmax :: IntValue -> IntValue -> IntValue
max :: IntValue -> IntValue -> IntValue
$cmin :: IntValue -> IntValue -> IntValue
min :: IntValue -> IntValue -> IntValue
Ord, Int -> IntValue -> ShowS
[IntValue] -> ShowS
IntValue -> String
(Int -> IntValue -> ShowS)
-> (IntValue -> String) -> ([IntValue] -> ShowS) -> Show IntValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IntValue -> ShowS
showsPrec :: Int -> IntValue -> ShowS
$cshow :: IntValue -> String
show :: IntValue -> String
$cshowList :: [IntValue] -> ShowS
showList :: [IntValue] -> ShowS
Show)
instance Pretty IntValue where
pretty :: forall ann. IntValue -> Doc ann
pretty (Int8Value Int8
v) = String -> Doc ann
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (String -> Doc ann) -> String -> Doc ann
forall a b. (a -> b) -> a -> b
$ Int8 -> String
forall a. Show a => a -> String
show Int8
v String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"i8"
pretty (Int16Value Int16
v) = String -> Doc ann
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (String -> Doc ann) -> String -> Doc ann
forall a b. (a -> b) -> a -> b
$ Int16 -> String
forall a. Show a => a -> String
show Int16
v String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"i16"
pretty (Int32Value Int32
v) = String -> Doc ann
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (String -> Doc ann) -> String -> Doc ann
forall a b. (a -> b) -> a -> b
$ Int32 -> String
forall a. Show a => a -> String
show Int32
v String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"i32"
pretty (Int64Value Int64
v) = String -> Doc ann
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (String -> Doc ann) -> String -> Doc ann
forall a b. (a -> b) -> a -> b
$ Int64 -> String
forall a. Show a => a -> String
show Int64
v String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"i64"
intValue :: Integral int => IntType -> int -> IntValue
intValue :: forall int. Integral int => IntType -> int -> IntValue
intValue IntType
Int8 = Int8 -> IntValue
Int8Value (Int8 -> IntValue) -> (int -> Int8) -> int -> IntValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. int -> Int8
forall a b. (Integral a, Num b) => a -> b
fromIntegral
intValue IntType
Int16 = Int16 -> IntValue
Int16Value (Int16 -> IntValue) -> (int -> Int16) -> int -> IntValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. int -> Int16
forall a b. (Integral a, Num b) => a -> b
fromIntegral
intValue IntType
Int32 = Int32 -> IntValue
Int32Value (Int32 -> IntValue) -> (int -> Int32) -> int -> IntValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral
intValue IntType
Int64 = Int64 -> IntValue
Int64Value (Int64 -> IntValue) -> (int -> Int64) -> int -> IntValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral
intValueType :: IntValue -> IntType
intValueType :: IntValue -> IntType
intValueType Int8Value {} = IntType
Int8
intValueType Int16Value {} = IntType
Int16
intValueType Int32Value {} = IntType
Int32
intValueType Int64Value {} = IntType
Int64
valueIntegral :: Integral int => IntValue -> int
valueIntegral :: forall int. Integral int => IntValue -> int
valueIntegral (Int8Value Int8
v) = Int8 -> int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int8
v
valueIntegral (Int16Value Int16
v) = Int16 -> int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int16
v
valueIntegral (Int32Value Int32
v) = Int32 -> int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
v
valueIntegral (Int64Value Int64
v) = Int64 -> int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
v
data FloatValue
= Float16Value !Half
| Float32Value !Float
| Float64Value !Double
deriving (Int -> FloatValue -> ShowS
[FloatValue] -> ShowS
FloatValue -> String
(Int -> FloatValue -> ShowS)
-> (FloatValue -> String)
-> ([FloatValue] -> ShowS)
-> Show FloatValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FloatValue -> ShowS
showsPrec :: Int -> FloatValue -> ShowS
$cshow :: FloatValue -> String
show :: FloatValue -> String
$cshowList :: [FloatValue] -> ShowS
showList :: [FloatValue] -> ShowS
Show)
instance Eq FloatValue where
Float16Value Half
x == :: FloatValue -> FloatValue -> Bool
== Float16Value Half
y = Half -> Bool
forall a. RealFloat a => a -> Bool
isNaN Half
x Bool -> Bool -> Bool
&& Half -> Bool
forall a. RealFloat a => a -> Bool
isNaN Half
y Bool -> Bool -> Bool
|| Half
x Half -> Half -> Bool
forall a. Eq a => a -> a -> Bool
== Half
y
Float32Value Float
x == Float32Value Float
y = Float -> Bool
forall a. RealFloat a => a -> Bool
isNaN Float
x Bool -> Bool -> Bool
&& Float -> Bool
forall a. RealFloat a => a -> Bool
isNaN Float
y Bool -> Bool -> Bool
|| Float
x Float -> Float -> Bool
forall a. Eq a => a -> a -> Bool
== Float
y
Float64Value Double
x == Float64Value Double
y = Double -> Bool
forall a. RealFloat a => a -> Bool
isNaN Double
x Bool -> Bool -> Bool
&& Double -> Bool
forall a. RealFloat a => a -> Bool
isNaN Double
y Bool -> Bool -> Bool
|| Double
x Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
y
FloatValue
_ == FloatValue
_ = Bool
False
instance Ord FloatValue where
Float16Value Half
x <= :: FloatValue -> FloatValue -> Bool
<= Float16Value Half
y = Half
x Half -> Half -> Bool
forall a. Ord a => a -> a -> Bool
<= Half
y
Float32Value Float
x <= Float32Value Float
y = Float
x Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
<= Float
y
Float64Value Double
x <= Float64Value Double
y = Double
x Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= Double
y
Float16Value Half
_ <= Float32Value Float
_ = Bool
True
Float16Value Half
_ <= Float64Value Double
_ = Bool
True
Float32Value Float
_ <= Float16Value Half
_ = Bool
False
Float32Value Float
_ <= Float64Value Double
_ = Bool
True
Float64Value Double
_ <= Float16Value Half
_ = Bool
False
Float64Value Double
_ <= Float32Value Float
_ = Bool
False
Float16Value Half
x < :: FloatValue -> FloatValue -> Bool
< Float16Value Half
y = Half
x Half -> Half -> Bool
forall a. Ord a => a -> a -> Bool
< Half
y
Float32Value Float
x < Float32Value Float
y = Float
x Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
< Float
y
Float64Value Double
x < Float64Value Double
y = Double
x Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
y
Float16Value Half
_ < Float32Value Float
_ = Bool
True
Float16Value Half
_ < Float64Value Double
_ = Bool
True
Float32Value Float
_ < Float16Value Half
_ = Bool
False
Float32Value Float
_ < Float64Value Double
_ = Bool
True
Float64Value Double
_ < Float16Value Half
_ = Bool
False
Float64Value Double
_ < Float32Value Float
_ = Bool
False
> :: FloatValue -> FloatValue -> Bool
(>) = (FloatValue -> FloatValue -> Bool)
-> FloatValue -> FloatValue -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip FloatValue -> FloatValue -> Bool
forall a. Ord a => a -> a -> Bool
(<)
>= :: FloatValue -> FloatValue -> Bool
(>=) = (FloatValue -> FloatValue -> Bool)
-> FloatValue -> FloatValue -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip FloatValue -> FloatValue -> Bool
forall a. Ord a => a -> a -> Bool
(<=)
instance Pretty FloatValue where
pretty :: forall ann. FloatValue -> Doc ann
pretty (Float16Value Half
v)
| Half -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Half
v, Half
v Half -> Half -> Bool
forall a. Ord a => a -> a -> Bool
>= Half
0 = Doc ann
"f16.inf"
| Half -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Half
v, Half
v Half -> Half -> Bool
forall a. Ord a => a -> a -> Bool
< Half
0 = Doc ann
"-f16.inf"
| Half -> Bool
forall a. RealFloat a => a -> Bool
isNaN Half
v = Doc ann
"f16.nan"
| Bool
otherwise = String -> Doc ann
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (String -> Doc ann) -> String -> Doc ann
forall a b. (a -> b) -> a -> b
$ Half -> String
forall a. Show a => a -> String
show Half
v String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"f16"
pretty (Float32Value Float
v)
| Float -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Float
v, Float
v Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
>= Float
0 = Doc ann
"f32.inf"
| Float -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Float
v, Float
v Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
< Float
0 = Doc ann
"-f32.inf"
| Float -> Bool
forall a. RealFloat a => a -> Bool
isNaN Float
v = Doc ann
"f32.nan"
| Bool
otherwise = String -> Doc ann
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (String -> Doc ann) -> String -> Doc ann
forall a b. (a -> b) -> a -> b
$ Float -> String
forall a. Show a => a -> String
show Float
v String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"f32"
pretty (Float64Value Double
v)
| Double -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Double
v, Double
v Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
>= Double
0 = Doc ann
"f64.inf"
| Double -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Double
v, Double
v Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
0 = Doc ann
"-f64.inf"
| Double -> Bool
forall a. RealFloat a => a -> Bool
isNaN Double
v = Doc ann
"f64.nan"
| Bool
otherwise = String -> Doc ann
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (String -> Doc ann) -> String -> Doc ann
forall a b. (a -> b) -> a -> b
$ Double -> String
forall a. Show a => a -> String
show Double
v String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"f64"
floatValue :: Real num => FloatType -> num -> FloatValue
floatValue :: forall num. Real num => FloatType -> num -> FloatValue
floatValue FloatType
Float16 = Half -> FloatValue
Float16Value (Half -> FloatValue) -> (num -> Half) -> num -> FloatValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Rational -> Half
forall a. Fractional a => Rational -> a
fromRational (Rational -> Half) -> (num -> Rational) -> num -> Half
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. num -> Rational
forall a. Real a => a -> Rational
toRational
floatValue FloatType
Float32 = Float -> FloatValue
Float32Value (Float -> FloatValue) -> (num -> Float) -> num -> FloatValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Rational -> Float
forall a. Fractional a => Rational -> a
fromRational (Rational -> Float) -> (num -> Rational) -> num -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. num -> Rational
forall a. Real a => a -> Rational
toRational
floatValue FloatType
Float64 = Double -> FloatValue
Float64Value (Double -> FloatValue) -> (num -> Double) -> num -> FloatValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Rational -> Double
forall a. Fractional a => Rational -> a
fromRational (Rational -> Double) -> (num -> Rational) -> num -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. num -> Rational
forall a. Real a => a -> Rational
toRational
floatValueType :: FloatValue -> FloatType
floatValueType :: FloatValue -> FloatType
floatValueType Float16Value {} = FloatType
Float16
floatValueType Float32Value {} = FloatType
Float32
floatValueType Float64Value {} = FloatType
Float64
data PrimValue
= IntValue !IntValue
| FloatValue !FloatValue
| BoolValue !Bool
|
UnitValue
deriving (PrimValue -> PrimValue -> Bool
(PrimValue -> PrimValue -> Bool)
-> (PrimValue -> PrimValue -> Bool) -> Eq PrimValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PrimValue -> PrimValue -> Bool
== :: PrimValue -> PrimValue -> Bool
$c/= :: PrimValue -> PrimValue -> Bool
/= :: PrimValue -> PrimValue -> Bool
Eq, Eq PrimValue
Eq PrimValue
-> (PrimValue -> PrimValue -> Ordering)
-> (PrimValue -> PrimValue -> Bool)
-> (PrimValue -> PrimValue -> Bool)
-> (PrimValue -> PrimValue -> Bool)
-> (PrimValue -> PrimValue -> Bool)
-> (PrimValue -> PrimValue -> PrimValue)
-> (PrimValue -> PrimValue -> PrimValue)
-> Ord PrimValue
PrimValue -> PrimValue -> Bool
PrimValue -> PrimValue -> Ordering
PrimValue -> PrimValue -> PrimValue
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: PrimValue -> PrimValue -> Ordering
compare :: PrimValue -> PrimValue -> Ordering
$c< :: PrimValue -> PrimValue -> Bool
< :: PrimValue -> PrimValue -> Bool
$c<= :: PrimValue -> PrimValue -> Bool
<= :: PrimValue -> PrimValue -> Bool
$c> :: PrimValue -> PrimValue -> Bool
> :: PrimValue -> PrimValue -> Bool
$c>= :: PrimValue -> PrimValue -> Bool
>= :: PrimValue -> PrimValue -> Bool
$cmax :: PrimValue -> PrimValue -> PrimValue
max :: PrimValue -> PrimValue -> PrimValue
$cmin :: PrimValue -> PrimValue -> PrimValue
min :: PrimValue -> PrimValue -> PrimValue
Ord, Int -> PrimValue -> ShowS
[PrimValue] -> ShowS
PrimValue -> String
(Int -> PrimValue -> ShowS)
-> (PrimValue -> String)
-> ([PrimValue] -> ShowS)
-> Show PrimValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PrimValue -> ShowS
showsPrec :: Int -> PrimValue -> ShowS
$cshow :: PrimValue -> String
show :: PrimValue -> String
$cshowList :: [PrimValue] -> ShowS
showList :: [PrimValue] -> ShowS
Show)
instance Pretty PrimValue where
pretty :: forall ann. PrimValue -> Doc ann
pretty (IntValue IntValue
v) = IntValue -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. IntValue -> Doc ann
pretty IntValue
v
pretty (BoolValue Bool
True) = Doc ann
"true"
pretty (BoolValue Bool
False) = Doc ann
"false"
pretty (FloatValue FloatValue
v) = FloatValue -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. FloatValue -> Doc ann
pretty FloatValue
v
pretty PrimValue
UnitValue = Doc ann
"()"
primValueType :: PrimValue -> PrimType
primValueType :: PrimValue -> PrimType
primValueType (IntValue IntValue
v) = IntType -> PrimType
IntType (IntType -> PrimType) -> IntType -> PrimType
forall a b. (a -> b) -> a -> b
$ IntValue -> IntType
intValueType IntValue
v
primValueType (FloatValue FloatValue
v) = FloatType -> PrimType
FloatType (FloatType -> PrimType) -> FloatType -> PrimType
forall a b. (a -> b) -> a -> b
$ FloatValue -> FloatType
floatValueType FloatValue
v
primValueType BoolValue {} = PrimType
Bool
primValueType PrimValue
UnitValue = PrimType
Unit
blankPrimValue :: PrimType -> PrimValue
blankPrimValue :: PrimType -> PrimValue
blankPrimValue (IntType IntType
Int8) = IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Int8 -> IntValue
Int8Value Int8
0
blankPrimValue (IntType IntType
Int16) = IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Int16 -> IntValue
Int16Value Int16
0
blankPrimValue (IntType IntType
Int32) = IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Int32 -> IntValue
Int32Value Int32
0
blankPrimValue (IntType IntType
Int64) = IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Int64 -> IntValue
Int64Value Int64
0
blankPrimValue (FloatType FloatType
Float16) = FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Half -> FloatValue
Float16Value Half
0.0
blankPrimValue (FloatType FloatType
Float32) = FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Float -> FloatValue
Float32Value Float
0.0
blankPrimValue (FloatType FloatType
Float64) = FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Double -> FloatValue
Float64Value Double
0.0
blankPrimValue PrimType
Bool = Bool -> PrimValue
BoolValue Bool
False
blankPrimValue PrimType
Unit = PrimValue
UnitValue
onePrimValue :: PrimType -> PrimValue
onePrimValue :: PrimType -> PrimValue
onePrimValue (IntType IntType
Int8) = IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Int8 -> IntValue
Int8Value Int8
1
onePrimValue (IntType IntType
Int16) = IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Int16 -> IntValue
Int16Value Int16
1
onePrimValue (IntType IntType
Int32) = IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Int32 -> IntValue
Int32Value Int32
1
onePrimValue (IntType IntType
Int64) = IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Int64 -> IntValue
Int64Value Int64
1
onePrimValue (FloatType FloatType
Float16) = FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Half -> FloatValue
Float16Value Half
1.0
onePrimValue (FloatType FloatType
Float32) = FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Float -> FloatValue
Float32Value Float
1.0
onePrimValue (FloatType FloatType
Float64) = FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Double -> FloatValue
Float64Value Double
1.0
onePrimValue PrimType
Bool = Bool -> PrimValue
BoolValue Bool
True
onePrimValue PrimType
Unit = PrimValue
UnitValue
data UnOp
=
Not
|
Complement IntType
|
Abs IntType
|
FAbs FloatType
|
SSignum IntType
|
USignum IntType
|
FSignum FloatType
deriving (UnOp -> UnOp -> Bool
(UnOp -> UnOp -> Bool) -> (UnOp -> UnOp -> Bool) -> Eq UnOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UnOp -> UnOp -> Bool
== :: UnOp -> UnOp -> Bool
$c/= :: UnOp -> UnOp -> Bool
/= :: UnOp -> UnOp -> Bool
Eq, Eq UnOp
Eq UnOp
-> (UnOp -> UnOp -> Ordering)
-> (UnOp -> UnOp -> Bool)
-> (UnOp -> UnOp -> Bool)
-> (UnOp -> UnOp -> Bool)
-> (UnOp -> UnOp -> Bool)
-> (UnOp -> UnOp -> UnOp)
-> (UnOp -> UnOp -> UnOp)
-> Ord UnOp
UnOp -> UnOp -> Bool
UnOp -> UnOp -> Ordering
UnOp -> UnOp -> UnOp
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: UnOp -> UnOp -> Ordering
compare :: UnOp -> UnOp -> Ordering
$c< :: UnOp -> UnOp -> Bool
< :: UnOp -> UnOp -> Bool
$c<= :: UnOp -> UnOp -> Bool
<= :: UnOp -> UnOp -> Bool
$c> :: UnOp -> UnOp -> Bool
> :: UnOp -> UnOp -> Bool
$c>= :: UnOp -> UnOp -> Bool
>= :: UnOp -> UnOp -> Bool
$cmax :: UnOp -> UnOp -> UnOp
max :: UnOp -> UnOp -> UnOp
$cmin :: UnOp -> UnOp -> UnOp
min :: UnOp -> UnOp -> UnOp
Ord, Int -> UnOp -> ShowS
[UnOp] -> ShowS
UnOp -> String
(Int -> UnOp -> ShowS)
-> (UnOp -> String) -> ([UnOp] -> ShowS) -> Show UnOp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UnOp -> ShowS
showsPrec :: Int -> UnOp -> ShowS
$cshow :: UnOp -> String
show :: UnOp -> String
$cshowList :: [UnOp] -> ShowS
showList :: [UnOp] -> ShowS
Show)
data Overflow = OverflowWrap | OverflowUndef
deriving (Int -> Overflow -> ShowS
[Overflow] -> ShowS
Overflow -> String
(Int -> Overflow -> ShowS)
-> (Overflow -> String) -> ([Overflow] -> ShowS) -> Show Overflow
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Overflow -> ShowS
showsPrec :: Int -> Overflow -> ShowS
$cshow :: Overflow -> String
show :: Overflow -> String
$cshowList :: [Overflow] -> ShowS
showList :: [Overflow] -> ShowS
Show)
instance Eq Overflow where
Overflow
_ == :: Overflow -> Overflow -> Bool
== Overflow
_ = Bool
True
instance Ord Overflow where
Overflow
_ compare :: Overflow -> Overflow -> Ordering
`compare` Overflow
_ = Ordering
EQ
data Safety = Unsafe | Safe deriving (Safety -> Safety -> Bool
(Safety -> Safety -> Bool)
-> (Safety -> Safety -> Bool) -> Eq Safety
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Safety -> Safety -> Bool
== :: Safety -> Safety -> Bool
$c/= :: Safety -> Safety -> Bool
/= :: Safety -> Safety -> Bool
Eq, Eq Safety
Eq Safety
-> (Safety -> Safety -> Ordering)
-> (Safety -> Safety -> Bool)
-> (Safety -> Safety -> Bool)
-> (Safety -> Safety -> Bool)
-> (Safety -> Safety -> Bool)
-> (Safety -> Safety -> Safety)
-> (Safety -> Safety -> Safety)
-> Ord Safety
Safety -> Safety -> Bool
Safety -> Safety -> Ordering
Safety -> Safety -> Safety
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Safety -> Safety -> Ordering
compare :: Safety -> Safety -> Ordering
$c< :: Safety -> Safety -> Bool
< :: Safety -> Safety -> Bool
$c<= :: Safety -> Safety -> Bool
<= :: Safety -> Safety -> Bool
$c> :: Safety -> Safety -> Bool
> :: Safety -> Safety -> Bool
$c>= :: Safety -> Safety -> Bool
>= :: Safety -> Safety -> Bool
$cmax :: Safety -> Safety -> Safety
max :: Safety -> Safety -> Safety
$cmin :: Safety -> Safety -> Safety
min :: Safety -> Safety -> Safety
Ord, Int -> Safety -> ShowS
[Safety] -> ShowS
Safety -> String
(Int -> Safety -> ShowS)
-> (Safety -> String) -> ([Safety] -> ShowS) -> Show Safety
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Safety -> ShowS
showsPrec :: Int -> Safety -> ShowS
$cshow :: Safety -> String
show :: Safety -> String
$cshowList :: [Safety] -> ShowS
showList :: [Safety] -> ShowS
Show)
data BinOp
=
Add IntType Overflow
|
FAdd FloatType
|
Sub IntType Overflow
|
FSub FloatType
|
Mul IntType Overflow
|
FMul FloatType
|
UDiv IntType Safety
|
UDivUp IntType Safety
|
SDiv IntType Safety
|
SDivUp IntType Safety
|
FDiv FloatType
|
FMod FloatType
|
UMod IntType Safety
|
SMod IntType Safety
|
SQuot IntType Safety
|
SRem IntType Safety
|
SMin IntType
|
UMin IntType
|
FMin FloatType
|
SMax IntType
|
UMax IntType
|
FMax FloatType
|
Shl IntType
|
LShr IntType
|
AShr IntType
|
And IntType
|
Or IntType
|
Xor IntType
|
Pow IntType
|
FPow FloatType
|
LogAnd
|
LogOr
deriving (BinOp -> BinOp -> Bool
(BinOp -> BinOp -> Bool) -> (BinOp -> BinOp -> Bool) -> Eq BinOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BinOp -> BinOp -> Bool
== :: BinOp -> BinOp -> Bool
$c/= :: BinOp -> BinOp -> Bool
/= :: BinOp -> BinOp -> Bool
Eq, Eq BinOp
Eq BinOp
-> (BinOp -> BinOp -> Ordering)
-> (BinOp -> BinOp -> Bool)
-> (BinOp -> BinOp -> Bool)
-> (BinOp -> BinOp -> Bool)
-> (BinOp -> BinOp -> Bool)
-> (BinOp -> BinOp -> BinOp)
-> (BinOp -> BinOp -> BinOp)
-> Ord BinOp
BinOp -> BinOp -> Bool
BinOp -> BinOp -> Ordering
BinOp -> BinOp -> BinOp
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: BinOp -> BinOp -> Ordering
compare :: BinOp -> BinOp -> Ordering
$c< :: BinOp -> BinOp -> Bool
< :: BinOp -> BinOp -> Bool
$c<= :: BinOp -> BinOp -> Bool
<= :: BinOp -> BinOp -> Bool
$c> :: BinOp -> BinOp -> Bool
> :: BinOp -> BinOp -> Bool
$c>= :: BinOp -> BinOp -> Bool
>= :: BinOp -> BinOp -> Bool
$cmax :: BinOp -> BinOp -> BinOp
max :: BinOp -> BinOp -> BinOp
$cmin :: BinOp -> BinOp -> BinOp
min :: BinOp -> BinOp -> BinOp
Ord, Int -> BinOp -> ShowS
[BinOp] -> ShowS
BinOp -> String
(Int -> BinOp -> ShowS)
-> (BinOp -> String) -> ([BinOp] -> ShowS) -> Show BinOp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BinOp -> ShowS
showsPrec :: Int -> BinOp -> ShowS
$cshow :: BinOp -> String
show :: BinOp -> String
$cshowList :: [BinOp] -> ShowS
showList :: [BinOp] -> ShowS
Show)
data CmpOp
=
CmpEq PrimType
|
CmpUlt IntType
|
CmpUle IntType
|
CmpSlt IntType
|
CmpSle IntType
|
FCmpLt FloatType
|
FCmpLe FloatType
|
CmpLlt
|
CmpLle
deriving (CmpOp -> CmpOp -> Bool
(CmpOp -> CmpOp -> Bool) -> (CmpOp -> CmpOp -> Bool) -> Eq CmpOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CmpOp -> CmpOp -> Bool
== :: CmpOp -> CmpOp -> Bool
$c/= :: CmpOp -> CmpOp -> Bool
/= :: CmpOp -> CmpOp -> Bool
Eq, Eq CmpOp
Eq CmpOp
-> (CmpOp -> CmpOp -> Ordering)
-> (CmpOp -> CmpOp -> Bool)
-> (CmpOp -> CmpOp -> Bool)
-> (CmpOp -> CmpOp -> Bool)
-> (CmpOp -> CmpOp -> Bool)
-> (CmpOp -> CmpOp -> CmpOp)
-> (CmpOp -> CmpOp -> CmpOp)
-> Ord CmpOp
CmpOp -> CmpOp -> Bool
CmpOp -> CmpOp -> Ordering
CmpOp -> CmpOp -> CmpOp
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: CmpOp -> CmpOp -> Ordering
compare :: CmpOp -> CmpOp -> Ordering
$c< :: CmpOp -> CmpOp -> Bool
< :: CmpOp -> CmpOp -> Bool
$c<= :: CmpOp -> CmpOp -> Bool
<= :: CmpOp -> CmpOp -> Bool
$c> :: CmpOp -> CmpOp -> Bool
> :: CmpOp -> CmpOp -> Bool
$c>= :: CmpOp -> CmpOp -> Bool
>= :: CmpOp -> CmpOp -> Bool
$cmax :: CmpOp -> CmpOp -> CmpOp
max :: CmpOp -> CmpOp -> CmpOp
$cmin :: CmpOp -> CmpOp -> CmpOp
min :: CmpOp -> CmpOp -> CmpOp
Ord, Int -> CmpOp -> ShowS
[CmpOp] -> ShowS
CmpOp -> String
(Int -> CmpOp -> ShowS)
-> (CmpOp -> String) -> ([CmpOp] -> ShowS) -> Show CmpOp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CmpOp -> ShowS
showsPrec :: Int -> CmpOp -> ShowS
$cshow :: CmpOp -> String
show :: CmpOp -> String
$cshowList :: [CmpOp] -> ShowS
showList :: [CmpOp] -> ShowS
Show)
data ConvOp
=
ZExt IntType IntType
|
SExt IntType IntType
|
FPConv FloatType FloatType
|
FPToUI FloatType IntType
|
FPToSI FloatType IntType
|
UIToFP IntType FloatType
|
SIToFP IntType FloatType
|
IToB IntType
|
BToI IntType
|
FToB FloatType
|
BToF FloatType
deriving (ConvOp -> ConvOp -> Bool
(ConvOp -> ConvOp -> Bool)
-> (ConvOp -> ConvOp -> Bool) -> Eq ConvOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConvOp -> ConvOp -> Bool
== :: ConvOp -> ConvOp -> Bool
$c/= :: ConvOp -> ConvOp -> Bool
/= :: ConvOp -> ConvOp -> Bool
Eq, Eq ConvOp
Eq ConvOp
-> (ConvOp -> ConvOp -> Ordering)
-> (ConvOp -> ConvOp -> Bool)
-> (ConvOp -> ConvOp -> Bool)
-> (ConvOp -> ConvOp -> Bool)
-> (ConvOp -> ConvOp -> Bool)
-> (ConvOp -> ConvOp -> ConvOp)
-> (ConvOp -> ConvOp -> ConvOp)
-> Ord ConvOp
ConvOp -> ConvOp -> Bool
ConvOp -> ConvOp -> Ordering
ConvOp -> ConvOp -> ConvOp
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ConvOp -> ConvOp -> Ordering
compare :: ConvOp -> ConvOp -> Ordering
$c< :: ConvOp -> ConvOp -> Bool
< :: ConvOp -> ConvOp -> Bool
$c<= :: ConvOp -> ConvOp -> Bool
<= :: ConvOp -> ConvOp -> Bool
$c> :: ConvOp -> ConvOp -> Bool
> :: ConvOp -> ConvOp -> Bool
$c>= :: ConvOp -> ConvOp -> Bool
>= :: ConvOp -> ConvOp -> Bool
$cmax :: ConvOp -> ConvOp -> ConvOp
max :: ConvOp -> ConvOp -> ConvOp
$cmin :: ConvOp -> ConvOp -> ConvOp
min :: ConvOp -> ConvOp -> ConvOp
Ord, Int -> ConvOp -> ShowS
[ConvOp] -> ShowS
ConvOp -> String
(Int -> ConvOp -> ShowS)
-> (ConvOp -> String) -> ([ConvOp] -> ShowS) -> Show ConvOp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConvOp -> ShowS
showsPrec :: Int -> ConvOp -> ShowS
$cshow :: ConvOp -> String
show :: ConvOp -> String
$cshowList :: [ConvOp] -> ShowS
showList :: [ConvOp] -> ShowS
Show)
allUnOps :: [UnOp]
allUnOps :: [UnOp]
allUnOps =
UnOp
Not
UnOp -> [UnOp] -> [UnOp]
forall a. a -> [a] -> [a]
: (IntType -> UnOp) -> [IntType] -> [UnOp]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> UnOp
Complement [IntType
forall a. Bounded a => a
minBound .. IntType
forall a. Bounded a => a
maxBound]
[UnOp] -> [UnOp] -> [UnOp]
forall a. [a] -> [a] -> [a]
++ (IntType -> UnOp) -> [IntType] -> [UnOp]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> UnOp
Abs [IntType
forall a. Bounded a => a
minBound .. IntType
forall a. Bounded a => a
maxBound]
[UnOp] -> [UnOp] -> [UnOp]
forall a. [a] -> [a] -> [a]
++ (FloatType -> UnOp) -> [FloatType] -> [UnOp]
forall a b. (a -> b) -> [a] -> [b]
map FloatType -> UnOp
FAbs [FloatType
forall a. Bounded a => a
minBound .. FloatType
forall a. Bounded a => a
maxBound]
[UnOp] -> [UnOp] -> [UnOp]
forall a. [a] -> [a] -> [a]
++ (IntType -> UnOp) -> [IntType] -> [UnOp]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> UnOp
SSignum [IntType
forall a. Bounded a => a
minBound .. IntType
forall a. Bounded a => a
maxBound]
[UnOp] -> [UnOp] -> [UnOp]
forall a. [a] -> [a] -> [a]
++ (IntType -> UnOp) -> [IntType] -> [UnOp]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> UnOp
USignum [IntType
forall a. Bounded a => a
minBound .. IntType
forall a. Bounded a => a
maxBound]
[UnOp] -> [UnOp] -> [UnOp]
forall a. [a] -> [a] -> [a]
++ (FloatType -> UnOp) -> [FloatType] -> [UnOp]
forall a b. (a -> b) -> [a] -> [b]
map FloatType -> UnOp
FSignum [FloatType
forall a. Bounded a => a
minBound .. FloatType
forall a. Bounded a => a
maxBound]
allBinOps :: [BinOp]
allBinOps :: [BinOp]
allBinOps =
[[BinOp]] -> [BinOp]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ IntType -> Overflow -> BinOp
Add (IntType -> Overflow -> BinOp) -> [IntType] -> [Overflow -> BinOp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IntType]
allIntTypes [Overflow -> BinOp] -> [Overflow] -> [BinOp]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [Overflow
OverflowWrap, Overflow
OverflowUndef],
(FloatType -> BinOp) -> [FloatType] -> [BinOp]
forall a b. (a -> b) -> [a] -> [b]
map FloatType -> BinOp
FAdd [FloatType]
allFloatTypes,
IntType -> Overflow -> BinOp
Sub (IntType -> Overflow -> BinOp) -> [IntType] -> [Overflow -> BinOp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IntType]
allIntTypes [Overflow -> BinOp] -> [Overflow] -> [BinOp]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [Overflow
OverflowWrap, Overflow
OverflowUndef],
(FloatType -> BinOp) -> [FloatType] -> [BinOp]
forall a b. (a -> b) -> [a] -> [b]
map FloatType -> BinOp
FSub [FloatType]
allFloatTypes,
IntType -> Overflow -> BinOp
Mul (IntType -> Overflow -> BinOp) -> [IntType] -> [Overflow -> BinOp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IntType]
allIntTypes [Overflow -> BinOp] -> [Overflow] -> [BinOp]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [Overflow
OverflowWrap, Overflow
OverflowUndef],
(FloatType -> BinOp) -> [FloatType] -> [BinOp]
forall a b. (a -> b) -> [a] -> [b]
map FloatType -> BinOp
FMul [FloatType]
allFloatTypes,
IntType -> Safety -> BinOp
UDiv (IntType -> Safety -> BinOp) -> [IntType] -> [Safety -> BinOp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IntType]
allIntTypes [Safety -> BinOp] -> [Safety] -> [BinOp]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [Safety
Unsafe, Safety
Safe],
IntType -> Safety -> BinOp
UDivUp (IntType -> Safety -> BinOp) -> [IntType] -> [Safety -> BinOp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IntType]
allIntTypes [Safety -> BinOp] -> [Safety] -> [BinOp]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [Safety
Unsafe, Safety
Safe],
IntType -> Safety -> BinOp
SDiv (IntType -> Safety -> BinOp) -> [IntType] -> [Safety -> BinOp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IntType]
allIntTypes [Safety -> BinOp] -> [Safety] -> [BinOp]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [Safety
Unsafe, Safety
Safe],
IntType -> Safety -> BinOp
SDivUp (IntType -> Safety -> BinOp) -> [IntType] -> [Safety -> BinOp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IntType]
allIntTypes [Safety -> BinOp] -> [Safety] -> [BinOp]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [Safety
Unsafe, Safety
Safe],
(FloatType -> BinOp) -> [FloatType] -> [BinOp]
forall a b. (a -> b) -> [a] -> [b]
map FloatType -> BinOp
FDiv [FloatType]
allFloatTypes,
(FloatType -> BinOp) -> [FloatType] -> [BinOp]
forall a b. (a -> b) -> [a] -> [b]
map FloatType -> BinOp
FMod [FloatType]
allFloatTypes,
IntType -> Safety -> BinOp
UMod (IntType -> Safety -> BinOp) -> [IntType] -> [Safety -> BinOp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IntType]
allIntTypes [Safety -> BinOp] -> [Safety] -> [BinOp]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [Safety
Unsafe, Safety
Safe],
IntType -> Safety -> BinOp
SMod (IntType -> Safety -> BinOp) -> [IntType] -> [Safety -> BinOp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IntType]
allIntTypes [Safety -> BinOp] -> [Safety] -> [BinOp]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [Safety
Unsafe, Safety
Safe],
IntType -> Safety -> BinOp
SQuot (IntType -> Safety -> BinOp) -> [IntType] -> [Safety -> BinOp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IntType]
allIntTypes [Safety -> BinOp] -> [Safety] -> [BinOp]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [Safety
Unsafe, Safety
Safe],
IntType -> Safety -> BinOp
SRem (IntType -> Safety -> BinOp) -> [IntType] -> [Safety -> BinOp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IntType]
allIntTypes [Safety -> BinOp] -> [Safety] -> [BinOp]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [Safety
Unsafe, Safety
Safe],
(IntType -> BinOp) -> [IntType] -> [BinOp]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> BinOp
SMin [IntType]
allIntTypes,
(IntType -> BinOp) -> [IntType] -> [BinOp]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> BinOp
UMin [IntType]
allIntTypes,
(FloatType -> BinOp) -> [FloatType] -> [BinOp]
forall a b. (a -> b) -> [a] -> [b]
map FloatType -> BinOp
FMin [FloatType]
allFloatTypes,
(IntType -> BinOp) -> [IntType] -> [BinOp]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> BinOp
SMax [IntType]
allIntTypes,
(IntType -> BinOp) -> [IntType] -> [BinOp]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> BinOp
UMax [IntType]
allIntTypes,
(FloatType -> BinOp) -> [FloatType] -> [BinOp]
forall a b. (a -> b) -> [a] -> [b]
map FloatType -> BinOp
FMax [FloatType]
allFloatTypes,
(IntType -> BinOp) -> [IntType] -> [BinOp]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> BinOp
Shl [IntType]
allIntTypes,
(IntType -> BinOp) -> [IntType] -> [BinOp]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> BinOp
LShr [IntType]
allIntTypes,
(IntType -> BinOp) -> [IntType] -> [BinOp]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> BinOp
AShr [IntType]
allIntTypes,
(IntType -> BinOp) -> [IntType] -> [BinOp]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> BinOp
And [IntType]
allIntTypes,
(IntType -> BinOp) -> [IntType] -> [BinOp]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> BinOp
Or [IntType]
allIntTypes,
(IntType -> BinOp) -> [IntType] -> [BinOp]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> BinOp
Xor [IntType]
allIntTypes,
(IntType -> BinOp) -> [IntType] -> [BinOp]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> BinOp
Pow [IntType]
allIntTypes,
(FloatType -> BinOp) -> [FloatType] -> [BinOp]
forall a b. (a -> b) -> [a] -> [b]
map FloatType -> BinOp
FPow [FloatType]
allFloatTypes,
[BinOp
LogAnd, BinOp
LogOr]
]
allCmpOps :: [CmpOp]
allCmpOps :: [CmpOp]
allCmpOps =
[[CmpOp]] -> [CmpOp]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ (PrimType -> CmpOp) -> [PrimType] -> [CmpOp]
forall a b. (a -> b) -> [a] -> [b]
map PrimType -> CmpOp
CmpEq [PrimType]
allPrimTypes,
(IntType -> CmpOp) -> [IntType] -> [CmpOp]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> CmpOp
CmpUlt [IntType]
allIntTypes,
(IntType -> CmpOp) -> [IntType] -> [CmpOp]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> CmpOp
CmpUle [IntType]
allIntTypes,
(IntType -> CmpOp) -> [IntType] -> [CmpOp]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> CmpOp
CmpSlt [IntType]
allIntTypes,
(IntType -> CmpOp) -> [IntType] -> [CmpOp]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> CmpOp
CmpSle [IntType]
allIntTypes,
(FloatType -> CmpOp) -> [FloatType] -> [CmpOp]
forall a b. (a -> b) -> [a] -> [b]
map FloatType -> CmpOp
FCmpLt [FloatType]
allFloatTypes,
(FloatType -> CmpOp) -> [FloatType] -> [CmpOp]
forall a b. (a -> b) -> [a] -> [b]
map FloatType -> CmpOp
FCmpLe [FloatType]
allFloatTypes,
[CmpOp
CmpLlt, CmpOp
CmpLle]
]
allConvOps :: [ConvOp]
allConvOps :: [ConvOp]
allConvOps =
[[ConvOp]] -> [ConvOp]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ IntType -> IntType -> ConvOp
ZExt (IntType -> IntType -> ConvOp) -> [IntType] -> [IntType -> ConvOp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IntType]
allIntTypes [IntType -> ConvOp] -> [IntType] -> [ConvOp]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [IntType]
allIntTypes,
IntType -> IntType -> ConvOp
SExt (IntType -> IntType -> ConvOp) -> [IntType] -> [IntType -> ConvOp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IntType]
allIntTypes [IntType -> ConvOp] -> [IntType] -> [ConvOp]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [IntType]
allIntTypes,
FloatType -> FloatType -> ConvOp
FPConv (FloatType -> FloatType -> ConvOp)
-> [FloatType] -> [FloatType -> ConvOp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [FloatType]
allFloatTypes [FloatType -> ConvOp] -> [FloatType] -> [ConvOp]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [FloatType]
allFloatTypes,
FloatType -> IntType -> ConvOp
FPToUI (FloatType -> IntType -> ConvOp)
-> [FloatType] -> [IntType -> ConvOp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [FloatType]
allFloatTypes [IntType -> ConvOp] -> [IntType] -> [ConvOp]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [IntType]
allIntTypes,
FloatType -> IntType -> ConvOp
FPToSI (FloatType -> IntType -> ConvOp)
-> [FloatType] -> [IntType -> ConvOp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [FloatType]
allFloatTypes [IntType -> ConvOp] -> [IntType] -> [ConvOp]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [IntType]
allIntTypes,
IntType -> FloatType -> ConvOp
UIToFP (IntType -> FloatType -> ConvOp)
-> [IntType] -> [FloatType -> ConvOp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IntType]
allIntTypes [FloatType -> ConvOp] -> [FloatType] -> [ConvOp]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [FloatType]
allFloatTypes,
IntType -> FloatType -> ConvOp
SIToFP (IntType -> FloatType -> ConvOp)
-> [IntType] -> [FloatType -> ConvOp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IntType]
allIntTypes [FloatType -> ConvOp] -> [FloatType] -> [ConvOp]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [FloatType]
allFloatTypes,
IntType -> ConvOp
IToB (IntType -> ConvOp) -> [IntType] -> [ConvOp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IntType]
allIntTypes,
IntType -> ConvOp
BToI (IntType -> ConvOp) -> [IntType] -> [ConvOp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IntType]
allIntTypes,
FloatType -> ConvOp
FToB (FloatType -> ConvOp) -> [FloatType] -> [ConvOp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [FloatType]
allFloatTypes,
FloatType -> ConvOp
BToF (FloatType -> ConvOp) -> [FloatType] -> [ConvOp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [FloatType]
allFloatTypes
]
doUnOp :: UnOp -> PrimValue -> Maybe PrimValue
doUnOp :: UnOp -> PrimValue -> Maybe PrimValue
doUnOp UnOp
Not (BoolValue Bool
b) = PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ Bool -> PrimValue
BoolValue (Bool -> PrimValue) -> Bool -> PrimValue
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not Bool
b
doUnOp Complement {} (IntValue IntValue
v) = PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> IntValue
doComplement IntValue
v
doUnOp Abs {} (IntValue IntValue
v) = PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> IntValue
doAbs IntValue
v
doUnOp FAbs {} (FloatValue FloatValue
v) = PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> FloatValue
doFAbs FloatValue
v
doUnOp SSignum {} (IntValue IntValue
v) = PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> IntValue
doSSignum IntValue
v
doUnOp USignum {} (IntValue IntValue
v) = PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> IntValue
doUSignum IntValue
v
doUnOp FSignum {} (FloatValue FloatValue
v) = PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> FloatValue
doFSignum FloatValue
v
doUnOp UnOp
_ PrimValue
_ = Maybe PrimValue
forall a. Maybe a
Nothing
doComplement :: IntValue -> IntValue
doComplement :: IntValue -> IntValue
doComplement IntValue
v = IntType -> Int64 -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue (IntValue -> IntType
intValueType IntValue
v) (Int64 -> IntValue) -> Int64 -> IntValue
forall a b. (a -> b) -> a -> b
$ Int64 -> Int64
forall a. Bits a => a -> a
complement (Int64 -> Int64) -> Int64 -> Int64
forall a b. (a -> b) -> a -> b
$ IntValue -> Int64
intToInt64 IntValue
v
doAbs :: IntValue -> IntValue
doAbs :: IntValue -> IntValue
doAbs IntValue
v = IntType -> Int64 -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue (IntValue -> IntType
intValueType IntValue
v) (Int64 -> IntValue) -> Int64 -> IntValue
forall a b. (a -> b) -> a -> b
$ Int64 -> Int64
forall a. Num a => a -> a
abs (Int64 -> Int64) -> Int64 -> Int64
forall a b. (a -> b) -> a -> b
$ IntValue -> Int64
intToInt64 IntValue
v
doFAbs :: FloatValue -> FloatValue
doFAbs :: FloatValue -> FloatValue
doFAbs (Float16Value Half
x) = Half -> FloatValue
Float16Value (Half -> FloatValue) -> Half -> FloatValue
forall a b. (a -> b) -> a -> b
$ Half -> Half
forall a. Num a => a -> a
abs Half
x
doFAbs (Float32Value Float
x) = Float -> FloatValue
Float32Value (Float -> FloatValue) -> Float -> FloatValue
forall a b. (a -> b) -> a -> b
$ Float -> Float
forall a. Num a => a -> a
abs Float
x
doFAbs (Float64Value Double
x) = Double -> FloatValue
Float64Value (Double -> FloatValue) -> Double -> FloatValue
forall a b. (a -> b) -> a -> b
$ Double -> Double
forall a. Num a => a -> a
abs Double
x
doSSignum :: IntValue -> IntValue
doSSignum :: IntValue -> IntValue
doSSignum IntValue
v = IntType -> Int64 -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue (IntValue -> IntType
intValueType IntValue
v) (Int64 -> IntValue) -> Int64 -> IntValue
forall a b. (a -> b) -> a -> b
$ Int64 -> Int64
forall a. Num a => a -> a
signum (Int64 -> Int64) -> Int64 -> Int64
forall a b. (a -> b) -> a -> b
$ IntValue -> Int64
intToInt64 IntValue
v
doUSignum :: IntValue -> IntValue
doUSignum :: IntValue -> IntValue
doUSignum IntValue
v = IntType -> Word64 -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue (IntValue -> IntType
intValueType IntValue
v) (Word64 -> IntValue) -> Word64 -> IntValue
forall a b. (a -> b) -> a -> b
$ Word64 -> Word64
forall a. Num a => a -> a
signum (Word64 -> Word64) -> Word64 -> Word64
forall a b. (a -> b) -> a -> b
$ IntValue -> Word64
intToWord64 IntValue
v
doFSignum :: FloatValue -> FloatValue
doFSignum :: FloatValue -> FloatValue
doFSignum (Float16Value Half
v) = Half -> FloatValue
Float16Value (Half -> FloatValue) -> Half -> FloatValue
forall a b. (a -> b) -> a -> b
$ Half -> Half
forall a. Num a => a -> a
signum Half
v
doFSignum (Float32Value Float
v) = Float -> FloatValue
Float32Value (Float -> FloatValue) -> Float -> FloatValue
forall a b. (a -> b) -> a -> b
$ Float -> Float
forall a. Num a => a -> a
signum Float
v
doFSignum (Float64Value Double
v) = Double -> FloatValue
Float64Value (Double -> FloatValue) -> Double -> FloatValue
forall a b. (a -> b) -> a -> b
$ Double -> Double
forall a. Num a => a -> a
signum Double
v
doBinOp :: BinOp -> PrimValue -> PrimValue -> Maybe PrimValue
doBinOp :: BinOp -> PrimValue -> PrimValue -> Maybe PrimValue
doBinOp Add {} = (IntValue -> IntValue -> IntValue)
-> PrimValue -> PrimValue -> Maybe PrimValue
doIntBinOp IntValue -> IntValue -> IntValue
doAdd
doBinOp FAdd {} = (Half -> Half -> Half)
-> (Float -> Float -> Float)
-> (Double -> Double -> Double)
-> PrimValue
-> PrimValue
-> Maybe PrimValue
doFloatBinOp Half -> Half -> Half
forall a. Num a => a -> a -> a
(+) Float -> Float -> Float
forall a. Num a => a -> a -> a
(+) Double -> Double -> Double
forall a. Num a => a -> a -> a
(+)
doBinOp Sub {} = (IntValue -> IntValue -> IntValue)
-> PrimValue -> PrimValue -> Maybe PrimValue
doIntBinOp IntValue -> IntValue -> IntValue
doSub
doBinOp FSub {} = (Half -> Half -> Half)
-> (Float -> Float -> Float)
-> (Double -> Double -> Double)
-> PrimValue
-> PrimValue
-> Maybe PrimValue
doFloatBinOp (-) (-) (-)
doBinOp Mul {} = (IntValue -> IntValue -> IntValue)
-> PrimValue -> PrimValue -> Maybe PrimValue
doIntBinOp IntValue -> IntValue -> IntValue
doMul
doBinOp FMul {} = (Half -> Half -> Half)
-> (Float -> Float -> Float)
-> (Double -> Double -> Double)
-> PrimValue
-> PrimValue
-> Maybe PrimValue
doFloatBinOp Half -> Half -> Half
forall a. Num a => a -> a -> a
(*) Float -> Float -> Float
forall a. Num a => a -> a -> a
(*) Double -> Double -> Double
forall a. Num a => a -> a -> a
(*)
doBinOp UDiv {} = (IntValue -> IntValue -> Maybe IntValue)
-> PrimValue -> PrimValue -> Maybe PrimValue
doRiskyIntBinOp IntValue -> IntValue -> Maybe IntValue
doUDiv
doBinOp UDivUp {} = (IntValue -> IntValue -> Maybe IntValue)
-> PrimValue -> PrimValue -> Maybe PrimValue
doRiskyIntBinOp IntValue -> IntValue -> Maybe IntValue
doUDivUp
doBinOp SDiv {} = (IntValue -> IntValue -> Maybe IntValue)
-> PrimValue -> PrimValue -> Maybe PrimValue
doRiskyIntBinOp IntValue -> IntValue -> Maybe IntValue
doSDiv
doBinOp SDivUp {} = (IntValue -> IntValue -> Maybe IntValue)
-> PrimValue -> PrimValue -> Maybe PrimValue
doRiskyIntBinOp IntValue -> IntValue -> Maybe IntValue
doSDivUp
doBinOp FDiv {} = (Half -> Half -> Half)
-> (Float -> Float -> Float)
-> (Double -> Double -> Double)
-> PrimValue
-> PrimValue
-> Maybe PrimValue
doFloatBinOp Half -> Half -> Half
forall a. Fractional a => a -> a -> a
(/) Float -> Float -> Float
forall a. Fractional a => a -> a -> a
(/) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
(/)
doBinOp FMod {} = (Half -> Half -> Half)
-> (Float -> Float -> Float)
-> (Double -> Double -> Double)
-> PrimValue
-> PrimValue
-> Maybe PrimValue
doFloatBinOp Half -> Half -> Half
forall a. Real a => a -> a -> a
mod' Float -> Float -> Float
forall a. Real a => a -> a -> a
mod' Double -> Double -> Double
forall a. Real a => a -> a -> a
mod'
doBinOp UMod {} = (IntValue -> IntValue -> Maybe IntValue)
-> PrimValue -> PrimValue -> Maybe PrimValue
doRiskyIntBinOp IntValue -> IntValue -> Maybe IntValue
doUMod
doBinOp SMod {} = (IntValue -> IntValue -> Maybe IntValue)
-> PrimValue -> PrimValue -> Maybe PrimValue
doRiskyIntBinOp IntValue -> IntValue -> Maybe IntValue
doSMod
doBinOp SQuot {} = (IntValue -> IntValue -> Maybe IntValue)
-> PrimValue -> PrimValue -> Maybe PrimValue
doRiskyIntBinOp IntValue -> IntValue -> Maybe IntValue
doSQuot
doBinOp SRem {} = (IntValue -> IntValue -> Maybe IntValue)
-> PrimValue -> PrimValue -> Maybe PrimValue
doRiskyIntBinOp IntValue -> IntValue -> Maybe IntValue
doSRem
doBinOp SMin {} = (IntValue -> IntValue -> IntValue)
-> PrimValue -> PrimValue -> Maybe PrimValue
doIntBinOp IntValue -> IntValue -> IntValue
doSMin
doBinOp UMin {} = (IntValue -> IntValue -> IntValue)
-> PrimValue -> PrimValue -> Maybe PrimValue
doIntBinOp IntValue -> IntValue -> IntValue
doUMin
doBinOp FMin {} = (Half -> Half -> Half)
-> (Float -> Float -> Float)
-> (Double -> Double -> Double)
-> PrimValue
-> PrimValue
-> Maybe PrimValue
doFloatBinOp Half -> Half -> Half
forall {a}. RealFloat a => a -> a -> a
fmin Float -> Float -> Float
forall {a}. RealFloat a => a -> a -> a
fmin Double -> Double -> Double
forall {a}. RealFloat a => a -> a -> a
fmin
where
fmin :: a -> a -> a
fmin a
x a
y
| a -> Bool
forall a. RealFloat a => a -> Bool
isNaN a
x = a
y
| a -> Bool
forall a. RealFloat a => a -> Bool
isNaN a
y = a
x
| Bool
otherwise = a -> a -> a
forall a. Ord a => a -> a -> a
min a
x a
y
doBinOp SMax {} = (IntValue -> IntValue -> IntValue)
-> PrimValue -> PrimValue -> Maybe PrimValue
doIntBinOp IntValue -> IntValue -> IntValue
doSMax
doBinOp UMax {} = (IntValue -> IntValue -> IntValue)
-> PrimValue -> PrimValue -> Maybe PrimValue
doIntBinOp IntValue -> IntValue -> IntValue
doUMax
doBinOp FMax {} = (Half -> Half -> Half)
-> (Float -> Float -> Float)
-> (Double -> Double -> Double)
-> PrimValue
-> PrimValue
-> Maybe PrimValue
doFloatBinOp Half -> Half -> Half
forall {a}. RealFloat a => a -> a -> a
fmax Float -> Float -> Float
forall {a}. RealFloat a => a -> a -> a
fmax Double -> Double -> Double
forall {a}. RealFloat a => a -> a -> a
fmax
where
fmax :: a -> a -> a
fmax a
x a
y
| a -> Bool
forall a. RealFloat a => a -> Bool
isNaN a
x = a
y
| a -> Bool
forall a. RealFloat a => a -> Bool
isNaN a
y = a
x
| Bool
otherwise = a -> a -> a
forall a. Ord a => a -> a -> a
max a
x a
y
doBinOp Shl {} = (IntValue -> IntValue -> IntValue)
-> PrimValue -> PrimValue -> Maybe PrimValue
doIntBinOp IntValue -> IntValue -> IntValue
doShl
doBinOp LShr {} = (IntValue -> IntValue -> IntValue)
-> PrimValue -> PrimValue -> Maybe PrimValue
doIntBinOp IntValue -> IntValue -> IntValue
doLShr
doBinOp AShr {} = (IntValue -> IntValue -> IntValue)
-> PrimValue -> PrimValue -> Maybe PrimValue
doIntBinOp IntValue -> IntValue -> IntValue
doAShr
doBinOp And {} = (IntValue -> IntValue -> IntValue)
-> PrimValue -> PrimValue -> Maybe PrimValue
doIntBinOp IntValue -> IntValue -> IntValue
doAnd
doBinOp Or {} = (IntValue -> IntValue -> IntValue)
-> PrimValue -> PrimValue -> Maybe PrimValue
doIntBinOp IntValue -> IntValue -> IntValue
doOr
doBinOp Xor {} = (IntValue -> IntValue -> IntValue)
-> PrimValue -> PrimValue -> Maybe PrimValue
doIntBinOp IntValue -> IntValue -> IntValue
doXor
doBinOp Pow {} = (IntValue -> IntValue -> Maybe IntValue)
-> PrimValue -> PrimValue -> Maybe PrimValue
doRiskyIntBinOp IntValue -> IntValue -> Maybe IntValue
doPow
doBinOp FPow {} = (Half -> Half -> Half)
-> (Float -> Float -> Float)
-> (Double -> Double -> Double)
-> PrimValue
-> PrimValue
-> Maybe PrimValue
doFloatBinOp Half -> Half -> Half
forall a. Floating a => a -> a -> a
(**) Float -> Float -> Float
forall a. Floating a => a -> a -> a
(**) Double -> Double -> Double
forall a. Floating a => a -> a -> a
(**)
doBinOp LogAnd {} = (Bool -> Bool -> Bool) -> PrimValue -> PrimValue -> Maybe PrimValue
doBoolBinOp Bool -> Bool -> Bool
(&&)
doBinOp LogOr {} = (Bool -> Bool -> Bool) -> PrimValue -> PrimValue -> Maybe PrimValue
doBoolBinOp Bool -> Bool -> Bool
(||)
doIntBinOp ::
(IntValue -> IntValue -> IntValue) ->
PrimValue ->
PrimValue ->
Maybe PrimValue
doIntBinOp :: (IntValue -> IntValue -> IntValue)
-> PrimValue -> PrimValue -> Maybe PrimValue
doIntBinOp IntValue -> IntValue -> IntValue
f (IntValue IntValue
v1) (IntValue IntValue
v2) =
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> IntValue -> IntValue
f IntValue
v1 IntValue
v2
doIntBinOp IntValue -> IntValue -> IntValue
_ PrimValue
_ PrimValue
_ = Maybe PrimValue
forall a. Maybe a
Nothing
doRiskyIntBinOp ::
(IntValue -> IntValue -> Maybe IntValue) ->
PrimValue ->
PrimValue ->
Maybe PrimValue
doRiskyIntBinOp :: (IntValue -> IntValue -> Maybe IntValue)
-> PrimValue -> PrimValue -> Maybe PrimValue
doRiskyIntBinOp IntValue -> IntValue -> Maybe IntValue
f (IntValue IntValue
v1) (IntValue IntValue
v2) =
IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> Maybe IntValue -> Maybe PrimValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IntValue -> IntValue -> Maybe IntValue
f IntValue
v1 IntValue
v2
doRiskyIntBinOp IntValue -> IntValue -> Maybe IntValue
_ PrimValue
_ PrimValue
_ = Maybe PrimValue
forall a. Maybe a
Nothing
doFloatBinOp ::
(Half -> Half -> Half) ->
(Float -> Float -> Float) ->
(Double -> Double -> Double) ->
PrimValue ->
PrimValue ->
Maybe PrimValue
doFloatBinOp :: (Half -> Half -> Half)
-> (Float -> Float -> Float)
-> (Double -> Double -> Double)
-> PrimValue
-> PrimValue
-> Maybe PrimValue
doFloatBinOp Half -> Half -> Half
f16 Float -> Float -> Float
_ Double -> Double -> Double
_ (FloatValue (Float16Value Half
v1)) (FloatValue (Float16Value Half
v2)) =
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Half -> FloatValue
Float16Value (Half -> FloatValue) -> Half -> FloatValue
forall a b. (a -> b) -> a -> b
$ Half -> Half -> Half
f16 Half
v1 Half
v2
doFloatBinOp Half -> Half -> Half
_ Float -> Float -> Float
f32 Double -> Double -> Double
_ (FloatValue (Float32Value Float
v1)) (FloatValue (Float32Value Float
v2)) =
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Float -> FloatValue
Float32Value (Float -> FloatValue) -> Float -> FloatValue
forall a b. (a -> b) -> a -> b
$ Float -> Float -> Float
f32 Float
v1 Float
v2
doFloatBinOp Half -> Half -> Half
_ Float -> Float -> Float
_ Double -> Double -> Double
f64 (FloatValue (Float64Value Double
v1)) (FloatValue (Float64Value Double
v2)) =
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Double -> FloatValue
Float64Value (Double -> FloatValue) -> Double -> FloatValue
forall a b. (a -> b) -> a -> b
$ Double -> Double -> Double
f64 Double
v1 Double
v2
doFloatBinOp Half -> Half -> Half
_ Float -> Float -> Float
_ Double -> Double -> Double
_ PrimValue
_ PrimValue
_ = Maybe PrimValue
forall a. Maybe a
Nothing
doBoolBinOp ::
(Bool -> Bool -> Bool) ->
PrimValue ->
PrimValue ->
Maybe PrimValue
doBoolBinOp :: (Bool -> Bool -> Bool) -> PrimValue -> PrimValue -> Maybe PrimValue
doBoolBinOp Bool -> Bool -> Bool
f (BoolValue Bool
v1) (BoolValue Bool
v2) =
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ Bool -> PrimValue
BoolValue (Bool -> PrimValue) -> Bool -> PrimValue
forall a b. (a -> b) -> a -> b
$ Bool -> Bool -> Bool
f Bool
v1 Bool
v2
doBoolBinOp Bool -> Bool -> Bool
_ PrimValue
_ PrimValue
_ = Maybe PrimValue
forall a. Maybe a
Nothing
doAdd :: IntValue -> IntValue -> IntValue
doAdd :: IntValue -> IntValue -> IntValue
doAdd IntValue
v1 IntValue
v2 = IntType -> Int64 -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue (IntValue -> IntType
intValueType IntValue
v1) (Int64 -> IntValue) -> Int64 -> IntValue
forall a b. (a -> b) -> a -> b
$ IntValue -> Int64
intToInt64 IntValue
v1 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ IntValue -> Int64
intToInt64 IntValue
v2
doSub :: IntValue -> IntValue -> IntValue
doSub :: IntValue -> IntValue -> IntValue
doSub IntValue
v1 IntValue
v2 = IntType -> Int64 -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue (IntValue -> IntType
intValueType IntValue
v1) (Int64 -> IntValue) -> Int64 -> IntValue
forall a b. (a -> b) -> a -> b
$ IntValue -> Int64
intToInt64 IntValue
v1 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- IntValue -> Int64
intToInt64 IntValue
v2
doMul :: IntValue -> IntValue -> IntValue
doMul :: IntValue -> IntValue -> IntValue
doMul IntValue
v1 IntValue
v2 = IntType -> Int64 -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue (IntValue -> IntType
intValueType IntValue
v1) (Int64 -> IntValue) -> Int64 -> IntValue
forall a b. (a -> b) -> a -> b
$ IntValue -> Int64
intToInt64 IntValue
v1 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* IntValue -> Int64
intToInt64 IntValue
v2
doUDiv :: IntValue -> IntValue -> Maybe IntValue
doUDiv :: IntValue -> IntValue -> Maybe IntValue
doUDiv IntValue
v1 IntValue
v2
| IntValue -> Bool
zeroIshInt IntValue
v2 = Maybe IntValue
forall a. Maybe a
Nothing
| Bool
otherwise =
IntValue -> Maybe IntValue
forall a. a -> Maybe a
Just (IntValue -> Maybe IntValue)
-> (Word64 -> IntValue) -> Word64 -> Maybe IntValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. IntType -> Word64 -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue (IntValue -> IntType
intValueType IntValue
v1) (Word64 -> Maybe IntValue) -> Word64 -> Maybe IntValue
forall a b. (a -> b) -> a -> b
$
IntValue -> Word64
intToWord64 IntValue
v1 Word64 -> Word64 -> Word64
forall a. Integral a => a -> a -> a
`div` IntValue -> Word64
intToWord64 IntValue
v2
doUDivUp :: IntValue -> IntValue -> Maybe IntValue
doUDivUp :: IntValue -> IntValue -> Maybe IntValue
doUDivUp IntValue
v1 IntValue
v2
| IntValue -> Bool
zeroIshInt IntValue
v2 = Maybe IntValue
forall a. Maybe a
Nothing
| Bool
otherwise =
IntValue -> Maybe IntValue
forall a. a -> Maybe a
Just (IntValue -> Maybe IntValue)
-> (Word64 -> IntValue) -> Word64 -> Maybe IntValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. IntType -> Word64 -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue (IntValue -> IntType
intValueType IntValue
v1) (Word64 -> Maybe IntValue) -> Word64 -> Maybe IntValue
forall a b. (a -> b) -> a -> b
$
(IntValue -> Word64
intToWord64 IntValue
v1 Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ IntValue -> Word64
intToWord64 IntValue
v2 Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
- Word64
1) Word64 -> Word64 -> Word64
forall a. Integral a => a -> a -> a
`div` IntValue -> Word64
intToWord64 IntValue
v2
doSDiv :: IntValue -> IntValue -> Maybe IntValue
doSDiv :: IntValue -> IntValue -> Maybe IntValue
doSDiv IntValue
v1 IntValue
v2
| IntValue -> Bool
zeroIshInt IntValue
v2 = Maybe IntValue
forall a. Maybe a
Nothing
| Bool
otherwise =
IntValue -> Maybe IntValue
forall a. a -> Maybe a
Just (IntValue -> Maybe IntValue) -> IntValue -> Maybe IntValue
forall a b. (a -> b) -> a -> b
$
IntType -> Int64 -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue (IntValue -> IntType
intValueType IntValue
v1) (Int64 -> IntValue) -> Int64 -> IntValue
forall a b. (a -> b) -> a -> b
$
IntValue -> Int64
intToInt64 IntValue
v1 Int64 -> Int64 -> Int64
forall a. Integral a => a -> a -> a
`div` IntValue -> Int64
intToInt64 IntValue
v2
doSDivUp :: IntValue -> IntValue -> Maybe IntValue
doSDivUp :: IntValue -> IntValue -> Maybe IntValue
doSDivUp IntValue
v1 IntValue
v2
| IntValue -> Bool
zeroIshInt IntValue
v2 = Maybe IntValue
forall a. Maybe a
Nothing
| Bool
otherwise =
IntValue -> Maybe IntValue
forall a. a -> Maybe a
Just (IntValue -> Maybe IntValue)
-> (Int64 -> IntValue) -> Int64 -> Maybe IntValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. IntType -> Int64 -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue (IntValue -> IntType
intValueType IntValue
v1) (Int64 -> Maybe IntValue) -> Int64 -> Maybe IntValue
forall a b. (a -> b) -> a -> b
$
(IntValue -> Int64
intToInt64 IntValue
v1 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ IntValue -> Int64
intToInt64 IntValue
v2 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- Int64
1) Int64 -> Int64 -> Int64
forall a. Integral a => a -> a -> a
`div` IntValue -> Int64
intToInt64 IntValue
v2
doUMod :: IntValue -> IntValue -> Maybe IntValue
doUMod :: IntValue -> IntValue -> Maybe IntValue
doUMod IntValue
v1 IntValue
v2
| IntValue -> Bool
zeroIshInt IntValue
v2 = Maybe IntValue
forall a. Maybe a
Nothing
| Bool
otherwise = IntValue -> Maybe IntValue
forall a. a -> Maybe a
Just (IntValue -> Maybe IntValue) -> IntValue -> Maybe IntValue
forall a b. (a -> b) -> a -> b
$ IntType -> Word64 -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue (IntValue -> IntType
intValueType IntValue
v1) (Word64 -> IntValue) -> Word64 -> IntValue
forall a b. (a -> b) -> a -> b
$ IntValue -> Word64
intToWord64 IntValue
v1 Word64 -> Word64 -> Word64
forall a. Integral a => a -> a -> a
`mod` IntValue -> Word64
intToWord64 IntValue
v2
doSMod :: IntValue -> IntValue -> Maybe IntValue
doSMod :: IntValue -> IntValue -> Maybe IntValue
doSMod IntValue
v1 IntValue
v2
| IntValue -> Bool
zeroIshInt IntValue
v2 = Maybe IntValue
forall a. Maybe a
Nothing
| Bool
otherwise = IntValue -> Maybe IntValue
forall a. a -> Maybe a
Just (IntValue -> Maybe IntValue) -> IntValue -> Maybe IntValue
forall a b. (a -> b) -> a -> b
$ IntType -> Int64 -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue (IntValue -> IntType
intValueType IntValue
v1) (Int64 -> IntValue) -> Int64 -> IntValue
forall a b. (a -> b) -> a -> b
$ IntValue -> Int64
intToInt64 IntValue
v1 Int64 -> Int64 -> Int64
forall a. Integral a => a -> a -> a
`mod` IntValue -> Int64
intToInt64 IntValue
v2
doSQuot :: IntValue -> IntValue -> Maybe IntValue
doSQuot :: IntValue -> IntValue -> Maybe IntValue
doSQuot IntValue
v1 IntValue
v2
| IntValue -> Bool
zeroIshInt IntValue
v2 = Maybe IntValue
forall a. Maybe a
Nothing
| Bool
otherwise = IntValue -> Maybe IntValue
forall a. a -> Maybe a
Just (IntValue -> Maybe IntValue) -> IntValue -> Maybe IntValue
forall a b. (a -> b) -> a -> b
$ IntType -> Int64 -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue (IntValue -> IntType
intValueType IntValue
v1) (Int64 -> IntValue) -> Int64 -> IntValue
forall a b. (a -> b) -> a -> b
$ IntValue -> Int64
intToInt64 IntValue
v1 Int64 -> Int64 -> Int64
forall a. Integral a => a -> a -> a
`quot` IntValue -> Int64
intToInt64 IntValue
v2
doSRem :: IntValue -> IntValue -> Maybe IntValue
doSRem :: IntValue -> IntValue -> Maybe IntValue
doSRem IntValue
v1 IntValue
v2
| IntValue -> Bool
zeroIshInt IntValue
v2 = Maybe IntValue
forall a. Maybe a
Nothing
| Bool
otherwise = IntValue -> Maybe IntValue
forall a. a -> Maybe a
Just (IntValue -> Maybe IntValue) -> IntValue -> Maybe IntValue
forall a b. (a -> b) -> a -> b
$ IntType -> Int64 -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue (IntValue -> IntType
intValueType IntValue
v1) (Int64 -> IntValue) -> Int64 -> IntValue
forall a b. (a -> b) -> a -> b
$ IntValue -> Int64
intToInt64 IntValue
v1 Int64 -> Int64 -> Int64
forall a. Integral a => a -> a -> a
`rem` IntValue -> Int64
intToInt64 IntValue
v2
doSMin :: IntValue -> IntValue -> IntValue
doSMin :: IntValue -> IntValue -> IntValue
doSMin IntValue
v1 IntValue
v2 = IntType -> Int64 -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue (IntValue -> IntType
intValueType IntValue
v1) (Int64 -> IntValue) -> Int64 -> IntValue
forall a b. (a -> b) -> a -> b
$ IntValue -> Int64
intToInt64 IntValue
v1 Int64 -> Int64 -> Int64
forall a. Ord a => a -> a -> a
`min` IntValue -> Int64
intToInt64 IntValue
v2
doUMin :: IntValue -> IntValue -> IntValue
doUMin :: IntValue -> IntValue -> IntValue
doUMin IntValue
v1 IntValue
v2 = IntType -> Word64 -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue (IntValue -> IntType
intValueType IntValue
v1) (Word64 -> IntValue) -> Word64 -> IntValue
forall a b. (a -> b) -> a -> b
$ IntValue -> Word64
intToWord64 IntValue
v1 Word64 -> Word64 -> Word64
forall a. Ord a => a -> a -> a
`min` IntValue -> Word64
intToWord64 IntValue
v2
doSMax :: IntValue -> IntValue -> IntValue
doSMax :: IntValue -> IntValue -> IntValue
doSMax IntValue
v1 IntValue
v2 = IntType -> Int64 -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue (IntValue -> IntType
intValueType IntValue
v1) (Int64 -> IntValue) -> Int64 -> IntValue
forall a b. (a -> b) -> a -> b
$ IntValue -> Int64
intToInt64 IntValue
v1 Int64 -> Int64 -> Int64
forall a. Ord a => a -> a -> a
`max` IntValue -> Int64
intToInt64 IntValue
v2
doUMax :: IntValue -> IntValue -> IntValue
doUMax :: IntValue -> IntValue -> IntValue
doUMax IntValue
v1 IntValue
v2 = IntType -> Word64 -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue (IntValue -> IntType
intValueType IntValue
v1) (Word64 -> IntValue) -> Word64 -> IntValue
forall a b. (a -> b) -> a -> b
$ IntValue -> Word64
intToWord64 IntValue
v1 Word64 -> Word64 -> Word64
forall a. Ord a => a -> a -> a
`max` IntValue -> Word64
intToWord64 IntValue
v2
doShl :: IntValue -> IntValue -> IntValue
doShl :: IntValue -> IntValue -> IntValue
doShl IntValue
v1 IntValue
v2 = IntType -> Int64 -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue (IntValue -> IntType
intValueType IntValue
v1) (Int64 -> IntValue) -> Int64 -> IntValue
forall a b. (a -> b) -> a -> b
$ IntValue -> Int64
intToInt64 IntValue
v1 Int64 -> Int -> Int64
forall a. Bits a => a -> Int -> a
`shift` IntValue -> Int
intToInt IntValue
v2
doLShr :: IntValue -> IntValue -> IntValue
doLShr :: IntValue -> IntValue -> IntValue
doLShr IntValue
v1 IntValue
v2 = IntType -> Word64 -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue (IntValue -> IntType
intValueType IntValue
v1) (Word64 -> IntValue) -> Word64 -> IntValue
forall a b. (a -> b) -> a -> b
$ IntValue -> Word64
intToWord64 IntValue
v1 Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shift` Int -> Int
forall a. Num a => a -> a
negate (IntValue -> Int
intToInt IntValue
v2)
doAShr :: IntValue -> IntValue -> IntValue
doAShr :: IntValue -> IntValue -> IntValue
doAShr IntValue
v1 IntValue
v2 = IntType -> Int64 -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue (IntValue -> IntType
intValueType IntValue
v1) (Int64 -> IntValue) -> Int64 -> IntValue
forall a b. (a -> b) -> a -> b
$ IntValue -> Int64
intToInt64 IntValue
v1 Int64 -> Int -> Int64
forall a. Bits a => a -> Int -> a
`shift` Int -> Int
forall a. Num a => a -> a
negate (IntValue -> Int
intToInt IntValue
v2)
doAnd :: IntValue -> IntValue -> IntValue
doAnd :: IntValue -> IntValue -> IntValue
doAnd IntValue
v1 IntValue
v2 = IntType -> Word64 -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue (IntValue -> IntType
intValueType IntValue
v1) (Word64 -> IntValue) -> Word64 -> IntValue
forall a b. (a -> b) -> a -> b
$ IntValue -> Word64
intToWord64 IntValue
v1 Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.&. IntValue -> Word64
intToWord64 IntValue
v2
doOr :: IntValue -> IntValue -> IntValue
doOr :: IntValue -> IntValue -> IntValue
doOr IntValue
v1 IntValue
v2 = IntType -> Word64 -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue (IntValue -> IntType
intValueType IntValue
v1) (Word64 -> IntValue) -> Word64 -> IntValue
forall a b. (a -> b) -> a -> b
$ IntValue -> Word64
intToWord64 IntValue
v1 Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|. IntValue -> Word64
intToWord64 IntValue
v2
doXor :: IntValue -> IntValue -> IntValue
doXor :: IntValue -> IntValue -> IntValue
doXor IntValue
v1 IntValue
v2 = IntType -> Word64 -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue (IntValue -> IntType
intValueType IntValue
v1) (Word64 -> IntValue) -> Word64 -> IntValue
forall a b. (a -> b) -> a -> b
$ IntValue -> Word64
intToWord64 IntValue
v1 Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
`xor` IntValue -> Word64
intToWord64 IntValue
v2
doPow :: IntValue -> IntValue -> Maybe IntValue
doPow :: IntValue -> IntValue -> Maybe IntValue
doPow IntValue
v1 IntValue
v2
| IntValue -> Bool
negativeIshInt IntValue
v2 = Maybe IntValue
forall a. Maybe a
Nothing
| Bool
otherwise = IntValue -> Maybe IntValue
forall a. a -> Maybe a
Just (IntValue -> Maybe IntValue) -> IntValue -> Maybe IntValue
forall a b. (a -> b) -> a -> b
$ IntType -> Int64 -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue (IntValue -> IntType
intValueType IntValue
v1) (Int64 -> IntValue) -> Int64 -> IntValue
forall a b. (a -> b) -> a -> b
$ IntValue -> Int64
intToInt64 IntValue
v1 Int64 -> Int64 -> Int64
forall a b. (Num a, Integral b) => a -> b -> a
^ IntValue -> Int64
intToInt64 IntValue
v2
doConvOp :: ConvOp -> PrimValue -> Maybe PrimValue
doConvOp :: ConvOp -> PrimValue -> Maybe PrimValue
doConvOp (ZExt IntType
_ IntType
to) (IntValue IntValue
v) = PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> IntType -> IntValue
doZExt IntValue
v IntType
to
doConvOp (SExt IntType
_ IntType
to) (IntValue IntValue
v) = PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> IntType -> IntValue
doSExt IntValue
v IntType
to
doConvOp (FPConv FloatType
_ FloatType
to) (FloatValue FloatValue
v) = PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> FloatType -> FloatValue
doFPConv FloatValue
v FloatType
to
doConvOp (FPToUI FloatType
_ IntType
to) (FloatValue FloatValue
v) = PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> IntType -> IntValue
doFPToUI FloatValue
v IntType
to
doConvOp (FPToSI FloatType
_ IntType
to) (FloatValue FloatValue
v) = PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> IntType -> IntValue
doFPToSI FloatValue
v IntType
to
doConvOp (UIToFP IntType
_ FloatType
to) (IntValue IntValue
v) = PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> FloatType -> FloatValue
doUIToFP IntValue
v FloatType
to
doConvOp (SIToFP IntType
_ FloatType
to) (IntValue IntValue
v) = PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> FloatType -> FloatValue
doSIToFP IntValue
v FloatType
to
doConvOp (IToB IntType
_) (IntValue IntValue
v) = PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ Bool -> PrimValue
BoolValue (Bool -> PrimValue) -> Bool -> PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> Int64
intToInt64 IntValue
v Int64 -> Int64 -> Bool
forall a. Eq a => a -> a -> Bool
/= Int64
0
doConvOp (BToI IntType
to) (BoolValue Bool
v) = PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ IntType -> Int -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue IntType
to (Int -> IntValue) -> Int -> IntValue
forall a b. (a -> b) -> a -> b
$ if Bool
v then Int
1 else Int
0 :: Int
doConvOp (FToB FloatType
_) (FloatValue FloatValue
v) = PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ Bool -> PrimValue
BoolValue (Bool -> PrimValue) -> Bool -> PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> Double
floatToDouble FloatValue
v Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
/= Double
0
doConvOp (BToF FloatType
to) (BoolValue Bool
v) = PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ FloatType -> Double -> FloatValue
forall num. Real num => FloatType -> num -> FloatValue
floatValue FloatType
to (Double -> FloatValue) -> Double -> FloatValue
forall a b. (a -> b) -> a -> b
$ if Bool
v then Double
1 else Double
0 :: Double
doConvOp ConvOp
_ PrimValue
_ = Maybe PrimValue
forall a. Maybe a
Nothing
flipConvOp :: ConvOp -> ConvOp
flipConvOp :: ConvOp -> ConvOp
flipConvOp (ZExt IntType
from IntType
to) = IntType -> IntType -> ConvOp
ZExt IntType
to IntType
from
flipConvOp (SExt IntType
from IntType
to) = IntType -> IntType -> ConvOp
SExt IntType
to IntType
from
flipConvOp (FPConv FloatType
from FloatType
to) = FloatType -> FloatType -> ConvOp
FPConv FloatType
to FloatType
from
flipConvOp (FPToUI FloatType
from IntType
to) = IntType -> FloatType -> ConvOp
UIToFP IntType
to FloatType
from
flipConvOp (FPToSI FloatType
from IntType
to) = IntType -> FloatType -> ConvOp
SIToFP IntType
to FloatType
from
flipConvOp (UIToFP IntType
from FloatType
to) = FloatType -> IntType -> ConvOp
FPToSI FloatType
to IntType
from
flipConvOp (SIToFP IntType
from FloatType
to) = FloatType -> IntType -> ConvOp
FPToSI FloatType
to IntType
from
flipConvOp (IToB IntType
from) = IntType -> ConvOp
BToI IntType
from
flipConvOp (BToI IntType
to) = IntType -> ConvOp
IToB IntType
to
flipConvOp (FToB FloatType
from) = FloatType -> ConvOp
BToF FloatType
from
flipConvOp (BToF FloatType
to) = FloatType -> ConvOp
FToB FloatType
to
doZExt :: IntValue -> IntType -> IntValue
doZExt :: IntValue -> IntType -> IntValue
doZExt (Int8Value Int8
x) IntType
t = IntType -> Integer -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue IntType
t (Integer -> IntValue) -> Integer -> IntValue
forall a b. (a -> b) -> a -> b
$ Word8 -> Integer
forall a. Integral a => a -> Integer
toInteger (Int8 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int8
x :: Word8)
doZExt (Int16Value Int16
x) IntType
t = IntType -> Integer -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue IntType
t (Integer -> IntValue) -> Integer -> IntValue
forall a b. (a -> b) -> a -> b
$ Word16 -> Integer
forall a. Integral a => a -> Integer
toInteger (Int16 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int16
x :: Word16)
doZExt (Int32Value Int32
x) IntType
t = IntType -> Integer -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue IntType
t (Integer -> IntValue) -> Integer -> IntValue
forall a b. (a -> b) -> a -> b
$ Word32 -> Integer
forall a. Integral a => a -> Integer
toInteger (Int32 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
x :: Word32)
doZExt (Int64Value Int64
x) IntType
t = IntType -> Integer -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue IntType
t (Integer -> IntValue) -> Integer -> IntValue
forall a b. (a -> b) -> a -> b
$ Word64 -> Integer
forall a. Integral a => a -> Integer
toInteger (Int64 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
x :: Word64)
doSExt :: IntValue -> IntType -> IntValue
doSExt :: IntValue -> IntType -> IntValue
doSExt (Int8Value Int8
x) IntType
t = IntType -> Integer -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue IntType
t (Integer -> IntValue) -> Integer -> IntValue
forall a b. (a -> b) -> a -> b
$ Int8 -> Integer
forall a. Integral a => a -> Integer
toInteger Int8
x
doSExt (Int16Value Int16
x) IntType
t = IntType -> Integer -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue IntType
t (Integer -> IntValue) -> Integer -> IntValue
forall a b. (a -> b) -> a -> b
$ Int16 -> Integer
forall a. Integral a => a -> Integer
toInteger Int16
x
doSExt (Int32Value Int32
x) IntType
t = IntType -> Integer -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue IntType
t (Integer -> IntValue) -> Integer -> IntValue
forall a b. (a -> b) -> a -> b
$ Int32 -> Integer
forall a. Integral a => a -> Integer
toInteger Int32
x
doSExt (Int64Value Int64
x) IntType
t = IntType -> Integer -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue IntType
t (Integer -> IntValue) -> Integer -> IntValue
forall a b. (a -> b) -> a -> b
$ Int64 -> Integer
forall a. Integral a => a -> Integer
toInteger Int64
x
doFPConv :: FloatValue -> FloatType -> FloatValue
doFPConv :: FloatValue -> FloatType -> FloatValue
doFPConv FloatValue
v FloatType
Float16 = Half -> FloatValue
Float16Value (Half -> FloatValue) -> Half -> FloatValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> Half
floatToHalf FloatValue
v
doFPConv FloatValue
v FloatType
Float32 = Float -> FloatValue
Float32Value (Float -> FloatValue) -> Float -> FloatValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> Float
floatToFloat FloatValue
v
doFPConv FloatValue
v FloatType
Float64 = Double -> FloatValue
Float64Value (Double -> FloatValue) -> Double -> FloatValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> Double
floatToDouble FloatValue
v
doFPToUI :: FloatValue -> IntType -> IntValue
doFPToUI :: FloatValue -> IntType -> IntValue
doFPToUI FloatValue
v IntType
t = IntType -> Word64 -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue IntType
t (Double -> Word64
forall b. Integral b => Double -> b
forall a b. (RealFrac a, Integral b) => a -> b
truncate (Double -> Word64) -> Double -> Word64
forall a b. (a -> b) -> a -> b
$ FloatValue -> Double
floatToDouble FloatValue
v :: Word64)
doFPToSI :: FloatValue -> IntType -> IntValue
doFPToSI :: FloatValue -> IntType -> IntValue
doFPToSI FloatValue
v IntType
t = IntType -> Word64 -> IntValue
forall int. Integral int => IntType -> int -> IntValue
intValue IntType
t (Double -> Word64
forall b. Integral b => Double -> b
forall a b. (RealFrac a, Integral b) => a -> b
truncate (Double -> Word64) -> Double -> Word64
forall a b. (a -> b) -> a -> b
$ FloatValue -> Double
floatToDouble FloatValue
v :: Word64)
doUIToFP :: IntValue -> FloatType -> FloatValue
doUIToFP :: IntValue -> FloatType -> FloatValue
doUIToFP IntValue
v FloatType
t = FloatType -> Word64 -> FloatValue
forall num. Real num => FloatType -> num -> FloatValue
floatValue FloatType
t (Word64 -> FloatValue) -> Word64 -> FloatValue
forall a b. (a -> b) -> a -> b
$ IntValue -> Word64
intToWord64 IntValue
v
doSIToFP :: IntValue -> FloatType -> FloatValue
doSIToFP :: IntValue -> FloatType -> FloatValue
doSIToFP IntValue
v FloatType
t = FloatType -> Int64 -> FloatValue
forall num. Real num => FloatType -> num -> FloatValue
floatValue FloatType
t (Int64 -> FloatValue) -> Int64 -> FloatValue
forall a b. (a -> b) -> a -> b
$ IntValue -> Int64
intToInt64 IntValue
v
doCmpOp :: CmpOp -> PrimValue -> PrimValue -> Maybe Bool
doCmpOp :: CmpOp -> PrimValue -> PrimValue -> Maybe Bool
doCmpOp CmpEq {} PrimValue
v1 PrimValue
v2 = Bool -> Maybe Bool
forall a. a -> Maybe a
Just (Bool -> Maybe Bool) -> Bool -> Maybe Bool
forall a b. (a -> b) -> a -> b
$ PrimValue -> PrimValue -> Bool
doCmpEq PrimValue
v1 PrimValue
v2
doCmpOp CmpUlt {} (IntValue IntValue
v1) (IntValue IntValue
v2) = Bool -> Maybe Bool
forall a. a -> Maybe a
Just (Bool -> Maybe Bool) -> Bool -> Maybe Bool
forall a b. (a -> b) -> a -> b
$ IntValue -> IntValue -> Bool
doCmpUlt IntValue
v1 IntValue
v2
doCmpOp CmpUle {} (IntValue IntValue
v1) (IntValue IntValue
v2) = Bool -> Maybe Bool
forall a. a -> Maybe a
Just (Bool -> Maybe Bool) -> Bool -> Maybe Bool
forall a b. (a -> b) -> a -> b
$ IntValue -> IntValue -> Bool
doCmpUle IntValue
v1 IntValue
v2
doCmpOp CmpSlt {} (IntValue IntValue
v1) (IntValue IntValue
v2) = Bool -> Maybe Bool
forall a. a -> Maybe a
Just (Bool -> Maybe Bool) -> Bool -> Maybe Bool
forall a b. (a -> b) -> a -> b
$ IntValue -> IntValue -> Bool
doCmpSlt IntValue
v1 IntValue
v2
doCmpOp CmpSle {} (IntValue IntValue
v1) (IntValue IntValue
v2) = Bool -> Maybe Bool
forall a. a -> Maybe a
Just (Bool -> Maybe Bool) -> Bool -> Maybe Bool
forall a b. (a -> b) -> a -> b
$ IntValue -> IntValue -> Bool
doCmpSle IntValue
v1 IntValue
v2
doCmpOp FCmpLt {} (FloatValue FloatValue
v1) (FloatValue FloatValue
v2) = Bool -> Maybe Bool
forall a. a -> Maybe a
Just (Bool -> Maybe Bool) -> Bool -> Maybe Bool
forall a b. (a -> b) -> a -> b
$ FloatValue -> FloatValue -> Bool
doFCmpLt FloatValue
v1 FloatValue
v2
doCmpOp FCmpLe {} (FloatValue FloatValue
v1) (FloatValue FloatValue
v2) = Bool -> Maybe Bool
forall a. a -> Maybe a
Just (Bool -> Maybe Bool) -> Bool -> Maybe Bool
forall a b. (a -> b) -> a -> b
$ FloatValue -> FloatValue -> Bool
doFCmpLe FloatValue
v1 FloatValue
v2
doCmpOp CmpLlt {} (BoolValue Bool
v1) (BoolValue Bool
v2) = Bool -> Maybe Bool
forall a. a -> Maybe a
Just (Bool -> Maybe Bool) -> Bool -> Maybe Bool
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not Bool
v1 Bool -> Bool -> Bool
&& Bool
v2
doCmpOp CmpLle {} (BoolValue Bool
v1) (BoolValue Bool
v2) = Bool -> Maybe Bool
forall a. a -> Maybe a
Just (Bool -> Maybe Bool) -> Bool -> Maybe Bool
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Bool
v1 Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
v2)
doCmpOp CmpOp
_ PrimValue
_ PrimValue
_ = Maybe Bool
forall a. Maybe a
Nothing
doCmpEq :: PrimValue -> PrimValue -> Bool
doCmpEq :: PrimValue -> PrimValue -> Bool
doCmpEq (FloatValue (Float32Value Float
v1)) (FloatValue (Float32Value Float
v2)) = Float
v1 Float -> Float -> Bool
forall a. Eq a => a -> a -> Bool
== Float
v2
doCmpEq (FloatValue (Float64Value Double
v1)) (FloatValue (Float64Value Double
v2)) = Double
v1 Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
v2
doCmpEq PrimValue
v1 PrimValue
v2 = PrimValue
v1 PrimValue -> PrimValue -> Bool
forall a. Eq a => a -> a -> Bool
== PrimValue
v2
doCmpUlt :: IntValue -> IntValue -> Bool
doCmpUlt :: IntValue -> IntValue -> Bool
doCmpUlt IntValue
v1 IntValue
v2 = IntValue -> Word64
intToWord64 IntValue
v1 Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
< IntValue -> Word64
intToWord64 IntValue
v2
doCmpUle :: IntValue -> IntValue -> Bool
doCmpUle :: IntValue -> IntValue -> Bool
doCmpUle IntValue
v1 IntValue
v2 = IntValue -> Word64
intToWord64 IntValue
v1 Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
<= IntValue -> Word64
intToWord64 IntValue
v2
doCmpSlt :: IntValue -> IntValue -> Bool
doCmpSlt :: IntValue -> IntValue -> Bool
doCmpSlt = IntValue -> IntValue -> Bool
forall a. Ord a => a -> a -> Bool
(<)
doCmpSle :: IntValue -> IntValue -> Bool
doCmpSle :: IntValue -> IntValue -> Bool
doCmpSle = IntValue -> IntValue -> Bool
forall a. Ord a => a -> a -> Bool
(<=)
doFCmpLt :: FloatValue -> FloatValue -> Bool
doFCmpLt :: FloatValue -> FloatValue -> Bool
doFCmpLt = FloatValue -> FloatValue -> Bool
forall a. Ord a => a -> a -> Bool
(<)
doFCmpLe :: FloatValue -> FloatValue -> Bool
doFCmpLe :: FloatValue -> FloatValue -> Bool
doFCmpLe = FloatValue -> FloatValue -> Bool
forall a. Ord a => a -> a -> Bool
(<=)
intToWord64 :: IntValue -> Word64
intToWord64 :: IntValue -> Word64
intToWord64 (Int8Value Int8
v) = Word8 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int8 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int8
v :: Word8)
intToWord64 (Int16Value Int16
v) = Word16 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int16 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int16
v :: Word16)
intToWord64 (Int32Value Int32
v) = Word32 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int32 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
v :: Word32)
intToWord64 (Int64Value Int64
v) = Word64 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
v :: Word64)
intToInt64 :: IntValue -> Int64
intToInt64 :: IntValue -> Int64
intToInt64 (Int8Value Int8
v) = Int8 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int8
v
intToInt64 (Int16Value Int16
v) = Int16 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int16
v
intToInt64 (Int32Value Int32
v) = Int32 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
v
intToInt64 (Int64Value Int64
v) = Int64 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
v
intToInt :: IntValue -> Int
intToInt :: IntValue -> Int
intToInt = Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64 -> Int) -> (IntValue -> Int64) -> IntValue -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. IntValue -> Int64
intToInt64
floatToDouble :: FloatValue -> Double
floatToDouble :: FloatValue -> Double
floatToDouble (Float16Value Half
v)
| Half -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Half
v, Half
v Half -> Half -> Bool
forall a. Ord a => a -> a -> Bool
> Half
0 = Double
1 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
0
| Half -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Half
v, Half
v Half -> Half -> Bool
forall a. Ord a => a -> a -> Bool
< Half
0 = -Double
1 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
0
| Half -> Bool
forall a. RealFloat a => a -> Bool
isNaN Half
v = Double
0 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
0
| Bool
otherwise = Rational -> Double
forall a. Fractional a => Rational -> a
fromRational (Rational -> Double) -> Rational -> Double
forall a b. (a -> b) -> a -> b
$ Half -> Rational
forall a. Real a => a -> Rational
toRational Half
v
floatToDouble (Float32Value Float
v)
| Float -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Float
v, Float
v Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
> Float
0 = Double
1 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
0
| Float -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Float
v, Float
v Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
< Float
0 = -Double
1 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
0
| Float -> Bool
forall a. RealFloat a => a -> Bool
isNaN Float
v = Double
0 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
0
| Bool
otherwise = Rational -> Double
forall a. Fractional a => Rational -> a
fromRational (Rational -> Double) -> Rational -> Double
forall a b. (a -> b) -> a -> b
$ Float -> Rational
forall a. Real a => a -> Rational
toRational Float
v
floatToDouble (Float64Value Double
v) = Double
v
floatToFloat :: FloatValue -> Float
floatToFloat :: FloatValue -> Float
floatToFloat (Float16Value Half
v)
| Half -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Half
v, Half
v Half -> Half -> Bool
forall a. Ord a => a -> a -> Bool
> Half
0 = Float
1 Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/ Float
0
| Half -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Half
v, Half
v Half -> Half -> Bool
forall a. Ord a => a -> a -> Bool
< Half
0 = -Float
1 Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/ Float
0
| Half -> Bool
forall a. RealFloat a => a -> Bool
isNaN Half
v = Float
0 Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/ Float
0
| Bool
otherwise = Rational -> Float
forall a. Fractional a => Rational -> a
fromRational (Rational -> Float) -> Rational -> Float
forall a b. (a -> b) -> a -> b
$ Half -> Rational
forall a. Real a => a -> Rational
toRational Half
v
floatToFloat (Float32Value Float
v) = Float
v
floatToFloat (Float64Value Double
v)
| Double -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Double
v, Double
v Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
0 = Float
1 Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/ Float
0
| Double -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Double
v, Double
v Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
0 = -Float
1 Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/ Float
0
| Double -> Bool
forall a. RealFloat a => a -> Bool
isNaN Double
v = Float
0 Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/ Float
0
| Bool
otherwise = Rational -> Float
forall a. Fractional a => Rational -> a
fromRational (Rational -> Float) -> Rational -> Float
forall a b. (a -> b) -> a -> b
$ Double -> Rational
forall a. Real a => a -> Rational
toRational Double
v
floatToHalf :: FloatValue -> Half
floatToHalf :: FloatValue -> Half
floatToHalf (Float16Value Half
v) = Half
v
floatToHalf (Float32Value Float
v)
| Float -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Float
v, Float
v Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
> Float
0 = Half
1 Half -> Half -> Half
forall a. Fractional a => a -> a -> a
/ Half
0
| Float -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Float
v, Float
v Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
< Float
0 = -Half
1 Half -> Half -> Half
forall a. Fractional a => a -> a -> a
/ Half
0
| Float -> Bool
forall a. RealFloat a => a -> Bool
isNaN Float
v = Half
0 Half -> Half -> Half
forall a. Fractional a => a -> a -> a
/ Half
0
| Bool
otherwise = Rational -> Half
forall a. Fractional a => Rational -> a
fromRational (Rational -> Half) -> Rational -> Half
forall a b. (a -> b) -> a -> b
$ Float -> Rational
forall a. Real a => a -> Rational
toRational Float
v
floatToHalf (Float64Value Double
v)
| Double -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Double
v, Double
v Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
0 = Half
1 Half -> Half -> Half
forall a. Fractional a => a -> a -> a
/ Half
0
| Double -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Double
v, Double
v Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
0 = -Half
1 Half -> Half -> Half
forall a. Fractional a => a -> a -> a
/ Half
0
| Double -> Bool
forall a. RealFloat a => a -> Bool
isNaN Double
v = Half
0 Half -> Half -> Half
forall a. Fractional a => a -> a -> a
/ Half
0
| Bool
otherwise = Rational -> Half
forall a. Fractional a => Rational -> a
fromRational (Rational -> Half) -> Rational -> Half
forall a b. (a -> b) -> a -> b
$ Double -> Rational
forall a. Real a => a -> Rational
toRational Double
v
binOpType :: BinOp -> PrimType
binOpType :: BinOp -> PrimType
binOpType (Add IntType
t Overflow
_) = IntType -> PrimType
IntType IntType
t
binOpType (Sub IntType
t Overflow
_) = IntType -> PrimType
IntType IntType
t
binOpType (Mul IntType
t Overflow
_) = IntType -> PrimType
IntType IntType
t
binOpType (SDiv IntType
t Safety
_) = IntType -> PrimType
IntType IntType
t
binOpType (SDivUp IntType
t Safety
_) = IntType -> PrimType
IntType IntType
t
binOpType (SMod IntType
t Safety
_) = IntType -> PrimType
IntType IntType
t
binOpType (SQuot IntType
t Safety
_) = IntType -> PrimType
IntType IntType
t
binOpType (SRem IntType
t Safety
_) = IntType -> PrimType
IntType IntType
t
binOpType (UDiv IntType
t Safety
_) = IntType -> PrimType
IntType IntType
t
binOpType (UDivUp IntType
t Safety
_) = IntType -> PrimType
IntType IntType
t
binOpType (UMod IntType
t Safety
_) = IntType -> PrimType
IntType IntType
t
binOpType (SMin IntType
t) = IntType -> PrimType
IntType IntType
t
binOpType (UMin IntType
t) = IntType -> PrimType
IntType IntType
t
binOpType (FMin FloatType
t) = FloatType -> PrimType
FloatType FloatType
t
binOpType (SMax IntType
t) = IntType -> PrimType
IntType IntType
t
binOpType (UMax IntType
t) = IntType -> PrimType
IntType IntType
t
binOpType (FMax FloatType
t) = FloatType -> PrimType
FloatType FloatType
t
binOpType (Shl IntType
t) = IntType -> PrimType
IntType IntType
t
binOpType (LShr IntType
t) = IntType -> PrimType
IntType IntType
t
binOpType (AShr IntType
t) = IntType -> PrimType
IntType IntType
t
binOpType (And IntType
t) = IntType -> PrimType
IntType IntType
t
binOpType (Or IntType
t) = IntType -> PrimType
IntType IntType
t
binOpType (Xor IntType
t) = IntType -> PrimType
IntType IntType
t
binOpType (Pow IntType
t) = IntType -> PrimType
IntType IntType
t
binOpType (FPow FloatType
t) = FloatType -> PrimType
FloatType FloatType
t
binOpType BinOp
LogAnd = PrimType
Bool
binOpType BinOp
LogOr = PrimType
Bool
binOpType (FAdd FloatType
t) = FloatType -> PrimType
FloatType FloatType
t
binOpType (FSub FloatType
t) = FloatType -> PrimType
FloatType FloatType
t
binOpType (FMul FloatType
t) = FloatType -> PrimType
FloatType FloatType
t
binOpType (FDiv FloatType
t) = FloatType -> PrimType
FloatType FloatType
t
binOpType (FMod FloatType
t) = FloatType -> PrimType
FloatType FloatType
t
cmpOpType :: CmpOp -> PrimType
cmpOpType :: CmpOp -> PrimType
cmpOpType (CmpEq PrimType
t) = PrimType
t
cmpOpType (CmpSlt IntType
t) = IntType -> PrimType
IntType IntType
t
cmpOpType (CmpSle IntType
t) = IntType -> PrimType
IntType IntType
t
cmpOpType (CmpUlt IntType
t) = IntType -> PrimType
IntType IntType
t
cmpOpType (CmpUle IntType
t) = IntType -> PrimType
IntType IntType
t
cmpOpType (FCmpLt FloatType
t) = FloatType -> PrimType
FloatType FloatType
t
cmpOpType (FCmpLe FloatType
t) = FloatType -> PrimType
FloatType FloatType
t
cmpOpType CmpOp
CmpLlt = PrimType
Bool
cmpOpType CmpOp
CmpLle = PrimType
Bool
unOpType :: UnOp -> PrimType
unOpType :: UnOp -> PrimType
unOpType (SSignum IntType
t) = IntType -> PrimType
IntType IntType
t
unOpType (USignum IntType
t) = IntType -> PrimType
IntType IntType
t
unOpType UnOp
Not = PrimType
Bool
unOpType (Complement IntType
t) = IntType -> PrimType
IntType IntType
t
unOpType (Abs IntType
t) = IntType -> PrimType
IntType IntType
t
unOpType (FAbs FloatType
t) = FloatType -> PrimType
FloatType FloatType
t
unOpType (FSignum FloatType
t) = FloatType -> PrimType
FloatType FloatType
t
convOpType :: ConvOp -> (PrimType, PrimType)
convOpType :: ConvOp -> (PrimType, PrimType)
convOpType (ZExt IntType
from IntType
to) = (IntType -> PrimType
IntType IntType
from, IntType -> PrimType
IntType IntType
to)
convOpType (SExt IntType
from IntType
to) = (IntType -> PrimType
IntType IntType
from, IntType -> PrimType
IntType IntType
to)
convOpType (FPConv FloatType
from FloatType
to) = (FloatType -> PrimType
FloatType FloatType
from, FloatType -> PrimType
FloatType FloatType
to)
convOpType (FPToUI FloatType
from IntType
to) = (FloatType -> PrimType
FloatType FloatType
from, IntType -> PrimType
IntType IntType
to)
convOpType (FPToSI FloatType
from IntType
to) = (FloatType -> PrimType
FloatType FloatType
from, IntType -> PrimType
IntType IntType
to)
convOpType (UIToFP IntType
from FloatType
to) = (IntType -> PrimType
IntType IntType
from, FloatType -> PrimType
FloatType FloatType
to)
convOpType (SIToFP IntType
from FloatType
to) = (IntType -> PrimType
IntType IntType
from, FloatType -> PrimType
FloatType FloatType
to)
convOpType (IToB IntType
from) = (IntType -> PrimType
IntType IntType
from, PrimType
Bool)
convOpType (BToI IntType
to) = (PrimType
Bool, IntType -> PrimType
IntType IntType
to)
convOpType (FToB FloatType
from) = (FloatType -> PrimType
FloatType FloatType
from, PrimType
Bool)
convOpType (BToF FloatType
to) = (PrimType
Bool, FloatType -> PrimType
FloatType FloatType
to)
halfToWord :: Half -> Word16
halfToWord :: Half -> Word16
halfToWord (Half (CUShort Word16
x)) = Word16
x
wordToHalf :: Word16 -> Half
wordToHalf :: Word16 -> Half
wordToHalf = CUShort -> Half
Half (CUShort -> Half) -> (Word16 -> CUShort) -> Word16 -> Half
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Word16 -> CUShort
CUShort
floatToWord :: Float -> Word32
floatToWord :: Float -> Word32
floatToWord = Get Word32 -> ByteString -> Word32
forall a. Get a -> ByteString -> a
G.runGet Get Word32
G.getWord32le (ByteString -> Word32) -> (Float -> ByteString) -> Float -> Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Put -> ByteString
P.runPut (Put -> ByteString) -> (Float -> Put) -> Float -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Float -> Put
P.putFloatle
wordToFloat :: Word32 -> Float
wordToFloat :: Word32 -> Float
wordToFloat = Get Float -> ByteString -> Float
forall a. Get a -> ByteString -> a
G.runGet Get Float
G.getFloatle (ByteString -> Float) -> (Word32 -> ByteString) -> Word32 -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Put -> ByteString
P.runPut (Put -> ByteString) -> (Word32 -> Put) -> Word32 -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Word32 -> Put
P.putWord32le
doubleToWord :: Double -> Word64
doubleToWord :: Double -> Word64
doubleToWord = Get Word64 -> ByteString -> Word64
forall a. Get a -> ByteString -> a
G.runGet Get Word64
G.getWord64le (ByteString -> Word64)
-> (Double -> ByteString) -> Double -> Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Put -> ByteString
P.runPut (Put -> ByteString) -> (Double -> Put) -> Double -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Double -> Put
P.putDoublele
wordToDouble :: Word64 -> Double
wordToDouble :: Word64 -> Double
wordToDouble = Get Double -> ByteString -> Double
forall a. Get a -> ByteString -> a
G.runGet Get Double
G.getDoublele (ByteString -> Double)
-> (Word64 -> ByteString) -> Word64 -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Put -> ByteString
P.runPut (Put -> ByteString) -> (Word64 -> Put) -> Word64 -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Word64 -> Put
P.putWord64le
primFuns ::
M.Map
String
( [PrimType],
PrimType,
[PrimValue] -> Maybe PrimValue
)
primFuns :: Map String ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue)
primFuns =
[(String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))]
-> Map
String ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue)
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
[ String
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16 String
"sqrt16" Half -> Half
forall a. Floating a => a -> a
sqrt,
String
-> (Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32 String
"sqrt32" Float -> Float
forall a. Floating a => a -> a
sqrt,
String
-> (Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64 String
"sqrt64" Double -> Double
forall a. Floating a => a -> a
sqrt,
String
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16 String
"cbrt16" ((Half -> Half)
-> (String,
([PrimType], PrimType, [PrimValue] -> Maybe PrimValue)))
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall a b. (a -> b) -> a -> b
$ Float -> Half
forall from to. (RealFloat from, RealFloat to) => from -> to
convFloat (Float -> Half) -> (Half -> Float) -> Half -> Half
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Float -> Float
cbrtf (Float -> Float) -> (Half -> Float) -> Half -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Half -> Float
forall from to. (RealFloat from, RealFloat to) => from -> to
convFloat,
String
-> (Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32 String
"cbrt32" Float -> Float
cbrtf,
String
-> (Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64 String
"cbrt64" Double -> Double
cbrt,
String
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16 String
"log16" Half -> Half
forall a. Floating a => a -> a
log,
String
-> (Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32 String
"log32" Float -> Float
forall a. Floating a => a -> a
log,
String
-> (Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64 String
"log64" Double -> Double
forall a. Floating a => a -> a
log,
String
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16 String
"log10_16" (Half -> Half -> Half
forall a. Floating a => a -> a -> a
logBase Half
10),
String
-> (Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32 String
"log10_32" (Float -> Float -> Float
forall a. Floating a => a -> a -> a
logBase Float
10),
String
-> (Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64 String
"log10_64" (Double -> Double -> Double
forall a. Floating a => a -> a -> a
logBase Double
10),
String
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16 String
"log1p_16" Half -> Half
forall a. Floating a => a -> a
log1p,
String
-> (Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32 String
"log1p_32" Float -> Float
forall a. Floating a => a -> a
log1p,
String
-> (Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64 String
"log1p_64" Double -> Double
forall a. Floating a => a -> a
log1p,
String
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16 String
"log2_16" (Half -> Half -> Half
forall a. Floating a => a -> a -> a
logBase Half
2),
String
-> (Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32 String
"log2_32" (Float -> Float -> Float
forall a. Floating a => a -> a -> a
logBase Float
2),
String
-> (Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64 String
"log2_64" (Double -> Double -> Double
forall a. Floating a => a -> a -> a
logBase Double
2),
String
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16 String
"exp16" Half -> Half
forall a. Floating a => a -> a
exp,
String
-> (Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32 String
"exp32" Float -> Float
forall a. Floating a => a -> a
exp,
String
-> (Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64 String
"exp64" Double -> Double
forall a. Floating a => a -> a
exp,
String
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16 String
"sin16" Half -> Half
forall a. Floating a => a -> a
sin,
String
-> (Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32 String
"sin32" Float -> Float
forall a. Floating a => a -> a
sin,
String
-> (Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64 String
"sin64" Double -> Double
forall a. Floating a => a -> a
sin,
String
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16 String
"sinh16" Half -> Half
forall a. Floating a => a -> a
sinh,
String
-> (Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32 String
"sinh32" Float -> Float
forall a. Floating a => a -> a
sinh,
String
-> (Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64 String
"sinh64" Double -> Double
forall a. Floating a => a -> a
sinh,
String
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16 String
"cos16" Half -> Half
forall a. Floating a => a -> a
cos,
String
-> (Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32 String
"cos32" Float -> Float
forall a. Floating a => a -> a
cos,
String
-> (Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64 String
"cos64" Double -> Double
forall a. Floating a => a -> a
cos,
String
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16 String
"cosh16" Half -> Half
forall a. Floating a => a -> a
cosh,
String
-> (Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32 String
"cosh32" Float -> Float
forall a. Floating a => a -> a
cosh,
String
-> (Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64 String
"cosh64" Double -> Double
forall a. Floating a => a -> a
cosh,
String
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16 String
"tan16" Half -> Half
forall a. Floating a => a -> a
tan,
String
-> (Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32 String
"tan32" Float -> Float
forall a. Floating a => a -> a
tan,
String
-> (Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64 String
"tan64" Double -> Double
forall a. Floating a => a -> a
tan,
String
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16 String
"tanh16" Half -> Half
forall a. Floating a => a -> a
tanh,
String
-> (Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32 String
"tanh32" Float -> Float
forall a. Floating a => a -> a
tanh,
String
-> (Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64 String
"tanh64" Double -> Double
forall a. Floating a => a -> a
tanh,
String
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16 String
"asin16" Half -> Half
forall a. Floating a => a -> a
asin,
String
-> (Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32 String
"asin32" Float -> Float
forall a. Floating a => a -> a
asin,
String
-> (Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64 String
"asin64" Double -> Double
forall a. Floating a => a -> a
asin,
String
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16 String
"asinh16" Half -> Half
forall a. Floating a => a -> a
asinh,
String
-> (Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32 String
"asinh32" Float -> Float
forall a. Floating a => a -> a
asinh,
String
-> (Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64 String
"asinh64" Double -> Double
forall a. Floating a => a -> a
asinh,
String
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16 String
"acos16" Half -> Half
forall a. Floating a => a -> a
acos,
String
-> (Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32 String
"acos32" Float -> Float
forall a. Floating a => a -> a
acos,
String
-> (Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64 String
"acos64" Double -> Double
forall a. Floating a => a -> a
acos,
String
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16 String
"acosh16" Half -> Half
forall a. Floating a => a -> a
acosh,
String
-> (Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32 String
"acosh32" Float -> Float
forall a. Floating a => a -> a
acosh,
String
-> (Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64 String
"acosh64" Double -> Double
forall a. Floating a => a -> a
acosh,
String
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16 String
"atan16" Half -> Half
forall a. Floating a => a -> a
atan,
String
-> (Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32 String
"atan32" Float -> Float
forall a. Floating a => a -> a
atan,
String
-> (Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64 String
"atan64" Double -> Double
forall a. Floating a => a -> a
atan,
String
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16 String
"atanh16" Half -> Half
forall a. Floating a => a -> a
atanh,
String
-> (Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32 String
"atanh32" Float -> Float
forall a. Floating a => a -> a
atanh,
String
-> (Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64 String
"atanh64" Double -> Double
forall a. Floating a => a -> a
atanh,
String
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16 String
"round16" ((Half -> Half)
-> (String,
([PrimType], PrimType, [PrimValue] -> Maybe PrimValue)))
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall a b. (a -> b) -> a -> b
$ Float -> Half
forall from to. (RealFloat from, RealFloat to) => from -> to
convFloat (Float -> Half) -> (Half -> Float) -> Half -> Half
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Float -> Float
roundFloat (Float -> Float) -> (Half -> Float) -> Half -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Half -> Float
forall from to. (RealFloat from, RealFloat to) => from -> to
convFloat,
String
-> (Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32 String
"round32" Float -> Float
roundFloat,
String
-> (Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64 String
"round64" Double -> Double
roundDouble,
String
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16 String
"ceil16" ((Half -> Half)
-> (String,
([PrimType], PrimType, [PrimValue] -> Maybe PrimValue)))
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall a b. (a -> b) -> a -> b
$ Float -> Half
forall from to. (RealFloat from, RealFloat to) => from -> to
convFloat (Float -> Half) -> (Half -> Float) -> Half -> Half
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Float -> Float
ceilFloat (Float -> Float) -> (Half -> Float) -> Half -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Half -> Float
forall from to. (RealFloat from, RealFloat to) => from -> to
convFloat,
String
-> (Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32 String
"ceil32" Float -> Float
ceilFloat,
String
-> (Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64 String
"ceil64" Double -> Double
ceilDouble,
String
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16 String
"floor16" ((Half -> Half)
-> (String,
([PrimType], PrimType, [PrimValue] -> Maybe PrimValue)))
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall a b. (a -> b) -> a -> b
$ Float -> Half
forall from to. (RealFloat from, RealFloat to) => from -> to
convFloat (Float -> Half) -> (Half -> Float) -> Half -> Half
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Float -> Float
floorFloat (Float -> Float) -> (Half -> Float) -> Half -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Half -> Float
forall from to. (RealFloat from, RealFloat to) => from -> to
convFloat,
String
-> (Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32 String
"floor32" Float -> Float
floorFloat,
String
-> (Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64 String
"floor64" Double -> Double
floorDouble,
String
-> (Half -> Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16_2 String
"nextafter16" (\Half
x Half
y -> Float -> Half
forall from to. (RealFloat from, RealFloat to) => from -> to
convFloat (Float -> Half) -> Float -> Half
forall a b. (a -> b) -> a -> b
$ Float -> Float -> Float
nextafterf (Half -> Float
forall from to. (RealFloat from, RealFloat to) => from -> to
convFloat Half
x) (Half -> Float
forall from to. (RealFloat from, RealFloat to) => from -> to
convFloat Half
y)),
String
-> (Float -> Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32_2 String
"nextafter32" Float -> Float -> Float
nextafterf,
String
-> (Double -> Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64_2 String
"nextafter64" Double -> Double -> Double
nextafter,
String
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16 String
"gamma16" ((Half -> Half)
-> (String,
([PrimType], PrimType, [PrimValue] -> Maybe PrimValue)))
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall a b. (a -> b) -> a -> b
$ Float -> Half
forall from to. (RealFloat from, RealFloat to) => from -> to
convFloat (Float -> Half) -> (Half -> Float) -> Half -> Half
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Float -> Float
tgammaf (Float -> Float) -> (Half -> Float) -> Half -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Half -> Float
forall from to. (RealFloat from, RealFloat to) => from -> to
convFloat,
String
-> (Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32 String
"gamma32" Float -> Float
tgammaf,
String
-> (Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64 String
"gamma64" Double -> Double
tgamma,
String
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16 String
"lgamma16" ((Half -> Half)
-> (String,
([PrimType], PrimType, [PrimValue] -> Maybe PrimValue)))
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall a b. (a -> b) -> a -> b
$ Float -> Half
forall from to. (RealFloat from, RealFloat to) => from -> to
convFloat (Float -> Half) -> (Half -> Float) -> Half -> Half
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Float -> Float
lgammaf (Float -> Float) -> (Half -> Float) -> Half -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Half -> Float
forall from to. (RealFloat from, RealFloat to) => from -> to
convFloat,
String
-> (Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32 String
"lgamma32" Float -> Float
lgammaf,
String
-> (Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64 String
"lgamma64" Double -> Double
lgamma,
String
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16 String
"erf16" ((Half -> Half)
-> (String,
([PrimType], PrimType, [PrimValue] -> Maybe PrimValue)))
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall a b. (a -> b) -> a -> b
$ Float -> Half
forall from to. (RealFloat from, RealFloat to) => from -> to
convFloat (Float -> Half) -> (Half -> Float) -> Half -> Half
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Float -> Float
erff (Float -> Float) -> (Half -> Float) -> Half -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Half -> Float
forall from to. (RealFloat from, RealFloat to) => from -> to
convFloat,
String
-> (Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32 String
"erf32" Float -> Float
erff,
String
-> (Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64 String
"erf64" Double -> Double
erf,
String
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16 String
"erfc16" ((Half -> Half)
-> (String,
([PrimType], PrimType, [PrimValue] -> Maybe PrimValue)))
-> (Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall a b. (a -> b) -> a -> b
$ Float -> Half
forall from to. (RealFloat from, RealFloat to) => from -> to
convFloat (Float -> Half) -> (Half -> Float) -> Half -> Half
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Float -> Float
erfcf (Float -> Float) -> (Half -> Float) -> Half -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Half -> Float
forall from to. (RealFloat from, RealFloat to) => from -> to
convFloat,
String
-> (Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32 String
"erfc32" Float -> Float
erfcf,
String
-> (Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64 String
"erfc64" Double -> Double
erfc,
String
-> (Int8 -> PrimValue)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a} {a}.
a
-> (Int8 -> a)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe a))
i8 String
"clz8" ((Int8 -> PrimValue)
-> (String,
([PrimType], PrimType, [PrimValue] -> Maybe PrimValue)))
-> (Int8 -> PrimValue)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> (Int8 -> IntValue) -> Int8 -> PrimValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int32 -> IntValue
Int32Value (Int32 -> IntValue) -> (Int8 -> Int32) -> Int8 -> IntValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> (Int8 -> Int) -> Int8 -> Int32
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int8 -> Int
forall b. FiniteBits b => b -> Int
countLeadingZeros,
String
-> (Int16 -> PrimValue)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a} {a}.
a
-> (Int16 -> a)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe a))
i16 String
"clz16" ((Int16 -> PrimValue)
-> (String,
([PrimType], PrimType, [PrimValue] -> Maybe PrimValue)))
-> (Int16 -> PrimValue)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue)
-> (Int16 -> IntValue) -> Int16 -> PrimValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int32 -> IntValue
Int32Value (Int32 -> IntValue) -> (Int16 -> Int32) -> Int16 -> IntValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> (Int16 -> Int) -> Int16 -> Int32
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int16 -> Int
forall b. FiniteBits b => b -> Int
countLeadingZeros,
String
-> (Int32 -> PrimValue)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a} {a}.
a
-> (Int32 -> a)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe a))
i32 String
"clz32" ((Int32 -> PrimValue)
-> (String,
([PrimType], PrimType, [PrimValue] -> Maybe PrimValue)))
-> (Int32 -> PrimValue)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue)
-> (Int32 -> IntValue) -> Int32 -> PrimValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int32 -> IntValue
Int32Value (Int32 -> IntValue) -> (Int32 -> Int32) -> Int32 -> IntValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> (Int32 -> Int) -> Int32 -> Int32
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int32 -> Int
forall b. FiniteBits b => b -> Int
countLeadingZeros,
String
-> (Int64 -> PrimValue)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a} {a}.
a
-> (Int64 -> a)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe a))
i64 String
"clz64" ((Int64 -> PrimValue)
-> (String,
([PrimType], PrimType, [PrimValue] -> Maybe PrimValue)))
-> (Int64 -> PrimValue)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue)
-> (Int64 -> IntValue) -> Int64 -> PrimValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int32 -> IntValue
Int32Value (Int32 -> IntValue) -> (Int64 -> Int32) -> Int64 -> IntValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> (Int64 -> Int) -> Int64 -> Int32
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int64 -> Int
forall b. FiniteBits b => b -> Int
countLeadingZeros,
String
-> (Int8 -> PrimValue)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a} {a}.
a
-> (Int8 -> a)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe a))
i8 String
"ctz8" ((Int8 -> PrimValue)
-> (String,
([PrimType], PrimType, [PrimValue] -> Maybe PrimValue)))
-> (Int8 -> PrimValue)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> (Int8 -> IntValue) -> Int8 -> PrimValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int32 -> IntValue
Int32Value (Int32 -> IntValue) -> (Int8 -> Int32) -> Int8 -> IntValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> (Int8 -> Int) -> Int8 -> Int32
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int8 -> Int
forall b. FiniteBits b => b -> Int
countTrailingZeros,
String
-> (Int16 -> PrimValue)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a} {a}.
a
-> (Int16 -> a)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe a))
i16 String
"ctz16" ((Int16 -> PrimValue)
-> (String,
([PrimType], PrimType, [PrimValue] -> Maybe PrimValue)))
-> (Int16 -> PrimValue)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue)
-> (Int16 -> IntValue) -> Int16 -> PrimValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int32 -> IntValue
Int32Value (Int32 -> IntValue) -> (Int16 -> Int32) -> Int16 -> IntValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> (Int16 -> Int) -> Int16 -> Int32
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int16 -> Int
forall b. FiniteBits b => b -> Int
countTrailingZeros,
String
-> (Int32 -> PrimValue)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a} {a}.
a
-> (Int32 -> a)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe a))
i32 String
"ctz32" ((Int32 -> PrimValue)
-> (String,
([PrimType], PrimType, [PrimValue] -> Maybe PrimValue)))
-> (Int32 -> PrimValue)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue)
-> (Int32 -> IntValue) -> Int32 -> PrimValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int32 -> IntValue
Int32Value (Int32 -> IntValue) -> (Int32 -> Int32) -> Int32 -> IntValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> (Int32 -> Int) -> Int32 -> Int32
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int32 -> Int
forall b. FiniteBits b => b -> Int
countTrailingZeros,
String
-> (Int64 -> PrimValue)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a} {a}.
a
-> (Int64 -> a)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe a))
i64 String
"ctz64" ((Int64 -> PrimValue)
-> (String,
([PrimType], PrimType, [PrimValue] -> Maybe PrimValue)))
-> (Int64 -> PrimValue)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue)
-> (Int64 -> IntValue) -> Int64 -> PrimValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int32 -> IntValue
Int32Value (Int32 -> IntValue) -> (Int64 -> Int32) -> Int64 -> IntValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> (Int64 -> Int) -> Int64 -> Int32
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int64 -> Int
forall b. FiniteBits b => b -> Int
countTrailingZeros,
String
-> (Int8 -> PrimValue)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a} {a}.
a
-> (Int8 -> a)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe a))
i8 String
"popc8" ((Int8 -> PrimValue)
-> (String,
([PrimType], PrimType, [PrimValue] -> Maybe PrimValue)))
-> (Int8 -> PrimValue)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> (Int8 -> IntValue) -> Int8 -> PrimValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int32 -> IntValue
Int32Value (Int32 -> IntValue) -> (Int8 -> Int32) -> Int8 -> IntValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> (Int8 -> Int) -> Int8 -> Int32
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int8 -> Int
forall a. Bits a => a -> Int
popCount,
String
-> (Int16 -> PrimValue)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a} {a}.
a
-> (Int16 -> a)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe a))
i16 String
"popc16" ((Int16 -> PrimValue)
-> (String,
([PrimType], PrimType, [PrimValue] -> Maybe PrimValue)))
-> (Int16 -> PrimValue)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue)
-> (Int16 -> IntValue) -> Int16 -> PrimValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int32 -> IntValue
Int32Value (Int32 -> IntValue) -> (Int16 -> Int32) -> Int16 -> IntValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> (Int16 -> Int) -> Int16 -> Int32
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int16 -> Int
forall a. Bits a => a -> Int
popCount,
String
-> (Int32 -> PrimValue)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a} {a}.
a
-> (Int32 -> a)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe a))
i32 String
"popc32" ((Int32 -> PrimValue)
-> (String,
([PrimType], PrimType, [PrimValue] -> Maybe PrimValue)))
-> (Int32 -> PrimValue)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue)
-> (Int32 -> IntValue) -> Int32 -> PrimValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int32 -> IntValue
Int32Value (Int32 -> IntValue) -> (Int32 -> Int32) -> Int32 -> IntValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> (Int32 -> Int) -> Int32 -> Int32
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int32 -> Int
forall a. Bits a => a -> Int
popCount,
String
-> (Int64 -> PrimValue)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a} {a}.
a
-> (Int64 -> a)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe a))
i64 String
"popc64" ((Int64 -> PrimValue)
-> (String,
([PrimType], PrimType, [PrimValue] -> Maybe PrimValue)))
-> (Int64 -> PrimValue)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue)
-> (Int64 -> IntValue) -> Int64 -> PrimValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int32 -> IntValue
Int32Value (Int32 -> IntValue) -> (Int64 -> Int32) -> Int64 -> IntValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> (Int64 -> Int) -> Int64 -> Int32
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int64 -> Int
forall a. Bits a => a -> Int
popCount,
String
-> (Int8 -> Int8 -> Int8 -> Int8)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Int8 -> Int8 -> Int8 -> Int8)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
i8_3 String
"umad_hi8" Int8 -> Int8 -> Int8 -> Int8
umad_hi8,
String
-> (Int16 -> Int16 -> Int16 -> Int16)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Int16 -> Int16 -> Int16 -> Int16)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
i16_3 String
"umad_hi16" Int16 -> Int16 -> Int16 -> Int16
umad_hi16,
String
-> (Int32 -> Int32 -> Int32 -> Int32)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Int32 -> Int32 -> Int32 -> Int32)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
i32_3 String
"umad_hi32" Int32 -> Int32 -> Int32 -> Int32
umad_hi32,
String
-> (Int64 -> Int64 -> Int64 -> Int64)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Int64 -> Int64 -> Int64 -> Int64)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
i64_3 String
"umad_hi64" Int64 -> Int64 -> Int64 -> Int64
umad_hi64,
String
-> (Int8 -> Int8 -> Int8)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Int8 -> Int8 -> Int8)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
i8_2 String
"umul_hi8" Int8 -> Int8 -> Int8
umul_hi8,
String
-> (Int16 -> Int16 -> Int16)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Int16 -> Int16 -> Int16)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
i16_2 String
"umul_hi16" Int16 -> Int16 -> Int16
umul_hi16,
String
-> (Int32 -> Int32 -> Int32)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Int32 -> Int32 -> Int32)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
i32_2 String
"umul_hi32" Int32 -> Int32 -> Int32
umul_hi32,
String
-> (Int64 -> Int64 -> Int64)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Int64 -> Int64 -> Int64)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
i64_2 String
"umul_hi64" Int64 -> Int64 -> Int64
umul_hi64,
String
-> (Int8 -> Int8 -> Int8 -> Int8)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Int8 -> Int8 -> Int8 -> Int8)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
i8_3 String
"smad_hi8" Int8 -> Int8 -> Int8 -> Int8
smad_hi8,
String
-> (Int16 -> Int16 -> Int16 -> Int16)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Int16 -> Int16 -> Int16 -> Int16)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
i16_3 String
"smad_hi16" Int16 -> Int16 -> Int16 -> Int16
smad_hi16,
String
-> (Int32 -> Int32 -> Int32 -> Int32)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Int32 -> Int32 -> Int32 -> Int32)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
i32_3 String
"smad_hi32" Int32 -> Int32 -> Int32 -> Int32
smad_hi32,
String
-> (Int64 -> Int64 -> Int64 -> Int64)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Int64 -> Int64 -> Int64 -> Int64)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
i64_3 String
"smad_hi64" Int64 -> Int64 -> Int64 -> Int64
smad_hi64,
String
-> (Int8 -> Int8 -> Int8)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Int8 -> Int8 -> Int8)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
i8_2 String
"smul_hi8" Int8 -> Int8 -> Int8
smul_hi8,
String
-> (Int16 -> Int16 -> Int16)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Int16 -> Int16 -> Int16)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
i16_2 String
"smul_hi16" Int16 -> Int16 -> Int16
smul_hi16,
String
-> (Int32 -> Int32 -> Int32)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Int32 -> Int32 -> Int32)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
i32_2 String
"smul_hi32" Int32 -> Int32 -> Int32
smul_hi32,
String
-> (Int64 -> Int64 -> Int64)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Int64 -> Int64 -> Int64)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
i64_2 String
"smul_hi64" Int64 -> Int64 -> Int64
smul_hi64,
( String
"atan2_16",
( [FloatType -> PrimType
FloatType FloatType
Float16, FloatType -> PrimType
FloatType FloatType
Float16],
FloatType -> PrimType
FloatType FloatType
Float16,
\case
[FloatValue (Float16Value Half
x), FloatValue (Float16Value Half
y)] ->
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Half -> FloatValue
Float16Value (Half -> FloatValue) -> Half -> FloatValue
forall a b. (a -> b) -> a -> b
$ Half -> Half -> Half
forall {a}. RealFloat a => a -> a -> a
atan2 Half
x Half
y
[PrimValue]
_ -> Maybe PrimValue
forall a. Maybe a
Nothing
)
),
( String
"atan2_32",
( [FloatType -> PrimType
FloatType FloatType
Float32, FloatType -> PrimType
FloatType FloatType
Float32],
FloatType -> PrimType
FloatType FloatType
Float32,
\case
[FloatValue (Float32Value Float
x), FloatValue (Float32Value Float
y)] ->
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Float -> FloatValue
Float32Value (Float -> FloatValue) -> Float -> FloatValue
forall a b. (a -> b) -> a -> b
$ Float -> Float -> Float
forall {a}. RealFloat a => a -> a -> a
atan2 Float
x Float
y
[PrimValue]
_ -> Maybe PrimValue
forall a. Maybe a
Nothing
)
),
( String
"atan2_64",
( [FloatType -> PrimType
FloatType FloatType
Float64, FloatType -> PrimType
FloatType FloatType
Float64],
FloatType -> PrimType
FloatType FloatType
Float64,
\case
[FloatValue (Float64Value Double
x), FloatValue (Float64Value Double
y)] ->
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Double -> FloatValue
Float64Value (Double -> FloatValue) -> Double -> FloatValue
forall a b. (a -> b) -> a -> b
$ Double -> Double -> Double
forall {a}. RealFloat a => a -> a -> a
atan2 Double
x Double
y
[PrimValue]
_ -> Maybe PrimValue
forall a. Maybe a
Nothing
)
),
( String
"hypot16",
( [FloatType -> PrimType
FloatType FloatType
Float16, FloatType -> PrimType
FloatType FloatType
Float16],
FloatType -> PrimType
FloatType FloatType
Float16,
\case
[FloatValue (Float16Value Half
x), FloatValue (Float16Value Half
y)] ->
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Half -> FloatValue
Float16Value (Half -> FloatValue) -> Half -> FloatValue
forall a b. (a -> b) -> a -> b
$ Float -> Half
forall from to. (RealFloat from, RealFloat to) => from -> to
convFloat (Float -> Half) -> Float -> Half
forall a b. (a -> b) -> a -> b
$ Float -> Float -> Float
hypotf (Half -> Float
forall from to. (RealFloat from, RealFloat to) => from -> to
convFloat Half
x) (Half -> Float
forall from to. (RealFloat from, RealFloat to) => from -> to
convFloat Half
y)
[PrimValue]
_ -> Maybe PrimValue
forall a. Maybe a
Nothing
)
),
( String
"hypot32",
( [FloatType -> PrimType
FloatType FloatType
Float32, FloatType -> PrimType
FloatType FloatType
Float32],
FloatType -> PrimType
FloatType FloatType
Float32,
\case
[FloatValue (Float32Value Float
x), FloatValue (Float32Value Float
y)] ->
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Float -> FloatValue
Float32Value (Float -> FloatValue) -> Float -> FloatValue
forall a b. (a -> b) -> a -> b
$ Float -> Float -> Float
hypotf Float
x Float
y
[PrimValue]
_ -> Maybe PrimValue
forall a. Maybe a
Nothing
)
),
( String
"hypot64",
( [FloatType -> PrimType
FloatType FloatType
Float64, FloatType -> PrimType
FloatType FloatType
Float64],
FloatType -> PrimType
FloatType FloatType
Float64,
\case
[FloatValue (Float64Value Double
x), FloatValue (Float64Value Double
y)] ->
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Double -> FloatValue
Float64Value (Double -> FloatValue) -> Double -> FloatValue
forall a b. (a -> b) -> a -> b
$ Double -> Double -> Double
hypot Double
x Double
y
[PrimValue]
_ -> Maybe PrimValue
forall a. Maybe a
Nothing
)
),
( String
"isinf16",
( [FloatType -> PrimType
FloatType FloatType
Float16],
PrimType
Bool,
\case
[FloatValue (Float16Value Half
x)] -> PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ Bool -> PrimValue
BoolValue (Bool -> PrimValue) -> Bool -> PrimValue
forall a b. (a -> b) -> a -> b
$ Half -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Half
x
[PrimValue]
_ -> Maybe PrimValue
forall a. Maybe a
Nothing
)
),
( String
"isinf32",
( [FloatType -> PrimType
FloatType FloatType
Float32],
PrimType
Bool,
\case
[FloatValue (Float32Value Float
x)] -> PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ Bool -> PrimValue
BoolValue (Bool -> PrimValue) -> Bool -> PrimValue
forall a b. (a -> b) -> a -> b
$ Float -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Float
x
[PrimValue]
_ -> Maybe PrimValue
forall a. Maybe a
Nothing
)
),
( String
"isinf64",
( [FloatType -> PrimType
FloatType FloatType
Float64],
PrimType
Bool,
\case
[FloatValue (Float64Value Double
x)] -> PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ Bool -> PrimValue
BoolValue (Bool -> PrimValue) -> Bool -> PrimValue
forall a b. (a -> b) -> a -> b
$ Double -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Double
x
[PrimValue]
_ -> Maybe PrimValue
forall a. Maybe a
Nothing
)
),
( String
"isnan16",
( [FloatType -> PrimType
FloatType FloatType
Float16],
PrimType
Bool,
\case
[FloatValue (Float16Value Half
x)] -> PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ Bool -> PrimValue
BoolValue (Bool -> PrimValue) -> Bool -> PrimValue
forall a b. (a -> b) -> a -> b
$ Half -> Bool
forall a. RealFloat a => a -> Bool
isNaN Half
x
[PrimValue]
_ -> Maybe PrimValue
forall a. Maybe a
Nothing
)
),
( String
"isnan32",
( [FloatType -> PrimType
FloatType FloatType
Float32],
PrimType
Bool,
\case
[FloatValue (Float32Value Float
x)] -> PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ Bool -> PrimValue
BoolValue (Bool -> PrimValue) -> Bool -> PrimValue
forall a b. (a -> b) -> a -> b
$ Float -> Bool
forall a. RealFloat a => a -> Bool
isNaN Float
x
[PrimValue]
_ -> Maybe PrimValue
forall a. Maybe a
Nothing
)
),
( String
"isnan64",
( [FloatType -> PrimType
FloatType FloatType
Float64],
PrimType
Bool,
\case
[FloatValue (Float64Value Double
x)] -> PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ Bool -> PrimValue
BoolValue (Bool -> PrimValue) -> Bool -> PrimValue
forall a b. (a -> b) -> a -> b
$ Double -> Bool
forall a. RealFloat a => a -> Bool
isNaN Double
x
[PrimValue]
_ -> Maybe PrimValue
forall a. Maybe a
Nothing
)
),
( String
"to_bits16",
( [FloatType -> PrimType
FloatType FloatType
Float16],
IntType -> PrimType
IntType IntType
Int16,
\case
[FloatValue (Float16Value Half
x)] ->
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Int16 -> IntValue
Int16Value (Int16 -> IntValue) -> Int16 -> IntValue
forall a b. (a -> b) -> a -> b
$ Word16 -> Int16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16 -> Int16) -> Word16 -> Int16
forall a b. (a -> b) -> a -> b
$ Half -> Word16
halfToWord Half
x
[PrimValue]
_ -> Maybe PrimValue
forall a. Maybe a
Nothing
)
),
( String
"to_bits32",
( [FloatType -> PrimType
FloatType FloatType
Float32],
IntType -> PrimType
IntType IntType
Int32,
\case
[FloatValue (Float32Value Float
x)] ->
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Int32 -> IntValue
Int32Value (Int32 -> IntValue) -> Int32 -> IntValue
forall a b. (a -> b) -> a -> b
$ Word32 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Int32) -> Word32 -> Int32
forall a b. (a -> b) -> a -> b
$ Float -> Word32
floatToWord Float
x
[PrimValue]
_ -> Maybe PrimValue
forall a. Maybe a
Nothing
)
),
( String
"to_bits64",
( [FloatType -> PrimType
FloatType FloatType
Float64],
IntType -> PrimType
IntType IntType
Int64,
\case
[FloatValue (Float64Value Double
x)] ->
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Int64 -> IntValue
Int64Value (Int64 -> IntValue) -> Int64 -> IntValue
forall a b. (a -> b) -> a -> b
$ Word64 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Int64) -> Word64 -> Int64
forall a b. (a -> b) -> a -> b
$ Double -> Word64
doubleToWord Double
x
[PrimValue]
_ -> Maybe PrimValue
forall a. Maybe a
Nothing
)
),
( String
"from_bits16",
( [IntType -> PrimType
IntType IntType
Int16],
FloatType -> PrimType
FloatType FloatType
Float16,
\case
[IntValue (Int16Value Int16
x)] ->
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Half -> FloatValue
Float16Value (Half -> FloatValue) -> Half -> FloatValue
forall a b. (a -> b) -> a -> b
$ Word16 -> Half
wordToHalf (Word16 -> Half) -> Word16 -> Half
forall a b. (a -> b) -> a -> b
$ Int16 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int16
x
[PrimValue]
_ -> Maybe PrimValue
forall a. Maybe a
Nothing
)
),
( String
"from_bits32",
( [IntType -> PrimType
IntType IntType
Int32],
FloatType -> PrimType
FloatType FloatType
Float32,
\case
[IntValue (Int32Value Int32
x)] ->
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Float -> FloatValue
Float32Value (Float -> FloatValue) -> Float -> FloatValue
forall a b. (a -> b) -> a -> b
$ Word32 -> Float
wordToFloat (Word32 -> Float) -> Word32 -> Float
forall a b. (a -> b) -> a -> b
$ Int32 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
x
[PrimValue]
_ -> Maybe PrimValue
forall a. Maybe a
Nothing
)
),
( String
"from_bits64",
( [IntType -> PrimType
IntType IntType
Int64],
FloatType -> PrimType
FloatType FloatType
Float64,
\case
[IntValue (Int64Value Int64
x)] ->
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Double -> FloatValue
Float64Value (Double -> FloatValue) -> Double -> FloatValue
forall a b. (a -> b) -> a -> b
$ Word64 -> Double
wordToDouble (Word64 -> Double) -> Word64 -> Double
forall a b. (a -> b) -> a -> b
$ Int64 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
x
[PrimValue]
_ -> Maybe PrimValue
forall a. Maybe a
Nothing
)
),
String
-> (Half -> Half -> Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half -> Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16_3 String
"lerp16" (\Half
v0 Half
v1 Half
t -> Half
v0 Half -> Half -> Half
forall a. Num a => a -> a -> a
+ (Half
v1 Half -> Half -> Half
forall a. Num a => a -> a -> a
- Half
v0) Half -> Half -> Half
forall a. Num a => a -> a -> a
* Half -> Half -> Half
forall a. Ord a => a -> a -> a
max Half
0 (Half -> Half -> Half
forall a. Ord a => a -> a -> a
min Half
1 Half
t)),
String
-> (Float -> Float -> Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float -> Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32_3 String
"lerp32" (\Float
v0 Float
v1 Float
t -> Float
v0 Float -> Float -> Float
forall a. Num a => a -> a -> a
+ (Float
v1 Float -> Float -> Float
forall a. Num a => a -> a -> a
- Float
v0) Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float -> Float -> Float
forall a. Ord a => a -> a -> a
max Float
0 (Float -> Float -> Float
forall a. Ord a => a -> a -> a
min Float
1 Float
t)),
String
-> (Double -> Double -> Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double -> Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64_3 String
"lerp64" (\Double
v0 Double
v1 Double
t -> Double
v0 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ (Double
v1 Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
v0) Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double -> Double -> Double
forall a. Ord a => a -> a -> a
max Double
0 (Double -> Double -> Double
forall a. Ord a => a -> a -> a
min Double
1 Double
t)),
String
-> (Half -> Half -> Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half -> Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16_3 String
"mad16" (\Half
a Half
b Half
c -> Half
a Half -> Half -> Half
forall a. Num a => a -> a -> a
* Half
b Half -> Half -> Half
forall a. Num a => a -> a -> a
+ Half
c),
String
-> (Float -> Float -> Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float -> Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32_3 String
"mad32" (\Float
a Float
b Float
c -> Float
a Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
b Float -> Float -> Float
forall a. Num a => a -> a -> a
+ Float
c),
String
-> (Double -> Double -> Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double -> Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64_3 String
"mad64" (\Double
a Double
b Double
c -> Double
a Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
b Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
c),
String
-> (Half -> Half -> Half -> Half)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Half -> Half -> Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16_3 String
"fma16" (\Half
a Half
b Half
c -> Half
a Half -> Half -> Half
forall a. Num a => a -> a -> a
* Half
b Half -> Half -> Half
forall a. Num a => a -> a -> a
+ Half
c),
String
-> (Float -> Float -> Float -> Float)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Float -> Float -> Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32_3 String
"fma32" (\Float
a Float
b Float
c -> Float
a Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
b Float -> Float -> Float
forall a. Num a => a -> a -> a
+ Float
c),
String
-> (Double -> Double -> Double -> Double)
-> (String, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {a}.
a
-> (Double -> Double -> Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64_3 String
"fma64" (\Double
a Double
b Double
c -> Double
a Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
b Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
c)
]
where
i8 :: a
-> (Int8 -> a)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe a))
i8 a
s Int8 -> a
f = (a
s, ([IntType -> PrimType
IntType IntType
Int8], IntType -> PrimType
IntType IntType
Int32, (Int8 -> a) -> [PrimValue] -> Maybe a
forall {a}. (Int8 -> a) -> [PrimValue] -> Maybe a
i8PrimFun Int8 -> a
f))
i16 :: a
-> (Int16 -> a)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe a))
i16 a
s Int16 -> a
f = (a
s, ([IntType -> PrimType
IntType IntType
Int16], IntType -> PrimType
IntType IntType
Int32, (Int16 -> a) -> [PrimValue] -> Maybe a
forall {a}. (Int16 -> a) -> [PrimValue] -> Maybe a
i16PrimFun Int16 -> a
f))
i32 :: a
-> (Int32 -> a)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe a))
i32 a
s Int32 -> a
f = (a
s, ([IntType -> PrimType
IntType IntType
Int32], IntType -> PrimType
IntType IntType
Int32, (Int32 -> a) -> [PrimValue] -> Maybe a
forall {a}. (Int32 -> a) -> [PrimValue] -> Maybe a
i32PrimFun Int32 -> a
f))
i64 :: a
-> (Int64 -> a)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe a))
i64 a
s Int64 -> a
f = (a
s, ([IntType -> PrimType
IntType IntType
Int64], IntType -> PrimType
IntType IntType
Int32, (Int64 -> a) -> [PrimValue] -> Maybe a
forall {a}. (Int64 -> a) -> [PrimValue] -> Maybe a
i64PrimFun Int64 -> a
f))
f16 :: a
-> (Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16 a
s Half -> Half
f = (a
s, ([FloatType -> PrimType
FloatType FloatType
Float16], FloatType -> PrimType
FloatType FloatType
Float16, (Half -> Half) -> [PrimValue] -> Maybe PrimValue
f16PrimFun Half -> Half
f))
f32 :: a
-> (Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32 a
s Float -> Float
f = (a
s, ([FloatType -> PrimType
FloatType FloatType
Float32], FloatType -> PrimType
FloatType FloatType
Float32, (Float -> Float) -> [PrimValue] -> Maybe PrimValue
f32PrimFun Float -> Float
f))
f64 :: a
-> (Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64 a
s Double -> Double
f = (a
s, ([FloatType -> PrimType
FloatType FloatType
Float64], FloatType -> PrimType
FloatType FloatType
Float64, (Double -> Double) -> [PrimValue] -> Maybe PrimValue
f64PrimFun Double -> Double
f))
t_2 :: b -> a -> c -> (a, ([b], b, c))
t_2 b
t a
s c
f = (a
s, ([b
t, b
t], b
t, c
f))
t_3 :: b -> a -> c -> (a, ([b], b, c))
t_3 b
t a
s c
f = (a
s, ([b
t, b
t, b
t], b
t, c
f))
f16_2 :: a
-> (Half -> Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16_2 a
s Half -> Half -> Half
f = PrimType
-> a
-> ([PrimValue] -> Maybe PrimValue)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {b} {a} {c}. b -> a -> c -> (a, ([b], b, c))
t_2 (FloatType -> PrimType
FloatType FloatType
Float16) a
s ((Half -> Half -> Half) -> [PrimValue] -> Maybe PrimValue
f16PrimFun2 Half -> Half -> Half
f)
f32_2 :: a
-> (Float -> Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32_2 a
s Float -> Float -> Float
f = PrimType
-> a
-> ([PrimValue] -> Maybe PrimValue)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {b} {a} {c}. b -> a -> c -> (a, ([b], b, c))
t_2 (FloatType -> PrimType
FloatType FloatType
Float32) a
s ((Float -> Float -> Float) -> [PrimValue] -> Maybe PrimValue
f32PrimFun2 Float -> Float -> Float
f)
f64_2 :: a
-> (Double -> Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64_2 a
s Double -> Double -> Double
f = PrimType
-> a
-> ([PrimValue] -> Maybe PrimValue)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {b} {a} {c}. b -> a -> c -> (a, ([b], b, c))
t_2 (FloatType -> PrimType
FloatType FloatType
Float64) a
s ((Double -> Double -> Double) -> [PrimValue] -> Maybe PrimValue
f64PrimFun2 Double -> Double -> Double
f)
f16_3 :: a
-> (Half -> Half -> Half -> Half)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f16_3 a
s Half -> Half -> Half -> Half
f = PrimType
-> a
-> ([PrimValue] -> Maybe PrimValue)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {b} {a} {c}. b -> a -> c -> (a, ([b], b, c))
t_3 (FloatType -> PrimType
FloatType FloatType
Float16) a
s ((Half -> Half -> Half -> Half) -> [PrimValue] -> Maybe PrimValue
f16PrimFun3 Half -> Half -> Half -> Half
f)
f32_3 :: a
-> (Float -> Float -> Float -> Float)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f32_3 a
s Float -> Float -> Float -> Float
f = PrimType
-> a
-> ([PrimValue] -> Maybe PrimValue)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {b} {a} {c}. b -> a -> c -> (a, ([b], b, c))
t_3 (FloatType -> PrimType
FloatType FloatType
Float32) a
s ((Float -> Float -> Float -> Float)
-> [PrimValue] -> Maybe PrimValue
f32PrimFun3 Float -> Float -> Float -> Float
f)
f64_3 :: a
-> (Double -> Double -> Double -> Double)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
f64_3 a
s Double -> Double -> Double -> Double
f = PrimType
-> a
-> ([PrimValue] -> Maybe PrimValue)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {b} {a} {c}. b -> a -> c -> (a, ([b], b, c))
t_3 (FloatType -> PrimType
FloatType FloatType
Float64) a
s ((Double -> Double -> Double -> Double)
-> [PrimValue] -> Maybe PrimValue
f64PrimFun3 Double -> Double -> Double -> Double
f)
i8_2 :: a
-> (Int8 -> Int8 -> Int8)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
i8_2 a
s Int8 -> Int8 -> Int8
f = PrimType
-> a
-> ([PrimValue] -> Maybe PrimValue)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {b} {a} {c}. b -> a -> c -> (a, ([b], b, c))
t_2 (IntType -> PrimType
IntType IntType
Int8) a
s ((Int8 -> Int8 -> Int8) -> [PrimValue] -> Maybe PrimValue
i8PrimFun2 Int8 -> Int8 -> Int8
f)
i16_2 :: a
-> (Int16 -> Int16 -> Int16)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
i16_2 a
s Int16 -> Int16 -> Int16
f = PrimType
-> a
-> ([PrimValue] -> Maybe PrimValue)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {b} {a} {c}. b -> a -> c -> (a, ([b], b, c))
t_2 (IntType -> PrimType
IntType IntType
Int16) a
s ((Int16 -> Int16 -> Int16) -> [PrimValue] -> Maybe PrimValue
i16PrimFun2 Int16 -> Int16 -> Int16
f)
i32_2 :: a
-> (Int32 -> Int32 -> Int32)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
i32_2 a
s Int32 -> Int32 -> Int32
f = PrimType
-> a
-> ([PrimValue] -> Maybe PrimValue)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {b} {a} {c}. b -> a -> c -> (a, ([b], b, c))
t_2 (IntType -> PrimType
IntType IntType
Int32) a
s ((Int32 -> Int32 -> Int32) -> [PrimValue] -> Maybe PrimValue
i32PrimFun2 Int32 -> Int32 -> Int32
f)
i64_2 :: a
-> (Int64 -> Int64 -> Int64)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
i64_2 a
s Int64 -> Int64 -> Int64
f = PrimType
-> a
-> ([PrimValue] -> Maybe PrimValue)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {b} {a} {c}. b -> a -> c -> (a, ([b], b, c))
t_2 (IntType -> PrimType
IntType IntType
Int64) a
s ((Int64 -> Int64 -> Int64) -> [PrimValue] -> Maybe PrimValue
i64PrimFun2 Int64 -> Int64 -> Int64
f)
i8_3 :: a
-> (Int8 -> Int8 -> Int8 -> Int8)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
i8_3 a
s Int8 -> Int8 -> Int8 -> Int8
f = PrimType
-> a
-> ([PrimValue] -> Maybe PrimValue)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {b} {a} {c}. b -> a -> c -> (a, ([b], b, c))
t_3 (IntType -> PrimType
IntType IntType
Int8) a
s ((Int8 -> Int8 -> Int8 -> Int8) -> [PrimValue] -> Maybe PrimValue
i8PrimFun3 Int8 -> Int8 -> Int8 -> Int8
f)
i16_3 :: a
-> (Int16 -> Int16 -> Int16 -> Int16)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
i16_3 a
s Int16 -> Int16 -> Int16 -> Int16
f = PrimType
-> a
-> ([PrimValue] -> Maybe PrimValue)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {b} {a} {c}. b -> a -> c -> (a, ([b], b, c))
t_3 (IntType -> PrimType
IntType IntType
Int16) a
s ((Int16 -> Int16 -> Int16 -> Int16)
-> [PrimValue] -> Maybe PrimValue
i16PrimFun3 Int16 -> Int16 -> Int16 -> Int16
f)
i32_3 :: a
-> (Int32 -> Int32 -> Int32 -> Int32)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
i32_3 a
s Int32 -> Int32 -> Int32 -> Int32
f = PrimType
-> a
-> ([PrimValue] -> Maybe PrimValue)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {b} {a} {c}. b -> a -> c -> (a, ([b], b, c))
t_3 (IntType -> PrimType
IntType IntType
Int32) a
s ((Int32 -> Int32 -> Int32 -> Int32)
-> [PrimValue] -> Maybe PrimValue
i32PrimFun3 Int32 -> Int32 -> Int32 -> Int32
f)
i64_3 :: a
-> (Int64 -> Int64 -> Int64 -> Int64)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
i64_3 a
s Int64 -> Int64 -> Int64 -> Int64
f = PrimType
-> a
-> ([PrimValue] -> Maybe PrimValue)
-> (a, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
forall {b} {a} {c}. b -> a -> c -> (a, ([b], b, c))
t_3 (IntType -> PrimType
IntType IntType
Int64) a
s ((Int64 -> Int64 -> Int64 -> Int64)
-> [PrimValue] -> Maybe PrimValue
i64PrimFun3 Int64 -> Int64 -> Int64 -> Int64
f)
i8PrimFun :: (Int8 -> a) -> [PrimValue] -> Maybe a
i8PrimFun Int8 -> a
f [IntValue (Int8Value Int8
x)] = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Int8 -> a
f Int8
x
i8PrimFun Int8 -> a
_ [PrimValue]
_ = Maybe a
forall a. Maybe a
Nothing
i16PrimFun :: (Int16 -> a) -> [PrimValue] -> Maybe a
i16PrimFun Int16 -> a
f [IntValue (Int16Value Int16
x)] = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Int16 -> a
f Int16
x
i16PrimFun Int16 -> a
_ [PrimValue]
_ = Maybe a
forall a. Maybe a
Nothing
i32PrimFun :: (Int32 -> a) -> [PrimValue] -> Maybe a
i32PrimFun Int32 -> a
f [IntValue (Int32Value Int32
x)] = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Int32 -> a
f Int32
x
i32PrimFun Int32 -> a
_ [PrimValue]
_ = Maybe a
forall a. Maybe a
Nothing
i64PrimFun :: (Int64 -> a) -> [PrimValue] -> Maybe a
i64PrimFun Int64 -> a
f [IntValue (Int64Value Int64
x)] = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Int64 -> a
f Int64
x
i64PrimFun Int64 -> a
_ [PrimValue]
_ = Maybe a
forall a. Maybe a
Nothing
f16PrimFun :: (Half -> Half) -> [PrimValue] -> Maybe PrimValue
f16PrimFun Half -> Half
f [FloatValue (Float16Value Half
x)] =
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Half -> FloatValue
Float16Value (Half -> FloatValue) -> Half -> FloatValue
forall a b. (a -> b) -> a -> b
$ Half -> Half
f Half
x
f16PrimFun Half -> Half
_ [PrimValue]
_ = Maybe PrimValue
forall a. Maybe a
Nothing
f32PrimFun :: (Float -> Float) -> [PrimValue] -> Maybe PrimValue
f32PrimFun Float -> Float
f [FloatValue (Float32Value Float
x)] =
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Float -> FloatValue
Float32Value (Float -> FloatValue) -> Float -> FloatValue
forall a b. (a -> b) -> a -> b
$ Float -> Float
f Float
x
f32PrimFun Float -> Float
_ [PrimValue]
_ = Maybe PrimValue
forall a. Maybe a
Nothing
f64PrimFun :: (Double -> Double) -> [PrimValue] -> Maybe PrimValue
f64PrimFun Double -> Double
f [FloatValue (Float64Value Double
x)] =
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Double -> FloatValue
Float64Value (Double -> FloatValue) -> Double -> FloatValue
forall a b. (a -> b) -> a -> b
$ Double -> Double
f Double
x
f64PrimFun Double -> Double
_ [PrimValue]
_ = Maybe PrimValue
forall a. Maybe a
Nothing
f16PrimFun2 :: (Half -> Half -> Half) -> [PrimValue] -> Maybe PrimValue
f16PrimFun2
Half -> Half -> Half
f
[ FloatValue (Float16Value Half
a),
FloatValue (Float16Value Half
b)
] =
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Half -> FloatValue
Float16Value (Half -> FloatValue) -> Half -> FloatValue
forall a b. (a -> b) -> a -> b
$ Half -> Half -> Half
f Half
a Half
b
f16PrimFun2 Half -> Half -> Half
_ [PrimValue]
_ = Maybe PrimValue
forall a. Maybe a
Nothing
f32PrimFun2 :: (Float -> Float -> Float) -> [PrimValue] -> Maybe PrimValue
f32PrimFun2
Float -> Float -> Float
f
[ FloatValue (Float32Value Float
a),
FloatValue (Float32Value Float
b)
] =
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Float -> FloatValue
Float32Value (Float -> FloatValue) -> Float -> FloatValue
forall a b. (a -> b) -> a -> b
$ Float -> Float -> Float
f Float
a Float
b
f32PrimFun2 Float -> Float -> Float
_ [PrimValue]
_ = Maybe PrimValue
forall a. Maybe a
Nothing
f64PrimFun2 :: (Double -> Double -> Double) -> [PrimValue] -> Maybe PrimValue
f64PrimFun2
Double -> Double -> Double
f
[ FloatValue (Float64Value Double
a),
FloatValue (Float64Value Double
b)
] =
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Double -> FloatValue
Float64Value (Double -> FloatValue) -> Double -> FloatValue
forall a b. (a -> b) -> a -> b
$ Double -> Double -> Double
f Double
a Double
b
f64PrimFun2 Double -> Double -> Double
_ [PrimValue]
_ = Maybe PrimValue
forall a. Maybe a
Nothing
f16PrimFun3 :: (Half -> Half -> Half -> Half) -> [PrimValue] -> Maybe PrimValue
f16PrimFun3
Half -> Half -> Half -> Half
f
[ FloatValue (Float16Value Half
a),
FloatValue (Float16Value Half
b),
FloatValue (Float16Value Half
c)
] =
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Half -> FloatValue
Float16Value (Half -> FloatValue) -> Half -> FloatValue
forall a b. (a -> b) -> a -> b
$ Half -> Half -> Half -> Half
f Half
a Half
b Half
c
f16PrimFun3 Half -> Half -> Half -> Half
_ [PrimValue]
_ = Maybe PrimValue
forall a. Maybe a
Nothing
f32PrimFun3 :: (Float -> Float -> Float -> Float)
-> [PrimValue] -> Maybe PrimValue
f32PrimFun3
Float -> Float -> Float -> Float
f
[ FloatValue (Float32Value Float
a),
FloatValue (Float32Value Float
b),
FloatValue (Float32Value Float
c)
] =
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Float -> FloatValue
Float32Value (Float -> FloatValue) -> Float -> FloatValue
forall a b. (a -> b) -> a -> b
$ Float -> Float -> Float -> Float
f Float
a Float
b Float
c
f32PrimFun3 Float -> Float -> Float -> Float
_ [PrimValue]
_ = Maybe PrimValue
forall a. Maybe a
Nothing
f64PrimFun3 :: (Double -> Double -> Double -> Double)
-> [PrimValue] -> Maybe PrimValue
f64PrimFun3
Double -> Double -> Double -> Double
f
[ FloatValue (Float64Value Double
a),
FloatValue (Float64Value Double
b),
FloatValue (Float64Value Double
c)
] =
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ FloatValue -> PrimValue
FloatValue (FloatValue -> PrimValue) -> FloatValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Double -> FloatValue
Float64Value (Double -> FloatValue) -> Double -> FloatValue
forall a b. (a -> b) -> a -> b
$ Double -> Double -> Double -> Double
f Double
a Double
b Double
c
f64PrimFun3 Double -> Double -> Double -> Double
_ [PrimValue]
_ = Maybe PrimValue
forall a. Maybe a
Nothing
i8PrimFun2 :: (Int8 -> Int8 -> Int8) -> [PrimValue] -> Maybe PrimValue
i8PrimFun2
Int8 -> Int8 -> Int8
f
[IntValue (Int8Value Int8
a), IntValue (Int8Value Int8
b)] =
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Int8 -> IntValue
Int8Value (Int8 -> IntValue) -> Int8 -> IntValue
forall a b. (a -> b) -> a -> b
$ Int8 -> Int8 -> Int8
f Int8
a Int8
b
i8PrimFun2 Int8 -> Int8 -> Int8
_ [PrimValue]
_ = Maybe PrimValue
forall a. Maybe a
Nothing
i16PrimFun2 :: (Int16 -> Int16 -> Int16) -> [PrimValue] -> Maybe PrimValue
i16PrimFun2
Int16 -> Int16 -> Int16
f
[IntValue (Int16Value Int16
a), IntValue (Int16Value Int16
b)] =
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Int16 -> IntValue
Int16Value (Int16 -> IntValue) -> Int16 -> IntValue
forall a b. (a -> b) -> a -> b
$ Int16 -> Int16 -> Int16
f Int16
a Int16
b
i16PrimFun2 Int16 -> Int16 -> Int16
_ [PrimValue]
_ = Maybe PrimValue
forall a. Maybe a
Nothing
i32PrimFun2 :: (Int32 -> Int32 -> Int32) -> [PrimValue] -> Maybe PrimValue
i32PrimFun2
Int32 -> Int32 -> Int32
f
[IntValue (Int32Value Int32
a), IntValue (Int32Value Int32
b)] =
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Int32 -> IntValue
Int32Value (Int32 -> IntValue) -> Int32 -> IntValue
forall a b. (a -> b) -> a -> b
$ Int32 -> Int32 -> Int32
f Int32
a Int32
b
i32PrimFun2 Int32 -> Int32 -> Int32
_ [PrimValue]
_ = Maybe PrimValue
forall a. Maybe a
Nothing
i64PrimFun2 :: (Int64 -> Int64 -> Int64) -> [PrimValue] -> Maybe PrimValue
i64PrimFun2
Int64 -> Int64 -> Int64
f
[IntValue (Int64Value Int64
a), IntValue (Int64Value Int64
b)] =
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Int64 -> IntValue
Int64Value (Int64 -> IntValue) -> Int64 -> IntValue
forall a b. (a -> b) -> a -> b
$ Int64 -> Int64 -> Int64
f Int64
a Int64
b
i64PrimFun2 Int64 -> Int64 -> Int64
_ [PrimValue]
_ = Maybe PrimValue
forall a. Maybe a
Nothing
i8PrimFun3 :: (Int8 -> Int8 -> Int8 -> Int8) -> [PrimValue] -> Maybe PrimValue
i8PrimFun3
Int8 -> Int8 -> Int8 -> Int8
f
[IntValue (Int8Value Int8
a), IntValue (Int8Value Int8
b), IntValue (Int8Value Int8
c)] =
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Int8 -> IntValue
Int8Value (Int8 -> IntValue) -> Int8 -> IntValue
forall a b. (a -> b) -> a -> b
$ Int8 -> Int8 -> Int8 -> Int8
f Int8
a Int8
b Int8
c
i8PrimFun3 Int8 -> Int8 -> Int8 -> Int8
_ [PrimValue]
_ = Maybe PrimValue
forall a. Maybe a
Nothing
i16PrimFun3 :: (Int16 -> Int16 -> Int16 -> Int16)
-> [PrimValue] -> Maybe PrimValue
i16PrimFun3
Int16 -> Int16 -> Int16 -> Int16
f
[IntValue (Int16Value Int16
a), IntValue (Int16Value Int16
b), IntValue (Int16Value Int16
c)] =
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Int16 -> IntValue
Int16Value (Int16 -> IntValue) -> Int16 -> IntValue
forall a b. (a -> b) -> a -> b
$ Int16 -> Int16 -> Int16 -> Int16
f Int16
a Int16
b Int16
c
i16PrimFun3 Int16 -> Int16 -> Int16 -> Int16
_ [PrimValue]
_ = Maybe PrimValue
forall a. Maybe a
Nothing
i32PrimFun3 :: (Int32 -> Int32 -> Int32 -> Int32)
-> [PrimValue] -> Maybe PrimValue
i32PrimFun3
Int32 -> Int32 -> Int32 -> Int32
f
[IntValue (Int32Value Int32
a), IntValue (Int32Value Int32
b), IntValue (Int32Value Int32
c)] =
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Int32 -> IntValue
Int32Value (Int32 -> IntValue) -> Int32 -> IntValue
forall a b. (a -> b) -> a -> b
$ Int32 -> Int32 -> Int32 -> Int32
f Int32
a Int32
b Int32
c
i32PrimFun3 Int32 -> Int32 -> Int32 -> Int32
_ [PrimValue]
_ = Maybe PrimValue
forall a. Maybe a
Nothing
i64PrimFun3 :: (Int64 -> Int64 -> Int64 -> Int64)
-> [PrimValue] -> Maybe PrimValue
i64PrimFun3
Int64 -> Int64 -> Int64 -> Int64
f
[IntValue (Int64Value Int64
a), IntValue (Int64Value Int64
b), IntValue (Int64Value Int64
c)] =
PrimValue -> Maybe PrimValue
forall a. a -> Maybe a
Just (PrimValue -> Maybe PrimValue) -> PrimValue -> Maybe PrimValue
forall a b. (a -> b) -> a -> b
$ IntValue -> PrimValue
IntValue (IntValue -> PrimValue) -> IntValue -> PrimValue
forall a b. (a -> b) -> a -> b
$ Int64 -> IntValue
Int64Value (Int64 -> IntValue) -> Int64 -> IntValue
forall a b. (a -> b) -> a -> b
$ Int64 -> Int64 -> Int64 -> Int64
f Int64
a Int64
b Int64
c
i64PrimFun3 Int64 -> Int64 -> Int64 -> Int64
_ [PrimValue]
_ = Maybe PrimValue
forall a. Maybe a
Nothing
zeroIsh :: PrimValue -> Bool
zeroIsh :: PrimValue -> Bool
zeroIsh (IntValue IntValue
k) = IntValue -> Bool
zeroIshInt IntValue
k
zeroIsh (FloatValue (Float16Value Half
k)) = Half
k Half -> Half -> Bool
forall a. Eq a => a -> a -> Bool
== Half
0
zeroIsh (FloatValue (Float32Value Float
k)) = Float
k Float -> Float -> Bool
forall a. Eq a => a -> a -> Bool
== Float
0
zeroIsh (FloatValue (Float64Value Double
k)) = Double
k Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
0
zeroIsh (BoolValue Bool
False) = Bool
True
zeroIsh PrimValue
_ = Bool
False
oneIsh :: PrimValue -> Bool
oneIsh :: PrimValue -> Bool
oneIsh (IntValue IntValue
k) = IntValue -> Bool
oneIshInt IntValue
k
oneIsh (FloatValue (Float16Value Half
k)) = Half
k Half -> Half -> Bool
forall a. Eq a => a -> a -> Bool
== Half
1
oneIsh (FloatValue (Float32Value Float
k)) = Float
k Float -> Float -> Bool
forall a. Eq a => a -> a -> Bool
== Float
1
oneIsh (FloatValue (Float64Value Double
k)) = Double
k Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
1
oneIsh (BoolValue Bool
True) = Bool
True
oneIsh PrimValue
_ = Bool
False
negativeIsh :: PrimValue -> Bool
negativeIsh :: PrimValue -> Bool
negativeIsh (IntValue IntValue
k) = IntValue -> Bool
negativeIshInt IntValue
k
negativeIsh (FloatValue (Float16Value Half
k)) = Half
k Half -> Half -> Bool
forall a. Ord a => a -> a -> Bool
< Half
0
negativeIsh (FloatValue (Float32Value Float
k)) = Float
k Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
< Float
0
negativeIsh (FloatValue (Float64Value Double
k)) = Double
k Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
0
negativeIsh (BoolValue Bool
_) = Bool
False
negativeIsh PrimValue
UnitValue = Bool
False
zeroIshInt :: IntValue -> Bool
zeroIshInt :: IntValue -> Bool
zeroIshInt (Int8Value Int8
k) = Int8
k Int8 -> Int8 -> Bool
forall a. Eq a => a -> a -> Bool
== Int8
0
zeroIshInt (Int16Value Int16
k) = Int16
k Int16 -> Int16 -> Bool
forall a. Eq a => a -> a -> Bool
== Int16
0
zeroIshInt (Int32Value Int32
k) = Int32
k Int32 -> Int32 -> Bool
forall a. Eq a => a -> a -> Bool
== Int32
0
zeroIshInt (Int64Value Int64
k) = Int64
k Int64 -> Int64 -> Bool
forall a. Eq a => a -> a -> Bool
== Int64
0
oneIshInt :: IntValue -> Bool
oneIshInt :: IntValue -> Bool
oneIshInt (Int8Value Int8
k) = Int8
k Int8 -> Int8 -> Bool
forall a. Eq a => a -> a -> Bool
== Int8
1
oneIshInt (Int16Value Int16
k) = Int16
k Int16 -> Int16 -> Bool
forall a. Eq a => a -> a -> Bool
== Int16
1
oneIshInt (Int32Value Int32
k) = Int32
k Int32 -> Int32 -> Bool
forall a. Eq a => a -> a -> Bool
== Int32
1
oneIshInt (Int64Value Int64
k) = Int64
k Int64 -> Int64 -> Bool
forall a. Eq a => a -> a -> Bool
== Int64
1
negativeIshInt :: IntValue -> Bool
negativeIshInt :: IntValue -> Bool
negativeIshInt (Int8Value Int8
k) = Int8
k Int8 -> Int8 -> Bool
forall a. Ord a => a -> a -> Bool
< Int8
0
negativeIshInt (Int16Value Int16
k) = Int16
k Int16 -> Int16 -> Bool
forall a. Ord a => a -> a -> Bool
< Int16
0
negativeIshInt (Int32Value Int32
k) = Int32
k Int32 -> Int32 -> Bool
forall a. Ord a => a -> a -> Bool
< Int32
0
negativeIshInt (Int64Value Int64
k) = Int64
k Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< Int64
0
primBitSize :: PrimType -> Int
primBitSize :: PrimType -> Int
primBitSize = (Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8) (Int -> Int) -> (PrimType -> Int) -> PrimType -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. PrimType -> Int
forall a. Num a => PrimType -> a
primByteSize
primByteSize :: Num a => PrimType -> a
primByteSize :: forall a. Num a => PrimType -> a
primByteSize (IntType IntType
t) = IntType -> a
forall a. Num a => IntType -> a
intByteSize IntType
t
primByteSize (FloatType FloatType
t) = FloatType -> a
forall a. Num a => FloatType -> a
floatByteSize FloatType
t
primByteSize PrimType
Bool = a
1
primByteSize PrimType
Unit = a
0
intByteSize :: Num a => IntType -> a
intByteSize :: forall a. Num a => IntType -> a
intByteSize IntType
Int8 = a
1
intByteSize IntType
Int16 = a
2
intByteSize IntType
Int32 = a
4
intByteSize IntType
Int64 = a
8
floatByteSize :: Num a => FloatType -> a
floatByteSize :: forall a. Num a => FloatType -> a
floatByteSize FloatType
Float16 = a
2
floatByteSize FloatType
Float32 = a
4
floatByteSize FloatType
Float64 = a
8
commutativeBinOp :: BinOp -> Bool
commutativeBinOp :: BinOp -> Bool
commutativeBinOp Add {} = Bool
True
commutativeBinOp FAdd {} = Bool
True
commutativeBinOp Mul {} = Bool
True
commutativeBinOp FMul {} = Bool
True
commutativeBinOp And {} = Bool
True
commutativeBinOp Or {} = Bool
True
commutativeBinOp Xor {} = Bool
True
commutativeBinOp LogOr {} = Bool
True
commutativeBinOp LogAnd {} = Bool
True
commutativeBinOp SMax {} = Bool
True
commutativeBinOp SMin {} = Bool
True
commutativeBinOp UMax {} = Bool
True
commutativeBinOp UMin {} = Bool
True
commutativeBinOp FMax {} = Bool
True
commutativeBinOp FMin {} = Bool
True
commutativeBinOp BinOp
_ = Bool
False
associativeBinOp :: BinOp -> Bool
associativeBinOp :: BinOp -> Bool
associativeBinOp Add {} = Bool
True
associativeBinOp Mul {} = Bool
True
associativeBinOp And {} = Bool
True
associativeBinOp Or {} = Bool
True
associativeBinOp Xor {} = Bool
True
associativeBinOp LogOr {} = Bool
True
associativeBinOp LogAnd {} = Bool
True
associativeBinOp SMax {} = Bool
True
associativeBinOp SMin {} = Bool
True
associativeBinOp UMax {} = Bool
True
associativeBinOp UMin {} = Bool
True
associativeBinOp FMax {} = Bool
True
associativeBinOp FMin {} = Bool
True
associativeBinOp BinOp
_ = Bool
False
instance Pretty BinOp where
pretty :: forall ann. BinOp -> Doc ann
pretty (Add IntType
t Overflow
OverflowWrap) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"add" IntType
t
pretty (Add IntType
t Overflow
OverflowUndef) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"add_nw" IntType
t
pretty (Sub IntType
t Overflow
OverflowWrap) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"sub" IntType
t
pretty (Sub IntType
t Overflow
OverflowUndef) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"sub_nw" IntType
t
pretty (Mul IntType
t Overflow
OverflowWrap) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"mul" IntType
t
pretty (Mul IntType
t Overflow
OverflowUndef) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"mul_nw" IntType
t
pretty (FAdd FloatType
t) = String -> FloatType -> Doc ann
forall a. String -> FloatType -> Doc a
taggedF String
"fadd" FloatType
t
pretty (FSub FloatType
t) = String -> FloatType -> Doc ann
forall a. String -> FloatType -> Doc a
taggedF String
"fsub" FloatType
t
pretty (FMul FloatType
t) = String -> FloatType -> Doc ann
forall a. String -> FloatType -> Doc a
taggedF String
"fmul" FloatType
t
pretty (UDiv IntType
t Safety
Safe) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"udiv_safe" IntType
t
pretty (UDiv IntType
t Safety
Unsafe) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"udiv" IntType
t
pretty (UDivUp IntType
t Safety
Safe) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"udiv_up_safe" IntType
t
pretty (UDivUp IntType
t Safety
Unsafe) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"udiv_up" IntType
t
pretty (UMod IntType
t Safety
Safe) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"umod_safe" IntType
t
pretty (UMod IntType
t Safety
Unsafe) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"umod" IntType
t
pretty (SDiv IntType
t Safety
Safe) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"sdiv_safe" IntType
t
pretty (SDiv IntType
t Safety
Unsafe) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"sdiv" IntType
t
pretty (SDivUp IntType
t Safety
Safe) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"sdiv_up_safe" IntType
t
pretty (SDivUp IntType
t Safety
Unsafe) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"sdiv_up" IntType
t
pretty (SMod IntType
t Safety
Safe) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"smod_safe" IntType
t
pretty (SMod IntType
t Safety
Unsafe) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"smod" IntType
t
pretty (SQuot IntType
t Safety
Safe) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"squot_safe" IntType
t
pretty (SQuot IntType
t Safety
Unsafe) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"squot" IntType
t
pretty (SRem IntType
t Safety
Safe) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"srem_safe" IntType
t
pretty (SRem IntType
t Safety
Unsafe) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"srem" IntType
t
pretty (FDiv FloatType
t) = String -> FloatType -> Doc ann
forall a. String -> FloatType -> Doc a
taggedF String
"fdiv" FloatType
t
pretty (FMod FloatType
t) = String -> FloatType -> Doc ann
forall a. String -> FloatType -> Doc a
taggedF String
"fmod" FloatType
t
pretty (SMin IntType
t) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"smin" IntType
t
pretty (UMin IntType
t) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"umin" IntType
t
pretty (FMin FloatType
t) = String -> FloatType -> Doc ann
forall a. String -> FloatType -> Doc a
taggedF String
"fmin" FloatType
t
pretty (SMax IntType
t) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"smax" IntType
t
pretty (UMax IntType
t) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"umax" IntType
t
pretty (FMax FloatType
t) = String -> FloatType -> Doc ann
forall a. String -> FloatType -> Doc a
taggedF String
"fmax" FloatType
t
pretty (Shl IntType
t) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"shl" IntType
t
pretty (LShr IntType
t) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"lshr" IntType
t
pretty (AShr IntType
t) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"ashr" IntType
t
pretty (And IntType
t) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"and" IntType
t
pretty (Or IntType
t) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"or" IntType
t
pretty (Xor IntType
t) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"xor" IntType
t
pretty (Pow IntType
t) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"pow" IntType
t
pretty (FPow FloatType
t) = String -> FloatType -> Doc ann
forall a. String -> FloatType -> Doc a
taggedF String
"fpow" FloatType
t
pretty BinOp
LogAnd = Doc ann
"logand"
pretty BinOp
LogOr = Doc ann
"logor"
instance Pretty CmpOp where
pretty :: forall ann. CmpOp -> Doc ann
pretty (CmpEq PrimType
t) = Doc ann
"eq_" Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> PrimType -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. PrimType -> Doc ann
pretty PrimType
t
pretty (CmpUlt IntType
t) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"ult" IntType
t
pretty (CmpUle IntType
t) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"ule" IntType
t
pretty (CmpSlt IntType
t) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"slt" IntType
t
pretty (CmpSle IntType
t) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"sle" IntType
t
pretty (FCmpLt FloatType
t) = String -> FloatType -> Doc ann
forall a. String -> FloatType -> Doc a
taggedF String
"lt" FloatType
t
pretty (FCmpLe FloatType
t) = String -> FloatType -> Doc ann
forall a. String -> FloatType -> Doc a
taggedF String
"le" FloatType
t
pretty CmpOp
CmpLlt = Doc ann
"llt"
pretty CmpOp
CmpLle = Doc ann
"lle"
instance Pretty ConvOp where
pretty :: forall ann. ConvOp -> Doc ann
pretty ConvOp
op = String -> PrimType -> PrimType -> Doc ann
forall from to a.
(Pretty from, Pretty to) =>
String -> from -> to -> Doc a
convOp (ConvOp -> String
convOpFun ConvOp
op) PrimType
from PrimType
to
where
(PrimType
from, PrimType
to) = ConvOp -> (PrimType, PrimType)
convOpType ConvOp
op
instance Pretty UnOp where
pretty :: forall ann. UnOp -> Doc ann
pretty UnOp
Not = Doc ann
"not"
pretty (Abs IntType
t) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"abs" IntType
t
pretty (FAbs FloatType
t) = String -> FloatType -> Doc ann
forall a. String -> FloatType -> Doc a
taggedF String
"fabs" FloatType
t
pretty (SSignum IntType
t) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"ssignum" IntType
t
pretty (USignum IntType
t) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"usignum" IntType
t
pretty (FSignum FloatType
t) = String -> FloatType -> Doc ann
forall a. String -> FloatType -> Doc a
taggedF String
"fsignum" FloatType
t
pretty (Complement IntType
t) = String -> IntType -> Doc ann
forall a. String -> IntType -> Doc a
taggedI String
"complement" IntType
t
convOpFun :: ConvOp -> String
convOpFun :: ConvOp -> String
convOpFun ZExt {} = String
"zext"
convOpFun SExt {} = String
"sext"
convOpFun FPConv {} = String
"fpconv"
convOpFun FPToUI {} = String
"fptoui"
convOpFun FPToSI {} = String
"fptosi"
convOpFun UIToFP {} = String
"uitofp"
convOpFun SIToFP {} = String
"sitofp"
convOpFun IToB {} = String
"itob"
convOpFun BToI {} = String
"btoi"
convOpFun FToB {} = String
"ftob"
convOpFun BToF {} = String
"btof"
taggedI :: String -> IntType -> Doc a
taggedI :: forall a. String -> IntType -> Doc a
taggedI String
s IntType
Int8 = String -> Doc a
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (String -> Doc a) -> String -> Doc a
forall a b. (a -> b) -> a -> b
$ String
s String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"8"
taggedI String
s IntType
Int16 = String -> Doc a
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (String -> Doc a) -> String -> Doc a
forall a b. (a -> b) -> a -> b
$ String
s String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"16"
taggedI String
s IntType
Int32 = String -> Doc a
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (String -> Doc a) -> String -> Doc a
forall a b. (a -> b) -> a -> b
$ String
s String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"32"
taggedI String
s IntType
Int64 = String -> Doc a
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (String -> Doc a) -> String -> Doc a
forall a b. (a -> b) -> a -> b
$ String
s String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"64"
taggedF :: String -> FloatType -> Doc a
taggedF :: forall a. String -> FloatType -> Doc a
taggedF String
s FloatType
Float16 = String -> Doc a
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (String -> Doc a) -> String -> Doc a
forall a b. (a -> b) -> a -> b
$ String
s String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"16"
taggedF String
s FloatType
Float32 = String -> Doc a
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (String -> Doc a) -> String -> Doc a
forall a b. (a -> b) -> a -> b
$ String
s String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"32"
taggedF String
s FloatType
Float64 = String -> Doc a
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (String -> Doc a) -> String -> Doc a
forall a b. (a -> b) -> a -> b
$ String
s String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"64"
convOp :: (Pretty from, Pretty to) => String -> from -> to -> Doc a
convOp :: forall from to a.
(Pretty from, Pretty to) =>
String -> from -> to -> Doc a
convOp String
s from
from to
to = String -> Doc a
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty String
s Doc a -> Doc a -> Doc a
forall a. Semigroup a => a -> a -> a
<> Doc a
"_" Doc a -> Doc a -> Doc a
forall a. Semigroup a => a -> a -> a
<> from -> Doc a
forall ann. from -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty from
from Doc a -> Doc a -> Doc a
forall a. Semigroup a => a -> a -> a
<> Doc a
"_" Doc a -> Doc a -> Doc a
forall a. Semigroup a => a -> a -> a
<> to -> Doc a
forall ann. to -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty to
to
prettySigned :: Bool -> PrimType -> T.Text
prettySigned :: Bool -> PrimType -> Text
prettySigned Bool
True (IntType IntType
it) = Char -> Text -> Text
T.cons Char
'u' (Int -> Text -> Text
T.drop Int
1 (IntType -> Text
forall a. Pretty a => a -> Text
prettyText IntType
it))
prettySigned Bool
_ PrimType
t = PrimType -> Text
forall a. Pretty a => a -> Text
prettyText PrimType
t
umul_hi8 :: Int8 -> Int8 -> Int8
umul_hi8 :: Int8 -> Int8 -> Int8
umul_hi8 Int8
a Int8
b =
let a' :: Word64
a' = Word8 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int8 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int8
a :: Word8) :: Word64
b' :: Word64
b' = Word8 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int8 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int8
b :: Word8) :: Word64
in Word64 -> Int8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
shiftR (Word64
a' Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
* Word64
b') Int
8)
umul_hi16 :: Int16 -> Int16 -> Int16
umul_hi16 :: Int16 -> Int16 -> Int16
umul_hi16 Int16
a Int16
b =
let a' :: Word64
a' = Word16 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int16 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int16
a :: Word16) :: Word64
b' :: Word64
b' = Word16 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int16 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int16
b :: Word16) :: Word64
in Word64 -> Int16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
shiftR (Word64
a' Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
* Word64
b') Int
16)
umul_hi32 :: Int32 -> Int32 -> Int32
umul_hi32 :: Int32 -> Int32 -> Int32
umul_hi32 Int32
a Int32
b =
let a' :: Word64
a' = Word32 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int32 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
a :: Word32) :: Word64
b' :: Word64
b' = Word32 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int32 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
b :: Word32) :: Word64
in Word64 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
shiftR (Word64
a' Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
* Word64
b') Int
32)
umul_hi64 :: Int64 -> Int64 -> Int64
umul_hi64 :: Int64 -> Int64 -> Int64
umul_hi64 Int64
a Int64
b =
let a' :: Integer
a' = Word64 -> Integer
forall a. Integral a => a -> Integer
toInteger (Int64 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
a :: Word64)
b' :: Integer
b' = Word64 -> Integer
forall a. Integral a => a -> Integer
toInteger (Int64 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
b :: Word64)
in Integer -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftR (Integer
a' Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
b') Int
64)
umad_hi8 :: Int8 -> Int8 -> Int8 -> Int8
umad_hi8 :: Int8 -> Int8 -> Int8 -> Int8
umad_hi8 Int8
a Int8
b Int8
c = Int8 -> Int8 -> Int8
umul_hi8 Int8
a Int8
b Int8 -> Int8 -> Int8
forall a. Num a => a -> a -> a
+ Int8
c
umad_hi16 :: Int16 -> Int16 -> Int16 -> Int16
umad_hi16 :: Int16 -> Int16 -> Int16 -> Int16
umad_hi16 Int16
a Int16
b Int16
c = Int16 -> Int16 -> Int16
umul_hi16 Int16
a Int16
b Int16 -> Int16 -> Int16
forall a. Num a => a -> a -> a
+ Int16
c
umad_hi32 :: Int32 -> Int32 -> Int32 -> Int32
umad_hi32 :: Int32 -> Int32 -> Int32 -> Int32
umad_hi32 Int32
a Int32
b Int32
c = Int32 -> Int32 -> Int32
umul_hi32 Int32
a Int32
b Int32 -> Int32 -> Int32
forall a. Num a => a -> a -> a
+ Int32
c
umad_hi64 :: Int64 -> Int64 -> Int64 -> Int64
umad_hi64 :: Int64 -> Int64 -> Int64 -> Int64
umad_hi64 Int64
a Int64
b Int64
c = Int64 -> Int64 -> Int64
umul_hi64 Int64
a Int64
b Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int64
c
smul_hi8 :: Int8 -> Int8 -> Int8
smul_hi8 :: Int8 -> Int8 -> Int8
smul_hi8 Int8
a Int8
b =
let a' :: Int64
a' = Int8 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int8
a :: Int64
b' :: Int64
b' = Int8 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int8
b :: Int64
in Int64 -> Int8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64 -> Int -> Int64
forall a. Bits a => a -> Int -> a
shiftR (Int64
a' Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
b') Int
8)
smul_hi16 :: Int16 -> Int16 -> Int16
smul_hi16 :: Int16 -> Int16 -> Int16
smul_hi16 Int16
a Int16
b =
let a' :: Int64
a' = Int16 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int16
a :: Int64
b' :: Int64
b' = Int16 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int16
b :: Int64
in Int64 -> Int16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64 -> Int -> Int64
forall a. Bits a => a -> Int -> a
shiftR (Int64
a' Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
b') Int
16)
smul_hi32 :: Int32 -> Int32 -> Int32
smul_hi32 :: Int32 -> Int32 -> Int32
smul_hi32 Int32
a Int32
b =
let a' :: Int64
a' = Int32 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
a :: Int64
b' :: Int64
b' = Int32 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
b :: Int64
in Int64 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64 -> Int -> Int64
forall a. Bits a => a -> Int -> a
shiftR (Int64
a' Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
b') Int
32)
smul_hi64 :: Int64 -> Int64 -> Int64
smul_hi64 :: Int64 -> Int64 -> Int64
smul_hi64 Int64
a Int64
b =
let a' :: Integer
a' = Int64 -> Integer
forall a. Integral a => a -> Integer
toInteger Int64
a
b' :: Integer
b' = Int64 -> Integer
forall a. Integral a => a -> Integer
toInteger Int64
b
in Integer -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftR (Integer
a' Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
b') Int
64)
smad_hi8 :: Int8 -> Int8 -> Int8 -> Int8
smad_hi8 :: Int8 -> Int8 -> Int8 -> Int8
smad_hi8 Int8
a Int8
b Int8
c = Int8 -> Int8 -> Int8
smul_hi8 Int8
a Int8
b Int8 -> Int8 -> Int8
forall a. Num a => a -> a -> a
+ Int8
c
smad_hi16 :: Int16 -> Int16 -> Int16 -> Int16
smad_hi16 :: Int16 -> Int16 -> Int16 -> Int16
smad_hi16 Int16
a Int16
b Int16
c = Int16 -> Int16 -> Int16
smul_hi16 Int16
a Int16
b Int16 -> Int16 -> Int16
forall a. Num a => a -> a -> a
+ Int16
c
smad_hi32 :: Int32 -> Int32 -> Int32 -> Int32
smad_hi32 :: Int32 -> Int32 -> Int32 -> Int32
smad_hi32 Int32
a Int32
b Int32
c = Int32 -> Int32 -> Int32
smul_hi32 Int32
a Int32
b Int32 -> Int32 -> Int32
forall a. Num a => a -> a -> a
+ Int32
c
smad_hi64 :: Int64 -> Int64 -> Int64 -> Int64
smad_hi64 :: Int64 -> Int64 -> Int64 -> Int64
smad_hi64 Int64
a Int64
b Int64
c = Int64 -> Int64 -> Int64
smul_hi64 Int64
a Int64
b Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int64
c