~alcinnz/CatTrap

272852e8b518fb81dcd92d785f8284a713df0e2b — Adrian Cochrane 1 year, 4 months ago 3dce4d7
Draft new CatTrap API which hopefully is easier to implement.
5 files changed, 57 insertions(+), 36 deletions(-)

M Graphics/Layout.hs
M Graphics/Layout/Box.hs
M Graphics/Layout/Flow.hs
M Graphics/Layout/Grid.hs
M cattrap.cabal
M Graphics/Layout.hs => Graphics/Layout.hs +14 -7
@@ 3,12 3,19 @@ module Graphics.Layout where
import Graphics.Layout.Box
import Graphics.Layout.Grid

data LayoutItem n x =
    LayoutFlow x (PaddedBox n) [LayoutItem n x]
    | LayoutGrid x (Grid n) [(GridItem n, LayoutItem n x)]
data LayoutItem m n x =
    LayoutFlow x (PaddedBox m n) [LayoutItem m n x]
    | LayoutGrid x (Grid m n) [(GridItem m n, LayoutItem m n x)]
-- More to come...

{-sizeBound :: LayoutItem Length () -> LayoutItem Length ()
size :: PaddedBox Double -> LayoutItem Length () -> LayoutItem Double ()
position :: LayoutItem Double -> LayoutItem Double Size
layout :: PaddedBox Double -> LayoutItem Length () -> Bool -> [LayoutItem Double Size]-}
boxMinWidth :: Double -> LayoutItem y Length x -> (Double, LayoutItem y Length x)
boxNatWidth :: Double -> LayoutItem y Length x -> (Double, LayoutItem y Length x)
boxMaxWidth :: PaddedBox y Length -> LayoutItem y Length x -> (Double, LayoutItem y Length x)
boxWidth :: PaddedBox y Length -> LayoutItem y Length x -> (Double, LayoutItem y Double x)
boxNatHeight :: LayoutItem Length Double x -> (Double, LayoutItem Length Double x)
boxMinHeight :: Double -> LayoutItem Length Double x -> (Double, LayoutItem Length Double x)
boxMaxHeight :: Double -> LayoutItem Length Double x -> (Double, LayoutItem Length Double x)
boxHeight :: Double -> LayoutItem Length Double x -> (Double, LayoutItem Length Length x)
boxPosition :: LayoutItem Double Double x -> LayoutItem Double Double x
boxLayout :: PaddedBox Double Double -> LayoutItem Length Length x -> Bool ->
        LayoutItem Double Double x

M Graphics/Layout/Box.hs => Graphics/Layout/Box.hs +16 -12
@@ 1,22 1,26 @@
{-# LANGUAGE RecordWildCards #-}
module Graphics.Layout.Box where

data Border n = Border {
    top :: n, bottom :: n, left :: n, right :: n
data Border m n = Border {
    top :: m, bottom :: m, left :: n, right :: n
}
data Size n = Size {inline :: n, block :: n}
data Size m n = Size {inline :: n, block :: m}

data PaddedBox n = PaddedBox {
    min :: Size n,
    max :: Size n,
    size :: Size n,
    padding :: Border n,
    border :: Border n,
    margin :: Border n
data PaddedBox m n = PaddedBox {
    min :: Size m n,
    max :: Size m n,
    size :: Size m n,
    padding :: Border m n,
    border :: Border m n,
    margin :: Border m n
}
width' PaddedBox {..} = left margin + left border + left padding +
width PaddedBox {..} = left margin + left border + left padding +
    inline size + right padding + right border + right margin
height' PaddedBox {..} = top margin + top border + top padding +
height PaddedBox {..} = top margin + top border + top padding +
    block size + bottom padding + bottom border + bottom margin
minWidth PaddedBox {..} = left margin + left border + left padding +
    inline min + right padding + right border + right margin
minHeight PaddedBox {..} = top margin + top border + top padding +
    block min + bottom padding + bottom border + bottom margin

data Length = Pixels Double | Percent Double | Auto | Preferred | Min

M Graphics/Layout/Flow.hs => Graphics/Layout/Flow.hs +8 -3
@@ 1,10 1,15 @@
module Graphics.Layout.Flow where

import Graphics.Layout.Box
import Stylist.Tree (StyleTree(..))

sizeBoundFlow :: PaddedBox Length -> [PaddedBox Length] -> PaddedBox Length
sizeFlow :: PaddedBox Double -> PaddedBox Length -> PaddedBox Double
flowMinWidth :: Double -> PaddedBox Length -> [PaddedBox Length] -> Double
flowNatWidth :: Double -> PaddedBox Length -> [PaddedBox Length] -> Double
flowMaxWidth :: PaddedBox Double -> PaddedBox Length -> Double
flowWidth :: PaddedBox Double -> PaddedBox Length -> Double
flowNatHeight :: PaddedBox Length -> [PaddedBox Double] -> Double
flowMinHeight :: Double -> PaddedBox Double -> Double
flowMaxHeight :: Double -> PaddedBox Double -> Double
flowHeight :: Double -> PaddedBox Double -> Double
positionFlow :: PaddedBox Double -> [PaddedBox Double] -> [Size Double]
layoutFlow :: PaddedBox Double -> PaddedBox Length -> [PaddedBox Length] -> Bool ->
        [(PaddedBox Double, [(Size Double, PaddedBox Double)])]

M Graphics/Layout/Grid.hs => Graphics/Layout/Grid.hs +18 -12
@@ 3,22 3,28 @@ module Graphics.Layout.Grid where
import Data.Text (Text)
import Graphics.Layout.Box

data Grid n = Grid {
    rows :: [(Name, Either n Double)],
data Grid m n = Grid {
    rows :: [(Name, Either m Double)],
    columns :: [(Name, Either n Double)],
    gap :: Size n,
    gridBox :: PaddedBox n
    gap :: Size m n,
    gridBox :: PaddedBox m n
}
data GridItem n = GridItem {
data GridItem m n = GridItem {
    startRow :: Int, endRow :: Int, startCol :: Int, endCol :: Int,
    gridItemBox :: PaddedBox n
    gridItemBox :: PaddedBox m n
}

type Name = Text

{-sizeBoundGrid :: Grid Length -> [GridItem Length] -> Grid Length
sizeGrid :: PaddedBox Double -> Grid Length -> Grid Double
sizeGridItem :: Grid Length -> GridItem Length -> Grid Double
positionGrid :: Grid Double -> [GridItem Double] -> [Size]
layoutGrid :: PaddedBox Double -> Grid Length -> [GridItem Length] -> Bool ->
    [(Grid Double, [(Size, GridItem Double)])]-}
gridMinWidths :: Double -> Grid y Length -> [GridItem y Length] -> (Double, [Double])
gridNatWidths :: Double -> Grid y Length -> [GridItem y Length] -> (Double, [Double])
gridMaxWidths :: PaddedBox y Double -> Grid y Length -> (Double, [Double])
gridWidths :: PaddedBox y Double -> Grid y Length -> (Double, [Double])
gridNatHeights :: PaddedBox Length Double -> [GridItem Length Double] -> (Double, [Double])
gridMinHeights :: Double -> Grid Length Double -> (Double, [Double])
gridMaxHeights :: Double -> Grid Length Double -> (Double, [Double])
gridHeights :: Double -> Grid Length Double -> (Double, [Double])
gridPosition :: GridLength Double Double -> [GridItem Double Double] -> [Size Double Double]
gridLayout :: PaddedBox Double Double -> Grid Length Length ->
        [GridItem Length Length] -> Bool ->
        (Grid Double Double, [(Size Double Double, GridItem Double Double)])

M cattrap.cabal => cattrap.cabal +1 -2
@@ 17,8 17,7 @@ extra-source-files:  CHANGELOG.md
cabal-version:       >=1.10

library
  exposed-modules:     Graphics.Layout, Graphics.Layout.CSS, 
-- Graphics.Layout.Flow,
  exposed-modules:     Graphics.Layout, Graphics.Layout.CSS, Graphics.Layout.Flow,
                        Graphics.Layout.Grid, Graphics.Layout.Box, Graphics.Layout.Arithmetic
  -- other-modules:
  -- other-extensions: