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.V2

Description

2-D Vectors

Synopsis

Documentation

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

Defined in Linear.V2

Associated Types

type Rep V2

Methods

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

index :: V2 a -> Rep V2 -> a

MonadFix V2 Source # 
Instance details

Defined in Linear.V2

Methods

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

MonadZip V2 Source # 
Instance details

Defined in Linear.V2

Methods

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

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

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

Foldable V2 Source # 
Instance details

Defined in Linear.V2

Methods

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

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

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

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

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

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

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

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

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

toList :: V2 a -> [a]

null :: V2 a -> Bool

length :: V2 a -> Int

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

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

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

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

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

Foldable1 V2 Source # 
Instance details

Defined in Linear.V2

Methods

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

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

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

toNonEmpty :: V2 a -> NonEmpty a

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

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

head :: V2 a -> a

last :: V2 a -> a

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

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

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

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

Eq1 V2 Source # 
Instance details

Defined in Linear.V2

Methods

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

Ord1 V2 Source # 
Instance details

Defined in Linear.V2

Methods

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

Read1 V2 Source # 
Instance details

Defined in Linear.V2

Methods

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

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

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

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

Show1 V2 Source # 
Instance details

Defined in Linear.V2

Methods

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

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

Traversable V2 Source # 
Instance details

Defined in Linear.V2

Methods

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

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

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

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

Applicative V2 Source # 
Instance details

Defined in Linear.V2

Methods

pure :: a -> V2 a

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

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

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

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

Functor V2 Source # 
Instance details

Defined in Linear.V2

Methods

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

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

Monad V2 Source # 
Instance details

Defined in Linear.V2

Methods

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

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

return :: a -> V2 a

Serial1 V2 Source # 
Instance details

Defined in Linear.V2

Methods

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

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

Distributive V2 Source # 
Instance details

Defined in Linear.V2

Methods

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

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

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

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

Hashable1 V2 Source # 
Instance details

Defined in Linear.V2

Methods

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

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

Defined in Linear.Trace

Methods

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

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

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

Defined in Linear.V2

Methods

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

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

Defined in Linear.V2

Methods

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

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

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

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

Bind V2 Source # 
Instance details

Defined in Linear.V2

Methods

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

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

Traversable1 V2 Source # 
Instance details

Defined in Linear.V2

Methods

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

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

Generic1 V2 Source # 
Instance details

Defined in Linear.V2

Associated Types

type Rep1 V2 :: k -> Type

Methods

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

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

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

Defined in Linear.Algebra

Methods

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

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

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

Defined in Linear.V2

Methods

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

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

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

Defined in Linear.V2

Methods

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

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

basicLength :: Vector (V2 a) -> Int

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

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

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

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

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

Defined in Linear.V2

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

toConstr :: V2 a -> Constr

dataTypeOf :: V2 a -> DataType

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

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

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

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

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

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

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

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

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

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

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

Defined in Linear.V2

Methods

sizeOf :: V2 a -> Int

alignment :: V2 a -> Int

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

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

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

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

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

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

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

Defined in Linear.V2

Methods

mempty :: V2 a

mappend :: V2 a -> V2 a -> V2 a

mconcat :: [V2 a] -> V2 a

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

Defined in Linear.V2

Methods

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

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

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

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

Defined in Linear.V2

Methods

minBound :: V2 a

maxBound :: V2 a

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

Defined in Linear.V2

Methods

pi :: V2 a

exp :: V2 a -> V2 a

log :: V2 a -> V2 a

sqrt :: V2 a -> V2 a

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

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

sin :: V2 a -> V2 a

cos :: V2 a -> V2 a

tan :: V2 a -> V2 a

asin :: V2 a -> V2 a

acos :: V2 a -> V2 a

atan :: V2 a -> V2 a

sinh :: V2 a -> V2 a

cosh :: V2 a -> V2 a

tanh :: V2 a -> V2 a

asinh :: V2 a -> V2 a

acosh :: V2 a -> V2 a

atanh :: V2 a -> V2 a

log1p :: V2 a -> V2 a

expm1 :: V2 a -> V2 a

log1pexp :: V2 a -> V2 a

log1mexp :: V2 a -> V2 a

Generic (V2 a) Source # 
Instance details

Defined in Linear.V2

Associated Types

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

Methods

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

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

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

Defined in Linear.V2

Methods

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

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

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

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

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

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

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

Defined in Linear.V2

Methods

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

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

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

negate :: V2 a -> V2 a

abs :: V2 a -> V2 a

signum :: V2 a -> V2 a

fromInteger :: Integer -> V2 a

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

Defined in Linear.V2

Methods

readsPrec :: Int -> ReadS (V2 a)

readList :: ReadS [V2 a]

readPrec :: ReadPrec (V2 a)

readListPrec :: ReadPrec [V2 a]

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

Defined in Linear.V2

Methods

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

recip :: V2 a -> V2 a

fromRational :: Rational -> V2 a

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

Defined in Linear.V2

Methods

showsPrec :: Int -> V2 a -> ShowS

show :: V2 a -> String

showList :: [V2 a] -> ShowS

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

Defined in Linear.V2

Methods

put :: V2 a -> Put

get :: Get (V2 a)

putList :: [V2 a] -> Put

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

Defined in Linear.V2

Methods

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

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

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

Defined in Linear.V2

Methods

put :: Putter (V2 a)

get :: Get (V2 a)

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

Defined in Linear.V2

Methods

rnf :: V2 a -> ()

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

Defined in Linear.V2

Methods

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

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

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

Defined in Linear.V2

Methods

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

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

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

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

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

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

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

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

Defined in Linear.V2

Methods

hashWithSalt :: Int -> V2 a -> Int

hash :: V2 a -> Int

Ixed (V2 a) Source # 
Instance details

Defined in Linear.V2

Methods

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

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

Defined in Linear.V2

Methods

nearZero :: V2 a -> Bool Source #

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

Defined in Linear.V2

Methods

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

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

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

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

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

Defined in Linear.V2

FoldableWithIndex (E V2) V2 Source # 
Instance details

Defined in Linear.V2

Methods

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

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

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

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

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

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

FunctorWithIndex (E V2) V2 Source # 
Instance details

Defined in Linear.V2

Methods

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

TraversableWithIndex (E V2) V2 Source # 
Instance details

Defined in Linear.V2

Methods

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

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

Defined in Linear.V2

Methods

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

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

Defined in Linear.V2

Methods

_1 :: Lens (V2 a) (V2 a) a a

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

Defined in Linear.V2

Methods

_2 :: Lens (V2 a) (V2 a) a a

type Rep V2 Source # 
Instance details

Defined in Linear.V2

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

Defined in Linear.Affine

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

Defined in Linear.V2

type Size V2 = 2
type Rep1 V2 Source # 
Instance details

Defined in Linear.V2

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

Defined in Linear.V2

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

Defined in Linear.V2

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

Defined in Linear.V2

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

Defined in Linear.V2

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

Defined in Linear.V2

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

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

ex :: R1 t => E t Source #

ey :: R2 t => E t Source #

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

the counter-clockwise perpendicular vector

>>> perp $ V2 10 20
V2 (-20) 10

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

unangle :: (Floating a, Ord a) => V2 a -> a Source #

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

The Z-component of the cross product of two vectors in the XY-plane.

>>> crossZ (V2 1 0) (V2 0 1)
1