Skip to content

Commit

Permalink
Implement instrumentation RFC (#3535)
Browse files Browse the repository at this point in the history
Generalise the support for bisect_ppx to all ppx based instrumentors.

Signed-off-by: Nicolás Ojeda Bär <n.oje.bar@gmail.com>
  • Loading branch information
nojb committed Jul 7, 2020
1 parent e28ac7c commit 4f0fa1b
Show file tree
Hide file tree
Showing 52 changed files with 995 additions and 608 deletions.
2 changes: 2 additions & 0 deletions bin/arg.ml
Original file line number Diff line number Diff line change
Expand Up @@ -122,3 +122,5 @@ let bytes =
conv (decode, pp_print_int64)

let context_name : Context_name.t conv = conv Context_name.conv

let lib_name = conv Dune.Lib_name.conv
2 changes: 2 additions & 0 deletions bin/arg.mli
Original file line number Diff line number Diff line change
Expand Up @@ -36,3 +36,5 @@ val path : Path.t conv
val package_name : Package.Name.t conv

val profile : Profile.t conv

val lib_name : Lib_name.t conv
19 changes: 18 additions & 1 deletion bin/common.ml
Original file line number Diff line number Diff line change
Expand Up @@ -49,6 +49,7 @@ type t =
; stats_trace_file : string option
; always_show_command_line : bool
; promote_install_files : bool
; instrument_with : Dune.Lib_name.t list option
}

let workspace_file t = t.workspace_file
Expand All @@ -71,6 +72,8 @@ let default_target t = t.default_target

let prefix_target common s = common.target_prefix ^ s

let instrument_with t = t.instrument_with

let set_dirs c =
if c.root.dir <> Filename.current_dir_name then Sys.chdir c.root.dir;
Path.set_root (Path.External.cwd ());
Expand Down Expand Up @@ -634,7 +637,20 @@ let term =
~docs
~env:(Arg.env_var ~doc "DUNE_CACHE_CHECK_PROBABILITY")
~doc)
and+ () = build_info in
and+ () = build_info
and+ instrument_with =
let doc =
{|"Enable instrumentation by $(b,BACKENDS).
$(b,BACKENDS) is a comma-separated list of library names,
each one of which must declare an instrumentation backend.|}
in
Arg.(
value
& opt (some (list lib_name)) None
& info [ "instrument-with" ] ~docs
~env:(Arg.env_var ~doc "DUNE_INSTRUMENT_WITH")
~docv:"BACKENDS" ~doc)
in
let build_dir = Option.value ~default:default_build_dir build_dir in
let root = Workspace_root.create ~specified_by_user:root in
let config = config_of_file config_file in
Expand Down Expand Up @@ -683,6 +699,7 @@ let term =
; stats_trace_file
; always_show_command_line
; promote_install_files
; instrument_with
}
let term =
Expand Down
2 changes: 2 additions & 0 deletions bin/common.mli
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,8 @@ val default_target : t -> Arg.Dep.t

val prefix_target : t -> string -> string

val instrument_with : t -> Dune.Lib_name.t list option

(** [set_common ?log common ~targets ~external_lib_deps_mode] is
[set_dirs common] followed by [set_common_other common ~targets]. In
general, [set_common] executes sequence of side-effecting actions to
Expand Down
4 changes: 3 additions & 1 deletion bin/import.ml
Original file line number Diff line number Diff line change
Expand Up @@ -75,9 +75,11 @@ module Main = struct
in
let x = Common.x common in
let profile = Common.profile common in
let instrument_with = Common.instrument_with common in
let capture_outputs = Common.capture_outputs common in
let ancestor_vcs = (Common.root common).ancestor_vcs in
scan_workspace ?workspace_file ?x ?profile ~capture_outputs ~ancestor_vcs ()
scan_workspace ?workspace_file ?x ?profile ?instrument_with ~capture_outputs
~ancestor_vcs ()

let setup common =
let open Fiber.O in
Expand Down
72 changes: 0 additions & 72 deletions doc/bisect.rst

This file was deleted.

2 changes: 1 addition & 1 deletion doc/index.rst
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ Welcome to dune's documentation!
dune-files
concepts
tests
bisect
instrumentation
foreign-code
documentation
jsoo
Expand Down
120 changes: 120 additions & 0 deletions doc/instrumentation.rst
Original file line number Diff line number Diff line change
@@ -0,0 +1,120 @@
***************
Instrumentation
***************

In this section, we will explain how define and use instrumentation backends
(such as ``bisect_ppx`` or ``landmarks``) so that you can enable and disable
coverage via ``dune-workspace`` files or by passing a command-line flag or
environment variable. In addition to providing an easy way to toggle
instrumentation of your code, this setup avoids creating a hard dependency on
the precise instrumentation backend in your project.

Specifying what to instrument
=============================

When an instrumentation backend is activated, Dune will only instrument
libraries and executables for which the user has requested instrumentation.

To request instrumentation, one must add the following field to a library or
executable stanza:

.. code:: scheme
(library
(name ...)
(instrumentation
(backend <name>)))
This field can be repeated multiple times in order to support various
backends. For instance:

.. code:: scheme
(library
(name foo)
(modules foo)
(instrumentation (backend bisect_ppx))
(instrumentation (backend landmarks)))
This will instruct Dune that when either the ``bisect_ppx`` or ``landmarks``
instrumentation is activated, the library should be instrumented with this
backend.

By default, these fields are simply ignored. However, when the corresponding
instrumentation backend is activated, Dune will implicitly add the relevant ``ppx``
rewriter to the list of ``ppx`` rewriters.

At the moment, it is not possible to instrument code that is preprocessed via an
action preprocessors. As these preprocessors are quite rare nowadays, there is
no plan to add support for them in the future.

Enabling/disabling instrumentation
==================================

Activating an instrumentation backend can be done via the command line or the
``dune-workspace`` file.

Via the command line, it is done as follows:

.. code:: bash
$ dune build --instrument-with <names>
Here ``<names>`` is a comma-separated list of instrumentation backends. For example:

.. code:: bash
$ dune build --instrument-with bisect_ppx,landmarks
This will instruct Dune to activate the given backend globally, i.e. in all
defined build contexts.

It is also possible to enable instrumentation backends via the
``dune-workspace`` file, either globally, or for specific builds contexts.

To enable an instrumentation backend globally, you can type in your
``dune-workspace`` file:

.. code:: scheme
(lang dune 2.7)
(instrument_with bisect_ppx)
or for each context individually:

.. code:: scheme
(lang dune 2.7)
(context default)
(context (default (name coverage) (instrument_with bisect_ppx)))
(context (default (name profiling) (instrument_with landmarks)))
If both the global and local fields are present, the precedence is the same as
for the ``profile`` field: the per-context setting takes precedence over the
command-line flag, which takes precedence over the global field.

Declaring an instrumentation backend
====================================

Instrumentation backends are libraries with the special field
``(instrumentation.backend)``. This field instructs Dune that the library can be
used as an intrumentation backend and also provides the parameters that are
specific to this backend.

Currently, Dune will only support ``ppx`` instrumentation tools, and the
instrumentation library must specify the ``ppx`` rewriters that instruments the
code. This can be done as follows:

.. code:: scheme
(library
...
(instrumentation.backend
(ppx <ppx-rewriter-name>)))
When such an instrumentation backend is activated, Dune will implicitly add the
mentioned ``ppx`` rewriter to the list of ``ppx`` rewriters for libraries and
executables that specify this instrumentation backend.

.. _bisect_ppx: https://github.com/aantron/bisect_ppx
.. _landmarks: https://github.com/LexiFi/landmarks
9 changes: 5 additions & 4 deletions src/dune/cinaps.ml
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ type t =
{ loc : Loc.t
; files : Predicate_lang.Glob.t
; libraries : Lib_dep.t list
; preprocess : Dune_file.Preprocess_map.t
; preprocess : Preprocess.Without_instrumentation.t Preprocess.Per_module.t
; preprocessor_deps : Dep_conf.t list
; flags : Ocaml_flags.Spec.t
}
Expand Down Expand Up @@ -78,8 +78,9 @@ let gen_rules sctx t ~dir ~scope =
let expander = Super_context.expander sctx ~dir in
let preprocess =
Preprocessing.make sctx ~dir ~expander ~dep_kind:Required
~lint:Dune_file.Preprocess_map.no_preprocessing ~preprocess:t.preprocess
~preprocessor_deps:t.preprocessor_deps ~lib_name:None ~scope
~lint:(Preprocess.Per_module.no_preprocessing ())
~preprocess:t.preprocess ~preprocessor_deps:t.preprocessor_deps
~lib_name:None ~scope
in
let modules =
Modules.singleton_exe module_
Expand All @@ -90,7 +91,7 @@ let gen_rules sctx t ~dir ~scope =
Lib.DB.resolve_user_written_deps_for_exes (Scope.libs scope)
[ (t.loc, name) ]
(Lib_dep.Direct (loc, Lib_name.of_string "cinaps.runtime") :: t.libraries)
~pps:(Dune_file.Preprocess_map.pps t.preprocess)
~pps:(Preprocess.Per_module.pps t.preprocess)
~dune_version ~optional:false
in
let cctx =
Expand Down
Loading

0 comments on commit 4f0fa1b

Please sign in to comment.