{-# LANGUAGE TupleSections #-} module Graphics.Layout.Inline(inlineMinWidth, inlineMin, inlineNatWidth, inlineHeight, inlineSize, inlineChildren, 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 = Size (c font $ width r) (c font $ height r) where r = paragraphRect $ layoutPlain self inlineChildren :: [x] -> Paragraph -> [(x, Fragment)] inlineChildren vals self = zip vals $ concat $ map inner $ spanLayouts $ layoutPlain 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