{-# LANGUAGE TemplateHaskell #-}
module Client.State.EditBox
(
EditBox
, defaultEditBox
, content
, lastOperation
, Line(Line)
, singleLine
, endLine
, HasLine(..)
, Content
, shift
, above
, below
, delete
, backspace
, home
, end
, killHome
, killEnd
, killWordBackward
, killWordForward
, yank
, toggle
, left
, right
, leftWord
, rightWord
, insert
, insertPaste
, insertString
, earlier
, later
, success
, insertDigraph
, LastOperation(..)
) where
import Client.State.EditBox.Content
import Control.Lens hiding (below)
import Data.Char
import Data.List.NonEmpty (NonEmpty)
data EditBox = EditBox
{ _content :: !Content
, _history :: ![NonEmpty String]
, _historyPos :: !Int
, _yankBuffer :: String
, _lastOperation :: !LastOperation
}
deriving (Read, Show)
data LastOperation
= TabOperation String
| KillOperation
| OtherOperation
deriving (Read, Show)
makeLenses ''EditBox
defaultEditBox :: EditBox
defaultEditBox = EditBox
{ _content = noContent
, _history = []
, _historyPos = -1
, _yankBuffer = ""
, _lastOperation = OtherOperation
}
instance HasLine EditBox where
line = content . line
data KillDirection = KillForward | KillBackward
updateYankBuffer :: KillDirection -> String -> EditBox -> EditBox
updateYankBuffer dir str e =
case view lastOperation e of
_ | null str -> set lastOperation OtherOperation e
KillOperation ->
case dir of
KillForward -> over yankBuffer (++ str) e
KillBackward -> over yankBuffer (str ++) e
_ -> set yankBuffer str
$ set lastOperation KillOperation e
success :: EditBox -> EditBox
success e
= over history (cons (pure sent))
$ set content c
$ set lastOperation OtherOperation
$ set historyPos (-1)
$ e
where
(sent, c) = shift $ view content e
replaceList :: Int -> [a] -> [a] -> [a]
replaceList i rpl xs =
case splitAt i xs of
(a, b) -> a ++ rpl ++ drop 1 b
earlier :: EditBox -> Maybe EditBox
earlier e =
do x <- preview (history . ix (i+1)) e
return $ set content (fromStrings x)
$ set lastOperation OtherOperation
$ set historyPos i'
$ over history updateHistory e
where
i = view historyPos e
i' | i < 0 = length txt
| otherwise = length txt + i
txt = filter (/= pure "") [toStrings (view content e)]
updateHistory h
| i < 0 = txt ++ h
| otherwise = replaceList i txt h
later :: EditBox -> Maybe EditBox
later e
| i < 0 && null txt = Nothing
| otherwise = Just $!
set content newContent
$ set lastOperation OtherOperation
$ set historyPos i'
$ over history updateHistory e
where
txt = filter (/= pure "") [toStrings (view content e)]
i = view historyPos e
i' | i < 0 = -1
| otherwise = i - 1
newContent = maybe noContent fromStrings
$ preview (history . ix (i-1)) e
updateHistory h
| i < 0 = txt ++ h
| otherwise = replaceList i txt h
home :: EditBox -> EditBox
home
= set lastOperation OtherOperation
. over content jumpLeft
end :: EditBox -> EditBox
end
= set lastOperation OtherOperation
. over content jumpRight
killEnd :: EditBox -> EditBox
killEnd e
| null kill
= case view (content . below) e of
[] -> e
b:bs -> set (content . below) bs
$ updateYankBuffer KillForward ('\n':b) e
| otherwise
= set line (endLine keep)
$ updateYankBuffer KillForward kill e
where
Line n txt = view line e
(keep,kill) = splitAt n txt
killHome :: EditBox -> EditBox
killHome e
| null kill
= case view (content . above) e of
[] -> e
a:as -> set (content . above) as
$ updateYankBuffer KillBackward (a++"\n") e
| otherwise
= set line (Line 0 keep)
$ updateYankBuffer KillBackward kill e
where
Line n txt = view line e
(kill,keep) = splitAt n txt
yank :: EditBox -> EditBox
yank e
= over content (insertString (view yankBuffer e))
$ set lastOperation OtherOperation e
killWordBackward :: Bool -> EditBox -> EditBox
killWordBackward saveKill e
= sometimesUpdateYank
$ set line (Line (length l') (l'++r))
$ e
where
Line n txt = view line e
(l,r) = splitAt n txt
(sp,l1) = span isSpace (reverse l)
(wd,l2) = break isSpace l1
l' = reverse l2
yanked = reverse (sp++wd)
sometimesUpdateYank
| saveKill = updateYankBuffer KillBackward yanked
| otherwise = id
killWordForward :: Bool -> EditBox -> EditBox
killWordForward saveKill e
= sometimesUpdateYank
$ set line (Line (length l) (l++r2))
$ e
where
Line n txt = view line e
(l,r) = splitAt n txt
(sp,r1) = span isSpace r
(wd,r2) = break isSpace r1
yanked = sp++wd
sometimesUpdateYank
| saveKill = updateYankBuffer KillForward yanked
| otherwise = id
insert :: Char -> EditBox -> EditBox
insert c
= set lastOperation OtherOperation
. over content (insertChar c)
insertPaste :: String -> EditBox -> EditBox
insertPaste paste
= over content (insertPastedString paste)
. set lastOperation OtherOperation
insertDigraph :: EditBox -> Maybe EditBox
insertDigraph
= content digraph
. set lastOperation OtherOperation