{-# LANGUAGE CPP                        #-}
{-# LANGUAGE DeriveDataTypeable         #-}
{-# LANGUAGE DeriveGeneric              #-}
{-# LANGUAGE DeriveTraversable          #-}
{-# LANGUAGE FlexibleContexts           #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses      #-}
{-# LANGUAGE ScopedTypeVariables        #-}
{-# LANGUAGE Trustworthy                #-}
{-# LANGUAGE TypeFamilies               #-}

#ifndef MIN_VERSION_vector
#define MIN_VERSION_vector(x,y,z) 1
#endif

-----------------------------------------------------------------------------
-- |
-- Copyright   :  (C) 2012-2015 Edward Kmett
-- License     :  BSD-style (see the file LICENSE)
--
-- Maintainer  :  Edward Kmett <ekmett@gmail.com>
-- Stability   :  experimental
-- Portability :  non-portable
----------------------------------------------------------------------------

module SDL.Internal.Vect
  ( Point (..)
  , V2 (..)
  , V3 (..)
  , V4 (..)
  ) where

import           Control.Applicative
import           Control.Monad               (liftM)
import           Control.Monad.Fix
import           Control.Monad.Zip
import           Data.Data
import           Data.Foldable
import           Data.Monoid
import           Data.Traversable
import qualified Data.Vector.Generic         as G
import qualified Data.Vector.Generic.Mutable as M
import qualified Data.Vector.Unboxed.Base    as U
import           Foreign.Ptr                 (castPtr)
import           Foreign.Storable            (Storable (..))
import           GHC.Arr                     (Ix (..))
import           GHC.Generics                (Generic, Generic1)
import           Prelude
-- Explicit Prelude import suppresses warnings about redundant imports.
{-# ANN module "HLint: ignore Reduce duplication" #-}
{-# ANN module "HLint: ignore Use fmap" #-}


-- | A handy wrapper to help distinguish points from vectors at the
-- type level
newtype Point f a = P (f a)
  deriving ( Point f a -> Point f a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (f :: Type -> Type) a.
Eq (f a) =>
Point f a -> Point f a -> Bool
/= :: Point f a -> Point f a -> Bool
$c/= :: forall (f :: Type -> Type) a.
Eq (f a) =>
Point f a -> Point f a -> Bool
== :: Point f a -> Point f a -> Bool
$c== :: forall (f :: Type -> Type) a.
Eq (f a) =>
Point f a -> Point f a -> Bool
Eq, Point f a -> Point f a -> Bool
Point f a -> Point f a -> Ordering
Point f a -> Point f a -> Point f a
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
forall {f :: Type -> Type} {a}. Ord (f a) => Eq (Point f a)
forall (f :: Type -> Type) a.
Ord (f a) =>
Point f a -> Point f a -> Bool
forall (f :: Type -> Type) a.
Ord (f a) =>
Point f a -> Point f a -> Ordering
forall (f :: Type -> Type) a.
Ord (f a) =>
Point f a -> Point f a -> Point f a
min :: Point f a -> Point f a -> Point f a
$cmin :: forall (f :: Type -> Type) a.
Ord (f a) =>
Point f a -> Point f a -> Point f a
max :: Point f a -> Point f a -> Point f a
$cmax :: forall (f :: Type -> Type) a.
Ord (f a) =>
Point f a -> Point f a -> Point f a
>= :: Point f a -> Point f a -> Bool
$c>= :: forall (f :: Type -> Type) a.
Ord (f a) =>
Point f a -> Point f a -> Bool
> :: Point f a -> Point f a -> Bool
$c> :: forall (f :: Type -> Type) a.
Ord (f a) =>
Point f a -> Point f a -> Bool
<= :: Point f a -> Point f a -> Bool
$c<= :: forall (f :: Type -> Type) a.
Ord (f a) =>
Point f a -> Point f a -> Bool
< :: Point f a -> Point f a -> Bool
$c< :: forall (f :: Type -> Type) a.
Ord (f a) =>
Point f a -> Point f a -> Bool
compare :: Point f a -> Point f a -> Ordering
$ccompare :: forall (f :: Type -> Type) a.
Ord (f a) =>
Point f a -> Point f a -> Ordering
Ord, Int -> Point f a -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (f :: Type -> Type) a.
Show (f a) =>
Int -> Point f a -> ShowS
forall (f :: Type -> Type) a. Show (f a) => [Point f a] -> ShowS
forall (f :: Type -> Type) a. Show (f a) => Point f a -> String
showList :: [Point f a] -> ShowS
$cshowList :: forall (f :: Type -> Type) a. Show (f a) => [Point f a] -> ShowS
show :: Point f a -> String
$cshow :: forall (f :: Type -> Type) a. Show (f a) => Point f a -> String
showsPrec :: Int -> Point f a -> ShowS
$cshowsPrec :: forall (f :: Type -> Type) a.
Show (f a) =>
Int -> Point f a -> ShowS
Show, ReadPrec [Point f a]
ReadPrec (Point f a)
ReadS [Point f a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall (f :: Type -> Type) a. Read (f a) => ReadPrec [Point f a]
forall (f :: Type -> Type) a. Read (f a) => ReadPrec (Point f a)
forall (f :: Type -> Type) a.
Read (f a) =>
Int -> ReadS (Point f a)
forall (f :: Type -> Type) a. Read (f a) => ReadS [Point f a]
readListPrec :: ReadPrec [Point f a]
$creadListPrec :: forall (f :: Type -> Type) a. Read (f a) => ReadPrec [Point f a]
readPrec :: ReadPrec (Point f a)
$creadPrec :: forall (f :: Type -> Type) a. Read (f a) => ReadPrec (Point f a)
readList :: ReadS [Point f a]
$creadList :: forall (f :: Type -> Type) a. Read (f a) => ReadS [Point f a]
readsPrec :: Int -> ReadS (Point f a)
$creadsPrec :: forall (f :: Type -> Type) a.
Read (f a) =>
Int -> ReadS (Point f a)
Read, forall a. a -> Point f a
forall a b. Point f a -> Point f b -> Point f b
forall a b. Point f a -> (a -> Point f b) -> Point f b
forall {f :: Type -> Type}. Monad f => Applicative (Point f)
forall (f :: Type -> Type) a. Monad f => a -> Point f a
forall (f :: Type -> Type) a b.
Monad f =>
Point f a -> Point f b -> Point f b
forall (f :: Type -> Type) a b.
Monad f =>
Point f a -> (a -> Point f b) -> Point f b
forall (m :: Type -> Type).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: forall a. a -> Point f a
$creturn :: forall (f :: Type -> Type) a. Monad f => a -> Point f a
>> :: forall a b. Point f a -> Point f b -> Point f b
$c>> :: forall (f :: Type -> Type) a b.
Monad f =>
Point f a -> Point f b -> Point f b
>>= :: forall a b. Point f a -> (a -> Point f b) -> Point f b
$c>>= :: forall (f :: Type -> Type) a b.
Monad f =>
Point f a -> (a -> Point f b) -> Point f b
Monad, forall a b. a -> Point f b -> Point f a
forall a b. (a -> b) -> Point f a -> Point f b
forall (f :: Type -> Type) a b.
Functor f =>
a -> Point f b -> Point f a
forall (f :: Type -> Type) a b.
Functor f =>
(a -> b) -> Point f a -> Point f b
forall (f :: Type -> Type).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Point f b -> Point f a
$c<$ :: forall (f :: Type -> Type) a b.
Functor f =>
a -> Point f b -> Point f a
fmap :: forall a b. (a -> b) -> Point f a -> Point f b
$cfmap :: forall (f :: Type -> Type) a b.
Functor f =>
(a -> b) -> Point f a -> Point f b
Functor, forall a. a -> Point f a
forall a b. Point f a -> Point f b -> Point f a
forall a b. Point f a -> Point f b -> Point f b
forall a b. Point f (a -> b) -> Point f a -> Point f b
forall a b c. (a -> b -> c) -> Point f a -> Point f b -> Point f c
forall (f :: Type -> Type).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
forall {f :: Type -> Type}. Applicative f => Functor (Point f)
forall (f :: Type -> Type) a. Applicative f => a -> Point f a
forall (f :: Type -> Type) a b.
Applicative f =>
Point f a -> Point f b -> Point f a
forall (f :: Type -> Type) a b.
Applicative f =>
Point f a -> Point f b -> Point f b
forall (f :: Type -> Type) a b.
Applicative f =>
Point f (a -> b) -> Point f a -> Point f b
forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> Point f a -> Point f b -> Point f c
<* :: forall a b. Point f a -> Point f b -> Point f a
$c<* :: forall (f :: Type -> Type) a b.
Applicative f =>
Point f a -> Point f b -> Point f a
*> :: forall a b. Point f a -> Point f b -> Point f b
$c*> :: forall (f :: Type -> Type) a b.
Applicative f =>
Point f a -> Point f b -> Point f b
liftA2 :: forall a b c. (a -> b -> c) -> Point f a -> Point f b -> Point f c
$cliftA2 :: forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> Point f a -> Point f b -> Point f c
<*> :: forall a b. Point f (a -> b) -> Point f a -> Point f b
$c<*> :: forall (f :: Type -> Type) a b.
Applicative f =>
Point f (a -> b) -> Point f a -> Point f b
pure :: forall a. a -> Point f a
$cpure :: forall (f :: Type -> Type) a. Applicative f => a -> Point f a
Applicative, forall a. Eq a => a -> Point f a -> Bool
forall a. Num a => Point f a -> a
forall a. Ord a => Point f a -> a
forall m. Monoid m => Point f m -> m
forall a. Point f a -> Bool
forall a. Point f a -> Int
forall a. Point f a -> [a]
forall a. (a -> a -> a) -> Point f a -> a
forall m a. Monoid m => (a -> m) -> Point f a -> m
forall b a. (b -> a -> b) -> b -> Point f a -> b
forall a b. (a -> b -> b) -> b -> Point f a -> b
forall (f :: Type -> Type) a.
(Foldable f, Eq a) =>
a -> Point f a -> Bool
forall (f :: Type -> Type) a. (Foldable f, Num a) => Point f a -> a
forall (f :: Type -> Type) a. (Foldable f, Ord a) => Point f a -> a
forall (f :: Type -> Type) m.
(Foldable f, Monoid m) =>
Point f m -> m
forall (f :: Type -> Type) a. Foldable f => Point f a -> Bool
forall (f :: Type -> Type) a. Foldable f => Point f a -> Int
forall (f :: Type -> Type) a. Foldable f => Point f a -> [a]
forall (f :: Type -> Type) a.
Foldable f =>
(a -> a -> a) -> Point f a -> a
forall (f :: Type -> Type) m a.
(Foldable f, Monoid m) =>
(a -> m) -> Point f a -> m
forall (f :: Type -> Type) b a.
Foldable f =>
(b -> a -> b) -> b -> Point f a -> b
forall (f :: Type -> Type) a b.
Foldable f =>
(a -> b -> b) -> b -> Point f a -> b
forall (t :: Type -> Type).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => Point f a -> a
$cproduct :: forall (f :: Type -> Type) a. (Foldable f, Num a) => Point f a -> a
sum :: forall a. Num a => Point f a -> a
$csum :: forall (f :: Type -> Type) a. (Foldable f, Num a) => Point f a -> a
minimum :: forall a. Ord a => Point f a -> a
$cminimum :: forall (f :: Type -> Type) a. (Foldable f, Ord a) => Point f a -> a
maximum :: forall a. Ord a => Point f a -> a
$cmaximum :: forall (f :: Type -> Type) a. (Foldable f, Ord a) => Point f a -> a
elem :: forall a. Eq a => a -> Point f a -> Bool
$celem :: forall (f :: Type -> Type) a.
(Foldable f, Eq a) =>
a -> Point f a -> Bool
length :: forall a. Point f a -> Int
$clength :: forall (f :: Type -> Type) a. Foldable f => Point f a -> Int
null :: forall a. Point f a -> Bool
$cnull :: forall (f :: Type -> Type) a. Foldable f => Point f a -> Bool
toList :: forall a. Point f a -> [a]
$ctoList :: forall (f :: Type -> Type) a. Foldable f => Point f a -> [a]
foldl1 :: forall a. (a -> a -> a) -> Point f a -> a
$cfoldl1 :: forall (f :: Type -> Type) a.
Foldable f =>
(a -> a -> a) -> Point f a -> a
foldr1 :: forall a. (a -> a -> a) -> Point f a -> a
$cfoldr1 :: forall (f :: Type -> Type) a.
Foldable f =>
(a -> a -> a) -> Point f a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> Point f a -> b
$cfoldl' :: forall (f :: Type -> Type) b a.
Foldable f =>
(b -> a -> b) -> b -> Point f a -> b
foldl :: forall b a. (b -> a -> b) -> b -> Point f a -> b
$cfoldl :: forall (f :: Type -> Type) b a.
Foldable f =>
(b -> a -> b) -> b -> Point f a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> Point f a -> b
$cfoldr' :: forall (f :: Type -> Type) a b.
Foldable f =>
(a -> b -> b) -> b -> Point f a -> b
foldr :: forall a b. (a -> b -> b) -> b -> Point f a -> b
$cfoldr :: forall (f :: Type -> Type) a b.
Foldable f =>
(a -> b -> b) -> b -> Point f a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> Point f a -> m
$cfoldMap' :: forall (f :: Type -> Type) m a.
(Foldable f, Monoid m) =>
(a -> m) -> Point f a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> Point f a -> m
$cfoldMap :: forall (f :: Type -> Type) m a.
(Foldable f, Monoid m) =>
(a -> m) -> Point f a -> m
fold :: forall m. Monoid m => Point f m -> m
$cfold :: forall (f :: Type -> Type) m.
(Foldable f, Monoid m) =>
Point f m -> m
Foldable
           , forall (t :: Type -> Type).
Functor t
-> Foldable t
-> (forall (f :: Type -> Type) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: Type -> Type) a.
    Applicative f =>
    t (f a) -> f (t a))
-> (forall (m :: Type -> Type) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: Type -> Type) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall {f :: Type -> Type}. Traversable f => Functor (Point f)
forall {f :: Type -> Type}. Traversable f => Foldable (Point f)
forall (f :: Type -> Type) (m :: Type -> Type) a.
(Traversable f, Monad m) =>
Point f (m a) -> m (Point f a)
forall (f :: Type -> Type) (f :: Type -> Type) a.
(Traversable f, Applicative f) =>
Point f (f a) -> f (Point f a)
forall (f :: Type -> Type) (m :: Type -> Type) a b.
(Traversable f, Monad m) =>
(a -> m b) -> Point f a -> m (Point f b)
forall (f :: Type -> Type) (f :: Type -> Type) a b.
(Traversable f, Applicative f) =>
(a -> f b) -> Point f a -> f (Point f b)
forall (f :: Type -> Type) a b.
Applicative f =>
(a -> f b) -> Point f a -> f (Point f b)
sequence :: forall (m :: Type -> Type) a.
Monad m =>
Point f (m a) -> m (Point f a)
$csequence :: forall (f :: Type -> Type) (m :: Type -> Type) a.
(Traversable f, Monad m) =>
Point f (m a) -> m (Point f a)
mapM :: forall (m :: Type -> Type) a b.
Monad m =>
(a -> m b) -> Point f a -> m (Point f b)
$cmapM :: forall (f :: Type -> Type) (m :: Type -> Type) a b.
(Traversable f, Monad m) =>
(a -> m b) -> Point f a -> m (Point f b)
sequenceA :: forall (f :: Type -> Type) a.
Applicative f =>
Point f (f a) -> f (Point f a)
$csequenceA :: forall (f :: Type -> Type) (f :: Type -> Type) a.
(Traversable f, Applicative f) =>
Point f (f a) -> f (Point f a)
traverse :: forall (f :: Type -> Type) a b.
Applicative f =>
(a -> f b) -> Point f a -> f (Point f b)
$ctraverse :: forall (f :: Type -> Type) (f :: Type -> Type) a b.
(Traversable f, Applicative f) =>
(a -> f b) -> Point f a -> f (Point f b)
Traversable, Rational -> Point f a
Point f a -> Point f a
Point f a -> Point f a -> Point f a
forall a.
Num a
-> (a -> a -> a) -> (a -> a) -> (Rational -> a) -> Fractional a
forall {f :: Type -> Type} {a}. Fractional (f a) => Num (Point f a)
forall (f :: Type -> Type) a.
Fractional (f a) =>
Rational -> Point f a
forall (f :: Type -> Type) a.
Fractional (f a) =>
Point f a -> Point f a
forall (f :: Type -> Type) a.
Fractional (f a) =>
Point f a -> Point f a -> Point f a
fromRational :: Rational -> Point f a
$cfromRational :: forall (f :: Type -> Type) a.
Fractional (f a) =>
Rational -> Point f a
recip :: Point f a -> Point f a
$crecip :: forall (f :: Type -> Type) a.
Fractional (f a) =>
Point f a -> Point f a
/ :: Point f a -> Point f a -> Point f a
$c/ :: forall (f :: Type -> Type) a.
Fractional (f a) =>
Point f a -> Point f a -> Point f a
Fractional , Integer -> Point f a
Point f a -> Point f a
Point f a -> Point f a -> Point f a
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
forall (f :: Type -> Type) a. Num (f a) => Integer -> Point f a
forall (f :: Type -> Type) a. Num (f a) => Point f a -> Point f a
forall (f :: Type -> Type) a.
Num (f a) =>
Point f a -> Point f a -> Point f a
fromInteger :: Integer -> Point f a
$cfromInteger :: forall (f :: Type -> Type) a. Num (f a) => Integer -> Point f a
signum :: Point f a -> Point f a
$csignum :: forall (f :: Type -> Type) a. Num (f a) => Point f a -> Point f a
abs :: Point f a -> Point f a
$cabs :: forall (f :: Type -> Type) a. Num (f a) => Point f a -> Point f a
negate :: Point f a -> Point f a
$cnegate :: forall (f :: Type -> Type) a. Num (f a) => Point f a -> Point f a
* :: Point f a -> Point f a -> Point f a
$c* :: forall (f :: Type -> Type) a.
Num (f a) =>
Point f a -> Point f a -> Point f a
- :: Point f a -> Point f a -> Point f a
$c- :: forall (f :: Type -> Type) a.
Num (f a) =>
Point f a -> Point f a -> Point f a
+ :: Point f a -> Point f a -> Point f a
$c+ :: forall (f :: Type -> Type) a.
Num (f a) =>
Point f a -> Point f a -> Point f a
Num, (Point f a, Point f a) -> Int
(Point f a, Point f a) -> [Point f a]
(Point f a, Point f a) -> Point f a -> Bool
(Point f a, Point f a) -> Point f a -> Int
forall a.
Ord a
-> ((a, a) -> [a])
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Bool)
-> ((a, a) -> Int)
-> ((a, a) -> Int)
-> Ix a
forall {f :: Type -> Type} {a}. Ix (f a) => Ord (Point f a)
forall (f :: Type -> Type) a.
Ix (f a) =>
(Point f a, Point f a) -> Int
forall (f :: Type -> Type) a.
Ix (f a) =>
(Point f a, Point f a) -> [Point f a]
forall (f :: Type -> Type) a.
Ix (f a) =>
(Point f a, Point f a) -> Point f a -> Bool
forall (f :: Type -> Type) a.
Ix (f a) =>
(Point f a, Point f a) -> Point f a -> Int
unsafeRangeSize :: (Point f a, Point f a) -> Int
$cunsafeRangeSize :: forall (f :: Type -> Type) a.
Ix (f a) =>
(Point f a, Point f a) -> Int
rangeSize :: (Point f a, Point f a) -> Int
$crangeSize :: forall (f :: Type -> Type) a.
Ix (f a) =>
(Point f a, Point f a) -> Int
inRange :: (Point f a, Point f a) -> Point f a -> Bool
$cinRange :: forall (f :: Type -> Type) a.
Ix (f a) =>
(Point f a, Point f a) -> Point f a -> Bool
unsafeIndex :: (Point f a, Point f a) -> Point f a -> Int
$cunsafeIndex :: forall (f :: Type -> Type) a.
Ix (f a) =>
(Point f a, Point f a) -> Point f a -> Int
index :: (Point f a, Point f a) -> Point f a -> Int
$cindex :: forall (f :: Type -> Type) a.
Ix (f a) =>
(Point f a, Point f a) -> Point f a -> Int
range :: (Point f a, Point f a) -> [Point f a]
$crange :: forall (f :: Type -> Type) a.
Ix (f a) =>
(Point f a, Point f a) -> [Point f a]
Ix, Ptr (Point f a) -> IO (Point f a)
Ptr (Point f a) -> Int -> IO (Point f a)
Ptr (Point f a) -> Int -> Point f a -> IO ()
Ptr (Point f a) -> Point f a -> IO ()
Point f a -> Int
forall b. Ptr b -> Int -> IO (Point f a)
forall b. Ptr b -> Int -> Point f a -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
forall (f :: Type -> Type) a.
Storable (f a) =>
Ptr (Point f a) -> IO (Point f a)
forall (f :: Type -> Type) a.
Storable (f a) =>
Ptr (Point f a) -> Int -> IO (Point f a)
forall (f :: Type -> Type) a.
Storable (f a) =>
Ptr (Point f a) -> Int -> Point f a -> IO ()
forall (f :: Type -> Type) a.
Storable (f a) =>
Ptr (Point f a) -> Point f a -> IO ()
forall (f :: Type -> Type) a. Storable (f a) => Point f a -> Int
forall (f :: Type -> Type) a b.
Storable (f a) =>
Ptr b -> Int -> IO (Point f a)
forall (f :: Type -> Type) a b.
Storable (f a) =>
Ptr b -> Int -> Point f a -> IO ()
poke :: Ptr (Point f a) -> Point f a -> IO ()
$cpoke :: forall (f :: Type -> Type) a.
Storable (f a) =>
Ptr (Point f a) -> Point f a -> IO ()
peek :: Ptr (Point f a) -> IO (Point f a)
$cpeek :: forall (f :: Type -> Type) a.
Storable (f a) =>
Ptr (Point f a) -> IO (Point f a)
pokeByteOff :: forall b. Ptr b -> Int -> Point f a -> IO ()
$cpokeByteOff :: forall (f :: Type -> Type) a b.
Storable (f a) =>
Ptr b -> Int -> Point f a -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO (Point f a)
$cpeekByteOff :: forall (f :: Type -> Type) a b.
Storable (f a) =>
Ptr b -> Int -> IO (Point f a)
pokeElemOff :: Ptr (Point f a) -> Int -> Point f a -> IO ()
$cpokeElemOff :: forall (f :: Type -> Type) a.
Storable (f a) =>
Ptr (Point f a) -> Int -> Point f a -> IO ()
peekElemOff :: Ptr (Point f a) -> Int -> IO (Point f a)
$cpeekElemOff :: forall (f :: Type -> Type) a.
Storable (f a) =>
Ptr (Point f a) -> Int -> IO (Point f a)
alignment :: Point f a -> Int
$calignment :: forall (f :: Type -> Type) a. Storable (f a) => Point f a -> Int
sizeOf :: Point f a -> Int
$csizeOf :: forall (f :: Type -> Type) a. Storable (f a) => Point f a -> Int
Storable, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: Type -> Type) a x. Rep (Point f a) x -> Point f a
forall (f :: Type -> Type) a x. Point f a -> Rep (Point f a) x
$cto :: forall (f :: Type -> Type) a x. Rep (Point f a) x -> Point f a
$cfrom :: forall (f :: Type -> Type) a x. Point f a -> Rep (Point f a) x
Generic, forall k (f :: k -> Type).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
forall (f :: Type -> Type) a. Rep1 (Point f) a -> Point f a
forall (f :: Type -> Type) a. Point f a -> Rep1 (Point f) a
$cto1 :: forall (f :: Type -> Type) a. Rep1 (Point f) a -> Point f a
$cfrom1 :: forall (f :: Type -> Type) a. Point f a -> Rep1 (Point f) a
Generic1
           , Typeable, Point f a -> DataType
Point f a -> Constr
forall a.
Typeable a
-> (forall (c :: Type -> Type).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Point f a)
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Point f a -> c (Point f a)
forall {f :: Type -> Type} {a}.
(Typeable f, Typeable a, Data (f a)) =>
Typeable (Point f a)
forall (f :: Type -> Type) a.
(Typeable f, Typeable a, Data (f a)) =>
Point f a -> DataType
forall (f :: Type -> Type) a.
(Typeable f, Typeable a, Data (f a)) =>
Point f a -> Constr
forall (f :: Type -> Type) a.
(Typeable f, Typeable a, Data (f a)) =>
(forall b. Data b => b -> b) -> Point f a -> Point f a
forall (f :: Type -> Type) a u.
(Typeable f, Typeable a, Data (f a)) =>
Int -> (forall d. Data d => d -> u) -> Point f a -> u
forall (f :: Type -> Type) a u.
(Typeable f, Typeable a, Data (f a)) =>
(forall d. Data d => d -> u) -> Point f a -> [u]
forall (f :: Type -> Type) a r r'.
(Typeable f, Typeable a, Data (f a)) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Point f a -> r
forall (f :: Type -> Type) a r r'.
(Typeable f, Typeable a, Data (f a)) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Point f a -> r
forall (f :: Type -> Type) a (m :: Type -> Type).
(Typeable f, Typeable a, Data (f a), Monad m) =>
(forall d. Data d => d -> m d) -> Point f a -> m (Point f a)
forall (f :: Type -> Type) a (m :: Type -> Type).
(Typeable f, Typeable a, Data (f a), MonadPlus m) =>
(forall d. Data d => d -> m d) -> Point f a -> m (Point f a)
forall (f :: Type -> Type) a (c :: Type -> Type).
(Typeable f, Typeable a, Data (f a)) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Point f a)
forall (f :: Type -> Type) a (c :: Type -> Type).
(Typeable f, Typeable a, Data (f a)) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Point f a -> c (Point f a)
forall (f :: Type -> Type) a (t :: Type -> Type)
       (c :: Type -> Type).
(Typeable f, Typeable a, Data (f a), Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Point f a))
forall (f :: Type -> Type) a (t :: Type -> Type -> Type)
       (c :: Type -> Type).
(Typeable f, Typeable a, Data (f a), Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Point f a))
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Point f a -> m (Point f a)
$cgmapMo :: forall (f :: Type -> Type) a (m :: Type -> Type).
(Typeable f, Typeable a, Data (f a), MonadPlus m) =>
(forall d. Data d => d -> m d) -> Point f a -> m (Point f a)
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Point f a -> m (Point f a)
$cgmapMp :: forall (f :: Type -> Type) a (m :: Type -> Type).
(Typeable f, Typeable a, Data (f a), MonadPlus m) =>
(forall d. Data d => d -> m d) -> Point f a -> m (Point f a)
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> Point f a -> m (Point f a)
$cgmapM :: forall (f :: Type -> Type) a (m :: Type -> Type).
(Typeable f, Typeable a, Data (f a), Monad m) =>
(forall d. Data d => d -> m d) -> Point f a -> m (Point f a)
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Point f a -> u
$cgmapQi :: forall (f :: Type -> Type) a u.
(Typeable f, Typeable a, Data (f a)) =>
Int -> (forall d. Data d => d -> u) -> Point f a -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Point f a -> [u]
$cgmapQ :: forall (f :: Type -> Type) a u.
(Typeable f, Typeable a, Data (f a)) =>
(forall d. Data d => d -> u) -> Point f a -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Point f a -> r
$cgmapQr :: forall (f :: Type -> Type) a r r'.
(Typeable f, Typeable a, Data (f a)) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Point f a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Point f a -> r
$cgmapQl :: forall (f :: Type -> Type) a r r'.
(Typeable f, Typeable a, Data (f a)) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Point f a -> r
gmapT :: (forall b. Data b => b -> b) -> Point f a -> Point f a
$cgmapT :: forall (f :: Type -> Type) a.
(Typeable f, Typeable a, Data (f a)) =>
(forall b. Data b => b -> b) -> Point f a -> Point f a
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Point f a))
$cdataCast2 :: forall (f :: Type -> Type) a (t :: Type -> Type -> Type)
       (c :: Type -> Type).
(Typeable f, Typeable a, Data (f a), Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Point f a))
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Point f a))
$cdataCast1 :: forall (f :: Type -> Type) a (t :: Type -> Type)
       (c :: Type -> Type).
(Typeable f, Typeable a, Data (f a), Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Point f a))
dataTypeOf :: Point f a -> DataType
$cdataTypeOf :: forall (f :: Type -> Type) a.
(Typeable f, Typeable a, Data (f a)) =>
Point f a -> DataType
toConstr :: Point f a -> Constr
$ctoConstr :: forall (f :: Type -> Type) a.
(Typeable f, Typeable a, Data (f a)) =>
Point f a -> Constr
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Point f a)
$cgunfold :: forall (f :: Type -> Type) a (c :: Type -> Type).
(Typeable f, Typeable a, Data (f a)) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Point f a)
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Point f a -> c (Point f a)
$cgfoldl :: forall (f :: Type -> Type) a (c :: Type -> Type).
(Typeable f, Typeable a, Data (f a)) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Point f a -> c (Point f a)
Data
           )

data instance U.Vector    (Point f a) =  V_P !(U.Vector    (f a))
data instance U.MVector s (Point f a) = MV_P !(U.MVector s (f a))
instance U.Unbox (f a) => U.Unbox (Point f a)

instance U.Unbox (f a) => M.MVector U.MVector (Point f a) where
  {-# INLINE basicLength #-}
  {-# INLINE basicUnsafeSlice #-}
  {-# INLINE basicOverlaps #-}
  {-# INLINE basicUnsafeNew #-}
  {-# INLINE basicUnsafeRead #-}
  {-# INLINE basicUnsafeWrite #-}
  basicLength :: forall s. MVector s (Point f a) -> Int
basicLength (MV_P MVector s (f a)
v) = forall (v :: Type -> Type -> Type) a s. MVector v a => v s a -> Int
M.basicLength MVector s (f a)
v
  basicUnsafeSlice :: forall s.
Int -> Int -> MVector s (Point f a) -> MVector s (Point f a)
basicUnsafeSlice Int
m Int
n (MV_P MVector s (f a)
v) = forall s (f :: Type -> Type) a.
MVector s (f a) -> MVector s (Point f a)
MV_P (forall (v :: Type -> Type -> Type) a s.
MVector v a =>
Int -> Int -> v s a -> v s a
M.basicUnsafeSlice Int
m Int
n MVector s (f a)
v)
  basicOverlaps :: forall s. MVector s (Point f a) -> MVector s (Point f a) -> Bool
basicOverlaps (MV_P MVector s (f a)
v) (MV_P MVector s (f a)
u) = forall (v :: Type -> Type -> Type) a s.
MVector v a =>
v s a -> v s a -> Bool
M.basicOverlaps MVector s (f a)
v MVector s (f a)
u
  basicUnsafeNew :: forall (m :: Type -> Type).
PrimMonad m =>
Int -> m (MVector (PrimState m) (Point f a))
basicUnsafeNew Int
n = forall s (f :: Type -> Type) a.
MVector s (f a) -> MVector s (Point f a)
MV_P forall (m :: Type -> Type) a1 r.
Monad m =>
(a1 -> r) -> m a1 -> m r
`liftM` forall (v :: Type -> Type -> Type) a (m :: Type -> Type).
(MVector v a, PrimMonad m) =>
Int -> m (v (PrimState m) a)
M.basicUnsafeNew Int
n
  basicUnsafeRead :: forall (m :: Type -> Type).
PrimMonad m =>
MVector (PrimState m) (Point f a) -> Int -> m (Point f a)
basicUnsafeRead (MV_P MVector (PrimState m) (f a)
v) Int
i = forall (f :: Type -> Type) a. f a -> Point f a
P forall (m :: Type -> Type) a1 r.
Monad m =>
(a1 -> r) -> m a1 -> m r
`liftM` forall (v :: Type -> Type -> Type) a (m :: Type -> Type).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m a
M.basicUnsafeRead MVector (PrimState m) (f a)
v Int
i
  basicUnsafeWrite :: forall (m :: Type -> Type).
PrimMonad m =>
MVector (PrimState m) (Point f a) -> Int -> Point f a -> m ()
basicUnsafeWrite (MV_P MVector (PrimState m) (f a)
v) Int
i (P f a
x) = forall (v :: Type -> Type -> Type) a (m :: Type -> Type).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> a -> m ()
M.basicUnsafeWrite MVector (PrimState m) (f a)
v Int
i f a
x
#if MIN_VERSION_vector(0,11,0)
  basicInitialize :: forall (m :: Type -> Type).
PrimMonad m =>
MVector (PrimState m) (Point f a) -> m ()
basicInitialize (MV_P MVector (PrimState m) (f a)
v) = forall (v :: Type -> Type -> Type) a (m :: Type -> Type).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> m ()
M.basicInitialize MVector (PrimState m) (f a)
v
  {-# INLINE basicInitialize #-}
#endif

instance U.Unbox (f a) => G.Vector U.Vector (Point f a) where
  {-# INLINE basicUnsafeFreeze #-}
  {-# INLINE basicUnsafeThaw   #-}
  {-# INLINE basicLength       #-}
  {-# INLINE basicUnsafeSlice  #-}
  {-# INLINE basicUnsafeIndexM #-}
  basicUnsafeFreeze :: forall (m :: Type -> Type).
PrimMonad m =>
Mutable Vector (PrimState m) (Point f a) -> m (Vector (Point f a))
basicUnsafeFreeze (MV_P MVector (PrimState m) (f a)
v) = forall (f :: Type -> Type) a. Vector (f a) -> Vector (Point f a)
V_P forall (m :: Type -> Type) a1 r.
Monad m =>
(a1 -> r) -> m a1 -> m r
`liftM` forall (v :: Type -> Type) a (m :: Type -> Type).
(Vector v a, PrimMonad m) =>
Mutable v (PrimState m) a -> m (v a)
G.basicUnsafeFreeze MVector (PrimState m) (f a)
v
  basicUnsafeThaw :: forall (m :: Type -> Type).
PrimMonad m =>
Vector (Point f a) -> m (Mutable Vector (PrimState m) (Point f a))
basicUnsafeThaw   ( V_P Vector (f a)
v) = forall s (f :: Type -> Type) a.
MVector s (f a) -> MVector s (Point f a)
MV_P forall (m :: Type -> Type) a1 r.
Monad m =>
(a1 -> r) -> m a1 -> m r
`liftM` forall (v :: Type -> Type) a (m :: Type -> Type).
(Vector v a, PrimMonad m) =>
v a -> m (Mutable v (PrimState m) a)
G.basicUnsafeThaw   Vector (f a)
v
  basicLength :: Vector (Point f a) -> Int
basicLength       ( V_P Vector (f a)
v) = forall (v :: Type -> Type) a. Vector v a => v a -> Int
G.basicLength Vector (f a)
v
  basicUnsafeSlice :: Int -> Int -> Vector (Point f a) -> Vector (Point f a)
basicUnsafeSlice Int
m Int
n (V_P Vector (f a)
v) = forall (f :: Type -> Type) a. Vector (f a) -> Vector (Point f a)
V_P (forall (v :: Type -> Type) a.
Vector v a =>
Int -> Int -> v a -> v a
G.basicUnsafeSlice Int
m Int
n Vector (f a)
v)
  basicUnsafeIndexM :: forall (m :: Type -> Type).
Monad m =>
Vector (Point f a) -> Int -> m (Point f a)
basicUnsafeIndexM (V_P Vector (f a)
v) Int
i = forall (f :: Type -> Type) a. f a -> Point f a
P forall (m :: Type -> Type) a1 r.
Monad m =>
(a1 -> r) -> m a1 -> m r
`liftM` forall (v :: Type -> Type) a (m :: Type -> Type).
(Vector v a, Monad m) =>
v a -> Int -> m a
G.basicUnsafeIndexM Vector (f a)
v Int
i


-- | A 2-dimensional vector
--
-- >>> pure 1 :: V2 Int
-- V2 1 1
--
-- >>> V2 1 2 + V2 3 4
-- V2 4 6
--
-- >>> V2 1 2 * V2 3 4
-- V2 3 8
--
-- >>> sum (V2 1 2)
-- 3
data V2 a = V2 !a !a
  deriving (V2 a -> V2 a -> Bool
forall a. Eq a => V2 a -> V2 a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: V2 a -> V2 a -> Bool
$c/= :: forall a. Eq a => V2 a -> V2 a -> Bool
== :: V2 a -> V2 a -> Bool
$c== :: forall a. Eq a => V2 a -> V2 a -> Bool
Eq, V2 a -> V2 a -> Bool
V2 a -> V2 a -> Ordering
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
forall {a}. Ord a => Eq (V2 a)
forall a. Ord a => V2 a -> V2 a -> Bool
forall a. Ord a => V2 a -> V2 a -> Ordering
forall a. Ord a => V2 a -> V2 a -> V2 a
min :: V2 a -> V2 a -> V2 a
$cmin :: forall a. Ord a => V2 a -> V2 a -> V2 a
max :: V2 a -> V2 a -> V2 a
$cmax :: forall a. Ord a => V2 a -> V2 a -> V2 a
>= :: V2 a -> V2 a -> Bool
$c>= :: forall a. Ord a => V2 a -> V2 a -> Bool
> :: V2 a -> V2 a -> Bool
$c> :: forall a. Ord a => V2 a -> V2 a -> Bool
<= :: V2 a -> V2 a -> Bool
$c<= :: forall a. Ord a => V2 a -> V2 a -> Bool
< :: V2 a -> V2 a -> Bool
$c< :: forall a. Ord a => V2 a -> V2 a -> Bool
compare :: V2 a -> V2 a -> Ordering
$ccompare :: forall a. Ord a => V2 a -> V2 a -> Ordering
Ord, Int -> V2 a -> ShowS
forall a. Show a => Int -> V2 a -> ShowS
forall a. Show a => [V2 a] -> ShowS
forall a. Show a => V2 a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [V2 a] -> ShowS
$cshowList :: forall a. Show a => [V2 a] -> ShowS
show :: V2 a -> String
$cshow :: forall a. Show a => V2 a -> String
showsPrec :: Int -> V2 a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> V2 a -> ShowS
Show, ReadPrec [V2 a]
ReadPrec (V2 a)
ReadS [V2 a]
forall a. Read a => ReadPrec [V2 a]
forall a. Read a => ReadPrec (V2 a)
forall a. Read a => Int -> ReadS (V2 a)
forall a. Read a => ReadS [V2 a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [V2 a]
$creadListPrec :: forall a. Read a => ReadPrec [V2 a]
readPrec :: ReadPrec (V2 a)
$creadPrec :: forall a. Read a => ReadPrec (V2 a)
readList :: ReadS [V2 a]
$creadList :: forall a. Read a => ReadS [V2 a]
readsPrec :: Int -> ReadS (V2 a)
$creadsPrec :: forall a. Read a => Int -> ReadS (V2 a)
Read, V2 a -> DataType
V2 a -> Constr
forall {a}. Data a => Typeable (V2 a)
forall a. Data a => V2 a -> DataType
forall a. Data a => V2 a -> Constr
forall a. Data a => (forall b. Data b => b -> b) -> V2 a -> V2 a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> V2 a -> u
forall a u. Data a => (forall d. Data d => d -> u) -> V2 a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V2 a -> r
forall a r r'.
Data a =>
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V2 a -> r
forall a (m :: Type -> Type).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> V2 a -> m (V2 a)
forall a (m :: Type -> Type).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> V2 a -> m (V2 a)
forall a (c :: Type -> Type).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (V2 a)
forall a (c :: Type -> Type).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> V2 a -> c (V2 a)
forall a (t :: Type -> Type) (c :: Type -> Type).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (V2 a))
forall a (t :: Type -> Type -> Type) (c :: Type -> Type).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V2 a))
forall a.
Typeable a
-> (forall (c :: Type -> Type).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (V2 a)
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> V2 a -> c (V2 a)
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (V2 a))
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> V2 a -> m (V2 a)
$cgmapMo :: forall a (m :: Type -> Type).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> V2 a -> m (V2 a)
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> V2 a -> m (V2 a)
$cgmapMp :: forall a (m :: Type -> Type).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> V2 a -> m (V2 a)
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> V2 a -> m (V2 a)
$cgmapM :: forall a (m :: Type -> Type).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> V2 a -> m (V2 a)
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> V2 a -> u
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> V2 a -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> V2 a -> [u]
$cgmapQ :: forall a u. Data a => (forall d. Data d => d -> u) -> V2 a -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V2 a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V2 a -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V2 a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V2 a -> r
gmapT :: (forall b. Data b => b -> b) -> V2 a -> V2 a
$cgmapT :: forall a. Data a => (forall b. Data b => b -> b) -> V2 a -> V2 a
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V2 a))
$cdataCast2 :: forall a (t :: Type -> Type -> Type) (c :: Type -> Type).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V2 a))
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (V2 a))
$cdataCast1 :: forall a (t :: Type -> Type) (c :: Type -> Type).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (V2 a))
dataTypeOf :: V2 a -> DataType
$cdataTypeOf :: forall a. Data a => V2 a -> DataType
toConstr :: V2 a -> Constr
$ctoConstr :: forall a. Data a => V2 a -> Constr
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (V2 a)
$cgunfold :: forall a (c :: Type -> Type).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (V2 a)
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> V2 a -> c (V2 a)
$cgfoldl :: forall a (c :: Type -> Type).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> V2 a -> c (V2 a)
Data, Typeable, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (V2 a) x -> V2 a
forall a x. V2 a -> Rep (V2 a) x
$cto :: forall a x. Rep (V2 a) x -> V2 a
$cfrom :: forall a x. V2 a -> Rep (V2 a) x
Generic, forall a. Rep1 V2 a -> V2 a
forall a. V2 a -> Rep1 V2 a
forall k (f :: k -> Type).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cto1 :: forall a. Rep1 V2 a -> V2 a
$cfrom1 :: forall a. V2 a -> Rep1 V2 a
Generic1)

instance Functor V2 where
  fmap :: forall a b. (a -> b) -> V2 a -> V2 b
fmap a -> b
f (V2 a
a a
b) = forall a. a -> a -> V2 a
V2 (a -> b
f a
a) (a -> b
f a
b)
  {-# INLINE fmap #-}
  a
a <$ :: forall a b. a -> V2 b -> V2 a
<$ V2 b
_ = forall a. a -> a -> V2 a
V2 a
a a
a
  {-# INLINE (<$) #-}

instance Foldable V2 where
  foldMap :: forall m a. Monoid m => (a -> m) -> V2 a -> m
foldMap a -> m
f (V2 a
a a
b) = a -> m
f a
a forall a. Monoid a => a -> a -> a
`mappend` a -> m
f a
b
  {-# INLINE foldMap #-}

instance Traversable V2 where
  traverse :: forall (f :: Type -> Type) a b.
Applicative f =>
(a -> f b) -> V2 a -> f (V2 b)
traverse a -> f b
f (V2 a
a a
b) = forall a. a -> a -> V2 a
V2 forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> a -> f b
f a
b
  {-# INLINE traverse #-}

instance Applicative V2 where
  pure :: forall a. a -> V2 a
pure a
a = forall a. a -> a -> V2 a
V2 a
a a
a
  {-# INLINE pure #-}
  V2 a -> b
a a -> b
b <*> :: forall a b. V2 (a -> b) -> V2 a -> V2 b
<*> V2 a
d a
e = forall a. a -> a -> V2 a
V2 (a -> b
a a
d) (a -> b
b a
e)
  {-# INLINE (<*>) #-}

instance Monad V2 where
  return :: forall a. a -> V2 a
return = forall (f :: Type -> Type) a. Applicative f => a -> f a
pure
  {-# INLINE return #-}
  V2 a
a a
b >>= :: forall a b. V2 a -> (a -> V2 b) -> V2 b
>>= a -> V2 b
f = forall a. a -> a -> V2 a
V2 b
a' b
b' where
    V2 b
a' b
_ = a -> V2 b
f a
a
    V2 b
_ b
b' = a -> V2 b
f a
b
  {-# INLINE (>>=) #-}

instance Num a => Num (V2 a) where
  + :: V2 a -> V2 a -> V2 a
(+) = forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 forall a. Num a => a -> a -> a
(+)
  {-# INLINE (+) #-}
  (-) = forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (-)
  {-# INLINE (-) #-}
  * :: V2 a -> V2 a -> V2 a
(*) = forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 forall a. Num a => a -> a -> a
(*)
  {-# INLINE (*) #-}
  negate :: V2 a -> V2 a
negate = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Num a => a -> a
negate
  {-# INLINE negate #-}
  abs :: V2 a -> V2 a
abs = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Num a => a -> a
abs
  {-# INLINE abs #-}
  signum :: V2 a -> V2 a
signum = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Num a => a -> a
signum
  {-# INLINE signum #-}
  fromInteger :: Integer -> V2 a
fromInteger = forall (f :: Type -> Type) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Num a => Integer -> a
fromInteger
  {-# INLINE fromInteger #-}

instance Fractional a => Fractional (V2 a) where
  recip :: V2 a -> V2 a
recip = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Fractional a => a -> a
recip
  {-# INLINE recip #-}
  / :: V2 a -> V2 a -> V2 a
(/) = forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 forall a. Fractional a => a -> a -> a
(/)
  {-# INLINE (/) #-}
  fromRational :: Rational -> V2 a
fromRational = forall (f :: Type -> Type) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Fractional a => Rational -> a
fromRational
  {-# INLINE fromRational #-}

instance Floating a => Floating (V2 a) where
    pi :: V2 a
pi = forall (f :: Type -> Type) a. Applicative f => a -> f a
pure forall a. Floating a => a
pi
    {-# INLINE pi #-}
    exp :: V2 a -> V2 a
exp = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
exp
    {-# INLINE exp #-}
    sqrt :: V2 a -> V2 a
sqrt = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
sqrt
    {-# INLINE sqrt #-}
    log :: V2 a -> V2 a
log = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
log
    {-# INLINE log #-}
    ** :: V2 a -> V2 a -> V2 a
(**) = forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 forall a. Floating a => a -> a -> a
(**)
    {-# INLINE (**) #-}
    logBase :: V2 a -> V2 a -> V2 a
logBase = forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 forall a. Floating a => a -> a -> a
logBase
    {-# INLINE logBase #-}
    sin :: V2 a -> V2 a
sin = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
sin
    {-# INLINE sin #-}
    tan :: V2 a -> V2 a
tan = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
tan
    {-# INLINE tan #-}
    cos :: V2 a -> V2 a
cos = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
cos
    {-# INLINE cos #-}
    asin :: V2 a -> V2 a
asin = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
asin
    {-# INLINE asin #-}
    atan :: V2 a -> V2 a
atan = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
atan
    {-# INLINE atan #-}
    acos :: V2 a -> V2 a
acos = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
acos
    {-# INLINE acos #-}
    sinh :: V2 a -> V2 a
sinh = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
sinh
    {-# INLINE sinh #-}
    tanh :: V2 a -> V2 a
tanh = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
tanh
    {-# INLINE tanh #-}
    cosh :: V2 a -> V2 a
cosh = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
cosh
    {-# INLINE cosh #-}
    asinh :: V2 a -> V2 a
asinh = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
asinh
    {-# INLINE asinh #-}
    atanh :: V2 a -> V2 a
atanh = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
atanh
    {-# INLINE atanh #-}
    acosh :: V2 a -> V2 a
acosh = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
acosh
    {-# INLINE acosh #-}

instance Storable a => Storable (V2 a) where
  sizeOf :: V2 a -> Int
sizeOf V2 a
_ = Int
2 forall a. Num a => a -> a -> a
* forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined::a)
  {-# INLINE sizeOf #-}
  alignment :: V2 a -> Int
alignment V2 a
_ = forall a. Storable a => a -> Int
alignment (forall a. HasCallStack => a
undefined::a)
  {-# INLINE alignment #-}
  poke :: Ptr (V2 a) -> V2 a -> IO ()
poke Ptr (V2 a)
ptr (V2 a
x a
y) = forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr a
ptr' a
x forall (m :: Type -> Type) a b. Monad m => m a -> m b -> m b
>> forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr a
ptr' Int
1 a
y
    where ptr' :: Ptr a
ptr' = forall a b. Ptr a -> Ptr b
castPtr Ptr (V2 a)
ptr
  {-# INLINE poke #-}
  peek :: Ptr (V2 a) -> IO (V2 a)
peek Ptr (V2 a)
ptr = forall a. a -> a -> V2 a
V2 forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Storable a => Ptr a -> IO a
peek Ptr a
ptr' forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr a
ptr' Int
1
    where ptr' :: Ptr a
ptr' = forall a b. Ptr a -> Ptr b
castPtr Ptr (V2 a)
ptr
  {-# INLINE peek #-}

instance Ix a => Ix (V2 a) where
  {-# SPECIALISE instance Ix (V2 Int) #-}

  range :: (V2 a, V2 a) -> [V2 a]
range (V2 a
l1 a
l2,V2 a
u1 a
u2) =
    [ forall a. a -> a -> V2 a
V2 a
i1 a
i2 | a
i1 <- forall a. Ix a => (a, a) -> [a]
range (a
l1,a
u1), a
i2 <- forall a. Ix a => (a, a) -> [a]
range (a
l2,a
u2) ]
  {-# INLINE range #-}

  unsafeIndex :: (V2 a, V2 a) -> V2 a -> Int
unsafeIndex (V2 a
l1 a
l2,V2 a
u1 a
u2) (V2 a
i1 a
i2) =
    forall a. Ix a => (a, a) -> a -> Int
unsafeIndex (a
l1,a
u1) a
i1 forall a. Num a => a -> a -> a
* forall a. Ix a => (a, a) -> Int
unsafeRangeSize (a
l2,a
u2) forall a. Num a => a -> a -> a
+ forall a. Ix a => (a, a) -> a -> Int
unsafeIndex (a
l2,a
u2) a
i2
  {-# INLINE unsafeIndex #-}

  inRange :: (V2 a, V2 a) -> V2 a -> Bool
inRange (V2 a
l1 a
l2,V2 a
u1 a
u2) (V2 a
i1 a
i2) =
    forall a. Ix a => (a, a) -> a -> Bool
inRange (a
l1,a
u1) a
i1 Bool -> Bool -> Bool
&& forall a. Ix a => (a, a) -> a -> Bool
inRange (a
l2,a
u2) a
i2
  {-# INLINE inRange #-}

data instance U.Vector    (V2 a) =  V_V2 {-# UNPACK #-} !Int !(U.Vector    a)
data instance U.MVector s (V2 a) = MV_V2 {-# UNPACK #-} !Int !(U.MVector s a)
instance U.Unbox a => U.Unbox (V2 a)

instance U.Unbox a => M.MVector U.MVector (V2 a) where
  {-# INLINE basicLength #-}
  {-# INLINE basicUnsafeSlice #-}
  {-# INLINE basicOverlaps #-}
  {-# INLINE basicUnsafeNew #-}
  {-# INLINE basicUnsafeRead #-}
  {-# INLINE basicUnsafeWrite #-}
  basicLength :: forall s. MVector s (V2 a) -> Int
basicLength (MV_V2 Int
n MVector s a
_) = Int
n
  basicUnsafeSlice :: forall s. Int -> Int -> MVector s (V2 a) -> MVector s (V2 a)
basicUnsafeSlice Int
m Int
n (MV_V2 Int
_ MVector s a
v) = forall s a. Int -> MVector s a -> MVector s (V2 a)
MV_V2 Int
n (forall (v :: Type -> Type -> Type) a s.
MVector v a =>
Int -> Int -> v s a -> v s a
M.basicUnsafeSlice (Int
2forall a. Num a => a -> a -> a
*Int
m) (Int
2forall a. Num a => a -> a -> a
*Int
n) MVector s a
v)
  basicOverlaps :: forall s. MVector s (V2 a) -> MVector s (V2 a) -> Bool
basicOverlaps (MV_V2 Int
_ MVector s a
v) (MV_V2 Int
_ MVector s a
u) = forall (v :: Type -> Type -> Type) a s.
MVector v a =>
v s a -> v s a -> Bool
M.basicOverlaps MVector s a
v MVector s a
u
  basicUnsafeNew :: forall (m :: Type -> Type).
PrimMonad m =>
Int -> m (MVector (PrimState m) (V2 a))
basicUnsafeNew Int
n = forall (m :: Type -> Type) a1 r.
Monad m =>
(a1 -> r) -> m a1 -> m r
liftM (forall s a. Int -> MVector s a -> MVector s (V2 a)
MV_V2 Int
n) (forall (v :: Type -> Type -> Type) a (m :: Type -> Type).
(MVector v a, PrimMonad m) =>
Int -> m (v (PrimState m) a)
M.basicUnsafeNew (Int
2forall a. Num a => a -> a -> a
*Int
n))
  basicUnsafeRead :: forall (m :: Type -> Type).
PrimMonad m =>
MVector (PrimState m) (V2 a) -> Int -> m (V2 a)
basicUnsafeRead (MV_V2 Int
_ MVector (PrimState m) a
v) Int
i =
    do let o :: Int
o = Int
2forall a. Num a => a -> a -> a
*Int
i
       a
x <- forall (v :: Type -> Type -> Type) a (m :: Type -> Type).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m a
M.basicUnsafeRead MVector (PrimState m) a
v Int
o
       a
y <- forall (v :: Type -> Type -> Type) a (m :: Type -> Type).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m a
M.basicUnsafeRead MVector (PrimState m) a
v (Int
oforall a. Num a => a -> a -> a
+Int
1)
       forall (m :: Type -> Type) a. Monad m => a -> m a
return (forall a. a -> a -> V2 a
V2 a
x a
y)
  basicUnsafeWrite :: forall (m :: Type -> Type).
PrimMonad m =>
MVector (PrimState m) (V2 a) -> Int -> V2 a -> m ()
basicUnsafeWrite (MV_V2 Int
_ MVector (PrimState m) a
v) Int
i (V2 a
x a
y) =
    do let o :: Int
o = Int
2forall a. Num a => a -> a -> a
*Int
i
       forall (v :: Type -> Type -> Type) a (m :: Type -> Type).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> a -> m ()
M.basicUnsafeWrite MVector (PrimState m) a
v Int
o     a
x
       forall (v :: Type -> Type -> Type) a (m :: Type -> Type).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> a -> m ()
M.basicUnsafeWrite MVector (PrimState m) a
v (Int
oforall a. Num a => a -> a -> a
+Int
1) a
y
#if MIN_VERSION_vector(0,11,0)
  basicInitialize :: forall (m :: Type -> Type).
PrimMonad m =>
MVector (PrimState m) (V2 a) -> m ()
basicInitialize (MV_V2 Int
_ MVector (PrimState m) a
v) = forall (v :: Type -> Type -> Type) a (m :: Type -> Type).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> m ()
M.basicInitialize MVector (PrimState m) a
v
  {-# INLINE basicInitialize #-}
#endif

instance U.Unbox a => G.Vector U.Vector (V2 a) where
  {-# INLINE basicUnsafeFreeze #-}
  {-# INLINE basicUnsafeThaw   #-}
  {-# INLINE basicLength       #-}
  {-# INLINE basicUnsafeSlice  #-}
  {-# INLINE basicUnsafeIndexM #-}
  basicUnsafeFreeze :: forall (m :: Type -> Type).
PrimMonad m =>
Mutable Vector (PrimState m) (V2 a) -> m (Vector (V2 a))
basicUnsafeFreeze (MV_V2 Int
n MVector (PrimState m) a
v) = forall (m :: Type -> Type) a1 r.
Monad m =>
(a1 -> r) -> m a1 -> m r
liftM ( forall a. Int -> Vector a -> Vector (V2 a)
V_V2 Int
n) (forall (v :: Type -> Type) a (m :: Type -> Type).
(Vector v a, PrimMonad m) =>
Mutable v (PrimState m) a -> m (v a)
G.basicUnsafeFreeze MVector (PrimState m) a
v)
  basicUnsafeThaw :: forall (m :: Type -> Type).
PrimMonad m =>
Vector (V2 a) -> m (Mutable Vector (PrimState m) (V2 a))
basicUnsafeThaw   ( V_V2 Int
n Vector a
v) = forall (m :: Type -> Type) a1 r.
Monad m =>
(a1 -> r) -> m a1 -> m r
liftM (forall s a. Int -> MVector s a -> MVector s (V2 a)
MV_V2 Int
n) (forall (v :: Type -> Type) a (m :: Type -> Type).
(Vector v a, PrimMonad m) =>
v a -> m (Mutable v (PrimState m) a)
G.basicUnsafeThaw   Vector a
v)
  basicLength :: Vector (V2 a) -> Int
basicLength       ( V_V2 Int
n Vector a
_) = Int
n
  basicUnsafeSlice :: Int -> Int -> Vector (V2 a) -> Vector (V2 a)
basicUnsafeSlice Int
m Int
n (V_V2 Int
_ Vector a
v) = forall a. Int -> Vector a -> Vector (V2 a)
V_V2 Int
n (forall (v :: Type -> Type) a.
Vector v a =>
Int -> Int -> v a -> v a
G.basicUnsafeSlice (Int
2forall a. Num a => a -> a -> a
*Int
m) (Int
2forall a. Num a => a -> a -> a
*Int
n) Vector a
v)
  basicUnsafeIndexM :: forall (m :: Type -> Type).
Monad m =>
Vector (V2 a) -> Int -> m (V2 a)
basicUnsafeIndexM (V_V2 Int
_ Vector a
v) Int
i =
    do let o :: Int
o = Int
2forall a. Num a => a -> a -> a
*Int
i
       a
x <- forall (v :: Type -> Type) a (m :: Type -> Type).
(Vector v a, Monad m) =>
v a -> Int -> m a
G.basicUnsafeIndexM Vector a
v Int
o
       a
y <- forall (v :: Type -> Type) a (m :: Type -> Type).
(Vector v a, Monad m) =>
v a -> Int -> m a
G.basicUnsafeIndexM Vector a
v (Int
oforall a. Num a => a -> a -> a
+Int
1)
       forall (m :: Type -> Type) a. Monad m => a -> m a
return (forall a. a -> a -> V2 a
V2 a
x a
y)

instance MonadZip V2 where
  mzipWith :: forall a b c. (a -> b -> c) -> V2 a -> V2 b -> V2 c
mzipWith = forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2

instance MonadFix V2 where
  mfix :: forall a. (a -> V2 a) -> V2 a
mfix a -> V2 a
f = forall a. a -> a -> V2 a
V2 (let V2 a
a a
_ = a -> V2 a
f a
a in a
a)
              (let V2 a
_ a
a = a -> V2 a
f a
a in a
a)

instance Bounded a => Bounded (V2 a) where
  minBound :: V2 a
minBound = forall (f :: Type -> Type) a. Applicative f => a -> f a
pure forall a. Bounded a => a
minBound
  {-# INLINE minBound #-}
  maxBound :: V2 a
maxBound = forall (f :: Type -> Type) a. Applicative f => a -> f a
pure forall a. Bounded a => a
maxBound
  {-# INLINE maxBound #-}


-- | A 3-dimensional vector
data V3 a = V3 !a !a !a
  deriving (V3 a -> V3 a -> Bool
forall a. Eq a => V3 a -> V3 a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: V3 a -> V3 a -> Bool
$c/= :: forall a. Eq a => V3 a -> V3 a -> Bool
== :: V3 a -> V3 a -> Bool
$c== :: forall a. Eq a => V3 a -> V3 a -> Bool
Eq, V3 a -> V3 a -> Bool
V3 a -> V3 a -> Ordering
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
forall {a}. Ord a => Eq (V3 a)
forall a. Ord a => V3 a -> V3 a -> Bool
forall a. Ord a => V3 a -> V3 a -> Ordering
forall a. Ord a => V3 a -> V3 a -> V3 a
min :: V3 a -> V3 a -> V3 a
$cmin :: forall a. Ord a => V3 a -> V3 a -> V3 a
max :: V3 a -> V3 a -> V3 a
$cmax :: forall a. Ord a => V3 a -> V3 a -> V3 a
>= :: V3 a -> V3 a -> Bool
$c>= :: forall a. Ord a => V3 a -> V3 a -> Bool
> :: V3 a -> V3 a -> Bool
$c> :: forall a. Ord a => V3 a -> V3 a -> Bool
<= :: V3 a -> V3 a -> Bool
$c<= :: forall a. Ord a => V3 a -> V3 a -> Bool
< :: V3 a -> V3 a -> Bool
$c< :: forall a. Ord a => V3 a -> V3 a -> Bool
compare :: V3 a -> V3 a -> Ordering
$ccompare :: forall a. Ord a => V3 a -> V3 a -> Ordering
Ord, Int -> V3 a -> ShowS
forall a. Show a => Int -> V3 a -> ShowS
forall a. Show a => [V3 a] -> ShowS
forall a. Show a => V3 a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [V3 a] -> ShowS
$cshowList :: forall a. Show a => [V3 a] -> ShowS
show :: V3 a -> String
$cshow :: forall a. Show a => V3 a -> String
showsPrec :: Int -> V3 a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> V3 a -> ShowS
Show, ReadPrec [V3 a]
ReadPrec (V3 a)
ReadS [V3 a]
forall a. Read a => ReadPrec [V3 a]
forall a. Read a => ReadPrec (V3 a)
forall a. Read a => Int -> ReadS (V3 a)
forall a. Read a => ReadS [V3 a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [V3 a]
$creadListPrec :: forall a. Read a => ReadPrec [V3 a]
readPrec :: ReadPrec (V3 a)
$creadPrec :: forall a. Read a => ReadPrec (V3 a)
readList :: ReadS [V3 a]
$creadList :: forall a. Read a => ReadS [V3 a]
readsPrec :: Int -> ReadS (V3 a)
$creadsPrec :: forall a. Read a => Int -> ReadS (V3 a)
Read, V3 a -> DataType
V3 a -> Constr
forall {a}. Data a => Typeable (V3 a)
forall a. Data a => V3 a -> DataType
forall a. Data a => V3 a -> Constr
forall a. Data a => (forall b. Data b => b -> b) -> V3 a -> V3 a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> V3 a -> u
forall a u. Data a => (forall d. Data d => d -> u) -> V3 a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V3 a -> r
forall a r r'.
Data a =>
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V3 a -> r
forall a (m :: Type -> Type).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> V3 a -> m (V3 a)
forall a (m :: Type -> Type).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> V3 a -> m (V3 a)
forall a (c :: Type -> Type).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (V3 a)
forall a (c :: Type -> Type).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> V3 a -> c (V3 a)
forall a (t :: Type -> Type) (c :: Type -> Type).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (V3 a))
forall a (t :: Type -> Type -> Type) (c :: Type -> Type).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V3 a))
forall a.
Typeable a
-> (forall (c :: Type -> Type).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (V3 a)
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> V3 a -> c (V3 a)
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (V3 a))
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> V3 a -> m (V3 a)
$cgmapMo :: forall a (m :: Type -> Type).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> V3 a -> m (V3 a)
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> V3 a -> m (V3 a)
$cgmapMp :: forall a (m :: Type -> Type).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> V3 a -> m (V3 a)
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> V3 a -> m (V3 a)
$cgmapM :: forall a (m :: Type -> Type).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> V3 a -> m (V3 a)
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> V3 a -> u
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> V3 a -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> V3 a -> [u]
$cgmapQ :: forall a u. Data a => (forall d. Data d => d -> u) -> V3 a -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V3 a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V3 a -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V3 a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V3 a -> r
gmapT :: (forall b. Data b => b -> b) -> V3 a -> V3 a
$cgmapT :: forall a. Data a => (forall b. Data b => b -> b) -> V3 a -> V3 a
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V3 a))
$cdataCast2 :: forall a (t :: Type -> Type -> Type) (c :: Type -> Type).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V3 a))
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (V3 a))
$cdataCast1 :: forall a (t :: Type -> Type) (c :: Type -> Type).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (V3 a))
dataTypeOf :: V3 a -> DataType
$cdataTypeOf :: forall a. Data a => V3 a -> DataType
toConstr :: V3 a -> Constr
$ctoConstr :: forall a. Data a => V3 a -> Constr
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (V3 a)
$cgunfold :: forall a (c :: Type -> Type).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (V3 a)
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> V3 a -> c (V3 a)
$cgfoldl :: forall a (c :: Type -> Type).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> V3 a -> c (V3 a)
Data, Typeable, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (V3 a) x -> V3 a
forall a x. V3 a -> Rep (V3 a) x
$cto :: forall a x. Rep (V3 a) x -> V3 a
$cfrom :: forall a x. V3 a -> Rep (V3 a) x
Generic, forall a. Rep1 V3 a -> V3 a
forall a. V3 a -> Rep1 V3 a
forall k (f :: k -> Type).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cto1 :: forall a. Rep1 V3 a -> V3 a
$cfrom1 :: forall a. V3 a -> Rep1 V3 a
Generic1)

instance Functor V3 where
  fmap :: forall a b. (a -> b) -> V3 a -> V3 b
fmap a -> b
f (V3 a
a a
b a
c) = forall a. a -> a -> a -> V3 a
V3 (a -> b
f a
a) (a -> b
f a
b) (a -> b
f a
c)
  {-# INLINE fmap #-}
  a
a <$ :: forall a b. a -> V3 b -> V3 a
<$ V3 b
_ = forall a. a -> a -> a -> V3 a
V3 a
a a
a a
a
  {-# INLINE (<$) #-}

instance Foldable V3 where
  foldMap :: forall m a. Monoid m => (a -> m) -> V3 a -> m
foldMap a -> m
f (V3 a
a a
b a
c) = a -> m
f a
a forall a. Monoid a => a -> a -> a
`mappend` a -> m
f a
b forall a. Monoid a => a -> a -> a
`mappend` a -> m
f a
c
  {-# INLINE foldMap #-}

instance Traversable V3 where
  traverse :: forall (f :: Type -> Type) a b.
Applicative f =>
(a -> f b) -> V3 a -> f (V3 b)
traverse a -> f b
f (V3 a
a a
b a
c) = forall a. a -> a -> a -> V3 a
V3 forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> a -> f b
f a
b forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> a -> f b
f a
c
  {-# INLINE traverse #-}

instance Applicative V3 where
  pure :: forall a. a -> V3 a
pure a
a = forall a. a -> a -> a -> V3 a
V3 a
a a
a a
a
  {-# INLINE pure #-}
  V3 a -> b
a a -> b
b a -> b
c <*> :: forall a b. V3 (a -> b) -> V3 a -> V3 b
<*> V3 a
d a
e a
f = forall a. a -> a -> a -> V3 a
V3 (a -> b
a a
d) (a -> b
b a
e) (a -> b
c a
f)
  {-# INLINE (<*>) #-}

instance Monad V3 where
  return :: forall a. a -> V3 a
return = forall (f :: Type -> Type) a. Applicative f => a -> f a
pure
  {-# INLINE return #-}
  V3 a
a a
b a
c >>= :: forall a b. V3 a -> (a -> V3 b) -> V3 b
>>= a -> V3 b
f = forall a. a -> a -> a -> V3 a
V3 b
a' b
b' b
c' where
    V3 b
a' b
_ b
_ = a -> V3 b
f a
a
    V3 b
_ b
b' b
_ = a -> V3 b
f a
b
    V3 b
_ b
_ b
c' = a -> V3 b
f a
c
  {-# INLINE (>>=) #-}

instance Num a => Num (V3 a) where
  + :: V3 a -> V3 a -> V3 a
(+) = forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 forall a. Num a => a -> a -> a
(+)
  {-# INLINE (+) #-}
  (-) = forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (-)
  {-# INLINE (-) #-}
  * :: V3 a -> V3 a -> V3 a
(*) = forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 forall a. Num a => a -> a -> a
(*)
  {-# INLINE (*) #-}
  negate :: V3 a -> V3 a
negate = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Num a => a -> a
negate
  {-# INLINE negate #-}
  abs :: V3 a -> V3 a
abs = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Num a => a -> a
abs
  {-# INLINE abs #-}
  signum :: V3 a -> V3 a
signum = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Num a => a -> a
signum
  {-# INLINE signum #-}
  fromInteger :: Integer -> V3 a
fromInteger = forall (f :: Type -> Type) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Num a => Integer -> a
fromInteger
  {-# INLINE fromInteger #-}

instance Fractional a => Fractional (V3 a) where
  recip :: V3 a -> V3 a
recip = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Fractional a => a -> a
recip
  {-# INLINE recip #-}
  / :: V3 a -> V3 a -> V3 a
(/) = forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 forall a. Fractional a => a -> a -> a
(/)
  {-# INLINE (/) #-}
  fromRational :: Rational -> V3 a
fromRational = forall (f :: Type -> Type) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Fractional a => Rational -> a
fromRational
  {-# INLINE fromRational #-}

instance Floating a => Floating (V3 a) where
    pi :: V3 a
pi = forall (f :: Type -> Type) a. Applicative f => a -> f a
pure forall a. Floating a => a
pi
    {-# INLINE pi #-}
    exp :: V3 a -> V3 a
exp = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
exp
    {-# INLINE exp #-}
    sqrt :: V3 a -> V3 a
sqrt = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
sqrt
    {-# INLINE sqrt #-}
    log :: V3 a -> V3 a
log = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
log
    {-# INLINE log #-}
    ** :: V3 a -> V3 a -> V3 a
(**) = forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 forall a. Floating a => a -> a -> a
(**)
    {-# INLINE (**) #-}
    logBase :: V3 a -> V3 a -> V3 a
logBase = forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 forall a. Floating a => a -> a -> a
logBase
    {-# INLINE logBase #-}
    sin :: V3 a -> V3 a
sin = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
sin
    {-# INLINE sin #-}
    tan :: V3 a -> V3 a
tan = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
tan
    {-# INLINE tan #-}
    cos :: V3 a -> V3 a
cos = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
cos
    {-# INLINE cos #-}
    asin :: V3 a -> V3 a
asin = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
asin
    {-# INLINE asin #-}
    atan :: V3 a -> V3 a
atan = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
atan
    {-# INLINE atan #-}
    acos :: V3 a -> V3 a
acos = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
acos
    {-# INLINE acos #-}
    sinh :: V3 a -> V3 a
sinh = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
sinh
    {-# INLINE sinh #-}
    tanh :: V3 a -> V3 a
tanh = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
tanh
    {-# INLINE tanh #-}
    cosh :: V3 a -> V3 a
cosh = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
cosh
    {-# INLINE cosh #-}
    asinh :: V3 a -> V3 a
asinh = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
asinh
    {-# INLINE asinh #-}
    atanh :: V3 a -> V3 a
atanh = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
atanh
    {-# INLINE atanh #-}
    acosh :: V3 a -> V3 a
acosh = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
acosh
    {-# INLINE acosh #-}

instance Storable a => Storable (V3 a) where
  sizeOf :: V3 a -> Int
sizeOf V3 a
_ = Int
3 forall a. Num a => a -> a -> a
* forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined::a)
  {-# INLINE sizeOf #-}
  alignment :: V3 a -> Int
alignment V3 a
_ = forall a. Storable a => a -> Int
alignment (forall a. HasCallStack => a
undefined::a)
  {-# INLINE alignment #-}
  poke :: Ptr (V3 a) -> V3 a -> IO ()
poke Ptr (V3 a)
ptr (V3 a
x a
y a
z) = do forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr a
ptr' a
x
                           forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr a
ptr' Int
1 a
y
                           forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr a
ptr' Int
2 a
z
    where ptr' :: Ptr a
ptr' = forall a b. Ptr a -> Ptr b
castPtr Ptr (V3 a)
ptr
  {-# INLINE poke #-}
  peek :: Ptr (V3 a) -> IO (V3 a)
peek Ptr (V3 a)
ptr = forall a. a -> a -> a -> V3 a
V3 forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Storable a => Ptr a -> IO a
peek Ptr a
ptr' forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr a
ptr' Int
1 forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr a
ptr' Int
2
    where ptr' :: Ptr a
ptr' = forall a b. Ptr a -> Ptr b
castPtr Ptr (V3 a)
ptr
  {-# INLINE peek #-}

instance Ix a => Ix (V3 a) where
  {-# SPECIALISE instance Ix (V3 Int) #-}

  range :: (V3 a, V3 a) -> [V3 a]
range (V3 a
l1 a
l2 a
l3,V3 a
u1 a
u2 a
u3) =
      [forall a. a -> a -> a -> V3 a
V3 a
i1 a
i2 a
i3 | a
i1 <- forall a. Ix a => (a, a) -> [a]
range (a
l1,a
u1)
                   , a
i2 <- forall a. Ix a => (a, a) -> [a]
range (a
l2,a
u2)
                   , a
i3 <- forall a. Ix a => (a, a) -> [a]
range (a
l3,a
u3)
                   ]
  {-# INLINE range #-}

  unsafeIndex :: (V3 a, V3 a) -> V3 a -> Int
unsafeIndex (V3 a
l1 a
l2 a
l3,V3 a
u1 a
u2 a
u3) (V3 a
i1 a
i2 a
i3) =
    forall a. Ix a => (a, a) -> a -> Int
unsafeIndex (a
l3,a
u3) a
i3 forall a. Num a => a -> a -> a
+ forall a. Ix a => (a, a) -> Int
unsafeRangeSize (a
l3,a
u3) forall a. Num a => a -> a -> a
* (
    forall a. Ix a => (a, a) -> a -> Int
unsafeIndex (a
l2,a
u2) a
i2 forall a. Num a => a -> a -> a
+ forall a. Ix a => (a, a) -> Int
unsafeRangeSize (a
l2,a
u2) forall a. Num a => a -> a -> a
*
    forall a. Ix a => (a, a) -> a -> Int
unsafeIndex (a
l1,a
u1) a
i1)
  {-# INLINE unsafeIndex #-}

  inRange :: (V3 a, V3 a) -> V3 a -> Bool
inRange (V3 a
l1 a
l2 a
l3,V3 a
u1 a
u2 a
u3) (V3 a
i1 a
i2 a
i3) =
    forall a. Ix a => (a, a) -> a -> Bool
inRange (a
l1,a
u1) a
i1 Bool -> Bool -> Bool
&& forall a. Ix a => (a, a) -> a -> Bool
inRange (a
l2,a
u2) a
i2 Bool -> Bool -> Bool
&&
    forall a. Ix a => (a, a) -> a -> Bool
inRange (a
l3,a
u3) a
i3
  {-# INLINE inRange #-}

data instance U.Vector    (V3 a) =  V_V3 {-# UNPACK #-} !Int !(U.Vector    a)
data instance U.MVector s (V3 a) = MV_V3 {-# UNPACK #-} !Int !(U.MVector s a)
instance U.Unbox a => U.Unbox (V3 a)

instance U.Unbox a => M.MVector U.MVector (V3 a) where
  {-# INLINE basicLength #-}
  {-# INLINE basicUnsafeSlice #-}
  {-# INLINE basicOverlaps #-}
  {-# INLINE basicUnsafeNew #-}
  {-# INLINE basicUnsafeRead #-}
  {-# INLINE basicUnsafeWrite #-}
  basicLength :: forall s. MVector s (V3 a) -> Int
basicLength (MV_V3 Int
n MVector s a
_) = Int
n
  basicUnsafeSlice :: forall s. Int -> Int -> MVector s (V3 a) -> MVector s (V3 a)
basicUnsafeSlice Int
m Int
n (MV_V3 Int
_ MVector s a
v) = forall s a. Int -> MVector s a -> MVector s (V3 a)
MV_V3 Int
n (forall (v :: Type -> Type -> Type) a s.
MVector v a =>
Int -> Int -> v s a -> v s a
M.basicUnsafeSlice (Int
3forall a. Num a => a -> a -> a
*Int
m) (Int
3forall a. Num a => a -> a -> a
*Int
n) MVector s a
v)
  basicOverlaps :: forall s. MVector s (V3 a) -> MVector s (V3 a) -> Bool
basicOverlaps (MV_V3 Int
_ MVector s a
v) (MV_V3 Int
_ MVector s a
u) = forall (v :: Type -> Type -> Type) a s.
MVector v a =>
v s a -> v s a -> Bool
M.basicOverlaps MVector s a
v MVector s a
u
  basicUnsafeNew :: forall (m :: Type -> Type).
PrimMonad m =>
Int -> m (MVector (PrimState m) (V3 a))
basicUnsafeNew Int
n = forall (m :: Type -> Type) a1 r.
Monad m =>
(a1 -> r) -> m a1 -> m r
liftM (forall s a. Int -> MVector s a -> MVector s (V3 a)
MV_V3 Int
n) (forall (v :: Type -> Type -> Type) a (m :: Type -> Type).
(MVector v a, PrimMonad m) =>
Int -> m (v (PrimState m) a)
M.basicUnsafeNew (Int
3forall a. Num a => a -> a -> a
*Int
n))
  basicUnsafeRead :: forall (m :: Type -> Type).
PrimMonad m =>
MVector (PrimState m) (V3 a) -> Int -> m (V3 a)
basicUnsafeRead (MV_V3 Int
_ MVector (PrimState m) a
v) Int
i =
    do let o :: Int
o = Int
3forall a. Num a => a -> a -> a
*Int
i
       a
x <- forall (v :: Type -> Type -> Type) a (m :: Type -> Type).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m a
M.basicUnsafeRead MVector (PrimState m) a
v Int
o
       a
y <- forall (v :: Type -> Type -> Type) a (m :: Type -> Type).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m a
M.basicUnsafeRead MVector (PrimState m) a
v (Int
oforall a. Num a => a -> a -> a
+Int
1)
       a
z <- forall (v :: Type -> Type -> Type) a (m :: Type -> Type).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m a
M.basicUnsafeRead MVector (PrimState m) a
v (Int
oforall a. Num a => a -> a -> a
+Int
2)
       forall (m :: Type -> Type) a. Monad m => a -> m a
return (forall a. a -> a -> a -> V3 a
V3 a
x a
y a
z)
  basicUnsafeWrite :: forall (m :: Type -> Type).
PrimMonad m =>
MVector (PrimState m) (V3 a) -> Int -> V3 a -> m ()
basicUnsafeWrite (MV_V3 Int
_ MVector (PrimState m) a
v) Int
i (V3 a
x a
y a
z) =
    do let o :: Int
o = Int
3forall a. Num a => a -> a -> a
*Int
i
       forall (v :: Type -> Type -> Type) a (m :: Type -> Type).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> a -> m ()
M.basicUnsafeWrite MVector (PrimState m) a
v Int
o     a
x
       forall (v :: Type -> Type -> Type) a (m :: Type -> Type).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> a -> m ()
M.basicUnsafeWrite MVector (PrimState m) a
v (Int
oforall a. Num a => a -> a -> a
+Int
1) a
y
       forall (v :: Type -> Type -> Type) a (m :: Type -> Type).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> a -> m ()
M.basicUnsafeWrite MVector (PrimState m) a
v (Int
oforall a. Num a => a -> a -> a
+Int
2) a
z
#if MIN_VERSION_vector(0,11,0)
  basicInitialize :: forall (m :: Type -> Type).
PrimMonad m =>
MVector (PrimState m) (V3 a) -> m ()
basicInitialize (MV_V3 Int
_ MVector (PrimState m) a
v) = forall (v :: Type -> Type -> Type) a (m :: Type -> Type).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> m ()
M.basicInitialize MVector (PrimState m) a
v
  {-# INLINE basicInitialize #-}
#endif

instance U.Unbox a => G.Vector U.Vector (V3 a) where
  {-# INLINE basicUnsafeFreeze #-}
  {-# INLINE basicUnsafeThaw   #-}
  {-# INLINE basicLength       #-}
  {-# INLINE basicUnsafeSlice  #-}
  {-# INLINE basicUnsafeIndexM #-}
  basicUnsafeFreeze :: forall (m :: Type -> Type).
PrimMonad m =>
Mutable Vector (PrimState m) (V3 a) -> m (Vector (V3 a))
basicUnsafeFreeze (MV_V3 Int
n MVector (PrimState m) a
v) = forall (m :: Type -> Type) a1 r.
Monad m =>
(a1 -> r) -> m a1 -> m r
liftM ( forall a. Int -> Vector a -> Vector (V3 a)
V_V3 Int
n) (forall (v :: Type -> Type) a (m :: Type -> Type).
(Vector v a, PrimMonad m) =>
Mutable v (PrimState m) a -> m (v a)
G.basicUnsafeFreeze MVector (PrimState m) a
v)
  basicUnsafeThaw :: forall (m :: Type -> Type).
PrimMonad m =>
Vector (V3 a) -> m (Mutable Vector (PrimState m) (V3 a))
basicUnsafeThaw   ( V_V3 Int
n Vector a
v) = forall (m :: Type -> Type) a1 r.
Monad m =>
(a1 -> r) -> m a1 -> m r
liftM (forall s a. Int -> MVector s a -> MVector s (V3 a)
MV_V3 Int
n) (forall (v :: Type -> Type) a (m :: Type -> Type).
(Vector v a, PrimMonad m) =>
v a -> m (Mutable v (PrimState m) a)
G.basicUnsafeThaw   Vector a
v)
  basicLength :: Vector (V3 a) -> Int
basicLength       ( V_V3 Int
n Vector a
_) = Int
n
  basicUnsafeSlice :: Int -> Int -> Vector (V3 a) -> Vector (V3 a)
basicUnsafeSlice Int
m Int
n (V_V3 Int
_ Vector a
v) = forall a. Int -> Vector a -> Vector (V3 a)
V_V3 Int
n (forall (v :: Type -> Type) a.
Vector v a =>
Int -> Int -> v a -> v a
G.basicUnsafeSlice (Int
3forall a. Num a => a -> a -> a
*Int
m) (Int
3forall a. Num a => a -> a -> a
*Int
n) Vector a
v)
  basicUnsafeIndexM :: forall (m :: Type -> Type).
Monad m =>
Vector (V3 a) -> Int -> m (V3 a)
basicUnsafeIndexM (V_V3 Int
_ Vector a
v) Int
i =
    do let o :: Int
o = Int
3forall a. Num a => a -> a -> a
*Int
i
       a
x <- forall (v :: Type -> Type) a (m :: Type -> Type).
(Vector v a, Monad m) =>
v a -> Int -> m a
G.basicUnsafeIndexM Vector a
v Int
o
       a
y <- forall (v :: Type -> Type) a (m :: Type -> Type).
(Vector v a, Monad m) =>
v a -> Int -> m a
G.basicUnsafeIndexM Vector a
v (Int
oforall a. Num a => a -> a -> a
+Int
1)
       a
z <- forall (v :: Type -> Type) a (m :: Type -> Type).
(Vector v a, Monad m) =>
v a -> Int -> m a
G.basicUnsafeIndexM Vector a
v (Int
oforall a. Num a => a -> a -> a
+Int
2)
       forall (m :: Type -> Type) a. Monad m => a -> m a
return (forall a. a -> a -> a -> V3 a
V3 a
x a
y a
z)

instance MonadZip V3 where
  mzipWith :: forall a b c. (a -> b -> c) -> V3 a -> V3 b -> V3 c
mzipWith = forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2

instance MonadFix V3 where
  mfix :: forall a. (a -> V3 a) -> V3 a
mfix a -> V3 a
f = forall a. a -> a -> a -> V3 a
V3 (let V3 a
a a
_ a
_ = a -> V3 a
f a
a in a
a)
              (let V3 a
_ a
a a
_ = a -> V3 a
f a
a in a
a)
              (let V3 a
_ a
_ a
a = a -> V3 a
f a
a in a
a)

instance Bounded a => Bounded (V3 a) where
  minBound :: V3 a
minBound = forall (f :: Type -> Type) a. Applicative f => a -> f a
pure forall a. Bounded a => a
minBound
  {-# INLINE minBound #-}
  maxBound :: V3 a
maxBound = forall (f :: Type -> Type) a. Applicative f => a -> f a
pure forall a. Bounded a => a
maxBound
  {-# INLINE maxBound #-}


-- | A 4-dimensional vector.
data V4 a = V4 !a !a !a !a
  deriving (V4 a -> V4 a -> Bool
forall a. Eq a => V4 a -> V4 a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: V4 a -> V4 a -> Bool
$c/= :: forall a. Eq a => V4 a -> V4 a -> Bool
== :: V4 a -> V4 a -> Bool
$c== :: forall a. Eq a => V4 a -> V4 a -> Bool
Eq, V4 a -> V4 a -> Bool
V4 a -> V4 a -> Ordering
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
forall {a}. Ord a => Eq (V4 a)
forall a. Ord a => V4 a -> V4 a -> Bool
forall a. Ord a => V4 a -> V4 a -> Ordering
forall a. Ord a => V4 a -> V4 a -> V4 a
min :: V4 a -> V4 a -> V4 a
$cmin :: forall a. Ord a => V4 a -> V4 a -> V4 a
max :: V4 a -> V4 a -> V4 a
$cmax :: forall a. Ord a => V4 a -> V4 a -> V4 a
>= :: V4 a -> V4 a -> Bool
$c>= :: forall a. Ord a => V4 a -> V4 a -> Bool
> :: V4 a -> V4 a -> Bool
$c> :: forall a. Ord a => V4 a -> V4 a -> Bool
<= :: V4 a -> V4 a -> Bool
$c<= :: forall a. Ord a => V4 a -> V4 a -> Bool
< :: V4 a -> V4 a -> Bool
$c< :: forall a. Ord a => V4 a -> V4 a -> Bool
compare :: V4 a -> V4 a -> Ordering
$ccompare :: forall a. Ord a => V4 a -> V4 a -> Ordering
Ord, Int -> V4 a -> ShowS
forall a. Show a => Int -> V4 a -> ShowS
forall a. Show a => [V4 a] -> ShowS
forall a. Show a => V4 a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [V4 a] -> ShowS
$cshowList :: forall a. Show a => [V4 a] -> ShowS
show :: V4 a -> String
$cshow :: forall a. Show a => V4 a -> String
showsPrec :: Int -> V4 a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> V4 a -> ShowS
Show, ReadPrec [V4 a]
ReadPrec (V4 a)
ReadS [V4 a]
forall a. Read a => ReadPrec [V4 a]
forall a. Read a => ReadPrec (V4 a)
forall a. Read a => Int -> ReadS (V4 a)
forall a. Read a => ReadS [V4 a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [V4 a]
$creadListPrec :: forall a. Read a => ReadPrec [V4 a]
readPrec :: ReadPrec (V4 a)
$creadPrec :: forall a. Read a => ReadPrec (V4 a)
readList :: ReadS [V4 a]
$creadList :: forall a. Read a => ReadS [V4 a]
readsPrec :: Int -> ReadS (V4 a)
$creadsPrec :: forall a. Read a => Int -> ReadS (V4 a)
Read, V4 a -> DataType
V4 a -> Constr
forall {a}. Data a => Typeable (V4 a)
forall a. Data a => V4 a -> DataType
forall a. Data a => V4 a -> Constr
forall a. Data a => (forall b. Data b => b -> b) -> V4 a -> V4 a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> V4 a -> u
forall a u. Data a => (forall d. Data d => d -> u) -> V4 a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V4 a -> r
forall a r r'.
Data a =>
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V4 a -> r
forall a (m :: Type -> Type).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> V4 a -> m (V4 a)
forall a (m :: Type -> Type).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> V4 a -> m (V4 a)
forall a (c :: Type -> Type).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (V4 a)
forall a (c :: Type -> Type).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> V4 a -> c (V4 a)
forall a (t :: Type -> Type) (c :: Type -> Type).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (V4 a))
forall a (t :: Type -> Type -> Type) (c :: Type -> Type).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V4 a))
forall a.
Typeable a
-> (forall (c :: Type -> Type).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (V4 a)
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> V4 a -> c (V4 a)
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (V4 a))
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> V4 a -> m (V4 a)
$cgmapMo :: forall a (m :: Type -> Type).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> V4 a -> m (V4 a)
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> V4 a -> m (V4 a)
$cgmapMp :: forall a (m :: Type -> Type).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> V4 a -> m (V4 a)
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> V4 a -> m (V4 a)
$cgmapM :: forall a (m :: Type -> Type).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> V4 a -> m (V4 a)
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> V4 a -> u
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> V4 a -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> V4 a -> [u]
$cgmapQ :: forall a u. Data a => (forall d. Data d => d -> u) -> V4 a -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V4 a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V4 a -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V4 a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V4 a -> r
gmapT :: (forall b. Data b => b -> b) -> V4 a -> V4 a
$cgmapT :: forall a. Data a => (forall b. Data b => b -> b) -> V4 a -> V4 a
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V4 a))
$cdataCast2 :: forall a (t :: Type -> Type -> Type) (c :: Type -> Type).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V4 a))
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (V4 a))
$cdataCast1 :: forall a (t :: Type -> Type) (c :: Type -> Type).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (V4 a))
dataTypeOf :: V4 a -> DataType
$cdataTypeOf :: forall a. Data a => V4 a -> DataType
toConstr :: V4 a -> Constr
$ctoConstr :: forall a. Data a => V4 a -> Constr
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (V4 a)
$cgunfold :: forall a (c :: Type -> Type).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (V4 a)
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> V4 a -> c (V4 a)
$cgfoldl :: forall a (c :: Type -> Type).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> V4 a -> c (V4 a)
Data, Typeable, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (V4 a) x -> V4 a
forall a x. V4 a -> Rep (V4 a) x
$cto :: forall a x. Rep (V4 a) x -> V4 a
$cfrom :: forall a x. V4 a -> Rep (V4 a) x
Generic, forall a. Rep1 V4 a -> V4 a
forall a. V4 a -> Rep1 V4 a
forall k (f :: k -> Type).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cto1 :: forall a. Rep1 V4 a -> V4 a
$cfrom1 :: forall a. V4 a -> Rep1 V4 a
Generic1)

instance Functor V4 where
  fmap :: forall a b. (a -> b) -> V4 a -> V4 b
fmap a -> b
f (V4 a
a a
b a
c a
d) = forall a. a -> a -> a -> a -> V4 a
V4 (a -> b
f a
a) (a -> b
f a
b) (a -> b
f a
c) (a -> b
f a
d)
  {-# INLINE fmap #-}
  a
a <$ :: forall a b. a -> V4 b -> V4 a
<$ V4 b
_ = forall a. a -> a -> a -> a -> V4 a
V4 a
a a
a a
a a
a
  {-# INLINE (<$) #-}

instance Foldable V4 where
  foldMap :: forall m a. Monoid m => (a -> m) -> V4 a -> m
foldMap a -> m
f (V4 a
a a
b a
c a
d) = a -> m
f a
a forall a. Monoid a => a -> a -> a
`mappend` a -> m
f a
b forall a. Monoid a => a -> a -> a
`mappend` a -> m
f a
c forall a. Monoid a => a -> a -> a
`mappend` a -> m
f a
d
  {-# INLINE foldMap #-}

instance Traversable V4 where
  traverse :: forall (f :: Type -> Type) a b.
Applicative f =>
(a -> f b) -> V4 a -> f (V4 b)
traverse a -> f b
f (V4 a
a a
b a
c a
d) = forall a. a -> a -> a -> a -> V4 a
V4 forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> a -> f b
f a
b forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> a -> f b
f a
c forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> a -> f b
f a
d
  {-# INLINE traverse #-}

instance Applicative V4 where
  pure :: forall a. a -> V4 a
pure a
a = forall a. a -> a -> a -> a -> V4 a
V4 a
a a
a a
a a
a
  {-# INLINE pure #-}
  V4 a -> b
a a -> b
b a -> b
c a -> b
d <*> :: forall a b. V4 (a -> b) -> V4 a -> V4 b
<*> V4 a
e a
f a
g a
h = forall a. a -> a -> a -> a -> V4 a
V4 (a -> b
a a
e) (a -> b
b a
f) (a -> b
c a
g) (a -> b
d a
h)
  {-# INLINE (<*>) #-}

instance Monad V4 where
  return :: forall a. a -> V4 a
return = forall (f :: Type -> Type) a. Applicative f => a -> f a
pure
  {-# INLINE return #-}
  V4 a
a a
b a
c a
d >>= :: forall a b. V4 a -> (a -> V4 b) -> V4 b
>>= a -> V4 b
f = forall a. a -> a -> a -> a -> V4 a
V4 b
a' b
b' b
c' b
d' where
    V4 b
a' b
_ b
_ b
_ = a -> V4 b
f a
a
    V4 b
_ b
b' b
_ b
_ = a -> V4 b
f a
b
    V4 b
_ b
_ b
c' b
_ = a -> V4 b
f a
c
    V4 b
_ b
_ b
_ b
d' = a -> V4 b
f a
d
  {-# INLINE (>>=) #-}

instance Num a => Num (V4 a) where
  + :: V4 a -> V4 a -> V4 a
(+) = forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 forall a. Num a => a -> a -> a
(+)
  {-# INLINE (+) #-}
  * :: V4 a -> V4 a -> V4 a
(*) = forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 forall a. Num a => a -> a -> a
(*)
  {-# INLINE (-) #-}
  (-) = forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (-)
  {-# INLINE (*) #-}
  negate :: V4 a -> V4 a
negate = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Num a => a -> a
negate
  {-# INLINE negate #-}
  abs :: V4 a -> V4 a
abs = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Num a => a -> a
abs
  {-# INLINE abs #-}
  signum :: V4 a -> V4 a
signum = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Num a => a -> a
signum
  {-# INLINE signum #-}
  fromInteger :: Integer -> V4 a
fromInteger = forall (f :: Type -> Type) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Num a => Integer -> a
fromInteger
  {-# INLINE fromInteger #-}

instance Fractional a => Fractional (V4 a) where
  recip :: V4 a -> V4 a
recip = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Fractional a => a -> a
recip
  {-# INLINE recip #-}
  / :: V4 a -> V4 a -> V4 a
(/) = forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 forall a. Fractional a => a -> a -> a
(/)
  {-# INLINE (/) #-}
  fromRational :: Rational -> V4 a
fromRational = forall (f :: Type -> Type) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Fractional a => Rational -> a
fromRational
  {-# INLINE fromRational #-}

instance Floating a => Floating (V4 a) where
    pi :: V4 a
pi = forall (f :: Type -> Type) a. Applicative f => a -> f a
pure forall a. Floating a => a
pi
    {-# INLINE pi #-}
    exp :: V4 a -> V4 a
exp = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
exp
    {-# INLINE exp #-}
    sqrt :: V4 a -> V4 a
sqrt = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
sqrt
    {-# INLINE sqrt #-}
    log :: V4 a -> V4 a
log = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
log
    {-# INLINE log #-}
    ** :: V4 a -> V4 a -> V4 a
(**) = forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 forall a. Floating a => a -> a -> a
(**)
    {-# INLINE (**) #-}
    logBase :: V4 a -> V4 a -> V4 a
logBase = forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 forall a. Floating a => a -> a -> a
logBase
    {-# INLINE logBase #-}
    sin :: V4 a -> V4 a
sin = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
sin
    {-# INLINE sin #-}
    tan :: V4 a -> V4 a
tan = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
tan
    {-# INLINE tan #-}
    cos :: V4 a -> V4 a
cos = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
cos
    {-# INLINE cos #-}
    asin :: V4 a -> V4 a
asin = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
asin
    {-# INLINE asin #-}
    atan :: V4 a -> V4 a
atan = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
atan
    {-# INLINE atan #-}
    acos :: V4 a -> V4 a
acos = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
acos
    {-# INLINE acos #-}
    sinh :: V4 a -> V4 a
sinh = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
sinh
    {-# INLINE sinh #-}
    tanh :: V4 a -> V4 a
tanh = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
tanh
    {-# INLINE tanh #-}
    cosh :: V4 a -> V4 a
cosh = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
cosh
    {-# INLINE cosh #-}
    asinh :: V4 a -> V4 a
asinh = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
asinh
    {-# INLINE asinh #-}
    atanh :: V4 a -> V4 a
atanh = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
atanh
    {-# INLINE atanh #-}
    acosh :: V4 a -> V4 a
acosh = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Floating a => a -> a
acosh
    {-# INLINE acosh #-}

instance Storable a => Storable (V4 a) where
  sizeOf :: V4 a -> Int
sizeOf V4 a
_ = Int
4 forall a. Num a => a -> a -> a
* forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined::a)
  {-# INLINE sizeOf #-}
  alignment :: V4 a -> Int
alignment V4 a
_ = forall a. Storable a => a -> Int
alignment (forall a. HasCallStack => a
undefined::a)
  {-# INLINE alignment #-}
  poke :: Ptr (V4 a) -> V4 a -> IO ()
poke Ptr (V4 a)
ptr (V4 a
x a
y a
z a
w) = do forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr a
ptr' a
x
                             forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr a
ptr' Int
1 a
y
                             forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr a
ptr' Int
2 a
z
                             forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr a
ptr' Int
3 a
w
    where ptr' :: Ptr a
ptr' = forall a b. Ptr a -> Ptr b
castPtr Ptr (V4 a)
ptr
  {-# INLINE poke #-}
  peek :: Ptr (V4 a) -> IO (V4 a)
peek Ptr (V4 a)
ptr = forall a. a -> a -> a -> a -> V4 a
V4 forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Storable a => Ptr a -> IO a
peek Ptr a
ptr' forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr a
ptr' Int
1
                forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr a
ptr' Int
2 forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr a
ptr' Int
3
    where ptr' :: Ptr a
ptr' = forall a b. Ptr a -> Ptr b
castPtr Ptr (V4 a)
ptr
  {-# INLINE peek #-}

instance Ix a => Ix (V4 a) where
  {-# SPECIALISE instance Ix (V4 Int) #-}

  range :: (V4 a, V4 a) -> [V4 a]
range (V4 a
l1 a
l2 a
l3 a
l4,V4 a
u1 a
u2 a
u3 a
u4) =
    [forall a. a -> a -> a -> a -> V4 a
V4 a
i1 a
i2 a
i3 a
i4 | a
i1 <- forall a. Ix a => (a, a) -> [a]
range (a
l1,a
u1)
                    , a
i2 <- forall a. Ix a => (a, a) -> [a]
range (a
l2,a
u2)
                    , a
i3 <- forall a. Ix a => (a, a) -> [a]
range (a
l3,a
u3)
                    , a
i4 <- forall a. Ix a => (a, a) -> [a]
range (a
l4,a
u4)
                    ]
  {-# INLINE range #-}

  unsafeIndex :: (V4 a, V4 a) -> V4 a -> Int
unsafeIndex (V4 a
l1 a
l2 a
l3 a
l4,V4 a
u1 a
u2 a
u3 a
u4) (V4 a
i1 a
i2 a
i3 a
i4) =
    forall a. Ix a => (a, a) -> a -> Int
unsafeIndex (a
l4,a
u4) a
i4 forall a. Num a => a -> a -> a
+ forall a. Ix a => (a, a) -> Int
unsafeRangeSize (a
l4,a
u4) forall a. Num a => a -> a -> a
* (
    forall a. Ix a => (a, a) -> a -> Int
unsafeIndex (a
l3,a
u3) a
i3 forall a. Num a => a -> a -> a
+ forall a. Ix a => (a, a) -> Int
unsafeRangeSize (a
l3,a
u3) forall a. Num a => a -> a -> a
* (
    forall a. Ix a => (a, a) -> a -> Int
unsafeIndex (a
l2,a
u2) a
i2 forall a. Num a => a -> a -> a
+ forall a. Ix a => (a, a) -> Int
unsafeRangeSize (a
l2,a
u2) forall a. Num a => a -> a -> a
*
    forall a. Ix a => (a, a) -> a -> Int
unsafeIndex (a
l1,a
u1) a
i1))
  {-# INLINE unsafeIndex #-}

  inRange :: (V4 a, V4 a) -> V4 a -> Bool
inRange (V4 a
l1 a
l2 a
l3 a
l4,V4 a
u1 a
u2 a
u3 a
u4) (V4 a
i1 a
i2 a
i3 a
i4) =
    forall a. Ix a => (a, a) -> a -> Bool
inRange (a
l1,a
u1) a
i1 Bool -> Bool -> Bool
&& forall a. Ix a => (a, a) -> a -> Bool
inRange (a
l2,a
u2) a
i2 Bool -> Bool -> Bool
&&
    forall a. Ix a => (a, a) -> a -> Bool
inRange (a
l3,a
u3) a
i3 Bool -> Bool -> Bool
&& forall a. Ix a => (a, a) -> a -> Bool
inRange (a
l4,a
u4) a
i4
  {-# INLINE inRange #-}

data instance U.Vector    (V4 a) =  V_V4 {-# UNPACK #-} !Int !(U.Vector    a)
data instance U.MVector s (V4 a) = MV_V4 {-# UNPACK #-} !Int !(U.MVector s a)
instance U.Unbox a => U.Unbox (V4 a)

instance U.Unbox a => M.MVector U.MVector (V4 a) where
  basicLength :: forall s. MVector s (V4 a) -> Int
basicLength (MV_V4 Int
n MVector s a
_) = Int
n
  basicUnsafeSlice :: forall s. Int -> Int -> MVector s (V4 a) -> MVector s (V4 a)
basicUnsafeSlice Int
m Int
n (MV_V4 Int
_ MVector s a
v) = forall s a. Int -> MVector s a -> MVector s (V4 a)
MV_V4 Int
n (forall (v :: Type -> Type -> Type) a s.
MVector v a =>
Int -> Int -> v s a -> v s a
M.basicUnsafeSlice (Int
4forall a. Num a => a -> a -> a
*Int
m) (Int
4forall a. Num a => a -> a -> a
*Int
n) MVector s a
v)
  basicOverlaps :: forall s. MVector s (V4 a) -> MVector s (V4 a) -> Bool
basicOverlaps (MV_V4 Int
_ MVector s a
v) (MV_V4 Int
_ MVector s a
u) = forall (v :: Type -> Type -> Type) a s.
MVector v a =>
v s a -> v s a -> Bool
M.basicOverlaps MVector s a
v MVector s a
u
  basicUnsafeNew :: forall (m :: Type -> Type).
PrimMonad m =>
Int -> m (MVector (PrimState m) (V4 a))
basicUnsafeNew Int
n = forall (m :: Type -> Type) a1 r.
Monad m =>
(a1 -> r) -> m a1 -> m r
liftM (forall s a. Int -> MVector s a -> MVector s (V4 a)
MV_V4 Int
n) (forall (v :: Type -> Type -> Type) a (m :: Type -> Type).
(MVector v a, PrimMonad m) =>
Int -> m (v (PrimState m) a)
M.basicUnsafeNew (Int
4forall a. Num a => a -> a -> a
*Int
n))
  basicUnsafeRead :: forall (m :: Type -> Type).
PrimMonad m =>
MVector (PrimState m) (V4 a) -> Int -> m (V4 a)
basicUnsafeRead (MV_V4 Int
_ MVector (PrimState m) a
v) Int
i =
    do let o :: Int
o = Int
4forall a. Num a => a -> a -> a
*Int
i
       a
x <- forall (v :: Type -> Type -> Type) a (m :: Type -> Type).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m a
M.basicUnsafeRead MVector (PrimState m) a
v Int
o
       a
y <- forall (v :: Type -> Type -> Type) a (m :: Type -> Type).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m a
M.basicUnsafeRead MVector (PrimState m) a
v (Int
oforall a. Num a => a -> a -> a
+Int
1)
       a
z <- forall (v :: Type -> Type -> Type) a (m :: Type -> Type).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m a
M.basicUnsafeRead MVector (PrimState m) a
v (Int
oforall a. Num a => a -> a -> a
+Int
2)
       a
w <- forall (v :: Type -> Type -> Type) a (m :: Type -> Type).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m a
M.basicUnsafeRead MVector (PrimState m) a
v (Int
oforall a. Num a => a -> a -> a
+Int
3)
       forall (m :: Type -> Type) a. Monad m => a -> m a
return (forall a. a -> a -> a -> a -> V4 a
V4 a
x a
y a
z a
w)
  basicUnsafeWrite :: forall (m :: Type -> Type).
PrimMonad m =>
MVector (PrimState m) (V4 a) -> Int -> V4 a -> m ()
basicUnsafeWrite (MV_V4 Int
_ MVector (PrimState m) a
v) Int
i (V4 a
x a
y a
z a
w) =
    do let o :: Int
o = Int
4forall a. Num a => a -> a -> a
*Int
i
       forall (v :: Type -> Type -> Type) a (m :: Type -> Type).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> a -> m ()
M.basicUnsafeWrite MVector (PrimState m) a
v Int
o     a
x
       forall (v :: Type -> Type -> Type) a (m :: Type -> Type).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> a -> m ()
M.basicUnsafeWrite MVector (PrimState m) a
v (Int
oforall a. Num a => a -> a -> a
+Int
1) a
y
       forall (v :: Type -> Type -> Type) a (m :: Type -> Type).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> a -> m ()
M.basicUnsafeWrite MVector (PrimState m) a
v (Int
oforall a. Num a => a -> a -> a
+Int
2) a
z
       forall (v :: Type -> Type -> Type) a (m :: Type -> Type).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> a -> m ()
M.basicUnsafeWrite MVector (PrimState m) a
v (Int
oforall a. Num a => a -> a -> a
+Int
3) a
w
#if MIN_VERSION_vector(0,11,0)
  basicInitialize :: forall (m :: Type -> Type).
PrimMonad m =>
MVector (PrimState m) (V4 a) -> m ()
basicInitialize (MV_V4 Int
_ MVector (PrimState m) a
v) = forall (v :: Type -> Type -> Type) a (m :: Type -> Type).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> m ()
M.basicInitialize MVector (PrimState m) a
v
#endif

instance U.Unbox a => G.Vector U.Vector (V4 a) where
  basicUnsafeFreeze :: forall (m :: Type -> Type).
PrimMonad m =>
Mutable Vector (PrimState m) (V4 a) -> m (Vector (V4 a))
basicUnsafeFreeze (MV_V4 Int
n MVector (PrimState m) a
v) = forall (m :: Type -> Type) a1 r.
Monad m =>
(a1 -> r) -> m a1 -> m r
liftM ( forall a. Int -> Vector a -> Vector (V4 a)
V_V4 Int
n) (forall (v :: Type -> Type) a (m :: Type -> Type).
(Vector v a, PrimMonad m) =>
Mutable v (PrimState m) a -> m (v a)
G.basicUnsafeFreeze MVector (PrimState m) a
v)
  basicUnsafeThaw :: forall (m :: Type -> Type).
PrimMonad m =>
Vector (V4 a) -> m (Mutable Vector (PrimState m) (V4 a))
basicUnsafeThaw   ( V_V4 Int
n Vector a
v) = forall (m :: Type -> Type) a1 r.
Monad m =>
(a1 -> r) -> m a1 -> m r
liftM (forall s a. Int -> MVector s a -> MVector s (V4 a)
MV_V4 Int
n) (forall (v :: Type -> Type) a (m :: Type -> Type).
(Vector v a, PrimMonad m) =>
v a -> m (Mutable v (PrimState m) a)
G.basicUnsafeThaw   Vector a
v)
  basicLength :: Vector (V4 a) -> Int
basicLength       ( V_V4 Int
n Vector a
_) = Int
n
  basicUnsafeSlice :: Int -> Int -> Vector (V4 a) -> Vector (V4 a)
basicUnsafeSlice Int
m Int
n (V_V4 Int
_ Vector a
v) = forall a. Int -> Vector a -> Vector (V4 a)
V_V4 Int
n (forall (v :: Type -> Type) a.
Vector v a =>
Int -> Int -> v a -> v a
G.basicUnsafeSlice (Int
4forall a. Num a => a -> a -> a
*Int
m) (Int
4forall a. Num a => a -> a -> a
*Int
n) Vector a
v)
  basicUnsafeIndexM :: forall (m :: Type -> Type).
Monad m =>
Vector (V4 a) -> Int -> m (V4 a)
basicUnsafeIndexM (V_V4 Int
_ Vector a
v) Int
i =
    do let o :: Int
o = Int
4forall a. Num a => a -> a -> a
*Int
i
       a
x <- forall (v :: Type -> Type) a (m :: Type -> Type).
(Vector v a, Monad m) =>
v a -> Int -> m a
G.basicUnsafeIndexM Vector a
v Int
o
       a
y <- forall (v :: Type -> Type) a (m :: Type -> Type).
(Vector v a, Monad m) =>
v a -> Int -> m a
G.basicUnsafeIndexM Vector a
v (Int
oforall a. Num a => a -> a -> a
+Int
1)
       a
z <- forall (v :: Type -> Type) a (m :: Type -> Type).
(Vector v a, Monad m) =>
v a -> Int -> m a
G.basicUnsafeIndexM Vector a
v (Int
oforall a. Num a => a -> a -> a
+Int
2)
       a
w <- forall (v :: Type -> Type) a (m :: Type -> Type).
(Vector v a, Monad m) =>
v a -> Int -> m a
G.basicUnsafeIndexM Vector a
v (Int
oforall a. Num a => a -> a -> a
+Int
3)
       forall (m :: Type -> Type) a. Monad m => a -> m a
return (forall a. a -> a -> a -> a -> V4 a
V4 a
x a
y a
z a
w)

instance MonadZip V4 where
  mzipWith :: forall a b c. (a -> b -> c) -> V4 a -> V4 b -> V4 c
mzipWith = forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2

instance MonadFix V4 where
  mfix :: forall a. (a -> V4 a) -> V4 a
mfix a -> V4 a
f = forall a. a -> a -> a -> a -> V4 a
V4 (let V4 a
a a
_ a
_ a
_ = a -> V4 a
f a
a in a
a)
              (let V4 a
_ a
a a
_ a
_ = a -> V4 a
f a
a in a
a)
              (let V4 a
_ a
_ a
a a
_ = a -> V4 a
f a
a in a
a)
              (let V4 a
_ a
_ a
_ a
a = a -> V4 a
f a
a in a
a)

instance Bounded a => Bounded (V4 a) where
  minBound :: V4 a
minBound = forall (f :: Type -> Type) a. Applicative f => a -> f a
pure forall a. Bounded a => a
minBound
  {-# INLINE minBound #-}
  maxBound :: V4 a
maxBound = forall (f :: Type -> Type) a. Applicative f => a -> f a
pure forall a. Bounded a => a
maxBound
  {-# INLINE maxBound #-}