- readline :: String -> IO (Maybe String)
- addHistory :: String -> IO ()
- lineBuffer :: StateVar String
- point :: StateVar Int
- end :: StateVar Int
- mark :: StateVar Int
- done :: SettableStateVar Bool
- pendingInput :: SettableStateVar Char
- eraseEmptyLine :: SettableStateVar Bool
- prompt :: GettableStateVar String
- alreadyPrompted :: SettableStateVar Bool
- libraryVersion :: GettableStateVar String
- terminalName :: GettableStateVar String
- readLineName :: SettableStateVar String
- inStream :: GettableStateVar Handle
- outStream :: GettableStateVar Handle
- startupHook :: SettableStateVar (Maybe (IO ()))
- preInputHook :: SettableStateVar (Maybe (IO ()))
- eventHook :: SettableStateVar (Maybe (IO ()))
- redisplayFunction :: SettableStateVar (Maybe (IO ()))
- data Keymap
- newBareKeymap :: IO Keymap
- copyKeymap :: Keymap -> IO Keymap
- newKeymap :: IO Keymap
- freeKeymap :: Keymap -> IO ()
- keymap :: StateVar Keymap
- keymapByName :: String -> GettableStateVar Keymap
- keymapName :: Keymap -> GettableStateVar (Maybe String)
- executingKeymap :: GettableStateVar Keymap
- bindingKeymap :: GettableStateVar Keymap
- type Callback = Int -> Char -> IO Int
- addDefun :: String -> Callback -> Maybe Char -> IO ()
- bindKey :: Char -> Callback -> IO ()
- bindKeyInMap :: Char -> Callback -> Keymap -> IO ()
- unbindKey :: Char -> IO ()
- unbindKeyInMap :: Char -> Keymap -> IO ()
- unbindCommandInMap :: String -> Keymap -> IO ()
- data Entry
- genericBind :: String -> Entry -> Keymap -> IO ()
- parseAndBind :: String -> IO ()
- readInitFile :: String -> IO ()
- namedFunction :: String -> IO (Maybe Callback)
- functionOfKeyseq :: String -> Maybe Keymap -> IO Entry
- functionDumper :: Bool -> IO ()
- listFunmapNames :: IO ()
- funmapNames :: IO [String]
- beginUndoGroup :: IO ()
- endUndoGroup :: IO ()
- data UndoCode
- = UndoDelete
- | UndoInsert
- | UndoBegin
- | UndoEnd
- addUndo :: UndoCode -> Int -> Int -> String -> IO ()
- freeUndoList :: IO ()
- doUndo :: IO Bool
- modifying :: Int -> Int -> IO ()
- redisplay :: IO ()
- forcedUpdateDisplay :: IO ()
- onNewLine :: IO ()
- onNewLineWithPrompt :: IO ()
- resetLineState :: IO ()
- message :: String -> IO ()
- clearMessage :: IO ()
- savePrompt :: IO ()
- restorePrompt :: IO ()
- insertText :: String -> IO ()
- deleteText :: Int -> Int -> IO ()
- copyText :: Int -> Int -> IO String
- killText :: Int -> Int -> IO ()
- readKey :: IO Char
- stuffChar :: Char -> IO Bool
- initialize :: IO ()
- resetTerminal :: Maybe String -> IO ()
- ding :: IO Bool
- displayMatchList :: [String] -> IO ()
- callbackHandlerInstall :: String -> (String -> IO ()) -> IO (IO ())
- callbackReadChar :: IO ()
- catchSignals :: StateVar Bool
- catchSigwinch :: StateVar Bool
- cleanupAfterSignal :: IO ()
- freeLineState :: IO ()
- resetAfterSignal :: IO ()
- resizeTerminal :: IO ()
- setSignals :: IO ()
- clearSignals :: IO ()
- completeInternal :: Char -> IO ()
- complete :: Int -> Char -> IO Int
- possibleCompletions :: Int -> Char -> IO Int
- insertCompletions :: Int -> Char -> IO Int
- completionMatches :: String -> (String -> IO [String]) -> IO (Maybe (String, [String]))
- filenameCompletionFunction :: String -> IO [String]
- usernameCompletionFunction :: String -> IO [String]
- completionEntryFunction :: SettableStateVar (Maybe (String -> IO [String]))
- attemptedCompletionFunction :: SettableStateVar (Maybe (String -> Int -> Int -> IO (Maybe (String, [String]))))
- filenameQuotingFunction :: SettableStateVar (Maybe (String -> Bool -> Ptr CChar -> IO String))
- quoteFilename :: String -> Bool -> Ptr CChar -> IO String
- filenameDequotingFunction :: SettableStateVar (Maybe (String -> Maybe Char -> IO String))
- charIsQuotedP :: SettableStateVar (Maybe (String -> Int -> IO Bool))
- completionQueryItems :: StateVar Int
- basicWordBreakCharacters :: StateVar String
- basicQuoteCharacters :: StateVar String
- completerWordBreakCharacters :: StateVar String
- completerQuoteCharacters :: StateVar String
- filenameQuoteCharacters :: StateVar String
- specialPrefixes :: StateVar String
- completionAppendCharacter :: StateVar (Maybe Char)
- ignoreCompletionDuplicates :: StateVar Bool
- filenameCompletionDesired :: StateVar Bool
- filenameQuotingDesired :: StateVar Bool
- inhibitCompletion :: StateVar Bool
- attemptedCompletionOver :: StateVar Bool
- ignoreSomeCompletionsFunction :: SettableStateVar (Maybe ([String] -> IO [String]))
- directoryCompletionHook :: SettableStateVar (Maybe (String -> IO String))
- completionWordBreakHook :: SettableStateVar (Maybe (IO (Maybe String)))
- completionDisplayMatchesHook :: SettableStateVar (Maybe ([String] -> IO ()))
Documentation
:: String | prompt |
-> IO (Maybe String) | returns the line the user input, or Nothing if EOF is encountered. |
readline is similar to System.IO.getLine
, but with rich edit
functionality and history capability. readline will read a line
from the terminal and return it, using prompt as a prompt. If
prompt is the empty string, no prompt is issued. The line returned
has the final newline removed, so only the text of the line
remains. A blank line returns the empty string. If EOF is
encountered while reading a line, and the line is empty, Nothing is
returned. If an EOF is read with a non-empty line, it is treated
as a newline.
addHistory :: String -> IO ()
Add this command to the history. This allows users to search backward through history with C-r and step through with up and down arrows, among other things.
startupHook :: SettableStateVar (Maybe (IO ()))Source
preInputHook :: SettableStateVar (Maybe (IO ()))Source
Keymaps
data Keymap
copyKeymap :: Keymap -> IO Keymap
freeKeymap :: Keymap -> IO ()
Keymap vars
Callbacks
bindKeyInMap :: Char -> Callback -> Keymap -> IO ()
unbindKeyInMap :: Char -> Keymap -> IO ()
unbindCommandInMap :: String -> Keymap -> IO ()
genericBind :: String -> Entry -> Keymap -> IO ()
parseAndBind :: String -> IO ()
readInitFile :: String -> IO ()
namedFunction :: String -> IO (Maybe Callback)
functionDumper :: Bool -> IO ()
listFunmapNames :: IO ()
funmapNames :: IO [String]
beginUndoGroup :: IO ()
endUndoGroup :: IO ()
freeUndoList :: IO ()
forcedUpdateDisplay :: IO ()
onNewLineWithPrompt :: IO ()
resetLineState :: IO ()
clearMessage :: IO ()
savePrompt :: IO ()
restorePrompt :: IO ()
insertText :: String -> IO ()
deleteText :: Int -> Int -> IO ()
initialize :: IO ()
resetTerminal :: Maybe String -> IO ()
displayMatchList :: [String] -> IO ()
callbackReadChar :: IO ()
cleanupAfterSignal :: IO ()
freeLineState :: IO ()
resetAfterSignal :: IO ()
resizeTerminal :: IO ()
setSignals :: IO ()
clearSignals :: IO ()
completeInternal :: Char -> IO ()
possibleCompletions :: Int -> Char -> IO Int
insertCompletions :: Int -> Char -> IO Int
filenameCompletionFunction :: String -> IO [String]
usernameCompletionFunction :: String -> IO [String]
completionEntryFunction :: SettableStateVar (Maybe (String -> IO [String]))Source
attemptedCompletionFunction :: SettableStateVar (Maybe (String -> Int -> Int -> IO (Maybe (String, [String]))))Source
filenameQuotingFunction :: SettableStateVar (Maybe (String -> Bool -> Ptr CChar -> IO String))Source
filenameDequotingFunction :: SettableStateVar (Maybe (String -> Maybe Char -> IO String))Source
charIsQuotedP :: SettableStateVar (Maybe (String -> Int -> IO Bool))Source
ignoreSomeCompletionsFunction :: SettableStateVar (Maybe ([String] -> IO [String]))Source
completionDisplayMatchesHook :: SettableStateVar (Maybe ([String] -> IO ()))Source