Skip to content

Commit

Permalink
Merge branch 'visual-text-objects'
Browse files Browse the repository at this point in the history
  • Loading branch information
ethercrow committed Aug 5, 2016
2 parents e6b66af + c2c42af commit 9e08919
Show file tree
Hide file tree
Showing 7 changed files with 53 additions and 12 deletions.
7 changes: 7 additions & 0 deletions src/library/Yi/Keymap/Vim/MatchResult.hs
Expand Up @@ -34,3 +34,10 @@ instance Show (MatchResult a) where
show (WholeMatch _) = "WholeMatch"
show PartialMatch = "PartialMatch"
show NoMatch = "NoMatch"

matchFromBool :: Bool -> MatchResult ()
matchFromBool b = if b then WholeMatch () else NoMatch

matchFromMaybe :: Maybe a -> MatchResult a
matchFromMaybe Nothing = NoMatch
matchFromMaybe (Just a) = WholeMatch a
4 changes: 2 additions & 2 deletions src/library/Yi/Keymap/Vim/NormalOperatorPendingMap.hs
Expand Up @@ -146,9 +146,9 @@ parseCommand n sm _ s = case stringToMove . Ev $ T.pack s of
WholeMatch m -> JustMove $ CountedMove n $ changeMoveStyle sm m
PartialMatch -> PartialOperand
NoMatch -> case stringToTextObject s of
Just to -> JustTextObject $ CountedTextObject (fromMaybe 1 n)
WholeMatch to -> JustTextObject $ CountedTextObject (fromMaybe 1 n)
$ changeTextObjectStyle sm to
Nothing -> NoOperand
_ -> NoOperand

-- TODO: setup doctests
-- Parse event string that can go after operator
Expand Down
11 changes: 7 additions & 4 deletions src/library/Yi/Keymap/Vim/TextObject.hs
Expand Up @@ -9,6 +9,7 @@ module Yi.Keymap.Vim.TextObject

import Control.Monad (replicateM_, (<=<))
import Yi.Buffer.Adjusted
import Yi.Keymap.Vim.MatchResult
import Yi.Keymap.Vim.StyledRegion (StyledRegion (..), normalizeRegion)

data TextObject = TextObject !RegionStyle !TextUnit
Expand All @@ -29,10 +30,12 @@ textObjectRegionB' (CountedTextObject count (TextObject style unit)) =
changeTextObjectStyle :: (RegionStyle -> RegionStyle) -> TextObject -> TextObject
changeTextObjectStyle smod (TextObject s u) = TextObject (smod s) u

stringToTextObject :: String -> Maybe TextObject
stringToTextObject ('i':s) = parseTextObject InsideBound s
stringToTextObject ('a':s) = parseTextObject OutsideBound s
stringToTextObject _ = Nothing
stringToTextObject :: String -> MatchResult TextObject
stringToTextObject "a" = PartialMatch
stringToTextObject "i" = PartialMatch
stringToTextObject ('i':s) = matchFromMaybe (parseTextObject InsideBound s)
stringToTextObject ('a':s) = matchFromMaybe (parseTextObject OutsideBound s)
stringToTextObject _ = NoMatch

parseTextObject :: BoundarySide -> String -> Maybe TextObject
parseTextObject bs (c:[]) = fmap (TextObject Exclusive . ($ bs == OutsideBound)) mkUnit
Expand Down
4 changes: 1 addition & 3 deletions src/library/Yi/Keymap/Vim/Utils.hs
Expand Up @@ -42,6 +42,7 @@ import Yi.Event (Event)
import Yi.Keymap (YiM)
import Yi.Keymap.Vim.Common
import Yi.Keymap.Vim.EventUtils (eventToEventString, splitCountedCommand)
import Yi.Keymap.Vim.MatchResult
import Yi.Keymap.Vim.Motion (Move (Move), stringToMove)
import Yi.Keymap.Vim.StateUtils (getMaybeCountE, modifyStateE,
resetCountE, getRegisterE)
Expand Down Expand Up @@ -96,9 +97,6 @@ selectBinding input state = asum . fmap try
where try (VimBindingY matcher) = matcher input state
try (VimBindingE matcher) = fmap withEditor $ matcher input state

matchFromBool :: Bool -> MatchResult ()
matchFromBool b = if b then WholeMatch () else NoMatch

setUnjumpMarks :: Point -> BufferM ()
setUnjumpMarks p = do
solP <- solPointB p
Expand Down
23 changes: 20 additions & 3 deletions src/library/Yi/Keymap/Vim/VisualMap.hs
@@ -1,4 +1,5 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_HADDOCK show-extensions #-}

-- |
Expand All @@ -16,7 +17,7 @@ import Lens.Micro.Platform ((.=))
import Control.Monad (forM_, void)
import Data.Char (ord)
import Data.List (group)
import Data.Maybe (fromJust)
import Data.Maybe (fromJust, fromMaybe)
import qualified Data.Text as T (unpack)
import Yi.Buffer.Adjusted hiding (Insert)
import Yi.Editor
Expand All @@ -25,6 +26,7 @@ import Yi.Keymap.Vim.Operator (VimOperator (..), opDelete, stringT
import Yi.Keymap.Vim.StateUtils
import Yi.Keymap.Vim.StyledRegion (StyledRegion (StyledRegion), transformCharactersInRegionB)
import Yi.Keymap.Vim.Tag (gotoTag)
import Yi.Keymap.Vim.TextObject
import Yi.Keymap.Vim.Utils (matchFromBool, mkChooseRegisterBinding, mkMotionBinding)
import Yi.MiniBuffer (spawnMinibufferE)
import Yi.Monad (whenM)
Expand All @@ -34,7 +36,7 @@ import Yi.Utils (SemiNum ((-~)))

defVisualMap :: [VimOperator] -> [VimBinding]
defVisualMap operators =
[escBinding, motionBinding, changeVisualStyleBinding, setMarkBinding]
[escBinding, motionBinding, textObjectBinding, changeVisualStyleBinding, setMarkBinding]
++ [chooseRegisterBinding]
++ operatorBindings operators ++ digitBindings ++ [replaceBinding, switchEdgeBinding]
++ [insertBinding, exBinding, shiftDBinding]
Expand Down Expand Up @@ -131,6 +133,21 @@ motionBinding = mkMotionBinding Continue $
Visual _ -> True
_ -> False

textObjectBinding :: VimBinding
textObjectBinding = VimBindingE (f . T.unpack . _unEv)
where
f (stringToTextObject -> PartialMatch) (VimState {vsMode = Visual _}) = PartialMatch
f (stringToTextObject -> WholeMatch to) (VimState {vsMode = Visual _, vsCount = mbCount}) =
let count = fromMaybe 1 mbCount
in
WholeMatch $ do
withCurrentBuffer $ do
StyledRegion _ reg <- regionOfTextObjectB (CountedTextObject count to)
setSelectionMarkPointB (regionStart reg)
moveTo (regionEnd reg -~ 1)
return Continue
f _ _ = NoMatch

regionOfSelectionB :: BufferM Region
regionOfSelectionB = savingPointB $ do
start <- getSelectionMarkPointB
Expand Down Expand Up @@ -255,7 +272,7 @@ insertBinding = VimBindingE (f . T.unpack . _unEv)
tagJumpBinding :: VimBinding
tagJumpBinding = VimBindingY (f . T.unpack . _unEv)
where f "<C-]>" (VimState { vsMode = (Visual _) })
= WholeMatch $ do
= WholeMatch $ do
tag <- Tag . R.toText <$> withCurrentBuffer
(regionOfSelectionB >>= readRegionB)
withEditor $ switchModeE Normal
Expand Down
8 changes: 8 additions & 0 deletions src/tests/vimtests/visual/v3iwx.test
@@ -0,0 +1,8 @@
-- Input
(1,1)
123 456 789
-- Output
(1,1)
789
-- Events
v3iwx
8 changes: 8 additions & 0 deletions src/tests/vimtests/visual/viw.test
@@ -0,0 +1,8 @@
-- Input
(1,6)
123 456 789
-- Output
(1,5)
123 789
-- Events
viwx

0 comments on commit 9e08919

Please sign in to comment.