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

« back to all changes in this revision

Viewing changes to testsuite/tests/tool-lexyacc/input

  • 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:
 
1
(***********************************************************************)
 
2
(*                                                                     *)
 
3
(*                           Objective Caml                            *)
 
4
(*                                                                     *)
 
5
(*            Xavier Leroy, projet Cristal, INRIA Rocquencourt         *)
 
6
(*                                                                     *)
 
7
(*  Copyright 1996 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: scanner.mll,v 1.5 1999/11/17 18:58:39 xleroy Exp $ *)
 
14
 
 
15
(* The lexical analyzer for lexer definitions. *)
 
16
 
 
17
{
 
18
open Syntax
 
19
open Grammar
 
20
open Scan_aux
 
21
}
 
22
 
 
23
rule main = parse
 
24
    [' ' '\010' '\013' '\009' ] + 
 
25
    { main lexbuf }
 
26
  | "(*" 
 
27
    { comment_depth := 1;
 
28
      comment lexbuf;
 
29
      main lexbuf }
 
30
  | (['A'-'Z' 'a'-'z'] | '_' ['A'-'Z' 'a'-'z' '\'' '0'-'9'])
 
31
    ( '_' ? ['A'-'Z' 'a'-'z' ''' '0'-'9'] ) * 
 
32
    { match Lexing.lexeme lexbuf with
 
33
        "rule" -> Trule
 
34
      | "parse" -> Tparse
 
35
      | "and" -> Tand
 
36
      | "eof" -> Teof
 
37
      | s -> Tident s }
 
38
  | '"' 
 
39
    { reset_string_buffer();
 
40
      string lexbuf;
 
41
      Tstring(get_stored_string()) }
 
42
  | "'" 
 
43
    { Tchar(char lexbuf) }
 
44
  | '{' 
 
45
    { let n1 = Lexing.lexeme_end lexbuf in
 
46
        brace_depth := 1;
 
47
        let n2 = action lexbuf in
 
48
          Taction(Location(n1, n2)) }
 
49
  | '='  { Tequal }
 
50
  | ";;"  { Tend }
 
51
  | '|'  { Tor }
 
52
  | '_'  { Tunderscore }
 
53
  | "eof"  { Teof }
 
54
  | '['  { Tlbracket }
 
55
  | ']'  { Trbracket }
 
56
  | '*'  { Tstar }
 
57
  | '?'  { Tmaybe }
 
58
  | '+'  { Tplus }
 
59
  | '('  { Tlparen }
 
60
  | ')'  { Trparen }
 
61
  | '^'  { Tcaret }
 
62
  | '-'  { Tdash }
 
63
  | eof
 
64
    { raise(Lexical_error "unterminated lexer definition") }
 
65
  | _
 
66
    { raise(Lexical_error("illegal character " ^ Lexing.lexeme lexbuf)) }
 
67
 
 
68
and action = parse
 
69
    '{' 
 
70
    { incr brace_depth;
 
71
      action lexbuf }
 
72
  | '}' 
 
73
    { decr brace_depth;
 
74
      if !brace_depth = 0 then Lexing.lexeme_start lexbuf else action lexbuf }
 
75
  | '"' 
 
76
    { reset_string_buffer();
 
77
      string lexbuf;
 
78
      reset_string_buffer();
 
79
      action lexbuf }
 
80
  | '\''
 
81
    { let _ = char lexbuf in action lexbuf }
 
82
  | "(*" 
 
83
    { comment_depth := 1;
 
84
      comment lexbuf;
 
85
      action lexbuf }
 
86
  | eof 
 
87
    { raise (Lexical_error "unterminated action") }
 
88
  | _ 
 
89
    { action lexbuf }
 
90
      
 
91
and string = parse
 
92
    '"' 
 
93
    { () }
 
94
  | '\\' [' ' '\010' '\013' '\009' '\026' '\012'] +
 
95
    { string lexbuf }
 
96
  | '\\' ['\\' '"' 'n' 't' 'b' 'r'] 
 
97
    { store_string_char(char_for_backslash(Lexing.lexeme_char lexbuf 1));
 
98
      string lexbuf }
 
99
  | '\\' ['0'-'9'] ['0'-'9'] ['0'-'9'] 
 
100
    { store_string_char(char_for_decimal_code lexbuf 1);
 
101
      string lexbuf }
 
102
  | eof 
 
103
    { raise(Lexical_error "unterminated string") }
 
104
  | _ 
 
105
    { store_string_char(Lexing.lexeme_char lexbuf 0);
 
106
      string lexbuf }
 
107
 
 
108
and char = parse
 
109
    [^ '\\'] "'" 
 
110
    { Lexing.lexeme_char lexbuf 0 }
 
111
  | '\\' ['\\' '\'' 'n' 't' 'b' 'r'] "'" 
 
112
    { char_for_backslash (Lexing.lexeme_char lexbuf 1) }
 
113
  | '\\' ['0'-'9'] ['0'-'9'] ['0'-'9'] "'" 
 
114
    { char_for_decimal_code lexbuf 1 }
 
115
  | _ 
 
116
    { raise(Lexical_error "bad character constant") }
 
117
 
 
118
and comment = parse
 
119
    "(*" 
 
120
    { incr comment_depth; comment lexbuf }
 
121
  | "*)" 
 
122
    { decr comment_depth;
 
123
      if !comment_depth = 0 then () else comment lexbuf }
 
124
  | '"' 
 
125
    { reset_string_buffer();
 
126
      string lexbuf;
 
127
      reset_string_buffer();
 
128
      comment lexbuf }
 
129
  | eof 
 
130
    { raise(Lexical_error "unterminated comment") }
 
131
  | _ 
 
132
    { comment lexbuf }
 
133
;;