Skip to content

Commit

Permalink
pseudocode direction
Browse files Browse the repository at this point in the history
  • Loading branch information
mbacarella committed Nov 6, 2020
1 parent 40463b5 commit ec9e8c1
Show file tree
Hide file tree
Showing 6 changed files with 175 additions and 52 deletions.
33 changes: 0 additions & 33 deletions src/dune_rules/ctypes.ml

This file was deleted.

13 changes: 0 additions & 13 deletions src/dune_rules/ctypes.mli

This file was deleted.

117 changes: 117 additions & 0 deletions src/dune_rules/ctypes_rules.ml
Original file line number Diff line number Diff line change
@@ -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
44 changes: 39 additions & 5 deletions src/dune_rules/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -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 =
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -288,7 +285,6 @@ module Buildable = struct
; flags
; js_of_ocaml
; allow_overlapping_dependencies
; ctypes
}

let has_foreign t =
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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 =
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -705,6 +738,7 @@ module Library = struct
; special_builtin_support
; enabled_if
; instrumentation_backend
; ctypes
})

let package t =
Expand Down
14 changes: 13 additions & 1 deletion src/dune_rules/dune_file.mli
Original file line number Diff line number Diff line change
Expand Up @@ -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. *)
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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
Expand Down
6 changes: 6 additions & 0 deletions src/dune_rules/dune_load.ml
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down

0 comments on commit ec9e8c1

Please sign in to comment.