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