disambiguate polymorphic variants (PR#4753/#4803)

git-svn-id: http://caml.inria.fr/svn/ocamldoc/trunk@10314 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Jacques Garrigue 2010-04-27 07:05:32 +00:00
parent b4493a2990
commit 11abcdde8a
3 changed files with 27 additions and 25 deletions

View File

@ -559,13 +559,13 @@ to do the method call "foo#bar" from the C side, you should call:
callback(caml_get_public_method(foo, hash_variant("bar")), foo);
\end{verbatim}
\subsection{Variants}
\subsection{Prolymorphic variants}
Like constructed terms, values of variant types are represented either
as integers (for variants without arguments), or as blocks (for
variants with an argument). Unlike constructed terms, variant
constructors are not numbered starting from 0, but identified by a
hash value (a Caml integer), as computed by the C function
Like constructed terms, polymorphic variant values are represented either
as integers (for polymorphic variants without arguments), or as blocks
(for polymorphic variants with an argument). Unlike constructed
terms, variant constructors are not numbered starting from 0, but
identified by a hash value (a Caml integer), as computed by the C function
"hash_variant" (declared in "<caml/mlvalues.h>"):
the hash value for a variant constructor named, say, "VConstr"
is "hash_variant(\"VConstr\")".
@ -576,11 +576,12 @@ represented by a block of size 2 and tag 0, with field number 0
containing "hash_variant(\"VConstr\")" and field number 1 containing
\var{v}.
Unlike constructed values, variant values taking several arguments are
not flattened. That is, "`VConstr("\var{v}", "\var{v'}")" is
represented by a block of size 2, whose field number 1 contains
the representation of the pair "("\var{v}", "\var{v'}")", rather than a
block of size 3 containing \var{v} and \var{v'} in fields 1 and 2.
Unlike constructed values, polymorphic variant values taking several
arguments are not flattened.
That is, "`VConstr("\var{v}", "\var{v'}")" is represented by a block
of size 2, whose field number 1 contains the representation of the
pair "("\var{v}", "\var{v'}")", rather than a block of size 3
containing \var{v} and \var{v'} in fields 1 and 2.
\section{Operations on values}
\pdfsection{Operations on values}

View File

@ -508,8 +508,8 @@ values of @expr_1@ to @expr_n@.
\subsubsection*{Polymorphic variants}
The expression @"`"tag-name expr@ evaluates to the variant value whose
tag is @tag-name@, and whose argument is the value of @expr@.
The expression @"`"tag-name expr@ evaluates to the polymorphic variant
value whose tag is @tag-name@, and whose argument is the value of @expr@.
\subsubsection*{Records}
@ -713,9 +713,9 @@ expression @expr@ from type @typexpr_1@ to type @typexpr_2@.
The former operator will sometimes fail to coerce an expression @expr@
from a type $t_1$ to a type $t_2$ even if type $t_1$ is a subtype of type
$t_2$: in the current implementation it only expands two levels of
type abbreviations containing objects and/or variants, keeping only
recursion when it is explicit in the class type (for objects). As an
exception to the above algorithm, if both the inferred type of @expr@
type abbreviations containing objects and/or polymorphic variants,
keeping only recursion when it is explicit in the class type (for objects).
As an exception to the above algorithm, if both the inferred type of @expr@
and @typexpr@ are ground ({\em i.e.} do not contain type variables), the
former operator behaves as the latter one, taking the inferred type of
@expr@ as @typexpr_1@. In case of failure with the former operator,

View File

@ -14,7 +14,7 @@ typexpr:
| typexpr typeconstr
| '(' typexpr { ',' typexpr } ')' typeconstr
| typexpr 'as' "'" ident
| variant-type
| polymorphic-variant-type
| '<' ['..'] '>'
| '<' method-type { ';' method-type } [';' '..'] '>'
| '#' class-path
@ -113,17 +113,17 @@ the same as for a named type variable, and covers the whole enclosing
definition. If the type variable
@ident@ actually occurs in @typexpr@, a recursive type is created. Recursive
types for which there exists a recursive path that does not contain
an object or variant type constructor are rejected, except when the
"-rectypes" mode is selected.
an object or polymorphic variant type constructor are rejected, except
when the "-rectypes" mode is selected.
If @"'" ident@ denotes an explicit polymorphic variable, and @typexpr@
denotes either an object or variant type, the row variable of @typexpr@
is captured by @"'" ident@, and quantified upon.
denotes either an object or polymorphic variant type, the row variable
of @typexpr@ is captured by @"'" ident@, and quantified upon.
\subsubsection*{Variant types}
\subsubsection*{Polymorphic variant types}
\begin{syntax}
variant-type:
polymorphic-variant-type:
'[' [ '|' ] tag-spec { '|' tag-spec } ']'
| '[>' [ tag-spec ] { '|' tag-spec } ']'
| '[<' [ '|' ] tag-spec-full { '|' tag-spec-full } [ '>' {{ '`'tag-name }} ] ']'
@ -142,7 +142,8 @@ tag-spec-full:
;
\end{syntax}
Variant types describe the values a polymorphic variant may take.
Polymorphic variant types describe the values a polymorphic variant
may take.
The first case is an exact variant type: all possible tags are
known, with their associated types, and they can all be present.
@ -211,7 +212,7 @@ type @'#' class-path '->' '#' class-path@ is usually not the same as
type @('#' class-path 'as' "'" ident) '->' "'" ident@.
%
Use of \#-types to abbreviate variant types is deprecated.
Use of \#-types to abbreviate polymorphic variant types is deprecated.
If "t" is an exact variant type then "#t" translates to "[< t]",
and @"#t[>" "`tag"_1 \dots"`tag"_k"]"@ translates to
@"[<" "t" ">" "`tag"_1 \dots"`tag"_k"]"@