module Yi.Keymap.Vim2.Common
( VimMode(..)
, VimBinding(..)
, GotoCharCommand(..)
, VimState(..)
, Register(..)
, RepeatToken(..)
, RepeatableAction(..)
, MatchResult(..)
, EventString
, OperatorName
, RegisterName
, module Yi.Keymap.Vim2.MatchResult
) where
import Yi.Prelude
import Prelude ()
import Data.Binary
import Data.DeriveTH
import qualified Data.HashMap.Strict as HM
import qualified Data.Rope as R
import Yi.Buffer hiding (Insert)
import Yi.Dynamic
import Yi.Editor
import Yi.Keymap
import Yi.Keymap.Vim2.MatchResult
type EventString = String
type OperatorName = String
type RegisterName = Char
data RepeatableAction = RepeatableAction {
raPreviousCount :: !Int
, raActionString :: !EventString
}
deriving (Typeable, Eq, Show)
data Register = Register {
regRegionStyle :: RegionStyle
, regContent :: R.Rope
}
data VimMode = Normal
| NormalOperatorPending OperatorName
| Insert Char
| Replace
| ReplaceSingleChar
| InsertNormal
| InsertVisual
| Visual RegionStyle
| Ex
| Search { previousMode :: VimMode, direction :: Direction }
deriving (Typeable, Eq, Show)
data GotoCharCommand = GotoCharCommand !Char !Direction !RegionStyle
data VimState = VimState {
vsMode :: !VimMode
, vsCount :: !(Maybe Int)
, vsAccumulator :: !EventString
, vsTextObjectAccumulator :: !EventString
, vsRegisterMap :: !(HM.HashMap RegisterName Register)
, vsActiveRegister :: !RegisterName
, vsRepeatableAction :: !(Maybe RepeatableAction)
, vsStringToEval :: !EventString
, vsStickyEol :: !Bool
, vsOngoingInsertEvents :: !EventString
, vsLastGotoCharCommand :: !(Maybe GotoCharCommand)
, vsBindingAccumulator :: !EventString
, vsSecondaryCursors :: ![Point]
, vsPaste :: !Bool
} deriving (Typeable)
$(derive makeBinary ''RepeatableAction)
$(derive makeBinary ''Register)
$(derive makeBinary ''GotoCharCommand)
instance Initializable VimMode where
initial = Normal
$(derive makeBinary ''VimMode)
instance Initializable VimState where
initial = VimState Normal Nothing [] [] HM.empty '\0' Nothing [] False [] Nothing [] [] False
$(derive makeBinary ''VimState)
instance YiVariable VimState
data RepeatToken = Finish
| Drop
| Continue
deriving Show
data VimBinding = VimBindingY {
vbPrerequisite :: EventString -> VimState -> MatchResult (),
vbyAction :: EventString -> YiM RepeatToken
}
| VimBindingE {
vbPrerequisite :: EventString -> VimState -> MatchResult (),
vbeAction :: EventString -> EditorM RepeatToken
}