Extending the list of static autocompletion commands with dynamic values

∥☆過路亽.° 提交于 2019-12-24 15:29:27

问题


I have following program in Haskell that takes input from command line and modifies state of mydata variable:

{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, UndecidableInstances #-}

import Text.Regex.PCRE
import System.Console.Haskeline
import System.IO
import System.IO.Unsafe
import Control.Monad.State.Strict
import qualified Data.ByteString.Char8 as B
import Data.Maybe
import Data.List 
import qualified Data.Map as M

data MyDataState = MyDataState {
  mydata :: [Int],
  showEven :: Bool
} deriving (Show)

myfile :: FilePath
myfile = "data.txt"

defaultFlagValue :: Bool
defaultFlagValue = False

saveDataToFile :: [Int] -> IO ()
saveDataToFile _data = withFile myfile WriteMode $ \h -> hPutStr h (unwords $ map show _data)

{-# NOINLINE loadDataFromFile #-} 
loadDataFromFile :: [Int]
loadDataFromFile = map read . words $ B.unpack $ unsafePerformIO $ B.readFile myfile

wordList = [":help", ":q", ":commands", ":show", ":save", ":edit", ":new", ":toggleShowEven"]

searchFunc :: String -> [Completion]
searchFunc str = map simpleCompletion $ filter (str `isPrefixOf`) (wordList)

mySettings :: Settings (StateT MyDataState IO)
mySettings = Settings { historyFile = Just "myhist"
                      , complete = completeWord Nothing " \t" $ return . searchFunc
                      , autoAddHistory = True
                      }

help :: InputT (StateT MyDataState IO) ()
help = liftIO $ mapM_ putStrLn
       [ ""
       , ":help     - this help"
       , ":q        - quit"
       , ":commands - list available commands"
       , ""
       ]

commands :: InputT (StateT MyDataState IO) ()
commands = liftIO $ mapM_ putStrLn
       [ ""
       , ":show           - display data"
       , ":save           - save results to file"
       , ":edit           - edit data"
       , ":new            - generate new element "
       , ":toggleShowEven - toggle display of even elements"
       , ""
       ]

toggleFlag :: InputT (StateT MyDataState IO) ()
toggleFlag = do
  MyDataState mydata flag <- get
  put $ MyDataState mydata (not flag)

instance MonadState s m => MonadState s (InputT m) where
    get = lift get
    put = lift . put
    state = lift . state

parseInput :: String -> InputT (StateT MyDataState IO) () 
parseInput inp
  | inp =~ "^\\:q"        = return ()

  | inp =~ "^\\:he"       = help >> mainLoop

  | inp =~ "^\\:commands" = commands >> mainLoop

  | inp =~ "^\\:toggleShowEven" = toggleFlag >> mainLoop

  | inp =~ "^\\:show" = do
      MyDataState mydata showEven <- get
      liftIO $ putStrLn $ unwords $ if showEven 
        then map show mydata
        else map show $ filter odd mydata
      mainLoop 

  | inp =~ "^\\:save" = do
      MyDataState mydata _ <- get 
      liftIO $ saveDataToFile mydata
      mainLoop

  | inp =~ "^\\:load" = do
      put (MyDataState loadDataFromFile defaultFlagValue)
      mainLoop

  | inp =~ "^\\:new" = do
      MyDataState mydata showEven <- get                     -- reads the state
      inputData <- getInputLine "\tEnter data: "
      case inputData of 
        Nothing -> put ( MyDataState [0] showEven )
        Just inputD -> 
          put $ if null mydata 
            then MyDataState [read inputD] showEven
            else MyDataState (mydata ++ [read inputD]) showEven -- updates the state
      mainLoop

  | inp =~ ":" = do
    outputStrLn $ "\nNo command \"" ++ inp ++ "\"\n"
    mainLoop

  | otherwise = handleInput inp

handleInput :: String -> InputT (StateT MyDataState IO) ()
handleInput inp = mainLoop

mainLoop :: InputT (StateT MyDataState IO ) ()
mainLoop = do
  inp <- getInputLine "% "
  maybe (return ()) parseInput inp

greet :: IO ()
greet = mapM_ putStrLn
        [ ""
        , "          MyProgram"
        , "=============================="
        , "For help type \":help\""
        , ""
        ]

main :: IO ((), MyDataState)
main = do 
    greet 
    runStateT (runInputT mySettings mainLoop) MyDataState {mydata = [] , showEven = defaultFlagValue}

Example of interaction with the program above:

*Main> main

          MyProgram
==============================
For help type ":help"

% :commands 

:show           - display data
:save           - save results to file
:edit           - edit data
:new            - generate new element 
:toggleShowEven - toggle display of even elements

% :show

% :new
    Enter data: 1
% :new 
    Enter data: 2
% :new 
    Enter data: 3
% :show
1 3
% :toggleShowEven 
% :show
1 2 3
% 

As you might have noticed, this program is using command line autocompletion for typical commands such as :show, :edit, :new, etc.

My question is following. Is it possible to extend the list of commands available for autocompletion (wordsList variable) with the values from MyDataState? For example, if mydata contains values 1, 2, 3, I want it to be shown together with commands available for autocompletion - when typing :Tab, I would get the following list of commands instead of just statically defined via wordsList: :help, :q, :commands, :show, :save, :edit, :new, :toggleShowEven, :1, :2, :3. How do I need to extend searchFunc definition to include values defined in MyDataState? Is it possible at all?


回答1:


In the Settings record, the field complete has type CompletionFunc (StateT MyDataState IO), implying that we have access to the state for autocompletion.

Currently the definition of mySettings uses

complete = completeWord Nothing " \t" $ return . searchFunc

This return wraps a pure function, which thus ignores the stateful context. We can replace that with a computation accessing the state:

complete = completeWord Nothing " \t" $ \str -> do
  _data <- get
  return (searchFunc _data str)

also changing the type of searchFunc for example to:

searchFunc :: MyDataState -> String -> [Completion]


来源:https://stackoverflow.com/questions/49617675/extending-the-list-of-static-autocompletion-commands-with-dynamic-values

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!