module Data.Text.ParagraphLayout.Internal.ResolvedSpan (ResolvedSpan(..) ,WithSpan(WithSpan) ,splitBySpanIndex ) where import Data.Text (Text) import Data.Text.Glyphize (Font) import qualified Data.Text.ICU as BreakStatus (Line) import Data.Text.ParagraphLayout.Internal.LineHeight import Data.Text.ParagraphLayout.Internal.TextContainer -- | Internal structure containing resolved values that may be shared with -- other spans across the paragraph. data ResolvedSpan = ResolvedSpan { spanIndex :: Int , spanOffsetInParagraph :: Int , spanText :: Text , spanFont :: Font , spanLineHeight :: LineHeight , spanLanguage :: String , spanLineBreaks :: [(Int, BreakStatus.Line)] -- TODO: Can be optimised by starting with the shortest line break. , spanCharacterBreaks :: [(Int, ())] } deriving (Show) instance Eq ResolvedSpan where a == b = spanIndex a == spanIndex b instance TextContainer ResolvedSpan where getText = spanText -- | Wrapper for temporarily mapping the relationship to a `Span`. data WithSpan a = WithSpan ResolvedSpan a instance Functor WithSpan where fmap f (WithSpan s a) = WithSpan s (f a) instance TextContainer a => TextContainer (WithSpan a) where getText (WithSpan _ c) = getText c instance SeparableTextContainer a => SeparableTextContainer (WithSpan a) where splitTextAt8 n (WithSpan rs c) = (WithSpan rs c1, WithSpan rs c2) where (c1, c2) = splitTextAt8 n c dropWhileEnd p (WithSpan rs c) = WithSpan rs (dropWhileEnd p c) splitBySpanIndex :: [WithSpan a] -> [[a]] splitBySpanIndex xs = [getBySpanIndex i xs | i <- [0..]] getBySpanIndex :: Int -> [WithSpan a] -> [a] getBySpanIndex idx xs = map contents $ filter matchingIndex $ xs where matchingIndex (WithSpan rs _) = (spanIndex rs) == idx contents (WithSpan _ x) = x