Skip to content

Commit

Permalink
Merge pull request #939 from Octachron/manual_camlexample_for_exten
Browse files Browse the repository at this point in the history
Manual: caml_example for language extensions
  • Loading branch information
gasche committed Nov 29, 2016
2 parents 9df8c63 + a57a5d4 commit 4c04dee
Show file tree
Hide file tree
Showing 8 changed files with 92 additions and 86 deletions.
5 changes: 5 additions & 0 deletions Changes
Original file line number Diff line number Diff line change
Expand Up @@ -65,6 +65,11 @@ Next version (4.05.0):

### Manual and documentation:

- GPR#939: activate the caml_example environment in the language
extensions section of the manual. Convert some existing code
examples to this format.
(Florian Angeletti)

- add a HACKING.adoc file to contain various tips and tricks for
people hacking on the repository. See also CONTRIBUTING.md for
advice on sending contributions upstream.
Expand Down
4 changes: 2 additions & 2 deletions manual/README.md
Original file line number Diff line number Diff line change
Expand Up @@ -116,8 +116,8 @@ Latex extensions

###Caml environments
The tool `tool/caml-tex2` is used to generate the latex code for the examples
in the introduction part of the manual. It implements two pseudo-environments:
`caml_example` and `caml_eval`.
in the introduction and language extension parts of the manual. It implements
two pseudo-environments: `caml_example` and `caml_eval`.

The pseudo-environment `caml_example` evaluates its contents using an ocaml
interpreter and then translates both the input code and the interpreter output
Expand Down
1 change: 0 additions & 1 deletion manual/manual/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -76,7 +76,6 @@ html: files
-I ../tutorials -I ../../styles -I ../texstuff manual.hva \
-e macros.tex ../manual.tex ; \
${HACHA} -tocter manual.html ; \
cat ../manual.css >> manual.css

info: files
cd infoman; rm -f ocaml.info*; \
Expand Down
7 changes: 6 additions & 1 deletion manual/manual/macros.hva
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,12 @@
\newstyle{a:link}{color:\link@color;text-decoration:underline;}
\newstyle{a:visited}{color:\visited@color;text-decoration:underline;}
\newstyle{a:hover}{color:black;text-decoration:none;background-color:\hover@color}
\externalcsstrue % needed due to hevea partial css handling

\newstyle{div.caml-output}{color:maroon;}
\newstyle{div.caml-input::before}{content:"\#"; color:black;}
\newstyle{div.caml-input}{color:\#006000;}
\newstyle{div.caml-example pre}{margin:2ex 0px;}

%%%
\newcommand{\input@color}{\htmlcolor{006000}}
\newcommand{\output@color}{\maroon}
Expand Down
6 changes: 0 additions & 6 deletions manual/manual/manual.css

This file was deleted.

10 changes: 10 additions & 0 deletions manual/manual/refman/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@ TOPDIR=../../..

include $(TOPDIR)/Makefile.tools

CAMLLATEX= $(OCAMLRUN) ../../tools/caml-tex2
TRANSF=../../tools/transf
TEXQUOTE=../../tools/texquote2

Expand All @@ -20,6 +21,15 @@ clean:
.SUFFIXES:
.SUFFIXES: .etex .tex

exten.tex:exten.etex
@$(CAMLLATEX) -caml "TERM=norepeat $(OCAML)" -n 80 -v false \
-o $*.caml_tex_error.tex $*.etex \
&& mv $*.caml_tex_error.tex $*.gen.tex \
&& $(OCAMLRUN) $(TRANSF) < $*.gen.tex > $*.transf_error.tex \
&& mv $*.transf_error.tex $*.gen.tex\
&& $(TEXQUOTE) < $*.gen.tex > $*.texquote_error.tex\
&& mv $*.texquote_error.tex $*.tex\
|| printf "Failure when generating %s\n" $*.tex
.etex.tex:
@$(OCAMLRUN) $(TRANSF) < $*.etex > $*.transf_error.tex \
&& mv $*.transf_error.tex $*.gen.tex\
Expand Down
126 changes: 53 additions & 73 deletions manual/manual/refman/exten.etex
Original file line number Diff line number Diff line change
@@ -1,10 +1,6 @@
\chapter{Language extensions} \label{c:extensions}
\pdfchapter{Language extensions}
%HEVEA\cutname{extn.html}
%%%%%%%%%%%%%%%%%%%%%%%%%%
% Specific macros:
\newcommand{\tq}{\textquotesingle}
%%%%%%%%%%%%%%%%%%%%%%%%%%%

This chapter describes language extensions and convenience features
that are implemented in OCaml, but not described in the
Expand Down Expand Up @@ -531,12 +527,10 @@ Note that "'b" is not explicitly polymorphic here, and it will
actually be unified with "int".

The other application is to ensure that some definition is sufficiently
polymorphic.
\caml
\?let id : \tq\-a. \tq\-a -> \tq\-a = \<fun x -> x+1\> ;;
\:Error: This definition has type int -> int which is less general than
\: \tq\-a. \tq\-a -> \tq\-a
\endcaml
polymorphic:
\begin{caml_example}[error]
let id: 'a. 'a -> 'a = fun x -> x + 1;;
\end{caml_example}

\section{Locally abstract types}
\ikwd{type\@\texttt{type}}
Expand Down Expand Up @@ -933,7 +927,7 @@ parameters.

A natural application of destructive substitution is merging two
signatures sharing a type name.
\begin{verbatim}
\begin{caml_example*}
module type Printable = sig
type t
val print : Format.formatter -> t -> unit
Expand All @@ -945,31 +939,27 @@ signatures sharing a type name.
module type PrintableComparable = sig
include Printable
include Comparable with type t := t
end
\end{verbatim}
end;;
\end{caml_example*}

One can also use this to completely remove a field:
\caml
\?module type S = Comparable with type t := int;;
\:module type S = sig val compare : int -> int -> int end
\endcaml
\begin{caml_example}
module type S = Comparable with type t := int;;
\end{caml_example}
or to rename one:
\caml
\?module type S = sig
\? type u
\? include Comparable with type t := u
\?end;;
\:module type S = sig type u val compare : u -> u -> int end
\endcaml
\begin{caml_example}
module type S = sig
type u
include Comparable with type t := u
end;;
\end{caml_example}

Note that you can also remove manifest types, by substituting with the
same type.
\caml
\?module type ComparableInt = Comparable with type t = int ;;
\:module type ComparableInt = sig type t = int val compare : t -> t -> int end
\?module type CompareInt = ComparableInt with type t := int ;;
\:module type CompareInt = sig val compare : int -> int -> int end
\endcaml
\begin{caml_example}
module type ComparableInt = Comparable with type t = int ;;
module type CompareInt = ComparableInt with type t := int ;;
\end{caml_example}

\section{Type-level module aliases}
\ikwd{module\@\texttt{module}}
Expand Down Expand Up @@ -1000,9 +990,12 @@ There are several restrictions on @module-path@:

Such specifications are also inferred. Namely, when @P@ is a path
satisfying the above constraints,
\caml
\?module N = P
\endcaml
\begin{caml_eval}
module P = struct end
\end{caml_eval}
\begin{caml_example*}
module N = P;;
\end{caml_example*}
has type
\caml
\:module N = P
Expand Down Expand Up @@ -1386,41 +1379,29 @@ compiler generates these names according to the following nomenclature:
\item First, types whose name starts with a "$" are existentials.
\item "$Constr_'a" denotes an existential type introduced for the type
variable "'a" of the GADT constructor "Constr":
\caml
\? type any = Any : \tq\-name -> any
\? let escape (Any x) = \<x\>;;
\: Error: This expression has type $Any_\tq\-name
\: but an expression was expected of type \tq\-a
\: The type constructor $Any_\tq\-name would escape its scope
\endcaml
\item "$Constr" denotes an existential type introduced for an anonymous
\begin{caml_example}[error]
type any = Any : 'name -> any
let escape (Any x) = x;;
\end{caml_example}
\item "$Constr" denotes an existential type introduced for an anonymous %$
type variable in the GADT constructor "Constr":
\caml
\? type any = Any : _ -> any
\? let escape (Any x) = \<x\>;;
\: Error: This expression has type $Any but an expression was expected of type
\: \tq\-a
\: The type constructor $Any would escape its scope
\endcaml
\item "$'a" if the existential variable was unified with the type
\begin{caml_example}[error]
type any = Any : _ -> any
let escape (Any x) = x;;
\end{caml_example}
\item "$'a" if the existential variable was unified with the type %$
variable "'a" during typing:
\caml
\? type (\tq\-arg,\tq\-result,\tq\-aux) fn =
\? | Fun: (\tq\-a ->\tq\-b) -> (\tq\-a,\tq\-b,unit) fn
\? | Mem1: (\tq\-a ->\tq\-b) * \tq\-a * \tq\-b -> (\tq\-a, \tq\-b, \tq\-a * \tq\-b) fn

\? let apply: (\tq\-arg,\tq\-result, _ ) fn -> \tq\-arg -> \tq\-result = fun f x ->
\? match f with
\? | Fun f -> f x
\? | \<Mem1 (f,y,fy)\> -> if x = y then fy else f x;;

\: Error: This pattern matches values of type
\: ($\tq\-arg, $\tq\-result, $\tq\-arg * $\tq\-result) fn
\: but a pattern was expected which matches values of type
\: ($\tq\-arg, $\tq\-result, unit) fn
\: Type $\tq\-arg * $\tq\-result is not compatible with type unit
\endcaml
\item "$n" (n a number) is an internally generated existential
\begin{caml_example}[error]
type ('arg,'result,'aux) fn =
| Fun: ('a ->'b) -> ('a,'b,unit) fn
| Mem1: ('a ->'b) * 'a * 'b -> ('a, 'b, 'a * 'b) fn

let apply: ('arg,'result, _ ) fn -> 'arg -> 'result = fun f x ->
match f with
| Fun f -> f x
| Mem1 (f,y,fy) -> if x = y then fy else f x;;
\end{caml_example}
\item "$n" (n a number) is an internally generated existential %$
which could not be named using one of the previous schemes.
\end{itemize}

Expand Down Expand Up @@ -1914,16 +1895,15 @@ Some extension nodes are understood by the compiler itself:
constructor slot.
\end{itemize}

\begin{verbatim}
\begin{caml_example*}
type t = ..
type t += X of int | Y of string
let x = [%extension_constructor X]
let y = [%extension_constructor Y]
\end{verbatim}
\caml
\? x <> y;;
\:- : bool = true
\endcaml
let y = [%extension_constructor Y];;
\end{caml_example*}
\begin{caml_example}
x <> y;;
\end{caml_example}

\section{Quoted strings}\label{s:quoted-strings}

Expand Down
19 changes: 16 additions & 3 deletions manual/tools/caml_tex2.ml
Original file line number Diff line number Diff line change
Expand Up @@ -118,7 +118,7 @@ module Output = struct
Printf.eprintf
"Error when evaluating a guarded caml_example environment in %a\n\
Unexpected %a status, %a status was expected.\n\
If %a states was in fact expected, change the status annotation to \
If %a status was in fact expected, change the status annotation to \
[@@expect %a].\n"
print_source source
pp_status got
Expand Down Expand Up @@ -231,6 +231,8 @@ let escape_specials s =
let s3 = global_replace ~!"`" "\\\\textasciigrave\\\\-" s2 in
s3

exception Missing_double_semicolon of string * int

let process_file file =
prerr_endline ("Processing " ^ file);
let ic = try open_in file with _ -> failwith "Cannot read input file" in
Expand Down Expand Up @@ -266,7 +268,12 @@ let process_file file =
let input = incr phrase_stop; input_line ic in
if string_match ~!"\\\\end{caml_example\\*?}[ \t]*$"
input 0
then raise End_of_file;
then begin
if !phrase_stop = 1 + !phrase_start then
raise End_of_file
else
raise @@ Missing_double_semicolon (file,!phrase_stop)
end;
if Buffer.length phrase > 0 then Buffer.add_char phrase '\n';
let stop = string_match ~!"\\(.*\\)[ \t]*;;[ \t]*$" input 0 in
if not stop then (
Expand Down Expand Up @@ -350,12 +357,18 @@ let process_file file =
flush oc
end
done with
| End_of_file -> close_in ic; close_out oc
| End_of_file -> close_in ic; close_out oc
| Output.Unexpected_status r ->
( Output.print_unexpected r; close_in ic; close_out oc; exit 1 )
| Output.Parsing_error (k,s) ->
( Output.print_parsing_error k s;
close_in ic; close_out oc; exit 1 )
| Missing_double_semicolon (file, line_number) ->
( Format.eprintf "Error when evaluating a caml_example environment in \
%s:\nmissing \";;\" at line %d\n" file (line_number-2);
close_in ic; close_out oc;
exit 1
)

let _ =
if !outfile <> "-" && !outfile <> "" then begin
Expand Down

0 comments on commit 4c04dee

Please sign in to comment.