~alcinnz/CatTrap

ref: c06fd5523fd9a30b1da5cb86bc6f862715b0b5d2 CatTrap/test/Test.hs -rw-r--r-- 3.9 KiB
c06fd552 — Adrian Cochrane Test & fix block layout. 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
{-# 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.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

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