caml-list - the Caml user's mailing list
 help / color / mirror / Atom feed
* [Caml-list] Polymorphic methods (longest error message ever!)
@ 2002-07-08  1:25 Brian Smith
  2002-07-08  2:08 ` John Max Skaller
                   ` (2 more replies)
  0 siblings, 3 replies; 4+ messages in thread
From: Brian Smith @ 2002-07-08  1:25 UTC (permalink / raw)
  To: OCaml Mailing list

Hi everybody,

First of all, where can I find some documentation about the CVS versino 
of O'Caml? Is the documentation kept in CVS too? Anyway, on to the 
problem at hand:

I have a class like this:
    class type ['a] node_type =
      object
        method as_variant : 'a
        constraint 'a = [> `Node of 'a node_type]
      end;;
    class ['a] node : ['a] node_type =
      object (self)
        method as_variant : 'a = `Node (self :> 'a node_type)
      end;;

That works fine in O'Caml 3.04. But, I want to use the new polymorphic 
method feature in O'Caml 3.04+15. So I tried:

  # class type node_type =  object
      method as_variant : [> `Node of node_type]
    end;;
  class type node_type =
     object method as_variant : [> `Node of node_type] end

  # class node : node_type = object (self)
      method as_variant = `Node (self :> node_type)
    end;;
                                 ^^^^
  This expression cannot be coerced to type
  node_type = < as_variant : 'a. [> `Node of node_type] as 'a >;
  it has type < as_variant : 'c; .. > as 'b but is here used with type 'b

  # class node : node_type = object (self)
      method as_variant : 'a. [> `Node of node_type] as 'a
                        = `Node (self :>  node_type)
    end;;
The class type object method as_variant : [> `Node of node_type] end
is not matched by the class type node_type
The class type object method as_variant : [> `Node of node_type] end
is not matched by the class type
   object method as_variant : [> `Node of node_type] end
The method as_variant has type 'a. [> `Node of node_type] as 'a
but is expected to have type 'b. [> `Node of node_type] as 'b
The universal variable 'b would escape its scope

I have no idea what the error message means. To me, it is saying that 
class "node" doesn't match class type "node_type" even though everything 
has exactly the same type. Could somebody please explain it to me? What 
is the correct way of doing the above?

Thanks,
Brian


-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


^ permalink raw reply	[flat|nested] 4+ messages in thread

* Re: [Caml-list] Polymorphic methods (longest error message ever!)
  2002-07-08  1:25 [Caml-list] Polymorphic methods (longest error message ever!) Brian Smith
@ 2002-07-08  2:08 ` John Max Skaller
  2002-07-08  2:53 ` Jacques Garrigue
  2002-07-09  6:23 ` [Caml-list] Polymorphic methods (syntax) Brian Smith
  2 siblings, 0 replies; 4+ messages in thread
From: John Max Skaller @ 2002-07-08  2:08 UTC (permalink / raw)
  To: Brian Smith; +Cc: OCaml Mailing list

Brian Smith wrote:

>
>  # class node : node_type = object (self)
>      method as_variant = `Node (self :> node_type)
>    end;;
>                                 ^^^^
>  This expression cannot be coerced to type
>  node_type = < as_variant : 'a. [> `Node of node_type] as 'a >;
>  it has type < as_variant : 'c; .. > as 'b but is here used with type 'b
>
>  # class node : node_type = object (self)
>      method as_variant : 'a. [> `Node of node_type] as 'a
>                        = `Node (self :>  node_type)
>    end;;
> The class type object method as_variant : [> `Node of node_type] end
> is not matched by the class type node_type
> The class type object method as_variant : [> `Node of node_type] end
> is not matched by the class type
>   object method as_variant : [> `Node of node_type] end
> The method as_variant has type 'a. [> `Node of node_type] as 'a
> but is expected to have type 'b. [> `Node of node_type] as 'b
> The universal variable 'b would escape its scope
>
> I have no idea what the error message means. 

Heh. I can't answer your question, but I have to fall about laughing
(is there a French idiom for that?) at the idea this is a long error 
message.
I often get error messages of 100's of lines, my console buffer isn't set
to 10,000 lines without reason. Just imagine your polymophic variant type

    [> Node of node_type]

was replace statement_t below .. and don't ignore the fact that
the ctor arguments themselves are similar polymorphic variant types
like expr_t ... and this isn't a large variant.

----------------------------------------------
and statement_t =
  [
  | `AST_open of range_srcref * qualified_name_t
  | `AST_comment of string (* for documenting generated code *)

  (* definitions *)
  | `AST_function of range_srcref * id_t * parameter_t list * typecode_t 
* statement_t list
  | `AST_procedure of range_srcref * id_t * parameter_t list * 
statement_t list

  (* types *)
  | `AST_union of range_srcref * id_t * (id_t * typecode_t) list
  | `AST_struct of range_srcref * id_t * (id_t * typecode_t) list
  | `AST_type_alias of range_srcref * id_t * typecode_t

  (* variables *)
  | `AST_val_decl of range_srcref * id_t * typecode_t option * expr_t option
  | `AST_var_decl of range_srcref * id_t * typecode_t option * expr_t option
 
  (* module system *)
  | `AST_untyped_module of range_srcref * id_t * statement_t list 
  | `AST_typed_module of range_srcref * id_t * typecode_t * statement_t 
list 
  | `AST_module_binding of range_srcref * id_t * expr_t
  | `AST_typed_functor of range_srcref * id_t * parameter_t list * 
typecode_t * statement_t list
  | `AST_untyped_functor of range_srcref * id_t * parameter_t list * 
statement_t list
  | `AST_interface of range_srcref * id_t * statement_t list
  | `AST_type of range_srcref * id_t
  | `AST_function_decl of range_srcref * id_t * typecode_t
  | `AST_procedure_decl of range_srcref * id_t * typecode_t

 
  (* control structures: primitives *)
  | `AST_label of range_srcref * id_t (* for testing the code generator! *)
  | `AST_goto of range_srcref * id_t (* for testing the code generator! *)
  | `AST_call of range_srcref * expr_t * expr_t
  | `AST_read of range_srcref * id_t
  | `AST_return of range_srcref * expr_t
  | `AST_nop of range_srcref * string

  | `AST_block of range_srcref * statement_t list
  | `AST_if of
    range_srcref *
    (range_srcref * (expr_t * statement_t)) list *
    (range_srcref * statement_t)
  | `AST_while of range_srcref * expr_t * statement_t

  (* exceptions *)
  | `AST_attempt of
    range_srcref *
    (range_srcref * statement_t) *         (* the attempt *)
    (range_srcref * statement_t list) *    (* the handlers *)
    (range_srcref * statement_t list)      (* the finally block *)
  | `AST_except_handler of range_srcref * id_t * parameter_t list * 
statement_t list
  | `AST_raise of range_srcref * id_t * expr_t

  (* binding structures [prolog] *)
  | `AST_abs_decl of range_srcref * id_t * c_t
  | `AST_const_decl of range_srcref * id_t * typecode_t * c_t
  | `AST_fun_decl of range_srcref * id_t * typecode_t list * typecode_t 
* c_t
  | `AST_proc_decl of range_srcref * id_t * typecode_t list * c_t
  | `AST_header of range_srcref * string
  | `AST_code of range_srcref * string

  | `AST_export of range_srcref * suffixed_name_t * string
  ]


-- 
John Max Skaller, mailto:skaller@ozemail.com.au
snail:10/1 Toxteth Rd, Glebe, NSW 2037, Australia.
voice:61-2-9660-0850




-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


^ permalink raw reply	[flat|nested] 4+ messages in thread

* Re: [Caml-list] Polymorphic methods (longest error message ever!)
  2002-07-08  1:25 [Caml-list] Polymorphic methods (longest error message ever!) Brian Smith
  2002-07-08  2:08 ` John Max Skaller
@ 2002-07-08  2:53 ` Jacques Garrigue
  2002-07-09  6:23 ` [Caml-list] Polymorphic methods (syntax) Brian Smith
  2 siblings, 0 replies; 4+ messages in thread
From: Jacques Garrigue @ 2002-07-08  2:53 UTC (permalink / raw)
  To: brian-l-smith; +Cc: caml-list

From: Brian Smith <brian-l-smith@uiowa.edu>

> First of all, where can I find some documentation about the CVS versino 
> of O'Caml? Is the documentation kept in CVS too?

Yes, but it is not public.
Anyway, it is not updated simultaneously with the source, so you
wont't find the documentation for a new feature there immediately.
So basically, new features in CVS are given as is, without other
documentation than asking the developpers.

In the present case, the release is probably not too far away, so you
should not have to wait too long.

Until that, for polymorphic methods, there are examples in
testlabl/poly.ml, but it's about all.

> Anyway, on to the problem at hand:
> That works fine in O'Caml 3.04. But, I want to use the new polymorphic 
> method feature in O'Caml 3.04+15. So I tried:
> 
>   # class type node_type =  object
>       method as_variant : [> `Node of node_type]
>     end;;
>   class type node_type =
>      object method as_variant : [> `Node of node_type] end
> 
>   # class node : node_type = object (self)
>       method as_variant = `Node (self :> node_type)
>     end;;
>                                  ^^^^
>   This expression cannot be coerced to type
>   node_type = < as_variant : 'a. [> `Node of node_type] as 'a >;
>   it has type < as_variant : 'c; .. > as 'b but is here used with type 'b

That one is correct behaviour: as_variant is inferred to be
monomorphic, since in the first pass the checker doesn't look inside
method, where is your only type annotation.
(Unfortunately the node: node_type constraint is only applied
afterwards, applying it early being rather complex.)

>   # class node : node_type = object (self)
>       method as_variant : 'a. [> `Node of node_type] as 'a
>                         = `Node (self :>  node_type)
>     end;;
> The class type object method as_variant : [> `Node of node_type] end
> is not matched by the class type node_type
> The class type object method as_variant : [> `Node of node_type] end
> is not matched by the class type
>    object method as_variant : [> `Node of node_type] end
> The method as_variant has type 'a. [> `Node of node_type] as 'a
> but is expected to have type 'b. [> `Node of node_type] as 'b
> The universal variable 'b would escape its scope
> 
> I have no idea what the error message means. To me, it is saying that 
> class "node" doesn't match class type "node_type" even though everything 
> has exactly the same type. Could somebody please explain it to me? What 
> is the correct way of doing the above?

As skaller says, this is hardly a long message :-)
It is also clearly wrong: it tells you that two identical types are
incompatible.
The problem seems to come from the node : node_type part. The
following version works:

# class node = object (self)
    method as_variant : 'a. [> `Node of node_type] as 'a
                      = `Node (self :>  node_type)
  end;;
class node : object method as_variant : [> `Node of node_type] end

And that shorter one also:
# class node = object (self : #node_type)
    method as_variant = `Node (self :> node_type)
  end;;
class node : object method as_variant : [> `Node of node_type] end

Thank you for the bug report, I'll try to correct it.

      Jacques
-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


^ permalink raw reply	[flat|nested] 4+ messages in thread

* Re: [Caml-list] Polymorphic methods (syntax)
  2002-07-08  1:25 [Caml-list] Polymorphic methods (longest error message ever!) Brian Smith
  2002-07-08  2:08 ` John Max Skaller
  2002-07-08  2:53 ` Jacques Garrigue
@ 2002-07-09  6:23 ` Brian Smith
  2 siblings, 0 replies; 4+ messages in thread
From: Brian Smith @ 2002-07-09  6:23 UTC (permalink / raw)
  To: OCaml Mailing list

My original problem has already been fixed in the latest CVS version by
Jacques. And, I found out that there is some documentation about 
polymorphic methods on the O'Labl website. But, now I have another 
question, this time about syntax.

Consider,

# class ['a] example = object
      method id x : 'a = x
    end;;

Now, let's say I want to move the type variable from the class to the
method. Intuitively, I expect that O'Caml could use this definition:

# class example = object
      method id x = x
    end;;
Some type variables are unbound in this type:
   class example : object method id : 'a -> 'a end
The method id has type 'a -> 'a where 'a is unbound

I would hope that O'Caml would infer that the type of the method x is
('a -> 'a) for all 'a. But, I know that Jacques has already said that
type inference of this type is not practical and so type annotations are
needed (Although, O'Caml actually does infer the correct type in this 
situation, it just disallows it). With that in mind, my next inutition 
is to try:

      # class example = object
          method ['a] id x : 'a = x
        end;;

or equivalently:

      # class example = object
          method ['a] id (x : 'a) = x
        end;;

Notice, I took the type parameter from the polymorphic class and just
moved it down to the method. But, currently this doesn't work either. I
propose that, if practical, this syntax be made to work. The benefits
are (1) symmetry with the syntax used for polymorphic classes, and (2)
less verbosity. As a comparison, in the current syntax (CVS version of
O'Caml), the definition would be:

# class example = object
      method id : 'a. 'a -> 'a = fun x -> x
    end;;

What do you think?

- Brian


-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


^ permalink raw reply	[flat|nested] 4+ messages in thread

end of thread, other threads:[~2002-07-09  6:23 UTC | newest]

Thread overview: 4+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2002-07-08  1:25 [Caml-list] Polymorphic methods (longest error message ever!) Brian Smith
2002-07-08  2:08 ` John Max Skaller
2002-07-08  2:53 ` Jacques Garrigue
2002-07-09  6:23 ` [Caml-list] Polymorphic methods (syntax) Brian Smith

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for NNTP newsgroup(s).