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

-- | Specialized and inlined @V2 Int32@.

module Geomancy.IVec4
  ( IVec4
  , ivec4
  , withIVec4
  , pattern WithIVec4
  , fromTuple
  ) where

import Control.DeepSeq (NFData(rnf))
import Data.Int (Int32)
import Foreign (Storable(..))

data IVec4 = IVec4
  {-# UNPACK #-} !Int32
  {-# UNPACK #-} !Int32
  {-# UNPACK #-} !Int32
  {-# UNPACK #-} !Int32
  deriving (IVec4 -> IVec4 -> Bool
(IVec4 -> IVec4 -> Bool) -> (IVec4 -> IVec4 -> Bool) -> Eq IVec4
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IVec4 -> IVec4 -> Bool
$c/= :: IVec4 -> IVec4 -> Bool
== :: IVec4 -> IVec4 -> Bool
$c== :: IVec4 -> IVec4 -> Bool
Eq, Eq IVec4
Eq IVec4
-> (IVec4 -> IVec4 -> Ordering)
-> (IVec4 -> IVec4 -> Bool)
-> (IVec4 -> IVec4 -> Bool)
-> (IVec4 -> IVec4 -> Bool)
-> (IVec4 -> IVec4 -> Bool)
-> (IVec4 -> IVec4 -> IVec4)
-> (IVec4 -> IVec4 -> IVec4)
-> Ord IVec4
IVec4 -> IVec4 -> Bool
IVec4 -> IVec4 -> Ordering
IVec4 -> IVec4 -> IVec4
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 :: IVec4 -> IVec4 -> IVec4
$cmin :: IVec4 -> IVec4 -> IVec4
max :: IVec4 -> IVec4 -> IVec4
$cmax :: IVec4 -> IVec4 -> IVec4
>= :: IVec4 -> IVec4 -> Bool
$c>= :: IVec4 -> IVec4 -> Bool
> :: IVec4 -> IVec4 -> Bool
$c> :: IVec4 -> IVec4 -> Bool
<= :: IVec4 -> IVec4 -> Bool
$c<= :: IVec4 -> IVec4 -> Bool
< :: IVec4 -> IVec4 -> Bool
$c< :: IVec4 -> IVec4 -> Bool
compare :: IVec4 -> IVec4 -> Ordering
$ccompare :: IVec4 -> IVec4 -> Ordering
$cp1Ord :: Eq IVec4
Ord, Int -> IVec4 -> ShowS
[IVec4] -> ShowS
IVec4 -> String
(Int -> IVec4 -> ShowS)
-> (IVec4 -> String) -> ([IVec4] -> ShowS) -> Show IVec4
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IVec4] -> ShowS
$cshowList :: [IVec4] -> ShowS
show :: IVec4 -> String
$cshow :: IVec4 -> String
showsPrec :: Int -> IVec4 -> ShowS
$cshowsPrec :: Int -> IVec4 -> ShowS
Show)

{-# INLINE ivec4 #-}
ivec4 :: Int32 -> Int32 -> Int32 -> Int32 -> IVec4
ivec4 :: Int32 -> Int32 -> Int32 -> Int32 -> IVec4
ivec4 = Int32 -> Int32 -> Int32 -> Int32 -> IVec4
IVec4

{-# INLINE withIVec4 #-}
withIVec4
  :: IVec4
  -> (Int32 -> Int32 -> Int32 -> Int32 -> r)
  -> r
withIVec4 :: IVec4 -> (Int32 -> Int32 -> Int32 -> Int32 -> r) -> r
withIVec4 (IVec4 Int32
a Int32
b Int32
c Int32
d) Int32 -> Int32 -> Int32 -> Int32 -> r
f = Int32 -> Int32 -> Int32 -> Int32 -> r
f Int32
a Int32
b Int32
c Int32
d

pattern WithIVec4 :: Int32 -> Int32 -> Int32 -> Int32 -> IVec4
pattern $mWithIVec4 :: forall r.
IVec4
-> (Int32 -> Int32 -> Int32 -> Int32 -> r) -> (Void# -> r) -> r
WithIVec4 a b c d <- ((`withIVec4` (,,,)) -> (a, b, c, d))
{-# COMPLETE WithIVec4 #-}

{-# INLINE fromTuple #-}
fromTuple :: (Int32, Int32, Int32, Int32) -> IVec4
fromTuple :: (Int32, Int32, Int32, Int32) -> IVec4
fromTuple (Int32
x, Int32
y, Int32
z, Int32
w) = Int32 -> Int32 -> Int32 -> Int32 -> IVec4
ivec4 Int32
x Int32
y Int32
z Int32
w

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

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

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

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

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

  {-# INLINE signum #-}
  signum :: IVec4 -> IVec4
signum IVec4
v4 = IVec4 -> (Int32 -> Int32 -> Int32 -> Int32 -> IVec4) -> IVec4
forall r. IVec4 -> (Int32 -> Int32 -> Int32 -> Int32 -> r) -> r
withIVec4 IVec4
v4 \Int32
a Int32
b Int32
c Int32
d ->
    Int32 -> Int32 -> Int32 -> Int32 -> IVec4
ivec4 (Int32 -> Int32
forall a. Num a => a -> a
signum Int32
a) (Int32 -> Int32
forall a. Num a => a -> a
signum Int32
b) (Int32 -> Int32
forall a. Num a => a -> a
signum Int32
c) (Int32 -> Int32
forall a. Num a => a -> a
signum Int32
d)

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

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

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

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

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