{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE GHCForeignImportPrim #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE UnliftedFFITypes #-}
{-# OPTIONS_GHC -fobject-code #-}
module Numeric.Rounded.Hardware.Backend.FastFFI
( CDouble(..)
, fastIntervalAdd
, fastIntervalSub
, fastIntervalRecip
, VUM.MVector(MV_CFloat, MV_CDouble)
, VU.Vector(V_CFloat, V_CDouble)
) where
import Control.DeepSeq (NFData (..))
import Data.Coerce
import Data.Proxy
import Data.Tagged
import qualified Data.Vector.Generic as VG
import qualified Data.Vector.Generic.Mutable as VGM
import qualified Data.Vector.Storable as VS
import qualified Data.Vector.Unboxed as VU
import qualified Data.Vector.Unboxed.Mutable as VUM
import qualified FFIWrapper.Double as D
import Foreign.C.String (CString, peekCString)
import Foreign.Storable (Storable)
import GHC.Exts
import GHC.Generics (Generic)
import qualified Numeric.Rounded.Hardware.Backend.C as C
import Numeric.Rounded.Hardware.Internal.Class
import System.IO.Unsafe (unsafePerformIO)
import Unsafe.Coerce
#include "MachDeps.h"
newtype CDouble = CDouble Double
deriving (CDouble -> CDouble -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CDouble -> CDouble -> Bool
$c/= :: CDouble -> CDouble -> Bool
== :: CDouble -> CDouble -> Bool
$c== :: CDouble -> CDouble -> Bool
Eq,Eq CDouble
CDouble -> CDouble -> Bool
CDouble -> CDouble -> Ordering
CDouble -> CDouble -> CDouble
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
min :: CDouble -> CDouble -> CDouble
$cmin :: CDouble -> CDouble -> CDouble
max :: CDouble -> CDouble -> CDouble
$cmax :: CDouble -> CDouble -> CDouble
>= :: CDouble -> CDouble -> Bool
$c>= :: CDouble -> CDouble -> Bool
> :: CDouble -> CDouble -> Bool
$c> :: CDouble -> CDouble -> Bool
<= :: CDouble -> CDouble -> Bool
$c<= :: CDouble -> CDouble -> Bool
< :: CDouble -> CDouble -> Bool
$c< :: CDouble -> CDouble -> Bool
compare :: CDouble -> CDouble -> Ordering
$ccompare :: CDouble -> CDouble -> Ordering
Ord,Int -> CDouble -> ShowS
[CDouble] -> ShowS
CDouble -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CDouble] -> ShowS
$cshowList :: [CDouble] -> ShowS
show :: CDouble -> String
$cshow :: CDouble -> String
showsPrec :: Int -> CDouble -> ShowS
$cshowsPrec :: Int -> CDouble -> ShowS
Show,forall x. Rep CDouble x -> CDouble
forall x. CDouble -> Rep CDouble x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CDouble x -> CDouble
$cfrom :: forall x. CDouble -> Rep CDouble x
Generic,Integer -> CDouble
CDouble -> CDouble
CDouble -> CDouble -> CDouble
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> CDouble
$cfromInteger :: Integer -> CDouble
signum :: CDouble -> CDouble
$csignum :: CDouble -> CDouble
abs :: CDouble -> CDouble
$cabs :: CDouble -> CDouble
negate :: CDouble -> CDouble
$cnegate :: CDouble -> CDouble
* :: CDouble -> CDouble -> CDouble
$c* :: CDouble -> CDouble -> CDouble
- :: CDouble -> CDouble -> CDouble
$c- :: CDouble -> CDouble -> CDouble
+ :: CDouble -> CDouble -> CDouble
$c+ :: CDouble -> CDouble -> CDouble
Num,Ptr CDouble -> IO CDouble
Ptr CDouble -> Int -> IO CDouble
Ptr CDouble -> Int -> CDouble -> IO ()
Ptr CDouble -> CDouble -> IO ()
CDouble -> Int
forall b. Ptr b -> Int -> IO CDouble
forall b. Ptr b -> Int -> CDouble -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr CDouble -> CDouble -> IO ()
$cpoke :: Ptr CDouble -> CDouble -> IO ()
peek :: Ptr CDouble -> IO CDouble
$cpeek :: Ptr CDouble -> IO CDouble
pokeByteOff :: forall b. Ptr b -> Int -> CDouble -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> CDouble -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO CDouble
$cpeekByteOff :: forall b. Ptr b -> Int -> IO CDouble
pokeElemOff :: Ptr CDouble -> Int -> CDouble -> IO ()
$cpokeElemOff :: Ptr CDouble -> Int -> CDouble -> IO ()
peekElemOff :: Ptr CDouble -> Int -> IO CDouble
$cpeekElemOff :: Ptr CDouble -> Int -> IO CDouble
alignment :: CDouble -> Int
$calignment :: CDouble -> Int
sizeOf :: CDouble -> Int
$csizeOf :: CDouble -> Int
Storable)
instance NFData CDouble
instance RoundedRing CDouble where
roundedAdd :: RoundingMode -> CDouble -> CDouble -> CDouble
roundedAdd = coerce :: forall a b. Coercible a b => a -> b
coerce RoundingMode -> Double -> Double -> Double
D.roundedAdd
roundedSub :: RoundingMode -> CDouble -> CDouble -> CDouble
roundedSub = coerce :: forall a b. Coercible a b => a -> b
coerce RoundingMode -> Double -> Double -> Double
D.roundedSub
roundedMul :: RoundingMode -> CDouble -> CDouble -> CDouble
roundedMul = coerce :: forall a b. Coercible a b => a -> b
coerce RoundingMode -> Double -> Double -> Double
D.roundedMul
roundedFusedMultiplyAdd :: RoundingMode -> CDouble -> CDouble -> CDouble -> CDouble
roundedFusedMultiplyAdd = coerce :: forall a b. Coercible a b => a -> b
coerce RoundingMode -> Double -> Double -> Double -> Double
D.roundedFMA
intervalAdd :: Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble)
intervalAdd Rounded 'TowardNegInf CDouble
x Rounded 'TowardInf CDouble
x' Rounded 'TowardNegInf CDouble
y Rounded 'TowardInf CDouble
y' = coerce :: forall a b. Coercible a b => a -> b
coerce Double -> Double -> Double -> Double -> (Double, Double)
fastIntervalAdd Rounded 'TowardNegInf CDouble
x Rounded 'TowardInf CDouble
x' Rounded 'TowardNegInf CDouble
y Rounded 'TowardInf CDouble
y'
intervalSub :: Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble)
intervalSub Rounded 'TowardNegInf CDouble
x Rounded 'TowardInf CDouble
x' Rounded 'TowardNegInf CDouble
y Rounded 'TowardInf CDouble
y' = coerce :: forall a b. Coercible a b => a -> b
coerce Double -> Double -> Double -> Double -> (Double, Double)
fastIntervalSub Rounded 'TowardNegInf CDouble
x Rounded 'TowardInf CDouble
x' Rounded 'TowardNegInf CDouble
y Rounded 'TowardInf CDouble
y'
intervalMul :: Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble)
intervalMul Rounded 'TowardNegInf CDouble
x Rounded 'TowardInf CDouble
x' Rounded 'TowardNegInf CDouble
y Rounded 'TowardInf CDouble
y' = (coerce :: forall a b. Coercible a b => a -> b
coerce Double -> Double -> Double -> Double -> Double
D.intervalMul_down Rounded 'TowardNegInf CDouble
x Rounded 'TowardInf CDouble
x' Rounded 'TowardNegInf CDouble
y Rounded 'TowardInf CDouble
y', coerce :: forall a b. Coercible a b => a -> b
coerce Double -> Double -> Double -> Double -> Double
D.intervalMul_up Rounded 'TowardNegInf CDouble
x Rounded 'TowardInf CDouble
x' Rounded 'TowardNegInf CDouble
y Rounded 'TowardInf CDouble
y')
intervalMulAdd :: Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble)
intervalMulAdd Rounded 'TowardNegInf CDouble
x Rounded 'TowardInf CDouble
x' Rounded 'TowardNegInf CDouble
y Rounded 'TowardInf CDouble
y' Rounded 'TowardNegInf CDouble
z Rounded 'TowardInf CDouble
z' = (coerce :: forall a b. Coercible a b => a -> b
coerce Double -> Double -> Double -> Double -> Double -> Double
D.intervalMulAdd_down Rounded 'TowardNegInf CDouble
x Rounded 'TowardInf CDouble
x' Rounded 'TowardNegInf CDouble
y Rounded 'TowardInf CDouble
y' Rounded 'TowardNegInf CDouble
z, coerce :: forall a b. Coercible a b => a -> b
coerce Double -> Double -> Double -> Double -> Double -> Double
D.intervalMulAdd_up Rounded 'TowardNegInf CDouble
x Rounded 'TowardInf CDouble
x' Rounded 'TowardNegInf CDouble
y Rounded 'TowardInf CDouble
y' Rounded 'TowardInf CDouble
z')
roundedFromInteger :: RoundingMode -> Integer -> CDouble
roundedFromInteger = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. RoundedRing a => RoundingMode -> Integer -> a
roundedFromInteger :: RoundingMode -> Integer -> C.CDouble)
intervalFromInteger :: Integer
-> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble)
intervalFromInteger = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a.
RoundedRing a =>
Integer -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a)
intervalFromInteger :: Integer -> (Rounded 'TowardNegInf C.CDouble, Rounded 'TowardInf C.CDouble))
backendNameT :: Tagged CDouble String
backendNameT = forall {k} (s :: k) b. b -> Tagged s b
Tagged forall a b. (a -> b) -> a -> b
$ let base :: String
base = forall a (proxy :: * -> *). RoundedRing a => proxy a -> String
backendName (forall {k} (t :: k). Proxy t
Proxy :: Proxy C.CDouble)
intervals :: String
intervals = String
intervalBackendName
in if String
base forall a. Eq a => a -> a -> Bool
== String
intervals
then String
base forall a. [a] -> [a] -> [a]
++ String
"+FastFFI"
else String
base forall a. [a] -> [a] -> [a]
++ String
"+FastFFI(" forall a. [a] -> [a] -> [a]
++ String
intervals forall a. [a] -> [a] -> [a]
++ String
")"
{-# INLINE roundedAdd #-}
{-# INLINE roundedSub #-}
{-# INLINE roundedMul #-}
{-# INLINE roundedFusedMultiplyAdd #-}
{-# INLINE intervalAdd #-}
{-# INLINE intervalSub #-}
{-# INLINE intervalMul #-}
{-# INLINE roundedFromInteger #-}
{-# INLINE intervalFromInteger #-}
instance RoundedFractional CDouble where
roundedDiv :: RoundingMode -> CDouble -> CDouble -> CDouble
roundedDiv = coerce :: forall a b. Coercible a b => a -> b
coerce RoundingMode -> Double -> Double -> Double
D.roundedDiv
intervalDiv :: Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble)
intervalDiv Rounded 'TowardNegInf CDouble
x Rounded 'TowardInf CDouble
x' Rounded 'TowardNegInf CDouble
y Rounded 'TowardInf CDouble
y' = (coerce :: forall a b. Coercible a b => a -> b
coerce Double -> Double -> Double -> Double -> Double
D.intervalDiv_down Rounded 'TowardNegInf CDouble
x Rounded 'TowardInf CDouble
x' Rounded 'TowardNegInf CDouble
y Rounded 'TowardInf CDouble
y', coerce :: forall a b. Coercible a b => a -> b
coerce Double -> Double -> Double -> Double -> Double
D.intervalDiv_up Rounded 'TowardNegInf CDouble
x Rounded 'TowardInf CDouble
x' Rounded 'TowardNegInf CDouble
y Rounded 'TowardInf CDouble
y')
intervalDivAdd :: Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble)
intervalDivAdd Rounded 'TowardNegInf CDouble
x Rounded 'TowardInf CDouble
x' Rounded 'TowardNegInf CDouble
y Rounded 'TowardInf CDouble
y' Rounded 'TowardNegInf CDouble
z Rounded 'TowardInf CDouble
z' = (coerce :: forall a b. Coercible a b => a -> b
coerce Double -> Double -> Double -> Double -> Double -> Double
D.intervalDivAdd_down Rounded 'TowardNegInf CDouble
x Rounded 'TowardInf CDouble
x' Rounded 'TowardNegInf CDouble
y Rounded 'TowardInf CDouble
y' Rounded 'TowardNegInf CDouble
z, coerce :: forall a b. Coercible a b => a -> b
coerce Double -> Double -> Double -> Double -> Double -> Double
D.intervalDivAdd_up Rounded 'TowardNegInf CDouble
x Rounded 'TowardInf CDouble
x' Rounded 'TowardNegInf CDouble
y Rounded 'TowardInf CDouble
y' Rounded 'TowardInf CDouble
z')
intervalRecip :: Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble)
intervalRecip Rounded 'TowardNegInf CDouble
x Rounded 'TowardInf CDouble
x' = coerce :: forall a b. Coercible a b => a -> b
coerce Double -> Double -> (Double, Double)
fastIntervalRecip Rounded 'TowardNegInf CDouble
x Rounded 'TowardInf CDouble
x'
roundedFromRational :: RoundingMode -> Rational -> CDouble
roundedFromRational = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. RoundedFractional a => RoundingMode -> Rational -> a
roundedFromRational :: RoundingMode -> Rational -> C.CDouble)
roundedFromRealFloat :: forall b. RealFloat b => RoundingMode -> b -> CDouble
roundedFromRealFloat RoundingMode
r b
x = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a b.
(RoundedFractional a, RealFloat b) =>
RoundingMode -> b -> a
roundedFromRealFloat RoundingMode
r b
x :: C.CDouble)
intervalFromRational :: Rational
-> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble)
intervalFromRational = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a.
RoundedFractional a =>
Rational -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a)
intervalFromRational :: Rational -> (Rounded 'TowardNegInf C.CDouble, Rounded 'TowardInf C.CDouble))
{-# INLINE roundedDiv #-}
{-# INLINE intervalDiv #-}
{-# INLINE intervalRecip #-}
{-# INLINE roundedFromRational #-}
{-# INLINE roundedFromRealFloat #-}
{-# INLINE intervalFromRational #-}
instance RoundedSqrt CDouble where
roundedSqrt :: RoundingMode -> CDouble -> CDouble
roundedSqrt = coerce :: forall a b. Coercible a b => a -> b
coerce RoundingMode -> Double -> Double
D.roundedSqrt
{-# INLINE roundedSqrt #-}
instance RoundedRing_Vector VS.Vector CDouble where
roundedSum :: RoundingMode -> Vector CDouble -> CDouble
roundedSum RoundingMode
mode Vector CDouble
vec = coerce :: forall a b. Coercible a b => a -> b
coerce (forall (vector :: * -> *) a.
RoundedRing_Vector vector a =>
RoundingMode -> vector a -> a
roundedSum RoundingMode
mode (forall a b. a -> b
unsafeCoerce Vector CDouble
vec :: VS.Vector C.CDouble))
zipWith_roundedAdd :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble
zipWith_roundedAdd RoundingMode
mode Vector CDouble
vec Vector CDouble
vec' = forall a b. a -> b
unsafeCoerce (forall (vector :: * -> *) a.
RoundedRing_Vector vector a =>
RoundingMode -> vector a -> vector a -> vector a
zipWith_roundedAdd RoundingMode
mode (forall a b. a -> b
unsafeCoerce Vector CDouble
vec) (forall a b. a -> b
unsafeCoerce Vector CDouble
vec') :: VS.Vector C.CDouble)
zipWith_roundedSub :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble
zipWith_roundedSub RoundingMode
mode Vector CDouble
vec Vector CDouble
vec' = forall a b. a -> b
unsafeCoerce (forall (vector :: * -> *) a.
RoundedRing_Vector vector a =>
RoundingMode -> vector a -> vector a -> vector a
zipWith_roundedSub RoundingMode
mode (forall a b. a -> b
unsafeCoerce Vector CDouble
vec) (forall a b. a -> b
unsafeCoerce Vector CDouble
vec') :: VS.Vector C.CDouble)
zipWith_roundedMul :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble
zipWith_roundedMul RoundingMode
mode Vector CDouble
vec Vector CDouble
vec' = forall a b. a -> b
unsafeCoerce (forall (vector :: * -> *) a.
RoundedRing_Vector vector a =>
RoundingMode -> vector a -> vector a -> vector a
zipWith_roundedMul RoundingMode
mode (forall a b. a -> b
unsafeCoerce Vector CDouble
vec) (forall a b. a -> b
unsafeCoerce Vector CDouble
vec') :: VS.Vector C.CDouble)
zipWith3_roundedFusedMultiplyAdd :: RoundingMode
-> Vector CDouble
-> Vector CDouble
-> Vector CDouble
-> Vector CDouble
zipWith3_roundedFusedMultiplyAdd RoundingMode
mode Vector CDouble
vec1 Vector CDouble
vec2 Vector CDouble
vec3 = forall a b. a -> b
unsafeCoerce (forall (vector :: * -> *) a.
RoundedRing_Vector vector a =>
RoundingMode -> vector a -> vector a -> vector a -> vector a
zipWith3_roundedFusedMultiplyAdd RoundingMode
mode (forall a b. a -> b
unsafeCoerce Vector CDouble
vec1) (forall a b. a -> b
unsafeCoerce Vector CDouble
vec2) (forall a b. a -> b
unsafeCoerce Vector CDouble
vec3) :: VS.Vector C.CDouble)
{-# INLINE roundedSum #-}
{-# INLINE zipWith_roundedAdd #-}
{-# INLINE zipWith_roundedSub #-}
{-# INLINE zipWith_roundedMul #-}
{-# INLINE zipWith3_roundedFusedMultiplyAdd #-}
instance RoundedFractional_Vector VS.Vector CDouble where
zipWith_roundedDiv :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble
zipWith_roundedDiv RoundingMode
mode Vector CDouble
vec Vector CDouble
vec' = forall a b. a -> b
unsafeCoerce (forall (vector :: * -> *) a.
RoundedFractional_Vector vector a =>
RoundingMode -> vector a -> vector a -> vector a
zipWith_roundedDiv RoundingMode
mode (forall a b. a -> b
unsafeCoerce Vector CDouble
vec) (forall a b. a -> b
unsafeCoerce Vector CDouble
vec') :: VS.Vector C.CDouble)
{-# INLINE zipWith_roundedDiv #-}
instance RoundedSqrt_Vector VS.Vector CDouble where
map_roundedSqrt :: RoundingMode -> Vector CDouble -> Vector CDouble
map_roundedSqrt RoundingMode
mode Vector CDouble
vec = forall a b. a -> b
unsafeCoerce (forall (vector :: * -> *) a.
RoundedSqrt_Vector vector a =>
RoundingMode -> vector a -> vector a
map_roundedSqrt RoundingMode
mode (forall a b. a -> b
unsafeCoerce Vector CDouble
vec) :: VS.Vector C.CDouble)
{-# INLINE map_roundedSqrt #-}
deriving via C.CDouble instance RoundedRing_Vector VU.Vector CDouble
deriving via C.CDouble instance RoundedFractional_Vector VU.Vector CDouble
deriving via C.CDouble instance RoundedSqrt_Vector VU.Vector CDouble
foreign import prim "rounded_hw_interval_add"
fastIntervalAdd# :: Double#
-> Double#
-> Double#
-> Double#
-> (# Double#
, Double#
#)
foreign import prim "rounded_hw_interval_sub"
fastIntervalSub# :: Double#
-> Double#
-> Double#
-> Double#
-> (# Double#
, Double#
#)
foreign import prim "rounded_hw_interval_recip"
fastIntervalRecip# :: Double#
-> Double#
-> (# Double#
, Double#
#)
fastIntervalAdd :: Double -> Double -> Double -> Double -> (Double, Double)
fastIntervalAdd :: Double -> Double -> Double -> Double -> (Double, Double)
fastIntervalAdd (D# Double#
l1) (D# Double#
h1) (D# Double#
l2) (D# Double#
h2) = case Double# -> Double# -> Double# -> Double# -> (# Double#, Double# #)
fastIntervalAdd# Double#
l1 Double#
h1 Double#
l2 Double#
h2 of
(# Double#
l3, Double#
h3 #) -> (Double# -> Double
D# Double#
l3, Double# -> Double
D# Double#
h3)
{-# INLINE fastIntervalAdd #-}
fastIntervalSub :: Double -> Double -> Double -> Double -> (Double, Double)
fastIntervalSub :: Double -> Double -> Double -> Double -> (Double, Double)
fastIntervalSub (D# Double#
l1) (D# Double#
h1) (D# Double#
l2) (D# Double#
h2) = case Double# -> Double# -> Double# -> Double# -> (# Double#, Double# #)
fastIntervalSub# Double#
l1 Double#
h1 Double#
l2 Double#
h2 of
(# Double#
l3, Double#
h3 #) -> (Double# -> Double
D# Double#
l3, Double# -> Double
D# Double#
h3)
{-# INLINE fastIntervalSub #-}
fastIntervalRecip :: Double -> Double -> (Double, Double)
fastIntervalRecip :: Double -> Double -> (Double, Double)
fastIntervalRecip (D# Double#
l1) (D# Double#
h1) = case Double# -> Double# -> (# Double#, Double# #)
fastIntervalRecip# Double#
l1 Double#
h1 of
(# Double#
l2, Double#
h2 #) -> (Double# -> Double
D# Double#
l2, Double# -> Double
D# Double#
h2)
{-# INLINE fastIntervalRecip #-}
foreign import ccall "&rounded_hw_interval_backend_name"
c_interval_backend_name :: CString
intervalBackendName :: String
intervalBackendName :: String
intervalBackendName = forall a. IO a -> a
unsafePerformIO (CString -> IO String
peekCString CString
c_interval_backend_name)
newtype instance VUM.MVector s CDouble = MV_CDouble (VUM.MVector s Double)
newtype instance VU.Vector CDouble = V_CDouble (VU.Vector Double)
instance VGM.MVector VUM.MVector CDouble where
basicLength :: forall s. MVector s CDouble -> Int
basicLength (MV_CDouble MVector s Double
mv) = forall (v :: * -> * -> *) a s. MVector v a => v s a -> Int
VGM.basicLength MVector s Double
mv
basicUnsafeSlice :: forall s. Int -> Int -> MVector s CDouble -> MVector s CDouble
basicUnsafeSlice Int
i Int
l (MV_CDouble MVector s Double
mv) = forall s. MVector s Double -> MVector s CDouble
MV_CDouble (forall (v :: * -> * -> *) a s.
MVector v a =>
Int -> Int -> v s a -> v s a
VGM.basicUnsafeSlice Int
i Int
l MVector s Double
mv)
basicOverlaps :: forall s. MVector s CDouble -> MVector s CDouble -> Bool
basicOverlaps (MV_CDouble MVector s Double
mv) (MV_CDouble MVector s Double
mv') = forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> Bool
VGM.basicOverlaps MVector s Double
mv MVector s Double
mv'
basicUnsafeNew :: forall s. Int -> ST s (MVector s CDouble)
basicUnsafeNew Int
l = forall s. MVector s Double -> MVector s CDouble
MV_CDouble forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (v :: * -> * -> *) a s. MVector v a => Int -> ST s (v s a)
VGM.basicUnsafeNew Int
l
basicInitialize :: forall s. MVector s CDouble -> ST s ()
basicInitialize (MV_CDouble MVector s Double
mv) = forall (v :: * -> * -> *) a s. MVector v a => v s a -> ST s ()
VGM.basicInitialize MVector s Double
mv
basicUnsafeReplicate :: forall s. Int -> CDouble -> ST s (MVector s CDouble)
basicUnsafeReplicate Int
i CDouble
x = forall s. MVector s Double -> MVector s CDouble
MV_CDouble forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (v :: * -> * -> *) a s.
MVector v a =>
Int -> a -> ST s (v s a)
VGM.basicUnsafeReplicate Int
i (coerce :: forall a b. Coercible a b => a -> b
coerce CDouble
x)
basicUnsafeRead :: forall s. MVector s CDouble -> Int -> ST s CDouble
basicUnsafeRead (MV_CDouble MVector s Double
mv) Int
i = coerce :: forall a b. Coercible a b => a -> b
coerce forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> Int -> ST s a
VGM.basicUnsafeRead MVector s Double
mv Int
i
basicUnsafeWrite :: forall s. MVector s CDouble -> Int -> CDouble -> ST s ()
basicUnsafeWrite (MV_CDouble MVector s Double
mv) Int
i CDouble
x = forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> Int -> a -> ST s ()
VGM.basicUnsafeWrite MVector s Double
mv Int
i (coerce :: forall a b. Coercible a b => a -> b
coerce CDouble
x)
basicClear :: forall s. MVector s CDouble -> ST s ()
basicClear (MV_CDouble MVector s Double
mv) = forall (v :: * -> * -> *) a s. MVector v a => v s a -> ST s ()
VGM.basicClear MVector s Double
mv
basicSet :: forall s. MVector s CDouble -> CDouble -> ST s ()
basicSet (MV_CDouble MVector s Double
mv) CDouble
x = forall (v :: * -> * -> *) a s. MVector v a => v s a -> a -> ST s ()
VGM.basicSet MVector s Double
mv (coerce :: forall a b. Coercible a b => a -> b
coerce CDouble
x)
basicUnsafeCopy :: forall s. MVector s CDouble -> MVector s CDouble -> ST s ()
basicUnsafeCopy (MV_CDouble MVector s Double
mv) (MV_CDouble MVector s Double
mv') = forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> ST s ()
VGM.basicUnsafeCopy MVector s Double
mv MVector s Double
mv'
basicUnsafeMove :: forall s. MVector s CDouble -> MVector s CDouble -> ST s ()
basicUnsafeMove (MV_CDouble MVector s Double
mv) (MV_CDouble MVector s Double
mv') = forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> ST s ()
VGM.basicUnsafeMove MVector s Double
mv MVector s Double
mv'
basicUnsafeGrow :: forall s. MVector s CDouble -> Int -> ST s (MVector s CDouble)
basicUnsafeGrow (MV_CDouble MVector s Double
mv) Int
n = forall s. MVector s Double -> MVector s CDouble
MV_CDouble forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> Int -> ST s (v s a)
VGM.basicUnsafeGrow MVector s Double
mv Int
n
instance VG.Vector VU.Vector CDouble where
basicUnsafeFreeze :: forall s. Mutable Vector s CDouble -> ST s (Vector CDouble)
basicUnsafeFreeze (MV_CDouble MVector s Double
mv) = Vector Double -> Vector CDouble
V_CDouble forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (v :: * -> *) a s. Vector v a => Mutable v s a -> ST s (v a)
VG.basicUnsafeFreeze MVector s Double
mv
basicUnsafeThaw :: forall s. Vector CDouble -> ST s (Mutable Vector s CDouble)
basicUnsafeThaw (V_CDouble Vector Double
v) = forall s. MVector s Double -> MVector s CDouble
MV_CDouble forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (v :: * -> *) a s. Vector v a => v a -> ST s (Mutable v s a)
VG.basicUnsafeThaw Vector Double
v
basicLength :: Vector CDouble -> Int
basicLength (V_CDouble Vector Double
v) = forall (v :: * -> *) a. Vector v a => v a -> Int
VG.basicLength Vector Double
v
basicUnsafeSlice :: Int -> Int -> Vector CDouble -> Vector CDouble
basicUnsafeSlice Int
i Int
l (V_CDouble Vector Double
v) = Vector Double -> Vector CDouble
V_CDouble (forall (v :: * -> *) a. Vector v a => Int -> Int -> v a -> v a
VG.basicUnsafeSlice Int
i Int
l Vector Double
v)
basicUnsafeIndexM :: Vector CDouble -> Int -> Box CDouble
basicUnsafeIndexM (V_CDouble Vector Double
v) Int
i = coerce :: forall a b. Coercible a b => a -> b
coerce forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (v :: * -> *) a. Vector v a => v a -> Int -> Box a
VG.basicUnsafeIndexM Vector Double
v Int
i
basicUnsafeCopy :: forall s. Mutable Vector s CDouble -> Vector CDouble -> ST s ()
basicUnsafeCopy (MV_CDouble MVector s Double
mv) (V_CDouble Vector Double
v) = forall (v :: * -> *) a s.
Vector v a =>
Mutable v s a -> v a -> ST s ()
VG.basicUnsafeCopy MVector s Double
mv Vector Double
v
elemseq :: forall b. Vector CDouble -> CDouble -> b -> b
elemseq (V_CDouble Vector Double
v) CDouble
x b
y = forall (v :: * -> *) a b. Vector v a => v a -> a -> b -> b
VG.elemseq Vector Double
v (coerce :: forall a b. Coercible a b => a -> b
coerce CDouble
x) b
y
instance VU.Unbox CDouble