module Data.Text.ParagraphLayout.Internal.Rich.ParagraphLayout ( ParagraphLayout (..) , appendContents , emptyParagraphLayout , filterLine , paragraphOriginX , paragraphOriginY , paragraphSafeWidth , shapedRuns , shiftContents , topDistance ) where import Data.Int (Int32) import Data.Text.ParagraphLayout.Internal.Fragment import Data.Text.ParagraphLayout.Internal.Line import Data.Text.ParagraphLayout.Internal.LineNumbers import Data.Text.ParagraphLayout.Internal.LinePagination import Data.Text.ParagraphLayout.Internal.ParagraphExtents import Data.Text.ParagraphLayout.Internal.Rect -- | The resulting layout of the whole paragraph. data ParagraphLayout d = ParagraphLayout { paragraphRect :: Rect Int32 -- ^ The containing block (CSS3). , paragraphLines :: [Line] -- ^ Information about line boxes (CSS). -- May describe additional empty space around text fragments. , paragraphFragments :: [Fragment d] -- ^ The resulting layout of all input text, divided into fragments as -- required by the input structure, line breaking, text writing direction, -- and changes of script. } deriving (Eq, Read, Show) instance LineNumbers (ParagraphLayout d) where lineNumbersWithDuplication pl = map fragmentLine $ paragraphFragments pl instance LineHeight (ParagraphLayout d) where lineHeight pl = height $ paragraphRect pl -- | A `ParagraphLayout` with no fragments and no lines. -- Useful as an identity element for `appendContents`. emptyParagraphLayout :: ParagraphLayout a emptyParagraphLayout = ParagraphLayout emptyRect [] [] -- | Distance from the paragraph origin to its topmost line. topDistance :: ParagraphLayout d -> Int32 topDistance pl = case paragraphLines pl of [] -> 0 ls -> maximum $ map (y_origin . lineRect) ls -- | Keep the line with the given number and its fragments, -- and remove everything else. filterLine :: Int -> ParagraphLayout d -> ParagraphLayout d filterLine num (ParagraphLayout _ ls frags) = ParagraphLayout pRect' ls' frags' where pRect' = containRects $ map lineRect ls ls' = filter ((== num) . lineNumber) ls frags' = filter ((== num) . fragmentLine) frags -- | Add @dx@ and @dy@ to the origins of each line and fragment, -- effectively shifting the whole paragraph by the given amount. shiftContents :: Int32 -> Int32 -> ParagraphLayout d -> ParagraphLayout d shiftContents dx dy (ParagraphLayout _ ls frags) = ParagraphLayout pRect' ls' frags' where pRect' = containRects $ map lineRect ls ls' = map (shiftLine dx dy) ls frags' = map (shiftFragment dx dy) frags -- | Combine fragments from two `ParagraphLayout`s. appendContents :: ParagraphLayout d -> ParagraphLayout d -> ParagraphLayout d appendContents (ParagraphLayout _ ls1 frags1) (ParagraphLayout _ ls2 frags2) = ParagraphLayout pRect ls frags where pRect = containRects $ map lineRect ls ls = ls1 ++ ls2 frags = frags1 ++ frags2 -- | Return all shaped runs in the paragraph. shapedRuns :: ParagraphLayout d -> [ShapedRun] shapedRuns pl = map shapedRun $ paragraphFragments pl -- | Width of the widest line, including spacing. -- -- This is the smallest `Data.Text.ParagraphLayout.Rich.paragraphMaxWidth` -- that will not introduce new line breaks. -- -- When `Data.Text.ParagraphLayout.Rich.paragraphMaxWidth` is set to `maxBound`, -- `paragraphSafeWidth` can be used to determine the @max-content@ width of the -- paragraph for CSS. paragraphSafeWidth :: ParagraphLayout d -> Int32 paragraphSafeWidth pl = maximum $ map (lineWidth pl) $ lineNumbers pl lineWidth :: ParagraphLayout d -> Int -> Int32 lineWidth pl line = sum $ map fragmentWidth $ lineFragments pl line fragmentWidth :: Fragment d -> Int32 fragmentWidth f = width $ fragmentSpacedRect f lineFragments :: ParagraphLayout d -> Int -> [Fragment d] lineFragments pl line = filter byLine $ paragraphFragments pl where byLine frag = line == fragmentLine frag