cattrap-0.1.0.0: Lays out boxes according to the CSS Box Model.
Safe HaskellSafe
LanguageHaskell2010

Graphics.Layout.Box

Description

Datastructures representing the CSS box model, & utilities for operating on them.

Synopsis

Documentation

data Border m n Source #

Amount of space surrounding the box.

Constructors

Border 

Fields

mapX :: (n -> nn) -> Border m n -> Border m nn Source #

Convert horizontal spacing via given callback.

mapY :: (m -> mm) -> Border m n -> Border mm n Source #

Convert vertical spacing via given callback.

data Size m n Source #

2D size of a box. Typically inline is width & block is height. This may change as support for vertical layout is added.

Constructors

Size 

Fields

Instances

Instances details
(Eq n, Eq m) => Eq (Size m n) Source # 
Instance details

Defined in Graphics.Layout.Box

Methods

(==) :: Size m n -> Size m n -> Bool

(/=) :: Size m n -> Size m n -> Bool

(Show n, Show m) => Show (Size m n) Source # 
Instance details

Defined in Graphics.Layout.Box

Methods

showsPrec :: Int -> Size m n -> ShowS

show :: Size m n -> String

showList :: [Size m n] -> ShowS

mapSizeX :: (n -> nn) -> Size m n -> Size m nn Source #

Convert block size via given callback

mapSizeY :: (m -> mm) -> Size m n -> Size mm n Source #

Convert inline size via given callback

data PaddedBox m n Source #

A box with min & max bounds & surrounding borders. The CSS Box Model.

Constructors

PaddedBox 

Fields

  • min :: Size m n

    The minimum amount of pixels this box should take.

  • max :: Size m n

    The maximum amount of pixels this box should take.

  • nat :: Size Double Double

    The ideal number of pixels this box should take.

  • size :: Size m n

    The amount of pixels this box should take.

  • padding :: Border m n

    The amount of space between the box & the border.

  • border :: Border m n

    The amount of space for the border.

  • margin :: Border m n

    The amount of space between the border & anything else.

Instances

Instances details
(Zero m, Zero n) => Zero (PaddedBox m n) Source # 
Instance details

Defined in Graphics.Layout.Box

Methods

zero :: PaddedBox m n Source #

zeroBox :: PaddedBox Double Double Source #

An empty box, takes up nospace onscreen.

lengthBox :: PaddedBox Length Length Source #

A box which takes up all available space with no borders.

mapX' :: (n -> nn) -> PaddedBox m n -> PaddedBox m nn Source #

Convert all sizes along the inline axis via given callback.

mapY' :: (m -> mm) -> PaddedBox m n -> PaddedBox mm n Source #

Convert all sizes along the block axis via given callback.

width :: Num n => PaddedBox m n -> n Source #

The total size along the inline axis including borders, etc.

height :: Num m => PaddedBox m n -> m Source #

The total size along the block axis, including borders, etc.

minWidth :: Num n => PaddedBox m n -> n Source #

The total minimum size along the inline axis.

minHeight :: Num m => PaddedBox m n -> m Source #

The total minimum size along the block axis.

maxWidth :: Num n => PaddedBox m n -> n Source #

The total maximum size along the inline axis.

maxHeight :: Num m => PaddedBox m n -> m Source #

The total maximum size along the block axis.

data Length Source #

A partially-computed length value.

Constructors

Pixels Double

Absolute number of device pixels.

Percent Double

Multiplier by container width.

Auto

Use normal layout computations.

Preferred

Use computed preferred width.

Min

Use minimum legible width.

Instances

Instances details
Eq Length Source # 
Instance details

Defined in Graphics.Layout.Box

Methods

(==) :: Length -> Length -> Bool

(/=) :: Length -> Length -> Bool

CastDouble Length Source # 
Instance details

Defined in Graphics.Layout.Box

Methods

fromDouble :: Double -> Length Source #

toDouble :: Length -> Double Source #

Zero Length Source # 
Instance details

Defined in Graphics.Layout.Box

Methods

zero :: Length Source #

mapAuto :: Double -> Length -> Length Source #

Replace keywords with a given number of pixels. Useful for avoiding messing up percentage calculations in later processing.

lowerLength :: Double -> Length -> Double Source #

Convert a length given the container's width. Filling in 0 for keywords. If you wish for keywords to be handled differently, callers need to compute that themselves.

class Zero a where Source #

Methods

zero :: a Source #

Return the empty (or zero) value for a CatTrap geometric type.

Instances

Instances details
Zero Double Source # 
Instance details

Defined in Graphics.Layout.Box

Methods

zero :: Double Source #

Zero Length Source # 
Instance details

Defined in Graphics.Layout.Box

Methods

zero :: Length Source #

(Zero m, Zero n) => Zero (PaddedBox m n) Source # 
Instance details

Defined in Graphics.Layout.Box

Methods

zero :: PaddedBox m n Source #

class CastDouble a where Source #

Methods

fromDouble :: Double -> a Source #

Convert a double to a double or length.

toDouble :: a -> Double Source #

Convert a double or length to a double.

Instances

Instances details
CastDouble Double Source # 
Instance details

Defined in Graphics.Layout.Box

Methods

fromDouble :: Double -> Double Source #

toDouble :: Double -> Double Source #

CastDouble Length Source # 
Instance details

Defined in Graphics.Layout.Box

Methods

fromDouble :: Double -> Length Source #

toDouble :: Length -> Double Source #