{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}

-- | Specialized and inlined @V2 Word32@.

module Geomancy.UVec4
  ( UVec4
  , uvec4
  , withUVec4
  , pattern WithUVec4
  , fromTuple
  ) where

import Control.DeepSeq (NFData(rnf))
import Data.Word (Word32)
import Data.MonoTraversable (Element, MonoFunctor(..), MonoPointed(..))
import Foreign (Storable(..))
import Foreign.Ptr.Diff (peekDiffOff, pokeDiffOff)

import Geomancy.Elementwise (Elementwise(..))
import Geomancy.Gl.Block (Block(..))

data UVec4 = UVec4
  {-# UNPACK #-} !Word32
  {-# UNPACK #-} !Word32
  {-# UNPACK #-} !Word32
  {-# UNPACK #-} !Word32
  deriving (UVec4 -> UVec4 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UVec4 -> UVec4 -> Bool
$c/= :: UVec4 -> UVec4 -> Bool
== :: UVec4 -> UVec4 -> Bool
$c== :: UVec4 -> UVec4 -> Bool
Eq, Eq UVec4
UVec4 -> UVec4 -> Bool
UVec4 -> UVec4 -> Ordering
UVec4 -> UVec4 -> UVec4
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: UVec4 -> UVec4 -> UVec4
$cmin :: UVec4 -> UVec4 -> UVec4
max :: UVec4 -> UVec4 -> UVec4
$cmax :: UVec4 -> UVec4 -> UVec4
>= :: UVec4 -> UVec4 -> Bool
$c>= :: UVec4 -> UVec4 -> Bool
> :: UVec4 -> UVec4 -> Bool
$c> :: UVec4 -> UVec4 -> Bool
<= :: UVec4 -> UVec4 -> Bool
$c<= :: UVec4 -> UVec4 -> Bool
< :: UVec4 -> UVec4 -> Bool
$c< :: UVec4 -> UVec4 -> Bool
compare :: UVec4 -> UVec4 -> Ordering
$ccompare :: UVec4 -> UVec4 -> Ordering
Ord, Int -> UVec4 -> ShowS
[UVec4] -> ShowS
UVec4 -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UVec4] -> ShowS
$cshowList :: [UVec4] -> ShowS
show :: UVec4 -> String
$cshow :: UVec4 -> String
showsPrec :: Int -> UVec4 -> ShowS
$cshowsPrec :: Int -> UVec4 -> ShowS
Show)

{-# INLINE uvec4 #-}
uvec4 :: Word32 -> Word32 -> Word32 -> Word32 -> UVec4
uvec4 :: Word32 -> Word32 -> Word32 -> Word32 -> UVec4
uvec4 = Word32 -> Word32 -> Word32 -> Word32 -> UVec4
UVec4

{-# INLINE withUVec4 #-}
withUVec4
  :: UVec4
  -> (Word32 -> Word32 -> Word32 -> Word32 -> r)
  -> r
withUVec4 :: forall r. UVec4 -> (Word32 -> Word32 -> Word32 -> Word32 -> r) -> r
withUVec4 (UVec4 Word32
a Word32
b Word32
c Word32
d) Word32 -> Word32 -> Word32 -> Word32 -> r
f = Word32 -> Word32 -> Word32 -> Word32 -> r
f Word32
a Word32
b Word32
c Word32
d

pattern WithUVec4 :: Word32 -> Word32 -> Word32 -> Word32 -> UVec4
pattern $mWithUVec4 :: forall {r}.
UVec4
-> (Word32 -> Word32 -> Word32 -> Word32 -> r) -> ((# #) -> r) -> r
WithUVec4 a b c d <- ((`withUVec4` (,,,)) -> (a, b, c, d))
{-# COMPLETE WithUVec4 #-}

{-# INLINE fromTuple #-}
fromTuple :: (Word32, Word32, Word32, Word32) -> UVec4
fromTuple :: (Word32, Word32, Word32, Word32) -> UVec4
fromTuple (Word32
x, Word32
y, Word32
z, Word32
w) = Word32 -> Word32 -> Word32 -> Word32 -> UVec4
uvec4 Word32
x Word32
y Word32
z Word32
w

instance NFData UVec4 where
  rnf :: UVec4 -> ()
rnf UVec4{} = ()

type instance Element UVec4 = Word32

instance MonoFunctor UVec4 where
  {-# INLINE omap #-}
  omap :: (Element UVec4 -> Element UVec4) -> UVec4 -> UVec4
omap Element UVec4 -> Element UVec4
f UVec4
v =
    forall r. UVec4 -> (Word32 -> Word32 -> Word32 -> Word32 -> r) -> r
withUVec4 UVec4
v \Word32
x Word32
y Word32
z Word32
w ->
      Word32 -> Word32 -> Word32 -> Word32 -> UVec4
uvec4 (Element UVec4 -> Element UVec4
f Word32
x) (Element UVec4 -> Element UVec4
f Word32
y) (Element UVec4 -> Element UVec4
f Word32
z) (Element UVec4 -> Element UVec4
f Word32
w)

instance MonoPointed UVec4 where
  {-# INLINE opoint #-}
  opoint :: Element UVec4 -> UVec4
opoint Element UVec4
x = Word32 -> Word32 -> Word32 -> Word32 -> UVec4
uvec4 Element UVec4
x Element UVec4
x Element UVec4
x Element UVec4
x

instance Elementwise UVec4 where
  {-# INLINE emap2 #-}
  emap2 :: (Element UVec4 -> Element UVec4 -> Element UVec4)
-> UVec4 -> UVec4 -> UVec4
emap2 Element UVec4 -> Element UVec4 -> Element UVec4
f UVec4
p0 UVec4
p1 =
    forall r. UVec4 -> (Word32 -> Word32 -> Word32 -> Word32 -> r) -> r
withUVec4 UVec4
p0 \Word32
x0 Word32
y0 Word32
z0 Word32
w0 ->
    forall r. UVec4 -> (Word32 -> Word32 -> Word32 -> Word32 -> r) -> r
withUVec4 UVec4
p1 \Word32
x1 Word32
y1 Word32
z1 Word32
w1 ->
      Word32 -> Word32 -> Word32 -> Word32 -> UVec4
uvec4
        (Element UVec4 -> Element UVec4 -> Element UVec4
f Word32
x0 Word32
x1)
        (Element UVec4 -> Element UVec4 -> Element UVec4
f Word32
y0 Word32
y1)
        (Element UVec4 -> Element UVec4 -> Element UVec4
f Word32
z0 Word32
z1)
        (Element UVec4 -> Element UVec4 -> Element UVec4
f Word32
w0 Word32
w1)

  {-# INLINE emap3 #-}
  emap3 :: (Element UVec4 -> Element UVec4 -> Element UVec4 -> Element UVec4)
-> UVec4 -> UVec4 -> UVec4 -> UVec4
emap3 Element UVec4 -> Element UVec4 -> Element UVec4 -> Element UVec4
f UVec4
p0 UVec4
p1 UVec4
p2 =
    forall r. UVec4 -> (Word32 -> Word32 -> Word32 -> Word32 -> r) -> r
withUVec4 UVec4
p0 \Word32
x0 Word32
y0 Word32
z0 Word32
w0 ->
    forall r. UVec4 -> (Word32 -> Word32 -> Word32 -> Word32 -> r) -> r
withUVec4 UVec4
p1 \Word32
x1 Word32
y1 Word32
z1 Word32
w1 ->
    forall r. UVec4 -> (Word32 -> Word32 -> Word32 -> Word32 -> r) -> r
withUVec4 UVec4
p2 \Word32
x2 Word32
y2 Word32
z2 Word32
w2 ->
      Word32 -> Word32 -> Word32 -> Word32 -> UVec4
uvec4
        (Element UVec4 -> Element UVec4 -> Element UVec4 -> Element UVec4
f Word32
x0 Word32
x1 Word32
x2)
        (Element UVec4 -> Element UVec4 -> Element UVec4 -> Element UVec4
f Word32
y0 Word32
y1 Word32
y2)
        (Element UVec4 -> Element UVec4 -> Element UVec4 -> Element UVec4
f Word32
z0 Word32
z1 Word32
z2)
        (Element UVec4 -> Element UVec4 -> Element UVec4 -> Element UVec4
f Word32
w0 Word32
w1 Word32
w2)

  {-# INLINE emap4 #-}
  emap4 :: (Element UVec4
 -> Element UVec4
 -> Element UVec4
 -> Element UVec4
 -> Element UVec4)
-> UVec4 -> UVec4 -> UVec4 -> UVec4 -> UVec4
emap4 Element UVec4
-> Element UVec4 -> Element UVec4 -> Element UVec4 -> Element UVec4
f UVec4
p0 UVec4
p1 UVec4
p2 UVec4
p3 =
    forall r. UVec4 -> (Word32 -> Word32 -> Word32 -> Word32 -> r) -> r
withUVec4 UVec4
p0 \Word32
x0 Word32
y0 Word32
z0 Word32
w0 ->
    forall r. UVec4 -> (Word32 -> Word32 -> Word32 -> Word32 -> r) -> r
withUVec4 UVec4
p1 \Word32
x1 Word32
y1 Word32
z1 Word32
w1 ->
    forall r. UVec4 -> (Word32 -> Word32 -> Word32 -> Word32 -> r) -> r
withUVec4 UVec4
p2 \Word32
x2 Word32
y2 Word32
z2 Word32
w2 ->
    forall r. UVec4 -> (Word32 -> Word32 -> Word32 -> Word32 -> r) -> r
withUVec4 UVec4
p3 \Word32
x3 Word32
y3 Word32
z3 Word32
w3 ->
      Word32 -> Word32 -> Word32 -> Word32 -> UVec4
uvec4
        (Element UVec4
-> Element UVec4 -> Element UVec4 -> Element UVec4 -> Element UVec4
f Word32
x0 Word32
x1 Word32
x2 Word32
x3)
        (Element UVec4
-> Element UVec4 -> Element UVec4 -> Element UVec4 -> Element UVec4
f Word32
y0 Word32
y1 Word32
y2 Word32
y3)
        (Element UVec4
-> Element UVec4 -> Element UVec4 -> Element UVec4 -> Element UVec4
f Word32
z0 Word32
z1 Word32
z2 Word32
z3)
        (Element UVec4
-> Element UVec4 -> Element UVec4 -> Element UVec4 -> Element UVec4
f Word32
w0 Word32
w1 Word32
w2 Word32
w3)

  {-# INLINE emap5 #-}
  emap5 :: (Element UVec4
 -> Element UVec4
 -> Element UVec4
 -> Element UVec4
 -> Element UVec4
 -> Element UVec4)
-> UVec4 -> UVec4 -> UVec4 -> UVec4 -> UVec4 -> UVec4
emap5 Element UVec4
-> Element UVec4
-> Element UVec4
-> Element UVec4
-> Element UVec4
-> Element UVec4
f UVec4
p0 UVec4
p1 UVec4
p2 UVec4
p3 UVec4
p4 =
    forall r. UVec4 -> (Word32 -> Word32 -> Word32 -> Word32 -> r) -> r
withUVec4 UVec4
p0 \Word32
x0 Word32
y0 Word32
z0 Word32
w0 ->
    forall r. UVec4 -> (Word32 -> Word32 -> Word32 -> Word32 -> r) -> r
withUVec4 UVec4
p1 \Word32
x1 Word32
y1 Word32
z1 Word32
w1 ->
    forall r. UVec4 -> (Word32 -> Word32 -> Word32 -> Word32 -> r) -> r
withUVec4 UVec4
p2 \Word32
x2 Word32
y2 Word32
z2 Word32
w2 ->
    forall r. UVec4 -> (Word32 -> Word32 -> Word32 -> Word32 -> r) -> r
withUVec4 UVec4
p3 \Word32
x3 Word32
y3 Word32
z3 Word32
w3 ->
    forall r. UVec4 -> (Word32 -> Word32 -> Word32 -> Word32 -> r) -> r
withUVec4 UVec4
p4 \Word32
x4 Word32
y4 Word32
z4 Word32
w4 ->
      Word32 -> Word32 -> Word32 -> Word32 -> UVec4
uvec4
        (Element UVec4
-> Element UVec4
-> Element UVec4
-> Element UVec4
-> Element UVec4
-> Element UVec4
f Word32
x0 Word32
x1 Word32
x2 Word32
x3 Word32
x4)
        (Element UVec4
-> Element UVec4
-> Element UVec4
-> Element UVec4
-> Element UVec4
-> Element UVec4
f Word32
y0 Word32
y1 Word32
y2 Word32
y3 Word32
y4)
        (Element UVec4
-> Element UVec4
-> Element UVec4
-> Element UVec4
-> Element UVec4
-> Element UVec4
f Word32
z0 Word32
z1 Word32
z2 Word32
z3 Word32
z4)
        (Element UVec4
-> Element UVec4
-> Element UVec4
-> Element UVec4
-> Element UVec4
-> Element UVec4
f Word32
w0 Word32
w1 Word32
w2 Word32
w3 Word32
w4)

-- XXX: That's another nasty instance...
instance Num UVec4 where
  {-# INLINE (+) #-}
  UVec4 Word32
l1 Word32
l2 Word32
l3 Word32
l4 + :: UVec4 -> UVec4 -> UVec4
+ UVec4 Word32
r1 Word32
r2 Word32
r3 Word32
r4 =
    Word32 -> Word32 -> Word32 -> Word32 -> UVec4
UVec4
      (Word32
l1 forall a. Num a => a -> a -> a
+ Word32
r1)
      (Word32
l2 forall a. Num a => a -> a -> a
+ Word32
r2)
      (Word32
l3 forall a. Num a => a -> a -> a
+ Word32
r3)
      (Word32
l4 forall a. Num a => a -> a -> a
+ Word32
r4)

  {-# INLINE (-) #-}
  UVec4 Word32
l1 Word32
l2 Word32
l3 Word32
l4 - :: UVec4 -> UVec4 -> UVec4
- UVec4 Word32
r1 Word32
r2 Word32
r3 Word32
r4 =
    Word32 -> Word32 -> Word32 -> Word32 -> UVec4
UVec4
      (Word32
l1 forall a. Num a => a -> a -> a
- Word32
r1)
      (Word32
l2 forall a. Num a => a -> a -> a
- Word32
r2)
      (Word32
l3 forall a. Num a => a -> a -> a
- Word32
r3)
      (Word32
l4 forall a. Num a => a -> a -> a
- Word32
r4)

  {-# INLINE (*) #-}
  UVec4 Word32
l1 Word32
l2 Word32
l3 Word32
l4 * :: UVec4 -> UVec4 -> UVec4
* UVec4 Word32
r1 Word32
r2 Word32
r3 Word32
r4 =
    Word32 -> Word32 -> Word32 -> Word32 -> UVec4
UVec4
      (Word32
l1 forall a. Num a => a -> a -> a
* Word32
r1)
      (Word32
l2 forall a. Num a => a -> a -> a
* Word32
r2)
      (Word32
l3 forall a. Num a => a -> a -> a
* Word32
r3)
      (Word32
l4 forall a. Num a => a -> a -> a
* Word32
r4)

  {-# INLINE abs #-}
  abs :: UVec4 -> UVec4
abs UVec4
x = UVec4
x

  {-# INLINE signum #-}
  signum :: UVec4 -> UVec4
signum UVec4
v4 = forall r. UVec4 -> (Word32 -> Word32 -> Word32 -> Word32 -> r) -> r
withUVec4 UVec4
v4 \Word32
a Word32
b Word32
c Word32
d ->
    Word32 -> Word32 -> Word32 -> Word32 -> UVec4
uvec4 (forall a. Num a => a -> a
signum Word32
a) (forall a. Num a => a -> a
signum Word32
b) (forall a. Num a => a -> a
signum Word32
c) (forall a. Num a => a -> a
signum Word32
d)

  {-# INLINE fromInteger #-}
  fromInteger :: Integer -> UVec4
fromInteger Integer
x = Word32 -> Word32 -> Word32 -> Word32 -> UVec4
UVec4 Word32
x' Word32
x' Word32
x' Word32
x'
    where
      x' :: Word32
x' = forall a. Num a => Integer -> a
fromInteger Integer
x

instance Storable UVec4 where
  {-# INLINE sizeOf #-}
  sizeOf :: UVec4 -> Int
sizeOf UVec4
_ = Int
16

  {-# INLINE alignment #-}
  alignment :: UVec4 -> Int
alignment UVec4
_ = Int
8

  {-# INLINE poke #-}
  poke :: Ptr UVec4 -> UVec4 -> IO ()
poke Ptr UVec4
ptr UVec4
v4 =
    forall r. UVec4 -> (Word32 -> Word32 -> Word32 -> Word32 -> r) -> r
withUVec4 UVec4
v4 \Word32
a Word32
b Word32
c Word32
d -> do
      forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr UVec4
ptr  Int
0 Word32
a
      forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr UVec4
ptr  Int
4 Word32
b
      forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr UVec4
ptr  Int
8 Word32
c
      forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr UVec4
ptr Int
12 Word32
d

  {-# INLINE peek #-}
  peek :: Ptr UVec4 -> IO UVec4
peek Ptr UVec4
ptr = Word32 -> Word32 -> Word32 -> Word32 -> UVec4
uvec4
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr UVec4
ptr  Int
0
    forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr UVec4
ptr  Int
4
    forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr UVec4
ptr  Int
8
    forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr UVec4
ptr Int
12

instance Block UVec4 where
  sizeOfPacked :: forall (proxy :: * -> *). proxy UVec4 -> Int
sizeOfPacked proxy UVec4
_  = Int
16
  alignment140 :: forall (proxy :: * -> *). proxy UVec4 -> Int
alignment140 proxy UVec4
_  = Int
16
  sizeOf140 :: forall (proxy :: * -> *). proxy UVec4 -> Int
sizeOf140 proxy UVec4
_     = Int
16
  alignment430 :: forall (proxy :: * -> *). proxy UVec4 -> Int
alignment430    = forall b (proxy :: * -> *). Block b => proxy b -> Int
alignment140
  sizeOf430 :: forall (proxy :: * -> *). proxy UVec4 -> Int
sizeOf430       = forall b (proxy :: * -> *). Block b => proxy b -> Int
sizeOf140
  isStruct :: forall (proxy :: * -> *). proxy UVec4 -> Bool
isStruct proxy UVec4
_      = Bool
False
  read140 :: forall (m :: * -> *) a.
MonadIO m =>
Ptr a -> Diff a UVec4 -> m UVec4
read140     = forall (m :: * -> *) b a.
(MonadIO m, Storable b) =>
Ptr a -> Diff a b -> m b
peekDiffOff
  write140 :: forall (m :: * -> *) a.
MonadIO m =>
Ptr a -> Diff a UVec4 -> UVec4 -> m ()
write140    = forall (m :: * -> *) b a.
(MonadIO m, Storable b) =>
Ptr a -> Diff a b -> b -> m ()
pokeDiffOff
  read430 :: forall (m :: * -> *) a.
MonadIO m =>
Ptr a -> Diff a UVec4 -> m UVec4
read430     = forall b (m :: * -> *) a.
(Block b, MonadIO m) =>
Ptr a -> Diff a b -> m b
read140
  write430 :: forall (m :: * -> *) a.
MonadIO m =>
Ptr a -> Diff a UVec4 -> UVec4 -> m ()
write430    = forall b (m :: * -> *) a.
(Block b, MonadIO m) =>
Ptr a -> Diff a b -> b -> m ()
write140
  readPacked :: forall (m :: * -> *) a.
MonadIO m =>
Ptr a -> Diff a UVec4 -> m UVec4
readPacked  = forall b (m :: * -> *) a.
(Block b, MonadIO m) =>
Ptr a -> Diff a b -> m b
read140
  writePacked :: forall (m :: * -> *) a.
MonadIO m =>
Ptr a -> Diff a UVec4 -> UVec4 -> m ()
writePacked = forall b (m :: * -> *) a.
(Block b, MonadIO m) =>
Ptr a -> Diff a b -> b -> m ()
write140
  {-# INLINE sizeOfPacked #-}
  {-# INLINE alignment140 #-}
  {-# INLINE sizeOf140 #-}
  {-# INLINE alignment430 #-}
  {-# INLINE sizeOf430 #-}
  {-# INLINE isStruct #-}
  {-# INLINE read140 #-}
  {-# INLINE write140 #-}
  {-# INLINE read430 #-}
  {-# INLINE write430 #-}
  {-# INLINE readPacked #-}
  {-# INLINE writePacked #-}