~alcinnz/CatTrap

ref: eae2c2003d8f7d331e6e97364ed25ede50be6d81 CatTrap/test/Test.hs -rw-r--r-- 6.0 KiB
eae2c200 — Adrian Cochrane Unittest basic grid sizing. 1 year, 4 months ago
                                                                                
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
{-# LANGUAGE OverloadedStrings #-}
module Main where

import Test.Hspec

import Graphics.Layout.Arithmetic
import Data.CSS.Syntax.Tokens (tokenize, Token(..))
import Graphics.Layout.Box as B
import Graphics.Layout.Grid
import Graphics.Layout.Flow

main :: IO ()
main = hspec spec

spec :: Spec
spec = do
    describe "canary" $ do
        it "test framework works" $ do
            True `shouldBe` True
    describe "calc()" $ do
        it "Can perform basic arithmatic" $ do
            runMath "42" `shouldBe` 42
            runMath "6 * 9" `shouldBe` 54
            runMath "6 * 9 - 42" `shouldBe` 12
            runMath "6 * (9 - 42)" `shouldBe` -198
            runMath "6 * calc(9 - 42)" `shouldBe` -198
            runMath "6 * abs(9 - 42)" `shouldBe` 198
    describe "Width sizing" $ do
        -- Based on http://hixie.ch/tests/adhoc/css/box/block/
        it "Can overflow parent" $ do
            width (fst $ layoutFlow zeroBox {
                    size = Size 3 1
                } lengthBox {
                    border = Border (Pixels 0) (Pixels 0) (Pixels 2) (Pixels 2)
                } [] False) `shouldBe` 4
            width (fst $ layoutFlow zeroBox {
                    size = Size 3 1
                } lengthBox {
                    padding = Border (Pixels 0) (Pixels 0) (Pixels 2) (Pixels 2)
                } [] False) `shouldBe` 4
            width (fst $ layoutFlow zeroBox {
                    size = Size 3 1
                } lengthBox {
                    margin = Border (Pixels 0) (Pixels 0) (Pixels 2) (Pixels 2)
                } [] False) `shouldBe` 4
        it "Fits to parent" $ do
            width (fst $ layoutFlow zeroBox {
                    size = Size 5 1
                } lengthBox {
                    border = Border (Pixels 0) (Pixels 0) (Pixels 2) (Pixels 2),
                    size = Size Auto $ Pixels 1
                } [] False) `shouldBe` 5
            width (fst $ layoutFlow zeroBox {
                    size = Size 5 1
                } lengthBox {
                    padding = Border (Pixels 0) (Pixels 0) (Pixels 2) (Pixels 2),
                    size = Size Auto $ Pixels 1
                } [] False) `shouldBe` 5
            width (fst $ layoutFlow zeroBox {
                    size = Size 5 1
                } lengthBox {
                    margin = Border (Pixels 0) (Pixels 0) (Pixels 2) (Pixels 2),
                    size = Size Auto $ Pixels 1
                } [] False) `shouldBe` 5
        it "Collapses margins" $ do
            let a :: PaddedBox Length Double
                a = PaddedBox {
                    B.min = Size 0 Auto,
                    size = Size 0 Auto,
                    B.max = Size 0 Auto,
                    padding = Border (Pixels 0) (Pixels 0) 0 0,
                    border = Border (Pixels 0) (Pixels 0) 0 0,
                    margin = Border (Pixels 5) (Pixels 10) 0 0
                  }
                b :: PaddedBox Length Double
                b = PaddedBox {
                    B.min = Size 0 Auto,
                    size = Size 0 Auto,
                    B.max = Size 0 Auto,
                    padding = Border (Pixels 0) (Pixels 0) 0 0,
                    border = Border (Pixels 0) (Pixels 0) 0 0,
                    margin = Border (Pixels 10) (Pixels 5) 0 0
                  }
            height (fst $ layoutFlow zeroBox {
                    size = Size 100 100
                } lengthBox [a, a] False) `shouldBe` 25
            height (fst $ layoutFlow zeroBox {
                    size = Size 100 100
                } lengthBox [b, b] False) `shouldBe` 25
            height (fst $ layoutFlow zeroBox {
                    size = Size 100 100
                } lengthBox [a, b] False) `shouldBe` 20
            height (fst $ layoutFlow zeroBox {
                    size = Size 100 100
                } lengthBox [b, a] False) `shouldBe` 25
    describe "Grid" $ do
        it "computes single-columns widths/heights" $ do
            let (pxGrid, pxCells) = gridLayout zeroBox {
                    size = Size 100 100
                  } (buildGrid [Left $ Pixels 10] [Left $ Pixels 10])
                    [GridItem 0 1 0 1 (Size Start Start) zeroBox] True
            containerSize pxGrid `shouldBe` Size 10 10
            fst (head pxCells) `shouldBe` Size 0 0
            let (pcGrid, pcCells) = gridLayout zeroBox {
                    size = Size 100 100
                  } (buildGrid [Left $ Percent 0.5] [Left $ Percent 0.5])
                    [GridItem 0 1 0 1 (Size Start Start) zeroBox] True
            containerSize pcGrid `shouldBe` Size 50 50
            fst (head pcCells) `shouldBe` Size 0 0
            let (autoGrid, autoCells) = gridLayout zeroBox {
                    size = Size 100 100
                  } (buildGrid [Left Auto] [Left Auto])
                    [GridItem 0 1 0 1 (Size Start Start) zeroBox {
                        B.min = Size 10 10,
                        size = Size 20 20
                    }] True
            containerSize autoGrid `shouldBe` Size 20 20
            fst (head autoCells) `shouldBe` Size 0 0
            let (prefGrid, prefCells) = gridLayout zeroBox {
                    size = Size 100 100
                  } (buildGrid [Left Preferred] [Left Preferred])
                    [GridItem 0 1 0 1 (Size Start Start) zeroBox {
                        B.min = Size 10 10,
                        size = Size 15 15
                    }] True
            containerSize prefGrid `shouldBe` Size 15 15
            fst (head prefCells) `shouldBe` Size 0 0
            let (minGrid, minCells) = gridLayout zeroBox {
                    size = Size 100 100
                  } (buildGrid [Left Min] [Left Min])
                    [GridItem 0 1 0 1 (Size Start Start) zeroBox {
                        B.min = Size 10 10,
                        size = Size 15 15
                    }] True
            containerSize minGrid `shouldBe` Size 10 10
            fst (head minCells) `shouldBe` Size 0 0

runMath = flip evalCalc [] . mapCalc fst . flip parseCalc [] . filter (/= Whitespace) . tokenize