geni-gui-0.25.1: GenI graphical user interface

Safe HaskellNone
LanguageHaskell2010

NLP.GenI.GuiHelper

Synopsis

Documentation

pauseOnLexGui Source #

Arguments

:: Params 
-> Window a

parent window

-> [LexEntry]

lexically selected items (before anchoring)

-> [TagElem]

lexically selected items

-> GeniWarnings

lexical selection warnings

-> Maybe ([TagElem] -> IO ())

run when “begin” is clicked

-> GvIO () (GvItem Bool TagElem) 

pauseOnLexGui allows the user to see lexical selection only and either dump it to file or read replace it by the contents of some other file

candidateGui :: Params -> Window a -> [TagElem] -> GeniWarnings -> GvIO () (GvItem Bool TagElem) Source #

candidateGui displays the lexically selected items, grouped by the semantics they subsume.

polarityGui Source #

Arguments

:: Window a

parent window

-> [AutDebug]

intermediary automata

-> PolAut

final automaton

-> GvIO () (GvItem () PolAut) 

A browser to see the automata constructed during the polarity optimisation step.

class XMGDerivation a where Source #

Any data structure which has corresponds to a TAG tree and which has some notion of derivation

Minimal complete definition

getSourceTrees

Methods

getSourceTrees :: a -> [Text] Source #

toSentence :: TagElem -> Text Source #

toSentence almost displays a TagElem as a sentence, but only good enough for debugging needs. The problem is that each leaf may be an atomic disjunction. Our solution is just to display each choice and use some delimiter to seperate them. We also do not do any morphological processing.

squishLeaf :: (a, ([Text], b)) -> Text Source #

tagViewerGui Source #

Arguments

:: (GraphvizShow (GvItem Bool t), XMGDerivation t) 
=> Params 
-> Window a

parent

-> Text

tooltip

-> FilePath

cache directory for graphviz

-> [GvItem Bool t]

items

-> GvIO () (GvItem Bool t) 

Variant of graphvizGui with a toggle to view feature structures

viewTagWidgets Source #

Arguments

:: XMGDerivation t 
=> Window a

parent window

-> GraphvizGuiRef st (GvItem Bool t) 
-> Params 
-> IO Layout 

Calls Yannick Parmentier's handy visualisation tool ViewTAG.

type DebuggerItemBar st flg itm Source #

Arguments

 = Panel ()

parent panel

-> GraphvizGuiRef st (GvItem flg itm)

gv ref to use

-> GvUpdater

onUpdate

-> IO (Layout, GvUpdater) 

data GraphvizShow (GvItem flg itm) => Debugger st flg itm Source #

Constructors

Debugger 

Fields

debuggerPanel Source #

Arguments

:: GraphvizShow (GvItem flg itm) 
=> Debugger st flg itm 
-> ProgState 
-> Window a

parent window

-> Input 
-> Maybe Params

test case parameters

-> IO Layout 

A generic graphical debugger widget for GenI, including

  • item viewer which allows the user to select one of the items in the builder state.
  • item bar which provides some options on how to view the currently selected item, for example, if you want to display the features or not.
  • A dashboard which lets the user do things like ``go ahead 6 steps''.

Besides the Builder, there are two functions you need to pass in make this work:

  1. a stateToGv which converts the builder state into a list of items and labels the way graphvizGui likes it
  2. an 'item bar' function which lets you control what bits you display of a selected item (for example, if you want a detailed view or not) the item bar should return a layout

Note that we don't constrain the type of item returned by the builder to be the same as the type handled by your gui: that's quite normal because you might want to decorate the type with some other information

data GraphvizGuiSt st a Source #

Constructors

GvSt 

Fields

type GraphvizGuiRef st a = IORef (GraphvizGuiSt st a) Source #

This provides a mechanism for communicating with the GUI. The basic idea:

  1. you create a GvRef with newGvRef
  2. you call graphvizGui and get back an updater function
  3. whenever you want to modify something, you use setGvWhatever and call the updater function
  4. if you want to react to the selection being changed, you should set gvhandler

newGvRef :: st -> Text -> IO (GraphvizGuiRef st a) Source #

modifyGvItems :: GraphvizGuiRef st a -> (a -> a) -> IO () Source #

setGvDrawables :: GraphvizGuiRef st (GvItem f a) -> [GvItem f a] -> IO () Source #

gvOnSelect :: IO () -> (a -> IO ()) -> GraphvizGuiSt st (GvItem f a) -> IO () Source #

Helper function for making selection handlers (see addGvHandler) Note that this was designed for cases where the contents is a Maybe

setGvHandler :: GraphvizGuiRef st a -> Maybe (GraphvizGuiSt st a -> IO ()) -> IO () Source #

addGvHandler :: GraphvizGuiRef st a -> (GraphvizGuiSt st a -> IO ()) -> IO () Source #

add a selection handler - if there already is a handler this handler will be called before the new one

type GvUpdater = IO () Source #

graphvizGui :: GraphvizShow d => Window a -> String -> GraphvizGuiRef st d -> GvIO st d Source #

graphvizGui f glab cachedir gvRef is a general-purpose GUI for displaying a list of items graphically via AT&T's excellent Graphviz utility. We have a list box where we display all the labels the user provided. If the user selects an entry from this box, then the item corresponding to that label will be displayed.

This returns a layout (wxhaskell container) and a function that you're expected to call whever something changes that would require the GUI to refresh itself (for example, you create a new chart item)

  • f - (parent window) the GUI is provided as a panel within the parent. Note: we use window in the WxWidget's sense, meaning it could be anything as simple as a another panel, or a notebook tab.
  • glab - (gui labels) a tuple of strings (tooltip, next button text)
  • cachedir - the cache subdirectory. We intialise this by creating a cache directory for images which will be generated from the results
  • gvRef - see above

scrolledBitmap :: Window a -> IO (VarBitmap, ScrolledWindow ()) Source #

Bitmap with a scrollbar

onPaint :: VarBitmap -> DC a -> b -> IO () Source #

createAndOpenImage Source #

Arguments

:: GraphvizShow b 
=> FilePath

cache directory

-> Window a

parent window

-> GraphvizGuiRef st b 
-> OpenImageFn 
-> IO () 

createAndOpenImage attempts to draw an image (or retrieve it from cache) and opens it if we succeed. Otherwise, it does nothing at all; the creation function will display an error message if it fails.

createImage Source #

Arguments

:: GraphvizShow b 
=> FilePath

cache directory

-> Window a

parent window

-> GraphvizGuiRef st b

stuff to display

-> IO GraphvizStatus 

Creates a graphical visualisation for anything which can be displayed by graphviz.

initCacheDir :: String -> IO () Source #

Directory to dump image files in so that we can avoid regenerating them. If the directory already exists, we can just delete all the files in it.

setSelection Source #

Arguments

:: (Selecting w, Selection w) 
=> w

widget

-> [a]

items

-> Int

initial selection

-> (a -> IO ())

on selection

-> IO () 

Set a selection widget's selection reactor We assume you've already populated it (radio boxes cannot be added to, so we have to let you do it manually on initialisation)

maybeSaveAsFile :: Window a -> Text -> IO () Source #

Save the given string to a file, if the user selets one via the file save dialog. Otherwise, don't do anything.

messageGui :: Window a -> Text -> IO Layout Source #

A message panel for use by the Results gui panels.

maybeOrWarn Source #

Arguments

:: String

warning

-> Maybe a 
-> (a -> IO ()) 
-> IO () 

maybeIO :: (a -> IO ()) -> Maybe a -> IO () Source #