geomancy-layout-0.1: Geometry and matrix manipulation
Safe HaskellSafe-Inferred
LanguageGHC2021

Geomancy.Layout.Box

Synopsis

Documentation

data Box Source #

2D rectangle with its origin at the center.

Size transformations don't affect its position and vice versa.

┏━━━━━┓
┃     ┃
┃  *  ┃
┃     ┃
┗━━━━━┛

Constructors

Box 

Fields

Instances

Instances details
Storable Box Source # 
Instance details

Defined in Geomancy.Layout.Box

Methods

sizeOf :: Box -> Int #

alignment :: Box -> Int #

peekElemOff :: Ptr Box -> Int -> IO Box #

pokeElemOff :: Ptr Box -> Int -> Box -> IO () #

peekByteOff :: Ptr b -> Int -> IO Box #

pokeByteOff :: Ptr b -> Int -> Box -> IO () #

peek :: Ptr Box -> IO Box #

poke :: Ptr Box -> Box -> IO () #

Semigroup Box Source # 
Instance details

Defined in Geomancy.Layout.Box

Methods

(<>) :: Box -> Box -> Box #

sconcat :: NonEmpty Box -> Box #

stimes :: Integral b => b -> Box -> Box #

Generic Box Source # 
Instance details

Defined in Geomancy.Layout.Box

Associated Types

type Rep Box :: Type -> Type #

Methods

from :: Box -> Rep Box x #

to :: Rep Box x -> Box #

Show Box Source # 
Instance details

Defined in Geomancy.Layout.Box

Methods

showsPrec :: Int -> Box -> ShowS #

show :: Box -> String #

showList :: [Box] -> ShowS #

Eq Box Source # 
Instance details

Defined in Geomancy.Layout.Box

Methods

(==) :: Box -> Box -> Bool #

(/=) :: Box -> Box -> Bool #

Ord Box Source # 
Instance details

Defined in Geomancy.Layout.Box

Methods

compare :: Box -> Box -> Ordering #

(<) :: Box -> Box -> Bool #

(<=) :: Box -> Box -> Bool #

(>) :: Box -> Box -> Bool #

(>=) :: Box -> Box -> Bool #

max :: Box -> Box -> Box #

min :: Box -> Box -> Box #

Block Box Source # 
Instance details

Defined in Geomancy.Layout.Box

Associated Types

type PackedSize Box :: Nat #

Methods

alignment140 :: proxy Box -> Int #

sizeOf140 :: proxy Box -> Int #

isStruct :: proxy Box -> Bool #

read140 :: MonadIO m => Ptr a -> Diff a Box -> m Box #

write140 :: MonadIO m => Ptr a -> Diff a Box -> Box -> m () #

alignment430 :: proxy Box -> Int #

sizeOf430 :: proxy Box -> Int #

read430 :: MonadIO m => Ptr a -> Diff a Box -> m Box #

write430 :: MonadIO m => Ptr a -> Diff a Box -> Box -> m () #

sizeOfPacked :: proxy Box -> Int #

readPacked :: MonadIO m => Ptr a -> Diff a Box -> m Box #

writePacked :: MonadIO m => Ptr a -> Diff a Box -> Box -> m () #

type Rep Box Source # 
Instance details

Defined in Geomancy.Layout.Box

type Rep Box = D1 ('MetaData "Box" "Geomancy.Layout.Box" "geomancy-layout-0.1-6gfOOfJe0gTH6A2Oj8TBop" 'False) (C1 ('MetaCons "Box" 'PrefixI 'True) (S1 ('MetaSel ('Just "position") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Vec2) :*: S1 ('MetaSel ('Just "size") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Vec2)))
type PackedSize Box Source # 
Instance details

Defined in Geomancy.Layout.Box

box_ :: Vec2 -> Box Source #

Place a Box with given dimensions at (0,0).

degenerate :: Box -> Bool Source #

Check if one of the dimensions is negative.

move :: Vec2 -> Box -> Box Source #

Move the Box by the given vector.

resize :: Vec2 -> Box -> Box Source #

Adjust Box size by a given amount (absolute).

rescale :: Vec2 -> Box -> Box Source #

Adjust Box size by a given amount (relative).

Edge representation

newtype TRBL Source #

Packed top- right- bottom- left- edge values.

Constructors

TRBL Vec4 

Instances

Instances details
Semigroup TRBL Source # 
Instance details

Defined in Geomancy.Layout.Box

Methods

(<>) :: TRBL -> TRBL -> TRBL #

sconcat :: NonEmpty TRBL -> TRBL #

stimes :: Integral b => b -> TRBL -> TRBL #

Generic TRBL Source # 
Instance details

Defined in Geomancy.Layout.Box

Associated Types

type Rep TRBL :: Type -> Type #

Methods

from :: TRBL -> Rep TRBL x #

to :: Rep TRBL x -> TRBL #

Show TRBL Source # 
Instance details

Defined in Geomancy.Layout.Box

Methods

showsPrec :: Int -> TRBL -> ShowS #

show :: TRBL -> String #

showList :: [TRBL] -> ShowS #

Eq TRBL Source # 
Instance details

Defined in Geomancy.Layout.Box

Methods

(==) :: TRBL -> TRBL -> Bool #

(/=) :: TRBL -> TRBL -> Bool #

Ord TRBL Source # 
Instance details

Defined in Geomancy.Layout.Box

Methods

compare :: TRBL -> TRBL -> Ordering #

(<) :: TRBL -> TRBL -> Bool #

(<=) :: TRBL -> TRBL -> Bool #

(>) :: TRBL -> TRBL -> Bool #

(>=) :: TRBL -> TRBL -> Bool #

max :: TRBL -> TRBL -> TRBL #

min :: TRBL -> TRBL -> TRBL #

type Rep TRBL Source # 
Instance details

Defined in Geomancy.Layout.Box

type Rep TRBL = D1 ('MetaData "TRBL" "Geomancy.Layout.Box" "geomancy-layout-0.1-6gfOOfJe0gTH6A2Oj8TBop" 'True) (C1 ('MetaCons "TRBL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Vec4)))

type WithTRBL r = Float -> Float -> Float -> Float -> r Source #

addPadding :: TRBL -> Box -> Box Source #

Construct a smaller Box by adding non-uniform padding.

addPaddingRel :: TRBL -> Box -> Box Source #

Construct a smaller Box by adding non-uniform padding as a fraction of Box size.

addMargins :: TRBL -> Box -> Box Source #

Construct a larger Box by adding non-uniform margins.

addMarginsRel :: TRBL -> Box -> Box Source #

Construct a larger Box by adding non-uniform margins as a fraction of Box size.

AABB representation

fromCorners :: Vec2 -> Vec2 -> Box Source #

Bounding box from 2 points, automatically sorted.

toCorners :: Box -> (Vec2, Vec2) Source #

2-point AABB.

withCorners :: Box -> (Vec2 -> Vec2 -> r) -> r Source #

Point-box interaction

projectInto :: Vec2 -> Box -> Vec2 Source #

Project a point into the Box space.

inside :: Vec2 -> Box -> Bool Source #

Test if a point is within the Box bounds.

whenInside :: Applicative m => Vec2 -> Box -> (Vec2 -> m ()) -> m () Source #

Box-box interaction

canContain :: Box -> Box -> Bool Source #

Test if a Box can contain a given Box.

contains :: Box -> Box -> Bool Source #

Test if a Box fully contains a given Box.

union :: Box -> Box -> Box Source #

Get a Box that tightly wraps both its elements.

intersection :: Box -> Box -> Maybe Box Source #

Get an intersection between two boxes, if there is one.

Use faster intersects instead if only need a test.

intersectionDirty :: Box -> Box -> Box Source #

Get a potentially-degenerate intersection between two boxes.

intersects :: Box -> Box -> Bool Source #

Box-box intersection test.

Any edge contact counts as intersection. For area contact use intersection, which is a little less efficient.

leftovers :: Box -> Box -> TRBL Source #

Remaining space when one box is placed inside another.

All positive when the box is fully inside. Negative edges mean the box is "outside" in that direction.

addPadding (leftovers inner outer) inner === outer
addMargins (leftovers inner outer) outer === inner

Conversion

mkTransform :: Box -> Transform Source #

Build a transformation matrix to stretch a unit square and place it at depth 0.0.

mkTransformZ :: Float -> Box -> Transform Source #

Build a transformation matrix to stretch a unit square and place it at a given depth.