module System.Console.Editline.Readline (
readline,
addHistory,
readHistory,
writeHistory,
clearHistory,
stifleHistory,
unstifleHistory,
historyIsStifled,
historyMaxEntries,
getLineBuffer,
getPoint,
setPoint,
getEnd,
setEnd,
getPrompt,
getLibraryVersion,
getTerminalName,
setReadlineName,
getInStream,
getOutStream,
setStartupHook,
setRedisplayFunction,
Callback,
addDefun,
bindKey,
parseAndBind,
readInitFile,
redisplay,
readKey,
stuffChar,
initialize,
resetTerminal,
callbackHandlerInstall,
callbackReadChar,
complete,
completionMatches,
filenameCompletionFunction,
usernameCompletionFunction,
setCompletionEntryFunction,
setAttemptedCompletionFunction,
getCompletionQueryItems,
setCompletionQueryItems,
getBasicWordBreakCharacters,
setBasicWordBreakCharacters,
getCompleterWordBreakCharacters,
setCompleterWordBreakCharacters,
getCompleterQuoteCharacters,
setCompleterQuoteCharacters,
getSpecialPrefixes,
setSpecialPrefixes,
getCompletionAppendCharacter,
setCompletionAppendCharacter,
setInhibitCompletion,
getInhibitCompletion,
setAttemptedCompletionOver,
getAttemptedCompletionOver,
)
where
import Control.Monad ( liftM, when, unless )
import Data.Char ( chr, ord )
import System.IO ( Handle )
import System.IO.Unsafe ( unsafePerformIO )
import Data.IORef ( newIORef, readIORef, writeIORef )
import Foreign.Ptr ( Ptr, nullPtr, FunPtr, nullFunPtr, freeHaskellFunPtr )
import Foreign.Storable ( Storable(..) )
import Foreign.Marshal.Utils ( maybePeek, maybeWith )
import Foreign.Marshal.Alloc ( free )
import Foreign.Marshal.Array ( mallocArray, peekArray0, pokeArray0 )
import Foreign.C.Types ( CInt, CChar, CFile )
import Foreign.C.String ( newCString, peekCString, withCString,
castCharToCChar, castCCharToChar )
import GHC.Handle ( fdToHandle )
readline :: String
-> IO (Maybe String)
readline prompt = do
ptr <- withCString prompt readlineC
flip maybePeek ptr $ \ptr' -> do
line <- peekCString ptr'
free ptr'
return line
foreign import ccall "readline" readlineC :: Ptr CChar -> IO (Ptr CChar)
addHistory :: String -> IO ()
addHistory line = withCString line add_history
foreign import ccall unsafe add_history :: Ptr CChar -> IO ()
readHistory :: FilePath
-> IO Bool
readHistory fp = do
ok <- withCString fp read_history
return (histResultIsOK ok)
foreign import ccall unsafe read_history :: Ptr CChar -> IO CInt
writeHistory :: FilePath
-> IO Bool
writeHistory fp = do
ok <- withCString fp write_history
return (histResultIsOK ok)
foreign import ccall unsafe write_history :: Ptr CChar -> IO CInt
histResultIsOK :: CInt -> Bool
histResultIsOK = (==0)
clearHistory :: IO ()
clearHistory = clear_history
foreign import ccall unsafe clear_history :: IO ()
stifleHistory :: Int -> IO ()
stifleHistory n = stifle_history n
foreign import ccall unsafe stifle_history :: Int -> IO ()
unstifleHistory :: IO Int
unstifleHistory = unstifle_history
foreign import ccall unsafe unstifle_history :: IO Int
historyIsStifled :: IO Bool
historyIsStifled = do
isStifledInt <- history_is_stifled
let isStifled = case isStifledInt of
0 -> False
1 -> True
_ -> error "historyIsStifled: history_is_stifled returned unexpected value (expected 0 or 1, received other)"
return isStifled
foreign import ccall unsafe history_is_stifled :: IO Int
historyMaxEntries :: IO Int
historyMaxEntries = liftM fromIntegral (peek max_input_history)
foreign import ccall "&" max_input_history :: Ptr CInt
getLineBuffer :: IO String
getLineBuffer = peek rl_line_buffer >>= peekCString
foreign import ccall "&"
rl_line_buffer :: Ptr (Ptr CChar)
getPoint :: IO Int
getPoint = liftM fromIntegral (peek rl_point)
setPoint :: Int -> IO ()
setPoint p = poke rl_point (fromIntegral p)
foreign import ccall "&" rl_point :: Ptr CInt
getEnd :: IO Int
getEnd = liftM fromIntegral (peek rl_end)
setEnd :: Int -> IO ()
setEnd p = poke rl_end (fromIntegral p)
foreign import ccall "&" rl_end :: Ptr CInt
getPrompt :: IO String
getPrompt = peek rl_prompt >>= peekCString
foreign import ccall "&" rl_prompt :: Ptr (Ptr CChar)
getLibraryVersion :: IO String
getLibraryVersion = peek rl_library_version >>= peekCString
foreign import ccall "&" rl_library_version :: Ptr (Ptr CChar)
getTerminalName :: IO String
getTerminalName = peek rl_terminal_name >>= peekCString
foreign import ccall "&" rl_terminal_name :: Ptr (Ptr CChar)
setReadlineName :: String -> IO ()
setReadlineName name = newCString name >>= poke rl_readline_name
foreign import ccall "&" rl_readline_name :: Ptr (Ptr CChar)
getInStream :: IO Handle
getInStream = peek rl_instream >>= hs_fileno >>= fdToHandle . fromIntegral
foreign import ccall "&" rl_instream :: Ptr (Ptr CFile)
getOutStream :: IO Handle
getOutStream = peek rl_outstream >>= hs_fileno >>= fdToHandle . fromIntegral
foreign import ccall "&" rl_outstream :: Ptr (Ptr CFile)
foreign import ccall unsafe "__hscore_hs_fileno"
hs_fileno :: Ptr CFile -> IO CInt
setStartupHook :: Maybe (IO ()) -> IO ()
setStartupHook hook = setFunPtr rl_startup_hook hook exportHookInt
foreign import ccall "&" rl_startup_hook :: Ptr (FunPtr (IO CInt))
setRedisplayFunction :: Maybe (IO ()) -> IO ()
setRedisplayFunction fun = do
oldPtr <- peek rl_redisplay_function
when (oldPtr /= nullFunPtr && oldPtr /= rl_redisplay) $
freeHaskellFunPtr oldPtr
newPtr <- case fun of
Nothing -> return rl_redisplay
Just f -> exportHookVoid f
poke rl_redisplay_function newPtr
foreign import ccall "&" rl_redisplay_function :: Ptr (FunPtr (IO ()))
foreign import ccall "&" rl_redisplay :: FunPtr (IO ())
exportHookInt :: IO () -> IO (FunPtr (IO CInt))
exportHookInt hook = exportHookIntC (hook >> return 0)
foreign import ccall "wrapper"
exportHookIntC :: IO CInt -> IO (FunPtr (IO CInt))
foreign import ccall "wrapper"
exportHookVoid :: IO () -> IO (FunPtr (IO ()))
setFunPtr_freeIf :: (FunPtr a -> Bool)
-> Ptr (FunPtr a)
-> Maybe b
-> (b -> IO (FunPtr a))
-> IO ()
setFunPtr_freeIf predicate variable newFun makeNewFun = do
oldPtr <- peek variable
when (predicate oldPtr) $ freeHaskellFunPtr oldPtr
newPtr <- case newFun of
Nothing -> return nullFunPtr
Just f -> makeNewFun f
poke variable newPtr
setFunPtr :: Ptr (FunPtr a)
-> Maybe b
-> (b -> IO (FunPtr a))
-> IO ()
setFunPtr = setFunPtr_freeIf (/= nullFunPtr)
type Callback = Int -> Char -> IO Int
type CallbackC = CInt -> CInt -> IO CInt
addDefun :: String -> Callback -> Maybe Char -> IO ()
addDefun name cb key = do
namePtr <- newCString name
cbPtr <- exportCallback cb
rl_add_defun namePtr cbPtr (maybe (1) (fromIntegral . ord) key)
return ()
foreign import ccall unsafe "rl_add_defun"
rl_add_defun :: Ptr CChar -> FunPtr CallbackC -> CInt -> IO CInt
bindKey :: Char -> Callback -> IO ()
bindKey key cb = do
cbPtr <- exportCallback cb
rl_bind_key (fromIntegral (ord key)) cbPtr
return ()
foreign import ccall unsafe "rl_bind_key"
rl_bind_key :: CInt -> FunPtr CallbackC -> IO CInt
parseAndBind :: String -> IO ()
parseAndBind s = do
ok <- withCString s rl_parse_and_bind
unless (ok == 0) $ ioError (userError "Parse error")
foreign import ccall unsafe "rl_parse_and_bind"
rl_parse_and_bind :: Ptr CChar -> IO CInt
readInitFile :: String -> IO ()
readInitFile name = do
ok <- withCString name rl_read_init_file
unless (ok == 0) $ ioError (userError "Can't read file")
foreign import ccall unsafe "rl_read_init_file"
rl_read_init_file :: Ptr CChar -> IO CInt
exportCallback :: Callback -> IO (FunPtr CallbackC)
exportCallback cb =
exportCallbackC $ \n key ->
liftM fromIntegral (cb (fromIntegral n) (chr (fromIntegral key)))
foreign import ccall "wrapper"
exportCallbackC :: CallbackC -> IO (FunPtr CallbackC)
foreign import ccall unsafe "rl_redisplay" redisplay :: IO ()
readKey :: IO Char
readKey = liftM (chr . fromIntegral) rl_read_key
foreign import ccall unsafe "rl_read_key"
rl_read_key :: IO CInt
stuffChar :: Char -> IO Bool
stuffChar key = liftM (/= 0) (rl_stuff_char (fromIntegral (ord key)))
foreign import ccall unsafe "rl_stuff_char"
rl_stuff_char :: CInt -> IO CInt
initialize :: IO ()
initialize = do rl_initialize; return ()
foreign import ccall unsafe "rl_initialize"
rl_initialize :: IO CInt
resetTerminal :: Maybe String -> IO ()
resetTerminal name = do
maybeWith withCString name rl_reset_terminal
return ()
foreign import ccall unsafe "rl_reset_terminal"
rl_reset_terminal :: Ptr CChar -> IO CInt
type Handler = Ptr CChar -> IO ()
callbackHandlerInstall :: String -> (String -> IO ()) -> IO (IO ())
callbackHandlerInstall prompt lhandler = do
lhandlerPtr <- exportHandler $ \linePtr -> peekCString linePtr >>= lhandler
withCString prompt $ \promptPtr -> do
rl_callback_handler_install promptPtr lhandlerPtr
return (do rl_callback_handler_remove; freeHaskellFunPtr lhandlerPtr)
foreign import ccall "wrapper"
exportHandler :: Handler -> IO (FunPtr Handler)
foreign import ccall unsafe "rl_callback_handler_install"
rl_callback_handler_install :: Ptr CChar -> FunPtr Handler -> IO ()
foreign import ccall unsafe "rl_callback_handler_remove"
rl_callback_handler_remove :: IO ()
foreign import ccall "rl_callback_read_char"
callbackReadChar :: IO ()
complete :: Int -> Char -> IO Int
complete n key =
liftM fromIntegral $
rl_complete (fromIntegral n) (fromIntegral (ord key))
foreign import ccall "rl_complete"
rl_complete :: CInt -> CInt -> IO CInt
type Generator = Ptr CChar -> CInt -> IO (Ptr CChar)
singleToWhole :: Generator -> String -> IO [String]
singleToWhole f text =
withCString text $ \textPtr -> let
loop n = do
ptr <- f textPtr n
if ptr == nullPtr
then return []
else do
str <- peekCString ptr
free ptr
rest <- loop (n+1)
return (str:rest)
in loop 0
wholeToSingle :: (String -> IO [String]) -> IO Generator
wholeToSingle f = do
ref <- newIORef []
return $ \textPtr state -> do
when (state == 0) $ peekCString textPtr >>= f >>= writeIORef ref
next <- readIORef ref
case next of
[] -> return nullPtr
x:xs -> do
writeIORef ref xs
newCString x
completionMatches
:: String -> (String -> IO [String]) -> IO (Maybe (String, [String]))
completionMatches text entry =
withCString text $ \textPtr -> do
entryPtr <- wholeToSingle entry >>= exportGenerator
matchesPtr <- rl_completion_matches textPtr entryPtr
freeHaskellFunPtr entryPtr
if matchesPtr == nullPtr then return Nothing else do
matchPtrs <- peekArray0 nullPtr matchesPtr
(text':matches) <- mapM peekCString matchPtrs
mapM_ free matchPtrs
free matchesPtr
return (Just (text', matches))
foreign import ccall "rl_completion_matches"
rl_completion_matches :: Ptr CChar -> FunPtr Generator -> IO (Ptr (Ptr CChar))
filenameCompletionFunction :: String -> IO [String]
filenameCompletionFunction = singleToWhole rl_filename_completion_function
foreign import ccall unsafe "filename_completion_function"
rl_filename_completion_function :: Generator
usernameCompletionFunction :: String -> IO [String]
usernameCompletionFunction = singleToWhole rl_username_completion_function
foreign import ccall unsafe "username_completion_function"
rl_username_completion_function :: Generator
setCompletionEntryFunction :: Maybe (String -> IO [String]) -> IO ()
setCompletionEntryFunction fun =
setFunPtr rl_completion_entry_function fun $ \f ->
wholeToSingle f >>= exportGenerator
foreign import ccall "&" rl_completion_entry_function :: Ptr (FunPtr Generator)
foreign import ccall "wrapper"
exportGenerator :: Generator -> IO (FunPtr Generator)
type Completer = Ptr CChar -> CInt -> CInt -> IO (Ptr (Ptr CChar))
setAttemptedCompletionFunction
:: Maybe (String -> Int -> Int -> IO (Maybe (String, [String]))) -> IO ()
setAttemptedCompletionFunction fun =
setFunPtr rl_attempted_completion_function fun $ \f ->
exportCompleter $ \textPtr start end -> do
text <- peekCString textPtr
found <- f text (fromIntegral start) (fromIntegral end)
case found of
Nothing -> return nullPtr
Just (text', matches) -> do
let matches' = if null matches then [text'] else matches
matchPtrs <- mapM newCString (text':matches')
matchesPtr <- mallocArray (length matchPtrs + 1)
pokeArray0 nullPtr matchesPtr matchPtrs
return matchesPtr
foreign import ccall "&" rl_attempted_completion_function :: Ptr (FunPtr Completer)
foreign import ccall "wrapper"
exportCompleter :: Completer -> IO (FunPtr Completer)
getCompletionQueryItems :: IO Int
getCompletionQueryItems =
liftM fromIntegral (peek rl_completion_query_items)
setCompletionQueryItems :: Int -> IO ()
setCompletionQueryItems items =
poke rl_completion_query_items (fromIntegral items)
foreign import ccall "&" rl_completion_query_items :: Ptr CInt
getBasicWordBreakCharacters :: IO String
getBasicWordBreakCharacters = getCharacters rl_basic_word_break_characters
setBasicWordBreakCharacters :: String -> IO ()
setBasicWordBreakCharacters =
setCharacters_freeIf
(/= orig_rl_basic_word_break_characters)
rl_basic_word_break_characters
foreign import ccall "&" rl_basic_word_break_characters :: Ptr (Ptr CChar)
orig_rl_basic_word_break_characters :: Ptr CChar
orig_rl_basic_word_break_characters = unsafePerformIO $
peek rl_basic_word_break_characters
getCompleterWordBreakCharacters :: IO String
getCompleterWordBreakCharacters = getCharacters rl_completer_word_break_characters
setCompleterWordBreakCharacters :: String -> IO ()
setCompleterWordBreakCharacters =
setCharacters_freeIf
(\oldPtr -> oldPtr /= nullPtr &&
oldPtr /= orig_rl_basic_word_break_characters)
rl_completer_word_break_characters
foreign import ccall "&" rl_completer_word_break_characters :: Ptr (Ptr CChar)
getCompleterQuoteCharacters :: IO String
getCompleterQuoteCharacters = getCharacters rl_completer_quote_characters
setCompleterQuoteCharacters :: String -> IO ()
setCompleterQuoteCharacters cs = do
oldPtr <- peek rl_completer_quote_characters
when (oldPtr /= nullPtr) $ free oldPtr
newPtr <- if null cs
then return nullPtr
else do
ptr <- mallocArray (length cs + 1)
pokeArray0 0 ptr (map castCharToCChar cs)
return ptr
poke rl_completer_quote_characters newPtr
foreign import ccall "&" rl_completer_quote_characters :: Ptr (Ptr CChar)
getSpecialPrefixes :: IO String
getSpecialPrefixes = getCharacters rl_special_prefixes
setSpecialPrefixes :: String -> IO ()
setSpecialPrefixes = setCharacters rl_special_prefixes
foreign import ccall "&" rl_special_prefixes :: Ptr (Ptr CChar)
getCompletionAppendCharacter :: IO (Maybe Char)
getCompletionAppendCharacter = do
ch <- peek rl_completion_append_character
return $ if ch == 0 then Nothing else Just (chr (fromIntegral ch))
setCompletionAppendCharacter :: Maybe Char -> IO ()
setCompletionAppendCharacter ch =
poke rl_completion_append_character (maybe 0 (fromIntegral . ord) ch)
foreign import ccall "&" rl_completion_append_character :: Ptr CInt
setInhibitCompletion :: Bool -> IO ()
setInhibitCompletion inh = poke rl_inhibit_completion (if inh then 1 else 0)
getInhibitCompletion :: IO Bool
getInhibitCompletion = liftM (/= 0) (peek rl_inhibit_completion)
foreign import ccall "&" rl_attempted_completion_over :: Ptr CInt
getAttemptedCompletionOver :: IO Bool
getAttemptedCompletionOver =
liftM (/=0) (peek rl_attempted_completion_over)
setAttemptedCompletionOver :: Bool -> IO ()
setAttemptedCompletionOver over =
poke rl_attempted_completion_over (if over then 1 else 0)
foreign import ccall "&" rl_inhibit_completion :: Ptr CInt
setCharacters_freeIf :: (Ptr CChar -> Bool) -> Ptr (Ptr CChar) -> String -> IO ()
setCharacters_freeIf predicate variable chars = do
oldPtr <- peek variable
when (predicate oldPtr) $ free oldPtr
newPtr <- mallocArray (length chars + 1)
pokeArray0 0 newPtr (map castCharToCChar chars)
poke variable newPtr
setCharacters :: Ptr (Ptr CChar) -> String -> IO ()
setCharacters = setCharacters_freeIf (/= nullPtr)
getCharacters :: Ptr (Ptr CChar) -> IO String
getCharacters variable = do
ptr <- peek variable
if ptr == nullPtr then return "" else do
cs <- peekArray0 0 ptr
return (map castCCharToChar cs)