module Data.Text.Zipper.Generic.Words
( moveWordLeft
, moveWordRight
, deletePrevWord
, deleteWord
)
where
import Data.Char
import Data.Text.Zipper
import qualified Data.Text.Zipper.Generic as TZ
moveWordLeft :: TZ.GenericTextZipper a => TextZipper a -> TextZipper a
moveWordLeft = doWordLeft False moveLeft
deletePrevWord :: (Eq a, TZ.GenericTextZipper a) => TextZipper a -> TextZipper a
deletePrevWord = doWordLeft False deletePrevChar
doWordLeft :: TZ.GenericTextZipper a
=> Bool
-> (TextZipper a -> TextZipper a)
-> TextZipper a
-> TextZipper a
doWordLeft inWord transform zipper = case charToTheLeft zipper of
Nothing -> zipper
Just c
| isSpace c && not inWord ->
doWordLeft False transform (transform zipper)
| not (isSpace c) && not inWord ->
doWordLeft True transform zipper
| not (isSpace c) && inWord ->
doWordLeft True transform (transform zipper)
| otherwise ->
zipper
moveWordRight :: TZ.GenericTextZipper a => TextZipper a -> TextZipper a
moveWordRight = doWordRight False moveRight
deleteWord :: TZ.GenericTextZipper a => TextZipper a -> TextZipper a
deleteWord = doWordRight False deleteChar
doWordRight :: TZ.GenericTextZipper a
=> Bool
-> (TextZipper a -> TextZipper a)
-> TextZipper a
-> TextZipper a
doWordRight inWord transform zipper = case charToTheRight zipper of
Nothing -> zipper
Just c
| isSpace c && not inWord ->
doWordRight False transform (transform zipper)
| not (isSpace c) && not inWord ->
doWordRight True transform zipper
| not (isSpace c) && inWord ->
doWordRight True transform (transform zipper)
| otherwise ->
zipper
charToTheLeft :: TZ.GenericTextZipper a => TextZipper a -> Maybe Char
charToTheLeft zipper = case cursorPosition zipper of
(0, 0) -> Nothing
(_, 0) -> Just '\n'
(_, x) -> Just (TZ.toList (currentLine zipper) !! (x1))
charToTheRight :: TZ.GenericTextZipper a => TextZipper a -> Maybe Char
charToTheRight zipper
| null (getText zipper) = Nothing
| otherwise =
let
(row, col) = cursorPosition zipper
content = getText zipper
curLine = content !! row
numLines = length content
in
if row == numLines 1 && col == (TZ.length curLine) then
Nothing
else if col == (TZ.length curLine) then
Just '\n'
else
Just (TZ.toList curLine !! col)