Skip to content

Commit

Permalink
Add the -no-g option to ocamlc and ocamlopt (#11696)
Browse files Browse the repository at this point in the history
  • Loading branch information
Abiola-Zeenat committed Nov 18, 2022
1 parent d979990 commit 5360277
Show file tree
Hide file tree
Showing 6 changed files with 24 additions and 1 deletion.
4 changes: 4 additions & 0 deletions Changes
Original file line number Diff line number Diff line change
Expand Up @@ -155,6 +155,10 @@ Working version
- #11653: Add the -no-absname option to ocamlc, ocamlopt and ocamldep.
(Abiola Abdulsalam, review by Sébastien Hinderer and Florian Angeletti)

- #11696: Add the -no-g option to ocamlc and ocamlopt.
(Abiola Abdulsalam, review by Sébastien Hinderer, Nicolás Ojeda Bär and
Florian Angeletti)

### Internal/compiler-libs changes:
- #11027: Separate typing counter-examples from type_pat into retype_pat;
type_pat is no longer in CPS.
Expand Down
9 changes: 8 additions & 1 deletion driver/main_args.ml
Original file line number Diff line number Diff line change
Expand Up @@ -138,6 +138,10 @@ let mk_g_byt f =
let mk_g_opt f =
"-g", Arg.Unit f, " Record debugging information for exception backtrace"

let mk_no_g f =
"-no-g", Arg.Unit f,
" Do not record debugging information (default)"

let mk_i f =
"-i", Arg.Unit f, " Print inferred interface"

Expand Down Expand Up @@ -816,6 +820,7 @@ module type Compiler_options = sig
val _config_var : string -> unit
val _for_pack : string -> unit
val _g : unit -> unit
val _no_g : unit -> unit
val _stop_after : string -> unit
val _i : unit -> unit
val _impl : string -> unit
Expand Down Expand Up @@ -847,7 +852,6 @@ module type Compiler_options = sig
val _where : unit -> unit
val _color : string -> unit
val _error_style : string -> unit

val _match_context_rows : int -> unit
val _dtimings : unit -> unit
val _dprofile : unit -> unit
Expand Down Expand Up @@ -1017,6 +1021,7 @@ struct
mk_dtypes F._annot;
mk_for_pack_byt F._for_pack;
mk_g_byt F._g;
mk_no_g F._no_g;
mk_stop_after ~native:false F._stop_after;
mk_i F._i;
mk_I F._I;
Expand Down Expand Up @@ -1206,6 +1211,7 @@ struct
mk_dtypes F._annot;
mk_for_pack_opt F._for_pack;
mk_g_opt F._g;
mk_no_g F._no_g;
mk_function_sections F._function_sections;
mk_stop_after ~native:true F._stop_after;
mk_save_ir_after ~native:true F._save_ir_after;
Expand Down Expand Up @@ -1725,6 +1731,7 @@ module Default = struct
let _dump_dir s = dump_dir := Some s
let _for_pack s = for_package := (Some s)
let _g = set debug
let _no_g = clear debug
let _i = set print_types
let _impl = Compenv.impl
let _intf = Compenv.intf
Expand Down
1 change: 1 addition & 0 deletions driver/main_args.mli
Original file line number Diff line number Diff line change
Expand Up @@ -85,6 +85,7 @@ module type Compiler_options = sig
val _config_var : string -> unit
val _for_pack : string -> unit
val _g : unit -> unit
val _no_g : unit -> unit
val _stop_after : string -> unit
val _i : unit -> unit
val _impl : string -> unit
Expand Down
3 changes: 3 additions & 0 deletions man/ocamlc.1
Original file line number Diff line number Diff line change
Expand Up @@ -391,6 +391,9 @@ required in order to be able to debug the program with
and to produce stack backtraces when
the program terminates on an uncaught exception.
.TP
.B \-no-g
Do not record debugging information (default).
.TP
.B \-i
Cause the compiler to print all defined names (with their inferred
types or their definitions) when compiling an implementation (.ml
Expand Down
3 changes: 3 additions & 0 deletions man/ocamlopt.1
Original file line number Diff line number Diff line change
Expand Up @@ -294,6 +294,9 @@ required in order to produce stack backtraces when
the program terminates on an uncaught exception (see
.BR ocamlrun (1)).
.TP
.B \-no-g
Do not record debugging information (default).
.TP
.B \-i
Cause the compiler to print all defined names (with their inferred
types or their definitions) when compiling an implementation (.ml
Expand Down
5 changes: 5 additions & 0 deletions manual/src/cmds/unified-options.etex
Original file line number Diff line number Diff line change
Expand Up @@ -259,6 +259,11 @@ the program terminates on an uncaught exception (see
section~\ref{s:ocamlrun-options}).
}%notop

\notop{%
\item["-no-g"]
Do not record debugging information (default).
}%notop

\notop{%
\item["-i"]
Cause the compiler to print all defined names (with their inferred
Expand Down

0 comments on commit 5360277

Please sign in to comment.