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

Linear.V4

Description

4-D Vectors

Synopsis

Documentation

data V4 a Source #

A 4-dimensional vector.

Constructors

V4 !a !a !a !a 

Instances

Instances details
Monad V4 Source # 
Instance details

Defined in Linear.V4

Methods

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

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

return :: a -> V4 a

Functor V4 Source # 
Instance details

Defined in Linear.V4

Methods

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

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

MonadFix V4 Source # 
Instance details

Defined in Linear.V4

Methods

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

Applicative V4 Source # 
Instance details

Defined in Linear.V4

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 # 
Instance details

Defined in Linear.V4

Methods

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

foldMap :: Monoid m => (a -> m) -> V4 a -> 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 # 
Instance details

Defined in Linear.V4

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)

Distributive V4 Source # 
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 #

Representable V4 Source # 
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 #

Show1 V4 Source # 
Instance details

Defined in Linear.V4

Methods

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

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

Read1 V4 Source # 
Instance details

Defined in Linear.V4

Methods

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

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

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

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

Ord1 V4 Source # 
Instance details

Defined in Linear.V4

Methods

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

Eq1 V4 Source # 
Instance details

Defined in Linear.V4

Methods

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

MonadZip V4 Source # 
Instance details

Defined in Linear.V4

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)

Serial1 V4 Source # 
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 #

Hashable1 V4 Source # 
Instance details

Defined in Linear.V4

Methods

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

Apply V4 Source # 
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 #

Traversable1 V4 Source # 
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 #

Foldable1 V4 Source # 
Instance details

Defined in Linear.V4

Methods

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

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

toNonEmpty :: V4 a -> NonEmpty a Source #

Bind V4 Source # 
Instance details

Defined in Linear.V4

Methods

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

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

Additive V4 Source # 
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 #

Metric V4 Source # 
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 #

Finite V4 Source # 
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 Source # 
Instance details

Defined in Linear.V4

Methods

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

R2 V4 Source # 
Instance details

Defined in Linear.V4

Methods

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

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

R3 V4 Source # 
Instance details

Defined in Linear.V4

Methods

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

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

R4 V4 Source # 
Instance details

Defined in Linear.V4

Methods

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

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

Trace V4 Source # 
Instance details

Defined in Linear.Trace

Methods

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

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

Affine V4 Source # 
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 #

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

Defined in Linear.V4

Methods

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

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

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

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

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

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

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

Unbox a => MVector MVector (V4 a) Source # 
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 :: PrimMonad m => Int -> m (MVector (PrimState m) (V4 a)) Source #

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

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

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

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

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

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

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

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

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

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

Defined in Linear.Algebra

Methods

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

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

Bounded a => Bounded (V4 a) Source # 
Instance details

Defined in Linear.V4

Methods

minBound :: V4 a

maxBound :: V4 a

Eq a => Eq (V4 a) Source # 
Instance details

Defined in Linear.V4

Methods

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

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

Floating a => Floating (V4 a) Source # 
Instance details

Defined in Linear.V4

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 # 
Instance details

Defined in Linear.V4

Methods

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

recip :: V4 a -> V4 a

fromRational :: Rational -> V4 a

Data a => Data (V4 a) Source # 
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)

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 :: forall r r'. (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 # 
Instance details

Defined in Linear.V4

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 # 
Instance details

Defined in Linear.V4

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 # 
Instance details

Defined in Linear.V4

Methods

readsPrec :: Int -> ReadS (V4 a)

readList :: ReadS [V4 a]

readPrec :: ReadPrec (V4 a)

readListPrec :: ReadPrec [V4 a]

Show a => Show (V4 a) Source # 
Instance details

Defined in Linear.V4

Methods

showsPrec :: Int -> V4 a -> ShowS

show :: V4 a -> String

showList :: [V4 a] -> ShowS

Ix a => Ix (V4 a) Source # 
Instance details

Defined in Linear.V4

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 # 
Instance details

Defined in Linear.V4

Associated Types

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

Methods

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

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

Lift a => Lift (V4 a) Source # 
Instance details

Defined in Linear.V4

Methods

lift :: V4 a -> Q Exp

Storable a => Storable (V4 a) Source # 
Instance details

Defined in Linear.V4

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 ()

Serial a => Serial (V4 a) Source # 
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) Source # 
Instance details

Defined in Linear.V4

Methods

put :: Putter (V4 a) Source #

get :: Get (V4 a) Source #

Hashable a => Hashable (V4 a) Source # 
Instance details

Defined in Linear.V4

Methods

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

hash :: V4 a -> Int Source #

Unbox a => Unbox (V4 a) Source # 
Instance details

Defined in Linear.V4

Ixed (V4 a) Source # 
Instance details

Defined in Linear.V4

Methods

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

Binary a => Binary (V4 a) Source # 
Instance details

Defined in Linear.V4

Methods

put :: V4 a -> Put

get :: Get (V4 a)

putList :: [V4 a] -> Put

NFData a => NFData (V4 a) Source # 
Instance details

Defined in Linear.V4

Methods

rnf :: V4 a -> ()

Epsilon a => Epsilon (V4 a) Source # 
Instance details

Defined in Linear.V4

Methods

nearZero :: V4 a -> Bool Source #

Generic1 V4 Source # 
Instance details

Defined in Linear.V4

Associated Types

type Rep1 V4 :: k -> Type

Methods

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

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

FunctorWithIndex (E V4) V4 Source # 
Instance details

Defined in Linear.V4

Methods

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

imapped :: IndexedSetter (E V4) (V4 a) (V4 b) a b Source #

FoldableWithIndex (E V4) V4 Source # 
Instance details

Defined in Linear.V4

Methods

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

ifolded :: IndexedFold (E V4) (V4 a) a 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 #

TraversableWithIndex (E V4) V4 Source # 
Instance details

Defined in Linear.V4

Methods

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

itraversed :: IndexedTraversal (E V4) (V4 a) (V4 b) a b Source #

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

Defined in Linear.V4

Methods

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

Field1 (V4 a) (V4 a) a a Source # 
Instance details

Defined in Linear.V4

Methods

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

Field2 (V4 a) (V4 a) a a Source # 
Instance details

Defined in Linear.V4

Methods

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

Field3 (V4 a) (V4 a) a a Source # 
Instance details

Defined in Linear.V4

Methods

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

Field4 (V4 a) (V4 a) a a Source # 
Instance details

Defined in Linear.V4

Methods

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

type Rep V4 Source # 
Instance details

Defined in Linear.V4

type Rep V4 = E V4
type Size V4 Source # 
Instance details

Defined in Linear.V4

type Size V4 = 4
type Diff V4 Source # 
Instance details

Defined in Linear.Affine

type Diff V4 = V4
data MVector s (V4 a) Source # 
Instance details

Defined in Linear.V4

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

Defined in Linear.V4

type Rep (V4 a) = D1 ('MetaData "V4" "Linear.V4" "linear-1.20.9-DOReBBPX45Z7wmILVkBViE" '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))))
data Vector (V4 a) Source # 
Instance details

Defined in Linear.V4

data Vector (V4 a) = V_V4 !Int !(Vector a)
type Index (V4 a) Source # 
Instance details

Defined in Linear.V4

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

Defined in Linear.V4

type IxValue (V4 a) = a
type Rep1 V4 Source # 
Instance details

Defined in Linear.V4

type Rep1 V4 = D1 ('MetaData "V4" "Linear.V4" "linear-1.20.9-DOReBBPX45Z7wmILVkBViE" 'False) (C1 ('MetaCons "V4" '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 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1)))

vector :: Num a => V3 a -> V4 a Source #

Convert a 3-dimensional affine vector into a 4-dimensional homogeneous vector, i.e. sets the w coordinate to 0.

point :: Num a => V3 a -> V4 a Source #

Convert a 3-dimensional affine point into a 4-dimensional homogeneous vector, i.e. sets the w coordinate to 1.

normalizePoint :: Fractional a => V4 a -> V3 a Source #

Convert 4-dimensional projective coordinates to a 3-dimensional point. This operation may be denoted, euclidean [x:y:z:w] = (x/w, y/w, z/w) where the projective, homogenous, coordinate [x:y:z:w] is one of many associated with a single point (x/w, y/w, z/w).

class R1 t where Source #

A space that has at least 1 basis vector _x.

Methods

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

>>> V1 2 ^._x
2
>>> V1 2 & _x .~ 3
V1 3

Instances

Instances details
R1 Identity Source # 
Instance details

Defined in Linear.V1

Methods

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

R1 V1 Source # 
Instance details

Defined in Linear.V1

Methods

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

R1 V2 Source # 
Instance details

Defined in Linear.V2

Methods

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

R1 V3 Source # 
Instance details

Defined in Linear.V3

Methods

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

R1 V4 Source # 
Instance details

Defined in Linear.V4

Methods

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

R1 f => R1 (Point f) Source # 
Instance details

Defined in Linear.Affine

Methods

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

class R1 t => R2 t where Source #

A space that distinguishes 2 orthogonal basis vectors _x and _y, but may have more.

Minimal complete definition

_xy

Methods

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

>>> V2 1 2 ^._y
2
>>> V2 1 2 & _y .~ 3
V2 1 3

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

Instances

Instances details
R2 V2 Source # 
Instance details

Defined in Linear.V2

Methods

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

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

R2 V3 Source # 
Instance details

Defined in Linear.V3

Methods

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

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

R2 V4 Source # 
Instance details

Defined in Linear.V4

Methods

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

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

R2 f => R2 (Point f) Source # 
Instance details

Defined in Linear.Affine

Methods

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

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

_yx :: R2 t => Lens' (t a) (V2 a) Source #

>>> V2 1 2 ^. _yx
V2 2 1

class R2 t => R3 t where Source #

A space that distinguishes 3 orthogonal basis vectors: _x, _y, and _z. (It may have more)

Methods

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

>>> V3 1 2 3 ^. _z
3

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

Instances

Instances details
R3 V3 Source # 
Instance details

Defined in Linear.V3

Methods

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

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

R3 V4 Source # 
Instance details

Defined in Linear.V4

Methods

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

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

R3 f => R3 (Point f) Source # 
Instance details

Defined in Linear.Affine

Methods

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

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

_xz :: R3 t => Lens' (t a) (V2 a) Source #

_yz :: R3 t => Lens' (t a) (V2 a) Source #

_zx :: R3 t => Lens' (t a) (V2 a) Source #

_zy :: R3 t => Lens' (t a) (V2 a) Source #

_xzy :: R3 t => Lens' (t a) (V3 a) Source #

_yxz :: R3 t => Lens' (t a) (V3 a) Source #

_yzx :: R3 t => Lens' (t a) (V3 a) Source #

_zxy :: R3 t => Lens' (t a) (V3 a) Source #

_zyx :: R3 t => Lens' (t a) (V3 a) Source #

class R3 t => R4 t where Source #

A space that distinguishes orthogonal basis vectors _x, _y, _z, _w. (It may have more.)

Methods

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

>>> V4 1 2 3 4 ^._w
4

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

Instances

Instances details
R4 V4 Source # 
Instance details

Defined in Linear.V4

Methods

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

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

R4 f => R4 (Point f) Source # 
Instance details

Defined in Linear.Affine

Methods

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

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

_xw :: R4 t => Lens' (t a) (V2 a) Source #

_yw :: R4 t => Lens' (t a) (V2 a) Source #

_zw :: R4 t => Lens' (t a) (V2 a) Source #

_wx :: R4 t => Lens' (t a) (V2 a) Source #

_wy :: R4 t => Lens' (t a) (V2 a) Source #

_wz :: R4 t => Lens' (t a) (V2 a) Source #

_xyw :: R4 t => Lens' (t a) (V3 a) Source #

_xzw :: R4 t => Lens' (t a) (V3 a) Source #

_xwy :: R4 t => Lens' (t a) (V3 a) Source #

_xwz :: R4 t => Lens' (t a) (V3 a) Source #

_yxw :: R4 t => Lens' (t a) (V3 a) Source #

_yzw :: R4 t => Lens' (t a) (V3 a) Source #

_ywx :: R4 t => Lens' (t a) (V3 a) Source #

_ywz :: R4 t => Lens' (t a) (V3 a) Source #

_zxw :: R4 t => Lens' (t a) (V3 a) Source #

_zyw :: R4 t => Lens' (t a) (V3 a) Source #

_zwx :: R4 t => Lens' (t a) (V3 a) Source #

_zwy :: R4 t => Lens' (t a) (V3 a) Source #

_wxy :: R4 t => Lens' (t a) (V3 a) Source #

_wxz :: R4 t => Lens' (t a) (V3 a) Source #

_wyx :: R4 t => Lens' (t a) (V3 a) Source #

_wyz :: R4 t => Lens' (t a) (V3 a) Source #

_wzx :: R4 t => Lens' (t a) (V3 a) Source #

_wzy :: R4 t => Lens' (t a) (V3 a) Source #

_xywz :: R4 t => Lens' (t a) (V4 a) Source #

_xzyw :: R4 t => Lens' (t a) (V4 a) Source #

_xzwy :: R4 t => Lens' (t a) (V4 a) Source #

_xwyz :: R4 t => Lens' (t a) (V4 a) Source #

_xwzy :: R4 t => Lens' (t a) (V4 a) Source #

_yxzw :: R4 t => Lens' (t a) (V4 a) Source #

_yxwz :: R4 t => Lens' (t a) (V4 a) Source #

_yzxw :: R4 t => Lens' (t a) (V4 a) Source #

_yzwx :: R4 t => Lens' (t a) (V4 a) Source #

_ywxz :: R4 t => Lens' (t a) (V4 a) Source #

_ywzx :: R4 t => Lens' (t a) (V4 a) Source #

_zxyw :: R4 t => Lens' (t a) (V4 a) Source #

_zxwy :: R4 t => Lens' (t a) (V4 a) Source #

_zyxw :: R4 t => Lens' (t a) (V4 a) Source #

_zywx :: R4 t => Lens' (t a) (V4 a) Source #

_zwxy :: R4 t => Lens' (t a) (V4 a) Source #

_zwyx :: R4 t => Lens' (t a) (V4 a) Source #

_wxyz :: R4 t => Lens' (t a) (V4 a) Source #

_wxzy :: R4 t => Lens' (t a) (V4 a) Source #

_wyxz :: R4 t => Lens' (t a) (V4 a) Source #

_wyzx :: R4 t => Lens' (t a) (V4 a) Source #

_wzxy :: R4 t => Lens' (t a) (V4 a) Source #

_wzyx :: R4 t => Lens' (t a) (V4 a) Source #

ex :: R1 t => E t Source #

ey :: R2 t => E t Source #

ez :: R3 t => E t Source #

ew :: R4 t => E t Source #