]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/ocamldoc/odoc_parser.mly
Inital import
[l4.git] / l4 / pkg / ocaml / contrib / ocamldoc / odoc_parser.mly
1 %{
2 (***********************************************************************)
3 (*                             OCamldoc                                *)
4 (*                                                                     *)
5 (*            Maxence Guesdon, projet Cristal, INRIA Rocquencourt      *)
6 (*                                                                     *)
7 (*  Copyright 2001 Institut National de Recherche en Informatique et   *)
8 (*  en Automatique.  All rights reserved.  This file is distributed    *)
9 (*  under the terms of the Q Public License version 1.0.               *)
10 (*                                                                     *)
11 (***********************************************************************)
12
13 (* $Id: odoc_parser.mly 5973 2003-11-24 10:44:07Z starynke $ *)
14
15 open Odoc_types
16 open Odoc_comments_global
17
18 let uppercase = "[A-Z\192-\214\216-\222]"
19 let identchar = 
20   "[A-Za-z_\192-\214\216-\246\248-\255'0-9]"
21 let blank = "[ \010\013\009\012]"
22
23 let print_DEBUG s = print_string s; print_newline ()
24 %}
25
26 %token <string * (string option)> Description
27
28 %token <string> See_url
29 %token <string> See_file
30 %token <string> See_doc
31
32 %token T_PARAM
33 %token T_AUTHOR
34 %token T_VERSION
35 %token T_SEE
36 %token T_SINCE
37 %token T_DEPRECATED
38 %token T_RAISES
39 %token T_RETURN
40 %token <string> T_CUSTOM
41
42 %token EOF
43
44 %token <string> Desc
45
46 /* Start Symbols */
47 %start main info_part2 see_info
48 %type <(string * (string option)) option> main
49 %type <unit> info_part2
50 %type <Odoc_types.see_ref * string> see_info
51
52
53 %%
54 see_info:
55   see_ref Desc { ($1, $2) }
56 ;
57
58 see_ref:
59     See_url { Odoc_types.See_url $1 }
60 | See_file { Odoc_types.See_file $1 }
61 | See_doc { Odoc_types.See_doc $1 }
62 ;
63
64 main:
65   Description { Some $1 }
66 | EOF { None }
67 ;
68
69 info_part2:
70   element_list EOF { () }
71 ;
72
73 element_list:
74   element { () }
75 | element element_list { () }
76 ;
77
78 element:
79 | param { () }
80 | author { () }
81 | version { () }
82 | see { () }
83 | since { () }
84 | deprecated { () }
85 | raise_exc { () }
86 | return { () }
87 | custom { () }
88 ;
89
90 param:
91     T_PARAM Desc
92     { 
93       (* isolate the identificator *)
94       (* we only look for simple id, no pattern nor tuples *)
95       let s = $2 in
96       match Str.split (Str.regexp (blank^"+")) s with
97         []
98       | _ :: [] ->
99           raise (Failure "usage: @param id description")
100       | id :: _ ->    
101           print_DEBUG ("Identificator "^id);
102           let reg = identchar^"+" in
103           print_DEBUG ("reg="^reg);
104           if Str.string_match (Str.regexp reg) id 0 then
105             let remain = String.sub s (String.length id) ((String.length s) - (String.length id)) in
106             print_DEBUG ("T_PARAM Desc remain="^remain);
107             let remain2 = Str.replace_first (Str.regexp ("^"^blank^"+")) "" remain in
108             params := !params @ [(id, remain2)] 
109           else
110             raise (Failure (id^" is not a valid parameter identificator in \"@param "^s^"\""))
111     }
112 ;
113 author:
114     T_AUTHOR Desc { authors := !authors @ [ $2 ] }
115 ;
116 version:
117     T_VERSION Desc { version := Some $2 }
118 ;
119 see:
120     T_SEE Desc { sees := !sees @ [$2] }
121 ;
122 since:
123     T_SINCE Desc { since := Some $2 }
124 ;
125 deprecated:
126     T_DEPRECATED Desc { deprecated := Some $2 }
127 ;
128 raise_exc:
129     T_RAISES Desc 
130     { 
131       (* isolate the exception construtor name *)
132       let s = $2 in
133       match Str.split (Str.regexp (blank^"+")) s with
134         []
135       | _ :: [] ->
136           raise (Failure "usage: @raise Exception description")
137       | id :: _ ->    
138           print_DEBUG ("exception "^id);
139           let reg = uppercase^identchar^"*"^"\\(\\."^uppercase^identchar^"*\\)*" in
140           print_DEBUG ("reg="^reg);
141           if Str.string_match (Str.regexp reg) id 0 then
142             let remain = String.sub s (String.length id) ((String.length s) - (String.length id)) in
143             let remain2 = Str.replace_first (Str.regexp ("^"^blank^"+")) "" remain in
144             raised_exceptions := !raised_exceptions @ [(id, remain2)] 
145           else
146             raise (Failure (id^" is not a valid exception constructor in \"@raise "^s^"\""))
147     } 
148 ;
149 return:
150     T_RETURN Desc { return_value := Some $2 }
151 ;
152
153 custom:
154     T_CUSTOM Desc { customs := !customs @ [($1, $2)] }
155 ;
156
157
158 %%