Skip to content

Commit

Permalink
refactor: limit [Stdune] usage in code gen
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <me@rgrinberg.com>

<!-- ps-id: 0d5cd638-b1bf-4f84-92a2-259fcb7307e0 -->
  • Loading branch information
rgrinberg committed May 12, 2024
1 parent 8367e35 commit 61397c8
Show file tree
Hide file tree
Showing 4 changed files with 15 additions and 7 deletions.
14 changes: 13 additions & 1 deletion lsp/bin/import.ml
Original file line number Diff line number Diff line change
@@ -1 +1,13 @@
include Stdune
include struct
open Stdune
module List = List
module Id = Id
module String = String
module Code_error = Code_error
module Comparable = Comparable
module Top_closure = Top_closure
module Poly = Poly
module Option = Option

let sprintf = sprintf
end
2 changes: 0 additions & 2 deletions lsp/bin/ocaml/ml.mli
Original file line number Diff line number Diff line change
@@ -1,7 +1,5 @@
(** Representation of OCaml code used for generation *)

open Import

val is_kw : string -> bool

module Kind : sig
Expand Down
4 changes: 2 additions & 2 deletions lsp/bin/ocaml/ocaml.ml
Original file line number Diff line number Diff line change
Expand Up @@ -342,7 +342,7 @@ end = struct
let remove_null cs =
let is_null x =
match x with
| Resolved.Ident Prim.Null -> Left x
| Resolved.Ident Prim.Null -> Either.Left x
| _ -> Right x
in
let nulls, non_nulls = List.partition_map ~f:is_null cs in
Expand Down Expand Up @@ -436,7 +436,7 @@ end = struct
let key = make_typ db { Named.name = field.name; data = pat } in
let data = make_typ db { Named.name = field.name; data = typ } in
let typ = Type.assoc_list ~key ~data in
Left (Ml.Type.field typ ~name:field.name)
Either.Left (Ml.Type.field typ ~name:field.name)
| Single { typ = Literal s; optional = false } ->
let literal_value =
match s with
Expand Down
2 changes: 0 additions & 2 deletions lsp/bin/ocaml/w.mli
Original file line number Diff line number Diff line change
@@ -1,7 +1,5 @@
(** Helpers to generate OCaml code. Consider merging with ML *)

open Import

type t = unit Pp.t

type w = t
Expand Down

0 comments on commit 61397c8

Please sign in to comment.