caml-list - the Caml user's mailing list
 help / color / mirror / Atom feed
* [Caml-list] lisp -> ocaml
@ 2001-05-22 16:33 Miles Egan
  2001-05-22 16:52 ` Markus Mottl
                   ` (3 more replies)
  0 siblings, 4 replies; 13+ messages in thread
From: Miles Egan @ 2001-05-22 16:33 UTC (permalink / raw)
  To: caml-list

For my own edification I've been translating some of the code from Norvig's
PAIP AI text to get an idea of what this kind of code looks like in OCaml and
I've come up against two small problems.

First, I have two mutually recursive function definitions:

let apply_op op =
  if (Stateset.for_all achieve op.op_preconds) then
    begin
      print_endline ("executing " ^ op.op_action);
      global_state := Stateset.diff !global_state op.op_dellist;
      global_state := Stateset.union !global_state op.op_addlist;
      true
    end
    else
      false

let achieve goal ops =
  Stateset.mem goal global_state or
  List.exists apply_op (List.filter (appropriate_p goal) ops)

Which fails to compile, for obvious reasons.  Is the solution to refactor the
code into a nonrecursive form?  In the absence of forward declarations, I'm
not sure what else to do.

Second, the PAIP code makes fairly heavy use of Lisp's symbolic features and
uses symbols as a kind of type tag but also as printable strings.  I've been
using variants, both traditional and polymorphic, as a substitute, but they're
not really quite equivalent.  For example, one of the first programs is a
simple implementation of the old GPS (general problem solver), which
manipulates sets of states.  Lisp provides set operations on lists and allows
printing of symbols, which makes it possible to both manipulate "state" lists
and print them with very little code.  I can't use variants with the same
flexibility because I have to provide an explicit ordering if I want to use
them as set members and I can't print them because there doesn't seem to be a
way to print something like:

type t = ONE | TWO | THREE

as "ONE", "TWO", "THREE".

I'm using strings in the meantime but this isn't very satisfying.                                                                               
-- 
miles
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] lisp -> ocaml
  2001-05-22 16:33 [Caml-list] lisp -> ocaml Miles Egan
@ 2001-05-22 16:52 ` Markus Mottl
  2001-05-22 17:09 ` Brian Rogoff
                   ` (2 subsequent siblings)
  3 siblings, 0 replies; 13+ messages in thread
From: Markus Mottl @ 2001-05-22 16:52 UTC (permalink / raw)
  To: Miles Egan; +Cc: caml-list

On Tue, 22 May 2001, Miles Egan wrote:
> Which fails to compile, for obvious reasons.  Is the solution to
> refactor the code into a nonrecursive form?  In the absence of forward
> declarations, I'm not sure what else to do.

No, you have to explicitly express that the two functions are mutually
recursive by using the "and" keyword as in, e.g.:

  let rec f () = g ()
  and g () = f ()

Regards,
Markus Mottl

-- 
Markus Mottl, mottl@miss.wu-wien.ac.at, http://miss.wu-wien.ac.at/~mottl
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] lisp -> ocaml
  2001-05-22 16:33 [Caml-list] lisp -> ocaml Miles Egan
  2001-05-22 16:52 ` Markus Mottl
@ 2001-05-22 17:09 ` Brian Rogoff
  2001-05-22 18:27 ` Remi VANICAT
  2001-05-27 13:01 ` Xavier Leroy
  3 siblings, 0 replies; 13+ messages in thread
From: Brian Rogoff @ 2001-05-22 17:09 UTC (permalink / raw)
  To: Miles Egan; +Cc: caml-list

On Tue, 22 May 2001, Miles Egan wrote:
> Which fails to compile, for obvious reasons.  Is the solution to refactor the
> code into a nonrecursive form? 

In Caml you declare mutually recursive functions and types with a
"rec" and an "and" 

let rec apply_op op = ...
and achieve goal ops = ...

You can also use the same syntax to emulate "where" clauses of Haskell and
other FPLs. 

> Second, the PAIP code makes fairly heavy use of Lisp's symbolic features and
> uses symbols as a kind of type tag but also as printable strings.  I've been
> using variants, both traditional and polymorphic, as a substitute, but they're
> not really quite equivalent.  For example, one of the first programs is a
> simple implementation of the old GPS (general problem solver), which
> manipulates sets of states.  Lisp provides set operations on lists and allows
> printing of symbols, which makes it possible to both manipulate "state" lists
> and print them with very little code.  I can't use variants with the same
> flexibility because I have to provide an explicit ordering if I want to use
> them as set members and I can't print them because there doesn't seem to be a
> way to print something like:

One thing you can do is write polymorphic versions of the OCaml library
set functor, which you'll need anyways as soon as you want to have a type 
recursive with a functor instantiation. Insert long whining and sobbing
here about how this is a pain :-).

For this problem though, it seems that you just want nullary constructors
of a sum type to behave as integers, as in C or Ada. Easy enough with a 
bit of boilerplate code. 

> type t = ONE | TWO | THREE
> 
> as "ONE", "TWO", "THREE".

let pos = function ONE -> 1 | TWO -> 2 | THREE -> 3
let image = function ONE -> "uno" | TWO -> "dos" | THREE -> "tres"

> I'm using strings in the meantime but this isn't very satisfying.

Indeed.

-- Brian


-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] lisp -> ocaml
  2001-05-22 18:27 ` Remi VANICAT
@ 2001-05-22 17:12   ` Miles Egan
  2001-05-22 18:26     ` Chris Hecker
  0 siblings, 1 reply; 13+ messages in thread
From: Miles Egan @ 2001-05-22 17:12 UTC (permalink / raw)
  To: caml-list

On Tue, May 22, 2001 at 08:27:01PM +0200, Remi VANICAT wrote:
> the 
> let rec ... = ..
> and ... = ...
> and ... = ...
> 
> make the trick

Great.  This is easy enough.  Thanks (and thanks to Markus).

> no you haven't, the function compare is a very good ordering for
> variant:
> 
> # compare `Aze `Azr ;;
> - : int = -1
> # compare (Some 0) None;;
> - : int = 1
> # type response = Yes | No;;
> type response = Yes | No
> # compare Yes No;;
> - : int = -1

I wasn't aware of this function, but it's exactly what I need.  Thanks again.

> yes this a problem. but often there is better way to print thing than
> just the name of the variant.
> 
> You can also use camlp4 to make a construct who build the variant and
> the printer at the same time.

I haven't had a chance to familiarize myself with camlp4 yet.  I guess I should.

-- 
miles
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] lisp -> ocaml
  2001-05-22 17:12   ` Miles Egan
@ 2001-05-22 18:26     ` Chris Hecker
  0 siblings, 0 replies; 13+ messages in thread
From: Chris Hecker @ 2001-05-22 18:26 UTC (permalink / raw)
  To: Miles Egan, caml-list


>> yes this a problem. but often there is better way to print thing than
>> just the name of the variant.
>> You can also use camlp4 to make a construct who build the variant and
>> the printer at the same time.
>I haven't had a chance to familiarize myself with camlp4 yet.  I guess I should.

Isn't there something that could be done with the toplevel libraries?  The toplevel prints variant ctors correctly.

Chris


-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] lisp -> ocaml
  2001-05-22 16:33 [Caml-list] lisp -> ocaml Miles Egan
  2001-05-22 16:52 ` Markus Mottl
  2001-05-22 17:09 ` Brian Rogoff
@ 2001-05-22 18:27 ` Remi VANICAT
  2001-05-22 17:12   ` Miles Egan
  2001-05-27 13:01 ` Xavier Leroy
  3 siblings, 1 reply; 13+ messages in thread
From: Remi VANICAT @ 2001-05-22 18:27 UTC (permalink / raw)
  To: caml-list

Miles Egan <miles@caddr.com> writes:

> For my own edification I've been translating some of the code from Norvig's
> PAIP AI text to get an idea of what this kind of code looks like in OCaml and
> I've come up against two small problems.
> 
> First, I have two mutually recursive function definitions:
> 
> let apply_op op =
>   if (Stateset.for_all achieve op.op_preconds) then
>     begin
>       print_endline ("executing " ^ op.op_action);
>       global_state := Stateset.diff !global_state op.op_dellist;
>       global_state := Stateset.union !global_state op.op_addlist;
>       true
>     end
>     else
>       false
> 
> let achieve goal ops =
>   Stateset.mem goal global_state or
>   List.exists apply_op (List.filter (appropriate_p goal) ops)


something like 

let rec apply_op op =
   if (Stateset.for_all achieve op.op_preconds) then
     begin
       print_endline ("executing " ^ op.op_action);
       global_state := Stateset.diff !global_state op.op_dellist;
       global_state := Stateset.union !global_state op.op_addlist;
       true
     end
     else
       false
 
and achieve goal ops =
   Stateset.mem goal global_state or
   List.exists apply_op (List.filter (appropriate_p goal) ops)

will work

> 
> Which fails to compile, for obvious reasons.  Is the solution to refactor the
> code into a nonrecursive form?  In the absence of forward declarations, I'm
> not sure what else to do.

the 
let rec ... = ..
and ... = ...
and ... = ...

make the trick

> Lisp provides set operations on lists and allows printing of
> symbols, which makes it possible to both manipulate "state" lists
> and print them with very little code.  I can't use variants with the
> same flexibility because I have to provide an explicit ordering if I
> want to use them as set members

no you haven't, the function compare is a very good ordering for
variant:

# compare `Aze `Azr ;;
- : int = -1
# compare (Some 0) None;;
- : int = 1
# type response = Yes | No;;
type response = Yes | No
# compare Yes No;;
- : int = -1


> and I can't print them because there doesn't seem to be a way to
> print something like:
> 
> type t = ONE | TWO | THREE
> 
> as "ONE", "TWO", "THREE".

yes this a problem. but often there is better way to print thing than
just the name of the variant.

You can also use camlp4 to make a construct who build the variant and
the printer at the same time.

-- 
Rémi Vanicat
vanicat@labri.u-bordeaux.fr
http://dept-info.labri.u-bordeaux.fr/~vanicat
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] lisp -> ocaml
  2001-05-22 16:33 [Caml-list] lisp -> ocaml Miles Egan
                   ` (2 preceding siblings ...)
  2001-05-22 18:27 ` Remi VANICAT
@ 2001-05-27 13:01 ` Xavier Leroy
  2001-05-27 14:43   ` Miles Egan
                     ` (2 more replies)
  3 siblings, 3 replies; 13+ messages in thread
From: Xavier Leroy @ 2001-05-27 13:01 UTC (permalink / raw)
  To: Miles Egan; +Cc: caml-list

> Second, the PAIP code makes fairly heavy use of Lisp's symbolic
> features and uses symbols as a kind of type tag but also as
> printable strings.  I've been using variants, both traditional and
> polymorphic, as a substitute, but they're not really quite
> equivalent.

Right.  The closest OCaml equivalent to a Lisp atom is unique strings,
which are not provided by the standard library but can easily be
implemented as a module.

With some trickery, you can even implement atoms with property lists,
type safe but dynamically typed of course.  See the code below.
(Warning: the implementation of properties is a real mind-twister,
using a folklore trick to implement dynamics using references and
functions that I learnt from Daniel de Rauglaudre, although it's been
reinvented independently quite a number of times.)

I agree it's best to use variants instead of strings, since this gives
much better static typing guarantees.  As for printing, it is possible
to generate printing functions automatically, as others pointed out,
but it's a bit of a sledgehammer if all your variant constructors are
constant; a simple association list or hash table works fine, e.g.

let name_table = [ One, "one"; Two, "two"; Three, "three"]

let print_name x =
  try
    print_string (List.assoc x name_table)
  with Not_found ->
    print_string "???"

Chris Hecker asked:

> Isn't there something that could be done with the toplevel libraries?
> The toplevel prints variant ctors correctly.

True, but it has access to a wealth of typing information: the
inferred type for the value to be printed, plus the whole typing
environment.  This allows it to decipher the machine representation of
values, using the types to provide symbolic names for constructors and
record labels.  In a separately-compiled program, this typing
information is available at compile-time, but not at run-time.

There have been several attempts at making some type information
available at run-time, e.g. dynamics, or Furuse-Weis' extensional
polymorphism, but this is still ongoing work.

- Xavier Leroy

(* atoms.mli *)

type atom

val intern: string -> atom
val name: atom -> string

type 'a property

val new_property: unit -> 'a property
val put_property: atom -> 'a property -> 'a -> unit
val get_property: atom -> 'a property -> 'a

(* atoms.ml *)

type atom = { name: string; mutable properties: (unit -> unit) list }

let atom_table = (Hashtbl.create 37 : (string, atom) Hashtbl.t)

let intern s =
  try
    Hashtbl.find atom_table s
  with Not_found ->
    let a = { name = s; properties = [] } in
    Hashtbl.add atom_table s a;
    a

let name atom = atom.name

type 'a property = 'a option ref

let new_property () = ref None

let put_property atom prop value =
  atom.properties <- (fun () -> prop := Some value) :: atom.properties

let get_property atom prop =
  let rec get = function
    [] -> raise Not_found
  | fn :: rem ->
      fn();
      match !prop with
        None -> get rem
      | Some v -> prop := None; v
  in get atom.properties

(* A more careful version of put that erases overwritten properties:

let put_property atom prop value =
  let rec put = function
    [] -> [fun () -> prop := Some value]
  | fn :: rem ->
      fn();
      match !prop with
        None -> fn :: put rem
      | Some v -> prop := None; (fun () -> prop := Some value) :: rem
  in atom.properties <- put atom.properties

*)
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] lisp -> ocaml
  2001-05-27 13:01 ` Xavier Leroy
@ 2001-05-27 14:43   ` Miles Egan
  2001-05-27 21:24   ` Dave Mason
  2001-05-28  0:06   ` Chris Hecker
  2 siblings, 0 replies; 13+ messages in thread
From: Miles Egan @ 2001-05-27 14:43 UTC (permalink / raw)
  To: caml-list

On Sun, May 27, 2001 at 03:01:19PM +0200, Xavier Leroy wrote:
> > Second, the PAIP code makes fairly heavy use of Lisp's symbolic
> > features and uses symbols as a kind of type tag but also as
> > printable strings.  I've been using variants, both traditional and
> > polymorphic, as a substitute, but they're not really quite
> > equivalent.
> 
> Right.  The closest OCaml equivalent to a Lisp atom is unique strings,
> which are not provided by the standard library but can easily be
> implemented as a module.
> 
> With some trickery, you can even implement atoms with property lists,
> type safe but dynamically typed of course.  See the code below.
> (Warning: the implementation of properties is a real mind-twister,
> using a folklore trick to implement dynamics using references and
> functions that I learnt from Daniel de Rauglaudre, although it's been
> reinvented independently quite a number of times.)

Thanks for the suggestions and the code.  I'll give this a shot.

--
miles
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] lisp -> ocaml
  2001-05-27 13:01 ` Xavier Leroy
  2001-05-27 14:43   ` Miles Egan
@ 2001-05-27 21:24   ` Dave Mason
  2001-05-28 17:10     ` William Chesters
  2001-05-28  0:06   ` Chris Hecker
  2 siblings, 1 reply; 13+ messages in thread
From: Dave Mason @ 2001-05-27 21:24 UTC (permalink / raw)
  To: caml-list

>>>>> On Sun, 27 May 2001 15:01:19 +0200, Xavier Leroy <Xavier.Leroy@inria.fr> said:

> With some trickery, you can even implement atoms with property
> lists, type safe but dynamically typed of course.  See the code
> below.  (Warning: the implementation of properties is a real
> mind-twister, using a folklore trick to implement dynamics using
> references and functions that I learnt from Daniel de Rauglaudre,
> although it's been reinvented independently quite a number of
> times.)

Very cute!  But not threadsafe among threads that use the same set of
attributes (unless I missed something).  I point this out simply as a
warning, not because I think it invalidates the (neat) trick.

../Dave
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] lisp -> ocaml
  2001-05-27 13:01 ` Xavier Leroy
  2001-05-27 14:43   ` Miles Egan
  2001-05-27 21:24   ` Dave Mason
@ 2001-05-28  0:06   ` Chris Hecker
  2001-05-28 13:32     ` Xavier Leroy
  2 siblings, 1 reply; 13+ messages in thread
From: Chris Hecker @ 2001-05-28  0:06 UTC (permalink / raw)
  To: Xavier Leroy, Miles Egan; +Cc: caml-list


>> Isn't there something that could be done with the toplevel libraries?
>> The toplevel prints variant ctors correctly.
>...
>record labels.  In a separately-compiled program, this typing
>information is available at compile-time, but not at run-time.

Right, I just meant in a program known to be running under the toplevel, would it be possible to use the typing information that's already there?  Those functions aren't available right now, but I don't see why they couldn't be.  

> val new_property: unit -> 'a property
>val put_property: atom -> 'a property -> 'a -> unit
>val get_property: atom -> 'a property -> 'a
>...

I'm confused by what this code is trying to do.  Maybe I don't know enough about lisp to know how this code maps to it, but what's an example code snippet you'd use this code for?

Chris


-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] lisp -> ocaml
  2001-05-28  0:06   ` Chris Hecker
@ 2001-05-28 13:32     ` Xavier Leroy
  2001-05-28 19:02       ` Chris Hecker
  0 siblings, 1 reply; 13+ messages in thread
From: Xavier Leroy @ 2001-05-28 13:32 UTC (permalink / raw)
  To: Chris Hecker; +Cc: Miles Egan, caml-list

> Right, I just meant in a program known to be running under the
> toplevel, would it be possible to use the typing information that's
> already there?  Those functions aren't available right now, but I
> don't see why they couldn't be.

The "print" function cannot be a regular function because it needs
both the value to be printed and the (representation of) the type of
this value.  In other terms, just having
        val print: 'a -> unit
isn't enough, because the actual type of the argument would not be
known to the print function.


> > val new_property: unit -> 'a property
> >val put_property: atom -> 'a property -> 'a -> unit
> >val get_property: atom -> 'a property -> 'a
> >...
> 
> I'm confused by what this code is trying to do.  Maybe I don't know
> enough about lisp to know how this code maps to it, but what's an
> example code snippet you'd use this code for?

Property lists in classic Lisp are association lists attached to
atoms.  They provide a simple way to attach information to atoms.
The keys of the a-list are arbitrary Lisp values (I think) but in
practice are generally atoms or integers.  The associated data are
arbitrary Lisp values.

The natural way to handle this in Caml is to parameterize the type of
atoms by the types of the keys and data of the property list:

type ('a, 'b) atom = { name : string;
                       mutable properties : ('a * 'b) list }

but this constraints quite a lot the data that can be put in property
lists.  If you're translating old Lisp code verbatim, it may be a
problem.

The mysterious code I sent works around this limitation by allowing
data of several types to be stored in property lists, without being
reflected in the type of atoms.  Of course, to preserve type safety,
property keys need to be typed, so that when we recover a data from a
property list, its type is known.

Here is how you'd use all this.  Start with Lisp code where property A
can be associated with integers or strings, and property B can be
associated with booleans.  You'd first define three Caml properties
and assign them types:

   let prop_A_int = (new_property : int property)
   let prop_A_string = (new_property : string property)
   let prop_B = (new_property : bool property)

Then you can add properties to any atom:

  put_property atom prop_A_int 12;
  put_property atom prop_B true;
  put_property atom2 prop_A_string "Hello"

And recover the values in a type-safe way:

  get_property atom prop_A_int  (--> type int, value 12 )
  get_property atom prop_A_string ( --> type string, raises Not_found)

Silly trick, but I find this quite enjoyable.

- Xavier Leroy
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] lisp -> ocaml
  2001-05-27 21:24   ` Dave Mason
@ 2001-05-28 17:10     ` William Chesters
  0 siblings, 0 replies; 13+ messages in thread
From: William Chesters @ 2001-05-28 17:10 UTC (permalink / raw)
  To: caml-list

Dave Mason writes:
 > Very cute!  But not threadsafe among threads that use the same set of
 > attributes (unless I missed something).  I point this out simply as a
 > warning, not because I think it invalidates the (neat) trick.

That's easy to fix, and while you're about it you may as well extend
the idea to implement object-orientation a la Perl---only type-safe :).
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] lisp -> ocaml
  2001-05-28 13:32     ` Xavier Leroy
@ 2001-05-28 19:02       ` Chris Hecker
  0 siblings, 0 replies; 13+ messages in thread
From: Chris Hecker @ 2001-05-28 19:02 UTC (permalink / raw)
  To: Xavier Leroy; +Cc: Miles Egan, caml-list


>reflected in the type of atoms.  Of course, to preserve type safety,
>property keys need to be typed, so that when we recover a data from a
>property list, its type is known.

Yeah, this was the part that I was missing (that you needed to have the preallocated property around to pass in).

So, in lisp, I assume I don't need to pass in this other piece of data since it's dynamically typed.

However, with this, it seems like I need to pass in the same property instance to "get" that I gave to "put" (so that the closure sets the right thing), so if I want somebody else to be able to get the properties I set, then I have to pass them all my property instances as well, right?  Which sort of causes the same heterogeneity problem again.  ;)  Or am I missing something?

I guess you could preallocate properties for the basic types in the atoms.mli file so everybody could use them, but you'd still have to have a set that your app uses for your own types.

Still, it's definitely a cute trick!

Somebody needs to make a website with "wacky but potentially useful functional patterns", since there's no way I'd have thought of this, or combinators, or whatever.  :)

Chris

-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

end of thread, other threads:[~2001-05-28 19:10 UTC | newest]

Thread overview: 13+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2001-05-22 16:33 [Caml-list] lisp -> ocaml Miles Egan
2001-05-22 16:52 ` Markus Mottl
2001-05-22 17:09 ` Brian Rogoff
2001-05-22 18:27 ` Remi VANICAT
2001-05-22 17:12   ` Miles Egan
2001-05-22 18:26     ` Chris Hecker
2001-05-27 13:01 ` Xavier Leroy
2001-05-27 14:43   ` Miles Egan
2001-05-27 21:24   ` Dave Mason
2001-05-28 17:10     ` William Chesters
2001-05-28  0:06   ` Chris Hecker
2001-05-28 13:32     ` Xavier Leroy
2001-05-28 19:02       ` Chris Hecker

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).