Skip to content
Closed
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
The table of contents is too big for display.
Diff view
Diff view
  •  
  •  
  •  
7 changes: 1 addition & 6 deletions Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -38,12 +38,7 @@ serve :

.PHONY : test
test : build
$(DUNE) runtest $(DUNE_ARGS) src/parser/test
$(DUNE) build $(DUNE_ARGS) @test/model/runtest --no-buffer -j 1
$(DUNE) build $(DUNE_ARGS) @test/html/runtest --no-buffer -j 1
$(DUNE) build $(DUNE_ARGS) @test/man/runtest --no-buffer -j 1
$(DUNE) build $(DUNE_ARGS) @test/latex/runtest --no-buffer -j 1
$(DUNE) build $(DUNE_ARGS) @test/xref2/runtest --no-buffer -j 1
$(DUNE) runtest $(DUNE_ARGS)

ODOC_RELATIVE_PATH := ../../_build/install/default/bin/

Expand Down
1 change: 0 additions & 1 deletion test/cases/ocamlary.mli

This file was deleted.

29 changes: 0 additions & 29 deletions test/cases/recent_impl.ml

This file was deleted.

File renamed without changes.
Original file line number Diff line number Diff line change
Expand Up @@ -2,44 +2,44 @@

(** {1:L2 Attached to nothing} *)

(** {1:L3 Attached to module} *)
module A : sig end
(** {1:L3 Attached to module} *)

(** {1:L4 Attached to type} *)
type t
(** {1:L4 Attached to type} *)

(** {1:L5 Attached to value} *)
val f : t
(** {1:L5 Attached to value} *)

(** {1:L5bis Attached to external} *)
external e : unit -> t = "t"
(** {1:L5bis Attached to external} *)

(** {1:L6 Attached to module type} *)
module type S = sig end
(** {1:L6 Attached to module type} *)

(** {1:L6 Attached to class} *)
class c : object end
(** {1:L6 Attached to class} *)

(** {1:L7 Attached to class type} *)
class type cs = object end
(** {1:L7 Attached to class type} *)

(** {1:L8 Attached to exception} *)
exception E
(** {1:L8 Attached to exception} *)

type x = ..

(** {1:L9 Attached to extension} *)
type x += X

(** {1:L10 Attached to module subst} *)
module S := A
(** {1:L10 Attached to module subst} *)

(** {1:L11 Attached to type subst} *)
type s := t
(** {1:L11 Attached to type subst} *)

type u = A' (** {1:L12 Attached to constructor} *)
type u = A' (** {1:L12 Attached to constructor} *)

type v = { f : t (** {1:L13 Attached to field} *) }
type v = { f : t (** {1:L13 Attached to field} *) }

(** Testing that labels can be referenced
- {!L1}
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -4,37 +4,34 @@

module type S = sig end

module type S1 = S -> S
module type S1 = functor (_ : S) -> S

type variant =
| A
| B of int
| C (** foo *)
| D (** {e bar} *)
| E of {a : int}
| C (** foo *)
| D (** {e bar} *)
| E of { a : int }

type _ gadt =
| A : int gadt
| B : int -> string gadt (** foo *)
| C : {a : int} -> unit gadt
| B : int -> string gadt (** foo *)
| C : { a : int } -> unit gadt

type polymorphic_variant = [
| `A
| `B of int
| `C (** foo *)
| `D (** bar *)
]
type polymorphic_variant = [ `A | `B of int | `C (** foo *) | `D (** bar *) ]

type empty_variant = |

type nonrec nonrec_ = int


(* Conjunctive types: dune compilation scheme exposes a bug in old
versions of the compiler *)
type empty_conj= X: [< `X of & 'a & int * float ] -> empty_conj
type conj = X: [< `X of int & [< `B of int & float ] ] -> conj
val empty_conj: [< `X of & 'a & int * float ]
type empty_conj = X : [< `X of & 'a & int * float ] -> empty_conj

type conj = X : [< `X of int & [< `B of int & float ] ] -> conj

val empty_conj : [< `X of & 'a & int * float ]

val conj : [< `X of int & [< `B of int & float ] ]

module Z : sig
Expand All @@ -47,12 +44,17 @@ end

module X : sig
module L := Z.Y

type t = int L.X.t

type u := int

type v = u L.X.t
end

module type PolyS =
sig type a = [ `A ] type t = [ a | `B ] end with type a := [ `A ]

module type PolyS = sig
type a = [ `A ]

type t = [ a | `B ]
end
with type a := [ `A ]
38 changes: 38 additions & 0 deletions test/generators/cases_post408/cases/recent_impl.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,38 @@
module Foo = struct
module A = struct
type t = A
end

module B = struct
type t = B
end
end

open (Foo : module type of Foo with module A := Foo.A)

module B = B

open Set.Make (struct
type t = Foo.A.t

let compare = compare
end)

type u = t

module type S = sig
module F (_ : sig end) : sig
type t
end

module X : sig end

open F(X)

val f : t
end

open Foo

(* Check that regular open still works as expected *)
module B' = B
20 changes: 20 additions & 0 deletions test/generators/cases_post408/dune
Original file line number Diff line number Diff line change
@@ -0,0 +1,20 @@
(include link.dune.inc)

(rule
(deps
(glob_files cases/*))
(enabled_if
(>= %{ocaml_version} 4.08))
(action
(with-stdout-to
link.dune.inc.gen
(pipe-stdout
(run gen_link/gen_link.exe)
(run dune format-dune-file)))))

(rule
(enabled_if
(>= %{ocaml_version} 4.08))
(alias runtest)
(action
(diff link.dune.inc link.dune.inc.gen)))
5 changes: 5 additions & 0 deletions test/generators/cases_post408/gen_link/dune
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
(executable
(name gen_link)
(libraries gen_link_lib)
(enabled_if
(>= %{ocaml_version} 4.04)))
9 changes: 9 additions & 0 deletions test/generators/cases_post408/gen_link/gen_link.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
let () =
let paths =
Gen_link_lib.read_file_from_dir (Fpath.filename Gen_link_lib.cases)
in
let paths =
List.filter (fun p -> not (Gen_link_lib.is_dot_ocamlformat p)) paths
in
let stanzas = Gen_link_lib.gen_rule paths "4.08" in
List.iter (Sexplib0.Sexp.pp Format.std_formatter) stanzas
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
<!DOCTYPE html>
<html xmlns="http://www.w3.org/1999/xhtml">
<head><title>let_open' (test.Bugs_post_406.let_open')</title>
<link rel="stylesheet" href="../../../odoc.css"/><meta charset="utf-8"/>
<meta name="generator" content="odoc %%VERSION%%"/>
<meta name="viewport" content="width=device-width,initial-scale=1.0"/>
<script src="../../../highlight.pack.js"></script>
<script>hljs.initHighlightingOnLoad();</script>
</head>
<body class="odoc">
<nav class="odoc-nav"><a href="../index.html">Up</a> –
<a href="../../index.html">test</a> &#x00BB;
<a href="../index.html">Bugs_post_406</a> &#x00BB; let_open'
</nav>
<header class="odoc-preamble">
<h1>Class <code><span>Bugs_post_406.let_open'</span></code></h1>
</header><div class="odoc-content"></div>
</body>
</html>
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
<!DOCTYPE html>
<html xmlns="http://www.w3.org/1999/xhtml">
<head><title>let_open (test.Bugs_post_406.let_open)</title>
<link rel="stylesheet" href="../../../odoc.css"/><meta charset="utf-8"/>
<meta name="generator" content="odoc %%VERSION%%"/>
<meta name="viewport" content="width=device-width,initial-scale=1.0"/>
<script src="../../../highlight.pack.js"></script>
<script>hljs.initHighlightingOnLoad();</script>
</head>
<body class="odoc">
<nav class="odoc-nav"><a href="../index.html">Up</a> –
<a href="../../index.html">test</a> &#x00BB;
<a href="../index.html">Bugs_post_406</a> &#x00BB; let_open
</nav>
<header class="odoc-preamble">
<h1>Class type <code><span>Bugs_post_406.let_open</span></code></h1>
</header><div class="odoc-content"></div>
</body>
</html>
48 changes: 48 additions & 0 deletions test/generators/cases_post408/html/Bugs_post_406.index.html
Original file line number Diff line number Diff line change
@@ -0,0 +1,48 @@
<!DOCTYPE html>
<html xmlns="http://www.w3.org/1999/xhtml">
<head><title>Bugs_post_406 (test.Bugs_post_406)</title>
<link rel="stylesheet" href="../../odoc.css"/><meta charset="utf-8"/>
<meta name="generator" content="odoc %%VERSION%%"/>
<meta name="viewport" content="width=device-width,initial-scale=1.0"/>
<script src="../../highlight.pack.js"></script>
<script>hljs.initHighlightingOnLoad();</script>
</head>
<body class="odoc">
<nav class="odoc-nav"><a href="../index.html">Up</a> –
<a href="../index.html">test</a> &#x00BB; Bugs_post_406
</nav>
<header class="odoc-preamble">
<h1>Module <code><span>Bugs_post_406</span></code></h1>
<p>Let-open in class types, https://github.com/ocaml/odoc/issues/543
This was added to the language in 4.06
</p>
</header>
<div class="odoc-content">
<div class="odoc-spec">
<div class="spec class-type" id="class-type-let_open" class="anchored">
<a href="#class-type-let_open" class="anchor"></a>
<code>
<span><span class="keyword">class</span>
<span class="keyword">type</span>
</span>
<span><a href="class-type-let_open/index.html">let_open</a></span>
<span> = <span class="keyword">object</span> ...
<span class="keyword">end</span>
</span>
</code>
</div>
</div>
<div class="odoc-spec">
<div class="spec class" id="class-let_open'" class="anchored">
<a href="#class-let_open'" class="anchor"></a>
<code><span><span class="keyword">class</span> </span>
<span><a href="class-let_open'/index.html">let_open'</a></span>
<span> : <span class="keyword">object</span> ...
<span class="keyword">end</span>
</span>
</code>
</div>
</div>
</div>
</body>
</html>
25 changes: 25 additions & 0 deletions test/generators/cases_post408/html/Labels.A.index.html
Original file line number Diff line number Diff line change
@@ -0,0 +1,25 @@
<!DOCTYPE html>
<html xmlns="http://www.w3.org/1999/xhtml">
<head><title>A (test.Labels.A)</title>
<link rel="stylesheet" href="../../../odoc.css"/><meta charset="utf-8"/>
<meta name="generator" content="odoc %%VERSION%%"/>
<meta name="viewport" content="width=device-width,initial-scale=1.0"/>
<script src="../../../highlight.pack.js"></script>
<script>hljs.initHighlightingOnLoad();</script>
</head>
<body class="odoc">
<nav class="odoc-nav"><a href="../index.html">Up</a> –
<a href="../../index.html">test</a> &#x00BB;
<a href="../index.html">Labels</a> &#x00BB; A
</nav>
<header class="odoc-preamble">
<h1>Module <code><span>Labels.A</span></code></h1>
</header>
<nav class="odoc-toc">
<ul><li><a href="#L3">Attached to module</a></li></ul>
</nav>
<div class="odoc-content">
<h2 id="L3"><a href="#L3" class="anchor"></a>Attached to module</h2>
</div>
</body>
</html>
24 changes: 24 additions & 0 deletions test/generators/cases_post408/html/Labels.class-c.index.html
Original file line number Diff line number Diff line change
@@ -0,0 +1,24 @@
<!DOCTYPE html>
<html xmlns="http://www.w3.org/1999/xhtml">
<head><title>c (test.Labels.c)</title>
<link rel="stylesheet" href="../../../odoc.css"/><meta charset="utf-8"/>
<meta name="generator" content="odoc %%VERSION%%"/>
<meta name="viewport" content="width=device-width,initial-scale=1.0"/>
<script src="../../../highlight.pack.js"></script>
<script>hljs.initHighlightingOnLoad();</script>
</head>
<body class="odoc">
<nav class="odoc-nav"><a href="../index.html">Up</a> –
<a href="../../index.html">test</a> &#x00BB;
<a href="../index.html">Labels</a> &#x00BB; c
</nav>
<header class="odoc-preamble">
<h1>Class <code><span>Labels.c</span></code></h1>
</header>
<nav class="odoc-toc"><ul><li><a href="#L6">Attached to class</a></li></ul>
</nav>
<div class="odoc-content">
<h2 id="L6"><a href="#L6" class="anchor"></a>Attached to class</h2>
</div>
</body>
</html>
Loading