1/* COPYRIGHT ************************************************************
    2
    3Conceptual Graph Editor (CGE) - an X-Windows graphical interface to CGT
    4Copyright (C) 1990 Miguel Alexandre Wermelinger
    5
    6    This program is free software; you can redistribute it and/or modify
    7    it under the terms of the GNU General Public License as published by
    8    the Free Software Foundation; either version 2 of the License, or
    9    (at your option) any later version.
   10
   11    This program is distributed in the hope that it will be useful,
   12    but WITHOUT ANY WARRANTY; without even the implied warranty of
   13    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   14    GNU General Public License for more details.
   15
   16    You should have received a copy of the GNU General Public License
   17    along with this program; if not, write to the Free Software
   18    Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
   19
   20************************************************************************/
   21
   22/* AUTHOR(S) ************************************************************
   23
   24Michel Wermelinger
   25Dept. de Informatica, Univ. Nova de Lisboa, Quinta da Torre
   26P - 2825 Monte da Caparica, PORTUGAL
   27Phone: (+351) (1) 295 44 64 ext. 1360  Internet: mw@fct.unl.pt
   28
   29************************************************************************/
   30
   31/* GENERALITIES *********************************************************
   32 
   33File Name       : WIDGETS.PL
   34Creation Date   : 90/11/20 
   35Author(s)       : Michel Wermelinger (mw)
   36Description     : Widgets for the Conceptual Graph Editor
   37 
   38************************************************************************/
   39
   40/* HISTORY **************************************************************
   41
   420.0     90/11/29  mw    Displays graphs but doesn't show coreference links
   430.1	90/12/07  mw	graph and node menus
   441.0	90/12/14  mw	editor menu, icons, multiple editors
   451.01    91/02/19  mw    minor improvements and debugging
   46
   47************************************************************************/
   48
   49
   50:- use_module(library(cgt/cge/swi_apeal)).   51
   52/* CONTENTS *************************************************************
   53
   54shell widget cge/4	the editor window widget
   55
   56************************************************************************/
   57:- set_prolog_flag(swi_apeal,false).   58
   59_Parent widget Graph= graphViewer(Width, Height, Editor)  <->
   60    Graph= graphGraph
   61      / [
   62	width(Width), height(Height),
   63        borderWidth(0),
   64	%destroyCallback( g(cge_destroy(cge_graph, Graph)) ),
   65	layoutStyle(top_down),				% initial layout style
   66        defaultHorizDistance(30),			% hz distance of arcs
   67        defaultVertDistance(30)				% vt distance of arcs
   68        ]
   69      + [
   70	recorda(cge_graph, Graph-none+Editor, _)	% remember graph's WID
   71        ].
   72
   73
   74shell widget cge(DisplayWidth, MiniatureFraction, LinearHeight, Editor) <->
   75    ( recorded(cge_num, _-N, _), succ(N, Number) ; Number = 1 ),
   76    name('Conceptual Graph Editor #', Ascii1), name(Number, Ascii2),
   77    conc(Ascii1, Ascii2, Ascii3), name(Title, Ascii3),
   78    name('CG Editor #', Ascii4),
   79    conc(Ascii4, Ascii2, Ascii5), name(IconName, Ascii5), 
   80    MiniatureWidth is DisplayWidth // MiniatureFraction,
   81    MiniatureDist is DisplayWidth - MiniatureWidth,
   82    cge: Editor= topLevelShell 
   83      / [
   84	iconName(IconName),
   85	title(Title),
   86	destroyCallback(g(cge_destroy(Editor)))
   87	]
   88      - [
   89        form
   90          - [
   91            Palette= cuTbl		% widget with easy access commands
   92              / [         
   93                right(left), bottom(top),	% in upper left corner of editor
   94                formatString([ 
   95		  [@(c), c, @(c)],		% buttons for commands without
   96		  [  ^,  c,   ^ ],		% keyboard shortcuts
   97		  [c]      			% layout command box is centered
   98		]),
   99                borderWidth(0)
  100                ]
  101              - [
  102		space(1, 1),
  103		RestrictType= command
  104		  / [
  105	    	    callback(g(cge_action(indiv, cge_restrict_type, Editor, only-concept, multiple))),
  106		    shapeStyle(rectangle)
  107		    ]
  108		  + [
  109		    xt_parse(enter : set, ComTrans),
  110		    override_translations(ComTrans),
  111		    read_bitmap('rest_type.icon', RestTypeIcon),
  112		    RestrictType wset bitmap(RestTypeIcon)
  113		    ],
  114		space(1, 1),
  115		RestrictRef= command
  116		  / [
  117	    	    callback(g(cge_action(indiv, cge_restrict_ref, Editor, only-concept, multiple))),
  118		    shapeStyle(rectangle)
  119		    ]
  120		  + [
  121		    override_translations(ComTrans),
  122		    read_bitmap('rest_ref.icon', RestRefIcon),
  123		    RestrictRef wset bitmap(RestRefIcon)
  124		    ],
  125		space(1, 15),
  126		box
  127		  / [
  128		    hSpace(0),
  129		    vSpace(0),
  130		    borderWidth(1)
  131		    ]
  132		  - [
  133                    cuTbl			% commands for layout control
  134                      / [
  135		    	formatString([ [c] ]),
  136		    	internalHeight(3),	% vt dist betw. cuTbl & buttons
  137		    	internalWidth(3),	% hz dist betw. cuTbl & buttons
  138		    	interHeight(2)		% vt dist between buttons
  139                    	]
  140                      - [
  141			Mode= cuButton
  142			  / [
  143			    label('Auto'),	% initial mode is automatic
  144			    set(true),		% no graph in manual mode
  145			    highlightColor(white),
  146			    callback(g(toggle_mode(Mode)))
  147			    ],
  148			space(1, 8),
  149                        'Hierarchy': Hier= cuButton
  150                          / [highlightColor(white),
  151                            set(true)                   % initial layout mode
  152                            ],
  153                        'Spring': Spring= cuButton
  154			  / [
  155			    highlightColor(white)
  156			    ],
  157                        'Tree': Tree= cuButton
  158			  / [
  159			    highlightColor(white)
  160			    ],
  161			space(1, 8),
  162			cuTbl				% style buttons
  163			  / [
  164			    formatString([
  165				[@(c), @(c), c, <, @(c), @(c)],
  166				[ ^  ,   c , <, c,  <  ,  ^  ],
  167				[ ^  , @(c), c, <, @(c),  ^  ]
  168			    ])
  169			    ]
  170			  - [
  171			    space(1, 1),
  172			    space(1, 1),
  173			    style: BU= toggle
  174			      / [
  175				callback(g(cge_style(Editor, BU, bottom_up)))
  176				]
  177 			      + [
  178				read_bitmap('bu.icon', BUIcon),
  179			    	BU wset bitmap(BUIcon)
  180			    	],
  181			    space(1, 1),
  182			    space(1, 1),
  183			    style: RL= toggle
  184			      / [
  185				callback(g(cge_style(Editor, RL, right_left))),
  186				radioGroup(BU)
  187				]
  188			      + [
  189				read_bitmap('rl.icon', RLIcon),
  190			    	RL wset bitmap(RLIcon)
  191			    	],
  192			    style: LR= toggle
  193			      / [
  194				callback(g(cge_style(Editor, LR, left_right))),
  195				radioGroup(BU)
  196				]
  197			      + [
  198				read_bitmap('lr.icon', LRIcon),
  199			    	LR wset bitmap(LRIcon)
  200			    	],
  201			    space(1, 1),
  202			    style: TD= toggle
  203			      / [
  204				callback(g(cge_style(Editor, TD, top_down))),
  205				radioGroup(BU), state(true)	% initial style
  206				]
  207			      + [
  208			    	read_bitmap('td.icon', TDIcon),
  209			    	TD wset bitmap(TDIcon)
  210			    	],
  211			    space(1, 1)
  212			    ]
  213			  + [
  214			    [LR, RL, TD, BU] wset [
  215				shapeStyle(rectangle), highlightThickness(1)
  216			    ]
  217			    ]
  218                        ]
  219		      + [
  220			[Mode, Hier, Spring, Tree] wset
  221			    [ shadow(false), dimFacetColor(gray40), 
  222			      brightFacetColor(lightGray), 
  223			      highlightColor(white)
  224			    ],
  225			xt_parse(btn(up) : goal(true), NoUpTrans),
  226			[Mode, Hier, Spring, Tree] wproc
  227			    override_translations(NoUpTrans)
  228			]
  229		    ],
  230                    Layout= cuBmgr			% outside of box
  231                      / [
  232			setCallback(g((next_event(E), cge_layout(Editor, E)))),
  233                        bmgrType(one_of_many)       	% only one layout mode
  234                        ]
  235                      + [
  236                        Layout wproc manage(
  237			    [Tree,    Hier, 	       Spring],
  238			    [t(tree), t(hierarchical), t(spring)]
  239			)
  240                        ]
  241                    ],
  242                Header= asciiText	% describes kind of graph (schema, etc.)
  243                  / [
  244    		    font(courier-[bold, size(pixel)=10, slant=r]),
  245                    bottom(top),        	% fixed dist from top of editor
  246                    right(left),        	% fixed dist from left of editor
  247                    fromHoriz(Palette),		% to the right of Palette
  248		    editType(edit),		% displayed text may be edited
  249		    sensitive(false),		% but not by the user
  250		    resize(width),		% Header may get wider
  251		    resizable(true),		% Form allows Header to resize
  252		    displayCaret(false),	% don't show insertion point
  253		    borderWidth(0)%,
  254		    %cursor(68)			% northwest arrow (XC_left_ptr)
  255                    ],
  256		Display= paned 
  257		  / [
  258                    fromVert(Header),		% under the graph description
  259                    fromHoriz(Palette)		% to the right of the palette
  260		    ]
  261		  - [
  262		    _Graphical= form 
  263		      / [
  264			defaultDistance(0)
  265			]
  266		      - [
  267		    	Shadow= core		% miniature of whole graph
  268		      	  / [
  269			    top(rubber), left(rubber),	% proportionally in
  270			    bottom(bottom), right(right),% bottom right corner
  271			    mappedWhenManaged(false),	% initially invisible
  272			    width(MiniatureWidth), horizDistance(MiniatureDist),
  273			    height(MiniatureWidth), vertDistance(MiniatureDist)
  274			    ],
  275                    	viewport
  276                      	  / [
  277			    borderWidth(0),
  278                    	    forceBars(true),	% scrollbars always present
  279                    	    allowHoriz(true),   % allow displayed graph to widen
  280                    	    allowVert(true),    % allow displayed graph to grow
  281                    	    width(DisplayWidth), height(DisplayWidth)
  282              		    ]
  283                       	  - [
  284                    	    Graph= graphViewer(DisplayWidth, DisplayWidth,
  285					       Editor)
  286			      + [
  287				Graph wset shadowWidget(Shadow)
  288				]
  289                    	    ]
  290			],
  291		    Linear= asciiText
  292		      / [
  293			editType(edit),		% displayed text may be edited
  294			scrollVertical(always),	% vt scrollbar always present
  295			scrollHorizontal(whenNeeded),
  296			dataCompression(true),	% save memory space
  297			width(DisplayWidth), 
  298			height(LinearHeight),
  299			skipAdjust(true)	% try to resize Graphical first
  300			]
  301		    ],
  302                _MenuBar= box
  303                  / [
  304                    top(bottom),        	% don't change size vertically
  305                    right(left),        	% don't change size horizontally
  306                    fromVert(Display),		% under the Display
  307                    fromHoriz(Palette), 	% to the right of the palette
  308                    background(white),  	% white bar
  309		    orientation(horizontal),	% menu options side by side
  310                    vSpace(0), hSpace(0)	% no space between menu options
  311                    ]
  312		  - [
  313		    MainMB= menuButton
  314		      / [
  315			label('Editor'), menuName(mainMenu)
  316			],
  317		    GraphMB= menuButton
  318		      / [
  319			label('Graph'), menuName(graphMenu)
  320			],
  321		    NodeMB= menuButton
  322		      / [
  323			label('Node'), menuName(nodeMenu)
  324			]
  325		    ]
  326		  + [
  327		    [MainMB, GraphMB, NodeMB] wset borderWidth(0),
  328		    xt_parse([enter: set], ButtonTrans),
  329		    [MainMB, GraphMB, NodeMB] wproc
  330			override_translations(ButtonTrans)
  331		    ],
  332                modified: Modified= label       % appears upon changes
  333                  / [
  334                    fromVert(Display),		% under the display
  335                    top(bottom), right(left)	% in bottom left corner of Form
  336                    ]
  337		  + [
  338		    ( recorded(get_db_modif, Yes, _)	% was database modified?
  339		    ; Yes = false
  340		    ),
  341		    Modified wset mappedWhenManaged(Yes)% map label iff modified
  342		    ]
  343                ]
  344        ]
  345      + [
  346	read_bitmap('cge.icon', Icon),
  347	Editor wset iconPixmap(Icon),
  348	popup(Editor) widget mainMenu,
  349	popup(Editor) widget graphMenu,
  350	popup(Editor) widget nodeMenu,
  351        xt_parse([
  352	    key-'Up'   : goal(Style wproc set_child(BU)),
  353	    key-'Down' : goal(Style wproc set_child(TD)),
  354	    key-'Left' : goal(Style wproc set_child(RL)),
  355	    key-'Right': goal(Style wproc set_child(LR)),
  356
  357	    % editor menu
  358
  359	    control/key-l :
  360	      goal(cge_load(Editor)),
  361	    control/key-s :
  362	      goal(cge_save_gr(Editor)),
  363	    key-'Delete' :
  364	      goal(cge_clear_editor(Editor)),
  365	    control/key-o :
  366	      goal(cge_open_db(Editor)),
  367	    control/key-u :
  368	      goal(cge_save_db(Editor)),
  369	    control/key-h :
  370	      goal(cge_help),
  371	    control/key-q :
  372	      goal(cge_quit(Editor)),
  373
  374	    % graph menu
  375
  376	    meta/key-c :
  377	      goal(cge_action(indiv, cge_copy, Editor, graph, multiple)),
  378	    meta/key-o :
  379	      goal(cge_action(conj, cge_join_on, Editor, only-concept, multiple)),
  380	    meta/key-j :
  381	      goal(cge_action(conj, cge_join, Editor, graph, multiple)),
  382	    [meta, shift]/key-j :
  383	      goal(cge_action(conj, cge_max_join, Editor, graph, multiple)),
  384	    meta/key-s :
  385	      goal(cge_action(indiv, cge_simplify, Editor, graph, multiple)),
  386	    meta/key-e :
  387	      goal(cge_action(indiv, cge_erasure, Editor, graph, multiple)),
  388	    meta/key-i :
  389	      goal(cge_action(indiv, cge_insertion, Editor, graph, single)),
  390	    [meta, shift]/key-a :
  391	      goal(cge_action(indiv, cge_iteration, Editor, graph, single)),
  392	    meta/key-a :
  393	      goal(cge_action(indiv, cge_deiteration, Editor, graph, multiple)),
  394	    [meta, shift]/key-d :
  395	      goal(cge_draw_dn(Editor)),
  396	    meta/key-d :
  397	      goal(cge_action(indiv, cge_erase_dn, Editor, graph, multiple)),
  398
  399	    % node menu
  400
  401	    [meta, shift]/key-t : 
  402	      goal(cge_action(indiv, cge_max_exp, Editor, only-concept, multiple)),
  403	    meta/key-t :
  404	      goal(cge_action(indiv, cge_min_exp, Editor, only-concept, multiple)),
  405	    [meta, shift]/key-r :
  406	      goal(cge_action(indiv, cge_rel_exp, Editor, only-relation, multiple)),
  407	    [meta, shift]/key-m :
  408	      goal(cge_action(indiv, cge_meas_exp, Editor, only-concept, multiple)),
  409	    meta/key-m :
  410	      goal(cge_action(indiv, cge_meas_ctr, Editor, only-relation, multiple)),
  411	    [meta, shift]/key-n :
  412	      goal(cge_action(indiv, cge_name_exp, Editor, only-concept, multiple)),
  413	    meta/key-n :
  414	      goal(cge_action(indiv, cge_name_ctr, Editor, only-relation, multiple)),
  415	    [meta, shift]/key-q :
  416	      goal(cge_action(indiv, cge_qty_exp, Editor, only-concept, multiple)),
  417	    meta/key-q :
  418	      goal(cge_action(indiv, cge_qty_ctr, Editor, only-relation, multiple)),
  419	    [meta, shift]/key-u :
  420	      goal(cge_action(indiv, cge_univ_exp, Editor, only-concept, multiple))
  421
  422	    ], Shortcuts),
  423            override_translations(Shortcuts),
  424            recorda(cg_editor, 
  425		    Editor-Header-Graph-Linear-Mode/[Hier, Spring, Tree]/[LR, RL, TD, BU],
  426		    _),
  427	    recorda(cge_shadow, Editor-Shadow, _),
  428	    recorda(cge_modif, Editor-Modified, _),
  429	    recorda(cge_num, Editor-Number, _)
  430            ].
  431
  432popup(Editor) widget mainMenu <->
  433    mainMenu: simpleMenu
  434      - [
  435	'Load graph...      C-L': smeBSB
  436	  / [
  437	    callback(g(cge_load(Editor)))
  438	    ],
  439	'Store graph...     C-S': smeBSB
  440	  / [
  441	    callback(g(cge_save_gr(Editor)))
  442	    ],
  443	'Clear graph(s)  Delete': smeBSB
  444	  / [
  445	    callback(g(cge_clear_editor(Editor)))
  446	    ],
  447	smeLine,
  448	'Open database...   C-O': smeBSB
  449	  / [
  450	    callback(g(cge_open_db(Editor)))
  451	    ],
  452	'Update database... C-U': smeBSB
  453	  / [
  454	    callback(g(cge_save_db(Editor)))
  455	    ],
  456	smeLine,
  457	'HEEEEEELP!!!       C-H': smeBSB
  458	  / [
  459	    callback(g(cge_help))
  460	    ],
  461	ShadowEntry= smeBSB
  462	  / [
  463	    label('Show Miniature'),
  464	    callback(g(toggle_shadow(ShadowEntry, Editor)))
  465	    ],
  466	'Quit               C-Q': smeBSB
  467	  / [
  468	    callback(g(cge_quit(Editor)))
  469	    ]
  470	].
  471
  472popup(Editor) widget graphMenu <->
  473    graphMenu: simpleMenu
  474      - [
  475	'Copy             M-C': smeBSB
  476	  / [
  477	    callback(g(cge_action(indiv, cge_copy, Editor, graph, multiple)))
  478	    ],
  479	'Join on          M-O': smeBSB
  480	  / [
  481	    callback(g(cge_action(conj, cge_join_on, Editor, only-concept, multiple)))
  482	    ],
  483	'Join             M-J': smeBSB
  484	  / [
  485	    callback(g(cge_action(conj, cge_join, Editor, graph, multiple)))
  486	    ],
  487	'Maximal Join    MS-J': smeBSB
  488	  / [
  489	    callback(g(cge_action(conj, cge_max_join, Editor, graph, multiple)))
  490	    ],
  491	'Simplify         M-S': smeBSB
  492	  / [
  493	    callback(g(cge_action(indiv, cge_simplify, Editor, graph, multiple)))
  494	    ],
  495	smeLine,
  496	'Erasure          M-E': smeBSB
  497	  / [
  498	    callback(g(cge_action(indiv, cge_erasure, Editor, graph, multiple)))
  499	    ],
  500	'Insertion        M-I': smeBSB
  501	  / [
  502	    callback(g(cge_action(indiv, cge_insertion, Editor, graph, single)))
  503	    ],
  504	'Iteration       MS-A': smeBSB
  505	  / [
  506	    callback(g(cge_action(indiv, cge_iteration, Editor, graph, single)))
  507	    ],
  508	'Deiteration      M-A': smeBSB
  509	  / [
  510	    callback(g(cge_action(indiv, cge_deiteration, Editor, graph, multiple)))
  511	    ],
  512	'Draw Double Neg MS-D': smeBSB
  513	  / [
  514	    callback(g(cge_draw_dn(Editor)))
  515	    ],
  516	'Erase Double Neg M-D': smeBSB
  517	  / [
  518	    callback(g(cge_action(indiv, cge_erase_dn, Editor, graph, multiple)))
  519	    ],
  520	smeLine,
  521	'Compare             ': smeBSB
  522	  / [
  523	    callback(g(cge_action(indiv, cge_compare, Editor, graph, single)))
  524	    ],
  525	'Depth               ': smeBSB
  526	  / [
  527	    callback(g(cge_action(indiv, cge_depth, Editor, graph, single)))
  528	    ]
  529	].
  530
  531popup(Editor) widget nodeMenu <->
  532    nodeMenu: simpleMenu
  533      - [
  534	'Restrict Type              ': smeBSB
  535	  / [
  536	    callback(g(cge_action(indiv, cge_restrict_type, Editor, only-concept, multiple)))
  537	    ],
  538	'Restrict Referent          ': smeBSB
  539	  / [
  540	    callback(g(cge_action(indiv, cge_restrict_ref, Editor, only-concept, multiple)))
  541	    ],
  542	smeLine,
  543	'Max Type Expansion     MS-T': smeBSB
  544	  / [
  545	    callback(g(cge_action(indiv, cge_max_exp, Editor, only-concept, multiple)))
  546	    ],
  547	'Min Type Expansion      M-T': smeBSB
  548	  / [
  549	    callback(g(cge_action(indiv, cge_min_exp, Editor, only-concept, multiple)))
  550	    ],
  551	'Relational Expansion   MS-R': smeBSB
  552	  / [
  553	    callback(g(cge_action(indiv, cge_rel_exp, Editor, only-relation, multiple)))
  554	    ],
  555	smeLine,
  556	'Measure Expansion      MS-M': smeBSB
  557	  / [
  558	    callback(g(cge_action(indiv, cge_meas_exp, Editor, only-concept, single)))
  559	    ],
  560	'Measure Contraction     M-M': smeBSB
  561	  / [
  562	    callback(g(cge_action(indiv, cge_meas_ctr, Editor, only-relation, single)))
  563	    ],
  564	'Name Expansion         MS-N': smeBSB
  565	  / [
  566	    callback(g(cge_action(indiv, cge_name_exp, Editor, only-concept, single)))
  567	    ],
  568	'Name Contraction        M-N': smeBSB
  569	  / [
  570	    callback(g(cge_action(indiv, cge_name_ctr, Editor, only-relation, single)))
  571	    ],
  572	'Quantity Expansion     MS-Q': smeBSB
  573	  / [
  574	    callback(g(cge_action(indiv, cge_qty_exp, Editor, only-concept, single)))
  575	    ],
  576	'Quantity Contraction    M-Q': smeBSB
  577	  / [
  578	    callback(g(cge_action(indiv, cge_qty_ctr, Editor, only-relation, single)))
  579	    ],
  580	'Expand Univ Quantifier MS-U': smeBSB
  581	  / [
  582	    callback(g(cge_action(indiv, cge_univ_exp, Editor, only-concept, single)))
  583	    ]
  584	].
  585
  586Graph= graphGraph widget Relation= relation(Label, Links) <->
  587    recorded(cge_graph, Graph-_+Editor, _),	% get associated Editor
  588    Label: Relation= toggle
  589      / [
  590        linkedNodes(Links),			% concepts linked to Relation
  591        resizable(true),			% Relation may grow
  592	%destroyCallback( g(cge_destroy(cge_relation, Relation)) ),
  593        font(courier-[bold, size(pixel)=10, slant=r])
  594        ]
  595      + [
  596	xt_parse([
  597	    btn(right, down) : goal(cge_move(Relation)),
  598	    [meta, ctrl]/btn(left, down) :
  599		goal(toggle_sel(sec, relation, Relation, Graph, Editor)),
  600	    btn(left, down)*2: goal((Graph wproc unmap, cge_rel_exp(Relation), Graph wproc map, update_linear(Editor))),
  601	    btn(left, down)  :
  602		goal(toggle_sel(prim, relation, Relation, Graph, Editor))
  603	], RelTrans),
  604	override_translations(RelTrans),
  605	recorda(cge_relation, Relation-_+Editor, _)
  606	].
  607
  608Graph= graphGraph widget Concept= concept(Links) <->
  609    recorded(cge_graph, Graph-_+Editor, _),	% get associated Editor
  610    Concept= form
  611      / [
  612	defaultDistance(0),
  613	%destroyCallback( g(cge_destroy(cge_concept, Concept)) ),
  614	width(10), height(10),
  615        linkedNodes(Links),         % relations linked to Concept
  616        resizable(true)            % Concept may grow
  617        ]
  618      + [
  619	xt_accelerators([
  620	    btn(right, down) : goal(cge_move(Concept)),
  621	    [meta, ctrl]/btn(left, down) :
  622		goal(toggle_sel(sec, concept, Concept, Graph, Editor)),
  623	    btn(left, down)*2: goal((Graph wproc unmap, cge_max_exp(Concept), Graph wproc map, update_linear(Editor))),
  624	    btn(left, down) :
  625		goal(toggle_sel(prim, concept, Concept, Graph, Editor))
  626	], ConAcc),
  627	Concept wset accelerators(ConAcc),
  628	recorda(cge_concept, Concept-none/none+Editor, _)
  629        ].
  630
  631Concept= form widget Type= typeField(TypeLabel) <->
  632    Type= unmanaged form
  633      / [
  634	%destroyCallback( g(cge_destroy(cge_type, Type)) ),
  635	%bottom(top), right(left),	% in upper left corner of Concept
  636        borderWidth(0),
  637	defaultDistance(0),		% children all together
  638	resizable(true)
  639        ]
  640      - [
  641	Label= label
  642	  / [
  643	    %borderWidth(1),
  644            font(courier-[bold,size(pixel)=10,slant=r]), label(TypeLabel),
  645	    %bottom(top), right(left),
  646	    resizable(true)
  647	    ]
  648	]
  649      + [
  650	install_accelerators(Concept),
  651	manage,
  652	( recorded(cge_concept, Concept-none/Ref+Editor, DbR), erase(DbR),
  653	  recorda(cge_concept, Concept-Type/Ref+Editor, _)
  654	; recorded(cge_context, Concept-none/Ref/Graph+Editor, DbR), erase(DbR),
  655	  recorda(cge_context, Concept-Type/Ref/Graph+Editor, _)
  656	),
  657	recorda(cge_type, Type-none/Label/none+Editor, _)
  658	].
  659
  660Concept= form widget Type= typeField(TypeLabel, Graph) <->
  661    ( recorded(cge_concept, Concept-_+Editor, _)
  662    ; recorded(cge_context, Concept-_+Editor, _)
  663    ),
  664    Type= unmanaged form
  665      / [
  666	%destroyCallback( g(cge_destroy(cge_type, Type)) ),
  667        borderWidth(0),
  668	defaultDistance(0),			% children all together
  669	resizable(true)
  670        ]
  671      - [
  672	l: Lambda= label
  673	  / [
  674	    borderWidth(0),
  675	    font(symbol-[size(pixel)=10]),	% display lambda letter
  676	    bottom(top), right(left)
  677	    ],
  678	TypeLabel: Label= label
  679	  / [
  680	    borderWidth(0),
  681            font(courier-[bold,size(pixel)=10,slant=r]),
  682	    fromHoriz(Lambda),
  683	    %bottom(top), right(left),
  684	    resizable(true)
  685	    ],
  686        Graph= graphViewer(1, 1, Editor)
  687	  + [
  688	    Graph wset [resizable(true), fromVert(Lambda)]
  689	    ]
  690        ]
  691      + [
  692	install_accelerators(Concept),
  693	manage,
  694	( recorded(cge_concept, Concept-none/Ref+Editor, DbR), erase(DbR),
  695	  recorda(cge_concept, Concept-Type/Ref+Editor, _)
  696	; recorded(cge_context, Concept-none/Ref/Graph+Editor, DbR), erase(DbR),
  697	  recorda(cge_context, Concept-Type/Ref/Graph+Editor, _)
  698	),
  699	recorda(cge_type, Type-Lambda/Label/Graph+Editor, _)
  700	].
  701
  702Concept= form widget Ref= refField(Label) <->
  703    recorded(cge_concept, Concept-Type/none+Editor, DbR), 
  704    Ref= asciiText
  705      / [
  706	%top(bottom), left(right),
  707	fromHoriz(Type),
  708	font(courier-[bold,size(pixel)=10,slant=r]),
  709	editType(edit),			% displayed text may be edited
  710	sensitive(false),		% but not by the user
  711	resize(width),			% Ref may get wider
  712	width(1),			% to stretch only as necessary
  713	resizable(true),		% Concept allows it actually to resize
  714	displayCaret(false),
  715	borderWidth(0)%,
  716	%cursor(68)
  717	]
  718      + [
  719	install_accelerators(Concept),
  720	replace_text(Ref, Label),
  721	erase(DbR), recorda(cge_concept, Concept-Type/Ref+Editor, _)
  722	].
  723
  724Graph= graphGraph widget Context= context(Links) <->
  725    recorded(cge_graph, Graph-_+Editor, _),
  726    Context= form
  727      / [
  728	defaultDistance(0),
  729	width(10), height(10),
  730        linkedNodes(Links),         % relations linked to Concept
  731        resizable(true)            % Concept may grow
  732	]
  733      + [
  734	xt_accelerators([
  735	    btn(right, down) : goal(cge_move(Context)),
  736	    [meta, ctrl]/btn(left, down) :
  737		goal(toggle_sel(sec, context, Context, Graph, Editor)),
  738	    btn(left, down)*2: goal((Graph wproc unmap, cge_max_exp(Context), Graph wproc map, update_linear(Editor))),
  739	    btn(left, down) :
  740		goal(toggle_sel(prim, context, Context, Graph, Editor))
  741	], EnvAcc),
  742	Context wset accelerators(EnvAcc),
  743	recorda(cge_context, Context-none/none/none+Editor, _)
  744	].
  745
  746Context= form widget Graph= graphs <->
  747    recorded(cge_context, Context-Type/Ref/none+Editor, DbR),
  748    Graph= graphViewer(1, 1, Editor)
  749      + [
  750	install_accelerators(Context),
  751	Graph wset resizable(true),
  752	erase(DbR), recorda(cge_context, Context-Type/Ref/Graph+Editor, _)
  753	].
  754
  755shell widget graphLoader(S, LIST, Items) <->
  756  S= transientShell / [
  757    title('Modal Dialog'),
  758    geometry('+400+400')
  759  ] - [
  760    box / [
  761      vSpace(2), hSpace(2)
  762    ] - [
  763      form / [
  764	borderWidth(2), defaultDistance(2)
  765      ] - [
  766	OK= cuCommand / [ label('OK'), callback(t(LIST-ok)) ],
  767	
  768	CANCEL= cuCommand / [
  769	  fromVert(OK), label('Cancel'), callback(t(LIST-cancel))
  770	],
  771
  772	viewport / [
  773	  fromHoriz(CANCEL),
  774	  forceBars(true), allowVert(true),
  775	  height(100), width(200)
  776	] - [
  777	  LIST= list / [
  778	    list(Items), 
  779	    borderWidth(0), 
  780	    forceColumns(true)			% show the initial two columns
  781	  ] + [
  782	    LIST wproc highlight(0),		% highlight first item
  783	    xt_parse([btn(down) : 'Set',
  784		      btn(up)*2 : term(t(LIST-ok)) ], Tr),
  785	    override_translations(Tr)
  786	  ]
  787	]
  788      ]
  789    ]
  790  ].
  791
  792:- set_prolog_flag(swi_apeal,false).