From 716d790204d0a6b31683c88c914fa8a8a632fc4d Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Fri, 30 Oct 2020 11:19:37 -0700 Subject: [PATCH 01/69] start working on ctypes stanza --- src/dune_rules/ctypes.ml | 33 +++++++++++++++++++++++++++++++++ src/dune_rules/ctypes.mli | 13 +++++++++++++ src/dune_rules/dune_file.ml | 4 ++++ src/dune_rules/dune_file.mli | 1 + 4 files changed, 51 insertions(+) create mode 100644 src/dune_rules/ctypes.ml create mode 100644 src/dune_rules/ctypes.mli diff --git a/src/dune_rules/ctypes.ml b/src/dune_rules/ctypes.ml new file mode 100644 index 00000000000..2dc9572e88d --- /dev/null +++ b/src/dune_rules/ctypes.ml @@ -0,0 +1,33 @@ +open! Dune_engine + +type t = + { name : string + ; pkg_config_name : string option + ; c_headers : string option + ; generated_modules : string list + } + +let name = "ctypes" + +type Stanza.t += T of t + +let decode = + let open Dune_lang.Decoder in + fields + (let+ name = field "name" string + and+ pkg_config_name = field_o "pkg_config_name" string + and+ c_headers = field_o "c_headers" string + and+ generated_modules = field "generated_modules" (repeat string) + in + { name; pkg_config_name; c_headers; generated_modules }) + +let syntax = + Dune_lang.Syntax.create ~name ~desc:"the ctypes extension" + (* XXX: insert the latest version of dune language *) + [ ((0, 1), `Since (2, 8)) + ] + +let () = + let open Dune_lang.Decoder in + Dune_project.Extension.register_simple syntax + (return [ (name, decode >>| fun x -> [ T x ]) ]) diff --git a/src/dune_rules/ctypes.mli b/src/dune_rules/ctypes.mli new file mode 100644 index 00000000000..3a02f1958bb --- /dev/null +++ b/src/dune_rules/ctypes.mli @@ -0,0 +1,13 @@ +(** Ctypes integration *) +open! Dune_engine + +(** Ctypes is a library for generating C-stubs from pure OCaml. + + These dune rules are to help reduce the boilerplate involved in + setting up the build system tooling to generate the stubs. *) + +type t + +type Stanza.t += T of t + +val decode : t Dune_lang.Decoder.t diff --git a/src/dune_rules/dune_file.ml b/src/dune_rules/dune_file.ml index e15478789cf..a7a48044730 100644 --- a/src/dune_rules/dune_file.ml +++ b/src/dune_rules/dune_file.ml @@ -161,6 +161,7 @@ module Buildable = struct ; flags : Ocaml_flags.Spec.t ; js_of_ocaml : Js_of_ocaml.t ; allow_overlapping_dependencies : bool + ; ctypes : Ctypes.t list } let decode ~in_library ~allow_re_export = @@ -232,6 +233,8 @@ module Buildable = struct (multi_field "instrumentation" ( Dune_lang.Syntax.since Stanza.syntax (2, 7) >>> fields (field "backend" (located Lib_name.decode)) )) + and+ ctypes = + (multi_field "ctypes" Ctypes.decode) in let preprocess = let init = @@ -285,6 +288,7 @@ module Buildable = struct ; flags ; js_of_ocaml ; allow_overlapping_dependencies + ; ctypes } let has_foreign t = diff --git a/src/dune_rules/dune_file.mli b/src/dune_rules/dune_file.mli index bd3ba3c1caa..5193260e9e3 100644 --- a/src/dune_rules/dune_file.mli +++ b/src/dune_rules/dune_file.mli @@ -49,6 +49,7 @@ module Buildable : sig ; flags : Ocaml_flags.Spec.t ; js_of_ocaml : Js_of_ocaml.t ; allow_overlapping_dependencies : bool + ; ctypes : Ctypes.t list } (** Check if the buildable has any foreign stubs or archives. *) From ec9e8c1641334432413c034a5a2c7a64fc868e00 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Fri, 6 Nov 2020 10:52:32 -0800 Subject: [PATCH 02/69] pseudocode direction --- src/dune_rules/ctypes.ml | 33 ---------- src/dune_rules/ctypes.mli | 13 ---- src/dune_rules/ctypes_rules.ml | 117 +++++++++++++++++++++++++++++++++ src/dune_rules/dune_file.ml | 44 +++++++++++-- src/dune_rules/dune_file.mli | 14 +++- src/dune_rules/dune_load.ml | 6 ++ 6 files changed, 175 insertions(+), 52 deletions(-) delete mode 100644 src/dune_rules/ctypes.ml delete mode 100644 src/dune_rules/ctypes.mli create mode 100644 src/dune_rules/ctypes_rules.ml diff --git a/src/dune_rules/ctypes.ml b/src/dune_rules/ctypes.ml deleted file mode 100644 index 2dc9572e88d..00000000000 --- a/src/dune_rules/ctypes.ml +++ /dev/null @@ -1,33 +0,0 @@ -open! Dune_engine - -type t = - { name : string - ; pkg_config_name : string option - ; c_headers : string option - ; generated_modules : string list - } - -let name = "ctypes" - -type Stanza.t += T of t - -let decode = - let open Dune_lang.Decoder in - fields - (let+ name = field "name" string - and+ pkg_config_name = field_o "pkg_config_name" string - and+ c_headers = field_o "c_headers" string - and+ generated_modules = field "generated_modules" (repeat string) - in - { name; pkg_config_name; c_headers; generated_modules }) - -let syntax = - Dune_lang.Syntax.create ~name ~desc:"the ctypes extension" - (* XXX: insert the latest version of dune language *) - [ ((0, 1), `Since (2, 8)) - ] - -let () = - let open Dune_lang.Decoder in - Dune_project.Extension.register_simple syntax - (return [ (name, decode >>| fun x -> [ T x ]) ]) diff --git a/src/dune_rules/ctypes.mli b/src/dune_rules/ctypes.mli deleted file mode 100644 index 3a02f1958bb..00000000000 --- a/src/dune_rules/ctypes.mli +++ /dev/null @@ -1,13 +0,0 @@ -(** Ctypes integration *) -open! Dune_engine - -(** Ctypes is a library for generating C-stubs from pure OCaml. - - These dune rules are to help reduce the boilerplate involved in - setting up the build system tooling to generate the stubs. *) - -type t - -type Stanza.t += T of t - -val decode : t Dune_lang.Decoder.t diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml new file mode 100644 index 00000000000..e43a34dbd70 --- /dev/null +++ b/src/dune_rules/ctypes_rules.ml @@ -0,0 +1,117 @@ +open! Dune_engine + +(* This module simply expands a [(library ... (ctypes ...))] stanza into the + set of [library], [rule] and [action] stanzas and .ml files needed to + more conveniently build OCaml bindings for C libraries. Aside from perhaps + providing a '#include "header.h"' line, you should be able to wrap an + entire C library without writing a single line of C code. + + The result of this stanza is a single library you can reference from your + projects to get at the underlying C types/data/functions that have been + exposed. + + All you have to do is configure the stanza and provide two ocaml modules + - the types/data wrapping module + - the functions wrapping module + + This module will then, behind the scenes + - generate a types/constants generator + - generate a functions generator + - set up a discovery program to query pkg-config for compile and link flags + - use the types/data and functions modules you filled in to tie everything + together into a neat library +*) + +let gen_rule ~targets ~action () = + let open Dune_file in + { Rule.targets; action } + +let gen_library ?wrapped ?foreign_stubs ?c_library_flags ~name + ~public_name ~modules ~libraries () = + let open Dune_file in + { Library.name; public_name; modules; libraries; wrapped; foreign_stubs } + +let gen_executable ~name ~modules ~libraries () = + let open Dune_file in + { Executable.name; modules; libraries } + +(* It may help to understand what this generator function is trying to do by + having a look at the hand-written version it's replacing. + XXX: link to mpg123 dune file *) +let really_expand lib ctypes = + let open Dune_file in + [ gen_executable + ~name:"mpg123_discover" + ~libraries:["dune.configurator"] + () + ; gen_rule + ~targets:["c_flags.sexp"; "c_flags.txt"; "c_library_flags.sexp"] + ~action:["run discover.exe"] + () + ; gen_library + ~name:("mpg123_c_type_descriptions") + ~public_name:("mpg123.c_type_descriptions") + ~modules:"Mpg123_c_type_descriptions" + ~libraries:["ctypes"] + () + ; gen_executable + ~name:"type_gen" + ~modules:"Type_gen" + ~libraries:["ctypes.stubs"; "ctypes.foreign"; "mpg123_c_type_descriptions"] + () + ; gen_rule_stdout + ~with_stdout_to:"c_generated_types.c" + ~run:("./type_gen.exe") + () + ; gen_rule + ~targets:["c_generated_types.exe"] + ~deps:[":c c_generated_types.c"] + ~action:["system blah blah"] + () + ; gen_rule_stdout + ~with_stdout_to:"mpg123_c_generated_types.ml" + ~run:("./c_generated_types.exe") + () + ; gen_library + ~name:"mpg123_c_function_descriptions" + ~public_name:"mpg123.c_function_descriptions" + ~modules:["Mpg123_c_generated_types"; "Mpg123_c_function_descriptions"; + "Mpg123_c_types"] + ~wrapped:false + ~flags:":standard -w -27 -w -9" + ~libraries:["ctypes"; "mpg123_c_type_descriptions"] + () + ; gen_executable + ~name:"function_gen" + ~modules:"Function_gen" + ~libraries:["ctypes.stubs"; "mpg123_c_function_descriptions"] + () + ; gen_rule_stdout + ~with_stdout_to:"c_generated_functions.c" + ~run:"./function_gen.exe c mpg123_stub" + () + ; gen_rule_stdout + ~with_stdout_to:"mpg123_c_generated_functions.ml" + ~run:"./function_gen.exe ml mpg123_stub" + () + ; gen_library + ~name:"mpg123_c" + ~public_name:"mpg123.c" + ~libraries:["ctypes"; "mpg123_c_function_descriptions"] + ~modules:["Mpg123_c"; "Mpg123_c_generated_functions"] + ~foreign_stubs:[ + ("language" , "c"); + ("names" , "c_generated_functions"); + ("flags" , ":include c_flags.sexp") + ] + ~c_library_flags:":include c_library_flags.sexp" + () + ] + +let expand = function + | Dune_file.Library lib -> + begin match lib.Dune_file.Library.ctypes with + | Some ctypes -> really_expand lib ctypes + | None -> assert false + end + | _ -> assert false diff --git a/src/dune_rules/dune_file.ml b/src/dune_rules/dune_file.ml index f1994367ef9..056b0195749 100644 --- a/src/dune_rules/dune_file.ml +++ b/src/dune_rules/dune_file.ml @@ -161,7 +161,6 @@ module Buildable = struct ; flags : Ocaml_flags.Spec.t ; js_of_ocaml : Js_of_ocaml.t ; allow_overlapping_dependencies : bool - ; ctypes : Ctypes.t list } let decode ~in_library ~allow_re_export = @@ -233,9 +232,7 @@ module Buildable = struct (multi_field "instrumentation" ( Dune_lang.Syntax.since Stanza.syntax (2, 7) >>> fields (field "backend" (located Lib_name.decode)) )) - and+ ctypes = - (multi_field "ctypes" Ctypes.decode) - in + in let preprocess = let init = let f libname = Preprocess.With_instrumentation.Ordinary libname in @@ -288,7 +285,6 @@ module Buildable = struct ; flags ; js_of_ocaml ; allow_overlapping_dependencies - ; ctypes } let has_foreign t = @@ -479,6 +475,40 @@ module Mode_conf = struct end end +module Ctypes = struct + type t = + { name : string + ; pkg_config_name : string option + ; c_headers : string option + ; generated_modules : string list + } + + let name = "ctypes" + + type Stanza.t += T of t + + let decode = + let open Dune_lang.Decoder in + fields + (let+ name = field "name" string + and+ pkg_config_name = field_o "pkg_config_name" string + and+ c_headers = field_o "c_headers" string + and+ generated_modules = field "generated_modules" (repeat string) + in + { name; pkg_config_name; c_headers; generated_modules }) + + let syntax = + Dune_lang.Syntax.create ~name ~desc:"the ctypes extension" + (* XXX: insert the latest version of dune language *) + [ ((0, 1), `Since (2, 8)) + ] + + let () = + let open Dune_lang.Decoder in + Dune_project.Extension.register_simple syntax + (return [ (name, decode >>| fun x -> [ T x ]) ]) +end + module Library = struct module Wrapped = struct include Wrapped @@ -539,6 +569,7 @@ module Library = struct ; special_builtin_support : Lib_info.Special_builtin_support.t option ; enabled_if : Blang.t ; instrumentation_backend : (Loc.t * Lib_name.t) option + ; ctypes : Ctypes.t option } let decode = @@ -617,6 +648,8 @@ module Library = struct field_o "package" ( Dune_lang.Syntax.since Stanza.syntax (2, 8) >>> located Stanza_common.Pkg.decode ) + and+ ctypes = + (field_o "ctypes" Ctypes.decode) in let wrapped = Wrapped.make ~wrapped ~implements ~special_builtin_support @@ -705,6 +738,7 @@ module Library = struct ; special_builtin_support ; enabled_if ; instrumentation_backend + ; ctypes }) let package t = diff --git a/src/dune_rules/dune_file.mli b/src/dune_rules/dune_file.mli index 5193260e9e3..943117b0ffb 100644 --- a/src/dune_rules/dune_file.mli +++ b/src/dune_rules/dune_file.mli @@ -49,7 +49,6 @@ module Buildable : sig ; flags : Ocaml_flags.Spec.t ; js_of_ocaml : Js_of_ocaml.t ; allow_overlapping_dependencies : bool - ; ctypes : Ctypes.t list } (** Check if the buildable has any foreign stubs or archives. *) @@ -112,6 +111,18 @@ module Mode_conf : sig end end +module Ctypes : sig + type t = + { name : string + ; pkg_config_name : string option + ; c_headers : string option + ; generated_modules : string list + } + + type Stanza.t += T of t +end + + module Library : sig type visibility = | Public of Public_lib.t @@ -148,6 +159,7 @@ module Library : sig ; special_builtin_support : Lib_info.Special_builtin_support.t option ; enabled_if : Blang.t ; instrumentation_backend : (Loc.t * Lib_name.t) option + ; ctypes : Ctypes.t option } val sub_dir : t -> string option diff --git a/src/dune_rules/dune_load.ml b/src/dune_rules/dune_load.ml index cb07ca2b433..4d95a345943 100644 --- a/src/dune_rules/dune_load.ml +++ b/src/dune_rules/dune_load.ml @@ -11,6 +11,12 @@ module Dune_file = struct let parse sexps ~dir ~file ~project = let stanzas = Dune_file.Stanzas.parse ~file project sexps in + let stanzas = List.concat_map stanzas ~f:(fun stanza -> + match stanza with + | Dune_file.Stanzas.Library { ctypes = Some ctypes; _ } -> + Ctypes_rules.expand stanza + | _ -> [stanza]) + in let stanzas = if !Clflags.ignore_promoted_rules then List.filter stanzas ~f:(function From bbb3f935c733c2143782973d09ea3cace1d6bdd6 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Sun, 6 Dec 2020 12:17:34 -0800 Subject: [PATCH 03/69] naive first pass translation of hand-written dune file rules. with errors --- src/dune_rules/compilation_context.mli | 2 +- src/dune_rules/ctypes_rules.ml | 433 +++++++++++++++++----- src/dune_rules/ctypes_rules.mli | 9 + src/dune_rules/ctypes_stanzas.ml | 212 +++++++++++ src/dune_rules/ctypes_stanzas.mli | 24 ++ src/dune_rules/dune_file.ml | 33 +- src/dune_rules/dune_file.mli | 14 +- src/dune_rules/dune_load.ml | 12 +- src/dune_rules/lib_rules.ml | 13 +- src/dune_rules/modules_field_evaluator.ml | 3 - src/dune_rules/ordered_set_lang.ml | 4 + src/dune_rules/ordered_set_lang.mli | 2 + 12 files changed, 623 insertions(+), 138 deletions(-) create mode 100644 src/dune_rules/ctypes_rules.mli create mode 100644 src/dune_rules/ctypes_stanzas.ml create mode 100644 src/dune_rules/ctypes_stanzas.mli diff --git a/src/dune_rules/compilation_context.mli b/src/dune_rules/compilation_context.mli index 7bc3e2b80b2..c169c2409f9 100644 --- a/src/dune_rules/compilation_context.mli +++ b/src/dune_rules/compilation_context.mli @@ -13,7 +13,7 @@ type t (** Sets whether [-opaque] is going to be used during compilation. This constructs a different dependency graph for native executables. In - partricular, we can omit dependency on .cmx files. For mli only modules, + particular, we can omit dependency on .cmx files. For mli only modules, this setting is ignored and is always set when it's available. As there are no .cmx files for such modules anyway *) type opaque = diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index e43a34dbd70..672bf6973fd 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -1,117 +1,344 @@ open! Dune_engine +open! Stdune -(* This module simply expands a [(library ... (ctypes ...))] stanza into the - set of [library], [rule] and [action] stanzas and .ml files needed to - more conveniently build OCaml bindings for C libraries. Aside from perhaps - providing a '#include "header.h"' line, you should be able to wrap an +module Library = Dune_file.Library +module Ctypes = Dune_file.Ctypes + +(* This module expands a [(library ... (ctypes ...))] rule into the set of + [library], [executable], [rule] rules and .ml files needed to more + conveniently build OCaml bindings for C libraries. Aside from perhaps + providing an '#include "header.h"' line, you should be able to wrap an entire C library without writing a single line of C code. - The result of this stanza is a single library you can reference from your - projects to get at the underlying C types/data/functions that have been - exposed. + This stanza requires the user to define (and specify) two modules: + + (1) A "Type Descriptions" .ml file with the following top-level module: + + module Types (T : Ctypes.TYPE) = struct + (* put calls to Ctypes.TYPE.constant and Ctypes.TYPE.typedef here + to wrap C constants and structs *) + end + + (2) A 'Function Descriptions' .ml file with the following top-level module: - All you have to do is configure the stanza and provide two ocaml modules - - the types/data wrapping module - - the functions wrapping module + module Functions (F : Ctypes.FOREIGN) = struct + (* put calls to F.foreign here to wrap C functions *) + end + + The instantiated functor that was defined in 'Types' can be accessed from + the Function Descriptions module as Library_name__c_types. + + e.g. module Types = Library_name__c_types - This module will then, behind the scenes - - generate a types/constants generator + Once the above two modules are provided, the ctypes stanza will: + - generate a types/data generator - generate a functions generator - set up a discovery program to query pkg-config for compile and link flags - - use the types/data and functions modules you filled in to tie everything - together into a neat library + - use the types/data and functions modules you filled in with a functor + to tie everything into your library. + + The result of using a ctypes stanza is that it will introduce into your + project a library that provides interfaces to all of the types and functions + you described earlier, with the rather involved compilation and linking + details handled for you. + + It may help to view a real world example of all of the boilerplate that is + being replaced by a [ctypes] stanza: + + https://github.com/mbacarella/mpg123/blob/077a72d922931eb46d4b4e5842b0426fa3c161b5/c/dune *) -let gen_rule ~targets ~action () = - let open Dune_file in - { Rule.targets; action } - -let gen_library ?wrapped ?foreign_stubs ?c_library_flags ~name - ~public_name ~modules ~libraries () = - let open Dune_file in - { Library.name; public_name; modules; libraries; wrapped; foreign_stubs } - -let gen_executable ~name ~modules ~libraries () = - let open Dune_file in - { Executable.name; modules; libraries } - -(* It may help to understand what this generator function is trying to do by - having a look at the hand-written version it's replacing. - XXX: link to mpg123 dune file *) -let really_expand lib ctypes = - let open Dune_file in - [ gen_executable - ~name:"mpg123_discover" +let sprintf = Printf.sprintf + +let ml_of_module_name mn = + Module_name.to_string mn ^ ".ml" + |> String.lowercase + +let write_c_types_includer_module ~sctx ~dir ~filename ~type_description_module + ~c_generated_types_module = + let path = Path.Build.relative dir filename in + let contents = + let buf = Buffer.create 1024 in + let pr buf fmt = Printf.bprintf buf (fmt ^^ "\n") in + pr buf "include %s.Types (%s)" + (Module_name.to_string type_description_module) + (Module_name.to_string c_generated_types_module); + Buffer.contents buf + in + Super_context.add_rule ~loc:Loc.none sctx ~dir + (Build.write_file path contents) + +let discover_gen ~external_lib_name:lib ~cflags_sexp ~cflags_txt + ~c_library_flags_sexp = + let buf = Buffer.create 1024 in + let pr buf fmt = Printf.bprintf buf (fmt ^^ "\n") in + pr buf "module C = Configurator.V1"; + pr buf "let () ="; + pr buf " C.main ~name:\"%s\" (fun c ->" lib; + pr buf " let default : C.Pkg_config.package_conf ="; + pr buf " { libs = [\"-l%s\"];" lib; + pr buf " cflags = [\"-I/usr/include\"] }"; + pr buf " in"; + pr buf " let conf ="; + pr buf " match C.Pkg_config.get c with"; + pr buf " | None -> default"; + pr buf " | Some pc ->"; + pr buf " match C.Pkg_config.query pc ~package:\"%s\" with" lib; + pr buf " | None -> default"; + pr buf " | Some deps -> deps"; + pr buf " in"; + pr buf " C.Flags.write_sexp \"%s\" conf.cflags;" cflags_sexp; + pr buf " C.Flags.write_sexp \"%s\" conf.libs;" c_library_flags_sexp; + pr buf " let oc = open_out \"%s\" in" cflags_txt; + pr buf " List.iter (Printf.fprintf oc \"%%s\") conf.cflags;"; + pr buf " close_out oc)"; + Buffer.contents buf + +let write_discover_script ~filename ~sctx ~dir ~external_lib_name ~cflags_sexp + ~cflags_txt ~c_library_flags_sexp = + let path = Path.Build.relative dir filename in + let script = + discover_gen ~external_lib_name ~cflags_sexp ~cflags_txt + ~c_library_flags_sexp + in + Super_context.add_rule ~loc:Loc.none sctx ~dir (Build.write_file path script) + +let type_gen_gen ~include_headers ~type_description_module = + let buf = Buffer.create 1024 in + let pr buf fmt = Printf.bprintf buf (fmt ^^ "\n") in + pr buf "let () ="; + List.iter include_headers ~f:(fun h -> + pr buf " print_endline \"#include <%s>\";" h); + pr buf " Cstubs_structs.write_c Format.std_formatter"; + pr buf " (module %s.Types)" (Module_name.to_string type_description_module); + Buffer.contents buf + +let function_gen_gen ~include_headers ~function_description_module = + (* XXX: make concurrency configurable *) + let function_description_module = + Module_name.to_string function_description_module + in + let concurrency = "Cstubs.unlocked" in + let buf = Buffer.create 1024 in + let pr buf fmt = Printf.bprintf buf (fmt ^^ "\n") in + pr buf "let () ="; + pr buf " let concurrency = %s in" concurrency; + pr buf " let prefix = Sys.argv.(2) in"; + pr buf " match Sys.argv.(1) with"; + pr buf " | \"ml\" ->"; + pr buf " Cstubs.write_ml ~concurrency Format.std_formatter ~prefix"; + pr buf " (module %s.Functions)" function_description_module; + pr buf " | \"c\" ->"; + List.iter include_headers ~f:(fun h -> + pr buf " print_endline \"#include <%s>\";" h); + pr buf " Cstubs.write_c ~concurrency Format.std_formatter ~prefix"; + pr buf " (module %s.Functions)" function_description_module; + pr buf " | s -> failwith (\"unknown functions \"^s)"; + Buffer.contents buf + +let write_type_gen_script ~include_headers ~dir ~filename ~sctx + ~type_description_module = + let path = Path.Build.relative dir filename in + let script = type_gen_gen ~include_headers ~type_description_module in + Super_context.add_rule ~loc:Loc.none sctx ~dir (Build.write_file path script) + +let write_function_gen_script ~include_headers ~sctx ~dir ~name + ~function_description_module = + let path = Path.Build.relative dir (name ^ ".ml") in + let script = function_gen_gen ~include_headers ~function_description_module in + Super_context.add_rule ~loc:Loc.none sctx ~dir (Build.write_file path script) + +let rule ?stdout_to ?(targets=[]) ~run ~sctx ~dir () = + let build = + let targets = List.map targets ~f:(Path.Build.relative dir) in + let exe = Ok (Path.build (Path.Build.relative dir run)) in + let args = [ Command.Args.Hidden_targets targets ] in + let stdout_to = Option.map stdout_to ~f:(Path.Build.relative dir) in + Command.run exe ~dir:(Path.build dir) ?stdout_to args + in + Super_context.add_rule sctx ~dir build + +let rule_shell_action ~deps ~targets ~action_args ~sctx ~dir () = + let build = + let sh_path, sh_arg = Utils.system_shell_exn ~needed_to:"build ctypes" in + let targets = List.map targets ~f:(Path.Build.relative dir) in + let deps = List.map deps ~f:(Path.relative (Path.build dir)) in + let exe = Ok sh_path in + let args = + let open Command.Args in + [ Deps deps + ; Hidden_targets targets + ; As (sh_arg :: action_args) ] + in + Command.run exe ~dir:(Path.build dir) args + in + Super_context.add_rule sctx ~dir build + +let cctx ~base_lib ?(libraries=[]) ~loc ~dir ~scope ~expander ~sctx = + let compile_info = + let dune_version = Scope.project scope |> Dune_project.dune_version in + Lib.DB.resolve_user_written_deps_for_exes (Scope.libs scope) + [ (loc, "ctypes") ] + (List.map libraries ~f:(fun lib -> + Lib_dep.Direct (loc, Lib_name.of_string lib))) + ~dune_version ~optional:false + ~pps:[] + in + let dynlink = + let ctx = Super_context.context sctx in + Dynlink_supported.get base_lib.Library.dynlink + ctx.Context.supports_shared_libraries + in + Compilation_context.create + ~super_context:sctx ~scope ~expander + ~js_of_ocaml:None + ~dynlink + ~package:None + ~flags:(Super_context.ocaml_flags sctx ~dir base_lib.buildable.flags) + ~requires_compile:(Lib.Compile.direct_requires compile_info) + ~requires_link:(Lib.Compile.requires_link compile_info) + ~obj_dir:(Library.obj_dir ~dir base_lib) + ~opaque:Compilation_context.Inherit_from_settings + +let executable ?(modules=[]) ~base_lib ~loc ~dir ~sctx ~scope ~expander + ~program ~libraries () = + let build_dir = Path.build dir in + let cctx = + let modules = + let name_map = + List.map (program :: modules) ~f:(fun name -> + let module_name = Module_name.of_string name in + let path = Path.relative build_dir (name ^ ".ml") in + let impl = Module.File.make Dialect.ocaml path in + let source = Module.Source.make ~impl module_name in + Module.of_source ~visibility:Visibility.Public + ~kind:Module.Kind.Impl source) + |> Module.Name_map.of_list_exn + in + Modules.exe_wrapped ~src_dir:dir ~modules:name_map + in + cctx ~base_lib ~dir ~loc ~scope ~sctx ~expander ~modules ~libraries () + in + let program = + Exe.Program.{ + name = program; + main_module_name = Module_name.of_string program; + loc = Loc.in_file (Path.relative build_dir program) + } + in + Exe.build_and_link ~program ~linkages:[Exe.Linkage.native] ~promote:None cctx + +let gen_rules ~base_lib ~scope ~expander ~dir ~sctx = + let loc, _name = base_lib.Library.name in + let rule = rule ~sctx ~dir in + let executable = executable ~base_lib ~loc ~dir ~sctx ~scope ~expander in + let ctypes = + match base_lib.Library.ctypes with + | Some ctypes -> ctypes + | None -> assert false + in + let external_lib_name = ctypes.Ctypes.lib_name in + let type_description_module = Ctypes_stanzas.type_description_module ctypes in + let type_description_library = Ctypes_stanzas.type_description_library ctypes in + let function_description_module = Ctypes_stanzas.function_description_module ctypes in + let function_description_library = Ctypes_stanzas.function_description_library ctypes in + (* This includer module is simply some glue to instantiate the Types functor + that the user provides in the type description module. *) + let () = + write_c_types_includer_module + ~sctx ~dir + ~filename:(Ctypes_stanzas.c_types_includer_module ctypes + |> ml_of_module_name) + ~c_generated_types_module:(Ctypes_stanzas.c_generated_types_module ctypes) + ~type_description_module; + in + (* The discover script uses dune configurator / pkg_config to figure out + how to invoke the compiler and linker for your external C library. + + https://dune.readthedocs.io/en/stable/quick-start.html#defining-a-library-with-c-stubs-using-pkg-config *) + let c_library_flags_sexp = Ctypes_stanzas.c_library_flags_sexp ctypes in + let () = + let cflags_txt = Ctypes_stanzas.cflags_txt ctypes in + let cflags_sexp = Ctypes_stanzas.cflags_sexp ctypes in + let discover_script = sprintf "%s__ctypes_discover" external_lib_name in + write_discover_script + ~sctx ~dir ~filename:(discover_script ^ ".ml") ~cflags_sexp + ~cflags_txt ~c_library_flags_sexp ~external_lib_name; + executable + ~program:discover_script ~libraries:["dune.configurator"] + (); + rule + ~targets:[cflags_sexp; cflags_txt; c_library_flags_sexp] + ~run:(discover_script ^ ".exe") () - ; gen_rule - ~targets:["c_flags.sexp"; "c_flags.txt"; "c_library_flags.sexp"] - ~action:["run discover.exe"] - () - ; gen_library - ~name:("mpg123_c_type_descriptions") - ~public_name:("mpg123.c_type_descriptions") - ~modules:"Mpg123_c_type_descriptions" - ~libraries:["ctypes"] - () - ; gen_executable - ~name:"type_gen" - ~modules:"Type_gen" - ~libraries:["ctypes.stubs"; "ctypes.foreign"; "mpg123_c_type_descriptions"] - () - ; gen_rule_stdout - ~with_stdout_to:"c_generated_types.c" - ~run:("./type_gen.exe") - () - ; gen_rule - ~targets:["c_generated_types.exe"] - ~deps:[":c c_generated_types.c"] - ~action:["system blah blah"] - () - ; gen_rule_stdout - ~with_stdout_to:"mpg123_c_generated_types.ml" - ~run:("./c_generated_types.exe") - () - ; gen_library - ~name:"mpg123_c_function_descriptions" - ~public_name:"mpg123.c_function_descriptions" - ~modules:["Mpg123_c_generated_types"; "Mpg123_c_function_descriptions"; - "Mpg123_c_types"] - ~wrapped:false - ~flags:":standard -w -27 -w -9" - ~libraries:["ctypes"; "mpg123_c_type_descriptions"] - () - ; gen_executable - ~name:"function_gen" - ~modules:"Function_gen" - ~libraries:["ctypes.stubs"; "mpg123_c_function_descriptions"] - () - ; gen_rule_stdout - ~with_stdout_to:"c_generated_functions.c" - ~run:"./function_gen.exe c mpg123_stub" - () - ; gen_rule_stdout - ~with_stdout_to:"mpg123_c_generated_functions.ml" - ~run:"./function_gen.exe ml mpg123_stub" + in + let include_headers = ctypes.Ctypes.includes in + (* Type_gen produces a .c file, taking your type description module above + as an input. + The .c file is compiled into an .exe. + The .exe, when run produces an .ml file. + The .ml file is compiled into a module that will have the user's + ML-wrapped C data/types. + + Note the similar function_gen process below depends on the ML-wrapped C + data/types produced in this step. *) + let () = + let type_gen_script = sprintf "%s__type_gen" external_lib_name in + let c_generated_types_cout_c = + Ctypes_stanzas.c_generated_types_cout_c ctypes + in + let c_generated_types_cout_exe = + Ctypes_stanzas.c_generated_types_cout_exe ctypes + in + write_type_gen_script ~include_headers ~sctx ~dir + ~filename:(type_gen_script ^ ".ml") + ~type_description_module; + executable + ~program:type_gen_script + ~libraries:["ctypes.stubs"; "ctypes.foreign"; type_description_library] + (); + rule ~stdout_to:c_generated_types_cout_c ~run:(type_gen_script ^ ".exe") (); + rule_shell_action + ~sctx ~dir + ~targets:[c_generated_types_cout_exe] + ~deps:[c_generated_types_cout_c] + (* XXX: these substitutions probably won't work *) + ~action_args:["%{cc}"; c_generated_types_cout_c; + "-I"; "%{lib:ctypes:.}"; + "-I"; "%{ocaml_where}"; + "%{read:c_flags.txt}"; + "-o"; "%{targets}"] + (); + rule + ~stdout_to:(Ctypes_stanzas.c_generated_types_module ctypes + |> ml_of_module_name) + ~run:c_generated_types_cout_exe () - ; gen_library - ~name:"mpg123_c" - ~public_name:"mpg123.c" - ~libraries:["ctypes"; "mpg123_c_function_descriptions"] - ~modules:["Mpg123_c"; "Mpg123_c_generated_functions"] - ~foreign_stubs:[ - ("language" , "c"); - ("names" , "c_generated_functions"); - ("flags" , ":include c_flags.sexp") - ] - ~c_library_flags:":include c_library_flags.sexp" + in + (* Function_gen is similar to type_gen above, though it produces both an + .ml file and a .c file. These files correspond to the files you would + have to write by hand to wrap C code (if ctypes didn't exist!) *) + let () = + let stubs_prefix = external_lib_name ^ "_stubs" in + let function_gen_script = sprintf "%s__function_gen" external_lib_name in + let c_generated_functions_cout_c = + Ctypes_stanzas.c_generated_functions_cout_c ctypes + in + write_function_gen_script ~include_headers ~sctx ~dir + ~name:function_gen_script ~function_description_module; + executable + ~program:function_gen_script + ~libraries:["ctypes.stubs"; function_description_library] + (); + rule + ~stdout_to:c_generated_functions_cout_c + ~run:(sprintf "%s.exe c %s" function_gen_script stubs_prefix) + (); + rule + ~stdout_to:(Ctypes_stanzas.c_generated_functions_module ctypes + |> ml_of_module_name) + ~run:(sprintf "%s.exe ml %s" function_gen_script stubs_prefix) () - ] - -let expand = function - | Dune_file.Library lib -> - begin match lib.Dune_file.Library.ctypes with - | Some ctypes -> really_expand lib ctypes - | None -> assert false - end - | _ -> assert false + in + () diff --git a/src/dune_rules/ctypes_rules.mli b/src/dune_rules/ctypes_rules.mli new file mode 100644 index 00000000000..669a48bd53d --- /dev/null +++ b/src/dune_rules/ctypes_rules.mli @@ -0,0 +1,9 @@ +open! Stdune + +val gen_rules : + base_lib:Dune_file.Library.t + -> scope:Scope.t + -> expander:Expander.t + -> dir:Path.Build.t + -> sctx:Super_context.t + -> unit diff --git a/src/dune_rules/ctypes_stanzas.ml b/src/dune_rules/ctypes_stanzas.ml new file mode 100644 index 00000000000..27dbb03e38f --- /dev/null +++ b/src/dune_rules/ctypes_stanzas.ml @@ -0,0 +1,212 @@ +open! Dune_engine +open! Stdune + +module Library = Dune_file.Library +module Ctypes = Dune_file.Ctypes + +let osl_pos _base_lib = "", 0, 0, 0 ;; + +let library_stanza ?public_name ?(foreign_stubs=[]) ?c_library_flags + ~base_lib:lib ~name ~modules ~libraries ~wrapped () = + Printf.printf "*** generate library stanza: %s\n%!" name; + let loc, _libname = lib.Library.name in + let open Dune_file in + let visibility = + match public_name with + | None -> Library.Private None + | Some _public_name -> + Library.Private None + (* XXX: can only do this if the base library is public as well *) + (* + let plib = + match + Public_lib.make ~allow_deprecated_names:false + lib.Library.project (loc, Lib_name.of_string public_name) + with + | Ok plib -> plib + | Error e -> + (* XXX: present this as a proper error *) + failwith (sprintf "user message: %s" (User_message.to_string e)) + in + Library.Public plib + *) + in + let buildable = + let libraries = + List.map libraries ~f:(fun library -> + Lib_dep.Direct (loc, Lib_name.of_string library)) + in + let modules = List.map modules ~f:Module_name.to_string in + { Buildable.loc + ; modules = Ordered_set_lang.of_atoms ~loc modules + ; modules_without_implementation = Ordered_set_lang.of_atoms ~loc [] + ; libraries + ; foreign_archives= [] + ; foreign_stubs + ; preprocess = Preprocess.Per_module.default () + ; preprocessor_deps = [] + ; lint = Lint.no_lint + ; flags = Ocaml_flags.Spec.standard + ; js_of_ocaml = Js_of_ocaml.default + ; allow_overlapping_dependencies = false + } + in + let c_library_flags = + match c_library_flags with + | None -> Ordered_set_lang.Unexpanded.standard + | Some lst -> + let pos = osl_pos lib in + Ordered_set_lang.Unexpanded.of_strings ~pos lst + in + { Library.name = (loc, Lib_name.of_string name |> Lib_name.to_local_exn) + ; visibility + ; synopsis = None + ; install_c_headers = [] + ; ppx_runtime_libraries = [] + ; modes = Mode_conf.Set.of_list [Mode_conf.Native, Mode_conf.Kind.Inherited] + ; kind = Lib_kind.Normal + ; library_flags = Ordered_set_lang.Unexpanded.standard + ; c_library_flags + ; virtual_deps = [] + ; wrapped = Lib_info.Inherited.This (Wrapped.Simple wrapped) + ; optional = false + ; buildable + ; dynlink = Dynlink_supported.of_bool false + ; project = lib.Library.project + ; sub_systems = lib.Library.sub_systems + ; dune_version = lib.Library.dune_version + ; virtual_modules = None + ; implements = None + ; default_implementation = None + ; private_modules = None + ; stdlib = None + ; special_builtin_support = None + ; enabled_if = Blang.true_ + ; instrumentation_backend = None + ; ctypes = None } + +let sprintf = Printf.sprintf + +let type_description_module ctypes = + sprintf "%s__c_type_descriptions" ctypes.Ctypes.lib_name + |> Module_name.of_string + +let type_description_library ctypes = + sprintf "%s__c_type_descriptions" ctypes.Ctypes.lib_name + +let type_description_library_public ctypes = + sprintf "%s.c_type_descriptions" ctypes.Ctypes.lib_name + +let function_description_module ctypes = + sprintf "%s__c_function_descriptions" ctypes.Ctypes.lib_name + |> Module_name.of_string + +let function_description_library ctypes = + sprintf "%s__c_function_descriptions" ctypes.Ctypes.lib_name + +let function_description_library_public ctypes = + sprintf "%s.c_function_descriptions" ctypes.Ctypes.lib_name + +let entry_module ctypes = + sprintf "%s_c" ctypes.Ctypes.lib_name + |> Module_name.of_string + +let entry_library ctypes = + sprintf "%s_c" ctypes.Ctypes.lib_name + +let entry_library_public ctypes = + sprintf "%s.c" ctypes.Ctypes.lib_name + +let cflags_sexp ctypes = + sprintf "%s__c_flags.sexp" ctypes.Ctypes.lib_name + +let cflags_txt ctypes = + sprintf "%s__c_flags.txt" ctypes.Ctypes.lib_name + +let c_library_flags_sexp ctypes = + sprintf "%s__c_library_flags.sexp" ctypes.Ctypes.lib_name + +let c_generated_types_module ctypes = + sprintf "%s__c_generated_types" ctypes.Ctypes.lib_name + |> Module_name.of_string + +let c_generated_functions_module ctypes = + sprintf "%s__c_generated_functions" ctypes.Ctypes.lib_name + |> Module_name.of_string + +let c_types_includer_module ctypes = + sprintf "%s__c_types" ctypes.Ctypes.lib_name + |> Module_name.of_string + +let c_generated_types_cout_c ctypes = + sprintf "%s__c_cout_generated_types.c" ctypes.Ctypes.lib_name + +let c_generated_types_cout_exe ctypes = + sprintf "%s__c_cout_generated_types.exe" ctypes.Ctypes.lib_name + +let c_generated_functions_cout_c ctypes = + sprintf "%s__c_cout_generated_functions.c" ctypes.Ctypes.lib_name + +let c_generated_functions_cout_no_ext ctypes = + sprintf "%s__c_cout_generated_functions" ctypes.Ctypes.lib_name + +(* Unlike for [executable] and [rule] generation which have neat convenience + functions for creating new ones, the machinery for creating new [library]s + does several passes to populate global data structures. + + Rather than attempting to teach each of those passes about ctypes, the + approach here is to simply do a quasi-lexical expansion of the base library + config stanza into several additional support library stanzas, right after + the dune config file parsing is completed. *) +let library_stanzas base_lib = + let ctypes = + match base_lib.Library.ctypes with + | Some ctypes -> ctypes + | None -> assert false + in + let type_descriptions = + library_stanza + ~base_lib + ~name:(type_description_library ctypes) + ~public_name:(type_description_library_public ctypes) + ~modules:[type_description_module ctypes] + ~libraries:["ctypes"] + ~wrapped:true () + in + let function_descriptions = + library_stanza + ~base_lib + ~name:(function_description_library ctypes) + ~public_name:(function_description_library_public ctypes) + ~modules:[ c_generated_types_module ctypes + ; function_description_module ctypes + ; c_types_includer_module ctypes ] + (* ~flags:"-w -27 -w -9" ?*) + ~libraries:["ctypes"; (type_description_library ctypes)] + ~wrapped:false () + in + let combined_final = + let foreign_stub = + let loc, _libname = base_lib.Library.name in + let pos = osl_pos base_lib in + Foreign.Stubs.make ~loc ~language:Foreign_language.C + ~names:(Ordered_set_lang.of_atoms ~loc + [c_generated_functions_cout_no_ext ctypes]) + ~flags:(Ordered_set_lang.Unexpanded.of_strings + ~pos [":include"; cflags_sexp ctypes]) + in + library_stanza + ~base_lib + ~name:(entry_library ctypes) + ~public_name:(entry_library_public ctypes) + ~libraries:["ctypes"; function_description_library ctypes] + ~modules:[ entry_module ctypes + ; c_generated_functions_module ctypes ] + ~foreign_stubs:[foreign_stub] + ~c_library_flags:[":include"; c_library_flags_sexp ctypes] + ~wrapped:true + () + in + [ type_descriptions + ; function_descriptions + ; combined_final ] diff --git a/src/dune_rules/ctypes_stanzas.mli b/src/dune_rules/ctypes_stanzas.mli new file mode 100644 index 00000000000..c670177cab7 --- /dev/null +++ b/src/dune_rules/ctypes_stanzas.mli @@ -0,0 +1,24 @@ +(* Expand a library with a ctypes stanza into several support libraries. *) +open Dune_file + +val type_description_module : Ctypes.t -> Module_name.t +val type_description_library : Ctypes.t -> string + +val function_description_module : Ctypes.t -> Module_name.t +val function_description_library : Ctypes.t -> string + +val cflags_sexp : Ctypes.t -> string +val cflags_txt : Ctypes.t -> string +val c_library_flags_sexp : Ctypes.t -> string +val c_generated_types_module : Ctypes.t -> Module_name.t +val c_generated_functions_module : Ctypes.t -> Module_name.t +val entry_module : Ctypes.t -> Module_name.t + +val c_types_includer_module : Ctypes.t -> Module_name.t + +val c_generated_types_cout_c : Ctypes.t -> string +val c_generated_types_cout_exe : Ctypes.t -> string + +val c_generated_functions_cout_c : Ctypes.t -> string + +val library_stanzas : Library.t -> Library.t list diff --git a/src/dune_rules/dune_file.ml b/src/dune_rules/dune_file.ml index 056b0195749..da5f889039d 100644 --- a/src/dune_rules/dune_file.ml +++ b/src/dune_rules/dune_file.ml @@ -399,11 +399,13 @@ module Mode_conf = struct end module Set = struct + type mode_conf = t + type nonrec t = Kind.t option Map.t let empty : t = Map.make_one None - let of_list (input : (T.t * Kind.t) list) : t = + let of_list (input : (mode_conf * Kind.t) list) : t = List.fold_left ~init:empty input ~f:(fun acc (key, kind) -> Map.update acc key ~f:(function | None -> Some kind @@ -439,6 +441,7 @@ module Mode_conf = struct y end + let eval_detailed t ~has_native = let exists = function | Best @@ -477,31 +480,24 @@ end module Ctypes = struct type t = - { name : string - ; pkg_config_name : string option - ; c_headers : string option - ; generated_modules : string list - } + { lib_name : string + ; includes : string list } let name = "ctypes" type Stanza.t += T of t + let syntax = + Dune_lang.Syntax.create ~name ~desc:"the ctypes extension" + [ ((0, 1), `Since (2, 8)) ] + let decode = let open Dune_lang.Decoder in fields - (let+ name = field "name" string - and+ pkg_config_name = field_o "pkg_config_name" string - and+ c_headers = field_o "c_headers" string - and+ generated_modules = field "generated_modules" (repeat string) + (let+ lib_name = field "lib_name" string + and+ includes = field "includes" (repeat string) ~default:[] in - { name; pkg_config_name; c_headers; generated_modules }) - - let syntax = - Dune_lang.Syntax.create ~name ~desc:"the ctypes extension" - (* XXX: insert the latest version of dune language *) - [ ((0, 1), `Since (2, 8)) - ] + { lib_name; includes }) let () = let open Dune_lang.Decoder in @@ -649,7 +645,8 @@ module Library = struct ( Dune_lang.Syntax.since Stanza.syntax (2, 8) >>> located Stanza_common.Pkg.decode ) and+ ctypes = - (field_o "ctypes" Ctypes.decode) + (field_o "ctypes" + (Dune_lang.Syntax.since Ctypes.syntax (0, 1) >>> Ctypes.decode)) in let wrapped = Wrapped.make ~wrapped ~implements ~special_builtin_support diff --git a/src/dune_rules/dune_file.mli b/src/dune_rules/dune_file.mli index 943117b0ffb..a6c9eaf0839 100644 --- a/src/dune_rules/dune_file.mli +++ b/src/dune_rules/dune_file.mli @@ -68,6 +68,9 @@ module Public_lib : sig (** Package it is part of *) val package : t -> Package.t + + val make : allow_deprecated_names:bool -> Dune_project.t -> + (Loc.t * Lib_name.t) -> (t, User_message.t) result end module Mode_conf : sig @@ -97,8 +100,11 @@ module Mode_conf : sig end module Set : sig + type mode_conf = t type nonrec t = Kind.t option Map.t + val of_list : (mode_conf * Kind.t) list -> t + val decode : t Dune_lang.Decoder.t module Details : sig @@ -108,16 +114,14 @@ module Mode_conf : sig val eval_detailed : t -> has_native:bool -> Details.t Mode.Dict.t val eval : t -> has_native:bool -> Mode.Dict.Set.t + end end module Ctypes : sig type t = - { name : string - ; pkg_config_name : string option - ; c_headers : string option - ; generated_modules : string list - } + { lib_name : string + ; includes : string list } type Stanza.t += T of t end diff --git a/src/dune_rules/dune_load.ml b/src/dune_rules/dune_load.ml index 4d95a345943..e06d3c8dcaf 100644 --- a/src/dune_rules/dune_load.ml +++ b/src/dune_rules/dune_load.ml @@ -11,11 +11,13 @@ module Dune_file = struct let parse sexps ~dir ~file ~project = let stanzas = Dune_file.Stanzas.parse ~file project sexps in - let stanzas = List.concat_map stanzas ~f:(fun stanza -> - match stanza with - | Dune_file.Stanzas.Library { ctypes = Some ctypes; _ } -> - Ctypes_rules.expand stanza - | _ -> [stanza]) + let stanzas = + List.concat_map stanzas ~f:(fun stanza -> + match stanza with + | Dune_file.Library ({ ctypes = Some _; _ } as base_lib) -> + let libs = Ctypes_stanzas.library_stanzas base_lib in + (List.map libs ~f:(fun l -> Dune_file.Library l)) @ [stanza] + | _ -> [stanza]) in let stanzas = if !Clflags.ignore_promoted_rules then diff --git a/src/dune_rules/lib_rules.ml b/src/dune_rules/lib_rules.ml index f41b5053809..84873a24822 100644 --- a/src/dune_rules/lib_rules.ml +++ b/src/dune_rules/lib_rules.ml @@ -430,6 +430,11 @@ let rules (lib : Library.t) ~sctx ~dir_contents ~dir ~expander ~scope : Lib.DB.get_compile_info (Scope.libs scope) (Library.best_name lib) ~allow_overlaps:lib.buildable.allow_overlapping_dependencies in + Option.iter (lib.Library.ctypes) ~f:(fun _ctypes -> + (* ctypes rules need to be generated before the source modules are probed + because it introduces generated modules into the workspace that + library stanzas may depend on. *) + Ctypes_rules.gen_rules ~base_lib:lib ~sctx ~scope ~expander ~dir); let f () = let source_modules = Dir_contents.ocaml dir_contents @@ -441,6 +446,8 @@ let rules (lib : Library.t) ~sctx ~dir_contents ~dir ~expander ~scope : library_rules lib ~cctx ~source_modules ~dir_contents ~compile_info in Buildable_rules.gen_select_rules sctx compile_info ~dir; - Buildable_rules.with_lib_deps - (Super_context.context sctx) - compile_info ~dir ~f + let cctx, merlin = + Buildable_rules.with_lib_deps + (Super_context.context sctx) compile_info ~dir ~f + in + cctx, merlin diff --git a/src/dune_rules/modules_field_evaluator.ml b/src/dune_rules/modules_field_evaluator.ml index 97d408bc066..785f9848e8d 100644 --- a/src/dune_rules/modules_field_evaluator.ml +++ b/src/dune_rules/modules_field_evaluator.ml @@ -40,9 +40,6 @@ let eval = match m with | Ok m -> Some (loc, m) | Error s -> - (* We are going to fail only if the module appear in the final set, - foo \ bar doesn't fail if bar doesn't exists (for jbuild file - compatibility) *) User_error.raise ~loc [ Pp.textf "Module %s doesn't exist." (Module_name.to_string s) ]) diff --git a/src/dune_rules/ordered_set_lang.ml b/src/dune_rules/ordered_set_lang.ml index 10af9380680..e9d7c72f7f9 100644 --- a/src/dune_rules/ordered_set_lang.ml +++ b/src/dune_rules/ordered_set_lang.ml @@ -44,6 +44,10 @@ type ast_expanded = (Loc.t * string, Ast.expanded) Ast.t contained in the set, like we do with the predicate language. *) type t = ast_expanded generic +let of_atoms ~loc lst = + let ast = Ast.Union (List.map lst ~f:(fun s -> Ast.Element (loc, s))) in + { ast; loc = Some loc; context = Univ_map.empty } + let equal = equal_generic (Ast.equal (fun (_, x) (_, y) -> String.equal x y)) let loc t = t.loc diff --git a/src/dune_rules/ordered_set_lang.mli b/src/dune_rules/ordered_set_lang.mli index 68c5a6ec9ab..519a3d11c0d 100644 --- a/src/dune_rules/ordered_set_lang.mli +++ b/src/dune_rules/ordered_set_lang.mli @@ -6,6 +6,8 @@ open Dune_engine type t +val of_atoms : loc:Loc.t -> string list -> t + val decode : t Dune_lang.Decoder.t (** Return the location of the set. [loc standard] returns [None] *) From 6f68c0cc339ae9638ed81c2d0a9e0ce953763da6 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Sun, 6 Dec 2020 18:27:00 -0800 Subject: [PATCH 04/69] have ctypes provide list of generated files to Dir_contents --- src/dune_rules/ctypes_rules.ml | 31 ++++++++++++++++++++----------- src/dune_rules/ctypes_stanzas.ml | 14 +++++++++++++- src/dune_rules/ctypes_stanzas.mli | 2 ++ src/dune_rules/dir_contents.ml | 26 +++++++++++++++++--------- src/dune_rules/dune_load.ml | 2 +- src/dune_rules/lib_rules.ml | 5 +---- 6 files changed, 54 insertions(+), 26 deletions(-) diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index 672bf6973fd..2d8f5dfadd8 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -148,11 +148,15 @@ let write_function_gen_script ~include_headers ~sctx ~dir ~name let script = function_gen_gen ~include_headers ~function_description_module in Super_context.add_rule ~loc:Loc.none sctx ~dir (Build.write_file path script) -let rule ?stdout_to ?(targets=[]) ~run ~sctx ~dir () = +let rule ?stdout_to ?(action_args=[]) ?(targets=[]) ~exe ~sctx ~dir () = let build = let targets = List.map targets ~f:(Path.Build.relative dir) in - let exe = Ok (Path.build (Path.Build.relative dir run)) in - let args = [ Command.Args.Hidden_targets targets ] in + let exe = Ok (Path.build (Path.Build.relative dir exe)) in + let args = + let open Command.Args in + [ Hidden_targets targets + ; As action_args ] + in let stdout_to = Option.map stdout_to ~f:(Path.Build.relative dir) in Command.run exe ~dir:(Path.build dir) ?stdout_to args in @@ -162,13 +166,16 @@ let rule_shell_action ~deps ~targets ~action_args ~sctx ~dir () = let build = let sh_path, sh_arg = Utils.system_shell_exn ~needed_to:"build ctypes" in let targets = List.map targets ~f:(Path.Build.relative dir) in - let deps = List.map deps ~f:(Path.relative (Path.build dir)) in + let deps = + List.map deps ~f:(Path.relative (Path.build dir)) + |> Dep.Set.of_files + in let exe = Ok sh_path in let args = let open Command.Args in - [ Deps deps + [ As (sh_arg :: action_args) ; Hidden_targets targets - ; As (sh_arg :: action_args) ] + ; Hidden_deps deps ] in Command.run exe ~dir:(Path.build dir) args in @@ -270,7 +277,7 @@ let gen_rules ~base_lib ~scope ~expander ~dir ~sctx = (); rule ~targets:[cflags_sexp; cflags_txt; c_library_flags_sexp] - ~run:(discover_script ^ ".exe") + ~exe:(discover_script ^ ".exe") () in let include_headers = ctypes.Ctypes.includes in @@ -298,7 +305,7 @@ let gen_rules ~base_lib ~scope ~expander ~dir ~sctx = ~program:type_gen_script ~libraries:["ctypes.stubs"; "ctypes.foreign"; type_description_library] (); - rule ~stdout_to:c_generated_types_cout_c ~run:(type_gen_script ^ ".exe") (); + rule ~stdout_to:c_generated_types_cout_c ~exe:(type_gen_script ^ ".exe") (); rule_shell_action ~sctx ~dir ~targets:[c_generated_types_cout_exe] @@ -313,7 +320,7 @@ let gen_rules ~base_lib ~scope ~expander ~dir ~sctx = rule ~stdout_to:(Ctypes_stanzas.c_generated_types_module ctypes |> ml_of_module_name) - ~run:c_generated_types_cout_exe + ~exe:c_generated_types_cout_exe () in (* Function_gen is similar to type_gen above, though it produces both an @@ -333,12 +340,14 @@ let gen_rules ~base_lib ~scope ~expander ~dir ~sctx = (); rule ~stdout_to:c_generated_functions_cout_c - ~run:(sprintf "%s.exe c %s" function_gen_script stubs_prefix) + ~exe:(function_gen_script ^ ".exe") + ~action_args:["c"; stubs_prefix] (); rule ~stdout_to:(Ctypes_stanzas.c_generated_functions_module ctypes |> ml_of_module_name) - ~run:(sprintf "%s.exe ml %s" function_gen_script stubs_prefix) + ~exe:(function_gen_script ^ ".exe") + ~action_args:["ml"; stubs_prefix] () in () diff --git a/src/dune_rules/ctypes_stanzas.ml b/src/dune_rules/ctypes_stanzas.ml index 27dbb03e38f..b0aa56f614a 100644 --- a/src/dune_rules/ctypes_stanzas.ml +++ b/src/dune_rules/ctypes_stanzas.ml @@ -8,7 +8,6 @@ let osl_pos _base_lib = "", 0, 0, 0 ;; let library_stanza ?public_name ?(foreign_stubs=[]) ?c_library_flags ~base_lib:lib ~name ~modules ~libraries ~wrapped () = - Printf.printf "*** generate library stanza: %s\n%!" name; let loc, _libname = lib.Library.name in let open Dune_file in let visibility = @@ -210,3 +209,16 @@ let library_stanzas base_lib = [ type_descriptions ; function_descriptions ; combined_final ] + +let generated_ml_and_c_files ctypes = + let ml_files = + List.map [ c_generated_functions_module ctypes + ; c_generated_types_module ctypes + ; c_types_includer_module ctypes ] + ~f:Module_name.to_string + |> List.map ~f:(fun m -> m ^ ".ml") + in + let c_files = + [ c_generated_functions_cout_c ctypes ] + in + ml_files @ c_files diff --git a/src/dune_rules/ctypes_stanzas.mli b/src/dune_rules/ctypes_stanzas.mli index c670177cab7..5dabddfbad9 100644 --- a/src/dune_rules/ctypes_stanzas.mli +++ b/src/dune_rules/ctypes_stanzas.mli @@ -22,3 +22,5 @@ val c_generated_types_cout_exe : Ctypes.t -> string val c_generated_functions_cout_c : Ctypes.t -> string val library_stanzas : Library.t -> Library.t list + +val generated_ml_and_c_files : Ctypes.t -> string list diff --git a/src/dune_rules/dir_contents.ml b/src/dune_rules/dir_contents.ml index e5ba636b924..7f231e6f9c9 100644 --- a/src/dune_rules/dir_contents.ml +++ b/src/dune_rules/dir_contents.ml @@ -132,6 +132,15 @@ end = struct in Expander.set_artifacts_dynamic expander true in + let buildable_select_deps buildable = + (* Manually add files generated by the (select ...) dependencies *) + List.filter_map buildable.Buildable.libraries ~f:(fun dep -> + match (dep : Lib_dep.t) with + | Re_export _ + | Direct _ -> + None + | Select s -> Some s.result_fn) + in let generated_files = List.concat_map stanzas ~f:(fun stanza -> match (stanza : Stanza.t) with @@ -150,15 +159,14 @@ end = struct |> Path.Set.to_list |> List.map ~f:Path.basename | Generate_module def -> [ Generate_module_rules.setup_rules sctx ~dir def ] - | Library { buildable; _ } - | Executables { buildable; _ } -> - (* Manually add files generated by the (select ...) dependencies *) - List.filter_map buildable.libraries ~f:(fun dep -> - match (dep : Lib_dep.t) with - | Re_export _ - | Direct _ -> - None - | Select s -> Some s.result_fn) + | Executables { buildable; _ } -> buildable_select_deps buildable + | Library { buildable; ctypes; _ } -> + let ctypes_generated_ml_and_c_files = + match ctypes with + | Some ctypes -> Ctypes_stanzas.generated_ml_and_c_files ctypes + | None -> [] + in + ctypes_generated_ml_and_c_files @ buildable_select_deps buildable | _ -> []) |> String.Set.of_list in diff --git a/src/dune_rules/dune_load.ml b/src/dune_rules/dune_load.ml index e06d3c8dcaf..aa1a069e897 100644 --- a/src/dune_rules/dune_load.ml +++ b/src/dune_rules/dune_load.ml @@ -16,7 +16,7 @@ module Dune_file = struct match stanza with | Dune_file.Library ({ ctypes = Some _; _ } as base_lib) -> let libs = Ctypes_stanzas.library_stanzas base_lib in - (List.map libs ~f:(fun l -> Dune_file.Library l)) @ [stanza] + stanza :: (List.map libs ~f:(fun l -> Dune_file.Library l)) | _ -> [stanza]) in let stanzas = diff --git a/src/dune_rules/lib_rules.ml b/src/dune_rules/lib_rules.ml index 84873a24822..54cfc3aa74c 100644 --- a/src/dune_rules/lib_rules.ml +++ b/src/dune_rules/lib_rules.ml @@ -430,10 +430,7 @@ let rules (lib : Library.t) ~sctx ~dir_contents ~dir ~expander ~scope : Lib.DB.get_compile_info (Scope.libs scope) (Library.best_name lib) ~allow_overlaps:lib.buildable.allow_overlapping_dependencies in - Option.iter (lib.Library.ctypes) ~f:(fun _ctypes -> - (* ctypes rules need to be generated before the source modules are probed - because it introduces generated modules into the workspace that - library stanzas may depend on. *) + Option.iter lib.Library.ctypes ~f:(fun _ctypes -> Ctypes_rules.gen_rules ~base_lib:lib ~sctx ~scope ~expander ~dir); let f () = let source_modules = From 5ea1a03a631a43d3481a314a24d7a190d42a2ebc Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Sun, 6 Dec 2020 18:39:03 -0800 Subject: [PATCH 05/69] lowercase --- src/dune_rules/ctypes_stanzas.ml | 1 + 1 file changed, 1 insertion(+) diff --git a/src/dune_rules/ctypes_stanzas.ml b/src/dune_rules/ctypes_stanzas.ml index b0aa56f614a..35bfe856371 100644 --- a/src/dune_rules/ctypes_stanzas.ml +++ b/src/dune_rules/ctypes_stanzas.ml @@ -216,6 +216,7 @@ let generated_ml_and_c_files ctypes = ; c_generated_types_module ctypes ; c_types_includer_module ctypes ] ~f:Module_name.to_string + |> List.map ~f:String.lowercase |> List.map ~f:(fun m -> m ^ ".ml") in let c_files = From f372ccdbd99efb8f28b2202953d7956803728ff6 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Thu, 24 Dec 2020 11:19:58 -0800 Subject: [PATCH 06/69] save progress --- src/dune_rules/ctypes_rules.ml | 99 +++++++++++++++++++++------------- 1 file changed, 61 insertions(+), 38 deletions(-) diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index 2d8f5dfadd8..e20d8832ea8 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -148,38 +148,63 @@ let write_function_gen_script ~include_headers ~sctx ~dir ~name let script = function_gen_gen ~include_headers ~function_description_module in Super_context.add_rule ~loc:Loc.none sctx ~dir (Build.write_file path script) -let rule ?stdout_to ?(action_args=[]) ?(targets=[]) ~exe ~sctx ~dir () = +let rule ?(deps=[]) ?stdout_to ?(args=[]) ?(targets=[]) ~exe ~sctx ~dir () = let build = - let targets = List.map targets ~f:(Path.Build.relative dir) in - let exe = Ok (Path.build (Path.Build.relative dir exe)) in + let exe = + match exe with + | `relative exe -> Ok (Path.build (Path.Build.relative dir exe)) + | `unresolved exe -> Super_context.resolve_program ~loc:None ~dir sctx exe + in let args = + let targets = List.map targets ~f:(Path.Build.relative dir) in + let deps = + List.map deps ~f:(Path.relative (Path.build dir)) + |> Dep.Set.of_files + in let open Command.Args in [ Hidden_targets targets - ; As action_args ] + ; Hidden_deps deps + ; As args ] in let stdout_to = Option.map stdout_to ~f:(Path.Build.relative dir) in Command.run exe ~dir:(Path.build dir) ?stdout_to args in Super_context.add_rule sctx ~dir build -let rule_shell_action ~deps ~targets ~action_args ~sctx ~dir () = - let build = - let sh_path, sh_arg = Utils.system_shell_exn ~needed_to:"build ctypes" in - let targets = List.map targets ~f:(Path.Build.relative dir) in - let deps = - List.map deps ~f:(Path.relative (Path.build dir)) - |> Dep.Set.of_files - in - let exe = Ok sh_path in - let args = - let open Command.Args in - [ As (sh_arg :: action_args) - ; Hidden_targets targets - ; Hidden_deps deps ] +let build_c_program ~sctx ~dir ~source_files ~scope ~cflags_txt ~output () = + let ctx = Super_context.context sctx in + let exe = `unresolved (Ocaml_config.c_compiler ctx.Context.ocaml_config) in + let include_args = + (* XXX: need glob dependency *) + let ocaml_where = Path.to_string ctx.Context.stdlib_dir in + (* XXX: need glob dependency *) + let ctypes_include_dirs = + let ctypes = Lib_name.of_string "ctypes" in + let lib = + match Lib.DB.resolve (Scope.libs scope) (Loc.none, ctypes) with + | Ok lib -> lib + | Error _res -> + (* XXX: User_error.raise *) + failwith "error resolving 'ctypes' lib" + in + Lib.L.include_paths [lib] + |> Path.Set.to_list + |> List.map ~f:Path.to_string in - Command.run exe ~dir:(Path.build dir) args + let include_dirs = ocaml_where :: ctypes_include_dirs in + List.concat_map include_dirs ~f:(fun dir -> ["-I"; dir]) in - Super_context.add_rule sctx ~dir build + let cflags_args = + (* XXX: can we read the semantically identical cflags_sexp file and eliminate creating + this extra cflags_txt file? We do this in ctypes_stanzas: + Ordered_set_lang.Unexpanded.of_strings ~pos [":include"; cflags_sexp ... ] *) + let build = Build.contents (Path.relative (Path.build dir) cflags_txt) in + let contents, deps = Build.exec build in + assert (Dep.Set.is_empty deps); + String.split ~on:' ' contents + in + rule ~deps:source_files ~targets:[output] ~exe ~sctx ~dir + ~args:(cflags_args @ include_args @ source_files @ ["-o"; output]) () let cctx ~base_lib ?(libraries=[]) ~loc ~dir ~scope ~expander ~sctx = let compile_info = @@ -264,8 +289,8 @@ let gen_rules ~base_lib ~scope ~expander ~dir ~sctx = https://dune.readthedocs.io/en/stable/quick-start.html#defining-a-library-with-c-stubs-using-pkg-config *) let c_library_flags_sexp = Ctypes_stanzas.c_library_flags_sexp ctypes in + let cflags_txt = Ctypes_stanzas.cflags_txt ctypes in let () = - let cflags_txt = Ctypes_stanzas.cflags_txt ctypes in let cflags_sexp = Ctypes_stanzas.cflags_sexp ctypes in let discover_script = sprintf "%s__ctypes_discover" external_lib_name in write_discover_script @@ -277,7 +302,7 @@ let gen_rules ~base_lib ~scope ~expander ~dir ~sctx = (); rule ~targets:[cflags_sexp; cflags_txt; c_library_flags_sexp] - ~exe:(discover_script ^ ".exe") + ~exe:(`relative (discover_script ^ ".exe")) () in let include_headers = ctypes.Ctypes.includes in @@ -305,22 +330,20 @@ let gen_rules ~base_lib ~scope ~expander ~dir ~sctx = ~program:type_gen_script ~libraries:["ctypes.stubs"; "ctypes.foreign"; type_description_library] (); - rule ~stdout_to:c_generated_types_cout_c ~exe:(type_gen_script ^ ".exe") (); - rule_shell_action - ~sctx ~dir - ~targets:[c_generated_types_cout_exe] - ~deps:[c_generated_types_cout_c] - (* XXX: these substitutions probably won't work *) - ~action_args:["%{cc}"; c_generated_types_cout_c; - "-I"; "%{lib:ctypes:.}"; - "-I"; "%{ocaml_where}"; - "%{read:c_flags.txt}"; - "-o"; "%{targets}"] + rule + ~stdout_to:c_generated_types_cout_c + ~exe:(`relative (type_gen_script ^ ".exe")) + (); + build_c_program + ~sctx ~dir ~scope + ~source_files:[c_generated_types_cout_c] + ~cflags_txt (*" %{read:c_flags.txt}" *) + ~output:c_generated_types_cout_exe (); rule ~stdout_to:(Ctypes_stanzas.c_generated_types_module ctypes |> ml_of_module_name) - ~exe:c_generated_types_cout_exe + ~exe:(`relative c_generated_types_cout_exe) () in (* Function_gen is similar to type_gen above, though it produces both an @@ -340,14 +363,14 @@ let gen_rules ~base_lib ~scope ~expander ~dir ~sctx = (); rule ~stdout_to:c_generated_functions_cout_c - ~exe:(function_gen_script ^ ".exe") - ~action_args:["c"; stubs_prefix] + ~exe:(`relative (function_gen_script ^ ".exe")) + ~args:["c"; stubs_prefix] (); rule ~stdout_to:(Ctypes_stanzas.c_generated_functions_module ctypes |> ml_of_module_name) - ~exe:(function_gen_script ^ ".exe") - ~action_args:["ml"; stubs_prefix] + ~exe:(`relative (function_gen_script ^ ".exe")) + ~args:["ml"; stubs_prefix] () in () From 5743185e49c51e50d1cdf7ca48310efb16154ae7 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Fri, 25 Dec 2020 07:31:56 -0800 Subject: [PATCH 07/69] dont use Build.exec --- src/dune_rules/ctypes_rules.ml | 31 ++++++++++++++++++++++++------- 1 file changed, 24 insertions(+), 7 deletions(-) diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index e20d8832ea8..22d4a5b312c 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -173,7 +173,10 @@ let rule ?(deps=[]) ?stdout_to ?(args=[]) ?(targets=[]) ~exe ~sctx ~dir () = let build_c_program ~sctx ~dir ~source_files ~scope ~cflags_txt ~output () = let ctx = Super_context.context sctx in - let exe = `unresolved (Ocaml_config.c_compiler ctx.Context.ocaml_config) in + let exe = + Ocaml_config.c_compiler ctx.Context.ocaml_config + |> Super_context.resolve_program ~loc:None ~dir sctx + in let include_args = (* XXX: need glob dependency *) let ocaml_where = Path.to_string ctx.Context.stdlib_dir in @@ -194,17 +197,31 @@ let build_c_program ~sctx ~dir ~source_files ~scope ~cflags_txt ~output () = let include_dirs = ocaml_where :: ctypes_include_dirs in List.concat_map include_dirs ~f:(fun dir -> ["-I"; dir]) in - let cflags_args = + let deps = + List.map source_files ~f:(Path.relative (Path.build dir)) + |> Dep.Set.of_files + in + let build = (* XXX: can we read the semantically identical cflags_sexp file and eliminate creating this extra cflags_txt file? We do this in ctypes_stanzas: Ordered_set_lang.Unexpanded.of_strings ~pos [":include"; cflags_sexp ... ] *) - let build = Build.contents (Path.relative (Path.build dir) cflags_txt) in - let contents, deps = Build.exec build in - assert (Dep.Set.is_empty deps); - String.split ~on:' ' contents + let contents = Build.contents (Path.relative (Path.build dir) cflags_txt) in + let cflags_args = Build.map contents ~f:(String.split ~on:' ') in + let action = + let open Build.O in + Build.deps deps + >>> Build.map cflags_args ~f:(fun cflags_args -> + let args = cflags_args @ include_args @ source_files @ ["-o"; output] in + Action.run exe args) + in + Build.with_targets action ~targets:[Path.Build.relative dir output] in - rule ~deps:source_files ~targets:[output] ~exe ~sctx ~dir + Super_context.add_rule sctx ~dir build +(* + + rule ~promised_args:cflags_args ~deps:source_files ~targets:[output] ~exe ~sctx ~dir ~args:(cflags_args @ include_args @ source_files @ ["-o"; output]) () + *) let cctx ~base_lib ?(libraries=[]) ~loc ~dir ~scope ~expander ~sctx = let compile_info = From c68c1b6d802cfc4fced596b58733590142691a6d Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Fri, 25 Dec 2020 07:36:10 -0800 Subject: [PATCH 08/69] no need for this variant anymore --- src/dune_rules/ctypes_rules.ml | 16 ++++++---------- 1 file changed, 6 insertions(+), 10 deletions(-) diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index 22d4a5b312c..e5533349a61 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -150,11 +150,7 @@ let write_function_gen_script ~include_headers ~sctx ~dir ~name let rule ?(deps=[]) ?stdout_to ?(args=[]) ?(targets=[]) ~exe ~sctx ~dir () = let build = - let exe = - match exe with - | `relative exe -> Ok (Path.build (Path.Build.relative dir exe)) - | `unresolved exe -> Super_context.resolve_program ~loc:None ~dir sctx exe - in + let exe = Ok (Path.build (Path.Build.relative dir exe)) in let args = let targets = List.map targets ~f:(Path.Build.relative dir) in let deps = @@ -319,7 +315,7 @@ let gen_rules ~base_lib ~scope ~expander ~dir ~sctx = (); rule ~targets:[cflags_sexp; cflags_txt; c_library_flags_sexp] - ~exe:(`relative (discover_script ^ ".exe")) + ~exe:(discover_script ^ ".exe") () in let include_headers = ctypes.Ctypes.includes in @@ -349,7 +345,7 @@ let gen_rules ~base_lib ~scope ~expander ~dir ~sctx = (); rule ~stdout_to:c_generated_types_cout_c - ~exe:(`relative (type_gen_script ^ ".exe")) + ~exe:(type_gen_script ^ ".exe") (); build_c_program ~sctx ~dir ~scope @@ -360,7 +356,7 @@ let gen_rules ~base_lib ~scope ~expander ~dir ~sctx = rule ~stdout_to:(Ctypes_stanzas.c_generated_types_module ctypes |> ml_of_module_name) - ~exe:(`relative c_generated_types_cout_exe) + ~exe:(c_generated_types_cout_exe) () in (* Function_gen is similar to type_gen above, though it produces both an @@ -380,13 +376,13 @@ let gen_rules ~base_lib ~scope ~expander ~dir ~sctx = (); rule ~stdout_to:c_generated_functions_cout_c - ~exe:(`relative (function_gen_script ^ ".exe")) + ~exe:(function_gen_script ^ ".exe") ~args:["c"; stubs_prefix] (); rule ~stdout_to:(Ctypes_stanzas.c_generated_functions_module ctypes |> ml_of_module_name) - ~exe:(`relative (function_gen_script ^ ".exe")) + ~exe:(function_gen_script ^ ".exe") ~args:["ml"; stubs_prefix] () in From 83947d81e598acdc2df23feaa7a74ea3a08a6a1e Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Tue, 26 Jan 2021 12:02:27 -0800 Subject: [PATCH 09/69] saving work, almost almost compiles a ctypes module --- src/dune_rules/ctypes_stanzas.ml | 19 +++++++++++++------ src/dune_rules/dune_file.ml | 3 +++ src/dune_rules/ocaml_flags.ml | 4 ++++ src/dune_rules/ocaml_flags.mli | 2 ++ src/dune_rules/ordered_set_lang.ml | 16 ++++++++++++++++ src/dune_rules/ordered_set_lang.mli | 4 ++++ 6 files changed, 42 insertions(+), 6 deletions(-) diff --git a/src/dune_rules/ctypes_stanzas.ml b/src/dune_rules/ctypes_stanzas.ml index 35bfe856371..2209fd4e932 100644 --- a/src/dune_rules/ctypes_stanzas.ml +++ b/src/dune_rules/ctypes_stanzas.ml @@ -6,8 +6,8 @@ module Ctypes = Dune_file.Ctypes let osl_pos _base_lib = "", 0, 0, 0 ;; -let library_stanza ?public_name ?(foreign_stubs=[]) ?c_library_flags - ~base_lib:lib ~name ~modules ~libraries ~wrapped () = +let library_stanza ?(flags=Ocaml_flags.Spec.standard) ?public_name ?(foreign_stubs=[]) + ?c_library_flags ~base_lib:lib ~name ~modules ~libraries ~wrapped () = let loc, _libname = lib.Library.name in let open Dune_file in let visibility = @@ -45,7 +45,7 @@ let library_stanza ?public_name ?(foreign_stubs=[]) ?c_library_flags ; preprocess = Preprocess.Per_module.default () ; preprocessor_deps = [] ; lint = Lint.no_lint - ; flags = Ocaml_flags.Spec.standard + ; flags ; js_of_ocaml = Js_of_ocaml.default ; allow_overlapping_dependencies = false } @@ -173,6 +173,13 @@ let library_stanzas base_lib = ~wrapped:true () in let function_descriptions = + let flags = + (* The ctypes library emits code with some warnings; disable them so we + don't break compilation when warnings-as-errors *) + Ocaml_flags.Spec.of_unexpanded_ordered_set_lang + (Ordered_set_lang.Unexpanded.standard_with_of_strings + ~pos:(osl_pos base_lib) ["-w"; "-27"; "-w"; "-9"]) + in library_stanza ~base_lib ~name:(function_description_library ctypes) @@ -180,7 +187,7 @@ let library_stanzas base_lib = ~modules:[ c_generated_types_module ctypes ; function_description_module ctypes ; c_types_includer_module ctypes ] - (* ~flags:"-w -27 -w -9" ?*) + ~flags ~libraries:["ctypes"; (type_description_library ctypes)] ~wrapped:false () in @@ -191,8 +198,8 @@ let library_stanzas base_lib = Foreign.Stubs.make ~loc ~language:Foreign_language.C ~names:(Ordered_set_lang.of_atoms ~loc [c_generated_functions_cout_no_ext ctypes]) - ~flags:(Ordered_set_lang.Unexpanded.of_strings - ~pos [":include"; cflags_sexp ctypes]) + ~flags:(Ordered_set_lang.Unexpanded.include_single + ~pos (cflags_sexp ctypes)) in library_stanza ~base_lib diff --git a/src/dune_rules/dune_file.ml b/src/dune_rules/dune_file.ml index da5f889039d..309473e3f7e 100644 --- a/src/dune_rules/dune_file.ml +++ b/src/dune_rules/dune_file.ml @@ -479,6 +479,9 @@ module Mode_conf = struct end module Ctypes = struct + (* XXX: this is a placeholder for the spec we talked about in PR#3905. + At the moment just trying to get a minimal example to compile and build + properly. *) type t = { lib_name : string ; includes : string list } diff --git a/src/dune_rules/ocaml_flags.ml b/src/dune_rules/ocaml_flags.ml index c350b70bbc0..cbe0d8405b9 100644 --- a/src/dune_rules/ocaml_flags.ml +++ b/src/dune_rules/ocaml_flags.ml @@ -76,6 +76,10 @@ module Spec = struct ; specific = Mode.Dict.make_both Ordered_set_lang.Unexpanded.standard } + let of_unexpanded_ordered_set_lang osl = + { common = osl + ; specific = Mode.Dict.make_both osl } + let decode = let open Dune_lang.Decoder in let field_oslu = Ordered_set_lang.Unexpanded.field in diff --git a/src/dune_rules/ocaml_flags.mli b/src/dune_rules/ocaml_flags.mli index 832c873c40f..3e18379942c 100644 --- a/src/dune_rules/ocaml_flags.mli +++ b/src/dune_rules/ocaml_flags.mli @@ -13,6 +13,8 @@ module Spec : sig val decode : t Dune_lang.Decoder.fields_parser val standard : t + + val of_unexpanded_ordered_set_lang : Ordered_set_lang.Unexpanded.t -> t end val make : diff --git a/src/dune_rules/ordered_set_lang.ml b/src/dune_rules/ordered_set_lang.ml index e9d7c72f7f9..ec1ae9fbd20 100644 --- a/src/dune_rules/ordered_set_lang.ml +++ b/src/dune_rules/ordered_set_lang.ml @@ -269,6 +269,22 @@ module Unexpanded = struct ; context = Univ_map.empty } + let standard_with_of_strings ~pos l = + { ast = + Ast.Union + (Standard :: List.map l ~f:(fun x -> + Ast.Element (String_with_vars.virt_text pos x))) + ; loc = Some (Loc.of_pos pos) + ; context = Univ_map.empty + } + + let include_single ~pos f = + { ast = Ast.Include (String_with_vars.virt_text pos f) + ; loc = Some (Loc.of_pos pos) + ; context = Univ_map.empty + } + + let field ?check name = let decode = match check with diff --git a/src/dune_rules/ordered_set_lang.mli b/src/dune_rules/ordered_set_lang.mli index 519a3d11c0d..cff35eaa9a1 100644 --- a/src/dune_rules/ordered_set_lang.mli +++ b/src/dune_rules/ordered_set_lang.mli @@ -57,6 +57,10 @@ module Unexpanded : sig val of_strings : pos:string * int * int * int -> string list -> t + val standard_with_of_strings : pos:string * int * int * int -> string list -> t + + val include_single : pos:string * int * int * int -> string -> t + val field : ?check:unit Dune_lang.Decoder.t -> string From 69a0f55d0fceacbec0fbc63e689f47834fdac1c7 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Fri, 29 Jan 2021 12:15:36 -0800 Subject: [PATCH 10/69] include parsing_context for :include directives --- src/dune_engine/dune_project.ml | 2 ++ src/dune_engine/dune_project.mli | 2 ++ src/dune_rules/ctypes_stanzas.ml | 20 ++++++++------------ src/dune_rules/ctypes_stanzas.mli | 2 +- src/dune_rules/dune_load.ml | 5 ++++- src/dune_rules/ordered_set_lang.ml | 4 ++-- src/dune_rules/ordered_set_lang.mli | 2 +- 7 files changed, 20 insertions(+), 17 deletions(-) diff --git a/src/dune_engine/dune_project.ml b/src/dune_engine/dune_project.ml index a143383f57c..e8865e16433 100644 --- a/src/dune_engine/dune_project.ml +++ b/src/dune_engine/dune_project.ml @@ -174,6 +174,8 @@ let equal = ( == ) let hash = Hashtbl.hash +let parsing_context t = t.parsing_context + let packages t = t.packages let version t = t.version diff --git a/src/dune_engine/dune_project.mli b/src/dune_engine/dune_project.mli index 9d069ab0ace..ec49c495af5 100644 --- a/src/dune_engine/dune_project.mli +++ b/src/dune_engine/dune_project.mli @@ -77,6 +77,8 @@ val equal : t -> t -> bool val hash : t -> int +val parsing_context : t -> Univ_map.t + (** Return the path of the project file. *) val file : t -> Path.Source.t diff --git a/src/dune_rules/ctypes_stanzas.ml b/src/dune_rules/ctypes_stanzas.ml index 2209fd4e932..740b3f90aaa 100644 --- a/src/dune_rules/ctypes_stanzas.ml +++ b/src/dune_rules/ctypes_stanzas.ml @@ -7,7 +7,8 @@ module Ctypes = Dune_file.Ctypes let osl_pos _base_lib = "", 0, 0, 0 ;; let library_stanza ?(flags=Ocaml_flags.Spec.standard) ?public_name ?(foreign_stubs=[]) - ?c_library_flags ~base_lib:lib ~name ~modules ~libraries ~wrapped () = + ?(c_library_flags=Ordered_set_lang.Unexpanded.standard) ~base_lib:lib + ~name ~modules ~libraries ~wrapped () = let loc, _libname = lib.Library.name in let open Dune_file in let visibility = @@ -50,13 +51,6 @@ let library_stanza ?(flags=Ocaml_flags.Spec.standard) ?public_name ?(foreign_stu ; allow_overlapping_dependencies = false } in - let c_library_flags = - match c_library_flags with - | None -> Ordered_set_lang.Unexpanded.standard - | Some lst -> - let pos = osl_pos lib in - Ordered_set_lang.Unexpanded.of_strings ~pos lst - in { Library.name = (loc, Lib_name.of_string name |> Lib_name.to_local_exn) ; visibility ; synopsis = None @@ -157,7 +151,7 @@ let c_generated_functions_cout_no_ext ctypes = approach here is to simply do a quasi-lexical expansion of the base library config stanza into several additional support library stanzas, right after the dune config file parsing is completed. *) -let library_stanzas base_lib = +let library_stanzas ~parsing_context base_lib = let ctypes = match base_lib.Library.ctypes with | Some ctypes -> ctypes @@ -192,14 +186,14 @@ let library_stanzas base_lib = ~wrapped:false () in let combined_final = + let pos = osl_pos base_lib in let foreign_stub = let loc, _libname = base_lib.Library.name in - let pos = osl_pos base_lib in Foreign.Stubs.make ~loc ~language:Foreign_language.C ~names:(Ordered_set_lang.of_atoms ~loc [c_generated_functions_cout_no_ext ctypes]) ~flags:(Ordered_set_lang.Unexpanded.include_single - ~pos (cflags_sexp ctypes)) + ~context:parsing_context ~pos (cflags_sexp ctypes)) in library_stanza ~base_lib @@ -209,7 +203,9 @@ let library_stanzas base_lib = ~modules:[ entry_module ctypes ; c_generated_functions_module ctypes ] ~foreign_stubs:[foreign_stub] - ~c_library_flags:[":include"; c_library_flags_sexp ctypes] + ~c_library_flags:(Ordered_set_lang.Unexpanded.include_single + ~context:parsing_context ~pos + (c_library_flags_sexp ctypes)) ~wrapped:true () in diff --git a/src/dune_rules/ctypes_stanzas.mli b/src/dune_rules/ctypes_stanzas.mli index 5dabddfbad9..76518857ede 100644 --- a/src/dune_rules/ctypes_stanzas.mli +++ b/src/dune_rules/ctypes_stanzas.mli @@ -21,6 +21,6 @@ val c_generated_types_cout_exe : Ctypes.t -> string val c_generated_functions_cout_c : Ctypes.t -> string -val library_stanzas : Library.t -> Library.t list +val library_stanzas : parsing_context:Stdune.Univ_map.t -> Library.t -> Library.t list val generated_ml_and_c_files : Ctypes.t -> string list diff --git a/src/dune_rules/dune_load.ml b/src/dune_rules/dune_load.ml index aa1a069e897..9ec9df5573c 100644 --- a/src/dune_rules/dune_load.ml +++ b/src/dune_rules/dune_load.ml @@ -15,7 +15,10 @@ module Dune_file = struct List.concat_map stanzas ~f:(fun stanza -> match stanza with | Dune_file.Library ({ ctypes = Some _; _ } as base_lib) -> - let libs = Ctypes_stanzas.library_stanzas base_lib in + let libs = + let parsing_context = Dune_project.parsing_context project in + Ctypes_stanzas.library_stanzas ~parsing_context base_lib + in stanza :: (List.map libs ~f:(fun l -> Dune_file.Library l)) | _ -> [stanza]) in diff --git a/src/dune_rules/ordered_set_lang.ml b/src/dune_rules/ordered_set_lang.ml index ec1ae9fbd20..532c468f196 100644 --- a/src/dune_rules/ordered_set_lang.ml +++ b/src/dune_rules/ordered_set_lang.ml @@ -278,10 +278,10 @@ module Unexpanded = struct ; context = Univ_map.empty } - let include_single ~pos f = + let include_single ~context ~pos f = { ast = Ast.Include (String_with_vars.virt_text pos f) ; loc = Some (Loc.of_pos pos) - ; context = Univ_map.empty + ; context } diff --git a/src/dune_rules/ordered_set_lang.mli b/src/dune_rules/ordered_set_lang.mli index cff35eaa9a1..4fe79e7ed1c 100644 --- a/src/dune_rules/ordered_set_lang.mli +++ b/src/dune_rules/ordered_set_lang.mli @@ -59,7 +59,7 @@ module Unexpanded : sig val standard_with_of_strings : pos:string * int * int * int -> string list -> t - val include_single : pos:string * int * int * int -> string -> t + val include_single : context:Univ_map.t -> pos:string * int * int * int -> string -> t val field : ?check:unit Dune_lang.Decoder.t From a4d7fc37cc9d5251f352f06a2dcac835dfdc712d Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Sun, 31 Jan 2021 07:46:05 -0800 Subject: [PATCH 11/69] minimal example works --- src/dune_rules/ctypes_stanzas.ml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/dune_rules/ctypes_stanzas.ml b/src/dune_rules/ctypes_stanzas.ml index 740b3f90aaa..8166a4d3af8 100644 --- a/src/dune_rules/ctypes_stanzas.ml +++ b/src/dune_rules/ctypes_stanzas.ml @@ -64,7 +64,7 @@ let library_stanza ?(flags=Ocaml_flags.Spec.standard) ?public_name ?(foreign_stu ; wrapped = Lib_info.Inherited.This (Wrapped.Simple wrapped) ; optional = false ; buildable - ; dynlink = Dynlink_supported.of_bool false + ; dynlink = Dynlink_supported.of_bool true ; project = lib.Library.project ; sub_systems = lib.Library.sub_systems ; dune_version = lib.Library.dune_version From 76a50c91cc7efcc726434736a58267013c7dcc13 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Tue, 2 Feb 2021 15:18:35 -0800 Subject: [PATCH 12/69] declare module names --- src/dune_rules/ctypes_rules.ml | 40 ++++++++++++++++++++++++-------- src/dune_rules/ctypes_stanzas.ml | 27 +++++++++++++-------- src/dune_rules/dune_file.ml | 13 +++++++++-- src/dune_rules/dune_file.mli | 7 ++++-- 4 files changed, 63 insertions(+), 24 deletions(-) diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index e5533349a61..14087cfdce6 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -61,8 +61,23 @@ let write_c_types_includer_module ~sctx ~dir ~filename ~type_description_module let buf = Buffer.create 1024 in let pr buf fmt = Printf.bprintf buf (fmt ^^ "\n") in pr buf "include %s.Types (%s)" - (Module_name.to_string type_description_module) - (Module_name.to_string c_generated_types_module); + (Module_name.to_string type_description_module) + (Module_name.to_string c_generated_types_module); + Buffer.contents buf + in + Super_context.add_rule ~loc:Loc.none sctx ~dir + (Build.write_file path contents) + +let write_entry_point_module ~sctx ~dir ~filename ~function_description_module + ~c_generated_functions_module ~c_types_includer_module = + let path = Path.Build.relative dir filename in + let contents = + let buf = Buffer.create 1024 in + let pr buf fmt = Printf.bprintf buf (fmt ^^ "\n") in + pr buf "module Types = %s" (Module_name.to_string c_types_includer_module); + pr buf "module Functions = %s.Functions (%s)" + (Module_name.to_string function_description_module) + (Module_name.to_string c_generated_functions_module); Buffer.contents buf in Super_context.add_rule ~loc:Loc.none sctx ~dir @@ -213,11 +228,6 @@ let build_c_program ~sctx ~dir ~source_files ~scope ~cflags_txt ~output () = Build.with_targets action ~targets:[Path.Build.relative dir output] in Super_context.add_rule sctx ~dir build -(* - - rule ~promised_args:cflags_args ~deps:source_files ~targets:[output] ~exe ~sctx ~dir - ~args:(cflags_args @ include_args @ source_files @ ["-o"; output]) () - *) let cctx ~base_lib ?(libraries=[]) ~loc ~dir ~scope ~expander ~sctx = let compile_info = @@ -289,13 +299,13 @@ let gen_rules ~base_lib ~scope ~expander ~dir ~sctx = let function_description_library = Ctypes_stanzas.function_description_library ctypes in (* This includer module is simply some glue to instantiate the Types functor that the user provides in the type description module. *) + let c_types_includer_module = Ctypes_stanzas.c_types_includer_module ctypes in let () = write_c_types_includer_module ~sctx ~dir - ~filename:(Ctypes_stanzas.c_types_includer_module ctypes - |> ml_of_module_name) + ~filename:(ml_of_module_name c_types_includer_module) ~c_generated_types_module:(Ctypes_stanzas.c_generated_types_module ctypes) - ~type_description_module; + ~type_description_module in (* The discover script uses dune configurator / pkg_config to figure out how to invoke the compiler and linker for your external C library. @@ -386,4 +396,14 @@ let gen_rules ~base_lib ~scope ~expander ~dir ~sctx = ~args:["ml"; stubs_prefix] () in + (* The entry point module binds the instantiated Types and Functions functors + to the entry point module name the user specified. *) + let () = + write_entry_point_module + ~sctx ~dir + ~filename:(Ctypes_stanzas.entry_module ctypes |> ml_of_module_name) + ~function_description_module:(Ctypes_stanzas.function_description_module ctypes) + ~c_generated_functions_module:(Ctypes_stanzas.c_generated_functions_module ctypes) + ~c_types_includer_module + in () diff --git a/src/dune_rules/ctypes_stanzas.ml b/src/dune_rules/ctypes_stanzas.ml index 8166a4d3af8..396c3a079a0 100644 --- a/src/dune_rules/ctypes_stanzas.ml +++ b/src/dune_rules/ctypes_stanzas.ml @@ -81,31 +81,32 @@ let library_stanza ?(flags=Ocaml_flags.Spec.standard) ?public_name ?(foreign_stu let sprintf = Printf.sprintf let type_description_module ctypes = - sprintf "%s__c_type_descriptions" ctypes.Ctypes.lib_name - |> Module_name.of_string + ctypes.Ctypes.type_descriptions let type_description_library ctypes = - sprintf "%s__c_type_descriptions" ctypes.Ctypes.lib_name + type_description_module ctypes + |> Module_name.to_string + |> String.lowercase let type_description_library_public ctypes = sprintf "%s.c_type_descriptions" ctypes.Ctypes.lib_name let function_description_module ctypes = - sprintf "%s__c_function_descriptions" ctypes.Ctypes.lib_name - |> Module_name.of_string + ctypes.Ctypes.function_descriptions let function_description_library ctypes = - sprintf "%s__c_function_descriptions" ctypes.Ctypes.lib_name + function_description_module ctypes + |> Module_name.to_string + |> String.lowercase let function_description_library_public ctypes = sprintf "%s.c_function_descriptions" ctypes.Ctypes.lib_name let entry_module ctypes = - sprintf "%s_c" ctypes.Ctypes.lib_name - |> Module_name.of_string + ctypes.Ctypes.generated_entry_point let entry_library ctypes = - sprintf "%s_c" ctypes.Ctypes.lib_name + entry_module ctypes |> Module_name.to_string |> String.lowercase let entry_library_public ctypes = sprintf "%s.c" ctypes.Ctypes.lib_name @@ -127,9 +128,14 @@ let c_generated_functions_module ctypes = sprintf "%s__c_generated_functions" ctypes.Ctypes.lib_name |> Module_name.of_string +(* let c_types_includer_module ctypes = sprintf "%s__c_types" ctypes.Ctypes.lib_name |> Module_name.of_string +*) + +let c_types_includer_module ctypes = + ctypes.Ctypes.generated_types let c_generated_types_cout_c ctypes = sprintf "%s__c_cout_generated_types.c" ctypes.Ctypes.lib_name @@ -217,7 +223,8 @@ let generated_ml_and_c_files ctypes = let ml_files = List.map [ c_generated_functions_module ctypes ; c_generated_types_module ctypes - ; c_types_includer_module ctypes ] + ; c_types_includer_module ctypes + ; entry_module ctypes ] ~f:Module_name.to_string |> List.map ~f:String.lowercase |> List.map ~f:(fun m -> m ^ ".ml") diff --git a/src/dune_rules/dune_file.ml b/src/dune_rules/dune_file.ml index 309473e3f7e..a86a818b0b2 100644 --- a/src/dune_rules/dune_file.ml +++ b/src/dune_rules/dune_file.ml @@ -484,7 +484,11 @@ module Ctypes = struct properly. *) type t = { lib_name : string - ; includes : string list } + ; includes : string list + ; type_descriptions : Module_name.t + ; function_descriptions : Module_name.t + ; generated_types : Module_name.t + ; generated_entry_point : Module_name.t } let name = "ctypes" @@ -499,8 +503,13 @@ module Ctypes = struct fields (let+ lib_name = field "lib_name" string and+ includes = field "includes" (repeat string) ~default:[] + and+ type_descriptions = field "type_descriptions" Module_name.decode + and+ function_descriptions = field "function_descriptions" Module_name.decode + and+ generated_types = field "generated_types" Module_name.decode + and+ generated_entry_point = field "generated_entry_point" Module_name.decode in - { lib_name; includes }) + { lib_name; includes; type_descriptions; function_descriptions; + generated_types; generated_entry_point }) let () = let open Dune_lang.Decoder in diff --git a/src/dune_rules/dune_file.mli b/src/dune_rules/dune_file.mli index a6c9eaf0839..a7a3ff40bf5 100644 --- a/src/dune_rules/dune_file.mli +++ b/src/dune_rules/dune_file.mli @@ -121,8 +121,11 @@ end module Ctypes : sig type t = { lib_name : string - ; includes : string list } - + ; includes : string list + ; type_descriptions : Module_name.t + ; function_descriptions : Module_name.t + ; generated_types : Module_name.t + ; generated_entry_point : Module_name.t } type Stanza.t += T of t end From 760b3ea88c82cbdd8d9c599bba0e67624080ecdd Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Thu, 4 Feb 2021 10:37:40 -0800 Subject: [PATCH 13/69] move from library to buildable stanza, so exe can use ctypes too --- src/dune_rules/ctypes_rules.ml | 30 +++++------ src/dune_rules/ctypes_rules.mli | 5 +- src/dune_rules/ctypes_stanzas.ml | 32 ++++++----- src/dune_rules/ctypes_stanzas.mli | 8 ++- src/dune_rules/dir_contents.ml | 5 +- src/dune_rules/dune_file.ml | 89 ++++++++++++++++--------------- src/dune_rules/dune_file.mli | 25 +++++---- src/dune_rules/dune_load.ml | 29 ++++++++-- src/dune_rules/exe_rules.ml | 15 +++++- src/dune_rules/lib_rules.ml | 15 +++++- 10 files changed, 150 insertions(+), 103 deletions(-) diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index 14087cfdce6..bdd24bb3f05 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -1,7 +1,8 @@ open! Dune_engine open! Stdune -module Library = Dune_file.Library +module Buildable = Dune_file.Buildable +module Library = Dune_file.Library module Ctypes = Dune_file.Ctypes (* This module expands a [(library ... (ctypes ...))] rule into the set of @@ -229,7 +230,7 @@ let build_c_program ~sctx ~dir ~source_files ~scope ~cflags_txt ~output () = in Super_context.add_rule sctx ~dir build -let cctx ~base_lib ?(libraries=[]) ~loc ~dir ~scope ~expander ~sctx = +let cctx ?(libraries=[]) ~buildable ~dynlink ~loc ~obj_dir ~dir ~scope ~expander ~sctx = let compile_info = let dune_version = Scope.project scope |> Dune_project.dune_version in Lib.DB.resolve_user_written_deps_for_exes (Scope.libs scope) @@ -239,24 +240,19 @@ let cctx ~base_lib ?(libraries=[]) ~loc ~dir ~scope ~expander ~sctx = ~dune_version ~optional:false ~pps:[] in - let dynlink = - let ctx = Super_context.context sctx in - Dynlink_supported.get base_lib.Library.dynlink - ctx.Context.supports_shared_libraries - in Compilation_context.create ~super_context:sctx ~scope ~expander ~js_of_ocaml:None ~dynlink ~package:None - ~flags:(Super_context.ocaml_flags sctx ~dir base_lib.buildable.flags) + ~flags:(Super_context.ocaml_flags sctx ~dir buildable.Buildable.flags) ~requires_compile:(Lib.Compile.direct_requires compile_info) ~requires_link:(Lib.Compile.requires_link compile_info) - ~obj_dir:(Library.obj_dir ~dir base_lib) + ~obj_dir ~opaque:Compilation_context.Inherit_from_settings -let executable ?(modules=[]) ~base_lib ~loc ~dir ~sctx ~scope ~expander - ~program ~libraries () = +let executable ?(modules=[]) ~buildable ~loc ~obj_dir ~dynlink ~dir ~sctx ~scope + ~expander ~program ~libraries () = let build_dir = Path.build dir in let cctx = let modules = @@ -272,7 +268,8 @@ let executable ?(modules=[]) ~base_lib ~loc ~dir ~sctx ~scope ~expander in Modules.exe_wrapped ~src_dir:dir ~modules:name_map in - cctx ~base_lib ~dir ~loc ~scope ~sctx ~expander ~modules ~libraries () + cctx ~buildable ~dir ~loc ~obj_dir ~dynlink ~scope ~sctx ~expander + ~modules ~libraries () in let program = Exe.Program.{ @@ -283,12 +280,13 @@ let executable ?(modules=[]) ~base_lib ~loc ~dir ~sctx ~scope ~expander in Exe.build_and_link ~program ~linkages:[Exe.Linkage.native] ~promote:None cctx -let gen_rules ~base_lib ~scope ~expander ~dir ~sctx = - let loc, _name = base_lib.Library.name in +let gen_rules ~buildable ~dynlink ~loc ~obj_dir ~scope ~expander ~dir ~sctx = let rule = rule ~sctx ~dir in - let executable = executable ~base_lib ~loc ~dir ~sctx ~scope ~expander in + let executable = + executable ~buildable ~loc ~obj_dir ~dynlink ~dir ~sctx ~scope ~expander + in let ctypes = - match base_lib.Library.ctypes with + match buildable.Buildable.ctypes with | Some ctypes -> ctypes | None -> assert false in diff --git a/src/dune_rules/ctypes_rules.mli b/src/dune_rules/ctypes_rules.mli index 669a48bd53d..f39e166dbc3 100644 --- a/src/dune_rules/ctypes_rules.mli +++ b/src/dune_rules/ctypes_rules.mli @@ -1,7 +1,10 @@ open! Stdune val gen_rules : - base_lib:Dune_file.Library.t + buildable:Dune_file.Buildable.t + -> dynlink:bool + -> loc:Loc.t + -> obj_dir:Path.Build.t Obj_dir.t -> scope:Scope.t -> expander:Expander.t -> dir:Path.Build.t diff --git a/src/dune_rules/ctypes_stanzas.ml b/src/dune_rules/ctypes_stanzas.ml index 396c3a079a0..764495d30b6 100644 --- a/src/dune_rules/ctypes_stanzas.ml +++ b/src/dune_rules/ctypes_stanzas.ml @@ -1,15 +1,15 @@ open! Dune_engine open! Stdune +module Buildable = Dune_file.Buildable module Library = Dune_file.Library module Ctypes = Dune_file.Ctypes -let osl_pos _base_lib = "", 0, 0, 0 ;; +let osl_pos () = "", 0, 0, 0 ;; let library_stanza ?(flags=Ocaml_flags.Spec.standard) ?public_name ?(foreign_stubs=[]) - ?(c_library_flags=Ordered_set_lang.Unexpanded.standard) ~base_lib:lib - ~name ~modules ~libraries ~wrapped () = - let loc, _libname = lib.Library.name in + ?(c_library_flags=Ordered_set_lang.Unexpanded.standard) ~loc ~project ~sub_systems + ~dune_version ~name ~modules ~libraries ~wrapped () = let open Dune_file in let visibility = match public_name with @@ -49,6 +49,7 @@ let library_stanza ?(flags=Ocaml_flags.Spec.standard) ?public_name ?(foreign_stu ; flags ; js_of_ocaml = Js_of_ocaml.default ; allow_overlapping_dependencies = false + ; ctypes = None; } in { Library.name = (loc, Lib_name.of_string name |> Lib_name.to_local_exn) @@ -65,9 +66,9 @@ let library_stanza ?(flags=Ocaml_flags.Spec.standard) ?public_name ?(foreign_stu ; optional = false ; buildable ; dynlink = Dynlink_supported.of_bool true - ; project = lib.Library.project - ; sub_systems = lib.Library.sub_systems - ; dune_version = lib.Library.dune_version + ; project + ; sub_systems + ; dune_version ; virtual_modules = None ; implements = None ; default_implementation = None @@ -75,8 +76,7 @@ let library_stanza ?(flags=Ocaml_flags.Spec.standard) ?public_name ?(foreign_stu ; stdlib = None ; special_builtin_support = None ; enabled_if = Blang.true_ - ; instrumentation_backend = None - ; ctypes = None } + ; instrumentation_backend = None } let sprintf = Printf.sprintf @@ -157,15 +157,16 @@ let c_generated_functions_cout_no_ext ctypes = approach here is to simply do a quasi-lexical expansion of the base library config stanza into several additional support library stanzas, right after the dune config file parsing is completed. *) -let library_stanzas ~parsing_context base_lib = +let library_stanzas ~parsing_context ~project ~sub_systems ~dune_version buildable = let ctypes = - match base_lib.Library.ctypes with + match buildable.Buildable.ctypes with | Some ctypes -> ctypes | None -> assert false in + let loc = buildable.Buildable.loc in + let library_stanza = library_stanza ~loc ~project ~sub_systems ~dune_version in let type_descriptions = library_stanza - ~base_lib ~name:(type_description_library ctypes) ~public_name:(type_description_library_public ctypes) ~modules:[type_description_module ctypes] @@ -178,10 +179,9 @@ let library_stanzas ~parsing_context base_lib = don't break compilation when warnings-as-errors *) Ocaml_flags.Spec.of_unexpanded_ordered_set_lang (Ordered_set_lang.Unexpanded.standard_with_of_strings - ~pos:(osl_pos base_lib) ["-w"; "-27"; "-w"; "-9"]) + ~pos:(osl_pos ()) ["-w"; "-27"; "-w"; "-9"]) in library_stanza - ~base_lib ~name:(function_description_library ctypes) ~public_name:(function_description_library_public ctypes) ~modules:[ c_generated_types_module ctypes @@ -192,9 +192,8 @@ let library_stanzas ~parsing_context base_lib = ~wrapped:false () in let combined_final = - let pos = osl_pos base_lib in + let pos = osl_pos () in let foreign_stub = - let loc, _libname = base_lib.Library.name in Foreign.Stubs.make ~loc ~language:Foreign_language.C ~names:(Ordered_set_lang.of_atoms ~loc [c_generated_functions_cout_no_ext ctypes]) @@ -202,7 +201,6 @@ let library_stanzas ~parsing_context base_lib = ~context:parsing_context ~pos (cflags_sexp ctypes)) in library_stanza - ~base_lib ~name:(entry_library ctypes) ~public_name:(entry_library_public ctypes) ~libraries:["ctypes"; function_description_library ctypes] diff --git a/src/dune_rules/ctypes_stanzas.mli b/src/dune_rules/ctypes_stanzas.mli index 76518857ede..7d1f8090960 100644 --- a/src/dune_rules/ctypes_stanzas.mli +++ b/src/dune_rules/ctypes_stanzas.mli @@ -21,6 +21,12 @@ val c_generated_types_cout_exe : Ctypes.t -> string val c_generated_functions_cout_c : Ctypes.t -> string -val library_stanzas : parsing_context:Stdune.Univ_map.t -> Library.t -> Library.t list +val library_stanzas : + parsing_context:Stdune.Univ_map.t + -> project:Dune_engine.Dune_project.t + -> sub_systems:Sub_system_info.t Sub_system_name.Map.t + -> dune_version:Dune_lang.Syntax.Version.t + -> Buildable.t + -> Library.t list val generated_ml_and_c_files : Ctypes.t -> string list diff --git a/src/dune_rules/dir_contents.ml b/src/dune_rules/dir_contents.ml index 7f231e6f9c9..8ce68c20bfb 100644 --- a/src/dune_rules/dir_contents.ml +++ b/src/dune_rules/dir_contents.ml @@ -159,10 +159,9 @@ end = struct |> Path.Set.to_list |> List.map ~f:Path.basename | Generate_module def -> [ Generate_module_rules.setup_rules sctx ~dir def ] - | Executables { buildable; _ } -> buildable_select_deps buildable - | Library { buildable; ctypes; _ } -> + | Executables { buildable; _ } | Library { buildable; _ } -> let ctypes_generated_ml_and_c_files = - match ctypes with + match buildable.ctypes with | Some ctypes -> Ctypes_stanzas.generated_ml_and_c_files ctypes | None -> [] in diff --git a/src/dune_rules/dune_file.ml b/src/dune_rules/dune_file.ml index a86a818b0b2..de6fa3ecc12 100644 --- a/src/dune_rules/dune_file.ml +++ b/src/dune_rules/dune_file.ml @@ -45,6 +45,45 @@ module Js_of_ocaml = struct { flags = Ordered_set_lang.Unexpanded.standard; javascript_files = [] } end +module Ctypes = struct + (* XXX: this is a placeholder for the spec we talked about in PR#3905. + At the moment just trying to get a minimal example to compile and build + properly. *) + type t = + { lib_name : string + ; includes : string list + ; type_descriptions : Module_name.t + ; function_descriptions : Module_name.t + ; generated_types : Module_name.t + ; generated_entry_point : Module_name.t } + + let name = "ctypes" + + type Stanza.t += T of t + + let syntax = + Dune_lang.Syntax.create ~name ~desc:"the ctypes extension" + [ ((0, 1), `Since (2, 8)) ] + + let decode = + let open Dune_lang.Decoder in + fields + (let+ lib_name = field "lib_name" string + and+ includes = field "includes" (repeat string) ~default:[] + and+ type_descriptions = field "type_descriptions" Module_name.decode + and+ function_descriptions = field "function_descriptions" Module_name.decode + and+ generated_types = field "generated_types" Module_name.decode + and+ generated_entry_point = field "generated_entry_point" Module_name.decode + in + { lib_name; includes; type_descriptions; function_descriptions; + generated_types; generated_entry_point }) + + let () = + let open Dune_lang.Decoder in + Dune_project.Extension.register_simple syntax + (return [ (name, decode >>| fun x -> [ T x ]) ]) +end + module Lib_deps = struct type t = Lib_dep.t list @@ -161,6 +200,7 @@ module Buildable = struct ; flags : Ocaml_flags.Spec.t ; js_of_ocaml : Js_of_ocaml.t ; allow_overlapping_dependencies : bool + ; ctypes : Ctypes.t option } let decode ~in_library ~allow_re_export = @@ -232,7 +272,10 @@ module Buildable = struct (multi_field "instrumentation" ( Dune_lang.Syntax.since Stanza.syntax (2, 7) >>> fields (field "backend" (located Lib_name.decode)) )) - in + and+ ctypes = + (field_o "ctypes" + (Dune_lang.Syntax.since Ctypes.syntax (0, 1) >>> Ctypes.decode)) + in let preprocess = let init = let f libname = Preprocess.With_instrumentation.Ordinary libname in @@ -285,6 +328,7 @@ module Buildable = struct ; flags ; js_of_ocaml ; allow_overlapping_dependencies + ; ctypes } let has_foreign t = @@ -478,44 +522,6 @@ module Mode_conf = struct end end -module Ctypes = struct - (* XXX: this is a placeholder for the spec we talked about in PR#3905. - At the moment just trying to get a minimal example to compile and build - properly. *) - type t = - { lib_name : string - ; includes : string list - ; type_descriptions : Module_name.t - ; function_descriptions : Module_name.t - ; generated_types : Module_name.t - ; generated_entry_point : Module_name.t } - - let name = "ctypes" - - type Stanza.t += T of t - - let syntax = - Dune_lang.Syntax.create ~name ~desc:"the ctypes extension" - [ ((0, 1), `Since (2, 8)) ] - - let decode = - let open Dune_lang.Decoder in - fields - (let+ lib_name = field "lib_name" string - and+ includes = field "includes" (repeat string) ~default:[] - and+ type_descriptions = field "type_descriptions" Module_name.decode - and+ function_descriptions = field "function_descriptions" Module_name.decode - and+ generated_types = field "generated_types" Module_name.decode - and+ generated_entry_point = field "generated_entry_point" Module_name.decode - in - { lib_name; includes; type_descriptions; function_descriptions; - generated_types; generated_entry_point }) - - let () = - let open Dune_lang.Decoder in - Dune_project.Extension.register_simple syntax - (return [ (name, decode >>| fun x -> [ T x ]) ]) -end module Library = struct module Wrapped = struct @@ -577,7 +583,6 @@ module Library = struct ; special_builtin_support : Lib_info.Special_builtin_support.t option ; enabled_if : Blang.t ; instrumentation_backend : (Loc.t * Lib_name.t) option - ; ctypes : Ctypes.t option } let decode = @@ -656,9 +661,6 @@ module Library = struct field_o "package" ( Dune_lang.Syntax.since Stanza.syntax (2, 8) >>> located Stanza_common.Pkg.decode ) - and+ ctypes = - (field_o "ctypes" - (Dune_lang.Syntax.since Ctypes.syntax (0, 1) >>> Ctypes.decode)) in let wrapped = Wrapped.make ~wrapped ~implements ~special_builtin_support @@ -747,7 +749,6 @@ module Library = struct ; special_builtin_support ; enabled_if ; instrumentation_backend - ; ctypes }) let package t = diff --git a/src/dune_rules/dune_file.mli b/src/dune_rules/dune_file.mli index a7a3ff40bf5..8fa42c1001d 100644 --- a/src/dune_rules/dune_file.mli +++ b/src/dune_rules/dune_file.mli @@ -29,6 +29,17 @@ module Lib_deps : sig val decode : allow_re_export:bool -> t Dune_lang.Decoder.t end +module Ctypes : sig + type t = + { lib_name : string + ; includes : string list + ; type_descriptions : Module_name.t + ; function_descriptions : Module_name.t + ; generated_types : Module_name.t + ; generated_entry_point : Module_name.t } + type Stanza.t += T of t +end + (** [preprocess] and [preprocessor_deps] fields *) val preprocess_fields : ( Preprocess.Without_instrumentation.t Preprocess.Per_module.t @@ -49,6 +60,7 @@ module Buildable : sig ; flags : Ocaml_flags.Spec.t ; js_of_ocaml : Js_of_ocaml.t ; allow_overlapping_dependencies : bool + ; ctypes : Ctypes.t option } (** Check if the buildable has any foreign stubs or archives. *) @@ -118,18 +130,6 @@ module Mode_conf : sig end end -module Ctypes : sig - type t = - { lib_name : string - ; includes : string list - ; type_descriptions : Module_name.t - ; function_descriptions : Module_name.t - ; generated_types : Module_name.t - ; generated_entry_point : Module_name.t } - type Stanza.t += T of t -end - - module Library : sig type visibility = | Public of Public_lib.t @@ -166,7 +166,6 @@ module Library : sig ; special_builtin_support : Lib_info.Special_builtin_support.t option ; enabled_if : Blang.t ; instrumentation_backend : (Loc.t * Lib_name.t) option - ; ctypes : Ctypes.t option } val sub_dir : t -> string option diff --git a/src/dune_rules/dune_load.ml b/src/dune_rules/dune_load.ml index 9ec9df5573c..e54205d39d3 100644 --- a/src/dune_rules/dune_load.ml +++ b/src/dune_rules/dune_load.ml @@ -12,14 +12,33 @@ module Dune_file = struct let parse sexps ~dir ~file ~project = let stanzas = Dune_file.Stanzas.parse ~file project sexps in let stanzas = - List.concat_map stanzas ~f:(fun stanza -> - match stanza with - | Dune_file.Library ({ ctypes = Some _; _ } as base_lib) -> + let maybe_expand_ctypes ~dune_version ~sub_systems stanza buildable = + match buildable.Dune_file.Buildable.ctypes with + | None -> [stanza] + | Some _ctypes -> let libs = - let parsing_context = Dune_project.parsing_context project in - Ctypes_stanzas.library_stanzas ~parsing_context base_lib + Ctypes_stanzas.library_stanzas + ~parsing_context:(Dune_project.parsing_context project) + ~project ~dune_version ~sub_systems + buildable in stanza :: (List.map libs ~f:(fun l -> Dune_file.Library l)) + in + List.concat_map stanzas ~f:(fun stanza -> + match stanza with + | Dune_file.Executables _exe -> + (* XXX: implement me + maybe_expand_ctypes + ~sub_systems:() + ~dune_version:() + stanza exe.Dune_file.Executable.buildable + *) + [stanza] + | Dune_file.Library lib -> + maybe_expand_ctypes + ~sub_systems:lib.Dune_file.Library.sub_systems + ~dune_version:lib.Dune_file.Library.dune_version + stanza lib.Dune_file.Library.buildable | _ -> [stanza]) in let stanzas = diff --git a/src/dune_rules/exe_rules.ml b/src/dune_rules/exe_rules.ml index b95e4a5d70d..d408f88d796 100644 --- a/src/dune_rules/exe_rules.ml +++ b/src/dune_rules/exe_rules.ml @@ -3,6 +3,7 @@ open Import open! No_io open Build.O module Executables = Dune_file.Executables +module Buildable = Dune_file.Buildable let first_exe (exes : Executables.t) = snd (List.hd exes.names) @@ -66,7 +67,7 @@ let o_files sctx ~dir ~expander ~(exes : Executables.t) ~linkages ~dir_contents [] else let what = - if List.is_empty exes.buildable.Dune_file.Buildable.foreign_stubs then + if List.is_empty exes.buildable.Buildable.foreign_stubs then "archives" else "stubs" @@ -200,6 +201,18 @@ let compile_info ~scope (exes : Dune_file.Executables.t) = let rules ~sctx ~dir ~dir_contents ~scope ~expander (exes : Dune_file.Executables.t) = let compile_info = compile_info ~scope exes in + let () = + let buildable = exes.Executables.buildable in + Option.iter buildable.Buildable.ctypes ~f:(fun _ctypes -> + let loc = + match exes.Executables.names with + | hd :: _ -> fst hd + | [] -> assert false + in + let obj_dir = Executables.obj_dir ~dir exes in + Ctypes_rules.gen_rules ~buildable ~dynlink:false ~loc ~obj_dir ~sctx + ~scope ~expander ~dir) + in let f () = executables_rules exes ~sctx ~dir ~dir_contents ~scope ~expander ~compile_info ~embed_in_plugin_libraries:exes.embed_in_plugin_libraries diff --git a/src/dune_rules/lib_rules.ml b/src/dune_rules/lib_rules.ml index 54cfc3aa74c..65261fdb7e8 100644 --- a/src/dune_rules/lib_rules.ml +++ b/src/dune_rules/lib_rules.ml @@ -430,8 +430,19 @@ let rules (lib : Library.t) ~sctx ~dir_contents ~dir ~expander ~scope : Lib.DB.get_compile_info (Scope.libs scope) (Library.best_name lib) ~allow_overlaps:lib.buildable.allow_overlapping_dependencies in - Option.iter lib.Library.ctypes ~f:(fun _ctypes -> - Ctypes_rules.gen_rules ~base_lib:lib ~sctx ~scope ~expander ~dir); + let () = + let buildable = lib.Library.buildable in + Option.iter buildable.Buildable.ctypes ~f:(fun _ctypes -> + let loc, _name = lib.Library.name in + let dynlink = + let ctx = Super_context.context sctx in + Dynlink_supported.get lib.Library.dynlink + ctx.Context.supports_shared_libraries + in + let obj_dir = Library.obj_dir ~dir lib in + Ctypes_rules.gen_rules ~buildable ~dynlink ~loc ~obj_dir ~sctx ~scope + ~expander ~dir) + in let f () = let source_modules = Dir_contents.ocaml dir_contents From 1a0875fa5fa7fc6627bfc46496fde0275b621adf Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Thu, 4 Feb 2021 13:04:50 -0800 Subject: [PATCH 14/69] finish ctypes stanza for executables --- src/dune_rules/dune_file.ml | 15 ++++++++++++++- src/dune_rules/dune_file.mli | 2 ++ src/dune_rules/dune_load.ml | 13 +++++-------- 3 files changed, 21 insertions(+), 9 deletions(-) diff --git a/src/dune_rules/dune_file.ml b/src/dune_rules/dune_file.ml index de6fa3ecc12..906736eba73 100644 --- a/src/dune_rules/dune_file.ml +++ b/src/dune_rules/dune_file.ml @@ -1359,6 +1359,8 @@ module Executables = struct ; forbidden_libraries : (Loc.t * Lib_name.t) list ; bootstrap_info : string option ; enabled_if : Blang.t + ; sub_systems : Sub_system_info.t Sub_system_name.Map.t + ; dune_version : Dune_lang.Syntax.Version.t } let bootstrap_info_extension = @@ -1426,6 +1428,9 @@ module Executables = struct Dune_lang.Syntax.Version.Infix.(syntax_version >= (2, 6)) in Enabled_if.decode ~allowed_vars ~is_error ~since:(Some (2, 3)) () + and+ sub_systems = + let* () = return () in + Sub_system_info.record_parser () in fun names ~multi -> let has_public_name = Names.has_public_name names in @@ -1483,6 +1488,8 @@ module Executables = struct ; forbidden_libraries ; bootstrap_info ; enabled_if + ; dune_version + ; sub_systems } let single, multi = @@ -1796,7 +1803,8 @@ module Tests = struct let gen_parse names = fields - (let+ buildable = + (let* dune_version = Dune_lang.Syntax.get_exn Stanza.syntax in + let+ buildable = Buildable.decode ~in_library:false ~allow_re_export:false and+ link_flags = Ordered_set_lang.Unexpanded.field "link_flags" and+ names = names @@ -1818,6 +1826,9 @@ module Tests = struct ( Dune_lang.Syntax.since Stanza.syntax (2, 0) >>> repeat (located Lib_name.decode) ) ~default:[] + and+ sub_systems = + let* () = return () in + Sub_system_info.record_parser () in { exes = { Executables.link_flags @@ -1833,6 +1844,8 @@ module Tests = struct ; forbidden_libraries ; bootstrap_info = None ; enabled_if + ; dune_version + ; sub_systems } ; locks ; package diff --git a/src/dune_rules/dune_file.mli b/src/dune_rules/dune_file.mli index 8fa42c1001d..d7f1ebe2673 100644 --- a/src/dune_rules/dune_file.mli +++ b/src/dune_rules/dune_file.mli @@ -266,6 +266,8 @@ module Executables : sig ; forbidden_libraries : (Loc.t * Lib_name.t) list ; bootstrap_info : string option ; enabled_if : Blang.t + ; sub_systems : Sub_system_info.t Sub_system_name.Map.t + ; dune_version : Dune_lang.Syntax.Version.t } (** Check if the executables have any foreign stubs or archives. *) diff --git a/src/dune_rules/dune_load.ml b/src/dune_rules/dune_load.ml index e54205d39d3..ddcda97e983 100644 --- a/src/dune_rules/dune_load.ml +++ b/src/dune_rules/dune_load.ml @@ -26,14 +26,11 @@ module Dune_file = struct in List.concat_map stanzas ~f:(fun stanza -> match stanza with - | Dune_file.Executables _exe -> - (* XXX: implement me - maybe_expand_ctypes - ~sub_systems:() - ~dune_version:() - stanza exe.Dune_file.Executable.buildable - *) - [stanza] + | Dune_file.Executables exes -> + maybe_expand_ctypes + ~sub_systems:exes.Dune_file.Executables.sub_systems + ~dune_version:exes.Dune_file.Executables.dune_version + stanza exes.Dune_file.Executables.buildable | Dune_file.Library lib -> maybe_expand_ctypes ~sub_systems:lib.Dune_file.Library.sub_systems From 8b8ca1ff4b323d74310134b3d2fea57eaede11e9 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Sat, 13 Feb 2021 08:20:30 -0800 Subject: [PATCH 15/69] inch towards a finalized ctypes config (for ctypes 0.1) --- src/dune_rules/ctypes_rules.ml | 71 ++++++++++++++++----------- src/dune_rules/ctypes_stanzas.ml | 26 +++++----- src/dune_rules/dune_file.ml | 83 +++++++++++++++++++++++++++++--- src/dune_rules/dune_file.mli | 22 ++++++++- 4 files changed, 154 insertions(+), 48 deletions(-) diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index bdd24bb3f05..0e831726487 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -84,7 +84,7 @@ let write_entry_point_module ~sctx ~dir ~filename ~function_description_module Super_context.add_rule ~loc:Loc.none sctx ~dir (Build.write_file path contents) -let discover_gen ~external_lib_name:lib ~cflags_sexp ~cflags_txt +let discover_gen ~external_library_name:lib ~cflags_sexp ~cflags_txt ~c_library_flags_sexp = let buf = Buffer.create 1024 in let pr buf fmt = Printf.bprintf buf (fmt ^^ "\n") in @@ -110,11 +110,11 @@ let discover_gen ~external_lib_name:lib ~cflags_sexp ~cflags_txt pr buf " close_out oc)"; Buffer.contents buf -let write_discover_script ~filename ~sctx ~dir ~external_lib_name ~cflags_sexp +let write_discover_script ~filename ~sctx ~dir ~external_library_name ~cflags_sexp ~cflags_txt ~c_library_flags_sexp = let path = Path.Build.relative dir filename in let script = - discover_gen ~external_lib_name ~cflags_sexp ~cflags_txt + discover_gen ~external_library_name ~cflags_sexp ~cflags_txt ~c_library_flags_sexp in Super_context.add_rule ~loc:Loc.none sctx ~dir (Build.write_file path script) @@ -129,12 +129,17 @@ let type_gen_gen ~include_headers ~type_description_module = pr buf " (module %s.Types)" (Module_name.to_string type_description_module); Buffer.contents buf -let function_gen_gen ~include_headers ~function_description_module = - (* XXX: make concurrency configurable *) +let function_gen_gen ~concurrency ~include_headers ~function_description_module = let function_description_module = Module_name.to_string function_description_module in - let concurrency = "Cstubs.unlocked" in + let concurrency = + match concurrency with + | Ctypes.Concurrency_policy.Unlocked -> "Cstubs.unlocked" + | Sequential -> "Cstubs.sequential" + | Lwt_jobs -> "Cstubs.lwt_jobs" + | Lwt_preemptive -> "Cstubs.lwt_preemptive" + in let buf = Buffer.create 1024 in let pr buf fmt = Printf.bprintf buf (fmt ^^ "\n") in pr buf "let () ="; @@ -159,9 +164,9 @@ let write_type_gen_script ~include_headers ~dir ~filename ~sctx Super_context.add_rule ~loc:Loc.none sctx ~dir (Build.write_file path script) let write_function_gen_script ~include_headers ~sctx ~dir ~name - ~function_description_module = + ~function_description_module ~concurrency = let path = Path.Build.relative dir (name ^ ".ml") in - let script = function_gen_gen ~include_headers ~function_description_module in + let script = function_gen_gen ~concurrency ~include_headers ~function_description_module in Super_context.add_rule ~loc:Loc.none sctx ~dir (Build.write_file path script) let rule ?(deps=[]) ?stdout_to ?(args=[]) ?(targets=[]) ~exe ~sctx ~dir () = @@ -290,7 +295,7 @@ let gen_rules ~buildable ~dynlink ~loc ~obj_dir ~scope ~expander ~dir ~sctx = | Some ctypes -> ctypes | None -> assert false in - let external_lib_name = ctypes.Ctypes.lib_name in + let external_library_name = ctypes.Ctypes.external_library_name in let type_description_module = Ctypes_stanzas.type_description_module ctypes in let type_description_library = Ctypes_stanzas.type_description_library ctypes in let function_description_module = Ctypes_stanzas.function_description_module ctypes in @@ -305,26 +310,37 @@ let gen_rules ~buildable ~dynlink ~loc ~obj_dir ~scope ~expander ~dir ~sctx = ~c_generated_types_module:(Ctypes_stanzas.c_generated_types_module ctypes) ~type_description_module in - (* The discover script uses dune configurator / pkg_config to figure out + (* The output of this process is to generate two cflags and one c library flags file. + We can probe it using the system pkg-config, if it's an external system + library, or the user tells us where they are if they're vendored. + + The discover script uses dune configurator / pkg_config to figure out how to invoke the compiler and linker for your external C library. https://dune.readthedocs.io/en/stable/quick-start.html#defining-a-library-with-c-stubs-using-pkg-config *) let c_library_flags_sexp = Ctypes_stanzas.c_library_flags_sexp ctypes in let cflags_txt = Ctypes_stanzas.cflags_txt ctypes in let () = - let cflags_sexp = Ctypes_stanzas.cflags_sexp ctypes in - let discover_script = sprintf "%s__ctypes_discover" external_lib_name in - write_discover_script - ~sctx ~dir ~filename:(discover_script ^ ".ml") ~cflags_sexp - ~cflags_txt ~c_library_flags_sexp ~external_lib_name; - executable - ~program:discover_script - ~libraries:["dune.configurator"] - (); - rule - ~targets:[cflags_sexp; cflags_txt; c_library_flags_sexp] - ~exe:(discover_script ^ ".exe") - () + match ctypes.Ctypes.build_flags_resolver with + | Ctypes.Build_flags_resolver.Pkg_config -> + let cflags_sexp = Ctypes_stanzas.cflags_sexp ctypes in + let discover_script = sprintf "%s__ctypes_discover" external_library_name in + write_discover_script + ~sctx ~dir ~filename:(discover_script ^ ".ml") ~cflags_sexp + ~cflags_txt ~c_library_flags_sexp ~external_library_name; + executable + ~program:discover_script + ~libraries:["dune.configurator"] + (); + (* XXX: maybe we should read these files into dune after they've been generated? rather + than constructing Ordered_set_langs with include directives for these files? *) + rule + ~targets:[cflags_sexp; cflags_txt; c_library_flags_sexp] + ~exe:(discover_script ^ ".exe") + () + | Vendored _vendored -> + (* XXX: easier to implement if we read the above files into dune *) + failwith "TODO: implement vendored" in let include_headers = ctypes.Ctypes.includes in (* Type_gen produces a .c file, taking your type description module above @@ -337,7 +353,7 @@ let gen_rules ~buildable ~dynlink ~loc ~obj_dir ~scope ~expander ~dir ~sctx = Note the similar function_gen process below depends on the ML-wrapped C data/types produced in this step. *) let () = - let type_gen_script = sprintf "%s__type_gen" external_lib_name in + let type_gen_script = sprintf "%s__type_gen" external_library_name in let c_generated_types_cout_c = Ctypes_stanzas.c_generated_types_cout_c ctypes in @@ -371,13 +387,14 @@ let gen_rules ~buildable ~dynlink ~loc ~obj_dir ~scope ~expander ~dir ~sctx = .ml file and a .c file. These files correspond to the files you would have to write by hand to wrap C code (if ctypes didn't exist!) *) let () = - let stubs_prefix = external_lib_name ^ "_stubs" in - let function_gen_script = sprintf "%s__function_gen" external_lib_name in + let stubs_prefix = external_library_name ^ "_stubs" in + let function_gen_script = sprintf "%s__function_gen" external_library_name in let c_generated_functions_cout_c = Ctypes_stanzas.c_generated_functions_cout_c ctypes in write_function_gen_script ~include_headers ~sctx ~dir - ~name:function_gen_script ~function_description_module; + ~name:function_gen_script ~function_description_module + ~concurrency:ctypes.Ctypes.concurrency; executable ~program:function_gen_script ~libraries:["ctypes.stubs"; function_description_library] diff --git a/src/dune_rules/ctypes_stanzas.ml b/src/dune_rules/ctypes_stanzas.ml index 764495d30b6..06914eb8e8e 100644 --- a/src/dune_rules/ctypes_stanzas.ml +++ b/src/dune_rules/ctypes_stanzas.ml @@ -89,7 +89,7 @@ let type_description_library ctypes = |> String.lowercase let type_description_library_public ctypes = - sprintf "%s.c_type_descriptions" ctypes.Ctypes.lib_name + sprintf "%s.c_type_descriptions" ctypes.Ctypes.external_library_name let function_description_module ctypes = ctypes.Ctypes.function_descriptions @@ -100,7 +100,7 @@ let function_description_library ctypes = |> String.lowercase let function_description_library_public ctypes = - sprintf "%s.c_function_descriptions" ctypes.Ctypes.lib_name + sprintf "%s.c_function_descriptions" ctypes.Ctypes.external_library_name let entry_module ctypes = ctypes.Ctypes.generated_entry_point @@ -109,28 +109,28 @@ let entry_library ctypes = entry_module ctypes |> Module_name.to_string |> String.lowercase let entry_library_public ctypes = - sprintf "%s.c" ctypes.Ctypes.lib_name + sprintf "%s.c" ctypes.Ctypes.external_library_name let cflags_sexp ctypes = - sprintf "%s__c_flags.sexp" ctypes.Ctypes.lib_name + sprintf "%s__c_flags.sexp" ctypes.Ctypes.external_library_name let cflags_txt ctypes = - sprintf "%s__c_flags.txt" ctypes.Ctypes.lib_name + sprintf "%s__c_flags.txt" ctypes.Ctypes.external_library_name let c_library_flags_sexp ctypes = - sprintf "%s__c_library_flags.sexp" ctypes.Ctypes.lib_name + sprintf "%s__c_library_flags.sexp" ctypes.Ctypes.external_library_name let c_generated_types_module ctypes = - sprintf "%s__c_generated_types" ctypes.Ctypes.lib_name + sprintf "%s__c_generated_types" ctypes.Ctypes.external_library_name |> Module_name.of_string let c_generated_functions_module ctypes = - sprintf "%s__c_generated_functions" ctypes.Ctypes.lib_name + sprintf "%s__c_generated_functions" ctypes.Ctypes.external_library_name |> Module_name.of_string (* let c_types_includer_module ctypes = - sprintf "%s__c_types" ctypes.Ctypes.lib_name + sprintf "%s__c_types" ctypes.Ctypes.external_library_name |> Module_name.of_string *) @@ -138,16 +138,16 @@ let c_types_includer_module ctypes = ctypes.Ctypes.generated_types let c_generated_types_cout_c ctypes = - sprintf "%s__c_cout_generated_types.c" ctypes.Ctypes.lib_name + sprintf "%s__c_cout_generated_types.c" ctypes.Ctypes.external_library_name let c_generated_types_cout_exe ctypes = - sprintf "%s__c_cout_generated_types.exe" ctypes.Ctypes.lib_name + sprintf "%s__c_cout_generated_types.exe" ctypes.Ctypes.external_library_name let c_generated_functions_cout_c ctypes = - sprintf "%s__c_cout_generated_functions.c" ctypes.Ctypes.lib_name + sprintf "%s__c_cout_generated_functions.c" ctypes.Ctypes.external_library_name let c_generated_functions_cout_no_ext ctypes = - sprintf "%s__c_cout_generated_functions" ctypes.Ctypes.lib_name + sprintf "%s__c_cout_generated_functions" ctypes.Ctypes.external_library_name (* Unlike for [executable] and [rule] generation which have neat convenience functions for creating new ones, the machinery for creating new [library]s diff --git a/src/dune_rules/dune_file.ml b/src/dune_rules/dune_file.ml index 906736eba73..462259cc027 100644 --- a/src/dune_rules/dune_file.ml +++ b/src/dune_rules/dune_file.ml @@ -46,12 +46,73 @@ module Js_of_ocaml = struct end module Ctypes = struct - (* XXX: this is a placeholder for the spec we talked about in PR#3905. - At the moment just trying to get a minimal example to compile and build - properly. *) + module Build_flags_resolver = struct + + module Vendored = struct + type t = + { c_flags : Ordered_set_lang.Unexpanded.t + ; c_library_flags : Ordered_set_lang.Unexpanded.t } + + let decode = + fields + (let+ c_flags = Ordered_set_lang.Unexpanded.field "c_flags" + and+ c_library_flags = Ordered_set_lang.Unexpanded.field "c_library_flags" in + { c_flags; c_library_flags }) + end + + type t = + | Pkg_config + | Vendored of Vendored.t + + let decode = + let vendored = + let+ p = Vendored.decode in + Vendored p + in + sum [ ("pkg_config" , return Pkg_config) + ; ("vendored" , vendored ) ] + + let default = Pkg_config + end + + module Concurrency_policy = struct + type t = + | Sequential + | Unlocked + | Lwt_jobs + | Lwt_preemptive + + let decode = + enum [ "sequential" , Sequential + ; "unlocked" , Unlocked + ; "lwt_jobs" , Lwt_jobs + ; "lwt_preemptive" , Lwt_preemptive ] + + let default = Sequential + end + + (* + module Headers = struct + type t = + | Include of string list + | Preamble of string + let decode = + let include_ = + let+ p = field "external_library_name" string + + in + let preamble = + + in + sum [ ("include" , return include_) + ; ("preamble" , return preamble) ] + end + *) type t = - { lib_name : string + { external_library_name : string + ; build_flags_resolver : Build_flags_resolver.t ; includes : string list + ; concurrency : Concurrency_policy.t ; type_descriptions : Module_name.t ; function_descriptions : Module_name.t ; generated_types : Module_name.t @@ -68,15 +129,23 @@ module Ctypes = struct let decode = let open Dune_lang.Decoder in fields - (let+ lib_name = field "lib_name" string + (let+ external_library_name = field "external_library_name" string + and+ build_flags_resolver = field_o "build_flags_resolver" Build_flags_resolver.decode and+ includes = field "includes" (repeat string) ~default:[] + and+ concurrency = field_o "concurrency" Concurrency_policy.decode and+ type_descriptions = field "type_descriptions" Module_name.decode and+ function_descriptions = field "function_descriptions" Module_name.decode and+ generated_types = field "generated_types" Module_name.decode and+ generated_entry_point = field "generated_entry_point" Module_name.decode in - { lib_name; includes; type_descriptions; function_descriptions; - generated_types; generated_entry_point }) + { external_library_name + ; build_flags_resolver = Option.value build_flags_resolver ~default:Build_flags_resolver.default + ; includes + ; concurrency = Option.value concurrency ~default:Concurrency_policy.default + ; type_descriptions + ; function_descriptions + ; generated_types + ; generated_entry_point }) let () = let open Dune_lang.Decoder in diff --git a/src/dune_rules/dune_file.mli b/src/dune_rules/dune_file.mli index d7f1ebe2673..91f52a735a3 100644 --- a/src/dune_rules/dune_file.mli +++ b/src/dune_rules/dune_file.mli @@ -29,10 +29,30 @@ module Lib_deps : sig val decode : allow_re_export:bool -> t Dune_lang.Decoder.t end + module Ctypes : sig + module Build_flags_resolver : sig + module Vendored : sig + type t = + { c_flags : Ordered_set_lang.Unexpanded.t + ; c_library_flags : Ordered_set_lang.Unexpanded.t } + end + type t = + | Pkg_config + | Vendored of Vendored.t + end + module Concurrency_policy : sig + type t = + | Sequential + | Unlocked + | Lwt_jobs + | Lwt_preemptive + end type t = - { lib_name : string + { external_library_name : string + ; build_flags_resolver : Build_flags_resolver.t ; includes : string list + ; concurrency : Concurrency_policy.t ; type_descriptions : Module_name.t ; function_descriptions : Module_name.t ; generated_types : Module_name.t From ef8877230baaa682d143cb2d3208f03fcfb3460e Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Sun, 14 Feb 2021 07:35:05 -0800 Subject: [PATCH 16/69] headers include or preamble --- src/dune_rules/ctypes_rules.ml | 46 +++++++++++++++++++--------------- src/dune_rules/dune_file.ml | 23 +++++++++-------- src/dune_rules/dune_file.mli | 11 +++++++- 3 files changed, 49 insertions(+), 31 deletions(-) diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index 0e831726487..2f71310593b 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -119,17 +119,26 @@ let write_discover_script ~filename ~sctx ~dir ~external_library_name ~cflags_se in Super_context.add_rule ~loc:Loc.none sctx ~dir (Build.write_file path script) -let type_gen_gen ~include_headers ~type_description_module = +let gen_headers headers buf = + let pr buf fmt = Printf.bprintf buf (fmt ^^ "\n") in + begin match headers with + | Ctypes.Headers.Include lst -> + List.iter lst ~f:(fun h -> pr buf " print_endline \"#include <%s>\";" h) + | Preamble s -> + (* XXX: escape s *) + pr buf " print_endline \"%s\";" s + end + +let type_gen_gen ~headers ~type_description_module = let buf = Buffer.create 1024 in let pr buf fmt = Printf.bprintf buf (fmt ^^ "\n") in pr buf "let () ="; - List.iter include_headers ~f:(fun h -> - pr buf " print_endline \"#include <%s>\";" h); + gen_headers headers buf; pr buf " Cstubs_structs.write_c Format.std_formatter"; pr buf " (module %s.Types)" (Module_name.to_string type_description_module); Buffer.contents buf -let function_gen_gen ~concurrency ~include_headers ~function_description_module = +let function_gen_gen ~concurrency ~headers ~function_description_module = let function_description_module = Module_name.to_string function_description_module in @@ -150,23 +159,22 @@ let function_gen_gen ~concurrency ~include_headers ~function_description_module pr buf " Cstubs.write_ml ~concurrency Format.std_formatter ~prefix"; pr buf " (module %s.Functions)" function_description_module; pr buf " | \"c\" ->"; - List.iter include_headers ~f:(fun h -> - pr buf " print_endline \"#include <%s>\";" h); + gen_headers headers buf; pr buf " Cstubs.write_c ~concurrency Format.std_formatter ~prefix"; pr buf " (module %s.Functions)" function_description_module; pr buf " | s -> failwith (\"unknown functions \"^s)"; Buffer.contents buf -let write_type_gen_script ~include_headers ~dir ~filename ~sctx +let write_type_gen_script ~headers ~dir ~filename ~sctx ~type_description_module = let path = Path.Build.relative dir filename in - let script = type_gen_gen ~include_headers ~type_description_module in + let script = type_gen_gen ~headers ~type_description_module in Super_context.add_rule ~loc:Loc.none sctx ~dir (Build.write_file path script) -let write_function_gen_script ~include_headers ~sctx ~dir ~name +let write_function_gen_script ~headers ~sctx ~dir ~name ~function_description_module ~concurrency = let path = Path.Build.relative dir (name ^ ".ml") in - let script = function_gen_gen ~concurrency ~include_headers ~function_description_module in + let script = function_gen_gen ~concurrency ~headers ~function_description_module in Super_context.add_rule ~loc:Loc.none sctx ~dir (Build.write_file path script) let rule ?(deps=[]) ?stdout_to ?(args=[]) ?(targets=[]) ~exe ~sctx ~dir () = @@ -311,11 +319,8 @@ let gen_rules ~buildable ~dynlink ~loc ~obj_dir ~scope ~expander ~dir ~sctx = ~type_description_module in (* The output of this process is to generate two cflags and one c library flags file. - We can probe it using the system pkg-config, if it's an external system - library, or the user tells us where they are if they're vendored. - - The discover script uses dune configurator / pkg_config to figure out - how to invoke the compiler and linker for your external C library. + We can probe these flags by using the system pkg-config, if it's an external system + library. The user could also tell us what they are, if the library is vendored. https://dune.readthedocs.io/en/stable/quick-start.html#defining-a-library-with-c-stubs-using-pkg-config *) let c_library_flags_sexp = Ctypes_stanzas.c_library_flags_sexp ctypes in @@ -332,8 +337,9 @@ let gen_rules ~buildable ~dynlink ~loc ~obj_dir ~scope ~expander ~dir ~sctx = ~program:discover_script ~libraries:["dune.configurator"] (); - (* XXX: maybe we should read these files into dune after they've been generated? rather - than constructing Ordered_set_langs with include directives for these files? *) + (* XXX: maybe we should read these files into dune after they've been + generated? rather than constructing Ordered_set_langs with include + directives for these files? *) rule ~targets:[cflags_sexp; cflags_txt; c_library_flags_sexp] ~exe:(discover_script ^ ".exe") @@ -342,7 +348,7 @@ let gen_rules ~buildable ~dynlink ~loc ~obj_dir ~scope ~expander ~dir ~sctx = (* XXX: easier to implement if we read the above files into dune *) failwith "TODO: implement vendored" in - let include_headers = ctypes.Ctypes.includes in + let headers = ctypes.Ctypes.headers in (* Type_gen produces a .c file, taking your type description module above as an input. The .c file is compiled into an .exe. @@ -360,7 +366,7 @@ let gen_rules ~buildable ~dynlink ~loc ~obj_dir ~scope ~expander ~dir ~sctx = let c_generated_types_cout_exe = Ctypes_stanzas.c_generated_types_cout_exe ctypes in - write_type_gen_script ~include_headers ~sctx ~dir + write_type_gen_script ~headers ~sctx ~dir ~filename:(type_gen_script ^ ".ml") ~type_description_module; executable @@ -392,7 +398,7 @@ let gen_rules ~buildable ~dynlink ~loc ~obj_dir ~scope ~expander ~dir ~sctx = let c_generated_functions_cout_c = Ctypes_stanzas.c_generated_functions_cout_c ctypes in - write_function_gen_script ~include_headers ~sctx ~dir + write_function_gen_script ~headers ~sctx ~dir ~name:function_gen_script ~function_description_module ~concurrency:ctypes.Ctypes.concurrency; executable diff --git a/src/dune_rules/dune_file.ml b/src/dune_rules/dune_file.ml index 462259cc027..acd5fdacf03 100644 --- a/src/dune_rules/dune_file.ml +++ b/src/dune_rules/dune_file.ml @@ -91,27 +91,30 @@ module Ctypes = struct let default = Sequential end - (* module Headers = struct type t = | Include of string list | Preamble of string + let decode = let include_ = - let+ p = field "external_library_name" string - + let+ s = repeat string in + Include s in let preamble = - + let+ p = string in + Preamble p in - sum [ ("include" , return include_) - ; ("preamble" , return preamble) ] + sum [ ("include" , include_) + ; ("preamble" , preamble) ] + + let default = Include [] end - *) + type t = { external_library_name : string ; build_flags_resolver : Build_flags_resolver.t - ; includes : string list + ; headers : Headers.t ; concurrency : Concurrency_policy.t ; type_descriptions : Module_name.t ; function_descriptions : Module_name.t @@ -131,7 +134,7 @@ module Ctypes = struct fields (let+ external_library_name = field "external_library_name" string and+ build_flags_resolver = field_o "build_flags_resolver" Build_flags_resolver.decode - and+ includes = field "includes" (repeat string) ~default:[] + and+ headers = field_o "headers" Headers.decode and+ concurrency = field_o "concurrency" Concurrency_policy.decode and+ type_descriptions = field "type_descriptions" Module_name.decode and+ function_descriptions = field "function_descriptions" Module_name.decode @@ -140,7 +143,7 @@ module Ctypes = struct in { external_library_name ; build_flags_resolver = Option.value build_flags_resolver ~default:Build_flags_resolver.default - ; includes + ; headers = Option.value headers ~default:Headers.default ; concurrency = Option.value concurrency ~default:Concurrency_policy.default ; type_descriptions ; function_descriptions diff --git a/src/dune_rules/dune_file.mli b/src/dune_rules/dune_file.mli index 91f52a735a3..1f2d2f3fa77 100644 --- a/src/dune_rules/dune_file.mli +++ b/src/dune_rules/dune_file.mli @@ -31,6 +31,7 @@ end module Ctypes : sig + module Build_flags_resolver : sig module Vendored : sig type t = @@ -41,6 +42,7 @@ module Ctypes : sig | Pkg_config | Vendored of Vendored.t end + module Concurrency_policy : sig type t = | Sequential @@ -48,10 +50,17 @@ module Ctypes : sig | Lwt_jobs | Lwt_preemptive end + + module Headers : sig + type t = + | Include of string list + | Preamble of string + end + type t = { external_library_name : string ; build_flags_resolver : Build_flags_resolver.t - ; includes : string list + ; headers : Headers.t ; concurrency : Concurrency_policy.t ; type_descriptions : Module_name.t ; function_descriptions : Module_name.t From 545bf2e2eb45d722ae3e30da6436ba57ed3d896a Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Sun, 14 Feb 2021 12:24:17 -0800 Subject: [PATCH 17/69] get rid of extra cflags file. support vendoring --- src/dune_rules/ctypes_rules.ml | 74 ++++++++++++++++++++----------- src/dune_rules/ctypes_stanzas.ml | 3 -- src/dune_rules/ctypes_stanzas.mli | 1 - 3 files changed, 48 insertions(+), 30 deletions(-) diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index 2f71310593b..b663548bf35 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -84,8 +84,7 @@ let write_entry_point_module ~sctx ~dir ~filename ~function_description_module Super_context.add_rule ~loc:Loc.none sctx ~dir (Build.write_file path contents) -let discover_gen ~external_library_name:lib ~cflags_sexp ~cflags_txt - ~c_library_flags_sexp = +let discover_gen ~external_library_name:lib ~cflags_sexp ~c_library_flags_sexp = let buf = Buffer.create 1024 in let pr buf fmt = Printf.bprintf buf (fmt ^^ "\n") in pr buf "module C = Configurator.V1"; @@ -105,17 +104,14 @@ let discover_gen ~external_library_name:lib ~cflags_sexp ~cflags_txt pr buf " in"; pr buf " C.Flags.write_sexp \"%s\" conf.cflags;" cflags_sexp; pr buf " C.Flags.write_sexp \"%s\" conf.libs;" c_library_flags_sexp; - pr buf " let oc = open_out \"%s\" in" cflags_txt; - pr buf " List.iter (Printf.fprintf oc \"%%s\") conf.cflags;"; - pr buf " close_out oc)"; + pr buf " )"; Buffer.contents buf let write_discover_script ~filename ~sctx ~dir ~external_library_name ~cflags_sexp - ~cflags_txt ~c_library_flags_sexp = + ~c_library_flags_sexp = let path = Path.Build.relative dir filename in let script = - discover_gen ~external_library_name ~cflags_sexp ~cflags_txt - ~c_library_flags_sexp + discover_gen ~external_library_name ~cflags_sexp ~c_library_flags_sexp in Super_context.add_rule ~loc:Loc.none sctx ~dir (Build.write_file path script) @@ -196,7 +192,7 @@ let rule ?(deps=[]) ?stdout_to ?(args=[]) ?(targets=[]) ~exe ~sctx ~dir () = in Super_context.add_rule sctx ~dir build -let build_c_program ~sctx ~dir ~source_files ~scope ~cflags_txt ~output () = +let build_c_program ~sctx ~dir ~source_files ~scope ~cflags_sexp ~output () = let ctx = Super_context.context sctx in let exe = Ocaml_config.c_compiler ctx.Context.ocaml_config @@ -227,11 +223,24 @@ let build_c_program ~sctx ~dir ~source_files ~scope ~cflags_txt ~output () = |> Dep.Set.of_files in let build = - (* XXX: can we read the semantically identical cflags_sexp file and eliminate creating - this extra cflags_txt file? We do this in ctypes_stanzas: - Ordered_set_lang.Unexpanded.of_strings ~pos [":include"; cflags_sexp ... ] *) - let contents = Build.contents (Path.relative (Path.build dir) cflags_txt) in - let cflags_args = Build.map contents ~f:(String.split ~on:' ') in + let cflags_args = + let contents = Build.contents (Path.relative (Path.build dir) cflags_sexp) in + Build.map contents ~f:(fun sexp -> + let ast = + Dune_lang.Parser.parse_string ~mode:Dune_lang.Parser.Mode.Single + ~fname:cflags_sexp sexp + in + match ast with + | Dune_lang.Ast.Atom (_loc, atom) -> [Dune_lang.Atom.to_string atom] + | Template _ -> failwith "'template' not supported in ctypes build flags" + | Quoted_string (_loc, s) -> [s] + | List (_loc, lst) -> + List.map lst ~f:(function + | Dune_lang.Ast.Atom (_loc, atom) -> Dune_lang.Atom.to_string atom + | Quoted_string (_loc, s) -> s + | Template _ -> failwith "'template' not supported in ctypes build flags" + | List _ -> failwith "nested lists not supported in ctypes build flags")) + in let action = let open Build.O in Build.deps deps @@ -293,6 +302,21 @@ let executable ?(modules=[]) ~buildable ~loc ~obj_dir ~dynlink ~dir ~sctx ~scope in Exe.build_and_link ~program ~linkages:[Exe.Linkage.native] ~promote:None cctx +let write_osl_to_sexp_file ~sctx ~dir ~filename osl = + let build = + let path = Path.Build.relative dir filename in + let sexp = + let encoded = + match Ordered_set_lang.Unexpanded.encode osl with + | [s] -> s + | _lst -> failwith "unexpected multi-element list" + in + Dune_lang.to_string encoded + in + Build.write_file path sexp + in + Super_context.add_rule ~loc:Loc.none sctx ~dir build + let gen_rules ~buildable ~dynlink ~loc ~obj_dir ~scope ~expander ~dir ~sctx = let rule = rule ~sctx ~dir in let executable = @@ -324,29 +348,28 @@ let gen_rules ~buildable ~dynlink ~loc ~obj_dir ~scope ~expander ~dir ~sctx = https://dune.readthedocs.io/en/stable/quick-start.html#defining-a-library-with-c-stubs-using-pkg-config *) let c_library_flags_sexp = Ctypes_stanzas.c_library_flags_sexp ctypes in - let cflags_txt = Ctypes_stanzas.cflags_txt ctypes in + let cflags_sexp = Ctypes_stanzas.cflags_sexp ctypes in let () = + let open Ctypes.Build_flags_resolver in match ctypes.Ctypes.build_flags_resolver with - | Ctypes.Build_flags_resolver.Pkg_config -> + | Vendored { c_flags; c_library_flags } -> + write_osl_to_sexp_file ~sctx ~dir ~filename:cflags_sexp c_flags; + write_osl_to_sexp_file ~sctx ~dir ~filename:c_library_flags_sexp + c_library_flags + | Pkg_config -> let cflags_sexp = Ctypes_stanzas.cflags_sexp ctypes in let discover_script = sprintf "%s__ctypes_discover" external_library_name in write_discover_script ~sctx ~dir ~filename:(discover_script ^ ".ml") ~cflags_sexp - ~cflags_txt ~c_library_flags_sexp ~external_library_name; + ~c_library_flags_sexp ~external_library_name; executable ~program:discover_script ~libraries:["dune.configurator"] (); - (* XXX: maybe we should read these files into dune after they've been - generated? rather than constructing Ordered_set_langs with include - directives for these files? *) rule - ~targets:[cflags_sexp; cflags_txt; c_library_flags_sexp] + ~targets:[cflags_sexp; c_library_flags_sexp] ~exe:(discover_script ^ ".exe") () - | Vendored _vendored -> - (* XXX: easier to implement if we read the above files into dune *) - failwith "TODO: implement vendored" in let headers = ctypes.Ctypes.headers in (* Type_gen produces a .c file, taking your type description module above @@ -378,9 +401,8 @@ let gen_rules ~buildable ~dynlink ~loc ~obj_dir ~scope ~expander ~dir ~sctx = ~exe:(type_gen_script ^ ".exe") (); build_c_program - ~sctx ~dir ~scope + ~sctx ~dir ~scope ~cflags_sexp ~source_files:[c_generated_types_cout_c] - ~cflags_txt (*" %{read:c_flags.txt}" *) ~output:c_generated_types_cout_exe (); rule diff --git a/src/dune_rules/ctypes_stanzas.ml b/src/dune_rules/ctypes_stanzas.ml index 06914eb8e8e..f9637287213 100644 --- a/src/dune_rules/ctypes_stanzas.ml +++ b/src/dune_rules/ctypes_stanzas.ml @@ -114,9 +114,6 @@ let entry_library_public ctypes = let cflags_sexp ctypes = sprintf "%s__c_flags.sexp" ctypes.Ctypes.external_library_name -let cflags_txt ctypes = - sprintf "%s__c_flags.txt" ctypes.Ctypes.external_library_name - let c_library_flags_sexp ctypes = sprintf "%s__c_library_flags.sexp" ctypes.Ctypes.external_library_name diff --git a/src/dune_rules/ctypes_stanzas.mli b/src/dune_rules/ctypes_stanzas.mli index 7d1f8090960..cb84c9f2bd1 100644 --- a/src/dune_rules/ctypes_stanzas.mli +++ b/src/dune_rules/ctypes_stanzas.mli @@ -8,7 +8,6 @@ val function_description_module : Ctypes.t -> Module_name.t val function_description_library : Ctypes.t -> string val cflags_sexp : Ctypes.t -> string -val cflags_txt : Ctypes.t -> string val c_library_flags_sexp : Ctypes.t -> string val c_generated_types_module : Ctypes.t -> Module_name.t val c_generated_functions_module : Ctypes.t -> Module_name.t From 227f5209e48817f53502dff9916953e4d9a35647 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Tue, 16 Feb 2021 07:42:49 -0800 Subject: [PATCH 18/69] user_error instead of failwith --- src/dune_rules/ctypes_rules.ml | 13 +++++++------ 1 file changed, 7 insertions(+), 6 deletions(-) diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index b663548bf35..e56de46c0b8 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -203,13 +203,13 @@ let build_c_program ~sctx ~dir ~source_files ~scope ~cflags_sexp ~output () = let ocaml_where = Path.to_string ctx.Context.stdlib_dir in (* XXX: need glob dependency *) let ctypes_include_dirs = - let ctypes = Lib_name.of_string "ctypes" in let lib = + let ctypes = Lib_name.of_string "ctypes" in match Lib.DB.resolve (Scope.libs scope) (Loc.none, ctypes) with | Ok lib -> lib | Error _res -> - (* XXX: User_error.raise *) - failwith "error resolving 'ctypes' lib" + User_error.raise + [ Pp.textf "the 'ctypes' library needs to be installed to use the ctypes stanza"] in Lib.L.include_paths [lib] |> Path.Set.to_list @@ -226,20 +226,21 @@ let build_c_program ~sctx ~dir ~source_files ~scope ~cflags_sexp ~output () = let cflags_args = let contents = Build.contents (Path.relative (Path.build dir) cflags_sexp) in Build.map contents ~f:(fun sexp -> + let fail s = User_error.raise [ Pp.textf s ] in let ast = Dune_lang.Parser.parse_string ~mode:Dune_lang.Parser.Mode.Single ~fname:cflags_sexp sexp in match ast with | Dune_lang.Ast.Atom (_loc, atom) -> [Dune_lang.Atom.to_string atom] - | Template _ -> failwith "'template' not supported in ctypes build flags" + | Template _ -> fail "'template' not supported in ctypes c_flags" | Quoted_string (_loc, s) -> [s] | List (_loc, lst) -> List.map lst ~f:(function | Dune_lang.Ast.Atom (_loc, atom) -> Dune_lang.Atom.to_string atom | Quoted_string (_loc, s) -> s - | Template _ -> failwith "'template' not supported in ctypes build flags" - | List _ -> failwith "nested lists not supported in ctypes build flags")) + | Template _ -> fail "'template' not supported in ctypes c_flags" + | List _ -> fail "nested lists not supported in ctypes c_flags")) in let action = let open Build.O in From fdbbb133d9089cda84fab148a59fa4bf869c3a4b Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Sun, 21 Feb 2021 07:33:02 -0800 Subject: [PATCH 19/69] ctypes_library is its own top-level stanza now --- src/dune_rules/ctypes_rules.ml | 76 +++++++++++++++++------------ src/dune_rules/ctypes_rules.mli | 7 +-- src/dune_rules/ctypes_stanzas.ml | 69 +++++++++++++------------- src/dune_rules/ctypes_stanzas.mli | 17 +++++-- src/dune_rules/dir_contents.ml | 24 ++++----- src/dune_rules/dune_file.ml | 81 +++++++++++++++++++------------ src/dune_rules/dune_file.mli | 18 ++++--- src/dune_rules/dune_load.ml | 25 ++-------- src/dune_rules/exe_rules.ml | 12 ----- src/dune_rules/gen_rules.ml | 3 ++ src/dune_rules/lib_rules.ml | 13 ----- 11 files changed, 174 insertions(+), 171 deletions(-) diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index e56de46c0b8..28598d1ba10 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -3,14 +3,17 @@ open! Stdune module Buildable = Dune_file.Buildable module Library = Dune_file.Library -module Ctypes = Dune_file.Ctypes +module Ctypes = Dune_file.Ctypes_library -(* This module expands a [(library ... (ctypes ...))] rule into the set of - [library], [executable], [rule] rules and .ml files needed to more +(* This module semantically expands a [(ctypes_library ... )] stanza into + [executable] and, [rule] rules and generates .ml files needed to more conveniently build OCaml bindings for C libraries. Aside from perhaps providing an '#include "header.h"' line, you should be able to wrap an entire C library without writing a single line of C code. + See also Ctypes_stanzas for the additional lexical expansion of library + stanzas needed to complete the picture. + This stanza requires the user to define (and specify) two modules: (1) A "Type Descriptions" .ml file with the following top-level module: @@ -120,9 +123,8 @@ let gen_headers headers buf = begin match headers with | Ctypes.Headers.Include lst -> List.iter lst ~f:(fun h -> pr buf " print_endline \"#include <%s>\";" h) - | Preamble s -> - (* XXX: escape s *) - pr buf " print_endline \"%s\";" s + | Preamble_file s -> + pr buf " print_endline \"#include \"%s\"" s end let type_gen_gen ~headers ~type_description_module = @@ -199,9 +201,9 @@ let build_c_program ~sctx ~dir ~source_files ~scope ~cflags_sexp ~output () = |> Super_context.resolve_program ~loc:None ~dir sctx in let include_args = - (* XXX: need glob dependency *) + (* XXX: need glob dependency? *) let ocaml_where = Path.to_string ctx.Context.stdlib_dir in - (* XXX: need glob dependency *) + (* XXX: need glob dependency? *) let ctypes_include_dirs = let lib = let ctypes = Lib_name.of_string "ctypes" in @@ -209,7 +211,7 @@ let build_c_program ~sctx ~dir ~source_files ~scope ~cflags_sexp ~output () = | Ok lib -> lib | Error _res -> User_error.raise - [ Pp.textf "the 'ctypes' library needs to be installed to use the ctypes stanza"] + [ Pp.textf "the 'ctypes' library needs to be installed to use the ctypes_library stanza"] in Lib.L.include_paths [lib] |> Path.Set.to_list @@ -219,7 +221,9 @@ let build_c_program ~sctx ~dir ~source_files ~scope ~cflags_sexp ~output () = List.concat_map include_dirs ~f:(fun dir -> ["-I"; dir]) in let deps = - List.map source_files ~f:(Path.relative (Path.build dir)) + List.map source_files ~f:(fun source_file -> + let path = Path.build dir in + Path.relative path source_file) |> Dep.Set.of_files in let build = @@ -253,7 +257,8 @@ let build_c_program ~sctx ~dir ~source_files ~scope ~cflags_sexp ~output () = in Super_context.add_rule sctx ~dir build -let cctx ?(libraries=[]) ~buildable ~dynlink ~loc ~obj_dir ~dir ~scope ~expander ~sctx = +let cctx ?(libraries=[]) ~buildable ~dynlink ~loc ~obj_dir ~dir ~scope + ~modules ~expander ~sctx () = let compile_info = let dune_version = Scope.project scope |> Dune_project.dune_version in Lib.DB.resolve_user_written_deps_for_exes (Scope.libs scope) @@ -268,31 +273,36 @@ let cctx ?(libraries=[]) ~buildable ~dynlink ~loc ~obj_dir ~dir ~scope ~expander ~js_of_ocaml:None ~dynlink ~package:None + ~modules ~flags:(Super_context.ocaml_flags sctx ~dir buildable.Buildable.flags) ~requires_compile:(Lib.Compile.direct_requires compile_info) ~requires_link:(Lib.Compile.requires_link compile_info) ~obj_dir - ~opaque:Compilation_context.Inherit_from_settings + ~opaque:Compilation_context.Inherit_from_settings () -let executable ?(modules=[]) ~buildable ~loc ~obj_dir ~dynlink ~dir ~sctx ~scope +let executable ?(modules=[]) ~loc ~obj_dir ~dynlink ~dir ~sctx ~scope ~expander ~program ~libraries () = let build_dir = Path.build dir in let cctx = let modules = - let name_map = - List.map (program :: modules) ~f:(fun name -> - let module_name = Module_name.of_string name in - let path = Path.relative build_dir (name ^ ".ml") in - let impl = Module.File.make Dialect.ocaml path in - let source = Module.Source.make ~impl module_name in - Module.of_source ~visibility:Visibility.Public - ~kind:Module.Kind.Impl source) - |> Module.Name_map.of_list_exn - in + List.map (program :: modules) ~f:(fun name -> + let module_name = Module_name.of_string name in + let path = Path.relative build_dir (name ^ ".ml") in + let impl = Module.File.make Dialect.ocaml path in + let source = Module.Source.make ~impl module_name in + Module.of_source ~visibility:Visibility.Public + ~kind:Module.Kind.Impl source) + in + let exe_wrapped_modules = + let name_map = Module.Name_map.of_list_exn modules in Modules.exe_wrapped ~src_dir:dir ~modules:name_map in - cctx ~buildable ~dir ~loc ~obj_dir ~dynlink ~scope ~sctx ~expander - ~modules ~libraries () + let buildable = + let names = List.map modules ~f:Module.name in + Ctypes_stanzas.buildable ~loc ~libraries ~modules:names () + in + cctx ~dir ~buildable ~loc ~obj_dir ~dynlink ~scope ~sctx ~expander + ~libraries ~modules:exe_wrapped_modules () in let program = Exe.Program.{ @@ -318,15 +328,17 @@ let write_osl_to_sexp_file ~sctx ~dir ~filename osl = in Super_context.add_rule ~loc:Loc.none sctx ~dir build -let gen_rules ~buildable ~dynlink ~loc ~obj_dir ~scope ~expander ~dir ~sctx = +let gen_rules ~scope ~expander ~dir ~sctx ~ctypes_library:ctypes = + let loc = fst ctypes.Ctypes.name in let rule = rule ~sctx ~dir in let executable = - executable ~buildable ~loc ~obj_dir ~dynlink ~dir ~sctx ~scope ~expander - in - let ctypes = - match buildable.Buildable.ctypes with - | Some ctypes -> ctypes - | None -> assert false + let dynlink = + let dynlink = Ctypes_stanzas.dynlink ctypes in + let ctx = Super_context.context sctx in + Dynlink_supported.get dynlink ctx.supports_shared_libraries + in + let obj_dir = Dune_file.Ctypes_library.obj_dir ~dir ctypes in + executable ~loc ~obj_dir ~dynlink ~dir ~sctx ~scope ~expander in let external_library_name = ctypes.Ctypes.external_library_name in let type_description_module = Ctypes_stanzas.type_description_module ctypes in diff --git a/src/dune_rules/ctypes_rules.mli b/src/dune_rules/ctypes_rules.mli index f39e166dbc3..1255f62013d 100644 --- a/src/dune_rules/ctypes_rules.mli +++ b/src/dune_rules/ctypes_rules.mli @@ -1,12 +1,9 @@ open! Stdune val gen_rules : - buildable:Dune_file.Buildable.t - -> dynlink:bool - -> loc:Loc.t - -> obj_dir:Path.Build.t Obj_dir.t - -> scope:Scope.t + scope:Scope.t -> expander:Expander.t -> dir:Path.Build.t -> sctx:Super_context.t + -> ctypes_library:Dune_file.Ctypes_library.t -> unit diff --git a/src/dune_rules/ctypes_stanzas.ml b/src/dune_rules/ctypes_stanzas.ml index f9637287213..cd1579e31bc 100644 --- a/src/dune_rules/ctypes_stanzas.ml +++ b/src/dune_rules/ctypes_stanzas.ml @@ -3,13 +3,35 @@ open! Stdune module Buildable = Dune_file.Buildable module Library = Dune_file.Library -module Ctypes = Dune_file.Ctypes +module Ctypes = Dune_file.Ctypes_library let osl_pos () = "", 0, 0, 0 ;; -let library_stanza ?(flags=Ocaml_flags.Spec.standard) ?public_name ?(foreign_stubs=[]) - ?(c_library_flags=Ordered_set_lang.Unexpanded.standard) ~loc ~project ~sub_systems - ~dune_version ~name ~modules ~libraries ~wrapped () = +let buildable ?(flags=Ocaml_flags.Spec.standard) ?(foreign_stubs=[]) ~loc + ~libraries ~modules () = + let libraries = + List.map libraries ~f:(fun library -> + Lib_dep.Direct (loc, Lib_name.of_string library)) + in + let modules = List.map modules ~f:Module_name.to_string in + { Buildable.loc + ; modules = Ordered_set_lang.of_atoms ~loc modules + ; modules_without_implementation = Ordered_set_lang.of_atoms ~loc [] + ; libraries + ; foreign_archives= [] + ; foreign_stubs + ; preprocess = Preprocess.Per_module.default () + ; preprocessor_deps = [] + ; lint = Dune_file.Lint.no_lint + ; flags + ; js_of_ocaml = Dune_file.Js_of_ocaml.default + ; allow_overlapping_dependencies = false + } + +let library_stanza ?(flags=Ocaml_flags.Spec.standard) ?public_name + ?(foreign_stubs=[]) ?(c_library_flags=Ordered_set_lang.Unexpanded.standard) + ~loc ~project ~sub_systems ~dynlink ~dune_version ~name ~modules + ~libraries ~wrapped () = let open Dune_file in let visibility = match public_name with @@ -31,27 +53,7 @@ let library_stanza ?(flags=Ocaml_flags.Spec.standard) ?public_name ?(foreign_stu Library.Public plib *) in - let buildable = - let libraries = - List.map libraries ~f:(fun library -> - Lib_dep.Direct (loc, Lib_name.of_string library)) - in - let modules = List.map modules ~f:Module_name.to_string in - { Buildable.loc - ; modules = Ordered_set_lang.of_atoms ~loc modules - ; modules_without_implementation = Ordered_set_lang.of_atoms ~loc [] - ; libraries - ; foreign_archives= [] - ; foreign_stubs - ; preprocess = Preprocess.Per_module.default () - ; preprocessor_deps = [] - ; lint = Lint.no_lint - ; flags - ; js_of_ocaml = Js_of_ocaml.default - ; allow_overlapping_dependencies = false - ; ctypes = None; - } - in + let buildable = buildable ~foreign_stubs ~flags ~modules ~libraries ~loc () in { Library.name = (loc, Lib_name.of_string name |> Lib_name.to_local_exn) ; visibility ; synopsis = None @@ -65,7 +67,7 @@ let library_stanza ?(flags=Ocaml_flags.Spec.standard) ?public_name ?(foreign_stu ; wrapped = Lib_info.Inherited.This (Wrapped.Simple wrapped) ; optional = false ; buildable - ; dynlink = Dynlink_supported.of_bool true + ; dynlink ; project ; sub_systems ; dune_version @@ -146,6 +148,9 @@ let c_generated_functions_cout_c ctypes = let c_generated_functions_cout_no_ext ctypes = sprintf "%s__c_cout_generated_functions" ctypes.Ctypes.external_library_name +let dynlink _ctypes = + Dynlink_supported.of_bool true + (* Unlike for [executable] and [rule] generation which have neat convenience functions for creating new ones, the machinery for creating new [library]s does several passes to populate global data structures. @@ -154,14 +159,12 @@ let c_generated_functions_cout_no_ext ctypes = approach here is to simply do a quasi-lexical expansion of the base library config stanza into several additional support library stanzas, right after the dune config file parsing is completed. *) -let library_stanzas ~parsing_context ~project ~sub_systems ~dune_version buildable = - let ctypes = - match buildable.Buildable.ctypes with - | Some ctypes -> ctypes - | None -> assert false +let library_stanzas ~parsing_context ~project ~ctypes_library:ctypes = + let loc = fst ctypes.Ctypes.name in + let library_stanza = + library_stanza ~loc ~project ~dune_version:ctypes.Ctypes.dune_version + ~sub_systems:ctypes.Ctypes.sub_systems ~dynlink:(dynlink ctypes) in - let loc = buildable.Buildable.loc in - let library_stanza = library_stanza ~loc ~project ~sub_systems ~dune_version in let type_descriptions = library_stanza ~name:(type_description_library ctypes) diff --git a/src/dune_rules/ctypes_stanzas.mli b/src/dune_rules/ctypes_stanzas.mli index cb84c9f2bd1..ae62a81b05f 100644 --- a/src/dune_rules/ctypes_stanzas.mli +++ b/src/dune_rules/ctypes_stanzas.mli @@ -1,6 +1,17 @@ (* Expand a library with a ctypes stanza into several support libraries. *) open Dune_file +module Ctypes = Ctypes_library + +val buildable : + ?flags:Ocaml_flags.Spec.t + -> ?foreign_stubs:Foreign.Stubs.t list + -> loc:Stdune.Loc.t + -> libraries:string list + -> modules:Module_name.t list + -> unit + -> Buildable.t + val type_description_module : Ctypes.t -> Module_name.t val type_description_library : Ctypes.t -> string @@ -20,12 +31,12 @@ val c_generated_types_cout_exe : Ctypes.t -> string val c_generated_functions_cout_c : Ctypes.t -> string +val dynlink : Ctypes_library.t -> Dynlink_supported.t + val library_stanzas : parsing_context:Stdune.Univ_map.t -> project:Dune_engine.Dune_project.t - -> sub_systems:Sub_system_info.t Sub_system_name.Map.t - -> dune_version:Dune_lang.Syntax.Version.t - -> Buildable.t + -> ctypes_library:Ctypes_library.t -> Library.t list val generated_ml_and_c_files : Ctypes.t -> string list diff --git a/src/dune_rules/dir_contents.ml b/src/dune_rules/dir_contents.ml index 8ce68c20bfb..e8f926cd66c 100644 --- a/src/dune_rules/dir_contents.ml +++ b/src/dune_rules/dir_contents.ml @@ -132,15 +132,6 @@ end = struct in Expander.set_artifacts_dynamic expander true in - let buildable_select_deps buildable = - (* Manually add files generated by the (select ...) dependencies *) - List.filter_map buildable.Buildable.libraries ~f:(fun dep -> - match (dep : Lib_dep.t) with - | Re_export _ - | Direct _ -> - None - | Select s -> Some s.result_fn) - in let generated_files = List.concat_map stanzas ~f:(fun stanza -> match (stanza : Stanza.t) with @@ -159,13 +150,16 @@ end = struct |> Path.Set.to_list |> List.map ~f:Path.basename | Generate_module def -> [ Generate_module_rules.setup_rules sctx ~dir def ] + | Ctypes_library ctypes_library -> + Ctypes_stanzas.generated_ml_and_c_files ctypes_library | Executables { buildable; _ } | Library { buildable; _ } -> - let ctypes_generated_ml_and_c_files = - match buildable.ctypes with - | Some ctypes -> Ctypes_stanzas.generated_ml_and_c_files ctypes - | None -> [] - in - ctypes_generated_ml_and_c_files @ buildable_select_deps buildable + (* Manually add files generated by the (select ...) dependencies *) + List.filter_map buildable.Buildable.libraries ~f:(fun dep -> + match (dep : Lib_dep.t) with + | Re_export _ + | Direct _ -> + None + | Select s -> Some s.result_fn) | _ -> []) |> String.Set.of_list in diff --git a/src/dune_rules/dune_file.ml b/src/dune_rules/dune_file.ml index acd5fdacf03..d8294b3a3cc 100644 --- a/src/dune_rules/dune_file.ml +++ b/src/dune_rules/dune_file.ml @@ -45,7 +45,7 @@ module Js_of_ocaml = struct { flags = Ordered_set_lang.Unexpanded.standard; javascript_files = [] } end -module Ctypes = struct +module Ctypes_library = struct module Build_flags_resolver = struct module Vendored = struct @@ -94,32 +94,38 @@ module Ctypes = struct module Headers = struct type t = | Include of string list - | Preamble of string + | Preamble_file of string let decode = let include_ = let+ s = repeat string in Include s in - let preamble = + let preamble_file = let+ p = string in - Preamble p + Preamble_file p in - sum [ ("include" , include_) - ; ("preamble" , preamble) ] + sum [ ("include" , include_) + ; ("preamble_file" , preamble_file) ] let default = Include [] end type t = - { external_library_name : string + { name : Loc.t * Lib_name.Local.t + ; external_library_name : string ; build_flags_resolver : Build_flags_resolver.t ; headers : Headers.t ; concurrency : Concurrency_policy.t ; type_descriptions : Module_name.t ; function_descriptions : Module_name.t ; generated_types : Module_name.t - ; generated_entry_point : Module_name.t } + ; generated_entry_point : Module_name.t + ; dune_version : Dune_lang.Syntax.Version.t + (* ctypes doesn't do anything special with sub_systems, this is just a way + of getting a default sub_systems value required for creating Buildable *) + ; sub_systems : Sub_system_info.t Sub_system_name.Map.t + } let name = "ctypes" @@ -132,7 +138,9 @@ module Ctypes = struct let decode = let open Dune_lang.Decoder in fields - (let+ external_library_name = field "external_library_name" string + (let* dune_version = Dune_lang.Syntax.get_exn Stanza.syntax in + let+ external_library_name = field "external_library_name" string + and+ name = field "name" Lib_name.Local.decode_loc and+ build_flags_resolver = field_o "build_flags_resolver" Build_flags_resolver.decode and+ headers = field_o "headers" Headers.decode and+ concurrency = field_o "concurrency" Concurrency_policy.decode @@ -140,15 +148,39 @@ module Ctypes = struct and+ function_descriptions = field "function_descriptions" Module_name.decode and+ generated_types = field "generated_types" Module_name.decode and+ generated_entry_point = field "generated_entry_point" Module_name.decode + and+ sub_systems = + let* () = return () in + Sub_system_info.record_parser () in - { external_library_name - ; build_flags_resolver = Option.value build_flags_resolver ~default:Build_flags_resolver.default + { name + ; external_library_name + ; build_flags_resolver = + Option.value build_flags_resolver ~default:Build_flags_resolver.default ; headers = Option.value headers ~default:Headers.default ; concurrency = Option.value concurrency ~default:Concurrency_policy.default ; type_descriptions ; function_descriptions ; generated_types - ; generated_entry_point }) + ; generated_entry_point + ; dune_version + ; sub_systems }) + + let obj_dir ~dir t = + (* XXX: fill me out properly *) + (* XXX: make sure Ctypes_stanzas.library_stanzas does the same *) + (* + let private_lib = + match t.visibility with + | Private (Some _) -> true + | Private None + | Public _ -> + false + in + let has_private_modules = t.private_modules <> None) + *) + Obj_dir.make_lib ~dir + ~has_private_modules:false + ~private_lib:true (snd t.name) let () = let open Dune_lang.Decoder in @@ -272,7 +304,6 @@ module Buildable = struct ; flags : Ocaml_flags.Spec.t ; js_of_ocaml : Js_of_ocaml.t ; allow_overlapping_dependencies : bool - ; ctypes : Ctypes.t option } let decode ~in_library ~allow_re_export = @@ -344,9 +375,6 @@ module Buildable = struct (multi_field "instrumentation" ( Dune_lang.Syntax.since Stanza.syntax (2, 7) >>> fields (field "backend" (located Lib_name.decode)) )) - and+ ctypes = - (field_o "ctypes" - (Dune_lang.Syntax.since Ctypes.syntax (0, 1) >>> Ctypes.decode)) in let preprocess = let init = @@ -400,7 +428,6 @@ module Buildable = struct ; flags ; js_of_ocaml ; allow_overlapping_dependencies - ; ctypes } let has_foreign t = @@ -1431,8 +1458,6 @@ module Executables = struct ; forbidden_libraries : (Loc.t * Lib_name.t) list ; bootstrap_info : string option ; enabled_if : Blang.t - ; sub_systems : Sub_system_info.t Sub_system_name.Map.t - ; dune_version : Dune_lang.Syntax.Version.t } let bootstrap_info_extension = @@ -1500,9 +1525,6 @@ module Executables = struct Dune_lang.Syntax.Version.Infix.(syntax_version >= (2, 6)) in Enabled_if.decode ~allowed_vars ~is_error ~since:(Some (2, 3)) () - and+ sub_systems = - let* () = return () in - Sub_system_info.record_parser () in fun names ~multi -> let has_public_name = Names.has_public_name names in @@ -1560,8 +1582,6 @@ module Executables = struct ; forbidden_libraries ; bootstrap_info ; enabled_if - ; dune_version - ; sub_systems } let single, multi = @@ -1875,8 +1895,7 @@ module Tests = struct let gen_parse names = fields - (let* dune_version = Dune_lang.Syntax.get_exn Stanza.syntax in - let+ buildable = + (let+ buildable = Buildable.decode ~in_library:false ~allow_re_export:false and+ link_flags = Ordered_set_lang.Unexpanded.field "link_flags" and+ names = names @@ -1898,9 +1917,6 @@ module Tests = struct ( Dune_lang.Syntax.since Stanza.syntax (2, 0) >>> repeat (located Lib_name.decode) ) ~default:[] - and+ sub_systems = - let* () = return () in - Sub_system_info.record_parser () in { exes = { Executables.link_flags @@ -1916,8 +1932,6 @@ module Tests = struct ; forbidden_libraries ; bootstrap_info = None ; enabled_if - ; dune_version - ; sub_systems } ; locks ; package @@ -2171,6 +2185,7 @@ type Stanza.t += | Cram of Cram_stanza.t | Generate_module of Generate_module.t | Plugin of Plugin.t + | Ctypes_library of Ctypes_library.t module Stanzas = struct type t = Stanza.t list @@ -2280,6 +2295,10 @@ module Stanzas = struct , let+ () = Dune_lang.Syntax.since Section.dune_site_syntax (0, 1) and+ t = Plugin.decode in [ Plugin t ] ) + ; ( "ctypes_library" + , let+ () = Dune_lang.Syntax.since Stanza.syntax (2, 8) + and+ x = Ctypes_library.decode in + [ Ctypes_library x ] ) ] let () = Dune_project.Lang.register Stanza.syntax stanzas diff --git a/src/dune_rules/dune_file.mli b/src/dune_rules/dune_file.mli index 1f2d2f3fa77..6ada7d50f90 100644 --- a/src/dune_rules/dune_file.mli +++ b/src/dune_rules/dune_file.mli @@ -30,7 +30,7 @@ module Lib_deps : sig end -module Ctypes : sig +module Ctypes_library : sig module Build_flags_resolver : sig module Vendored : sig @@ -54,19 +54,25 @@ module Ctypes : sig module Headers : sig type t = | Include of string list - | Preamble of string + | Preamble_file of string end type t = - { external_library_name : string + { name : Loc.t * Lib_name.Local.t + ; external_library_name : string ; build_flags_resolver : Build_flags_resolver.t ; headers : Headers.t ; concurrency : Concurrency_policy.t ; type_descriptions : Module_name.t ; function_descriptions : Module_name.t ; generated_types : Module_name.t - ; generated_entry_point : Module_name.t } + ; generated_entry_point : Module_name.t + ; dune_version : Dune_lang.Syntax.Version.t + ; sub_systems : Sub_system_info.t Sub_system_name.Map.t + } type Stanza.t += T of t + + val obj_dir : dir:Path.Build.t -> t -> Path.Build.t Obj_dir.t end (** [preprocess] and [preprocessor_deps] fields *) @@ -89,7 +95,6 @@ module Buildable : sig ; flags : Ocaml_flags.Spec.t ; js_of_ocaml : Js_of_ocaml.t ; allow_overlapping_dependencies : bool - ; ctypes : Ctypes.t option } (** Check if the buildable has any foreign stubs or archives. *) @@ -295,8 +300,6 @@ module Executables : sig ; forbidden_libraries : (Loc.t * Lib_name.t) list ; bootstrap_info : string option ; enabled_if : Blang.t - ; sub_systems : Sub_system_info.t Sub_system_name.Map.t - ; dune_version : Dune_lang.Syntax.Version.t } (** Check if the executables have any foreign stubs or archives. *) @@ -466,6 +469,7 @@ type Stanza.t += | Cram of Cram_stanza.t | Generate_module of Generate_module.t | Plugin of Plugin.t + | Ctypes_library of Ctypes_library.t val stanza_package : Stanza.t -> Package.t option diff --git a/src/dune_rules/dune_load.ml b/src/dune_rules/dune_load.ml index ddcda97e983..eb6d889fd79 100644 --- a/src/dune_rules/dune_load.ml +++ b/src/dune_rules/dune_load.ml @@ -12,30 +12,15 @@ module Dune_file = struct let parse sexps ~dir ~file ~project = let stanzas = Dune_file.Stanzas.parse ~file project sexps in let stanzas = - let maybe_expand_ctypes ~dune_version ~sub_systems stanza buildable = - match buildable.Dune_file.Buildable.ctypes with - | None -> [stanza] - | Some _ctypes -> + List.concat_map stanzas ~f:(fun stanza -> + match stanza with + | Dune_file.Ctypes_library ctypes_library -> let libs = Ctypes_stanzas.library_stanzas ~parsing_context:(Dune_project.parsing_context project) - ~project ~dune_version ~sub_systems - buildable + ~project ~ctypes_library in - stanza :: (List.map libs ~f:(fun l -> Dune_file.Library l)) - in - List.concat_map stanzas ~f:(fun stanza -> - match stanza with - | Dune_file.Executables exes -> - maybe_expand_ctypes - ~sub_systems:exes.Dune_file.Executables.sub_systems - ~dune_version:exes.Dune_file.Executables.dune_version - stanza exes.Dune_file.Executables.buildable - | Dune_file.Library lib -> - maybe_expand_ctypes - ~sub_systems:lib.Dune_file.Library.sub_systems - ~dune_version:lib.Dune_file.Library.dune_version - stanza lib.Dune_file.Library.buildable + stanza :: List.map libs ~f:(fun lib -> Dune_file.Library lib) | _ -> [stanza]) in let stanzas = diff --git a/src/dune_rules/exe_rules.ml b/src/dune_rules/exe_rules.ml index d408f88d796..297428a19c8 100644 --- a/src/dune_rules/exe_rules.ml +++ b/src/dune_rules/exe_rules.ml @@ -201,18 +201,6 @@ let compile_info ~scope (exes : Dune_file.Executables.t) = let rules ~sctx ~dir ~dir_contents ~scope ~expander (exes : Dune_file.Executables.t) = let compile_info = compile_info ~scope exes in - let () = - let buildable = exes.Executables.buildable in - Option.iter buildable.Buildable.ctypes ~f:(fun _ctypes -> - let loc = - match exes.Executables.names with - | hd :: _ -> fst hd - | [] -> assert false - in - let obj_dir = Executables.obj_dir ~dir exes in - Ctypes_rules.gen_rules ~buildable ~dynlink:false ~loc ~obj_dir ~sctx - ~scope ~expander ~dir) - in let f () = executables_rules exes ~sctx ~dir ~dir_contents ~scope ~expander ~compile_info ~embed_in_plugin_libraries:exes.embed_in_plugin_libraries diff --git a/src/dune_rules/gen_rules.ml b/src/dune_rules/gen_rules.ml index 053fcf3291c..56e4c9e78c9 100644 --- a/src/dune_rules/gen_rules.ml +++ b/src/dune_rules/gen_rules.ml @@ -81,6 +81,9 @@ end = struct ; js = None ; source_dirs = None } + | Ctypes_library ctypes_library -> + Ctypes_rules.gen_rules ~scope ~dir ~expander ~ctypes_library ~sctx; + empty_none | Foreign_library lib -> Lib_rules.foreign_rules lib ~sctx ~dir ~dir_contents ~expander; empty_none diff --git a/src/dune_rules/lib_rules.ml b/src/dune_rules/lib_rules.ml index 65261fdb7e8..5266d380c24 100644 --- a/src/dune_rules/lib_rules.ml +++ b/src/dune_rules/lib_rules.ml @@ -430,19 +430,6 @@ let rules (lib : Library.t) ~sctx ~dir_contents ~dir ~expander ~scope : Lib.DB.get_compile_info (Scope.libs scope) (Library.best_name lib) ~allow_overlaps:lib.buildable.allow_overlapping_dependencies in - let () = - let buildable = lib.Library.buildable in - Option.iter buildable.Buildable.ctypes ~f:(fun _ctypes -> - let loc, _name = lib.Library.name in - let dynlink = - let ctx = Super_context.context sctx in - Dynlink_supported.get lib.Library.dynlink - ctx.Context.supports_shared_libraries - in - let obj_dir = Library.obj_dir ~dir lib in - Ctypes_rules.gen_rules ~buildable ~dynlink ~loc ~obj_dir ~sctx ~scope - ~expander ~dir) - in let f () = let source_modules = Dir_contents.ocaml dir_contents From d993a1d48bb177506abcb7235166e5542c10df91 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Mon, 22 Feb 2021 08:35:20 -0800 Subject: [PATCH 20/69] decided to not do a top-level stanza after all Revert "ctypes_library is its own top-level stanza now" This reverts commit fdbbb133d9089cda84fab148a59fa4bf869c3a4b. --- src/dune_rules/ctypes_rules.ml | 76 ++++++++++++----------------- src/dune_rules/ctypes_rules.mli | 7 ++- src/dune_rules/ctypes_stanzas.ml | 69 +++++++++++++------------- src/dune_rules/ctypes_stanzas.mli | 17 ++----- src/dune_rules/dir_contents.ml | 24 +++++---- src/dune_rules/dune_file.ml | 81 ++++++++++++------------------- src/dune_rules/dune_file.mli | 18 +++---- src/dune_rules/dune_load.ml | 25 ++++++++-- src/dune_rules/exe_rules.ml | 12 +++++ src/dune_rules/gen_rules.ml | 3 -- src/dune_rules/lib_rules.ml | 13 +++++ 11 files changed, 171 insertions(+), 174 deletions(-) diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index 28598d1ba10..e56de46c0b8 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -3,17 +3,14 @@ open! Stdune module Buildable = Dune_file.Buildable module Library = Dune_file.Library -module Ctypes = Dune_file.Ctypes_library +module Ctypes = Dune_file.Ctypes -(* This module semantically expands a [(ctypes_library ... )] stanza into - [executable] and, [rule] rules and generates .ml files needed to more +(* This module expands a [(library ... (ctypes ...))] rule into the set of + [library], [executable], [rule] rules and .ml files needed to more conveniently build OCaml bindings for C libraries. Aside from perhaps providing an '#include "header.h"' line, you should be able to wrap an entire C library without writing a single line of C code. - See also Ctypes_stanzas for the additional lexical expansion of library - stanzas needed to complete the picture. - This stanza requires the user to define (and specify) two modules: (1) A "Type Descriptions" .ml file with the following top-level module: @@ -123,8 +120,9 @@ let gen_headers headers buf = begin match headers with | Ctypes.Headers.Include lst -> List.iter lst ~f:(fun h -> pr buf " print_endline \"#include <%s>\";" h) - | Preamble_file s -> - pr buf " print_endline \"#include \"%s\"" s + | Preamble s -> + (* XXX: escape s *) + pr buf " print_endline \"%s\";" s end let type_gen_gen ~headers ~type_description_module = @@ -201,9 +199,9 @@ let build_c_program ~sctx ~dir ~source_files ~scope ~cflags_sexp ~output () = |> Super_context.resolve_program ~loc:None ~dir sctx in let include_args = - (* XXX: need glob dependency? *) + (* XXX: need glob dependency *) let ocaml_where = Path.to_string ctx.Context.stdlib_dir in - (* XXX: need glob dependency? *) + (* XXX: need glob dependency *) let ctypes_include_dirs = let lib = let ctypes = Lib_name.of_string "ctypes" in @@ -211,7 +209,7 @@ let build_c_program ~sctx ~dir ~source_files ~scope ~cflags_sexp ~output () = | Ok lib -> lib | Error _res -> User_error.raise - [ Pp.textf "the 'ctypes' library needs to be installed to use the ctypes_library stanza"] + [ Pp.textf "the 'ctypes' library needs to be installed to use the ctypes stanza"] in Lib.L.include_paths [lib] |> Path.Set.to_list @@ -221,9 +219,7 @@ let build_c_program ~sctx ~dir ~source_files ~scope ~cflags_sexp ~output () = List.concat_map include_dirs ~f:(fun dir -> ["-I"; dir]) in let deps = - List.map source_files ~f:(fun source_file -> - let path = Path.build dir in - Path.relative path source_file) + List.map source_files ~f:(Path.relative (Path.build dir)) |> Dep.Set.of_files in let build = @@ -257,8 +253,7 @@ let build_c_program ~sctx ~dir ~source_files ~scope ~cflags_sexp ~output () = in Super_context.add_rule sctx ~dir build -let cctx ?(libraries=[]) ~buildable ~dynlink ~loc ~obj_dir ~dir ~scope - ~modules ~expander ~sctx () = +let cctx ?(libraries=[]) ~buildable ~dynlink ~loc ~obj_dir ~dir ~scope ~expander ~sctx = let compile_info = let dune_version = Scope.project scope |> Dune_project.dune_version in Lib.DB.resolve_user_written_deps_for_exes (Scope.libs scope) @@ -273,36 +268,31 @@ let cctx ?(libraries=[]) ~buildable ~dynlink ~loc ~obj_dir ~dir ~scope ~js_of_ocaml:None ~dynlink ~package:None - ~modules ~flags:(Super_context.ocaml_flags sctx ~dir buildable.Buildable.flags) ~requires_compile:(Lib.Compile.direct_requires compile_info) ~requires_link:(Lib.Compile.requires_link compile_info) ~obj_dir - ~opaque:Compilation_context.Inherit_from_settings () + ~opaque:Compilation_context.Inherit_from_settings -let executable ?(modules=[]) ~loc ~obj_dir ~dynlink ~dir ~sctx ~scope +let executable ?(modules=[]) ~buildable ~loc ~obj_dir ~dynlink ~dir ~sctx ~scope ~expander ~program ~libraries () = let build_dir = Path.build dir in let cctx = let modules = - List.map (program :: modules) ~f:(fun name -> - let module_name = Module_name.of_string name in - let path = Path.relative build_dir (name ^ ".ml") in - let impl = Module.File.make Dialect.ocaml path in - let source = Module.Source.make ~impl module_name in - Module.of_source ~visibility:Visibility.Public - ~kind:Module.Kind.Impl source) - in - let exe_wrapped_modules = - let name_map = Module.Name_map.of_list_exn modules in + let name_map = + List.map (program :: modules) ~f:(fun name -> + let module_name = Module_name.of_string name in + let path = Path.relative build_dir (name ^ ".ml") in + let impl = Module.File.make Dialect.ocaml path in + let source = Module.Source.make ~impl module_name in + Module.of_source ~visibility:Visibility.Public + ~kind:Module.Kind.Impl source) + |> Module.Name_map.of_list_exn + in Modules.exe_wrapped ~src_dir:dir ~modules:name_map in - let buildable = - let names = List.map modules ~f:Module.name in - Ctypes_stanzas.buildable ~loc ~libraries ~modules:names () - in - cctx ~dir ~buildable ~loc ~obj_dir ~dynlink ~scope ~sctx ~expander - ~libraries ~modules:exe_wrapped_modules () + cctx ~buildable ~dir ~loc ~obj_dir ~dynlink ~scope ~sctx ~expander + ~modules ~libraries () in let program = Exe.Program.{ @@ -328,17 +318,15 @@ let write_osl_to_sexp_file ~sctx ~dir ~filename osl = in Super_context.add_rule ~loc:Loc.none sctx ~dir build -let gen_rules ~scope ~expander ~dir ~sctx ~ctypes_library:ctypes = - let loc = fst ctypes.Ctypes.name in +let gen_rules ~buildable ~dynlink ~loc ~obj_dir ~scope ~expander ~dir ~sctx = let rule = rule ~sctx ~dir in let executable = - let dynlink = - let dynlink = Ctypes_stanzas.dynlink ctypes in - let ctx = Super_context.context sctx in - Dynlink_supported.get dynlink ctx.supports_shared_libraries - in - let obj_dir = Dune_file.Ctypes_library.obj_dir ~dir ctypes in - executable ~loc ~obj_dir ~dynlink ~dir ~sctx ~scope ~expander + executable ~buildable ~loc ~obj_dir ~dynlink ~dir ~sctx ~scope ~expander + in + let ctypes = + match buildable.Buildable.ctypes with + | Some ctypes -> ctypes + | None -> assert false in let external_library_name = ctypes.Ctypes.external_library_name in let type_description_module = Ctypes_stanzas.type_description_module ctypes in diff --git a/src/dune_rules/ctypes_rules.mli b/src/dune_rules/ctypes_rules.mli index 1255f62013d..f39e166dbc3 100644 --- a/src/dune_rules/ctypes_rules.mli +++ b/src/dune_rules/ctypes_rules.mli @@ -1,9 +1,12 @@ open! Stdune val gen_rules : - scope:Scope.t + buildable:Dune_file.Buildable.t + -> dynlink:bool + -> loc:Loc.t + -> obj_dir:Path.Build.t Obj_dir.t + -> scope:Scope.t -> expander:Expander.t -> dir:Path.Build.t -> sctx:Super_context.t - -> ctypes_library:Dune_file.Ctypes_library.t -> unit diff --git a/src/dune_rules/ctypes_stanzas.ml b/src/dune_rules/ctypes_stanzas.ml index cd1579e31bc..f9637287213 100644 --- a/src/dune_rules/ctypes_stanzas.ml +++ b/src/dune_rules/ctypes_stanzas.ml @@ -3,35 +3,13 @@ open! Stdune module Buildable = Dune_file.Buildable module Library = Dune_file.Library -module Ctypes = Dune_file.Ctypes_library +module Ctypes = Dune_file.Ctypes let osl_pos () = "", 0, 0, 0 ;; -let buildable ?(flags=Ocaml_flags.Spec.standard) ?(foreign_stubs=[]) ~loc - ~libraries ~modules () = - let libraries = - List.map libraries ~f:(fun library -> - Lib_dep.Direct (loc, Lib_name.of_string library)) - in - let modules = List.map modules ~f:Module_name.to_string in - { Buildable.loc - ; modules = Ordered_set_lang.of_atoms ~loc modules - ; modules_without_implementation = Ordered_set_lang.of_atoms ~loc [] - ; libraries - ; foreign_archives= [] - ; foreign_stubs - ; preprocess = Preprocess.Per_module.default () - ; preprocessor_deps = [] - ; lint = Dune_file.Lint.no_lint - ; flags - ; js_of_ocaml = Dune_file.Js_of_ocaml.default - ; allow_overlapping_dependencies = false - } - -let library_stanza ?(flags=Ocaml_flags.Spec.standard) ?public_name - ?(foreign_stubs=[]) ?(c_library_flags=Ordered_set_lang.Unexpanded.standard) - ~loc ~project ~sub_systems ~dynlink ~dune_version ~name ~modules - ~libraries ~wrapped () = +let library_stanza ?(flags=Ocaml_flags.Spec.standard) ?public_name ?(foreign_stubs=[]) + ?(c_library_flags=Ordered_set_lang.Unexpanded.standard) ~loc ~project ~sub_systems + ~dune_version ~name ~modules ~libraries ~wrapped () = let open Dune_file in let visibility = match public_name with @@ -53,7 +31,27 @@ let library_stanza ?(flags=Ocaml_flags.Spec.standard) ?public_name Library.Public plib *) in - let buildable = buildable ~foreign_stubs ~flags ~modules ~libraries ~loc () in + let buildable = + let libraries = + List.map libraries ~f:(fun library -> + Lib_dep.Direct (loc, Lib_name.of_string library)) + in + let modules = List.map modules ~f:Module_name.to_string in + { Buildable.loc + ; modules = Ordered_set_lang.of_atoms ~loc modules + ; modules_without_implementation = Ordered_set_lang.of_atoms ~loc [] + ; libraries + ; foreign_archives= [] + ; foreign_stubs + ; preprocess = Preprocess.Per_module.default () + ; preprocessor_deps = [] + ; lint = Lint.no_lint + ; flags + ; js_of_ocaml = Js_of_ocaml.default + ; allow_overlapping_dependencies = false + ; ctypes = None; + } + in { Library.name = (loc, Lib_name.of_string name |> Lib_name.to_local_exn) ; visibility ; synopsis = None @@ -67,7 +65,7 @@ let library_stanza ?(flags=Ocaml_flags.Spec.standard) ?public_name ; wrapped = Lib_info.Inherited.This (Wrapped.Simple wrapped) ; optional = false ; buildable - ; dynlink + ; dynlink = Dynlink_supported.of_bool true ; project ; sub_systems ; dune_version @@ -148,9 +146,6 @@ let c_generated_functions_cout_c ctypes = let c_generated_functions_cout_no_ext ctypes = sprintf "%s__c_cout_generated_functions" ctypes.Ctypes.external_library_name -let dynlink _ctypes = - Dynlink_supported.of_bool true - (* Unlike for [executable] and [rule] generation which have neat convenience functions for creating new ones, the machinery for creating new [library]s does several passes to populate global data structures. @@ -159,12 +154,14 @@ let dynlink _ctypes = approach here is to simply do a quasi-lexical expansion of the base library config stanza into several additional support library stanzas, right after the dune config file parsing is completed. *) -let library_stanzas ~parsing_context ~project ~ctypes_library:ctypes = - let loc = fst ctypes.Ctypes.name in - let library_stanza = - library_stanza ~loc ~project ~dune_version:ctypes.Ctypes.dune_version - ~sub_systems:ctypes.Ctypes.sub_systems ~dynlink:(dynlink ctypes) +let library_stanzas ~parsing_context ~project ~sub_systems ~dune_version buildable = + let ctypes = + match buildable.Buildable.ctypes with + | Some ctypes -> ctypes + | None -> assert false in + let loc = buildable.Buildable.loc in + let library_stanza = library_stanza ~loc ~project ~sub_systems ~dune_version in let type_descriptions = library_stanza ~name:(type_description_library ctypes) diff --git a/src/dune_rules/ctypes_stanzas.mli b/src/dune_rules/ctypes_stanzas.mli index ae62a81b05f..cb84c9f2bd1 100644 --- a/src/dune_rules/ctypes_stanzas.mli +++ b/src/dune_rules/ctypes_stanzas.mli @@ -1,17 +1,6 @@ (* Expand a library with a ctypes stanza into several support libraries. *) open Dune_file -module Ctypes = Ctypes_library - -val buildable : - ?flags:Ocaml_flags.Spec.t - -> ?foreign_stubs:Foreign.Stubs.t list - -> loc:Stdune.Loc.t - -> libraries:string list - -> modules:Module_name.t list - -> unit - -> Buildable.t - val type_description_module : Ctypes.t -> Module_name.t val type_description_library : Ctypes.t -> string @@ -31,12 +20,12 @@ val c_generated_types_cout_exe : Ctypes.t -> string val c_generated_functions_cout_c : Ctypes.t -> string -val dynlink : Ctypes_library.t -> Dynlink_supported.t - val library_stanzas : parsing_context:Stdune.Univ_map.t -> project:Dune_engine.Dune_project.t - -> ctypes_library:Ctypes_library.t + -> sub_systems:Sub_system_info.t Sub_system_name.Map.t + -> dune_version:Dune_lang.Syntax.Version.t + -> Buildable.t -> Library.t list val generated_ml_and_c_files : Ctypes.t -> string list diff --git a/src/dune_rules/dir_contents.ml b/src/dune_rules/dir_contents.ml index e8f926cd66c..8ce68c20bfb 100644 --- a/src/dune_rules/dir_contents.ml +++ b/src/dune_rules/dir_contents.ml @@ -132,6 +132,15 @@ end = struct in Expander.set_artifacts_dynamic expander true in + let buildable_select_deps buildable = + (* Manually add files generated by the (select ...) dependencies *) + List.filter_map buildable.Buildable.libraries ~f:(fun dep -> + match (dep : Lib_dep.t) with + | Re_export _ + | Direct _ -> + None + | Select s -> Some s.result_fn) + in let generated_files = List.concat_map stanzas ~f:(fun stanza -> match (stanza : Stanza.t) with @@ -150,16 +159,13 @@ end = struct |> Path.Set.to_list |> List.map ~f:Path.basename | Generate_module def -> [ Generate_module_rules.setup_rules sctx ~dir def ] - | Ctypes_library ctypes_library -> - Ctypes_stanzas.generated_ml_and_c_files ctypes_library | Executables { buildable; _ } | Library { buildable; _ } -> - (* Manually add files generated by the (select ...) dependencies *) - List.filter_map buildable.Buildable.libraries ~f:(fun dep -> - match (dep : Lib_dep.t) with - | Re_export _ - | Direct _ -> - None - | Select s -> Some s.result_fn) + let ctypes_generated_ml_and_c_files = + match buildable.ctypes with + | Some ctypes -> Ctypes_stanzas.generated_ml_and_c_files ctypes + | None -> [] + in + ctypes_generated_ml_and_c_files @ buildable_select_deps buildable | _ -> []) |> String.Set.of_list in diff --git a/src/dune_rules/dune_file.ml b/src/dune_rules/dune_file.ml index d8294b3a3cc..acd5fdacf03 100644 --- a/src/dune_rules/dune_file.ml +++ b/src/dune_rules/dune_file.ml @@ -45,7 +45,7 @@ module Js_of_ocaml = struct { flags = Ordered_set_lang.Unexpanded.standard; javascript_files = [] } end -module Ctypes_library = struct +module Ctypes = struct module Build_flags_resolver = struct module Vendored = struct @@ -94,38 +94,32 @@ module Ctypes_library = struct module Headers = struct type t = | Include of string list - | Preamble_file of string + | Preamble of string let decode = let include_ = let+ s = repeat string in Include s in - let preamble_file = + let preamble = let+ p = string in - Preamble_file p + Preamble p in - sum [ ("include" , include_) - ; ("preamble_file" , preamble_file) ] + sum [ ("include" , include_) + ; ("preamble" , preamble) ] let default = Include [] end type t = - { name : Loc.t * Lib_name.Local.t - ; external_library_name : string + { external_library_name : string ; build_flags_resolver : Build_flags_resolver.t ; headers : Headers.t ; concurrency : Concurrency_policy.t ; type_descriptions : Module_name.t ; function_descriptions : Module_name.t ; generated_types : Module_name.t - ; generated_entry_point : Module_name.t - ; dune_version : Dune_lang.Syntax.Version.t - (* ctypes doesn't do anything special with sub_systems, this is just a way - of getting a default sub_systems value required for creating Buildable *) - ; sub_systems : Sub_system_info.t Sub_system_name.Map.t - } + ; generated_entry_point : Module_name.t } let name = "ctypes" @@ -138,9 +132,7 @@ module Ctypes_library = struct let decode = let open Dune_lang.Decoder in fields - (let* dune_version = Dune_lang.Syntax.get_exn Stanza.syntax in - let+ external_library_name = field "external_library_name" string - and+ name = field "name" Lib_name.Local.decode_loc + (let+ external_library_name = field "external_library_name" string and+ build_flags_resolver = field_o "build_flags_resolver" Build_flags_resolver.decode and+ headers = field_o "headers" Headers.decode and+ concurrency = field_o "concurrency" Concurrency_policy.decode @@ -148,39 +140,15 @@ module Ctypes_library = struct and+ function_descriptions = field "function_descriptions" Module_name.decode and+ generated_types = field "generated_types" Module_name.decode and+ generated_entry_point = field "generated_entry_point" Module_name.decode - and+ sub_systems = - let* () = return () in - Sub_system_info.record_parser () in - { name - ; external_library_name - ; build_flags_resolver = - Option.value build_flags_resolver ~default:Build_flags_resolver.default + { external_library_name + ; build_flags_resolver = Option.value build_flags_resolver ~default:Build_flags_resolver.default ; headers = Option.value headers ~default:Headers.default ; concurrency = Option.value concurrency ~default:Concurrency_policy.default ; type_descriptions ; function_descriptions ; generated_types - ; generated_entry_point - ; dune_version - ; sub_systems }) - - let obj_dir ~dir t = - (* XXX: fill me out properly *) - (* XXX: make sure Ctypes_stanzas.library_stanzas does the same *) - (* - let private_lib = - match t.visibility with - | Private (Some _) -> true - | Private None - | Public _ -> - false - in - let has_private_modules = t.private_modules <> None) - *) - Obj_dir.make_lib ~dir - ~has_private_modules:false - ~private_lib:true (snd t.name) + ; generated_entry_point }) let () = let open Dune_lang.Decoder in @@ -304,6 +272,7 @@ module Buildable = struct ; flags : Ocaml_flags.Spec.t ; js_of_ocaml : Js_of_ocaml.t ; allow_overlapping_dependencies : bool + ; ctypes : Ctypes.t option } let decode ~in_library ~allow_re_export = @@ -375,6 +344,9 @@ module Buildable = struct (multi_field "instrumentation" ( Dune_lang.Syntax.since Stanza.syntax (2, 7) >>> fields (field "backend" (located Lib_name.decode)) )) + and+ ctypes = + (field_o "ctypes" + (Dune_lang.Syntax.since Ctypes.syntax (0, 1) >>> Ctypes.decode)) in let preprocess = let init = @@ -428,6 +400,7 @@ module Buildable = struct ; flags ; js_of_ocaml ; allow_overlapping_dependencies + ; ctypes } let has_foreign t = @@ -1458,6 +1431,8 @@ module Executables = struct ; forbidden_libraries : (Loc.t * Lib_name.t) list ; bootstrap_info : string option ; enabled_if : Blang.t + ; sub_systems : Sub_system_info.t Sub_system_name.Map.t + ; dune_version : Dune_lang.Syntax.Version.t } let bootstrap_info_extension = @@ -1525,6 +1500,9 @@ module Executables = struct Dune_lang.Syntax.Version.Infix.(syntax_version >= (2, 6)) in Enabled_if.decode ~allowed_vars ~is_error ~since:(Some (2, 3)) () + and+ sub_systems = + let* () = return () in + Sub_system_info.record_parser () in fun names ~multi -> let has_public_name = Names.has_public_name names in @@ -1582,6 +1560,8 @@ module Executables = struct ; forbidden_libraries ; bootstrap_info ; enabled_if + ; dune_version + ; sub_systems } let single, multi = @@ -1895,7 +1875,8 @@ module Tests = struct let gen_parse names = fields - (let+ buildable = + (let* dune_version = Dune_lang.Syntax.get_exn Stanza.syntax in + let+ buildable = Buildable.decode ~in_library:false ~allow_re_export:false and+ link_flags = Ordered_set_lang.Unexpanded.field "link_flags" and+ names = names @@ -1917,6 +1898,9 @@ module Tests = struct ( Dune_lang.Syntax.since Stanza.syntax (2, 0) >>> repeat (located Lib_name.decode) ) ~default:[] + and+ sub_systems = + let* () = return () in + Sub_system_info.record_parser () in { exes = { Executables.link_flags @@ -1932,6 +1916,8 @@ module Tests = struct ; forbidden_libraries ; bootstrap_info = None ; enabled_if + ; dune_version + ; sub_systems } ; locks ; package @@ -2185,7 +2171,6 @@ type Stanza.t += | Cram of Cram_stanza.t | Generate_module of Generate_module.t | Plugin of Plugin.t - | Ctypes_library of Ctypes_library.t module Stanzas = struct type t = Stanza.t list @@ -2295,10 +2280,6 @@ module Stanzas = struct , let+ () = Dune_lang.Syntax.since Section.dune_site_syntax (0, 1) and+ t = Plugin.decode in [ Plugin t ] ) - ; ( "ctypes_library" - , let+ () = Dune_lang.Syntax.since Stanza.syntax (2, 8) - and+ x = Ctypes_library.decode in - [ Ctypes_library x ] ) ] let () = Dune_project.Lang.register Stanza.syntax stanzas diff --git a/src/dune_rules/dune_file.mli b/src/dune_rules/dune_file.mli index 6ada7d50f90..1f2d2f3fa77 100644 --- a/src/dune_rules/dune_file.mli +++ b/src/dune_rules/dune_file.mli @@ -30,7 +30,7 @@ module Lib_deps : sig end -module Ctypes_library : sig +module Ctypes : sig module Build_flags_resolver : sig module Vendored : sig @@ -54,25 +54,19 @@ module Ctypes_library : sig module Headers : sig type t = | Include of string list - | Preamble_file of string + | Preamble of string end type t = - { name : Loc.t * Lib_name.Local.t - ; external_library_name : string + { external_library_name : string ; build_flags_resolver : Build_flags_resolver.t ; headers : Headers.t ; concurrency : Concurrency_policy.t ; type_descriptions : Module_name.t ; function_descriptions : Module_name.t ; generated_types : Module_name.t - ; generated_entry_point : Module_name.t - ; dune_version : Dune_lang.Syntax.Version.t - ; sub_systems : Sub_system_info.t Sub_system_name.Map.t - } + ; generated_entry_point : Module_name.t } type Stanza.t += T of t - - val obj_dir : dir:Path.Build.t -> t -> Path.Build.t Obj_dir.t end (** [preprocess] and [preprocessor_deps] fields *) @@ -95,6 +89,7 @@ module Buildable : sig ; flags : Ocaml_flags.Spec.t ; js_of_ocaml : Js_of_ocaml.t ; allow_overlapping_dependencies : bool + ; ctypes : Ctypes.t option } (** Check if the buildable has any foreign stubs or archives. *) @@ -300,6 +295,8 @@ module Executables : sig ; forbidden_libraries : (Loc.t * Lib_name.t) list ; bootstrap_info : string option ; enabled_if : Blang.t + ; sub_systems : Sub_system_info.t Sub_system_name.Map.t + ; dune_version : Dune_lang.Syntax.Version.t } (** Check if the executables have any foreign stubs or archives. *) @@ -469,7 +466,6 @@ type Stanza.t += | Cram of Cram_stanza.t | Generate_module of Generate_module.t | Plugin of Plugin.t - | Ctypes_library of Ctypes_library.t val stanza_package : Stanza.t -> Package.t option diff --git a/src/dune_rules/dune_load.ml b/src/dune_rules/dune_load.ml index eb6d889fd79..ddcda97e983 100644 --- a/src/dune_rules/dune_load.ml +++ b/src/dune_rules/dune_load.ml @@ -12,15 +12,30 @@ module Dune_file = struct let parse sexps ~dir ~file ~project = let stanzas = Dune_file.Stanzas.parse ~file project sexps in let stanzas = - List.concat_map stanzas ~f:(fun stanza -> - match stanza with - | Dune_file.Ctypes_library ctypes_library -> + let maybe_expand_ctypes ~dune_version ~sub_systems stanza buildable = + match buildable.Dune_file.Buildable.ctypes with + | None -> [stanza] + | Some _ctypes -> let libs = Ctypes_stanzas.library_stanzas ~parsing_context:(Dune_project.parsing_context project) - ~project ~ctypes_library + ~project ~dune_version ~sub_systems + buildable in - stanza :: List.map libs ~f:(fun lib -> Dune_file.Library lib) + stanza :: (List.map libs ~f:(fun l -> Dune_file.Library l)) + in + List.concat_map stanzas ~f:(fun stanza -> + match stanza with + | Dune_file.Executables exes -> + maybe_expand_ctypes + ~sub_systems:exes.Dune_file.Executables.sub_systems + ~dune_version:exes.Dune_file.Executables.dune_version + stanza exes.Dune_file.Executables.buildable + | Dune_file.Library lib -> + maybe_expand_ctypes + ~sub_systems:lib.Dune_file.Library.sub_systems + ~dune_version:lib.Dune_file.Library.dune_version + stanza lib.Dune_file.Library.buildable | _ -> [stanza]) in let stanzas = diff --git a/src/dune_rules/exe_rules.ml b/src/dune_rules/exe_rules.ml index 297428a19c8..d408f88d796 100644 --- a/src/dune_rules/exe_rules.ml +++ b/src/dune_rules/exe_rules.ml @@ -201,6 +201,18 @@ let compile_info ~scope (exes : Dune_file.Executables.t) = let rules ~sctx ~dir ~dir_contents ~scope ~expander (exes : Dune_file.Executables.t) = let compile_info = compile_info ~scope exes in + let () = + let buildable = exes.Executables.buildable in + Option.iter buildable.Buildable.ctypes ~f:(fun _ctypes -> + let loc = + match exes.Executables.names with + | hd :: _ -> fst hd + | [] -> assert false + in + let obj_dir = Executables.obj_dir ~dir exes in + Ctypes_rules.gen_rules ~buildable ~dynlink:false ~loc ~obj_dir ~sctx + ~scope ~expander ~dir) + in let f () = executables_rules exes ~sctx ~dir ~dir_contents ~scope ~expander ~compile_info ~embed_in_plugin_libraries:exes.embed_in_plugin_libraries diff --git a/src/dune_rules/gen_rules.ml b/src/dune_rules/gen_rules.ml index 56e4c9e78c9..053fcf3291c 100644 --- a/src/dune_rules/gen_rules.ml +++ b/src/dune_rules/gen_rules.ml @@ -81,9 +81,6 @@ end = struct ; js = None ; source_dirs = None } - | Ctypes_library ctypes_library -> - Ctypes_rules.gen_rules ~scope ~dir ~expander ~ctypes_library ~sctx; - empty_none | Foreign_library lib -> Lib_rules.foreign_rules lib ~sctx ~dir ~dir_contents ~expander; empty_none diff --git a/src/dune_rules/lib_rules.ml b/src/dune_rules/lib_rules.ml index 5266d380c24..65261fdb7e8 100644 --- a/src/dune_rules/lib_rules.ml +++ b/src/dune_rules/lib_rules.ml @@ -430,6 +430,19 @@ let rules (lib : Library.t) ~sctx ~dir_contents ~dir ~expander ~scope : Lib.DB.get_compile_info (Scope.libs scope) (Library.best_name lib) ~allow_overlaps:lib.buildable.allow_overlapping_dependencies in + let () = + let buildable = lib.Library.buildable in + Option.iter buildable.Buildable.ctypes ~f:(fun _ctypes -> + let loc, _name = lib.Library.name in + let dynlink = + let ctx = Super_context.context sctx in + Dynlink_supported.get lib.Library.dynlink + ctx.Context.supports_shared_libraries + in + let obj_dir = Library.obj_dir ~dir lib in + Ctypes_rules.gen_rules ~buildable ~dynlink ~loc ~obj_dir ~sctx ~scope + ~expander ~dir) + in let f () = let source_modules = Dir_contents.ocaml dir_contents From 1bd95b13d500c8a171b010d7cd7d29510656ef62 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Mon, 8 Mar 2021 07:53:45 -0800 Subject: [PATCH 21/69] trying an approach with no intermediate libraries --- src/dune_rules/ctypes_rules.ml | 260 +++++++++++++++++++++--------- src/dune_rules/ctypes_rules.mli | 12 -- src/dune_rules/ctypes_stanzas.ml | 230 -------------------------- src/dune_rules/ctypes_stanzas.mli | 31 ---- src/dune_rules/dep_rules.ml | 6 +- src/dune_rules/dir_contents.ml | 2 +- src/dune_rules/dune_load.ml | 27 ---- src/dune_rules/exe.ml | 32 ++++ src/dune_rules/exe.mli | 13 ++ src/dune_rules/exe_rules.ml | 22 ++- src/dune_rules/lib_rules.ml | 19 +-- 11 files changed, 254 insertions(+), 400 deletions(-) delete mode 100644 src/dune_rules/ctypes_rules.mli delete mode 100644 src/dune_rules/ctypes_stanzas.ml delete mode 100644 src/dune_rules/ctypes_stanzas.mli diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index e56de46c0b8..d1e7b7a3b10 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -49,12 +49,106 @@ module Ctypes = Dune_file.Ctypes https://github.com/mbacarella/mpg123/blob/077a72d922931eb46d4b4e5842b0426fa3c161b5/c/dune *) +module Stanza_util = struct + + let sprintf = Printf.sprintf + + let type_description_module ctypes = + ctypes.Ctypes.type_descriptions + + let type_description_library ctypes = + type_description_module ctypes + |> Module_name.to_string + |> String.lowercase + + let function_description_module ctypes = + ctypes.Ctypes.function_descriptions + + let function_description_library ctypes = + function_description_module ctypes + |> Module_name.to_string + |> String.lowercase + + let entry_module ctypes = + ctypes.Ctypes.generated_entry_point +(* + let entry_library ctypes = + entry_module ctypes |> Module_name.to_string |> String.lowercase + *) + + let cflags_sexp ctypes = + sprintf "%s__c_flags.sexp" ctypes.Ctypes.external_library_name + + let c_library_flags_sexp ctypes = + sprintf "%s__c_library_flags.sexp" ctypes.Ctypes.external_library_name + + let c_generated_types_module ctypes = + sprintf "%s__c_generated_types" ctypes.Ctypes.external_library_name + |> Module_name.of_string + + let c_generated_functions_module ctypes = + sprintf "%s__c_generated_functions" ctypes.Ctypes.external_library_name + |> Module_name.of_string + + let c_types_includer_module ctypes = + ctypes.Ctypes.generated_types + + let c_generated_types_cout_c ctypes = + sprintf "%s__c_cout_generated_types.c" ctypes.Ctypes.external_library_name + + let c_generated_types_cout_exe ctypes = + sprintf "%s__c_cout_generated_types.exe" ctypes.Ctypes.external_library_name + + let c_generated_functions_cout_c ctypes = + sprintf "%s__c_cout_generated_functions.c" ctypes.Ctypes.external_library_name + + let generated_modules ctypes = + List.map ~f:Module_name.to_string + [ c_generated_functions_module ctypes + ; c_generated_types_module ctypes + ; c_types_includer_module ctypes ] + (* + ; entry_module ctypes ] *) + + let generated_ml_and_c_files ctypes = + let ml_files = + generated_modules ctypes + |> List.map ~f:String.lowercase + |> List.map ~f:(fun m -> m ^ ".ml") + in + let c_files = + [ c_generated_functions_cout_c ctypes ] + in + ml_files @ c_files +end + +let osl_pos () = "", 0, 0, 0 + let sprintf = Printf.sprintf let ml_of_module_name mn = Module_name.to_string mn ^ ".ml" |> String.lowercase +let modules_of_list ~dir ~modules = + let name_map = + let build_dir = Path.build dir in + let modules = + List.map modules ~f:(fun name -> + let module_name = Module_name.of_string name in + let path = Path.relative build_dir (String.lowercase name ^ ".ml") in + let impl = Module.File.make Dialect.ocaml path in + let source = Module.Source.make ~impl module_name in + Module.of_source ~visibility:Visibility.Public + ~kind:Module.Kind.Impl source) + in + Module.Name_map.of_list_exn modules + in + Modules.exe_unwrapped name_map + (* + Modules.exe_wrapped ~src_dir:dir ~modules:name_map + *) + let write_c_types_includer_module ~sctx ~dir ~filename ~type_description_module ~c_generated_types_module = let path = Path.Build.relative dir filename in @@ -117,12 +211,11 @@ let write_discover_script ~filename ~sctx ~dir ~external_library_name ~cflags_se let gen_headers headers buf = let pr buf fmt = Printf.bprintf buf (fmt ^^ "\n") in - begin match headers with + begin match headers with | Ctypes.Headers.Include lst -> List.iter lst ~f:(fun h -> pr buf " print_endline \"#include <%s>\";" h) | Preamble s -> - (* XXX: escape s *) - pr buf " print_endline \"%s\";" s + pr buf " print_endline \"%S\";" s end let type_gen_gen ~headers ~type_description_module = @@ -253,7 +346,7 @@ let build_c_program ~sctx ~dir ~source_files ~scope ~cflags_sexp ~output () = in Super_context.add_rule sctx ~dir build -let cctx ?(libraries=[]) ~buildable ~dynlink ~loc ~obj_dir ~dir ~scope ~expander ~sctx = +let cctx_with_substitutions ?flags ?(libraries=[]) ~modules ~dir ~loc ~scope ~cctx = let compile_info = let dune_version = Scope.project scope |> Dune_project.dune_version in Lib.DB.resolve_user_written_deps_for_exes (Scope.libs scope) @@ -263,45 +356,51 @@ let cctx ?(libraries=[]) ~buildable ~dynlink ~loc ~obj_dir ~dir ~scope ~expander ~dune_version ~optional:false ~pps:[] in - Compilation_context.create - ~super_context:sctx ~scope ~expander - ~js_of_ocaml:None - ~dynlink - ~package:None - ~flags:(Super_context.ocaml_flags sctx ~dir buildable.Buildable.flags) + let modules = modules_of_list ~dir ~modules in + let module Cctx = Compilation_context in + Cctx.create + ~super_context:(Cctx.super_context cctx) + ~scope:(Cctx.scope cctx) + ~expander:(Cctx.expander cctx) + ~js_of_ocaml:(Cctx.js_of_ocaml cctx) + ~dynlink:(Cctx.dynlink cctx) + ~package:(Cctx.package cctx) + ~flags:(match flags with + | Some flags -> flags + | None -> Cctx.flags cctx) ~requires_compile:(Lib.Compile.direct_requires compile_info) ~requires_link:(Lib.Compile.requires_link compile_info) - ~obj_dir - ~opaque:Compilation_context.Inherit_from_settings + ~obj_dir:(Cctx.obj_dir cctx) + ~opaque:(Cctx.Explicit (Cctx.opaque cctx)) + ~modules () -let executable ?(modules=[]) ~buildable ~loc ~obj_dir ~dynlink ~dir ~sctx ~scope - ~expander ~program ~libraries () = - let build_dir = Path.build dir in +let executable ?flags ?libraries ?(modules=[]) ~scope ~loc ~dir ~cctx program = let cctx = - let modules = - let name_map = - List.map (program :: modules) ~f:(fun name -> - let module_name = Module_name.of_string name in - let path = Path.relative build_dir (name ^ ".ml") in - let impl = Module.File.make Dialect.ocaml path in - let source = Module.Source.make ~impl module_name in - Module.of_source ~visibility:Visibility.Public - ~kind:Module.Kind.Impl source) - |> Module.Name_map.of_list_exn - in - Modules.exe_wrapped ~src_dir:dir ~modules:name_map - in - cctx ~buildable ~dir ~loc ~obj_dir ~dynlink ~scope ~sctx ~expander - ~modules ~libraries () + cctx_with_substitutions ?flags ?libraries ~modules:(program :: modules) + ~loc ~scope ~dir ~cctx + in + let program = + let build_dir = Path.build dir in + Exe.Program.{ + name = program; + main_module_name = Module_name.of_string program; + loc = Loc.in_file (Path.relative build_dir program) + } in + Exe.build_and_link ~program ~linkages:[Exe.Linkage.native] + ~promote:None cctx + +let executable_with_shared_cctx ~dir ~shared_cctx ~dep_graphs program = let program = + let build_dir = Path.build dir in Exe.Program.{ name = program; main_module_name = Module_name.of_string program; loc = Loc.in_file (Path.relative build_dir program) } in - Exe.build_and_link ~program ~linkages:[Exe.Linkage.native] ~promote:None cctx + Exe.link_many ~programs:[program] ~linkages:[Exe.Linkage.native] + ~dep_graphs ~promote:None shared_cctx let write_osl_to_sexp_file ~sctx ~dir ~filename osl = let build = @@ -318,38 +417,39 @@ let write_osl_to_sexp_file ~sctx ~dir ~filename osl = in Super_context.add_rule ~loc:Loc.none sctx ~dir build -let gen_rules ~buildable ~dynlink ~loc ~obj_dir ~scope ~expander ~dir ~sctx = - let rule = rule ~sctx ~dir in - let executable = - executable ~buildable ~loc ~obj_dir ~dynlink ~dir ~sctx ~scope ~expander - in +let gen_rules ~cctx ~buildable ~loc ~scope ~dir ~sctx = let ctypes = match buildable.Buildable.ctypes with | Some ctypes -> ctypes | None -> assert false in let external_library_name = ctypes.Ctypes.external_library_name in - let type_description_module = Ctypes_stanzas.type_description_module ctypes in - let type_description_library = Ctypes_stanzas.type_description_library ctypes in - let function_description_module = Ctypes_stanzas.function_description_module ctypes in - let function_description_library = Ctypes_stanzas.function_description_library ctypes in + let discover_script = sprintf "%s__ctypes_discover" external_library_name in + let type_gen_script = sprintf "%s__type_gen" external_library_name in + let function_gen_script = sprintf "%s__function_gen" external_library_name in + let type_description_module = Stanza_util.type_description_module ctypes in + let function_description_module = Stanza_util.function_description_module ctypes in (* This includer module is simply some glue to instantiate the Types functor that the user provides in the type description module. *) - let c_types_includer_module = Ctypes_stanzas.c_types_includer_module ctypes in + let c_types_includer_module = Stanza_util.c_types_includer_module ctypes in + let c_generated_types_module = Stanza_util.c_generated_types_module ctypes in + let rule = rule ~sctx ~dir in + let executable = executable ~scope ~loc ~dir ~cctx in let () = write_c_types_includer_module ~sctx ~dir ~filename:(ml_of_module_name c_types_includer_module) - ~c_generated_types_module:(Ctypes_stanzas.c_generated_types_module ctypes) + ~c_generated_types_module ~type_description_module in - (* The output of this process is to generate two cflags and one c library flags file. - We can probe these flags by using the system pkg-config, if it's an external system - library. The user could also tell us what they are, if the library is vendored. + (* The output of this process is to generate a cflags sexp and a c library + flags sexp file. We can probe these flags by using the system pkg-config, + if it's an external system library. The user could also tell us what + they are, if the library is vendored. https://dune.readthedocs.io/en/stable/quick-start.html#defining-a-library-with-c-stubs-using-pkg-config *) - let c_library_flags_sexp = Ctypes_stanzas.c_library_flags_sexp ctypes in - let cflags_sexp = Ctypes_stanzas.cflags_sexp ctypes in + let c_library_flags_sexp = Stanza_util.c_library_flags_sexp ctypes in + let cflags_sexp = Stanza_util.cflags_sexp ctypes in let () = let open Ctypes.Build_flags_resolver in match ctypes.Ctypes.build_flags_resolver with @@ -358,21 +458,44 @@ let gen_rules ~buildable ~dynlink ~loc ~obj_dir ~scope ~expander ~dir ~sctx = write_osl_to_sexp_file ~sctx ~dir ~filename:c_library_flags_sexp c_library_flags | Pkg_config -> - let cflags_sexp = Ctypes_stanzas.cflags_sexp ctypes in - let discover_script = sprintf "%s__ctypes_discover" external_library_name in + let cflags_sexp = Stanza_util.cflags_sexp ctypes in write_discover_script ~sctx ~dir ~filename:(discover_script ^ ".ml") ~cflags_sexp ~c_library_flags_sexp ~external_library_name; - executable - ~program:discover_script - ~libraries:["dune.configurator"] - (); + executable ~libraries:["dune.configurator"] discover_script; rule ~targets:[cflags_sexp; c_library_flags_sexp] ~exe:(discover_script ^ ".exe") () in let headers = ctypes.Ctypes.headers in + let executable_with_shared_cctx = + let shared_cctx = + let flags = + (* ctypes stubgen emits ocaml code with warnings which can make + compilation impossible if you're in warnings-as-errors mode; + disable the warnings *) + Ocaml_flags.of_list ["-w"; "-27"; "-w"; "-9"] + in + cctx_with_substitutions + ~cctx ~dir ~loc ~scope ~flags + ~libraries:["ctypes"; "ctypes.foreign"; "ctypes.stubs"] + ~modules:[ function_gen_script + ; type_gen_script + ; Module_name.to_string type_description_module + ; Module_name.to_string function_description_module + ; Module_name.to_string c_types_includer_module + ; Module_name.to_string c_generated_types_module + ] + in + (* Process the build rules once, to avoid bombing out on duplicate rules + errors when building executables that share modules between them. *) + let dep_graphs = + Dep_rules.rules shared_cctx ~modules:(Compilation_context.modules shared_cctx) + in + let () = Module_compilation.build_all shared_cctx ~dep_graphs in + executable_with_shared_cctx ~dir ~shared_cctx ~dep_graphs + in (* Type_gen produces a .c file, taking your type description module above as an input. The .c file is compiled into an .exe. @@ -383,20 +506,16 @@ let gen_rules ~buildable ~dynlink ~loc ~obj_dir ~scope ~expander ~dir ~sctx = Note the similar function_gen process below depends on the ML-wrapped C data/types produced in this step. *) let () = - let type_gen_script = sprintf "%s__type_gen" external_library_name in let c_generated_types_cout_c = - Ctypes_stanzas.c_generated_types_cout_c ctypes + Stanza_util.c_generated_types_cout_c ctypes in let c_generated_types_cout_exe = - Ctypes_stanzas.c_generated_types_cout_exe ctypes + Stanza_util.c_generated_types_cout_exe ctypes in write_type_gen_script ~headers ~sctx ~dir ~filename:(type_gen_script ^ ".ml") ~type_description_module; - executable - ~program:type_gen_script - ~libraries:["ctypes.stubs"; "ctypes.foreign"; type_description_library] - (); + executable_with_shared_cctx type_gen_script; rule ~stdout_to:c_generated_types_cout_c ~exe:(type_gen_script ^ ".exe") @@ -407,8 +526,7 @@ let gen_rules ~buildable ~dynlink ~loc ~obj_dir ~scope ~expander ~dir ~sctx = ~output:c_generated_types_cout_exe (); rule - ~stdout_to:(Ctypes_stanzas.c_generated_types_module ctypes - |> ml_of_module_name) + ~stdout_to:(c_generated_types_module |> ml_of_module_name) ~exe:(c_generated_types_cout_exe) () in @@ -417,37 +535,35 @@ let gen_rules ~buildable ~dynlink ~loc ~obj_dir ~scope ~expander ~dir ~sctx = have to write by hand to wrap C code (if ctypes didn't exist!) *) let () = let stubs_prefix = external_library_name ^ "_stubs" in - let function_gen_script = sprintf "%s__function_gen" external_library_name in let c_generated_functions_cout_c = - Ctypes_stanzas.c_generated_functions_cout_c ctypes + Stanza_util.c_generated_functions_cout_c ctypes in write_function_gen_script ~headers ~sctx ~dir ~name:function_gen_script ~function_description_module ~concurrency:ctypes.Ctypes.concurrency; - executable - ~program:function_gen_script - ~libraries:["ctypes.stubs"; function_description_library] - (); + executable_with_shared_cctx function_gen_script; rule ~stdout_to:c_generated_functions_cout_c ~exe:(function_gen_script ^ ".exe") ~args:["c"; stubs_prefix] (); rule - ~stdout_to:(Ctypes_stanzas.c_generated_functions_module ctypes + ~stdout_to:(Stanza_util.c_generated_functions_module ctypes |> ml_of_module_name) ~exe:(function_gen_script ^ ".exe") ~args:["ml"; stubs_prefix] () in + (* (* The entry point module binds the instantiated Types and Functions functors to the entry point module name the user specified. *) let () = write_entry_point_module ~sctx ~dir - ~filename:(Ctypes_stanzas.entry_module ctypes |> ml_of_module_name) - ~function_description_module:(Ctypes_stanzas.function_description_module ctypes) - ~c_generated_functions_module:(Ctypes_stanzas.c_generated_functions_module ctypes) + ~filename:(Stanza_util.entry_module ctypes |> ml_of_module_name) + ~function_description_module:(Stanza_util.function_description_module ctypes) + ~c_generated_functions_module:(Stanza_util.c_generated_functions_module ctypes) ~c_types_includer_module in + *) () diff --git a/src/dune_rules/ctypes_rules.mli b/src/dune_rules/ctypes_rules.mli deleted file mode 100644 index f39e166dbc3..00000000000 --- a/src/dune_rules/ctypes_rules.mli +++ /dev/null @@ -1,12 +0,0 @@ -open! Stdune - -val gen_rules : - buildable:Dune_file.Buildable.t - -> dynlink:bool - -> loc:Loc.t - -> obj_dir:Path.Build.t Obj_dir.t - -> scope:Scope.t - -> expander:Expander.t - -> dir:Path.Build.t - -> sctx:Super_context.t - -> unit diff --git a/src/dune_rules/ctypes_stanzas.ml b/src/dune_rules/ctypes_stanzas.ml deleted file mode 100644 index f9637287213..00000000000 --- a/src/dune_rules/ctypes_stanzas.ml +++ /dev/null @@ -1,230 +0,0 @@ -open! Dune_engine -open! Stdune - -module Buildable = Dune_file.Buildable -module Library = Dune_file.Library -module Ctypes = Dune_file.Ctypes - -let osl_pos () = "", 0, 0, 0 ;; - -let library_stanza ?(flags=Ocaml_flags.Spec.standard) ?public_name ?(foreign_stubs=[]) - ?(c_library_flags=Ordered_set_lang.Unexpanded.standard) ~loc ~project ~sub_systems - ~dune_version ~name ~modules ~libraries ~wrapped () = - let open Dune_file in - let visibility = - match public_name with - | None -> Library.Private None - | Some _public_name -> - Library.Private None - (* XXX: can only do this if the base library is public as well *) - (* - let plib = - match - Public_lib.make ~allow_deprecated_names:false - lib.Library.project (loc, Lib_name.of_string public_name) - with - | Ok plib -> plib - | Error e -> - (* XXX: present this as a proper error *) - failwith (sprintf "user message: %s" (User_message.to_string e)) - in - Library.Public plib - *) - in - let buildable = - let libraries = - List.map libraries ~f:(fun library -> - Lib_dep.Direct (loc, Lib_name.of_string library)) - in - let modules = List.map modules ~f:Module_name.to_string in - { Buildable.loc - ; modules = Ordered_set_lang.of_atoms ~loc modules - ; modules_without_implementation = Ordered_set_lang.of_atoms ~loc [] - ; libraries - ; foreign_archives= [] - ; foreign_stubs - ; preprocess = Preprocess.Per_module.default () - ; preprocessor_deps = [] - ; lint = Lint.no_lint - ; flags - ; js_of_ocaml = Js_of_ocaml.default - ; allow_overlapping_dependencies = false - ; ctypes = None; - } - in - { Library.name = (loc, Lib_name.of_string name |> Lib_name.to_local_exn) - ; visibility - ; synopsis = None - ; install_c_headers = [] - ; ppx_runtime_libraries = [] - ; modes = Mode_conf.Set.of_list [Mode_conf.Native, Mode_conf.Kind.Inherited] - ; kind = Lib_kind.Normal - ; library_flags = Ordered_set_lang.Unexpanded.standard - ; c_library_flags - ; virtual_deps = [] - ; wrapped = Lib_info.Inherited.This (Wrapped.Simple wrapped) - ; optional = false - ; buildable - ; dynlink = Dynlink_supported.of_bool true - ; project - ; sub_systems - ; dune_version - ; virtual_modules = None - ; implements = None - ; default_implementation = None - ; private_modules = None - ; stdlib = None - ; special_builtin_support = None - ; enabled_if = Blang.true_ - ; instrumentation_backend = None } - -let sprintf = Printf.sprintf - -let type_description_module ctypes = - ctypes.Ctypes.type_descriptions - -let type_description_library ctypes = - type_description_module ctypes - |> Module_name.to_string - |> String.lowercase - -let type_description_library_public ctypes = - sprintf "%s.c_type_descriptions" ctypes.Ctypes.external_library_name - -let function_description_module ctypes = - ctypes.Ctypes.function_descriptions - -let function_description_library ctypes = - function_description_module ctypes - |> Module_name.to_string - |> String.lowercase - -let function_description_library_public ctypes = - sprintf "%s.c_function_descriptions" ctypes.Ctypes.external_library_name - -let entry_module ctypes = - ctypes.Ctypes.generated_entry_point - -let entry_library ctypes = - entry_module ctypes |> Module_name.to_string |> String.lowercase - -let entry_library_public ctypes = - sprintf "%s.c" ctypes.Ctypes.external_library_name - -let cflags_sexp ctypes = - sprintf "%s__c_flags.sexp" ctypes.Ctypes.external_library_name - -let c_library_flags_sexp ctypes = - sprintf "%s__c_library_flags.sexp" ctypes.Ctypes.external_library_name - -let c_generated_types_module ctypes = - sprintf "%s__c_generated_types" ctypes.Ctypes.external_library_name - |> Module_name.of_string - -let c_generated_functions_module ctypes = - sprintf "%s__c_generated_functions" ctypes.Ctypes.external_library_name - |> Module_name.of_string - -(* -let c_types_includer_module ctypes = - sprintf "%s__c_types" ctypes.Ctypes.external_library_name - |> Module_name.of_string -*) - -let c_types_includer_module ctypes = - ctypes.Ctypes.generated_types - -let c_generated_types_cout_c ctypes = - sprintf "%s__c_cout_generated_types.c" ctypes.Ctypes.external_library_name - -let c_generated_types_cout_exe ctypes = - sprintf "%s__c_cout_generated_types.exe" ctypes.Ctypes.external_library_name - -let c_generated_functions_cout_c ctypes = - sprintf "%s__c_cout_generated_functions.c" ctypes.Ctypes.external_library_name - -let c_generated_functions_cout_no_ext ctypes = - sprintf "%s__c_cout_generated_functions" ctypes.Ctypes.external_library_name - -(* Unlike for [executable] and [rule] generation which have neat convenience - functions for creating new ones, the machinery for creating new [library]s - does several passes to populate global data structures. - - Rather than attempting to teach each of those passes about ctypes, the - approach here is to simply do a quasi-lexical expansion of the base library - config stanza into several additional support library stanzas, right after - the dune config file parsing is completed. *) -let library_stanzas ~parsing_context ~project ~sub_systems ~dune_version buildable = - let ctypes = - match buildable.Buildable.ctypes with - | Some ctypes -> ctypes - | None -> assert false - in - let loc = buildable.Buildable.loc in - let library_stanza = library_stanza ~loc ~project ~sub_systems ~dune_version in - let type_descriptions = - library_stanza - ~name:(type_description_library ctypes) - ~public_name:(type_description_library_public ctypes) - ~modules:[type_description_module ctypes] - ~libraries:["ctypes"] - ~wrapped:true () - in - let function_descriptions = - let flags = - (* The ctypes library emits code with some warnings; disable them so we - don't break compilation when warnings-as-errors *) - Ocaml_flags.Spec.of_unexpanded_ordered_set_lang - (Ordered_set_lang.Unexpanded.standard_with_of_strings - ~pos:(osl_pos ()) ["-w"; "-27"; "-w"; "-9"]) - in - library_stanza - ~name:(function_description_library ctypes) - ~public_name:(function_description_library_public ctypes) - ~modules:[ c_generated_types_module ctypes - ; function_description_module ctypes - ; c_types_includer_module ctypes ] - ~flags - ~libraries:["ctypes"; (type_description_library ctypes)] - ~wrapped:false () - in - let combined_final = - let pos = osl_pos () in - let foreign_stub = - Foreign.Stubs.make ~loc ~language:Foreign_language.C - ~names:(Ordered_set_lang.of_atoms ~loc - [c_generated_functions_cout_no_ext ctypes]) - ~flags:(Ordered_set_lang.Unexpanded.include_single - ~context:parsing_context ~pos (cflags_sexp ctypes)) - in - library_stanza - ~name:(entry_library ctypes) - ~public_name:(entry_library_public ctypes) - ~libraries:["ctypes"; function_description_library ctypes] - ~modules:[ entry_module ctypes - ; c_generated_functions_module ctypes ] - ~foreign_stubs:[foreign_stub] - ~c_library_flags:(Ordered_set_lang.Unexpanded.include_single - ~context:parsing_context ~pos - (c_library_flags_sexp ctypes)) - ~wrapped:true - () - in - [ type_descriptions - ; function_descriptions - ; combined_final ] - -let generated_ml_and_c_files ctypes = - let ml_files = - List.map [ c_generated_functions_module ctypes - ; c_generated_types_module ctypes - ; c_types_includer_module ctypes - ; entry_module ctypes ] - ~f:Module_name.to_string - |> List.map ~f:String.lowercase - |> List.map ~f:(fun m -> m ^ ".ml") - in - let c_files = - [ c_generated_functions_cout_c ctypes ] - in - ml_files @ c_files diff --git a/src/dune_rules/ctypes_stanzas.mli b/src/dune_rules/ctypes_stanzas.mli deleted file mode 100644 index cb84c9f2bd1..00000000000 --- a/src/dune_rules/ctypes_stanzas.mli +++ /dev/null @@ -1,31 +0,0 @@ -(* Expand a library with a ctypes stanza into several support libraries. *) -open Dune_file - -val type_description_module : Ctypes.t -> Module_name.t -val type_description_library : Ctypes.t -> string - -val function_description_module : Ctypes.t -> Module_name.t -val function_description_library : Ctypes.t -> string - -val cflags_sexp : Ctypes.t -> string -val c_library_flags_sexp : Ctypes.t -> string -val c_generated_types_module : Ctypes.t -> Module_name.t -val c_generated_functions_module : Ctypes.t -> Module_name.t -val entry_module : Ctypes.t -> Module_name.t - -val c_types_includer_module : Ctypes.t -> Module_name.t - -val c_generated_types_cout_c : Ctypes.t -> string -val c_generated_types_cout_exe : Ctypes.t -> string - -val c_generated_functions_cout_c : Ctypes.t -> string - -val library_stanzas : - parsing_context:Stdune.Univ_map.t - -> project:Dune_engine.Dune_project.t - -> sub_systems:Sub_system_info.t Sub_system_name.Map.t - -> dune_version:Dune_lang.Syntax.Version.t - -> Buildable.t - -> Library.t list - -val generated_ml_and_c_files : Ctypes.t -> string list diff --git a/src/dune_rules/dep_rules.ml b/src/dune_rules/dep_rules.ml index 6923a48f774..d8caace3474 100644 --- a/src/dune_rules/dep_rules.ml +++ b/src/dune_rules/dep_rules.ml @@ -50,7 +50,8 @@ let deps_of_module cctx ~ml_kind m = | None -> Modules.compat_for_exn modules m in Build.return (List.singleton interface_module) - | _ -> Ocamldep.deps_of ~cctx ~ml_kind m + | _ -> + Ocamldep.deps_of ~cctx ~ml_kind m let deps_of_vlib_module cctx ~ml_kind m = let vimpl = Option.value_exn (Compilation_context.vimpl cctx) in @@ -89,8 +90,9 @@ let rec deps_of cctx ~ml_kind (m : Modules.Sourced_module.t) = let skip_if_source_absent f m = if Module.has m ~ml_kind then f m - else + else begin Build.return [] + end in match m with | Imported_from_vlib m -> diff --git a/src/dune_rules/dir_contents.ml b/src/dune_rules/dir_contents.ml index 8ce68c20bfb..671ba78b3eb 100644 --- a/src/dune_rules/dir_contents.ml +++ b/src/dune_rules/dir_contents.ml @@ -162,7 +162,7 @@ end = struct | Executables { buildable; _ } | Library { buildable; _ } -> let ctypes_generated_ml_and_c_files = match buildable.ctypes with - | Some ctypes -> Ctypes_stanzas.generated_ml_and_c_files ctypes + | Some ctypes -> Ctypes_rules.Stanza_util.generated_ml_and_c_files ctypes | None -> [] in ctypes_generated_ml_and_c_files @ buildable_select_deps buildable diff --git a/src/dune_rules/dune_load.ml b/src/dune_rules/dune_load.ml index ddcda97e983..cb07ca2b433 100644 --- a/src/dune_rules/dune_load.ml +++ b/src/dune_rules/dune_load.ml @@ -11,33 +11,6 @@ module Dune_file = struct let parse sexps ~dir ~file ~project = let stanzas = Dune_file.Stanzas.parse ~file project sexps in - let stanzas = - let maybe_expand_ctypes ~dune_version ~sub_systems stanza buildable = - match buildable.Dune_file.Buildable.ctypes with - | None -> [stanza] - | Some _ctypes -> - let libs = - Ctypes_stanzas.library_stanzas - ~parsing_context:(Dune_project.parsing_context project) - ~project ~dune_version ~sub_systems - buildable - in - stanza :: (List.map libs ~f:(fun l -> Dune_file.Library l)) - in - List.concat_map stanzas ~f:(fun stanza -> - match stanza with - | Dune_file.Executables exes -> - maybe_expand_ctypes - ~sub_systems:exes.Dune_file.Executables.sub_systems - ~dune_version:exes.Dune_file.Executables.dune_version - stanza exes.Dune_file.Executables.buildable - | Dune_file.Library lib -> - maybe_expand_ctypes - ~sub_systems:lib.Dune_file.Library.sub_systems - ~dune_version:lib.Dune_file.Library.dune_version - stanza lib.Dune_file.Library.buildable - | _ -> [stanza]) - in let stanzas = if !Clflags.ignore_promoted_rules then List.filter stanzas ~f:(function diff --git a/src/dune_rules/exe.ml b/src/dune_rules/exe.ml index 934c39a5ee2..41645f18a6b 100644 --- a/src/dune_rules/exe.ml +++ b/src/dune_rules/exe.ml @@ -237,5 +237,37 @@ let build_and_link_many ~programs ~linkages ~promote ?link_args ?o_files let build_and_link ~program = build_and_link_many ~programs:[ program ] +let link_many ?link_args ?o_files ?(embed_in_plugin_libraries=[]) ~dep_graphs + ~programs ~linkages ~promote cctx = + let dep_graphs : Dep_graph.t Ml_kind.Dict.t = dep_graphs in + let modules = Compilation_context.modules cctx in + let link_time_code_gen = Link_time_code_gen.handle_special_libs cctx in + List.iter programs ~f:(fun { Program.name; main_module_name; loc } -> + let cm_files = + let sctx = CC.super_context cctx in + let ctx = SC.context sctx in + let obj_dir = CC.obj_dir cctx in + let top_sorted_modules = + let main = Option.value_exn (Modules.find modules main_module_name) in + Dep_graph.top_closed_implementations dep_graphs.impl [ main ] + in + Cm_files.make ~obj_dir ~modules ~top_sorted_modules + ~ext_obj:ctx.lib_config.ext_obj + in + List.iter linkages ~f:(fun linkage -> + if linkage = Linkage.js then + link_js ~name ~cm_files ~promote cctx + else + let link_time_code_gen = + if Linkage.is_plugin linkage then + Link_time_code_gen.handle_special_libs + (CC.for_plugin_executable cctx ~embed_in_plugin_libraries) + else + link_time_code_gen + in + link_exe cctx ~loc ~name ~linkage ~cm_files ~link_time_code_gen + ~promote ?link_args ?o_files)) + + let exe_path cctx ~(program : Program.t) ~linkage = exe_path_from_name cctx ~name:program.name ~linkage diff --git a/src/dune_rules/exe.mli b/src/dune_rules/exe.mli index 7df500d2a60..936e6c137ff 100644 --- a/src/dune_rules/exe.mli +++ b/src/dune_rules/exe.mli @@ -57,6 +57,19 @@ val build_and_link_many : -> Compilation_context.t -> unit +(* [link_many] is like [build_and_link_many], but it allows you to share + modules between executables without requiring an intermediate library. *) +val link_many : + ?link_args:Command.Args.static Command.Args.t Build.t + -> ?o_files:Path.t list + -> ?embed_in_plugin_libraries:(Loc.t * Lib_name.t) list + -> dep_graphs:Dep_graph.t Ml_kind.Dict.t + -> programs:Program.t list + -> linkages:Linkage.t list + -> promote:Rule.Promote.t option + -> Compilation_context.t + -> unit + val exe_path : Compilation_context.t -> program:Program.t diff --git a/src/dune_rules/exe_rules.ml b/src/dune_rules/exe_rules.ml index d408f88d796..0dbe598412e 100644 --- a/src/dune_rules/exe_rules.ml +++ b/src/dune_rules/exe_rules.ml @@ -180,6 +180,16 @@ let executables_rules ~sctx ~dir ~expander ~dir_contents ~scope ~compile_info Exe.build_and_link_many cctx ~programs ~linkages ~link_args ~o_files ~promote:exes.promote ~embed_in_plugin_libraries in + let () = + let buildable = exes.Executables.buildable in + Option.iter buildable.Buildable.ctypes ~f:(fun _ctypes -> + let loc = + match exes.Executables.names with + | hd :: _ -> fst hd + | [] -> assert false + in + Ctypes_rules.gen_rules ~cctx ~buildable ~loc ~sctx ~scope ~dir) + in ( cctx , Merlin.make () ~requires:requires_compile ~flags ~modules ~preprocess:(Preprocess.Per_module.single_preprocess preprocess) @@ -201,18 +211,6 @@ let compile_info ~scope (exes : Dune_file.Executables.t) = let rules ~sctx ~dir ~dir_contents ~scope ~expander (exes : Dune_file.Executables.t) = let compile_info = compile_info ~scope exes in - let () = - let buildable = exes.Executables.buildable in - Option.iter buildable.Buildable.ctypes ~f:(fun _ctypes -> - let loc = - match exes.Executables.names with - | hd :: _ -> fst hd - | [] -> assert false - in - let obj_dir = Executables.obj_dir ~dir exes in - Ctypes_rules.gen_rules ~buildable ~dynlink:false ~loc ~obj_dir ~sctx - ~scope ~expander ~dir) - in let f () = executables_rules exes ~sctx ~dir ~dir_contents ~scope ~expander ~compile_info ~embed_in_plugin_libraries:exes.embed_in_plugin_libraries diff --git a/src/dune_rules/lib_rules.ml b/src/dune_rules/lib_rules.ml index 65261fdb7e8..7839faf12c4 100644 --- a/src/dune_rules/lib_rules.ml +++ b/src/dune_rules/lib_rules.ml @@ -430,19 +430,6 @@ let rules (lib : Library.t) ~sctx ~dir_contents ~dir ~expander ~scope : Lib.DB.get_compile_info (Scope.libs scope) (Library.best_name lib) ~allow_overlaps:lib.buildable.allow_overlapping_dependencies in - let () = - let buildable = lib.Library.buildable in - Option.iter buildable.Buildable.ctypes ~f:(fun _ctypes -> - let loc, _name = lib.Library.name in - let dynlink = - let ctx = Super_context.context sctx in - Dynlink_supported.get lib.Library.dynlink - ctx.Context.supports_shared_libraries - in - let obj_dir = Library.obj_dir ~dir lib in - Ctypes_rules.gen_rules ~buildable ~dynlink ~loc ~obj_dir ~sctx ~scope - ~expander ~dir) - in let f () = let source_modules = Dir_contents.ocaml dir_contents @@ -451,6 +438,12 @@ let rules (lib : Library.t) ~sctx ~dir_contents ~dir ~expander ~scope : let cctx = cctx lib ~sctx ~source_modules ~dir ~scope ~expander ~compile_info in + let () = + let buildable = lib.Library.buildable in + Option.iter buildable.Buildable.ctypes ~f:(fun _ctypes -> + let loc, _name = lib.Library.name in + Ctypes_rules.gen_rules ~cctx ~buildable ~loc ~sctx ~scope ~dir) + in library_rules lib ~cctx ~source_modules ~dir_contents ~compile_info in Buildable_rules.gen_select_rules sctx compile_info ~dir; From 9d4662d77396f88c491b3bb018c3828b79d7b1ca Mon Sep 17 00:00:00 2001 From: Jeremie Dimino Date: Mon, 8 Mar 2021 17:31:02 +0000 Subject: [PATCH 22/69] Add a test showing that Dune always pulls unused ml files Signed-off-by: Jeremie Dimino --- ...pull-all-ml-files-for-transitive-closure.t | 35 +++++++++++++++++++ 1 file changed, 35 insertions(+) create mode 100644 test/blackbox-tests/test-cases/dont-pull-all-ml-files-for-transitive-closure.t diff --git a/test/blackbox-tests/test-cases/dont-pull-all-ml-files-for-transitive-closure.t b/test/blackbox-tests/test-cases/dont-pull-all-ml-files-for-transitive-closure.t new file mode 100644 index 00000000000..e4270fa1b7c --- /dev/null +++ b/test/blackbox-tests/test-cases/dont-pull-all-ml-files-for-transitive-closure.t @@ -0,0 +1,35 @@ +This test checks that when an executable doesn't depend on an .ml +file, Dune won't even look at the .ml file. This is important for: + +- executables stanzas with multiple executables. If we build only one +of the executables, Dune shouldn't care if .ml files not pulled by +this exe don't parse + +- for the upcoming ctypes rules where we build several intermediate +executables out of the same compilation context + + $ echo '(lang dune 2.8)' > dune-project + $ cat >dune< (executables (names x y)) + > EOF + $ cat >x.ml< print_endline "Hello, world!" + > EOF + $ cat >y.ml< (* unclosed comment + > EOF + $ cp y.ml z.ml + +At the moment, this doesn't work; dune still try to parse ml files +that are not used: + + $ dune exec ./x.exe + File "y.ml", line 1, characters 0-2: + 1 | (* unclosed comment + ^^ + Error: Comment not terminated + File "z.ml", line 1, characters 0-2: + 1 | (* unclosed comment + ^^ + Error: Comment not terminated + [1] From 7bd71b90114a6430dd05524b7551287ef5f99556 Mon Sep 17 00:00:00 2001 From: Jeremie Dimino Date: Mon, 8 Mar 2021 17:46:38 +0000 Subject: [PATCH 23/69] Narrow dependencies on .ml files for executables Signed-off-by: Jeremie Dimino --- CHANGES.md | 3 ++ src/dune_rules/dep_graph.ml | 28 +++++++++++++------ src/dune_rules/module.ml | 4 --- src/dune_rules/module.mli | 3 -- ...pull-all-ml-files-for-transitive-closure.t | 10 +------ .../test-cases/jsoo/simple.t/run.t | 6 ++-- .../test-cases/reporting-of-cycles.t/run.t | 4 +-- 7 files changed, 29 insertions(+), 29 deletions(-) diff --git a/CHANGES.md b/CHANGES.md index 7225a9ff457..c6e1c1ecf9a 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -89,6 +89,9 @@ Unreleased - It is now possible to define action dependencies through a chain of aliases. (#4303, @aalekseyev) +- If an .ml file is not used by an executable, Dune no longer report + parsing error in this file (#...., @jeremiedimino) + 2.8.2 (21/01/2021) ------------------ diff --git a/src/dune_rules/dep_graph.ml b/src/dune_rules/dep_graph.ml index aa1e73712d7..5f0f2e71157 100644 --- a/src/dune_rules/dep_graph.ml +++ b/src/dune_rules/dep_graph.ml @@ -21,16 +21,28 @@ let deps_of t (m : Module.t) = ; ("m", Module.to_dyn m) ] +module Top_closure = struct + module Action_builder = struct + include Action_builder + + let ( >>= ) t f = Action_builder.Expert.action_builder (map t ~f) + + module O = struct + include O + + let ( let* ) = ( >>= ) + end + end + + include Top_closure.Make (Module_name.Unique.Set) (Action_builder) +end + let top_closed t modules = - let+ per_module = - Module.Obj_map.to_list t.per_module - |> List.map ~f:(fun (unit, deps) -> - let+ deps = deps in - (unit, deps)) - |> Action_builder.all + let+ res = + Top_closure.top_closure modules ~key:Module.obj_name + ~deps:(Module.Obj_map.find_exn t.per_module) in - let per_module = Module.Obj_map.of_list_exn per_module in - match Module.Obj_map.top_closure per_module modules with + match res with | Ok modules -> modules | Error cycle -> User_error.raise diff --git a/src/dune_rules/module.ml b/src/dune_rules/module.ml index 37ddb7b1039..4c87401cee6 100644 --- a/src/dune_rules/module.ml +++ b/src/dune_rules/module.ml @@ -249,10 +249,6 @@ module Obj_map = struct let to_dyn = to_dyn end) - - let top_closure = - let module T = Top_closure.Make (Module_name.Unique.Set) (Monad.Id) in - fun t -> T.top_closure ~key:obj_name ~deps:(find_exn t) end let encode diff --git a/src/dune_rules/module.mli b/src/dune_rules/module.mli index bb724a234f8..789c99e18e0 100644 --- a/src/dune_rules/module.mli +++ b/src/dune_rules/module.mli @@ -103,9 +103,6 @@ module Obj_map : sig include Map.S with type key = module_ val find_exn : 'a t -> module_ -> 'a - - val top_closure : - module_ list t -> module_ list -> (module_ list, module_ list) Result.result end with type module_ := t diff --git a/test/blackbox-tests/test-cases/dont-pull-all-ml-files-for-transitive-closure.t b/test/blackbox-tests/test-cases/dont-pull-all-ml-files-for-transitive-closure.t index e4270fa1b7c..f3379d38e67 100644 --- a/test/blackbox-tests/test-cases/dont-pull-all-ml-files-for-transitive-closure.t +++ b/test/blackbox-tests/test-cases/dont-pull-all-ml-files-for-transitive-closure.t @@ -24,12 +24,4 @@ At the moment, this doesn't work; dune still try to parse ml files that are not used: $ dune exec ./x.exe - File "y.ml", line 1, characters 0-2: - 1 | (* unclosed comment - ^^ - Error: Comment not terminated - File "z.ml", line 1, characters 0-2: - 1 | (* unclosed comment - ^^ - Error: Comment not terminated - [1] + Hello, world! diff --git a/test/blackbox-tests/test-cases/jsoo/simple.t/run.t b/test/blackbox-tests/test-cases/jsoo/simple.t/run.t index 4e2c0d014eb..507023eafc9 100644 --- a/test/blackbox-tests/test-cases/jsoo/simple.t/run.t +++ b/test/blackbox-tests/test-cases/jsoo/simple.t/run.t @@ -4,17 +4,17 @@ Compilation using jsoo > sed s,^\ *$(ocamlc -config-var c_compiler),\ \ C_COMPILER,g js_of_ocaml bin/technologic.bc.runtime.js ocamldep bin/.technologic.eobjs/technologic.ml.d - ocamldep bin/.technologic.eobjs/z.ml.d js_of_ocaml .js/stdlib/std_exit.cmo.js C_COMPILER lib/stubs.o ocamldep lib/.x.objs/x.ml.d ocamlc lib/.x.objs/byte/x__.{cmi,cmo,cmt} ocamldep lib/.x.objs/y.ml.d - js_of_ocaml .js/js_of_ocaml/js_of_ocaml.cma.js - js_of_ocaml .js/stdlib/stdlib.cma.js + ocamldep bin/.technologic.eobjs/z.ml.d ocamlmklib lib/dllx_stubs.so,lib/libx_stubs.a ocamlopt lib/.x.objs/native/x__.{cmx,o} ocamlc lib/.x.objs/byte/x__Y.{cmi,cmo,cmt} + js_of_ocaml .js/js_of_ocaml/js_of_ocaml.cma.js + js_of_ocaml .js/stdlib/stdlib.cma.js ocamlopt lib/.x.objs/native/x__Y.{cmx,o} ocamlc lib/.x.objs/byte/x.{cmi,cmo,cmt} ocamlopt lib/.x.objs/native/x.{cmx,o} diff --git a/test/blackbox-tests/test-cases/reporting-of-cycles.t/run.t b/test/blackbox-tests/test-cases/reporting-of-cycles.t/run.t index dffb0a581d8..4a5b3a6b6e3 100644 --- a/test/blackbox-tests/test-cases/reporting-of-cycles.t/run.t +++ b/test/blackbox-tests/test-cases/reporting-of-cycles.t/run.t @@ -58,8 +58,8 @@ cryptic and can involve unrelated files: $ echo 'val xx : B.t' >> indirect/c.mli $ dune build @indirect-deps Error: Dependency cycle between the following files: - _build/default/indirect/.a.eobjs/b.impl.all-deps + _build/default/indirect/.a.eobjs/a.impl.all-deps + -> _build/default/indirect/.a.eobjs/b.impl.all-deps -> _build/default/indirect/.a.eobjs/c.intf.all-deps -> _build/default/indirect/.a.eobjs/a.impl.all-deps - -> _build/default/indirect/.a.eobjs/b.impl.all-deps [1] From 365505e6d5905255f13420c4eb74858448ac2af9 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Tue, 9 Mar 2021 10:44:17 -0800 Subject: [PATCH 24/69] (executables ... (ctypes ...)) almost works --- src/dune_rules/ctypes_rules.ml | 175 ++++++++++++-------------------- src/dune_rules/ctypes_rules.mli | 14 +++ src/dune_rules/dir_contents.ml | 2 +- src/dune_rules/exe.ml | 93 +++++++---------- src/dune_rules/exe.mli | 28 ++--- src/dune_rules/exe_rules.ml | 36 ++++--- src/dune_rules/lib_rules.ml | 6 +- src/dune_rules/modules.ml | 18 ++-- 8 files changed, 173 insertions(+), 199 deletions(-) create mode 100644 src/dune_rules/ctypes_rules.mli diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index d074515c462..5b2c1b1796d 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -5,11 +5,13 @@ module Buildable = Dune_file.Buildable module Library = Dune_file.Library module Ctypes = Dune_file.Ctypes -(* This module expands a [(library ... (ctypes ...))] rule into the set of - [library], [executable], [rule] rules and .ml files needed to more - conveniently build OCaml bindings for C libraries. Aside from perhaps - providing an '#include "header.h"' line, you should be able to wrap an - entire C library without writing a single line of C code. +(* This module expands either a (library ... (ctypes_stubgen ...)) rule + or an (executables ... (ctypes_stubgen ...)) rule into the generated + set of .ml files needed to conveniently build OCaml bindings for C + libraries. + + Aside from perhaps providing an '#include "header.h"' line, you should be + able to wrap an entire C library without writing a single line of C code. This stanza requires the user to define (and specify) two modules: @@ -53,28 +55,23 @@ module Stanza_util = struct let sprintf = Printf.sprintf + let discover_script ctypes = + sprintf "%s__ctypes_discover" ctypes.Ctypes.external_library_name + + let type_gen_script ctypes = + sprintf "%s__type_gen" ctypes.Ctypes.external_library_name + + let function_gen_script ctypes = + sprintf "%s__function_gen" ctypes.Ctypes.external_library_name + let type_description_module ctypes = ctypes.Ctypes.type_descriptions - let type_description_library ctypes = - type_description_module ctypes - |> Module_name.to_string - |> String.lowercase - let function_description_module ctypes = ctypes.Ctypes.function_descriptions - let function_description_library ctypes = - function_description_module ctypes - |> Module_name.to_string - |> String.lowercase - let entry_module ctypes = ctypes.Ctypes.generated_entry_point -(* - let entry_library ctypes = - entry_module ctypes |> Module_name.to_string |> String.lowercase - *) let cflags_sexp ctypes = sprintf "%s__c_flags.sexp" ctypes.Ctypes.external_library_name @@ -90,6 +87,8 @@ module Stanza_util = struct sprintf "%s__c_generated_functions" ctypes.Ctypes.external_library_name |> Module_name.of_string + (* This includer module is simply some glue to instantiate the Types functor + that the user provides in the type description module. *) let c_types_includer_module ctypes = ctypes.Ctypes.generated_types @@ -102,17 +101,21 @@ module Stanza_util = struct let c_generated_functions_cout_c ctypes = sprintf "%s__c_cout_generated_functions.c" ctypes.Ctypes.external_library_name + let _libraries_needed_for_ctypes () = + ["ctypes"; "ctypes.foreign"; "ctypes.stubs"] + let generated_modules ctypes = - List.map ~f:Module_name.to_string - [ c_generated_functions_module ctypes - ; c_generated_types_module ctypes - ; c_types_includer_module ctypes ] - (* - ; entry_module ctypes ] *) + [ type_gen_script ctypes |> Module_name.of_string + ; function_gen_script ctypes |> Module_name.of_string + ; c_generated_functions_module ctypes + ; c_generated_types_module ctypes + ; c_types_includer_module ctypes + ; entry_module ctypes ] let generated_ml_and_c_files ctypes = let ml_files = generated_modules ctypes + |> List.map ~f:Module_name.to_string |> List.map ~f:String.lowercase |> List.map ~f:(fun m -> m ^ ".ml") in @@ -122,9 +125,7 @@ module Stanza_util = struct ml_files @ c_files end -let osl_pos () = "", 0, 0, 0 - -let sprintf = Printf.sprintf +let generated_ml_and_c_files = Stanza_util.generated_ml_and_c_files let ml_of_module_name mn = Module_name.to_string mn ^ ".ml" @@ -145,9 +146,7 @@ let modules_of_list ~dir ~modules = Module.Name_map.of_list_exn modules in Modules.exe_unwrapped name_map - (* - Modules.exe_wrapped ~src_dir:dir ~modules:name_map - *) + (* Modules.exe_wrapped ~src_dir:dir ~modules:name_map *) let write_c_types_includer_module ~sctx ~dir ~filename ~type_description_module ~c_generated_types_module = @@ -348,7 +347,8 @@ let build_c_program ~sctx ~dir ~source_files ~scope ~cflags_sexp ~output () = in Super_context.add_rule sctx ~dir build -let cctx_with_substitutions ?flags ?(libraries=[]) ~modules ~dir ~loc ~scope ~cctx = +let cctx_with_substitutions ?(libraries=[]) ~modules ~dir + ~loc ~scope ~cctx = let compile_info = let dune_version = Scope.project scope |> Dune_project.dune_version in Lib.DB.resolve_user_written_deps_for_exes (Scope.libs scope) @@ -365,40 +365,32 @@ let cctx_with_substitutions ?flags ?(libraries=[]) ~modules ~dir ~loc ~scope ~cc ~expander:(Cctx.expander cctx) ~js_of_ocaml:(Cctx.js_of_ocaml cctx) ~package:(Cctx.package cctx) - ~flags:(match flags with - | Some flags -> flags - | None -> Cctx.flags cctx) + ~flags:(Cctx.flags cctx) ~requires_compile:(Lib.Compile.direct_requires compile_info) ~requires_link:(Lib.Compile.requires_link compile_info) ~obj_dir:(Cctx.obj_dir cctx) ~opaque:(Cctx.Explicit (Cctx.opaque cctx)) ~modules () -let executable ?flags ?libraries ?(modules=[]) ~scope ~loc ~dir ~cctx program = +let program_of_module_and_dir ~dir program = + let build_dir = Path.build dir in + Exe.Program.{ + name = program; + main_module_name = Module_name.of_string program; + loc = Loc.in_file (Path.relative build_dir program) + } + +let exe_build_and_link ?libraries ?(modules=[]) ~scope ~loc ~dir ~cctx program = let cctx = - cctx_with_substitutions ?flags ?libraries ~modules:(program :: modules) - ~loc ~scope ~dir ~cctx - in - let program = - let build_dir = Path.build dir in - Exe.Program.{ - name = program; - main_module_name = Module_name.of_string program; - loc = Loc.in_file (Path.relative build_dir program) - } + cctx_with_substitutions ?libraries ~loc ~scope ~dir ~cctx + ~modules:(program :: modules) in + let program = program_of_module_and_dir ~dir program in Exe.build_and_link ~program ~linkages:[Exe.Linkage.native] ~promote:None cctx -let executable_with_shared_cctx ~dir ~shared_cctx ~dep_graphs program = - let program = - let build_dir = Path.build dir in - Exe.Program.{ - name = program; - main_module_name = Module_name.of_string program; - loc = Loc.in_file (Path.relative build_dir program) - } - in +let exe_link_only ~dir ~shared_cctx ~dep_graphs program = + let program = program_of_module_and_dir ~dir program in Exe.link_many ~programs:[program] ~linkages:[Exe.Linkage.native] ~dep_graphs ~promote:None shared_cctx @@ -417,24 +409,14 @@ let write_osl_to_sexp_file ~sctx ~dir ~filename osl = in Super_context.add_rule ~loc:Loc.none sctx ~dir build -let gen_rules ~cctx ~buildable ~loc ~scope ~dir ~sctx = - let ctypes = - match buildable.Buildable.ctypes with - | Some ctypes -> ctypes - | None -> assert false - in +let gen_rules ~dep_graphs ~cctx ~buildable ~loc ~scope ~dir ~sctx = + let ctypes = Option.value_exn buildable.Buildable.ctypes in let external_library_name = ctypes.Ctypes.external_library_name in - let discover_script = sprintf "%s__ctypes_discover" external_library_name in - let type_gen_script = sprintf "%s__type_gen" external_library_name in - let function_gen_script = sprintf "%s__function_gen" external_library_name in let type_description_module = Stanza_util.type_description_module ctypes in let function_description_module = Stanza_util.function_description_module ctypes in - (* This includer module is simply some glue to instantiate the Types functor - that the user provides in the type description module. *) let c_types_includer_module = Stanza_util.c_types_includer_module ctypes in let c_generated_types_module = Stanza_util.c_generated_types_module ctypes in let rule = rule ~sctx ~dir in - let executable = executable ~scope ~loc ~dir ~cctx in let () = write_c_types_includer_module ~sctx ~dir @@ -447,7 +429,8 @@ let gen_rules ~cctx ~buildable ~loc ~scope ~dir ~sctx = if it's an external system library. The user could also tell us what they are, if the library is vendored. - https://dune.readthedocs.io/en/stable/quick-start.html#defining-a-library-with-c-stubs-using-pkg-config *) + https://dune.readthedocs.io/en/stable/quick-start.html#defining-a-library-with-c-stubs-using-pkg-config + *) let c_library_flags_sexp = Stanza_util.c_library_flags_sexp ctypes in let cflags_sexp = Stanza_util.cflags_sexp ctypes in let () = @@ -459,43 +442,20 @@ let gen_rules ~cctx ~buildable ~loc ~scope ~dir ~sctx = c_library_flags | Pkg_config -> let cflags_sexp = Stanza_util.cflags_sexp ctypes in + let discover_script = Stanza_util.discover_script ctypes in write_discover_script ~sctx ~dir ~filename:(discover_script ^ ".ml") ~cflags_sexp ~c_library_flags_sexp ~external_library_name; - executable ~libraries:["dune.configurator"] discover_script; + exe_build_and_link ~scope ~loc ~dir ~cctx ~libraries:["dune.configurator"] + discover_script; rule ~targets:[cflags_sexp; c_library_flags_sexp] ~exe:(discover_script ^ ".exe") () in + let generated_entry_module = Stanza_util.entry_module ctypes in let headers = ctypes.Ctypes.headers in - let executable_with_shared_cctx = - let shared_cctx = - let flags = - (* ctypes stubgen emits ocaml code with warnings which can make - compilation impossible if you're in warnings-as-errors mode; - disable the warnings *) - Ocaml_flags.of_list ["-w"; "-27"; "-w"; "-9"] - in - cctx_with_substitutions - ~cctx ~dir ~loc ~scope ~flags - ~libraries:["ctypes"; "ctypes.foreign"; "ctypes.stubs"] - ~modules:[ function_gen_script - ; type_gen_script - ; Module_name.to_string type_description_module - ; Module_name.to_string function_description_module - ; Module_name.to_string c_types_includer_module - ; Module_name.to_string c_generated_types_module - ] - in - (* Process the build rules once, to avoid bombing out on duplicate rules - errors when building executables that share modules between them. *) - let dep_graphs = - Dep_rules.rules shared_cctx ~modules:(Compilation_context.modules shared_cctx) - in - let () = Module_compilation.build_all shared_cctx ~dep_graphs in - executable_with_shared_cctx ~dir ~shared_cctx ~dep_graphs - in + let exe_link_only = exe_link_only ~dir ~shared_cctx:cctx ~dep_graphs in (* Type_gen produces a .c file, taking your type description module above as an input. The .c file is compiled into an .exe. @@ -512,10 +472,11 @@ let gen_rules ~cctx ~buildable ~loc ~scope ~dir ~sctx = let c_generated_types_cout_exe = Stanza_util.c_generated_types_cout_exe ctypes in + let type_gen_script = Stanza_util.type_gen_script ctypes in write_type_gen_script ~headers ~sctx ~dir ~filename:(type_gen_script ^ ".ml") ~type_description_module; - executable_with_shared_cctx type_gen_script; + exe_link_only type_gen_script; rule ~stdout_to:c_generated_types_cout_c ~exe:(type_gen_script ^ ".exe") @@ -538,10 +499,11 @@ let gen_rules ~cctx ~buildable ~loc ~scope ~dir ~sctx = let c_generated_functions_cout_c = Stanza_util.c_generated_functions_cout_c ctypes in + let function_gen_script = Stanza_util.function_gen_script ctypes in write_function_gen_script ~headers ~sctx ~dir ~name:function_gen_script ~function_description_module ~concurrency:ctypes.Ctypes.concurrency; - executable_with_shared_cctx function_gen_script; + exe_link_only function_gen_script; rule ~stdout_to:c_generated_functions_cout_c ~exe:(function_gen_script ^ ".exe") @@ -554,16 +516,11 @@ let gen_rules ~cctx ~buildable ~loc ~scope ~dir ~sctx = ~args:["ml"; stubs_prefix] () in - (* (* The entry point module binds the instantiated Types and Functions functors to the entry point module name the user specified. *) - let () = - write_entry_point_module - ~sctx ~dir - ~filename:(Stanza_util.entry_module ctypes |> ml_of_module_name) - ~function_description_module:(Stanza_util.function_description_module ctypes) - ~c_generated_functions_module:(Stanza_util.c_generated_functions_module ctypes) - ~c_types_includer_module - in - *) - () + write_entry_point_module + ~sctx ~dir + ~filename:(generated_entry_module |> ml_of_module_name) + ~function_description_module:(Stanza_util.function_description_module ctypes) + ~c_generated_functions_module:(Stanza_util.c_generated_functions_module ctypes) + ~c_types_includer_module diff --git a/src/dune_rules/ctypes_rules.mli b/src/dune_rules/ctypes_rules.mli new file mode 100644 index 00000000000..eb4da68523b --- /dev/null +++ b/src/dune_rules/ctypes_rules.mli @@ -0,0 +1,14 @@ +open! Dune_engine +open Import + +val generated_ml_and_c_files : Dune_file.Ctypes.t -> string list + +val gen_rules : + dep_graphs : Dep_graph.t Ml_kind.Dict.t + -> cctx : Compilation_context.t + -> buildable : Dune_file.Buildable.t + -> loc : Loc.t + -> scope : Scope.t + -> dir : Path.Build.t + -> sctx : Super_context.t + -> unit diff --git a/src/dune_rules/dir_contents.ml b/src/dune_rules/dir_contents.ml index 3d3a28197c1..de767a3fdb5 100644 --- a/src/dune_rules/dir_contents.ml +++ b/src/dune_rules/dir_contents.ml @@ -162,7 +162,7 @@ end = struct @ (match buildable.ctypes with | None -> [] | Some ctypes -> - Ctypes_rules.Stanza_util.generated_ml_and_c_files ctypes) + Ctypes_rules.generated_ml_and_c_files ctypes) | _ -> []) |> String.Set.of_list in diff --git a/src/dune_rules/exe.ml b/src/dune_rules/exe.ml index f820cbb3286..be375516c6f 100644 --- a/src/dune_rules/exe.ml +++ b/src/dune_rules/exe.ml @@ -213,71 +213,54 @@ let link_js ~name ~cm_files ~promote cctx = Jsoo_rules.build_exe cctx ~js_of_ocaml ~src ~cm:top_sorted_cms ~flags:(Command.Args.dyn flags) ~promote -let build_and_link_many ~programs ~linkages ~promote ?link_args ?o_files - ?(embed_in_plugin_libraries = []) cctx = - let modules = Compilation_context.modules cctx in - let dep_graphs = Dep_rules.rules cctx ~modules in - Module_compilation.build_all cctx ~dep_graphs; - let link_time_code_gen = Link_time_code_gen.handle_special_libs cctx in - List.iter programs ~f:(fun { Program.name; main_module_name; loc } -> - let cm_files = - let sctx = CC.super_context cctx in - let ctx = SC.context sctx in - let obj_dir = CC.obj_dir cctx in - let top_sorted_modules = - let main = Option.value_exn (Modules.find modules main_module_name) in - Dep_graph.top_closed_implementations dep_graphs.impl [ main ] - in - Cm_files.make ~obj_dir ~modules ~top_sorted_modules - ~ext_obj:ctx.lib_config.ext_obj - in - List.iter linkages ~f:(fun linkage -> - if linkage = Linkage.js then - link_js ~name ~cm_files ~promote cctx - else - let link_time_code_gen = - if Linkage.is_plugin linkage then - Link_time_code_gen.handle_special_libs - (CC.for_plugin_executable cctx ~embed_in_plugin_libraries) - else - link_time_code_gen - in - link_exe cctx ~loc ~name ~linkage ~cm_files ~link_time_code_gen - ~promote ?link_args ?o_files)) - -let build_and_link ~program = build_and_link_many ~programs:[ program ] - let link_many ?link_args ?o_files ?(embed_in_plugin_libraries=[]) ~dep_graphs ~programs ~linkages ~promote cctx = let dep_graphs : Dep_graph.t Ml_kind.Dict.t = dep_graphs in let modules = Compilation_context.modules cctx in let link_time_code_gen = Link_time_code_gen.handle_special_libs cctx in List.iter programs ~f:(fun { Program.name; main_module_name; loc } -> - let cm_files = - let sctx = CC.super_context cctx in - let ctx = SC.context sctx in - let obj_dir = CC.obj_dir cctx in - let top_sorted_modules = - let main = Option.value_exn (Modules.find modules main_module_name) in + let cm_files = + let sctx = CC.super_context cctx in + let ctx = SC.context sctx in + let obj_dir = CC.obj_dir cctx in + let top_sorted_modules = + match Modules.find modules main_module_name with + | None -> + (* XXX: make this a nicer error *) + failwith (Printf.sprintf "module %s not found in compilation context" + (Module_name.to_string main_module_name)) + | Some main -> Dep_graph.top_closed_implementations dep_graphs.impl [ main ] - in - Cm_files.make ~obj_dir ~modules ~top_sorted_modules - ~ext_obj:ctx.lib_config.ext_obj in - List.iter linkages ~f:(fun linkage -> - if linkage = Linkage.js then - link_js ~name ~cm_files ~promote cctx + Cm_files.make ~obj_dir ~modules ~top_sorted_modules + ~ext_obj:ctx.lib_config.ext_obj + in + List.iter linkages ~f:(fun linkage -> + if linkage = Linkage.js then + link_js ~name ~cm_files ~promote cctx + else + let link_time_code_gen = + if Linkage.is_plugin linkage then + Link_time_code_gen.handle_special_libs + (CC.for_plugin_executable cctx ~embed_in_plugin_libraries) else - let link_time_code_gen = - if Linkage.is_plugin linkage then - Link_time_code_gen.handle_special_libs - (CC.for_plugin_executable cctx ~embed_in_plugin_libraries) - else - link_time_code_gen - in - link_exe cctx ~loc ~name ~linkage ~cm_files ~link_time_code_gen - ~promote ?link_args ?o_files)) + link_time_code_gen + in + link_exe cctx ~loc ~name ~linkage ~cm_files ~link_time_code_gen + ~promote ?link_args ?o_files)) + +let build_and_link_many ?link_args ?o_files ?(embed_in_plugin_libraries = []) + ~programs ~linkages ~promote cctx = + let modules = Compilation_context.modules cctx in + let dep_graphs = Dep_rules.rules cctx ~modules in + Module_compilation.build_all cctx ~dep_graphs; + link_many ?link_args ?o_files ~embed_in_plugin_libraries ~dep_graphs + ~programs ~linkages ~promote cctx +let build_and_link ?link_args ?o_files ?(embed_in_plugin_libraries = []) + ~program = + build_and_link_many ?link_args ?o_files ~embed_in_plugin_libraries + ~programs:[program] let exe_path cctx ~(program : Program.t) ~linkage = exe_path_from_name cctx ~name:program.name ~linkage diff --git a/src/dune_rules/exe.mli b/src/dune_rules/exe.mli index c4b1028f933..cd5694d8c99 100644 --- a/src/dune_rules/exe.mli +++ b/src/dune_rules/exe.mli @@ -39,33 +39,33 @@ end (** Build and link one or more executables *) -val build_and_link : - program:Program.t - -> linkages:Linkage.t list - -> promote:Rule.Promote.t option - -> ?link_args:Command.Args.static Command.Args.t Action_builder.t +(* [link_many] is like [build_and_link_many], but it allows you to share + modules between executables without requiring an intermediate library. *) +val link_many : + ?link_args:Command.Args.static Command.Args.t Action_builder.t -> ?o_files:Path.t list -> ?embed_in_plugin_libraries:(Loc.t * Lib_name.t) list + -> dep_graphs:Dep_graph.t Import.Ml_kind.Dict.t + -> programs:Program.t list + -> linkages:Linkage.t list + -> promote:Rule.Promote.t option -> Compilation_context.t -> unit -val build_and_link_many : - programs:Program.t list - -> linkages:Linkage.t list - -> promote:Rule.Promote.t option - -> ?link_args:Command.Args.static Command.Args.t Action_builder.t +val build_and_link : + ?link_args:Command.Args.static Command.Args.t Action_builder.t -> ?o_files:Path.t list -> ?embed_in_plugin_libraries:(Loc.t * Lib_name.t) list + -> program:Program.t + -> linkages:Linkage.t list + -> promote:Rule.Promote.t option -> Compilation_context.t -> unit -(* [link_many] is like [build_and_link_many], but it allows you to share - modules between executables without requiring an intermediate library. *) -val link_many : +val build_and_link_many : ?link_args:Command.Args.static Command.Args.t Action_builder.t -> ?o_files:Path.t list -> ?embed_in_plugin_libraries:(Loc.t * Lib_name.t) list - -> dep_graphs:Dep_graph.t Import.Ml_kind.Dict.t -> programs:Program.t list -> linkages:Linkage.t list -> promote:Rule.Promote.t option diff --git a/src/dune_rules/exe_rules.ml b/src/dune_rules/exe_rules.ml index 0425d657f06..ae037c9f76e 100644 --- a/src/dune_rules/exe_rules.ml +++ b/src/dune_rules/exe_rules.ml @@ -203,18 +203,30 @@ let executables_rules ~sctx ~dir ~expander ~dir_contents ~scope ~compile_info ~requires_compile in Check_rules.add_files sctx ~dir o_files; - Exe.build_and_link_many cctx ~programs ~linkages ~link_args ~o_files - ~promote:exes.promote ~embed_in_plugin_libraries - in - let () = - let buildable = exes.Executables.buildable in - Option.iter buildable.Buildable.ctypes ~f:(fun _ctypes -> - let loc = - match exes.Executables.names with - | hd :: _ -> fst hd - | [] -> assert false - in - Ctypes_rules.gen_rules ~cctx ~buildable ~loc ~sctx ~scope ~dir) + begin + let buildable = exes.Executables.buildable in + match buildable.Buildable.ctypes with + | None -> + Exe.build_and_link_many cctx ~programs ~linkages ~link_args ~o_files + ~promote:exes.promote ~embed_in_plugin_libraries + | Some _ctypes -> + (* Ctypes stubgen builds utility .exe files that need to share modules + with this compilation context. To support that, we extract the + one-time run bits from [Exe.build_and_link_many] and run them here, + then pass that to the [Exe.link_many] call here as well as the + Ctypes_rules. This dance is done to avoid triggering duplicate rule + exceptions. *) + let dep_graphs = + Dep_rules.rules cctx ~modules:(Compilation_context.modules cctx) + in + let () = + let loc = fst (List.hd exes.Executables.names) in + Ctypes_rules.gen_rules ~dep_graphs ~cctx ~buildable ~loc ~sctx ~scope ~dir + in + let () = Module_compilation.build_all cctx ~dep_graphs in + Exe.link_many ~programs ~dep_graphs ~linkages ~link_args ~o_files + ~promote:exes.promote ~embed_in_plugin_libraries cctx + end in ( cctx , Merlin.make ~requires:requires_compile ~stdlib_dir ~flags ~modules diff --git a/src/dune_rules/lib_rules.ml b/src/dune_rules/lib_rules.ml index afe8b52314a..a00ba825e5e 100644 --- a/src/dune_rules/lib_rules.ml +++ b/src/dune_rules/lib_rules.ml @@ -439,8 +439,10 @@ let rules (lib : Library.t) ~sctx ~dir_contents ~dir ~expander ~scope : let () = let buildable = lib.Library.buildable in Option.iter buildable.Buildable.ctypes ~f:(fun _ctypes -> - let loc, _name = lib.Library.name in - Ctypes_rules.gen_rules ~cctx ~buildable ~loc ~sctx ~scope ~dir) + let _loc, _name = lib.Library.name in + () + (*Ctypes_rules.gen_rules ~cctx ~buildable ~loc ~sctx ~scope ~dir*) + ) in library_rules lib ~cctx ~source_modules ~dir_contents ~compile_info in diff --git a/src/dune_rules/modules.ml b/src/dune_rules/modules.ml index 023b616470e..e0159b6a692 100644 --- a/src/dune_rules/modules.ml +++ b/src/dune_rules/modules.ml @@ -110,7 +110,8 @@ module Stdlib = struct Module_name.Map.values t.modules |> List.filter ~f:(fun m -> Some (Module.name m) <> t.exit_module) - let find t = Module_name.Map.find t.modules + let find t module_name = + Module_name.Map.find t.modules module_name let find_dep t ~of_ name = let of_name = Module.name of_ in @@ -528,11 +529,16 @@ let impl impl ~vlib = let rec find t name = match t with - | Singleton m -> Option.some_if (Module.name m = name) m - | Unwrapped m -> Module_name.Map.find m name - | Stdlib w -> Stdlib.find w name - | Wrapped w -> Wrapped.find w name - | Impl { impl; vlib } -> ( + | Singleton m -> + Option.some_if (Module.name m = name) m + | Unwrapped m -> + Module_name.Map.find m name + | Stdlib w -> + Stdlib.find w name + | Wrapped w -> + Wrapped.find w name + | Impl { impl; vlib } -> + ( match find impl name with | Some _ as m -> m | None -> find vlib name) From 8a9c92111a90266c77569b5e01a625bf2c55242c Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Wed, 10 Mar 2021 15:57:10 -0800 Subject: [PATCH 25/69] dont need the ctypes.foreign library --- src/dune_rules/ctypes_rules.ml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index 5b2c1b1796d..134b6ed3f6a 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -102,7 +102,7 @@ module Stanza_util = struct sprintf "%s__c_cout_generated_functions.c" ctypes.Ctypes.external_library_name let _libraries_needed_for_ctypes () = - ["ctypes"; "ctypes.foreign"; "ctypes.stubs"] + ["ctypes"; "ctypes.stubs"] let generated_modules ctypes = [ type_gen_script ctypes |> Module_name.of_string From 827ec0626d06d9e355a5bb98c0b47ddc0266021f Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Thu, 11 Mar 2021 07:32:01 -0800 Subject: [PATCH 26/69] pull ctypes stubs into Buildable.foreign_stubs --- src/dune_rules/ctypes_rules.ml | 3 ++- src/dune_rules/ctypes_rules.mli | 4 +++- src/dune_rules/ctypes_stubs.ml | 19 +++++++++++++++++++ src/dune_rules/ctypes_stubs.mli | 22 ++++++++++++++++++++++ src/dune_rules/dune_file.ml | 10 ++++++++++ 5 files changed, 56 insertions(+), 2 deletions(-) create mode 100644 src/dune_rules/ctypes_stubs.ml create mode 100644 src/dune_rules/ctypes_stubs.mli diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index 134b6ed3f6a..7ac625c349a 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -74,7 +74,8 @@ module Stanza_util = struct ctypes.Ctypes.generated_entry_point let cflags_sexp ctypes = - sprintf "%s__c_flags.sexp" ctypes.Ctypes.external_library_name + Ctypes_stubs.cflags_sexp + ~external_library_name:ctypes.Ctypes.external_library_name let c_library_flags_sexp ctypes = sprintf "%s__c_library_flags.sexp" ctypes.Ctypes.external_library_name diff --git a/src/dune_rules/ctypes_rules.mli b/src/dune_rules/ctypes_rules.mli index eb4da68523b..c34ba77c2cc 100644 --- a/src/dune_rules/ctypes_rules.mli +++ b/src/dune_rules/ctypes_rules.mli @@ -1,7 +1,9 @@ open! Dune_engine open Import -val generated_ml_and_c_files : Dune_file.Ctypes.t -> string list +module Ctypes = Dune_file.Ctypes + +val generated_ml_and_c_files : Ctypes.t -> string list val gen_rules : dep_graphs : Dep_graph.t Ml_kind.Dict.t diff --git a/src/dune_rules/ctypes_stubs.ml b/src/dune_rules/ctypes_stubs.ml new file mode 100644 index 00000000000..6a037cf40a7 --- /dev/null +++ b/src/dune_rules/ctypes_stubs.ml @@ -0,0 +1,19 @@ +open! Dune_engine +open! Stdune + +let cflags_sexp ~external_library_name = + sprintf "%s__c_flags.sexp" external_library_name + +let c_generated_functions_cout_no_ext ~external_library_name = + sprintf "%s__c_cout_generated_functions" external_library_name + +let add ~loc ~parsing_context ~external_library_name ~add_stubs ~foreign_stubs = + add_stubs + Foreign_language.C + ~loc + ~names:(Some (Ordered_set_lang.of_atoms ~loc + [c_generated_functions_cout_no_ext ~external_library_name])) + ~flags:(Some (Ordered_set_lang.Unexpanded.include_single + ~context:parsing_context ~pos:("", 0, 0, 0) + (cflags_sexp ~external_library_name))) + foreign_stubs diff --git a/src/dune_rules/ctypes_stubs.mli b/src/dune_rules/ctypes_stubs.mli new file mode 100644 index 00000000000..dc6af59eaf7 --- /dev/null +++ b/src/dune_rules/ctypes_stubs.mli @@ -0,0 +1,22 @@ +open! Dune_engine +open! Stdune + +(* This module would be part of Ctypes_rules, except it creates a circular + dependency if Dune_file tries to access it. *) + +val cflags_sexp : external_library_name:string -> string + +val c_generated_functions_cout_no_ext : external_library_name:string -> string + +val add : + loc:Loc.t + -> parsing_context:Univ_map.t + -> external_library_name:string + -> add_stubs:(Foreign_language.t + -> loc:Loc.t + -> names:Ordered_set_lang.t option + -> flags:Ordered_set_lang.Unexpanded.t option + -> Foreign.Stubs.t list + -> Foreign.Stubs.t list) + -> foreign_stubs:Foreign.Stubs.t list + -> Foreign.Stubs.t list diff --git a/src/dune_rules/dune_file.ml b/src/dune_rules/dune_file.ml index 65b199121ee..5aca7a79c63 100644 --- a/src/dune_rules/dune_file.ml +++ b/src/dune_rules/dune_file.ml @@ -297,6 +297,7 @@ module Buildable = struct Foreign.Stubs.make ~loc ~language ~names ~flags :: foreign_stubs in let+ loc = loc + and+ project = Dune_project.get_exn () and+ preprocess, preprocessor_deps = preprocess_fields and+ lint = field "lint" Lint.decode ~default:Lint.default and+ foreign_stubs = @@ -395,6 +396,15 @@ module Buildable = struct |> add_stubs C ~loc:c_names_loc ~names:c_names ~flags:c_flags |> add_stubs Cxx ~loc:cxx_names_loc ~names:cxx_names ~flags:cxx_flags in + let foreign_stubs = + match ctypes with + | None -> foreign_stubs + | Some ctypes -> + Ctypes_stubs.add ~loc + ~parsing_context:(Dune_project.parsing_context project) + ~external_library_name:ctypes.Ctypes.external_library_name + ~add_stubs ~foreign_stubs + in let foreign_archives = Option.value ~default:[] foreign_archives in let foreign_archives = if From a75d8d6a0859d4fe06fb77682f4eb55ff3168a2d Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Thu, 11 Mar 2021 13:51:22 -0800 Subject: [PATCH 27/69] implement ctypes for libraries too --- src/dune_rules/ctypes_rules.ml | 14 ++++++++---- src/dune_rules/ctypes_rules.mli | 2 ++ src/dune_rules/ctypes_stubs.ml | 3 +++ src/dune_rules/ctypes_stubs.mli | 2 ++ src/dune_rules/exe_rules.ml | 40 ++++++++++++++++++++++++++++----- src/dune_rules/lib_rules.ml | 15 ++++++++----- 6 files changed, 61 insertions(+), 15 deletions(-) diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index 7ac625c349a..1c78ca3b644 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -102,8 +102,13 @@ module Stanza_util = struct let c_generated_functions_cout_c ctypes = sprintf "%s__c_cout_generated_functions.c" ctypes.Ctypes.external_library_name - let _libraries_needed_for_ctypes () = - ["ctypes"; "ctypes.stubs"] + let lib_deps_of_strings ~loc lst = + List.map lst ~f:(fun lib -> + Lib_dep.Direct (loc, Lib_name.of_string lib)) + + let libraries_needed_for_ctypes ~loc = + let libraries = ["ctypes"; "ctypes.stubs"] in + lib_deps_of_strings ~loc libraries let generated_modules ctypes = [ type_gen_script ctypes |> Module_name.of_string @@ -128,6 +133,8 @@ end let generated_ml_and_c_files = Stanza_util.generated_ml_and_c_files +let libraries_needed_for_ctypes = Stanza_util.libraries_needed_for_ctypes + let ml_of_module_name mn = Module_name.to_string mn ^ ".ml" |> String.lowercase @@ -354,8 +361,7 @@ let cctx_with_substitutions ?(libraries=[]) ~modules ~dir let dune_version = Scope.project scope |> Dune_project.dune_version in Lib.DB.resolve_user_written_deps_for_exes (Scope.libs scope) [ (loc, "ctypes") ] - (List.map libraries ~f:(fun lib -> - Lib_dep.Direct (loc, Lib_name.of_string lib))) + (Stanza_util.lib_deps_of_strings ~loc libraries) ~dune_version ~pps:[] in let modules = modules_of_list ~dir ~modules in diff --git a/src/dune_rules/ctypes_rules.mli b/src/dune_rules/ctypes_rules.mli index c34ba77c2cc..e208c7b9630 100644 --- a/src/dune_rules/ctypes_rules.mli +++ b/src/dune_rules/ctypes_rules.mli @@ -3,6 +3,8 @@ open Import module Ctypes = Dune_file.Ctypes +val libraries_needed_for_ctypes : loc:Loc.t -> Lib_dep.t list + val generated_ml_and_c_files : Ctypes.t -> string list val gen_rules : diff --git a/src/dune_rules/ctypes_stubs.ml b/src/dune_rules/ctypes_stubs.ml index 6a037cf40a7..9c0ec31d922 100644 --- a/src/dune_rules/ctypes_stubs.ml +++ b/src/dune_rules/ctypes_stubs.ml @@ -7,6 +7,9 @@ let cflags_sexp ~external_library_name = let c_generated_functions_cout_no_ext ~external_library_name = sprintf "%s__c_cout_generated_functions" external_library_name +let c_library_flags ~external_library_name = + sprintf "%s__c_library_flags.sexp" external_library_name + let add ~loc ~parsing_context ~external_library_name ~add_stubs ~foreign_stubs = add_stubs Foreign_language.C diff --git a/src/dune_rules/ctypes_stubs.mli b/src/dune_rules/ctypes_stubs.mli index dc6af59eaf7..241d93610f1 100644 --- a/src/dune_rules/ctypes_stubs.mli +++ b/src/dune_rules/ctypes_stubs.mli @@ -6,6 +6,8 @@ open! Stdune val cflags_sexp : external_library_name:string -> string +val c_library_flags : external_library_name:string -> string + val c_generated_functions_cout_no_ext : external_library_name:string -> string val add : diff --git a/src/dune_rules/exe_rules.ml b/src/dune_rules/exe_rules.ml index ae037c9f76e..d02f50b95b3 100644 --- a/src/dune_rules/exe_rules.ml +++ b/src/dune_rules/exe_rules.ml @@ -103,6 +103,27 @@ let with_empty_intf ~sctx ~dir module_ = Super_context.add_rule sctx ~dir rule; Module.add_file module_ Ml_kind.Intf (Module.File.make Dialect.ocaml name) +let ctypes_cclib_flags ~standard ~scope ~expander exes = + let buildable = exes.Executables.buildable in + match buildable.Buildable.ctypes with + | None -> standard + | Some ctypes -> + let ctypes_c_library_flags = + let path_to_sexp_file = + Ctypes_stubs.c_library_flags + ~external_library_name:ctypes.Dune_file.Ctypes.external_library_name + in + let parsing_context = + let project = Scope.project scope in + Dune_project.parsing_context project + in + Ordered_set_lang.Unexpanded.include_single + ~context:parsing_context ~pos:("", 0, 0, 0) + path_to_sexp_file + in + Expander.expand_and_eval_set expander ctypes_c_library_flags + ~standard + let executables_rules ~sctx ~dir ~expander ~dir_contents ~scope ~compile_info ~embed_in_plugin_libraries (exes : Dune_file.Executables.t) = (* Use "eobjs" rather than "objs" to avoid a potential conflict with a library @@ -179,13 +200,15 @@ let executables_rules ~sctx ~dir ~expander ~dir_contents ~scope ~compile_info (* Building an archive for foreign stubs, we link the corresponding object files directly to improve perf. *) let link_args = + let standard = Action_builder.return [] in let link_flags = let link_deps = Dep_conf_eval.unnamed ~expander exes.link_deps in link_deps >>> Expander.expand_and_eval_set expander exes.link_flags - ~standard:(Action_builder.return []) + ~standard in - let+ flags = link_flags in + let+ flags = link_flags + and+ ctypes_cclib_flags = ctypes_cclib_flags ~scope ~standard ~expander exes in Command.Args.S [ Command.Args.As flags ; Command.Args.S @@ -194,8 +217,10 @@ let executables_rules ~sctx ~dir ~expander ~dir_contents ~scope ~compile_info exes.buildable.foreign_archives |> List.map ~f:snd in List.map foreign_archives ~f:(fun archive -> - let lib = Foreign.Archive.lib_file ~archive ~dir ~ext_lib in - Command.Args.S [ A "-cclib"; Dep (Path.build lib) ])) + let lib = Foreign.Archive.lib_file ~archive ~dir ~ext_lib in + Command.Args.S [ A "-cclib"; Dep (Path.build lib) ])) + ; Command.Args.As + (List.concat_map ctypes_cclib_flags ~f:(fun f -> ["-cclib"; f])) ] in let o_files = @@ -243,8 +268,13 @@ let compile_info ~scope (exes : Dune_file.Executables.t) = ~instrumentation_backend: (Lib.DB.instrumentation_backend (Scope.libs scope))) in + let ctypes_libraries = + if Option.is_none exes.buildable.ctypes then [] + else Ctypes_rules.libraries_needed_for_ctypes ~loc:Loc.none + in + let libraries = exes.buildable.libraries @ ctypes_libraries in Lib.DB.resolve_user_written_deps_for_exes (Scope.libs scope) exes.names - exes.buildable.libraries ~pps ~dune_version + libraries ~pps ~dune_version ~allow_overlaps:exes.buildable.allow_overlapping_dependencies ~forbidden_libraries:exes.forbidden_libraries diff --git a/src/dune_rules/lib_rules.ml b/src/dune_rules/lib_rules.ml index a00ba825e5e..194fdb83878 100644 --- a/src/dune_rules/lib_rules.ml +++ b/src/dune_rules/lib_rules.ml @@ -373,7 +373,7 @@ let cctx (lib : Library.t) ~sctx ~source_modules ~dir ~expander ~scope ?stdlib:lib.stdlib ~package ?vimpl ~modes let library_rules (lib : Library.t) ~cctx ~source_modules ~dir_contents - ~compile_info = + ~compile_info ~dep_graphs = (* Preprocess before adding the alias module as it doesn't need preprocessing *) let source_modules = Modules.fold_user_written source_modules ~init:[] ~f:(fun m acc -> m :: acc) @@ -387,7 +387,6 @@ let library_rules (lib : Library.t) ~cctx ~source_modules ~dir_contents let scope = Compilation_context.scope cctx in let requires_compile = Compilation_context.requires_compile cctx in let stdlib_dir = (Compilation_context.context cctx).Context.stdlib_dir in - let dep_graphs = Dep_rules.rules cctx ~modules in Option.iter vimpl ~f:(Virtual_rules.setup_copy_rules_for_impl ~sctx ~dir); Check_rules.add_obj_dir sctx ~obj_dir; gen_wrapped_compat_modules lib cctx; @@ -436,19 +435,23 @@ let rules (lib : Library.t) ~sctx ~dir_contents ~dir ~expander ~scope : let cctx = cctx lib ~sctx ~source_modules ~dir ~scope ~expander ~compile_info in + let dep_graphs = + Dep_rules.rules cctx ~modules:(Compilation_context.modules cctx) + in let () = let buildable = lib.Library.buildable in Option.iter buildable.Buildable.ctypes ~f:(fun _ctypes -> - let _loc, _name = lib.Library.name in - () - (*Ctypes_rules.gen_rules ~cctx ~buildable ~loc ~sctx ~scope ~dir*) - ) + Ctypes_rules.gen_rules + ~loc:(fst lib.Library.name) + ~cctx ~dep_graphs ~buildable ~sctx ~scope ~dir) in library_rules lib ~cctx ~source_modules ~dir_contents ~compile_info + ~dep_graphs in Buildable_rules.gen_select_rules sctx compile_info ~dir; let cctx, merlin = Buildable_rules.with_lib_deps (Super_context.context sctx) compile_info ~dir ~f + in cctx, merlin From b1c9e403b0ba3c399f90f72d0de4314c882ec38a Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Fri, 12 Mar 2021 11:51:45 -0800 Subject: [PATCH 28/69] add ctypes libraries to buildable if user uses ctypes --- src/dune_rules/ctypes_rules.ml | 6 ------ src/dune_rules/ctypes_rules.mli | 1 - src/dune_rules/ctypes_stubs.ml | 8 ++++++++ src/dune_rules/ctypes_stubs.mli | 2 ++ src/dune_rules/dune_file.ml | 7 +++++++ src/dune_rules/exe_rules.ml | 7 +------ 6 files changed, 18 insertions(+), 13 deletions(-) diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index 1c78ca3b644..01725d4fc82 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -106,10 +106,6 @@ module Stanza_util = struct List.map lst ~f:(fun lib -> Lib_dep.Direct (loc, Lib_name.of_string lib)) - let libraries_needed_for_ctypes ~loc = - let libraries = ["ctypes"; "ctypes.stubs"] in - lib_deps_of_strings ~loc libraries - let generated_modules ctypes = [ type_gen_script ctypes |> Module_name.of_string ; function_gen_script ctypes |> Module_name.of_string @@ -133,8 +129,6 @@ end let generated_ml_and_c_files = Stanza_util.generated_ml_and_c_files -let libraries_needed_for_ctypes = Stanza_util.libraries_needed_for_ctypes - let ml_of_module_name mn = Module_name.to_string mn ^ ".ml" |> String.lowercase diff --git a/src/dune_rules/ctypes_rules.mli b/src/dune_rules/ctypes_rules.mli index e208c7b9630..39d98a8de3b 100644 --- a/src/dune_rules/ctypes_rules.mli +++ b/src/dune_rules/ctypes_rules.mli @@ -3,7 +3,6 @@ open Import module Ctypes = Dune_file.Ctypes -val libraries_needed_for_ctypes : loc:Loc.t -> Lib_dep.t list val generated_ml_and_c_files : Ctypes.t -> string list diff --git a/src/dune_rules/ctypes_stubs.ml b/src/dune_rules/ctypes_stubs.ml index 9c0ec31d922..dc12f3b6edb 100644 --- a/src/dune_rules/ctypes_stubs.ml +++ b/src/dune_rules/ctypes_stubs.ml @@ -10,6 +10,14 @@ let c_generated_functions_cout_no_ext ~external_library_name = let c_library_flags ~external_library_name = sprintf "%s__c_library_flags.sexp" external_library_name +let lib_deps_of_strings ~loc lst = + List.map lst ~f:(fun lib -> + Lib_dep.Direct (loc, Lib_name.of_string lib)) + +let libraries_needed_for_ctypes ~loc = + let libraries = ["ctypes"; "ctypes.stubs"] in + lib_deps_of_strings ~loc libraries + let add ~loc ~parsing_context ~external_library_name ~add_stubs ~foreign_stubs = add_stubs Foreign_language.C diff --git a/src/dune_rules/ctypes_stubs.mli b/src/dune_rules/ctypes_stubs.mli index 241d93610f1..43d64085d6f 100644 --- a/src/dune_rules/ctypes_stubs.mli +++ b/src/dune_rules/ctypes_stubs.mli @@ -10,6 +10,8 @@ val c_library_flags : external_library_name:string -> string val c_generated_functions_cout_no_ext : external_library_name:string -> string +val libraries_needed_for_ctypes : loc:Loc.t -> Lib_dep.t list + val add : loc:Loc.t -> parsing_context:Univ_map.t diff --git a/src/dune_rules/dune_file.ml b/src/dune_rules/dune_file.ml index 5aca7a79c63..be46a58d8e3 100644 --- a/src/dune_rules/dune_file.ml +++ b/src/dune_rules/dune_file.ml @@ -396,6 +396,13 @@ module Buildable = struct |> add_stubs C ~loc:c_names_loc ~names:c_names ~flags:c_flags |> add_stubs Cxx ~loc:cxx_names_loc ~names:cxx_names ~flags:cxx_flags in + let libraries = + let ctypes_libraries = + if Option.is_none ctypes then [] + else Ctypes_stubs.libraries_needed_for_ctypes ~loc:Loc.none + in + libraries @ ctypes_libraries + in let foreign_stubs = match ctypes with | None -> foreign_stubs diff --git a/src/dune_rules/exe_rules.ml b/src/dune_rules/exe_rules.ml index d02f50b95b3..ca028930257 100644 --- a/src/dune_rules/exe_rules.ml +++ b/src/dune_rules/exe_rules.ml @@ -268,13 +268,8 @@ let compile_info ~scope (exes : Dune_file.Executables.t) = ~instrumentation_backend: (Lib.DB.instrumentation_backend (Scope.libs scope))) in - let ctypes_libraries = - if Option.is_none exes.buildable.ctypes then [] - else Ctypes_rules.libraries_needed_for_ctypes ~loc:Loc.none - in - let libraries = exes.buildable.libraries @ ctypes_libraries in Lib.DB.resolve_user_written_deps_for_exes (Scope.libs scope) exes.names - libraries ~pps ~dune_version + exes.buildable.libraries ~pps ~dune_version ~allow_overlaps:exes.buildable.allow_overlapping_dependencies ~forbidden_libraries:exes.forbidden_libraries From 93f69cd617dc8719505e0929cf4eca5627c76868 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Fri, 12 Mar 2021 12:17:12 -0800 Subject: [PATCH 29/69] use ctypes link flags in libraries --- src/dune_rules/ctypes_rules.ml | 20 ++++++++++++++++++++ src/dune_rules/ctypes_rules.mli | 22 ++++++++++++++-------- src/dune_rules/exe_rules.ml | 33 ++++++++++----------------------- src/dune_rules/lib_rules.ml | 22 ++++++++++++++-------- 4 files changed, 58 insertions(+), 39 deletions(-) diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index 01725d4fc82..99a5d631ed9 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -525,3 +525,23 @@ let gen_rules ~dep_graphs ~cctx ~buildable ~loc ~scope ~dir ~sctx = ~function_description_module:(Stanza_util.function_description_module ctypes) ~c_generated_functions_module:(Stanza_util.c_generated_functions_module ctypes) ~c_types_includer_module + +let ctypes_cclib_flags ~standard ~scope ~expander ~buildable = + match buildable.Buildable.ctypes with + | None -> standard + | Some ctypes -> + let ctypes_c_library_flags = + let path_to_sexp_file = + Ctypes_stubs.c_library_flags + ~external_library_name:ctypes.Dune_file.Ctypes.external_library_name + in + let parsing_context = + let project = Scope.project scope in + Dune_project.parsing_context project + in + Ordered_set_lang.Unexpanded.include_single + ~context:parsing_context ~pos:("", 0, 0, 0) + path_to_sexp_file + in + Expander.expand_and_eval_set expander ctypes_c_library_flags + ~standard diff --git a/src/dune_rules/ctypes_rules.mli b/src/dune_rules/ctypes_rules.mli index 39d98a8de3b..a229fc338bc 100644 --- a/src/dune_rules/ctypes_rules.mli +++ b/src/dune_rules/ctypes_rules.mli @@ -3,15 +3,21 @@ open Import module Ctypes = Dune_file.Ctypes - val generated_ml_and_c_files : Ctypes.t -> string list val gen_rules : - dep_graphs : Dep_graph.t Ml_kind.Dict.t - -> cctx : Compilation_context.t - -> buildable : Dune_file.Buildable.t - -> loc : Loc.t - -> scope : Scope.t - -> dir : Path.Build.t - -> sctx : Super_context.t + dep_graphs:Dep_graph.t Ml_kind.Dict.t + -> cctx:Compilation_context.t + -> buildable:Dune_file.Buildable.t + -> loc:Loc.t + -> scope:Scope.t + -> dir:Path.Build.t + -> sctx:Super_context.t -> unit + +val ctypes_cclib_flags : + standard:string list Action_builder.t + -> scope:Scope.t + -> expander:Expander.t + -> buildable:Dune_file.Buildable.t + -> string list Action_builder.t diff --git a/src/dune_rules/exe_rules.ml b/src/dune_rules/exe_rules.ml index ca028930257..bf1a3867457 100644 --- a/src/dune_rules/exe_rules.ml +++ b/src/dune_rules/exe_rules.ml @@ -103,27 +103,6 @@ let with_empty_intf ~sctx ~dir module_ = Super_context.add_rule sctx ~dir rule; Module.add_file module_ Ml_kind.Intf (Module.File.make Dialect.ocaml name) -let ctypes_cclib_flags ~standard ~scope ~expander exes = - let buildable = exes.Executables.buildable in - match buildable.Buildable.ctypes with - | None -> standard - | Some ctypes -> - let ctypes_c_library_flags = - let path_to_sexp_file = - Ctypes_stubs.c_library_flags - ~external_library_name:ctypes.Dune_file.Ctypes.external_library_name - in - let parsing_context = - let project = Scope.project scope in - Dune_project.parsing_context project - in - Ordered_set_lang.Unexpanded.include_single - ~context:parsing_context ~pos:("", 0, 0, 0) - path_to_sexp_file - in - Expander.expand_and_eval_set expander ctypes_c_library_flags - ~standard - let executables_rules ~sctx ~dir ~expander ~dir_contents ~scope ~compile_info ~embed_in_plugin_libraries (exes : Dune_file.Executables.t) = (* Use "eobjs" rather than "objs" to avoid a potential conflict with a library @@ -208,7 +187,10 @@ let executables_rules ~sctx ~dir ~expander ~dir_contents ~scope ~compile_info ~standard in let+ flags = link_flags - and+ ctypes_cclib_flags = ctypes_cclib_flags ~scope ~standard ~expander exes in + and+ ctypes_cclib_flags = + Ctypes_rules.ctypes_cclib_flags ~scope ~standard ~expander + ~buildable:exes.buildable + in Command.Args.S [ Command.Args.As flags ; Command.Args.S @@ -216,11 +198,16 @@ let executables_rules ~sctx ~dir ~expander ~dir_contents ~scope ~compile_info let foreign_archives = exes.buildable.foreign_archives |> List.map ~f:snd in + (* XXX: don't these need the msvc hack being done in lib_rules? *) + (* XXX: also the Command.quote_args being done in lib_rules? *) List.map foreign_archives ~f:(fun archive -> let lib = Foreign.Archive.lib_file ~archive ~dir ~ext_lib in Command.Args.S [ A "-cclib"; Dep (Path.build lib) ])) + (* XXX: don't these need the msvc hack being done in lib_rules? *) + (* XXX: also the Command.quote_args being done in lib_rules? *) ; Command.Args.As - (List.concat_map ctypes_cclib_flags ~f:(fun f -> ["-cclib"; f])) + (List.concat_map ctypes_cclib_flags ~f:(fun f -> + ["-cclib"; f])) ] in let o_files = diff --git a/src/dune_rules/lib_rules.ml b/src/dune_rules/lib_rules.ml index 194fdb83878..29ea666ebbc 100644 --- a/src/dune_rules/lib_rules.ml +++ b/src/dune_rules/lib_rules.ml @@ -17,7 +17,7 @@ let msvc_hack_cclibs = (* Build an OCaml library. *) let build_lib (lib : Library.t) ~native_archives ~sctx ~expander ~flags ~dir - ~mode ~cm_files = + ~mode ~cm_files ~scope = let ctx = Super_context.context sctx in Result.iter (Context.compiler ctx mode) ~f:(fun compiler -> let target = Library.archive lib ~dir ~ext:(Mode.compiled_lib_ext mode) in @@ -42,13 +42,16 @@ let build_lib (lib : Library.t) ~native_archives ~sctx ~expander ~flags ~dir Action_builder.paths (Cm_files.unsorted_objects_and_cms cm_files ~mode) in let ocaml_flags = Ocaml_flags.get flags mode in + let standard = Action_builder.return [] in let cclibs = - Expander.expand_and_eval_set expander lib.c_library_flags - ~standard:(Action_builder.return []) + Expander.expand_and_eval_set expander lib.c_library_flags ~standard in let library_flags = - Expander.expand_and_eval_set expander lib.library_flags - ~standard:(Action_builder.return []) + Expander.expand_and_eval_set expander lib.library_flags ~standard + in + let ctypes_cclib_flags = + Ctypes_rules.ctypes_cclib_flags ~scope ~standard ~expander + ~buildable:lib.buildable in Super_context.add_rule ~dir sctx ~loc:lib.buildable.loc (let open Action_builder.With_targets.O in @@ -76,6 +79,9 @@ let build_lib (lib : Library.t) ~native_archives ~sctx ~expander ~flags ~dir (match mode with | Byte -> [] | Native -> native_archives) + ; Dyn + (Action_builder.map ctypes_cclib_flags ~f:(fun x -> + Command.quote_args "-cclib" (map_cclibs x))) ])) let gen_wrapped_compat_modules (lib : Library.t) cctx = @@ -268,7 +274,7 @@ let build_shared lib ~native_archives ~sctx ~dir ~flags = Super_context.add_rule sctx build ~dir) let setup_build_archives (lib : Dune_file.Library.t) ~cctx - ~(dep_graphs : Dep_graph.Ml_kind.t) ~expander = + ~(dep_graphs : Dep_graph.Ml_kind.t) ~expander ~scope = let obj_dir = Compilation_context.obj_dir cctx in let flags = Compilation_context.flags cctx in let modules = Compilation_context.modules cctx in @@ -317,7 +323,7 @@ let setup_build_archives (lib : Dune_file.Library.t) ~cctx in Mode.Dict.Set.iter modes ~f:(fun mode -> build_lib lib ~native_archives ~dir ~sctx ~expander ~flags ~mode - ~cm_files)); + ~cm_files ~scope)); (* Build *.cma.js *) if modes.byte then Super_context.add_rules sctx ~dir @@ -398,7 +404,7 @@ let library_rules (lib : Library.t) ~cctx ~source_modules ~dir_contents (Lib.DB.instrumentation_backend (Scope.libs scope)) in if not (Library.is_virtual lib) then - setup_build_archives lib ~cctx ~dep_graphs ~expander; + setup_build_archives lib ~cctx ~dep_graphs ~expander ~scope; let () = let vlib_stubs_o_files = Vimpl.vlib_stubs_o_files vimpl in if Library.has_foreign lib || List.is_non_empty vlib_stubs_o_files then From ac3ad60da0cf7c2acb0697dd1173e24b4a9c4244 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Sat, 13 Mar 2021 07:02:35 -0800 Subject: [PATCH 30/69] remove unneeded code --- src/dune_rules/modules.ml | 4 ++-- src/dune_rules/ocaml_flags.ml | 4 ---- src/dune_rules/ocaml_flags.mli | 2 -- src/dune_rules/ordered_set_lang.ml | 9 --------- src/dune_rules/ordered_set_lang.mli | 2 -- 5 files changed, 2 insertions(+), 19 deletions(-) diff --git a/src/dune_rules/modules.ml b/src/dune_rules/modules.ml index e0159b6a692..eee4f7ee03c 100644 --- a/src/dune_rules/modules.ml +++ b/src/dune_rules/modules.ml @@ -110,8 +110,8 @@ module Stdlib = struct Module_name.Map.values t.modules |> List.filter ~f:(fun m -> Some (Module.name m) <> t.exit_module) - let find t module_name = - Module_name.Map.find t.modules module_name + let find t = + Module_name.Map.find t.modules let find_dep t ~of_ name = let of_name = Module.name of_ in diff --git a/src/dune_rules/ocaml_flags.ml b/src/dune_rules/ocaml_flags.ml index cee238f8005..5766fdcb1c6 100644 --- a/src/dune_rules/ocaml_flags.ml +++ b/src/dune_rules/ocaml_flags.ml @@ -76,10 +76,6 @@ module Spec = struct ; specific = Mode.Dict.make_both Ordered_set_lang.Unexpanded.standard } - let of_unexpanded_ordered_set_lang osl = - { common = osl - ; specific = Mode.Dict.make_both osl } - let decode = let open Dune_lang.Decoder in let field_oslu = Ordered_set_lang.Unexpanded.field in diff --git a/src/dune_rules/ocaml_flags.mli b/src/dune_rules/ocaml_flags.mli index 06cdcee957d..9e2762f4739 100644 --- a/src/dune_rules/ocaml_flags.mli +++ b/src/dune_rules/ocaml_flags.mli @@ -13,8 +13,6 @@ module Spec : sig val decode : t Dune_lang.Decoder.fields_parser val standard : t - - val of_unexpanded_ordered_set_lang : Ordered_set_lang.Unexpanded.t -> t end val make : diff --git a/src/dune_rules/ordered_set_lang.ml b/src/dune_rules/ordered_set_lang.ml index 07617127a4d..441a965f5fe 100644 --- a/src/dune_rules/ordered_set_lang.ml +++ b/src/dune_rules/ordered_set_lang.ml @@ -270,15 +270,6 @@ module Unexpanded = struct ; context = Univ_map.empty } - let standard_with_of_strings ~pos l = - { ast = - Ast.Union - (Standard :: List.map l ~f:(fun x -> - Ast.Element (String_with_vars.virt_text pos x))) - ; loc = Some (Loc.of_pos pos) - ; context = Univ_map.empty - } - let include_single ~context ~pos f = { ast = Ast.Include (String_with_vars.virt_text pos f) ; loc = Some (Loc.of_pos pos) diff --git a/src/dune_rules/ordered_set_lang.mli b/src/dune_rules/ordered_set_lang.mli index 9b0babd6b19..38203d0e06c 100644 --- a/src/dune_rules/ordered_set_lang.mli +++ b/src/dune_rules/ordered_set_lang.mli @@ -58,8 +58,6 @@ module Unexpanded : sig val of_strings : pos:string * int * int * int -> string list -> t - val standard_with_of_strings : pos:string * int * int * int -> string list -> t - val include_single : context:Univ_map.t -> pos:string * int * int * int -> string -> t val field : From 326c2795bef66e8b6789de95c9077a8bb3d85e94 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Thu, 25 Mar 2021 10:01:42 -0700 Subject: [PATCH 31/69] build some blackbox tests --- Makefile | 1 + src/dune_rules/ctypes_rules.ml | 9 +++++++ .../test-cases/ctypes/exe-vendored.t/dune | 25 +++++++++++++++++ .../ctypes/exe-vendored.t/dune-project | 3 +++ .../ctypes/exe-vendored.t/example.ml | 2 ++ .../exe-vendored.t/function_descriptions.ml | 8 ++++++ .../test-cases/ctypes/exe-vendored.t/run.t | 2 ++ .../exe-vendored.t/type_descriptions.ml | 3 +++ .../exe-vendored.t/vendor/Makefile.unix | 13 +++++++++ .../ctypes/exe-vendored.t/vendor/example.c | 1 + .../ctypes/exe-vendored.t/vendor/example.h | 1 + .../test-cases/ctypes/lib-vendored.t/dune | 3 +++ .../ctypes/lib-vendored.t/dune-project | 3 +++ .../ctypes/lib-vendored.t/example.ml | 2 ++ .../test-cases/ctypes/lib-vendored.t/run.t | 2 ++ .../ctypes/lib-vendored.t/stubgen/dune | 27 +++++++++++++++++++ .../ctypes/lib-vendored.t/stubgen/example.ml | 2 ++ .../stubgen/function_descriptions.ml | 8 ++++++ .../stubgen/type_descriptions.ml | 3 +++ .../stubgen/vendor/Makefile.unix | 13 +++++++++ .../lib-vendored.t/stubgen/vendor/example.c | 1 + .../lib-vendored.t/stubgen/vendor/example.h | 1 + 22 files changed, 133 insertions(+) create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored.t/dune create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored.t/dune-project create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored.t/example.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored.t/function_descriptions.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored.t/run.t create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored.t/type_descriptions.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored.t/vendor/Makefile.unix create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored.t/vendor/example.c create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored.t/vendor/example.h create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-vendored.t/dune create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-vendored.t/dune-project create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-vendored.t/example.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-vendored.t/run.t create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/dune create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/example.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/function_descriptions.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/type_descriptions.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/vendor/Makefile.unix create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/vendor/example.c create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/vendor/example.h diff --git a/Makefile b/Makefile index f4b58ff67f5..ce2f8446aff 100644 --- a/Makefile +++ b/Makefile @@ -14,6 +14,7 @@ cinaps \ coq-native \ "coq>=8.12.1" \ core_bench \ +ctypes \ "csexp>=1.3.0" \ js_of_ocaml \ js_of_ocaml-compiler \ diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index 99a5d631ed9..cb4ad6b6dc7 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -338,10 +338,19 @@ let build_c_program ~sctx ~dir ~source_files ~scope ~cflags_sexp ~output () = | Template _ -> fail "'template' not supported in ctypes c_flags" | List _ -> fail "nested lists not supported in ctypes c_flags")) in + let absolute_path_hack p = + (* These normal path builder things construct relative paths like + _build/default/your/project/file.c but before dune runs gcc it + actually cds into _build/default, which fails, so we turn them + into absolutes to hack around it. *) + Path.relative (Path.build dir) p |> Path.to_absolute_filename + in let action = let open Action_builder.O in Action_builder.deps deps >>> Action_builder.map cflags_args ~f:(fun cflags_args -> + let source_files = List.map source_files ~f:absolute_path_hack in + let output = absolute_path_hack output in let args = cflags_args @ include_args @ source_files @ ["-o"; output] in Action.run exe args) in diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/dune b/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/dune new file mode 100644 index 00000000000..9845c3ca385 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/dune @@ -0,0 +1,25 @@ +(rule + (targets libexample.a dllexample%{ext_dll}) + (deps (source_tree vendor)) + (action + (no-infer + (progn + (chdir vendor (run make -s -f Makefile.unix)) + (copy vendor/libexample.a libexample.a) + (copy vendor/libexample%{ext_dll} dllexample%{ext_dll}))))) + +(executable + (name example) + (flags (:standard -w -9-27)) + (foreign_archives example) + (ctypes + (external_library_name examplelib) + (build_flags_resolver + (vendored + (c_flags "-Ivendor") + (c_library_flags ()))) + (headers (include "example.h")) + (type_descriptions Type_descriptions) + (generated_types Types_generated) + (function_descriptions Function_descriptions) + (generated_entry_point C))) diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/dune-project b/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/dune-project new file mode 100644 index 00000000000..776b2190292 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/dune-project @@ -0,0 +1,3 @@ +(lang dune 2.8) +(using ctypes 0.1) +(use_standard_c_and_cxx_flags false) diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/example.ml b/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/example.ml new file mode 100644 index 00000000000..98a01761fa6 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/example.ml @@ -0,0 +1,2 @@ +let () = + Printf.printf "%d\n" (C.Functions.add2 2) diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/function_descriptions.ml b/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/function_descriptions.ml new file mode 100644 index 00000000000..05c43d79e2f --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/function_descriptions.ml @@ -0,0 +1,8 @@ +open Ctypes + +module Types = Types_generated + +module Functions (F : Ctypes.FOREIGN) = struct + open F + let add2 = foreign "example_add2" (int @-> returning int) +end diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/run.t b/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/run.t new file mode 100644 index 00000000000..efd47f01251 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/run.t @@ -0,0 +1,2 @@ + $ dune exec ./example.exe + 4 diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/type_descriptions.ml b/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/type_descriptions.ml new file mode 100644 index 00000000000..41693fda9b3 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/type_descriptions.ml @@ -0,0 +1,3 @@ +module Types (F : Ctypes.TYPE) = struct + +end diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/vendor/Makefile.unix b/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/vendor/Makefile.unix new file mode 100644 index 00000000000..6b707dc9347 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/vendor/Makefile.unix @@ -0,0 +1,13 @@ +all: libexample.so libexample.a + +example.o: example.c + cc -c -fPIC -o example.o example.c + +libexample.a: example.o + ar rcs libexample.a example.o + +libexample.so: example.o + gcc -shared -o libexample.so example.o + +clean: + rm -f example.o libexample.so libexample.a diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/vendor/example.c b/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/vendor/example.c new file mode 100644 index 00000000000..544e41ad208 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/vendor/example.c @@ -0,0 +1 @@ +int example_add2(int x) { return x+2; } diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/vendor/example.h b/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/vendor/example.h new file mode 100644 index 00000000000..db8d04d2ab0 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/vendor/example.h @@ -0,0 +1 @@ +int example_add2(int); diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/dune b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/dune new file mode 100644 index 00000000000..251267cde5f --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/dune @@ -0,0 +1,3 @@ +(executable + (name example) + (libraries examplelib)) diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/dune-project b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/dune-project new file mode 100644 index 00000000000..776b2190292 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/dune-project @@ -0,0 +1,3 @@ +(lang dune 2.8) +(using ctypes 0.1) +(use_standard_c_and_cxx_flags false) diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/example.ml b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/example.ml new file mode 100644 index 00000000000..eebafeb3114 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/example.ml @@ -0,0 +1,2 @@ +let () = + Printf.printf "%d\n" (Examplelib.C.Functions.add2 2) diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/run.t b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/run.t new file mode 100644 index 00000000000..efd47f01251 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/run.t @@ -0,0 +1,2 @@ + $ dune exec ./example.exe + 4 diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/dune b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/dune new file mode 100644 index 00000000000..2b1a4ba71df --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/dune @@ -0,0 +1,27 @@ +(rule + (targets libexample.a dllexample%{ext_dll}) + (deps (source_tree vendor)) + (action + (no-infer + (progn + (chdir vendor (run make -s -f Makefile.unix)) + (copy vendor/libexample.a libexample.a) + (copy vendor/libexample%{ext_dll} dllexample%{ext_dll}))))) + +(library + (name examplelib) + (flags (:standard -w -9-27)) + (foreign_archives example) + (ctypes + (external_library_name examplelib) + (build_flags_resolver + (vendored + ; hack: multiple -I directives to work around cc commands being run from different + ; relative directories. Is there a cleaner way to do this? + (c_flags ("-Istubgen/vendor" "-Ivendor")) + (c_library_flags ()))) + (headers (include "example.h")) + (type_descriptions Type_descriptions) + (generated_types Types_generated) + (function_descriptions Function_descriptions) + (generated_entry_point C))) diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/example.ml b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/example.ml new file mode 100644 index 00000000000..98a01761fa6 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/example.ml @@ -0,0 +1,2 @@ +let () = + Printf.printf "%d\n" (C.Functions.add2 2) diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/function_descriptions.ml b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/function_descriptions.ml new file mode 100644 index 00000000000..05c43d79e2f --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/function_descriptions.ml @@ -0,0 +1,8 @@ +open Ctypes + +module Types = Types_generated + +module Functions (F : Ctypes.FOREIGN) = struct + open F + let add2 = foreign "example_add2" (int @-> returning int) +end diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/type_descriptions.ml b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/type_descriptions.ml new file mode 100644 index 00000000000..41693fda9b3 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/type_descriptions.ml @@ -0,0 +1,3 @@ +module Types (F : Ctypes.TYPE) = struct + +end diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/vendor/Makefile.unix b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/vendor/Makefile.unix new file mode 100644 index 00000000000..6b707dc9347 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/vendor/Makefile.unix @@ -0,0 +1,13 @@ +all: libexample.so libexample.a + +example.o: example.c + cc -c -fPIC -o example.o example.c + +libexample.a: example.o + ar rcs libexample.a example.o + +libexample.so: example.o + gcc -shared -o libexample.so example.o + +clean: + rm -f example.o libexample.so libexample.a diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/vendor/example.c b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/vendor/example.c new file mode 100644 index 00000000000..544e41ad208 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/vendor/example.c @@ -0,0 +1 @@ +int example_add2(int x) { return x+2; } diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/vendor/example.h b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/vendor/example.h new file mode 100644 index 00000000000..db8d04d2ab0 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/vendor/example.h @@ -0,0 +1 @@ +int example_add2(int); From 22d7771e9a0c56dc21b122a5fca813903de1e2a0 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Thu, 1 Apr 2021 11:52:41 -0700 Subject: [PATCH 32/69] simplify stanza a bit --- src/dune_rules/ctypes_rules.ml | 58 +++++++++++-------- src/dune_rules/dune_file.ml | 4 +- .../test-cases/ctypes/exe-vendored.t/dune | 4 +- .../ctypes/lib-vendored.t/stubgen/dune | 4 +- 4 files changed, 37 insertions(+), 33 deletions(-) diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index cb4ad6b6dc7..87c079667cd 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -1,56 +1,64 @@ open! Dune_engine open! Stdune -module Buildable = Dune_file.Buildable -module Library = Dune_file.Library -module Ctypes = Dune_file.Ctypes - -(* This module expands either a (library ... (ctypes_stubgen ...)) rule - or an (executables ... (ctypes_stubgen ...)) rule into the generated - set of .ml files needed to conveniently build OCaml bindings for C - libraries. +(* This module expands either a (library ... (ctypes ...)) rule or an + (executables ... (ctypes ...)) rule into the generated set of .ml and .c + files needed to conveniently write OCaml bindings for C libraries. - Aside from perhaps providing an '#include "header.h"' line, you should be + Aside from perhaps providing an "header.h" include line, you should be able to wrap an entire C library without writing a single line of C code. - This stanza requires the user to define (and specify) two modules: + This stanza requires the user to specify the names of 4 modules: - (1) A "Type Descriptions" .ml file with the following top-level module: + (type_descriptions Type_descriptions) + (generated_types Types_generated) + (function_descriptions Function_descriptions) + (generated_entry_point C)) + + The user must also implement two of the modules: + + (1) $type_descriptions.ml musth ave the following top-level functor: module Types (T : Ctypes.TYPE) = struct (* put calls to Ctypes.TYPE.constant and Ctypes.TYPE.typedef here to wrap C constants and structs *) end - (2) A 'Function Descriptions' .ml file with the following top-level module: + (2) $function_descriptions.ml must have the following two definitions: + + modules Types = $generated_types module Functions (F : Ctypes.FOREIGN) = struct (* put calls to F.foreign here to wrap C functions *) end - The instantiated functor that was defined in 'Types' can be accessed from - the Function Descriptions module as Library_name__c_types. - - e.g. module Types = Library_name__c_types - - Once the above two modules are provided, the ctypes stanza will: - - generate a types/data generator + Once the above modules are provided, the ctypes stanza will: + - generate a types generator - generate a functions generator - - set up a discovery program to query pkg-config for compile and link flags + - set up a discovery program to query pkg-config for compile and link flags, + if you decided to use pkg-config instead of vendored c-flags - use the types/data and functions modules you filled in with a functor - to tie everything into your library. + to tie everything into your library. - The result of using a ctypes stanza is that it will introduce into your - project a library that provides interfaces to all of the types and functions - you described earlier, with the rather involved compilation and linking - details handled for you. + The user must also specify the name of a final "Entry point" output module + ($generated_entry_point) that will be generated and added to your executable + or library. Suggest calling it "C" and accessing the instantiated functors + from your project as C.Types and C.Functions. It may help to view a real world example of all of the boilerplate that is being replaced by a [ctypes] stanza: https://github.com/mbacarella/mpg123/blob/077a72d922931eb46d4b4e5842b0426fa3c161b5/c/dune + + This implementation is not, however, a naive translation of the boilerplate + above. This module uses dune internal features to simplify the stub + generation. As a result, there are no intermediate libraries (or packages). *) +module Buildable = Dune_file.Buildable +module Library = Dune_file.Library +module Ctypes = Dune_file.Ctypes + module Stanza_util = struct let sprintf = Printf.sprintf diff --git a/src/dune_rules/dune_file.ml b/src/dune_rules/dune_file.ml index be46a58d8e3..ad5874a4d43 100644 --- a/src/dune_rules/dune_file.ml +++ b/src/dune_rules/dune_file.ml @@ -138,7 +138,7 @@ module Ctypes = struct and+ concurrency = field_o "concurrency" Concurrency_policy.decode and+ type_descriptions = field "type_descriptions" Module_name.decode and+ function_descriptions = field "function_descriptions" Module_name.decode - and+ generated_types = field "generated_types" Module_name.decode + and+ generated_types = field_o "generated_types" Module_name.decode and+ generated_entry_point = field "generated_entry_point" Module_name.decode in { external_library_name @@ -147,7 +147,7 @@ module Ctypes = struct ; concurrency = Option.value concurrency ~default:Concurrency_policy.default ; type_descriptions ; function_descriptions - ; generated_types + ; generated_types = Option.value generated_types ~default:(Module_name.of_string "Types_generated") ; generated_entry_point }) let () = diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/dune b/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/dune index 9845c3ca385..eaeb8c15bf3 100644 --- a/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/dune +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/dune @@ -16,10 +16,8 @@ (external_library_name examplelib) (build_flags_resolver (vendored - (c_flags "-Ivendor") - (c_library_flags ()))) + (c_flags "-Ivendor"))) (headers (include "example.h")) (type_descriptions Type_descriptions) - (generated_types Types_generated) (function_descriptions Function_descriptions) (generated_entry_point C))) diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/dune b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/dune index 2b1a4ba71df..aabb5850204 100644 --- a/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/dune +++ b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/dune @@ -18,10 +18,8 @@ (vendored ; hack: multiple -I directives to work around cc commands being run from different ; relative directories. Is there a cleaner way to do this? - (c_flags ("-Istubgen/vendor" "-Ivendor")) - (c_library_flags ()))) + (c_flags ("-Istubgen/vendor" "-Ivendor")))) (headers (include "example.h")) (type_descriptions Type_descriptions) - (generated_types Types_generated) (function_descriptions Function_descriptions) (generated_entry_point C))) From c2f2521e76ae5d3855865ef10a32453da28c9b86 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Thu, 1 Apr 2021 14:06:38 -0700 Subject: [PATCH 33/69] start documenting ctypes stanza --- doc/foreign-code.rst | 36 ++++++++++++++++++++++++++++++++++++ 1 file changed, 36 insertions(+) diff --git a/doc/foreign-code.rst b/doc/foreign-code.rst index 46238137f69..7f4ff7bb571 100644 --- a/doc/foreign-code.rst +++ b/doc/foreign-code.rst @@ -64,6 +64,42 @@ without the ``.h`` extension. When a library install header files, these are made visible to users of the library via the include search path. +Support for ctypes stub generation +---------------------------------- + +It is possible to use the ``ctypes`` stanza to generate bindings for C +libraries without writing any C code. + +You need only provide two OCaml modules, named ``Type_descriptions`` and +``Function_descriptions`` which describe the types, values and functions you +want to access in the C library from OCaml. Additionally, you must list C +any headers and a method for resolving build and link flags. + +If you're binding a library distributed by your OS, you can use the +``pkg-config`` utility to resolve any build and link flags. Alternatively, +if you're using a locally installed library or a vendored library, you can +provide the flags manually. + +.. code:: scheme + + (executable + (name foo) + (libraries core) + (flags (:standard -w -9-27)) + (ctypes + (external_library_name libfoo) + (build_flags_resolver pkg_config) + (headers (include "foo.h")) + (type_descriptions Type_descriptions) + (function_descriptions Function_descriptions) + (generated_entry_point C))) + +This stanza will introduce a module named ``C`` into your project, with the +sub-modules ``Types`` and ``Functions`` that will have your fully bound C +types, constants and functions. + +A complete example of using the ctypes stanza is available here (TBD). + .. _foreign-sandboxing: Foreign build sandboxing From 4702cb1483beb3cfb4c544ad43b1ba7a52cf2c4f Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Thu, 15 Apr 2021 19:31:03 -0700 Subject: [PATCH 34/69] capital percent S --- src/dune_rules/ctypes_rules.ml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index 87c079667cd..81757e52c47 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -225,7 +225,7 @@ let gen_headers headers buf = | Ctypes.Headers.Include lst -> List.iter lst ~f:(fun h -> pr buf " print_endline \"#include <%s>\";" h) | Preamble s -> - pr buf " print_endline \"%S\";" s + pr buf " print_endline %S;" s end let type_gen_gen ~headers ~type_description_module = From 64a581b012e3ce5f1077cf0be7de194d86b98ad6 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Fri, 16 Apr 2021 08:49:50 -0700 Subject: [PATCH 35/69] better error message --- src/dune_rules/ctypes_rules.ml | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index 81757e52c47..41dfb44a8ed 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -419,7 +419,9 @@ let write_osl_to_sexp_file ~sctx ~dir ~filename osl = let encoded = match Ordered_set_lang.Unexpanded.encode osl with | [s] -> s - | _lst -> failwith "unexpected multi-element list" + | _lst -> + User_error.raise + [ Pp.textf "expected %s to contain a list of atoms" filename] in Dune_lang.to_string encoded in From 44988cc44e0071fb118e540314b4821182be7380 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Fri, 23 Apr 2021 12:08:10 -0700 Subject: [PATCH 36/69] support building docs for libraries that depend on foreign_librarys --- src/dune_rules/odoc.ml | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/src/dune_rules/odoc.ml b/src/dune_rules/odoc.ml index 45fab295518..314b1937b12 100644 --- a/src/dune_rules/odoc.ml +++ b/src/dune_rules/odoc.ml @@ -305,9 +305,15 @@ let setup_library_odoc_rules cctx (library : Library.t) ~dep_graphs = compile_module sctx ~includes ~dep_graphs ~obj_dir ~pkg_or_lnu m in compiled :: acc) + |> Path.Set.of_list_map ~f:(fun (_, p) -> Path.build p) + in + let link_deps = + (* This is needed to build docs for libraries that depend on foreign + libraries. *) + Lib.link_deps lib Link_mode.Native |> Path.Set.of_list in Dep.setup_deps ctx (Lib local_lib) - (Path.Set.of_list_map modules_and_odoc_files ~f:(fun (_, p) -> Path.build p)) + (Path.Set.union modules_and_odoc_files link_deps) let setup_css_rule sctx = let ctx = Super_context.context sctx in From 968e2387ad909d6bd9522ee2b1d183e884fa7a35 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Fri, 23 Apr 2021 15:56:29 -0700 Subject: [PATCH 37/69] dont install modules that are for stub generation --- src/dune_rules/ctypes_rules.ml | 24 ++++++++++++++++++++++-- src/dune_rules/ctypes_rules.mli | 2 ++ src/dune_rules/install_rules.ml | 19 ++++++++++++++++--- 3 files changed, 40 insertions(+), 5 deletions(-) diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index 41dfb44a8ed..d81e31aaeec 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -114,14 +114,31 @@ module Stanza_util = struct List.map lst ~f:(fun lib -> Lib_dep.Direct (loc, Lib_name.of_string lib)) + let type_gen_script_module ctypes = + type_gen_script ctypes |> Module_name.of_string + + let function_gen_script_module ctypes = + function_gen_script ctypes |> Module_name.of_string + let generated_modules ctypes = - [ type_gen_script ctypes |> Module_name.of_string - ; function_gen_script ctypes |> Module_name.of_string + [ type_gen_script_module ctypes + ; function_gen_script_module ctypes ; c_generated_functions_module ctypes ; c_generated_types_module ctypes ; c_types_includer_module ctypes ; entry_module ctypes ] + (* not all modules that we generate should be bundled up into packages *) + let non_installable_modules ctypes = + let entire_set = Module_name.Set.of_list (generated_modules ctypes) in + let removal_set = + Module_name.Set.of_list + [ type_gen_script_module ctypes; + function_gen_script_module ctypes ] + in + Module_name.Set.diff entire_set removal_set + |> Module_name.Set.to_list + let generated_ml_and_c_files ctypes = let ml_files = generated_modules ctypes @@ -133,10 +150,13 @@ module Stanza_util = struct [ c_generated_functions_cout_c ctypes ] in ml_files @ c_files + end let generated_ml_and_c_files = Stanza_util.generated_ml_and_c_files +let non_installable_modules = Stanza_util.non_installable_modules + let ml_of_module_name mn = Module_name.to_string mn ^ ".ml" |> String.lowercase diff --git a/src/dune_rules/ctypes_rules.mli b/src/dune_rules/ctypes_rules.mli index a229fc338bc..f761c47d392 100644 --- a/src/dune_rules/ctypes_rules.mli +++ b/src/dune_rules/ctypes_rules.mli @@ -5,6 +5,8 @@ module Ctypes = Dune_file.Ctypes val generated_ml_and_c_files : Ctypes.t -> string list +val non_installable_modules : Ctypes.t -> Module_name.t list + val gen_rules : dep_graphs:Dep_graph.t Ml_kind.Dict.t -> cctx:Compilation_context.t diff --git a/src/dune_rules/install_rules.ml b/src/dune_rules/install_rules.ml index 2972d8149b8..7b202769bd0 100644 --- a/src/dune_rules/install_rules.ml +++ b/src/dune_rules/install_rules.ml @@ -111,9 +111,22 @@ end = struct | Some dir -> sprintf "%s/%s" dir dst) ) in let installable_modules = - Dir_contents.ocaml dir_contents - |> Ml_sources.modules ~for_:(Library (Library.best_name lib)) - |> Modules.fold_no_vlib ~init:[] ~f:(fun m acc -> m :: acc) + let all_modules = + Dir_contents.ocaml dir_contents + |> Ml_sources.modules ~for_:(Library (Library.best_name lib)) + |> Modules.fold_no_vlib ~init:[] ~f:(fun m acc -> m :: acc) + in + let non_installable_modules = + let lst = + match lib.buildable.ctypes with + | Some ctypes -> Ctypes_rules.non_installable_modules ctypes + | None -> [] + in + Module_name.Set.of_list lst + in + List.filter all_modules ~f:(fun module_ -> + let module_name = Module.name module_ in + not (Module_name.Set.mem non_installable_modules module_name)) in let sources = List.concat_map installable_modules ~f:(fun m -> From 12d58bf1f7fc1958f1942c2ad44ce843d435f46b Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Fri, 23 Apr 2021 17:49:11 -0700 Subject: [PATCH 38/69] simplifiy non_installable_modules --- src/dune_rules/ctypes_rules.ml | 10 ++-------- src/dune_rules/install_rules.ml | 4 ++-- 2 files changed, 4 insertions(+), 10 deletions(-) diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index d81e31aaeec..b8205fd9853 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -130,14 +130,8 @@ module Stanza_util = struct (* not all modules that we generate should be bundled up into packages *) let non_installable_modules ctypes = - let entire_set = Module_name.Set.of_list (generated_modules ctypes) in - let removal_set = - Module_name.Set.of_list - [ type_gen_script_module ctypes; - function_gen_script_module ctypes ] - in - Module_name.Set.diff entire_set removal_set - |> Module_name.Set.to_list + [ type_gen_script_module ctypes + ; function_gen_script_module ctypes ] let generated_ml_and_c_files ctypes = let ml_files = diff --git a/src/dune_rules/install_rules.ml b/src/dune_rules/install_rules.ml index 7b202769bd0..6ce5e8737f3 100644 --- a/src/dune_rules/install_rules.ml +++ b/src/dune_rules/install_rules.ml @@ -204,11 +204,11 @@ end = struct List.concat [ sources ; List.map module_files ~f:(fun (sub_dir, file) -> - make_entry ?sub_dir Lib file) + make_entry ?sub_dir Lib file) ; List.map lib_files ~f:(fun (section, file) -> make_entry section file) ; List.map execs ~f:(make_entry Libexec) ; List.map dll_files ~f:(fun a -> - (Some loc, Install.Entry.make Stublibs a)) + (Some loc, Install.Entry.make Stublibs a)) ; List.map ~f:(make_entry Lib) install_c_headers ] From 823151fade71f0c994e5ec0b912cc29f16c81156 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Fri, 23 Apr 2021 18:14:11 -0700 Subject: [PATCH 39/69] whitespace --- src/dune_rules/ctypes_rules.mli | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/dune_rules/ctypes_rules.mli b/src/dune_rules/ctypes_rules.mli index f761c47d392..a1ec55b633c 100644 --- a/src/dune_rules/ctypes_rules.mli +++ b/src/dune_rules/ctypes_rules.mli @@ -18,7 +18,7 @@ val gen_rules : -> unit val ctypes_cclib_flags : - standard:string list Action_builder.t + standard:string list Action_builder.t -> scope:Scope.t -> expander:Expander.t -> buildable:Dune_file.Buildable.t From cac6945d6b22b0d2048a3d215fde5b3b6e3fc042 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Fri, 23 Apr 2021 19:12:44 -0700 Subject: [PATCH 40/69] revert recent changes to install rules --- src/dune_rules/ctypes_rules.ml | 18 ++---------------- src/dune_rules/ctypes_rules.mli | 2 -- src/dune_rules/install_rules.ml | 19 +++---------------- 3 files changed, 5 insertions(+), 34 deletions(-) diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index b8205fd9853..41dfb44a8ed 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -114,25 +114,14 @@ module Stanza_util = struct List.map lst ~f:(fun lib -> Lib_dep.Direct (loc, Lib_name.of_string lib)) - let type_gen_script_module ctypes = - type_gen_script ctypes |> Module_name.of_string - - let function_gen_script_module ctypes = - function_gen_script ctypes |> Module_name.of_string - let generated_modules ctypes = - [ type_gen_script_module ctypes - ; function_gen_script_module ctypes + [ type_gen_script ctypes |> Module_name.of_string + ; function_gen_script ctypes |> Module_name.of_string ; c_generated_functions_module ctypes ; c_generated_types_module ctypes ; c_types_includer_module ctypes ; entry_module ctypes ] - (* not all modules that we generate should be bundled up into packages *) - let non_installable_modules ctypes = - [ type_gen_script_module ctypes - ; function_gen_script_module ctypes ] - let generated_ml_and_c_files ctypes = let ml_files = generated_modules ctypes @@ -144,13 +133,10 @@ module Stanza_util = struct [ c_generated_functions_cout_c ctypes ] in ml_files @ c_files - end let generated_ml_and_c_files = Stanza_util.generated_ml_and_c_files -let non_installable_modules = Stanza_util.non_installable_modules - let ml_of_module_name mn = Module_name.to_string mn ^ ".ml" |> String.lowercase diff --git a/src/dune_rules/ctypes_rules.mli b/src/dune_rules/ctypes_rules.mli index a1ec55b633c..8ac2071772b 100644 --- a/src/dune_rules/ctypes_rules.mli +++ b/src/dune_rules/ctypes_rules.mli @@ -5,8 +5,6 @@ module Ctypes = Dune_file.Ctypes val generated_ml_and_c_files : Ctypes.t -> string list -val non_installable_modules : Ctypes.t -> Module_name.t list - val gen_rules : dep_graphs:Dep_graph.t Ml_kind.Dict.t -> cctx:Compilation_context.t diff --git a/src/dune_rules/install_rules.ml b/src/dune_rules/install_rules.ml index 6ce5e8737f3..9e1874f4a1b 100644 --- a/src/dune_rules/install_rules.ml +++ b/src/dune_rules/install_rules.ml @@ -111,22 +111,9 @@ end = struct | Some dir -> sprintf "%s/%s" dir dst) ) in let installable_modules = - let all_modules = - Dir_contents.ocaml dir_contents - |> Ml_sources.modules ~for_:(Library (Library.best_name lib)) - |> Modules.fold_no_vlib ~init:[] ~f:(fun m acc -> m :: acc) - in - let non_installable_modules = - let lst = - match lib.buildable.ctypes with - | Some ctypes -> Ctypes_rules.non_installable_modules ctypes - | None -> [] - in - Module_name.Set.of_list lst - in - List.filter all_modules ~f:(fun module_ -> - let module_name = Module.name module_ in - not (Module_name.Set.mem non_installable_modules module_name)) + Dir_contents.ocaml dir_contents + |> Ml_sources.modules ~for_:(Library (Library.best_name lib)) + |> Modules.fold_no_vlib ~init:[] ~f:(fun m acc -> m :: acc) in let sources = List.concat_map installable_modules ~f:(fun m -> From 00d9efc079fba9aac2987278e69e9c8715fbf731 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Sat, 24 Apr 2021 08:40:48 -0700 Subject: [PATCH 41/69] exclude ctypes code-gen programs from being added to archives --- src/dune_rules/cm_files.ml | 21 ++++++++++++++++----- src/dune_rules/cm_files.mli | 4 +++- src/dune_rules/ctypes_rules.ml | 15 +++++++++++++-- src/dune_rules/ctypes_rules.mli | 2 ++ src/dune_rules/exe.ml | 2 +- src/dune_rules/lib_rules.ml | 21 +++++++++++++++------ 6 files changed, 50 insertions(+), 15 deletions(-) diff --git a/src/dune_rules/cm_files.ml b/src/dune_rules/cm_files.ml index 50879ca5b28..bee5f9878ec 100644 --- a/src/dune_rules/cm_files.ml +++ b/src/dune_rules/cm_files.ml @@ -6,14 +6,22 @@ type t = ; modules : Module.t list ; top_sorted_modules : Module.t list Action_builder.t ; ext_obj : string + ; excluded_modules : Module_name.Set.t } -let make ~obj_dir ~modules ~top_sorted_modules ~ext_obj = +let filter_excluded_modules t modules = + List.filter modules ~f:(fun module_ -> + let name = Module.name module_ in + not (Module_name.Set.mem t.excluded_modules name)) + +let make ?(excluded_modules=[]) ~obj_dir ~modules ~top_sorted_modules ~ext_obj () = let modules = Modules.impl_only modules in - { obj_dir; modules; top_sorted_modules; ext_obj } + let excluded_modules = Module_name.Set.of_list excluded_modules in + { obj_dir; modules; top_sorted_modules; ext_obj; excluded_modules } let objects_and_cms t ~mode modules = let kind = Mode.cm_kind mode in + let modules = filter_excluded_modules t modules in let cm_files = Obj_dir.Module.L.cm_files t.obj_dir modules ~kind in match mode with | Byte -> cm_files @@ -25,8 +33,11 @@ let unsorted_objects_and_cms t ~mode = objects_and_cms t ~mode t.modules let top_sorted_cms t ~mode = let kind = Mode.cm_kind mode in - Action_builder.map t.top_sorted_modules - ~f:(Obj_dir.Module.L.cm_files t.obj_dir ~kind) + Action_builder.map t.top_sorted_modules ~f:(fun modules -> + let modules = filter_excluded_modules t modules in + Obj_dir.Module.L.cm_files t.obj_dir ~kind modules) let top_sorted_objects_and_cms t ~mode = - Action_builder.map t.top_sorted_modules ~f:(objects_and_cms t ~mode) + Action_builder.map t.top_sorted_modules ~f:(fun modules -> + let modules = filter_excluded_modules t modules in + objects_and_cms t ~mode modules) diff --git a/src/dune_rules/cm_files.mli b/src/dune_rules/cm_files.mli index fc8990cd505..33974e4ce09 100644 --- a/src/dune_rules/cm_files.mli +++ b/src/dune_rules/cm_files.mli @@ -8,10 +8,12 @@ open Stdune type t val make : - obj_dir:Path.Build.t Obj_dir.t + ?excluded_modules:Module_name.t list + -> obj_dir:Path.Build.t Obj_dir.t -> modules:Modules.t -> top_sorted_modules:Module.t list Action_builder.t -> ext_obj:string + -> unit -> t val unsorted_objects_and_cms : t -> mode:Mode.t -> Path.t list diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index 41dfb44a8ed..fd09876988a 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -114,14 +114,24 @@ module Stanza_util = struct List.map lst ~f:(fun lib -> Lib_dep.Direct (loc, Lib_name.of_string lib)) + let type_gen_script_module ctypes = + type_gen_script ctypes |> Module_name.of_string + + let function_gen_script_module ctypes = + function_gen_script ctypes |> Module_name.of_string + let generated_modules ctypes = - [ type_gen_script ctypes |> Module_name.of_string - ; function_gen_script ctypes |> Module_name.of_string + [ type_gen_script_module ctypes + ; function_gen_script_module ctypes ; c_generated_functions_module ctypes ; c_generated_types_module ctypes ; c_types_includer_module ctypes ; entry_module ctypes ] + let non_installable_modules ctypes = + [ type_gen_script_module ctypes + ; function_gen_script_module ctypes ] + let generated_ml_and_c_files ctypes = let ml_files = generated_modules ctypes @@ -136,6 +146,7 @@ module Stanza_util = struct end let generated_ml_and_c_files = Stanza_util.generated_ml_and_c_files +let non_installable_modules = Stanza_util.non_installable_modules let ml_of_module_name mn = Module_name.to_string mn ^ ".ml" diff --git a/src/dune_rules/ctypes_rules.mli b/src/dune_rules/ctypes_rules.mli index 8ac2071772b..e1666f5762c 100644 --- a/src/dune_rules/ctypes_rules.mli +++ b/src/dune_rules/ctypes_rules.mli @@ -5,6 +5,8 @@ module Ctypes = Dune_file.Ctypes val generated_ml_and_c_files : Ctypes.t -> string list +val non_installable_modules : Ctypes.t -> Module_name.t list + val gen_rules : dep_graphs:Dep_graph.t Ml_kind.Dict.t -> cctx:Compilation_context.t diff --git a/src/dune_rules/exe.ml b/src/dune_rules/exe.ml index be375516c6f..a1f2fab0b1f 100644 --- a/src/dune_rules/exe.ml +++ b/src/dune_rules/exe.ml @@ -233,7 +233,7 @@ let link_many ?link_args ?o_files ?(embed_in_plugin_libraries=[]) ~dep_graphs Dep_graph.top_closed_implementations dep_graphs.impl [ main ] in Cm_files.make ~obj_dir ~modules ~top_sorted_modules - ~ext_obj:ctx.lib_config.ext_obj + ~ext_obj:ctx.lib_config.ext_obj () in List.iter linkages ~f:(fun linkage -> if linkage = Linkage.js then diff --git a/src/dune_rules/lib_rules.ml b/src/dune_rules/lib_rules.ml index 29ea666ebbc..f24dee6e93b 100644 --- a/src/dune_rules/lib_rules.ml +++ b/src/dune_rules/lib_rules.ml @@ -318,12 +318,21 @@ let setup_build_archives (lib : Dune_file.Library.t) ~cctx let lib_info = Library.to_lib_info lib ~dir ~lib_config in Lib_info.eval_native_archives_exn lib_info ~modules:(Some modules) in - (let cm_files = - Cm_files.make ~obj_dir ~ext_obj ~modules ~top_sorted_modules - in - Mode.Dict.Set.iter modes ~f:(fun mode -> - build_lib lib ~native_archives ~dir ~sctx ~expander ~flags ~mode - ~cm_files ~scope)); + let () = + let cm_files = + let excluded_modules = + (* ctypes type_gen and function_gen scripts should not be included in the + library. Otherwise they will spew stuff to stdout on library load. *) + match lib.buildable.ctypes with + | Some ctypes -> Ctypes_rules.non_installable_modules ctypes + | None -> [] + in + Cm_files.make ~excluded_modules ~obj_dir ~ext_obj ~modules ~top_sorted_modules () + in + Mode.Dict.Set.iter modes ~f:(fun mode -> + build_lib lib ~native_archives ~dir ~sctx ~expander ~flags ~mode + ~cm_files ~scope) + in (* Build *.cma.js *) if modes.byte then Super_context.add_rules sctx ~dir From 33b73de43207df70a4521f580d1b7ca24f7468aa Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Sat, 24 Apr 2021 08:52:42 -0700 Subject: [PATCH 42/69] ctypes doc fix --- doc/foreign-code.rst | 20 ++++++++++---------- 1 file changed, 10 insertions(+), 10 deletions(-) diff --git a/doc/foreign-code.rst b/doc/foreign-code.rst index 7f4ff7bb571..e453c073296 100644 --- a/doc/foreign-code.rst +++ b/doc/foreign-code.rst @@ -72,8 +72,8 @@ libraries without writing any C code. You need only provide two OCaml modules, named ``Type_descriptions`` and ``Function_descriptions`` which describe the types, values and functions you -want to access in the C library from OCaml. Additionally, you must list C -any headers and a method for resolving build and link flags. +want to access in the C library from OCaml. Additionally, you must list +any C headers and a method for resolving build and link flags. If you're binding a library distributed by your OS, you can use the ``pkg-config`` utility to resolve any build and link flags. Alternatively, @@ -85,14 +85,14 @@ provide the flags manually. (executable (name foo) (libraries core) - (flags (:standard -w -9-27)) - (ctypes - (external_library_name libfoo) - (build_flags_resolver pkg_config) - (headers (include "foo.h")) - (type_descriptions Type_descriptions) - (function_descriptions Function_descriptions) - (generated_entry_point C))) + (flags (:standard -w -9-27)) + (ctypes + (external_library_name libfoo) + (build_flags_resolver pkg_config) + (headers (include "foo.h")) + (type_descriptions Type_descriptions) + (function_descriptions Function_descriptions) + (generated_entry_point C))) This stanza will introduce a module named ``C`` into your project, with the sub-modules ``Types`` and ``Functions`` that will have your fully bound C From efcb33a8e55939b1a23cdf24bcab1b6c8f6cea61 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Wed, 28 Apr 2021 13:23:29 -0700 Subject: [PATCH 43/69] support repeated function_description stanzas --- src/dune_rules/ctypes_rules.ml | 178 ++++++++++-------- src/dune_rules/ctypes_stubs.ml | 13 +- src/dune_rules/ctypes_stubs.mli | 8 +- src/dune_rules/dune_file.ml | 59 ++++-- src/dune_rules/dune_file.mli | 18 +- .../test-cases/ctypes/exe-vendored.t/dune | 8 +- ...escriptions.ml => function_description.ml} | 0 ...pe_descriptions.ml => type_description.ml} | 0 .../ctypes/lib-vendored.t/stubgen/dune | 8 +- ...escriptions.ml => function_description.ml} | 0 ...pe_descriptions.ml => type_description.ml} | 0 11 files changed, 188 insertions(+), 104 deletions(-) rename test/blackbox-tests/test-cases/ctypes/exe-vendored.t/{function_descriptions.ml => function_description.ml} (100%) rename test/blackbox-tests/test-cases/ctypes/exe-vendored.t/{type_descriptions.ml => type_description.ml} (100%) rename test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/{function_descriptions.ml => function_description.ml} (100%) rename test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/{type_descriptions.ml => type_description.ml} (100%) diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index fd09876988a..9e1d10ff452 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -69,14 +69,19 @@ module Stanza_util = struct let type_gen_script ctypes = sprintf "%s__type_gen" ctypes.Ctypes.external_library_name - let function_gen_script ctypes = - sprintf "%s__function_gen" ctypes.Ctypes.external_library_name + let module_name_lower_string module_name = + String.lowercase (Module_name.to_string module_name) - let type_description_module ctypes = - ctypes.Ctypes.type_descriptions + let function_gen_script ctypes fd = + sprintf "%s__function_gen__%s__%s" ctypes.Ctypes.external_library_name + (module_name_lower_string fd.Ctypes.Function_description.functor_) + (module_name_lower_string fd.Ctypes.Function_description.instance) - let function_description_module ctypes = - ctypes.Ctypes.function_descriptions + let type_description_functor ctypes = + ctypes.Ctypes.type_description.functor_ + + let type_description_instance ctypes = + ctypes.Ctypes.type_description.instance let entry_module ctypes = ctypes.Ctypes.generated_entry_point @@ -92,8 +97,11 @@ module Stanza_util = struct sprintf "%s__c_generated_types" ctypes.Ctypes.external_library_name |> Module_name.of_string - let c_generated_functions_module ctypes = - sprintf "%s__c_generated_functions" ctypes.Ctypes.external_library_name + let c_generated_functions_module ctypes fd = + sprintf "%s__c_generated_functions__%s__%s" + ctypes.Ctypes.external_library_name + (module_name_lower_string fd.Ctypes.Function_description.functor_) + (module_name_lower_string fd.Ctypes.Function_description.instance) |> Module_name.of_string (* This includer module is simply some glue to instantiate the Types functor @@ -101,14 +109,11 @@ module Stanza_util = struct let c_types_includer_module ctypes = ctypes.Ctypes.generated_types - let c_generated_types_cout_c ctypes = - sprintf "%s__c_cout_generated_types.c" ctypes.Ctypes.external_library_name - - let c_generated_types_cout_exe ctypes = - sprintf "%s__c_cout_generated_types.exe" ctypes.Ctypes.external_library_name - - let c_generated_functions_cout_c ctypes = - sprintf "%s__c_cout_generated_functions.c" ctypes.Ctypes.external_library_name + let c_generated_functions_cout_c ctypes fd = + sprintf "%s__c_cout_generated_functions__%s__%s.c" + ctypes.Ctypes.external_library_name + (module_name_lower_string fd.Ctypes.Function_description.functor_) + (module_name_lower_string fd.Ctypes.Function_description.instance) let lib_deps_of_strings ~loc lst = List.map lst ~f:(fun lib -> @@ -117,20 +122,23 @@ module Stanza_util = struct let type_gen_script_module ctypes = type_gen_script ctypes |> Module_name.of_string - let function_gen_script_module ctypes = - function_gen_script ctypes |> Module_name.of_string + let function_gen_script_module ctypes function_description = + function_gen_script ctypes function_description |> Module_name.of_string let generated_modules ctypes = + List.concat_map ctypes.Ctypes.function_description ~f:(fun function_description -> + [ function_gen_script_module ctypes function_description + ; c_generated_functions_module ctypes function_description ]) + @ [ type_gen_script_module ctypes - ; function_gen_script_module ctypes - ; c_generated_functions_module ctypes ; c_generated_types_module ctypes ; c_types_includer_module ctypes ; entry_module ctypes ] let non_installable_modules ctypes = - [ type_gen_script_module ctypes - ; function_gen_script_module ctypes ] + type_gen_script_module ctypes + :: List.map ctypes.Ctypes.function_description ~f:(fun function_description -> + function_gen_script_module ctypes function_description) let generated_ml_and_c_files ctypes = let ml_files = @@ -140,7 +148,8 @@ module Stanza_util = struct |> List.map ~f:(fun m -> m ^ ".ml") in let c_files = - [ c_generated_functions_cout_c ctypes ] + List.map ctypes.Ctypes.function_description ~f:(fun fd -> + c_generated_functions_cout_c ctypes fd) in ml_files @ c_files end @@ -169,30 +178,39 @@ let modules_of_list ~dir ~modules = Modules.exe_unwrapped name_map (* Modules.exe_wrapped ~src_dir:dir ~modules:name_map *) -let write_c_types_includer_module ~sctx ~dir ~filename ~type_description_module - ~c_generated_types_module = +let write_c_types_includer_module ~sctx ~dir ~filename + ~type_description_functor ~c_generated_types_module = let path = Path.Build.relative dir filename in let contents = let buf = Buffer.create 1024 in let pr buf fmt = Printf.bprintf buf (fmt ^^ "\n") in pr buf "include %s.Types (%s)" - (Module_name.to_string type_description_module) + (Module_name.to_string type_description_functor) (Module_name.to_string c_generated_types_module); Buffer.contents buf in Super_context.add_rule ~loc:Loc.none sctx ~dir (Action_builder.write_file path contents) -let write_entry_point_module ~sctx ~dir ~filename ~function_description_module - ~c_generated_functions_module ~c_types_includer_module = +let write_entry_point_module ~ctypes ~sctx ~dir ~filename + ~type_description_instance ~function_description + ~c_types_includer_module = let path = Path.Build.relative dir filename in let contents = let buf = Buffer.create 1024 in let pr buf fmt = Printf.bprintf buf (fmt ^^ "\n") in - pr buf "module Types = %s" (Module_name.to_string c_types_includer_module); - pr buf "module Functions = %s.Functions (%s)" - (Module_name.to_string function_description_module) - (Module_name.to_string c_generated_functions_module); + pr buf "module %s = %s" + (Module_name.to_string type_description_instance) + (Module_name.to_string c_types_includer_module); + List.iter function_description ~f:(fun fd -> + let c_generated_functions_module = + Stanza_util.c_generated_functions_module ctypes fd + in + pr buf "module %s = %s.Functions (%s)" + (fd.Ctypes.Function_description.instance |> Module_name.to_string) + (fd.Ctypes.Function_description.functor_ |> Module_name.to_string) + (Module_name.to_string c_generated_functions_module) + ); Buffer.contents buf in Super_context.add_rule ~loc:Loc.none sctx ~dir @@ -239,19 +257,17 @@ let gen_headers headers buf = pr buf " print_endline %S;" s end -let type_gen_gen ~headers ~type_description_module = +let type_gen_gen ~headers ~type_description_functor = let buf = Buffer.create 1024 in let pr buf fmt = Printf.bprintf buf (fmt ^^ "\n") in pr buf "let () ="; gen_headers headers buf; pr buf " Cstubs_structs.write_c Format.std_formatter"; - pr buf " (module %s.Types)" (Module_name.to_string type_description_module); + pr buf " (module %s.Types)" (Module_name.to_string type_description_functor); Buffer.contents buf -let function_gen_gen ~concurrency ~headers ~function_description_module = - let function_description_module = - Module_name.to_string function_description_module - in +let function_gen_gen ~concurrency ~headers ~function_description_functor = + let module_name = Module_name.to_string function_description_functor in let concurrency = match concurrency with | Ctypes.Concurrency_policy.Unlocked -> "Cstubs.unlocked" @@ -267,25 +283,25 @@ let function_gen_gen ~concurrency ~headers ~function_description_module = pr buf " match Sys.argv.(1) with"; pr buf " | \"ml\" ->"; pr buf " Cstubs.write_ml ~concurrency Format.std_formatter ~prefix"; - pr buf " (module %s.Functions)" function_description_module; + pr buf " (module %s.Functions)" module_name; pr buf " | \"c\" ->"; gen_headers headers buf; pr buf " Cstubs.write_c ~concurrency Format.std_formatter ~prefix"; - pr buf " (module %s.Functions)" function_description_module; + pr buf " (module %s.Functions)" module_name; pr buf " | s -> failwith (\"unknown functions \"^s)"; Buffer.contents buf let write_type_gen_script ~headers ~dir ~filename ~sctx - ~type_description_module = + ~type_description_functor = let path = Path.Build.relative dir filename in - let script = type_gen_gen ~headers ~type_description_module in + let script = type_gen_gen ~headers ~type_description_functor in Super_context.add_rule ~loc:Loc.none sctx ~dir (Action_builder.write_file path script) let write_function_gen_script ~headers ~sctx ~dir ~name - ~function_description_module ~concurrency = + ~function_description_functor ~concurrency = let path = Path.Build.relative dir (name ^ ".ml") in - let script = function_gen_gen ~concurrency ~headers ~function_description_module in + let script = function_gen_gen ~concurrency ~headers ~function_description_functor in Super_context.add_rule ~loc:Loc.none sctx ~dir (Action_builder.write_file path script) let rule ?(deps=[]) ?stdout_to ?(args=[]) ?(targets=[]) ~exe ~sctx ~dir () = @@ -443,17 +459,14 @@ let write_osl_to_sexp_file ~sctx ~dir ~filename osl = let gen_rules ~dep_graphs ~cctx ~buildable ~loc ~scope ~dir ~sctx = let ctypes = Option.value_exn buildable.Buildable.ctypes in let external_library_name = ctypes.Ctypes.external_library_name in - let type_description_module = Stanza_util.type_description_module ctypes in - let function_description_module = Stanza_util.function_description_module ctypes in + let type_description_functor = Stanza_util.type_description_functor ctypes in let c_types_includer_module = Stanza_util.c_types_includer_module ctypes in let c_generated_types_module = Stanza_util.c_generated_types_module ctypes in let rule = rule ~sctx ~dir in let () = write_c_types_includer_module - ~sctx ~dir - ~filename:(ml_of_module_name c_types_includer_module) - ~c_generated_types_module - ~type_description_module + ~sctx ~dir ~filename:(ml_of_module_name c_types_includer_module) + ~c_generated_types_module ~type_description_functor in (* The output of this process is to generate a cflags sexp and a c library flags sexp file. We can probe these flags by using the system pkg-config, @@ -498,15 +511,15 @@ let gen_rules ~dep_graphs ~cctx ~buildable ~loc ~scope ~dir ~sctx = data/types produced in this step. *) let () = let c_generated_types_cout_c = - Stanza_util.c_generated_types_cout_c ctypes + sprintf "%s__c_cout_generated_types.c" external_library_name in let c_generated_types_cout_exe = - Stanza_util.c_generated_types_cout_exe ctypes + sprintf "%s__c_cout_generated_types.exe" external_library_name in let type_gen_script = Stanza_util.type_gen_script ctypes in write_type_gen_script ~headers ~sctx ~dir ~filename:(type_gen_script ^ ".ml") - ~type_description_module; + ~type_description_functor; exe_link_only type_gen_script; rule ~stdout_to:c_generated_types_cout_c @@ -524,36 +537,43 @@ let gen_rules ~dep_graphs ~cctx ~buildable ~loc ~scope ~dir ~sctx = in (* Function_gen is similar to type_gen above, though it produces both an .ml file and a .c file. These files correspond to the files you would - have to write by hand to wrap C code (if ctypes didn't exist!) *) + have to write by hand to wrap C code (if ctypes didn't exist!) + + Also the user can repeat the 'function_description' stanza to do this + more than once. This is needed for generating blocking and non-blocking + sets of functions, for example, which requires a different 'concurrency' + parameter in the code generator. *) let () = - let stubs_prefix = external_library_name ^ "_stubs" in - let c_generated_functions_cout_c = - Stanza_util.c_generated_functions_cout_c ctypes - in - let function_gen_script = Stanza_util.function_gen_script ctypes in - write_function_gen_script ~headers ~sctx ~dir - ~name:function_gen_script ~function_description_module - ~concurrency:ctypes.Ctypes.concurrency; - exe_link_only function_gen_script; - rule - ~stdout_to:c_generated_functions_cout_c - ~exe:(function_gen_script ^ ".exe") - ~args:["c"; stubs_prefix] - (); - rule - ~stdout_to:(Stanza_util.c_generated_functions_module ctypes - |> ml_of_module_name) - ~exe:(function_gen_script ^ ".exe") - ~args:["ml"; stubs_prefix] - () + List.iter ctypes.Ctypes.function_description ~f:(fun fd -> + let stubs_prefix = external_library_name ^ "_stubs" in + let c_generated_functions_cout_c = + Stanza_util.c_generated_functions_cout_c ctypes fd + in + let function_gen_script = Stanza_util.function_gen_script ctypes fd in + write_function_gen_script ~headers ~sctx ~dir + ~name:function_gen_script + ~concurrency:fd.Ctypes.Function_description.concurrency + ~function_description_functor:fd.Ctypes.Function_description.functor_; + exe_link_only function_gen_script; + rule + ~stdout_to:c_generated_functions_cout_c + ~exe:(function_gen_script ^ ".exe") + ~args:["c"; stubs_prefix] + (); + rule + ~stdout_to:(Stanza_util.c_generated_functions_module ctypes fd + |> ml_of_module_name) + ~exe:(function_gen_script ^ ".exe") + ~args:["ml"; stubs_prefix] + () + ) in (* The entry point module binds the instantiated Types and Functions functors - to the entry point module name the user specified. *) - write_entry_point_module - ~sctx ~dir + to the entry point module name and instances the user specified. *) + write_entry_point_module ~ctypes ~sctx ~dir ~filename:(generated_entry_module |> ml_of_module_name) - ~function_description_module:(Stanza_util.function_description_module ctypes) - ~c_generated_functions_module:(Stanza_util.c_generated_functions_module ctypes) + ~type_description_instance:(Stanza_util.type_description_instance ctypes) + ~function_description:ctypes.Ctypes.function_description ~c_types_includer_module let ctypes_cclib_flags ~standard ~scope ~expander ~buildable = diff --git a/src/dune_rules/ctypes_stubs.ml b/src/dune_rules/ctypes_stubs.ml index dc12f3b6edb..c5e87bcdabb 100644 --- a/src/dune_rules/ctypes_stubs.ml +++ b/src/dune_rules/ctypes_stubs.ml @@ -4,8 +4,11 @@ open! Stdune let cflags_sexp ~external_library_name = sprintf "%s__c_flags.sexp" external_library_name -let c_generated_functions_cout_no_ext ~external_library_name = - sprintf "%s__c_cout_generated_functions" external_library_name +let c_generated_functions_cout_no_ext ~external_library_name + ~functor_ ~instance = + sprintf "%s__c_cout_generated_functions__%s__%s" external_library_name + (Module_name.to_string functor_ |> String.lowercase) + (Module_name.to_string instance |> String.lowercase) let c_library_flags ~external_library_name = sprintf "%s__c_library_flags.sexp" external_library_name @@ -18,12 +21,14 @@ let libraries_needed_for_ctypes ~loc = let libraries = ["ctypes"; "ctypes.stubs"] in lib_deps_of_strings ~loc libraries -let add ~loc ~parsing_context ~external_library_name ~add_stubs ~foreign_stubs = +let add ~loc ~parsing_context ~external_library_name ~add_stubs ~functor_ + ~instance ~foreign_stubs = add_stubs Foreign_language.C ~loc ~names:(Some (Ordered_set_lang.of_atoms ~loc - [c_generated_functions_cout_no_ext ~external_library_name])) + [c_generated_functions_cout_no_ext ~external_library_name + ~functor_ ~instance])) ~flags:(Some (Ordered_set_lang.Unexpanded.include_single ~context:parsing_context ~pos:("", 0, 0, 0) (cflags_sexp ~external_library_name))) diff --git a/src/dune_rules/ctypes_stubs.mli b/src/dune_rules/ctypes_stubs.mli index 43d64085d6f..6331a70b86c 100644 --- a/src/dune_rules/ctypes_stubs.mli +++ b/src/dune_rules/ctypes_stubs.mli @@ -8,7 +8,11 @@ val cflags_sexp : external_library_name:string -> string val c_library_flags : external_library_name:string -> string -val c_generated_functions_cout_no_ext : external_library_name:string -> string +val c_generated_functions_cout_no_ext : + external_library_name:string + -> functor_:Module_name.t + -> instance:Module_name.t + -> string val libraries_needed_for_ctypes : loc:Loc.t -> Lib_dep.t list @@ -22,5 +26,7 @@ val add : -> flags:Ordered_set_lang.Unexpanded.t option -> Foreign.Stubs.t list -> Foreign.Stubs.t list) + -> functor_:Module_name.t + -> instance:Module_name.t -> foreign_stubs:Foreign.Stubs.t list -> Foreign.Stubs.t list diff --git a/src/dune_rules/dune_file.ml b/src/dune_rules/dune_file.ml index ad5874a4d43..ce9b2e36c9e 100644 --- a/src/dune_rules/dune_file.ml +++ b/src/dune_rules/dune_file.ml @@ -111,13 +111,44 @@ module Ctypes = struct let default = Include [] end + module Type_description = struct + type t = + { functor_ : Module_name.t + ; instance : Module_name.t } + + let decode = + let open Dune_lang.Decoder in + fields + (let+ functor_ = field "functor" Module_name.decode + and+ instance = field "instance" Module_name.decode + in + { functor_; instance }) + end + + module Function_description = struct + type t = + { concurrency : Concurrency_policy.t + ; functor_ : Module_name.t + ; instance : Module_name.t } + + let decode = + let open Dune_lang.Decoder in + fields + (let+ concurrency = field_o "concurrency" Concurrency_policy.decode + and+ functor_ = field "functor" Module_name.decode + and+ instance = field "instance" Module_name.decode + in + { concurrency = Option.value concurrency ~default:Concurrency_policy.default + ; functor_ + ; instance }) + end + type t = { external_library_name : string ; build_flags_resolver : Build_flags_resolver.t ; headers : Headers.t - ; concurrency : Concurrency_policy.t - ; type_descriptions : Module_name.t - ; function_descriptions : Module_name.t + ; type_description : Type_description.t + ; function_description : Function_description.t list ; generated_types : Module_name.t ; generated_entry_point : Module_name.t } @@ -134,19 +165,17 @@ module Ctypes = struct fields (let+ external_library_name = field "external_library_name" string and+ build_flags_resolver = field_o "build_flags_resolver" Build_flags_resolver.decode + and+ type_description = field "type_description" Type_description.decode + and+ function_description = multi_field "function_description" Function_description.decode and+ headers = field_o "headers" Headers.decode - and+ concurrency = field_o "concurrency" Concurrency_policy.decode - and+ type_descriptions = field "type_descriptions" Module_name.decode - and+ function_descriptions = field "function_descriptions" Module_name.decode and+ generated_types = field_o "generated_types" Module_name.decode and+ generated_entry_point = field "generated_entry_point" Module_name.decode in { external_library_name ; build_flags_resolver = Option.value build_flags_resolver ~default:Build_flags_resolver.default ; headers = Option.value headers ~default:Headers.default - ; concurrency = Option.value concurrency ~default:Concurrency_policy.default - ; type_descriptions - ; function_descriptions + ; type_description + ; function_description ; generated_types = Option.value generated_types ~default:(Module_name.of_string "Types_generated") ; generated_entry_point }) @@ -407,10 +436,14 @@ module Buildable = struct match ctypes with | None -> foreign_stubs | Some ctypes -> - Ctypes_stubs.add ~loc - ~parsing_context:(Dune_project.parsing_context project) - ~external_library_name:ctypes.Ctypes.external_library_name - ~add_stubs ~foreign_stubs + let init = foreign_stubs in + List.fold_left ctypes.function_description ~init ~f:(fun foreign_stubs fd -> + Ctypes_stubs.add ~loc + ~parsing_context:(Dune_project.parsing_context project) + ~external_library_name:ctypes.Ctypes.external_library_name + ~functor_:fd.Ctypes.Function_description.functor_ + ~instance:fd.Ctypes.Function_description.instance + ~add_stubs ~foreign_stubs) in let foreign_archives = Option.value ~default:[] foreign_archives in let foreign_archives = diff --git a/src/dune_rules/dune_file.mli b/src/dune_rules/dune_file.mli index f79a6eba3a2..bcbe47e56c1 100644 --- a/src/dune_rules/dune_file.mli +++ b/src/dune_rules/dune_file.mli @@ -59,13 +59,25 @@ module Ctypes : sig | Preamble of string end + module Type_description : sig + type t = + { functor_ : Module_name.t + ; instance : Module_name.t } + end + + module Function_description : sig + type t = + { concurrency : Concurrency_policy.t + ; functor_ : Module_name.t + ; instance : Module_name.t } + end + type t = { external_library_name : string ; build_flags_resolver : Build_flags_resolver.t ; headers : Headers.t - ; concurrency : Concurrency_policy.t - ; type_descriptions : Module_name.t - ; function_descriptions : Module_name.t + ; type_description : Type_description.t + ; function_description : Function_description.t list ; generated_types : Module_name.t ; generated_entry_point : Module_name.t } type Stanza.t += T of t diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/dune b/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/dune index eaeb8c15bf3..55faa272b34 100644 --- a/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/dune +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/dune @@ -18,6 +18,10 @@ (vendored (c_flags "-Ivendor"))) (headers (include "example.h")) - (type_descriptions Type_descriptions) - (function_descriptions Function_descriptions) + (type_description + (instance Types) + (functor Type_description)) + (function_description + (instance Functions) + (functor Function_description)) (generated_entry_point C))) diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/function_descriptions.ml b/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/function_description.ml similarity index 100% rename from test/blackbox-tests/test-cases/ctypes/exe-vendored.t/function_descriptions.ml rename to test/blackbox-tests/test-cases/ctypes/exe-vendored.t/function_description.ml diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/type_descriptions.ml b/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/type_description.ml similarity index 100% rename from test/blackbox-tests/test-cases/ctypes/exe-vendored.t/type_descriptions.ml rename to test/blackbox-tests/test-cases/ctypes/exe-vendored.t/type_description.ml diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/dune b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/dune index aabb5850204..b847ea32c37 100644 --- a/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/dune +++ b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/dune @@ -20,6 +20,10 @@ ; relative directories. Is there a cleaner way to do this? (c_flags ("-Istubgen/vendor" "-Ivendor")))) (headers (include "example.h")) - (type_descriptions Type_descriptions) - (function_descriptions Function_descriptions) + (type_description + (instance Types) + (functor Type_description)) + (function_description + (instance Functions) + (functor Function_description)) (generated_entry_point C))) diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/function_descriptions.ml b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/function_description.ml similarity index 100% rename from test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/function_descriptions.ml rename to test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/function_description.ml diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/type_descriptions.ml b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/type_description.ml similarity index 100% rename from test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/type_descriptions.ml rename to test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/type_description.ml From 4f535b8d2ed93293a4670e4c08eb93d25cf1a812 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Wed, 28 Apr 2021 19:51:23 -0700 Subject: [PATCH 44/69] list ctypes in CHANGES.md --- CHANGES.md | 3 +++ 1 file changed, 3 insertions(+) diff --git a/CHANGES.md b/CHANGES.md index c6e1c1ecf9a..cce2397f8e7 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -92,6 +92,9 @@ Unreleased - If an .ml file is not used by an executable, Dune no longer report parsing error in this file (#...., @jeremiedimino) +- Experimental ctypes support (#3905, fixes #135, @mbacarella) + + 2.8.2 (21/01/2021) ------------------ From 99aca83648677d4689c77e3bc84c8a28e095cb40 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Wed, 19 May 2021 09:55:31 -0700 Subject: [PATCH 45/69] fix descriptions --- doc/foreign-code.rst | 17 +++++++++++++---- 1 file changed, 13 insertions(+), 4 deletions(-) diff --git a/doc/foreign-code.rst b/doc/foreign-code.rst index e453c073296..3f7d18e8305 100644 --- a/doc/foreign-code.rst +++ b/doc/foreign-code.rst @@ -70,8 +70,8 @@ Support for ctypes stub generation It is possible to use the ``ctypes`` stanza to generate bindings for C libraries without writing any C code. -You need only provide two OCaml modules, named ``Type_descriptions`` and -``Function_descriptions`` which describe the types, values and functions you +You need only provide two OCaml modules, named ``Type_description`` and +``Function_description`` which describe the types, values and functions you want to access in the C library from OCaml. Additionally, you must list any C headers and a method for resolving build and link flags. @@ -80,6 +80,10 @@ If you're binding a library distributed by your OS, you can use the if you're using a locally installed library or a vendored library, you can provide the flags manually. +The ``Type_description`` module must define a functor named ``Types`` with +signature ``Ctypes.TYPE``. The ``Function_description`` module must define +a functor named ``Functions`` with signature ``Ctypes.FOREIGN``. + .. code:: scheme (executable @@ -90,8 +94,13 @@ provide the flags manually. (external_library_name libfoo) (build_flags_resolver pkg_config) (headers (include "foo.h")) - (type_descriptions Type_descriptions) - (function_descriptions Function_descriptions) + (type_description + (instance Types) + (functor Type_description)) + (function_description + (concurrency unlocked) + (instance Functions) + (functor Function_description)) (generated_entry_point C))) This stanza will introduce a module named ``C`` into your project, with the From e25db44f4359439a5497253bcf5ef70c8c34468e Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Thu, 20 May 2021 11:36:31 -0700 Subject: [PATCH 46/69] fix accidentally calling build_all twice --- src/dune_rules/exe.ml | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/dune_rules/exe.ml b/src/dune_rules/exe.ml index 4906893de69..75400d1dbf9 100644 --- a/src/dune_rules/exe.ml +++ b/src/dune_rules/exe.ml @@ -226,8 +226,7 @@ let link_many ?link_args ?o_files ?(embed_in_plugin_libraries=[]) ~dep_graphs let dep_graphs : Dep_graph.t Ml_kind.Dict.t = dep_graphs in let open Memo.Build.O in let modules = Compilation_context.modules cctx in - let* () = Module_compilation.build_all cctx ~dep_graphs - and* link_time_code_gen = Link_time_code_gen.handle_special_libs cctx in + let* link_time_code_gen = Link_time_code_gen.handle_special_libs cctx in Memo.Build.parallel_iter programs ~f:(fun { Program.name; main_module_name; loc } -> let cm_files = From 233efad6dbf3531fb67c8f4824940c0c52d9b9a1 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Thu, 20 May 2021 11:46:20 -0700 Subject: [PATCH 47/69] fix comment --- src/dune_rules/ctypes_rules.ml | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index 71f70bda959..a282b394fe1 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -8,23 +8,23 @@ open! Stdune Aside from perhaps providing an "header.h" include line, you should be able to wrap an entire C library without writing a single line of C code. - This stanza requires the user to specify the names of 4 modules: + This stanza requires the user to specify the names of 4 (or more) modules: - (type_descriptions Type_descriptions) + (type_description Type_description) (generated_types Types_generated) - (function_descriptions Function_descriptions) - (generated_entry_point C)) + (function_description Function_description) ; can be repeated + (generated_entry_point C) The user must also implement two of the modules: - (1) $type_descriptions.ml musth ave the following top-level functor: + (1) $type_description.ml must have the following top-level functor: module Types (T : Ctypes.TYPE) = struct (* put calls to Ctypes.TYPE.constant and Ctypes.TYPE.typedef here to wrap C constants and structs *) end - (2) $function_descriptions.ml must have the following two definitions: + (2) $function_description.ml must have the following two definitions: modules Types = $generated_types From 746744d2a46daa6f5158792e33513886c9694b70 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Thu, 27 May 2021 06:26:23 -0700 Subject: [PATCH 48/69] re-add PR request number to CHANGES.md entry --- CHANGES.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/CHANGES.md b/CHANGES.md index c1fe5b8e555..9ceae056f45 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -207,7 +207,7 @@ Unreleased bytecode (#4200, @nojb) - If an .ml file is not used by an executable, Dune no longer report - parsing error in this file (#...., @jeremiedimino) + parsing error in this file (#4330, @jeremiedimino) - Experimental ctypes support (#3905, fixes #135, @mbacarella) From 8f3227beca64ccf54618c3c679e4a3c0bd345635 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Thu, 27 May 2021 06:28:48 -0700 Subject: [PATCH 49/69] extension appears in dune 3.0 lang --- src/dune_rules/dune_file.ml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/dune_rules/dune_file.ml b/src/dune_rules/dune_file.ml index b29d4d9f9f3..4d3642e53e6 100644 --- a/src/dune_rules/dune_file.ml +++ b/src/dune_rules/dune_file.ml @@ -158,7 +158,7 @@ module Ctypes = struct let syntax = Dune_lang.Syntax.create ~name ~desc:"the ctypes extension" - [ ((0, 1), `Since (2, 8)) ] + [ ((0, 1), `Since (3, 0)) ] let decode = let open Dune_lang.Decoder in From 550e56f5d8fe48cc13479134bd14a2611f9185cb Mon Sep 17 00:00:00 2001 From: Rudi Grinberg Date: Mon, 19 Jul 2021 18:50:43 -0700 Subject: [PATCH 50/69] Small doc tweak Signed-off-by: Rudi Grinberg --- doc/foreign-code.rst | 48 +++++++++++++++++++++++--------------------- 1 file changed, 25 insertions(+), 23 deletions(-) diff --git a/doc/foreign-code.rst b/doc/foreign-code.rst index 3f7d18e8305..4c38c83f6a7 100644 --- a/doc/foreign-code.rst +++ b/doc/foreign-code.rst @@ -64,44 +64,44 @@ without the ``.h`` extension. When a library install header files, these are made visible to users of the library via the include search path. -Support for ctypes stub generation ----------------------------------- +Stub Generation with Ctypes +--------------------------- -It is possible to use the ``ctypes`` stanza to generate bindings for C -libraries without writing any C code. +It is possible to use the ctypes_ stanza to generate bindings for C libraries +without writing any C code. You need only provide two OCaml modules, named ``Type_description`` and ``Function_description`` which describe the types, values and functions you -want to access in the C library from OCaml. Additionally, you must list -any C headers and a method for resolving build and link flags. +want to access in the C library from OCaml. Additionally, you must list any C +headers and a method for resolving build and link flags. If you're binding a library distributed by your OS, you can use the -``pkg-config`` utility to resolve any build and link flags. Alternatively, -if you're using a locally installed library or a vendored library, you can -provide the flags manually. +``pkg-config`` utility to resolve any build and link flags. Alternatively, if +you're using a locally installed library or a vendored library, you can provide +the flags manually. The ``Type_description`` module must define a functor named ``Types`` with -signature ``Ctypes.TYPE``. The ``Function_description`` module must define -a functor named ``Functions`` with signature ``Ctypes.FOREIGN``. +signature ``Ctypes.TYPE``. The ``Function_description`` module must define a +functor named ``Functions`` with signature ``Ctypes.FOREIGN``. .. code:: scheme - (executable + (executable (name foo) (libraries core) (flags (:standard -w -9-27)) (ctypes - (external_library_name libfoo) - (build_flags_resolver pkg_config) - (headers (include "foo.h")) - (type_description - (instance Types) - (functor Type_description)) - (function_description - (concurrency unlocked) - (instance Functions) - (functor Function_description)) - (generated_entry_point C))) + (external_library_name libfoo) + (build_flags_resolver pkg_config) + (headers (include "foo.h")) + (type_description + (instance Types) + (functor Type_description)) + (function_description + (concurrency unlocked) + (instance Functions) + (functor Function_description)) + (generated_entry_point C))) This stanza will introduce a module named ``C`` into your project, with the sub-modules ``Types`` and ``Functions`` that will have your fully bound C @@ -193,3 +193,5 @@ The `re2 project `_ uses this method to build the re2 C library. You can look at the file ``re2/src/re2_c/dune`` in this project to see a full working example. + +.. _ctypes: https://github.com/ocamllabs/ocaml-ctypes From 8ed91d0236a53446ce4f3ceb4da7d0b380e3d986 Mon Sep 17 00:00:00 2001 From: Rudi Grinberg Date: Mon, 19 Jul 2021 21:11:13 -0700 Subject: [PATCH 51/69] Move Dune_file.Ctypes to own module Signed-off-by: Rudi Grinberg --- src/dune_rules/ctypes_rules.ml | 4 +- src/dune_rules/ctypes_rules.mli | 6 +- src/dune_rules/ctypes_stanza.ml | 141 ++++++++++++++++++++++++++++ src/dune_rules/ctypes_stanza.mli | 55 +++++++++++ src/dune_rules/dune_file.ml | 153 ++----------------------------- src/dune_rules/dune_file.mli | 54 +---------- 6 files changed, 208 insertions(+), 205 deletions(-) create mode 100644 src/dune_rules/ctypes_stanza.ml create mode 100644 src/dune_rules/ctypes_stanza.mli diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index a282b394fe1..b8fe459ab1c 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -57,7 +57,7 @@ open! Stdune module Buildable = Dune_file.Buildable module Library = Dune_file.Library -module Ctypes = Dune_file.Ctypes +module Ctypes = Ctypes_stanza module Stanza_util = struct @@ -610,7 +610,7 @@ let ctypes_cclib_flags ~standard ~scope ~expander ~buildable = let ctypes_c_library_flags = let path_to_sexp_file = Ctypes_stubs.c_library_flags - ~external_library_name:ctypes.Dune_file.Ctypes.external_library_name + ~external_library_name:ctypes.Ctypes.external_library_name in let parsing_context = let project = Scope.project scope in diff --git a/src/dune_rules/ctypes_rules.mli b/src/dune_rules/ctypes_rules.mli index 85c92999974..0eb2bcc3469 100644 --- a/src/dune_rules/ctypes_rules.mli +++ b/src/dune_rules/ctypes_rules.mli @@ -1,11 +1,9 @@ open! Dune_engine open Import -module Ctypes = Dune_file.Ctypes +val generated_ml_and_c_files : Ctypes_stanza.t -> string list -val generated_ml_and_c_files : Ctypes.t -> string list - -val non_installable_modules : Ctypes.t -> Module_name.t list +val non_installable_modules : Ctypes_stanza.t -> Module_name.t list val gen_rules : dep_graphs:Dep_graph.t Ml_kind.Dict.t diff --git a/src/dune_rules/ctypes_stanza.ml b/src/dune_rules/ctypes_stanza.ml new file mode 100644 index 00000000000..a291fd21f44 --- /dev/null +++ b/src/dune_rules/ctypes_stanza.ml @@ -0,0 +1,141 @@ +open! Stdune +open Import +open Dune_lang.Decoder + +module Build_flags_resolver = struct + + module Vendored = struct + type t = + { c_flags : Ordered_set_lang.Unexpanded.t + ; c_library_flags : Ordered_set_lang.Unexpanded.t } + + let decode = + fields + (let+ c_flags = Ordered_set_lang.Unexpanded.field "c_flags" + and+ c_library_flags = Ordered_set_lang.Unexpanded.field "c_library_flags" in + { c_flags; c_library_flags }) + end + + type t = + | Pkg_config + | Vendored of Vendored.t + + let decode = + let vendored = + let+ p = Vendored.decode in + Vendored p + in + sum [ ("pkg_config" , return Pkg_config) + ; ("vendored" , vendored ) ] + + let default = Pkg_config +end + +module Concurrency_policy = struct + type t = + | Sequential + | Unlocked + | Lwt_jobs + | Lwt_preemptive + + let decode = + enum [ "sequential" , Sequential + ; "unlocked" , Unlocked + ; "lwt_jobs" , Lwt_jobs + ; "lwt_preemptive" , Lwt_preemptive ] + + let default = Sequential +end + +module Headers = struct + type t = + | Include of string list + | Preamble of string + + let decode = + let include_ = + let+ s = repeat string in + Include s + in + let preamble = + let+ p = string in + Preamble p + in + sum [ ("include" , include_) + ; ("preamble" , preamble) ] + + let default = Include [] +end + +module Type_description = struct + type t = + { functor_ : Module_name.t + ; instance : Module_name.t } + + let decode = + let open Dune_lang.Decoder in + fields + (let+ functor_ = field "functor" Module_name.decode + and+ instance = field "instance" Module_name.decode + in + { functor_; instance }) +end + +module Function_description = struct + type t = + { concurrency : Concurrency_policy.t + ; functor_ : Module_name.t + ; instance : Module_name.t } + + let decode = + let open Dune_lang.Decoder in + fields + (let+ concurrency = field_o "concurrency" Concurrency_policy.decode + and+ functor_ = field "functor" Module_name.decode + and+ instance = field "instance" Module_name.decode + in + { concurrency = Option.value concurrency ~default:Concurrency_policy.default + ; functor_ + ; instance }) +end + +type t = + { external_library_name : string + ; build_flags_resolver : Build_flags_resolver.t + ; headers : Headers.t + ; type_description : Type_description.t + ; function_description : Function_description.t list + ; generated_types : Module_name.t + ; generated_entry_point : Module_name.t } + +let name = "ctypes" + +type Stanza.t += T of t + +let syntax = + Dune_lang.Syntax.create ~name ~desc:"the ctypes extension" + [ ((0, 1), `Since (3, 0)) ] + +let decode = + let open Dune_lang.Decoder in + fields + (let+ external_library_name = field "external_library_name" string + and+ build_flags_resolver = field_o "build_flags_resolver" Build_flags_resolver.decode + and+ type_description = field "type_description" Type_description.decode + and+ function_description = multi_field "function_description" Function_description.decode + and+ headers = field_o "headers" Headers.decode + and+ generated_types = field_o "generated_types" Module_name.decode + and+ generated_entry_point = field "generated_entry_point" Module_name.decode + in + { external_library_name + ; build_flags_resolver = Option.value build_flags_resolver ~default:Build_flags_resolver.default + ; headers = Option.value headers ~default:Headers.default + ; type_description + ; function_description + ; generated_types = Option.value generated_types ~default:(Module_name.of_string "Types_generated") + ; generated_entry_point }) + +let () = + let open Dune_lang.Decoder in + Dune_project.Extension.register_simple syntax + (return [ (name, decode >>| fun x -> [ T x ]) ]) diff --git a/src/dune_rules/ctypes_stanza.mli b/src/dune_rules/ctypes_stanza.mli new file mode 100644 index 00000000000..946f75769c5 --- /dev/null +++ b/src/dune_rules/ctypes_stanza.mli @@ -0,0 +1,55 @@ +open! Stdune +open Import + +module Build_flags_resolver : sig + module Vendored : sig + type t = + { c_flags : Ordered_set_lang.Unexpanded.t + ; c_library_flags : Ordered_set_lang.Unexpanded.t } + end + type t = + | Pkg_config + | Vendored of Vendored.t +end + +module Concurrency_policy : sig + type t = + | Sequential + | Unlocked + | Lwt_jobs + | Lwt_preemptive +end + +module Headers : sig + type t = + | Include of string list + | Preamble of string +end + +module Type_description : sig + type t = + { functor_ : Module_name.t + ; instance : Module_name.t } +end + +module Function_description : sig + type t = + { concurrency : Concurrency_policy.t + ; functor_ : Module_name.t + ; instance : Module_name.t } +end + +type t = + { external_library_name : string + ; build_flags_resolver : Build_flags_resolver.t + ; headers : Headers.t + ; type_description : Type_description.t + ; function_description : Function_description.t list + ; generated_types : Module_name.t + ; generated_entry_point : Module_name.t } + +type Stanza.t += T of t + +val decode : t Dune_lang.Decoder.t + +val syntax : Dune_lang.Syntax.t diff --git a/src/dune_rules/dune_file.ml b/src/dune_rules/dune_file.ml index 4d3642e53e6..017cb7a4e72 100644 --- a/src/dune_rules/dune_file.ml +++ b/src/dune_rules/dune_file.ml @@ -45,146 +45,6 @@ module Js_of_ocaml = struct { flags = Ordered_set_lang.Unexpanded.standard; javascript_files = [] } end -module Ctypes = struct - module Build_flags_resolver = struct - - module Vendored = struct - type t = - { c_flags : Ordered_set_lang.Unexpanded.t - ; c_library_flags : Ordered_set_lang.Unexpanded.t } - - let decode = - fields - (let+ c_flags = Ordered_set_lang.Unexpanded.field "c_flags" - and+ c_library_flags = Ordered_set_lang.Unexpanded.field "c_library_flags" in - { c_flags; c_library_flags }) - end - - type t = - | Pkg_config - | Vendored of Vendored.t - - let decode = - let vendored = - let+ p = Vendored.decode in - Vendored p - in - sum [ ("pkg_config" , return Pkg_config) - ; ("vendored" , vendored ) ] - - let default = Pkg_config - end - - module Concurrency_policy = struct - type t = - | Sequential - | Unlocked - | Lwt_jobs - | Lwt_preemptive - - let decode = - enum [ "sequential" , Sequential - ; "unlocked" , Unlocked - ; "lwt_jobs" , Lwt_jobs - ; "lwt_preemptive" , Lwt_preemptive ] - - let default = Sequential - end - - module Headers = struct - type t = - | Include of string list - | Preamble of string - - let decode = - let include_ = - let+ s = repeat string in - Include s - in - let preamble = - let+ p = string in - Preamble p - in - sum [ ("include" , include_) - ; ("preamble" , preamble) ] - - let default = Include [] - end - - module Type_description = struct - type t = - { functor_ : Module_name.t - ; instance : Module_name.t } - - let decode = - let open Dune_lang.Decoder in - fields - (let+ functor_ = field "functor" Module_name.decode - and+ instance = field "instance" Module_name.decode - in - { functor_; instance }) - end - - module Function_description = struct - type t = - { concurrency : Concurrency_policy.t - ; functor_ : Module_name.t - ; instance : Module_name.t } - - let decode = - let open Dune_lang.Decoder in - fields - (let+ concurrency = field_o "concurrency" Concurrency_policy.decode - and+ functor_ = field "functor" Module_name.decode - and+ instance = field "instance" Module_name.decode - in - { concurrency = Option.value concurrency ~default:Concurrency_policy.default - ; functor_ - ; instance }) - end - - type t = - { external_library_name : string - ; build_flags_resolver : Build_flags_resolver.t - ; headers : Headers.t - ; type_description : Type_description.t - ; function_description : Function_description.t list - ; generated_types : Module_name.t - ; generated_entry_point : Module_name.t } - - let name = "ctypes" - - type Stanza.t += T of t - - let syntax = - Dune_lang.Syntax.create ~name ~desc:"the ctypes extension" - [ ((0, 1), `Since (3, 0)) ] - - let decode = - let open Dune_lang.Decoder in - fields - (let+ external_library_name = field "external_library_name" string - and+ build_flags_resolver = field_o "build_flags_resolver" Build_flags_resolver.decode - and+ type_description = field "type_description" Type_description.decode - and+ function_description = multi_field "function_description" Function_description.decode - and+ headers = field_o "headers" Headers.decode - and+ generated_types = field_o "generated_types" Module_name.decode - and+ generated_entry_point = field "generated_entry_point" Module_name.decode - in - { external_library_name - ; build_flags_resolver = Option.value build_flags_resolver ~default:Build_flags_resolver.default - ; headers = Option.value headers ~default:Headers.default - ; type_description - ; function_description - ; generated_types = Option.value generated_types ~default:(Module_name.of_string "Types_generated") - ; generated_entry_point }) - - let () = - let open Dune_lang.Decoder in - Dune_project.Extension.register_simple syntax - (return [ (name, decode >>| fun x -> [ T x ]) ]) -end - type for_ = | Executable | Library of Wrapped.t option @@ -301,7 +161,7 @@ module Buildable = struct ; flags : Ocaml_flags.Spec.t ; js_of_ocaml : Js_of_ocaml.t ; allow_overlapping_dependencies : bool - ; ctypes : Ctypes.t option + ; ctypes : Ctypes_stanza.t option ; root_module : (Loc.t * Module_name.t) option } @@ -370,7 +230,8 @@ module Buildable = struct and+ version = Dune_lang.Syntax.get_exn Stanza.syntax and+ ctypes = field_o "ctypes" - (Dune_lang.Syntax.since Ctypes.syntax (0, 1) >>> Ctypes.decode) + (Dune_lang.Syntax.since Ctypes_stanza.syntax (0, 1) + >>> Ctypes_stanza.decode) and+ loc_instrumentation, instrumentation = located (multi_field "instrumentation" @@ -435,14 +296,14 @@ module Buildable = struct let foreign_stubs = match ctypes with | None -> foreign_stubs - | Some ctypes -> + | Some (ctypes : Ctypes_stanza.t) -> let init = foreign_stubs in List.fold_left ctypes.function_description ~init ~f:(fun foreign_stubs fd -> Ctypes_stubs.add ~loc ~parsing_context:(Dune_project.parsing_context project) - ~external_library_name:ctypes.Ctypes.external_library_name - ~functor_:fd.Ctypes.Function_description.functor_ - ~instance:fd.Ctypes.Function_description.instance + ~external_library_name:ctypes.external_library_name + ~functor_:fd.Ctypes_stanza.Function_description.functor_ + ~instance:fd.Ctypes_stanza.Function_description.instance ~add_stubs ~foreign_stubs) in let foreign_archives = Option.value ~default:[] foreign_archives in diff --git a/src/dune_rules/dune_file.mli b/src/dune_rules/dune_file.mli index bcbe47e56c1..185cbbeaed4 100644 --- a/src/dune_rules/dune_file.mli +++ b/src/dune_rules/dune_file.mli @@ -31,58 +31,6 @@ module Lib_deps : sig val decode : for_ -> t Dune_lang.Decoder.t end - -module Ctypes : sig - - module Build_flags_resolver : sig - module Vendored : sig - type t = - { c_flags : Ordered_set_lang.Unexpanded.t - ; c_library_flags : Ordered_set_lang.Unexpanded.t } - end - type t = - | Pkg_config - | Vendored of Vendored.t - end - - module Concurrency_policy : sig - type t = - | Sequential - | Unlocked - | Lwt_jobs - | Lwt_preemptive - end - - module Headers : sig - type t = - | Include of string list - | Preamble of string - end - - module Type_description : sig - type t = - { functor_ : Module_name.t - ; instance : Module_name.t } - end - - module Function_description : sig - type t = - { concurrency : Concurrency_policy.t - ; functor_ : Module_name.t - ; instance : Module_name.t } - end - - type t = - { external_library_name : string - ; build_flags_resolver : Build_flags_resolver.t - ; headers : Headers.t - ; type_description : Type_description.t - ; function_description : Function_description.t list - ; generated_types : Module_name.t - ; generated_entry_point : Module_name.t } - type Stanza.t += T of t -end - (** [preprocess] and [preprocessor_deps] fields *) val preprocess_fields : (Preprocess.Without_instrumentation.t Preprocess.Per_module.t @@ -103,7 +51,7 @@ module Buildable : sig ; flags : Ocaml_flags.Spec.t ; js_of_ocaml : Js_of_ocaml.t ; allow_overlapping_dependencies : bool - ; ctypes : Ctypes.t option + ; ctypes : Ctypes_stanza.t option ; root_module : (Loc.t * Module_name.t) option } From 60d13036d1df97ccc3c72f2696e5f5e2202b804a Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Tue, 20 Jul 2021 07:25:55 -0700 Subject: [PATCH 52/69] did not actually need to add this sub_systems field here --- src/dune_rules/dune_file.ml | 9 --------- src/dune_rules/dune_file.mli | 1 - 2 files changed, 10 deletions(-) diff --git a/src/dune_rules/dune_file.ml b/src/dune_rules/dune_file.ml index 017cb7a4e72..eea1ab14fee 100644 --- a/src/dune_rules/dune_file.ml +++ b/src/dune_rules/dune_file.ml @@ -1381,7 +1381,6 @@ module Executables = struct ; forbidden_libraries : (Loc.t * Lib_name.t) list ; bootstrap_info : string option ; enabled_if : Blang.t - ; sub_systems : Sub_system_info.t Sub_system_name.Map.t ; dune_version : Dune_lang.Syntax.Version.t } @@ -1450,9 +1449,6 @@ module Executables = struct Dune_lang.Syntax.Version.Infix.(syntax_version >= (2, 6)) in Enabled_if.decode ~allowed_vars ~is_error ~since:(Some (2, 3)) () - and+ sub_systems = - let* () = return () in - Sub_system_info.record_parser () in fun names ~multi -> let has_public_name = Names.has_public_name names in @@ -1511,7 +1507,6 @@ module Executables = struct ; bootstrap_info ; enabled_if ; dune_version - ; sub_systems } let single, multi = @@ -1858,9 +1853,6 @@ module Tests = struct ( Dune_lang.Syntax.since Stanza.syntax (2, 0) >>> repeat (located Lib_name.decode) ) ~default:[] - and+ sub_systems = - let* () = return () in - Sub_system_info.record_parser () in { exes = { Executables.link_flags @@ -1877,7 +1869,6 @@ module Tests = struct ; bootstrap_info = None ; enabled_if ; dune_version - ; sub_systems } ; locks ; package diff --git a/src/dune_rules/dune_file.mli b/src/dune_rules/dune_file.mli index 185cbbeaed4..fc572280165 100644 --- a/src/dune_rules/dune_file.mli +++ b/src/dune_rules/dune_file.mli @@ -258,7 +258,6 @@ module Executables : sig ; forbidden_libraries : (Loc.t * Lib_name.t) list ; bootstrap_info : string option ; enabled_if : Blang.t - ; sub_systems : Sub_system_info.t Sub_system_name.Map.t ; dune_version : Dune_lang.Syntax.Version.t } From 35f66b1d77d99336afe5f1ffe957b0422a1d2447 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Tue, 20 Jul 2021 07:26:19 -0700 Subject: [PATCH 53/69] ctypes build tests dune-project 2.8 -> 3.0 --- .../test-cases/ctypes/exe-vendored.t/dune-project | 2 +- .../test-cases/ctypes/lib-vendored.t/dune-project | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/dune-project b/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/dune-project index 776b2190292..4cac8e20f22 100644 --- a/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/dune-project +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/dune-project @@ -1,3 +1,3 @@ -(lang dune 2.8) +(lang dune 3.0) (using ctypes 0.1) (use_standard_c_and_cxx_flags false) diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/dune-project b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/dune-project index 776b2190292..4cac8e20f22 100644 --- a/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/dune-project +++ b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/dune-project @@ -1,3 +1,3 @@ -(lang dune 2.8) +(lang dune 3.0) (using ctypes 0.1) (use_standard_c_and_cxx_flags false) From 3a8d53d0695e78260ed35634732c8dc03123ce73 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Tue, 20 Jul 2021 07:30:34 -0700 Subject: [PATCH 54/69] quick description of each unit test --- .../blackbox-tests/test-cases/ctypes/exe-vendored.t/run.t | 8 ++++++++ .../blackbox-tests/test-cases/ctypes/lib-vendored.t/run.t | 8 ++++++++ 2 files changed, 16 insertions(+) diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/run.t b/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/run.t index efd47f01251..91f09d8ebaf 100644 --- a/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/run.t +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored.t/run.t @@ -1,2 +1,10 @@ +Generate cstubs for a "vendored" library. + +We have a dummy C library hosted entirely in the 'vendor' directory and use +the ctypes instrumentation and description language to generate bindings for +it. + +This is the version that builds into an executable. + $ dune exec ./example.exe 4 diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/run.t b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/run.t index efd47f01251..1b6c02ecefc 100644 --- a/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/run.t +++ b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/run.t @@ -1,2 +1,10 @@ +Generate cstubs for a "vendored" library. + +We have a dummy C library hosted entirely in the 'vendor' directory and use +the ctypes instrumentation and description language to generate bindings for +it. + +This is the version that builds into a library. + $ dune exec ./example.exe 4 From 84ab501f1c32692325fab76f91eab0e5e3312d32 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Tue, 20 Jul 2021 08:47:42 -0700 Subject: [PATCH 55/69] remove whitespace-only changes from PR --- doc/foreign-code.rst | 16 +++++++++++++--- src/dune_rules/dune_file.ml | 11 ++++++----- src/dune_rules/install_rules.ml | 4 ++-- src/dune_rules/modules.ml | 18 ++++++------------ 4 files changed, 27 insertions(+), 22 deletions(-) diff --git a/doc/foreign-code.rst b/doc/foreign-code.rst index 4c38c83f6a7..afa40f2c725 100644 --- a/doc/foreign-code.rst +++ b/doc/foreign-code.rst @@ -67,10 +67,20 @@ path. Stub Generation with Ctypes --------------------------- -It is possible to use the ctypes_ stanza to generate bindings for C libraries -without writing any C code. +Beginning in dune 3.0, it is possible to use the ctypes_ stanza to generate +bindings for C libraries without writing any C code. -You need only provide two OCaml modules, named ``Type_description`` and +To begin, you must declare the ctypes extension in your ``dune-project`` file. + +.. code:: scheme + + (lang dune 3.0) + (using ctypes 0.1) + +Note that dune support for this feature is experimental and is not subject +to backward compatibility guarantees. + +Next, you need only provide two OCaml modules, named ``Type_description`` and ``Function_description`` which describe the types, values and functions you want to access in the C library from OCaml. Additionally, you must list any C headers and a method for resolving build and link flags. diff --git a/src/dune_rules/dune_file.ml b/src/dune_rules/dune_file.ml index eea1ab14fee..1a3db5ce5c6 100644 --- a/src/dune_rules/dune_file.ml +++ b/src/dune_rules/dune_file.ml @@ -1838,7 +1838,8 @@ module Tests = struct and+ link_flags = Ordered_set_lang.Unexpanded.field "link_flags" and+ names = names and+ package = field_o "package" Stanza_common.Pkg.decode - and+ locks = field "locks" (repeat String_with_vars.decode) ~default:[] + and+ locks = + field "locks" (repeat String_with_vars.decode) ~default:[] and+ modes = field "modes" Executables.Link_mode.Map.decode ~default:Executables.Link_mode.Map.default_for_tests @@ -1846,12 +1847,12 @@ module Tests = struct Enabled_if.decode ~allowed_vars:Any ~since:(Some (1, 4)) () and+ action = field_o "action" - ( Dune_lang.Syntax.since ~fatal:false Stanza.syntax (1, 2) - >>> Action_dune_lang.decode ) + (Dune_lang.Syntax.since ~fatal:false Stanza.syntax (1, 2) + >>> Action_dune_lang.decode) and+ forbidden_libraries = field "forbidden_libraries" - ( Dune_lang.Syntax.since Stanza.syntax (2, 0) - >>> repeat (located Lib_name.decode) ) + (Dune_lang.Syntax.since Stanza.syntax (2, 0) + >>> repeat (located Lib_name.decode)) ~default:[] in { exes = diff --git a/src/dune_rules/install_rules.ml b/src/dune_rules/install_rules.ml index 4095dacbbdf..b8c589c76d8 100644 --- a/src/dune_rules/install_rules.ml +++ b/src/dune_rules/install_rules.ml @@ -196,11 +196,11 @@ end = struct List.concat [ sources ; List.map module_files ~f:(fun (sub_dir, file) -> - make_entry ?sub_dir Lib file) + make_entry ?sub_dir Lib file) ; List.map lib_files ~f:(fun (section, file) -> make_entry section file) ; List.map execs ~f:(make_entry Libexec) ; List.map dll_files ~f:(fun a -> - (Some loc, Install.Entry.make Stublibs a)) + (Some loc, Install.Entry.make Stublibs a)) ; List.map ~f:(make_entry Lib) install_c_headers ] diff --git a/src/dune_rules/modules.ml b/src/dune_rules/modules.ml index 6f4c64ec2fb..8b0b19c1946 100644 --- a/src/dune_rules/modules.ml +++ b/src/dune_rules/modules.ml @@ -117,8 +117,7 @@ module Stdlib = struct Module_name.Map.values t.modules |> List.filter ~f:(fun m -> Some (Module.name m) <> t.exit_module) - let find t = - Module_name.Map.find t.modules + let find t = Module_name.Map.find t.modules let find_dep t ~of_ name = let of_name = Module.name of_ in @@ -536,16 +535,11 @@ let impl impl ~vlib = let rec find t name = match t with - | Singleton m -> - Option.some_if (Module.name m = name) m - | Unwrapped m -> - Module_name.Map.find m name - | Stdlib w -> - Stdlib.find w name - | Wrapped w -> - Wrapped.find w name - | Impl { impl; vlib } -> - ( + | Singleton m -> Option.some_if (Module.name m = name) m + | Unwrapped m -> Module_name.Map.find m name + | Stdlib w -> Stdlib.find w name + | Wrapped w -> Wrapped.find w name + | Impl { impl; vlib } -> ( match find impl name with | Some _ as m -> m | None -> find vlib name) From 2da56ab4b8684d2d1f050158b0c11537daeedebd Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Tue, 20 Jul 2021 12:29:42 -0700 Subject: [PATCH 56/69] make fmt --- src/dune_rules/cm_files.ml | 15 +- src/dune_rules/compilation_context.mli | 6 +- src/dune_rules/ctypes_rules.ml | 393 ++++++++++++------------- src/dune_rules/ctypes_stanza.ml | 90 +++--- src/dune_rules/ctypes_stanza.mli | 13 +- src/dune_rules/ctypes_stubs.ml | 32 +- src/dune_rules/ctypes_stubs.mli | 13 +- src/dune_rules/dir_contents.ml | 16 +- src/dune_rules/dune_file.ml | 27 +- src/dune_rules/dune_file.mli | 9 +- src/dune_rules/exe.ml | 16 +- src/dune_rules/exe.mli | 4 +- src/dune_rules/exe_rules.ml | 60 ++-- src/dune_rules/lib_rules.ml | 9 +- src/dune_rules/ordered_set_lang.ml | 1 - src/dune_rules/ordered_set_lang.mli | 3 +- 16 files changed, 353 insertions(+), 354 deletions(-) diff --git a/src/dune_rules/cm_files.ml b/src/dune_rules/cm_files.ml index bee5f9878ec..54c2fdc1ef6 100644 --- a/src/dune_rules/cm_files.ml +++ b/src/dune_rules/cm_files.ml @@ -11,10 +11,11 @@ type t = let filter_excluded_modules t modules = List.filter modules ~f:(fun module_ -> - let name = Module.name module_ in - not (Module_name.Set.mem t.excluded_modules name)) + let name = Module.name module_ in + not (Module_name.Set.mem t.excluded_modules name)) -let make ?(excluded_modules=[]) ~obj_dir ~modules ~top_sorted_modules ~ext_obj () = +let make ?(excluded_modules = []) ~obj_dir ~modules ~top_sorted_modules ~ext_obj + () = let modules = Modules.impl_only modules in let excluded_modules = Module_name.Set.of_list excluded_modules in { obj_dir; modules; top_sorted_modules; ext_obj; excluded_modules } @@ -34,10 +35,10 @@ let unsorted_objects_and_cms t ~mode = objects_and_cms t ~mode t.modules let top_sorted_cms t ~mode = let kind = Mode.cm_kind mode in Action_builder.map t.top_sorted_modules ~f:(fun modules -> - let modules = filter_excluded_modules t modules in - Obj_dir.Module.L.cm_files t.obj_dir ~kind modules) + let modules = filter_excluded_modules t modules in + Obj_dir.Module.L.cm_files t.obj_dir ~kind modules) let top_sorted_objects_and_cms t ~mode = Action_builder.map t.top_sorted_modules ~f:(fun modules -> - let modules = filter_excluded_modules t modules in - objects_and_cms t ~mode modules) + let modules = filter_excluded_modules t modules in + objects_and_cms t ~mode modules) diff --git a/src/dune_rules/compilation_context.mli b/src/dune_rules/compilation_context.mli index f6ec2586bd2..ab902bdeada 100644 --- a/src/dune_rules/compilation_context.mli +++ b/src/dune_rules/compilation_context.mli @@ -13,9 +13,9 @@ type t (** Sets whether [-opaque] is going to be used during compilation. This constructs a different dependency graph for native executables. In - particular, we can omit dependency on .cmx files. For mli only modules, - this setting is ignored and is always set when it's available. As there are - no .cmx files for such modules anyway *) + particular, we can omit dependency on .cmx files. For mli only modules, this + setting is ignored and is always set when it's available. As there are no + .cmx files for such modules anyway *) type opaque = | Explicit of bool (** Set directly by the caller *) | Inherit_from_settings diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index b8fe459ab1c..291a88925a7 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -5,44 +5,44 @@ open! Stdune (executables ... (ctypes ...)) rule into the generated set of .ml and .c files needed to conveniently write OCaml bindings for C libraries. - Aside from perhaps providing an "header.h" include line, you should be - able to wrap an entire C library without writing a single line of C code. + Aside from perhaps providing an "header.h" include line, you should be able + to wrap an entire C library without writing a single line of C code. This stanza requires the user to specify the names of 4 (or more) modules: - (type_description Type_description) - (generated_types Types_generated) - (function_description Function_description) ; can be repeated - (generated_entry_point C) + (type_description Type_description) (generated_types Types_generated) + (function_description Function_description) ; can be repeated + (generated_entry_point C) The user must also implement two of the modules: (1) $type_description.ml must have the following top-level functor: - module Types (T : Ctypes.TYPE) = struct - (* put calls to Ctypes.TYPE.constant and Ctypes.TYPE.typedef here - to wrap C constants and structs *) - end + module Types (T : Ctypes.TYPE) = struct (* put calls to Ctypes.TYPE.constant + and Ctypes.TYPE.typedef here to wrap C constants and structs *) end (2) $function_description.ml must have the following two definitions: - modules Types = $generated_types + modules Types = $generated_types - module Functions (F : Ctypes.FOREIGN) = struct - (* put calls to F.foreign here to wrap C functions *) - end + module Functions (F : Ctypes.FOREIGN) = struct (* put calls to F.foreign here + to wrap C functions *) end Once the above modules are provided, the ctypes stanza will: - - generate a types generator - - generate a functions generator - - set up a discovery program to query pkg-config for compile and link flags, - if you decided to use pkg-config instead of vendored c-flags - - use the types/data and functions modules you filled in with a functor - to tie everything into your library. + + * generate a types generator + + * generate a functions generator + + * set up a discovery program to query pkg-config for compile and link flags, + if you decided to use pkg-config instead of vendored c-flags + + * use the types/data and functions modules you filled in with a functor to + tie everything into your library. The user must also specify the name of a final "Entry point" output module ($generated_entry_point) that will be generated and added to your executable - or library. Suggest calling it "C" and accessing the instantiated functors + or library. Suggest calling it "C" and accessing the instantiated functors from your project as C.Types and C.Functions. It may help to view a real world example of all of the boilerplate that is @@ -51,16 +51,14 @@ open! Stdune https://github.com/mbacarella/mpg123/blob/077a72d922931eb46d4b4e5842b0426fa3c161b5/c/dune This implementation is not, however, a naive translation of the boilerplate - above. This module uses dune internal features to simplify the stub - generation. As a result, there are no intermediate libraries (or packages). -*) + above. This module uses dune internal features to simplify the stub + generation. As a result, there are no intermediate libraries (or packages). *) module Buildable = Dune_file.Buildable -module Library = Dune_file.Library +module Library = Dune_file.Library module Ctypes = Ctypes_stanza module Stanza_util = struct - let sprintf = Printf.sprintf let discover_script ctypes = @@ -77,14 +75,11 @@ module Stanza_util = struct (module_name_lower_string fd.Ctypes.Function_description.functor_) (module_name_lower_string fd.Ctypes.Function_description.instance) - let type_description_functor ctypes = - ctypes.Ctypes.type_description.functor_ + let type_description_functor ctypes = ctypes.Ctypes.type_description.functor_ - let type_description_instance ctypes = - ctypes.Ctypes.type_description.instance + let type_description_instance ctypes = ctypes.Ctypes.type_description.instance - let entry_module ctypes = - ctypes.Ctypes.generated_entry_point + let entry_module ctypes = ctypes.Ctypes.generated_entry_point let cflags_sexp ctypes = Ctypes_stubs.cflags_sexp @@ -106,8 +101,7 @@ module Stanza_util = struct (* This includer module is simply some glue to instantiate the Types functor that the user provides in the type description module. *) - let c_types_includer_module ctypes = - ctypes.Ctypes.generated_types + let c_types_includer_module ctypes = ctypes.Ctypes.generated_types let c_generated_functions_cout_c ctypes fd = sprintf "%s__c_cout_generated_functions__%s__%s.c" @@ -116,8 +110,7 @@ module Stanza_util = struct (module_name_lower_string fd.Ctypes.Function_description.instance) let lib_deps_of_strings ~loc lst = - List.map lst ~f:(fun lib -> - Lib_dep.Direct (loc, Lib_name.of_string lib)) + List.map lst ~f:(fun lib -> Lib_dep.Direct (loc, Lib_name.of_string lib)) let type_gen_script_module ctypes = type_gen_script ctypes |> Module_name.of_string @@ -126,19 +119,22 @@ module Stanza_util = struct function_gen_script ctypes function_description |> Module_name.of_string let generated_modules ctypes = - List.concat_map ctypes.Ctypes.function_description ~f:(fun function_description -> - [ function_gen_script_module ctypes function_description - ; c_generated_functions_module ctypes function_description ]) - @ - [ type_gen_script_module ctypes - ; c_generated_types_module ctypes - ; c_types_includer_module ctypes - ; entry_module ctypes ] + List.concat_map ctypes.Ctypes.function_description + ~f:(fun function_description -> + [ function_gen_script_module ctypes function_description + ; c_generated_functions_module ctypes function_description + ]) + @ [ type_gen_script_module ctypes + ; c_generated_types_module ctypes + ; c_types_includer_module ctypes + ; entry_module ctypes + ] let non_installable_modules ctypes = type_gen_script_module ctypes - :: List.map ctypes.Ctypes.function_description ~f:(fun function_description -> - function_gen_script_module ctypes function_description) + :: + List.map ctypes.Ctypes.function_description ~f:(fun function_description -> + function_gen_script_module ctypes function_description) let generated_ml_and_c_files ctypes = let ml_files = @@ -149,52 +145,50 @@ module Stanza_util = struct in let c_files = List.map ctypes.Ctypes.function_description ~f:(fun fd -> - c_generated_functions_cout_c ctypes fd) + c_generated_functions_cout_c ctypes fd) in ml_files @ c_files end let generated_ml_and_c_files = Stanza_util.generated_ml_and_c_files + let non_installable_modules = Stanza_util.non_installable_modules -let ml_of_module_name mn = - Module_name.to_string mn ^ ".ml" - |> String.lowercase +let ml_of_module_name mn = Module_name.to_string mn ^ ".ml" |> String.lowercase let modules_of_list ~dir ~modules = let name_map = let build_dir = Path.build dir in let modules = List.map modules ~f:(fun name -> - let module_name = Module_name.of_string name in - let path = Path.relative build_dir (String.lowercase name ^ ".ml") in - let impl = Module.File.make Dialect.ocaml path in - let source = Module.Source.make ~impl module_name in - Module.of_source ~visibility:Visibility.Public - ~kind:Module.Kind.Impl source) + let module_name = Module_name.of_string name in + let path = Path.relative build_dir (String.lowercase name ^ ".ml") in + let impl = Module.File.make Dialect.ocaml path in + let source = Module.Source.make ~impl module_name in + Module.of_source ~visibility:Visibility.Public ~kind:Module.Kind.Impl + source) in Module.Name_map.of_list_exn modules in Modules.exe_unwrapped name_map - (* Modules.exe_wrapped ~src_dir:dir ~modules:name_map *) +(* Modules.exe_wrapped ~src_dir:dir ~modules:name_map *) -let write_c_types_includer_module ~sctx ~dir ~filename - ~type_description_functor ~c_generated_types_module = +let write_c_types_includer_module ~sctx ~dir ~filename ~type_description_functor + ~c_generated_types_module = let path = Path.Build.relative dir filename in let contents = let buf = Buffer.create 1024 in let pr buf fmt = Printf.bprintf buf (fmt ^^ "\n") in pr buf "include %s.Types (%s)" - (Module_name.to_string type_description_functor) - (Module_name.to_string c_generated_types_module); + (Module_name.to_string type_description_functor) + (Module_name.to_string c_generated_types_module); Buffer.contents buf in Super_context.add_rule ~loc:Loc.none sctx ~dir (Action_builder.write_file path contents) let write_entry_point_module ~ctypes ~sctx ~dir ~filename - ~type_description_instance ~function_description - ~c_types_includer_module = + ~type_description_instance ~function_description ~c_types_includer_module = let path = Path.Build.relative dir filename in let contents = let buf = Buffer.create 1024 in @@ -203,14 +197,13 @@ let write_entry_point_module ~ctypes ~sctx ~dir ~filename (Module_name.to_string type_description_instance) (Module_name.to_string c_types_includer_module); List.iter function_description ~f:(fun fd -> - let c_generated_functions_module = - Stanza_util.c_generated_functions_module ctypes fd - in - pr buf "module %s = %s.Functions (%s)" - (fd.Ctypes.Function_description.instance |> Module_name.to_string) - (fd.Ctypes.Function_description.functor_ |> Module_name.to_string) - (Module_name.to_string c_generated_functions_module) - ); + let c_generated_functions_module = + Stanza_util.c_generated_functions_module ctypes fd + in + pr buf "module %s = %s.Functions (%s)" + (fd.Ctypes.Function_description.instance |> Module_name.to_string) + (fd.Ctypes.Function_description.functor_ |> Module_name.to_string) + (Module_name.to_string c_generated_functions_module)); Buffer.contents buf in Super_context.add_rule ~loc:Loc.none sctx ~dir @@ -240,7 +233,7 @@ let discover_gen ~external_library_name:lib ~cflags_sexp ~c_library_flags_sexp = Buffer.contents buf let write_discover_script ~filename ~sctx ~dir ~external_library_name - ~cflags_sexp ~c_library_flags_sexp = + ~cflags_sexp ~c_library_flags_sexp = let path = Path.Build.relative dir filename in let script = discover_gen ~external_library_name ~cflags_sexp ~c_library_flags_sexp @@ -250,12 +243,10 @@ let write_discover_script ~filename ~sctx ~dir ~external_library_name let gen_headers headers buf = let pr buf fmt = Printf.bprintf buf (fmt ^^ "\n") in - begin match headers with + match headers with | Ctypes.Headers.Include lst -> List.iter lst ~f:(fun h -> pr buf " print_endline \"#include <%s>\";" h) - | Preamble s -> - pr buf " print_endline %S;" s - end + | Preamble s -> pr buf " print_endline %S;" s let type_gen_gen ~headers ~type_description_functor = let buf = Buffer.create 1024 in @@ -263,7 +254,8 @@ let type_gen_gen ~headers ~type_description_functor = pr buf "let () ="; gen_headers headers buf; pr buf " Cstubs_structs.write_c Format.std_formatter"; - pr buf " (module %s.Types)" (Module_name.to_string type_description_functor); + pr buf " (module %s.Types)" + (Module_name.to_string type_description_functor); Buffer.contents buf let function_gen_gen ~concurrency ~headers ~function_description_functor = @@ -292,31 +284,32 @@ let function_gen_gen ~concurrency ~headers ~function_description_functor = Buffer.contents buf let write_type_gen_script ~headers ~dir ~filename ~sctx - ~type_description_functor = + ~type_description_functor = let path = Path.Build.relative dir filename in let script = type_gen_gen ~headers ~type_description_functor in Super_context.add_rule ~loc:Loc.none sctx ~dir (Action_builder.write_file path script) let write_function_gen_script ~headers ~sctx ~dir ~name - ~function_description_functor ~concurrency = + ~function_description_functor ~concurrency = let path = Path.Build.relative dir (name ^ ".ml") in - let script = function_gen_gen ~concurrency ~headers ~function_description_functor in - Super_context.add_rule ~loc:Loc.none sctx ~dir (Action_builder.write_file path script) + let script = + function_gen_gen ~concurrency ~headers ~function_description_functor + in + Super_context.add_rule ~loc:Loc.none sctx ~dir + (Action_builder.write_file path script) -let rule ?(deps=[]) ?stdout_to ?(args=[]) ?(targets=[]) ~exe ~sctx ~dir () = +let rule ?(deps = []) ?stdout_to ?(args = []) ?(targets = []) ~exe ~sctx ~dir () + = let build = let exe = Ok (Path.build (Path.Build.relative dir exe)) in let args = let targets = List.map targets ~f:(Path.Build.relative dir) in let deps = - List.map deps ~f:(Path.relative (Path.build dir)) - |> Dep.Set.of_files + List.map deps ~f:(Path.relative (Path.build dir)) |> Dep.Set.of_files in let open Command.Args in - [ Hidden_targets targets - ; Hidden_deps deps - ; As args ] + [ Hidden_targets targets; Hidden_deps deps; As args ] in let stdout_to = Option.map stdout_to ~f:(Path.Build.relative dir) in Command.run exe ~dir:(Path.build dir) ?stdout_to args @@ -339,19 +332,14 @@ let build_c_program ~sctx ~dir ~source_files ~scope ~cflags_sexp ~output () = let+ lib = let ctypes = Lib_name.of_string "ctypes" in Lib.DB.resolve (Scope.libs scope) (Loc.none, ctypes) - (* - | Ok lib -> lib - | Error _res -> - User_error.raise - [ Pp.textf "the 'ctypes' library needs to be installed to use the ctypes stanza"] - *) + (* | Ok lib -> lib | Error _res -> User_error.raise [ Pp.textf "the + 'ctypes' library needs to be installed to use the ctypes stanza"] *) in - Lib.L.include_paths [lib] Mode.Native - |> Path.Set.to_list - |> List.map ~f:Path.to_string + Lib.L.include_paths [ lib ] Mode.Native + |> Path.Set.to_list |> List.map ~f:Path.to_string in let include_dirs = ocaml_where :: ctypes_include_dirs in - List.concat_map include_dirs ~f:(fun dir -> ["-I"; dir]) + List.concat_map include_dirs ~f:(fun dir -> [ "-I"; dir ]) in let deps = List.map source_files ~f:(Path.relative (Path.build dir)) @@ -359,29 +347,31 @@ let build_c_program ~sctx ~dir ~source_files ~scope ~cflags_sexp ~output () = in let build = let cflags_args = - let contents = Action_builder.contents (Path.relative (Path.build dir) cflags_sexp) in + let contents = + Action_builder.contents (Path.relative (Path.build dir) cflags_sexp) + in Action_builder.map contents ~f:(fun sexp -> - let fail s = User_error.raise [ Pp.textf s ] in - let ast = - Dune_lang.Parser.parse_string ~mode:Dune_lang.Parser.Mode.Single - ~fname:cflags_sexp sexp - in - match ast with - | Dune_lang.Ast.Atom (_loc, atom) -> [Dune_lang.Atom.to_string atom] - | Template _ -> fail "'template' not supported in ctypes c_flags" - | Quoted_string (_loc, s) -> [s] - | List (_loc, lst) -> - List.map lst ~f:(function - | Dune_lang.Ast.Atom (_loc, atom) -> Dune_lang.Atom.to_string atom - | Quoted_string (_loc, s) -> s - | Template _ -> fail "'template' not supported in ctypes c_flags" - | List _ -> fail "nested lists not supported in ctypes c_flags")) + let fail s = User_error.raise [ Pp.textf s ] in + let ast = + Dune_lang.Parser.parse_string ~mode:Dune_lang.Parser.Mode.Single + ~fname:cflags_sexp sexp + in + match ast with + | Dune_lang.Ast.Atom (_loc, atom) -> [ Dune_lang.Atom.to_string atom ] + | Template _ -> fail "'template' not supported in ctypes c_flags" + | Quoted_string (_loc, s) -> [ s ] + | List (_loc, lst) -> + List.map lst ~f:(function + | Dune_lang.Ast.Atom (_loc, atom) -> Dune_lang.Atom.to_string atom + | Quoted_string (_loc, s) -> s + | Template _ -> fail "'template' not supported in ctypes c_flags" + | List _ -> fail "nested lists not supported in ctypes c_flags")) in let absolute_path_hack p = (* These normal path builder things construct relative paths like - _build/default/your/project/file.c but before dune runs gcc it - actually cds into _build/default, which fails, so we turn them - into absolutes to hack around it. *) + _build/default/your/project/file.c but before dune runs gcc it actually + cds into _build/default, which fails, so we turn them into absolutes to + hack around it. *) Path.relative (Path.build dir) p |> Path.to_absolute_filename in let action = @@ -389,17 +379,19 @@ let build_c_program ~sctx ~dir ~source_files ~scope ~cflags_sexp ~output () = let* include_args = Resolve.read include_args in Action_builder.deps deps >>> Action_builder.map cflags_args ~f:(fun cflags_args -> - let source_files = List.map source_files ~f:absolute_path_hack in - let output = absolute_path_hack output in - let args = cflags_args @ include_args @ source_files @ ["-o"; output] in - Action.run exe args) + let source_files = List.map source_files ~f:absolute_path_hack in + let output = absolute_path_hack output in + let args = + cflags_args @ include_args @ source_files @ [ "-o"; output ] + in + Action.run exe args) in - Action_builder.with_targets action ~targets:[Path.Build.relative dir output] + Action_builder.with_targets action + ~targets:[ Path.Build.relative dir output ] in Super_context.add_rule sctx ~dir build -let cctx_with_substitutions ?(libraries=[]) ~modules ~dir - ~loc ~scope ~cctx = +let cctx_with_substitutions ?(libraries = []) ~modules ~dir ~loc ~scope ~cctx = let compile_info = let dune_version = Scope.project scope |> Dune_project.dune_version in Lib.DB.resolve_user_written_deps_for_exes (Scope.libs scope) @@ -409,13 +401,9 @@ let cctx_with_substitutions ?(libraries=[]) ~modules ~dir in let modules = modules_of_list ~dir ~modules in let module Cctx = Compilation_context in - Cctx.create - ~super_context:(Cctx.super_context cctx) - ~scope:(Cctx.scope cctx) - ~expander:(Cctx.expander cctx) - ~js_of_ocaml:(Cctx.js_of_ocaml cctx) - ~package:(Cctx.package cctx) - ~flags:(Cctx.flags cctx) + Cctx.create ~super_context:(Cctx.super_context cctx) ~scope:(Cctx.scope cctx) + ~expander:(Cctx.expander cctx) ~js_of_ocaml:(Cctx.js_of_ocaml cctx) + ~package:(Cctx.package cctx) ~flags:(Cctx.flags cctx) ~requires_compile:(Lib.Compile.direct_requires compile_info) ~requires_link:(Lib.Compile.requires_link compile_info) ~obj_dir:(Cctx.obj_dir cctx) @@ -424,24 +412,25 @@ let cctx_with_substitutions ?(libraries=[]) ~modules ~dir let program_of_module_and_dir ~dir program = let build_dir = Path.build dir in - Exe.Program.{ - name = program; - main_module_name = Module_name.of_string program; - loc = Loc.in_file (Path.relative build_dir program) - } - -let exe_build_and_link ?libraries ?(modules=[]) ~scope ~loc ~dir ~cctx program = + Exe.Program. + { name = program + ; main_module_name = Module_name.of_string program + ; loc = Loc.in_file (Path.relative build_dir program) + } + +let exe_build_and_link ?libraries ?(modules = []) ~scope ~loc ~dir ~cctx program + = let cctx = cctx_with_substitutions ?libraries ~loc ~scope ~dir ~cctx ~modules:(program :: modules) in let program = program_of_module_and_dir ~dir program in - Exe.build_and_link ~program ~linkages:[Exe.Linkage.native] - ~promote:None cctx + Exe.build_and_link ~program ~linkages:[ Exe.Linkage.native ] ~promote:None + cctx let exe_link_only ~dir ~shared_cctx ~dep_graphs program = let program = program_of_module_and_dir ~dir program in - Exe.link_many ~programs:[program] ~linkages:[Exe.Linkage.native] + Exe.link_many ~programs:[ program ] ~linkages:[ Exe.Linkage.native ] ~dep_graphs ~promote:None shared_cctx let write_osl_to_sexp_file ~sctx ~dir ~filename osl = @@ -450,10 +439,10 @@ let write_osl_to_sexp_file ~sctx ~dir ~filename osl = let sexp = let encoded = match Ordered_set_lang.Unexpanded.encode osl with - | [s] -> s + | [ s ] -> s | _lst -> User_error.raise - [ Pp.textf "expected %s to contain a list of atoms" filename] + [ Pp.textf "expected %s to contain a list of atoms" filename ] in Dune_lang.to_string encoded in @@ -461,8 +450,8 @@ let write_osl_to_sexp_file ~sctx ~dir ~filename osl = in Super_context.add_rule ~loc:Loc.none sctx ~dir build -(* Adding an 'iter' to Memo.Build produced pretty strange far-flung type - errors, so just doing this here. *) +(* Adding an 'iter' to Memo.Build produced pretty strange far-flung type errors, + so just doing this here. *) let rec memo_build_list_iter lst ~f = let open Memo.Build.O in match lst with @@ -480,17 +469,16 @@ let gen_rules ~dep_graphs ~cctx ~buildable ~loc ~scope ~dir ~sctx = let rule = rule ~sctx ~dir in let open Memo.Build.O in let* () = - write_c_types_includer_module - ~sctx ~dir ~filename:(ml_of_module_name c_types_includer_module) + write_c_types_includer_module ~sctx ~dir + ~filename:(ml_of_module_name c_types_includer_module) ~c_generated_types_module ~type_description_functor in (* The output of this process is to generate a cflags sexp and a c library - flags sexp file. We can probe these flags by using the system pkg-config, - if it's an external system library. The user could also tell us what - they are, if the library is vendored. + flags sexp file. We can probe these flags by using the system pkg-config, + if it's an external system library. The user could also tell us what they + are, if the library is vendored. - https://dune.readthedocs.io/en/stable/quick-start.html#defining-a-library-with-c-stubs-using-pkg-config - *) + https://dune.readthedocs.io/en/stable/quick-start.html#defining-a-library-with-c-stubs-using-pkg-config *) let c_library_flags_sexp = Stanza_util.c_library_flags_sexp ctypes in let cflags_sexp = Stanza_util.cflags_sexp ctypes in let* () = @@ -506,27 +494,24 @@ let gen_rules ~dep_graphs ~cctx ~buildable ~loc ~scope ~dir ~sctx = let cflags_sexp = Stanza_util.cflags_sexp ctypes in let discover_script = Stanza_util.discover_script ctypes in let* () = - write_discover_script - ~sctx ~dir ~filename:(discover_script ^ ".ml") ~cflags_sexp - ~c_library_flags_sexp ~external_library_name + write_discover_script ~sctx ~dir ~filename:(discover_script ^ ".ml") + ~cflags_sexp ~c_library_flags_sexp ~external_library_name in let* () = exe_build_and_link ~scope ~loc ~dir ~cctx - ~libraries:["dune.configurator"] discover_script + ~libraries:[ "dune.configurator" ] discover_script in rule - ~targets:[cflags_sexp; c_library_flags_sexp] + ~targets:[ cflags_sexp; c_library_flags_sexp ] ~exe:(discover_script ^ ".exe") () in let generated_entry_module = Stanza_util.entry_module ctypes in let headers = ctypes.Ctypes.headers in let exe_link_only = exe_link_only ~dir ~shared_cctx:cctx ~dep_graphs in - (* Type_gen produces a .c file, taking your type description module above - as an input. - The .c file is compiled into an .exe. - The .exe, when run produces an .ml file. - The .ml file is compiled into a module that will have the user's - ML-wrapped C data/types. + (* Type_gen produces a .c file, taking your type description module above as + an input. The .c file is compiled into an .exe. The .exe, when run produces + an .ml file. The .ml file is compiled into a module that will have the + user's ML-wrapped C data/types. Note the similar function_gen process below depends on the ML-wrapped C data/types produced in this step. *) @@ -540,60 +525,56 @@ let gen_rules ~dep_graphs ~cctx ~buildable ~loc ~scope ~dir ~sctx = let type_gen_script = Stanza_util.type_gen_script ctypes in let* () = write_type_gen_script ~headers ~sctx ~dir - ~filename:(type_gen_script ^ ".ml") - ~type_description_functor + ~filename:(type_gen_script ^ ".ml") ~type_description_functor in let* () = exe_link_only type_gen_script in let* () = - rule - ~stdout_to:c_generated_types_cout_c - ~exe:(type_gen_script ^ ".exe") () + rule ~stdout_to:c_generated_types_cout_c ~exe:(type_gen_script ^ ".exe") + () in let* () = - build_c_program - ~sctx ~dir ~scope ~cflags_sexp - ~source_files:[c_generated_types_cout_c] + build_c_program ~sctx ~dir ~scope ~cflags_sexp + ~source_files:[ c_generated_types_cout_c ] ~output:c_generated_types_cout_exe () in rule ~stdout_to:(c_generated_types_module |> ml_of_module_name) - ~exe:(c_generated_types_cout_exe) () + ~exe:c_generated_types_cout_exe () in - (* Function_gen is similar to type_gen above, though it produces both an - .ml file and a .c file. These files correspond to the files you would - have to write by hand to wrap C code (if ctypes didn't exist!) - - Also the user can repeat the 'function_description' stanza to do this - more than once. This is needed for generating blocking and non-blocking - sets of functions, for example, which requires a different 'concurrency' - parameter in the code generator. *) + (* Function_gen is similar to type_gen above, though it produces both an .ml + file and a .c file. These files correspond to the files you would have to + write by hand to wrap C code (if ctypes didn't exist!) + + Also the user can repeat the 'function_description' stanza to do this more + than once. This is needed for generating blocking and non-blocking sets of + functions, for example, which requires a different 'concurrency' parameter + in the code generator. *) let* () = memo_build_list_iter ctypes.Ctypes.function_description ~f:(fun fd -> - let stubs_prefix = external_library_name ^ "_stubs" in - let c_generated_functions_cout_c = - Stanza_util.c_generated_functions_cout_c ctypes fd - in - let function_gen_script = Stanza_util.function_gen_script ctypes fd in - let* () = - write_function_gen_script ~headers ~sctx ~dir - ~name:function_gen_script - ~concurrency:fd.Ctypes.Function_description.concurrency - ~function_description_functor:fd.Ctypes.Function_description.functor_ - in - let* () = exe_link_only function_gen_script in - let* () = + let stubs_prefix = external_library_name ^ "_stubs" in + let c_generated_functions_cout_c = + Stanza_util.c_generated_functions_cout_c ctypes fd + in + let function_gen_script = Stanza_util.function_gen_script ctypes fd in + let* () = + write_function_gen_script ~headers ~sctx ~dir + ~name:function_gen_script + ~concurrency:fd.Ctypes.Function_description.concurrency + ~function_description_functor: + fd.Ctypes.Function_description.functor_ + in + let* () = exe_link_only function_gen_script in + let* () = + rule ~stdout_to:c_generated_functions_cout_c + ~exe:(function_gen_script ^ ".exe") + ~args:[ "c"; stubs_prefix ] () + in rule - ~stdout_to:c_generated_functions_cout_c + ~stdout_to: + (Stanza_util.c_generated_functions_module ctypes fd + |> ml_of_module_name) ~exe:(function_gen_script ^ ".exe") - ~args:["c"; stubs_prefix] () - in - rule - ~stdout_to:(Stanza_util.c_generated_functions_module ctypes fd - |> ml_of_module_name) - ~exe:(function_gen_script ^ ".exe") - ~args:["ml"; stubs_prefix] - () - ) + ~args:[ "ml"; stubs_prefix ] ()) in (* The entry point module binds the instantiated Types and Functions functors to the entry point module name and instances the user specified. *) @@ -616,9 +597,7 @@ let ctypes_cclib_flags ~standard ~scope ~expander ~buildable = let project = Scope.project scope in Dune_project.parsing_context project in - Ordered_set_lang.Unexpanded.include_single - ~context:parsing_context ~pos:("", 0, 0, 0) - path_to_sexp_file + Ordered_set_lang.Unexpanded.include_single ~context:parsing_context + ~pos:("", 0, 0, 0) path_to_sexp_file in - Expander.expand_and_eval_set expander ctypes_c_library_flags - ~standard + Expander.expand_and_eval_set expander ctypes_c_library_flags ~standard diff --git a/src/dune_rules/ctypes_stanza.ml b/src/dune_rules/ctypes_stanza.ml index a291fd21f44..33ec3c860e4 100644 --- a/src/dune_rules/ctypes_stanza.ml +++ b/src/dune_rules/ctypes_stanza.ml @@ -3,17 +3,19 @@ open Import open Dune_lang.Decoder module Build_flags_resolver = struct - module Vendored = struct type t = { c_flags : Ordered_set_lang.Unexpanded.t - ; c_library_flags : Ordered_set_lang.Unexpanded.t } + ; c_library_flags : Ordered_set_lang.Unexpanded.t + } let decode = fields (let+ c_flags = Ordered_set_lang.Unexpanded.field "c_flags" - and+ c_library_flags = Ordered_set_lang.Unexpanded.field "c_library_flags" in - { c_flags; c_library_flags }) + and+ c_library_flags = + Ordered_set_lang.Unexpanded.field "c_library_flags" + in + { c_flags; c_library_flags }) end type t = @@ -25,8 +27,7 @@ module Build_flags_resolver = struct let+ p = Vendored.decode in Vendored p in - sum [ ("pkg_config" , return Pkg_config) - ; ("vendored" , vendored ) ] + sum [ ("pkg_config", return Pkg_config); ("vendored", vendored) ] let default = Pkg_config end @@ -39,10 +40,12 @@ module Concurrency_policy = struct | Lwt_preemptive let decode = - enum [ "sequential" , Sequential - ; "unlocked" , Unlocked - ; "lwt_jobs" , Lwt_jobs - ; "lwt_preemptive" , Lwt_preemptive ] + enum + [ ("sequential", Sequential) + ; ("unlocked", Unlocked) + ; ("lwt_jobs", Lwt_jobs) + ; ("lwt_preemptive", Lwt_preemptive) + ] let default = Sequential end @@ -61,8 +64,7 @@ module Headers = struct let+ p = string in Preamble p in - sum [ ("include" , include_) - ; ("preamble" , preamble) ] + sum [ ("include", include_); ("preamble", preamble) ] let default = Include [] end @@ -70,33 +72,35 @@ end module Type_description = struct type t = { functor_ : Module_name.t - ; instance : Module_name.t } + ; instance : Module_name.t + } let decode = let open Dune_lang.Decoder in fields (let+ functor_ = field "functor" Module_name.decode - and+ instance = field "instance" Module_name.decode - in - { functor_; instance }) + and+ instance = field "instance" Module_name.decode in + { functor_; instance }) end module Function_description = struct type t = { concurrency : Concurrency_policy.t ; functor_ : Module_name.t - ; instance : Module_name.t } + ; instance : Module_name.t + } let decode = let open Dune_lang.Decoder in fields (let+ concurrency = field_o "concurrency" Concurrency_policy.decode - and+ functor_ = field "functor" Module_name.decode - and+ instance = field "instance" Module_name.decode - in - { concurrency = Option.value concurrency ~default:Concurrency_policy.default - ; functor_ - ; instance }) + and+ functor_ = field "functor" Module_name.decode + and+ instance = field "instance" Module_name.decode in + { concurrency = + Option.value concurrency ~default:Concurrency_policy.default + ; functor_ + ; instance + }) end type t = @@ -105,8 +109,9 @@ type t = ; headers : Headers.t ; type_description : Type_description.t ; function_description : Function_description.t list - ; generated_types : Module_name.t - ; generated_entry_point : Module_name.t } + ; generated_types : Module_name.t + ; generated_entry_point : Module_name.t + } let name = "ctypes" @@ -120,20 +125,27 @@ let decode = let open Dune_lang.Decoder in fields (let+ external_library_name = field "external_library_name" string - and+ build_flags_resolver = field_o "build_flags_resolver" Build_flags_resolver.decode - and+ type_description = field "type_description" Type_description.decode - and+ function_description = multi_field "function_description" Function_description.decode - and+ headers = field_o "headers" Headers.decode - and+ generated_types = field_o "generated_types" Module_name.decode - and+ generated_entry_point = field "generated_entry_point" Module_name.decode - in - { external_library_name - ; build_flags_resolver = Option.value build_flags_resolver ~default:Build_flags_resolver.default - ; headers = Option.value headers ~default:Headers.default - ; type_description - ; function_description - ; generated_types = Option.value generated_types ~default:(Module_name.of_string "Types_generated") - ; generated_entry_point }) + and+ build_flags_resolver = + field_o "build_flags_resolver" Build_flags_resolver.decode + and+ type_description = field "type_description" Type_description.decode + and+ function_description = + multi_field "function_description" Function_description.decode + and+ headers = field_o "headers" Headers.decode + and+ generated_types = field_o "generated_types" Module_name.decode + and+ generated_entry_point = + field "generated_entry_point" Module_name.decode + in + { external_library_name + ; build_flags_resolver = + Option.value build_flags_resolver ~default:Build_flags_resolver.default + ; headers = Option.value headers ~default:Headers.default + ; type_description + ; function_description + ; generated_types = + Option.value generated_types + ~default:(Module_name.of_string "Types_generated") + ; generated_entry_point + }) let () = let open Dune_lang.Decoder in diff --git a/src/dune_rules/ctypes_stanza.mli b/src/dune_rules/ctypes_stanza.mli index 946f75769c5..7156731ec01 100644 --- a/src/dune_rules/ctypes_stanza.mli +++ b/src/dune_rules/ctypes_stanza.mli @@ -5,8 +5,10 @@ module Build_flags_resolver : sig module Vendored : sig type t = { c_flags : Ordered_set_lang.Unexpanded.t - ; c_library_flags : Ordered_set_lang.Unexpanded.t } + ; c_library_flags : Ordered_set_lang.Unexpanded.t + } end + type t = | Pkg_config | Vendored of Vendored.t @@ -29,14 +31,16 @@ end module Type_description : sig type t = { functor_ : Module_name.t - ; instance : Module_name.t } + ; instance : Module_name.t + } end module Function_description : sig type t = { concurrency : Concurrency_policy.t ; functor_ : Module_name.t - ; instance : Module_name.t } + ; instance : Module_name.t + } end type t = @@ -46,7 +50,8 @@ type t = ; type_description : Type_description.t ; function_description : Function_description.t list ; generated_types : Module_name.t - ; generated_entry_point : Module_name.t } + ; generated_entry_point : Module_name.t + } type Stanza.t += T of t diff --git a/src/dune_rules/ctypes_stubs.ml b/src/dune_rules/ctypes_stubs.ml index c5e87bcdabb..1c3a599d9fc 100644 --- a/src/dune_rules/ctypes_stubs.ml +++ b/src/dune_rules/ctypes_stubs.ml @@ -4,8 +4,8 @@ open! Stdune let cflags_sexp ~external_library_name = sprintf "%s__c_flags.sexp" external_library_name -let c_generated_functions_cout_no_ext ~external_library_name - ~functor_ ~instance = +let c_generated_functions_cout_no_ext ~external_library_name ~functor_ ~instance + = sprintf "%s__c_cout_generated_functions__%s__%s" external_library_name (Module_name.to_string functor_ |> String.lowercase) (Module_name.to_string instance |> String.lowercase) @@ -14,22 +14,24 @@ let c_library_flags ~external_library_name = sprintf "%s__c_library_flags.sexp" external_library_name let lib_deps_of_strings ~loc lst = - List.map lst ~f:(fun lib -> - Lib_dep.Direct (loc, Lib_name.of_string lib)) + List.map lst ~f:(fun lib -> Lib_dep.Direct (loc, Lib_name.of_string lib)) let libraries_needed_for_ctypes ~loc = - let libraries = ["ctypes"; "ctypes.stubs"] in + let libraries = [ "ctypes"; "ctypes.stubs" ] in lib_deps_of_strings ~loc libraries let add ~loc ~parsing_context ~external_library_name ~add_stubs ~functor_ - ~instance ~foreign_stubs = - add_stubs - Foreign_language.C - ~loc - ~names:(Some (Ordered_set_lang.of_atoms ~loc - [c_generated_functions_cout_no_ext ~external_library_name - ~functor_ ~instance])) - ~flags:(Some (Ordered_set_lang.Unexpanded.include_single - ~context:parsing_context ~pos:("", 0, 0, 0) - (cflags_sexp ~external_library_name))) + ~instance ~foreign_stubs = + add_stubs Foreign_language.C ~loc + ~names: + (Some + (Ordered_set_lang.of_atoms ~loc + [ c_generated_functions_cout_no_ext ~external_library_name ~functor_ + ~instance + ])) + ~flags: + (Some + (Ordered_set_lang.Unexpanded.include_single ~context:parsing_context + ~pos:("", 0, 0, 0) + (cflags_sexp ~external_library_name))) foreign_stubs diff --git a/src/dune_rules/ctypes_stubs.mli b/src/dune_rules/ctypes_stubs.mli index 6331a70b86c..dfdddf77e8a 100644 --- a/src/dune_rules/ctypes_stubs.mli +++ b/src/dune_rules/ctypes_stubs.mli @@ -20,12 +20,13 @@ val add : loc:Loc.t -> parsing_context:Univ_map.t -> external_library_name:string - -> add_stubs:(Foreign_language.t - -> loc:Loc.t - -> names:Ordered_set_lang.t option - -> flags:Ordered_set_lang.Unexpanded.t option - -> Foreign.Stubs.t list - -> Foreign.Stubs.t list) + -> add_stubs: + ( Foreign_language.t + -> loc:Loc.t + -> names:Ordered_set_lang.t option + -> flags:Ordered_set_lang.Unexpanded.t option + -> Foreign.Stubs.t list + -> Foreign.Stubs.t list) -> functor_:Module_name.t -> instance:Module_name.t -> foreign_stubs:Foreign.Stubs.t list diff --git a/src/dune_rules/dir_contents.ml b/src/dune_rules/dir_contents.ml index b2482be2096..2f2365804c5 100644 --- a/src/dune_rules/dir_contents.ml +++ b/src/dune_rules/dir_contents.ml @@ -156,22 +156,22 @@ end = struct | Generate_sites_module def -> let+ res = Generate_sites_module_rules.setup_rules sctx ~dir def in [ res ] - | Library { buildable; _ } | Executables { buildable; _ } -> + | Library { buildable; _ } + | Executables { buildable; _ } -> let select_deps_files = (* Manually add files generated by the (select ...) dependencies *) List.filter_map buildable.libraries ~f:(fun dep -> - match (dep : Lib_dep.t) with - | Re_export _ - | Direct _ -> - None - | Select s -> Some s.result_fn) + match (dep : Lib_dep.t) with + | Re_export _ + | Direct _ -> + None + | Select s -> Some s.result_fn) in let ctypes_files = (* Also manually add files generated by ctypes rules. *) match buildable.ctypes with | None -> [] - | Some ctypes -> - Ctypes_rules.generated_ml_and_c_files ctypes + | Some ctypes -> Ctypes_rules.generated_ml_and_c_files ctypes in Memo.Build.return (select_deps_files @ ctypes_files) | _ -> Memo.Build.return []) diff --git a/src/dune_rules/dune_file.ml b/src/dune_rules/dune_file.ml index 1a3db5ce5c6..9b6a766e76d 100644 --- a/src/dune_rules/dune_file.ml +++ b/src/dune_rules/dune_file.ml @@ -230,8 +230,8 @@ module Buildable = struct and+ version = Dune_lang.Syntax.get_exn Stanza.syntax and+ ctypes = field_o "ctypes" - (Dune_lang.Syntax.since Ctypes_stanza.syntax (0, 1) - >>> Ctypes_stanza.decode) + (Dune_lang.Syntax.since Ctypes_stanza.syntax (0, 1) + >>> Ctypes_stanza.decode) and+ loc_instrumentation, instrumentation = located (multi_field "instrumentation" @@ -288,8 +288,10 @@ module Buildable = struct in let libraries = let ctypes_libraries = - if Option.is_none ctypes then [] - else Ctypes_stubs.libraries_needed_for_ctypes ~loc:Loc.none + if Option.is_none ctypes then + [] + else + Ctypes_stubs.libraries_needed_for_ctypes ~loc:Loc.none in libraries @ ctypes_libraries in @@ -298,13 +300,14 @@ module Buildable = struct | None -> foreign_stubs | Some (ctypes : Ctypes_stanza.t) -> let init = foreign_stubs in - List.fold_left ctypes.function_description ~init ~f:(fun foreign_stubs fd -> - Ctypes_stubs.add ~loc - ~parsing_context:(Dune_project.parsing_context project) - ~external_library_name:ctypes.external_library_name - ~functor_:fd.Ctypes_stanza.Function_description.functor_ - ~instance:fd.Ctypes_stanza.Function_description.instance - ~add_stubs ~foreign_stubs) + List.fold_left ctypes.function_description ~init + ~f:(fun foreign_stubs fd -> + Ctypes_stubs.add ~loc + ~parsing_context:(Dune_project.parsing_context project) + ~external_library_name:ctypes.external_library_name + ~functor_:fd.Ctypes_stanza.Function_description.functor_ + ~instance:fd.Ctypes_stanza.Function_description.instance + ~add_stubs ~foreign_stubs) in let foreign_archives = Option.value ~default:[] foreign_archives in let foreign_archives = @@ -502,7 +505,6 @@ module Mode_conf = struct y end - let eval_detailed t ~has_native = let exists = function | Best @@ -539,7 +541,6 @@ module Mode_conf = struct end end - module Library = struct module Wrapped = struct include Wrapped diff --git a/src/dune_rules/dune_file.mli b/src/dune_rules/dune_file.mli index fc572280165..a1aaf2a5fe4 100644 --- a/src/dune_rules/dune_file.mli +++ b/src/dune_rules/dune_file.mli @@ -73,8 +73,11 @@ module Public_lib : sig (** Package it is part of *) val package : t -> Package.t - val make : allow_deprecated_names:bool -> Dune_project.t -> - (Loc.t * Lib_name.t) -> (t, User_message.t) result + val make : + allow_deprecated_names:bool + -> Dune_project.t + -> Loc.t * Lib_name.t + -> (t, User_message.t) result end module Mode_conf : sig @@ -105,6 +108,7 @@ module Mode_conf : sig module Set : sig type mode_conf = t + type nonrec t = Kind.t option Map.t val of_list : (mode_conf * Kind.t) list -> t @@ -118,7 +122,6 @@ module Mode_conf : sig val eval_detailed : t -> has_native:bool -> Details.t Mode.Dict.t val eval : t -> has_native:bool -> Mode.Dict.Set.t - end end diff --git a/src/dune_rules/exe.ml b/src/dune_rules/exe.ml index 75400d1dbf9..46e2d181ec2 100644 --- a/src/dune_rules/exe.ml +++ b/src/dune_rules/exe.ml @@ -221,8 +221,8 @@ let link_js ~name ~cm_files ~promote cctx = Jsoo_rules.build_exe cctx ~js_of_ocaml ~src ~cm:top_sorted_cms ~flags:(Command.Args.dyn flags) ~promote -let link_many ?link_args ?o_files ?(embed_in_plugin_libraries=[]) ~dep_graphs - ~programs ~linkages ~promote cctx = +let link_many ?link_args ?o_files ?(embed_in_plugin_libraries = []) ~dep_graphs + ~programs ~linkages ~promote cctx = let dep_graphs : Dep_graph.t Ml_kind.Dict.t = dep_graphs in let open Memo.Build.O in let modules = Compilation_context.modules cctx in @@ -254,17 +254,17 @@ let link_many ?link_args ?o_files ?(embed_in_plugin_libraries=[]) ~dep_graphs link_exe cctx ~loc ~name ~linkage ~cm_files ~link_time_code_gen ~promote ?link_args ?o_files)) -let build_and_link_many ?link_args ?o_files ?embed_in_plugin_libraries - ~programs ~linkages ~promote cctx = +let build_and_link_many ?link_args ?o_files ?embed_in_plugin_libraries ~programs + ~linkages ~promote cctx = let open Memo.Build.O in let modules = Compilation_context.modules cctx in let* dep_graphs = Dep_rules.rules cctx ~modules in let* () = Module_compilation.build_all cctx ~dep_graphs in - link_many ?link_args ?o_files ?embed_in_plugin_libraries ~dep_graphs - ~programs ~linkages ~promote cctx + link_many ?link_args ?o_files ?embed_in_plugin_libraries ~dep_graphs ~programs + ~linkages ~promote cctx -let build_and_link ?link_args ?o_files ?embed_in_plugin_libraries - ~program ~linkages ~promote cctx = +let build_and_link ?link_args ?o_files ?embed_in_plugin_libraries ~program + ~linkages ~promote cctx = build_and_link_many ?link_args ?o_files ?embed_in_plugin_libraries ~programs:[ program ] ~linkages ~promote cctx diff --git a/src/dune_rules/exe.mli b/src/dune_rules/exe.mli index 1cf5e678967..c6b88a57fbb 100644 --- a/src/dune_rules/exe.mli +++ b/src/dune_rules/exe.mli @@ -39,8 +39,8 @@ end (** Build and link one or more executables *) -(* [link_many] is like [build_and_link_many], but it allows you to share - modules between executables without requiring an intermediate library. *) +(* [link_many] is like [build_and_link_many], but it allows you to share modules + between executables without requiring an intermediate library. *) val link_many : ?link_args:Command.Args.without_targets Command.Args.t Action_builder.t -> ?o_files:Path.t list diff --git a/src/dune_rules/exe_rules.ml b/src/dune_rules/exe_rules.ml index 91aaf2cffcd..c4136ac31cb 100644 --- a/src/dune_rules/exe_rules.ml +++ b/src/dune_rules/exe_rules.ml @@ -190,8 +190,7 @@ let executables_rules ~sctx ~dir ~expander ~dir_contents ~scope ~compile_info let link_flags = let link_deps = Dep_conf_eval.unnamed ~expander exes.link_deps in link_deps - >>> Expander.expand_and_eval_set expander exes.link_flags - ~standard + >>> Expander.expand_and_eval_set expander exes.link_flags ~standard in let+ flags = link_flags and+ ctypes_cclib_flags = @@ -208,13 +207,12 @@ let executables_rules ~sctx ~dir ~expander ~dir_contents ~scope ~compile_info (* XXX: don't these need the msvc hack being done in lib_rules? *) (* XXX: also the Command.quote_args being done in lib_rules? *) List.map foreign_archives ~f:(fun archive -> - let lib = Foreign.Archive.lib_file ~archive ~dir ~ext_lib in - Command.Args.S [ A "-cclib"; Dep (Path.build lib) ])) - (* XXX: don't these need the msvc hack being done in lib_rules? *) - (* XXX: also the Command.quote_args being done in lib_rules? *) + let lib = Foreign.Archive.lib_file ~archive ~dir ~ext_lib in + Command.Args.S [ A "-cclib"; Dep (Path.build lib) ])) + (* XXX: don't these need the msvc hack being done in lib_rules? *) + (* XXX: also the Command.quote_args being done in lib_rules? *) ; Command.Args.As - (List.concat_map ctypes_cclib_flags ~f:(fun f -> - ["-cclib"; f])) + (List.concat_map ctypes_cclib_flags ~f:(fun f -> [ "-cclib"; f ])) ] in let* o_files = @@ -222,30 +220,28 @@ let executables_rules ~sctx ~dir ~expander ~dir_contents ~scope ~compile_info ~requires_compile in let* () = Check_rules.add_files sctx ~dir o_files in - begin - let buildable = exes.Executables.buildable in - match buildable.Buildable.ctypes with - | None -> - Exe.build_and_link_many cctx ~programs ~linkages ~link_args ~o_files - ~promote:exes.promote ~embed_in_plugin_libraries - | Some _ctypes -> - (* Ctypes stubgen builds utility .exe files that need to share modules - with this compilation context. To support that, we extract the - one-time run bits from [Exe.build_and_link_many] and run them here, - then pass that to the [Exe.link_many] call here as well as the - Ctypes_rules. This dance is done to avoid triggering duplicate rule - exceptions. *) - let* dep_graphs = - Dep_rules.rules cctx ~modules:(Compilation_context.modules cctx) - in - let* () = - let loc = fst (List.hd exes.Executables.names) in - Ctypes_rules.gen_rules ~dep_graphs ~cctx ~buildable ~loc ~sctx ~scope ~dir - in - let* () = Module_compilation.build_all cctx ~dep_graphs in - Exe.link_many ~programs ~dep_graphs ~linkages ~link_args ~o_files - ~promote:exes.promote ~embed_in_plugin_libraries cctx - end + let buildable = exes.Executables.buildable in + match buildable.Buildable.ctypes with + | None -> + Exe.build_and_link_many cctx ~programs ~linkages ~link_args ~o_files + ~promote:exes.promote ~embed_in_plugin_libraries + | Some _ctypes -> + (* Ctypes stubgen builds utility .exe files that need to share modules + with this compilation context. To support that, we extract the one-time + run bits from [Exe.build_and_link_many] and run them here, then pass + that to the [Exe.link_many] call here as well as the Ctypes_rules. This + dance is done to avoid triggering duplicate rule exceptions. *) + let* dep_graphs = + Dep_rules.rules cctx ~modules:(Compilation_context.modules cctx) + in + let* () = + let loc = fst (List.hd exes.Executables.names) in + Ctypes_rules.gen_rules ~dep_graphs ~cctx ~buildable ~loc ~sctx ~scope + ~dir + in + let* () = Module_compilation.build_all cctx ~dep_graphs in + Exe.link_many ~programs ~dep_graphs ~linkages ~link_args ~o_files + ~promote:exes.promote ~embed_in_plugin_libraries cctx in ( cctx , Merlin.make ~requires:requires_compile ~stdlib_dir ~flags ~modules diff --git a/src/dune_rules/lib_rules.ml b/src/dune_rules/lib_rules.ml index 14b78aea9ee..ebbd404892e 100644 --- a/src/dune_rules/lib_rules.ml +++ b/src/dune_rules/lib_rules.ml @@ -82,7 +82,7 @@ let build_lib (lib : Library.t) ~native_archives ~sctx ~expander ~flags ~dir | Native -> native_archives) ; Dyn (Action_builder.map ctypes_cclib_flags ~f:(fun x -> - Command.quote_args "-cclib" (map_cclibs x))) + Command.quote_args "-cclib" (map_cclibs x))) ])) let gen_wrapped_compat_modules (lib : Library.t) cctx = @@ -328,7 +328,7 @@ let setup_build_archives (lib : Dune_file.Library.t) ~cctx let cm_files = let excluded_modules = (* ctypes type_gen and function_gen scripts should not be included in the - library. Otherwise they will spew stuff to stdout on library load. *) + library. Otherwise they will spew stuff to stdout on library load. *) match lib.buildable.ctypes with | Some ctypes -> Ctypes_rules.non_installable_modules ctypes | None -> [] @@ -483,9 +483,8 @@ let rules (lib : Library.t) ~sctx ~dir_contents ~dir ~expander ~scope = match buildable.Buildable.ctypes with | None -> Memo.Build.return () | Some _ctypes -> - Ctypes_rules.gen_rules - ~loc:(fst lib.Library.name) - ~cctx ~dep_graphs ~buildable ~sctx ~scope ~dir + Ctypes_rules.gen_rules ~loc:(fst lib.Library.name) ~cctx ~dep_graphs + ~buildable ~sctx ~scope ~dir in library_rules lib ~cctx ~source_modules ~dir_contents ~compile_info ~dep_graphs diff --git a/src/dune_rules/ordered_set_lang.ml b/src/dune_rules/ordered_set_lang.ml index 07ee4c24eda..afa6ef40323 100644 --- a/src/dune_rules/ordered_set_lang.ml +++ b/src/dune_rules/ordered_set_lang.ml @@ -272,7 +272,6 @@ module Unexpanded = struct ; context } - let field ?check name = let decode = match check with diff --git a/src/dune_rules/ordered_set_lang.mli b/src/dune_rules/ordered_set_lang.mli index 38203d0e06c..1762d5d4b30 100644 --- a/src/dune_rules/ordered_set_lang.mli +++ b/src/dune_rules/ordered_set_lang.mli @@ -58,7 +58,8 @@ module Unexpanded : sig val of_strings : pos:string * int * int * int -> string list -> t - val include_single : context:Univ_map.t -> pos:string * int * int * int -> string -> t + val include_single : + context:Univ_map.t -> pos:string * int * int * int -> string -> t val field : ?check:unit Dune_lang.Decoder.t From 1655d9bd816420bee9c80da5bc22b7a255e6997b Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Wed, 21 Jul 2021 08:26:49 -0700 Subject: [PATCH 57/69] more ctypes unit tests (pkg-config probed args) --- .../test-cases/ctypes/exe-pkg_config.t/dune | 14 ++++++++++ .../ctypes/exe-pkg_config.t/dune-project | 3 ++ .../ctypes/exe-pkg_config.t/example.ml | 2 ++ .../exe-pkg_config.t/function_description.ml | 8 ++++++ .../ctypes/exe-pkg_config.t/gen-pc-file.sh | 14 ++++++++++ .../exe-pkg_config.t/libexample/Makefile.unix | 10 +++++++ .../exe-pkg_config.t/libexample/example.c | 1 + .../exe-pkg_config.t/libexample/example.h | 1 + .../exe-pkg_config.t/libexample/example.o | Bin 0 -> 1376 bytes .../exe-pkg_config.t/libexample/libexample.a | Bin 0 -> 1526 bytes .../exe-pkg_config.t/libexample/libexample.so | Bin 0 -> 15648 bytes .../test-cases/ctypes/exe-pkg_config.t/run.t | 26 ++++++++++++++++++ .../exe-pkg_config.t/type_description.ml | 3 ++ .../test-cases/ctypes/lib-pkg_config.t/dune | 3 ++ .../ctypes/lib-pkg_config.t/dune-project | 3 ++ .../ctypes/lib-pkg_config.t/example.ml | 2 ++ .../test-cases/ctypes/lib-pkg_config.t/run.t | 26 ++++++++++++++++++ .../ctypes/lib-pkg_config.t/stubgen/dune | 14 ++++++++++ .../lib-pkg_config.t/stubgen/example.ml | 2 ++ .../stubgen/function_description.ml | 8 ++++++ .../stubgen/libexample/Makefile.unix | 13 +++++++++ .../stubgen/libexample/example.c | 1 + .../stubgen/libexample/example.h | 1 + .../stubgen/type_description.ml | 3 ++ 24 files changed, 158 insertions(+) create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/dune create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/dune-project create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/example.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/function_description.ml create mode 100755 test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/gen-pc-file.sh create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/libexample/Makefile.unix create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/libexample/example.c create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/libexample/example.h create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/libexample/example.o create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/libexample/libexample.a create mode 100755 test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/libexample/libexample.so create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/run.t create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/type_description.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/dune create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/dune-project create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/example.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/run.t create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/dune create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/example.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/function_description.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/libexample/Makefile.unix create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/libexample/example.c create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/libexample/example.h create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/type_description.ml diff --git a/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/dune b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/dune new file mode 100644 index 00000000000..a904d9a9308 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/dune @@ -0,0 +1,14 @@ +(executable + (name example) + (flags (:standard -w -9-27)) + (ctypes + (external_library_name libexample) + (build_flags_resolver pkg_config) + (headers (include "example.h")) + (type_description + (instance Types) + (functor Type_description)) + (function_description + (instance Functions) + (functor Function_description)) + (generated_entry_point C))) diff --git a/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/dune-project b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/dune-project new file mode 100644 index 00000000000..4cac8e20f22 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/dune-project @@ -0,0 +1,3 @@ +(lang dune 3.0) +(using ctypes 0.1) +(use_standard_c_and_cxx_flags false) diff --git a/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/example.ml b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/example.ml new file mode 100644 index 00000000000..98a01761fa6 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/example.ml @@ -0,0 +1,2 @@ +let () = + Printf.printf "%d\n" (C.Functions.add2 2) diff --git a/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/function_description.ml b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/function_description.ml new file mode 100644 index 00000000000..05c43d79e2f --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/function_description.ml @@ -0,0 +1,8 @@ +open Ctypes + +module Types = Types_generated + +module Functions (F : Ctypes.FOREIGN) = struct + open F + let add2 = foreign "example_add2" (int @-> returning int) +end diff --git a/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/gen-pc-file.sh b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/gen-pc-file.sh new file mode 100755 index 00000000000..f8b2a68158e --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/gen-pc-file.sh @@ -0,0 +1,14 @@ +#!/bin/sh + +cat <C~@C9oH9CrPWIlZ2TLM8O9Lf_U*K z_)`Qg`x88R@ve9g5wvQiJL&Ys%WgrvzOJvkYP#nvwZ0s&EKp*>5>zvV0{o6t<3tc9 zpdH%awQJ}-y?XU@b@FkY`nb4@Y~RC5GPxKVO=n7ZQHm|FX%?TDoGS(C8*Fe8aZ-|AGO5n!WhB|rw1x$g zeWqz4ctuDiu z5T@RfTH8{A;Z6PsuG4$^SN=G1Y0o&SF6#U-9mH6jul%fr>7}Q7qQ#1*pcDr5x@zto z^K(>^SYWHh{CBo-iS{)4w~{h1y>cf17cS5%PN)LuA7!KcGH*pseJZ}f>zz%M2Qnzn np@SdjX%CZ6n0a?Z`D2_<7>R_#1Z_8JJ^q_4+^bZEfyw^@9avV* literal 0 HcmV?d00001 diff --git a/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/libexample/libexample.a b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/libexample/libexample.a new file mode 100644 index 0000000000000000000000000000000000000000..be384fb8c69d0b90b6d9b80cc8f99954344484fb GIT binary patch literal 1526 zcmbtUUuzRV5TDD{R@16!^+Bk}^-0Bcy`-^KkrD{8BI1J*5TP`iWNpA+67DXL3RXc7 ziZ6ZyKT5$DKZ1|G_^$XOQqYK<6ohj4;>Iu}%hjqYX4hi#7NzN++-it@z4GZ4l+|0@Mc-@PLlaidH zrFN$9Hdj48eIFAjo*>le6ny_ZZrdN*Io-u--Xi*=TUsExzU(H8QRKt)-=M^2CgAiX zvNDU|f^|>XJEfQ*XcJ+4kxg&rez}USI_h7? z$CIppB{YPYdD3a{*f@@L`Im8@=ILMg%gCjgA*wCr{A)IdzB%968y04#?%RRo8=iq` z=+Ja!-X7!Es3d`0j~Dm1vxQq!)8&8Al$+Wb^NHnYhT<1~8@qg;Xol&N8T>c;U{&5fh literal 0 HcmV?d00001 diff --git a/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/libexample/libexample.so b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/libexample/libexample.so new file mode 100755 index 0000000000000000000000000000000000000000..08a0a01b31a4b97101a92b13aa3ba4976418adda GIT binary patch literal 15648 zcmeHOU2GIp6u#SSq5Sj*s9M0tXfOeP##Q-IOkrzjS+E6!_JOFGOuN&cxIcAwHnhZ_ zCPV`v8hkN65`qcFnDD3%CLl_9&_sPO`qpSjFdD2H6^vm$XXbp{nd#IY9!xa%CcEdJ z@1F0RJLlf*z1zL_h3?*-xuB-K{MTDsLo($X-!Nh&1L>LIm+-dC!2&$fQHX-@4O zX@pebmt!=rwdhf~Qo00*c7{Ed29v26-g`}+5*0GYTR?47rf)E{H7rj^ywf7Vt0Ob! z9T(nl;X&>dd&oxLt=C8H=V^8jBMlF&bz4Pw7ljv`SY* z=BAFeU;AFYGV*r%3Y&6T*$4ZT{-=?A#@{-4{U#FgmL6&`Vp{K+2j@P=*>n6je1P!f zYO%T|30pzBS1fBJUo2Q<*Dkr1rL3L(eOA^fIU{3b*D3Y)b>)f$r{5mTIeuGwi#0T1 zTf<`oJ2!U7QO<;&AI~|Koy|TVVeq-Ye4LSf9Fchs{EXo3X`cuj`t&v*=N$91qFfH( zGR3{7nE;M4<%X*P9CHu8wA2~U8PFNf8PFNf8PFNf8PFNf8Te-z_^IW#-!g~4Ys?&L z_~t&PGB2KW>#Cn*4u8;i-g8vl_!YrFR`2|pM9Uh*_N2YxY1@hLa>tjz+Da%SG+!x#zm*4CoB#4CoB#4CoB#4CoB#4CoB#4CoB# z4E*;qkXW63WGy`g|K?`QRI6!{DUzckuaTT0$%TJg<&rqGPbDT=6RVdlY&=ds>@oLN zdVTSIwd(yO*xcIF+`g-2$-%}cwQbdwyB=J72lJRuU*pwT*fB_jxlhvT8H(lo*4f?M z`chq2(}GfpO!Y`rU2y!JfWOUDNzi|n&>xP+h0p0HV)BzGoa4?!{7-uJbMyQ<;c@++ z@3~HTewx$?gDQ~{=jROBBxn*w$Ln1WUr~E5xcX4==(v1Fc%7O%pTF>kbLZQ)p8eeU z`GeKjKd?>Xk6>r4%AjT}aRI(>6r{I<*)o{tqJ65)m z&rcF1pjl+;hD_z^1og_YdiHhpbz9xLxAVP>?FV*u_U-H}E zQ8V3AvAQ!t&TQYOy#6R_NAI3TJA17?Jw5xo`>p=YM|-=;ZTRAbcl#s$hR2`W3khBK zh}PF94S=H@ltWzDY=u%tU-g7v0V1vv8?h8M(y&bGP9Ef za^_37q|B0&vl&#T_vq$$&NWAht}znztA25@v(1#1RuO;{KtsTdlvAqZbBZHNVpRPKK3X3sh#&G;A5WzIVgMx`WT1G z6Qpt9z{ffaiG5MD|A_ApmwjSiR$H&-?>F{;Wa1V0f&LyRvq^;bZ-W z{3|}s!C?Hf5FkH7M@2^c9g6U=pMb>v7;d7^KP7zRUm0R4a;>NkQT{8`!2Jgw`xD4# zK@^Gk1DMxOUemF^#Xbi2|DyKLAx{yvCBVmi=LmnWsKCzGW_93asDbAW;$xk~eNNol z#PfuA3I?4PFTWGNTJd!Ky+AJSjPXZb2Ewkcm?p2GupkndANFh17(cHzS= z%7=cDDr|%P8)?7An1|1?g5_gU7!&ha6Zm)45WfO`P-5-`P4|k!y)xl$p~m&}!t)?6 iiwHyCgZvX4d~Fngq%oq>jyIm)DEFB^4?3lKl>Z0R{uq@2 literal 0 HcmV?d00001 diff --git a/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/run.t b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/run.t new file mode 100644 index 00000000000..5b0b55f3765 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/run.t @@ -0,0 +1,26 @@ +Build an example library as a DLL and set up the environment so that it looks +like a system/distro library that can be probed with pkg-config and dynamically +loaded. + +Then generate cstubs for it, build an executable that uses those cstubs, and +run the executable that tests the library through the cstubs. + + $ cd libexample + $ make -s -f Makefile.unix + $ cd .. + + $ cat >libexample.pc < prefix=$PWD/libexample + > exec_prefix=$PWD/libexample + > libdir=$PWD/libexample + > includedir=$PWD/libexample + > Name: libexample + > Description: An example library for testing dune ctypes + > Requires: + > Version: 1.00.00 + > Libs: -L$PWD/libexample -lexample + > Cflags: -I$PWD/libexample + > EOF + + $ LD_LIBRARY_PATH="$PWD/libexample" PKG_CONFIG_PATH="$PKG_CONFIG_PATH:$PWD" dune exec ./example.exe + 4 diff --git a/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/type_description.ml b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/type_description.ml new file mode 100644 index 00000000000..41693fda9b3 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/type_description.ml @@ -0,0 +1,3 @@ +module Types (F : Ctypes.TYPE) = struct + +end diff --git a/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/dune b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/dune new file mode 100644 index 00000000000..251267cde5f --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/dune @@ -0,0 +1,3 @@ +(executable + (name example) + (libraries examplelib)) diff --git a/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/dune-project b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/dune-project new file mode 100644 index 00000000000..4cac8e20f22 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/dune-project @@ -0,0 +1,3 @@ +(lang dune 3.0) +(using ctypes 0.1) +(use_standard_c_and_cxx_flags false) diff --git a/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/example.ml b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/example.ml new file mode 100644 index 00000000000..eebafeb3114 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/example.ml @@ -0,0 +1,2 @@ +let () = + Printf.printf "%d\n" (Examplelib.C.Functions.add2 2) diff --git a/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/run.t b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/run.t new file mode 100644 index 00000000000..bed7fc2fbfa --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/run.t @@ -0,0 +1,26 @@ +Build an example library as a DLL and set up the environment so that it looks +like a system/distro library that can be probed with pkg-config and dynamically +loaded. + +Then generate cstubs for it, build an executable that uses those cstubs, and +run the executable that tests the library through the cstubs. + + $ cd stubgen/libexample + $ make -s -f Makefile.unix + $ cd ../.. + + $ cat >libexample.pc < prefix=$PWD/stubgen/libexample + > exec_prefix=$PWD/stubgen/libexample + > libdir=$PWD/stubgen/libexample + > includedir=$PWD/stubgen/libexample + > Name: libexample + > Description: An example library for testing dune ctypes + > Requires: + > Version: 1.00.00 + > Libs: -L$PWD/stubgen/libexample -lexample + > Cflags: -I$PWD/stubgen/libexample + > EOF + + $ LD_LIBRARY_PATH="$PWD/stubgen/libexample" PKG_CONFIG_PATH="$PWD:$PKG_CONFIG_PATH" dune exec ./example.exe + 4 diff --git a/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/dune b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/dune new file mode 100644 index 00000000000..a426491271d --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/dune @@ -0,0 +1,14 @@ +(library + (name examplelib) + (flags (:standard -w -9-27)) + (ctypes + (external_library_name libexample) + (build_flags_resolver pkg_config) + (headers (include "example.h")) + (type_description + (instance Types) + (functor Type_description)) + (function_description + (instance Functions) + (functor Function_description)) + (generated_entry_point C))) diff --git a/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/example.ml b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/example.ml new file mode 100644 index 00000000000..98a01761fa6 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/example.ml @@ -0,0 +1,2 @@ +let () = + Printf.printf "%d\n" (C.Functions.add2 2) diff --git a/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/function_description.ml b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/function_description.ml new file mode 100644 index 00000000000..05c43d79e2f --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/function_description.ml @@ -0,0 +1,8 @@ +open Ctypes + +module Types = Types_generated + +module Functions (F : Ctypes.FOREIGN) = struct + open F + let add2 = foreign "example_add2" (int @-> returning int) +end diff --git a/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/libexample/Makefile.unix b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/libexample/Makefile.unix new file mode 100644 index 00000000000..6b707dc9347 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/libexample/Makefile.unix @@ -0,0 +1,13 @@ +all: libexample.so libexample.a + +example.o: example.c + cc -c -fPIC -o example.o example.c + +libexample.a: example.o + ar rcs libexample.a example.o + +libexample.so: example.o + gcc -shared -o libexample.so example.o + +clean: + rm -f example.o libexample.so libexample.a diff --git a/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/libexample/example.c b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/libexample/example.c new file mode 100644 index 00000000000..544e41ad208 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/libexample/example.c @@ -0,0 +1 @@ +int example_add2(int x) { return x+2; } diff --git a/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/libexample/example.h b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/libexample/example.h new file mode 100644 index 00000000000..db8d04d2ab0 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/libexample/example.h @@ -0,0 +1 @@ +int example_add2(int); diff --git a/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/type_description.ml b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/type_description.ml new file mode 100644 index 00000000000..41693fda9b3 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/type_description.ml @@ -0,0 +1,3 @@ +module Types (F : Ctypes.TYPE) = struct + +end From 0be0ea697a3d6dd23b80822541f7507f7788f468 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Thu, 22 Jul 2021 06:54:13 -0700 Subject: [PATCH 58/69] more docs on using ctypes, with quick example ocaml code --- doc/dune-files.rst | 10 +++ doc/foreign-code.rst | 192 ++++++++++++++++++++++++++++++++++++++----- 2 files changed, 183 insertions(+), 19 deletions(-) diff --git a/doc/dune-files.rst b/doc/dune-files.rst index a9ed5ac1557..7d8caa1e3ff 100644 --- a/doc/dune-files.rst +++ b/doc/dune-files.rst @@ -590,6 +590,11 @@ to use the :ref:`include_subdirs` stanza. is useful whenever a library is shadowed by a local module. The library may then still be accessible via this root module +- ``(ctypes )`` instructs dune to use ctypes stubgen to process + your type and function descriptions for binding system libraries, vendored + libraries, or other foreign code. See :ref:`ctypes-stubgen` for a full + reference. + Note that when binding C libraries, dune doesn't provide special support for tools such as ``pkg-config``, however it integrates easily with :ref:`configurator` by @@ -787,6 +792,11 @@ files for executables. See `executables_implicit_empty_intf`_. flag if some of the libraries listed here are not referenced from any of the plugin modules. +- ``(ctypes )`` instructs dune to use ctypes stubgen to process + your type and function descriptions for binding system libraries, vendored + libraries, or other foreign code. See :ref:`ctypes-stubgen` for a full + reference. + Linking modes ~~~~~~~~~~~~~ diff --git a/doc/foreign-code.rst b/doc/foreign-code.rst index afa40f2c725..361f51750cb 100644 --- a/doc/foreign-code.rst +++ b/doc/foreign-code.rst @@ -64,60 +64,214 @@ without the ``.h`` extension. When a library install header files, these are made visible to users of the library via the include search path. -Stub Generation with Ctypes ---------------------------- +.. _ctypes-stubgen: + +Stub Generation with Dune Ctypes +================================ Beginning in dune 3.0, it is possible to use the ctypes_ stanza to generate bindings for C libraries without writing any C code. -To begin, you must declare the ctypes extension in your ``dune-project`` file. - -.. code:: scheme - - (lang dune 3.0) - (using ctypes 0.1) - Note that dune support for this feature is experimental and is not subject to backward compatibility guarantees. -Next, you need only provide two OCaml modules, named ``Type_description`` and -``Function_description`` which describe the types, values and functions you -want to access in the C library from OCaml. Additionally, you must list any C -headers and a method for resolving build and link flags. +To use dune ctypes stub generation, you must provide two OCaml modules: a "type +description" module for describing the C library types and constants, and a +"function description" module for describing the C library functions. +Additionally, you must list any C headers and a method for resolving build and +link flags. If you're binding a library distributed by your OS, you can use the ``pkg-config`` utility to resolve any build and link flags. Alternatively, if you're using a locally installed library or a vendored library, you can provide the flags manually. -The ``Type_description`` module must define a functor named ``Types`` with -signature ``Ctypes.TYPE``. The ``Function_description`` module must define a +The "type description" module must define a functor named ``Types`` with +signature ``Ctypes.TYPE``. The "function description" module must define a functor named ``Functions`` with signature ``Ctypes.FOREIGN``. +A toy example +------------- + +To begin, you must declare the ctypes extension in your ``dune-project`` file: + +.. code:: scheme + + (lang dune 3.0) + (using ctypes 0.1) + + +Next, here is a ``dune`` file you can use to define an OCaml program that +binds a C system library called ``libfoo``, which offers ``foo.h`` in a +standard location. + .. code:: scheme (executable (name foo) (libraries core) + ; ctypes backward compatibility shims warn sometimes; suppress them (flags (:standard -w -9-27)) (ctypes (external_library_name libfoo) (build_flags_resolver pkg_config) (headers (include "foo.h")) (type_description - (instance Types) + (instance Type) (functor Type_description)) (function_description (concurrency unlocked) - (instance Functions) - (functor Function_description)) + (instance Function) + (functor Function_descriptio)) + (generated_types Types_generated) (generated_entry_point C))) This stanza will introduce a module named ``C`` into your project, with the sub-modules ``Types`` and ``Functions`` that will have your fully bound C types, constants and functions. -A complete example of using the ctypes stanza is available here (TBD). +Given libfoo with the C header file ``foo.h``: + +.. code:: c + + #define FOO_VERSION 1 + + int foo_init(void); + + int foo_fnubar(char *); + + void foo_exit(void); + +Your example ``type_description.ml`` file is: + +.. code:: ocaml + + open Ctypes + + module Types (F : Ctypes.TYPE) = struct + open F + + let foo_version = constant "FOO_VERSION" int + end + +Your example ``function_description.ml`` file is: + +.. code:: ocaml + + open Ctypes + + (* This Types_generated module is an instantiation of the Types + functor defined in the type_description.ml file. It's generated by + a C program that dune creates and runs behind the scenes. *) + module Types = Types_generated + + module Functions (F : Ctypes.FOREIGN) = struct + open F + + let foo_init = foreign "foo_init" (void @-> returning int) + + let foo_fnubar = foreign "foo_fnubar" (string_opt @-> returning int) + + let foo_exit = foreign "foo_exit" (void @-> returning void) + end + +Finally, the entry point of your executable named above, ``foo.ml``, +demonstrates how to access the bound C library functions and values: + +.. code:: ocaml + + let () = + if (C.Types.foo_version <> 1) then + failwith "foo only works with libfoo version 1"; + + match C.Functions.foo_init () with + | 0 -> + C.Functions.foo_fnubar "fnubar!"; + C.Functions.foo_exit () + | err_code -> + Printf.eprintf "foo_init failed: %d" err_code; + ;; + +From here, one only needs to run ``dune build ./foo.exe`` to generate the +stubs and build and link the example ``foo.exe`` program. + +Complete information about the ctypes combinators used above is available at +the ctypes_ project. + +Ctypes stanza reference +------------------------ + +The ``ctypes`` stanza can be used in any ``executable(s)`` or ``library`` +stanza. + +.. code:: scheme + + ((executable|library) + ... + (ctypes + (external_library_name ) + (type_description + (instance ) + (functor )) + (function_description + (instance ) + (functor ) + ) + (generated_entry_point ) + ) + ) + +- ``type_description``: the ``functor`` module is a description of the C library + types and constants written in the ``ctypes`` domain-specific language you + wish to bind. The ``instance`` module is the name the functor will be + instantiated under, inserted into the top-level of the + ``generated_entry_point`` module. + +- ``function_description``: the ``functor`` module is a description of the C + library functions written in the ``ctypes`` domain-specific language you wish + to bind. The ``instance`` module is the name the functor will be + instantiated under, inserted into the top-level of the + ``generated_entry_point`` module. The ``function_description`` stanza can be + repeated. This is useful if you need to specify sets of functions with + different concurrency policies (see below). + +The instantiated types described above can be accessed from the function +descriptions by referencing them as the module specified in optional +``generated_types`` field. + +```` are: + +- ``(build_flags_resolver )`` tells dune how to + compile and link your foreign library. Specifying ``pkg_config`` will use + the ``pkg-config`` tool to query the compilation and link flags for + ``external_library_name``. For vendored libraries, provide the build and link + flags using ``vendored`` stanza. If ``build_flags_resolver`` is not + specified, the default of ``pkg_config`` will be used. + +- ``(generated_types )`` is the name of an intermediate module. By + default it is named ``Types_generated``. You can use this module to access + the types defined in ``Type_description`` from your ``Function_description`` + module(s). + +- ``(generated_entry_point )`` is the name of a generated module + that your instantiated ``Types`` and ``Function`` modules will instantiated + under. We suggest calling it ``C``. + +```` are: + +- ``(concurrency )`` tells ctypes + stubgen whether to call your C functions with the runtime lock held or + released. These correspond to the ``concurrency_policy`` type in the + ``ctypes`` library. If ``concurrency`` is not specified, the default of + ``sequential`` will be used. + +```` is: + +- ``(vendored (c_flags ) (c_library_flags ))`` provide the build + and link flags for binding your vendored code. You must also provide + instructions in your ``dune`` file on how to build the vendored foreign + library; see the :ref:`foreign_library` stanza. + .. _foreign-sandboxing: From a9a88e63a2a0d65144b4f8738d9078ab9e31767f Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Thu, 22 Jul 2021 08:01:31 -0700 Subject: [PATCH 59/69] more unit test coverage --- .../ctypes/exe-pkg_config-multiple-fd.t/dune | 19 +++++++++++ .../exe-pkg_config-multiple-fd.t/dune-project | 3 ++ .../exe-pkg_config-multiple-fd.t/example.ml | 4 +++ .../function_description_sequential.ml | 8 +++++ .../function_description_unlocked.ml | 8 +++++ .../gen-pc-file.sh | 14 ++++++++ .../libexample/Makefile.unix | 10 ++++++ .../libexample/example.c | 2 ++ .../libexample/example.h | 2 ++ .../ctypes/exe-pkg_config-multiple-fd.t/run.t | 28 +++++++++++++++ .../type_description.ml | 3 ++ .../ctypes/exe-vendored-multiple-fd.t/dune | 32 +++++++++++++++++ .../exe-vendored-multiple-fd.t/dune-project | 3 ++ .../exe-vendored-multiple-fd.t/example.ml | 4 +++ .../function_description_sequential.ml | 8 +++++ .../function_description_unlocked.ml | 8 +++++ .../ctypes/exe-vendored-multiple-fd.t/run.t | 11 ++++++ .../type_description.ml | 3 ++ .../vendor/Makefile.unix | 13 +++++++ .../vendor/example.c | 2 ++ .../vendor/example.h | 2 ++ .../ctypes/lib-pkg_config-multiple-fd.t/dune | 3 ++ .../lib-pkg_config-multiple-fd.t/dune-project | 3 ++ .../lib-pkg_config-multiple-fd.t/example.ml | 4 +++ .../ctypes/lib-pkg_config-multiple-fd.t/run.t | 29 ++++++++++++++++ .../lib-pkg_config-multiple-fd.t/stubgen/dune | 19 +++++++++++ .../function_description_sequential.ml | 8 +++++ .../stubgen/function_description_unlocked.ml | 8 +++++ .../stubgen/libexample/Makefile.unix | 13 +++++++ .../stubgen/libexample/example.c | 2 ++ .../stubgen/libexample/example.h | 2 ++ .../stubgen/type_description.ml | 3 ++ .../test-cases/ctypes/lib-pkg_config.t/run.t | 2 ++ .../lib-pkg_config.t/stubgen/example.ml | 2 -- .../ctypes/lib-vendored-multiple-fd.t/dune | 3 ++ .../lib-vendored-multiple-fd.t/dune-project | 3 ++ .../lib-vendored-multiple-fd.t/example.ml | 4 +++ .../ctypes/lib-vendored-multiple-fd.t/run.t | 11 ++++++ .../lib-vendored-multiple-fd.t/stubgen/dune | 34 +++++++++++++++++++ .../function_description_sequential.ml | 8 +++++ .../stubgen/function_description_unlocked.ml | 8 +++++ .../stubgen/type_description.ml | 3 ++ .../stubgen/vendor/Makefile.unix | 13 +++++++ .../stubgen/vendor/example.c | 2 ++ .../stubgen/vendor/example.h | 2 ++ .../ctypes/lib-vendored.t/stubgen/example.ml | 2 -- 46 files changed, 374 insertions(+), 4 deletions(-) create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/dune create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/dune-project create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/example.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/function_description_sequential.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/function_description_unlocked.ml create mode 100755 test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/gen-pc-file.sh create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/libexample/Makefile.unix create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/libexample/example.c create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/libexample/example.h create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/run.t create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/type_description.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/dune create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/dune-project create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/example.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/function_description_sequential.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/function_description_unlocked.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/run.t create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/type_description.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/vendor/Makefile.unix create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/vendor/example.c create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/vendor/example.h create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/dune create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/dune-project create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/example.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/run.t create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/stubgen/dune create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/stubgen/function_description_sequential.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/stubgen/function_description_unlocked.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/stubgen/libexample/Makefile.unix create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/stubgen/libexample/example.c create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/stubgen/libexample/example.h create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/stubgen/type_description.ml delete mode 100644 test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/example.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/dune create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/dune-project create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/example.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/run.t create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/stubgen/dune create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/stubgen/function_description_sequential.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/stubgen/function_description_unlocked.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/stubgen/type_description.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/stubgen/vendor/Makefile.unix create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/stubgen/vendor/example.c create mode 100644 test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/stubgen/vendor/example.h delete mode 100644 test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/example.ml diff --git a/test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/dune b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/dune new file mode 100644 index 00000000000..295954c35ce --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/dune @@ -0,0 +1,19 @@ +(executable + (name example) + (flags (:standard -w -9-27)) + (ctypes + (external_library_name libexample) + (build_flags_resolver pkg_config) + (headers (include "example.h")) + (type_description + (instance Types) + (functor Type_description)) + (function_description + (concurrency unlocked) + (instance Functions_unlocked) + (functor Function_description_unlocked)) + (function_description + (concurrency sequential) + (instance Functions_sequential) + (functor Function_description_sequential)) + (generated_entry_point C))) diff --git a/test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/dune-project b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/dune-project new file mode 100644 index 00000000000..4cac8e20f22 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/dune-project @@ -0,0 +1,3 @@ +(lang dune 3.0) +(using ctypes 0.1) +(use_standard_c_and_cxx_flags false) diff --git a/test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/example.ml b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/example.ml new file mode 100644 index 00000000000..5cbbbce91ac --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/example.ml @@ -0,0 +1,4 @@ +let () = + let r1 = C.Functions_sequential.add2 0 in + let r2 = C.Functions_unlocked.add4 r1 in + Printf.printf "%d\n" r2 diff --git a/test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/function_description_sequential.ml b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/function_description_sequential.ml new file mode 100644 index 00000000000..05c43d79e2f --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/function_description_sequential.ml @@ -0,0 +1,8 @@ +open Ctypes + +module Types = Types_generated + +module Functions (F : Ctypes.FOREIGN) = struct + open F + let add2 = foreign "example_add2" (int @-> returning int) +end diff --git a/test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/function_description_unlocked.ml b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/function_description_unlocked.ml new file mode 100644 index 00000000000..b91b7fd1da7 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/function_description_unlocked.ml @@ -0,0 +1,8 @@ +open Ctypes + +module Types = Types_generated + +module Functions (F : Ctypes.FOREIGN) = struct + open F + let add4 = foreign "example_add4" (int @-> returning int) +end diff --git a/test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/gen-pc-file.sh b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/gen-pc-file.sh new file mode 100755 index 00000000000..f8b2a68158e --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/gen-pc-file.sh @@ -0,0 +1,14 @@ +#!/bin/sh + +cat <libexample.pc < prefix=$PWD/libexample + > exec_prefix=$PWD/libexample + > libdir=$PWD/libexample + > includedir=$PWD/libexample + > Name: libexample + > Description: An example library for testing dune ctypes + > Requires: + > Version: 1.00.00 + > Libs: -L$PWD/libexample -lexample + > Cflags: -I$PWD/libexample + > EOF + + $ LD_LIBRARY_PATH="$PWD/libexample" PKG_CONFIG_PATH="$PKG_CONFIG_PATH:$PWD" dune exec ./example.exe + 6 diff --git a/test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/type_description.ml b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/type_description.ml new file mode 100644 index 00000000000..41693fda9b3 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/type_description.ml @@ -0,0 +1,3 @@ +module Types (F : Ctypes.TYPE) = struct + +end diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/dune b/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/dune new file mode 100644 index 00000000000..77af44df7da --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/dune @@ -0,0 +1,32 @@ +(rule + (targets libexample.a dllexample%{ext_dll}) + (deps (source_tree vendor)) + (action + (no-infer + (progn + (chdir vendor (run make -s -f Makefile.unix)) + (copy vendor/libexample.a libexample.a) + (copy vendor/libexample%{ext_dll} dllexample%{ext_dll}))))) + +(executable + (name example) + (flags (:standard -w -9-27)) + (foreign_archives example) + (ctypes + (external_library_name examplelib) + (build_flags_resolver + (vendored + (c_flags "-Ivendor"))) + (headers (include "example.h")) + (type_description + (instance Types) + (functor Type_description)) + (function_description + (concurrency sequential) + (instance Functions_sequential) + (functor Function_description_sequential)) + (function_description + (concurrency unlocked) + (instance Functions_unlocked) + (functor Function_description_unlocked)) + (generated_entry_point C))) diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/dune-project b/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/dune-project new file mode 100644 index 00000000000..4cac8e20f22 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/dune-project @@ -0,0 +1,3 @@ +(lang dune 3.0) +(using ctypes 0.1) +(use_standard_c_and_cxx_flags false) diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/example.ml b/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/example.ml new file mode 100644 index 00000000000..5e1ac2e16ba --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/example.ml @@ -0,0 +1,4 @@ +let () = + let r1 = C.Functions_unlocked.add4 0 in + let r2 = C.Functions_sequential.add2 r1 in + Printf.printf "%d\n" r2 diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/function_description_sequential.ml b/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/function_description_sequential.ml new file mode 100644 index 00000000000..05c43d79e2f --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/function_description_sequential.ml @@ -0,0 +1,8 @@ +open Ctypes + +module Types = Types_generated + +module Functions (F : Ctypes.FOREIGN) = struct + open F + let add2 = foreign "example_add2" (int @-> returning int) +end diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/function_description_unlocked.ml b/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/function_description_unlocked.ml new file mode 100644 index 00000000000..b91b7fd1da7 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/function_description_unlocked.ml @@ -0,0 +1,8 @@ +open Ctypes + +module Types = Types_generated + +module Functions (F : Ctypes.FOREIGN) = struct + open F + let add4 = foreign "example_add4" (int @-> returning int) +end diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/run.t b/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/run.t new file mode 100644 index 00000000000..24d2bb4699d --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/run.t @@ -0,0 +1,11 @@ +Generate cstubs for a "vendored" library. + +We have a dummy C library hosted entirely in the 'vendor' directory and use +the ctypes instrumentation and description language to generate bindings for +it. + +This is the version that builds into an executable and tests multiple function +description modules. + + $ dune exec ./example.exe + 6 diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/type_description.ml b/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/type_description.ml new file mode 100644 index 00000000000..41693fda9b3 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/type_description.ml @@ -0,0 +1,3 @@ +module Types (F : Ctypes.TYPE) = struct + +end diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/vendor/Makefile.unix b/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/vendor/Makefile.unix new file mode 100644 index 00000000000..6b707dc9347 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/vendor/Makefile.unix @@ -0,0 +1,13 @@ +all: libexample.so libexample.a + +example.o: example.c + cc -c -fPIC -o example.o example.c + +libexample.a: example.o + ar rcs libexample.a example.o + +libexample.so: example.o + gcc -shared -o libexample.so example.o + +clean: + rm -f example.o libexample.so libexample.a diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/vendor/example.c b/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/vendor/example.c new file mode 100644 index 00000000000..34252d06261 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/vendor/example.c @@ -0,0 +1,2 @@ +int example_add2(int x) { return x+2; } +int example_add4(int x) { return x+4; } diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/vendor/example.h b/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/vendor/example.h new file mode 100644 index 00000000000..ab205db17e6 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored-multiple-fd.t/vendor/example.h @@ -0,0 +1,2 @@ +int example_add2(int); +int example_add4(int); diff --git a/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/dune b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/dune new file mode 100644 index 00000000000..251267cde5f --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/dune @@ -0,0 +1,3 @@ +(executable + (name example) + (libraries examplelib)) diff --git a/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/dune-project b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/dune-project new file mode 100644 index 00000000000..4cac8e20f22 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/dune-project @@ -0,0 +1,3 @@ +(lang dune 3.0) +(using ctypes 0.1) +(use_standard_c_and_cxx_flags false) diff --git a/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/example.ml b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/example.ml new file mode 100644 index 00000000000..2b9eb46473b --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/example.ml @@ -0,0 +1,4 @@ +let () = + let r1 = Examplelib.C.Functions_sequential.add2 0 in + let r2 = Examplelib.C.Functions_unlocked.add4 r1 in + Printf.printf "%d\n" r2 diff --git a/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/run.t b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/run.t new file mode 100644 index 00000000000..9cd44893476 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/run.t @@ -0,0 +1,29 @@ +Build an example library as a DLL and set up the environment so that it looks +like a system/distro library that can be probed with pkg-config and dynamically +loaded. + +Then generate cstubs for it, build an executable that uses those cstubs, and +run the executable that tests the library through the cstubs. + +This test tries multiple function description modules, one locked and one +unlocked. + + $ cd stubgen/libexample + $ make -s -f Makefile.unix + $ cd ../.. + + $ cat >libexample.pc < prefix=$PWD/stubgen/libexample + > exec_prefix=$PWD/stubgen/libexample + > libdir=$PWD/stubgen/libexample + > includedir=$PWD/stubgen/libexample + > Name: libexample + > Description: An example library for testing dune ctypes + > Requires: + > Version: 1.00.00 + > Libs: -L$PWD/stubgen/libexample -lexample + > Cflags: -I$PWD/stubgen/libexample + > EOF + + $ LD_LIBRARY_PATH="$PWD/stubgen/libexample" PKG_CONFIG_PATH="$PWD:$PKG_CONFIG_PATH" dune exec ./example.exe + 6 diff --git a/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/stubgen/dune b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/stubgen/dune new file mode 100644 index 00000000000..7cc43c15a9c --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/stubgen/dune @@ -0,0 +1,19 @@ +(library + (name examplelib) + (flags (:standard -w -9-27)) + (ctypes + (external_library_name libexample) + (build_flags_resolver pkg_config) + (headers (include "example.h")) + (type_description + (instance Types) + (functor Type_description)) + (function_description + (concurrency unlocked) + (instance Functions_unlocked) + (functor Function_description_unlocked)) + (function_description + (concurrency sequential) + (instance Functions_sequential) + (functor Function_description_sequential)) + (generated_entry_point C))) diff --git a/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/stubgen/function_description_sequential.ml b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/stubgen/function_description_sequential.ml new file mode 100644 index 00000000000..05c43d79e2f --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/stubgen/function_description_sequential.ml @@ -0,0 +1,8 @@ +open Ctypes + +module Types = Types_generated + +module Functions (F : Ctypes.FOREIGN) = struct + open F + let add2 = foreign "example_add2" (int @-> returning int) +end diff --git a/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/stubgen/function_description_unlocked.ml b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/stubgen/function_description_unlocked.ml new file mode 100644 index 00000000000..b91b7fd1da7 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/stubgen/function_description_unlocked.ml @@ -0,0 +1,8 @@ +open Ctypes + +module Types = Types_generated + +module Functions (F : Ctypes.FOREIGN) = struct + open F + let add4 = foreign "example_add4" (int @-> returning int) +end diff --git a/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/stubgen/libexample/Makefile.unix b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/stubgen/libexample/Makefile.unix new file mode 100644 index 00000000000..6b707dc9347 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/stubgen/libexample/Makefile.unix @@ -0,0 +1,13 @@ +all: libexample.so libexample.a + +example.o: example.c + cc -c -fPIC -o example.o example.c + +libexample.a: example.o + ar rcs libexample.a example.o + +libexample.so: example.o + gcc -shared -o libexample.so example.o + +clean: + rm -f example.o libexample.so libexample.a diff --git a/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/stubgen/libexample/example.c b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/stubgen/libexample/example.c new file mode 100644 index 00000000000..34252d06261 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/stubgen/libexample/example.c @@ -0,0 +1,2 @@ +int example_add2(int x) { return x+2; } +int example_add4(int x) { return x+4; } diff --git a/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/stubgen/libexample/example.h b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/stubgen/libexample/example.h new file mode 100644 index 00000000000..ab205db17e6 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/stubgen/libexample/example.h @@ -0,0 +1,2 @@ +int example_add2(int); +int example_add4(int); diff --git a/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/stubgen/type_description.ml b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/stubgen/type_description.ml new file mode 100644 index 00000000000..41693fda9b3 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config-multiple-fd.t/stubgen/type_description.ml @@ -0,0 +1,3 @@ +module Types (F : Ctypes.TYPE) = struct + +end diff --git a/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/run.t b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/run.t index bed7fc2fbfa..7c16a24e48a 100644 --- a/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/run.t +++ b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/run.t @@ -5,6 +5,8 @@ loaded. Then generate cstubs for it, build an executable that uses those cstubs, and run the executable that tests the library through the cstubs. +This test tries a single function description stanza. + $ cd stubgen/libexample $ make -s -f Makefile.unix $ cd ../.. diff --git a/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/example.ml b/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/example.ml deleted file mode 100644 index 98a01761fa6..00000000000 --- a/test/blackbox-tests/test-cases/ctypes/lib-pkg_config.t/stubgen/example.ml +++ /dev/null @@ -1,2 +0,0 @@ -let () = - Printf.printf "%d\n" (C.Functions.add2 2) diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/dune b/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/dune new file mode 100644 index 00000000000..251267cde5f --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/dune @@ -0,0 +1,3 @@ +(executable + (name example) + (libraries examplelib)) diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/dune-project b/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/dune-project new file mode 100644 index 00000000000..4cac8e20f22 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/dune-project @@ -0,0 +1,3 @@ +(lang dune 3.0) +(using ctypes 0.1) +(use_standard_c_and_cxx_flags false) diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/example.ml b/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/example.ml new file mode 100644 index 00000000000..2b9eb46473b --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/example.ml @@ -0,0 +1,4 @@ +let () = + let r1 = Examplelib.C.Functions_sequential.add2 0 in + let r2 = Examplelib.C.Functions_unlocked.add4 r1 in + Printf.printf "%d\n" r2 diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/run.t b/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/run.t new file mode 100644 index 00000000000..97750836771 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/run.t @@ -0,0 +1,11 @@ +Generate cstubs for a "vendored" library. + +We have a dummy C library hosted entirely in the 'vendor' directory and use +the ctypes instrumentation and description language to generate bindings for +it. + +This is the version that builds into a library and tests multiple function +description modules. + + $ dune exec ./example.exe + 6 diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/stubgen/dune b/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/stubgen/dune new file mode 100644 index 00000000000..b551b365930 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/stubgen/dune @@ -0,0 +1,34 @@ +(rule + (targets libexample.a dllexample%{ext_dll}) + (deps (source_tree vendor)) + (action + (no-infer + (progn + (chdir vendor (run make -s -f Makefile.unix)) + (copy vendor/libexample.a libexample.a) + (copy vendor/libexample%{ext_dll} dllexample%{ext_dll}))))) + +(library + (name examplelib) + (flags (:standard -w -9-27)) + (foreign_archives example) + (ctypes + (external_library_name examplelib) + (build_flags_resolver + (vendored + ; hack: multiple -I directives to work around cc commands being run from different + ; relative directories. Is there a cleaner way to do this? + (c_flags ("-Istubgen/vendor" "-Ivendor")))) + (headers (include "example.h")) + (type_description + (instance Types) + (functor Type_description)) + (function_description + (concurrency sequential) + (instance Functions_sequential) + (functor Function_description_sequential)) + (function_description + (concurrency unlocked) + (instance Functions_unlocked) + (functor Function_description_unlocked)) + (generated_entry_point C))) diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/stubgen/function_description_sequential.ml b/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/stubgen/function_description_sequential.ml new file mode 100644 index 00000000000..05c43d79e2f --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/stubgen/function_description_sequential.ml @@ -0,0 +1,8 @@ +open Ctypes + +module Types = Types_generated + +module Functions (F : Ctypes.FOREIGN) = struct + open F + let add2 = foreign "example_add2" (int @-> returning int) +end diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/stubgen/function_description_unlocked.ml b/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/stubgen/function_description_unlocked.ml new file mode 100644 index 00000000000..b91b7fd1da7 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/stubgen/function_description_unlocked.ml @@ -0,0 +1,8 @@ +open Ctypes + +module Types = Types_generated + +module Functions (F : Ctypes.FOREIGN) = struct + open F + let add4 = foreign "example_add4" (int @-> returning int) +end diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/stubgen/type_description.ml b/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/stubgen/type_description.ml new file mode 100644 index 00000000000..41693fda9b3 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/stubgen/type_description.ml @@ -0,0 +1,3 @@ +module Types (F : Ctypes.TYPE) = struct + +end diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/stubgen/vendor/Makefile.unix b/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/stubgen/vendor/Makefile.unix new file mode 100644 index 00000000000..6b707dc9347 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/stubgen/vendor/Makefile.unix @@ -0,0 +1,13 @@ +all: libexample.so libexample.a + +example.o: example.c + cc -c -fPIC -o example.o example.c + +libexample.a: example.o + ar rcs libexample.a example.o + +libexample.so: example.o + gcc -shared -o libexample.so example.o + +clean: + rm -f example.o libexample.so libexample.a diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/stubgen/vendor/example.c b/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/stubgen/vendor/example.c new file mode 100644 index 00000000000..34252d06261 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/stubgen/vendor/example.c @@ -0,0 +1,2 @@ +int example_add2(int x) { return x+2; } +int example_add4(int x) { return x+4; } diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/stubgen/vendor/example.h b/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/stubgen/vendor/example.h new file mode 100644 index 00000000000..ab205db17e6 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/lib-vendored-multiple-fd.t/stubgen/vendor/example.h @@ -0,0 +1,2 @@ +int example_add2(int); +int example_add4(int); diff --git a/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/example.ml b/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/example.ml deleted file mode 100644 index 98a01761fa6..00000000000 --- a/test/blackbox-tests/test-cases/ctypes/lib-vendored.t/stubgen/example.ml +++ /dev/null @@ -1,2 +0,0 @@ -let () = - Printf.printf "%d\n" (C.Functions.add2 2) From 4f341ec4e14fe50ee848729414eeeb19f48eb3ff Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Thu, 22 Jul 2021 08:02:24 -0700 Subject: [PATCH 60/69] unneeded file --- .../exe-pkg_config-multiple-fd.t/gen-pc-file.sh | 14 -------------- .../ctypes/exe-pkg_config.t/gen-pc-file.sh | 14 -------------- 2 files changed, 28 deletions(-) delete mode 100755 test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/gen-pc-file.sh delete mode 100755 test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/gen-pc-file.sh diff --git a/test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/gen-pc-file.sh b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/gen-pc-file.sh deleted file mode 100755 index f8b2a68158e..00000000000 --- a/test/blackbox-tests/test-cases/ctypes/exe-pkg_config-multiple-fd.t/gen-pc-file.sh +++ /dev/null @@ -1,14 +0,0 @@ -#!/bin/sh - -cat < Date: Thu, 22 Jul 2021 08:06:04 -0700 Subject: [PATCH 61/69] coverage for preamble headers --- .../ctypes/exe-vendored-preamble.t/dune | 27 +++++++++++++++++++ .../exe-vendored-preamble.t/dune-project | 3 +++ .../ctypes/exe-vendored-preamble.t/example.ml | 2 ++ .../function_description.ml | 8 ++++++ .../ctypes/exe-vendored-preamble.t/run.t | 13 +++++++++ .../type_description.ml | 3 +++ .../vendor/Makefile.unix | 13 +++++++++ .../exe-vendored-preamble.t/vendor/example.c | 1 + .../exe-vendored-preamble.t/vendor/example.h | 1 + 9 files changed, 71 insertions(+) create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/dune create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/dune-project create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/example.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/function_description.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/run.t create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/type_description.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/vendor/Makefile.unix create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/vendor/example.c create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/vendor/example.h diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/dune b/test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/dune new file mode 100644 index 00000000000..8e37bd6deec --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/dune @@ -0,0 +1,27 @@ +(rule + (targets libexample.a dllexample%{ext_dll}) + (deps (source_tree vendor)) + (action + (no-infer + (progn + (chdir vendor (run make -s -f Makefile.unix)) + (copy vendor/libexample.a libexample.a) + (copy vendor/libexample%{ext_dll} dllexample%{ext_dll}))))) + +(executable + (name example) + (flags (:standard -w -9-27)) + (foreign_archives example) + (ctypes + (external_library_name examplelib) + (build_flags_resolver + (vendored + (c_flags "-Ivendor"))) + (headers (preamble "#include ")) + (type_description + (instance Types) + (functor Type_description)) + (function_description + (instance Functions) + (functor Function_description)) + (generated_entry_point C))) diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/dune-project b/test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/dune-project new file mode 100644 index 00000000000..4cac8e20f22 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/dune-project @@ -0,0 +1,3 @@ +(lang dune 3.0) +(using ctypes 0.1) +(use_standard_c_and_cxx_flags false) diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/example.ml b/test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/example.ml new file mode 100644 index 00000000000..98a01761fa6 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/example.ml @@ -0,0 +1,2 @@ +let () = + Printf.printf "%d\n" (C.Functions.add2 2) diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/function_description.ml b/test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/function_description.ml new file mode 100644 index 00000000000..05c43d79e2f --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/function_description.ml @@ -0,0 +1,8 @@ +open Ctypes + +module Types = Types_generated + +module Functions (F : Ctypes.FOREIGN) = struct + open F + let add2 = foreign "example_add2" (int @-> returning int) +end diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/run.t b/test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/run.t new file mode 100644 index 00000000000..dc7659f590f --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/run.t @@ -0,0 +1,13 @@ +Generate cstubs for a "vendored" library. + +We have a dummy C library hosted entirely in the 'vendor' directory and use +the ctypes instrumentation and description language to generate bindings for +it. + +This is the version that builds into an executable. + +This test is identical to exe-vendored.t except it uses preamble instead of +include to require the example.h header. + + $ dune exec ./example.exe + 4 diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/type_description.ml b/test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/type_description.ml new file mode 100644 index 00000000000..41693fda9b3 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/type_description.ml @@ -0,0 +1,3 @@ +module Types (F : Ctypes.TYPE) = struct + +end diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/vendor/Makefile.unix b/test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/vendor/Makefile.unix new file mode 100644 index 00000000000..6b707dc9347 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/vendor/Makefile.unix @@ -0,0 +1,13 @@ +all: libexample.so libexample.a + +example.o: example.c + cc -c -fPIC -o example.o example.c + +libexample.a: example.o + ar rcs libexample.a example.o + +libexample.so: example.o + gcc -shared -o libexample.so example.o + +clean: + rm -f example.o libexample.so libexample.a diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/vendor/example.c b/test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/vendor/example.c new file mode 100644 index 00000000000..544e41ad208 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/vendor/example.c @@ -0,0 +1 @@ +int example_add2(int x) { return x+2; } diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/vendor/example.h b/test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/vendor/example.h new file mode 100644 index 00000000000..db8d04d2ab0 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored-preamble.t/vendor/example.h @@ -0,0 +1 @@ +int example_add2(int); From 9e165d615c04c115acf0dbdf6b058f45f1762d54 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Thu, 22 Jul 2021 08:11:49 -0700 Subject: [PATCH 62/69] one more test --- .../dune | 28 +++++++++++++++++++ .../dune-project | 3 ++ .../example.ml | 2 ++ .../function_description.ml | 8 ++++++ .../run.t | 13 +++++++++ .../type_description.ml | 3 ++ .../vendor/Makefile.unix | 13 +++++++++ .../vendor/example.c | 1 + .../vendor/example.h | 1 + 9 files changed, 72 insertions(+) create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/dune create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/dune-project create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/example.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/function_description.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/run.t create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/type_description.ml create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/vendor/Makefile.unix create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/vendor/example.c create mode 100644 test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/vendor/example.h diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/dune b/test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/dune new file mode 100644 index 00000000000..4d576f8f943 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/dune @@ -0,0 +1,28 @@ +(rule + (targets libexample.a dllexample%{ext_dll}) + (deps (source_tree vendor)) + (action + (no-infer + (progn + (chdir vendor (run make -s -f Makefile.unix)) + (copy vendor/libexample.a libexample.a) + (copy vendor/libexample%{ext_dll} dllexample%{ext_dll}))))) + +(executable + (name example) + (flags (:standard -w -9-27)) + (foreign_archives example) + (ctypes + (external_library_name examplelib) + (build_flags_resolver + (vendored + (c_flags "-Ivendor"))) + (headers (include "example.h")) + (type_description + (instance Types) + (functor Type_description)) + (function_description + (instance Functions) + (functor Function_description)) + (generated_types My_generated_types) + (generated_entry_point C))) diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/dune-project b/test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/dune-project new file mode 100644 index 00000000000..4cac8e20f22 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/dune-project @@ -0,0 +1,3 @@ +(lang dune 3.0) +(using ctypes 0.1) +(use_standard_c_and_cxx_flags false) diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/example.ml b/test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/example.ml new file mode 100644 index 00000000000..98a01761fa6 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/example.ml @@ -0,0 +1,2 @@ +let () = + Printf.printf "%d\n" (C.Functions.add2 2) diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/function_description.ml b/test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/function_description.ml new file mode 100644 index 00000000000..87c06376d67 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/function_description.ml @@ -0,0 +1,8 @@ +open Ctypes + +module Types = My_generated_types + +module Functions (F : Ctypes.FOREIGN) = struct + open F + let add2 = foreign "example_add2" (int @-> returning int) +end diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/run.t b/test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/run.t new file mode 100644 index 00000000000..6c6208c3459 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/run.t @@ -0,0 +1,13 @@ +Generate cstubs for a "vendored" library. + +We have a dummy C library hosted entirely in the 'vendor' directory and use +the ctypes instrumentation and description language to generate bindings for +it. + +This is the version that builds into an executable. + +This test is identical to exe-vendored.t except it overrides the +generated_types stanza field. + + $ dune exec ./example.exe + 4 diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/type_description.ml b/test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/type_description.ml new file mode 100644 index 00000000000..41693fda9b3 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/type_description.ml @@ -0,0 +1,3 @@ +module Types (F : Ctypes.TYPE) = struct + +end diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/vendor/Makefile.unix b/test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/vendor/Makefile.unix new file mode 100644 index 00000000000..6b707dc9347 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/vendor/Makefile.unix @@ -0,0 +1,13 @@ +all: libexample.so libexample.a + +example.o: example.c + cc -c -fPIC -o example.o example.c + +libexample.a: example.o + ar rcs libexample.a example.o + +libexample.so: example.o + gcc -shared -o libexample.so example.o + +clean: + rm -f example.o libexample.so libexample.a diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/vendor/example.c b/test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/vendor/example.c new file mode 100644 index 00000000000..544e41ad208 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/vendor/example.c @@ -0,0 +1 @@ +int example_add2(int x) { return x+2; } diff --git a/test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/vendor/example.h b/test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/vendor/example.h new file mode 100644 index 00000000000..db8d04d2ab0 --- /dev/null +++ b/test/blackbox-tests/test-cases/ctypes/exe-vendored-override-types-generated.t/vendor/example.h @@ -0,0 +1 @@ +int example_add2(int); From 5f5741098d7c5fa0d9709d1b4bf458dfdfcc8348 Mon Sep 17 00:00:00 2001 From: Michael Bacarella Date: Thu, 14 Oct 2021 20:54:28 -0700 Subject: [PATCH 63/69] resolve merge conflict markers in doc --- doc/dune-files.rst | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/doc/dune-files.rst b/doc/dune-files.rst index 5c1c00290e4..d0feadda8cb 100644 --- a/doc/dune-files.rst +++ b/doc/dune-files.rst @@ -626,17 +626,15 @@ to use the :ref:`include_subdirs` stanza. is useful whenever a library is shadowed by a local module. The library may then still be accessible via this root module -<<<<<<< HEAD - ``(ctypes )`` instructs dune to use ctypes stubgen to process your type and function descriptions for binding system libraries, vendored libraries, or other foreign code. See :ref:`ctypes-stubgen` for a full - reference. -======= + reference. This field is available since the 3.0 version of the dune language. + - ``(empty_module_interface_if_absent)`` causes the generation of empty interfaces for every module that does not have an interface file already. Useful when modules are used solely for their side-effects. This field is available since the 3.0 version of the dune language. ->>>>>>> master Note that when binding C libraries, dune doesn't provide special support for tools such as ``pkg-config``, however it integrates easily with From 52ed839e4bb8c255561f117a3deb364465120db1 Mon Sep 17 00:00:00 2001 From: Rudi Grinberg Date: Sat, 16 Oct 2021 18:31:54 -0600 Subject: [PATCH 64/69] fix(ctypes): busted merge conflict Signed-off-by: Rudi Grinberg --- src/dune_rules/ctypes_rules.ml | 19 ++++++++++--------- src/dune_rules/dir_contents.ml | 3 ++- 2 files changed, 12 insertions(+), 10 deletions(-) diff --git a/src/dune_rules/ctypes_rules.ml b/src/dune_rules/ctypes_rules.ml index 291a88925a7..1b6fa5e79f6 100644 --- a/src/dune_rules/ctypes_rules.ml +++ b/src/dune_rules/ctypes_rules.ml @@ -52,7 +52,8 @@ open! Stdune This implementation is not, however, a naive translation of the boilerplate above. This module uses dune internal features to simplify the stub - generation. As a result, there are no intermediate libraries (or packages). *) + generation. As a result, there are no intermediate libraries (or + packages). *) module Buildable = Dune_file.Buildable module Library = Dune_file.Library @@ -132,9 +133,9 @@ module Stanza_util = struct let non_installable_modules ctypes = type_gen_script_module ctypes - :: - List.map ctypes.Ctypes.function_description ~f:(fun function_description -> - function_gen_script_module ctypes function_description) + :: List.map ctypes.Ctypes.function_description + ~f:(fun function_description -> + function_gen_script_module ctypes function_description) let generated_ml_and_c_files ctypes = let ml_files = @@ -324,10 +325,9 @@ let build_c_program ~sctx ~dir ~source_files ~scope ~cflags_sexp ~output () = |> Super_context.resolve_program ~loc:None ~dir sctx in let include_args = - (* XXX: need glob dependency *) let ocaml_where = Path.to_string ctx.Context.stdlib_dir in (* XXX: need glob dependency *) - let open Resolve.O in + let open Resolve.Build.O in let+ ctypes_include_dirs = let+ lib = let ctypes = Lib_name.of_string "ctypes" in @@ -376,7 +376,7 @@ let build_c_program ~sctx ~dir ~source_files ~scope ~cflags_sexp ~output () = in let action = let open Action_builder.O in - let* include_args = Resolve.read include_args in + let* include_args = Resolve.Build.read include_args in Action_builder.deps deps >>> Action_builder.map cflags_args ~f:(fun cflags_args -> let source_files = List.map source_files ~f:absolute_path_hack in @@ -391,7 +391,8 @@ let build_c_program ~sctx ~dir ~source_files ~scope ~cflags_sexp ~output () = in Super_context.add_rule sctx ~dir build -let cctx_with_substitutions ?(libraries = []) ~modules ~dir ~loc ~scope ~cctx = +let cctx_with_substitutions ?(libraries = []) ~modules ~dir ~loc ~scope ~cctx () + = let compile_info = let dune_version = Scope.project scope |> Dune_project.dune_version in Lib.DB.resolve_user_written_deps_for_exes (Scope.libs scope) @@ -422,7 +423,7 @@ let exe_build_and_link ?libraries ?(modules = []) ~scope ~loc ~dir ~cctx program = let cctx = cctx_with_substitutions ?libraries ~loc ~scope ~dir ~cctx - ~modules:(program :: modules) + ~modules:(program :: modules) () in let program = program_of_module_and_dir ~dir program in Exe.build_and_link ~program ~linkages:[ Exe.Linkage.native ] ~promote:None diff --git a/src/dune_rules/dir_contents.ml b/src/dune_rules/dir_contents.ml index fb7276b89f7..2fe2538f5ab 100644 --- a/src/dune_rules/dir_contents.ml +++ b/src/dune_rules/dir_contents.ml @@ -156,7 +156,8 @@ end = struct | Library { buildable; _ } | Executables { buildable; _ } -> let select_deps_files = - (* Manually add files generated by the (select ...) dependencies *) + (* Manually add files generated by the (select ...) + dependencies *) List.filter_map buildable.libraries ~f:(fun dep -> match (dep : Lib_dep.t) with | Re_export _ From 8fa4100928d9bc0c1b00fffef9c153ffa5cf6891 Mon Sep 17 00:00:00 2001 From: Rudi Grinberg Date: Sat, 16 Oct 2021 18:33:29 -0600 Subject: [PATCH 65/69] test(ctypes): require ctypes as test dependency Signed-off-by: Rudi Grinberg --- test/blackbox-tests/test-cases/dune | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/test/blackbox-tests/test-cases/dune b/test/blackbox-tests/test-cases/dune index bd1ad3a02b0..32c40997185 100644 --- a/test/blackbox-tests/test-cases/dune +++ b/test/blackbox-tests/test-cases/dune @@ -75,6 +75,12 @@ (enabled_if (<> %{ocaml_version} 4.02.3)))) +(subdir + ctypes + (cram + (deps + (package ctypes)))) + (cram (applies_to output-obj) (enabled_if From 627967e01c5ece577fc3718d1ee6fdc1b2b3212f Mon Sep 17 00:00:00 2001 From: Rudi Grinberg Date: Sat, 16 Oct 2021 18:47:07 -0600 Subject: [PATCH 66/69] test(ctypes): remove binaries Signed-off-by: Rudi Grinberg --- .../exe-pkg_config.t/libexample/example.o | Bin 1376 -> 0 bytes .../exe-pkg_config.t/libexample/libexample.a | Bin 1526 -> 0 bytes .../exe-pkg_config.t/libexample/libexample.so | Bin 15648 -> 0 bytes 3 files changed, 0 insertions(+), 0 deletions(-) delete mode 100644 test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/libexample/example.o delete mode 100644 test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/libexample/libexample.a delete mode 100755 test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/libexample/libexample.so diff --git a/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/libexample/example.o b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/libexample/example.o deleted file mode 100644 index 2e9862d5821b4b550c90663312849badca60259d..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 1376 zcmbtTOG_g`5U$DiTwn2V5EO|gUDPJN@Ntkph>C~@C9oH9CrPWIlZ2TLM8O9Lf_U*K z_)`Qg`x88R@ve9g5wvQiJL&Ys%WgrvzOJvkYP#nvwZ0s&EKp*>5>zvV0{o6t<3tc9 zpdH%awQJ}-y?XU@b@FkY`nb4@Y~RC5GPxKVO=n7ZQHm|FX%?TDoGS(C8*Fe8aZ-|AGO5n!WhB|rw1x$g zeWqz4ctuDiu z5T@RfTH8{A;Z6PsuG4$^SN=G1Y0o&SF6#U-9mH6jul%fr>7}Q7qQ#1*pcDr5x@zto z^K(>^SYWHh{CBo-iS{)4w~{h1y>cf17cS5%PN)LuA7!KcGH*pseJZ}f>zz%M2Qnzn np@SdjX%CZ6n0a?Z`D2_<7>R_#1Z_8JJ^q_4+^bZEfyw^@9avV* diff --git a/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/libexample/libexample.a b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/libexample/libexample.a deleted file mode 100644 index be384fb8c69d0b90b6d9b80cc8f99954344484fb..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 1526 zcmbtUUuzRV5TDD{R@16!^+Bk}^-0Bcy`-^KkrD{8BI1J*5TP`iWNpA+67DXL3RXc7 ziZ6ZyKT5$DKZ1|G_^$XOQqYK<6ohj4;>Iu}%hjqYX4hi#7NzN++-it@z4GZ4l+|0@Mc-@PLlaidH zrFN$9Hdj48eIFAjo*>le6ny_ZZrdN*Io-u--Xi*=TUsExzU(H8QRKt)-=M^2CgAiX zvNDU|f^|>XJEfQ*XcJ+4kxg&rez}USI_h7? z$CIppB{YPYdD3a{*f@@L`Im8@=ILMg%gCjgA*wCr{A)IdzB%968y04#?%RRo8=iq` z=+Ja!-X7!Es3d`0j~Dm1vxQq!)8&8Al$+Wb^NHnYhT<1~8@qg;Xol&N8T>c;U{&5fh diff --git a/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/libexample/libexample.so b/test/blackbox-tests/test-cases/ctypes/exe-pkg_config.t/libexample/libexample.so deleted file mode 100755 index 08a0a01b31a4b97101a92b13aa3ba4976418adda..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 15648 zcmeHOU2GIp6u#SSq5Sj*s9M0tXfOeP##Q-IOkrzjS+E6!_JOFGOuN&cxIcAwHnhZ_ zCPV`v8hkN65`qcFnDD3%CLl_9&_sPO`qpSjFdD2H6^vm$XXbp{nd#IY9!xa%CcEdJ z@1F0RJLlf*z1zL_h3?*-xuB-K{MTDsLo($X-!Nh&1L>LIm+-dC!2&$fQHX-@4O zX@pebmt!=rwdhf~Qo00*c7{Ed29v26-g`}+5*0GYTR?47rf)E{H7rj^ywf7Vt0Ob! z9T(nl;X&>dd&oxLt=C8H=V^8jBMlF&bz4Pw7ljv`SY* z=BAFeU;AFYGV*r%3Y&6T*$4ZT{-=?A#@{-4{U#FgmL6&`Vp{K+2j@P=*>n6je1P!f zYO%T|30pzBS1fBJUo2Q<*Dkr1rL3L(eOA^fIU{3b*D3Y)b>)f$r{5mTIeuGwi#0T1 zTf<`oJ2!U7QO<;&AI~|Koy|TVVeq-Ye4LSf9Fchs{EXo3X`cuj`t&v*=N$91qFfH( zGR3{7nE;M4<%X*P9CHu8wA2~U8PFNf8PFNf8PFNf8PFNf8Te-z_^IW#-!g~4Ys?&L z_~t&PGB2KW>#Cn*4u8;i-g8vl_!YrFR`2|pM9Uh*_N2YxY1@hLa>tjz+Da%SG+!x#zm*4CoB#4CoB#4CoB#4CoB#4CoB#4CoB# z4E*;qkXW63WGy`g|K?`QRI6!{DUzckuaTT0$%TJg<&rqGPbDT=6RVdlY&=ds>@oLN zdVTSIwd(yO*xcIF+`g-2$-%}cwQbdwyB=J72lJRuU*pwT*fB_jxlhvT8H(lo*4f?M z`chq2(}GfpO!Y`rU2y!JfWOUDNzi|n&>xP+h0p0HV)BzGoa4?!{7-uJbMyQ<;c@++ z@3~HTewx$?gDQ~{=jROBBxn*w$Ln1WUr~E5xcX4==(v1Fc%7O%pTF>kbLZQ)p8eeU z`GeKjKd?>Xk6>r4%AjT}aRI(>6r{I<*)o{tqJ65)m z&rcF1pjl+;hD_z^1og_YdiHhpbz9xLxAVP>?FV*u_U-H}E zQ8V3AvAQ!t&TQYOy#6R_NAI3TJA17?Jw5xo`>p=YM|-=;ZTRAbcl#s$hR2`W3khBK zh}PF94S=H@ltWzDY=u%tU-g7v0V1vv8?h8M(y&bGP9Ef za^_37q|B0&vl&#T_vq$$&NWAht}znztA25@v(1#1RuO;{KtsTdlvAqZbBZHNVpRPKK3X3sh#&G;A5WzIVgMx`WT1G z6Qpt9z{ffaiG5MD|A_ApmwjSiR$H&-?>F{;Wa1V0f&LyRvq^;bZ-W z{3|}s!C?Hf5FkH7M@2^c9g6U=pMb>v7;d7^KP7zRUm0R4a;>NkQT{8`!2Jgw`xD4# zK@^Gk1DMxOUemF^#Xbi2|DyKLAx{yvCBVmi=LmnWsKCzGW_93asDbAW;$xk~eNNol z#PfuA3I?4PFTWGNTJd!Ky+AJSjPXZb2Ewkcm?p2GupkndANFh17(cHzS= z%7=cDDr|%P8)?7An1|1?g5_gU7!&ha6Zm)45WfO`P-5-`P4|k!y)xl$p~m&}!t)?6 iiwHyCgZvX4d~Fngq%oq>jyIm)DEFB^4?3lKl>Z0R{uq@2 From 18ca12c6259bb7f1c908b477d484405a41769288 Mon Sep 17 00:00:00 2001 From: Rudi Grinberg Date: Sat, 16 Oct 2021 19:29:44 -0600 Subject: [PATCH 67/69] chore(nix): add ctypes to test dependencies Signed-off-by: Rudi Grinberg --- nix/default.nix | 1 + nix/opam-selection.nix | 64 ++++++++++++++++++++++++++++++++++++++++++ shell.nix | 1 + 3 files changed, 66 insertions(+) diff --git a/nix/default.nix b/nix/default.nix index 861c2777d59..8214af663ae 100644 --- a/nix/default.nix +++ b/nix/default.nix @@ -40,6 +40,7 @@ let "ppxlib" "result" "utop" + "ctypes" "${coq}/coq-core.opam" ]); diff --git a/nix/opam-selection.nix b/nix/opam-selection.nix index 2a9a00ad3fa..eedcb9efaf5 100644 --- a/nix/opam-selection.nix +++ b/nix/opam-selection.nix @@ -163,6 +163,26 @@ in }; version = "v0.14.1"; }; + bigarray-compat = + { + opamInputs = + { + dune = selection.dune; + ocaml = selection.ocaml; + }; + opamSrc = repoPath (repos.opam-repository.src) + { + hash = "sha256:0mcg8csmd60ph17vam1s8xjsl9kp6k77i3mnkbxy0jvkn49m4a0k"; + package = "packages/bigarray-compat/bigarray-compat.1.0.0"; + }; + pname = "bigarray-compat"; + src = pkgs.fetchurl + { + sha256 = "1bpmmnxb1yx72aqlbdaqfl18rgz1cq9cf6cqvnfl88mz5dfr4x0d"; + url = "https://github.com/mirage/bigarray-compat/archive/v1.0.0.tar.gz"; + }; + version = "1.0.0"; + }; bin_prot = { opamInputs = @@ -481,6 +501,30 @@ in }; version = "1.5.1"; }; + ctypes = + { + opamInputs = + { + bigarray-compat = selection.bigarray-compat; + ctypes-foreign = selection.ctypes-foreign or null; + integers = selection.integers; + mirage-xen = selection.mirage-xen or null; + ocaml = selection.ocaml; + ocamlfind = selection.ocamlfind; + }; + opamSrc = repoPath (repos.opam-repository.src) + { + hash = "sha256:0cwxwp4bj0yyyg8pwd8v8v6x0gvjniwih922q6cglpc04n9w98py"; + package = "packages/ctypes/ctypes.0.19.1"; + }; + pname = "ctypes"; + src = pkgs.fetchurl + { + sha256 = "05q6xrl09g515njfx3cdb497460jy6x60fjbz8iz9ajg7x1y591f"; + url = "https://github.com/ocamllabs/ocaml-ctypes/archive/0.19.1.tar.gz"; + }; + version = "0.19.1"; + }; dot-merlin-reader = { opamInputs = @@ -637,6 +681,26 @@ in }; version = "0.7.3"; }; + integers = + { + opamInputs = + { + dune = selection.dune; + ocaml = selection.ocaml; + }; + opamSrc = repoPath (repos.opam-repository.src) + { + hash = "sha256:1n15jqsbgd9xp7xn68sb52m4jdw66l6rlnsza67nw0r164i2nj00"; + package = "packages/integers/integers.0.5.1"; + }; + pname = "integers"; + src = pkgs.fetchurl + { + sha256 = "1f1nkgpqjnavyw5vqlgrgsqaqdgzp0xngs4hx97dn7glraccw27n"; + url = "https://github.com/ocamllabs/ocaml-integers/archive/0.5.1.tar.gz"; + }; + version = "0.5.1"; + }; jane-street-headers = { opamInputs = diff --git a/shell.nix b/shell.nix index 213f336e6fa..9c705389108 100644 --- a/shell.nix +++ b/shell.nix @@ -45,5 +45,6 @@ in pkgs.mkShell { ppxlib result utop + ctypes ]) ++ [ local.coq-core ]; } From 9781f16d49c3fa5622dfa5cadeba8ae4cc88058e Mon Sep 17 00:00:00 2001 From: Rudi Grinberg Date: Sat, 16 Oct 2021 22:15:34 -0600 Subject: [PATCH 68/69] chore: add ctypes to test deps in makefile Signed-off-by: Rudi Grinberg --- Makefile | 1 + 1 file changed, 1 insertion(+) diff --git a/Makefile b/Makefile index a1cc2184d92..dfe6c7f83fa 100644 --- a/Makefile +++ b/Makefile @@ -29,6 +29,7 @@ ocamlformat.0.19.0 \ ppx_inline_test \ ppxlib \ result \ +ctypes \ "utop>=2.6.0" # Dependencies recommended for developing dune locally, From cda682e57f6d6dff614d812b89e321146fb00489 Mon Sep 17 00:00:00 2001 From: Rudi Grinberg Date: Sat, 16 Oct 2021 22:18:39 -0600 Subject: [PATCH 69/69] chore: enable ctypes tests on linux only Signed-off-by: Rudi Grinberg --- test/blackbox-tests/test-cases/dune | 2 ++ 1 file changed, 2 insertions(+) diff --git a/test/blackbox-tests/test-cases/dune b/test/blackbox-tests/test-cases/dune index 32c40997185..44ff5b9ef54 100644 --- a/test/blackbox-tests/test-cases/dune +++ b/test/blackbox-tests/test-cases/dune @@ -78,6 +78,8 @@ (subdir ctypes (cram + (enabled_if + (= ${ocaml-config:system} linux)) (deps (package ctypes))))