uni-graphs-2.2.1.1: Graphs

Safe HaskellNone
LanguageHaskell98

Graphs.GraphConfigure

Contents

Description

GraphConfigure contains definitions for the various configuration options for GraphDisp objects. These should be implemented using the HasConfig, HasConfigValue and ModifyHasDef, applied to instances of GraphParms, NodeTypeParms and ArcTypeParms.

Synopsis

Documentation

class (GraphAll graph graphParms node nodeType nodeTypeParms arc arcType arcTypeParms, HasGraphConfigs graphParms, HasNodeTypeConfigs nodeTypeParms, HasNodeModifies graph node, HasArcTypeConfigs arcTypeParms) => GraphAllConfig graph graphParms node nodeType nodeTypeParms arc arcType arcTypeParms Source #

Instances
(GraphAll graph graphParms node nodeType nodeTypeParms arc arcType arcTypeParms, HasGraphConfigs graphParms, HasNodeTypeConfigs nodeTypeParms, HasNodeModifies graph node, HasArcTypeConfigs arcTypeParms) => GraphAllConfig graph graphParms node nodeType nodeTypeParms arc arcType arcTypeParms Source # 
Instance details

Defined in Graphs.GraphConfigure

class (GraphParms graphParms, HasConfig GlobalMenu graphParms, HasConfig GraphTitle graphParms, HasConfig GraphGesture graphParms, HasConfig OptimiseLayout graphParms, HasConfig SurveyView graphParms, HasConfig AllowDragging graphParms, HasConfig AllowClose graphParms, HasConfig Orientation graphParms, HasConfig FileMenuAct graphParms, HasConfig ActionWrapper graphParms, HasConfig (SimpleSource GraphTitle) graphParms, HasConfig Delayer graphParms) => HasGraphConfigs graphParms Source #

Instances
(GraphParms graphParms, HasConfig GlobalMenu graphParms, HasConfig GraphTitle graphParms, HasConfig GraphGesture graphParms, HasConfig OptimiseLayout graphParms, HasConfig SurveyView graphParms, HasConfig AllowDragging graphParms, HasConfig AllowClose graphParms, HasConfig Orientation graphParms, HasConfig FileMenuAct graphParms, HasConfig ActionWrapper graphParms, HasConfig (SimpleSource GraphTitle) graphParms, HasConfig Delayer graphParms) => HasGraphConfigs graphParms Source # 
Instance details

Defined in Graphs.GraphConfigure

class (NodeTypeParms nodeTypeParms, HasConfigValue LocalMenu nodeTypeParms, HasConfigValue ValueTitle nodeTypeParms, HasConfigValue ValueTitleSource nodeTypeParms, HasConfigValue FontStyleSource nodeTypeParms, HasConfigValue BorderSource nodeTypeParms, HasConfigValue NodeGesture nodeTypeParms, HasConfigValue NodeDragAndDrop nodeTypeParms, HasConfigValue DoubleClickAction nodeTypeParms, HasConfigValue Shape nodeTypeParms, HasConfigValue Color nodeTypeParms) => HasNodeTypeConfigs nodeTypeParms Source #

Instances
(NodeTypeParms nodeTypeParms, HasConfigValue LocalMenu nodeTypeParms, HasConfigValue ValueTitle nodeTypeParms, HasConfigValue ValueTitleSource nodeTypeParms, HasConfigValue FontStyleSource nodeTypeParms, HasConfigValue BorderSource nodeTypeParms, HasConfigValue NodeGesture nodeTypeParms, HasConfigValue NodeDragAndDrop nodeTypeParms, HasConfigValue DoubleClickAction nodeTypeParms, HasConfigValue Shape nodeTypeParms, HasConfigValue Color nodeTypeParms) => HasNodeTypeConfigs nodeTypeParms Source # 
Instance details

Defined in Graphs.GraphConfigure

class HasModifyValue NodeArcsHidden graph node => HasNodeModifies graph node Source #

Instances
HasModifyValue NodeArcsHidden graph node => HasNodeModifies graph node Source # 
Instance details

Defined in Graphs.GraphConfigure

class (ArcTypeParms arcTypeParms, HasConfigValue DoubleClickAction arcTypeParms, HasConfigValue LocalMenu arcTypeParms, HasConfigValue ValueTitle arcTypeParms, HasConfigValue Color arcTypeParms, HasConfigValue EdgePattern arcTypeParms, HasConfigValue EdgeDir arcTypeParms, HasConfigValue Head arcTypeParms) => HasArcTypeConfigs arcTypeParms Source #

Instances
(ArcTypeParms arcTypeParms, HasConfigValue DoubleClickAction arcTypeParms, HasConfigValue LocalMenu arcTypeParms, HasConfigValue ValueTitle arcTypeParms, HasConfigValue Color arcTypeParms, HasConfigValue EdgePattern arcTypeParms, HasConfigValue EdgeDir arcTypeParms, HasConfigValue Head arcTypeParms) => HasArcTypeConfigs arcTypeParms Source # 
Instance details

Defined in Graphs.GraphConfigure

class HasConfig option configuration where #

Minimal complete definition

($$), configUsed

Methods

($$) :: option -> configuration -> configuration infixr 0 #

configUsed :: option -> configuration -> Bool #

Instances
(Typeable value, HasConfigValue option configuration) => HasConfig (option value) (configuration value) # 
Instance details

Defined in Graphs.GraphConfigure

Methods

($$) :: option value -> configuration value -> configuration value #

configUsed :: option value -> configuration value -> Bool #

class HasConfigValue option configuration where Source #

Minimal complete definition

($$$), configUsed'

Methods

($$$) :: Typeable value => option value -> configuration value -> configuration value infixr 0 Source #

configUsed' :: Typeable value => option value -> configuration value -> Bool Source #

class HasModifyValue option graph object where Source #

Minimal complete definition

modify

Methods

modify :: Typeable value => option -> graph -> object value -> IO () Source #

Instances
HasModifyValue option graph object => HasModifyValue (Maybe option) graph object Source # 
Instance details

Defined in Graphs.GraphConfigure

Methods

modify :: Typeable value => Maybe option -> graph -> object value -> IO () Source #

newtype LocalMenu value Source #

Constructors

LocalMenu (MenuPrim (Maybe String) (value -> IO ())) 
Instances
HasCoMapIO LocalMenu Source # 
Instance details

Defined in Graphs.GraphConfigure

Methods

coMapIO :: (a -> IO b) -> LocalMenu b -> LocalMenu a #

ArcTypeConfig LocalMenu Source # 
Instance details

Defined in Graphs.GraphConfigure

NodeTypeConfig LocalMenu Source # 
Instance details

Defined in Graphs.GraphConfigure

newtype GlobalMenu Source #

Constructors

GlobalMenu (MenuPrim (Maybe String) (IO ())) 
Instances
GraphConfig GlobalMenu Source # 
Instance details

Defined in Graphs.GraphConfigure

combineGlobalMenus :: [GlobalMenu] -> GlobalMenu Source #

As a service to MMiSS we provide a function which combines several GlobalMenus into one.

data MenuPrim subMenuValue value #

Constructors

Button String value 
Menu subMenuValue [MenuPrim subMenuValue value] 
Blank 

mapMenuPrim :: (a -> b) -> MenuPrim c a -> MenuPrim c b #

mapMenuPrim' :: (c -> d) -> MenuPrim c a -> MenuPrim d a #

mapMMenuPrim :: Monad m => (a -> m b) -> MenuPrim c a -> m (MenuPrim c b) #

mapMMenuPrim' :: Monad m => (c -> m d) -> MenuPrim c a -> m (MenuPrim d a) #

data GraphTitle Source #

Constructors

GraphTitle String 
Instances
GraphConfig GraphTitle Source # 
Instance details

Defined in Graphs.GraphConfigure

GraphConfig (SimpleSource GraphTitle) Source # 
Instance details

Defined in Graphs.GraphConfigure

data ValueTitle value Source #

Provide a function which computes a node or arc title string to be displayed.

Constructors

ValueTitle (value -> IO String) 
Instances
HasCoMapIO ValueTitle Source # 
Instance details

Defined in Graphs.GraphConfigure

Methods

coMapIO :: (a -> IO b) -> ValueTitle b -> ValueTitle a #

ArcTypeConfig ValueTitle Source # 
Instance details

Defined in Graphs.GraphConfigure

NodeTypeConfig ValueTitle Source # 
Instance details

Defined in Graphs.GraphConfigure

data ValueTitleSource value Source #

Provide a function which computes a source which generates a dynamically- changing title.

Constructors

ValueTitleSource (value -> IO (SimpleSource String)) 
Instances
NodeTypeConfig ValueTitleSource Source # 
Instance details

Defined in Graphs.GraphConfigure

data Shape value Source #

This datatype is based on DaVinciClasses, including several name clashes. However we omit Textual, add the file argument to Icon and the shape Triangle. This datatype may get bigger!

Instances
NodeTypeConfig Shape Source # 
Instance details

Defined in Graphs.GraphConfigure

Read (Shape value) Source # 
Instance details

Defined in Graphs.GraphConfigure

Methods

readsPrec :: Int -> ReadS (Shape value) #

readList :: ReadS [Shape value] #

readPrec :: ReadPrec (Shape value) #

readListPrec :: ReadPrec [Shape value] #

Show (Shape value) Source # 
Instance details

Defined in Graphs.GraphConfigure

Methods

showsPrec :: Int -> Shape value -> ShowS #

show :: Shape value -> String #

showList :: [Shape value] -> ShowS #

newtype Color value Source #

The user is responsible for making sure this String is properly formatted. To quote from the daVinci documentation:

Can be used to define the background color of a node. The value of this
attribute may be any X-Window colorname (see file lib/rgb.txt in your X11
directory) or any RGB color specification in a format like "#0f331e",
where 0f is the hexadecimal value for the red part of the color, 33 is
the green part and 1e is the blue.  Hence, a pallet of 16.7 million
colors is supported. The default color for nodes is "white".

There is a function for constructing "RGB color specification"s in Colour.

Constructors

Color String 
Instances
ArcTypeConfig Color Source # 
Instance details

Defined in Graphs.GraphConfigure

NodeTypeConfig Color Source # 
Instance details

Defined in Graphs.GraphConfigure

Read (Color value) Source # 
Instance details

Defined in Graphs.GraphConfigure

Methods

readsPrec :: Int -> ReadS (Color value) #

readList :: ReadS [Color value] #

readPrec :: ReadPrec (Color value) #

readListPrec :: ReadPrec [Color value] #

Show (Color value) Source # 
Instance details

Defined in Graphs.GraphConfigure

Methods

showsPrec :: Int -> Color value -> ShowS #

show :: Color value -> String #

showList :: [Color value] -> ShowS #

data EdgePattern value Source #

The pattern of an edge

Constructors

Solid 
Dotted 
Dashed 
Thick 
Double 
Instances
ArcTypeConfig EdgePattern Source # 
Instance details

Defined in Graphs.GraphConfigure

Read (EdgePattern value) Source # 
Instance details

Defined in Graphs.GraphConfigure

Show (EdgePattern value) Source # 
Instance details

Defined in Graphs.GraphConfigure

Methods

showsPrec :: Int -> EdgePattern value -> ShowS #

show :: EdgePattern value -> String #

showList :: [EdgePattern value] -> ShowS #

data EdgeDir value Source #

The user is responsible for making sure this String is properly formatted. To quote from the daVinci documentation:

 This attribute is used to control the arrow of an edge. In a graph visualization,
 each edge usually has an arrow pointing to the child node. This attribute can be
 used to let the arrow be drawn inverse (i.e. pointing to the parent), to get an arrow
 at both sides of an edge or to suppress arrows for a particular edge. The supported
 attribute values are: "last" (1 arrow pointing to the child, default), \"first\"
(1 arrow to the parent), "both" (2 arrows to the parent and to children) and "none"
(no arrows).

Constructors

Dir String 
Instances
ArcTypeConfig EdgeDir Source # 
Instance details

Defined in Graphs.GraphConfigure

Read (EdgeDir value) Source # 
Instance details

Defined in Graphs.GraphConfigure

Methods

readsPrec :: Int -> ReadS (EdgeDir value) #

readList :: ReadS [EdgeDir value] #

readPrec :: ReadPrec (EdgeDir value) #

readListPrec :: ReadPrec [EdgeDir value] #

Show (EdgeDir value) Source # 
Instance details

Defined in Graphs.GraphConfigure

Methods

showsPrec :: Int -> EdgeDir value -> ShowS #

show :: EdgeDir value -> String #

showList :: [EdgeDir value] -> ShowS #

data Head value Source #

The user is responsible for making sure this String is properly formatted. To quote from the daVinci documentation:

 With this attribute you can control the shape of the edge's arrows.
The possible values are: "farrow" (default), "arrow", "fcircle", and "circle",
where a leading 'f' means filled.

Constructors

Head String 
Instances
ArcTypeConfig Head Source # 
Instance details

Defined in Graphs.GraphConfigure

Read (Head value) Source # 
Instance details

Defined in Graphs.GraphConfigure

Methods

readsPrec :: Int -> ReadS (Head value) #

readList :: ReadS [Head value] #

readPrec :: ReadPrec (Head value) #

readListPrec :: ReadPrec [Head value] #

Show (Head value) Source # 
Instance details

Defined in Graphs.GraphConfigure

Methods

showsPrec :: Int -> Head value -> ShowS #

show :: Head value -> String #

showList :: [Head value] -> ShowS #

newtype NodeArcsHidden Source #

If True, arcs from the node are not displayed.

Constructors

NodeArcsHidden Bool 

data Border Source #

The border of this node

data BorderSource value Source #

Compute a Border which dynamically changes.

Constructors

BorderSource (value -> IO (SimpleSource Border)) 
Instances
NodeTypeConfig BorderSource Source # 
Instance details

Defined in Graphs.GraphConfigure

data FontStyle Source #

The font in which the label of this node is displayed.

Instances
Eq FontStyle Source # 
Instance details

Defined in Graphs.GraphConfigure

data FontStyleSource value Source #

Compute a FontStyle which dynamically changes.

Constructors

FontStyleSource (value -> IO (SimpleSource FontStyle)) 
Instances
NodeTypeConfig FontStyleSource Source # 
Instance details

Defined in Graphs.GraphConfigure

class ModifyHasDef modification where Source #

Minimal complete definition

def, isDef

Methods

def :: modification Source #

isDef :: modification -> Bool Source #

data GraphGesture Source #

Action to be performed after mouse action not involving any node but somewhere on the graph.

If you want to use this, the graph parameters need to include AllowDragging True

Constructors

GraphGesture (IO ()) 
Instances
GraphConfig GraphGesture Source # 
Instance details

Defined in Graphs.GraphConfigure

data NodeGesture value Source #

Action to be performed when the user drags a node somewhere else, but not onto another node.

If you want to use this, the graph parameters need to include AllowDragging True

Constructors

NodeGesture (value -> IO ()) 
Instances
HasCoMapIO NodeGesture Source # 
Instance details

Defined in Graphs.GraphConfigure

Methods

coMapIO :: (a -> IO b) -> NodeGesture b -> NodeGesture a #

NodeTypeConfig NodeGesture Source # 
Instance details

Defined in Graphs.GraphConfigure

data NodeDragAndDrop value Source #

Action to be performed when the user drags one node onto another. The dragged node's value is passed as a Dyn (since it could have any type).

If you want to use this, the graph parameters need to include AllowDragging True

Constructors

NodeDragAndDrop (Dyn -> value -> IO ()) 
Instances
NodeTypeConfig NodeDragAndDrop Source # 
Instance details

Defined in Graphs.GraphConfigure

newtype DoubleClickAction value Source #

Action to be performed when a node or arc is double-clicked.

Constructors

DoubleClickAction (value -> IO ()) 

newtype OptimiseLayout Source #

If True, try hard to optimise the layout of the graph on redrawing it.

Constructors

OptimiseLayout Bool 
Instances
GraphConfig OptimiseLayout Source # 
Instance details

Defined in Graphs.GraphConfigure

newtype SurveyView Source #

If True, add a survey view of the graph; IE display a picture of the whole graph which fits onto the screen (without displaying everything) as well as a picture of the details (which may not fit onto the screen).

(The user can do this anyway from daVinci's menus.)

Constructors

SurveyView Bool 
Instances
GraphConfig SurveyView Source # 
Instance details

Defined in Graphs.GraphConfigure

newtype AllowDragging Source #

If True, allow Drag-and-Drop operators.

Constructors

AllowDragging Bool 
Instances
GraphConfig AllowDragging Source # 
Instance details

Defined in Graphs.GraphConfigure

newtype AllowClose Source #

If set, action which is invoked if the user attempts to close the window. If the action returns True, we close it.

WARNING. This action is performed in the middle of the event loop, so please don't attempt to do any further graph interactions during it. (But HTk interactions should be fine.)

Constructors

AllowClose (IO Bool) 
Instances
GraphConfig AllowClose Source # 
Instance details

Defined in Graphs.GraphConfigure

data FileMenuAct Source #

Constructors

FileMenuAct FileMenuOption (Maybe (IO ())) 
Instances
GraphConfig FileMenuAct Source # 
Instance details

Defined in Graphs.GraphConfigure

data FileMenuOption Source #

The following options are provided specially by DaVinci (see, for now, http://www.informatik.uni-bremen.de/daVinci/old/docs/reference/api/api_app_menu_cmd.html for the daVinci2.1 documentation. If a FileMenuAct is used as a configuration with a specified action, the corresponding option is enabled in the daVinci File menu, and the action is performed when the option is selected.

The AllowClose configuration and CloseMenuOption both set the action to be taken when the user selects a close event, and each overrides the other.

By default the Close and Print options are enabled, however these and other options can be disabled by specifing Nothing as the second argument to FileMenuAct.

data Orientation Source #

Which way up the graph is.

We copy the DaVinciTypes constructors, though of course this will mean we have to painfully convert one to the other.

Instances
GraphConfig Orientation Source # 
Instance details

Defined in Graphs.GraphConfigure

newtype ActionWrapper Source #

Function to be applied to all user actions. This is useful for exception wrappers and so on.

Constructors

ActionWrapper (IO () -> IO ()) 
Instances
GraphConfig ActionWrapper Source # 
Instance details

Defined in Graphs.GraphConfigure

($$$?) :: (HasConfigValue option configuration, Typeable value) => Maybe (option value) -> configuration value -> configuration value infixr 0 Source #

$$$? can be a useful abbreviation

Orphan instances

GraphConfig Delayer Source #

Allows the user to specify a Delayer. This will postpone redrawing on the graph.

Instance details

(Typeable value, HasConfigValue option configuration) => HasConfig (option value) (configuration value) Source # 
Instance details

Methods

($$) :: option value -> configuration value -> configuration value #

configUsed :: option value -> configuration value -> Bool #