{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Database.Postgis.Trivial.Unboxed.PointND
( P2DU (..)
, P3DZU (..)
, P3DMU (..)
, P4DU (..)
) where
import GHC.Base
import GHC.Show ( Show )
import Control.Applicative ( (<$>) )
import Data.Tuple ( uncurry )
import Control.Exception ( throw )
import qualified Data.Vector.Generic as VG
import qualified Data.Vector.Generic.Mutable as VGM
import qualified Data.Vector.Unboxed as VU
import Database.Postgis.Trivial.Types
import Database.Postgis.Trivial.Cast
uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d
uncurry3 :: forall a b c d. (a -> b -> c -> d) -> (a, b, c) -> d
uncurry3 a -> b -> c -> d
f (a
a, b
b, c
c) = a -> b -> c -> d
f a
a b
b c
c
uncurry4 :: (a -> b -> c -> d -> e) -> (a, b, c, d) -> e
uncurry4 :: forall a b c d e. (a -> b -> c -> d -> e) -> (a, b, c, d) -> e
uncurry4 a -> b -> c -> d -> e
f (a
a, b
b, c
c, d
d) = a -> b -> c -> d -> e
f a
a b
b c
c d
d
data P2DU = Point2DU
{-# UNPACK #-} !Double
{-# UNPACK #-} !Double
deriving (Int -> P2DU -> ShowS
[P2DU] -> ShowS
P2DU -> String
(Int -> P2DU -> ShowS)
-> (P2DU -> String) -> ([P2DU] -> ShowS) -> Show P2DU
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> P2DU -> ShowS
showsPrec :: Int -> P2DU -> ShowS
$cshow :: P2DU -> String
show :: P2DU -> String
$cshowList :: [P2DU] -> ShowS
showList :: [P2DU] -> ShowS
Show, P2DU -> P2DU -> Bool
(P2DU -> P2DU -> Bool) -> (P2DU -> P2DU -> Bool) -> Eq P2DU
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: P2DU -> P2DU -> Bool
== :: P2DU -> P2DU -> Bool
$c/= :: P2DU -> P2DU -> Bool
/= :: P2DU -> P2DU -> Bool
Eq)
fromP2D :: P2DU -> (Double, Double)
fromP2D :: P2DU -> (Double, Double)
fromP2D (Point2DU Double
x Double
y) = (Double
x, Double
y)
newtype instance VU.MVector s P2DU = MV_P2D (VU.MVector s (Double, Double))
newtype instance VU.Vector P2DU = V_P2D (VU.Vector (Double, Double))
instance VGM.MVector VU.MVector P2DU where
{-# INLINE basicLength #-}
{-# INLINE basicUnsafeSlice #-}
{-# INLINE basicOverlaps #-}
{-# INLINE basicUnsafeNew #-}
{-# INLINE basicInitialize #-}
{-# INLINE basicUnsafeReplicate #-}
{-# INLINE basicUnsafeRead #-}
{-# INLINE basicUnsafeWrite #-}
{-# INLINE basicClear #-}
{-# INLINE basicSet #-}
{-# INLINE basicUnsafeCopy #-}
{-# INLINE basicUnsafeGrow #-}
basicLength :: forall s. MVector s P2DU -> Int
basicLength (MV_P2D MVector s (Double, Double)
v) = MVector s (Double, Double) -> Int
forall s. MVector s (Double, Double) -> Int
forall (v :: * -> * -> *) a s. MVector v a => v s a -> Int
VGM.basicLength MVector s (Double, Double)
v
basicUnsafeNew :: forall s. Int -> ST s (MVector s P2DU)
basicUnsafeNew Int
n = MVector s (Double, Double) -> MVector s P2DU
forall s. MVector s (Double, Double) -> MVector s P2DU
MV_P2D (MVector s (Double, Double) -> MVector s P2DU)
-> ST s (MVector s (Double, Double)) -> ST s (MVector s P2DU)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> ST s (MVector s (Double, Double))
forall s. Int -> ST s (MVector s (Double, Double))
forall (v :: * -> * -> *) a s. MVector v a => Int -> ST s (v s a)
VGM.basicUnsafeNew Int
n
basicUnsafeSlice :: forall s. Int -> Int -> MVector s P2DU -> MVector s P2DU
basicUnsafeSlice Int
i Int
n (MV_P2D MVector s (Double, Double)
v) = MVector s (Double, Double) -> MVector s P2DU
forall s. MVector s (Double, Double) -> MVector s P2DU
MV_P2D (MVector s (Double, Double) -> MVector s P2DU)
-> MVector s (Double, Double) -> MVector s P2DU
forall a b. (a -> b) -> a -> b
$ Int
-> Int -> MVector s (Double, Double) -> MVector s (Double, Double)
forall s.
Int
-> Int -> MVector s (Double, Double) -> MVector s (Double, Double)
forall (v :: * -> * -> *) a s.
MVector v a =>
Int -> Int -> v s a -> v s a
VGM.basicUnsafeSlice Int
i Int
n MVector s (Double, Double)
v
basicOverlaps :: forall s. MVector s P2DU -> MVector s P2DU -> Bool
basicOverlaps (MV_P2D MVector s (Double, Double)
v1) (MV_P2D MVector s (Double, Double)
v2) = MVector s (Double, Double) -> MVector s (Double, Double) -> Bool
forall s.
MVector s (Double, Double) -> MVector s (Double, Double) -> Bool
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> Bool
VGM.basicOverlaps MVector s (Double, Double)
v1 MVector s (Double, Double)
v2
basicInitialize :: forall s. MVector s P2DU -> ST s ()
basicInitialize (MV_P2D MVector s (Double, Double)
v) = MVector s (Double, Double) -> ST s ()
forall s. MVector s (Double, Double) -> ST s ()
forall (v :: * -> * -> *) a s. MVector v a => v s a -> ST s ()
VGM.basicInitialize MVector s (Double, Double)
v
basicUnsafeReplicate :: forall s. Int -> P2DU -> ST s (MVector s P2DU)
basicUnsafeReplicate Int
n P2DU
p = MVector s (Double, Double) -> MVector s P2DU
forall s. MVector s (Double, Double) -> MVector s P2DU
MV_P2D (MVector s (Double, Double) -> MVector s P2DU)
-> ST s (MVector s (Double, Double)) -> ST s (MVector s P2DU)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> (Double, Double) -> ST s (MVector s (Double, Double))
forall s.
Int -> (Double, Double) -> ST s (MVector s (Double, Double))
forall (v :: * -> * -> *) a s.
MVector v a =>
Int -> a -> ST s (v s a)
VGM.basicUnsafeReplicate Int
n (P2DU -> (Double, Double)
fromP2D P2DU
p)
basicUnsafeRead :: forall s. MVector s P2DU -> Int -> ST s P2DU
basicUnsafeRead (MV_P2D MVector s (Double, Double)
v) Int
i = (Double -> Double -> P2DU) -> (Double, Double) -> P2DU
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Double -> Double -> P2DU
Point2DU ((Double, Double) -> P2DU) -> ST s (Double, Double) -> ST s P2DU
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MVector s (Double, Double) -> Int -> ST s (Double, Double)
forall s.
MVector s (Double, Double) -> Int -> ST s (Double, Double)
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> Int -> ST s a
VGM.basicUnsafeRead MVector s (Double, Double)
v Int
i
basicUnsafeWrite :: forall s. MVector s P2DU -> Int -> P2DU -> ST s ()
basicUnsafeWrite (MV_P2D MVector s (Double, Double)
v) Int
i P2DU
p = MVector s (Double, Double) -> Int -> (Double, Double) -> ST s ()
forall s.
MVector s (Double, Double) -> Int -> (Double, Double) -> ST s ()
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> Int -> a -> ST s ()
VGM.basicUnsafeWrite MVector s (Double, Double)
v Int
i (P2DU -> (Double, Double)
fromP2D P2DU
p)
basicClear :: forall s. MVector s P2DU -> ST s ()
basicClear (MV_P2D MVector s (Double, Double)
v) = MVector s (Double, Double) -> ST s ()
forall s. MVector s (Double, Double) -> ST s ()
forall (v :: * -> * -> *) a s. MVector v a => v s a -> ST s ()
VGM.basicClear MVector s (Double, Double)
v
basicSet :: forall s. MVector s P2DU -> P2DU -> ST s ()
basicSet (MV_P2D MVector s (Double, Double)
v) P2DU
p = MVector s (Double, Double) -> (Double, Double) -> ST s ()
forall s. MVector s (Double, Double) -> (Double, Double) -> ST s ()
forall (v :: * -> * -> *) a s. MVector v a => v s a -> a -> ST s ()
VGM.basicSet MVector s (Double, Double)
v (P2DU -> (Double, Double)
fromP2D P2DU
p)
basicUnsafeCopy :: forall s. MVector s P2DU -> MVector s P2DU -> ST s ()
basicUnsafeCopy (MV_P2D MVector s (Double, Double)
v1) (MV_P2D MVector s (Double, Double)
v2) = MVector s (Double, Double) -> MVector s (Double, Double) -> ST s ()
forall s.
MVector s (Double, Double) -> MVector s (Double, Double) -> ST s ()
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> ST s ()
VGM.basicUnsafeCopy MVector s (Double, Double)
v1 MVector s (Double, Double)
v2
basicUnsafeMove :: forall s. MVector s P2DU -> MVector s P2DU -> ST s ()
basicUnsafeMove (MV_P2D MVector s (Double, Double)
v1) (MV_P2D MVector s (Double, Double)
v2) = MVector s (Double, Double) -> MVector s (Double, Double) -> ST s ()
forall s.
MVector s (Double, Double) -> MVector s (Double, Double) -> ST s ()
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> ST s ()
VGM.basicUnsafeMove MVector s (Double, Double)
v1 MVector s (Double, Double)
v2
basicUnsafeGrow :: forall s. MVector s P2DU -> Int -> ST s (MVector s P2DU)
basicUnsafeGrow (MV_P2D MVector s (Double, Double)
v) Int
n = MVector s (Double, Double) -> MVector s P2DU
forall s. MVector s (Double, Double) -> MVector s P2DU
MV_P2D (MVector s (Double, Double) -> MVector s P2DU)
-> ST s (MVector s (Double, Double)) -> ST s (MVector s P2DU)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MVector s (Double, Double)
-> Int -> ST s (MVector s (Double, Double))
forall s.
MVector s (Double, Double)
-> Int -> ST s (MVector s (Double, Double))
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> Int -> ST s (v s a)
VGM.basicUnsafeGrow MVector s (Double, Double)
v Int
n
instance VG.Vector VU.Vector P2DU where
{-# INLINE basicLength #-}
{-# INLINE basicUnsafeFreeze #-}
{-# INLINE basicUnsafeThaw #-}
{-# INLINE basicUnsafeSlice #-}
{-# INLINE basicUnsafeIndexM #-}
basicLength :: Vector P2DU -> Int
basicLength (V_P2D Vector (Double, Double)
v) = Vector (Double, Double) -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
VG.basicLength Vector (Double, Double)
v
basicUnsafeFreeze :: forall s. Mutable Vector s P2DU -> ST s (Vector P2DU)
basicUnsafeFreeze (MV_P2D MVector s (Double, Double)
v) = Vector (Double, Double) -> Vector P2DU
V_P2D (Vector (Double, Double) -> Vector P2DU)
-> ST s (Vector (Double, Double)) -> ST s (Vector P2DU)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Mutable Vector s (Double, Double) -> ST s (Vector (Double, Double))
forall s.
Mutable Vector s (Double, Double) -> ST s (Vector (Double, Double))
forall (v :: * -> *) a s. Vector v a => Mutable v s a -> ST s (v a)
VG.basicUnsafeFreeze Mutable Vector s (Double, Double)
MVector s (Double, Double)
v
basicUnsafeThaw :: forall s. Vector P2DU -> ST s (Mutable Vector s P2DU)
basicUnsafeThaw (V_P2D Vector (Double, Double)
v) = MVector s (Double, Double) -> MVector s P2DU
forall s. MVector s (Double, Double) -> MVector s P2DU
MV_P2D (MVector s (Double, Double) -> MVector s P2DU)
-> ST s (MVector s (Double, Double)) -> ST s (MVector s P2DU)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Vector (Double, Double) -> ST s (Mutable Vector s (Double, Double))
forall s.
Vector (Double, Double) -> ST s (Mutable Vector s (Double, Double))
forall (v :: * -> *) a s. Vector v a => v a -> ST s (Mutable v s a)
VG.basicUnsafeThaw Vector (Double, Double)
v
basicUnsafeSlice :: Int -> Int -> Vector P2DU -> Vector P2DU
basicUnsafeSlice Int
i Int
n (V_P2D Vector (Double, Double)
v) = Vector (Double, Double) -> Vector P2DU
V_P2D (Vector (Double, Double) -> Vector P2DU)
-> Vector (Double, Double) -> Vector P2DU
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Vector (Double, Double) -> Vector (Double, Double)
forall (v :: * -> *) a. Vector v a => Int -> Int -> v a -> v a
VG.basicUnsafeSlice Int
i Int
n Vector (Double, Double)
v
basicUnsafeIndexM :: Vector P2DU -> Int -> Box P2DU
basicUnsafeIndexM (V_P2D Vector (Double, Double)
v) Int
i = (Double -> Double -> P2DU) -> (Double, Double) -> P2DU
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Double -> Double -> P2DU
Point2DU ((Double, Double) -> P2DU) -> Box (Double, Double) -> Box P2DU
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Vector (Double, Double) -> Int -> Box (Double, Double)
forall (v :: * -> *) a. Vector v a => v a -> Int -> Box a
VG.basicUnsafeIndexM Vector (Double, Double)
v Int
i
basicUnsafeCopy :: forall s. Mutable Vector s P2DU -> Vector P2DU -> ST s ()
basicUnsafeCopy (MV_P2D MVector s (Double, Double)
mv) (V_P2D Vector (Double, Double)
v) = Mutable Vector s (Double, Double)
-> Vector (Double, Double) -> ST s ()
forall s.
Mutable Vector s (Double, Double)
-> Vector (Double, Double) -> ST s ()
forall (v :: * -> *) a s.
Vector v a =>
Mutable v s a -> v a -> ST s ()
VG.basicUnsafeCopy Mutable Vector s (Double, Double)
MVector s (Double, Double)
mv Vector (Double, Double)
v
instance VU.Unbox P2DU
instance PointND P2DU where
dimProps :: (Bool, Bool)
dimProps = (Bool
False, Bool
False)
components :: P2DU -> (Double, Double, Maybe Double, Maybe Double)
components (Point2DU Double
x Double
y) = (Double
x, Double
y, Maybe Double
forall a. Maybe a
Nothing, Maybe Double
forall a. Maybe a
Nothing)
fromComponents :: (Double, Double, Maybe Double, Maybe Double) -> P2DU
fromComponents (Double
x, Double
y, Maybe Double
Nothing, Maybe Double
Nothing) = Double -> Double -> P2DU
Point2DU Double
x Double
y
fromComponents (Double, Double, Maybe Double, Maybe Double)
_ = GeometryError -> P2DU
forall a e. Exception e => e -> a
throw (GeometryError -> P2DU) -> GeometryError -> P2DU
forall a b. (a -> b) -> a -> b
$
String -> GeometryError
GeometryError String
"invalid transition from user data type to P2D"
data P3DZU = Point3DZU
{-# UNPACK #-} !Double
{-# UNPACK #-} !Double
{-# UNPACK #-} !Double
deriving (Int -> P3DZU -> ShowS
[P3DZU] -> ShowS
P3DZU -> String
(Int -> P3DZU -> ShowS)
-> (P3DZU -> String) -> ([P3DZU] -> ShowS) -> Show P3DZU
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> P3DZU -> ShowS
showsPrec :: Int -> P3DZU -> ShowS
$cshow :: P3DZU -> String
show :: P3DZU -> String
$cshowList :: [P3DZU] -> ShowS
showList :: [P3DZU] -> ShowS
Show, P3DZU -> P3DZU -> Bool
(P3DZU -> P3DZU -> Bool) -> (P3DZU -> P3DZU -> Bool) -> Eq P3DZU
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: P3DZU -> P3DZU -> Bool
== :: P3DZU -> P3DZU -> Bool
$c/= :: P3DZU -> P3DZU -> Bool
/= :: P3DZU -> P3DZU -> Bool
Eq)
fromP3DZ :: P3DZU -> (Double, Double, Double)
fromP3DZ :: P3DZU -> (Double, Double, Double)
fromP3DZ (Point3DZU Double
x Double
y Double
z) = (Double
x, Double
y, Double
z)
newtype instance VU.MVector s P3DZU =
MV_P3DZ (VU.MVector s (Double, Double, Double))
newtype instance VU.Vector P3DZU =
V_P3DZ (VU.Vector (Double, Double, Double))
instance VGM.MVector VU.MVector P3DZU where
{-# INLINE basicLength #-}
{-# INLINE basicUnsafeSlice #-}
{-# INLINE basicOverlaps #-}
{-# INLINE basicUnsafeNew #-}
{-# INLINE basicInitialize #-}
{-# INLINE basicUnsafeReplicate #-}
{-# INLINE basicUnsafeRead #-}
{-# INLINE basicUnsafeWrite #-}
{-# INLINE basicClear #-}
{-# INLINE basicSet #-}
{-# INLINE basicUnsafeCopy #-}
{-# INLINE basicUnsafeGrow #-}
basicLength :: forall s. MVector s P3DZU -> Int
basicLength (MV_P3DZ MVector s (Double, Double, Double)
v) = MVector s (Double, Double, Double) -> Int
forall s. MVector s (Double, Double, Double) -> Int
forall (v :: * -> * -> *) a s. MVector v a => v s a -> Int
VGM.basicLength MVector s (Double, Double, Double)
v
basicUnsafeNew :: forall s. Int -> ST s (MVector s P3DZU)
basicUnsafeNew Int
n = MVector s (Double, Double, Double) -> MVector s P3DZU
forall s. MVector s (Double, Double, Double) -> MVector s P3DZU
MV_P3DZ (MVector s (Double, Double, Double) -> MVector s P3DZU)
-> ST s (MVector s (Double, Double, Double))
-> ST s (MVector s P3DZU)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> ST s (MVector s (Double, Double, Double))
forall s. Int -> ST s (MVector s (Double, Double, Double))
forall (v :: * -> * -> *) a s. MVector v a => Int -> ST s (v s a)
VGM.basicUnsafeNew Int
n
basicUnsafeSlice :: forall s. Int -> Int -> MVector s P3DZU -> MVector s P3DZU
basicUnsafeSlice Int
i Int
n (MV_P3DZ MVector s (Double, Double, Double)
v) = MVector s (Double, Double, Double) -> MVector s P3DZU
forall s. MVector s (Double, Double, Double) -> MVector s P3DZU
MV_P3DZ (MVector s (Double, Double, Double) -> MVector s P3DZU)
-> MVector s (Double, Double, Double) -> MVector s P3DZU
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> MVector s (Double, Double, Double)
-> MVector s (Double, Double, Double)
forall s.
Int
-> Int
-> MVector s (Double, Double, Double)
-> MVector s (Double, Double, Double)
forall (v :: * -> * -> *) a s.
MVector v a =>
Int -> Int -> v s a -> v s a
VGM.basicUnsafeSlice Int
i Int
n MVector s (Double, Double, Double)
v
basicOverlaps :: forall s. MVector s P3DZU -> MVector s P3DZU -> Bool
basicOverlaps (MV_P3DZ MVector s (Double, Double, Double)
v1) (MV_P3DZ MVector s (Double, Double, Double)
v2) = MVector s (Double, Double, Double)
-> MVector s (Double, Double, Double) -> Bool
forall s.
MVector s (Double, Double, Double)
-> MVector s (Double, Double, Double) -> Bool
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> Bool
VGM.basicOverlaps MVector s (Double, Double, Double)
v1 MVector s (Double, Double, Double)
v2
basicInitialize :: forall s. MVector s P3DZU -> ST s ()
basicInitialize (MV_P3DZ MVector s (Double, Double, Double)
v) = MVector s (Double, Double, Double) -> ST s ()
forall s. MVector s (Double, Double, Double) -> ST s ()
forall (v :: * -> * -> *) a s. MVector v a => v s a -> ST s ()
VGM.basicInitialize MVector s (Double, Double, Double)
v
basicUnsafeReplicate :: forall s. Int -> P3DZU -> ST s (MVector s P3DZU)
basicUnsafeReplicate Int
n P3DZU
p = MVector s (Double, Double, Double) -> MVector s P3DZU
forall s. MVector s (Double, Double, Double) -> MVector s P3DZU
MV_P3DZ (MVector s (Double, Double, Double) -> MVector s P3DZU)
-> ST s (MVector s (Double, Double, Double))
-> ST s (MVector s P3DZU)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int
-> (Double, Double, Double)
-> ST s (MVector s (Double, Double, Double))
forall s.
Int
-> (Double, Double, Double)
-> ST s (MVector s (Double, Double, Double))
forall (v :: * -> * -> *) a s.
MVector v a =>
Int -> a -> ST s (v s a)
VGM.basicUnsafeReplicate Int
n (P3DZU -> (Double, Double, Double)
fromP3DZ P3DZU
p)
basicUnsafeRead :: forall s. MVector s P3DZU -> Int -> ST s P3DZU
basicUnsafeRead (MV_P3DZ MVector s (Double, Double, Double)
v) Int
i = (Double -> Double -> Double -> P3DZU)
-> (Double, Double, Double) -> P3DZU
forall a b c d. (a -> b -> c -> d) -> (a, b, c) -> d
uncurry3 Double -> Double -> Double -> P3DZU
Point3DZU ((Double, Double, Double) -> P3DZU)
-> ST s (Double, Double, Double) -> ST s P3DZU
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MVector s (Double, Double, Double)
-> Int -> ST s (Double, Double, Double)
forall s.
MVector s (Double, Double, Double)
-> Int -> ST s (Double, Double, Double)
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> Int -> ST s a
VGM.basicUnsafeRead MVector s (Double, Double, Double)
v Int
i
basicUnsafeWrite :: forall s. MVector s P3DZU -> Int -> P3DZU -> ST s ()
basicUnsafeWrite (MV_P3DZ MVector s (Double, Double, Double)
v) Int
i P3DZU
p = MVector s (Double, Double, Double)
-> Int -> (Double, Double, Double) -> ST s ()
forall s.
MVector s (Double, Double, Double)
-> Int -> (Double, Double, Double) -> ST s ()
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> Int -> a -> ST s ()
VGM.basicUnsafeWrite MVector s (Double, Double, Double)
v Int
i (P3DZU -> (Double, Double, Double)
fromP3DZ P3DZU
p)
basicClear :: forall s. MVector s P3DZU -> ST s ()
basicClear (MV_P3DZ MVector s (Double, Double, Double)
v) = MVector s (Double, Double, Double) -> ST s ()
forall s. MVector s (Double, Double, Double) -> ST s ()
forall (v :: * -> * -> *) a s. MVector v a => v s a -> ST s ()
VGM.basicClear MVector s (Double, Double, Double)
v
basicSet :: forall s. MVector s P3DZU -> P3DZU -> ST s ()
basicSet (MV_P3DZ MVector s (Double, Double, Double)
v) P3DZU
p = MVector s (Double, Double, Double)
-> (Double, Double, Double) -> ST s ()
forall s.
MVector s (Double, Double, Double)
-> (Double, Double, Double) -> ST s ()
forall (v :: * -> * -> *) a s. MVector v a => v s a -> a -> ST s ()
VGM.basicSet MVector s (Double, Double, Double)
v (P3DZU -> (Double, Double, Double)
fromP3DZ P3DZU
p)
basicUnsafeCopy :: forall s. MVector s P3DZU -> MVector s P3DZU -> ST s ()
basicUnsafeCopy (MV_P3DZ MVector s (Double, Double, Double)
v1) (MV_P3DZ MVector s (Double, Double, Double)
v2) = MVector s (Double, Double, Double)
-> MVector s (Double, Double, Double) -> ST s ()
forall s.
MVector s (Double, Double, Double)
-> MVector s (Double, Double, Double) -> ST s ()
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> ST s ()
VGM.basicUnsafeCopy MVector s (Double, Double, Double)
v1 MVector s (Double, Double, Double)
v2
basicUnsafeMove :: forall s. MVector s P3DZU -> MVector s P3DZU -> ST s ()
basicUnsafeMove (MV_P3DZ MVector s (Double, Double, Double)
v1) (MV_P3DZ MVector s (Double, Double, Double)
v2) = MVector s (Double, Double, Double)
-> MVector s (Double, Double, Double) -> ST s ()
forall s.
MVector s (Double, Double, Double)
-> MVector s (Double, Double, Double) -> ST s ()
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> ST s ()
VGM.basicUnsafeMove MVector s (Double, Double, Double)
v1 MVector s (Double, Double, Double)
v2
basicUnsafeGrow :: forall s. MVector s P3DZU -> Int -> ST s (MVector s P3DZU)
basicUnsafeGrow (MV_P3DZ MVector s (Double, Double, Double)
v) Int
n = MVector s (Double, Double, Double) -> MVector s P3DZU
forall s. MVector s (Double, Double, Double) -> MVector s P3DZU
MV_P3DZ (MVector s (Double, Double, Double) -> MVector s P3DZU)
-> ST s (MVector s (Double, Double, Double))
-> ST s (MVector s P3DZU)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MVector s (Double, Double, Double)
-> Int -> ST s (MVector s (Double, Double, Double))
forall s.
MVector s (Double, Double, Double)
-> Int -> ST s (MVector s (Double, Double, Double))
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> Int -> ST s (v s a)
VGM.basicUnsafeGrow MVector s (Double, Double, Double)
v Int
n
instance VG.Vector VU.Vector P3DZU where
{-# INLINE basicLength #-}
{-# INLINE basicUnsafeFreeze #-}
{-# INLINE basicUnsafeThaw #-}
{-# INLINE basicUnsafeSlice #-}
{-# INLINE basicUnsafeIndexM #-}
basicLength :: Vector P3DZU -> Int
basicLength (V_P3DZ Vector (Double, Double, Double)
v) = Vector (Double, Double, Double) -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
VG.basicLength Vector (Double, Double, Double)
v
basicUnsafeFreeze :: forall s. Mutable Vector s P3DZU -> ST s (Vector P3DZU)
basicUnsafeFreeze (MV_P3DZ MVector s (Double, Double, Double)
v) = Vector (Double, Double, Double) -> Vector P3DZU
V_P3DZ (Vector (Double, Double, Double) -> Vector P3DZU)
-> ST s (Vector (Double, Double, Double)) -> ST s (Vector P3DZU)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Mutable Vector s (Double, Double, Double)
-> ST s (Vector (Double, Double, Double))
forall s.
Mutable Vector s (Double, Double, Double)
-> ST s (Vector (Double, Double, Double))
forall (v :: * -> *) a s. Vector v a => Mutable v s a -> ST s (v a)
VG.basicUnsafeFreeze Mutable Vector s (Double, Double, Double)
MVector s (Double, Double, Double)
v
basicUnsafeThaw :: forall s. Vector P3DZU -> ST s (Mutable Vector s P3DZU)
basicUnsafeThaw (V_P3DZ Vector (Double, Double, Double)
v) = MVector s (Double, Double, Double) -> MVector s P3DZU
forall s. MVector s (Double, Double, Double) -> MVector s P3DZU
MV_P3DZ (MVector s (Double, Double, Double) -> MVector s P3DZU)
-> ST s (MVector s (Double, Double, Double))
-> ST s (MVector s P3DZU)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Vector (Double, Double, Double)
-> ST s (Mutable Vector s (Double, Double, Double))
forall s.
Vector (Double, Double, Double)
-> ST s (Mutable Vector s (Double, Double, Double))
forall (v :: * -> *) a s. Vector v a => v a -> ST s (Mutable v s a)
VG.basicUnsafeThaw Vector (Double, Double, Double)
v
basicUnsafeSlice :: Int -> Int -> Vector P3DZU -> Vector P3DZU
basicUnsafeSlice Int
i Int
n (V_P3DZ Vector (Double, Double, Double)
v) = Vector (Double, Double, Double) -> Vector P3DZU
V_P3DZ (Vector (Double, Double, Double) -> Vector P3DZU)
-> Vector (Double, Double, Double) -> Vector P3DZU
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> Vector (Double, Double, Double)
-> Vector (Double, Double, Double)
forall (v :: * -> *) a. Vector v a => Int -> Int -> v a -> v a
VG.basicUnsafeSlice Int
i Int
n Vector (Double, Double, Double)
v
basicUnsafeIndexM :: Vector P3DZU -> Int -> Box P3DZU
basicUnsafeIndexM (V_P3DZ Vector (Double, Double, Double)
v) Int
i = (Double -> Double -> Double -> P3DZU)
-> (Double, Double, Double) -> P3DZU
forall a b c d. (a -> b -> c -> d) -> (a, b, c) -> d
uncurry3 Double -> Double -> Double -> P3DZU
Point3DZU ((Double, Double, Double) -> P3DZU)
-> Box (Double, Double, Double) -> Box P3DZU
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Vector (Double, Double, Double)
-> Int -> Box (Double, Double, Double)
forall (v :: * -> *) a. Vector v a => v a -> Int -> Box a
VG.basicUnsafeIndexM Vector (Double, Double, Double)
v Int
i
basicUnsafeCopy :: forall s. Mutable Vector s P3DZU -> Vector P3DZU -> ST s ()
basicUnsafeCopy (MV_P3DZ MVector s (Double, Double, Double)
mv) (V_P3DZ Vector (Double, Double, Double)
v) = Mutable Vector s (Double, Double, Double)
-> Vector (Double, Double, Double) -> ST s ()
forall s.
Mutable Vector s (Double, Double, Double)
-> Vector (Double, Double, Double) -> ST s ()
forall (v :: * -> *) a s.
Vector v a =>
Mutable v s a -> v a -> ST s ()
VG.basicUnsafeCopy Mutable Vector s (Double, Double, Double)
MVector s (Double, Double, Double)
mv Vector (Double, Double, Double)
v
instance VU.Unbox P3DZU
instance PointND P3DZU where
dimProps :: (Bool, Bool)
dimProps = (Bool
False, Bool
True)
components :: P3DZU -> (Double, Double, Maybe Double, Maybe Double)
components (Point3DZU Double
x Double
y Double
z) = (Double
x, Double
y, Double -> Maybe Double
forall a. a -> Maybe a
Just Double
z, Maybe Double
forall a. Maybe a
Nothing)
fromComponents :: (Double, Double, Maybe Double, Maybe Double) -> P3DZU
fromComponents (Double
x, Double
y, Just Double
z, Maybe Double
Nothing) = Double -> Double -> Double -> P3DZU
Point3DZU Double
x Double
y Double
z
fromComponents (Double, Double, Maybe Double, Maybe Double)
_ = GeometryError -> P3DZU
forall a e. Exception e => e -> a
throw (GeometryError -> P3DZU) -> GeometryError -> P3DZU
forall a b. (a -> b) -> a -> b
$
String -> GeometryError
GeometryError String
"invalid transition from user data type to P3DZ"
data P3DMU = Point3DMU
{-# UNPACK #-} !Double
{-# UNPACK #-} !Double
{-# UNPACK #-} !Double
deriving (Int -> P3DMU -> ShowS
[P3DMU] -> ShowS
P3DMU -> String
(Int -> P3DMU -> ShowS)
-> (P3DMU -> String) -> ([P3DMU] -> ShowS) -> Show P3DMU
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> P3DMU -> ShowS
showsPrec :: Int -> P3DMU -> ShowS
$cshow :: P3DMU -> String
show :: P3DMU -> String
$cshowList :: [P3DMU] -> ShowS
showList :: [P3DMU] -> ShowS
Show, P3DMU -> P3DMU -> Bool
(P3DMU -> P3DMU -> Bool) -> (P3DMU -> P3DMU -> Bool) -> Eq P3DMU
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: P3DMU -> P3DMU -> Bool
== :: P3DMU -> P3DMU -> Bool
$c/= :: P3DMU -> P3DMU -> Bool
/= :: P3DMU -> P3DMU -> Bool
Eq)
fromP3DM :: P3DMU -> (Double, Double, Double)
fromP3DM :: P3DMU -> (Double, Double, Double)
fromP3DM (Point3DMU Double
x Double
y Double
z) = (Double
x, Double
y, Double
z)
newtype instance VU.MVector s P3DMU =
MV_P3DM (VU.MVector s (Double, Double, Double))
newtype instance VU.Vector P3DMU =
V_P3DM (VU.Vector (Double, Double, Double))
instance VGM.MVector VU.MVector P3DMU where
{-# INLINE basicLength #-}
{-# INLINE basicUnsafeSlice #-}
{-# INLINE basicOverlaps #-}
{-# INLINE basicUnsafeNew #-}
{-# INLINE basicInitialize #-}
{-# INLINE basicUnsafeReplicate #-}
{-# INLINE basicUnsafeRead #-}
{-# INLINE basicUnsafeWrite #-}
{-# INLINE basicClear #-}
{-# INLINE basicSet #-}
{-# INLINE basicUnsafeCopy #-}
{-# INLINE basicUnsafeGrow #-}
basicLength :: forall s. MVector s P3DMU -> Int
basicLength (MV_P3DM MVector s (Double, Double, Double)
v) = MVector s (Double, Double, Double) -> Int
forall s. MVector s (Double, Double, Double) -> Int
forall (v :: * -> * -> *) a s. MVector v a => v s a -> Int
VGM.basicLength MVector s (Double, Double, Double)
v
basicUnsafeNew :: forall s. Int -> ST s (MVector s P3DMU)
basicUnsafeNew Int
n = MVector s (Double, Double, Double) -> MVector s P3DMU
forall s. MVector s (Double, Double, Double) -> MVector s P3DMU
MV_P3DM (MVector s (Double, Double, Double) -> MVector s P3DMU)
-> ST s (MVector s (Double, Double, Double))
-> ST s (MVector s P3DMU)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> ST s (MVector s (Double, Double, Double))
forall s. Int -> ST s (MVector s (Double, Double, Double))
forall (v :: * -> * -> *) a s. MVector v a => Int -> ST s (v s a)
VGM.basicUnsafeNew Int
n
basicUnsafeSlice :: forall s. Int -> Int -> MVector s P3DMU -> MVector s P3DMU
basicUnsafeSlice Int
i Int
n (MV_P3DM MVector s (Double, Double, Double)
v) = MVector s (Double, Double, Double) -> MVector s P3DMU
forall s. MVector s (Double, Double, Double) -> MVector s P3DMU
MV_P3DM (MVector s (Double, Double, Double) -> MVector s P3DMU)
-> MVector s (Double, Double, Double) -> MVector s P3DMU
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> MVector s (Double, Double, Double)
-> MVector s (Double, Double, Double)
forall s.
Int
-> Int
-> MVector s (Double, Double, Double)
-> MVector s (Double, Double, Double)
forall (v :: * -> * -> *) a s.
MVector v a =>
Int -> Int -> v s a -> v s a
VGM.basicUnsafeSlice Int
i Int
n MVector s (Double, Double, Double)
v
basicOverlaps :: forall s. MVector s P3DMU -> MVector s P3DMU -> Bool
basicOverlaps (MV_P3DM MVector s (Double, Double, Double)
v1) (MV_P3DM MVector s (Double, Double, Double)
v2) = MVector s (Double, Double, Double)
-> MVector s (Double, Double, Double) -> Bool
forall s.
MVector s (Double, Double, Double)
-> MVector s (Double, Double, Double) -> Bool
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> Bool
VGM.basicOverlaps MVector s (Double, Double, Double)
v1 MVector s (Double, Double, Double)
v2
basicInitialize :: forall s. MVector s P3DMU -> ST s ()
basicInitialize (MV_P3DM MVector s (Double, Double, Double)
v) = MVector s (Double, Double, Double) -> ST s ()
forall s. MVector s (Double, Double, Double) -> ST s ()
forall (v :: * -> * -> *) a s. MVector v a => v s a -> ST s ()
VGM.basicInitialize MVector s (Double, Double, Double)
v
basicUnsafeReplicate :: forall s. Int -> P3DMU -> ST s (MVector s P3DMU)
basicUnsafeReplicate Int
n P3DMU
p = MVector s (Double, Double, Double) -> MVector s P3DMU
forall s. MVector s (Double, Double, Double) -> MVector s P3DMU
MV_P3DM (MVector s (Double, Double, Double) -> MVector s P3DMU)
-> ST s (MVector s (Double, Double, Double))
-> ST s (MVector s P3DMU)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int
-> (Double, Double, Double)
-> ST s (MVector s (Double, Double, Double))
forall s.
Int
-> (Double, Double, Double)
-> ST s (MVector s (Double, Double, Double))
forall (v :: * -> * -> *) a s.
MVector v a =>
Int -> a -> ST s (v s a)
VGM.basicUnsafeReplicate Int
n (P3DMU -> (Double, Double, Double)
fromP3DM P3DMU
p)
basicUnsafeRead :: forall s. MVector s P3DMU -> Int -> ST s P3DMU
basicUnsafeRead (MV_P3DM MVector s (Double, Double, Double)
v) Int
i = (Double -> Double -> Double -> P3DMU)
-> (Double, Double, Double) -> P3DMU
forall a b c d. (a -> b -> c -> d) -> (a, b, c) -> d
uncurry3 Double -> Double -> Double -> P3DMU
Point3DMU ((Double, Double, Double) -> P3DMU)
-> ST s (Double, Double, Double) -> ST s P3DMU
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MVector s (Double, Double, Double)
-> Int -> ST s (Double, Double, Double)
forall s.
MVector s (Double, Double, Double)
-> Int -> ST s (Double, Double, Double)
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> Int -> ST s a
VGM.basicUnsafeRead MVector s (Double, Double, Double)
v Int
i
basicUnsafeWrite :: forall s. MVector s P3DMU -> Int -> P3DMU -> ST s ()
basicUnsafeWrite (MV_P3DM MVector s (Double, Double, Double)
v) Int
i P3DMU
p = MVector s (Double, Double, Double)
-> Int -> (Double, Double, Double) -> ST s ()
forall s.
MVector s (Double, Double, Double)
-> Int -> (Double, Double, Double) -> ST s ()
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> Int -> a -> ST s ()
VGM.basicUnsafeWrite MVector s (Double, Double, Double)
v Int
i (P3DMU -> (Double, Double, Double)
fromP3DM P3DMU
p)
basicClear :: forall s. MVector s P3DMU -> ST s ()
basicClear (MV_P3DM MVector s (Double, Double, Double)
v) = MVector s (Double, Double, Double) -> ST s ()
forall s. MVector s (Double, Double, Double) -> ST s ()
forall (v :: * -> * -> *) a s. MVector v a => v s a -> ST s ()
VGM.basicClear MVector s (Double, Double, Double)
v
basicSet :: forall s. MVector s P3DMU -> P3DMU -> ST s ()
basicSet (MV_P3DM MVector s (Double, Double, Double)
v) P3DMU
p = MVector s (Double, Double, Double)
-> (Double, Double, Double) -> ST s ()
forall s.
MVector s (Double, Double, Double)
-> (Double, Double, Double) -> ST s ()
forall (v :: * -> * -> *) a s. MVector v a => v s a -> a -> ST s ()
VGM.basicSet MVector s (Double, Double, Double)
v (P3DMU -> (Double, Double, Double)
fromP3DM P3DMU
p)
basicUnsafeCopy :: forall s. MVector s P3DMU -> MVector s P3DMU -> ST s ()
basicUnsafeCopy (MV_P3DM MVector s (Double, Double, Double)
v1) (MV_P3DM MVector s (Double, Double, Double)
v2) = MVector s (Double, Double, Double)
-> MVector s (Double, Double, Double) -> ST s ()
forall s.
MVector s (Double, Double, Double)
-> MVector s (Double, Double, Double) -> ST s ()
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> ST s ()
VGM.basicUnsafeCopy MVector s (Double, Double, Double)
v1 MVector s (Double, Double, Double)
v2
basicUnsafeMove :: forall s. MVector s P3DMU -> MVector s P3DMU -> ST s ()
basicUnsafeMove (MV_P3DM MVector s (Double, Double, Double)
v1) (MV_P3DM MVector s (Double, Double, Double)
v2) = MVector s (Double, Double, Double)
-> MVector s (Double, Double, Double) -> ST s ()
forall s.
MVector s (Double, Double, Double)
-> MVector s (Double, Double, Double) -> ST s ()
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> ST s ()
VGM.basicUnsafeMove MVector s (Double, Double, Double)
v1 MVector s (Double, Double, Double)
v2
basicUnsafeGrow :: forall s. MVector s P3DMU -> Int -> ST s (MVector s P3DMU)
basicUnsafeGrow (MV_P3DM MVector s (Double, Double, Double)
v) Int
n = MVector s (Double, Double, Double) -> MVector s P3DMU
forall s. MVector s (Double, Double, Double) -> MVector s P3DMU
MV_P3DM (MVector s (Double, Double, Double) -> MVector s P3DMU)
-> ST s (MVector s (Double, Double, Double))
-> ST s (MVector s P3DMU)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MVector s (Double, Double, Double)
-> Int -> ST s (MVector s (Double, Double, Double))
forall s.
MVector s (Double, Double, Double)
-> Int -> ST s (MVector s (Double, Double, Double))
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> Int -> ST s (v s a)
VGM.basicUnsafeGrow MVector s (Double, Double, Double)
v Int
n
instance VG.Vector VU.Vector P3DMU where
{-# INLINE basicLength #-}
{-# INLINE basicUnsafeFreeze #-}
{-# INLINE basicUnsafeThaw #-}
{-# INLINE basicUnsafeSlice #-}
{-# INLINE basicUnsafeIndexM #-}
basicLength :: Vector P3DMU -> Int
basicLength (V_P3DM Vector (Double, Double, Double)
v) = Vector (Double, Double, Double) -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
VG.basicLength Vector (Double, Double, Double)
v
basicUnsafeFreeze :: forall s. Mutable Vector s P3DMU -> ST s (Vector P3DMU)
basicUnsafeFreeze (MV_P3DM MVector s (Double, Double, Double)
v) = Vector (Double, Double, Double) -> Vector P3DMU
V_P3DM (Vector (Double, Double, Double) -> Vector P3DMU)
-> ST s (Vector (Double, Double, Double)) -> ST s (Vector P3DMU)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Mutable Vector s (Double, Double, Double)
-> ST s (Vector (Double, Double, Double))
forall s.
Mutable Vector s (Double, Double, Double)
-> ST s (Vector (Double, Double, Double))
forall (v :: * -> *) a s. Vector v a => Mutable v s a -> ST s (v a)
VG.basicUnsafeFreeze Mutable Vector s (Double, Double, Double)
MVector s (Double, Double, Double)
v
basicUnsafeThaw :: forall s. Vector P3DMU -> ST s (Mutable Vector s P3DMU)
basicUnsafeThaw (V_P3DM Vector (Double, Double, Double)
v) = MVector s (Double, Double, Double) -> MVector s P3DMU
forall s. MVector s (Double, Double, Double) -> MVector s P3DMU
MV_P3DM (MVector s (Double, Double, Double) -> MVector s P3DMU)
-> ST s (MVector s (Double, Double, Double))
-> ST s (MVector s P3DMU)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Vector (Double, Double, Double)
-> ST s (Mutable Vector s (Double, Double, Double))
forall s.
Vector (Double, Double, Double)
-> ST s (Mutable Vector s (Double, Double, Double))
forall (v :: * -> *) a s. Vector v a => v a -> ST s (Mutable v s a)
VG.basicUnsafeThaw Vector (Double, Double, Double)
v
basicUnsafeSlice :: Int -> Int -> Vector P3DMU -> Vector P3DMU
basicUnsafeSlice Int
i Int
n (V_P3DM Vector (Double, Double, Double)
v) = Vector (Double, Double, Double) -> Vector P3DMU
V_P3DM (Vector (Double, Double, Double) -> Vector P3DMU)
-> Vector (Double, Double, Double) -> Vector P3DMU
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> Vector (Double, Double, Double)
-> Vector (Double, Double, Double)
forall (v :: * -> *) a. Vector v a => Int -> Int -> v a -> v a
VG.basicUnsafeSlice Int
i Int
n Vector (Double, Double, Double)
v
basicUnsafeIndexM :: Vector P3DMU -> Int -> Box P3DMU
basicUnsafeIndexM (V_P3DM Vector (Double, Double, Double)
v) Int
i = (Double -> Double -> Double -> P3DMU)
-> (Double, Double, Double) -> P3DMU
forall a b c d. (a -> b -> c -> d) -> (a, b, c) -> d
uncurry3 Double -> Double -> Double -> P3DMU
Point3DMU ((Double, Double, Double) -> P3DMU)
-> Box (Double, Double, Double) -> Box P3DMU
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Vector (Double, Double, Double)
-> Int -> Box (Double, Double, Double)
forall (v :: * -> *) a. Vector v a => v a -> Int -> Box a
VG.basicUnsafeIndexM Vector (Double, Double, Double)
v Int
i
basicUnsafeCopy :: forall s. Mutable Vector s P3DMU -> Vector P3DMU -> ST s ()
basicUnsafeCopy (MV_P3DM MVector s (Double, Double, Double)
mv) (V_P3DM Vector (Double, Double, Double)
v) = Mutable Vector s (Double, Double, Double)
-> Vector (Double, Double, Double) -> ST s ()
forall s.
Mutable Vector s (Double, Double, Double)
-> Vector (Double, Double, Double) -> ST s ()
forall (v :: * -> *) a s.
Vector v a =>
Mutable v s a -> v a -> ST s ()
VG.basicUnsafeCopy Mutable Vector s (Double, Double, Double)
MVector s (Double, Double, Double)
mv Vector (Double, Double, Double)
v
instance VU.Unbox P3DMU
instance PointND P3DMU where
dimProps :: (Bool, Bool)
dimProps = (Bool
True, Bool
False)
components :: P3DMU -> (Double, Double, Maybe Double, Maybe Double)
components (Point3DMU Double
x Double
y Double
m) = (Double
x, Double
y, Double -> Maybe Double
forall a. a -> Maybe a
Just Double
m, Maybe Double
forall a. Maybe a
Nothing)
fromComponents :: (Double, Double, Maybe Double, Maybe Double) -> P3DMU
fromComponents (Double
x, Double
y, Just Double
m, Maybe Double
Nothing) = Double -> Double -> Double -> P3DMU
Point3DMU Double
x Double
y Double
m
fromComponents (Double, Double, Maybe Double, Maybe Double)
_ = GeometryError -> P3DMU
forall a e. Exception e => e -> a
throw (GeometryError -> P3DMU) -> GeometryError -> P3DMU
forall a b. (a -> b) -> a -> b
$
String -> GeometryError
GeometryError String
"invalid transition from user data type to P3DM"
data P4DU = Point4DU
{-# UNPACK #-} !Double
{-# UNPACK #-} !Double
{-# UNPACK #-} !Double
{-# UNPACK #-} !Double
deriving (Int -> P4DU -> ShowS
[P4DU] -> ShowS
P4DU -> String
(Int -> P4DU -> ShowS)
-> (P4DU -> String) -> ([P4DU] -> ShowS) -> Show P4DU
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> P4DU -> ShowS
showsPrec :: Int -> P4DU -> ShowS
$cshow :: P4DU -> String
show :: P4DU -> String
$cshowList :: [P4DU] -> ShowS
showList :: [P4DU] -> ShowS
Show, P4DU -> P4DU -> Bool
(P4DU -> P4DU -> Bool) -> (P4DU -> P4DU -> Bool) -> Eq P4DU
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: P4DU -> P4DU -> Bool
== :: P4DU -> P4DU -> Bool
$c/= :: P4DU -> P4DU -> Bool
/= :: P4DU -> P4DU -> Bool
Eq)
fromP4D :: P4DU -> (Double, Double, Double, Double)
fromP4D :: P4DU -> (Double, Double, Double, Double)
fromP4D (Point4DU Double
x Double
y Double
z Double
m) = (Double
x, Double
y, Double
z, Double
m)
newtype instance VU.MVector s P4DU =
MV_P4D (VU.MVector s (Double, Double, Double, Double))
newtype instance VU.Vector P4DU =
V_P4D (VU.Vector (Double, Double, Double, Double))
instance VGM.MVector VU.MVector P4DU where
{-# INLINE basicLength #-}
{-# INLINE basicUnsafeSlice #-}
{-# INLINE basicOverlaps #-}
{-# INLINE basicUnsafeNew #-}
{-# INLINE basicInitialize #-}
{-# INLINE basicUnsafeReplicate #-}
{-# INLINE basicUnsafeRead #-}
{-# INLINE basicUnsafeWrite #-}
{-# INLINE basicClear #-}
{-# INLINE basicSet #-}
{-# INLINE basicUnsafeCopy #-}
{-# INLINE basicUnsafeGrow #-}
basicLength :: forall s. MVector s P4DU -> Int
basicLength (MV_P4D MVector s (Double, Double, Double, Double)
v) = MVector s (Double, Double, Double, Double) -> Int
forall s. MVector s (Double, Double, Double, Double) -> Int
forall (v :: * -> * -> *) a s. MVector v a => v s a -> Int
VGM.basicLength MVector s (Double, Double, Double, Double)
v
basicUnsafeNew :: forall s. Int -> ST s (MVector s P4DU)
basicUnsafeNew Int
n = MVector s (Double, Double, Double, Double) -> MVector s P4DU
forall s.
MVector s (Double, Double, Double, Double) -> MVector s P4DU
MV_P4D (MVector s (Double, Double, Double, Double) -> MVector s P4DU)
-> ST s (MVector s (Double, Double, Double, Double))
-> ST s (MVector s P4DU)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> ST s (MVector s (Double, Double, Double, Double))
forall s. Int -> ST s (MVector s (Double, Double, Double, Double))
forall (v :: * -> * -> *) a s. MVector v a => Int -> ST s (v s a)
VGM.basicUnsafeNew Int
n
basicUnsafeSlice :: forall s. Int -> Int -> MVector s P4DU -> MVector s P4DU
basicUnsafeSlice Int
i Int
n (MV_P4D MVector s (Double, Double, Double, Double)
v) = MVector s (Double, Double, Double, Double) -> MVector s P4DU
forall s.
MVector s (Double, Double, Double, Double) -> MVector s P4DU
MV_P4D (MVector s (Double, Double, Double, Double) -> MVector s P4DU)
-> MVector s (Double, Double, Double, Double) -> MVector s P4DU
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> MVector s (Double, Double, Double, Double)
-> MVector s (Double, Double, Double, Double)
forall s.
Int
-> Int
-> MVector s (Double, Double, Double, Double)
-> MVector s (Double, Double, Double, Double)
forall (v :: * -> * -> *) a s.
MVector v a =>
Int -> Int -> v s a -> v s a
VGM.basicUnsafeSlice Int
i Int
n MVector s (Double, Double, Double, Double)
v
basicOverlaps :: forall s. MVector s P4DU -> MVector s P4DU -> Bool
basicOverlaps (MV_P4D MVector s (Double, Double, Double, Double)
v1) (MV_P4D MVector s (Double, Double, Double, Double)
v2) = MVector s (Double, Double, Double, Double)
-> MVector s (Double, Double, Double, Double) -> Bool
forall s.
MVector s (Double, Double, Double, Double)
-> MVector s (Double, Double, Double, Double) -> Bool
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> Bool
VGM.basicOverlaps MVector s (Double, Double, Double, Double)
v1 MVector s (Double, Double, Double, Double)
v2
basicInitialize :: forall s. MVector s P4DU -> ST s ()
basicInitialize (MV_P4D MVector s (Double, Double, Double, Double)
v) = MVector s (Double, Double, Double, Double) -> ST s ()
forall s. MVector s (Double, Double, Double, Double) -> ST s ()
forall (v :: * -> * -> *) a s. MVector v a => v s a -> ST s ()
VGM.basicInitialize MVector s (Double, Double, Double, Double)
v
basicUnsafeReplicate :: forall s. Int -> P4DU -> ST s (MVector s P4DU)
basicUnsafeReplicate Int
n P4DU
p = MVector s (Double, Double, Double, Double) -> MVector s P4DU
forall s.
MVector s (Double, Double, Double, Double) -> MVector s P4DU
MV_P4D (MVector s (Double, Double, Double, Double) -> MVector s P4DU)
-> ST s (MVector s (Double, Double, Double, Double))
-> ST s (MVector s P4DU)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int
-> (Double, Double, Double, Double)
-> ST s (MVector s (Double, Double, Double, Double))
forall s.
Int
-> (Double, Double, Double, Double)
-> ST s (MVector s (Double, Double, Double, Double))
forall (v :: * -> * -> *) a s.
MVector v a =>
Int -> a -> ST s (v s a)
VGM.basicUnsafeReplicate Int
n (P4DU -> (Double, Double, Double, Double)
fromP4D P4DU
p)
basicUnsafeRead :: forall s. MVector s P4DU -> Int -> ST s P4DU
basicUnsafeRead (MV_P4D MVector s (Double, Double, Double, Double)
v) Int
i = (Double -> Double -> Double -> Double -> P4DU)
-> (Double, Double, Double, Double) -> P4DU
forall a b c d e. (a -> b -> c -> d -> e) -> (a, b, c, d) -> e
uncurry4 Double -> Double -> Double -> Double -> P4DU
Point4DU ((Double, Double, Double, Double) -> P4DU)
-> ST s (Double, Double, Double, Double) -> ST s P4DU
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MVector s (Double, Double, Double, Double)
-> Int -> ST s (Double, Double, Double, Double)
forall s.
MVector s (Double, Double, Double, Double)
-> Int -> ST s (Double, Double, Double, Double)
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> Int -> ST s a
VGM.basicUnsafeRead MVector s (Double, Double, Double, Double)
v Int
i
basicUnsafeWrite :: forall s. MVector s P4DU -> Int -> P4DU -> ST s ()
basicUnsafeWrite (MV_P4D MVector s (Double, Double, Double, Double)
v) Int
i P4DU
p = MVector s (Double, Double, Double, Double)
-> Int -> (Double, Double, Double, Double) -> ST s ()
forall s.
MVector s (Double, Double, Double, Double)
-> Int -> (Double, Double, Double, Double) -> ST s ()
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> Int -> a -> ST s ()
VGM.basicUnsafeWrite MVector s (Double, Double, Double, Double)
v Int
i (P4DU -> (Double, Double, Double, Double)
fromP4D P4DU
p)
basicClear :: forall s. MVector s P4DU -> ST s ()
basicClear (MV_P4D MVector s (Double, Double, Double, Double)
v) = MVector s (Double, Double, Double, Double) -> ST s ()
forall s. MVector s (Double, Double, Double, Double) -> ST s ()
forall (v :: * -> * -> *) a s. MVector v a => v s a -> ST s ()
VGM.basicClear MVector s (Double, Double, Double, Double)
v
basicSet :: forall s. MVector s P4DU -> P4DU -> ST s ()
basicSet (MV_P4D MVector s (Double, Double, Double, Double)
v) P4DU
p = MVector s (Double, Double, Double, Double)
-> (Double, Double, Double, Double) -> ST s ()
forall s.
MVector s (Double, Double, Double, Double)
-> (Double, Double, Double, Double) -> ST s ()
forall (v :: * -> * -> *) a s. MVector v a => v s a -> a -> ST s ()
VGM.basicSet MVector s (Double, Double, Double, Double)
v (P4DU -> (Double, Double, Double, Double)
fromP4D P4DU
p)
basicUnsafeCopy :: forall s. MVector s P4DU -> MVector s P4DU -> ST s ()
basicUnsafeCopy (MV_P4D MVector s (Double, Double, Double, Double)
v1) (MV_P4D MVector s (Double, Double, Double, Double)
v2) = MVector s (Double, Double, Double, Double)
-> MVector s (Double, Double, Double, Double) -> ST s ()
forall s.
MVector s (Double, Double, Double, Double)
-> MVector s (Double, Double, Double, Double) -> ST s ()
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> ST s ()
VGM.basicUnsafeCopy MVector s (Double, Double, Double, Double)
v1 MVector s (Double, Double, Double, Double)
v2
basicUnsafeMove :: forall s. MVector s P4DU -> MVector s P4DU -> ST s ()
basicUnsafeMove (MV_P4D MVector s (Double, Double, Double, Double)
v1) (MV_P4D MVector s (Double, Double, Double, Double)
v2) = MVector s (Double, Double, Double, Double)
-> MVector s (Double, Double, Double, Double) -> ST s ()
forall s.
MVector s (Double, Double, Double, Double)
-> MVector s (Double, Double, Double, Double) -> ST s ()
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> ST s ()
VGM.basicUnsafeMove MVector s (Double, Double, Double, Double)
v1 MVector s (Double, Double, Double, Double)
v2
basicUnsafeGrow :: forall s. MVector s P4DU -> Int -> ST s (MVector s P4DU)
basicUnsafeGrow (MV_P4D MVector s (Double, Double, Double, Double)
v) Int
n = MVector s (Double, Double, Double, Double) -> MVector s P4DU
forall s.
MVector s (Double, Double, Double, Double) -> MVector s P4DU
MV_P4D (MVector s (Double, Double, Double, Double) -> MVector s P4DU)
-> ST s (MVector s (Double, Double, Double, Double))
-> ST s (MVector s P4DU)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MVector s (Double, Double, Double, Double)
-> Int -> ST s (MVector s (Double, Double, Double, Double))
forall s.
MVector s (Double, Double, Double, Double)
-> Int -> ST s (MVector s (Double, Double, Double, Double))
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> Int -> ST s (v s a)
VGM.basicUnsafeGrow MVector s (Double, Double, Double, Double)
v Int
n
instance VG.Vector VU.Vector P4DU where
{-# INLINE basicLength #-}
{-# INLINE basicUnsafeFreeze #-}
{-# INLINE basicUnsafeThaw #-}
{-# INLINE basicUnsafeSlice #-}
{-# INLINE basicUnsafeIndexM #-}
basicLength :: Vector P4DU -> Int
basicLength (V_P4D Vector (Double, Double, Double, Double)
v) = Vector (Double, Double, Double, Double) -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
VG.basicLength Vector (Double, Double, Double, Double)
v
basicUnsafeFreeze :: forall s. Mutable Vector s P4DU -> ST s (Vector P4DU)
basicUnsafeFreeze (MV_P4D MVector s (Double, Double, Double, Double)
v) = Vector (Double, Double, Double, Double) -> Vector P4DU
V_P4D (Vector (Double, Double, Double, Double) -> Vector P4DU)
-> ST s (Vector (Double, Double, Double, Double))
-> ST s (Vector P4DU)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Mutable Vector s (Double, Double, Double, Double)
-> ST s (Vector (Double, Double, Double, Double))
forall s.
Mutable Vector s (Double, Double, Double, Double)
-> ST s (Vector (Double, Double, Double, Double))
forall (v :: * -> *) a s. Vector v a => Mutable v s a -> ST s (v a)
VG.basicUnsafeFreeze Mutable Vector s (Double, Double, Double, Double)
MVector s (Double, Double, Double, Double)
v
basicUnsafeThaw :: forall s. Vector P4DU -> ST s (Mutable Vector s P4DU)
basicUnsafeThaw (V_P4D Vector (Double, Double, Double, Double)
v) = MVector s (Double, Double, Double, Double) -> MVector s P4DU
forall s.
MVector s (Double, Double, Double, Double) -> MVector s P4DU
MV_P4D (MVector s (Double, Double, Double, Double) -> MVector s P4DU)
-> ST s (MVector s (Double, Double, Double, Double))
-> ST s (MVector s P4DU)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Vector (Double, Double, Double, Double)
-> ST s (Mutable Vector s (Double, Double, Double, Double))
forall s.
Vector (Double, Double, Double, Double)
-> ST s (Mutable Vector s (Double, Double, Double, Double))
forall (v :: * -> *) a s. Vector v a => v a -> ST s (Mutable v s a)
VG.basicUnsafeThaw Vector (Double, Double, Double, Double)
v
basicUnsafeSlice :: Int -> Int -> Vector P4DU -> Vector P4DU
basicUnsafeSlice Int
i Int
n (V_P4D Vector (Double, Double, Double, Double)
v) = Vector (Double, Double, Double, Double) -> Vector P4DU
V_P4D (Vector (Double, Double, Double, Double) -> Vector P4DU)
-> Vector (Double, Double, Double, Double) -> Vector P4DU
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> Vector (Double, Double, Double, Double)
-> Vector (Double, Double, Double, Double)
forall (v :: * -> *) a. Vector v a => Int -> Int -> v a -> v a
VG.basicUnsafeSlice Int
i Int
n Vector (Double, Double, Double, Double)
v
basicUnsafeIndexM :: Vector P4DU -> Int -> Box P4DU
basicUnsafeIndexM (V_P4D Vector (Double, Double, Double, Double)
v) Int
i = (Double -> Double -> Double -> Double -> P4DU)
-> (Double, Double, Double, Double) -> P4DU
forall a b c d e. (a -> b -> c -> d -> e) -> (a, b, c, d) -> e
uncurry4 Double -> Double -> Double -> Double -> P4DU
Point4DU ((Double, Double, Double, Double) -> P4DU)
-> Box (Double, Double, Double, Double) -> Box P4DU
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Vector (Double, Double, Double, Double)
-> Int -> Box (Double, Double, Double, Double)
forall (v :: * -> *) a. Vector v a => v a -> Int -> Box a
VG.basicUnsafeIndexM Vector (Double, Double, Double, Double)
v Int
i
basicUnsafeCopy :: forall s. Mutable Vector s P4DU -> Vector P4DU -> ST s ()
basicUnsafeCopy (MV_P4D MVector s (Double, Double, Double, Double)
mv) (V_P4D Vector (Double, Double, Double, Double)
v) = Mutable Vector s (Double, Double, Double, Double)
-> Vector (Double, Double, Double, Double) -> ST s ()
forall s.
Mutable Vector s (Double, Double, Double, Double)
-> Vector (Double, Double, Double, Double) -> ST s ()
forall (v :: * -> *) a s.
Vector v a =>
Mutable v s a -> v a -> ST s ()
VG.basicUnsafeCopy Mutable Vector s (Double, Double, Double, Double)
MVector s (Double, Double, Double, Double)
mv Vector (Double, Double, Double, Double)
v
instance VU.Unbox P4DU
instance PointND P4DU where
dimProps :: (Bool, Bool)
dimProps = (Bool
True, Bool
True)
components :: P4DU -> (Double, Double, Maybe Double, Maybe Double)
components (Point4DU Double
x Double
y Double
z Double
m) = (Double
x, Double
y, Double -> Maybe Double
forall a. a -> Maybe a
Just Double
z, Double -> Maybe Double
forall a. a -> Maybe a
Just Double
m)
fromComponents :: (Double, Double, Maybe Double, Maybe Double) -> P4DU
fromComponents (Double
x, Double
y, Just Double
z, Just Double
m) = Double -> Double -> Double -> Double -> P4DU
Point4DU Double
x Double
y Double
z Double
m
fromComponents (Double, Double, Maybe Double, Maybe Double)
_ = GeometryError -> P4DU
forall a e. Exception e => e -> a
throw (GeometryError -> P4DU) -> GeometryError -> P4DU
forall a b. (a -> b) -> a -> b
$
String -> GeometryError
GeometryError String
"invalid transition from user data type to P4D"
type instance Cast P2DU = P2DU
type instance Cast P3DZU = P3DZU
type instance Cast P3DMU = P3DMU
type instance Cast P4DU = P4DU
instance Castable P2DU where
toPointND :: P2DU -> Cast P2DU
toPointND = P2DU -> Cast P2DU
P2DU -> P2DU
forall a b. Coercible a b => a -> b
coerce
fromPointND :: Cast P2DU -> P2DU
fromPointND = Cast P2DU -> P2DU
P2DU -> P2DU
forall a b. Coercible a b => a -> b
coerce
instance Castable P3DZU where
toPointND :: P3DZU -> Cast P3DZU
toPointND = P3DZU -> Cast P3DZU
P3DZU -> P3DZU
forall a b. Coercible a b => a -> b
coerce
fromPointND :: Cast P3DZU -> P3DZU
fromPointND = Cast P3DZU -> P3DZU
P3DZU -> P3DZU
forall a b. Coercible a b => a -> b
coerce
instance Castable P3DMU where
toPointND :: P3DMU -> Cast P3DMU
toPointND = P3DMU -> Cast P3DMU
P3DMU -> P3DMU
forall a b. Coercible a b => a -> b
coerce
fromPointND :: Cast P3DMU -> P3DMU
fromPointND = Cast P3DMU -> P3DMU
P3DMU -> P3DMU
forall a b. Coercible a b => a -> b
coerce
instance Castable P4DU where
toPointND :: P4DU -> Cast P4DU
toPointND = P4DU -> Cast P4DU
P4DU -> P4DU
forall a b. Coercible a b => a -> b
coerce
fromPointND :: Cast P4DU -> P4DU
fromPointND = Cast P4DU -> P4DU
P4DU -> P4DU
forall a b. Coercible a b => a -> b
coerce