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

Safe HaskellNone
LanguageHaskell2010

Physics.Constraint

Description

Types for describing the motion of physical objects. Functions for solving constraints.

Synopsis

Documentation

data InvMass2 Source #

Multiplicative inverse of linear and rotational mass

Constructors

InvMass2 

Fields

Instances

Eq InvMass2 Source # 
Show InvMass2 Source # 
NFData InvMass2 Source # 

Methods

rnf :: InvMass2 -> () #

Unbox InvMass2 Source # 
Vector Vector InvMass2 Source # 
MVector MVector InvMass2 Source # 
data Vector InvMass2 Source # 
data MVector s InvMass2 Source # 

data PhysicalObj Source #

The state of motion for a physical body. Rotation is measured in the Z direction (right-handed coordinates).

Instances

Show PhysicalObj Source # 
Generic PhysicalObj Source # 

Associated Types

type Rep PhysicalObj :: * -> * #

NFData PhysicalObj Source # 

Methods

rnf :: PhysicalObj -> () #

Unbox PhysicalObj Source # 
Vector Vector PhysicalObj Source # 
MVector MVector PhysicalObj Source # 
type Rep PhysicalObj Source # 
type Rep PhysicalObj = D1 * (MetaData "PhysicalObj" "Physics.Constraint" "shapes-0.1.0.0-E6UUiYRpOc15rGTlEn6KOE" False) (C1 * (MetaCons "PhysicalObj" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_physObjVel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * V2)) (S1 * (MetaSel (Just Symbol "_physObjRotVel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double))) ((:*:) * (S1 * (MetaSel (Just Symbol "_physObjPos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * V2)) ((:*:) * (S1 * (MetaSel (Just Symbol "_physObjRotPos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)) (S1 * (MetaSel (Just Symbol "_physObjInvMass") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * InvMass2))))))
data Vector PhysicalObj Source # 
data MVector s PhysicalObj Source # 

physObjVel3 :: Functor f => (V3 -> f V3) -> PhysicalObj -> f PhysicalObj Source #

Lens for 3D velocity vector: (v_x, v_y, v_rot)

toInvMass2 :: (Double, Double) -> InvMass2 Source #

Convert (linear mass, rotational inertia) into InvMass2. Use 0 for infinite mass (non-translating/non-rotating objects).

data Constraint Source #

A constraint equation between two objects to be solved using the objects' state of motion

Constructors

Constraint 

Fields

Instances

Show Constraint Source # 
Unbox Constraint Source # 
Flippable Constraint Source # 
Vector Vector Constraint Source # 
MVector MVector Constraint Source # 
data Vector Constraint Source # 
data MVector s Constraint Source # 

type Constraint' p = (p, p) -> Constraint Source #

Generates a constraint equation from a pair of objects

type PhysObjChanged = PhysicalObj -> PhysicalObj -> Bool Source #

Are these two different motion states? Used to determine whether the constraint solver has converged.

_constrainedVel6 :: (PhysicalObj, PhysicalObj) -> V6 Source #

Get a 6D velocity vector for a pair of objects. (a_vx, a_vy, a_vr, b_vx, b_vy, b_vr)

Called "constrained" because it's used with objects constrained together.

constrainedVel6 :: Functor f => (V6 -> f V6) -> (PhysicalObj, PhysicalObj) -> f (PhysicalObj, PhysicalObj) Source #

Lens for 6D velocity vector (_constrainedVel6)

invMassM2 :: InvMass2 -> InvMass2 -> Diag6 Source #

6x6 diagonal matrix of inverse mass

invMassM2 (InvMass2 ma ia) (InvMass2 mb ib) = Diag6 (V6 ma ma ia mb mb ib)

isStatic :: InvMass2 -> Bool Source #

Is this object completely static (unmoving)?

isStaticLin :: InvMass2 -> Bool Source #

Is this object non-translating (no center-of-mass movement)?

isStaticRot :: InvMass2 -> Bool Source #

Is this object non-rotating?

_physObjTransform :: PhysicalObj -> WorldTransform Source #

Get WorldTransform from origin to the current position (translation & rotation) of an object.

velocity2 :: PhysicalObj -> PhysicalObj -> V6 Source #

Get a 6D velocity vector for a pair of objects. Same as _constrainedVel6

lagrangian2 :: (PhysicalObj, PhysicalObj) -> Constraint -> Lagrangian Source #

Use objects' current state of motion to solve their constraint equation.

The Lagrangian multiplier is the (signed) magnitude of the constraint impulse along the constraint axis.

effMassM2 Source #

Arguments

:: V6

Jacobian

-> PhysicalObj 
-> PhysicalObj 
-> Double

Inverse of effective mass

The inverse effective mass of a pair of objects along the constraint axis

constraintImpulse2 Source #

Arguments

:: V6

Jacobian

-> Lagrangian 
-> V6

6D constraint impulse vector

Get the impulse that solves a constraint equation.

updateVelocity2_ Source #

Arguments

:: V6

6D velocity for two objects

-> Diag6

Inverse mass for two objects

-> V6

6D constraint impulse

-> V6

New 6D velocity

Apply a constraint impulse to two objects.

applyLagrangian2 Source #

Arguments

:: Diag6

Inverse mass

-> V6

Jacobian

-> Lagrangian 
-> (PhysicalObj, PhysicalObj) 
-> (PhysicalObj, PhysicalObj) 

Use a Lagrangian multiplier to update a pair of objects.

solveConstraint Source #

Arguments

:: Constraint

Constraint equation

-> (PhysicalObj, PhysicalObj) 
-> (PhysicalObj, PhysicalObj)

Updated state of motion

Solve a constraint between two objects.

applyLagrangian Source #

Arguments

:: Lagrangian

Lagrangian multiplier from solving the constraint

-> Constraint

The constraint equation

-> (PhysicalObj, PhysicalObj) 
-> (PhysicalObj, PhysicalObj)

Updated state of motion

Use a Lagrangian multiplier to update a pair of objects.

advanceObj :: PhysicalObj -> Double -> PhysicalObj Source #

Advance the position (translation & rotation) of an object by applying its velocity over a time delta.