{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}
module Geomancy.IVec4
( IVec4
, ivec4
, withIVec4
, pattern WithIVec4
, fromTuple
) where
import Control.DeepSeq (NFData(rnf))
import Data.Int (Int32)
import Data.MonoTraversable (Element, MonoFunctor(..), MonoPointed(..))
import Foreign (Storable(..))
import Geomancy.Elementwise (Elementwise(..))
data IVec4 = IVec4
{-# UNPACK #-} !Int32
{-# UNPACK #-} !Int32
{-# UNPACK #-} !Int32
{-# UNPACK #-} !Int32
deriving (IVec4 -> IVec4 -> Bool
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
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
Ord, Int -> IVec4 -> ShowS
[IVec4] -> ShowS
IVec4 -> String
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 :: forall r. 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) -> ((# #) -> 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{} = ()
type instance Element IVec4 = Int32
instance MonoFunctor IVec4 where
{-# INLINE omap #-}
omap :: (Element IVec4 -> Element IVec4) -> IVec4 -> IVec4
omap Element IVec4 -> Element IVec4
f IVec4
v =
forall r. IVec4 -> (Int32 -> Int32 -> Int32 -> Int32 -> r) -> r
withIVec4 IVec4
v \Int32
x Int32
y Int32
z Int32
w ->
Int32 -> Int32 -> Int32 -> Int32 -> IVec4
ivec4 (Element IVec4 -> Element IVec4
f Int32
x) (Element IVec4 -> Element IVec4
f Int32
y) (Element IVec4 -> Element IVec4
f Int32
z) (Element IVec4 -> Element IVec4
f Int32
w)
instance MonoPointed IVec4 where
opoint :: Element IVec4 -> IVec4
opoint Element IVec4
x = Int32 -> Int32 -> Int32 -> Int32 -> IVec4
ivec4 Element IVec4
x Element IVec4
x Element IVec4
x Element IVec4
x
instance Elementwise IVec4 where
{-# INLINE emap2 #-}
emap2 :: (Element IVec4 -> Element IVec4 -> Element IVec4)
-> IVec4 -> IVec4 -> IVec4
emap2 Element IVec4 -> Element IVec4 -> Element IVec4
f IVec4
p0 IVec4
p1 =
forall r. IVec4 -> (Int32 -> Int32 -> Int32 -> Int32 -> r) -> r
withIVec4 IVec4
p0 \Int32
x0 Int32
y0 Int32
z0 Int32
w0 ->
forall r. IVec4 -> (Int32 -> Int32 -> Int32 -> Int32 -> r) -> r
withIVec4 IVec4
p1 \Int32
x1 Int32
y1 Int32
z1 Int32
w1 ->
Int32 -> Int32 -> Int32 -> Int32 -> IVec4
ivec4
(Element IVec4 -> Element IVec4 -> Element IVec4
f Int32
x0 Int32
x1)
(Element IVec4 -> Element IVec4 -> Element IVec4
f Int32
y0 Int32
y1)
(Element IVec4 -> Element IVec4 -> Element IVec4
f Int32
z0 Int32
z1)
(Element IVec4 -> Element IVec4 -> Element IVec4
f Int32
w0 Int32
w1)
{-# INLINE emap3 #-}
emap3 :: (Element IVec4 -> Element IVec4 -> Element IVec4 -> Element IVec4)
-> IVec4 -> IVec4 -> IVec4 -> IVec4
emap3 Element IVec4 -> Element IVec4 -> Element IVec4 -> Element IVec4
f IVec4
p0 IVec4
p1 IVec4
p2 =
forall r. IVec4 -> (Int32 -> Int32 -> Int32 -> Int32 -> r) -> r
withIVec4 IVec4
p0 \Int32
x0 Int32
y0 Int32
z0 Int32
w0 ->
forall r. IVec4 -> (Int32 -> Int32 -> Int32 -> Int32 -> r) -> r
withIVec4 IVec4
p1 \Int32
x1 Int32
y1 Int32
z1 Int32
w1 ->
forall r. IVec4 -> (Int32 -> Int32 -> Int32 -> Int32 -> r) -> r
withIVec4 IVec4
p2 \Int32
x2 Int32
y2 Int32
z2 Int32
w2 ->
Int32 -> Int32 -> Int32 -> Int32 -> IVec4
ivec4
(Element IVec4 -> Element IVec4 -> Element IVec4 -> Element IVec4
f Int32
x0 Int32
x1 Int32
x2)
(Element IVec4 -> Element IVec4 -> Element IVec4 -> Element IVec4
f Int32
y0 Int32
y1 Int32
y2)
(Element IVec4 -> Element IVec4 -> Element IVec4 -> Element IVec4
f Int32
z0 Int32
z1 Int32
z2)
(Element IVec4 -> Element IVec4 -> Element IVec4 -> Element IVec4
f Int32
w0 Int32
w1 Int32
w2)
{-# INLINE emap4 #-}
emap4 :: (Element IVec4
-> Element IVec4
-> Element IVec4
-> Element IVec4
-> Element IVec4)
-> IVec4 -> IVec4 -> IVec4 -> IVec4 -> IVec4
emap4 Element IVec4
-> Element IVec4 -> Element IVec4 -> Element IVec4 -> Element IVec4
f IVec4
p0 IVec4
p1 IVec4
p2 IVec4
p3 =
forall r. IVec4 -> (Int32 -> Int32 -> Int32 -> Int32 -> r) -> r
withIVec4 IVec4
p0 \Int32
x0 Int32
y0 Int32
z0 Int32
w0 ->
forall r. IVec4 -> (Int32 -> Int32 -> Int32 -> Int32 -> r) -> r
withIVec4 IVec4
p1 \Int32
x1 Int32
y1 Int32
z1 Int32
w1 ->
forall r. IVec4 -> (Int32 -> Int32 -> Int32 -> Int32 -> r) -> r
withIVec4 IVec4
p2 \Int32
x2 Int32
y2 Int32
z2 Int32
w2 ->
forall r. IVec4 -> (Int32 -> Int32 -> Int32 -> Int32 -> r) -> r
withIVec4 IVec4
p3 \Int32
x3 Int32
y3 Int32
z3 Int32
w3 ->
Int32 -> Int32 -> Int32 -> Int32 -> IVec4
ivec4
(Element IVec4
-> Element IVec4 -> Element IVec4 -> Element IVec4 -> Element IVec4
f Int32
x0 Int32
x1 Int32
x2 Int32
x3)
(Element IVec4
-> Element IVec4 -> Element IVec4 -> Element IVec4 -> Element IVec4
f Int32
y0 Int32
y1 Int32
y2 Int32
y3)
(Element IVec4
-> Element IVec4 -> Element IVec4 -> Element IVec4 -> Element IVec4
f Int32
z0 Int32
z1 Int32
z2 Int32
z3)
(Element IVec4
-> Element IVec4 -> Element IVec4 -> Element IVec4 -> Element IVec4
f Int32
w0 Int32
w1 Int32
w2 Int32
w3)
{-# INLINE emap5 #-}
emap5 :: (Element IVec4
-> Element IVec4
-> Element IVec4
-> Element IVec4
-> Element IVec4
-> Element IVec4)
-> IVec4 -> IVec4 -> IVec4 -> IVec4 -> IVec4 -> IVec4
emap5 Element IVec4
-> Element IVec4
-> Element IVec4
-> Element IVec4
-> Element IVec4
-> Element IVec4
f IVec4
p0 IVec4
p1 IVec4
p2 IVec4
p3 IVec4
p4 =
forall r. IVec4 -> (Int32 -> Int32 -> Int32 -> Int32 -> r) -> r
withIVec4 IVec4
p0 \Int32
x0 Int32
y0 Int32
z0 Int32
w0 ->
forall r. IVec4 -> (Int32 -> Int32 -> Int32 -> Int32 -> r) -> r
withIVec4 IVec4
p1 \Int32
x1 Int32
y1 Int32
z1 Int32
w1 ->
forall r. IVec4 -> (Int32 -> Int32 -> Int32 -> Int32 -> r) -> r
withIVec4 IVec4
p2 \Int32
x2 Int32
y2 Int32
z2 Int32
w2 ->
forall r. IVec4 -> (Int32 -> Int32 -> Int32 -> Int32 -> r) -> r
withIVec4 IVec4
p3 \Int32
x3 Int32
y3 Int32
z3 Int32
w3 ->
forall r. IVec4 -> (Int32 -> Int32 -> Int32 -> Int32 -> r) -> r
withIVec4 IVec4
p4 \Int32
x4 Int32
y4 Int32
z4 Int32
w4 ->
Int32 -> Int32 -> Int32 -> Int32 -> IVec4
ivec4
(Element IVec4
-> Element IVec4
-> Element IVec4
-> Element IVec4
-> Element IVec4
-> Element IVec4
f Int32
x0 Int32
x1 Int32
x2 Int32
x3 Int32
x4)
(Element IVec4
-> Element IVec4
-> Element IVec4
-> Element IVec4
-> Element IVec4
-> Element IVec4
f Int32
y0 Int32
y1 Int32
y2 Int32
y3 Int32
y4)
(Element IVec4
-> Element IVec4
-> Element IVec4
-> Element IVec4
-> Element IVec4
-> Element IVec4
f Int32
z0 Int32
z1 Int32
z2 Int32
z3 Int32
z4)
(Element IVec4
-> Element IVec4
-> Element IVec4
-> Element IVec4
-> Element IVec4
-> Element IVec4
f Int32
w0 Int32
w1 Int32
w2 Int32
w3 Int32
w4)
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 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)
(Int32
l4 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 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)
(Int32
l4 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 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)
(Int32
l4 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 = 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 (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) (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' = 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 =
forall r. IVec4 -> (Int32 -> Int32 -> Int32 -> Int32 -> r) -> r
withIVec4 IVec4
v4 \Int32
a Int32
b Int32
c Int32
d -> do
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr IVec4
ptr Int
0 Int32
a
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr IVec4
ptr Int
4 Int32
b
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr IVec4
ptr Int
8 Int32
c
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
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr IVec4
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 IVec4
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 IVec4
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 IVec4
ptr Int
12