ocaml/utils/arg_helper.mli

69 lines
2.3 KiB
OCaml
Raw Permalink Normal View History

2016-01-14 03:34:49 -08:00
(**************************************************************************)
(* *)
(* OCaml *)
2016-01-14 03:34:49 -08:00
(* *)
2016-01-14 03:38:18 -08:00
(* Pierre Chambart, OCamlPro *)
(* Mark Shinwell and Leo White, Jane Street Europe *)
2016-01-14 03:34:49 -08:00
(* *)
2016-01-14 03:38:18 -08:00
(* Copyright 2015--2016 OCamlPro SAS *)
(* Copyright 2015--2016 Jane Street Group LLC *)
(* *)
(* All rights reserved. This file is distributed under the terms of *)
(* the GNU Lesser General Public License version 2.1, with the *)
(* special exception on linking described in the file LICENSE. *)
2016-01-14 03:34:49 -08:00
(* *)
(**************************************************************************)
(** Decipher command line arguments of the form
<value> | <key>=<value>[,...]
2016-01-14 03:34:49 -08:00
(as used for example for the specification of inlining parameters
varying by simplification round).
{b Warning:} this module is unstable and part of
{{!Compiler_libs}compiler-libs}.
2016-01-14 03:34:49 -08:00
*)
module Make (S : sig
module Key : sig
type t
(** The textual representation of a key must not contain '=' or ','. *)
val of_string : string -> t
module Map : Map.S with type key = t
end
module Value : sig
type t
2016-01-14 09:13:43 -08:00
(** The textual representation of a value must not contain ','. *)
2016-01-14 03:34:49 -08:00
val of_string : string -> t
end
end) : sig
2016-02-10 08:52:07 -08:00
type parsed
2016-01-14 03:34:49 -08:00
val default : S.Value.t -> parsed
2016-02-10 08:52:07 -08:00
val set_base_default : S.Value.t -> parsed -> parsed
val add_base_override : S.Key.t -> S.Value.t -> parsed -> parsed
val reset_base_overrides : parsed -> parsed
val set_user_default : S.Value.t -> parsed -> parsed
val add_user_override : S.Key.t -> S.Value.t -> parsed -> parsed
val parse : string -> string -> parsed ref -> unit
2016-01-14 03:34:49 -08:00
2016-01-14 09:13:43 -08:00
type parse_result =
| Ok
| Parse_failed of exn
val parse_no_error : string -> parsed ref -> parse_result
2016-01-14 09:13:43 -08:00
2016-01-14 03:34:49 -08:00
val get : key:S.Key.t -> parsed -> S.Value.t
end