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

Graphics.Layout.Grid

Description

Sizes grid cells & positions elements to them.

Synopsis

Documentation

type Grid m n = Size (Track m) (Track n) Source #

An element which positions it's children within a grid.

data Track x Source #

The sizes to which children are alonged on a single axis.

Constructors

Track 

Fields

  • cells :: [Either x Double]

    The desired size of each cell. If Left specifies ratio of excess space to use.

  • trackMins :: [Double]

    The minimum amount of space each cell should take.

  • trackNats :: [Double]

    The ideal amount of space each cell should take.

  • gap :: x

    How much space to add between cells.

Instances

Instances details
Read x => Read (Track x) Source # 
Instance details

Defined in Graphics.Layout.Grid

Show x => Show (Track x) Source # 
Instance details

Defined in Graphics.Layout.Grid

Methods

showsPrec :: Int -> Track x -> ShowS #

show :: Track x -> String #

showList :: [Track x] -> ShowS #

Eq x => Eq (Track x) Source # 
Instance details

Defined in Graphics.Layout.Grid

Methods

(==) :: Track x -> Track x -> Bool #

(/=) :: Track x -> Track x -> Bool #

Ord x => Ord (Track x) Source # 
Instance details

Defined in Graphics.Layout.Grid

Methods

compare :: Track x -> Track x -> Ordering #

(<) :: Track x -> Track x -> Bool #

(<=) :: Track x -> Track x -> Bool #

(>) :: Track x -> Track x -> Bool #

(>=) :: Track x -> Track x -> Bool #

max :: Track x -> Track x -> Track x #

min :: Track x -> Track x -> Track x #

type GridItem = Size GridItem' GridItem' Source #

Which cells a child should be aligned to.

data GridItem' Source #

How a grid child should be aligned per-axis.

Constructors

GridItem 

Fields

Instances

Instances details
Generic GridItem' Source # 
Instance details

Defined in Graphics.Layout.Grid

Associated Types

type Rep GridItem' :: Type -> Type #

Read GridItem' Source # 
Instance details

Defined in Graphics.Layout.Grid

Show GridItem' Source # 
Instance details

Defined in Graphics.Layout.Grid

NFData GridItem' Source # 
Instance details

Defined in Graphics.Layout.Grid

Methods

rnf :: GridItem' -> () #

Eq GridItem' Source # 
Instance details

Defined in Graphics.Layout.Grid

Ord GridItem' Source # 
Instance details

Defined in Graphics.Layout.Grid

type Rep GridItem' Source # 
Instance details

Defined in Graphics.Layout.Grid

data Alignment Source #

How to redistribute excess space.

Constructors

Start 
Mid 
End 

Instances

Instances details
Enum Alignment Source # 
Instance details

Defined in Graphics.Layout.Grid

Generic Alignment Source # 
Instance details

Defined in Graphics.Layout.Grid

Associated Types

type Rep Alignment :: Type -> Type #

Read Alignment Source # 
Instance details

Defined in Graphics.Layout.Grid

Show Alignment Source # 
Instance details

Defined in Graphics.Layout.Grid

NFData Alignment Source # 
Instance details

Defined in Graphics.Layout.Grid

Methods

rnf :: Alignment -> () #

Eq Alignment Source # 
Instance details

Defined in Graphics.Layout.Grid

Ord Alignment Source # 
Instance details

Defined in Graphics.Layout.Grid

type Rep Alignment Source # 
Instance details

Defined in Graphics.Layout.Grid

type Rep Alignment = D1 ('MetaData "Alignment" "Graphics.Layout.Grid" "cattrap-0.6.0.0-inplace" 'False) (C1 ('MetaCons "Start" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Mid" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "End" 'PrefixI 'False) (U1 :: Type -> Type)))

buildTrack :: CastDouble x => [Either x Double] -> Track x Source #

Constructs a track with default (to-be-computed) values & given cell sizes.

buildGrid :: (CastDouble m, CastDouble n) => [Either m Double] -> [Either n Double] -> Grid m n Source #

Constructs a grid with default (to-be-computed) values & given cell sizes.

setCellBox :: (CastDouble m, CastDouble n) => GridItem -> PaddedBox m n -> GridItem Source #

Sets minimum & natural sizes from the given padded box.

enumerate :: [b] -> [(Int, b)] Source #

Utility for associate an index with each item in a list.

gridItemBox :: (CastDouble x, CastDouble y) => Grid y x -> GridItem -> PaddedBox Double Double Source #

Compute the maximum size as a PaddedBox of a child, for it to be sized to.

cellSize :: CastDouble x => Track x -> GridItem' -> Double Source #

Compute the maximum size along an axis of a child, for it to be sized to.

trackMin :: (n -> Double) -> Track n -> Double Source #

Compute the minimum size for the track given cell sizes. Refers to computed min sizes if cached.

trackNat :: (n -> Double) -> Track n -> Double Source #

Compute the natural size for the track given cell sizes. Refers to compute natural sizes if cached.

gridEstWidth :: Grid y Length -> [GridItem] -> Double Source #

Estimate grid width to inform proper width calculation.

sizeTrackMins :: Double -> Track Length -> [GridItem'] -> [Double] Source #

Calculate minimum sizes for all cells in the track. Sized to fit given children.

sizeTrackNats :: Double -> Track Length -> [GridItem'] -> [Double] Source #

Compute natural sizes for all cells in the track. Sized to fit given children.

sizeTrackMaxs :: Double -> Track Length -> [Double] Source #

Compute maximum sizes for all cells in the track, sized to the parent element.

trackPosition :: Track Double -> [GridItem'] -> [Double] Source #

Compute the position of all children within the grid.

gridPosition :: Grid Double Double -> [GridItem] -> [(Double, Double)] Source #

Compute the position of all children in a grid.

trackLayout :: Double -> Double -> Track Length -> [GridItem'] -> (Track Double, [(Double, GridItem')]) Source #

Compute the track sizes & child positions along a single axis.

gridLayout :: Size Double Double -> Grid Length Length -> [GridItem] -> (Grid Double Double, [((Double, Double), GridItem)]) Source #

Compute the track sizes & child positions along both axes.