module Graphics.Vty.Span where
import Graphics.Vty.Attributes (Attr)
import Graphics.Vty.Image
import Graphics.Vty.Image.Internal ( clipText )
import qualified Data.Text.Lazy as TL
import Data.Vector (Vector)
import qualified Data.Vector as Vector
data SpanOp =
TextSpan
{ textSpanAttr :: !Attr
, textSpanOutputWidth :: !Int
, textSpanCharWidth :: !Int
, textSpanText :: DisplayText
}
| Skip !Int
| RowEnd !Int
deriving Eq
type SpanOps = Vector SpanOp
dropOps :: Int -> SpanOps -> SpanOps
dropOps w = snd . splitOpsAt w
splitOpsAt :: Int -> SpanOps -> (SpanOps, SpanOps)
splitOpsAt inW inOps = splitOpsAt' inW inOps
where
splitOpsAt' 0 ops = (Vector.empty, ops)
splitOpsAt' remainingColumns ops = case Vector.head ops of
t@(TextSpan {}) -> if remainingColumns >= textSpanOutputWidth t
then let (pre,post) = splitOpsAt' (remainingColumns textSpanOutputWidth t)
(Vector.tail ops)
in (Vector.cons t pre, post)
else let preTxt = clipText (textSpanText t) 0 remainingColumns
preOp = TextSpan { textSpanAttr = textSpanAttr t
, textSpanOutputWidth = remainingColumns
, textSpanCharWidth = fromIntegral $! TL.length preTxt
, textSpanText = preTxt
}
postWidth = textSpanOutputWidth t remainingColumns
postTxt = clipText (textSpanText t) remainingColumns postWidth
postOp = TextSpan { textSpanAttr = textSpanAttr t
, textSpanOutputWidth = postWidth
, textSpanCharWidth = fromIntegral $! TL.length postTxt
, textSpanText = postTxt
}
in ( Vector.singleton preOp
, Vector.cons postOp (Vector.tail ops)
)
Skip w -> if remainingColumns >= w
then let (pre,post) = splitOpsAt' (remainingColumns w) (Vector.tail ops)
in (Vector.cons (Skip w) pre, post)
else ( Vector.singleton $ Skip remainingColumns
, Vector.cons (Skip (w remainingColumns)) (Vector.tail ops)
)
RowEnd _ -> error "cannot split ops containing a row end"
type DisplayOps = Vector SpanOps
instance Show SpanOp where
show (TextSpan attr ow cw _) = "TextSpan(" ++ show attr ++ ")(" ++ show ow ++ ", " ++ show cw ++ ")"
show (Skip ow) = "Skip(" ++ show ow ++ ")"
show (RowEnd ow) = "RowEnd(" ++ show ow ++ ")"
displayOpsColumns :: DisplayOps -> Int
displayOpsColumns ops
| Vector.length ops == 0 = 0
| otherwise = Vector.length $ Vector.head ops
displayOpsRows :: DisplayOps -> Int
displayOpsRows ops = Vector.length ops
affectedRegion :: DisplayOps -> DisplayRegion
affectedRegion ops = (displayOpsColumns ops, displayOpsRows ops)
spanOpsEffectedColumns :: SpanOps -> Int
spanOpsEffectedColumns inOps = Vector.foldl' spanOpsEffectedColumns' 0 inOps
where
spanOpsEffectedColumns' t (TextSpan _ w _ _ ) = t + w
spanOpsEffectedColumns' t (Skip w) = t + w
spanOpsEffectedColumns' t (RowEnd w) = t + w
spanOpHasWidth :: SpanOp -> Maybe (Int, Int)
spanOpHasWidth (TextSpan _ ow cw _) = Just (cw, ow)
spanOpHasWidth (Skip ow) = Just (ow,ow)
spanOpHasWidth (RowEnd ow) = Just (ow,ow)
columnsToCharOffset :: Int -> SpanOp -> Int
columnsToCharOffset cx (TextSpan _ _ _ utf8Str) =
let str = TL.unpack utf8Str
in wcswidth (take cx str)
columnsToCharOffset cx (Skip _) = cx
columnsToCharOffset cx (RowEnd _) = cx