Skip to content

Commit

Permalink
Merge pull request yi-editor#453 from ethercrow/vim2
Browse files Browse the repository at this point in the history
":set paste" and incsearch history support for vim2.
  • Loading branch information
ethercrow committed Sep 26, 2013
2 parents f038252 + 25f2643 commit 2929d26
Show file tree
Hide file tree
Showing 19 changed files with 172 additions and 82 deletions.
5 changes: 3 additions & 2 deletions yi/src/library/Yi/Keymap/Vim2/Common.hs
Expand Up @@ -55,7 +55,7 @@ data VimMode = Normal
| InsertVisual -- ^ after C-o and one of v, V, C-v
| Visual RegionStyle
| Ex
| Search { searchCommand :: String, previousMode :: VimMode, direction :: Direction }
| Search { previousMode :: VimMode, direction :: Direction }
deriving (Typeable, Eq, Show)

data GotoCharCommand = GotoCharCommand !Char !Direction !RegionStyle
Expand All @@ -74,6 +74,7 @@ data VimState = VimState {
, vsLastGotoCharCommand :: !(Maybe GotoCharCommand)
, vsBindingAccumulator :: !EventString
, vsSecondaryCursors :: ![Point]
, vsPaste :: !Bool -- ^ like vim's :help paste
} deriving (Typeable)

$(derive makeBinary ''RepeatableAction)
Expand All @@ -88,7 +89,7 @@ instance Initializable VimMode where
$(derive makeBinary ''VimMode)

instance Initializable VimState where
initial = VimState Normal Nothing [] [] HM.empty '\0' Nothing [] False [] Nothing [] []
initial = VimState Normal Nothing [] [] HM.empty '\0' Nothing [] False [] Nothing [] [] False

$(derive makeBinary ''VimState)

Expand Down
2 changes: 2 additions & 0 deletions yi/src/library/Yi/Keymap/Vim2/Ex.hs
Expand Up @@ -15,6 +15,7 @@ import qualified Yi.Keymap.Vim2.Ex.Commands.Edit as Edit
import qualified Yi.Keymap.Vim2.Ex.Commands.Global as Global
import qualified Yi.Keymap.Vim2.Ex.Commands.GotoLine as GotoLine
import qualified Yi.Keymap.Vim2.Ex.Commands.Nohl as Nohl
import qualified Yi.Keymap.Vim2.Ex.Commands.Paste as Paste
import qualified Yi.Keymap.Vim2.Ex.Commands.Quit as Quit
import qualified Yi.Keymap.Vim2.Ex.Commands.Reload as Reload
import qualified Yi.Keymap.Vim2.Ex.Commands.Substitute as Substitute
Expand All @@ -29,6 +30,7 @@ defExCommandParsers =
, Global.parse
, GotoLine.parse
, Nohl.parse
, Paste.parse
, Quit.parse
, Reload.parse
, Substitute.parse
Expand Down
28 changes: 26 additions & 2 deletions yi/src/library/Yi/Keymap/Vim2/Ex/Commands/Common.hs
@@ -1,6 +1,8 @@
module Yi.Keymap.Vim2.Ex.Commands.Common
( parse
, parseRange
, OptionAction(..)
, parseOption
, filenameComplete
, forAllBuffers
, pureExCommand
Expand All @@ -11,7 +13,7 @@ import Prelude ()
import Yi.Prelude

import Data.Either (either)
import Data.List
import Data.List (isPrefixOf, drop, length)
import System.Directory
import System.FilePath
import qualified Text.ParserCombinators.Parsec as P
Expand All @@ -22,12 +24,34 @@ import Yi.Keymap
import Yi.Keymap.Vim2.Ex.Types
import Yi.Misc

parse :: P.GenParser Char () a -> String -> Maybe a
parse :: P.GenParser Char () ExCommand -> String -> Maybe ExCommand
parse parser s = either (const Nothing) Just (P.parse parser "" s)

parseRange :: P.GenParser Char () LineRange
parseRange = return CurrentLineRange

data OptionAction = Set !Bool | Invert | Ask

parseOption :: String -> (OptionAction -> Action) -> String -> Maybe ExCommand
parseOption name action = parse $ do
discard $ P.string "set "
nos <- P.many (P.string "no")
invs <- P.many (P.string "inv")
discard $ P.string name
bangs <- P.many (P.string "!")
qs <- P.many (P.string "?")
let
return $ pureExCommand {
cmdShow = "set " ++ concat nos ++ name ++ concat bangs ++ concat qs
, cmdAction = action $
case (fmap (not . null) [qs, bangs, invs, nos]) of
[True, _, _, _] -> Ask
[_, True, _, _] -> Invert
[_, _, True, _] -> Invert
[_, _, _, True] -> Set False
_ -> Set True
}

removePwd :: FilePath -> YiM FilePath
removePwd path = do
pwd <- io getCurrentDirectory
Expand Down
26 changes: 26 additions & 0 deletions yi/src/library/Yi/Keymap/Vim2/Ex/Commands/Paste.hs
@@ -0,0 +1,26 @@
module Yi.Keymap.Vim2.Ex.Commands.Paste
( parse
) where

import Prelude ()
import Yi.Prelude

import Yi.Editor
import Yi.Keymap
import Yi.Keymap.Vim2.Common
import Yi.Keymap.Vim2.Ex.Types
import Yi.Keymap.Vim2.StateUtils
import Yi.Keymap.Vim2.Ex.Commands.Common hiding (parse)

parse :: String -> Maybe ExCommand
parse = parseOption "paste" action

action :: OptionAction -> Action
action Ask = EditorA $ do
value <- vsPaste <$> getDynamic
printMsg $ "paste = " ++ show value
action (Set b) = modPaste $ const b
action Invert = modPaste not

modPaste :: (Bool -> Bool) -> Action
modPaste f = EditorA . modifyStateE $ \s -> s { vsPaste = f (vsPaste s) }
20 changes: 18 additions & 2 deletions yi/src/library/Yi/Keymap/Vim2/InsertMap.hs
Expand Up @@ -22,7 +22,8 @@ import Yi.Keymap.Vim2.StateUtils
import Yi.TextCompletion (completeWordB)

defInsertMap :: [(String, Char)] -> [VimBinding]
defInsertMap digraphs = specials digraphs ++ [printable]
defInsertMap digraphs =
[rawPrintable] ++ specials digraphs ++ [printable]

specials :: [(String, Char)] -> [VimBinding]
specials digraphs =
Expand Down Expand Up @@ -51,6 +52,22 @@ exitBinding digraphs = VimBindingE prereq action
whenM isCurrentLineAllWhiteSpaceB $ moveToSol >> deleteToEol
return Finish

rawPrintable :: VimBinding
rawPrintable = VimBindingE prereq action
where prereq evs s@(VimState { vsMode = (Insert _)}) =
matchFromBool $ vsPaste s && evs `notElem` ["<Esc>", "<C-c>"]
prereq _ _ = NoMatch
action evs = withBuffer0 $ do
case evs of
"<lt>" -> insertB '<'
"<CR>" -> newlineB
"<Tab>" -> insertB '\t'
"<BS>" -> deleteB Character Backward
"<C-h>" -> deleteB Character Backward
"<Del>" -> deleteB Character Forward
c -> insertN c
return Continue

replay :: [(String, Char)] -> [Event] -> EditorM ()
replay _ [] = return ()
replay digraphs (e1:es1) = do
Expand Down Expand Up @@ -154,7 +171,6 @@ printableAction evs = do
"<BS>" -> deleteB Character Backward
"<C-h>" -> deleteB Character Backward
"<Del>" -> deleteB Character Forward
"<C-j>" -> insertB '\n'
"<C-w>" -> deleteRegionB =<< regionOfPartNonEmptyB unitViWordOnLine Backward
"<lt>" -> insertB '<'
evs' -> error $ "Unhandled event " ++ evs' ++ " in insert mode"
Expand Down
4 changes: 3 additions & 1 deletion yi/src/library/Yi/Keymap/Vim2/NormalMap.hs
Expand Up @@ -298,8 +298,10 @@ searchBinding = VimBindingE prereq action
action evs = do
state <- fmap vsMode getDynamic
let dir = if evs == "/" then Forward else Backward
switchModeE $ Search "" state dir
switchModeE $ Search state dir
isearchInitE dir
historyStart
historyPrefixSet ""
return Continue

continueSearching :: (Direction -> Direction) -> EditorM ()
Expand Down
49 changes: 27 additions & 22 deletions yi/src/library/Yi/Keymap/Vim2/SearchMotionMap.hs
Expand Up @@ -6,64 +6,69 @@ import Prelude ()
import Yi.Prelude

import Control.Monad (replicateM_)
import Data.List (drop, lookup)
import Data.Maybe (fromMaybe)

import Yi.Buffer
import Yi.Editor
import Yi.History
import Yi.Keymap.Vim2.Common
import Yi.Keymap.Vim2.Search
import Yi.Keymap.Vim2.StateUtils
import Yi.Keymap.Vim2.Utils
import Yi.Search

defSearchMotionMap :: [VimBinding]
defSearchMotionMap = [enterBinding, escBinding, otherBinding]
defSearchMotionMap = [enterBinding, editBinding, exitBinding]

enterBinding :: VimBinding
enterBinding = VimBindingE prereq action
where prereq "<CR>" (VimState { vsMode = Search {}} ) = WholeMatch ()
prereq _ _ = NoMatch
action _ = do
Search _cmd prevMode dir <- fmap vsMode getDynamic
Search prevMode dir <- fmap vsMode getDynamic
-- TODO: parse cmd into regex and flags
count <- getCountE
isearchFinishE
historyFinish
switchModeE prevMode

count <- getCountE
Just regex <- getRegexE
withBuffer0 $ if count == 1 && dir == Forward
then do
-- Workaround for isearchFinishE leaving cursor after match
continueVimSearch (regex, Backward)
continueVimSearch (regex, Forward)
else replicateM_ (count - 1) $ continueVimSearch (regex, dir)

case prevMode of
Visual _ -> return Continue
_ -> return Finish

otherBinding :: VimBinding
otherBinding = VimBindingE prereq action
where prereq _ (VimState { vsMode = Search {}} ) = WholeMatch ()
editBinding :: VimBinding
editBinding = VimBindingE prereq action
where prereq evs (VimState { vsMode = Search {}} ) = matchFromBool $
evs `elem` (fmap fst binds)
|| (null (drop 1 evs))
prereq _ _ = NoMatch
action evs = do
Search cmd pm dir <- fmap vsMode getDynamic
case evs of
"<BS>" -> isearchDelE
"<C-h>" -> isearchDelE
"<lt>" -> do
switchModeE $ Search (cmd ++ ['<']) pm dir
isearchAddE "<"
[c] -> do
switchModeE $ Search (cmd ++ [c]) pm dir
isearchAddE evs
_ -> return ()
fromMaybe (isearchAddE evs) (lookup evs binds)
withBuffer0 elemsB >>= historyPrefixSet
return Continue
binds = [ ("<BS>", isearchDelE)
, ("<C-h>", isearchDelE)
, ("<C-p>", isearchHistory 1)
, ("<Up>", isearchHistory 1)
, ("<C-n>", isearchHistory (-1))
, ("<Down>", isearchHistory (-1))
, ("<lt>", isearchAddE "<")
]

escBinding :: VimBinding
escBinding = VimBindingE prereq action
where prereq "<Esc>" (VimState { vsMode = Search {}} ) = WholeMatch ()
exitBinding :: VimBinding
exitBinding = VimBindingE prereq action
where prereq _ (VimState { vsMode = Search {}} ) = WholeMatch ()
prereq _ _ = NoMatch
action _ = do
Search _cmd prevMode _dir <- fmap vsMode getDynamic
Search prevMode _dir <- fmap vsMode getDynamic
isearchCancelE
switchModeE prevMode
return Drop
6 changes: 4 additions & 2 deletions yi/src/library/Yi/Keymap/Vim2/StateUtils.hs
Expand Up @@ -123,10 +123,12 @@ setStickyEolE b = modifyStateE $ \s -> s { vsStickyEol = b }

updateModeIndicatorE :: VimMode -> EditorM ()
updateModeIndicatorE prevMode = do
mode <- fmap vsMode getDynamic
currentState <- getDynamic
let mode = vsMode currentState
paste = vsPaste currentState
when (mode /= prevMode) $ do
let modeName = case mode of
Insert _ -> "INSERT"
Insert _ -> "INSERT" ++ if paste then " (paste) " else ""
InsertNormal -> "(insert)"
InsertVisual -> "(insert) VISUAL"
Replace -> "REPLACE"
Expand Down
14 changes: 14 additions & 0 deletions yi/src/tests/vimtests/indent/setpaste.test
@@ -0,0 +1,14 @@
-- Input
(1,7)
foo
bar
baz
-- Output
(3,3)
foo
quux
123
bar
baz
-- Events
a<CR>quux<Esc>:set paste<CR>a<CR>123<Esc>
9 changes: 0 additions & 9 deletions yi/src/tests/vimtests/insertion/C-j_0.test

This file was deleted.

9 changes: 0 additions & 9 deletions yi/src/tests/vimtests/insertion/C-j_1.test

This file was deleted.

11 changes: 0 additions & 11 deletions yi/src/tests/vimtests/insertion/C-j_2.test

This file was deleted.

9 changes: 0 additions & 9 deletions yi/src/tests/vimtests/insertion/C-j_3.test

This file was deleted.

13 changes: 0 additions & 13 deletions yi/src/tests/vimtests/insertion/C-j_4.test

This file was deleted.

12 changes: 12 additions & 0 deletions yi/src/tests/vimtests/search/history1.test
@@ -0,0 +1,12 @@
-- Input
(1,1)
Lorem ipsum dolor sit amet
abc def ghi
qwe rty uiop
-- Output
(1,13)
Lorem ipsum olor sit amet
abc def ghi
qwe rty uiop
-- Events
/dolor<CR>/amet<CR>gg/<C-p><C-p><CR>x
12 changes: 12 additions & 0 deletions yi/src/tests/vimtests/search/history2.test
@@ -0,0 +1,12 @@
-- Input
(1,1)
Lorem ipsum dolor sit amet
abc def ghi
qwe rty uiop
-- Output
(1,13)
Lorem ipsum olor sit amet
abc def ghi
qwe rty uiop
-- Events
/dolor<CR>/amet<CR>gg/<C-p><Up><CR>x

0 comments on commit 2929d26

Please sign in to comment.