@@ 37,7 37,7 @@ layoutGetBox (LayoutGrid _ self _) = zero {
B.max = containerMax self
}
layoutGetBox (LayoutInline _ f self _) = zero {
- B.min = inlineSize f self, B.size = inlineSize f self, B.max = inlineSize f self
+ B.min = inlineMin f self, B.size = inlineSize f self, B.max = inlineSize f self
}
layoutGetBox (LayoutSpan _ f self) = zero {
B.min = fragmentSize f self, B.size = fragmentSize f self, B.max = fragmentSize f self
@@ 55,17 55,16 @@ layoutGetInner (LayoutSpan ret _ _) = ret
setCellBox' (child, cell) = cell { gridItemBox = layoutGetBox child }
boxMinWidth :: (Zero y, CastDouble y) =>
- Maybe Double -> LayoutItem y Length x -> (Double, LayoutItem y Length x)
-boxMinWidth parent (LayoutFlow val self childs) = (min', LayoutFlow val self' childs')
+ Maybe Double -> LayoutItem y Length x -> LayoutItem y Length x
+boxMinWidth parent (LayoutFlow val self childs) = LayoutFlow val self' childs'
where
self' = self { B.min = mapSizeX (B.mapAuto min') (B.min self) }
min' = flowMinWidth parent' self childs''
childs'' = map (mapX' $ lowerLength selfWidth) $ map layoutGetBox childs'
- childs' = map snd $ map (boxMinWidth $ Just selfWidth) childs
+ childs' = map (boxMinWidth $ Just selfWidth) childs
selfWidth = width $ mapX' (lowerLength parent') self
parent' = fromMaybe 0 parent
-boxMinWidth parent (LayoutGrid val self childs) =
- (min', LayoutGrid val self' $ zip cells' childs')
+boxMinWidth parent (LayoutGrid val self childs) = LayoutGrid val self' $ zip cells' childs'
where
self' = self {
containerMin = Size (Pixels min') (block $ containerMin self),
@@ 83,8 82,8 @@ boxMinWidth parent (LayoutGrid val self childs) =
(GridItem {..}, _) <- childs]) parent
zeroBox :: PaddedBox Double Double
zeroBox = zero
-boxMinWidth _ self@(LayoutInline _ font self' _) = (inlineMinWidth font self', self)
-boxMinWidth _ self@(LayoutSpan _ f self') = (B.inline $ fragmentSize' f self', self)
+boxMinWidth _ self@(LayoutInline _ font self' _) = self
+boxMinWidth _ self@(LayoutSpan _ f self') = self
boxNatWidth :: (Zero y, CastDouble y) =>
Maybe Double -> LayoutItem y Length x -> (Double, LayoutItem y Length x)
boxNatWidth parent (LayoutFlow val self childs) = (size', LayoutFlow val self' childs')
@@ 338,7 337,7 @@ boxLayout :: PaddedBox Double Double -> LayoutItem Length Length x -> Bool ->
LayoutItem Double Double ((Double, Double), x)
boxLayout parent self paginate = self8
where
- (_, self0) = boxMinWidth Nothing self
+ self0 = boxMinWidth Nothing self
(_, self1) = boxNatWidth Nothing self0
(_, self2) = boxMaxWidth parent self1
(_, self3) = boxWidth parent self2
@@ 1,5 1,5 @@
{-# LANGUAGE TupleSections #-}
-module Graphics.Layout.Inline(inlineMinWidth, inlineNatWidth, inlineHeight,
+module Graphics.Layout.Inline(inlineMinWidth, inlineMin, inlineNatWidth, inlineHeight,
inlineSize, inlineChildren, fragmentSize, fragmentSize', fragmentPos) where
import Data.Text.ParagraphLayout (Paragraph(..), ParagraphOptions(..),
@@ 19,6 19,9 @@ 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