]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/ocaml/contrib/driver/opterrors.ml
Update
[l4.git] / l4 / pkg / ocaml / ocaml / contrib / driver / opterrors.ml
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: opterrors.ml 8705 2007-12-04 13:38:58Z doligez $ *)
14
15 (* WARNING: if you change something in this file, you must look at
16    errors.ml to see if you need to make the same changes there.
17 *)
18
19 open Format
20
21 (* Report an error *)
22
23 let report_error ppf exn =
24   let report ppf = function
25   | Lexer.Error(err, l) ->
26       Location.print_error ppf l;
27       Lexer.report_error ppf err
28   | Syntaxerr.Error err ->
29       Syntaxerr.report_error ppf err
30   | Pparse.Error ->
31       Location.print_error_cur_file ppf;
32       fprintf ppf "Preprocessor error"
33   | Env.Error err ->
34       Location.print_error_cur_file ppf;
35       Env.report_error ppf err
36   | Ctype.Tags(l, l') ->
37       Location.print_error_cur_file ppf;
38       fprintf ppf
39       "In this program,@ variant constructors@ `%s and `%s@ \
40        have the same hash value.@ Change one of them." l l'
41   | Typecore.Error(loc, err) ->
42       Location.print_error ppf loc; Typecore.report_error ppf err
43   | Typetexp.Error(loc, err) ->
44       Location.print_error ppf loc; Typetexp.report_error ppf err
45   | Typedecl.Error(loc, err) ->
46       Location.print_error ppf loc; Typedecl.report_error ppf err
47   | Typeclass.Error(loc, err) ->
48       Location.print_error ppf loc; Typeclass.report_error ppf err
49   | Includemod.Error err ->
50       Location.print_error_cur_file ppf;
51       Includemod.report_error ppf err
52   | Typemod.Error(loc, err) ->
53       Location.print_error ppf loc; Typemod.report_error ppf err
54   | Translcore.Error(loc, err) ->
55       Location.print_error ppf loc; Translcore.report_error ppf err
56   | Translclass.Error(loc, err) ->
57       Location.print_error ppf loc; Translclass.report_error ppf err
58   | Translmod.Error(loc, err) ->
59       Location.print_error ppf loc; Translmod.report_error ppf err
60   | Compilenv.Error code ->
61       Location.print_error_cur_file ppf;
62       Compilenv.report_error ppf code
63   | Asmgen.Error code ->
64       Location.print_error_cur_file ppf;
65       Asmgen.report_error ppf code
66   | Asmlink.Error code ->
67       Location.print_error_cur_file ppf;
68       Asmlink.report_error ppf code
69   | Asmlibrarian.Error code ->
70       Location.print_error_cur_file ppf;
71       Asmlibrarian.report_error ppf code
72   | Asmpackager.Error code ->
73       Location.print_error_cur_file ppf;
74       Asmpackager.report_error ppf code
75   | Sys_error msg ->
76       Location.print_error_cur_file ppf;
77       fprintf ppf "I/O error: %s" msg
78   | Warnings.Errors (n) ->
79       Location.print_error_cur_file ppf;
80       fprintf ppf "Error-enabled warnings (%d occurrences)" n
81   | x -> fprintf ppf "@]"; raise x in
82
83   fprintf ppf "@[%a@]@." report exn