34
35:- module(editor_buttons, []). 36:- use_module(pce_boot(pce_principal)). 37:- use_module(pce_boot(pce_realise),
38 [ pce_register_class/1,
39 pce_begin_class_definition/4
40 ]). 41
42make_editor_recogniser(G) :-
43 new(Editor, @event?receiver),
44 new(G, handler_group(new(select_editor_text_gesture),
45 click_gesture(middle, '', single,
46 and(message(Editor, paste, primary),
47 message(Editor, mark_undo))))).
48
54
55:- pce_begin_class(select_editor_text_gesture, gesture,
56 ).
57
58variable(selecting, bool := @off, get, ).
59variable(down_position, point*, get, ).
60variable(origin, int*, get, ).
61variable(unit, {character,word,line}, get, ).
62variable(editor, editor*, get, ).
63
64initialise(G) :->
65 send_super(G, initialise),
66 send(G, slot, unit, character),
67 send(G, drag_scroll, self).
68
69
70initiate(G, Ev:event) :->
71 ::
72 send(G, slot, down_position, Ev?position),
73 get(Ev, receiver, Editor),
74 send(G, slot, editor, Editor),
75 get(Editor, image, Image),
76 get(Image, index, Ev, Index),
77 send(Editor, caret, Index),
78 get(Ev, multiclick, Multi),
79 selection_unit(Multi, Unit),
80 send(G, slot, unit, Unit),
81 ( Multi == single
82 -> send(G, slot, origin, Index),
83 send(G, selecting, @off)
84 ; send(G, selecting, @on)
85 ).
86
87selection_unit(single, character).
88selection_unit(double, word).
89selection_unit(triple, line).
90
91
92selecting(G, Val:bool) :->
93 ::
94 send(G, slot, selecting, Val),
95 get(G, editor, Editor),
96 ( Val == @on
97 -> get(G, origin, Origin), Origin \== @nil,
98 send(Editor, selection_unit, G?unit),
99 send(Editor, selection_origin, Origin)
100 ; send(Editor, mark_status, inactive)
101 ).
102
103
104drag(G, Ev:event) :->
105 ::
106 ( ( get(G, selecting, @on)
107 -> true
108 ; get(G, down_position, DownPos),
109 get(Ev, position, EvPos),
110 get(DownPos, distance, EvPos, D),
111 D > 25
112 -> send(G, selecting, @on)
113 )
114 -> get(Ev, receiver, Editor),
115 get(Editor, image, Image),
116 ( get(Image, index, Ev, Index)
117 -> send(Editor, selection_extend, Index)
118 ; true
119 )
120 ; true
121 ).
122
123terminate(G, _Ev:event) :->
124 ::
125 get(G, editor, Editor),
126 send(G, slot, editor, @nil),
127 ( get(G, selecting, @on),
128 get(Editor, class_variable_value, auto_copy, @on)
129 -> send(Editor, copy)
130 ; true
131 ).
132
133:- pce_end_class.
134
135:- free(@editor_recogniser). 136:- initialization
137 make_editor_recogniser(@editor_recogniser).