sdl2-2.5.5.0: Both high- and low-level bindings to the SDL library (version 2.0.6+).
Safe HaskellSafe-Inferred
LanguageHaskell2010

SDL.Vect

Contents

Description

SDL's vector representation.

By default, re-exports the Linear and Linear.Affine modules from the linear package. With the no-linear Cabal flag, instead exports a duplicate implementation of the V2, V3, V4 and Point types from SDL.Internal.Vect, which provides as many instances as possible for those types while avoiding any additional dependencies.

Synopsis

Documentation

module Linear

Point

newtype Point (f :: Type -> Type) a Source #

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

Constructors

P (f a) 

Instances

Instances details
Generic1 (Point f :: Type -> Type) 
Instance details

Defined in Linear.Affine

Associated Types

type Rep1 (Point f) :: k -> Type Source #

Methods

from1 :: forall (a :: k). Point f a -> Rep1 (Point f) a Source #

to1 :: forall (a :: k). Rep1 (Point f) a -> Point f a Source #

Unbox (f a) => Vector Vector (Point f a) 
Instance details

Defined in Linear.Affine

Methods

basicUnsafeFreeze :: Mutable Vector s (Point f a) -> ST s (Vector (Point f a)) Source #

basicUnsafeThaw :: Vector (Point f a) -> ST s (Mutable Vector s (Point f a)) Source #

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

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

basicUnsafeIndexM :: Vector (Point f a) -> Int -> Box (Point f a) Source #

basicUnsafeCopy :: Mutable Vector s (Point f a) -> Vector (Point f a) -> ST s () Source #

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

Unbox (f a) => MVector MVector (Point f a) 
Instance details

Defined in Linear.Affine

Methods

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

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

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

basicUnsafeNew :: Int -> ST s (MVector s (Point f a)) Source #

basicInitialize :: MVector s (Point f a) -> ST s () Source #

basicUnsafeReplicate :: Int -> Point f a -> ST s (MVector s (Point f a)) Source #

basicUnsafeRead :: MVector s (Point f a) -> Int -> ST s (Point f a) Source #

basicUnsafeWrite :: MVector s (Point f a) -> Int -> Point f a -> ST s () Source #

basicClear :: MVector s (Point f a) -> ST s () Source #

basicSet :: MVector s (Point f a) -> Point f a -> ST s () Source #

basicUnsafeCopy :: MVector s (Point f a) -> MVector s (Point f a) -> ST s () Source #

basicUnsafeMove :: MVector s (Point f a) -> MVector s (Point f a) -> ST s () Source #

basicUnsafeGrow :: MVector s (Point f a) -> Int -> ST s (MVector s (Point f a)) Source #

Representable f => Representable (Point f) 
Instance details

Defined in Linear.Affine

Associated Types

type Rep (Point f) Source #

Methods

tabulate :: (Rep (Point f) -> a) -> Point f a Source #

index :: Point f a -> Rep (Point f) -> a Source #

Foldable f => Foldable (Point f) 
Instance details

Defined in Linear.Affine

Methods

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

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

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

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

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

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

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

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

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

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

null :: Point f a -> Bool Source #

length :: Point f a -> Int Source #

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

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

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

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

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

Eq1 f => Eq1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

liftEq :: (a -> b -> Bool) -> Point f a -> Point f b -> Bool Source #

Ord1 f => Ord1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

liftCompare :: (a -> b -> Ordering) -> Point f a -> Point f b -> Ordering Source #

Read1 f => Read1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Point f a) Source #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Point f a] Source #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Point f a) Source #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Point f a] Source #

Show1 f => Show1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Point f a -> ShowS Source #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Point f a] -> ShowS Source #

Traversable f => Traversable (Point f) 
Instance details

Defined in Linear.Affine

Methods

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

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

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

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

Applicative f => Applicative (Point f) 
Instance details

Defined in Linear.Affine

Methods

pure :: a -> Point f a Source #

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

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

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

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

Functor f => Functor (Point f) 
Instance details

Defined in Linear.Affine

Methods

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

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

Monad f => Monad (Point f) 
Instance details

Defined in Linear.Affine

Methods

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

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

return :: a -> Point f a Source #

Serial1 f => Serial1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

serializeWith :: MonadPut m => (a -> m ()) -> Point f a -> m () Source #

deserializeWith :: MonadGet m => m a -> m (Point f a) Source #

Distributive f => Distributive (Point f) 
Instance details

Defined in Linear.Affine

Methods

distribute :: Functor f0 => f0 (Point f a) -> Point f (f0 a) Source #

collect :: Functor f0 => (a -> Point f b) -> f0 a -> Point f (f0 b) Source #

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

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

Hashable1 f => Hashable1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Point f a -> Int Source #

Additive f => Affine (Point f) 
Instance details

Defined in Linear.Affine

Associated Types

type Diff (Point f) :: Type -> Type Source #

Methods

(.-.) :: Num a => Point f a -> Point f a -> Diff (Point f) a Source #

(.+^) :: Num a => Point f a -> Diff (Point f) a -> Point f a Source #

(.-^) :: Num a => Point f a -> Diff (Point f) a -> Point f a Source #

Metric f => Metric (Point f) 
Instance details

Defined in Linear.Affine

Methods

dot :: Num a => Point f a -> Point f a -> a Source #

quadrance :: Num a => Point f a -> a Source #

qd :: Num a => Point f a -> Point f a -> a Source #

distance :: Floating a => Point f a -> Point f a -> a Source #

norm :: Floating a => Point f a -> a Source #

signorm :: Floating a => Point f a -> Point f a Source #

Finite f => Finite (Point f) 
Instance details

Defined in Linear.Affine

Associated Types

type Size (Point f) :: Nat Source #

Methods

toV :: Point f a -> V (Size (Point f)) a Source #

fromV :: V (Size (Point f)) a -> Point f a Source #

R1 f => R1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

_x :: Lens' (Point f a) a Source #

R2 f => R2 (Point f) 
Instance details

Defined in Linear.Affine

Methods

_y :: Lens' (Point f a) a Source #

_xy :: Lens' (Point f a) (V2 a) Source #

R3 f => R3 (Point f) 
Instance details

Defined in Linear.Affine

Methods

_z :: Lens' (Point f a) a Source #

_xyz :: Lens' (Point f a) (V3 a) Source #

R4 f => R4 (Point f) 
Instance details

Defined in Linear.Affine

Methods

_w :: Lens' (Point f a) a Source #

_xyzw :: Lens' (Point f a) (V4 a) Source #

Additive f => Additive (Point f) 
Instance details

Defined in Linear.Affine

Methods

zero :: Num a => Point f a Source #

(^+^) :: Num a => Point f a -> Point f a -> Point f a Source #

(^-^) :: Num a => Point f a -> Point f a -> Point f a Source #

lerp :: Num a => a -> Point f a -> Point f a -> Point f a Source #

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

liftI2 :: (a -> b -> c) -> Point f a -> Point f b -> Point f c Source #

Apply f => Apply (Point f) 
Instance details

Defined in Linear.Affine

Methods

(<.>) :: Point f (a -> b) -> Point f a -> Point f b Source #

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

(<.) :: Point f a -> Point f b -> Point f a Source #

liftF2 :: (a -> b -> c) -> Point f a -> Point f b -> Point f c Source #

Bind f => Bind (Point f) 
Instance details

Defined in Linear.Affine

Methods

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

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

(Typeable f, Typeable a, Data (f a)) => Data (Point f a) 
Instance details

Defined in Linear.Affine

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) Source #

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

toConstr :: Point f a -> Constr Source #

dataTypeOf :: Point f a -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Storable (f a) => Storable (Point f a) 
Instance details

Defined in Linear.Affine

Methods

sizeOf :: Point f a -> Int Source #

alignment :: Point f a -> Int Source #

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

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

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

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

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

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

Monoid (f a) => Monoid (Point f a) 
Instance details

Defined in Linear.Affine

Methods

mempty :: Point f a Source #

mappend :: Point f a -> Point f a -> Point f a Source #

mconcat :: [Point f a] -> Point f a Source #

Semigroup (f a) => Semigroup (Point f a) 
Instance details

Defined in Linear.Affine

Methods

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

sconcat :: NonEmpty (Point f a) -> Point f a Source #

stimes :: Integral b => b -> Point f a -> Point f a Source #

Generic (Point f a) 
Instance details

Defined in Linear.Affine

Associated Types

type Rep (Point f a) :: Type -> Type Source #

Methods

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

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

Ix (f a) => Ix (Point f a) 
Instance details

Defined in Linear.Affine

Methods

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

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

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

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

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

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

Num (f a) => Num (Point f a) 
Instance details

Defined in Linear.Affine

Methods

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

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

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

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

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

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

fromInteger :: Integer -> Point f a Source #

Read (f a) => Read (Point f a) 
Instance details

Defined in Linear.Affine

Fractional (f a) => Fractional (Point f a) 
Instance details

Defined in Linear.Affine

Methods

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

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

fromRational :: Rational -> Point f a Source #

Show (f a) => Show (Point f a) 
Instance details

Defined in Linear.Affine

Methods

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

show :: Point f a -> String Source #

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

Binary (f a) => Binary (Point f a) 
Instance details

Defined in Linear.Affine

Methods

put :: Point f a -> Put Source #

get :: Get (Point f a) Source #

putList :: [Point f a] -> Put Source #

Serial (f a) => Serial (Point f a) 
Instance details

Defined in Linear.Affine

Methods

serialize :: MonadPut m => Point f a -> m () Source #

deserialize :: MonadGet m => m (Point f a) Source #

Serialize (f a) => Serialize (Point f a) 
Instance details

Defined in Linear.Affine

Methods

put :: Putter (Point f a) Source #

get :: Get (Point f a) Source #

NFData (f a) => NFData (Point f a) 
Instance details

Defined in Linear.Affine

Methods

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

Eq (f a) => Eq (Point f a) 
Instance details

Defined in Linear.Affine

Methods

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

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

Ord (f a) => Ord (Point f a) 
Instance details

Defined in Linear.Affine

Methods

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

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

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

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

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

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

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

Hashable (f a) => Hashable (Point f a) 
Instance details

Defined in Linear.Affine

Methods

hashWithSalt :: Int -> Point f a -> Int Source #

hash :: Point f a -> Int Source #

Ixed (f a) => Ixed (Point f a) 
Instance details

Defined in Linear.Affine

Methods

ix :: Index (Point f a) -> Traversal' (Point f a) (IxValue (Point f a)) Source #

Wrapped (Point f a) 
Instance details

Defined in Linear.Affine

Associated Types

type Unwrapped (Point f a) Source #

Methods

_Wrapped' :: Iso' (Point f a) (Unwrapped (Point f a)) Source #

Epsilon (f a) => Epsilon (Point f a) 
Instance details

Defined in Linear.Affine

Methods

nearZero :: Point f a -> Bool Source #

Random (f a) => Random (Point f a) 
Instance details

Defined in Linear.Affine

Methods

randomR :: RandomGen g => (Point f a, Point f a) -> g -> (Point f a, g) Source #

random :: RandomGen g => g -> (Point f a, g) Source #

randomRs :: RandomGen g => (Point f a, Point f a) -> g -> [Point f a] Source #

randoms :: RandomGen g => g -> [Point f a] Source #

Unbox (f a) => Unbox (Point f a) 
Instance details

Defined in Linear.Affine

t ~ Point g b => Rewrapped (Point f a) t 
Instance details

Defined in Linear.Affine

Traversable f => Each (Point f a) (Point f b) a b 
Instance details

Defined in Linear.Affine

Methods

each :: Traversal (Point f a) (Point f b) a b Source #

type Rep1 (Point f :: Type -> Type) 
Instance details

Defined in Linear.Affine

type Rep1 (Point f :: Type -> Type) = D1 ('MetaData "Point" "Linear.Affine" "linear-1.22-1667eab2f2cd5289649209dbfe141e37d11497ebaa622eeb775018047bd531ed" 'True) (C1 ('MetaCons "P" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 f)))
newtype MVector s (Point f a) 
Instance details

Defined in Linear.Affine

newtype MVector s (Point f a) = MV_P (MVector s (f a))
type Rep (Point f) 
Instance details

Defined in Linear.Affine

type Rep (Point f) = Rep f
type Diff (Point f) 
Instance details

Defined in Linear.Affine

type Diff (Point f) = f
type Size (Point f) 
Instance details

Defined in Linear.Affine

type Size (Point f) = Size f
type Rep (Point f a) 
Instance details

Defined in Linear.Affine

type Rep (Point f a) = D1 ('MetaData "Point" "Linear.Affine" "linear-1.22-1667eab2f2cd5289649209dbfe141e37d11497ebaa622eeb775018047bd531ed" 'True) (C1 ('MetaCons "P" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f a))))
type Index (Point f a) 
Instance details

Defined in Linear.Affine

type Index (Point f a) = Index (f a)
type IxValue (Point f a) 
Instance details

Defined in Linear.Affine

type IxValue (Point f a) = IxValue (f a)
type Unwrapped (Point f a) 
Instance details

Defined in Linear.Affine

type Unwrapped (Point f a) = f a
newtype Vector (Point f a) 
Instance details

Defined in Linear.Affine

newtype Vector (Point f a) = V_P (Vector (f a))

Vectors

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

Instances details
Representable V2 
Instance details

Defined in Linear.V2

Associated Types

type Rep V2 Source #

Methods

tabulate :: (Rep V2 -> a) -> V2 a Source #

index :: V2 a -> Rep V2 -> a Source #

MonadFix V2 
Instance details

Defined in Linear.V2

Methods

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

MonadZip V2 
Instance details

Defined in Linear.V2

Methods

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

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

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

Foldable V2 
Instance details

Defined in Linear.V2

Methods

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

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

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

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

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

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

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

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

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

toList :: V2 a -> [a] Source #

null :: V2 a -> Bool Source #

length :: V2 a -> Int Source #

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

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

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

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

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

Eq1 V2 
Instance details

Defined in Linear.V2

Methods

liftEq :: (a -> b -> Bool) -> V2 a -> V2 b -> Bool Source #

Ord1 V2 
Instance details

Defined in Linear.V2

Methods

liftCompare :: (a -> b -> Ordering) -> V2 a -> V2 b -> Ordering Source #

Read1 V2 
Instance details

Defined in Linear.V2

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (V2 a) Source #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [V2 a] Source #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (V2 a) Source #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [V2 a] Source #

Show1 V2 
Instance details

Defined in Linear.V2

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> V2 a -> ShowS Source #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [V2 a] -> ShowS Source #

Traversable V2 
Instance details

Defined in Linear.V2

Methods

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

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

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

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

Applicative V2 
Instance details

Defined in Linear.V2

Methods

pure :: a -> V2 a Source #

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

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

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

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

Functor V2 
Instance details

Defined in Linear.V2

Methods

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

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

Monad V2 
Instance details

Defined in Linear.V2

Methods

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

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

return :: a -> V2 a Source #

Serial1 V2 
Instance details

Defined in Linear.V2

Methods

serializeWith :: MonadPut m => (a -> m ()) -> V2 a -> m () Source #

deserializeWith :: MonadGet m => m a -> m (V2 a) Source #

Distributive V2 
Instance details

Defined in Linear.V2

Methods

distribute :: Functor f => f (V2 a) -> V2 (f a) Source #

collect :: Functor f => (a -> V2 b) -> f a -> V2 (f b) Source #

distributeM :: Monad m => m (V2 a) -> V2 (m a) Source #

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

Foldable1 V2 
Instance details

Defined in Linear.V2

Methods

fold1 :: Semigroup m => V2 m -> m Source #

foldMap1 :: Semigroup m => (a -> m) -> V2 a -> m Source #

foldMap1' :: Semigroup m => (a -> m) -> V2 a -> m Source #

toNonEmpty :: V2 a -> NonEmpty a Source #

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

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

head :: V2 a -> a Source #

last :: V2 a -> a Source #

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

foldlMap1' :: (a -> b) -> (b -> a -> b) -> V2 a -> b Source #

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

foldrMap1' :: (a -> b) -> (a -> b -> b) -> V2 a -> b Source #

Hashable1 V2 
Instance details

Defined in Linear.V2

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> V2 a -> Int Source #

Affine V2 
Instance details

Defined in Linear.Affine

Associated Types

type Diff V2 :: Type -> Type Source #

Methods

(.-.) :: Num a => V2 a -> V2 a -> Diff V2 a Source #

(.+^) :: Num a => V2 a -> Diff V2 a -> V2 a Source #

(.-^) :: Num a => V2 a -> Diff V2 a -> V2 a Source #

Metric V2 
Instance details

Defined in Linear.V2

Methods

dot :: Num a => V2 a -> V2 a -> a Source #

quadrance :: Num a => V2 a -> a Source #

qd :: Num a => V2 a -> V2 a -> a Source #

distance :: Floating a => V2 a -> V2 a -> a Source #

norm :: Floating a => V2 a -> a Source #

signorm :: Floating a => V2 a -> V2 a Source #

Trace V2 
Instance details

Defined in Linear.Trace

Methods

trace :: Num a => V2 (V2 a) -> a Source #

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

Finite V2 
Instance details

Defined in Linear.V2

Associated Types

type Size V2 :: Nat Source #

Methods

toV :: V2 a -> V (Size V2) a Source #

fromV :: V (Size V2) a -> V2 a Source #

R1 V2 
Instance details

Defined in Linear.V2

Methods

_x :: Lens' (V2 a) a Source #

R2 V2 
Instance details

Defined in Linear.V2

Methods

_y :: Lens' (V2 a) a Source #

_xy :: Lens' (V2 a) (V2 a) Source #

Additive V2 
Instance details

Defined in Linear.V2

Methods

zero :: Num a => V2 a Source #

(^+^) :: Num a => V2 a -> V2 a -> V2 a Source #

(^-^) :: Num a => V2 a -> V2 a -> V2 a Source #

lerp :: Num a => a -> V2 a -> V2 a -> V2 a Source #

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

liftI2 :: (a -> b -> c) -> V2 a -> V2 b -> V2 c Source #

Apply V2 
Instance details

Defined in Linear.V2

Methods

(<.>) :: V2 (a -> b) -> V2 a -> V2 b Source #

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

(<.) :: V2 a -> V2 b -> V2 a Source #

liftF2 :: (a -> b -> c) -> V2 a -> V2 b -> V2 c Source #

Bind V2 
Instance details

Defined in Linear.V2

Methods

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

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

Traversable1 V2 
Instance details

Defined in Linear.V2

Methods

traverse1 :: Apply f => (a -> f b) -> V2 a -> f (V2 b) Source #

sequence1 :: Apply f => V2 (f b) -> f (V2 b) Source #

Generic1 V2 
Instance details

Defined in Linear.V2

Associated Types

type Rep1 V2 :: k -> Type Source #

Methods

from1 :: forall (a :: k). V2 a -> Rep1 V2 a Source #

to1 :: forall (a :: k). Rep1 V2 a -> V2 a Source #

Num r => Coalgebra r (E V2) 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E V2 -> r) -> E V2 -> E V2 -> r Source #

counital :: (E V2 -> r) -> r Source #

Unbox a => Vector Vector (V2 a) 
Instance details

Defined in Linear.V2

Methods

basicUnsafeFreeze :: Mutable Vector s (V2 a) -> ST s (Vector (V2 a)) Source #

basicUnsafeThaw :: Vector (V2 a) -> ST s (Mutable Vector s (V2 a)) Source #

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

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

basicUnsafeIndexM :: Vector (V2 a) -> Int -> Box (V2 a) Source #

basicUnsafeCopy :: Mutable Vector s (V2 a) -> Vector (V2 a) -> ST s () Source #

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

Unbox a => MVector MVector (V2 a) 
Instance details

Defined in Linear.V2

Methods

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

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

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

basicUnsafeNew :: Int -> ST s (MVector s (V2 a)) Source #

basicInitialize :: MVector s (V2 a) -> ST s () Source #

basicUnsafeReplicate :: Int -> V2 a -> ST s (MVector s (V2 a)) Source #

basicUnsafeRead :: MVector s (V2 a) -> Int -> ST s (V2 a) Source #

basicUnsafeWrite :: MVector s (V2 a) -> Int -> V2 a -> ST s () Source #

basicClear :: MVector s (V2 a) -> ST s () Source #

basicSet :: MVector s (V2 a) -> V2 a -> ST s () Source #

basicUnsafeCopy :: MVector s (V2 a) -> MVector s (V2 a) -> ST s () Source #

basicUnsafeMove :: MVector s (V2 a) -> MVector s (V2 a) -> ST s () Source #

basicUnsafeGrow :: MVector s (V2 a) -> Int -> ST s (MVector s (V2 a)) Source #

Data a => Data (V2 a) 
Instance details

Defined in Linear.V2

Methods

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

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

toConstr :: V2 a -> Constr Source #

dataTypeOf :: V2 a -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Storable a => Storable (V2 a) 
Instance details

Defined in Linear.V2

Methods

sizeOf :: V2 a -> Int Source #

alignment :: V2 a -> Int Source #

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

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

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

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

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

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

Monoid a => Monoid (V2 a) 
Instance details

Defined in Linear.V2

Methods

mempty :: V2 a Source #

mappend :: V2 a -> V2 a -> V2 a Source #

mconcat :: [V2 a] -> V2 a Source #

Semigroup a => Semigroup (V2 a) 
Instance details

Defined in Linear.V2

Methods

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

sconcat :: NonEmpty (V2 a) -> V2 a Source #

stimes :: Integral b => b -> V2 a -> V2 a Source #

Bounded a => Bounded (V2 a) 
Instance details

Defined in Linear.V2

Methods

minBound :: V2 a Source #

maxBound :: V2 a Source #

Floating a => Floating (V2 a) 
Instance details

Defined in Linear.V2

Methods

pi :: V2 a Source #

exp :: V2 a -> V2 a Source #

log :: V2 a -> V2 a Source #

sqrt :: V2 a -> V2 a Source #

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

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

sin :: V2 a -> V2 a Source #

cos :: V2 a -> V2 a Source #

tan :: V2 a -> V2 a Source #

asin :: V2 a -> V2 a Source #

acos :: V2 a -> V2 a Source #

atan :: V2 a -> V2 a Source #

sinh :: V2 a -> V2 a Source #

cosh :: V2 a -> V2 a Source #

tanh :: V2 a -> V2 a Source #

asinh :: V2 a -> V2 a Source #

acosh :: V2 a -> V2 a Source #

atanh :: V2 a -> V2 a Source #

log1p :: V2 a -> V2 a Source #

expm1 :: V2 a -> V2 a Source #

log1pexp :: V2 a -> V2 a Source #

log1mexp :: V2 a -> V2 a Source #

Generic (V2 a) 
Instance details

Defined in Linear.V2

Associated Types

type Rep (V2 a) :: Type -> Type Source #

Methods

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

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

Ix a => Ix (V2 a) 
Instance details

Defined in Linear.V2

Methods

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

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

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

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

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

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

Num a => Num (V2 a) 
Instance details

Defined in Linear.V2

Methods

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

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

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

negate :: V2 a -> V2 a Source #

abs :: V2 a -> V2 a Source #

signum :: V2 a -> V2 a Source #

fromInteger :: Integer -> V2 a Source #

Read a => Read (V2 a) 
Instance details

Defined in Linear.V2

Fractional a => Fractional (V2 a) 
Instance details

Defined in Linear.V2

Methods

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

recip :: V2 a -> V2 a Source #

fromRational :: Rational -> V2 a Source #

Show a => Show (V2 a) 
Instance details

Defined in Linear.V2

Methods

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

show :: V2 a -> String Source #

showList :: [V2 a] -> ShowS Source #

Binary a => Binary (V2 a) 
Instance details

Defined in Linear.V2

Methods

put :: V2 a -> Put Source #

get :: Get (V2 a) Source #

putList :: [V2 a] -> Put Source #

Serial a => Serial (V2 a) 
Instance details

Defined in Linear.V2

Methods

serialize :: MonadPut m => V2 a -> m () Source #

deserialize :: MonadGet m => m (V2 a) Source #

Serialize a => Serialize (V2 a) 
Instance details

Defined in Linear.V2

Methods

put :: Putter (V2 a) Source #

get :: Get (V2 a) Source #

NFData a => NFData (V2 a) 
Instance details

Defined in Linear.V2

Methods

rnf :: V2 a -> () Source #

Eq a => Eq (V2 a) 
Instance details

Defined in Linear.V2

Methods

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

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

Ord a => Ord (V2 a) 
Instance details

Defined in Linear.V2

Methods

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

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

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

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

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

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

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

Hashable a => Hashable (V2 a) 
Instance details

Defined in Linear.V2

Methods

hashWithSalt :: Int -> V2 a -> Int Source #

hash :: V2 a -> Int Source #

Ixed (V2 a) 
Instance details

Defined in Linear.V2

Methods

ix :: Index (V2 a) -> Traversal' (V2 a) (IxValue (V2 a)) Source #

Epsilon a => Epsilon (V2 a) 
Instance details

Defined in Linear.V2

Methods

nearZero :: V2 a -> Bool Source #

Random a => Random (V2 a) 
Instance details

Defined in Linear.V2

Methods

randomR :: RandomGen g => (V2 a, V2 a) -> g -> (V2 a, g) Source #

random :: RandomGen g => g -> (V2 a, g) Source #

randomRs :: RandomGen g => (V2 a, V2 a) -> g -> [V2 a] Source #

randoms :: RandomGen g => g -> [V2 a] Source #

Unbox a => Unbox (V2 a) 
Instance details

Defined in Linear.V2

FoldableWithIndex (E V2) V2 
Instance details

Defined in Linear.V2

Methods

ifoldMap :: Monoid m => (E V2 -> a -> m) -> V2 a -> m Source #

ifoldMap' :: Monoid m => (E V2 -> a -> m) -> V2 a -> m Source #

ifoldr :: (E V2 -> a -> b -> b) -> b -> V2 a -> b Source #

ifoldl :: (E V2 -> b -> a -> b) -> b -> V2 a -> b Source #

ifoldr' :: (E V2 -> a -> b -> b) -> b -> V2 a -> b Source #

ifoldl' :: (E V2 -> b -> a -> b) -> b -> V2 a -> b Source #

FunctorWithIndex (E V2) V2 
Instance details

Defined in Linear.V2

Methods

imap :: (E V2 -> a -> b) -> V2 a -> V2 b Source #

TraversableWithIndex (E V2) V2 
Instance details

Defined in Linear.V2

Methods

itraverse :: Applicative f => (E V2 -> a -> f b) -> V2 a -> f (V2 b) Source #

Lift a => Lift (V2 a :: Type) 
Instance details

Defined in Linear.V2

Methods

lift :: Quote m => V2 a -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => V2 a -> Code m (V2 a) Source #

Each (V2 a) (V2 b) a b 
Instance details

Defined in Linear.V2

Methods

each :: Traversal (V2 a) (V2 b) a b Source #

Field1 (V2 a) (V2 a) a a 
Instance details

Defined in Linear.V2

Methods

_1 :: Lens (V2 a) (V2 a) a a Source #

Field2 (V2 a) (V2 a) a a 
Instance details

Defined in Linear.V2

Methods

_2 :: Lens (V2 a) (V2 a) a a Source #

type Rep V2 
Instance details

Defined in Linear.V2

type Rep V2 = E V2
type Diff V2 
Instance details

Defined in Linear.Affine

type Diff V2 = V2
type Size V2 
Instance details

Defined in Linear.V2

type Size V2 = 2
type Rep1 V2 
Instance details

Defined in Linear.V2

type Rep1 V2 = D1 ('MetaData "V2" "Linear.V2" "linear-1.22-1667eab2f2cd5289649209dbfe141e37d11497ebaa622eeb775018047bd531ed" 'False) (C1 ('MetaCons "V2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1))
data MVector s (V2 a) 
Instance details

Defined in Linear.V2

data MVector s (V2 a) = MV_V2 !Int !(MVector s a)
type Rep (V2 a) 
Instance details

Defined in Linear.V2

type Rep (V2 a) = D1 ('MetaData "V2" "Linear.V2" "linear-1.22-1667eab2f2cd5289649209dbfe141e37d11497ebaa622eeb775018047bd531ed" 'False) (C1 ('MetaCons "V2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)))
type Index (V2 a) 
Instance details

Defined in Linear.V2

type Index (V2 a) = E V2
type IxValue (V2 a) 
Instance details

Defined in Linear.V2

type IxValue (V2 a) = a
data Vector (V2 a) 
Instance details

Defined in Linear.V2

data Vector (V2 a) = V_V2 !Int !(Vector a)

data V3 a Source #

A 3-dimensional vector

Constructors

V3 !a !a !a 

Instances

Instances details
Representable V3 
Instance details

Defined in Linear.V3

Associated Types

type Rep V3 Source #

Methods

tabulate :: (Rep V3 -> a) -> V3 a Source #

index :: V3 a -> Rep V3 -> a Source #

MonadFix V3 
Instance details

Defined in Linear.V3

Methods

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

MonadZip V3 
Instance details

Defined in Linear.V3

Methods

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

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

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

Foldable V3 
Instance details

Defined in Linear.V3

Methods

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

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

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

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

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

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

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

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

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

toList :: V3 a -> [a] Source #

null :: V3 a -> Bool Source #

length :: V3 a -> Int Source #

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

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

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

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

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

Eq1 V3 
Instance details

Defined in Linear.V3

Methods

liftEq :: (a -> b -> Bool) -> V3 a -> V3 b -> Bool Source #

Ord1 V3 
Instance details

Defined in Linear.V3

Methods

liftCompare :: (a -> b -> Ordering) -> V3 a -> V3 b -> Ordering Source #

Read1 V3 
Instance details

Defined in Linear.V3

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (V3 a) Source #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [V3 a] Source #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (V3 a) Source #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [V3 a] Source #

Show1 V3 
Instance details

Defined in Linear.V3

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> V3 a -> ShowS Source #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [V3 a] -> ShowS Source #

Traversable V3 
Instance details

Defined in Linear.V3

Methods

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

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

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

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

Applicative V3 
Instance details

Defined in Linear.V3

Methods

pure :: a -> V3 a Source #

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

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

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

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

Functor V3 
Instance details

Defined in Linear.V3

Methods

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

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

Monad V3 
Instance details

Defined in Linear.V3

Methods

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

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

return :: a -> V3 a Source #

Serial1 V3 
Instance details

Defined in Linear.V3

Methods

serializeWith :: MonadPut m => (a -> m ()) -> V3 a -> m () Source #

deserializeWith :: MonadGet m => m a -> m (V3 a) Source #

Distributive V3 
Instance details

Defined in Linear.V3

Methods

distribute :: Functor f => f (V3 a) -> V3 (f a) Source #

collect :: Functor f => (a -> V3 b) -> f a -> V3 (f b) Source #

distributeM :: Monad m => m (V3 a) -> V3 (m a) Source #

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

Foldable1 V3 
Instance details

Defined in Linear.V3

Methods

fold1 :: Semigroup m => V3 m -> m Source #

foldMap1 :: Semigroup m => (a -> m) -> V3 a -> m Source #

foldMap1' :: Semigroup m => (a -> m) -> V3 a -> m Source #

toNonEmpty :: V3 a -> NonEmpty a Source #

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

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

head :: V3 a -> a Source #

last :: V3 a -> a Source #

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

foldlMap1' :: (a -> b) -> (b -> a -> b) -> V3 a -> b Source #

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

foldrMap1' :: (a -> b) -> (a -> b -> b) -> V3 a -> b Source #

Hashable1 V3 
Instance details

Defined in Linear.V3

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> V3 a -> Int Source #

Affine V3 
Instance details

Defined in Linear.Affine

Associated Types

type Diff V3 :: Type -> Type Source #

Methods

(.-.) :: Num a => V3 a -> V3 a -> Diff V3 a Source #

(.+^) :: Num a => V3 a -> Diff V3 a -> V3 a Source #

(.-^) :: Num a => V3 a -> Diff V3 a -> V3 a Source #

Metric V3 
Instance details

Defined in Linear.V3

Methods

dot :: Num a => V3 a -> V3 a -> a Source #

quadrance :: Num a => V3 a -> a Source #

qd :: Num a => V3 a -> V3 a -> a Source #

distance :: Floating a => V3 a -> V3 a -> a Source #

norm :: Floating a => V3 a -> a Source #

signorm :: Floating a => V3 a -> V3 a Source #

Trace V3 
Instance details

Defined in Linear.Trace

Methods

trace :: Num a => V3 (V3 a) -> a Source #

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

Finite V3 
Instance details

Defined in Linear.V3

Associated Types

type Size V3 :: Nat Source #

Methods

toV :: V3 a -> V (Size V3) a Source #

fromV :: V (Size V3) a -> V3 a Source #

R1 V3 
Instance details

Defined in Linear.V3

Methods

_x :: Lens' (V3 a) a Source #

R2 V3 
Instance details

Defined in Linear.V3

Methods

_y :: Lens' (V3 a) a Source #

_xy :: Lens' (V3 a) (V2 a) Source #

R3 V3 
Instance details

Defined in Linear.V3

Methods

_z :: Lens' (V3 a) a Source #

_xyz :: Lens' (V3 a) (V3 a) Source #

Additive V3 
Instance details

Defined in Linear.V3

Methods

zero :: Num a => V3 a Source #

(^+^) :: Num a => V3 a -> V3 a -> V3 a Source #

(^-^) :: Num a => V3 a -> V3 a -> V3 a Source #

lerp :: Num a => a -> V3 a -> V3 a -> V3 a Source #

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

liftI2 :: (a -> b -> c) -> V3 a -> V3 b -> V3 c Source #

Apply V3 
Instance details

Defined in Linear.V3

Methods

(<.>) :: V3 (a -> b) -> V3 a -> V3 b Source #

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

(<.) :: V3 a -> V3 b -> V3 a Source #

liftF2 :: (a -> b -> c) -> V3 a -> V3 b -> V3 c Source #

Bind V3 
Instance details

Defined in Linear.V3

Methods

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

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

Traversable1 V3 
Instance details

Defined in Linear.V3

Methods

traverse1 :: Apply f => (a -> f b) -> V3 a -> f (V3 b) Source #

sequence1 :: Apply f => V3 (f b) -> f (V3 b) Source #

Generic1 V3 
Instance details

Defined in Linear.V3

Associated Types

type Rep1 V3 :: k -> Type Source #

Methods

from1 :: forall (a :: k). V3 a -> Rep1 V3 a Source #

to1 :: forall (a :: k). Rep1 V3 a -> V3 a Source #

Num r => Coalgebra r (E V3) 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E V3 -> r) -> E V3 -> E V3 -> r Source #

counital :: (E V3 -> r) -> r Source #

Unbox a => Vector Vector (V3 a) 
Instance details

Defined in Linear.V3

Methods

basicUnsafeFreeze :: Mutable Vector s (V3 a) -> ST s (Vector (V3 a)) Source #

basicUnsafeThaw :: Vector (V3 a) -> ST s (Mutable Vector s (V3 a)) Source #

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

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

basicUnsafeIndexM :: Vector (V3 a) -> Int -> Box (V3 a) Source #

basicUnsafeCopy :: Mutable Vector s (V3 a) -> Vector (V3 a) -> ST s () Source #

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

Unbox a => MVector MVector (V3 a) 
Instance details

Defined in Linear.V3

Methods

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

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

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

basicUnsafeNew :: Int -> ST s (MVector s (V3 a)) Source #

basicInitialize :: MVector s (V3 a) -> ST s () Source #

basicUnsafeReplicate :: Int -> V3 a -> ST s (MVector s (V3 a)) Source #

basicUnsafeRead :: MVector s (V3 a) -> Int -> ST s (V3 a) Source #

basicUnsafeWrite :: MVector s (V3 a) -> Int -> V3 a -> ST s () Source #

basicClear :: MVector s (V3 a) -> ST s () Source #

basicSet :: MVector s (V3 a) -> V3 a -> ST s () Source #

basicUnsafeCopy :: MVector s (V3 a) -> MVector s (V3 a) -> ST s () Source #

basicUnsafeMove :: MVector s (V3 a) -> MVector s (V3 a) -> ST s () Source #

basicUnsafeGrow :: MVector s (V3 a) -> Int -> ST s (MVector s (V3 a)) Source #

Data a => Data (V3 a) 
Instance details

Defined in Linear.V3

Methods

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

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

toConstr :: V3 a -> Constr Source #

dataTypeOf :: V3 a -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Storable a => Storable (V3 a) 
Instance details

Defined in Linear.V3

Methods

sizeOf :: V3 a -> Int Source #

alignment :: V3 a -> Int Source #

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

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

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

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

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

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

Monoid a => Monoid (V3 a) 
Instance details

Defined in Linear.V3

Methods

mempty :: V3 a Source #

mappend :: V3 a -> V3 a -> V3 a Source #

mconcat :: [V3 a] -> V3 a Source #

Semigroup a => Semigroup (V3 a) 
Instance details

Defined in Linear.V3

Methods

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

sconcat :: NonEmpty (V3 a) -> V3 a Source #

stimes :: Integral b => b -> V3 a -> V3 a Source #

Bounded a => Bounded (V3 a) 
Instance details

Defined in Linear.V3

Methods

minBound :: V3 a Source #

maxBound :: V3 a Source #

Floating a => Floating (V3 a) 
Instance details

Defined in Linear.V3

Methods

pi :: V3 a Source #

exp :: V3 a -> V3 a Source #

log :: V3 a -> V3 a Source #

sqrt :: V3 a -> V3 a Source #

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

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

sin :: V3 a -> V3 a Source #

cos :: V3 a -> V3 a Source #

tan :: V3 a -> V3 a Source #

asin :: V3 a -> V3 a Source #

acos :: V3 a -> V3 a Source #

atan :: V3 a -> V3 a Source #

sinh :: V3 a -> V3 a Source #

cosh :: V3 a -> V3 a Source #

tanh :: V3 a -> V3 a Source #

asinh :: V3 a -> V3 a Source #

acosh :: V3 a -> V3 a Source #

atanh :: V3 a -> V3 a Source #

log1p :: V3 a -> V3 a Source #

expm1 :: V3 a -> V3 a Source #

log1pexp :: V3 a -> V3 a Source #

log1mexp :: V3 a -> V3 a Source #

Generic (V3 a) 
Instance details

Defined in Linear.V3

Associated Types

type Rep (V3 a) :: Type -> Type Source #

Methods

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

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

Ix a => Ix (V3 a) 
Instance details

Defined in Linear.V3

Methods

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

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

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

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

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

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

Num a => Num (V3 a) 
Instance details

Defined in Linear.V3

Methods

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

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

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

negate :: V3 a -> V3 a Source #

abs :: V3 a -> V3 a Source #

signum :: V3 a -> V3 a Source #

fromInteger :: Integer -> V3 a Source #

Read a => Read (V3 a) 
Instance details

Defined in Linear.V3

Fractional a => Fractional (V3 a) 
Instance details

Defined in Linear.V3

Methods

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

recip :: V3 a -> V3 a Source #

fromRational :: Rational -> V3 a Source #

Show a => Show (V3 a) 
Instance details

Defined in Linear.V3

Methods

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

show :: V3 a -> String Source #

showList :: [V3 a] -> ShowS Source #

Binary a => Binary (V3 a) 
Instance details

Defined in Linear.V3

Methods

put :: V3 a -> Put Source #

get :: Get (V3 a) Source #

putList :: [V3 a] -> Put Source #

Serial a => Serial (V3 a) 
Instance details

Defined in Linear.V3

Methods

serialize :: MonadPut m => V3 a -> m () Source #

deserialize :: MonadGet m => m (V3 a) Source #

Serialize a => Serialize (V3 a) 
Instance details

Defined in Linear.V3

Methods

put :: Putter (V3 a) Source #

get :: Get (V3 a) Source #

NFData a => NFData (V3 a) 
Instance details

Defined in Linear.V3

Methods

rnf :: V3 a -> () Source #

Eq a => Eq (V3 a) 
Instance details

Defined in Linear.V3

Methods

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

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

Ord a => Ord (V3 a) 
Instance details

Defined in Linear.V3

Methods

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

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

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

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

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

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

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

Hashable a => Hashable (V3 a) 
Instance details

Defined in Linear.V3

Methods

hashWithSalt :: Int -> V3 a -> Int Source #

hash :: V3 a -> Int Source #

Ixed (V3 a) 
Instance details

Defined in Linear.V3

Methods

ix :: Index (V3 a) -> Traversal' (V3 a) (IxValue (V3 a)) Source #

Epsilon a => Epsilon (V3 a) 
Instance details

Defined in Linear.V3

Methods

nearZero :: V3 a -> Bool Source #

Random a => Random (V3 a) 
Instance details

Defined in Linear.V3

Methods

randomR :: RandomGen g => (V3 a, V3 a) -> g -> (V3 a, g) Source #

random :: RandomGen g => g -> (V3 a, g) Source #

randomRs :: RandomGen g => (V3 a, V3 a) -> g -> [V3 a] Source #

randoms :: RandomGen g => g -> [V3 a] Source #

Unbox a => Unbox (V3 a) 
Instance details

Defined in Linear.V3

FoldableWithIndex (E V3) V3 
Instance details

Defined in Linear.V3

Methods

ifoldMap :: Monoid m => (E V3 -> a -> m) -> V3 a -> m Source #

ifoldMap' :: Monoid m => (E V3 -> a -> m) -> V3 a -> m Source #

ifoldr :: (E V3 -> a -> b -> b) -> b -> V3 a -> b Source #

ifoldl :: (E V3 -> b -> a -> b) -> b -> V3 a -> b Source #

ifoldr' :: (E V3 -> a -> b -> b) -> b -> V3 a -> b Source #

ifoldl' :: (E V3 -> b -> a -> b) -> b -> V3 a -> b Source #

FunctorWithIndex (E V3) V3 
Instance details

Defined in Linear.V3

Methods

imap :: (E V3 -> a -> b) -> V3 a -> V3 b Source #

TraversableWithIndex (E V3) V3 
Instance details

Defined in Linear.V3

Methods

itraverse :: Applicative f => (E V3 -> a -> f b) -> V3 a -> f (V3 b) Source #

Lift a => Lift (V3 a :: Type) 
Instance details

Defined in Linear.V3

Methods

lift :: Quote m => V3 a -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => V3 a -> Code m (V3 a) Source #

Each (V3 a) (V3 b) a b 
Instance details

Defined in Linear.V3

Methods

each :: Traversal (V3 a) (V3 b) a b Source #

Field1 (V3 a) (V3 a) a a 
Instance details

Defined in Linear.V3

Methods

_1 :: Lens (V3 a) (V3 a) a a Source #

Field2 (V3 a) (V3 a) a a 
Instance details

Defined in Linear.V3

Methods

_2 :: Lens (V3 a) (V3 a) a a Source #

Field3 (V3 a) (V3 a) a a 
Instance details

Defined in Linear.V3

Methods

_3 :: Lens (V3 a) (V3 a) a a Source #

type Rep V3 
Instance details

Defined in Linear.V3

type Rep V3 = E V3
type Diff V3 
Instance details

Defined in Linear.Affine

type Diff V3 = V3
type Size V3 
Instance details

Defined in Linear.V3

type Size V3 = 3
type Rep1 V3 
Instance details

Defined in Linear.V3

type Rep1 V3 = D1 ('MetaData "V3" "Linear.V3" "linear-1.22-1667eab2f2cd5289649209dbfe141e37d11497ebaa622eeb775018047bd531ed" 'False) (C1 ('MetaCons "V3" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1 :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1)))
data MVector s (V3 a) 
Instance details

Defined in Linear.V3

data MVector s (V3 a) = MV_V3 !Int !(MVector s a)
type Rep (V3 a) 
Instance details

Defined in Linear.V3

type Rep (V3 a) = D1 ('MetaData "V3" "Linear.V3" "linear-1.22-1667eab2f2cd5289649209dbfe141e37d11497ebaa622eeb775018047bd531ed" 'False) (C1 ('MetaCons "V3" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a))))
type Index (V3 a) 
Instance details

Defined in Linear.V3

type Index (V3 a) = E V3
type IxValue (V3 a) 
Instance details

Defined in Linear.V3

type IxValue (V3 a) = a
data Vector (V3 a) 
Instance details

Defined in Linear.V3

data Vector (V3 a) = V_V3 !Int !(Vector a)

data V4 a Source #

A 4-dimensional vector.

Constructors

V4 !a !a !a !a 

Instances

Instances details
Representable V4 
Instance details

Defined in Linear.V4

Associated Types

type Rep V4 Source #

Methods

tabulate :: (Rep V4 -> a) -> V4 a Source #

index :: V4 a -> Rep V4 -> a Source #

MonadFix V4 
Instance details

Defined in Linear.V4

Methods

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

MonadZip V4 
Instance details

Defined in Linear.V4

Methods

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

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

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

Foldable V4 
Instance details

Defined in Linear.V4

Methods

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

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

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

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

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

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

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

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

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

toList :: V4 a -> [a] Source #

null :: V4 a -> Bool Source #

length :: V4 a -> Int Source #

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

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

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

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

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

Eq1 V4 
Instance details

Defined in Linear.V4

Methods

liftEq :: (a -> b -> Bool) -> V4 a -> V4 b -> Bool Source #

Ord1 V4 
Instance details

Defined in Linear.V4

Methods

liftCompare :: (a -> b -> Ordering) -> V4 a -> V4 b -> Ordering Source #

Read1 V4 
Instance details

Defined in Linear.V4

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (V4 a) Source #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [V4 a] Source #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (V4 a) Source #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [V4 a] Source #

Show1 V4 
Instance details

Defined in Linear.V4

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> V4 a -> ShowS Source #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [V4 a] -> ShowS Source #

Traversable V4 
Instance details

Defined in Linear.V4

Methods

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

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

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

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

Applicative V4 
Instance details

Defined in Linear.V4

Methods

pure :: a -> V4 a Source #

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

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

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

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

Functor V4 
Instance details

Defined in Linear.V4

Methods

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

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

Monad V4 
Instance details

Defined in Linear.V4

Methods

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

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

return :: a -> V4 a Source #

Serial1 V4 
Instance details

Defined in Linear.V4

Methods

serializeWith :: MonadPut m => (a -> m ()) -> V4 a -> m () Source #

deserializeWith :: MonadGet m => m a -> m (V4 a) Source #

Distributive V4 
Instance details

Defined in Linear.V4

Methods

distribute :: Functor f => f (V4 a) -> V4 (f a) Source #

collect :: Functor f => (a -> V4 b) -> f a -> V4 (f b) Source #

distributeM :: Monad m => m (V4 a) -> V4 (m a) Source #

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

Foldable1 V4 
Instance details

Defined in Linear.V4

Methods

fold1 :: Semigroup m => V4 m -> m Source #

foldMap1 :: Semigroup m => (a -> m) -> V4 a -> m Source #

foldMap1' :: Semigroup m => (a -> m) -> V4 a -> m Source #

toNonEmpty :: V4 a -> NonEmpty a Source #

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

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

head :: V4 a -> a Source #

last :: V4 a -> a Source #

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

foldlMap1' :: (a -> b) -> (b -> a -> b) -> V4 a -> b Source #

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

foldrMap1' :: (a -> b) -> (a -> b -> b) -> V4 a -> b Source #

Hashable1 V4 
Instance details

Defined in Linear.V4

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> V4 a -> Int Source #

Affine V4 
Instance details

Defined in Linear.Affine

Associated Types

type Diff V4 :: Type -> Type Source #

Methods

(.-.) :: Num a => V4 a -> V4 a -> Diff V4 a Source #

(.+^) :: Num a => V4 a -> Diff V4 a -> V4 a Source #

(.-^) :: Num a => V4 a -> Diff V4 a -> V4 a Source #

Metric V4 
Instance details

Defined in Linear.V4

Methods

dot :: Num a => V4 a -> V4 a -> a Source #

quadrance :: Num a => V4 a -> a Source #

qd :: Num a => V4 a -> V4 a -> a Source #

distance :: Floating a => V4 a -> V4 a -> a Source #

norm :: Floating a => V4 a -> a Source #

signorm :: Floating a => V4 a -> V4 a Source #

Trace V4 
Instance details

Defined in Linear.Trace

Methods

trace :: Num a => V4 (V4 a) -> a Source #

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

Finite V4 
Instance details

Defined in Linear.V4

Associated Types

type Size V4 :: Nat Source #

Methods

toV :: V4 a -> V (Size V4) a Source #

fromV :: V (Size V4) a -> V4 a Source #

R1 V4 
Instance details

Defined in Linear.V4

Methods

_x :: Lens' (V4 a) a Source #

R2 V4 
Instance details

Defined in Linear.V4

Methods

_y :: Lens' (V4 a) a Source #

_xy :: Lens' (V4 a) (V2 a) Source #

R3 V4 
Instance details

Defined in Linear.V4

Methods

_z :: Lens' (V4 a) a Source #

_xyz :: Lens' (V4 a) (V3 a) Source #

R4 V4 
Instance details

Defined in Linear.V4

Methods

_w :: Lens' (V4 a) a Source #

_xyzw :: Lens' (V4 a) (V4 a) Source #

Additive V4 
Instance details

Defined in Linear.V4

Methods

zero :: Num a => V4 a Source #

(^+^) :: Num a => V4 a -> V4 a -> V4 a Source #

(^-^) :: Num a => V4 a -> V4 a -> V4 a Source #

lerp :: Num a => a -> V4 a -> V4 a -> V4 a Source #

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

liftI2 :: (a -> b -> c) -> V4 a -> V4 b -> V4 c Source #

Apply V4 
Instance details

Defined in Linear.V4

Methods

(<.>) :: V4 (a -> b) -> V4 a -> V4 b Source #

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

(<.) :: V4 a -> V4 b -> V4 a Source #

liftF2 :: (a -> b -> c) -> V4 a -> V4 b -> V4 c Source #

Bind V4 
Instance details

Defined in Linear.V4

Methods

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

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

Traversable1 V4 
Instance details

Defined in Linear.V4

Methods

traverse1 :: Apply f => (a -> f b) -> V4 a -> f (V4 b) Source #

sequence1 :: Apply f => V4 (f b) -> f (V4 b) Source #

Generic1 V4 
Instance details

Defined in Linear.V4

Associated Types

type Rep1 V4 :: k -> Type Source #

Methods

from1 :: forall (a :: k). V4 a -> Rep1 V4 a Source #

to1 :: forall (a :: k). Rep1 V4 a -> V4 a Source #

Num r => Coalgebra r (E V4) 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E V4 -> r) -> E V4 -> E V4 -> r Source #

counital :: (E V4 -> r) -> r Source #

Unbox a => Vector Vector (V4 a) 
Instance details

Defined in Linear.V4

Methods

basicUnsafeFreeze :: Mutable Vector s (V4 a) -> ST s (Vector (V4 a)) Source #

basicUnsafeThaw :: Vector (V4 a) -> ST s (Mutable Vector s (V4 a)) Source #

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

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

basicUnsafeIndexM :: Vector (V4 a) -> Int -> Box (V4 a) Source #

basicUnsafeCopy :: Mutable Vector s (V4 a) -> Vector (V4 a) -> ST s () Source #

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

Unbox a => MVector MVector (V4 a) 
Instance details

Defined in Linear.V4

Methods

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

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

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

basicUnsafeNew :: Int -> ST s (MVector s (V4 a)) Source #

basicInitialize :: MVector s (V4 a) -> ST s () Source #

basicUnsafeReplicate :: Int -> V4 a -> ST s (MVector s (V4 a)) Source #

basicUnsafeRead :: MVector s (V4 a) -> Int -> ST s (V4 a) Source #

basicUnsafeWrite :: MVector s (V4 a) -> Int -> V4 a -> ST s () Source #

basicClear :: MVector s (V4 a) -> ST s () Source #

basicSet :: MVector s (V4 a) -> V4 a -> ST s () Source #

basicUnsafeCopy :: MVector s (V4 a) -> MVector s (V4 a) -> ST s () Source #

basicUnsafeMove :: MVector s (V4 a) -> MVector s (V4 a) -> ST s () Source #

basicUnsafeGrow :: MVector s (V4 a) -> Int -> ST s (MVector s (V4 a)) Source #

Data a => Data (V4 a) 
Instance details

Defined in Linear.V4

Methods

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

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

toConstr :: V4 a -> Constr Source #

dataTypeOf :: V4 a -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Storable a => Storable (V4 a) 
Instance details

Defined in Linear.V4

Methods

sizeOf :: V4 a -> Int Source #

alignment :: V4 a -> Int Source #

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

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

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

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

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

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

Monoid a => Monoid (V4 a) 
Instance details

Defined in Linear.V4

Methods

mempty :: V4 a Source #

mappend :: V4 a -> V4 a -> V4 a Source #

mconcat :: [V4 a] -> V4 a Source #

Semigroup a => Semigroup (V4 a) 
Instance details

Defined in Linear.V4

Methods

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

sconcat :: NonEmpty (V4 a) -> V4 a Source #

stimes :: Integral b => b -> V4 a -> V4 a Source #

Bounded a => Bounded (V4 a) 
Instance details

Defined in Linear.V4

Methods

minBound :: V4 a Source #

maxBound :: V4 a Source #

Floating a => Floating (V4 a) 
Instance details

Defined in Linear.V4

Methods

pi :: V4 a Source #

exp :: V4 a -> V4 a Source #

log :: V4 a -> V4 a Source #

sqrt :: V4 a -> V4 a Source #

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

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

sin :: V4 a -> V4 a Source #

cos :: V4 a -> V4 a Source #

tan :: V4 a -> V4 a Source #

asin :: V4 a -> V4 a Source #

acos :: V4 a -> V4 a Source #

atan :: V4 a -> V4 a Source #

sinh :: V4 a -> V4 a Source #

cosh :: V4 a -> V4 a Source #

tanh :: V4 a -> V4 a Source #

asinh :: V4 a -> V4 a Source #

acosh :: V4 a -> V4 a Source #

atanh :: V4 a -> V4 a Source #

log1p :: V4 a -> V4 a Source #

expm1 :: V4 a -> V4 a Source #

log1pexp :: V4 a -> V4 a Source #

log1mexp :: V4 a -> V4 a Source #

Generic (V4 a) 
Instance details

Defined in Linear.V4

Associated Types

type Rep (V4 a) :: Type -> Type Source #

Methods

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

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

Ix a => Ix (V4 a) 
Instance details

Defined in Linear.V4

Methods

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

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

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

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

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

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

Num a => Num (V4 a) 
Instance details

Defined in Linear.V4

Methods

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

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

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

negate :: V4 a -> V4 a Source #

abs :: V4 a -> V4 a Source #

signum :: V4 a -> V4 a Source #

fromInteger :: Integer -> V4 a Source #

Read a => Read (V4 a) 
Instance details

Defined in Linear.V4

Fractional a => Fractional (V4 a) 
Instance details

Defined in Linear.V4

Methods

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

recip :: V4 a -> V4 a Source #

fromRational :: Rational -> V4 a Source #

Show a => Show (V4 a) 
Instance details

Defined in Linear.V4

Methods

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

show :: V4 a -> String Source #

showList :: [V4 a] -> ShowS Source #

Binary a => Binary (V4 a) 
Instance details

Defined in Linear.V4

Methods

put :: V4 a -> Put Source #

get :: Get (V4 a) Source #

putList :: [V4 a] -> Put Source #

Serial a => Serial (V4 a) 
Instance details

Defined in Linear.V4

Methods

serialize :: MonadPut m => V4 a -> m () Source #

deserialize :: MonadGet m => m (V4 a) Source #

Serialize a => Serialize (V4 a) 
Instance details

Defined in Linear.V4

Methods

put :: Putter (V4 a) Source #

get :: Get (V4 a) Source #

NFData a => NFData (V4 a) 
Instance details

Defined in Linear.V4

Methods

rnf :: V4 a -> () Source #

Eq a => Eq (V4 a) 
Instance details

Defined in Linear.V4

Methods

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

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

Ord a => Ord (V4 a) 
Instance details

Defined in Linear.V4

Methods

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

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

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

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

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

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

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

Hashable a => Hashable (V4 a) 
Instance details

Defined in Linear.V4

Methods

hashWithSalt :: Int -> V4 a -> Int Source #

hash :: V4 a -> Int Source #

Ixed (V4 a) 
Instance details

Defined in Linear.V4

Methods

ix :: Index (V4 a) -> Traversal' (V4 a) (IxValue (V4 a)) Source #

Epsilon a => Epsilon (V4 a) 
Instance details

Defined in Linear.V4

Methods

nearZero :: V4 a -> Bool Source #

Random a => Random (V4 a) 
Instance details

Defined in Linear.V4

Methods

randomR :: RandomGen g => (V4 a, V4 a) -> g -> (V4 a, g) Source #

random :: RandomGen g => g -> (V4 a, g) Source #

randomRs :: RandomGen g => (V4 a, V4 a) -> g -> [V4 a] Source #

randoms :: RandomGen g => g -> [V4 a] Source #

Unbox a => Unbox (V4 a) 
Instance details

Defined in Linear.V4

FoldableWithIndex (E V4) V4 
Instance details

Defined in Linear.V4

Methods

ifoldMap :: Monoid m => (E V4 -> a -> m) -> V4 a -> m Source #

ifoldMap' :: Monoid m => (E V4 -> a -> m) -> V4 a -> m Source #

ifoldr :: (E V4 -> a -> b -> b) -> b -> V4 a -> b Source #

ifoldl :: (E V4 -> b -> a -> b) -> b -> V4 a -> b Source #

ifoldr' :: (E V4 -> a -> b -> b) -> b -> V4 a -> b Source #

ifoldl' :: (E V4 -> b -> a -> b) -> b -> V4 a -> b Source #

FunctorWithIndex (E V4) V4 
Instance details

Defined in Linear.V4

Methods

imap :: (E V4 -> a -> b) -> V4 a -> V4 b Source #

TraversableWithIndex (E V4) V4 
Instance details

Defined in Linear.V4

Methods

itraverse :: Applicative f => (E V4 -> a -> f b) -> V4 a -> f (V4 b) Source #

Lift a => Lift (V4 a :: Type) 
Instance details

Defined in Linear.V4

Methods

lift :: Quote m => V4 a -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => V4 a -> Code m (V4 a) Source #

Each (V4 a) (V4 b) a b 
Instance details

Defined in Linear.V4

Methods

each :: Traversal (V4 a) (V4 b) a b Source #

Field1 (V4 a) (V4 a) a a 
Instance details

Defined in Linear.V4

Methods

_1 :: Lens (V4 a) (V4 a) a a Source #

Field2 (V4 a) (V4 a) a a 
Instance details

Defined in Linear.V4

Methods

_2 :: Lens (V4 a) (V4 a) a a Source #

Field3 (V4 a) (V4 a) a a 
Instance details

Defined in Linear.V4

Methods

_3 :: Lens (V4 a) (V4 a) a a Source #

Field4 (V4 a) (V4 a) a a 
Instance details

Defined in Linear.V4

Methods

_4 :: Lens (V4 a) (V4 a) a a Source #

type Rep V4 
Instance details

Defined in Linear.V4

type Rep V4 = E V4
type Diff V4 
Instance details

Defined in Linear.Affine

type Diff V4 = V4
type Size V4 
Instance details

Defined in Linear.V4

type Size V4 = 4
type Rep1 V4 
Instance details

Defined in Linear.V4

data MVector s (V4 a) 
Instance details

Defined in Linear.V4

data MVector s (V4 a) = MV_V4 !Int !(MVector s a)
type Rep (V4 a) 
Instance details

Defined in Linear.V4

type Rep (V4 a) = D1 ('MetaData "V4" "Linear.V4" "linear-1.22-1667eab2f2cd5289649209dbfe141e37d11497ebaa622eeb775018047bd531ed" 'False) (C1 ('MetaCons "V4" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a))))
type Index (V4 a) 
Instance details

Defined in Linear.V4

type Index (V4 a) = E V4
type IxValue (V4 a) 
Instance details

Defined in Linear.V4

type IxValue (V4 a) = a
data Vector (V4 a) 
Instance details

Defined in Linear.V4

data Vector (V4 a) = V_V4 !Int !(Vector a)