shapes-0.1.0.0: physics engine and other tools for 2D shapes

Safe HaskellNone
LanguageHaskell2010

Physics.Linear

Description

Arithmetic utility functions for vectors and matrices.

Synopsis

Documentation

data V2 Source #

Constructors

V2 Double# Double# 

Instances

Show V2 Source # 

Methods

showsPrec :: Int -> V2 -> ShowS #

show :: V2 -> String #

showList :: [V2] -> ShowS #

Arbitrary V2 Source # 

Methods

arbitrary :: Gen V2 #

shrink :: V2 -> [V2] #

NFData V2 Source # 

Methods

rnf :: V2 -> () #

Unbox V2 Source # 
WorldTransformable V2 Source # 
Vector Vector V2 Source # 
MVector MVector V2 Source # 
data Vector V2 Source # 
data MVector s V2 Source # 

lift2V2 :: (Double# -> Double# -> Double#) -> V2 -> V2 -> V2 Source #

data V3 Source #

Constructors

V3 Double# Double# Double# 

Instances

Show V3 Source # 

Methods

showsPrec :: Int -> V3 -> ShowS #

show :: V3 -> String #

showList :: [V3] -> ShowS #

Arbitrary V3 Source # 

Methods

arbitrary :: Gen V3 #

shrink :: V3 -> [V3] #

lift2V3 :: (Double# -> Double# -> Double#) -> V3 -> V3 -> V3 Source #

data V6 Source #

Instances

Show V6 Source # 

Methods

showsPrec :: Int -> V6 -> ShowS #

show :: V6 -> String #

showList :: [V6] -> ShowS #

Arbitrary V6 Source # 

Methods

arbitrary :: Gen V6 #

shrink :: V6 -> [V6] #

Unbox V6 Source # 
Vector Vector V6 Source # 
MVector MVector V6 Source # 
data Vector V6 Source # 
data MVector s V6 Source # 

lift2V6 :: (Double# -> Double# -> Double#) -> V6 -> V6 -> V6 Source #

data M2x2 Source #

Instances

split3v3 :: V6 -> (V3, V3) Source #

join3v3 :: V3 -> V3 -> V6 Source #

newtype Diag6 Source #

Constructors

Diag6 V6 

Instances

newtype P2 Source #

Constructors

P2 V2 

Instances

Show P2 Source # 

Methods

showsPrec :: Int -> P2 -> ShowS #

show :: P2 -> String #

showList :: [P2] -> ShowS #

Generic P2 Source # 

Associated Types

type Rep P2 :: * -> * #

Methods

from :: P2 -> Rep P2 x #

to :: Rep P2 x -> P2 #

NFData P2 Source # 

Methods

rnf :: P2 -> () #

Unbox P2 Source # 
WorldTransformable P2 Source # 
Vector Vector P2 Source # 
MVector MVector P2 Source # 
type Rep P2 Source # 
type Rep P2 = D1 * (MetaData "P2" "Physics.Linear" "shapes-0.1.0.0-E6UUiYRpOc15rGTlEn6KOE" True) (C1 * (MetaCons "P2" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * V2)))
data Vector P2 Source # 
data MVector s P2 Source # 
data MVector s P2 = MV_P2 (MVector s V2)

plusV2 :: V2 -> V2 -> V2 Source #

plusV6 :: V6 -> V6 -> V6 Source #

minusV2 :: V2 -> V2 -> V2 Source #

crossV2V2 :: V2 -> V2 -> V2 -> V2 Source #

lengthV2 :: V2 -> Double Source #

Length of a vector.

sqLengthV2 :: V2 -> Double Source #

Squared length of a vector.

diffP2 :: P2 -> P2 -> V2 Source #

vplusP2 :: V2 -> P2 -> P2 Source #

pminusV2 :: P2 -> V2 -> P2 Source #

pplusV2 :: P2 -> V2 -> P2 Source #

afmul :: M3x3 -> V2 -> V2 Source #

afmul' :: M3x3 -> P2 -> P2 Source #

data Line2 Source #

Constructors

Line2 

Fields

data ClipResult a Source #

Constructors

ClipLeft !a

clip the left side to this new endpoint

ClipRight !a

clip the right side to this new endpoint

ClipBoth !a

the entire segment was out-of-bounds

ClipNone

the entire segment was in-bounds

applyClip :: ClipResult a -> SP a a -> Either a (SP a a) Source #

Apply a ClipResult to a line segment. Replaces clipped endpoints. If both endpoints (entire segment) clipped, use Lefted clip point.

TODO: Delete this function?

applyClip' :: ClipResult a -> SP a a -> Maybe (SP a a) Source #

Alternate form of applyClip. Nothing if entire segment clipped.

applyClip'' :: ClipResult a -> SP s s -> Maybe (Either s (SP s s)) Source #

Alternate form of applyClip. Removes clipped points.

lApplyClip Source #

Arguments

:: ASetter' s a

lens to access the "point" data to apply the clipping

-> ClipResult a

clipping

-> SP s s

line segment with endpoints that contain "point" data

-> Either s (SP s s) 

Alternate form of applyClip. Applies clipping using the given lens.

If ClipBoth, then use only the first vertex of the line segment and change it to use the clipping point. (TODO: Why?)

TODO: Delete this function?

lApplyClip' :: ASetter' s a -> ClipResult a -> SP s s -> Maybe (SP s s) Source #

Alternate form of lApplyClip. If the entire segment was behind the bound, use Nothing.

clipSegment Source #

Arguments

:: Line2

bounding plane

-> SP Line2 (SP P2 P2)

(plane of the line segment, endpoints of the line segment)

-> ClipResult P2

which endpoint(s) to clip, and what point to clip to

Given a bounding plane (expressed as a point and a normal), figure out how to clip a line segment so it is on the positive side of the plane.