module UI.Widgets.Editor.Cursor where import qualified Data.List as DL import Common offsetToScreenPos :: Int -- ^ Content width, where lines longer are wrapped. -> [Int] -- ^ Line lengths -> Int -- ^ Linear offset into cursor position. This is real offset that starts at 0 -> Maybe (ScreenPos, Int) -- Screen pos and actual line in content where cursor is at offsetToScreenPos _ [] _ = Just $ (ScreenPos 0 0, 1) offsetToScreenPos _ _ 0 = Just $ (ScreenPos 0 0, 1) offsetToScreenPos width lns offset = let (sp, _, _, _) = DL.foldl' foldFn (Nothing, 0, 0, 1) lns in sp where foldFn :: (Maybe (ScreenPos, Int), Int, Int, Int) -> Int -> (Maybe (ScreenPos, Int), Int, Int, Int) foldFn a@(Just _, _, _, _) _ = a foldFn (Nothing, leftOffset, lineCount, realLineCount) lineLength = case DL.foldl' foldFn' (Nothing, leftOffset, lineCount) (brokenLines width lineLength) of (Just a, _, _) -> (Just (a, realLineCount), 0, 0, 0) (Nothing, lo, lc) -> (Nothing, lo, lc, realLineCount+1) foldFn' :: (Maybe ScreenPos, Int, Int) -> Int -> (Maybe ScreenPos, Int, Int) foldFn' a@(Just _, _, _) _ = a foldFn' (Nothing, leftOffset, lineCount) lineLength = let rightOffset = leftOffset + lineLength - 1 in if offset >= leftOffset && offset <= rightOffset then (Just $ ScreenPos (offset - leftOffset) lineCount, 0, 0) else (Nothing, rightOffset+1, lineCount+1) brokenLines :: Int -> Int -> [Int] brokenLines _ 0 = [1] brokenLines width ll = let (flc, lll) = divMod ll width in if lll > 0 -- We add one char to the very endline to signify the ending newline. -- and to allow positioning of cursor the very last char in a line. then replicate flc width <> [lll+1] else replicate (flc - 1) width <> [width + 1] screenPosToOffset :: [Int] -- ^ Line lengths -> Int -- ^ Content width, where lines longer are wrapped. -> ScreenPos -- ^ Screen position relative to top left edget of content. -> Maybe (Int, Int, ScreenPos) -- Offset starting at zero, cursor line, and adjusted ScreenPos so cursor is at end of line screenPosToOffset lns width (ScreenPos x y) = let (sp, _, _, _) = DL.foldl' foldFn (Nothing, 0, 0, 1) lns in sp where foldFn :: (Maybe (Int, Int, ScreenPos), Int, Int, Int) -> Int -> (Maybe (Int, Int, ScreenPos), Int, Int, Int) foldFn a@(Just _, _, _, _) _ = a foldFn (Nothing, lineCount, leftOffset, currentLine) lineLength = case DL.foldl' foldFn' (Nothing, lineCount, leftOffset) (brokenLines width lineLength) of (Nothing, a, b) -> (Nothing, a, b, currentLine + 1) (Just (a, b), _, _) -> (Just (a, currentLine, b), 0, 0, 0) foldFn' :: ( Maybe (Int, ScreenPos) -- Result , Int -- current screen line no , Int -- current offset at line start ) -> Int -- current line width -> (Maybe (Int, ScreenPos), Int, Int) foldFn' a@(Just _, _, _) _ = a foldFn' (Nothing, lno, offset) lw = if lno == y then let aOffset = min (lw - 1) x in (Just (offset + aOffset, ScreenPos aOffset y), 0, 0) else (Nothing, lno+1, offset+lw)