sdl2-2.4.1.0: Both high- and low-level bindings to the SDL library (version 2.0.4+).

Copyright(C) 2012-2015 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellTrustworthy
LanguageHaskell2010

SDL.Internal.Vect

Description

 

Synopsis

Documentation

newtype Point f a Source #

A handy wrapper to help distinguish points from vectors at the type level

Constructors

P (f a) 

Instances

Unbox (f a) => Vector Vector (Point f a) Source # 

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Point f a) -> m (Vector (Point f a)) #

basicUnsafeThaw :: PrimMonad m => Vector (Point f a) -> m (Mutable Vector (PrimState m) (Point f a)) #

basicLength :: Vector (Point f a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Point f a) -> Vector (Point f a) #

basicUnsafeIndexM :: Monad m => Vector (Point f a) -> Int -> m (Point f a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Point f a) -> Vector (Point f a) -> m () #

elemseq :: Vector (Point f a) -> Point f a -> b -> b #

Unbox (f a) => MVector MVector (Point f a) Source # 

Methods

basicLength :: MVector s (Point f a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Point f a) -> MVector s (Point f a) #

basicOverlaps :: MVector s (Point f a) -> MVector s (Point f a) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (Point f a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Point f a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Point f a -> m (MVector (PrimState m) (Point f a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Point f a) -> Int -> m (Point f a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Point f a) -> Int -> Point f a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Point f a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Point f a) -> Point f a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Point f a) -> MVector (PrimState m) (Point f a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Point f a) -> MVector (PrimState m) (Point f a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Point f a) -> Int -> m (MVector (PrimState m) (Point f a)) #

Monad f => Monad (Point f) Source # 

Methods

(>>=) :: Point f a -> (a -> Point f b) -> Point f b #

(>>) :: Point f a -> Point f b -> Point f b #

return :: a -> Point f a #

fail :: String -> Point f a #

Functor f => Functor (Point f) Source # 

Methods

fmap :: (a -> b) -> Point f a -> Point f b #

(<$) :: a -> Point f b -> Point f a #

Applicative f => Applicative (Point f) Source # 

Methods

pure :: a -> Point f a #

(<*>) :: Point f (a -> b) -> Point f a -> Point f b #

liftA2 :: (a -> b -> c) -> Point f a -> Point f b -> Point f c #

(*>) :: Point f a -> Point f b -> Point f b #

(<*) :: Point f a -> Point f b -> Point f a #

Foldable f => Foldable (Point f) Source # 

Methods

fold :: Monoid m => Point f m -> m #

foldMap :: Monoid m => (a -> m) -> Point f a -> m #

foldr :: (a -> b -> b) -> b -> Point f a -> b #

foldr' :: (a -> b -> b) -> b -> Point f a -> b #

foldl :: (b -> a -> b) -> b -> Point f a -> b #

foldl' :: (b -> a -> b) -> b -> Point f a -> b #

foldr1 :: (a -> a -> a) -> Point f a -> a #

foldl1 :: (a -> a -> a) -> Point f a -> a #

toList :: Point f a -> [a] #

null :: Point f a -> Bool #

length :: Point f a -> Int #

elem :: Eq a => a -> Point f a -> Bool #

maximum :: Ord a => Point f a -> a #

minimum :: Ord a => Point f a -> a #

sum :: Num a => Point f a -> a #

product :: Num a => Point f a -> a #

Traversable f => Traversable (Point f) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Point f a -> f (Point f b) #

sequenceA :: Applicative f => Point f (f a) -> f (Point f a) #

mapM :: Monad m => (a -> m b) -> Point f a -> m (Point f b) #

sequence :: Monad m => Point f (m a) -> m (Point f a) #

Generic1 * (Point f) Source # 

Associated Types

type Rep1 (Point f) (f :: Point f -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 (Point f) f a #

to1 :: Rep1 (Point f) f a -> f a #

Eq (f a) => Eq (Point f a) Source # 

Methods

(==) :: Point f a -> Point f a -> Bool #

(/=) :: Point f a -> Point f a -> Bool #

Fractional (f a) => Fractional (Point f a) Source # 

Methods

(/) :: Point f a -> Point f a -> Point f a #

recip :: Point f a -> Point f a #

fromRational :: Rational -> Point f a #

(Data (f a), Typeable * a, Typeable (* -> *) f) => Data (Point f a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Point f a -> c (Point f a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Point f a) #

toConstr :: Point f a -> Constr #

dataTypeOf :: Point f a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Point f a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Point f a)) #

gmapT :: (forall b. Data b => b -> b) -> Point f a -> Point f a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Point f a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Point f a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Point f a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Point f a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Point f a -> m (Point f a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Point f a -> m (Point f a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Point f a -> m (Point f a) #

Num (f a) => Num (Point f a) Source # 

Methods

(+) :: Point f a -> Point f a -> Point f a #

(-) :: Point f a -> Point f a -> Point f a #

(*) :: Point f a -> Point f a -> Point f a #

negate :: Point f a -> Point f a #

abs :: Point f a -> Point f a #

signum :: Point f a -> Point f a #

fromInteger :: Integer -> Point f a #

Ord (f a) => Ord (Point f a) Source # 

Methods

compare :: Point f a -> Point f a -> Ordering #

(<) :: Point f a -> Point f a -> Bool #

(<=) :: Point f a -> Point f a -> Bool #

(>) :: Point f a -> Point f a -> Bool #

(>=) :: Point f a -> Point f a -> Bool #

max :: Point f a -> Point f a -> Point f a #

min :: Point f a -> Point f a -> Point f a #

Read (f a) => Read (Point f a) Source # 
Show (f a) => Show (Point f a) Source # 

Methods

showsPrec :: Int -> Point f a -> ShowS #

show :: Point f a -> String #

showList :: [Point f a] -> ShowS #

Ix (f a) => Ix (Point f a) Source # 

Methods

range :: (Point f a, Point f a) -> [Point f a] #

index :: (Point f a, Point f a) -> Point f a -> Int #

unsafeIndex :: (Point f a, Point f a) -> Point f a -> Int

inRange :: (Point f a, Point f a) -> Point f a -> Bool #

rangeSize :: (Point f a, Point f a) -> Int #

unsafeRangeSize :: (Point f a, Point f a) -> Int

Generic (Point f a) Source # 

Associated Types

type Rep (Point f a) :: * -> * #

Methods

from :: Point f a -> Rep (Point f a) x #

to :: Rep (Point f a) x -> Point f a #

Storable (f a) => Storable (Point f a) Source # 

Methods

sizeOf :: Point f a -> Int #

alignment :: Point f a -> Int #

peekElemOff :: Ptr (Point f a) -> Int -> IO (Point f a) #

pokeElemOff :: Ptr (Point f a) -> Int -> Point f a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Point f a) #

pokeByteOff :: Ptr b -> Int -> Point f a -> IO () #

peek :: Ptr (Point f a) -> IO (Point f a) #

poke :: Ptr (Point f a) -> Point f a -> IO () #

Unbox (f a) => Unbox (Point f a) Source # 
data MVector s (Point f a) Source # 
data MVector s (Point f a) = MV_P !(MVector s (f a))
type Rep1 * (Point f) Source # 
type Rep1 * (Point f) = D1 * (MetaData "Point" "SDL.Internal.Vect" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" True) (C1 * (MetaCons "P" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 * f)))
type Rep (Point f a) Source # 
type Rep (Point f a) = D1 * (MetaData "Point" "SDL.Internal.Vect" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" True) (C1 * (MetaCons "P" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f a))))
data Vector (Point f a) Source # 
data Vector (Point f a) = V_P !(Vector (f a))

data V2 a Source #

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

Constructors

V2 !a !a 

Instances

Monad V2 Source # 

Methods

(>>=) :: V2 a -> (a -> V2 b) -> V2 b #

(>>) :: V2 a -> V2 b -> V2 b #

return :: a -> V2 a #

fail :: String -> V2 a #

Functor V2 Source # 

Methods

fmap :: (a -> b) -> V2 a -> V2 b #

(<$) :: a -> V2 b -> V2 a #

MonadFix V2 Source # 

Methods

mfix :: (a -> V2 a) -> V2 a #

Applicative V2 Source # 

Methods

pure :: a -> V2 a #

(<*>) :: V2 (a -> b) -> V2 a -> V2 b #

liftA2 :: (a -> b -> c) -> V2 a -> V2 b -> V2 c #

(*>) :: V2 a -> V2 b -> V2 b #

(<*) :: V2 a -> V2 b -> V2 a #

Foldable V2 Source # 

Methods

fold :: Monoid m => V2 m -> m #

foldMap :: Monoid m => (a -> m) -> V2 a -> m #

foldr :: (a -> b -> b) -> b -> V2 a -> b #

foldr' :: (a -> b -> b) -> b -> V2 a -> b #

foldl :: (b -> a -> b) -> b -> V2 a -> b #

foldl' :: (b -> a -> b) -> b -> V2 a -> b #

foldr1 :: (a -> a -> a) -> V2 a -> a #

foldl1 :: (a -> a -> a) -> V2 a -> a #

toList :: V2 a -> [a] #

null :: V2 a -> Bool #

length :: V2 a -> Int #

elem :: Eq a => a -> V2 a -> Bool #

maximum :: Ord a => V2 a -> a #

minimum :: Ord a => V2 a -> a #

sum :: Num a => V2 a -> a #

product :: Num a => V2 a -> a #

Traversable V2 Source # 

Methods

traverse :: Applicative f => (a -> f b) -> V2 a -> f (V2 b) #

sequenceA :: Applicative f => V2 (f a) -> f (V2 a) #

mapM :: Monad m => (a -> m b) -> V2 a -> m (V2 b) #

sequence :: Monad m => V2 (m a) -> m (V2 a) #

MonadZip V2 Source # 

Methods

mzip :: V2 a -> V2 b -> V2 (a, b) #

mzipWith :: (a -> b -> c) -> V2 a -> V2 b -> V2 c #

munzip :: V2 (a, b) -> (V2 a, V2 b) #

Unbox a => Vector Vector (V2 a) Source # 

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (V2 a) -> m (Vector (V2 a)) #

basicUnsafeThaw :: PrimMonad m => Vector (V2 a) -> m (Mutable Vector (PrimState m) (V2 a)) #

basicLength :: Vector (V2 a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (V2 a) -> Vector (V2 a) #

basicUnsafeIndexM :: Monad m => Vector (V2 a) -> Int -> m (V2 a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (V2 a) -> Vector (V2 a) -> m () #

elemseq :: Vector (V2 a) -> V2 a -> b -> b #

Unbox a => MVector MVector (V2 a) Source # 

Methods

basicLength :: MVector s (V2 a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (V2 a) -> MVector s (V2 a) #

basicOverlaps :: MVector s (V2 a) -> MVector s (V2 a) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (V2 a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (V2 a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> V2 a -> m (MVector (PrimState m) (V2 a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (V2 a) -> Int -> m (V2 a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (V2 a) -> Int -> V2 a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (V2 a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (V2 a) -> V2 a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (V2 a) -> MVector (PrimState m) (V2 a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (V2 a) -> MVector (PrimState m) (V2 a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (V2 a) -> Int -> m (MVector (PrimState m) (V2 a)) #

Bounded a => Bounded (V2 a) Source # 

Methods

minBound :: V2 a #

maxBound :: V2 a #

Eq a => Eq (V2 a) Source # 

Methods

(==) :: V2 a -> V2 a -> Bool #

(/=) :: V2 a -> V2 a -> Bool #

Floating a => Floating (V2 a) Source # 

Methods

pi :: V2 a #

exp :: V2 a -> V2 a #

log :: V2 a -> V2 a #

sqrt :: V2 a -> V2 a #

(**) :: V2 a -> V2 a -> V2 a #

logBase :: V2 a -> V2 a -> V2 a #

sin :: V2 a -> V2 a #

cos :: V2 a -> V2 a #

tan :: V2 a -> V2 a #

asin :: V2 a -> V2 a #

acos :: V2 a -> V2 a #

atan :: V2 a -> V2 a #

sinh :: V2 a -> V2 a #

cosh :: V2 a -> V2 a #

tanh :: V2 a -> V2 a #

asinh :: V2 a -> V2 a #

acosh :: V2 a -> V2 a #

atanh :: V2 a -> V2 a #

log1p :: V2 a -> V2 a #

expm1 :: V2 a -> V2 a #

log1pexp :: V2 a -> V2 a #

log1mexp :: V2 a -> V2 a #

Fractional a => Fractional (V2 a) Source # 

Methods

(/) :: V2 a -> V2 a -> V2 a #

recip :: V2 a -> V2 a #

fromRational :: Rational -> V2 a #

Data a => Data (V2 a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> V2 a -> c (V2 a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (V2 a) #

toConstr :: V2 a -> Constr #

dataTypeOf :: V2 a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (V2 a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V2 a)) #

gmapT :: (forall b. Data b => b -> b) -> V2 a -> V2 a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V2 a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V2 a -> r #

gmapQ :: (forall d. Data d => d -> u) -> V2 a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> V2 a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> V2 a -> m (V2 a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V2 a -> m (V2 a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V2 a -> m (V2 a) #

Num a => Num (V2 a) Source # 

Methods

(+) :: V2 a -> V2 a -> V2 a #

(-) :: V2 a -> V2 a -> V2 a #

(*) :: V2 a -> V2 a -> V2 a #

negate :: V2 a -> V2 a #

abs :: V2 a -> V2 a #

signum :: V2 a -> V2 a #

fromInteger :: Integer -> V2 a #

Ord a => Ord (V2 a) Source # 

Methods

compare :: V2 a -> V2 a -> Ordering #

(<) :: V2 a -> V2 a -> Bool #

(<=) :: V2 a -> V2 a -> Bool #

(>) :: V2 a -> V2 a -> Bool #

(>=) :: V2 a -> V2 a -> Bool #

max :: V2 a -> V2 a -> V2 a #

min :: V2 a -> V2 a -> V2 a #

Read a => Read (V2 a) Source # 
Show a => Show (V2 a) Source # 

Methods

showsPrec :: Int -> V2 a -> ShowS #

show :: V2 a -> String #

showList :: [V2 a] -> ShowS #

Ix a => Ix (V2 a) Source # 

Methods

range :: (V2 a, V2 a) -> [V2 a] #

index :: (V2 a, V2 a) -> V2 a -> Int #

unsafeIndex :: (V2 a, V2 a) -> V2 a -> Int

inRange :: (V2 a, V2 a) -> V2 a -> Bool #

rangeSize :: (V2 a, V2 a) -> Int #

unsafeRangeSize :: (V2 a, V2 a) -> Int

Generic (V2 a) Source # 

Associated Types

type Rep (V2 a) :: * -> * #

Methods

from :: V2 a -> Rep (V2 a) x #

to :: Rep (V2 a) x -> V2 a #

Storable a => Storable (V2 a) Source # 

Methods

sizeOf :: V2 a -> Int #

alignment :: V2 a -> Int #

peekElemOff :: Ptr (V2 a) -> Int -> IO (V2 a) #

pokeElemOff :: Ptr (V2 a) -> Int -> V2 a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (V2 a) #

pokeByteOff :: Ptr b -> Int -> V2 a -> IO () #

peek :: Ptr (V2 a) -> IO (V2 a) #

poke :: Ptr (V2 a) -> V2 a -> IO () #

Unbox a => Unbox (V2 a) Source # 
Generic1 * V2 Source # 

Associated Types

type Rep1 V2 (f :: V2 -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 V2 f a #

to1 :: Rep1 V2 f a -> f a #

data MVector s (V2 a) Source # 
data MVector s (V2 a) = MV_V2 !Int !(MVector s a)
type Rep (V2 a) Source # 
type Rep (V2 a) = D1 * (MetaData "V2" "SDL.Internal.Vect" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) (C1 * (MetaCons "V2" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * a))))
data Vector (V2 a) Source # 
data Vector (V2 a) = V_V2 !Int !(Vector a)
type Rep1 * V2 Source # 

data V3 a Source #

A 3-dimensional vector

Constructors

V3 !a !a !a 

Instances

Monad V3 Source # 

Methods

(>>=) :: V3 a -> (a -> V3 b) -> V3 b #

(>>) :: V3 a -> V3 b -> V3 b #

return :: a -> V3 a #

fail :: String -> V3 a #

Functor V3 Source # 

Methods

fmap :: (a -> b) -> V3 a -> V3 b #

(<$) :: a -> V3 b -> V3 a #

MonadFix V3 Source # 

Methods

mfix :: (a -> V3 a) -> V3 a #

Applicative V3 Source # 

Methods

pure :: a -> V3 a #

(<*>) :: V3 (a -> b) -> V3 a -> V3 b #

liftA2 :: (a -> b -> c) -> V3 a -> V3 b -> V3 c #

(*>) :: V3 a -> V3 b -> V3 b #

(<*) :: V3 a -> V3 b -> V3 a #

Foldable V3 Source # 

Methods

fold :: Monoid m => V3 m -> m #

foldMap :: Monoid m => (a -> m) -> V3 a -> m #

foldr :: (a -> b -> b) -> b -> V3 a -> b #

foldr' :: (a -> b -> b) -> b -> V3 a -> b #

foldl :: (b -> a -> b) -> b -> V3 a -> b #

foldl' :: (b -> a -> b) -> b -> V3 a -> b #

foldr1 :: (a -> a -> a) -> V3 a -> a #

foldl1 :: (a -> a -> a) -> V3 a -> a #

toList :: V3 a -> [a] #

null :: V3 a -> Bool #

length :: V3 a -> Int #

elem :: Eq a => a -> V3 a -> Bool #

maximum :: Ord a => V3 a -> a #

minimum :: Ord a => V3 a -> a #

sum :: Num a => V3 a -> a #

product :: Num a => V3 a -> a #

Traversable V3 Source # 

Methods

traverse :: Applicative f => (a -> f b) -> V3 a -> f (V3 b) #

sequenceA :: Applicative f => V3 (f a) -> f (V3 a) #

mapM :: Monad m => (a -> m b) -> V3 a -> m (V3 b) #

sequence :: Monad m => V3 (m a) -> m (V3 a) #

MonadZip V3 Source # 

Methods

mzip :: V3 a -> V3 b -> V3 (a, b) #

mzipWith :: (a -> b -> c) -> V3 a -> V3 b -> V3 c #

munzip :: V3 (a, b) -> (V3 a, V3 b) #

Unbox a => Vector Vector (V3 a) Source # 

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (V3 a) -> m (Vector (V3 a)) #

basicUnsafeThaw :: PrimMonad m => Vector (V3 a) -> m (Mutable Vector (PrimState m) (V3 a)) #

basicLength :: Vector (V3 a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (V3 a) -> Vector (V3 a) #

basicUnsafeIndexM :: Monad m => Vector (V3 a) -> Int -> m (V3 a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (V3 a) -> Vector (V3 a) -> m () #

elemseq :: Vector (V3 a) -> V3 a -> b -> b #

Unbox a => MVector MVector (V3 a) Source # 

Methods

basicLength :: MVector s (V3 a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (V3 a) -> MVector s (V3 a) #

basicOverlaps :: MVector s (V3 a) -> MVector s (V3 a) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (V3 a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (V3 a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> V3 a -> m (MVector (PrimState m) (V3 a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (V3 a) -> Int -> m (V3 a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (V3 a) -> Int -> V3 a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (V3 a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (V3 a) -> V3 a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (V3 a) -> MVector (PrimState m) (V3 a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (V3 a) -> MVector (PrimState m) (V3 a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (V3 a) -> Int -> m (MVector (PrimState m) (V3 a)) #

Bounded a => Bounded (V3 a) Source # 

Methods

minBound :: V3 a #

maxBound :: V3 a #

Eq a => Eq (V3 a) Source # 

Methods

(==) :: V3 a -> V3 a -> Bool #

(/=) :: V3 a -> V3 a -> Bool #

Floating a => Floating (V3 a) Source # 

Methods

pi :: V3 a #

exp :: V3 a -> V3 a #

log :: V3 a -> V3 a #

sqrt :: V3 a -> V3 a #

(**) :: V3 a -> V3 a -> V3 a #

logBase :: V3 a -> V3 a -> V3 a #

sin :: V3 a -> V3 a #

cos :: V3 a -> V3 a #

tan :: V3 a -> V3 a #

asin :: V3 a -> V3 a #

acos :: V3 a -> V3 a #

atan :: V3 a -> V3 a #

sinh :: V3 a -> V3 a #

cosh :: V3 a -> V3 a #

tanh :: V3 a -> V3 a #

asinh :: V3 a -> V3 a #

acosh :: V3 a -> V3 a #

atanh :: V3 a -> V3 a #

log1p :: V3 a -> V3 a #

expm1 :: V3 a -> V3 a #

log1pexp :: V3 a -> V3 a #

log1mexp :: V3 a -> V3 a #

Fractional a => Fractional (V3 a) Source # 

Methods

(/) :: V3 a -> V3 a -> V3 a #

recip :: V3 a -> V3 a #

fromRational :: Rational -> V3 a #

Data a => Data (V3 a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> V3 a -> c (V3 a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (V3 a) #

toConstr :: V3 a -> Constr #

dataTypeOf :: V3 a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (V3 a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V3 a)) #

gmapT :: (forall b. Data b => b -> b) -> V3 a -> V3 a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V3 a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V3 a -> r #

gmapQ :: (forall d. Data d => d -> u) -> V3 a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> V3 a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> V3 a -> m (V3 a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V3 a -> m (V3 a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V3 a -> m (V3 a) #

Num a => Num (V3 a) Source # 

Methods

(+) :: V3 a -> V3 a -> V3 a #

(-) :: V3 a -> V3 a -> V3 a #

(*) :: V3 a -> V3 a -> V3 a #

negate :: V3 a -> V3 a #

abs :: V3 a -> V3 a #

signum :: V3 a -> V3 a #

fromInteger :: Integer -> V3 a #

Ord a => Ord (V3 a) Source # 

Methods

compare :: V3 a -> V3 a -> Ordering #

(<) :: V3 a -> V3 a -> Bool #

(<=) :: V3 a -> V3 a -> Bool #

(>) :: V3 a -> V3 a -> Bool #

(>=) :: V3 a -> V3 a -> Bool #

max :: V3 a -> V3 a -> V3 a #

min :: V3 a -> V3 a -> V3 a #

Read a => Read (V3 a) Source # 
Show a => Show (V3 a) Source # 

Methods

showsPrec :: Int -> V3 a -> ShowS #

show :: V3 a -> String #

showList :: [V3 a] -> ShowS #

Ix a => Ix (V3 a) Source # 

Methods

range :: (V3 a, V3 a) -> [V3 a] #

index :: (V3 a, V3 a) -> V3 a -> Int #

unsafeIndex :: (V3 a, V3 a) -> V3 a -> Int

inRange :: (V3 a, V3 a) -> V3 a -> Bool #

rangeSize :: (V3 a, V3 a) -> Int #

unsafeRangeSize :: (V3 a, V3 a) -> Int

Generic (V3 a) Source # 

Associated Types

type Rep (V3 a) :: * -> * #

Methods

from :: V3 a -> Rep (V3 a) x #

to :: Rep (V3 a) x -> V3 a #

Storable a => Storable (V3 a) Source # 

Methods

sizeOf :: V3 a -> Int #

alignment :: V3 a -> Int #

peekElemOff :: Ptr (V3 a) -> Int -> IO (V3 a) #

pokeElemOff :: Ptr (V3 a) -> Int -> V3 a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (V3 a) #

pokeByteOff :: Ptr b -> Int -> V3 a -> IO () #

peek :: Ptr (V3 a) -> IO (V3 a) #

poke :: Ptr (V3 a) -> V3 a -> IO () #

Unbox a => Unbox (V3 a) Source # 
Generic1 * V3 Source # 

Associated Types

type Rep1 V3 (f :: V3 -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 V3 f a #

to1 :: Rep1 V3 f a -> f a #

data MVector s (V3 a) Source # 
data MVector s (V3 a) = MV_V3 !Int !(MVector s a)
type Rep (V3 a) Source # 
data Vector (V3 a) Source # 
data Vector (V3 a) = V_V3 !Int !(Vector a)
type Rep1 * V3 Source # 

data V4 a Source #

A 4-dimensional vector.

Constructors

V4 !a !a !a !a 

Instances

Monad V4 Source # 

Methods

(>>=) :: V4 a -> (a -> V4 b) -> V4 b #

(>>) :: V4 a -> V4 b -> V4 b #

return :: a -> V4 a #

fail :: String -> V4 a #

Functor V4 Source # 

Methods

fmap :: (a -> b) -> V4 a -> V4 b #

(<$) :: a -> V4 b -> V4 a #

MonadFix V4 Source # 

Methods

mfix :: (a -> V4 a) -> V4 a #

Applicative V4 Source # 

Methods

pure :: a -> V4 a #

(<*>) :: V4 (a -> b) -> V4 a -> V4 b #

liftA2 :: (a -> b -> c) -> V4 a -> V4 b -> V4 c #

(*>) :: V4 a -> V4 b -> V4 b #

(<*) :: V4 a -> V4 b -> V4 a #

Foldable V4 Source # 

Methods

fold :: Monoid m => V4 m -> m #

foldMap :: Monoid m => (a -> m) -> V4 a -> m #

foldr :: (a -> b -> b) -> b -> V4 a -> b #

foldr' :: (a -> b -> b) -> b -> V4 a -> b #

foldl :: (b -> a -> b) -> b -> V4 a -> b #

foldl' :: (b -> a -> b) -> b -> V4 a -> b #

foldr1 :: (a -> a -> a) -> V4 a -> a #

foldl1 :: (a -> a -> a) -> V4 a -> a #

toList :: V4 a -> [a] #

null :: V4 a -> Bool #

length :: V4 a -> Int #

elem :: Eq a => a -> V4 a -> Bool #

maximum :: Ord a => V4 a -> a #

minimum :: Ord a => V4 a -> a #

sum :: Num a => V4 a -> a #

product :: Num a => V4 a -> a #

Traversable V4 Source # 

Methods

traverse :: Applicative f => (a -> f b) -> V4 a -> f (V4 b) #

sequenceA :: Applicative f => V4 (f a) -> f (V4 a) #

mapM :: Monad m => (a -> m b) -> V4 a -> m (V4 b) #

sequence :: Monad m => V4 (m a) -> m (V4 a) #

MonadZip V4 Source # 

Methods

mzip :: V4 a -> V4 b -> V4 (a, b) #

mzipWith :: (a -> b -> c) -> V4 a -> V4 b -> V4 c #

munzip :: V4 (a, b) -> (V4 a, V4 b) #

Unbox a => Vector Vector (V4 a) Source # 

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (V4 a) -> m (Vector (V4 a)) #

basicUnsafeThaw :: PrimMonad m => Vector (V4 a) -> m (Mutable Vector (PrimState m) (V4 a)) #

basicLength :: Vector (V4 a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (V4 a) -> Vector (V4 a) #

basicUnsafeIndexM :: Monad m => Vector (V4 a) -> Int -> m (V4 a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (V4 a) -> Vector (V4 a) -> m () #

elemseq :: Vector (V4 a) -> V4 a -> b -> b #

Unbox a => MVector MVector (V4 a) Source # 

Methods

basicLength :: MVector s (V4 a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (V4 a) -> MVector s (V4 a) #

basicOverlaps :: MVector s (V4 a) -> MVector s (V4 a) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (V4 a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (V4 a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> V4 a -> m (MVector (PrimState m) (V4 a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (V4 a) -> Int -> m (V4 a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (V4 a) -> Int -> V4 a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (V4 a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (V4 a) -> V4 a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (V4 a) -> MVector (PrimState m) (V4 a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (V4 a) -> MVector (PrimState m) (V4 a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (V4 a) -> Int -> m (MVector (PrimState m) (V4 a)) #

Bounded a => Bounded (V4 a) Source # 

Methods

minBound :: V4 a #

maxBound :: V4 a #

Eq a => Eq (V4 a) Source # 

Methods

(==) :: V4 a -> V4 a -> Bool #

(/=) :: V4 a -> V4 a -> Bool #

Floating a => Floating (V4 a) Source # 

Methods

pi :: V4 a #

exp :: V4 a -> V4 a #

log :: V4 a -> V4 a #

sqrt :: V4 a -> V4 a #

(**) :: V4 a -> V4 a -> V4 a #

logBase :: V4 a -> V4 a -> V4 a #

sin :: V4 a -> V4 a #

cos :: V4 a -> V4 a #

tan :: V4 a -> V4 a #

asin :: V4 a -> V4 a #

acos :: V4 a -> V4 a #

atan :: V4 a -> V4 a #

sinh :: V4 a -> V4 a #

cosh :: V4 a -> V4 a #

tanh :: V4 a -> V4 a #

asinh :: V4 a -> V4 a #

acosh :: V4 a -> V4 a #

atanh :: V4 a -> V4 a #

log1p :: V4 a -> V4 a #

expm1 :: V4 a -> V4 a #

log1pexp :: V4 a -> V4 a #

log1mexp :: V4 a -> V4 a #

Fractional a => Fractional (V4 a) Source # 

Methods

(/) :: V4 a -> V4 a -> V4 a #

recip :: V4 a -> V4 a #

fromRational :: Rational -> V4 a #

Data a => Data (V4 a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> V4 a -> c (V4 a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (V4 a) #

toConstr :: V4 a -> Constr #

dataTypeOf :: V4 a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (V4 a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V4 a)) #

gmapT :: (forall b. Data b => b -> b) -> V4 a -> V4 a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V4 a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V4 a -> r #

gmapQ :: (forall d. Data d => d -> u) -> V4 a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> V4 a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> V4 a -> m (V4 a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V4 a -> m (V4 a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V4 a -> m (V4 a) #

Num a => Num (V4 a) Source # 

Methods

(+) :: V4 a -> V4 a -> V4 a #

(-) :: V4 a -> V4 a -> V4 a #

(*) :: V4 a -> V4 a -> V4 a #

negate :: V4 a -> V4 a #

abs :: V4 a -> V4 a #

signum :: V4 a -> V4 a #

fromInteger :: Integer -> V4 a #

Ord a => Ord (V4 a) Source # 

Methods

compare :: V4 a -> V4 a -> Ordering #

(<) :: V4 a -> V4 a -> Bool #

(<=) :: V4 a -> V4 a -> Bool #

(>) :: V4 a -> V4 a -> Bool #

(>=) :: V4 a -> V4 a -> Bool #

max :: V4 a -> V4 a -> V4 a #

min :: V4 a -> V4 a -> V4 a #

Read a => Read (V4 a) Source # 
Show a => Show (V4 a) Source # 

Methods

showsPrec :: Int -> V4 a -> ShowS #

show :: V4 a -> String #

showList :: [V4 a] -> ShowS #

Ix a => Ix (V4 a) Source # 

Methods

range :: (V4 a, V4 a) -> [V4 a] #

index :: (V4 a, V4 a) -> V4 a -> Int #

unsafeIndex :: (V4 a, V4 a) -> V4 a -> Int

inRange :: (V4 a, V4 a) -> V4 a -> Bool #

rangeSize :: (V4 a, V4 a) -> Int #

unsafeRangeSize :: (V4 a, V4 a) -> Int

Generic (V4 a) Source # 

Associated Types

type Rep (V4 a) :: * -> * #

Methods

from :: V4 a -> Rep (V4 a) x #

to :: Rep (V4 a) x -> V4 a #

Storable a => Storable (V4 a) Source # 

Methods

sizeOf :: V4 a -> Int #

alignment :: V4 a -> Int #

peekElemOff :: Ptr (V4 a) -> Int -> IO (V4 a) #

pokeElemOff :: Ptr (V4 a) -> Int -> V4 a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (V4 a) #

pokeByteOff :: Ptr b -> Int -> V4 a -> IO () #

peek :: Ptr (V4 a) -> IO (V4 a) #

poke :: Ptr (V4 a) -> V4 a -> IO () #

Unbox a => Unbox (V4 a) Source # 
Generic1 * V4 Source # 

Associated Types

type Rep1 V4 (f :: V4 -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 V4 f a #

to1 :: Rep1 V4 f a -> f a #

data MVector s (V4 a) Source # 
data MVector s (V4 a) = MV_V4 !Int !(MVector s a)
type Rep (V4 a) Source # 
data Vector (V4 a) Source # 
data Vector (V4 a) = V_V4 !Int !(Vector a)
type Rep1 * V4 Source #