repline: Haskeline wrapper for GHCi-like REPL interfaces.

[ library, mit, user-interfaces ] [ Propose Tags ]

Haskeline wrapper for GHCi-like REPL interfaces. Composable with normal mtl transformers.


[Skip to Readme]

Modules

[Index]

Downloads

Note: This package has metadata revisions in the cabal description newer than included in the tarball. To unpack the package including the revisions, use 'cabal get'.

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1.0.0, 0.1.2.0, 0.1.3.0, 0.1.4.0, 0.1.5.0, 0.1.6.0, 0.1.7.0, 0.2.0.0, 0.2.1.0, 0.2.2.0, 0.3.0.0, 0.4.0.0, 0.4.2.0
Dependencies base (>=4.6 && <4.10), containers (>=0.5 && <0.6), haskeline (>=0.7 && <0.8), mtl (>=2.2 && <2.3), process (>=1.2.0.0), repline [details]
License MIT
Copyright 2014-2016 Stephen Diehl
Author Stephen Diehl
Maintainer stephen.m.diehl@gmail.com
Revised Revision 1 made by phadej at 2020-01-24T09:32:50Z
Category User Interfaces
Bug tracker https://github.com/sdiehl/repline/issues
Source repo head: git clone git@github.com:sdiehl/repline.git
Uploaded by sdiehl at 2016-03-05T22:48:02Z
Distributions Arch:0.4.2.0, Debian:0.2.2.0, Fedora:0.4.2.0, LTSHaskell:0.4.2.0, NixOS:0.4.2.0, Stackage:0.4.2.0
Reverse Dependencies 5 direct, 60 indirect [details]
Executables Example, Simple
Downloads 19358 total (123 in the last 30 days)
Rating 2.25 (votes: 2) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2016-03-05 [all 1 reports]

Readme for repline-0.1.5.0

[back to package description]

Repline

Build Status Hackage

Slightly higher level wrapper for creating GHCi-like REPL monads that are composable with normal MTL transformers. Mostly exists because I got tired of implementing the same interface for simple shells over and over and decided to canonize the giant pile of hacks that I use to make Haskeline work.

Usage

type Repl a = HaskelineT IO a

-- Evaluation : handle each line user inputs
cmd :: String -> Repl ()
cmd input = liftIO $ print input

-- Tab Completion: return a completion for partial words entered
completer :: Monad m => WordCompleter m
completer n = do
  let names = ["kirk", "spock", "mccoy"]
  return $ filter (isPrefixOf n) names

-- Commands
help :: [String] -> Repl ()
help args = liftIO $ print $ "Help: " ++ show args

say :: [String] -> Repl ()
say args = do
  _ <- liftIO $ system $ "cowsay" ++ " " ++ (unwords args)
  return ()

options :: [(String, [String] -> Repl ())]
options = [
    ("help", help)  -- :help
  , ("say", say)    -- :say
  ]

ini :: Repl ()
ini = liftIO $ putStrLn "Welcome!"

repl :: IO ()
repl = evalRepl ">>> " cmd options (Word completer) ini

Trying it out:

$ runhaskell Simple.hs
# Or if in a sandbox: cabal exec runhaskell Simple.hs
Welcome!
>>> <TAB>
kirk spock mccoy

>>> k<TAB>
kirk

>>> spam
"spam"

>>> :say Hello Haskell
 _______________ 
< Hello Haskell >
 --------------- 
        \   ^__^
         \  (oo)\_______
            (__)\       )\/\
                ||----w |
                ||     ||

Stateful Tab Completion

Quite often tab completion is dependent on the internal state of the Repl so we'd like to query state of the interpreter for tab completions based on actions performed themselves within the Repl, this is modeleted naturally as a monad transformer stack with StateT on top of HaskelineT.

type IState = Set.Set String
type Repl a = HaskelineT (StateT IState IO) a

-- Evaluation
cmd :: String -> Repl ()
cmd input = modify $ \s -> Set.insert input s

-- Completion
comp :: (Monad m, MonadState IState m) => WordCompleter m
comp n = do
  ns <- get
  return  $ filter (isPrefixOf n) (Set.toList ns)

-- Commands
help :: [String] -> Repl ()
help args = liftIO $ print $ "Help!" ++ show args

puts :: [String] -> Repl ()
puts args = modify $ \s -> Set.union s (Set.fromList args)

opts :: [(String, [String] -> Repl ())]
opts = [
    ("help", help) -- :help
  , ("puts", puts) -- :puts
  ]

ini :: Repl ()
ini = return ()

-- Tab completion inside of StateT
repl :: IO ()
repl = flip evalStateT Set.empty
     $ evalRepl ">>> " cmd opts (Word comp) init

Prefix Completion

Just as GHCi will provide different tab completion for kind-level vs type-level symbols based on which prefix the user has entered, we can also set up a provide this as a first-level construct using a Prefix tab completer which takes care of the string matching behind the API.

type Repl a = HaskelineT IO a

-- Evaluation
cmd :: String -> Repl ()
cmd input = liftIO $ print input

-- Prefix tab completeter
defaultMatcher :: MonadIO m => [(String, CompletionFunc m)]
defaultMatcher = [
    (":file"    , fileCompleter)
  , (":holiday" , listCompleter ["christmas", "thanksgiving", "festivus"])
  ]

-- Default tab completer
byWord :: Monad m => WordCompleter m
byWord n = do
  let names = ["picard", "riker", "data", ":file", ":holiday"]
  return $ filter (isPrefixOf n) names

files :: [String] -> Repl ()
files args = liftIO $ do
  contents <- readFile (unwords args)
  putStrLn contents

holidays :: [String] -> Repl ()
holidays [] = liftIO $ putStrLn "Enter a holiday."
holidays xs = liftIO $ do
  putStrLn $ "Happy " ++ unwords xs ++ "!"

opts :: [(String, [String] -> Repl ())]
opts = [
    ("file", files)
  , ("holiday", holidays)
  ]

init :: Repl ()
init = return ()

repl :: IO ()
repl = evalRepl ">> " cmd opts (Prefix (wordCompleter byWord) defaultMatcher) init

Trying it out:

$ runhaskell Main.hs
>>> :file <TAB>
sample1.txt sample2.txt

>>> :file sample1.txt

>>> :holiday <TAB>
christmas thanksgiving festivus

Installation

$ cabal install repline

License

Copyright (c) 2014, Stephen Diehl Released under the MIT License