module Yi.TextCompletion (
wordComplete,
wordComplete',
wordCompleteString,
wordCompleteString',
mkWordComplete,
resetComplete,
completeWordB,
) where
import Prelude ()
import Yi.Completion
import Data.Char
import Data.List (filter, drop, isPrefixOf, reverse, findIndex, length, groupBy)
import Data.Maybe
import Yi.Core
newtype Completion = Completion
[String]
deriving Typeable
instance Initializable Completion where
initial = Completion []
resetComplete :: EditorM ()
resetComplete = setDynamic (Completion [])
mkWordComplete :: YiM String -> (String -> YiM [String]) -> ([String] -> YiM () ) -> (String -> String -> Bool) -> YiM String
mkWordComplete extractFn sourceFn msgFn predMatch = do
Completion complList <- withEditor getDynamic
case complList of
(x:xs) -> do
msgFn (x:xs)
withEditor $ setDynamic (Completion xs)
return x
[] -> do
w <- extractFn
ws <- sourceFn w
withEditor $ setDynamic (Completion $ (nubSet $ filter (matches w) ws) ++ [w])
mkWordComplete extractFn sourceFn msgFn predMatch
where matches x y = x `predMatch` y && x/=y
wordCompleteString' :: Bool -> YiM String
wordCompleteString' caseSensitive = mkWordComplete
(withEditor $ withBuffer0 $ do readRegionB =<< regionOfPartB unitWord Backward)
(\_ -> withEditor wordsForCompletion)
(\_ -> return ())
(mkIsPrefixOf caseSensitive)
wordCompleteString :: YiM String
wordCompleteString = wordCompleteString' True
wordComplete' :: Bool -> YiM ()
wordComplete' caseSensitive = do
x <- wordCompleteString' caseSensitive
withEditor $ withBuffer0 $ flip replaceRegionB x =<< regionOfPartB unitWord Backward
wordComplete :: YiM ()
wordComplete = wordComplete' True
completeWordB :: EditorM ()
completeWordB = veryQuickCompleteWord
veryQuickCompleteWord :: EditorM ()
veryQuickCompleteWord =
do (curWord, curWords) <- withBuffer0 wordsAndCurrentWord
let match :: String -> Maybe String
match x = if (isPrefixOf curWord x) && (x /= curWord) then Just x else Nothing
preText <- completeInList curWord match curWords
if curWord == ""
then printMsg "No word to complete"
else withBuffer0 $ insertN $ drop (length curWord) preText
wordsAndCurrentWord :: BufferM (String, [String])
wordsAndCurrentWord =
do curText <- readRegionB =<< regionOfB Document
curWord <- readRegionB =<< regionOfPartB unitWord Backward
return (curWord, words' curText)
wordsForCompletionInBuffer :: BufferM [String]
wordsForCompletionInBuffer = do
above <- readRegionB =<< regionOfPartB Document Backward
below <- readRegionB =<< regionOfPartB Document Forward
return (reverse (words' above) ++ words' below)
wordsForCompletion :: EditorM [String]
wordsForCompletion = do
(_b:bs) <- fmap bkey <$> getBufferStack
w0 <- withBuffer0 $ wordsForCompletionInBuffer
contents <- forM bs $ \b->withGivenBuffer0 b elemsB
return $ w0 ++ concatMap words' contents
words' :: String -> [String]
words' = filter (not . isNothing . charClass . head) . groupBy ((==) `on` charClass)
charClass :: Char -> Maybe Int
charClass c = findIndex (generalCategory c `elem`)
[[UppercaseLetter, LowercaseLetter, TitlecaseLetter, ModifierLetter, OtherLetter,
ConnectorPunctuation,
NonSpacingMark, SpacingCombiningMark, EnclosingMark, DecimalNumber, LetterNumber, OtherNumber],
[MathSymbol, CurrencySymbol, ModifierSymbol, OtherSymbol]
]