Haskell Hierarchical Libraries (readline package)Source codeContentsIndex
System.Console.Readline
Portabilitynon-portable (requires libreadline)
Stabilityprovisional
Maintainerlibraries@haskell.org
Description
A Haskell binding to the GNU readline library.
Documentation
readline :: String -> IO (Maybe String)
addHistory :: String -> IO ()
getLineBuffer :: IO String
setLineBuffer :: String -> IO ()
getPoint :: IO Int
setPoint :: Int -> IO ()
getEnd :: IO Int
setEnd :: Int -> IO ()
getMark :: IO Int
setMark :: Int -> IO ()
setDone :: Bool -> IO ()
setPendingInput :: Char -> IO ()
setEraseEmptyLine :: Bool -> IO ()
getPrompt :: IO String
setAlreadyPrompted :: Bool -> IO ()
getLibraryVersion :: IO String
getTerminalName :: IO String
setReadlineName :: String -> IO ()
getInStream :: IO Handle
getOutStream :: IO Handle
setStartupHook :: Maybe (IO ()) -> IO ()
setPreInputHook :: Maybe (IO ()) -> IO ()
setEventHook :: Maybe (IO ()) -> IO ()
setRedisplayFunction :: Maybe (IO ()) -> IO ()
data Keymap
newBareKeymap :: IO Keymap
copyKeymap :: Keymap -> IO Keymap
newKeymap :: IO Keymap
freeKeymap :: Keymap -> IO ()
getKeymap :: IO Keymap
setKeymap :: Keymap -> IO ()
getKeymapByName :: String -> IO Keymap
getKeymapName :: Keymap -> IO (Maybe String)
getExecutingKeymap :: IO Keymap
getBindingKeymap :: IO 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
Constructors
Function Callback
Macro String
Keymap Keymap
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
Constructors
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 ()
setCatchSignals :: Bool -> IO ()
getCatchSignals :: IO Bool
setCatchSigwinch :: Bool -> IO ()
getCatchSigwinch :: IO 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]
setCompletionEntryFunction :: Maybe (String -> IO [String]) -> IO ()
setAttemptedCompletionFunction :: Maybe (String -> Int -> Int -> IO (Maybe (String, [String]))) -> IO ()
setFilenameQuotingFunction :: Maybe (String -> Bool -> Ptr CChar -> IO String) -> IO ()
quoteFilename :: String -> Bool -> Ptr CChar -> IO String
setFilenameDequotingFunction :: Maybe (String -> Maybe Char -> IO String) -> IO ()
setCharIsQuotedP :: Maybe (String -> Int -> IO Bool) -> IO ()
getCompletionQueryItems :: IO Int
setCompletionQueryItems :: Int -> IO ()
getBasicWordBreakCharacters :: IO String
setBasicWordBreakCharacters :: String -> IO ()
getBasicQuoteCharacters :: IO String
setBasicQuoteCharacters :: String -> IO ()
getCompleterWordBreakCharacters :: IO String
setCompleterWordBreakCharacters :: String -> IO ()
getCompleterQuoteCharacters :: IO String
setCompleterQuoteCharacters :: String -> IO ()
getFilenameQuoteCharacters :: IO String
setFilenameQuoteCharacters :: String -> IO ()
getSpecialPrefixes :: IO String
setSpecialPrefixes :: String -> IO ()
getCompletionAppendCharacter :: IO (Maybe Char)
setCompletionAppendCharacter :: Maybe Char -> IO ()
setIgnoreCompletionDuplicates :: Bool -> IO ()
getIgnoreCompletionDuplicates :: IO Bool
setFilenameCompletionDesired :: Bool -> IO ()
getFilenameCompletionDesired :: IO Bool
setFilenameQuotingDesired :: Bool -> IO ()
getFilenameQuotingDesired :: IO Bool
setInhibitCompletion :: Bool -> IO ()
getInhibitCompletion :: IO Bool
setIgnoreSomeCompletionsFunction :: Maybe ([String] -> IO [String]) -> IO ()
setDirectoryCompletionHook :: Maybe (String -> IO String) -> IO ()
setCompletionDisplayMatchesHook :: Maybe ([String] -> IO ()) -> IO ()
Produced by Haddock version 0.8