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

-- | Specialized and inlined @V2 Int32@.

module Geomancy.IVec3
  ( IVec3
  , ivec3
  , withIVec3
  , pattern WithIVec3
  , fromTuple

  , Packed(..)
  , packed
  ) where

import Control.DeepSeq (NFData(rnf))
import Data.Int (Int32)
import Data.MonoTraversable (Element, MonoFunctor(..), MonoPointed(..))
import Foreign (Storable(..))

import Geomancy.Elementwise (Elementwise(..))

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

{-# INLINE ivec3 #-}
ivec3 :: Int32 -> Int32 -> Int32 -> IVec3
ivec3 :: Int32 -> Int32 -> Int32 -> IVec3
ivec3 = Int32 -> Int32 -> Int32 -> IVec3
IVec3

{-# INLINE withIVec3 #-}
withIVec3
  :: IVec3
  -> (Int32 -> Int32 -> Int32 -> r)
  -> r
withIVec3 :: forall r. IVec3 -> (Int32 -> Int32 -> Int32 -> r) -> r
withIVec3 (IVec3 Int32
a Int32
b Int32
c) Int32 -> Int32 -> Int32 -> r
f = Int32 -> Int32 -> Int32 -> r
f Int32
a Int32
b Int32
c

pattern WithIVec3 :: Int32 -> Int32 -> Int32 -> IVec3
pattern $mWithIVec3 :: forall {r}.
IVec3 -> (Int32 -> Int32 -> Int32 -> r) -> ((# #) -> r) -> r
WithIVec3 a b c <- ((`withIVec3` (,,)) -> (a, b, c))
{-# COMPLETE WithIVec3 #-}

{-# INLINE fromTuple #-}
fromTuple :: (Int32, Int32, Int32) -> IVec3
fromTuple :: (Int32, Int32, Int32) -> IVec3
fromTuple (Int32
a, Int32
b, Int32
c) = Int32 -> Int32 -> Int32 -> IVec3
ivec3 Int32
a Int32
b Int32
c

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

type instance Element IVec3 = Int32

instance MonoFunctor IVec3 where
  {-# INLINE omap #-}
  omap :: (Element IVec3 -> Element IVec3) -> IVec3 -> IVec3
omap Element IVec3 -> Element IVec3
f IVec3
v =
    forall r. IVec3 -> (Int32 -> Int32 -> Int32 -> r) -> r
withIVec3 IVec3
v \Int32
x Int32
y Int32
z ->
      Int32 -> Int32 -> Int32 -> IVec3
ivec3 (Element IVec3 -> Element IVec3
f Int32
x) (Element IVec3 -> Element IVec3
f Int32
y) (Element IVec3 -> Element IVec3
f Int32
z)

instance MonoPointed IVec3 where
  opoint :: Element IVec3 -> IVec3
opoint Element IVec3
x = Int32 -> Int32 -> Int32 -> IVec3
ivec3 Element IVec3
x Element IVec3
x Element IVec3
x

instance Elementwise IVec3 where
  {-# INLINE emap2 #-}
  emap2 :: (Element IVec3 -> Element IVec3 -> Element IVec3)
-> IVec3 -> IVec3 -> IVec3
emap2 Element IVec3 -> Element IVec3 -> Element IVec3
f IVec3
p0 IVec3
p1 =
    forall r. IVec3 -> (Int32 -> Int32 -> Int32 -> r) -> r
withIVec3 IVec3
p0 \Int32
x0 Int32
y0 Int32
z0 ->
    forall r. IVec3 -> (Int32 -> Int32 -> Int32 -> r) -> r
withIVec3 IVec3
p1 \Int32
x1 Int32
y1 Int32
z1 ->
      Int32 -> Int32 -> Int32 -> IVec3
ivec3
        (Element IVec3 -> Element IVec3 -> Element IVec3
f Int32
x0 Int32
x1)
        (Element IVec3 -> Element IVec3 -> Element IVec3
f Int32
y0 Int32
y1)
        (Element IVec3 -> Element IVec3 -> Element IVec3
f Int32
z0 Int32
z1)

  {-# INLINE emap3 #-}
  emap3 :: (Element IVec3 -> Element IVec3 -> Element IVec3 -> Element IVec3)
-> IVec3 -> IVec3 -> IVec3 -> IVec3
emap3 Element IVec3 -> Element IVec3 -> Element IVec3 -> Element IVec3
f IVec3
p0 IVec3
p1 IVec3
p2 =
    forall r. IVec3 -> (Int32 -> Int32 -> Int32 -> r) -> r
withIVec3 IVec3
p0 \Int32
x0 Int32
y0 Int32
z0 ->
    forall r. IVec3 -> (Int32 -> Int32 -> Int32 -> r) -> r
withIVec3 IVec3
p1 \Int32
x1 Int32
y1 Int32
z1 ->
    forall r. IVec3 -> (Int32 -> Int32 -> Int32 -> r) -> r
withIVec3 IVec3
p2 \Int32
x2 Int32
y2 Int32
z2 ->
      Int32 -> Int32 -> Int32 -> IVec3
ivec3
        (Element IVec3 -> Element IVec3 -> Element IVec3 -> Element IVec3
f Int32
x0 Int32
x1 Int32
x2)
        (Element IVec3 -> Element IVec3 -> Element IVec3 -> Element IVec3
f Int32
y0 Int32
y1 Int32
y2)
        (Element IVec3 -> Element IVec3 -> Element IVec3 -> Element IVec3
f Int32
z0 Int32
z1 Int32
z2)

  {-# INLINE emap4 #-}
  emap4 :: (Element IVec3
 -> Element IVec3
 -> Element IVec3
 -> Element IVec3
 -> Element IVec3)
-> IVec3 -> IVec3 -> IVec3 -> IVec3 -> IVec3
emap4 Element IVec3
-> Element IVec3 -> Element IVec3 -> Element IVec3 -> Element IVec3
f IVec3
p0 IVec3
p1 IVec3
p2 IVec3
p3 =
    forall r. IVec3 -> (Int32 -> Int32 -> Int32 -> r) -> r
withIVec3 IVec3
p0 \Int32
x0 Int32
y0 Int32
z0 ->
    forall r. IVec3 -> (Int32 -> Int32 -> Int32 -> r) -> r
withIVec3 IVec3
p1 \Int32
x1 Int32
y1 Int32
z1 ->
    forall r. IVec3 -> (Int32 -> Int32 -> Int32 -> r) -> r
withIVec3 IVec3
p2 \Int32
x2 Int32
y2 Int32
z2 ->
    forall r. IVec3 -> (Int32 -> Int32 -> Int32 -> r) -> r
withIVec3 IVec3
p3 \Int32
x3 Int32
y3 Int32
z3 ->
      Int32 -> Int32 -> Int32 -> IVec3
ivec3
        (Element IVec3
-> Element IVec3 -> Element IVec3 -> Element IVec3 -> Element IVec3
f Int32
x0 Int32
x1 Int32
x2 Int32
x3)
        (Element IVec3
-> Element IVec3 -> Element IVec3 -> Element IVec3 -> Element IVec3
f Int32
y0 Int32
y1 Int32
y2 Int32
y3)
        (Element IVec3
-> Element IVec3 -> Element IVec3 -> Element IVec3 -> Element IVec3
f Int32
z0 Int32
z1 Int32
z2 Int32
z3)

  {-# INLINE emap5 #-}
  emap5 :: (Element IVec3
 -> Element IVec3
 -> Element IVec3
 -> Element IVec3
 -> Element IVec3
 -> Element IVec3)
-> IVec3 -> IVec3 -> IVec3 -> IVec3 -> IVec3 -> IVec3
emap5 Element IVec3
-> Element IVec3
-> Element IVec3
-> Element IVec3
-> Element IVec3
-> Element IVec3
f IVec3
p0 IVec3
p1 IVec3
p2 IVec3
p3 IVec3
p4 =
    forall r. IVec3 -> (Int32 -> Int32 -> Int32 -> r) -> r
withIVec3 IVec3
p0 \Int32
x0 Int32
y0 Int32
z0 ->
    forall r. IVec3 -> (Int32 -> Int32 -> Int32 -> r) -> r
withIVec3 IVec3
p1 \Int32
x1 Int32
y1 Int32
z1 ->
    forall r. IVec3 -> (Int32 -> Int32 -> Int32 -> r) -> r
withIVec3 IVec3
p2 \Int32
x2 Int32
y2 Int32
z2 ->
    forall r. IVec3 -> (Int32 -> Int32 -> Int32 -> r) -> r
withIVec3 IVec3
p3 \Int32
x3 Int32
y3 Int32
z3 ->
    forall r. IVec3 -> (Int32 -> Int32 -> Int32 -> r) -> r
withIVec3 IVec3
p4 \Int32
x4 Int32
y4 Int32
z4 ->
      Int32 -> Int32 -> Int32 -> IVec3
ivec3
        (Element IVec3
-> Element IVec3
-> Element IVec3
-> Element IVec3
-> Element IVec3
-> Element IVec3
f Int32
x0 Int32
x1 Int32
x2 Int32
x3 Int32
x4)
        (Element IVec3
-> Element IVec3
-> Element IVec3
-> Element IVec3
-> Element IVec3
-> Element IVec3
f Int32
y0 Int32
y1 Int32
y2 Int32
y3 Int32
y4)
        (Element IVec3
-> Element IVec3
-> Element IVec3
-> Element IVec3
-> Element IVec3
-> Element IVec3
f Int32
z0 Int32
z1 Int32
z2 Int32
z3 Int32
z4)

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

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

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

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

  {-# INLINE signum #-}
  signum :: IVec3 -> IVec3
signum IVec3
v3 = forall r. IVec3 -> (Int32 -> Int32 -> Int32 -> r) -> r
withIVec3 IVec3
v3 \Int32
a Int32
b Int32
c ->
    Int32 -> Int32 -> Int32 -> IVec3
ivec3 (forall a. Num a => a -> a
signum Int32
a) (forall a. Num a => a -> a
signum Int32
b) (forall a. Num a => a -> a
signum Int32
c)

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

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

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

  {-# INLINE poke #-}
  poke :: Ptr IVec3 -> IVec3 -> IO ()
poke Ptr IVec3
ptr IVec3
v3 =
    forall r. IVec3 -> (Int32 -> Int32 -> Int32 -> r) -> r
withIVec3 IVec3
v3 \Int32
a Int32
b Int32
c -> do
      forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr IVec3
ptr  Int
0 Int32
a
      forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr IVec3
ptr  Int
4 Int32
b
      forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr IVec3
ptr  Int
8 Int32
c

  {-# INLINE peek #-}
  peek :: Ptr IVec3 -> IO IVec3
peek Ptr IVec3
ptr = Int32 -> Int32 -> Int32 -> IVec3
ivec3
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr IVec3
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 IVec3
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 IVec3
ptr  Int
8

newtype Packed = Packed { Packed -> IVec3
unPacked :: IVec3 }
  deriving (Packed -> Packed -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Packed -> Packed -> Bool
$c/= :: Packed -> Packed -> Bool
== :: Packed -> Packed -> Bool
$c== :: Packed -> Packed -> Bool
Eq, Eq Packed
Packed -> Packed -> Bool
Packed -> Packed -> Ordering
Packed -> Packed -> Packed
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 :: Packed -> Packed -> Packed
$cmin :: Packed -> Packed -> Packed
max :: Packed -> Packed -> Packed
$cmax :: Packed -> Packed -> Packed
>= :: Packed -> Packed -> Bool
$c>= :: Packed -> Packed -> Bool
> :: Packed -> Packed -> Bool
$c> :: Packed -> Packed -> Bool
<= :: Packed -> Packed -> Bool
$c<= :: Packed -> Packed -> Bool
< :: Packed -> Packed -> Bool
$c< :: Packed -> Packed -> Bool
compare :: Packed -> Packed -> Ordering
$ccompare :: Packed -> Packed -> Ordering
Ord, Int -> Packed -> ShowS
[Packed] -> ShowS
Packed -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Packed] -> ShowS
$cshowList :: [Packed] -> ShowS
show :: Packed -> String
$cshow :: Packed -> String
showsPrec :: Int -> Packed -> ShowS
$cshowsPrec :: Int -> Packed -> ShowS
Show, Packed -> ()
forall a. (a -> ()) -> NFData a
rnf :: Packed -> ()
$crnf :: Packed -> ()
NFData, Integer -> Packed
Packed -> Packed
Packed -> Packed -> Packed
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Packed
$cfromInteger :: Integer -> Packed
signum :: Packed -> Packed
$csignum :: Packed -> Packed
abs :: Packed -> Packed
$cabs :: Packed -> Packed
negate :: Packed -> Packed
$cnegate :: Packed -> Packed
* :: Packed -> Packed -> Packed
$c* :: Packed -> Packed -> Packed
- :: Packed -> Packed -> Packed
$c- :: Packed -> Packed -> Packed
+ :: Packed -> Packed -> Packed
$c+ :: Packed -> Packed -> Packed
Num)

{-# INLINE packed #-}
packed :: Int32 -> Int32 -> Int32 -> Packed
packed :: Int32 -> Int32 -> Int32 -> Packed
packed Int32
a Int32
b Int32
c = IVec3 -> Packed
Packed (Int32 -> Int32 -> Int32 -> IVec3
ivec3 Int32
a Int32
b Int32
c)

instance Storable Packed where
  {-# INLINE sizeOf #-}
  sizeOf :: Packed -> Int
sizeOf Packed
_ = Int
12

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

  {-# INLINE poke #-}
  poke :: Ptr Packed -> Packed -> IO ()
poke Ptr Packed
ptr (Packed IVec3
v3) =
    forall r. IVec3 -> (Int32 -> Int32 -> Int32 -> r) -> r
withIVec3 IVec3
v3 \Int32
a Int32
b Int32
c -> do
      forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Packed
ptr Int
0 Int32
a
      forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Packed
ptr Int
4 Int32
b
      forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Packed
ptr Int
8 Int32
c

  {-# INLINE peek #-}
  peek :: Ptr Packed -> IO Packed
peek Ptr Packed
ptr = Int32 -> Int32 -> Int32 -> Packed
packed
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Packed
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 Packed
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 Packed
ptr Int
8