~ubuntu-branches/debian/sid/ocaml/sid

« back to all changes in this revision

Viewing changes to ocamlbuild/lexers.mll

  • Committer: Bazaar Package Importer
  • Author(s): Stéphane Glondu
  • Date: 2011-04-21 21:35:08 UTC
  • mfrom: (1.1.11 upstream) (12.1.14 sid)
  • Revision ID: james.westby@ubuntu.com-20110421213508-kg34453aqmb0moha
* Fixes related to -output-obj with g++ (in debian/patches):
  - add Declare-primitive-name-table-as-const-char
  - add Avoid-multiple-declarations-in-generated-.c-files-in
  - fix Embed-bytecode-in-C-object-when-using-custom: the closing
    brace for extern "C" { ... } was missing in some cases

Show diffs side-by-side

added added

removed removed

Lines of Context:
17
17
 
18
18
type conf_values =
19
19
  { plus_tags   : string list;
20
 
    minus_tags  : string list;
21
 
    plus_flags  : (string * string) list;
22
 
    minus_flags : (string * string) list }
 
20
    minus_tags  : string list }
23
21
 
24
22
type conf = (Glob.globber * conf_values) list
25
23
 
26
 
let empty = { plus_flags = []; minus_flags = []; plus_tags = []; minus_tags = [] }
 
24
let empty = { plus_tags = []; minus_tags = [] }
27
25
}
28
26
 
29
27
let newline = ('\n' | '\r' | "\r\n")
36
34
let not_newline_nor_colon = [^ '\n' '\r' ':' ]
37
35
let normal_flag_value = [^ '(' ')' '\n' '\r']
38
36
let normal = [^ ':' ',' '(' ')' ''' ' ' '\n' '\r']
39
 
let tag = normal+ | ( normal+ ':' normal+ )
40
 
let flag_name = normal+
41
 
let flag_value = normal_flag_value+
 
37
let tag = normal+ | ( normal+ ':' normal+ ) | normal+ '(' [^ ')' ]* ')'
42
38
let variable = [ 'a'-'z' 'A'-'Z' '_' '-' '0'-'9' ]*
43
39
let pattern = ([^ '(' ')' '\\' ] | '\\' [ '(' ')' ])*
44
40
 
85
81
  | space* eof { [] }
86
82
  | _ { raise (Error "Expecting (comma|blank)-separated strings (2)") }
87
83
 
88
 
and colon_sep_strings = parse
89
 
  | ([^ ':']+ as word) eof { [word] }
90
 
  | ([^ ':']+ as word) { word :: colon_sep_strings_aux lexbuf }
91
 
  | eof { [] }
92
 
  | _ { raise (Error "Expecting colon-separated strings (1)") }
93
 
and colon_sep_strings_aux = parse
94
 
  | ':'+ ([^ ':']+ as word) { word :: colon_sep_strings_aux lexbuf }
95
 
  | eof { [] }
96
 
  | _ { raise (Error "Expecting colon-separated strings (2)") }
 
84
and parse_environment_path = parse
 
85
  | ([^ ':']* as word) { word :: parse_environment_path_aux lexbuf }
 
86
  | ':' ([^ ':']* as word) { "" :: word :: parse_environment_path_aux lexbuf }
 
87
  | eof { [] }
 
88
and parse_environment_path_aux = parse
 
89
  | ':' ([^ ':']* as word) { word :: parse_environment_path_aux lexbuf }
 
90
  | eof { [] }
 
91
  | _ { raise (Error "Impossible: expecting colon-separated strings") }
97
92
 
98
93
and conf_lines dir pos err = parse
99
94
  | space* '#' not_newline* newline { conf_lines dir (pos + 1) err lexbuf }
110
105
  | _ { raise (Error(Printf.sprintf "Bad key in configuration line at line %d (from %s)" pos err)) }
111
106
 
112
107
and conf_value pos err x = parse
113
 
  | '-'  (flag_name as t1) '(' (flag_value as t2) ')' { { (x) with minus_flags = (t1, t2) :: x.minus_flags } }
114
 
  | '+'? (flag_name as t1) '(' (flag_value as t2) ')' { { (x) with plus_flags = (t1, t2) :: x.plus_flags } }
115
108
  | '-'  (tag as tag) { { (x) with minus_tags = tag :: x.minus_tags } }
116
109
  | '+'? (tag as tag) { { (x) with plus_tags = tag :: x.plus_tags } }
117
110
  | (_ | eof) { raise (Error(Printf.sprintf "Bad value in configuration line at line %d (from %s)" pos err)) }
143
136
  | '\\' (['(' ')'] as c)        { c :: unescape lexbuf }
144
137
  | _ as c                       { c :: unescape lexbuf }
145
138
  | eof                          { [] }
 
139
 
 
140
and ocamlfind_query = parse
 
141
  | newline*
 
142
    "package:" space* (not_newline* as n) newline+
 
143
    "description:" space* (not_newline* as d) newline+
 
144
    "version:" space* (not_newline* as v) newline+
 
145
    "archive(s):" space* (not_newline* as a) newline+
 
146
    "linkopts:" space* (not_newline* as lo) newline+
 
147
    "location:" space* (not_newline* as l) newline+
 
148
    { n, d, v, a, lo, l }
 
149
  | _ { raise (Error "Bad ocamlfind query") }
 
150
 
 
151
and trim_blanks = parse
 
152
  | blank* (not_blank* as word) blank* { word }
 
153
  | _ { raise (Error "Bad input for trim_blanks") }
 
154
 
 
155
and tag_gen = parse
 
156
  | (normal+ as name) ('(' ([^')']* as param) ')')? { name, param }