Created
August 4, 2014 14:51
-
-
Save chemist/9154f23f6db6bcfebc34 to your computer and use it in GitHub Desktop.
my config for yi
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE ScopedTypeVariables #-} | |
module Main where | |
import Yi | |
import Yi.Keymap.Vim (keymapSet, mkKeymapSet, defVimConfig, pureEval, impureEval, VimConfig(..), VimBinding(..)) | |
import Yi.Keymap.Vim.Common (VimMode(..), RepeatToken(..)) | |
import Yi.Keymap.Vim.Utils (mkStringBindingE, mkStringBindingY) | |
import qualified Yi.Mode.Haskell as Haskell | |
import Yi.Style | |
import Yi.Core (msgEditor) | |
import Yi.Style.Library | |
import Yi.Keymap.Vim.ExMap | |
import Text.Parsec.Char | |
import Text.Parsec.Combinator | |
import Control.Monad (void) | |
import Yi.Keymap.Vim.Ex.Types | |
import qualified Yi.Keymap.Vim.Ex.Commands.Common as Common | |
import Yi.Keymap.Vim.StateUtils | |
import Yi.Tag | |
import Control.Monad (when) | |
import Control.Monad.Base | |
import Control.Exception (try, SomeException) | |
import Yi.Keymap.Emacs.Utils | |
import Control.Applicative ((<*), (*>)) | |
-- import Yi.UI.Vty (start) | |
-- import Yi.UI.Pango (start) | |
{- | |
For now we just make the selected style the same as the | |
modeline_focused style... Just because i'm not good with | |
styles yet - Jim | |
-} | |
defaultVimUiTheme :: Theme | |
defaultVimUiTheme = defaultTheme `override` \super self -> super { | |
selectedStyle = modelineFocusStyle self | |
} | |
myConfigUI :: UIConfig | |
myConfigUI = (configUI defaultVimConfig) { | |
configFontSize = Just 10, | |
configTheme = defaultVimUiTheme, | |
configWindowFill = '~' | |
} | |
main :: IO () | |
main = yi $ defaultVimConfig { | |
-- Uncomment for Shim support | |
-- modeTable = [shimMode] <|> modeTable defaultVimConfig, | |
configUI = myConfigUI, | |
defaultKm = myKeymapSet | |
} | |
myKeymapSet :: KeymapSet | |
myKeymapSet = mkKeymapSet $ defVimConfig `override` bindings | |
where bindings :: VimConfig -> VimConfig -> VimConfig | |
bindings super _ = super { vimBindings = myBindings ++ myRunBindings ++ vimBindings super | |
, vimExCommandParsers = myEx ++ vimExCommandParsers super | |
} | |
myEx :: [String -> Maybe ExCommand] | |
myEx = [ splitWindow, tags ] | |
where splitWindow = Common.parse $ do | |
void $ string "split" | |
return $! cmdNow | |
cmdNow :: ExCommand | |
cmdNow = Common.impureExCommand | |
{ cmdShow = "split window" | |
, cmdAction = makeAction splitE | |
} | |
tags = Common.parse $ do | |
void $ string "tag" | |
tag <- space *> many1 anyChar <* eof | |
return $! makeTags tag | |
makeTags :: Tag -> ExCommand | |
makeTags tag = Common.impureExCommand | |
{ cmdShow = "go to tag" | |
, cmdAction = YiA $ (withEditor addJumpHereE) >> gotoTag tag | |
} | |
myBindings :: [VimBinding] | |
myBindings = fmap (mkStringBindingE Normal Drop) | |
[ (",", pword, resetCount) | |
] | |
where | |
pword = withBuffer0 readCurrentWordB >>= printMsg | |
myRunBindings :: [VimBinding] | |
myRunBindings = fmap (mkStringBindingY Normal) | |
[ ("<C-]>", go, id) | |
, ("<C-t>", back, id) | |
] | |
where | |
go = do | |
tag <- withBuffer $ readUnitB unitWord | |
withEditor $ addJumpHereE | |
gotoTag tag | |
back = withEditor $ do | |
jumpBackE | |
p <- withBuffer $ getLineAndCol | |
when (p == (1,0)) $ jumpBackE | |
-- | Opens the file that contains @tag@. Uses the global tag table and prompts | |
-- the user to open one if it does not exist | |
gotoTag :: Tag -> YiM () | |
gotoTag tag = | |
visitTagTable $ \tagTable -> | |
case lookupTag tag tagTable of | |
Nothing -> fail $ "No tags containing " ++ tag | |
Just (filename, line) -> do | |
void $ editFile filename | |
void $ withBuffer $ gotoLn line | |
return () | |
-- | Call continuation @act@ with the TagTable. Uses the global table | |
-- and prompts the user if it doesn't exist | |
visitTagTable :: (TagTable -> YiM ()) -> YiM () | |
visitTagTable act = do | |
posTagTable <- withEditor getTags | |
-- does the tagtable exist? | |
case posTagTable of | |
Just tagTable -> act tagTable | |
Nothing -> either bad good =<< (liftBase . try . importTagTable $ "TAGS") | |
where | |
bad :: SomeException ->YiM () | |
bad _ = fail "cant find TAGS file" | |
good :: TagTable -> YiM () | |
good t = (withEditor $ setTags t) >> act t |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment
visitTagTable and gotoTag stolen from Yi.Keymap.Emacs.Utils