character set difference
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@6269 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
01f0a146e8
commit
5040085fe2
|
@ -11,6 +11,9 @@
|
|||
(* *)
|
||||
(***********************************************************************)
|
||||
|
||||
(* $Id$ *)
|
||||
|
||||
|
||||
exception Bad
|
||||
|
||||
type t = (int * int) list
|
||||
|
|
|
@ -11,9 +11,12 @@
|
|||
(* *)
|
||||
(***********************************************************************)
|
||||
|
||||
(* $Id$ *)
|
||||
|
||||
(* Set of characters encoded as list of intervals *)
|
||||
|
||||
type t
|
||||
exception Bad
|
||||
|
||||
val empty : t
|
||||
val is_empty : t -> bool
|
||||
|
|
|
@ -186,6 +186,7 @@ rule main = parse
|
|||
| ')' { Trparen }
|
||||
| '^' { Tcaret }
|
||||
| '-' { Tdash }
|
||||
| '#' { Tsharp }
|
||||
| eof { Tend }
|
||||
| _
|
||||
{ raise_lexical_error lexbuf
|
||||
|
|
|
@ -79,7 +79,13 @@ let main () =
|
|||
Common.close_tracker tr;
|
||||
Sys.remove dest_name;
|
||||
begin match exn with
|
||||
Parsing.Parse_error ->
|
||||
| Cset.Bad ->
|
||||
let p = Lexing.lexeme_start_p lexbuf in
|
||||
Printf.fprintf stderr
|
||||
"File \"%s\", line %d, character %d: character set expected.\n"
|
||||
p.Lexing.pos_fname p.Lexing.pos_lnum
|
||||
(p.Lexing.pos_cnum - p.Lexing.pos_bol)
|
||||
| Parsing.Parse_error ->
|
||||
let p = Lexing.lexeme_start_p lexbuf in
|
||||
Printf.fprintf stderr
|
||||
"File \"%s\", line %d, character %d: syntax error.\n"
|
||||
|
|
|
@ -40,6 +40,10 @@ let rec remove_as = function
|
|||
| Alternative (e1, e2) -> Alternative (remove_as e1, remove_as e2)
|
||||
| Repetition e -> Repetition (remove_as e)
|
||||
|
||||
let as_cset = function
|
||||
| Characters s -> s
|
||||
| _ -> raise Cset.Bad
|
||||
|
||||
%}
|
||||
|
||||
%token <string> Tident
|
||||
|
@ -47,9 +51,10 @@ let rec remove_as = function
|
|||
%token <string> Tstring
|
||||
%token <Syntax.location> Taction
|
||||
%token Trule Tparse Tparse_shortest Tand Tequal Tend Tor Tunderscore Teof Tlbracket Trbracket
|
||||
%token Tstar Tmaybe Tplus Tlparen Trparen Tcaret Tdash Tlet Tas
|
||||
%token Tstar Tmaybe Tplus Tlparen Trparen Tcaret Tdash Tlet Tas Tsharp
|
||||
|
||||
%right Tas
|
||||
%left Tsharp
|
||||
%left Tor
|
||||
%nonassoc CONCAT
|
||||
%nonassoc Tmaybe Tstar Tplus
|
||||
|
@ -131,6 +136,12 @@ regexp:
|
|||
{ Alternative(Epsilon, $1) }
|
||||
| regexp Tplus
|
||||
{ Sequence(Repetition (remove_as $1), $1) }
|
||||
| regexp Tsharp regexp
|
||||
{
|
||||
let s1 = as_cset $1
|
||||
and s2 = as_cset $3 in
|
||||
Characters (Cset.diff s1 s2)
|
||||
}
|
||||
| regexp Tor regexp
|
||||
{ Alternative($1,$3) }
|
||||
| regexp regexp %prec CONCAT
|
||||
|
|
Loading…
Reference in New Issue