zipedit-0.2.3: Create simple list editor interfaces

Portabilityunportable
Stabilityunstable
Maintainer<byorgey@gmail.com>

System.Console.ZipEdit

Contents

Description

A library for creating simple interactive list editors, using a zipper to allow the user to navigate forward and back within the list and edit the list elements.

Synopsis

Example usage

Here is a simple example of using the ZipEdit library:

 module Main where

 import System.Console.ZipEdit

 myEd = EC { display = const ""
           , prompt  = \n -> maybe "" show n ++ "? "
           , actions = [ ('+', Modify (+1) ?? "Increment the current number.")
                       , ('i', InsFwd "Value to insert: " read ?? "Insert a number.")
                       ]
                       ++ stdActions
           }

 main = do
   mxs <- edit myEd [1..10]
   case mxs of
     Nothing -> putStrLn "Canceled."
     Just xs -> putStrLn ("Final edited version: " ++ show xs)

A session with this program might look something like this:

 $ test

 1? k

 1? j

 2? j

 3? +

 4? +

 5? j

 4? i
 Value to insert: 98

 98? d
 Final edited version: [1,2,5,4,98,5,6,7,8,9,10]

For more sophisticated examples, see planethaskell.hs and gmane.hs in http://code.haskell.org/~byorgey/code/hwn/utils.

Interface

data Action a Source

Actions that can be taken by an editor in response to user input.

Constructors

Fwd

move forward one item.

Back

move back one item.

Delete

delete the current item.

Modify (a -> a)

modify the current item by applying the given function.

ModifyIO (a -> IO a)

modify the current item by applying the given function, which gives its result in the IO monad.

ModifyFwd ([a] -> [a])

modify items following the current item by applying the given function.

ModifyBack ([a] -> [a])

modify items before the current item by applying the given function.

ModifyWInp String (String -> a -> a)

Using the given string as a prompt, obtain a line of user input, and apply the given function to the user input to obtain a function for modifying the current item.

ModifyWEditor (a -> String) (String -> a -> a)

Run the first function on the current item to produce a string, and open an editor (using the $EDITOR environment variable) on that string. After the user is done editing, pass the resulting string to the second function to obtain a function for modifying the current element.

InsFwd String (String -> a)

Using the given string as a prompt, obtain a line of user input, and apply the given function to the user input to obtain a new item, which should be inserted forward of the current item. The inserted item becomes the new current item.

InsBack String (String -> a)

Similar to InsFwd, except that the new item is inserted before the old current item.

Output (a -> String)

output a string which is a function of the current item.

Cancel

cancel the editing session.

Done

complete the editing session.

Seq [Action a]

perform a sequence of actions.

Help String (Action a)

an action annotated with a help string.

stdActions :: [(Char, Action a)]Source

Some standard actions which can be used in constructing editor configurations. The actions are: j - Fwd, k - Back, x - Delete, q - Cancel, d - Done.

(??) :: Action a -> String -> Action aSource

Annotate a command with a help string.

data EditorConf a Source

A configuration record determining the behavior of the editor.

Constructors

EC 

Fields

display :: Maybe a -> String

How to display the current item.

prompt :: Maybe a -> String

How to display a prompt to the user, based on the currently focused item.

actions :: [(Char, Action a)]

A list specifying the actions to take in response to user inputs.

Instances

MonadReader (EditorConf e) (Editor e) 

editSource

Arguments

:: EditorConf a

editor configuration

-> [a]

the list to edit

-> IO (Maybe [a]) 

Run the given editor on the given list, returning Nothing if the user canceled the editing process, or Just l if the editing process completed successfully, where l is the final state of the list being edited.

data LCont a Source

A continuation which can compute more of the list, along with (maybe) another continuation.

Constructors

LC (IO ([a], Maybe (LCont a))) 

editWCont :: EditorConf a -> [a] -> IO ([a], Maybe (LCont a)) -> IO (Maybe [a])Source

Like edit, but with an additional parameter for a continuation | which can be run to compute additional list elements and | (optionally) another continuation.