]> matita.cs.unibo.it Git - helm.git/blob - helm/DEVEL/gdome_xslt/ocaml/gdome_xslt/ml_gdome_xslt.c
Initial version.
[helm.git] / helm / DEVEL / gdome_xslt / ocaml / gdome_xslt / ml_gdome_xslt.c
1 /* This file is part of an ocaml binding of an XSLT engine working on Gdome
2  * documents.
3  * 
4  * The code is largely based on the code of T.J. Mather's XML::GDOME::XSLT
5  * Perl module (http://kobesearch.cpan.org/search?dist=XML-GDOME-XSLT)
6  *
7  * Copyright (C) 2002 Claudio Sacerdoti Coen <sacerdot@cs.unibo.it>
8  * 
9  * This library is free software; you can redistribute it and/or
10  * modify it under the terms of the GNU Lesser General Public
11  * License as published by the Free Software Foundation; either
12  * version 2.1 of the License, or (at your option) any later version.
13  * 
14  * This library is distributed in the hope that it will be useful,
15  * but WITHOUT ANY WARRANTY; without even the implied warranty of
16  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17  * Lesser General Public License for more details.
18  * 
19  * You should have received a copy of the GNU Lesser General Public
20  * License along with this library; if not, write to the Free Software
21  * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
22  *
23  * For more information, please send an email to <sacerdot@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 <libxslt/xsltconfig.h>
33 #include <libxslt/imports.h>
34
35 #include "mlgdomevalue.h"
36 #include "gdome_xslt.h"
37
38 xsltStylesheetPtr XsltStylesheetPtr_val(value);
39
40 static void ml_xsltFreeStylesheet(value v)
41 {
42    xsltFreeStylesheet(XsltStylesheetPtr_val(v));
43 }
44
45 xsltStylesheetPtr XsltStylesheetPtr_val(value v)
46 {
47    CAMLparam1(v);
48    xsltStylesheetPtr res = *((xsltStylesheetPtr*) Data_custom_val(v));
49    CAMLreturn(res);
50 }
51
52 value Val_XsltStylesheetPtr(xsltStylesheetPtr obj)
53 {
54    CAMLparam0();
55    CAMLlocal1(v);
56    static struct custom_operations ops = {
57       "http://www.cs.unibo.it/helm/gdome_xslt/XsltStylesheetPtr",
58       ml_xsltFreeStylesheet,
59       custom_compare_default,
60       custom_hash_default,
61       custom_serialize_default,
62       custom_deserialize_default
63    };
64
65    v = alloc_custom(&ops, sizeof(xsltStylesheetPtr), 0, 1);
66    *((xsltStylesheetPtr*) Data_custom_val(v)) = obj;
67
68    CAMLreturn(v);
69 }
70
71 value ml_processStylesheet(value style)
72 {
73    CAMLparam1(style);
74    xsltStylesheetPtr res;
75    res = processStylesheet(Document_val(style));
76    if (res == NULL) {
77       value* excp;
78       excp = caml_named_value("ProcessStylesheetException");
79       assert(excp != NULL);
80       raise_constant(*excp);
81    }
82    CAMLreturn(Val_XsltStylesheetPtr(res));
83 }
84
85 value setXsltMaxDepth(value depth)
86 {
87    CAMLparam1(depth);
88    xsltMaxDepth = Int_val(depth);
89    CAMLreturn0;
90 }
91
92 value ml_applyStylesheet(value source, value style, value params)
93 {
94    CAMLparam3(source,style,params);
95    CAMLlocal1(list);
96    GdomeDocument* res;
97    int i;
98    const char** c_params;
99
100    i = 0 ; list = params;
101    while(list != Val_int(0)) {
102       list = Field(list,1);
103       i++;
104    }
105    c_params = (const char **)malloc(sizeof(char *) * (i * 2 + 1));
106
107    i = 0; list = params;
108    while(list != Val_int(0)) {
109       c_params[i]   = String_val(Field(Field(list,0),0));
110       c_params[i+1] = String_val(Field(Field(list,0),1));
111       list = Field(list,1);
112       i+=2;
113    }
114    c_params[i] = NULL;
115    res = applyStylesheet(Document_val(source),
116                          XsltStylesheetPtr_val(style),
117                          c_params);
118    free(c_params);
119    if (res == NULL) {
120       value* excp;
121       excp = caml_named_value("ApplyStylesheetException");
122       assert(excp != NULL);
123       raise_constant(*excp);
124    }
125    CAMLreturn(Val_Document(res));
126 }