]> matita.cs.unibo.it Git - helm.git/blob - helm/DEVEL/mathml_editor/ocaml/ml_mathml_editor.c
* licenses updated
[helm.git] / helm / DEVEL / mathml_editor / ocaml / ml_mathml_editor.c
1 /* This file is part of EdiTeX, an editor of mathematical
2  * expressions based on TeX syntax.
3  * 
4  * Copyright (C) 2002-2003 Luca Padovani <lpadovan@cs.unibo.it>,
5  *                    2003 Paolo Marinelli <pmarinel@cs.unibo.it>.
6  *
7  * This library is free software; you can redistribute it and/or
8  * modify it under the terms of the GNU Lesser General Public
9  * License as published by the Free Software Foundation; either
10  * version 2.1 of the License, or (at your option) any later version.
11  *
12  * This library is distributed in the hope that it will be useful,
13  * but WITHOUT ANY WARRANTY; without even the implied warranty of
14  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
15  * Lesser General Public License for more details.
16  *
17  * You should have received a copy of the GNU Lesser General Public
18  * License along with this library; if not, write to the Free Software
19  * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
20  *
21  * For more information, please visit the project's home page
22  * http://helm.cs.unibo.it/editex/
23  * or send an email to <lpadovan@cs.unibo.it>
24  */
25
26 #include <assert.h>
27
28 #include <caml/memory.h>
29 #include <caml/custom.h>
30 #include <caml/callback.h>
31
32 #include "mlgdomevalue.h"
33
34 #include "c_mathml_editor.h"
35
36 typedef struct
37 {
38   Editor* c_editor;
39   value   callback;
40 } ml_Editor;
41
42 ml_Editor*
43 Editor_val(value v)
44 {
45   ml_Editor* editor = *((ml_Editor**) Data_custom_val(v));
46   assert(editor != NULL);
47   return editor;
48 }
49
50 static void
51 ml_mathml_editor_finalize(value v)
52 {
53   ml_Editor* editor = Editor_val(v);
54   assert(editor);
55
56   remove_global_root(&editor->callback);
57   c_mathml_editor_destroy(editor->c_editor);
58   free(editor);
59 }
60
61 void
62 ml_mathml_editor_log_callback(int level, const char* msg, void* user_data)
63 {
64   ml_Editor* ml_editor = (ml_Editor*) user_data;
65   assert(ml_editor);
66   callback2(ml_editor->callback, Val_int(level), copy_string(msg));
67 }
68
69 value
70 ml_mathml_editor_new(value dictionary,
71                      value tml_mml,
72                      value tml_tex,
73                      value log_message_cb)
74 {
75   static struct custom_operations ops =
76   {
77     "HELM/MathML Editor",
78     ml_mathml_editor_finalize,
79     custom_compare_default,
80     custom_hash_default,
81     custom_serialize_default,
82     custom_deserialize_default
83   };
84   
85   value v = alloc_custom(&ops, sizeof(ml_Editor*), 0, 1);
86   ml_Editor** ml_editor_ref = (ml_Editor**) Data_custom_val(v);
87   ml_Editor* ml_editor = *ml_editor_ref = malloc(sizeof(ml_Editor));
88   ml_editor->c_editor = c_mathml_editor_new(Document_val(dictionary),
89                                             Document_val(tml_mml),
90                                             Document_val(tml_tex),
91                                             ml_mathml_editor_log_callback,
92                                             (void*) ml_editor);
93   ml_editor->callback = log_message_cb;
94   register_global_root(&ml_editor->callback);
95
96   return v;
97 }
98
99 value
100 ml_mathml_editor_freeze(value v)
101 {
102   CAMLparam1(v);
103   ml_Editor* editor = Editor_val(v);
104   CAMLreturn(Val_bool(c_mathml_editor_freeze(editor->c_editor)));
105 }
106
107 value
108 ml_mathml_editor_thaw(value v)
109 {
110   CAMLparam1(v);
111   ml_Editor* editor = Editor_val(v);
112   CAMLreturn(Val_bool(c_mathml_editor_thaw(editor->c_editor)));
113 }
114
115 value
116 ml_mathml_editor_push(value v, value ch)
117 {
118   CAMLparam2(v, ch);
119   ml_Editor* editor = Editor_val(v);
120   c_mathml_editor_push(editor->c_editor, Int_val(ch));
121   CAMLreturn(Val_unit);
122 }
123
124 value
125 ml_mathml_editor_drop(value v, value alt)
126 {
127   CAMLparam2(v, alt);
128   ml_Editor* editor = Editor_val(v);
129   c_mathml_editor_drop(editor->c_editor, Bool_val(alt));
130   CAMLreturn(Val_unit);
131 }
132
133 value
134 ml_mathml_editor_cursor_hide(value v)
135 {
136   CAMLparam1(v);
137   ml_Editor* editor = Editor_val(v);
138   CAMLreturn(Val_bool(c_mathml_editor_cursor_hide(editor->c_editor)));
139 }
140
141 value
142 ml_mathml_editor_cursor_show(value v)
143 {
144   CAMLparam1(v);
145   ml_Editor* editor = Editor_val(v);
146   CAMLreturn(Val_bool(c_mathml_editor_cursor_show(editor->c_editor)));
147 }
148
149 value
150 ml_mathml_editor_get_tex(value v)
151 {
152   CAMLparam1(v);
153   ml_Editor* editor = Editor_val(v);
154   char* res = c_mathml_editor_get_tex(editor->c_editor);
155   CAMLlocal1(ml_res);
156   ml_res = copy_string(res);
157   free(res);
158   CAMLreturn(ml_res);
159 }
160
161 value
162 ml_mathml_editor_reset(value v, value s)
163 {
164   CAMLparam1(v);
165   ml_Editor* editor = Editor_val(v);
166   c_mathml_editor_reset(editor->c_editor);
167   CAMLreturn(Val_unit);
168 }
169
170 value
171 ml_mathml_editor_get_tml(value v)
172 {
173   CAMLparam1(v);
174   ml_Editor* editor = Editor_val(v);
175   GdomeDocument* doc = c_mathml_editor_get_tml(editor->c_editor);
176   CAMLreturn(Val_Document(doc));
177 }
178
179 value
180 ml_mathml_editor_get_mml(value v)
181 {
182   CAMLparam1(v);
183   ml_Editor* editor = Editor_val(v);
184   GdomeDocument* doc = c_mathml_editor_get_mml(editor->c_editor);
185   CAMLreturn(Val_Document(doc));
186 }
187