{-|
Module: Numeric.Rounded.Hardware.Backend.C

The types in this module implements rounding-mode-controlled operations in C.

There are several ways to control rounding mode in C, and an appropriate technology will be selected at compile time.
This library implements the following options:

    * C99 @fesetround@
    * On x86 systems,

        * SSE2 MXCSR (for 'Float' and 'Double')
        * AVX512 EVEX encoding (for 'Float' and 'Double')
        * x87 Control Word (for 'Numeric.LongDouble.LongDouble')

    * On AArch64, FPCR

You should not need to import this module directly.

This module is not available if the package flag @pure-hs@ is set.
-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module Numeric.Rounded.Hardware.Backend.C
  ( CFloat(..)
  , CDouble(..)
  , VUM.MVector(..)
  , VU.Vector(..)
  , roundedFloatFromInt64
  , roundedFloatFromWord64
  , roundedDoubleFromInt64
  , roundedDoubleFromWord64
  ) where
import           Control.DeepSeq (NFData (..))
import           Data.Bifunctor
import           Data.Coerce
import           Data.Int (Int64)
import           Data.Primitive (Prim)
import           Data.Primitive.ByteArray
import           Data.Tagged
import qualified Data.Vector.Generic as VG
import qualified Data.Vector.Generic.Mutable as VGM
import qualified Data.Vector.Primitive as VP
import qualified Data.Vector.Primitive.Mutable as VPM
import qualified Data.Vector.Storable as VS
import qualified Data.Vector.Storable.Mutable as VSM
import qualified Data.Vector.Unboxed.Base as VU
import qualified Data.Vector.Unboxed.Mutable as VUM
import           Data.Word (Word64)
import qualified FFIWrapper.Double as D
import qualified FFIWrapper.Float as F
import           Foreign.C.String (CString, peekCString)
import           Foreign.Ptr (Ptr, castPtr)
import           Foreign.Storable (Storable)
import           GHC.Generics (Generic)
import           GHC.Exts (RealWorld)
import           Numeric.Rounded.Hardware.Internal.Class
import           Numeric.Rounded.Hardware.Internal.Conversion
import           System.IO.Unsafe (unsafePerformIO)

--
-- Float
--

-- | A wrapper providing particular instances for 'RoundedRing', 'RoundedFractional' and 'RoundedSqrt'.
--
-- This type is different from @CFloat@ from "Foreign.C.Types".
newtype CFloat = CFloat Float
  deriving (CFloat -> CFloat -> Bool
(CFloat -> CFloat -> Bool)
-> (CFloat -> CFloat -> Bool) -> Eq CFloat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CFloat -> CFloat -> Bool
$c/= :: CFloat -> CFloat -> Bool
== :: CFloat -> CFloat -> Bool
$c== :: CFloat -> CFloat -> Bool
Eq,Eq CFloat
Eq CFloat
-> (CFloat -> CFloat -> Ordering)
-> (CFloat -> CFloat -> Bool)
-> (CFloat -> CFloat -> Bool)
-> (CFloat -> CFloat -> Bool)
-> (CFloat -> CFloat -> Bool)
-> (CFloat -> CFloat -> CFloat)
-> (CFloat -> CFloat -> CFloat)
-> Ord CFloat
CFloat -> CFloat -> Bool
CFloat -> CFloat -> Ordering
CFloat -> CFloat -> CFloat
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 :: CFloat -> CFloat -> CFloat
$cmin :: CFloat -> CFloat -> CFloat
max :: CFloat -> CFloat -> CFloat
$cmax :: CFloat -> CFloat -> CFloat
>= :: CFloat -> CFloat -> Bool
$c>= :: CFloat -> CFloat -> Bool
> :: CFloat -> CFloat -> Bool
$c> :: CFloat -> CFloat -> Bool
<= :: CFloat -> CFloat -> Bool
$c<= :: CFloat -> CFloat -> Bool
< :: CFloat -> CFloat -> Bool
$c< :: CFloat -> CFloat -> Bool
compare :: CFloat -> CFloat -> Ordering
$ccompare :: CFloat -> CFloat -> Ordering
$cp1Ord :: Eq CFloat
Ord,Int -> CFloat -> ShowS
[CFloat] -> ShowS
CFloat -> String
(Int -> CFloat -> ShowS)
-> (CFloat -> String) -> ([CFloat] -> ShowS) -> Show CFloat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CFloat] -> ShowS
$cshowList :: [CFloat] -> ShowS
show :: CFloat -> String
$cshow :: CFloat -> String
showsPrec :: Int -> CFloat -> ShowS
$cshowsPrec :: Int -> CFloat -> ShowS
Show,(forall x. CFloat -> Rep CFloat x)
-> (forall x. Rep CFloat x -> CFloat) -> Generic CFloat
forall x. Rep CFloat x -> CFloat
forall x. CFloat -> Rep CFloat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CFloat x -> CFloat
$cfrom :: forall x. CFloat -> Rep CFloat x
Generic,Integer -> CFloat
CFloat -> CFloat
CFloat -> CFloat -> CFloat
(CFloat -> CFloat -> CFloat)
-> (CFloat -> CFloat -> CFloat)
-> (CFloat -> CFloat -> CFloat)
-> (CFloat -> CFloat)
-> (CFloat -> CFloat)
-> (CFloat -> CFloat)
-> (Integer -> CFloat)
-> Num CFloat
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> CFloat
$cfromInteger :: Integer -> CFloat
signum :: CFloat -> CFloat
$csignum :: CFloat -> CFloat
abs :: CFloat -> CFloat
$cabs :: CFloat -> CFloat
negate :: CFloat -> CFloat
$cnegate :: CFloat -> CFloat
* :: CFloat -> CFloat -> CFloat
$c* :: CFloat -> CFloat -> CFloat
- :: CFloat -> CFloat -> CFloat
$c- :: CFloat -> CFloat -> CFloat
+ :: CFloat -> CFloat -> CFloat
$c+ :: CFloat -> CFloat -> CFloat
Num,Ptr b -> Int -> IO CFloat
Ptr b -> Int -> CFloat -> IO ()
Ptr CFloat -> IO CFloat
Ptr CFloat -> Int -> IO CFloat
Ptr CFloat -> Int -> CFloat -> IO ()
Ptr CFloat -> CFloat -> IO ()
CFloat -> Int
(CFloat -> Int)
-> (CFloat -> Int)
-> (Ptr CFloat -> Int -> IO CFloat)
-> (Ptr CFloat -> Int -> CFloat -> IO ())
-> (forall b. Ptr b -> Int -> IO CFloat)
-> (forall b. Ptr b -> Int -> CFloat -> IO ())
-> (Ptr CFloat -> IO CFloat)
-> (Ptr CFloat -> CFloat -> IO ())
-> Storable CFloat
forall b. Ptr b -> Int -> IO CFloat
forall b. Ptr b -> Int -> CFloat -> 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 CFloat -> CFloat -> IO ()
$cpoke :: Ptr CFloat -> CFloat -> IO ()
peek :: Ptr CFloat -> IO CFloat
$cpeek :: Ptr CFloat -> IO CFloat
pokeByteOff :: Ptr b -> Int -> CFloat -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> CFloat -> IO ()
peekByteOff :: Ptr b -> Int -> IO CFloat
$cpeekByteOff :: forall b. Ptr b -> Int -> IO CFloat
pokeElemOff :: Ptr CFloat -> Int -> CFloat -> IO ()
$cpokeElemOff :: Ptr CFloat -> Int -> CFloat -> IO ()
peekElemOff :: Ptr CFloat -> Int -> IO CFloat
$cpeekElemOff :: Ptr CFloat -> Int -> IO CFloat
alignment :: CFloat -> Int
$calignment :: CFloat -> Int
sizeOf :: CFloat -> Int
$csizeOf :: CFloat -> Int
Storable)

instance NFData CFloat

roundedFloatFromInt64 :: RoundingMode -> Int64 -> Float
roundedFloatFromInt64 :: RoundingMode -> Int64 -> Float
roundedFloatFromInt64 RoundingMode
r Int64
x = Bool -> Float -> Float -> Float
forall a. Bool -> a -> a -> a
staticIf
  (-Int64
0x1000000 Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Int64
x Bool -> Bool -> Bool
&& Int64
x Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Int64
0x1000000 {- abs x <= 2^24 -}) -- if input is known to be small enough
  (Int64 -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
x)
  (RoundingMode -> Int64 -> Float
F.roundedFromInt64 RoundingMode
r Int64
x)
{-# INLINE roundedFloatFromInt64 #-}

roundedFloatFromWord64 :: RoundingMode -> Word64 -> Float
roundedFloatFromWord64 :: RoundingMode -> Word64 -> Float
roundedFloatFromWord64 RoundingMode
r Word64
x = Bool -> Float -> Float -> Float
forall a. Bool -> a -> a -> a
staticIf
  (Word64
x Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Word64
0x1000000 {- x <= 2^24 -}) -- if input is known to be small enough
  (Word64 -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
x)
  (RoundingMode -> Word64 -> Float
F.roundedFromWord64 RoundingMode
r Word64
x)
{-# INLINE roundedFloatFromWord64 #-}

intervalFloatFromInteger :: Integer -> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float)
intervalFloatFromInteger :: Integer -> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float)
intervalFloatFromInteger Integer
x
  | -Integer
0x1000000 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
x Bool -> Bool -> Bool
&& Integer
x Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
0x1000000 {- abs x <= 2^24 -} = (Float -> Rounded 'TowardNegInf Float
forall (r :: RoundingMode) a. a -> Rounded r a
Rounded (Integer -> Float
forall a. Num a => Integer -> a
fromInteger Integer
x), Float -> Rounded 'TowardInf Float
forall (r :: RoundingMode) a. a -> Rounded r a
Rounded (Integer -> Float
forall a. Num a => Integer -> a
fromInteger Integer
x))
  | Bool
otherwise = Integer -> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float)
forall a.
RealFloat a =>
Integer -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a)
intervalFromInteger_default Integer
x

roundedFloatFromRealFloat :: RealFloat a => RoundingMode -> a -> Float
roundedFloatFromRealFloat :: RoundingMode -> a -> Float
roundedFloatFromRealFloat RoundingMode
r a
x | a -> Bool
forall a. RealFloat a => a -> Bool
isNaN a
x = Float
0Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/Float
0
                              | a -> Bool
forall a. RealFloat a => a -> Bool
isInfinite a
x = if a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
> a
0 then Float
1Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/Float
0 else -Float
1Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/Float
0
                              | a -> Bool
forall a. RealFloat a => a -> Bool
isNegativeZero a
x = -Float
0
                              | Bool
otherwise = CFloat -> Float
coerce (RoundingMode -> Rational -> CFloat
forall a. RoundedFractional a => RoundingMode -> Rational -> a
roundedFromRational RoundingMode
r (a -> Rational
forall a. Real a => a -> Rational
toRational a
x) :: CFloat)
{-# NOINLINE [1] roundedFloatFromRealFloat #-}
{-# RULES
"roundedFloatFromRealFloat/Float" forall r (x :: Float).
  roundedFloatFromRealFloat r x = x
  #-}

instance RoundedRing CFloat where
  roundedAdd :: RoundingMode -> CFloat -> CFloat -> CFloat
roundedAdd = (RoundingMode -> Float -> Float -> Float)
-> RoundingMode -> CFloat -> CFloat -> CFloat
coerce RoundingMode -> Float -> Float -> Float
F.roundedAdd
  roundedSub :: RoundingMode -> CFloat -> CFloat -> CFloat
roundedSub = (RoundingMode -> Float -> Float -> Float)
-> RoundingMode -> CFloat -> CFloat -> CFloat
coerce RoundingMode -> Float -> Float -> Float
F.roundedSub
  roundedMul :: RoundingMode -> CFloat -> CFloat -> CFloat
roundedMul = (RoundingMode -> Float -> Float -> Float)
-> RoundingMode -> CFloat -> CFloat -> CFloat
coerce RoundingMode -> Float -> Float -> Float
F.roundedMul
  roundedFusedMultiplyAdd :: RoundingMode -> CFloat -> CFloat -> CFloat -> CFloat
roundedFusedMultiplyAdd = (RoundingMode -> Float -> Float -> Float -> Float)
-> RoundingMode -> CFloat -> CFloat -> CFloat -> CFloat
coerce RoundingMode -> Float -> Float -> Float -> Float
F.roundedFMA
  intervalMul :: Rounded 'TowardNegInf CFloat
-> Rounded 'TowardInf CFloat
-> Rounded 'TowardNegInf CFloat
-> Rounded 'TowardInf CFloat
-> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat)
intervalMul Rounded 'TowardNegInf CFloat
x Rounded 'TowardInf CFloat
x' Rounded 'TowardNegInf CFloat
y Rounded 'TowardInf CFloat
y' = ((Float -> Float -> Float -> Float -> Float)
-> Rounded 'TowardNegInf CFloat
-> Rounded 'TowardInf CFloat
-> Rounded 'TowardNegInf CFloat
-> Rounded 'TowardInf CFloat
-> Rounded 'TowardNegInf CFloat
coerce Float -> Float -> Float -> Float -> Float
F.intervalMul_down Rounded 'TowardNegInf CFloat
x Rounded 'TowardInf CFloat
x' Rounded 'TowardNegInf CFloat
y Rounded 'TowardInf CFloat
y', (Float -> Float -> Float -> Float -> Float)
-> Rounded 'TowardNegInf CFloat
-> Rounded 'TowardInf CFloat
-> Rounded 'TowardNegInf CFloat
-> Rounded 'TowardInf CFloat
-> Rounded 'TowardInf CFloat
coerce Float -> Float -> Float -> Float -> Float
F.intervalMul_up Rounded 'TowardNegInf CFloat
x Rounded 'TowardInf CFloat
x' Rounded 'TowardNegInf CFloat
y Rounded 'TowardInf CFloat
y')
  intervalMulAdd :: Rounded 'TowardNegInf CFloat
-> Rounded 'TowardInf CFloat
-> Rounded 'TowardNegInf CFloat
-> Rounded 'TowardInf CFloat
-> Rounded 'TowardNegInf CFloat
-> Rounded 'TowardInf CFloat
-> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat)
intervalMulAdd Rounded 'TowardNegInf CFloat
x Rounded 'TowardInf CFloat
x' Rounded 'TowardNegInf CFloat
y Rounded 'TowardInf CFloat
y' Rounded 'TowardNegInf CFloat
z Rounded 'TowardInf CFloat
z' = ((Float -> Float -> Float -> Float -> Float -> Float)
-> Rounded 'TowardNegInf CFloat
-> Rounded 'TowardInf CFloat
-> Rounded 'TowardNegInf CFloat
-> Rounded 'TowardInf CFloat
-> Rounded 'TowardNegInf CFloat
-> Rounded 'TowardNegInf CFloat
coerce Float -> Float -> Float -> Float -> Float -> Float
F.intervalMulAdd_down Rounded 'TowardNegInf CFloat
x Rounded 'TowardInf CFloat
x' Rounded 'TowardNegInf CFloat
y Rounded 'TowardInf CFloat
y' Rounded 'TowardNegInf CFloat
z, (Float -> Float -> Float -> Float -> Float -> Float)
-> Rounded 'TowardNegInf CFloat
-> Rounded 'TowardInf CFloat
-> Rounded 'TowardNegInf CFloat
-> Rounded 'TowardInf CFloat
-> Rounded 'TowardInf CFloat
-> Rounded 'TowardInf CFloat
coerce Float -> Float -> Float -> Float -> Float -> Float
F.intervalMulAdd_up Rounded 'TowardNegInf CFloat
x Rounded 'TowardInf CFloat
x' Rounded 'TowardNegInf CFloat
y Rounded 'TowardInf CFloat
y' Rounded 'TowardInf CFloat
z')
  roundedFromInteger :: RoundingMode -> Integer -> CFloat
roundedFromInteger RoundingMode
r Integer
x = Float -> CFloat
CFloat (RoundingMode -> Integer -> Float
forall a. RealFloat a => RoundingMode -> Integer -> a
roundedFromInteger_default RoundingMode
r Integer
x)
  intervalFromInteger :: Integer
-> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat)
intervalFromInteger = ((Integer
 -> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float))
-> Integer
-> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat)
coerce ((Integer
  -> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float))
 -> Integer
 -> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat))
-> ((Integer
     -> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float))
    -> Integer
    -> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat))
-> (Integer
    -> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float))
-> Integer
-> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat)
forall a. a -> a -> a
`asTypeOf` ((Rounded 'TowardNegInf Float -> Rounded 'TowardNegInf CFloat)
-> (Rounded 'TowardInf Float -> Rounded 'TowardInf CFloat)
-> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float)
-> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap (Float -> CFloat
CFloat (Float -> CFloat)
-> Rounded 'TowardNegInf Float -> Rounded 'TowardNegInf CFloat
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) (Float -> CFloat
CFloat (Float -> CFloat)
-> Rounded 'TowardInf Float -> Rounded 'TowardInf CFloat
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) ((Rounded 'TowardNegInf Float, Rounded 'TowardInf Float)
 -> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat))
-> (Integer
    -> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float))
-> Integer
-> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.)) Integer -> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float)
forall a.
RealFloat a =>
Integer -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a)
intervalFromInteger_default
  backendNameT :: Tagged CFloat String
backendNameT = String -> Tagged CFloat String
forall k (s :: k) b. b -> Tagged s b
Tagged String
cBackendName
  {-# INLINE roundedAdd #-}
  {-# INLINE roundedSub #-}
  {-# INLINE roundedMul #-}
  {-# INLINE roundedFusedMultiplyAdd #-}
  {-# INLINE intervalMul #-}
  {-# INLINE roundedFromInteger #-}
  {-# INLINE intervalFromInteger #-}

instance RoundedFractional CFloat where
  roundedDiv :: RoundingMode -> CFloat -> CFloat -> CFloat
roundedDiv = (RoundingMode -> Float -> Float -> Float)
-> RoundingMode -> CFloat -> CFloat -> CFloat
coerce RoundingMode -> Float -> Float -> Float
F.roundedDiv
  intervalDiv :: Rounded 'TowardNegInf CFloat
-> Rounded 'TowardInf CFloat
-> Rounded 'TowardNegInf CFloat
-> Rounded 'TowardInf CFloat
-> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat)
intervalDiv Rounded 'TowardNegInf CFloat
x Rounded 'TowardInf CFloat
x' Rounded 'TowardNegInf CFloat
y Rounded 'TowardInf CFloat
y' = ((Float -> Float -> Float -> Float -> Float)
-> Rounded 'TowardNegInf CFloat
-> Rounded 'TowardInf CFloat
-> Rounded 'TowardNegInf CFloat
-> Rounded 'TowardInf CFloat
-> Rounded 'TowardNegInf CFloat
coerce Float -> Float -> Float -> Float -> Float
F.intervalDiv_down Rounded 'TowardNegInf CFloat
x Rounded 'TowardInf CFloat
x' Rounded 'TowardNegInf CFloat
y Rounded 'TowardInf CFloat
y', (Float -> Float -> Float -> Float -> Float)
-> Rounded 'TowardNegInf CFloat
-> Rounded 'TowardInf CFloat
-> Rounded 'TowardNegInf CFloat
-> Rounded 'TowardInf CFloat
-> Rounded 'TowardInf CFloat
coerce Float -> Float -> Float -> Float -> Float
F.intervalDiv_up Rounded 'TowardNegInf CFloat
x Rounded 'TowardInf CFloat
x' Rounded 'TowardNegInf CFloat
y Rounded 'TowardInf CFloat
y')
  intervalDivAdd :: Rounded 'TowardNegInf CFloat
-> Rounded 'TowardInf CFloat
-> Rounded 'TowardNegInf CFloat
-> Rounded 'TowardInf CFloat
-> Rounded 'TowardNegInf CFloat
-> Rounded 'TowardInf CFloat
-> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat)
intervalDivAdd Rounded 'TowardNegInf CFloat
x Rounded 'TowardInf CFloat
x' Rounded 'TowardNegInf CFloat
y Rounded 'TowardInf CFloat
y' Rounded 'TowardNegInf CFloat
z Rounded 'TowardInf CFloat
z' = ((Float -> Float -> Float -> Float -> Float -> Float)
-> Rounded 'TowardNegInf CFloat
-> Rounded 'TowardInf CFloat
-> Rounded 'TowardNegInf CFloat
-> Rounded 'TowardInf CFloat
-> Rounded 'TowardNegInf CFloat
-> Rounded 'TowardNegInf CFloat
coerce Float -> Float -> Float -> Float -> Float -> Float
F.intervalDivAdd_down Rounded 'TowardNegInf CFloat
x Rounded 'TowardInf CFloat
x' Rounded 'TowardNegInf CFloat
y Rounded 'TowardInf CFloat
y' Rounded 'TowardNegInf CFloat
z, (Float -> Float -> Float -> Float -> Float -> Float)
-> Rounded 'TowardNegInf CFloat
-> Rounded 'TowardInf CFloat
-> Rounded 'TowardNegInf CFloat
-> Rounded 'TowardInf CFloat
-> Rounded 'TowardInf CFloat
-> Rounded 'TowardInf CFloat
coerce Float -> Float -> Float -> Float -> Float -> Float
F.intervalDivAdd_up Rounded 'TowardNegInf CFloat
x Rounded 'TowardInf CFloat
x' Rounded 'TowardNegInf CFloat
y Rounded 'TowardInf CFloat
y' Rounded 'TowardInf CFloat
z')
  roundedFromRational :: RoundingMode -> Rational -> CFloat
roundedFromRational RoundingMode
r Rational
x = Float -> CFloat
CFloat (RoundingMode -> Rational -> Float
forall a. RealFloat a => RoundingMode -> Rational -> a
roundedFromRational_default RoundingMode
r Rational
x)
  intervalFromRational :: Rational
-> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat)
intervalFromRational = ((Rational
 -> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float))
-> Rational
-> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat)
coerce ((Rational
  -> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float))
 -> Rational
 -> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat))
-> ((Rational
     -> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float))
    -> Rational
    -> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat))
-> (Rational
    -> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float))
-> Rational
-> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat)
forall a. a -> a -> a
`asTypeOf` ((Rounded 'TowardNegInf Float -> Rounded 'TowardNegInf CFloat)
-> (Rounded 'TowardInf Float -> Rounded 'TowardInf CFloat)
-> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float)
-> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap (Float -> CFloat
CFloat (Float -> CFloat)
-> Rounded 'TowardNegInf Float -> Rounded 'TowardNegInf CFloat
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) (Float -> CFloat
CFloat (Float -> CFloat)
-> Rounded 'TowardInf Float -> Rounded 'TowardInf CFloat
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) ((Rounded 'TowardNegInf Float, Rounded 'TowardInf Float)
 -> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat))
-> (Rational
    -> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float))
-> Rational
-> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.)) Rational -> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float)
forall a.
RealFloat a =>
Rational -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a)
intervalFromRational_default
  roundedFromRealFloat :: RoundingMode -> b -> CFloat
roundedFromRealFloat RoundingMode
r b
x = Float -> CFloat
coerce (RoundingMode -> b -> Float
forall a. RealFloat a => RoundingMode -> a -> Float
roundedFloatFromRealFloat RoundingMode
r b
x)
  {-# INLINE roundedDiv #-}
  {-# INLINE intervalDiv #-}
  {-# INLINE roundedFromRational #-}
  {-# INLINE intervalFromRational #-}
  {-# INLINE roundedFromRealFloat #-}

instance RoundedSqrt CFloat where
  roundedSqrt :: RoundingMode -> CFloat -> CFloat
roundedSqrt = (RoundingMode -> Float -> Float)
-> RoundingMode -> CFloat -> CFloat
coerce RoundingMode -> Float -> Float
F.roundedSqrt
  {-# INLINE roundedSqrt #-}

instance RoundedRing_Vector VS.Vector CFloat where
  roundedSum :: RoundingMode -> Vector CFloat -> CFloat
roundedSum RoundingMode
mode Vector CFloat
vec = Float -> CFloat
CFloat (Float -> CFloat) -> Float -> CFloat
forall a b. (a -> b) -> a -> b
$ IO Float -> Float
forall a. IO a -> a
unsafePerformIO (IO Float -> Float) -> IO Float -> Float
forall a b. (a -> b) -> a -> b
$
    Vector CFloat -> (Ptr CFloat -> IO Float) -> IO Float
forall a b. Storable a => Vector a -> (Ptr a -> IO b) -> IO b
VS.unsafeWith Vector CFloat
vec ((Ptr CFloat -> IO Float) -> IO Float)
-> (Ptr CFloat -> IO Float) -> IO Float
forall a b. (a -> b) -> a -> b
$ \Ptr CFloat
ptr -> RoundingMode -> Int -> Int -> Ptr Float -> IO Float
F.vectorSumPtr RoundingMode
mode (Vector CFloat -> Int
forall a. Storable a => Vector a -> Int
VS.length Vector CFloat
vec) Int
0 (Ptr CFloat -> Ptr Float
forall a b. Ptr a -> Ptr b
castPtr Ptr CFloat
ptr)
  zipWith_roundedAdd :: RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat
zipWith_roundedAdd = (RoundingMode
 -> Int
 -> Int
 -> Ptr CFloat
 -> Int
 -> Ptr CFloat
 -> Int
 -> Ptr CFloat
 -> IO ())
-> RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat
forall a b c.
(Storable a, Storable b, Storable c) =>
(RoundingMode
 -> Int -> Int -> Ptr c -> Int -> Ptr a -> Int -> Ptr b -> IO ())
-> RoundingMode -> Vector a -> Vector b -> Vector c
zipWith_Storable ((RoundingMode
 -> Int
 -> Int
 -> Ptr Float
 -> Int
 -> Ptr Float
 -> Int
 -> Ptr Float
 -> IO ())
-> RoundingMode
-> Int
-> Int
-> Ptr CFloat
-> Int
-> Ptr CFloat
-> Int
-> Ptr CFloat
-> IO ()
coerce RoundingMode
-> Int
-> Int
-> Ptr Float
-> Int
-> Ptr Float
-> Int
-> Ptr Float
-> IO ()
F.vectorAddPtr)
  zipWith_roundedSub :: RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat
zipWith_roundedSub = (RoundingMode
 -> Int
 -> Int
 -> Ptr CFloat
 -> Int
 -> Ptr CFloat
 -> Int
 -> Ptr CFloat
 -> IO ())
-> RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat
forall a b c.
(Storable a, Storable b, Storable c) =>
(RoundingMode
 -> Int -> Int -> Ptr c -> Int -> Ptr a -> Int -> Ptr b -> IO ())
-> RoundingMode -> Vector a -> Vector b -> Vector c
zipWith_Storable ((RoundingMode
 -> Int
 -> Int
 -> Ptr Float
 -> Int
 -> Ptr Float
 -> Int
 -> Ptr Float
 -> IO ())
-> RoundingMode
-> Int
-> Int
-> Ptr CFloat
-> Int
-> Ptr CFloat
-> Int
-> Ptr CFloat
-> IO ()
coerce RoundingMode
-> Int
-> Int
-> Ptr Float
-> Int
-> Ptr Float
-> Int
-> Ptr Float
-> IO ()
F.vectorSubPtr)
  zipWith_roundedMul :: RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat
zipWith_roundedMul = (RoundingMode
 -> Int
 -> Int
 -> Ptr CFloat
 -> Int
 -> Ptr CFloat
 -> Int
 -> Ptr CFloat
 -> IO ())
-> RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat
forall a b c.
(Storable a, Storable b, Storable c) =>
(RoundingMode
 -> Int -> Int -> Ptr c -> Int -> Ptr a -> Int -> Ptr b -> IO ())
-> RoundingMode -> Vector a -> Vector b -> Vector c
zipWith_Storable ((RoundingMode
 -> Int
 -> Int
 -> Ptr Float
 -> Int
 -> Ptr Float
 -> Int
 -> Ptr Float
 -> IO ())
-> RoundingMode
-> Int
-> Int
-> Ptr CFloat
-> Int
-> Ptr CFloat
-> Int
-> Ptr CFloat
-> IO ()
coerce RoundingMode
-> Int
-> Int
-> Ptr Float
-> Int
-> Ptr Float
-> Int
-> Ptr Float
-> IO ()
F.vectorMulPtr)
  zipWith3_roundedFusedMultiplyAdd :: RoundingMode
-> Vector CFloat -> Vector CFloat -> Vector CFloat -> Vector CFloat
zipWith3_roundedFusedMultiplyAdd = (RoundingMode
 -> Int
 -> Int
 -> Ptr CFloat
 -> Int
 -> Ptr CFloat
 -> Int
 -> Ptr CFloat
 -> Int
 -> Ptr CFloat
 -> IO ())
-> RoundingMode
-> Vector CFloat
-> Vector CFloat
-> Vector CFloat
-> Vector CFloat
forall a b c d.
(Storable a, Storable b, Storable c, Storable d) =>
(RoundingMode
 -> Int
 -> Int
 -> Ptr d
 -> Int
 -> Ptr a
 -> Int
 -> Ptr b
 -> Int
 -> Ptr c
 -> IO ())
-> RoundingMode -> Vector a -> Vector b -> Vector c -> Vector d
zipWith3_Storable ((RoundingMode
 -> Int
 -> Int
 -> Ptr Float
 -> Int
 -> Ptr Float
 -> Int
 -> Ptr Float
 -> Int
 -> Ptr Float
 -> IO ())
-> RoundingMode
-> Int
-> Int
-> Ptr CFloat
-> Int
-> Ptr CFloat
-> Int
-> Ptr CFloat
-> Int
-> Ptr CFloat
-> IO ()
coerce RoundingMode
-> Int
-> Int
-> Ptr Float
-> Int
-> Ptr Float
-> Int
-> Ptr Float
-> Int
-> Ptr Float
-> IO ()
F.vectorFMAPtr)

instance RoundedFractional_Vector VS.Vector CFloat where
  zipWith_roundedDiv :: RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat
zipWith_roundedDiv = (RoundingMode
 -> Int
 -> Int
 -> Ptr CFloat
 -> Int
 -> Ptr CFloat
 -> Int
 -> Ptr CFloat
 -> IO ())
-> RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat
forall a b c.
(Storable a, Storable b, Storable c) =>
(RoundingMode
 -> Int -> Int -> Ptr c -> Int -> Ptr a -> Int -> Ptr b -> IO ())
-> RoundingMode -> Vector a -> Vector b -> Vector c
zipWith_Storable ((RoundingMode
 -> Int
 -> Int
 -> Ptr Float
 -> Int
 -> Ptr Float
 -> Int
 -> Ptr Float
 -> IO ())
-> RoundingMode
-> Int
-> Int
-> Ptr CFloat
-> Int
-> Ptr CFloat
-> Int
-> Ptr CFloat
-> IO ()
coerce RoundingMode
-> Int
-> Int
-> Ptr Float
-> Int
-> Ptr Float
-> Int
-> Ptr Float
-> IO ()
F.vectorDivPtr)

instance RoundedSqrt_Vector VS.Vector CFloat where
  map_roundedSqrt :: RoundingMode -> Vector CFloat -> Vector CFloat
map_roundedSqrt = (RoundingMode
 -> Int -> Int -> Ptr CFloat -> Int -> Ptr CFloat -> IO ())
-> RoundingMode -> Vector CFloat -> Vector CFloat
forall a b.
(Storable a, Storable b) =>
(RoundingMode -> Int -> Int -> Ptr b -> Int -> Ptr a -> IO ())
-> RoundingMode -> Vector a -> Vector b
map_Storable ((RoundingMode
 -> Int -> Int -> Ptr Float -> Int -> Ptr Float -> IO ())
-> RoundingMode
-> Int
-> Int
-> Ptr CFloat
-> Int
-> Ptr CFloat
-> IO ()
coerce RoundingMode
-> Int -> Int -> Ptr Float -> Int -> Ptr Float -> IO ()
F.vectorSqrtPtr)

instance RoundedRing_Vector VU.Vector CFloat where
  roundedSum :: RoundingMode -> Vector CFloat -> CFloat
roundedSum RoundingMode
mode (V_CFloat (VU.V_Float (VP.Vector off len (ByteArray arr)))) =
    Float -> CFloat
CFloat (Float -> CFloat) -> Float -> CFloat
forall a b. (a -> b) -> a -> b
$ RoundingMode -> Int -> Int -> ByteArray# -> Float
F.vectorSumByteArray RoundingMode
mode Int
len Int
off ByteArray#
arr
  zipWith_roundedAdd :: RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat
zipWith_roundedAdd = (RoundingMode -> Vector Float -> Vector Float -> Vector Float)
-> RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat
coerce ((RoundingMode
 -> Int
 -> Int
 -> MutableByteArray# RealWorld
 -> Int
 -> ByteArray#
 -> Int
 -> ByteArray#
 -> IO ())
-> RoundingMode -> Vector Float -> Vector Float -> Vector Float
forall a b c.
(Prim a, Prim b, Prim c) =>
(RoundingMode
 -> Int
 -> Int
 -> MutableByteArray# RealWorld
 -> Int
 -> ByteArray#
 -> Int
 -> ByteArray#
 -> IO ())
-> RoundingMode -> Vector a -> Vector b -> Vector c
zipWith_Primitive RoundingMode
-> Int
-> Int
-> MutableByteArray# RealWorld
-> Int
-> ByteArray#
-> Int
-> ByteArray#
-> IO ()
F.vectorAddByteArray :: RoundingMode -> VP.Vector Float -> VP.Vector Float -> VP.Vector Float)
  zipWith_roundedSub :: RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat
zipWith_roundedSub = (RoundingMode -> Vector Float -> Vector Float -> Vector Float)
-> RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat
coerce ((RoundingMode
 -> Int
 -> Int
 -> MutableByteArray# RealWorld
 -> Int
 -> ByteArray#
 -> Int
 -> ByteArray#
 -> IO ())
-> RoundingMode -> Vector Float -> Vector Float -> Vector Float
forall a b c.
(Prim a, Prim b, Prim c) =>
(RoundingMode
 -> Int
 -> Int
 -> MutableByteArray# RealWorld
 -> Int
 -> ByteArray#
 -> Int
 -> ByteArray#
 -> IO ())
-> RoundingMode -> Vector a -> Vector b -> Vector c
zipWith_Primitive RoundingMode
-> Int
-> Int
-> MutableByteArray# RealWorld
-> Int
-> ByteArray#
-> Int
-> ByteArray#
-> IO ()
F.vectorSubByteArray :: RoundingMode -> VP.Vector Float -> VP.Vector Float -> VP.Vector Float)
  zipWith_roundedMul :: RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat
zipWith_roundedMul = (RoundingMode -> Vector Float -> Vector Float -> Vector Float)
-> RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat
coerce ((RoundingMode
 -> Int
 -> Int
 -> MutableByteArray# RealWorld
 -> Int
 -> ByteArray#
 -> Int
 -> ByteArray#
 -> IO ())
-> RoundingMode -> Vector Float -> Vector Float -> Vector Float
forall a b c.
(Prim a, Prim b, Prim c) =>
(RoundingMode
 -> Int
 -> Int
 -> MutableByteArray# RealWorld
 -> Int
 -> ByteArray#
 -> Int
 -> ByteArray#
 -> IO ())
-> RoundingMode -> Vector a -> Vector b -> Vector c
zipWith_Primitive RoundingMode
-> Int
-> Int
-> MutableByteArray# RealWorld
-> Int
-> ByteArray#
-> Int
-> ByteArray#
-> IO ()
F.vectorMulByteArray :: RoundingMode -> VP.Vector Float -> VP.Vector Float -> VP.Vector Float)
  zipWith3_roundedFusedMultiplyAdd :: RoundingMode
-> Vector CFloat -> Vector CFloat -> Vector CFloat -> Vector CFloat
zipWith3_roundedFusedMultiplyAdd = (RoundingMode
 -> Vector Float -> Vector Float -> Vector Float -> Vector Float)
-> RoundingMode
-> Vector CFloat
-> Vector CFloat
-> Vector CFloat
-> Vector CFloat
coerce ((RoundingMode
 -> Int
 -> Int
 -> MutableByteArray# RealWorld
 -> Int
 -> ByteArray#
 -> Int
 -> ByteArray#
 -> Int
 -> ByteArray#
 -> IO ())
-> RoundingMode
-> Vector Float
-> Vector Float
-> Vector Float
-> Vector Float
forall a b c d.
(Prim a, Prim b, Prim c, Prim d) =>
(RoundingMode
 -> Int
 -> Int
 -> MutableByteArray# RealWorld
 -> Int
 -> ByteArray#
 -> Int
 -> ByteArray#
 -> Int
 -> ByteArray#
 -> IO ())
-> RoundingMode -> Vector a -> Vector b -> Vector c -> Vector d
zipWith3_Primitive RoundingMode
-> Int
-> Int
-> MutableByteArray# RealWorld
-> Int
-> ByteArray#
-> Int
-> ByteArray#
-> Int
-> ByteArray#
-> IO ()
F.vectorFMAByteArray :: RoundingMode -> VP.Vector Float -> VP.Vector Float -> VP.Vector Float -> VP.Vector Float)

instance RoundedFractional_Vector VU.Vector CFloat where
  zipWith_roundedDiv :: RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat
zipWith_roundedDiv = (RoundingMode -> Vector Float -> Vector Float -> Vector Float)
-> RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat
coerce ((RoundingMode
 -> Int
 -> Int
 -> MutableByteArray# RealWorld
 -> Int
 -> ByteArray#
 -> Int
 -> ByteArray#
 -> IO ())
-> RoundingMode -> Vector Float -> Vector Float -> Vector Float
forall a b c.
(Prim a, Prim b, Prim c) =>
(RoundingMode
 -> Int
 -> Int
 -> MutableByteArray# RealWorld
 -> Int
 -> ByteArray#
 -> Int
 -> ByteArray#
 -> IO ())
-> RoundingMode -> Vector a -> Vector b -> Vector c
zipWith_Primitive RoundingMode
-> Int
-> Int
-> MutableByteArray# RealWorld
-> Int
-> ByteArray#
-> Int
-> ByteArray#
-> IO ()
F.vectorDivByteArray :: RoundingMode -> VP.Vector Float -> VP.Vector Float -> VP.Vector Float)

instance RoundedSqrt_Vector VU.Vector CFloat where
  map_roundedSqrt :: RoundingMode -> Vector CFloat -> Vector CFloat
map_roundedSqrt = (RoundingMode -> Vector Float -> Vector Float)
-> RoundingMode -> Vector CFloat -> Vector CFloat
coerce ((RoundingMode
 -> Int
 -> Int
 -> MutableByteArray# RealWorld
 -> Int
 -> ByteArray#
 -> IO ())
-> RoundingMode -> Vector Float -> Vector Float
forall a b.
(Prim a, Prim b) =>
(RoundingMode
 -> Int
 -> Int
 -> MutableByteArray# RealWorld
 -> Int
 -> ByteArray#
 -> IO ())
-> RoundingMode -> Vector a -> Vector b
map_Primitive RoundingMode
-> Int
-> Int
-> MutableByteArray# RealWorld
-> Int
-> ByteArray#
-> IO ()
F.vectorSqrtByteArray :: RoundingMode -> VP.Vector Float -> VP.Vector Float)

--
-- Double
--

-- | A wrapper providing particular instances for 'RoundedRing', 'RoundedFractional' and 'RoundedSqrt'.
--
-- This type is different from @CDouble@ from "Foreign.C.Types".
newtype CDouble = CDouble Double
  deriving (CDouble -> CDouble -> Bool
(CDouble -> CDouble -> Bool)
-> (CDouble -> CDouble -> Bool) -> Eq CDouble
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
Eq CDouble
-> (CDouble -> CDouble -> Ordering)
-> (CDouble -> CDouble -> Bool)
-> (CDouble -> CDouble -> Bool)
-> (CDouble -> CDouble -> Bool)
-> (CDouble -> CDouble -> Bool)
-> (CDouble -> CDouble -> CDouble)
-> (CDouble -> CDouble -> CDouble)
-> Ord 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
$cp1Ord :: Eq CDouble
Ord,Int -> CDouble -> ShowS
[CDouble] -> ShowS
CDouble -> String
(Int -> CDouble -> ShowS)
-> (CDouble -> String) -> ([CDouble] -> ShowS) -> Show CDouble
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. CDouble -> Rep CDouble x)
-> (forall x. Rep CDouble x -> CDouble) -> Generic CDouble
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
(CDouble -> CDouble -> CDouble)
-> (CDouble -> CDouble -> CDouble)
-> (CDouble -> CDouble -> CDouble)
-> (CDouble -> CDouble)
-> (CDouble -> CDouble)
-> (CDouble -> CDouble)
-> (Integer -> CDouble)
-> Num 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 b -> Int -> IO CDouble
Ptr b -> Int -> CDouble -> IO ()
Ptr CDouble -> IO CDouble
Ptr CDouble -> Int -> IO CDouble
Ptr CDouble -> Int -> CDouble -> IO ()
Ptr CDouble -> CDouble -> IO ()
CDouble -> Int
(CDouble -> Int)
-> (CDouble -> Int)
-> (Ptr CDouble -> Int -> IO CDouble)
-> (Ptr CDouble -> Int -> CDouble -> IO ())
-> (forall b. Ptr b -> Int -> IO CDouble)
-> (forall b. Ptr b -> Int -> CDouble -> IO ())
-> (Ptr CDouble -> IO CDouble)
-> (Ptr CDouble -> CDouble -> IO ())
-> Storable CDouble
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 :: Ptr b -> Int -> CDouble -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> CDouble -> IO ()
peekByteOff :: 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

roundedDoubleFromInt64 :: RoundingMode -> Int64 -> Double
roundedDoubleFromInt64 :: RoundingMode -> Int64 -> Double
roundedDoubleFromInt64 RoundingMode
r Int64
x = Bool -> Double -> Double -> Double
forall a. Bool -> a -> a -> a
staticIf
  (-Int64
0x20000000000000 Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Int64
x Bool -> Bool -> Bool
&& Int64
x Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Int64
0x20000000000000 {- abs x <= 2^53 -}) -- if input is known to be small enough
  (Int64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
x)
  (RoundingMode -> Int64 -> Double
D.roundedFromInt64 RoundingMode
r Int64
x)
{-# INLINE roundedDoubleFromInt64 #-}

roundedDoubleFromWord64 :: RoundingMode -> Word64 -> Double
roundedDoubleFromWord64 :: RoundingMode -> Word64 -> Double
roundedDoubleFromWord64 RoundingMode
r Word64
x = Bool -> Double -> Double -> Double
forall a. Bool -> a -> a -> a
staticIf
  (Word64
x Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Word64
0x20000000000000 {- x <= 2^53 -}) -- if input is known to be small enough
  (Word64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
x)
  (RoundingMode -> Word64 -> Double
D.roundedFromWord64 RoundingMode
r Word64
x)
{-# INLINE roundedDoubleFromWord64 #-}

roundedDoubleFromRealFloat :: RealFloat a => RoundingMode -> a -> Double
roundedDoubleFromRealFloat :: RoundingMode -> a -> Double
roundedDoubleFromRealFloat RoundingMode
r a
x | a -> Bool
forall a. RealFloat a => a -> Bool
isNaN a
x = Double
0Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
0
                               | a -> Bool
forall a. RealFloat a => a -> Bool
isInfinite a
x = if a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
> a
0 then Double
1Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
0 else -Double
1Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
0
                               | a -> Bool
forall a. RealFloat a => a -> Bool
isNegativeZero a
x = -Double
0
                               | Bool
otherwise = CDouble -> Double
coerce (RoundingMode -> Rational -> CDouble
forall a. RoundedFractional a => RoundingMode -> Rational -> a
roundedFromRational RoundingMode
r (a -> Rational
forall a. Real a => a -> Rational
toRational a
x) :: CDouble)
{-# NOINLINE [1] roundedDoubleFromRealFloat #-}
{-# RULES
"roundedDoubleFromRealFloat/Double" forall r (x :: Double).
  roundedDoubleFromRealFloat r x = x
"roundedDoubleFromRealFloat/Float" forall r (x :: Float).
  roundedDoubleFromRealFloat r x = realToFrac x -- should be rewritten into float2Double
  #-}

instance RoundedRing CDouble where
  roundedAdd :: RoundingMode -> CDouble -> CDouble -> CDouble
roundedAdd = (RoundingMode -> Double -> Double -> Double)
-> RoundingMode -> CDouble -> CDouble -> CDouble
coerce RoundingMode -> Double -> Double -> Double
D.roundedAdd
  roundedSub :: RoundingMode -> CDouble -> CDouble -> CDouble
roundedSub = (RoundingMode -> Double -> Double -> Double)
-> RoundingMode -> CDouble -> CDouble -> CDouble
coerce RoundingMode -> Double -> Double -> Double
D.roundedSub
  roundedMul :: RoundingMode -> CDouble -> CDouble -> CDouble
roundedMul = (RoundingMode -> Double -> Double -> Double)
-> RoundingMode -> CDouble -> CDouble -> CDouble
coerce RoundingMode -> Double -> Double -> Double
D.roundedMul
  roundedFusedMultiplyAdd :: RoundingMode -> CDouble -> CDouble -> CDouble -> CDouble
roundedFusedMultiplyAdd = (RoundingMode -> Double -> Double -> Double -> Double)
-> RoundingMode -> CDouble -> CDouble -> CDouble -> CDouble
coerce RoundingMode -> Double -> Double -> Double -> Double
D.roundedFMA
  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' = ((Double -> Double -> Double -> Double -> Double)
-> Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> Rounded 'TowardNegInf CDouble
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', (Double -> Double -> Double -> Double -> Double)
-> Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> Rounded 'TowardInf CDouble
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' = ((Double -> Double -> Double -> Double -> Double -> Double)
-> Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> Rounded 'TowardNegInf CDouble
-> Rounded 'TowardNegInf CDouble
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, (Double -> Double -> Double -> Double -> Double -> Double)
-> Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> Rounded 'TowardInf CDouble
-> Rounded 'TowardInf CDouble
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 RoundingMode
r Integer
x = Double -> CDouble
CDouble (RoundingMode -> Integer -> Double
forall a. RealFloat a => RoundingMode -> Integer -> a
roundedFromInteger_default RoundingMode
r Integer
x)
  intervalFromInteger :: Integer
-> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble)
intervalFromInteger = ((Integer
 -> (Rounded 'TowardNegInf Double, Rounded 'TowardInf Double))
-> Integer
-> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble)
coerce ((Integer
  -> (Rounded 'TowardNegInf Double, Rounded 'TowardInf Double))
 -> Integer
 -> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble))
-> ((Integer
     -> (Rounded 'TowardNegInf Double, Rounded 'TowardInf Double))
    -> Integer
    -> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble))
-> (Integer
    -> (Rounded 'TowardNegInf Double, Rounded 'TowardInf Double))
-> Integer
-> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble)
forall a. a -> a -> a
`asTypeOf` ((Rounded 'TowardNegInf Double -> Rounded 'TowardNegInf CDouble)
-> (Rounded 'TowardInf Double -> Rounded 'TowardInf CDouble)
-> (Rounded 'TowardNegInf Double, Rounded 'TowardInf Double)
-> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap (Double -> CDouble
CDouble (Double -> CDouble)
-> Rounded 'TowardNegInf Double -> Rounded 'TowardNegInf CDouble
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) (Double -> CDouble
CDouble (Double -> CDouble)
-> Rounded 'TowardInf Double -> Rounded 'TowardInf CDouble
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) ((Rounded 'TowardNegInf Double, Rounded 'TowardInf Double)
 -> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble))
-> (Integer
    -> (Rounded 'TowardNegInf Double, Rounded 'TowardInf Double))
-> Integer
-> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.)) Integer
-> (Rounded 'TowardNegInf Double, Rounded 'TowardInf Double)
forall a.
RealFloat a =>
Integer -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a)
intervalFromInteger_default
  backendNameT :: Tagged CDouble String
backendNameT = String -> Tagged CDouble String
forall k (s :: k) b. b -> Tagged s b
Tagged String
cBackendName
  {-# INLINE roundedAdd #-}
  {-# INLINE roundedSub #-}
  {-# INLINE roundedMul #-}
  {-# INLINE roundedFusedMultiplyAdd #-}
  {-# INLINE intervalMul #-}
  {-# INLINE roundedFromInteger #-}
  {-# INLINE intervalFromInteger #-}

instance RoundedFractional CDouble where
  roundedDiv :: RoundingMode -> CDouble -> CDouble -> CDouble
roundedDiv = (RoundingMode -> Double -> Double -> Double)
-> RoundingMode -> CDouble -> CDouble -> CDouble
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' = ((Double -> Double -> Double -> Double -> Double)
-> Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> Rounded 'TowardNegInf CDouble
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', (Double -> Double -> Double -> Double -> Double)
-> Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> Rounded 'TowardInf CDouble
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' = ((Double -> Double -> Double -> Double -> Double -> Double)
-> Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> Rounded 'TowardNegInf CDouble
-> Rounded 'TowardNegInf CDouble
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, (Double -> Double -> Double -> Double -> Double -> Double)
-> Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> Rounded 'TowardNegInf CDouble
-> Rounded 'TowardInf CDouble
-> Rounded 'TowardInf CDouble
-> Rounded 'TowardInf CDouble
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')
  roundedFromRational :: RoundingMode -> Rational -> CDouble
roundedFromRational RoundingMode
r Rational
x = Double -> CDouble
CDouble (RoundingMode -> Rational -> Double
forall a. RealFloat a => RoundingMode -> Rational -> a
roundedFromRational_default RoundingMode
r Rational
x)
  intervalFromRational :: Rational
-> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble)
intervalFromRational = ((Rational
 -> (Rounded 'TowardNegInf Double, Rounded 'TowardInf Double))
-> Rational
-> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble)
coerce ((Rational
  -> (Rounded 'TowardNegInf Double, Rounded 'TowardInf Double))
 -> Rational
 -> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble))
-> ((Rational
     -> (Rounded 'TowardNegInf Double, Rounded 'TowardInf Double))
    -> Rational
    -> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble))
-> (Rational
    -> (Rounded 'TowardNegInf Double, Rounded 'TowardInf Double))
-> Rational
-> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble)
forall a. a -> a -> a
`asTypeOf` ((Rounded 'TowardNegInf Double -> Rounded 'TowardNegInf CDouble)
-> (Rounded 'TowardInf Double -> Rounded 'TowardInf CDouble)
-> (Rounded 'TowardNegInf Double, Rounded 'TowardInf Double)
-> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap (Double -> CDouble
CDouble (Double -> CDouble)
-> Rounded 'TowardNegInf Double -> Rounded 'TowardNegInf CDouble
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) (Double -> CDouble
CDouble (Double -> CDouble)
-> Rounded 'TowardInf Double -> Rounded 'TowardInf CDouble
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) ((Rounded 'TowardNegInf Double, Rounded 'TowardInf Double)
 -> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble))
-> (Rational
    -> (Rounded 'TowardNegInf Double, Rounded 'TowardInf Double))
-> Rational
-> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.)) Rational
-> (Rounded 'TowardNegInf Double, Rounded 'TowardInf Double)
forall a.
RealFloat a =>
Rational -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a)
intervalFromRational_default
  -- TODO: Specialize small case in ***FromRational?
  roundedFromRealFloat :: RoundingMode -> b -> CDouble
roundedFromRealFloat RoundingMode
r b
x = Double -> CDouble
coerce (RoundingMode -> b -> Double
forall a. RealFloat a => RoundingMode -> a -> Double
roundedDoubleFromRealFloat RoundingMode
r b
x)
  {-# INLINE roundedDiv #-}
  {-# INLINE intervalDiv #-}
  {-# INLINE roundedFromRational #-}
  {-# INLINE intervalFromRational #-}
  {-# INLINE roundedFromRealFloat #-}

instance RoundedSqrt CDouble where
  roundedSqrt :: RoundingMode -> CDouble -> CDouble
roundedSqrt = (RoundingMode -> Double -> Double)
-> RoundingMode -> CDouble -> CDouble
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 = Double -> CDouble
CDouble (Double -> CDouble) -> Double -> CDouble
forall a b. (a -> b) -> a -> b
$ IO Double -> Double
forall a. IO a -> a
unsafePerformIO (IO Double -> Double) -> IO Double -> Double
forall a b. (a -> b) -> a -> b
$
    Vector CDouble -> (Ptr CDouble -> IO Double) -> IO Double
forall a b. Storable a => Vector a -> (Ptr a -> IO b) -> IO b
VS.unsafeWith Vector CDouble
vec ((Ptr CDouble -> IO Double) -> IO Double)
-> (Ptr CDouble -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \Ptr CDouble
ptr -> RoundingMode -> Int -> Int -> Ptr Double -> IO Double
D.vectorSumPtr RoundingMode
mode (Vector CDouble -> Int
forall a. Storable a => Vector a -> Int
VS.length Vector CDouble
vec) Int
0 (Ptr CDouble -> Ptr Double
forall a b. Ptr a -> Ptr b
castPtr Ptr CDouble
ptr)
  zipWith_roundedAdd :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble
zipWith_roundedAdd = (RoundingMode
 -> Int
 -> Int
 -> Ptr CDouble
 -> Int
 -> Ptr CDouble
 -> Int
 -> Ptr CDouble
 -> IO ())
-> RoundingMode
-> Vector CDouble
-> Vector CDouble
-> Vector CDouble
forall a b c.
(Storable a, Storable b, Storable c) =>
(RoundingMode
 -> Int -> Int -> Ptr c -> Int -> Ptr a -> Int -> Ptr b -> IO ())
-> RoundingMode -> Vector a -> Vector b -> Vector c
zipWith_Storable ((RoundingMode
 -> Int
 -> Int
 -> Ptr Double
 -> Int
 -> Ptr Double
 -> Int
 -> Ptr Double
 -> IO ())
-> RoundingMode
-> Int
-> Int
-> Ptr CDouble
-> Int
-> Ptr CDouble
-> Int
-> Ptr CDouble
-> IO ()
coerce RoundingMode
-> Int
-> Int
-> Ptr Double
-> Int
-> Ptr Double
-> Int
-> Ptr Double
-> IO ()
D.vectorAddPtr)
  zipWith_roundedSub :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble
zipWith_roundedSub = (RoundingMode
 -> Int
 -> Int
 -> Ptr CDouble
 -> Int
 -> Ptr CDouble
 -> Int
 -> Ptr CDouble
 -> IO ())
-> RoundingMode
-> Vector CDouble
-> Vector CDouble
-> Vector CDouble
forall a b c.
(Storable a, Storable b, Storable c) =>
(RoundingMode
 -> Int -> Int -> Ptr c -> Int -> Ptr a -> Int -> Ptr b -> IO ())
-> RoundingMode -> Vector a -> Vector b -> Vector c
zipWith_Storable ((RoundingMode
 -> Int
 -> Int
 -> Ptr Double
 -> Int
 -> Ptr Double
 -> Int
 -> Ptr Double
 -> IO ())
-> RoundingMode
-> Int
-> Int
-> Ptr CDouble
-> Int
-> Ptr CDouble
-> Int
-> Ptr CDouble
-> IO ()
coerce RoundingMode
-> Int
-> Int
-> Ptr Double
-> Int
-> Ptr Double
-> Int
-> Ptr Double
-> IO ()
D.vectorSubPtr)
  zipWith_roundedMul :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble
zipWith_roundedMul = (RoundingMode
 -> Int
 -> Int
 -> Ptr CDouble
 -> Int
 -> Ptr CDouble
 -> Int
 -> Ptr CDouble
 -> IO ())
-> RoundingMode
-> Vector CDouble
-> Vector CDouble
-> Vector CDouble
forall a b c.
(Storable a, Storable b, Storable c) =>
(RoundingMode
 -> Int -> Int -> Ptr c -> Int -> Ptr a -> Int -> Ptr b -> IO ())
-> RoundingMode -> Vector a -> Vector b -> Vector c
zipWith_Storable ((RoundingMode
 -> Int
 -> Int
 -> Ptr Double
 -> Int
 -> Ptr Double
 -> Int
 -> Ptr Double
 -> IO ())
-> RoundingMode
-> Int
-> Int
-> Ptr CDouble
-> Int
-> Ptr CDouble
-> Int
-> Ptr CDouble
-> IO ()
coerce RoundingMode
-> Int
-> Int
-> Ptr Double
-> Int
-> Ptr Double
-> Int
-> Ptr Double
-> IO ()
D.vectorMulPtr)
  zipWith3_roundedFusedMultiplyAdd :: RoundingMode
-> Vector CDouble
-> Vector CDouble
-> Vector CDouble
-> Vector CDouble
zipWith3_roundedFusedMultiplyAdd = (RoundingMode
 -> Int
 -> Int
 -> Ptr CDouble
 -> Int
 -> Ptr CDouble
 -> Int
 -> Ptr CDouble
 -> Int
 -> Ptr CDouble
 -> IO ())
-> RoundingMode
-> Vector CDouble
-> Vector CDouble
-> Vector CDouble
-> Vector CDouble
forall a b c d.
(Storable a, Storable b, Storable c, Storable d) =>
(RoundingMode
 -> Int
 -> Int
 -> Ptr d
 -> Int
 -> Ptr a
 -> Int
 -> Ptr b
 -> Int
 -> Ptr c
 -> IO ())
-> RoundingMode -> Vector a -> Vector b -> Vector c -> Vector d
zipWith3_Storable ((RoundingMode
 -> Int
 -> Int
 -> Ptr Double
 -> Int
 -> Ptr Double
 -> Int
 -> Ptr Double
 -> Int
 -> Ptr Double
 -> IO ())
-> RoundingMode
-> Int
-> Int
-> Ptr CDouble
-> Int
-> Ptr CDouble
-> Int
-> Ptr CDouble
-> Int
-> Ptr CDouble
-> IO ()
coerce RoundingMode
-> Int
-> Int
-> Ptr Double
-> Int
-> Ptr Double
-> Int
-> Ptr Double
-> Int
-> Ptr Double
-> IO ()
D.vectorFMAPtr)

instance RoundedFractional_Vector VS.Vector CDouble where
  zipWith_roundedDiv :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble
zipWith_roundedDiv = (RoundingMode
 -> Int
 -> Int
 -> Ptr CDouble
 -> Int
 -> Ptr CDouble
 -> Int
 -> Ptr CDouble
 -> IO ())
-> RoundingMode
-> Vector CDouble
-> Vector CDouble
-> Vector CDouble
forall a b c.
(Storable a, Storable b, Storable c) =>
(RoundingMode
 -> Int -> Int -> Ptr c -> Int -> Ptr a -> Int -> Ptr b -> IO ())
-> RoundingMode -> Vector a -> Vector b -> Vector c
zipWith_Storable ((RoundingMode
 -> Int
 -> Int
 -> Ptr Double
 -> Int
 -> Ptr Double
 -> Int
 -> Ptr Double
 -> IO ())
-> RoundingMode
-> Int
-> Int
-> Ptr CDouble
-> Int
-> Ptr CDouble
-> Int
-> Ptr CDouble
-> IO ()
coerce RoundingMode
-> Int
-> Int
-> Ptr Double
-> Int
-> Ptr Double
-> Int
-> Ptr Double
-> IO ()
D.vectorDivPtr)

instance RoundedSqrt_Vector VS.Vector CDouble where
  map_roundedSqrt :: RoundingMode -> Vector CDouble -> Vector CDouble
map_roundedSqrt = (RoundingMode
 -> Int -> Int -> Ptr CDouble -> Int -> Ptr CDouble -> IO ())
-> RoundingMode -> Vector CDouble -> Vector CDouble
forall a b.
(Storable a, Storable b) =>
(RoundingMode -> Int -> Int -> Ptr b -> Int -> Ptr a -> IO ())
-> RoundingMode -> Vector a -> Vector b
map_Storable ((RoundingMode
 -> Int -> Int -> Ptr Double -> Int -> Ptr Double -> IO ())
-> RoundingMode
-> Int
-> Int
-> Ptr CDouble
-> Int
-> Ptr CDouble
-> IO ()
coerce RoundingMode
-> Int -> Int -> Ptr Double -> Int -> Ptr Double -> IO ()
D.vectorSqrtPtr)

instance RoundedRing_Vector VU.Vector CDouble where
  roundedSum :: RoundingMode -> Vector CDouble -> CDouble
roundedSum RoundingMode
mode (V_CDouble (VU.V_Double (VP.Vector off len (ByteArray arr)))) =
    Double -> CDouble
CDouble (Double -> CDouble) -> Double -> CDouble
forall a b. (a -> b) -> a -> b
$ RoundingMode -> Int -> Int -> ByteArray# -> Double
D.vectorSumByteArray RoundingMode
mode Int
len Int
off ByteArray#
arr
  zipWith_roundedAdd :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble
zipWith_roundedAdd = (RoundingMode -> Vector Double -> Vector Double -> Vector Double)
-> RoundingMode
-> Vector CDouble
-> Vector CDouble
-> Vector CDouble
coerce ((RoundingMode
 -> Int
 -> Int
 -> MutableByteArray# RealWorld
 -> Int
 -> ByteArray#
 -> Int
 -> ByteArray#
 -> IO ())
-> RoundingMode -> Vector Double -> Vector Double -> Vector Double
forall a b c.
(Prim a, Prim b, Prim c) =>
(RoundingMode
 -> Int
 -> Int
 -> MutableByteArray# RealWorld
 -> Int
 -> ByteArray#
 -> Int
 -> ByteArray#
 -> IO ())
-> RoundingMode -> Vector a -> Vector b -> Vector c
zipWith_Primitive RoundingMode
-> Int
-> Int
-> MutableByteArray# RealWorld
-> Int
-> ByteArray#
-> Int
-> ByteArray#
-> IO ()
D.vectorAddByteArray :: RoundingMode -> VP.Vector Double -> VP.Vector Double -> VP.Vector Double)
  zipWith_roundedSub :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble
zipWith_roundedSub = (RoundingMode -> Vector Double -> Vector Double -> Vector Double)
-> RoundingMode
-> Vector CDouble
-> Vector CDouble
-> Vector CDouble
coerce ((RoundingMode
 -> Int
 -> Int
 -> MutableByteArray# RealWorld
 -> Int
 -> ByteArray#
 -> Int
 -> ByteArray#
 -> IO ())
-> RoundingMode -> Vector Double -> Vector Double -> Vector Double
forall a b c.
(Prim a, Prim b, Prim c) =>
(RoundingMode
 -> Int
 -> Int
 -> MutableByteArray# RealWorld
 -> Int
 -> ByteArray#
 -> Int
 -> ByteArray#
 -> IO ())
-> RoundingMode -> Vector a -> Vector b -> Vector c
zipWith_Primitive RoundingMode
-> Int
-> Int
-> MutableByteArray# RealWorld
-> Int
-> ByteArray#
-> Int
-> ByteArray#
-> IO ()
D.vectorSubByteArray :: RoundingMode -> VP.Vector Double -> VP.Vector Double -> VP.Vector Double)
  zipWith_roundedMul :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble
zipWith_roundedMul = (RoundingMode -> Vector Double -> Vector Double -> Vector Double)
-> RoundingMode
-> Vector CDouble
-> Vector CDouble
-> Vector CDouble
coerce ((RoundingMode
 -> Int
 -> Int
 -> MutableByteArray# RealWorld
 -> Int
 -> ByteArray#
 -> Int
 -> ByteArray#
 -> IO ())
-> RoundingMode -> Vector Double -> Vector Double -> Vector Double
forall a b c.
(Prim a, Prim b, Prim c) =>
(RoundingMode
 -> Int
 -> Int
 -> MutableByteArray# RealWorld
 -> Int
 -> ByteArray#
 -> Int
 -> ByteArray#
 -> IO ())
-> RoundingMode -> Vector a -> Vector b -> Vector c
zipWith_Primitive RoundingMode
-> Int
-> Int
-> MutableByteArray# RealWorld
-> Int
-> ByteArray#
-> Int
-> ByteArray#
-> IO ()
D.vectorMulByteArray :: RoundingMode -> VP.Vector Double -> VP.Vector Double -> VP.Vector Double)
  zipWith3_roundedFusedMultiplyAdd :: RoundingMode
-> Vector CDouble
-> Vector CDouble
-> Vector CDouble
-> Vector CDouble
zipWith3_roundedFusedMultiplyAdd = (RoundingMode
 -> Vector Double
 -> Vector Double
 -> Vector Double
 -> Vector Double)
-> RoundingMode
-> Vector CDouble
-> Vector CDouble
-> Vector CDouble
-> Vector CDouble
coerce ((RoundingMode
 -> Int
 -> Int
 -> MutableByteArray# RealWorld
 -> Int
 -> ByteArray#
 -> Int
 -> ByteArray#
 -> Int
 -> ByteArray#
 -> IO ())
-> RoundingMode
-> Vector Double
-> Vector Double
-> Vector Double
-> Vector Double
forall a b c d.
(Prim a, Prim b, Prim c, Prim d) =>
(RoundingMode
 -> Int
 -> Int
 -> MutableByteArray# RealWorld
 -> Int
 -> ByteArray#
 -> Int
 -> ByteArray#
 -> Int
 -> ByteArray#
 -> IO ())
-> RoundingMode -> Vector a -> Vector b -> Vector c -> Vector d
zipWith3_Primitive RoundingMode
-> Int
-> Int
-> MutableByteArray# RealWorld
-> Int
-> ByteArray#
-> Int
-> ByteArray#
-> Int
-> ByteArray#
-> IO ()
D.vectorFMAByteArray :: RoundingMode -> VP.Vector Double -> VP.Vector Double -> VP.Vector Double -> VP.Vector Double)

instance RoundedFractional_Vector VU.Vector CDouble where
  zipWith_roundedDiv :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble
zipWith_roundedDiv = (RoundingMode -> Vector Double -> Vector Double -> Vector Double)
-> RoundingMode
-> Vector CDouble
-> Vector CDouble
-> Vector CDouble
coerce ((RoundingMode
 -> Int
 -> Int
 -> MutableByteArray# RealWorld
 -> Int
 -> ByteArray#
 -> Int
 -> ByteArray#
 -> IO ())
-> RoundingMode -> Vector Double -> Vector Double -> Vector Double
forall a b c.
(Prim a, Prim b, Prim c) =>
(RoundingMode
 -> Int
 -> Int
 -> MutableByteArray# RealWorld
 -> Int
 -> ByteArray#
 -> Int
 -> ByteArray#
 -> IO ())
-> RoundingMode -> Vector a -> Vector b -> Vector c
zipWith_Primitive RoundingMode
-> Int
-> Int
-> MutableByteArray# RealWorld
-> Int
-> ByteArray#
-> Int
-> ByteArray#
-> IO ()
D.vectorDivByteArray :: RoundingMode -> VP.Vector Double -> VP.Vector Double -> VP.Vector Double)

instance RoundedSqrt_Vector VU.Vector CDouble where
  map_roundedSqrt :: RoundingMode -> Vector CDouble -> Vector CDouble
map_roundedSqrt = (RoundingMode -> Vector Double -> Vector Double)
-> RoundingMode -> Vector CDouble -> Vector CDouble
coerce ((RoundingMode
 -> Int
 -> Int
 -> MutableByteArray# RealWorld
 -> Int
 -> ByteArray#
 -> IO ())
-> RoundingMode -> Vector Double -> Vector Double
forall a b.
(Prim a, Prim b) =>
(RoundingMode
 -> Int
 -> Int
 -> MutableByteArray# RealWorld
 -> Int
 -> ByteArray#
 -> IO ())
-> RoundingMode -> Vector a -> Vector b
map_Primitive RoundingMode
-> Int
-> Int
-> MutableByteArray# RealWorld
-> Int
-> ByteArray#
-> IO ()
D.vectorSqrtByteArray :: RoundingMode -> VP.Vector Double -> VP.Vector Double)

--
-- Backend name
--

foreign import ccall unsafe "rounded_hw_backend_name"
  c_backend_name :: CString

cBackendName :: String
cBackendName :: String
cBackendName = IO String -> String
forall a. IO a -> a
unsafePerformIO (CString -> IO String
peekCString CString
c_backend_name)

--
-- Utility function for constant folding
--

staticIf :: Bool -> a -> a -> a
staticIf :: Bool -> a -> a -> a
staticIf Bool
_ a
_ a
x = a
x
{-# INLINE [0] staticIf #-}

{-# RULES
"staticIf/True" forall x y. staticIf True x y = x
"staticIf/False" forall x y. staticIf False x y = y
  #-}

--
-- Utility functions for vector operations
--

map_Storable :: (Storable a, Storable b) => (RoundingMode -> Int -> Int -> Ptr b -> Int -> Ptr a -> IO ()) -> RoundingMode -> VS.Vector a -> VS.Vector b
map_Storable :: (RoundingMode -> Int -> Int -> Ptr b -> Int -> Ptr a -> IO ())
-> RoundingMode -> Vector a -> Vector b
map_Storable RoundingMode -> Int -> Int -> Ptr b -> Int -> Ptr a -> IO ()
f RoundingMode
mode Vector a
vec = IO (Vector b) -> Vector b
forall a. IO a -> a
unsafePerformIO (IO (Vector b) -> Vector b) -> IO (Vector b) -> Vector b
forall a b. (a -> b) -> a -> b
$ do
  let !len :: Int
len = Vector a -> Int
forall a. Storable a => Vector a -> Int
VS.length Vector a
vec
  IOVector b
result <- Int -> IO (MVector (PrimState IO) b)
forall (m :: * -> *) a.
(PrimMonad m, Storable a) =>
Int -> m (MVector (PrimState m) a)
VSM.new Int
len
  Vector a -> (Ptr a -> IO ()) -> IO ()
forall a b. Storable a => Vector a -> (Ptr a -> IO b) -> IO b
VS.unsafeWith Vector a
vec ((Ptr a -> IO ()) -> IO ()) -> (Ptr a -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr a
ptr ->
    IOVector b -> (Ptr b -> IO ()) -> IO ()
forall a b. Storable a => IOVector a -> (Ptr a -> IO b) -> IO b
VSM.unsafeWith IOVector b
result ((Ptr b -> IO ()) -> IO ()) -> (Ptr b -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr b
resultPtr ->
      RoundingMode -> Int -> Int -> Ptr b -> Int -> Ptr a -> IO ()
f RoundingMode
mode Int
len Int
0 Ptr b
resultPtr Int
0 Ptr a
ptr
  MVector (PrimState IO) b -> IO (Vector b)
forall a (m :: * -> *).
(Storable a, PrimMonad m) =>
MVector (PrimState m) a -> m (Vector a)
VS.unsafeFreeze IOVector b
MVector (PrimState IO) b
result
{-# INLINE map_Storable #-}

zipWith_Storable :: (Storable a, Storable b, Storable c) => (RoundingMode -> Int -> Int -> Ptr c -> Int -> Ptr a -> Int -> Ptr b -> IO ()) -> RoundingMode -> VS.Vector a -> VS.Vector b -> VS.Vector c
zipWith_Storable :: (RoundingMode
 -> Int -> Int -> Ptr c -> Int -> Ptr a -> Int -> Ptr b -> IO ())
-> RoundingMode -> Vector a -> Vector b -> Vector c
zipWith_Storable RoundingMode
-> Int -> Int -> Ptr c -> Int -> Ptr a -> Int -> Ptr b -> IO ()
f RoundingMode
mode Vector a
vec Vector b
vec' = IO (Vector c) -> Vector c
forall a. IO a -> a
unsafePerformIO (IO (Vector c) -> Vector c) -> IO (Vector c) -> Vector c
forall a b. (a -> b) -> a -> b
$ do
  let !len :: Int
len = Int -> Int -> Int
forall a. Ord a => a -> a -> a
min (Vector a -> Int
forall a. Storable a => Vector a -> Int
VS.length Vector a
vec) (Vector b -> Int
forall a. Storable a => Vector a -> Int
VS.length Vector b
vec')
  IOVector c
result <- Int -> IO (MVector (PrimState IO) c)
forall (m :: * -> *) a.
(PrimMonad m, Storable a) =>
Int -> m (MVector (PrimState m) a)
VSM.new Int
len
  Vector a -> (Ptr a -> IO ()) -> IO ()
forall a b. Storable a => Vector a -> (Ptr a -> IO b) -> IO b
VS.unsafeWith Vector a
vec ((Ptr a -> IO ()) -> IO ()) -> (Ptr a -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr a
ptr ->
    Vector b -> (Ptr b -> IO ()) -> IO ()
forall a b. Storable a => Vector a -> (Ptr a -> IO b) -> IO b
VS.unsafeWith Vector b
vec' ((Ptr b -> IO ()) -> IO ()) -> (Ptr b -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr b
ptr' ->
      IOVector c -> (Ptr c -> IO ()) -> IO ()
forall a b. Storable a => IOVector a -> (Ptr a -> IO b) -> IO b
VSM.unsafeWith IOVector c
result ((Ptr c -> IO ()) -> IO ()) -> (Ptr c -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr c
resultPtr ->
        RoundingMode
-> Int -> Int -> Ptr c -> Int -> Ptr a -> Int -> Ptr b -> IO ()
f RoundingMode
mode Int
len Int
0 Ptr c
resultPtr Int
0 Ptr a
ptr Int
0 Ptr b
ptr'
  MVector (PrimState IO) c -> IO (Vector c)
forall a (m :: * -> *).
(Storable a, PrimMonad m) =>
MVector (PrimState m) a -> m (Vector a)
VS.unsafeFreeze IOVector c
MVector (PrimState IO) c
result
{-# INLINE zipWith_Storable #-}

zipWith3_Storable :: (Storable a, Storable b, Storable c, Storable d) => (RoundingMode -> Int -> Int -> Ptr d -> Int -> Ptr a -> Int -> Ptr b -> Int -> Ptr c -> IO ()) -> RoundingMode -> VS.Vector a -> VS.Vector b -> VS.Vector c -> VS.Vector d
zipWith3_Storable :: (RoundingMode
 -> Int
 -> Int
 -> Ptr d
 -> Int
 -> Ptr a
 -> Int
 -> Ptr b
 -> Int
 -> Ptr c
 -> IO ())
-> RoundingMode -> Vector a -> Vector b -> Vector c -> Vector d
zipWith3_Storable RoundingMode
-> Int
-> Int
-> Ptr d
-> Int
-> Ptr a
-> Int
-> Ptr b
-> Int
-> Ptr c
-> IO ()
f RoundingMode
mode Vector a
vec1 Vector b
vec2 Vector c
vec3 = IO (Vector d) -> Vector d
forall a. IO a -> a
unsafePerformIO (IO (Vector d) -> Vector d) -> IO (Vector d) -> Vector d
forall a b. (a -> b) -> a -> b
$ do
  let !len :: Int
len = Int -> Int -> Int
forall a. Ord a => a -> a -> a
min (Vector a -> Int
forall a. Storable a => Vector a -> Int
VS.length Vector a
vec1) (Int -> Int -> Int
forall a. Ord a => a -> a -> a
min (Vector b -> Int
forall a. Storable a => Vector a -> Int
VS.length Vector b
vec2) (Vector c -> Int
forall a. Storable a => Vector a -> Int
VS.length Vector c
vec3))
  IOVector d
result <- Int -> IO (MVector (PrimState IO) d)
forall (m :: * -> *) a.
(PrimMonad m, Storable a) =>
Int -> m (MVector (PrimState m) a)
VSM.new Int
len
  Vector a -> (Ptr a -> IO ()) -> IO ()
forall a b. Storable a => Vector a -> (Ptr a -> IO b) -> IO b
VS.unsafeWith Vector a
vec1 ((Ptr a -> IO ()) -> IO ()) -> (Ptr a -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr a
ptr1 ->
    Vector b -> (Ptr b -> IO ()) -> IO ()
forall a b. Storable a => Vector a -> (Ptr a -> IO b) -> IO b
VS.unsafeWith Vector b
vec2 ((Ptr b -> IO ()) -> IO ()) -> (Ptr b -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr b
ptr2 ->
      Vector c -> (Ptr c -> IO ()) -> IO ()
forall a b. Storable a => Vector a -> (Ptr a -> IO b) -> IO b
VS.unsafeWith Vector c
vec3 ((Ptr c -> IO ()) -> IO ()) -> (Ptr c -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr c
ptr3 ->
        IOVector d -> (Ptr d -> IO ()) -> IO ()
forall a b. Storable a => IOVector a -> (Ptr a -> IO b) -> IO b
VSM.unsafeWith IOVector d
result ((Ptr d -> IO ()) -> IO ()) -> (Ptr d -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr d
resultPtr ->
          RoundingMode
-> Int
-> Int
-> Ptr d
-> Int
-> Ptr a
-> Int
-> Ptr b
-> Int
-> Ptr c
-> IO ()
f RoundingMode
mode Int
len Int
0 Ptr d
resultPtr Int
0 Ptr a
ptr1 Int
0 Ptr b
ptr2 Int
0 Ptr c
ptr3
  MVector (PrimState IO) d -> IO (Vector d)
forall a (m :: * -> *).
(Storable a, PrimMonad m) =>
MVector (PrimState m) a -> m (Vector a)
VS.unsafeFreeze IOVector d
MVector (PrimState IO) d
result
{-# INLINE zipWith3_Storable #-}

map_Primitive :: (Prim a, Prim b) => (RoundingMode -> Int -> Int -> MutableByteArray# RealWorld -> Int -> ByteArray# -> IO ()) -> RoundingMode -> VP.Vector a -> VP.Vector b
map_Primitive :: (RoundingMode
 -> Int
 -> Int
 -> MutableByteArray# RealWorld
 -> Int
 -> ByteArray#
 -> IO ())
-> RoundingMode -> Vector a -> Vector b
map_Primitive RoundingMode
-> Int
-> Int
-> MutableByteArray# RealWorld
-> Int
-> ByteArray#
-> IO ()
f RoundingMode
mode (VP.Vector Int
offA Int
lenA (ByteArray ByteArray#
arrA)) = IO (Vector b) -> Vector b
forall a. IO a -> a
unsafePerformIO (IO (Vector b) -> Vector b) -> IO (Vector b) -> Vector b
forall a b. (a -> b) -> a -> b
$ do
  result :: MVector RealWorld b
result@(VPM.MVector Int
offR Int
lenR (MutableByteArray MutableByteArray# RealWorld
arrR)) <- Int -> IO (MVector (PrimState IO) b)
forall (m :: * -> *) a.
(PrimMonad m, Prim a) =>
Int -> m (MVector (PrimState m) a)
VPM.unsafeNew Int
lenA
  RoundingMode
-> Int
-> Int
-> MutableByteArray# RealWorld
-> Int
-> ByteArray#
-> IO ()
f RoundingMode
mode Int
lenR Int
offR MutableByteArray# RealWorld
arrR Int
offA ByteArray#
arrA
  MVector (PrimState IO) b -> IO (Vector b)
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MVector (PrimState m) a -> m (Vector a)
VP.unsafeFreeze MVector RealWorld b
MVector (PrimState IO) b
result
{-# INLINE map_Primitive #-}

zipWith_Primitive :: (Prim a, Prim b, Prim c) => (RoundingMode -> Int -> Int -> MutableByteArray# RealWorld -> Int -> ByteArray# -> Int -> ByteArray# -> IO ()) -> RoundingMode -> VP.Vector a -> VP.Vector b -> VP.Vector c
zipWith_Primitive :: (RoundingMode
 -> Int
 -> Int
 -> MutableByteArray# RealWorld
 -> Int
 -> ByteArray#
 -> Int
 -> ByteArray#
 -> IO ())
-> RoundingMode -> Vector a -> Vector b -> Vector c
zipWith_Primitive RoundingMode
-> Int
-> Int
-> MutableByteArray# RealWorld
-> Int
-> ByteArray#
-> Int
-> ByteArray#
-> IO ()
f RoundingMode
mode (VP.Vector Int
offA Int
lenA (ByteArray ByteArray#
arrA)) (VP.Vector Int
offB Int
lenB (ByteArray ByteArray#
arrB)) = IO (Vector c) -> Vector c
forall a. IO a -> a
unsafePerformIO (IO (Vector c) -> Vector c) -> IO (Vector c) -> Vector c
forall a b. (a -> b) -> a -> b
$ do
  result :: MVector RealWorld c
result@(VPM.MVector Int
offR Int
lenR (MutableByteArray MutableByteArray# RealWorld
arrR)) <- Int -> IO (MVector (PrimState IO) c)
forall (m :: * -> *) a.
(PrimMonad m, Prim a) =>
Int -> m (MVector (PrimState m) a)
VPM.unsafeNew (Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
lenA Int
lenB)
  RoundingMode
-> Int
-> Int
-> MutableByteArray# RealWorld
-> Int
-> ByteArray#
-> Int
-> ByteArray#
-> IO ()
f RoundingMode
mode Int
lenR Int
offR MutableByteArray# RealWorld
arrR Int
offA ByteArray#
arrA Int
offB ByteArray#
arrB
  MVector (PrimState IO) c -> IO (Vector c)
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MVector (PrimState m) a -> m (Vector a)
VP.unsafeFreeze MVector RealWorld c
MVector (PrimState IO) c
result
{-# INLINE zipWith_Primitive #-}

zipWith3_Primitive :: (Prim a, Prim b, Prim c, Prim d) => (RoundingMode -> Int -> Int -> MutableByteArray# RealWorld -> Int -> ByteArray# -> Int -> ByteArray# -> Int -> ByteArray# -> IO ()) -> RoundingMode -> VP.Vector a -> VP.Vector b -> VP.Vector c -> VP.Vector d
zipWith3_Primitive :: (RoundingMode
 -> Int
 -> Int
 -> MutableByteArray# RealWorld
 -> Int
 -> ByteArray#
 -> Int
 -> ByteArray#
 -> Int
 -> ByteArray#
 -> IO ())
-> RoundingMode -> Vector a -> Vector b -> Vector c -> Vector d
zipWith3_Primitive RoundingMode
-> Int
-> Int
-> MutableByteArray# RealWorld
-> Int
-> ByteArray#
-> Int
-> ByteArray#
-> Int
-> ByteArray#
-> IO ()
f RoundingMode
mode (VP.Vector Int
offA Int
lenA (ByteArray ByteArray#
arrA)) (VP.Vector Int
offB Int
lenB (ByteArray ByteArray#
arrB)) (VP.Vector Int
offC Int
lenC (ByteArray ByteArray#
arrC))= IO (Vector d) -> Vector d
forall a. IO a -> a
unsafePerformIO (IO (Vector d) -> Vector d) -> IO (Vector d) -> Vector d
forall a b. (a -> b) -> a -> b
$ do
  result :: MVector RealWorld d
result@(VPM.MVector Int
offR Int
lenR (MutableByteArray MutableByteArray# RealWorld
arrR)) <- Int -> IO (MVector (PrimState IO) d)
forall (m :: * -> *) a.
(PrimMonad m, Prim a) =>
Int -> m (MVector (PrimState m) a)
VPM.unsafeNew (Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
lenA (Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
lenB Int
lenC))
  RoundingMode
-> Int
-> Int
-> MutableByteArray# RealWorld
-> Int
-> ByteArray#
-> Int
-> ByteArray#
-> Int
-> ByteArray#
-> IO ()
f RoundingMode
mode Int
lenR Int
offR MutableByteArray# RealWorld
arrR Int
offA ByteArray#
arrA Int
offB ByteArray#
arrB Int
offC ByteArray#
arrC
  MVector (PrimState IO) d -> IO (Vector d)
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MVector (PrimState m) a -> m (Vector a)
VP.unsafeFreeze MVector RealWorld d
MVector (PrimState IO) d
result
{-# INLINE zipWith3_Primitive #-}

--
-- instance for Data.Vector.Unboxed.Unbox
--

newtype instance VUM.MVector s CFloat = MV_CFloat (VUM.MVector s Float)
newtype instance VU.Vector CFloat = V_CFloat (VU.Vector Float)

instance VGM.MVector VUM.MVector CFloat where
  basicLength :: MVector s CFloat -> Int
basicLength (MV_CFloat mv) = MVector s Float -> Int
forall (v :: * -> * -> *) a s. MVector v a => v s a -> Int
VGM.basicLength MVector s Float
mv
  basicUnsafeSlice :: Int -> Int -> MVector s CFloat -> MVector s CFloat
basicUnsafeSlice Int
i Int
l (MV_CFloat mv) = MVector s Float -> MVector s CFloat
forall s. MVector s Float -> MVector s CFloat
MV_CFloat (Int -> Int -> MVector s Float -> MVector s Float
forall (v :: * -> * -> *) a s.
MVector v a =>
Int -> Int -> v s a -> v s a
VGM.basicUnsafeSlice Int
i Int
l MVector s Float
mv)
  basicOverlaps :: MVector s CFloat -> MVector s CFloat -> Bool
basicOverlaps (MV_CFloat mv) (MV_CFloat mv') = MVector s Float -> MVector s Float -> Bool
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> Bool
VGM.basicOverlaps MVector s Float
mv MVector s Float
mv'
  basicUnsafeNew :: Int -> m (MVector (PrimState m) CFloat)
basicUnsafeNew Int
l = MVector (PrimState m) Float -> MVector (PrimState m) CFloat
forall s. MVector s Float -> MVector s CFloat
MV_CFloat (MVector (PrimState m) Float -> MVector (PrimState m) CFloat)
-> m (MVector (PrimState m) Float)
-> m (MVector (PrimState m) CFloat)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> m (MVector (PrimState m) Float)
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
Int -> m (v (PrimState m) a)
VGM.basicUnsafeNew Int
l
  basicInitialize :: MVector (PrimState m) CFloat -> m ()
basicInitialize (MV_CFloat mv) = MVector (PrimState m) Float -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> m ()
VGM.basicInitialize MVector (PrimState m) Float
mv
  basicUnsafeReplicate :: Int -> CFloat -> m (MVector (PrimState m) CFloat)
basicUnsafeReplicate Int
i CFloat
x = MVector (PrimState m) Float -> MVector (PrimState m) CFloat
forall s. MVector s Float -> MVector s CFloat
MV_CFloat (MVector (PrimState m) Float -> MVector (PrimState m) CFloat)
-> m (MVector (PrimState m) Float)
-> m (MVector (PrimState m) CFloat)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Float -> m (MVector (PrimState m) Float)
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
Int -> a -> m (v (PrimState m) a)
VGM.basicUnsafeReplicate Int
i (CFloat -> Float
coerce CFloat
x)
  basicUnsafeRead :: MVector (PrimState m) CFloat -> Int -> m CFloat
basicUnsafeRead (MV_CFloat mv) Int
i = Float -> CFloat
coerce (Float -> CFloat) -> m Float -> m CFloat
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MVector (PrimState m) Float -> Int -> m Float
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m a
VGM.basicUnsafeRead MVector (PrimState m) Float
mv Int
i
  basicUnsafeWrite :: MVector (PrimState m) CFloat -> Int -> CFloat -> m ()
basicUnsafeWrite (MV_CFloat mv) Int
i CFloat
x = MVector (PrimState m) Float -> Int -> Float -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> a -> m ()
VGM.basicUnsafeWrite MVector (PrimState m) Float
mv Int
i (CFloat -> Float
coerce CFloat
x)
  basicClear :: MVector (PrimState m) CFloat -> m ()
basicClear (MV_CFloat mv) = MVector (PrimState m) Float -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> m ()
VGM.basicClear MVector (PrimState m) Float
mv
  basicSet :: MVector (PrimState m) CFloat -> CFloat -> m ()
basicSet (MV_CFloat mv) CFloat
x = MVector (PrimState m) Float -> Float -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> a -> m ()
VGM.basicSet MVector (PrimState m) Float
mv (CFloat -> Float
coerce CFloat
x)
  basicUnsafeCopy :: MVector (PrimState m) CFloat
-> MVector (PrimState m) CFloat -> m ()
basicUnsafeCopy (MV_CFloat mv) (MV_CFloat mv') = MVector (PrimState m) Float -> MVector (PrimState m) Float -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> v (PrimState m) a -> m ()
VGM.basicUnsafeCopy MVector (PrimState m) Float
mv MVector (PrimState m) Float
mv'
  basicUnsafeMove :: MVector (PrimState m) CFloat
-> MVector (PrimState m) CFloat -> m ()
basicUnsafeMove (MV_CFloat mv) (MV_CFloat mv') = MVector (PrimState m) Float -> MVector (PrimState m) Float -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> v (PrimState m) a -> m ()
VGM.basicUnsafeMove MVector (PrimState m) Float
mv MVector (PrimState m) Float
mv'
  basicUnsafeGrow :: MVector (PrimState m) CFloat
-> Int -> m (MVector (PrimState m) CFloat)
basicUnsafeGrow (MV_CFloat mv) Int
n = MVector (PrimState m) Float -> MVector (PrimState m) CFloat
forall s. MVector s Float -> MVector s CFloat
MV_CFloat (MVector (PrimState m) Float -> MVector (PrimState m) CFloat)
-> m (MVector (PrimState m) Float)
-> m (MVector (PrimState m) CFloat)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MVector (PrimState m) Float
-> Int -> m (MVector (PrimState m) Float)
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m (v (PrimState m) a)
VGM.basicUnsafeGrow MVector (PrimState m) Float
mv Int
n

instance VG.Vector VU.Vector CFloat where
  basicUnsafeFreeze :: Mutable Vector (PrimState m) CFloat -> m (Vector CFloat)
basicUnsafeFreeze (MV_CFloat mv) = Vector Float -> Vector CFloat
V_CFloat (Vector Float -> Vector CFloat)
-> m (Vector Float) -> m (Vector CFloat)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Mutable Vector (PrimState m) Float -> m (Vector Float)
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
Mutable v (PrimState m) a -> m (v a)
VG.basicUnsafeFreeze MVector (PrimState m) Float
Mutable Vector (PrimState m) Float
mv
  basicUnsafeThaw :: Vector CFloat -> m (Mutable Vector (PrimState m) CFloat)
basicUnsafeThaw (V_CFloat v) = MVector (PrimState m) Float -> MVector (PrimState m) CFloat
forall s. MVector s Float -> MVector s CFloat
MV_CFloat (MVector (PrimState m) Float -> MVector (PrimState m) CFloat)
-> m (MVector (PrimState m) Float)
-> m (MVector (PrimState m) CFloat)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Vector Float -> m (Mutable Vector (PrimState m) Float)
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
v a -> m (Mutable v (PrimState m) a)
VG.basicUnsafeThaw Vector Float
v
  basicLength :: Vector CFloat -> Int
basicLength (V_CFloat v) = Vector Float -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
VG.basicLength Vector Float
v
  basicUnsafeSlice :: Int -> Int -> Vector CFloat -> Vector CFloat
basicUnsafeSlice Int
i Int
l (V_CFloat v) = Vector Float -> Vector CFloat
V_CFloat (Int -> Int -> Vector Float -> Vector Float
forall (v :: * -> *) a. Vector v a => Int -> Int -> v a -> v a
VG.basicUnsafeSlice Int
i Int
l Vector Float
v)
  basicUnsafeIndexM :: Vector CFloat -> Int -> m CFloat
basicUnsafeIndexM (V_CFloat v) Int
i = Float -> CFloat
coerce (Float -> CFloat) -> m Float -> m CFloat
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Vector Float -> Int -> m Float
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, Monad m) =>
v a -> Int -> m a
VG.basicUnsafeIndexM Vector Float
v Int
i
  basicUnsafeCopy :: Mutable Vector (PrimState m) CFloat -> Vector CFloat -> m ()
basicUnsafeCopy (MV_CFloat mv) (V_CFloat v) = Mutable Vector (PrimState m) Float -> Vector Float -> m ()
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
Mutable v (PrimState m) a -> v a -> m ()
VG.basicUnsafeCopy MVector (PrimState m) Float
Mutable Vector (PrimState m) Float
mv Vector Float
v
  elemseq :: Vector CFloat -> CFloat -> b -> b
elemseq (V_CFloat v) CFloat
x b
y = Vector Float -> Float -> b -> b
forall (v :: * -> *) a b. Vector v a => v a -> a -> b -> b
VG.elemseq Vector Float
v (CFloat -> Float
coerce CFloat
x) b
y

instance VU.Unbox CFloat

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 :: MVector s CDouble -> Int
basicLength (MV_CDouble mv) = MVector s Double -> Int
forall (v :: * -> * -> *) a s. MVector v a => v s a -> Int
VGM.basicLength MVector s Double
mv
  basicUnsafeSlice :: Int -> Int -> MVector s CDouble -> MVector s CDouble
basicUnsafeSlice Int
i Int
l (MV_CDouble mv) = MVector s Double -> MVector s CDouble
forall s. MVector s Double -> MVector s CDouble
MV_CDouble (Int -> Int -> MVector s Double -> MVector s Double
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 :: MVector s CDouble -> MVector s CDouble -> Bool
basicOverlaps (MV_CDouble mv) (MV_CDouble mv') = MVector s Double -> MVector s Double -> Bool
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 :: Int -> m (MVector (PrimState m) CDouble)
basicUnsafeNew Int
l = MVector (PrimState m) Double -> MVector (PrimState m) CDouble
forall s. MVector s Double -> MVector s CDouble
MV_CDouble (MVector (PrimState m) Double -> MVector (PrimState m) CDouble)
-> m (MVector (PrimState m) Double)
-> m (MVector (PrimState m) CDouble)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> m (MVector (PrimState m) Double)
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
Int -> m (v (PrimState m) a)
VGM.basicUnsafeNew Int
l
  basicInitialize :: MVector (PrimState m) CDouble -> m ()
basicInitialize (MV_CDouble mv) = MVector (PrimState m) Double -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> m ()
VGM.basicInitialize MVector (PrimState m) Double
mv
  basicUnsafeReplicate :: Int -> CDouble -> m (MVector (PrimState m) CDouble)
basicUnsafeReplicate Int
i CDouble
x = MVector (PrimState m) Double -> MVector (PrimState m) CDouble
forall s. MVector s Double -> MVector s CDouble
MV_CDouble (MVector (PrimState m) Double -> MVector (PrimState m) CDouble)
-> m (MVector (PrimState m) Double)
-> m (MVector (PrimState m) CDouble)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Double -> m (MVector (PrimState m) Double)
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
Int -> a -> m (v (PrimState m) a)
VGM.basicUnsafeReplicate Int
i (CDouble -> Double
coerce CDouble
x)
  basicUnsafeRead :: MVector (PrimState m) CDouble -> Int -> m CDouble
basicUnsafeRead (MV_CDouble mv) Int
i = Double -> CDouble
coerce (Double -> CDouble) -> m Double -> m CDouble
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MVector (PrimState m) Double -> Int -> m Double
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m a
VGM.basicUnsafeRead MVector (PrimState m) Double
mv Int
i
  basicUnsafeWrite :: MVector (PrimState m) CDouble -> Int -> CDouble -> m ()
basicUnsafeWrite (MV_CDouble mv) Int
i CDouble
x = MVector (PrimState m) Double -> Int -> Double -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> a -> m ()
VGM.basicUnsafeWrite MVector (PrimState m) Double
mv Int
i (CDouble -> Double
coerce CDouble
x)
  basicClear :: MVector (PrimState m) CDouble -> m ()
basicClear (MV_CDouble mv) = MVector (PrimState m) Double -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> m ()
VGM.basicClear MVector (PrimState m) Double
mv
  basicSet :: MVector (PrimState m) CDouble -> CDouble -> m ()
basicSet (MV_CDouble mv) CDouble
x = MVector (PrimState m) Double -> Double -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> a -> m ()
VGM.basicSet MVector (PrimState m) Double
mv (CDouble -> Double
coerce CDouble
x)
  basicUnsafeCopy :: MVector (PrimState m) CDouble
-> MVector (PrimState m) CDouble -> m ()
basicUnsafeCopy (MV_CDouble mv) (MV_CDouble mv') = MVector (PrimState m) Double
-> MVector (PrimState m) Double -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> v (PrimState m) a -> m ()
VGM.basicUnsafeCopy MVector (PrimState m) Double
mv MVector (PrimState m) Double
mv'
  basicUnsafeMove :: MVector (PrimState m) CDouble
-> MVector (PrimState m) CDouble -> m ()
basicUnsafeMove (MV_CDouble mv) (MV_CDouble mv') = MVector (PrimState m) Double
-> MVector (PrimState m) Double -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> v (PrimState m) a -> m ()
VGM.basicUnsafeMove MVector (PrimState m) Double
mv MVector (PrimState m) Double
mv'
  basicUnsafeGrow :: MVector (PrimState m) CDouble
-> Int -> m (MVector (PrimState m) CDouble)
basicUnsafeGrow (MV_CDouble mv) Int
n = MVector (PrimState m) Double -> MVector (PrimState m) CDouble
forall s. MVector s Double -> MVector s CDouble
MV_CDouble (MVector (PrimState m) Double -> MVector (PrimState m) CDouble)
-> m (MVector (PrimState m) Double)
-> m (MVector (PrimState m) CDouble)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MVector (PrimState m) Double
-> Int -> m (MVector (PrimState m) Double)
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m (v (PrimState m) a)
VGM.basicUnsafeGrow MVector (PrimState m) Double
mv Int
n

instance VG.Vector VU.Vector CDouble where
  basicUnsafeFreeze :: Mutable Vector (PrimState m) CDouble -> m (Vector CDouble)
basicUnsafeFreeze (MV_CDouble mv) = Vector Double -> Vector CDouble
V_CDouble (Vector Double -> Vector CDouble)
-> m (Vector Double) -> m (Vector CDouble)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Mutable Vector (PrimState m) Double -> m (Vector Double)
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
Mutable v (PrimState m) a -> m (v a)
VG.basicUnsafeFreeze MVector (PrimState m) Double
Mutable Vector (PrimState m) Double
mv
  basicUnsafeThaw :: Vector CDouble -> m (Mutable Vector (PrimState m) CDouble)
basicUnsafeThaw (V_CDouble v) = MVector (PrimState m) Double -> MVector (PrimState m) CDouble
forall s. MVector s Double -> MVector s CDouble
MV_CDouble (MVector (PrimState m) Double -> MVector (PrimState m) CDouble)
-> m (MVector (PrimState m) Double)
-> m (MVector (PrimState m) CDouble)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Vector Double -> m (Mutable Vector (PrimState m) Double)
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
v a -> m (Mutable v (PrimState m) a)
VG.basicUnsafeThaw Vector Double
v
  basicLength :: Vector CDouble -> Int
basicLength (V_CDouble v) = Vector Double -> Int
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 v) = Vector Double -> Vector CDouble
V_CDouble (Int -> Int -> Vector Double -> Vector Double
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 -> m CDouble
basicUnsafeIndexM (V_CDouble v) Int
i = Double -> CDouble
coerce (Double -> CDouble) -> m Double -> m CDouble
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Vector Double -> Int -> m Double
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, Monad m) =>
v a -> Int -> m a
VG.basicUnsafeIndexM Vector Double
v Int
i
  basicUnsafeCopy :: Mutable Vector (PrimState m) CDouble -> Vector CDouble -> m ()
basicUnsafeCopy (MV_CDouble mv) (V_CDouble v) = Mutable Vector (PrimState m) Double -> Vector Double -> m ()
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
Mutable v (PrimState m) a -> v a -> m ()
VG.basicUnsafeCopy MVector (PrimState m) Double
Mutable Vector (PrimState m) Double
mv Vector Double
v
  elemseq :: Vector CDouble -> CDouble -> b -> b
elemseq (V_CDouble v) CDouble
x b
y = Vector Double -> Double -> b -> b
forall (v :: * -> *) a b. Vector v a => v a -> a -> b -> b
VG.elemseq Vector Double
v (CDouble -> Double
coerce CDouble
x) b
y

instance VU.Unbox CDouble