Skip to content

Commit

Permalink
Make no_keep_locs a no-op
Browse files Browse the repository at this point in the history
It was deprecated in 2.0, now it just emits a warning that it does
nothing.

Signed-off-by: Rudi Grinberg <rudi.grinberg@gmail.com>
  • Loading branch information
rgrinberg committed Oct 15, 2019
1 parent 48d5aeb commit ada6596
Show file tree
Hide file tree
Showing 7 changed files with 12 additions and 30 deletions.
6 changes: 1 addition & 5 deletions src/dune/compilation_context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -49,7 +49,6 @@ type t =
; requires_link : Lib.t list Or_exn.t Lazy.t
; includes : Includes.t
; preprocessing : Preprocessing.t
; no_keep_locs : bool
; opaque : bool
; stdlib : Ocaml_stdlib.t option
; js_of_ocaml : Dune_file.Js_of_ocaml.t option
Expand Down Expand Up @@ -82,8 +81,6 @@ let includes t = t.includes

let preprocessing t = t.preprocessing

let no_keep_locs t = t.no_keep_locs

let opaque t = t.opaque

let stdlib t = t.stdlib
Expand All @@ -104,7 +101,7 @@ let context t = Super_context.context t.super_context

let create ~super_context ~scope ~expander ~obj_dir ~modules ~flags
~requires_compile ~requires_link ?(preprocessing = Preprocessing.dummy)
?(no_keep_locs = false) ~opaque ?stdlib ~js_of_ocaml ~dynlink ~package
~opaque ?stdlib ~js_of_ocaml ~dynlink ~package
?vimpl ?modes () =
let requires_compile =
if Dune_project.implicit_transitive_deps (Scope.project scope) then
Expand All @@ -131,7 +128,6 @@ let create ~super_context ~scope ~expander ~obj_dir ~modules ~flags
; requires_link
; includes = Includes.make ~opaque ~requires:requires_compile
; preprocessing
; no_keep_locs
; opaque
; stdlib
; js_of_ocaml
Expand Down
3 changes: 0 additions & 3 deletions src/dune/compilation_context.mli
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,6 @@ val create :
-> requires_compile:Lib.t list Or_exn.t
-> requires_link:Lib.t list Or_exn.t Lazy.t
-> ?preprocessing:Preprocessing.t
-> ?no_keep_locs:bool
-> opaque:bool
-> ?stdlib:Ocaml_stdlib.t
-> js_of_ocaml:Dune_file.Js_of_ocaml.t option
Expand Down Expand Up @@ -59,8 +58,6 @@ val includes : t -> Command.Args.dynamic Command.Args.t Cm_kind.Dict.t

val preprocessing : t -> Preprocessing.t

val no_keep_locs : t -> bool

val opaque : t -> bool

val stdlib : t -> Ocaml_stdlib.t option
Expand Down
13 changes: 8 additions & 5 deletions src/dune/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -825,7 +825,6 @@ module Library = struct
; dynlink : Dynlink_supported.t
; project : Dune_project.t
; sub_systems : Sub_system_info.t Sub_system_name.Map.t
; no_keep_locs : bool
; dune_version : Dune_lang.Syntax.Version.t
; virtual_modules : Ordered_set_lang.t option
; implements : (Loc.t * Lib_name.t) option
Expand Down Expand Up @@ -864,9 +863,14 @@ module Library = struct
located
(field "self_build_stubs_archive" (option string) ~default:None)
and+ no_dynlink = field_b "no_dynlink"
and+ no_keep_locs =
field_b "no_keep_locs"
~check:(Dune_lang.Syntax.deprecated_in Stanza.syntax (1, 7))
and+ () =
let check =
let+ loc = loc in
User_warning.emit ~loc
[ Pp.text "no_keep_locs is a no-op. Please delete it." ]
in
let+ _ = field_b "no_keep_locs" ~check in
()
and+ sub_systems =
let* () = return () in
Sub_system_info.record_parser ()
Expand Down Expand Up @@ -1015,7 +1019,6 @@ module Library = struct
; dynlink = Dynlink_supported.of_bool (not no_dynlink)
; project
; sub_systems
; no_keep_locs
; dune_version
; virtual_modules
; implements
Expand Down
1 change: 0 additions & 1 deletion src/dune/dune_file.mli
Original file line number Diff line number Diff line change
Expand Up @@ -209,7 +209,6 @@ module Library : sig
; dynlink : Dynlink_supported.t
; project : Dune_project.t
; sub_systems : Sub_system_info.t Sub_system_name.Map.t
; no_keep_locs : bool
; dune_version : Dune_lang.Syntax.Version.t
; virtual_modules : Ordered_set_lang.t option
; implements : (Loc.t * Lib_name.t) option
Expand Down
2 changes: 1 addition & 1 deletion src/dune/lib_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -300,7 +300,7 @@ let cctx (lib : Library.t) ~sctx ~source_modules ~dir ~expander ~scope
in
Compilation_context.create () ~super_context:sctx ~expander ~scope ~obj_dir
~modules ~flags ~requires_compile ~requires_link ~preprocessing:pp
~no_keep_locs:lib.no_keep_locs ~opaque
~opaque
~js_of_ocaml:(Some lib.buildable.js_of_ocaml) ~dynlink ?stdlib:lib.stdlib
~package:(Option.map lib.public ~f:(fun p -> p.package))
?vimpl ~modes
Expand Down
15 changes: 1 addition & 14 deletions src/dune/module_compilation.ml
Original file line number Diff line number Diff line change
Expand Up @@ -114,19 +114,7 @@ let build_cm cctx ~dep_graphs ~precompiled_cmi ~cm_kind (m : Module.t) =
else
As []
in
let dir, no_keep_locs =
match
( CC.no_keep_locs cctx
, cm_kind
, Ocaml_version.supports_no_keep_locs ctx.version )
with
| true, Cmi, true -> (ctx.build_dir, Command.Args.As [ "-no-keep-locs" ])
| true, Cmi, false -> (Obj_dir.byte_dir obj_dir, As [])
(* emulated -no-keep-locs *)
| true, (Cmo | Cmx), _
| false, _, _ ->
(ctx.build_dir, As [])
in
let dir = ctx.build_dir in
let flags =
let flags = Ocaml_flags.get (CC.flags cctx) mode in
match Module.pp_flags m with
Expand All @@ -143,7 +131,6 @@ let build_cm cctx ~dep_graphs ~precompiled_cmi ~cm_kind (m : Module.t) =
Build.paths extra_deps >>> other_cm_files
>>> Command.run ~dir:(Path.build dir) (Ok compiler)
[ Command.Args.dyn flags
; no_keep_locs
; cmt_args
; Command.Args.S
( Obj_dir.all_obj_dirs obj_dir ~mode
Expand Down
2 changes: 1 addition & 1 deletion test/blackbox-tests/test-cases/syntax-versioning/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -50,5 +50,5 @@
File "dune", line 3, characters 1-15:
3 | (no_keep_locs))
^^^^^^^^^^^^^^
Warning: 'no_keep_locs' was deprecated in version 1.7 of the dune language.
Warning: no_keep_locs is a no-op. Please delete it.
$ rm -f dune

0 comments on commit ada6596

Please sign in to comment.