summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorPierre Weis <Pierre.Weis@inria.fr>2011-10-28 21:21:55 +0000
committerPierre Weis <Pierre.Weis@inria.fr>2011-10-28 21:21:55 +0000
commit87946c9536441f7af6a594b32bb2a17d19abd374 (patch)
tree22e8ea32a54e9be5a4807acdde8ae7b4dc27a3b4
parent4e63dbfff352834a34046f4c2cb4addaf2533861 (diff)
Get rid of spurious warnings
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@11252 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--parsing/lexer.mll2
-rw-r--r--parsing/longident.ml6
-rw-r--r--parsing/parser.mly13
3 files changed, 11 insertions, 10 deletions
diff --git a/parsing/lexer.mll b/parsing/lexer.mll
index 20af0fb31..87e2a8cbc 100644
--- a/parsing/lexer.mll
+++ b/parsing/lexer.mll
@@ -416,7 +416,7 @@ and comment = parse
| "*)"
{ match !comment_start_loc with
| [] -> assert false
- | [x] -> comment_start_loc := [];
+ | [_] -> comment_start_loc := [];
| _ :: l -> comment_start_loc := l;
comment lexbuf;
}
diff --git a/parsing/longident.ml b/parsing/longident.ml
index 1114a2ef5..612f9df19 100644
--- a/parsing/longident.ml
+++ b/parsing/longident.ml
@@ -20,14 +20,14 @@ type t =
let rec flat accu = function
Lident s -> s :: accu
| Ldot(lid, s) -> flat (s :: accu) lid
- | Lapply(l1, l2) -> Misc.fatal_error "Longident.flat"
+ | Lapply(_, _) -> Misc.fatal_error "Longident.flat"
let flatten lid = flat [] lid
let last = function
Lident s -> s
- | Ldot(lid, s) -> s
- | Lapply(l1, l2) -> Misc.fatal_error "Longident.last"
+ | Ldot(_, s) -> s
+ | Lapply(_, _) -> Misc.fatal_error "Longident.last"
let rec split_at_dots s pos =
try
diff --git a/parsing/parser.mly b/parsing/parser.mly
index bd0e373b6..f69284d8c 100644
--- a/parsing/parser.mly
+++ b/parsing/parser.mly
@@ -70,8 +70,9 @@ let ghtyp d = { ptyp_desc = d; ptyp_loc = symbol_gloc () };;
let mkassert e =
match e with
- | {pexp_desc = Pexp_construct (Lident "false", None, false) } ->
- mkexp (Pexp_assertfalse)
+ | { pexp_desc = Pexp_construct (Lident "false", None, false);
+ pexp_loc = _ } ->
+ mkexp (Pexp_assertfalse)
| _ -> mkexp (Pexp_assert (e))
;;
@@ -93,7 +94,7 @@ let mkuminus name arg =
mkexp(Pexp_constant(Const_int64(Int64.neg n)))
| "-", Pexp_constant(Const_nativeint n) ->
mkexp(Pexp_constant(Const_nativeint(Nativeint.neg n)))
- | ("-" | "-."), Pexp_constant(Const_float f) ->
+ | _, Pexp_constant(Const_float f) ->
mkexp(Pexp_constant(Const_float(neg_float_string f)))
| _ ->
mkexp(Pexp_apply(mkoperator ("~" ^ name) 1, ["", arg]))
@@ -160,7 +161,7 @@ let bigarray_function str name =
Ldot(Ldot(Lident "Bigarray", str), name)
let bigarray_untuplify = function
- { pexp_desc = Pexp_tuple explist} -> explist
+ { pexp_desc = Pexp_tuple explist; pexp_loc = _ } -> explist
| exp -> [exp]
let bigarray_get arr arg =
@@ -588,7 +589,7 @@ structure_tail:
structure_item:
LET rec_flag let_bindings
{ match $3 with
- [{ppat_desc = Ppat_any}, exp] -> mkstr(Pstr_eval exp)
+ [{ ppat_desc = Ppat_any; ppat_loc = _ }, exp] -> mkstr(Pstr_eval exp)
| _ -> mkstr(Pstr_value($2, List.rev $3)) }
| EXTERNAL val_ident COLON core_type EQUAL primitive_declaration
{ mkstr(Pstr_primitive($2, {pval_type = $4; pval_prim = $6})) }
@@ -1386,7 +1387,7 @@ type_declaration:
ptype_private = private_flag;
ptype_manifest = manifest;
ptype_variance = variance;
- ptype_loc = symbol_rloc()}) }
+ ptype_loc = symbol_rloc() }) }
;
constraints:
constraints CONSTRAINT constrain { $3 :: $1 }