Skip to content

Commit

Permalink
Merge pull request #5508 from Leonidas-from-XIV/no-cppo
Browse files Browse the repository at this point in the history
Remove preprocessing of backwards-compatibility code
  • Loading branch information
kit-ty-kate authored Apr 17, 2023
2 parents 0a174e1 + e9260ef commit f0a8f46
Show file tree
Hide file tree
Showing 7 changed files with 38 additions and 176 deletions.
1 change: 1 addition & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -285,6 +285,7 @@ users)
* `opam-state` depends on `opam-solver` [#5208 @rjbou]
* Specify the `opam` package for all rules that need `opamMain.exe.exe` [#5496 @Leonidas-from-XIV]
* Replace CPPO dependency with simple conditional compilation helper [#5498 @Leonidas-from-XIV]
* Remove conditional compilation [#5508 @Leonidas-from-XIV]

## Infrastructure
* Fix caching of Cygwin compiler on AppVeyor [#4988 @dra27]
Expand Down
9 changes: 0 additions & 9 deletions src/core/dune
Original file line number Diff line number Diff line change
Expand Up @@ -16,15 +16,6 @@
(:include ../ocaml-context-flags.sexp)))
(wrapped false))

(rule
(with-stdin-from opamCompat.pp.ml
(with-stdout-to opamCompat.ml
(run ./gen/gen.exe))))
(rule
(with-stdin-from opamCompat.pp.mli
(with-stdout-to opamCompat.mli
(run ./gen/gen.exe))))

(rule
(copy opamStubsTypes.ml opamStubsTypes.mli))

Expand Down
3 changes: 0 additions & 3 deletions src/core/gen/dune

This file was deleted.

98 changes: 0 additions & 98 deletions src/core/gen/gen.ml

This file was deleted.

55 changes: 22 additions & 33 deletions src/core/opamCompat.pp.ml → src/core/opamCompat.ml
Original file line number Diff line number Diff line change
Expand Up @@ -8,42 +8,33 @@
(* *)
(**************************************************************************)

module String =
#if OCAML_VERSION >= (4, 13, 0)
String
#else
struct
include String
module String = struct
[@@@warning "-32"]

(** NOTE: OCaml >= 4.13 *)
let exists p s =
let n = length s in
let n = String.length s in
let rec loop i =
if i = n then false
else if p (unsafe_get s i) then true
else if p (String.unsafe_get s i) then true
else loop (succ i) in
loop 0

include Stdlib.String
end
#endif

module Either =
#if OCAML_VERSION >= (4, 12, 0)
Either
#else
struct
module Either = struct
(** NOTE: OCaml >= 4.12 *)
type ('a, 'b) t =
| Left of 'a
| Right of 'b
| Left of 'a
| Right of 'b
end
#endif

module Unix =
struct
include Unix
module Unix = struct
[@@@warning "-32"]

#if OCAML_VERSION >= (4, 13, 0)
let normalise = realpath
#else
let normalise s =
(** NOTE: OCaml >= 4.13 *)
let realpath s =
let getchdir s =
let p =
try Sys.getcwd ()
Expand All @@ -53,18 +44,16 @@ struct
p
in
try getchdir (getchdir s) with Unix.Unix_error _ -> s
#endif

include Unix
end

module Lazy =
#if OCAML_VERSION >= (4, 13, 0)
Lazy
#else
struct
include Lazy
module Lazy = struct
[@@@warning "-32"]

(** NOTE: OCaml >= 4.13 *)
let map f x =
lazy (f (force x))
lazy (f (Lazy.force x))

include Stdlib.Lazy
end
#endif
42 changes: 12 additions & 30 deletions src/core/opamCompat.pp.mli → src/core/opamCompat.mli
Original file line number Diff line number Diff line change
Expand Up @@ -8,43 +8,25 @@
(* *)
(**************************************************************************)

module String
#if OCAML_VERSION >= (4, 13, 0)
= String
#else
: sig
include module type of struct include String end

module String : sig
(* NOTE: OCaml >= 4.13 *)
val exists: (char -> bool) -> string -> bool
end
#endif

module Either
#if OCAML_VERSION >= (4, 12, 0)
= Either
#else
: sig
module Either : sig
(* NOTE: OCaml >= 4.12 *)
type ('a, 'b) t =
| Left of 'a
| Right of 'b
| Left of 'a
| Right of 'b
end
#endif

module Unix : sig
include module type of struct include Unix end
module Lazy : sig
(* NOTE: OCaml >= 4.13 *)
val map : ('a -> 'b) -> 'a Lazy.t -> 'b Lazy.t
end

module Unix : sig
(* `realpath` for OCaml >= 4.13.0,
implementation with double chdir otherwise *)
val normalise: string -> string
end

module Lazy
#if OCAML_VERSION >= (4, 13, 0)
= Lazy
#else
: sig
include module type of struct include Lazy end

val map : ('a -> 'b) -> 'a t -> 'b t
val realpath: string -> string
end
#endif
6 changes: 3 additions & 3 deletions src/core/opamSystem.ml
Original file line number Diff line number Diff line change
Expand Up @@ -332,7 +332,7 @@ let real_path p =
match (try Some (Sys.is_directory p) with Sys_error _ -> None) with
| None ->
let rec resolve dir =
if Sys.file_exists dir then OpamCompat.Unix.normalise dir else
if Sys.file_exists dir then OpamCompat.Unix.realpath dir else
let parent = Filename.dirname dir in
if dir = parent then dir
else Filename.concat (resolve parent) (Filename.basename dir)
Expand All @@ -342,9 +342,9 @@ let real_path p =
else p
in
resolve p
| Some true -> OpamCompat.Unix.normalise p
| Some true -> OpamCompat.Unix.realpath p
| Some false ->
let dir = OpamCompat.Unix.normalise (Filename.dirname p) in
let dir = OpamCompat.Unix.realpath (Filename.dirname p) in
match Filename.basename p with
| "." -> dir
| base -> dir / base
Expand Down

0 comments on commit f0a8f46

Please sign in to comment.