~alcinnz/CatTrap

ref: 309a5a356b784d60e941172b535f3d40905595da CatTrap/Graphics/Layout/Inline.hs -rw-r--r-- 2.7 KiB
309a5a35 — Adrian Cochrane Decided against adding invisible length-lowering into CatTrap, Mondrian's would be too sophisticated! 1 year, 5 months ago
                                                                                
f5fbeaa6 Adrian Cochrane
ae8cdfe4 Adrian Cochrane
85d144a0 Adrian Cochrane
f5fbeaa6 Adrian Cochrane
55c1e702 Adrian Cochrane
f5fbeaa6 Adrian Cochrane
ddef83e3 Adrian Cochrane
f5fbeaa6 Adrian Cochrane
ae8cdfe4 Adrian Cochrane
93c6516b Adrian Cochrane
f5fbeaa6 Adrian Cochrane
85d144a0 Adrian Cochrane
f5fbeaa6 Adrian Cochrane
85d144a0 Adrian Cochrane
e9d8aec6 Adrian Cochrane
f5fbeaa6 Adrian Cochrane
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
{-# LANGUAGE TupleSections #-}
module Graphics.Layout.Inline(inlineMinWidth, inlineMin, inlineNatWidth, inlineHeight,
    inlineSize, inlineChildren, layoutSize, layoutChildren,
    fragmentSize, fragmentSize', fragmentPos) where

import Data.Text.ParagraphLayout (Paragraph(..), ParagraphOptions(..),
                                    SpanLayout(..), Fragment(..),
                                    ParagraphLayout(..), layoutPlain, Span(..))
import Data.Text.ParagraphLayout.Rect (Rect(..), width, height, x_min, y_min)
import Data.Text.Internal (Text(..))
import qualified Data.Text as Txt
import Data.Char (isSpace)
import Data.Int (Int32)

import Graphics.Layout.Box (Size(..), CastDouble(..), fromDouble)
import Graphics.Layout.CSS.Font (Font', hbScale)

hbScale' font = (/hbScale font) . fromIntegral
c font = fromDouble . hbScale' font

inlineMinWidth :: Font' -> Paragraph -> Double
inlineMinWidth font self = hbScale' font $ width $ layoutPlain' self 0
inlineMin :: (CastDouble x, CastDouble y) => Font' -> Paragraph -> Size x y
inlineMin font self = Size (c font $ width rect) (c font $ height rect)
    where rect = layoutPlain' self 0
inlineNatWidth :: Font' -> Paragraph -> Double
inlineNatWidth font self = hbScale' font $ width $ layoutPlain' self maxBound
inlineHeight :: Font' -> Double -> Paragraph -> Double
inlineHeight font width self =
    hbScale' font $ height $ layoutPlain' self $ round (hbScale font * width)

inlineSize :: (CastDouble x, CastDouble y) => Font' -> Paragraph -> Size x y
inlineSize font self = layoutSize font $ layoutPlain self
inlineChildren :: [x] -> Paragraph -> [(x, Fragment)]
inlineChildren vals self = layoutChildren vals $ layoutPlain self

layoutSize :: (CastDouble x, CastDouble y) => Font' -> ParagraphLayout -> Size x y
layoutSize font self = Size (c font $ width r) (c font $ height r)
  where r = paragraphRect self
layoutChildren :: [x] -> ParagraphLayout -> [(x, Fragment)]
layoutChildren vals self = zip vals $ concat $ map inner $ spanLayouts self
  where inner (SpanLayout y) = y

layoutPlain' :: Paragraph -> Int32 -> Rect Int32
layoutPlain' (Paragraph a b c d) width =
    paragraphRect $ layoutPlain $ Paragraph a b c d { paragraphMaxWidth = width }

fragmentSize :: (CastDouble x, CastDouble y) => Font' -> Fragment -> Size x y
fragmentSize font self = Size (c font $ width r) (c font $ height r)
    where r = fragmentRect self
fragmentSize' :: CastDouble x => Font' -> Fragment -> Size x x
fragmentSize' = fragmentSize -- Work around for typesystem.
fragmentPos :: Font' -> (Double, Double) -> Fragment -> (Double, Double)
fragmentPos font (x, y) self =
        (x + hbScale' font (x_min r), y + hbScale' font (y_min r))
    where r = fragmentRect self