isocline-1.0.9: A portable alternative to GNU Readline
Copyright(c) 2021 Daan Leijen
LicenseMIT
Maintainerdaan@effp.org
StabilityExperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

System.Console.Isocline

Description

A Haskell wrapper around the Isocline C library which can provide an alternative to GNU Readline. (The Isocline library is included whole and there are no runtime dependencies).

Isocline works across Unix, Windows, and macOS, and relies on a minimal subset of ANSI escape sequences. It has a good multi-line editing mode (use shift/ctrl-enter) which is nice for inputting small functions etc. Other features include support for colors, history, completion, unicode, undo/redo, incremental history search, inline hints, brace matching, syntax highlighting, rich text using bbcode formatting, etc.

Minimal example with history:

import System.Console.Isocline

main :: IO ()
main  = do putStrLn "Welcome"
           setHistory "history.txt" 200
           input <- readline "myprompt"     -- full prompt becomes "myprompt> "
           putFmtLn ("[gray]You wrote:[/gray]\n" ++ input)

Or using custom completions with an interactive loop:

import System.Console.Isocline
import Data.Char( toLower )

main :: IO ()
main 
  = do styleDef "ic-prompt" "ansi-maroon"
       setHistory "history.txt" 200
       enableAutoTab True
       interaction

interaction :: IO ()
interaction 
  = do s <- readlineEx "hαskell" (Just completer) Nothing 
       putStrLn ("You wrote:\n" ++ s)
       if (s == "" || s == "exit") then return () else interaction
                     
completer :: CompletionEnv -> String -> IO () 
completer cenv input
  = do completeFileName cenv input Nothing [".","/usr/local"] [".hs"]  -- use [] for any extension
       completeWord cenv input Nothing wcompleter

wcompleter :: String -> [Completion]
wcompleter input
  = completionsFor (map toLower input) 
      ["print","println","prints","printsln","prompt"]      

See a larger example with syntax highlighting and more extenstive custom completion in the Github repository.

Enjoy, -- Daan

Synopsis

Readline

readline :: String -> IO String Source #

readline prompt: Read (multi-line) input from the user with rich editing abilities. Takes the prompt text as an argument. The full prompt is the combination of the given prompt and the prompt marker ("> " by default) . See also readlineEx, readlineMaybe, enableMultiline, and setPromptMarker.

readlineEx :: String -> Maybe (CompletionEnv -> String -> IO ()) -> Maybe (String -> Fmt) -> IO String Source #

readlineEx prompt mbCompleter mbHighlighter: as readline but uses the given mbCompleter function to complete words on tab (instead of the default completer). and the given mbHighlighter function to highlight the input (instead of the default highlighter). See also readline and readlineExMaybe.

History

setHistory :: FilePath -> Int -> IO () Source #

setHistory filename maxEntries: Enable history that is persisted to the given file path with a given maximum number of entries. Use -1 for the default entries (200). See also enableHistoryDuplicates.

historyClear :: IO () Source #

Clear the history.

historyRemoveLast :: IO () Source #

Isocline automatically adds input of more than 1 character to the history. This command removes the last entry.

historyAdd :: String -> IO () Source #

historyAdd entry: add entry to the history.

Completion

data CompletionEnv Source #

Abstract list of current completions.

completeFileName :: CompletionEnv -> String -> Maybe Char -> [FilePath] -> [String] -> IO () Source #

completeFileName compls input dirSep roots extensions: Complete filenames with the given input, a possible directory separator dirSep, a list of root folders roots to search from (by default ["."]), and a list of extensions to match (use [] to match any extension). The directory separator is used when completing directory names. For example, using g '/' as a directory separator, we get:

/ho         --> /home/
/home/.ba   --> /home/.bashrc

completeWord :: CompletionEnv -> String -> Maybe (Char -> Bool) -> (String -> [Completion]) -> IO () Source #

completeWord compl input isWordChar completer: Complete a word (or token) and calls the user completer function with just the current word (instead of the whole input) Takes the CompletionEnv environment compl, the current input, an possible isWordChar function, and a user defined completer function that is called with adjusted input which is limited to the word just before the cursor. Pass Nothing to isWordChar for the default not . separator where separator = c -> c elem " \t\r\n,.;:/\\(){}[]".

completeQuotedWord :: CompletionEnv -> String -> Maybe (Char -> Bool) -> (String -> [Completion]) -> IO () Source #

completeQuotedWord compl input isWordChar completer: Complete a word taking care of automatically quoting and escaping characters. Takes the CompletionEnv environment compl, the current input, and a user defined completer function that is called with adjusted input which is unquoted, unescaped, and limited to the word just before the cursor. For example, with a hello world completion, we get:

hel        -->  hello\ world
hello\ w   -->  hello\ world
hello w    -->                   # no completion, the word is just 'w'>
"hel       -->  "hello world" 
"hello w   -->  "hello world"

The call (completeWord compl prefx isWordChar fun) is a short hand for (completeQuotedWord compl prefx isWordChar '\\' "'\"" fun). Pass Nothing to isWordChar for the default not . separator where separator = c -> c elem " \t\r\n,.;:/\\(){}[]".

completeQuotedWordEx :: CompletionEnv -> String -> Maybe (Char -> Bool) -> Maybe Char -> String -> (String -> [Completion]) -> IO () Source #

completeQuotedWordEx compl input isWordChar escapeChar quoteChars completer: Complete a word taking care of automatically quoting and escaping characters. Takes the CompletionEnv environment compl, the current input, and a user defined completer function that is called with adjusted input which is unquoted, unescaped, and limited to the word just before the cursor. Unlike completeQuotedWord, this function can specify the escape character and the quote characters. See also completeWord.

data Completion Source #

A completion entry

Constructors

Completion 

Fields

Instances

Instances details
Eq Completion Source # 
Instance details

Defined in System.Console.Isocline

Show Completion Source # 
Instance details

Defined in System.Console.Isocline

completion :: String -> Completion Source #

Create a completion with just a replacement

isPrefix :: String -> Completion -> Bool Source #

Is the given input a prefix of the completion replacement?

completionsFor :: String -> [String] -> [Completion] Source #

completionsFor input replacements: Filter those replacements that start with the given input, and return them as completions.

wordCompleter :: [String] -> CompletionEnv -> String -> IO () Source #

Convenience: creates a completer function directly from a list of candidate completion strings. Uses completionsFor to filter the input and completeWord to find the word boundary. For example: readlineEx "myprompt" (Just (wordCompleter completer)) Nothing.

Syntax Highlighting

highlightFmt :: (String -> Fmt) -> HighlightEnv -> String -> IO () Source #

Use an rich text formatted highlighter from inside a highlighter callback.

Rich text

type Style = String Source #

A style for formatted strings (Fmt). For example, a style can be "red" or "b #7B3050". See the full list of valid properties

type Fmt = String Source #

A string with bbcode formatting. For example "[red]this is red[/]".n

style :: Style -> Fmt -> Fmt Source #

Style a string, e.g. style "b red" "bold and red" (which is equivalent to "[b red]bold and red[/]"). See the repo for a full description of all styles.

plain :: String -> Fmt Source #

Escape a string so no tags are interpreted as formatting.

pre :: Style -> String -> Fmt Source #

Style a string that is printed as is without interpreting markup inside it (using plain).

putFmt :: Fmt -> IO () Source #

Output rich formatted text containing bbcode. For example: putFmt "[b]bold [red]and red[/][/]" All unclosed tags are automatically closed (but see also styleOpen). See the repo for more information about formatted output.

putFmtLn :: Fmt -> IO () Source #

Output rich formatted text containing bbcode's ending with a newline.

styleDef :: String -> Style -> IO () Source #

Define (or redefine) a style. For example styleDef "warning" "crimon underline", and then use it as putFmtLn "[warning]this is a warning[/]". This can be very useful for theming your application with semantic styles. See also formatted output

styleOpen :: Style -> IO () Source #

Open a style that is active for all putFmt and putFmtLn until it is closed again (styleClose).

styleClose :: IO () Source #

Close a previously opened style.

withStyle :: Style -> IO a -> IO a Source #

Use a style over an action.

Configuration

setPromptMarker :: String -> String -> IO () Source #

setPromptMarker marker multiline_marker: Set the prompt marker (by default "> "). and a possible different continuation prompt marker multiline_marker for multiline input (defaults to marker).

enableAutoTab :: Bool -> IO Bool Source #

Disable or enable automatic tab completion after a completion to expand as far as possible if the completions are unique. (disabled by default). Returns the previous value.

enableColor :: Bool -> IO Bool Source #

Disable or enable color output (enabled by default). Returns the previous value.

enableBeep :: Bool -> IO Bool Source #

Disable or enable sound (enabled by default). | A beep is used when tab cannot find any completion for example. Returns the previous value.

enableMultiline :: Bool -> IO Bool Source #

Disable or enable multi-line input (enabled by default). Returns the previous value.

enableHistoryDuplicates :: Bool -> IO Bool Source #

Disable or enable duplicate entries in the history (duplicate entries are not allowed by default). Returns the previous value.

enableCompletionPreview :: Bool -> IO Bool Source #

Disable or enable preview of a completion selection (enabled by default) Returns the previous value.

enableMultilineIndent :: Bool -> IO Bool Source #

Disable or enable automatic indentation to line up the multiline prompt marker with the initial prompt marker (enabled by default). Returns the previous value. See also setPromptMarker.

enableHighlight :: Bool -> IO Bool Source #

Disable or enable syntax highlighting (enabled by default). Returns the previous value.

enableInlineHelp :: Bool -> IO Bool Source #

Disable or enable short inline help message (for history search etc.) (enabled by default). Pressing F1 always shows full help regardless of this setting. Returns the previous value.

enableHint :: Bool -> IO Bool Source #

Disable or enable automatic inline hinting (enabled by default) Returns the previous value.

setHintDelay :: Int -> IO Int Source #

Set the delay in milliseconds before a hint is displayed (500ms by default) See also enableHint

enableBraceMatching :: Bool -> IO Bool Source #

Disable or enable brace matching (enabled by default) Returns the previous value.

enableBraceInsertion :: Bool -> IO Bool Source #

Disable or enable automatic close brace insertion (enabled by default) Returns the previous value.

setMatchingBraces :: String -> IO () Source #

Set pairs of matching braces, by default "(){}[]".

setInsertionBraces :: String -> IO () Source #

Set pairs of auto insertion braces, by default "(){}[]\"\"''".

Advanced

setDefaultCompleter :: (CompletionEnv -> String -> IO ()) -> IO () Source #

setDefaultCompleter completer: Set a new tab-completion function completer that is called by Isocline automatically. The callback is called with a CompletionEnv context and the current user input up to the cursor. By default the completeFileName completer is used. This overwrites any previously set completer.

addCompletion :: CompletionEnv -> Completion -> IO Bool Source #

addCompletion compl completion: Inside a completer callback, add a new completion. If addCompletion returns True keep adding completions, but if it returns False an effort should be made to return from the completer callback without adding more completions.

addCompletionPrim :: CompletionEnv -> Completion -> Int -> Int -> IO Bool Source #

addCompletionPrim compl completion deleteBefore deleteAfter: Primitive add completion, use with care and call only directly inside a completer callback. If addCompletion returns True keep adding completions, but if it returns False an effort should be made to return from the completer callback without adding more completions.

addCompletions :: CompletionEnv -> [Completion] -> IO Bool Source #

addCompletions compl completions: add multiple completions at once. If addCompletions returns True keep adding completions, but if it returns False an effort should be made to return from the completer callback without adding more completions.

completeWordPrim :: CompletionEnv -> String -> Maybe (Char -> Bool) -> (CompletionEnv -> String -> IO ()) -> IO () Source #

completeWord compl input isWordChar completer: Complete a word,token and calls the user completer function with just the current word (instead of the whole input) Takes the CompletionEnv environment compl, the current input, an possible isWordChar function, and a user defined completer function that is called with adjusted input which is limited to the word just before the cursor. Pass Nothing to isWordChar for the default not . separator where separator = c -> c elem " \t\r\n,.;:/\\(){}[]".

completeQuotedWordPrim :: CompletionEnv -> String -> Maybe (Char -> Bool) -> (CompletionEnv -> String -> IO ()) -> IO () Source #

completeWordPrim compl input isWordChar completer: Complete a word taking care of automatically quoting and escaping characters. Takes the CompletionEnv environment compl, the current input, and a user defined completer function that is called with adjusted input which is unquoted, unescaped, and limited to the word just before the cursor. For example, with a hello world completion, we get:

hel        -->  hello\ world
hello\ w   -->  hello\ world
hello w    -->                   # no completion, the word is just 'w'>
"hel       -->  "hello world" 
"hello w   -->  "hello world"

The call (completeWordPrim compl prefx isWordChar fun) is a short hand for (completeQuotedWordPrim compl prefx isWordChar '\\' "'\"" fun). Pass Nothing to isWordChar for the default not . separator where separator = c -> c elem " \t\r\n,.;:/\\(){}[]".

completeQuotedWordPrimEx :: CompletionEnv -> String -> Maybe (Char -> Bool) -> Maybe Char -> String -> (CompletionEnv -> String -> IO ()) -> IO () Source #

completeQuotedWordPrim compl input isWordChar escapeChar quoteChars completer: Complete a word taking care of automatically quoting and escaping characters. Takes the CompletionEnv environment compl, the current input, and a user defined completer function that is called with adjusted input which is unquoted, unescaped, and limited to the word just before the cursor. Unlike completeWord, this function takes an explicit function to determine word characters, the escape character, and a string of quote characters. See also completeWord.

readlineMaybe :: String -> IO (Maybe String) Source #

As readline but returns Nothing on end-of-file or other errors (ctrl-C/ctrl-D).

readlineExMaybe :: String -> Maybe (CompletionEnv -> String -> IO ()) -> Maybe (String -> Fmt) -> IO (Maybe String) Source #

As readlineEx but returns Nothing on end-of-file or other errors (ctrl-C/ctrl-D). See also readlineMaybe.

readlinePrim :: String -> Maybe (CompletionEnv -> String -> IO ()) -> Maybe (HighlightEnv -> String -> IO ()) -> IO String Source #

readlinePrim prompt mbCompleter mbHighlighter: as readline but uses the given mbCompleter function to complete words on tab (instead of the default completer). and the given mbHighlighter function to highlight the input (instead of the default highlighter). See also readlineEx and readlinePrimMaybe.

readlinePrimMaybe :: String -> Maybe (CompletionEnv -> String -> IO ()) -> Maybe (HighlightEnv -> String -> IO ()) -> IO (Maybe String) Source #

As readlinePrim but returns Nothing on end-of-file or other errors (ctrl-C/ctrl-D). See also readlineMaybe.

getPromptMarker :: IO String Source #

Get the current prompt marker.

getContinuationPromptMarker :: IO String Source #

Get the current prompt continuation marker for multi-line input.

stopCompleting :: CompletionEnv -> IO Bool Source #

If this returns True an effort should be made to stop completing and return from the callback.

hasCompletions :: CompletionEnv -> IO Bool Source #

Have any completions be generated so far?

asyncStop :: IO Bool Source #

Thread safe call to asynchronously send a stop event to a readline which behaves as if the user pressed ctrl-C, which will return with Nothing (or ""). Returns True if the event was successfully delivered.

Low-level highlighting

data HighlightEnv Source #

Abstract highlight environment

setDefaultHighlighter :: (HighlightEnv -> String -> IO ()) -> IO () Source #

Set a syntax highlighter. There can only be one highlight function, setting it again disables the previous one.

setDefaultFmtHighlighter :: (String -> Fmt) -> IO () Source #

Set a syntax highlighter that uses a pure function that returns a bbcode formatted string (using style, plain etc). See highlightFmt for more information. There can only be one highlight function, setting it again disables the previous one.

Low-level Terminal

termInit :: IO () Source #

Initialize the terminal for the term functions. Does nothing on most platforms but on windows enables UTF8 output and potentially enables virtual terminal processing. See also withTerm.

termDone :: IO () Source #

Done using term functions. See also withTerm.

withTerm :: IO a -> IO a Source #

Use the term functions (brackets termInit and termDone).

termFlush :: IO () Source #

Flush terminal output. Happens automatically on newline ('\n') characters as well.

termWrite :: String -> IO () Source #

Write output to the terminal where ANSI CSI sequences are handled portably across platforms (including Windows).

termWriteLn :: String -> IO () Source #

Write output with a ending newline to the terminal where ANSI CSI sequences are handled portably across platforms (including Windows).

termColor :: Int -> IO () Source #

Set the terminal text color as a hexadecimal number 0xrrggbb. The color is auto adjusted for terminals with less colors.

termBgColor :: Int -> IO () Source #

Set the terminal text background color. The color is auto adjusted for terminals with less colors.

termColorAnsi :: Int -> IO () Source #

Set the terminal text color as an ANSI palette color (between 0 and 255). Use 256 for the default. The color is auto adjusted for terminals with less colors.

termBgColorAnsi :: Int -> IO () Source #

Set the terminal text background color as an ANSI palette color (between 0 and 255). Use 256 for the default. The color is auto adjusted for terminals with less colors.

termUnderline :: Bool -> IO () Source #

Set the terminal text underline mode.

termReverse :: Bool -> IO () Source #

Set the terminal text reverse video mode.

termReset :: IO () Source #

Reset the terminal text mode to defaults