{-# LANGUAGE CPP                   #-}
{-# LANGUAGE FlexibleContexts      #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MagicHash             #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeApplications      #-}
{-# LANGUAGE UnboxedTuples         #-}
{-# LANGUAGE UndecidableInstances  #-}
module Numeric.DataFrame.Internal.Backend.Family.DoubleX3 (DoubleX3 (..)) where


import           GHC.Base
import           Numeric.DataFrame.Internal.PrimArray
import           Numeric.PrimBytes
import           Numeric.ProductOrd
import qualified Numeric.ProductOrd.NonTransitive     as NonTransitive
import qualified Numeric.ProductOrd.Partial           as Partial


data DoubleX3 = DoubleX3# Double# Double# Double#

-- | Since @Bounded@ is not implemented for floating point types, this instance
--   has an unresolvable constraint.
--   Nevetheless, it is good to have it here for nicer error messages.
instance Bounded Double => Bounded DoubleX3 where
    maxBound :: DoubleX3
maxBound = case Double
forall a. Bounded a => a
maxBound of D# Double#
x -> Double# -> Double# -> Double# -> DoubleX3
DoubleX3# Double#
x Double#
x Double#
x
    minBound :: DoubleX3
minBound = case Double
forall a. Bounded a => a
minBound of D# Double#
x -> Double# -> Double# -> Double# -> DoubleX3
DoubleX3# Double#
x Double#
x Double#
x


instance Eq DoubleX3 where

    DoubleX3# Double#
a1 Double#
a2 Double#
a3 == :: DoubleX3 -> DoubleX3 -> Bool
== DoubleX3# Double#
b1 Double#
b2 Double#
b3 =
      Int# -> Bool
isTrue#
      (       (Double#
a1 Double# -> Double# -> Int#
==## Double#
b1)
      Int# -> Int# -> Int#
`andI#` (Double#
a2 Double# -> Double# -> Int#
==## Double#
b2)
      Int# -> Int# -> Int#
`andI#` (Double#
a3 Double# -> Double# -> Int#
==## Double#
b3)
      )
    {-# INLINE (==) #-}

    DoubleX3# Double#
a1 Double#
a2 Double#
a3 /= :: DoubleX3 -> DoubleX3 -> Bool
/= DoubleX3# Double#
b1 Double#
b2 Double#
b3 =
      Int# -> Bool
isTrue#
      (      (Double#
a1 Double# -> Double# -> Int#
/=## Double#
b1)
      Int# -> Int# -> Int#
`orI#` (Double#
a2 Double# -> Double# -> Int#
/=## Double#
b2)
      Int# -> Int# -> Int#
`orI#` (Double#
a3 Double# -> Double# -> Int#
/=## Double#
b3)
      )
    {-# INLINE (/=) #-}



cmp' :: Double# -> Double# -> PartialOrdering
cmp' :: Double# -> Double# -> PartialOrdering
cmp' Double#
a Double#
b
  | Int# -> Bool
isTrue# (Double#
a Double# -> Double# -> Int#
>## Double#
b) = PartialOrdering
PGT
  | Int# -> Bool
isTrue# (Double#
a Double# -> Double# -> Int#
<## Double#
b) = PartialOrdering
PLT
  | Bool
otherwise  = PartialOrdering
PEQ

instance ProductOrder DoubleX3 where
    cmp :: DoubleX3 -> DoubleX3 -> PartialOrdering
cmp (DoubleX3# Double#
a1 Double#
a2 Double#
a3) (DoubleX3# Double#
b1 Double#
b2 Double#
b3)
      = Double# -> Double# -> PartialOrdering
cmp' Double#
a1 Double#
b1 PartialOrdering -> PartialOrdering -> PartialOrdering
forall a. Semigroup a => a -> a -> a
<> Double# -> Double# -> PartialOrdering
cmp' Double#
a2 Double#
b2 PartialOrdering -> PartialOrdering -> PartialOrdering
forall a. Semigroup a => a -> a -> a
<> Double# -> Double# -> PartialOrdering
cmp' Double#
a3 Double#
b3
    {-# INLINE cmp #-}

instance Ord (NonTransitive.ProductOrd DoubleX3) where
    NonTransitive.ProductOrd DoubleX3
x > :: ProductOrd DoubleX3 -> ProductOrd DoubleX3 -> Bool
> NonTransitive.ProductOrd DoubleX3
y = DoubleX3 -> DoubleX3 -> PartialOrdering
forall a. ProductOrder a => a -> a -> PartialOrdering
cmp DoubleX3
x DoubleX3
y PartialOrdering -> PartialOrdering -> Bool
forall a. Eq a => a -> a -> Bool
== PartialOrdering
PGT
    {-# INLINE (>) #-}
    NonTransitive.ProductOrd DoubleX3
x < :: ProductOrd DoubleX3 -> ProductOrd DoubleX3 -> Bool
< NonTransitive.ProductOrd DoubleX3
y = DoubleX3 -> DoubleX3 -> PartialOrdering
forall a. ProductOrder a => a -> a -> PartialOrdering
cmp DoubleX3
x DoubleX3
y PartialOrdering -> PartialOrdering -> Bool
forall a. Eq a => a -> a -> Bool
== PartialOrdering
PLT
    {-# INLINE (<) #-}
    >= :: ProductOrd DoubleX3 -> ProductOrd DoubleX3 -> Bool
(>=) (NonTransitive.ProductOrd (DoubleX3# Double#
a1 Double#
a2 Double#
a3))
         (NonTransitive.ProductOrd (DoubleX3# Double#
b1 Double#
b2 Double#
b3)) = Int# -> Bool
isTrue#
      ((Double#
a1 Double# -> Double# -> Int#
>=## Double#
b1) Int# -> Int# -> Int#
`andI#` (Double#
a2 Double# -> Double# -> Int#
>=## Double#
b2) Int# -> Int# -> Int#
`andI#` (Double#
a3 Double# -> Double# -> Int#
>=## Double#
b3))
    {-# INLINE (>=) #-}
    <= :: ProductOrd DoubleX3 -> ProductOrd DoubleX3 -> Bool
(<=) (NonTransitive.ProductOrd (DoubleX3# Double#
a1 Double#
a2 Double#
a3))
         (NonTransitive.ProductOrd (DoubleX3# Double#
b1 Double#
b2 Double#
b3)) = Int# -> Bool
isTrue#
      ((Double#
a1 Double# -> Double# -> Int#
<=## Double#
b1) Int# -> Int# -> Int#
`andI#` (Double#
a2 Double# -> Double# -> Int#
<=## Double#
b2) Int# -> Int# -> Int#
`andI#` (Double#
a3 Double# -> Double# -> Int#
<=## Double#
b3))
    {-# INLINE (<=) #-}
    compare :: ProductOrd DoubleX3 -> ProductOrd DoubleX3 -> Ordering
compare (NonTransitive.ProductOrd DoubleX3
a) (NonTransitive.ProductOrd DoubleX3
b)
      = PartialOrdering -> Ordering
NonTransitive.toOrdering (PartialOrdering -> Ordering) -> PartialOrdering -> Ordering
forall a b. (a -> b) -> a -> b
$ DoubleX3 -> DoubleX3 -> PartialOrdering
forall a. ProductOrder a => a -> a -> PartialOrdering
cmp DoubleX3
a DoubleX3
b
    {-# INLINE compare #-}
    min :: ProductOrd DoubleX3 -> ProductOrd DoubleX3 -> ProductOrd DoubleX3
min (NonTransitive.ProductOrd (DoubleX3# Double#
a1 Double#
a2 Double#
a3))
        (NonTransitive.ProductOrd (DoubleX3# Double#
b1 Double#
b2 Double#
b3))
      = DoubleX3 -> ProductOrd DoubleX3
forall a. a -> ProductOrd a
NonTransitive.ProductOrd
        ( Double# -> Double# -> Double# -> DoubleX3
DoubleX3#
          (if Int# -> Bool
isTrue# (Double#
a1 Double# -> Double# -> Int#
>## Double#
b1) then Double#
b1 else Double#
a1)
          (if Int# -> Bool
isTrue# (Double#
a2 Double# -> Double# -> Int#
>## Double#
b2) then Double#
b2 else Double#
a2)
          (if Int# -> Bool
isTrue# (Double#
a3 Double# -> Double# -> Int#
>## Double#
b3) then Double#
b3 else Double#
a3)
        )
    {-# INLINE min #-}
    max :: ProductOrd DoubleX3 -> ProductOrd DoubleX3 -> ProductOrd DoubleX3
max (NonTransitive.ProductOrd (DoubleX3# Double#
a1 Double#
a2 Double#
a3))
        (NonTransitive.ProductOrd (DoubleX3# Double#
b1 Double#
b2 Double#
b3))
      = DoubleX3 -> ProductOrd DoubleX3
forall a. a -> ProductOrd a
NonTransitive.ProductOrd
        ( Double# -> Double# -> Double# -> DoubleX3
DoubleX3#
          (if Int# -> Bool
isTrue# (Double#
a1 Double# -> Double# -> Int#
<## Double#
b1) then Double#
b1 else Double#
a1)
          (if Int# -> Bool
isTrue# (Double#
a2 Double# -> Double# -> Int#
<## Double#
b2) then Double#
b2 else Double#
a2)
          (if Int# -> Bool
isTrue# (Double#
a3 Double# -> Double# -> Int#
<## Double#
b3) then Double#
b3 else Double#
a3)
        )
    {-# INLINE max #-}

instance Ord (Partial.ProductOrd DoubleX3) where
    Partial.ProductOrd DoubleX3
x > :: ProductOrd DoubleX3 -> ProductOrd DoubleX3 -> Bool
> Partial.ProductOrd DoubleX3
y = DoubleX3 -> DoubleX3 -> PartialOrdering
forall a. ProductOrder a => a -> a -> PartialOrdering
cmp DoubleX3
x DoubleX3
y PartialOrdering -> PartialOrdering -> Bool
forall a. Eq a => a -> a -> Bool
== PartialOrdering
PGT
    {-# INLINE (>) #-}
    Partial.ProductOrd DoubleX3
x < :: ProductOrd DoubleX3 -> ProductOrd DoubleX3 -> Bool
< Partial.ProductOrd DoubleX3
y = DoubleX3 -> DoubleX3 -> PartialOrdering
forall a. ProductOrder a => a -> a -> PartialOrdering
cmp DoubleX3
x DoubleX3
y PartialOrdering -> PartialOrdering -> Bool
forall a. Eq a => a -> a -> Bool
== PartialOrdering
PLT
    {-# INLINE (<) #-}
    >= :: ProductOrd DoubleX3 -> ProductOrd DoubleX3 -> Bool
(>=) (Partial.ProductOrd (DoubleX3# Double#
a1 Double#
a2 Double#
a3))
         (Partial.ProductOrd (DoubleX3# Double#
b1 Double#
b2 Double#
b3)) = Int# -> Bool
isTrue#
      ((Double#
a1 Double# -> Double# -> Int#
>=## Double#
b1) Int# -> Int# -> Int#
`andI#` (Double#
a2 Double# -> Double# -> Int#
>=## Double#
b2) Int# -> Int# -> Int#
`andI#` (Double#
a3 Double# -> Double# -> Int#
>=## Double#
b3))
    {-# INLINE (>=) #-}
    <= :: ProductOrd DoubleX3 -> ProductOrd DoubleX3 -> Bool
(<=) (Partial.ProductOrd (DoubleX3# Double#
a1 Double#
a2 Double#
a3))
         (Partial.ProductOrd (DoubleX3# Double#
b1 Double#
b2 Double#
b3)) = Int# -> Bool
isTrue#
      ((Double#
a1 Double# -> Double# -> Int#
<=## Double#
b1) Int# -> Int# -> Int#
`andI#` (Double#
a2 Double# -> Double# -> Int#
<=## Double#
b2) Int# -> Int# -> Int#
`andI#` (Double#
a3 Double# -> Double# -> Int#
<=## Double#
b3))
    {-# INLINE (<=) #-}
    compare :: ProductOrd DoubleX3 -> ProductOrd DoubleX3 -> Ordering
compare (Partial.ProductOrd DoubleX3
a) (Partial.ProductOrd DoubleX3
b)
      = PartialOrdering -> Ordering
Partial.toOrdering (PartialOrdering -> Ordering) -> PartialOrdering -> Ordering
forall a b. (a -> b) -> a -> b
$ DoubleX3 -> DoubleX3 -> PartialOrdering
forall a. ProductOrder a => a -> a -> PartialOrdering
cmp DoubleX3
a DoubleX3
b
    {-# INLINE compare #-}
    min :: ProductOrd DoubleX3 -> ProductOrd DoubleX3 -> ProductOrd DoubleX3
min (Partial.ProductOrd (DoubleX3# Double#
a1 Double#
a2 Double#
a3))
        (Partial.ProductOrd (DoubleX3# Double#
b1 Double#
b2 Double#
b3))
      = DoubleX3 -> ProductOrd DoubleX3
forall a. a -> ProductOrd a
Partial.ProductOrd
        ( Double# -> Double# -> Double# -> DoubleX3
DoubleX3#
          (if Int# -> Bool
isTrue# (Double#
a1 Double# -> Double# -> Int#
>## Double#
b1) then Double#
b1 else Double#
a1)
          (if Int# -> Bool
isTrue# (Double#
a2 Double# -> Double# -> Int#
>## Double#
b2) then Double#
b2 else Double#
a2)
          (if Int# -> Bool
isTrue# (Double#
a3 Double# -> Double# -> Int#
>## Double#
b3) then Double#
b3 else Double#
a3)
        )
    {-# INLINE min #-}
    max :: ProductOrd DoubleX3 -> ProductOrd DoubleX3 -> ProductOrd DoubleX3
max (Partial.ProductOrd (DoubleX3# Double#
a1 Double#
a2 Double#
a3))
        (Partial.ProductOrd (DoubleX3# Double#
b1 Double#
b2 Double#
b3))
      = DoubleX3 -> ProductOrd DoubleX3
forall a. a -> ProductOrd a
Partial.ProductOrd
        ( Double# -> Double# -> Double# -> DoubleX3
DoubleX3#
          (if Int# -> Bool
isTrue# (Double#
a1 Double# -> Double# -> Int#
<## Double#
b1) then Double#
b1 else Double#
a1)
          (if Int# -> Bool
isTrue# (Double#
a2 Double# -> Double# -> Int#
<## Double#
b2) then Double#
b2 else Double#
a2)
          (if Int# -> Bool
isTrue# (Double#
a3 Double# -> Double# -> Int#
<## Double#
b3) then Double#
b3 else Double#
a3)
        )
    {-# INLINE max #-}

instance Ord DoubleX3 where
    DoubleX3# Double#
a1 Double#
a2 Double#
a3 > :: DoubleX3 -> DoubleX3 -> Bool
> DoubleX3# Double#
b1 Double#
b2 Double#
b3
      | Int# -> Bool
isTrue# (Double#
a1 Double# -> Double# -> Int#
>## Double#
b1) = Bool
True
      | Int# -> Bool
isTrue# (Double#
a1 Double# -> Double# -> Int#
<## Double#
b1) = Bool
False
      | Int# -> Bool
isTrue# (Double#
a2 Double# -> Double# -> Int#
>## Double#
b2) = Bool
True
      | Int# -> Bool
isTrue# (Double#
a2 Double# -> Double# -> Int#
<## Double#
b2) = Bool
False
      | Int# -> Bool
isTrue# (Double#
a3 Double# -> Double# -> Int#
>## Double#
b3) = Bool
True
      | Bool
otherwise           = Bool
False
    {-# INLINE (>) #-}

    DoubleX3# Double#
a1 Double#
a2 Double#
a3 < :: DoubleX3 -> DoubleX3 -> Bool
< DoubleX3# Double#
b1 Double#
b2 Double#
b3
      | Int# -> Bool
isTrue# (Double#
a1 Double# -> Double# -> Int#
<## Double#
b1) = Bool
True
      | Int# -> Bool
isTrue# (Double#
a1 Double# -> Double# -> Int#
>## Double#
b1) = Bool
False
      | Int# -> Bool
isTrue# (Double#
a2 Double# -> Double# -> Int#
<## Double#
b2) = Bool
True
      | Int# -> Bool
isTrue# (Double#
a2 Double# -> Double# -> Int#
>## Double#
b2) = Bool
False
      | Int# -> Bool
isTrue# (Double#
a3 Double# -> Double# -> Int#
<## Double#
b3) = Bool
True
      | Bool
otherwise           = Bool
False
    {-# INLINE (<) #-}

    DoubleX3# Double#
a1 Double#
a2 Double#
a3 >= :: DoubleX3 -> DoubleX3 -> Bool
>= DoubleX3# Double#
b1 Double#
b2 Double#
b3
      | Int# -> Bool
isTrue# (Double#
a1 Double# -> Double# -> Int#
<## Double#
b1) = Bool
False
      | Int# -> Bool
isTrue# (Double#
a1 Double# -> Double# -> Int#
>## Double#
b1) = Bool
True
      | Int# -> Bool
isTrue# (Double#
a2 Double# -> Double# -> Int#
<## Double#
b2) = Bool
False
      | Int# -> Bool
isTrue# (Double#
a2 Double# -> Double# -> Int#
>## Double#
b2) = Bool
True
      | Int# -> Bool
isTrue# (Double#
a3 Double# -> Double# -> Int#
<## Double#
b3) = Bool
False
      | Bool
otherwise           = Bool
True
    {-# INLINE (>=) #-}

    DoubleX3# Double#
a1 Double#
a2 Double#
a3 <= :: DoubleX3 -> DoubleX3 -> Bool
<= DoubleX3# Double#
b1 Double#
b2 Double#
b3
      | Int# -> Bool
isTrue# (Double#
a1 Double# -> Double# -> Int#
>## Double#
b1) = Bool
False
      | Int# -> Bool
isTrue# (Double#
a1 Double# -> Double# -> Int#
<## Double#
b1) = Bool
True
      | Int# -> Bool
isTrue# (Double#
a2 Double# -> Double# -> Int#
>## Double#
b2) = Bool
False
      | Int# -> Bool
isTrue# (Double#
a2 Double# -> Double# -> Int#
<## Double#
b2) = Bool
True
      | Int# -> Bool
isTrue# (Double#
a3 Double# -> Double# -> Int#
>## Double#
b3) = Bool
False
      | Bool
otherwise           = Bool
True
    {-# INLINE (<=) #-}

    compare :: DoubleX3 -> DoubleX3 -> Ordering
compare (DoubleX3# Double#
a1 Double#
a2 Double#
a3) (DoubleX3# Double#
b1 Double#
b2 Double#
b3)
      | Int# -> Bool
isTrue# (Double#
a1 Double# -> Double# -> Int#
>## Double#
b1) = Ordering
GT
      | Int# -> Bool
isTrue# (Double#
a1 Double# -> Double# -> Int#
<## Double#
b1) = Ordering
LT
      | Int# -> Bool
isTrue# (Double#
a2 Double# -> Double# -> Int#
>## Double#
b2) = Ordering
GT
      | Int# -> Bool
isTrue# (Double#
a2 Double# -> Double# -> Int#
<## Double#
b2) = Ordering
LT
      | Int# -> Bool
isTrue# (Double#
a3 Double# -> Double# -> Int#
>## Double#
b3) = Ordering
GT
      | Int# -> Bool
isTrue# (Double#
a3 Double# -> Double# -> Int#
<## Double#
b3) = Ordering
LT
      | Bool
otherwise           = Ordering
EQ
    {-# INLINE compare #-}




-- | element-wise operations for vectors
instance Num DoubleX3 where

    DoubleX3# Double#
a1 Double#
a2 Double#
a3 + :: DoubleX3 -> DoubleX3 -> DoubleX3
+ DoubleX3# Double#
b1 Double#
b2 Double#
b3
      = Double# -> Double# -> Double# -> DoubleX3
DoubleX3# (Double# -> Double# -> Double#
(+##) Double#
a1 Double#
b1) (Double# -> Double# -> Double#
(+##) Double#
a2 Double#
b2) (Double# -> Double# -> Double#
(+##) Double#
a3 Double#
b3)
    {-# INLINE (+) #-}

    DoubleX3# Double#
a1 Double#
a2 Double#
a3 - :: DoubleX3 -> DoubleX3 -> DoubleX3
- DoubleX3# Double#
b1 Double#
b2 Double#
b3
      = Double# -> Double# -> Double# -> DoubleX3
DoubleX3# (Double# -> Double# -> Double#
(-##) Double#
a1 Double#
b1) (Double# -> Double# -> Double#
(-##) Double#
a2 Double#
b2) (Double# -> Double# -> Double#
(-##) Double#
a3 Double#
b3)
    {-# INLINE (-) #-}

    DoubleX3# Double#
a1 Double#
a2 Double#
a3 * :: DoubleX3 -> DoubleX3 -> DoubleX3
* DoubleX3# Double#
b1 Double#
b2 Double#
b3
      = Double# -> Double# -> Double# -> DoubleX3
DoubleX3# (Double# -> Double# -> Double#
(*##) Double#
a1 Double#
b1) (Double# -> Double# -> Double#
(*##) Double#
a2 Double#
b2) (Double# -> Double# -> Double#
(*##) Double#
a3 Double#
b3)
    {-# INLINE (*) #-}

    negate :: DoubleX3 -> DoubleX3
negate (DoubleX3# Double#
a1 Double#
a2 Double#
a3) = Double# -> Double# -> Double# -> DoubleX3
DoubleX3#
      (Double# -> Double#
negateDouble# Double#
a1) (Double# -> Double#
negateDouble# Double#
a2) (Double# -> Double#
negateDouble# Double#
a3)
    {-# INLINE negate #-}

    abs :: DoubleX3 -> DoubleX3
abs (DoubleX3# Double#
a1 Double#
a2 Double#
a3)
      = Double# -> Double# -> Double# -> DoubleX3
DoubleX3#
      (if Int# -> Bool
isTrue# (Double#
a1 Double# -> Double# -> Int#
>=## Double#
0.0##) then Double#
a1 else Double# -> Double#
negateDouble# Double#
a1)
      (if Int# -> Bool
isTrue# (Double#
a2 Double# -> Double# -> Int#
>=## Double#
0.0##) then Double#
a2 else Double# -> Double#
negateDouble# Double#
a2)
      (if Int# -> Bool
isTrue# (Double#
a3 Double# -> Double# -> Int#
>=## Double#
0.0##) then Double#
a3 else Double# -> Double#
negateDouble# Double#
a3)
    {-# INLINE abs #-}

    signum :: DoubleX3 -> DoubleX3
signum (DoubleX3# Double#
a1 Double#
a2 Double#
a3)
      = Double# -> Double# -> Double# -> DoubleX3
DoubleX3# (if Int# -> Bool
isTrue# (Double#
a1 Double# -> Double# -> Int#
>## Double#
0.0##)
                  then Double#
1.0##
                  else if Int# -> Bool
isTrue# (Double#
a1 Double# -> Double# -> Int#
<## Double#
0.0##) then Double#
-1.0## else Double#
0.0## )
                 (if Int# -> Bool
isTrue# (Double#
a2 Double# -> Double# -> Int#
>## Double#
0.0##)
                  then Double#
1.0##
                  else if Int# -> Bool
isTrue# (Double#
a2 Double# -> Double# -> Int#
<## Double#
0.0##) then Double#
-1.0## else Double#
0.0## )
                 (if Int# -> Bool
isTrue# (Double#
a3 Double# -> Double# -> Int#
>## Double#
0.0##)
                  then Double#
1.0##
                  else if Int# -> Bool
isTrue# (Double#
a3 Double# -> Double# -> Int#
<## Double#
0.0##) then Double#
-1.0## else Double#
0.0## )
    {-# INLINE signum #-}

    fromInteger :: Integer -> DoubleX3
fromInteger Integer
n = case Integer -> Double
forall a. Num a => Integer -> a
fromInteger Integer
n of D# Double#
x -> Double# -> Double# -> Double# -> DoubleX3
DoubleX3# Double#
x Double#
x Double#
x
    {-# INLINE fromInteger #-}



instance Fractional DoubleX3 where

    DoubleX3# Double#
a1 Double#
a2 Double#
a3 / :: DoubleX3 -> DoubleX3 -> DoubleX3
/ DoubleX3# Double#
b1 Double#
b2 Double#
b3 = Double# -> Double# -> Double# -> DoubleX3
DoubleX3#
      (Double# -> Double# -> Double#
(/##) Double#
a1 Double#
b1) (Double# -> Double# -> Double#
(/##) Double#
a2 Double#
b2) (Double# -> Double# -> Double#
(/##) Double#
a3 Double#
b3)
    {-# INLINE (/) #-}

    recip :: DoubleX3 -> DoubleX3
recip (DoubleX3# Double#
a1 Double#
a2 Double#
a3) = Double# -> Double# -> Double# -> DoubleX3
DoubleX3#
      (Double# -> Double# -> Double#
(/##) Double#
1.0## Double#
a1) (Double# -> Double# -> Double#
(/##) Double#
1.0## Double#
a2) (Double# -> Double# -> Double#
(/##) Double#
1.0## Double#
a3)
    {-# INLINE recip #-}

    fromRational :: Rational -> DoubleX3
fromRational Rational
r = case Rational -> Double
forall a. Fractional a => Rational -> a
fromRational Rational
r of D# Double#
x -> Double# -> Double# -> Double# -> DoubleX3
DoubleX3# Double#
x Double#
x Double#
x
    {-# INLINE fromRational #-}



instance Floating DoubleX3 where

    pi :: DoubleX3
pi = Double# -> Double# -> Double# -> DoubleX3
DoubleX3#
      Double#
3.141592653589793238##
      Double#
3.141592653589793238##
      Double#
3.141592653589793238##
    {-# INLINE pi #-}

    exp :: DoubleX3 -> DoubleX3
exp (DoubleX3# Double#
a1 Double#
a2 Double#
a3) = Double# -> Double# -> Double# -> DoubleX3
DoubleX3#
      (Double# -> Double#
expDouble# Double#
a1) (Double# -> Double#
expDouble# Double#
a2) (Double# -> Double#
expDouble# Double#
a3)
    {-# INLINE exp #-}

    log :: DoubleX3 -> DoubleX3
log (DoubleX3# Double#
a1 Double#
a2 Double#
a3) = Double# -> Double# -> Double# -> DoubleX3
DoubleX3#
      (Double# -> Double#
logDouble# Double#
a1) (Double# -> Double#
logDouble# Double#
a2) (Double# -> Double#
logDouble# Double#
a3)
    {-# INLINE log #-}

    sqrt :: DoubleX3 -> DoubleX3
sqrt (DoubleX3# Double#
a1 Double#
a2 Double#
a3) = Double# -> Double# -> Double# -> DoubleX3
DoubleX3#
      (Double# -> Double#
sqrtDouble# Double#
a1) (Double# -> Double#
sqrtDouble# Double#
a2) (Double# -> Double#
sqrtDouble# Double#
a3)
    {-# INLINE sqrt #-}

    sin :: DoubleX3 -> DoubleX3
sin (DoubleX3# Double#
a1 Double#
a2 Double#
a3) = Double# -> Double# -> Double# -> DoubleX3
DoubleX3#
      (Double# -> Double#
sinDouble# Double#
a1) (Double# -> Double#
sinDouble# Double#
a2) (Double# -> Double#
sinDouble# Double#
a3)
    {-# INLINE sin #-}

    cos :: DoubleX3 -> DoubleX3
cos (DoubleX3# Double#
a1 Double#
a2 Double#
a3) = Double# -> Double# -> Double# -> DoubleX3
DoubleX3#
      (Double# -> Double#
cosDouble# Double#
a1) (Double# -> Double#
cosDouble# Double#
a2) (Double# -> Double#
cosDouble# Double#
a3)
    {-# INLINE cos #-}

    tan :: DoubleX3 -> DoubleX3
tan (DoubleX3# Double#
a1 Double#
a2 Double#
a3) = Double# -> Double# -> Double# -> DoubleX3
DoubleX3#
      (Double# -> Double#
tanDouble# Double#
a1) (Double# -> Double#
tanDouble# Double#
a2) (Double# -> Double#
tanDouble# Double#
a3)
    {-# INLINE tan #-}

    asin :: DoubleX3 -> DoubleX3
asin (DoubleX3# Double#
a1 Double#
a2 Double#
a3) = Double# -> Double# -> Double# -> DoubleX3
DoubleX3#
      (Double# -> Double#
asinDouble# Double#
a1) (Double# -> Double#
asinDouble# Double#
a2) (Double# -> Double#
asinDouble# Double#
a3)
    {-# INLINE asin #-}

    acos :: DoubleX3 -> DoubleX3
acos (DoubleX3# Double#
a1 Double#
a2 Double#
a3) = Double# -> Double# -> Double# -> DoubleX3
DoubleX3#
      (Double# -> Double#
acosDouble# Double#
a1) (Double# -> Double#
acosDouble# Double#
a2) (Double# -> Double#
acosDouble# Double#
a3)
    {-# INLINE acos #-}

    atan :: DoubleX3 -> DoubleX3
atan (DoubleX3# Double#
a1 Double#
a2 Double#
a3) = Double# -> Double# -> Double# -> DoubleX3
DoubleX3#
      (Double# -> Double#
atanDouble# Double#
a1) (Double# -> Double#
atanDouble# Double#
a2) (Double# -> Double#
atanDouble# Double#
a3)
    {-# INLINE atan #-}

    sinh :: DoubleX3 -> DoubleX3
sinh (DoubleX3# Double#
a1 Double#
a2 Double#
a3) = Double# -> Double# -> Double# -> DoubleX3
DoubleX3#
      (Double# -> Double#
sinhDouble# Double#
a1) (Double# -> Double#
sinhDouble# Double#
a2) (Double# -> Double#
sinhDouble# Double#
a3)
    {-# INLINE sinh #-}

    cosh :: DoubleX3 -> DoubleX3
cosh (DoubleX3# Double#
a1 Double#
a2 Double#
a3) = Double# -> Double# -> Double# -> DoubleX3
DoubleX3#
      (Double# -> Double#
coshDouble# Double#
a1) (Double# -> Double#
coshDouble# Double#
a2) (Double# -> Double#
coshDouble# Double#
a3)
    {-# INLINE cosh #-}

    tanh :: DoubleX3 -> DoubleX3
tanh (DoubleX3# Double#
a1 Double#
a2 Double#
a3) = Double# -> Double# -> Double# -> DoubleX3
DoubleX3#
      (Double# -> Double#
tanhDouble# Double#
a1) (Double# -> Double#
tanhDouble# Double#
a2) (Double# -> Double#
tanhDouble# Double#
a3)
    {-# INLINE tanh #-}

    DoubleX3# Double#
a1 Double#
a2 Double#
a3 ** :: DoubleX3 -> DoubleX3 -> DoubleX3
** DoubleX3# Double#
b1 Double#
b2 Double#
b3 = Double# -> Double# -> Double# -> DoubleX3
DoubleX3#
      (Double# -> Double# -> Double#
(**##) Double#
a1 Double#
b1) (Double# -> Double# -> Double#
(**##) Double#
a2 Double#
b2) (Double# -> Double# -> Double#
(**##) Double#
a3 Double#
b3)
    {-# INLINE (**) #-}

    logBase :: DoubleX3 -> DoubleX3 -> DoubleX3
logBase DoubleX3
x DoubleX3
y         =  DoubleX3 -> DoubleX3
forall a. Floating a => a -> a
log DoubleX3
y DoubleX3 -> DoubleX3 -> DoubleX3
forall a. Fractional a => a -> a -> a
/ DoubleX3 -> DoubleX3
forall a. Floating a => a -> a
log DoubleX3
x
    {-# INLINE logBase #-}

    asinh :: DoubleX3 -> DoubleX3
asinh DoubleX3
x = DoubleX3 -> DoubleX3
forall a. Floating a => a -> a
log (DoubleX3
x DoubleX3 -> DoubleX3 -> DoubleX3
forall a. Num a => a -> a -> a
+ DoubleX3 -> DoubleX3
forall a. Floating a => a -> a
sqrt (DoubleX3
1.0DoubleX3 -> DoubleX3 -> DoubleX3
forall a. Num a => a -> a -> a
+DoubleX3
xDoubleX3 -> DoubleX3 -> DoubleX3
forall a. Num a => a -> a -> a
*DoubleX3
x))
    {-# INLINE asinh #-}

    acosh :: DoubleX3 -> DoubleX3
acosh DoubleX3
x = DoubleX3 -> DoubleX3
forall a. Floating a => a -> a
log (DoubleX3
x DoubleX3 -> DoubleX3 -> DoubleX3
forall a. Num a => a -> a -> a
+ (DoubleX3
xDoubleX3 -> DoubleX3 -> DoubleX3
forall a. Num a => a -> a -> a
+DoubleX3
1.0) DoubleX3 -> DoubleX3 -> DoubleX3
forall a. Num a => a -> a -> a
* DoubleX3 -> DoubleX3
forall a. Floating a => a -> a
sqrt ((DoubleX3
xDoubleX3 -> DoubleX3 -> DoubleX3
forall a. Num a => a -> a -> a
-DoubleX3
1.0)DoubleX3 -> DoubleX3 -> DoubleX3
forall a. Fractional a => a -> a -> a
/(DoubleX3
xDoubleX3 -> DoubleX3 -> DoubleX3
forall a. Num a => a -> a -> a
+DoubleX3
1.0)))
    {-# INLINE acosh #-}

    atanh :: DoubleX3 -> DoubleX3
atanh DoubleX3
x = DoubleX3
0.5 DoubleX3 -> DoubleX3 -> DoubleX3
forall a. Num a => a -> a -> a
* DoubleX3 -> DoubleX3
forall a. Floating a => a -> a
log ((DoubleX3
1.0DoubleX3 -> DoubleX3 -> DoubleX3
forall a. Num a => a -> a -> a
+DoubleX3
x) DoubleX3 -> DoubleX3 -> DoubleX3
forall a. Fractional a => a -> a -> a
/ (DoubleX3
1.0DoubleX3 -> DoubleX3 -> DoubleX3
forall a. Num a => a -> a -> a
-DoubleX3
x))
    {-# INLINE atanh #-}

-- offset in bytes is S times bigger than offset in prim elements,
-- when S is power of two, this is equal to shift
#define BOFF_TO_PRIMOFF(off) uncheckedIShiftRL# off 3#
#define ELEM_N 3

instance PrimBytes DoubleX3 where

    getBytes :: DoubleX3 -> ByteArray#
getBytes (DoubleX3# Double#
a1 Double#
a2 Double#
a3) = case (State# RealWorld -> (# State# RealWorld, ByteArray# #))
-> (# State# RealWorld, ByteArray# #)
forall o. (State# RealWorld -> o) -> o
runRW#
       ( \State# RealWorld
s0 -> case Int#
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
newByteArray# (DoubleX3 -> Int#
forall a. PrimBytes a => a -> Int#
byteSize @DoubleX3 DoubleX3
forall a. HasCallStack => a
undefined) State# RealWorld
s0 of
           (# State# RealWorld
s1, MutableByteArray# RealWorld
marr #) -> case MutableByteArray# RealWorld
-> Int# -> Double# -> State# RealWorld -> State# RealWorld
forall d.
MutableByteArray# d -> Int# -> Double# -> State# d -> State# d
writeDoubleArray# MutableByteArray# RealWorld
marr Int#
0# Double#
a1 State# RealWorld
s1 of
             State# RealWorld
s2 -> case MutableByteArray# RealWorld
-> Int# -> Double# -> State# RealWorld -> State# RealWorld
forall d.
MutableByteArray# d -> Int# -> Double# -> State# d -> State# d
writeDoubleArray# MutableByteArray# RealWorld
marr Int#
1# Double#
a2 State# RealWorld
s2 of
               State# RealWorld
s3 -> case MutableByteArray# RealWorld
-> Int# -> Double# -> State# RealWorld -> State# RealWorld
forall d.
MutableByteArray# d -> Int# -> Double# -> State# d -> State# d
writeDoubleArray# MutableByteArray# RealWorld
marr Int#
2# Double#
a3 State# RealWorld
s3 of
                 State# RealWorld
s4 -> MutableByteArray# RealWorld
-> State# RealWorld -> (# State# RealWorld, ByteArray# #)
forall d.
MutableByteArray# d -> State# d -> (# State# d, ByteArray# #)
unsafeFreezeByteArray# MutableByteArray# RealWorld
marr State# RealWorld
s4
       ) of (# State# RealWorld
_, ByteArray#
a #) -> ByteArray#
a
    {-# INLINE getBytes #-}

    fromBytes :: Int# -> ByteArray# -> DoubleX3
fromBytes Int#
off ByteArray#
arr
      | Int#
i <- BOFF_TO_PRIMOFF(off)
      = Double# -> Double# -> Double# -> DoubleX3
DoubleX3#
      (ByteArray# -> Int# -> Double#
indexDoubleArray# ByteArray#
arr Int#
i)
      (ByteArray# -> Int# -> Double#
indexDoubleArray# ByteArray#
arr (Int#
i Int# -> Int# -> Int#
+# Int#
1#))
      (ByteArray# -> Int# -> Double#
indexDoubleArray# ByteArray#
arr (Int#
i Int# -> Int# -> Int#
+# Int#
2#))
    {-# INLINE fromBytes #-}

    readBytes :: MutableByteArray# s -> Int# -> State# s -> (# State# s, DoubleX3 #)
readBytes MutableByteArray# s
mba Int#
off State# s
s0
      | Int#
i <- BOFF_TO_PRIMOFF(off)
      = case MutableByteArray# s -> Int# -> State# s -> (# State# s, Double# #)
forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #)
readDoubleArray# MutableByteArray# s
mba Int#
i State# s
s0 of
      (# State# s
s1, Double#
a1 #) -> case MutableByteArray# s -> Int# -> State# s -> (# State# s, Double# #)
forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #)
readDoubleArray# MutableByteArray# s
mba (Int#
i Int# -> Int# -> Int#
+# Int#
1#) State# s
s1 of
        (# State# s
s2, Double#
a2 #) -> case MutableByteArray# s -> Int# -> State# s -> (# State# s, Double# #)
forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #)
readDoubleArray# MutableByteArray# s
mba (Int#
i Int# -> Int# -> Int#
+# Int#
2#) State# s
s2 of
          (# State# s
s3, Double#
a3 #) -> (# State# s
s3, Double# -> Double# -> Double# -> DoubleX3
DoubleX3# Double#
a1 Double#
a2 Double#
a3 #)
    {-# INLINE readBytes #-}

    writeBytes :: MutableByteArray# s -> Int# -> DoubleX3 -> State# s -> State# s
writeBytes MutableByteArray# s
mba Int#
off (DoubleX3# Double#
a1 Double#
a2 Double#
a3) State# s
s
      | Int#
i <- BOFF_TO_PRIMOFF(off)
      = MutableByteArray# s -> Int# -> Double# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Double# -> State# d -> State# d
writeDoubleArray# MutableByteArray# s
mba (Int#
i Int# -> Int# -> Int#
+# Int#
2#) Double#
a3
      ( MutableByteArray# s -> Int# -> Double# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Double# -> State# d -> State# d
writeDoubleArray# MutableByteArray# s
mba (Int#
i Int# -> Int# -> Int#
+# Int#
1#) Double#
a2
      ( MutableByteArray# s -> Int# -> Double# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Double# -> State# d -> State# d
writeDoubleArray# MutableByteArray# s
mba  Int#
i        Double#
a1 State# s
s ))
    {-# INLINE writeBytes #-}

    readAddr :: Addr# -> State# s -> (# State# s, DoubleX3 #)
readAddr Addr#
addr State# s
s0
      = case Addr# -> Int# -> State# s -> (# State# s, Double# #)
forall d. Addr# -> Int# -> State# d -> (# State# d, Double# #)
readDoubleOffAddr# Addr#
addr Int#
0# State# s
s0 of
      (# State# s
s1, Double#
a1 #) -> case Addr# -> Int# -> State# s -> (# State# s, Double# #)
forall d. Addr# -> Int# -> State# d -> (# State# d, Double# #)
readDoubleOffAddr# Addr#
addr Int#
1# State# s
s1 of
        (# State# s
s2, Double#
a2 #) -> case Addr# -> Int# -> State# s -> (# State# s, Double# #)
forall d. Addr# -> Int# -> State# d -> (# State# d, Double# #)
readDoubleOffAddr# Addr#
addr Int#
2# State# s
s2 of
          (# State# s
s3, Double#
a3 #) -> (# State# s
s3, Double# -> Double# -> Double# -> DoubleX3
DoubleX3# Double#
a1 Double#
a2 Double#
a3 #)
    {-# INLINE readAddr #-}

    writeAddr :: DoubleX3 -> Addr# -> State# s -> State# s
writeAddr (DoubleX3# Double#
a1 Double#
a2 Double#
a3) Addr#
addr State# s
s
      = Addr# -> Int# -> Double# -> State# s -> State# s
forall d. Addr# -> Int# -> Double# -> State# d -> State# d
writeDoubleOffAddr# Addr#
addr Int#
2# Double#
a3
      ( Addr# -> Int# -> Double# -> State# s -> State# s
forall d. Addr# -> Int# -> Double# -> State# d -> State# d
writeDoubleOffAddr# Addr#
addr Int#
1# Double#
a2
      ( Addr# -> Int# -> Double# -> State# s -> State# s
forall d. Addr# -> Int# -> Double# -> State# d -> State# d
writeDoubleOffAddr# Addr#
addr Int#
0# Double#
a1 State# s
s ))
    {-# INLINE writeAddr #-}

    byteSize :: DoubleX3 -> Int#
byteSize DoubleX3
_ = Double -> Int#
forall a. PrimBytes a => a -> Int#
byteSize @Double Double
forall a. HasCallStack => a
undefined Int# -> Int# -> Int#
*# ELEM_N#
    {-# INLINE byteSize #-}

    byteAlign :: DoubleX3 -> Int#
byteAlign DoubleX3
_ = Double -> Int#
forall a. PrimBytes a => a -> Int#
byteAlign @Double Double
forall a. HasCallStack => a
undefined
    {-# INLINE byteAlign #-}

    byteOffset :: DoubleX3 -> Int#
byteOffset DoubleX3
_ = Int#
0#
    {-# INLINE byteOffset #-}

    byteFieldOffset :: Proxy# name -> DoubleX3 -> Int#
byteFieldOffset Proxy# name
_ DoubleX3
_ = Int# -> Int#
negateInt# Int#
1#
    {-# INLINE byteFieldOffset #-}

    indexArray :: ByteArray# -> Int# -> DoubleX3
indexArray ByteArray#
ba Int#
off
      | Int#
i <- Int#
off Int# -> Int# -> Int#
*# ELEM_N#
      = Double# -> Double# -> Double# -> DoubleX3
DoubleX3#
      (ByteArray# -> Int# -> Double#
indexDoubleArray# ByteArray#
ba Int#
i)
      (ByteArray# -> Int# -> Double#
indexDoubleArray# ByteArray#
ba (Int#
i Int# -> Int# -> Int#
+# Int#
1#))
      (ByteArray# -> Int# -> Double#
indexDoubleArray# ByteArray#
ba (Int#
i Int# -> Int# -> Int#
+# Int#
2#))
    {-# INLINE indexArray #-}

    readArray :: MutableByteArray# s -> Int# -> State# s -> (# State# s, DoubleX3 #)
readArray MutableByteArray# s
mba Int#
off State# s
s0
      | Int#
i <- Int#
off Int# -> Int# -> Int#
*# ELEM_N#
      = case MutableByteArray# s -> Int# -> State# s -> (# State# s, Double# #)
forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #)
readDoubleArray# MutableByteArray# s
mba Int#
i State# s
s0 of
      (# State# s
s1, Double#
a1 #) -> case MutableByteArray# s -> Int# -> State# s -> (# State# s, Double# #)
forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #)
readDoubleArray# MutableByteArray# s
mba (Int#
i Int# -> Int# -> Int#
+# Int#
1#) State# s
s1 of
        (# State# s
s2, Double#
a2 #) -> case MutableByteArray# s -> Int# -> State# s -> (# State# s, Double# #)
forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #)
readDoubleArray# MutableByteArray# s
mba (Int#
i Int# -> Int# -> Int#
+# Int#
2#) State# s
s2 of
          (# State# s
s3, Double#
a3 #) -> (# State# s
s3, Double# -> Double# -> Double# -> DoubleX3
DoubleX3# Double#
a1 Double#
a2 Double#
a3 #)
    {-# INLINE readArray #-}

    writeArray :: MutableByteArray# s -> Int# -> DoubleX3 -> State# s -> State# s
writeArray MutableByteArray# s
mba Int#
off (DoubleX3# Double#
a1 Double#
a2 Double#
a3) State# s
s
      | Int#
i <- Int#
off Int# -> Int# -> Int#
*# ELEM_N#
      = MutableByteArray# s -> Int# -> Double# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Double# -> State# d -> State# d
writeDoubleArray# MutableByteArray# s
mba (Int#
i Int# -> Int# -> Int#
+# Int#
2#) Double#
a3
      ( MutableByteArray# s -> Int# -> Double# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Double# -> State# d -> State# d
writeDoubleArray# MutableByteArray# s
mba (Int#
i Int# -> Int# -> Int#
+# Int#
1#) Double#
a2
      ( MutableByteArray# s -> Int# -> Double# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Double# -> State# d -> State# d
writeDoubleArray# MutableByteArray# s
mba  Int#
i        Double#
a1 State# s
s ))
    {-# INLINE writeArray #-}


instance PrimArray Double DoubleX3 where

    broadcast# :: Double -> DoubleX3
broadcast# (D# Double#
x) = Double# -> Double# -> Double# -> DoubleX3
DoubleX3# Double#
x Double#
x Double#
x
    {-# INLINE broadcast# #-}

    ix# :: Int# -> DoubleX3 -> Double
ix# Int#
0# (DoubleX3# Double#
a1 Double#
_ Double#
_) = Double# -> Double
D# Double#
a1
    ix# Int#
1# (DoubleX3# Double#
_ Double#
a2 Double#
_) = Double# -> Double
D# Double#
a2
    ix# Int#
2# (DoubleX3# Double#
_ Double#
_ Double#
a3) = Double# -> Double
D# Double#
a3
    ix# Int#
_   DoubleX3
_                 = Double
forall a. HasCallStack => a
undefined
    {-# INLINE ix# #-}

    gen# :: CumulDims -> (s -> (# s, Double #)) -> s -> (# s, DoubleX3 #)
gen# CumulDims
_ s -> (# s, Double #)
f s
s0 = case s -> (# s, Double #)
f s
s0 of
      (# s
s1, D# Double#
a1 #) -> case s -> (# s, Double #)
f s
s1 of
        (# s
s2, D# Double#
a2 #) -> case s -> (# s, Double #)
f s
s2 of
          (# s
s3, D# Double#
a3 #) -> (# s
s3, Double# -> Double# -> Double# -> DoubleX3
DoubleX3# Double#
a1 Double#
a2 Double#
a3 #)


    upd# :: CumulDims -> Int# -> Double -> DoubleX3 -> DoubleX3
upd# CumulDims
_ Int#
0# (D# Double#
q) (DoubleX3# Double#
_ Double#
y Double#
z) = Double# -> Double# -> Double# -> DoubleX3
DoubleX3# Double#
q Double#
y Double#
z
    upd# CumulDims
_ Int#
1# (D# Double#
q) (DoubleX3# Double#
x Double#
_ Double#
z) = Double# -> Double# -> Double# -> DoubleX3
DoubleX3# Double#
x Double#
q Double#
z
    upd# CumulDims
_ Int#
2# (D# Double#
q) (DoubleX3# Double#
x Double#
y Double#
_) = Double# -> Double# -> Double# -> DoubleX3
DoubleX3# Double#
x Double#
y Double#
q
    upd# CumulDims
_ Int#
_ Double
_ DoubleX3
x                       = DoubleX3
x
    {-# INLINE upd# #-}

    withArrayContent# :: (Double -> r)
-> (CumulDims -> Int# -> ByteArray# -> r) -> DoubleX3 -> r
withArrayContent# Double -> r
_ CumulDims -> Int# -> ByteArray# -> r
g DoubleX3
x = CumulDims -> Int# -> ByteArray# -> r
g ([Word] -> CumulDims
CumulDims [ELEM_N, 1]) 0# (getBytes x)
    {-# INLINE withArrayContent# #-}

    offsetElems :: DoubleX3 -> Int#
offsetElems DoubleX3
_ = Int#
0#
    {-# INLINE offsetElems #-}

    uniqueOrCumulDims :: DoubleX3 -> Either Double CumulDims
uniqueOrCumulDims DoubleX3
_ = CumulDims -> Either Double CumulDims
forall a b. b -> Either a b
Right ([Word] -> CumulDims
CumulDims [ELEM_N, 1])
    {-# INLINE uniqueOrCumulDims #-}

    fromElems# :: CumulDims -> Int# -> ByteArray# -> DoubleX3
fromElems# CumulDims
_ Int#
off ByteArray#
ba = Double# -> Double# -> Double# -> DoubleX3
DoubleX3#
      (ByteArray# -> Int# -> Double#
indexDoubleArray# ByteArray#
ba Int#
off)
      (ByteArray# -> Int# -> Double#
indexDoubleArray# ByteArray#
ba (Int#
off Int# -> Int# -> Int#
+# Int#
1#))
      (ByteArray# -> Int# -> Double#
indexDoubleArray# ByteArray#
ba (Int#
off Int# -> Int# -> Int#
+# Int#
2#))
    {-# INLINE fromElems# #-}