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

Linear.V3

Description

3-D Vectors

Synopsis

Documentation

data V3 a Source #

A 3-dimensional vector

Constructors

V3 !a !a !a 

Instances

Instances details
Representable V3 Source # 
Instance details

Defined in Linear.V3

Associated Types

type Rep V3

Methods

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

index :: V3 a -> Rep V3 -> a

MonadFix V3 Source # 
Instance details

Defined in Linear.V3

Methods

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

MonadZip V3 Source # 
Instance details

Defined in Linear.V3

Methods

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

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

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

Foldable V3 Source # 
Instance details

Defined in Linear.V3

Methods

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

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

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

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

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

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

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

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

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

toList :: V3 a -> [a]

null :: V3 a -> Bool

length :: V3 a -> Int

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

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

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

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

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

Eq1 V3 Source # 
Instance details

Defined in Linear.V3

Methods

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

Ord1 V3 Source # 
Instance details

Defined in Linear.V3

Methods

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

Read1 V3 Source # 
Instance details

Defined in Linear.V3

Methods

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

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

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

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

Show1 V3 Source # 
Instance details

Defined in Linear.V3

Methods

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

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

Traversable V3 Source # 
Instance details

Defined in Linear.V3

Methods

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

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

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

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

Applicative V3 Source # 
Instance details

Defined in Linear.V3

Methods

pure :: a -> V3 a

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

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

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

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

Functor V3 Source # 
Instance details

Defined in Linear.V3

Methods

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

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

Monad V3 Source # 
Instance details

Defined in Linear.V3

Methods

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

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

return :: a -> V3 a

Serial1 V3 Source # 
Instance details

Defined in Linear.V3

Methods

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

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

Distributive V3 Source # 
Instance details

Defined in Linear.V3

Methods

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

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

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

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

Hashable1 V3 Source # 
Instance details

Defined in Linear.V3

Methods

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

Affine V3 Source # 
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 Source # 
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 Source # 
Instance details

Defined in Linear.Trace

Methods

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

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

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

Defined in Linear.V3

Methods

_x :: Lens' (V3 a) 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 #

R3 V3 Source # 
Instance details

Defined in Linear.V3

Methods

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

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

Additive V3 Source # 
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 Source # 
Instance details

Defined in Linear.V3

Methods

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

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

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

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

Bind V3 Source # 
Instance details

Defined in Linear.V3

Methods

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

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

Foldable1 V3 Source # 
Instance details

Defined in Linear.V3

Methods

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

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

toNonEmpty :: V3 a -> NonEmpty a

Traversable1 V3 Source # 
Instance details

Defined in Linear.V3

Methods

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

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

Generic1 V3 Source # 
Instance details

Defined in Linear.V3

Associated Types

type Rep1 V3 :: k -> Type

Methods

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

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

Num r => Coalgebra r (E V3) Source # 
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) Source # 
Instance details

Defined in Linear.V3

Methods

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

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

basicLength :: Vector (V3 a) -> Int

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

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

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

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

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

Defined in Linear.V3

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

toConstr :: V3 a -> Constr

dataTypeOf :: V3 a -> DataType

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

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

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

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

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

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

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

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

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

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

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

Defined in Linear.V3

Methods

sizeOf :: V3 a -> Int

alignment :: V3 a -> Int

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

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

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

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

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

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

Monoid a => Monoid (V3 a) Source # 
Instance details

Defined in Linear.V3

Methods

mempty :: V3 a

mappend :: V3 a -> V3 a -> V3 a

mconcat :: [V3 a] -> V3 a

Semigroup a => Semigroup (V3 a) Source # 
Instance details

Defined in Linear.V3

Methods

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

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

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

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

Defined in Linear.V3

Methods

minBound :: V3 a

maxBound :: V3 a

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

Defined in Linear.V3

Methods

pi :: V3 a

exp :: V3 a -> V3 a

log :: V3 a -> V3 a

sqrt :: V3 a -> V3 a

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

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

sin :: V3 a -> V3 a

cos :: V3 a -> V3 a

tan :: V3 a -> V3 a

asin :: V3 a -> V3 a

acos :: V3 a -> V3 a

atan :: V3 a -> V3 a

sinh :: V3 a -> V3 a

cosh :: V3 a -> V3 a

tanh :: V3 a -> V3 a

asinh :: V3 a -> V3 a

acosh :: V3 a -> V3 a

atanh :: V3 a -> V3 a

log1p :: V3 a -> V3 a

expm1 :: V3 a -> V3 a

log1pexp :: V3 a -> V3 a

log1mexp :: V3 a -> V3 a

Generic (V3 a) Source # 
Instance details

Defined in Linear.V3

Associated Types

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

Methods

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

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

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

Defined in Linear.V3

Methods

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

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

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

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

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

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

Num a => Num (V3 a) Source # 
Instance details

Defined in Linear.V3

Methods

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

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

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

negate :: V3 a -> V3 a

abs :: V3 a -> V3 a

signum :: V3 a -> V3 a

fromInteger :: Integer -> V3 a

Read a => Read (V3 a) Source # 
Instance details

Defined in Linear.V3

Methods

readsPrec :: Int -> ReadS (V3 a)

readList :: ReadS [V3 a]

readPrec :: ReadPrec (V3 a)

readListPrec :: ReadPrec [V3 a]

Fractional a => Fractional (V3 a) Source # 
Instance details

Defined in Linear.V3

Methods

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

recip :: V3 a -> V3 a

fromRational :: Rational -> V3 a

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

Defined in Linear.V3

Methods

showsPrec :: Int -> V3 a -> ShowS

show :: V3 a -> String

showList :: [V3 a] -> ShowS

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

Defined in Linear.V3

Methods

put :: V3 a -> Put

get :: Get (V3 a)

putList :: [V3 a] -> Put

Serial a => Serial (V3 a) Source # 
Instance details

Defined in Linear.V3

Methods

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

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

Serialize a => Serialize (V3 a) Source # 
Instance details

Defined in Linear.V3

Methods

put :: Putter (V3 a)

get :: Get (V3 a)

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

Defined in Linear.V3

Methods

rnf :: V3 a -> ()

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

Defined in Linear.V3

Methods

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

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

Ord a => Ord (V3 a) Source # 
Instance details

Defined in Linear.V3

Methods

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

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

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

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

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

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

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

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

Defined in Linear.V3

Methods

hashWithSalt :: Int -> V3 a -> Int

hash :: V3 a -> Int

Ixed (V3 a) Source # 
Instance details

Defined in Linear.V3

Methods

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

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

Defined in Linear.V3

Methods

nearZero :: V3 a -> Bool Source #

Random a => Random (V3 a) Source # 
Instance details

Defined in Linear.V3

Methods

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

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

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

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

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

Defined in Linear.V3

FoldableWithIndex (E V3) V3 Source # 
Instance details

Defined in Linear.V3

Methods

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

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

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

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

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

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

FunctorWithIndex (E V3) V3 Source # 
Instance details

Defined in Linear.V3

Methods

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

TraversableWithIndex (E V3) V3 Source # 
Instance details

Defined in Linear.V3

Methods

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

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

Defined in Linear.V3

Methods

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

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

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

Defined in Linear.V3

Methods

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

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

Defined in Linear.V3

Methods

_1 :: Lens (V3 a) (V3 a) a a

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

Defined in Linear.V3

Methods

_2 :: Lens (V3 a) (V3 a) a a

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

Defined in Linear.V3

Methods

_3 :: Lens (V3 a) (V3 a) a a

type Rep V3 Source # 
Instance details

Defined in Linear.V3

type Rep V3 = E V3
type Diff V3 Source # 
Instance details

Defined in Linear.Affine

type Diff V3 = V3
type Size V3 Source # 
Instance details

Defined in Linear.V3

type Size V3 = 3
type Rep1 V3 Source # 
Instance details

Defined in Linear.V3

type Rep1 V3 = D1 ('MetaData "V3" "Linear.V3" "linear-1.22-3z3UuwHbz5r31zmMhE7fht" '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) Source # 
Instance details

Defined in Linear.V3

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

Defined in Linear.V3

type Rep (V3 a) = D1 ('MetaData "V3" "Linear.V3" "linear-1.22-3z3UuwHbz5r31zmMhE7fht" '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) Source # 
Instance details

Defined in Linear.V3

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

Defined in Linear.V3

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

Defined in Linear.V3

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

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

cross product

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

scalar triple product

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

Defined in Linear.Quaternion

Methods

_x :: Lens' (Quaternion 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 Quaternion Source # 
Instance details

Defined in Linear.Quaternion

Methods

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

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

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

Defined in Linear.Quaternion

Methods

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

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

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 #

ex :: R1 t => E t Source #

ey :: R2 t => E t Source #

ez :: R3 t => E t Source #