Skip to content

Commit

Permalink
Merge pull request ocaml#718 from Octachron/ocamldoc_extension_cstr_o…
Browse files Browse the repository at this point in the history
…rder

Ocamldoc: fix extension constructor order
  • Loading branch information
gasche committed Jul 26, 2016
2 parents 8436ecc + 45df50c commit 38c3db4
Show file tree
Hide file tree
Showing 5 changed files with 135 additions and 2 deletions.
3 changes: 3 additions & 0 deletions Changes
Expand Up @@ -139,6 +139,9 @@ OCaml 4.04.0:
- GPR#613: make ocamldoc use -open arguments
(Florian Angeletti)

- GPR#718: ocamldoc, fix order of extensible variant constructors
(Florian Angeletti)

- Add the -no-version option to the toplevel
(Sébastien Hinderer)

Expand Down
1 change: 1 addition & 0 deletions ocamldoc/odoc_sig.ml
Expand Up @@ -636,6 +636,7 @@ module Analyser =
(env, [], None)
tyext.Parsetree.ptyext_constructors
in
let types_ext_list = List.rev types_ext_list in
let ty_path, ty_params, priv =
match last_ext with
None -> assert false
Expand Down
5 changes: 3 additions & 2 deletions testsuite/tests/tool-ocamldoc-2/Makefile
Expand Up @@ -33,10 +33,11 @@ default:
fi

.PHONY: run
run: *.mli
@for file in *.mli; do \
run: *.ml *.mli
@for file in *.mli *.ml; do \
printf " ... testing '$$file'"; \
F="`basename $$file .mli`"; \
F="`basename $$F .ml`"; \
$(OCAMLDOC) $(DOCFLAGS) -hide-warnings -latex $ \
-o $$F.result $$file; \
$(DIFF) $$F.reference $$F.result >/dev/null \
Expand Down
20 changes: 20 additions & 0 deletions testsuite/tests/tool-ocamldoc-2/extensible_variant.ml
@@ -0,0 +1,20 @@
(** Testing display of extensible variant types.
@test_types_display
*)

type e = ..

module M = struct
type e +=
| A (** A doc *)
| B (** B doc *)
| C (** C doc *)
end

module type MT = sig
type e +=
| A (** A doc *)
| B (** B doc *)
| C (** C doc *)
end
108 changes: 108 additions & 0 deletions testsuite/tests/tool-ocamldoc-2/extensible_variant.reference
@@ -0,0 +1,108 @@
\documentclass[11pt]{article}
\usepackage[latin1]{inputenc}
\usepackage[T1]{fontenc}
\usepackage{textcomp}
\usepackage{fullpage}
\usepackage{url}
\usepackage{ocamldoc}
\begin{document}
\tableofcontents
\section{Module {\tt{Extensible\_variant}} : Testing display of extensible variant types.}
\label{Extensible-underscorevariant}\index{Extensible-underscorevariant@\verb`Extensible_variant`}




\ocamldocvspace{0.5cm}



\label{TYPExtensible-underscorevariant.e}\begin{ocamldoccode}
type e = ..
\end{ocamldoccode}
\index{e@\verb`e`}




\begin{ocamldoccode}
{\tt{module }}{\tt{M}}{\tt{ : }}\end{ocamldoccode}
\label{Extensible-underscorevariant.M}\index{M@\verb`M`}

\begin{ocamldocsigend}


\begin{ocamldoccode}
type e +=
\end{ocamldoccode}
\label{extension:Extensible-underscorevariant.M.A}\begin{ocamldoccode}
| A
\end{ocamldoccode}
\begin{ocamldoccomment}
A doc


\end{ocamldoccomment}
\label{extension:Extensible-underscorevariant.M.B}\begin{ocamldoccode}
| B
\end{ocamldoccode}
\begin{ocamldoccomment}
B doc


\end{ocamldoccomment}
\label{extension:Extensible-underscorevariant.M.C}\begin{ocamldoccode}
| C
\end{ocamldoccode}
\begin{ocamldoccomment}
C doc


\end{ocamldoccomment}
\end{ocamldocsigend}






\begin{ocamldoccode}
{\tt{module type }}{\tt{MT}}{\tt{ = }}\end{ocamldoccode}
\label{Extensible-underscorevariant.MT}\index{MT@\verb`MT`}

\begin{ocamldocsigend}


\begin{ocamldoccode}
type e +=
\end{ocamldoccode}
\label{extension:Extensible-underscorevariant.MT.A}\begin{ocamldoccode}
| A
\end{ocamldoccode}
\begin{ocamldoccomment}
A doc


\end{ocamldoccomment}
\label{extension:Extensible-underscorevariant.MT.B}\begin{ocamldoccode}
| B
\end{ocamldoccode}
\begin{ocamldoccomment}
B doc


\end{ocamldoccomment}
\label{extension:Extensible-underscorevariant.MT.C}\begin{ocamldoccode}
| C
\end{ocamldoccode}
\begin{ocamldoccomment}
C doc


\end{ocamldoccomment}
\end{ocamldocsigend}




\end{document}

0 comments on commit 38c3db4

Please sign in to comment.