用动态值扩展静态自动完成命令列表 [英] Extending the list of static autocompletion commands with dynamic values

查看:53
本文介绍了用动态值扩展静态自动完成命令列表的处理方法,对大家解决问题具有一定的参考价值,需要的朋友们下面随着小编来一起学习吧!

问题描述

我在Haskell中有以下程序,该程序从命令行获取输入并修改mydata变量的状态:

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
% 

您可能已经注意到,该程序对典型命令(例如:show:edit:new等)使用命令行自动补全功能.

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

我的问题正在关注.是否可以使用MyDataState中的值扩展可用于自动补全的命令列表(wordsList变量)?例如,如果mydata包含值1, 2, 3,我希望将其与可用于自动补全的命令一起显示-键入: Tab 时,我将得到以下内容命令列表,而不是仅通过wordsList静态定义的命令列表: :help :q :commands :show :save :edit :new :toggleShowEven :1 :2 :3 .如何扩展searchFunc定义以包含在MyDataState中定义的值?有可能吗?

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?

推荐答案

Settings记录中,字段complete的类型为CompletionFunc (StateT MyDataState IO),这意味着我们可以访问自动完成状态.

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

当前mySettings使用的定义

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

return包装了一个纯函数,因此忽略了有状态上下文.我们可以用访问状态的计算来代替它:

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)

还将searchFunc的类型更改为:

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

这篇关于用动态值扩展静态自动完成命令列表的文章就介绍到这了,希望我们推荐的答案对大家有所帮助,也希望大家多多支持IT屋!

查看全文
登录 关闭
扫码关注1秒登录
发送“验证码”获取 | 15天全站免登陆