Sun Oct 5 20:51:57 PDT 2008 [EMAIL PROTECTED] * Add support for CTags and interface for emacs mode. Not having M-. was killing me. Added TagTable as part of the global state, Emacs prompting for getting tags, and trie structure for reasonably fast hinting. I'll try add a vi interface too.
--~--~---------~--~----~------------~-------~--~----~ Yi development mailing list yi-devel@googlegroups.com http://groups.google.com/group/yi-devel -~----------~----~----~----~------~----~------~--~---
New patches: [Add support for CTags and interface for emacs mode. [EMAIL PROTECTED] Not having M-. was killing me. Added TagTable as part of the global state, Emacs prompting for getting tags, and trie structure for reasonably fast hinting. I'll try add a vi interface too. ] { addfile ./Data/Trie.hs hunk ./Data/Trie.hs 1 +module Data.Trie where + +-- Trie module. Partly taken from http://www.haskell.org/haskellwiki/Haskell_Quiz/Word_Search/Solution_Sjanssen + +import qualified Data.Map as Map +import Control.Monad + +data Trie = Trie Bool (Map.Map Char Trie) deriving (Show) + +-- | A blank Trie +empty :: Trie +empty = Trie False Map.empty + +-- | Insert a new string into the trie. +insert :: String -> Trie -> Trie +insert [] (Trie b m) = Trie True m +insert (x:xs) (Trie b m) = Trie b $ Map.alter (maybe (Just $ fromString xs) (Just . insert xs)) x m + +fromString = foldr (\x xs -> Trie False (Map.singleton x xs)) (Trie True Map.empty) + +-- | Take a list of String and compress it into a Trie +fromList :: [String] -> Trie +fromList = foldr insert empty + +-- | Take a trie and expand it into the strings that it represents +toList :: Trie -> [String] +toList (Trie b m) = + if b then "":expand + else expand + where expand = [ char:word | (char, trie) <- Map.toList m, + word <- toList trie ] + +-- | Takes a trie and a prefix and returns the sub-trie that +-- of words with that prefix +lookupPrefix :: (Monad m) => String -> Trie -> m Trie +lookupPrefix [] trie = return trie +lookupPrefix (x:xs) (Trie _ m) = Map.lookup x m >>= lookupPrefix xs + +-- | Helper function, finds all the suffixes of a given prefix +possibleSuffixes :: String -> Trie -> [String] +possibleSuffixes prefix fulltrie = + lookupPrefix prefix fulltrie >>= toList hunk ./Yi/Editor.hs 15 +import Yi.Tag +import Yi.Window hunk ./Yi/Editor.hs 49 + ,tags :: !(Maybe TagTable) -- ^ table for ctags hunk ./Yi/Editor.hs 56 - put (Editor bss bs supply ts _dv sl kr _re _dir _ev) = put bss >> put bs >> put supply >> put ts >> put sl >> put kr - get = Editor <$> get <*> get <*> get <*> get <*> pure emptyDV <*> get <*> get <*> pure Nothing <*> pure Forward <*> pure [] + put (Editor bss bs supply ts _dv sl kr _re _tt _dir _ev) = put bss >> put bs >> put supply >> put ts >> put sl >> put kr + get = Editor <$> get <*> get <*> get <*> get <*> pure emptyDV <*> get <*> get <*> pure Nothing <*> pure Nothing <*>pure Forward <*> pure [] hunk ./Yi/Editor.hs 113 +tagsA :: Accessor Editor (Maybe TagTable) +tagsA = Accessor tags (\f e -> e {tags = f (tags e)}) + hunk ./Yi/Editor.hs 128 + ,tags = Nothing hunk ./Yi/Editor.hs 323 +-- --------------------------------------------------------------------- +-- Register interface to TagTable. + +-- | Set a new TagTable +setTags :: TagTable -> EditorM () +setTags = setA tagsA . Just + +-- | Reset the TagTable +resetTags :: EditorM () +resetTags = setA tagsA Nothing + +-- | Get the currently registered tag table +getTags :: EditorM (Maybe TagTable) +getTags = getA tagsA + + + hunk ./Yi/Keymap/Emacs.hs 35 + , promptTag hunk ./Yi/Keymap/Emacs.hs 158 + , metaCh '.' ?>>! promptTag hunk ./Yi/Keymap/Emacs/Utils.hs 32 + , promptTag hunk ./Yi/Keymap/Emacs/Utils.hs 40 +import Data.Maybe (maybe) hunk ./Yi/Keymap/Emacs/Utils.hs 42 -import System.FilePath (addTrailingPathSeparator) +import System.FilePath (addTrailingPathSeparator, takeDirectory, takeFileName, (</>)) hunk ./Yi/Keymap/Emacs/Utils.hs 59 +import Yi.Tag hunk ./Yi/Keymap/Emacs/Utils.hs 241 - + +-- | Generic emacs prompt file action. Takes a @prompt and a continuation @act +-- and prompts the user with file hints +promptFile :: String -> (String -> YiM ()) -> YiM () +promptFile prompt act = do maybePath <- withBuffer $ getA fileA + startPath <- addTrailingPathSeparator <$> (liftIO $ canonicalizePath' =<< getFolder maybePath) + -- TODO: Just call withMinibuffer + withMinibufferGen startPath (findFileHint startPath) prompt (simpleComplete $ matchingFileNames (Just startPath)) act + hunk ./Yi/Keymap/Emacs/Utils.hs 254 -findFile = do maybePath <- withBuffer $ getA fileA - startPath <- addTrailingPathSeparator <$> (liftIO $ canonicalizePath' =<< getFolder maybePath) - -- TODO: Just call withMinibuffer - withMinibufferGen startPath (findFileHint startPath) "find file:" (simpleComplete $ matchingFileNames (Just startPath)) $ \filename -> do +findFile = promptFile "find file:" $ \filename -> do hunk ./Yi/Keymap/Emacs/Utils.hs 297 + +-- | Shortcut to use a default list when a blank list is given. +-- Used for default values to emacs queries +maybeList :: [a] -> [a] -> [a] +maybeList def [] = def +maybeList _ ls = ls + +-------------------------------------------------- +-- TAGS - See Yi.Tag for more info + +-- | Prompt the user to give a tag and then jump to that tag +promptTag :: YiM () +promptTag = do + -- default tag is where the buffer is on + defaultTag <- withBuffer $ readUnitB Word + -- if we have tags use them to generate hints + tagTable <- withEditor getTags + let hinter = return . maybe fail hintTags tagTable + withMinibuffer ("Find tag: (default " ++ defaultTag ++ ")") hinter $ + -- if the string is "" use the defaultTag + gotoTag . maybeList defaultTag + +-- | 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 + fnewE $ filename + 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 -> + promptFile ("Visit tags table: (default tags) ") $ \path -> do + -- default emacs behavior, append tags + let filename = maybeList "tags" $ takeFileName path + tagTable <- liftIO $ importTagTable $ + takeDirectory path </> filename + withEditor $ setTags tagTable + act tagTable + +resetTagTable :: YiM() +resetTagTable = withEditor resetTags addfile ./Yi/Tag.hs hunk ./Yi/Tag.hs 1 + +-- | A module for CTags integration + +module Yi.Tag + ( + lookupTag, + importTagTable, + hintTags, + Tag, + TagTable(..) + ) +where + +{- Standard Library Module Imports -} + +import Data.Maybe (mapMaybe) +import System.FilePath (takeFileName, takeDirectory, FilePath, (</>)) +import System.FriendlyPath +import Data.Map (Map, fromList, lookup, keys) +import Control.Monad (liftM) + + +import qualified Data.Trie as Trie + + +type Tag = String + +data TagTable = TagTable { tagFileName:: FilePath + -- ^ local name of the tag file + -- TODO: reload if this file is change + , tagBaseDir :: FilePath + -- ^ path to the tag file directory + -- tags are relative to this path + , tagFileMap :: Map Tag (FilePath, Int) + -- ^ map from tags to files + , tagTrie :: Trie.Trie + -- ^ trie to speed up tag hinting + } + +-- | Find the location of a tag using the tag table. +-- Returns a full path and line number +lookupTag :: Tag -> TagTable -> Maybe (FilePath, Int) +lookupTag tag tagTable = do + (file, line) <- Data.Map.lookup tag $ tagFileMap tagTable + return $ (tagBaseDir tagTable </> file, line) + + +readCTags :: String -> Map Tag (FilePath, Int) +readCTags = + fromList . mapMaybe (parseTagLine . words) . lines + where parseTagLine [tag, tagfile, lineno] = Just (tag, (tagfile, read lineno)) + parseTagLine _ = Nothing + +-- | Read in a tag file from the system +importTagTable :: FilePath -> IO TagTable +importTagTable filename = do + friendlyName <- expandTilda filename + tagStr <- readFile friendlyName + let ctags = readCTags tagStr + return $ TagTable { tagFileName = takeFileName filename, + tagBaseDir = takeDirectory filename, + tagFileMap = ctags, + tagTrie = Trie.fromList $ keys ctags + } + +-- | Gives all the possible expanded tags that could match a given @prefix +hintTags :: TagTable -> String -> [String] +hintTags tags prefix = map (prefix ++) $ Trie.possibleSuffixes prefix $ tagTrie tags hunk ./yi.cabal 149 + Yi.Tag hunk ./yi.cabal 205 + Data.Trie } Context: [Fix single quote highlighting issue in python mode [EMAIL PROTECTED] [TAG 0.5.0.1 [EMAIL PROTECTED] [bump version number [EMAIL PROTECTED] [TAG 0.5.0 [EMAIL PROTECTED] Patch bundle hash: 494fdbd107a9d9f83c6f789caf408f3c2793ea23