module Buffer.Motion where

import Data.List (dropWhileEnd)
import Buffer.Class

--data Motion = Motion Int LeftRightMotion


-- TODO factor Count
-- TODO various Vim gX
data LeftRightMotion
  = GotoLeft Int
  | GotoRight Int
  | GotoFirstChar
  -- | GotoFirstNonBlankChar
  | GotoEndOfLine             -- XXX in Vi this can go downwards
  | GotoColumn Int
  -- | GotoFindLeft Int (Char -> Bool)   -- TODO don't use functions here
  -- | GotoFindRight Int (Char -> Bool)  -- TODO ^ dto.
  -- | GotillFindLeft Int Char
  -- | GotillFindRight Int Char
  -- | RepeatLastFind Int
  -- | RepeatLastFindReverse Int
  | WordsForward Int
  | WordsBackward Int
  deriving (Show)


-- TODO fail if cannot splitAt properly OR if we didn't modify the buffer
gotoLeft :: Int -> Buffer -> Buffer
gotoLeft i (ls, rs) =
  let (lls, rls) = splitAt (length ls - i) ls in (lls, rls ++ rs)


-- TODO fail if cannot splitAt properly OR if we didn't modify the buffer
gotoRight :: Int -> Buffer -> Buffer
gotoRight i (ls, rs) =
  let (lrs, rrs) = splitAt i rs in (ls ++ lrs, rrs)


gotoFirstChar :: Buffer -> Buffer
gotoFirstChar (ls, rs) = ("", ls ++ rs)


gotoEndOfLine :: Buffer -> Buffer
gotoEndOfLine (ls, rs) = (ls ++ rs, "")


-- TODO fail if i <= 0 or i > length
gotoColumn :: Int -> Buffer -> Buffer
gotoColumn i (ls, rs) = splitAt (i - 1) $ ls ++ rs


wordsForward :: Int -> Buffer -> Buffer
wordsForward i (ls, rs) =
  let rs' = dropWhile (==' ') $ dropWhile (/=' ') rs
      ls' = ls ++ take (length rs - length rs') rs
      b' = (ls', rs')
  in
    if i > 1
      then wordsForward (i - 1) b'
      else b'


wordsBackward :: Int -> Buffer -> Buffer
wordsBackward i (ls, rs) =
  let ls' = dropWhileEnd (/=' ') $ dropWhileEnd (==' ') ls
      rs' = drop (length ls') ls ++ rs
      b' = (ls', rs')
  in
    if i > 1
      then wordsBackward (i - 1) b'
      else b'


move :: LeftRightMotion -> Buffer -> Buffer
move (GotoLeft i) = gotoLeft i
move (GotoRight i) = gotoRight i
move GotoFirstChar = gotoFirstChar
move GotoEndOfLine = gotoEndOfLine
move (GotoColumn i) = gotoColumn i
move (WordsForward i) = wordsForward i
move (WordsBackward i) = wordsBackward i