caml-list - the Caml user's mailing list
 help / color / mirror / Atom feed
* Re: [Caml-list] Breaking out of iterative loops
@ 2002-05-02 13:15 Krishnaswami, Neel
  2002-05-02 13:34 ` Markus Mottl
  0 siblings, 1 reply; 11+ messages in thread
From: Krishnaswami, Neel @ 2002-05-02 13:15 UTC (permalink / raw)
  To: OCaml Mailing list

Markus Mottl [mailto:markus@oefai.at] wrote:
> On Wed, 01 May 2002, John Prevost wrote:
> > The drawback to allowing:
> > 
> > let rec ones = 1 :: ones
> > 
> > and such expressions is that when looking at the definition of, for
> > example, 'a list and length, one would expect it to be 
> > guaranteed that length terminates. 
> 
> I second this. Does anybody here really benefit from such cyclic
> structures?

Somewhat to my surprise, I can answer yes:

type expr =
  | Var of string
  | App of expr * expr
  | Fun of string * expr
  | Rec of string * string * expr
and denot = Closure of string * expr * env
and env = (string * denot) list

let rec eval e r =
  match e with
  | Var v -> List.assoc v r
  | App(f, arg) ->
      let Closure(n, body, r') = eval f r in
      let v = eval arg r in
      eval body ((n, v) :: r')
  | Fun(n, body) -> Closure(n, body, r)
  | Rec(name, n, body) -> 
      let rec c = Closure(n, body, r')
      and r' = (name, c) :: r in
      c

Using cyclic structures means I don't have to dink around with 
mutable references and all the headaches they bring, and so it's
very handy when prototyping. 

--
Neel Krishnaswami
neelk@cswcasa.com
-------------------
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] 11+ messages in thread

* Re: [Caml-list] Breaking out of iterative loops
  2002-05-02 13:15 [Caml-list] Breaking out of iterative loops Krishnaswami, Neel
@ 2002-05-02 13:34 ` Markus Mottl
  0 siblings, 0 replies; 11+ messages in thread
From: Markus Mottl @ 2002-05-02 13:34 UTC (permalink / raw)
  To: Krishnaswami, Neel; +Cc: OCaml Mailing list

On Thu, 02 May 2002, Krishnaswami, Neel wrote:
> Markus Mottl [mailto:markus@oefai.at] wrote:
> > I second this. Does anybody here really benefit from such cyclic
> > structures?
> 
> Somewhat to my surprise, I can answer yes:
[snip]
>   | Rec(name, n, body) -> 
>       let rec c = Closure(n, body, r')
>       and r' = (name, c) :: r in
>       c

> Using cyclic structures means I don't have to dink around with 
> mutable references and all the headaches they bring, and so it's
> very handy when prototyping. 

Ok, I agree that this is a nice solution. It's still funny that all
people mentioned environment handling with recursion as only example.
I am not sure whether this is justification enough to have this extra
feature in the language...

Regards,
Markus Mottl

-- 
Markus Mottl                                             markus@oefai.at
Austrian Research Institute
for Artificial Intelligence                  http://www.oefai.at/~markus
-------------------
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] 11+ messages in thread

* Re: [Caml-list] Breaking out of iterative loops
  2002-05-02  8:33       ` Markus Mottl
  2002-05-02  9:14         ` Francois Pottier
  2002-05-02 14:35         ` Alessandro Baretta
@ 2002-05-02 15:40         ` John Max Skaller
  2 siblings, 0 replies; 11+ messages in thread
From: John Max Skaller @ 2002-05-02 15:40 UTC (permalink / raw)
  To: Markus Mottl; +Cc: John Prevost, OCaml Mailing list

Markus Mottl wrote:

>On Wed, 01 May 2002, John Prevost wrote:
>
>>The drawback to allowing:
>>
>>let rec ones = 1 :: ones
>>
>>and such expressions is that when looking at the definition of, for
>>example, 'a list and length, one would expect it to be guaranteed that
>>length terminates.  Since you can't prevent recursive use of
>>constructors, well, you can no longer guarantee that.
>>
>
>I second this. Does anybody here really benefit from such cyclic
>structures?
>
Well .. don't they make a good representation of recursive types?

-- 
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] 11+ messages in thread

* Re: [Caml-list] Breaking out of iterative loops
  2002-05-02  8:33       ` Markus Mottl
  2002-05-02  9:14         ` Francois Pottier
@ 2002-05-02 14:35         ` Alessandro Baretta
  2002-05-02 15:40         ` John Max Skaller
  2 siblings, 0 replies; 11+ messages in thread
From: Alessandro Baretta @ 2002-05-02 14:35 UTC (permalink / raw)
  To: Ocaml

Markus Mottl wrote:

> 
> I second this. Does anybody here really benefit from such cyclic
> structures?

I feel it necessary to cite prof. Jean-Jacques Levy's course 
  on programming languages at the Ecole Polytechnique:
(http://www.enseignement.polytechnique.fr/informatique/M2/lp/).

The following code illustrates how recursive data structures 
might be used to build a caml interpreter.

type expression = string

type variable_name = string

type values =
	Variable of variable_name
| 
Const of int
| 
Function of variable_name * expression * environment

and environment = (variable_name * values) list


The following is the internal representation the caml 
interpreter would build of
"let rec fact x = if x = 0 then 1 else x * fact (x-1)"

let rec rho =
   ["fact" , Function ("x", "if x=0 then 1 else x * fact 
(x-1)", rho)]

I hope this helps.

Alex

-------------------
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] 11+ messages in thread

* Re: [Caml-list] Breaking out of iterative loops
  2002-05-02  9:14         ` Francois Pottier
@ 2002-05-02  9:50           ` Alain Frisch
  0 siblings, 0 replies; 11+ messages in thread
From: Alain Frisch @ 2002-05-02  9:50 UTC (permalink / raw)
  To: Francois Pottier; +Cc: caml-list

On Thu, 2 May 2002, Francois Pottier wrote:

> The situation is different in the case of immutable structures. I
> don't know of any situation where immutable, cyclic structures are
> useful.

FWIW, I used an immutable cyclic structure once in an interpreter for a
functional language; here is the code that evaluate a recursive
abstraction:

         let rec local' = (f,self)::local
         and self = Value.AbstrMatch (al,local',pl) in
         self

The closure (self) contains the environment (local') that makes reference
to the closure, hence the recursive definition.

-- Alain

-------------------
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] 11+ messages in thread

* Re: [Caml-list] Breaking out of iterative loops
  2002-05-02  8:33       ` Markus Mottl
@ 2002-05-02  9:14         ` Francois Pottier
  2002-05-02  9:50           ` Alain Frisch
  2002-05-02 14:35         ` Alessandro Baretta
  2002-05-02 15:40         ` John Max Skaller
  2 siblings, 1 reply; 11+ messages in thread
From: Francois Pottier @ 2002-05-02  9:14 UTC (permalink / raw)
  To: caml-list


On Thu, May 02, 2002 at 10:33:35AM +0200, Markus Mottl wrote:
> 
> I second this. Does anybody here really benefit from such cyclic
> structures?

Yes, they can be useful, at least when they are mutable. Sometimes
a pointer to a known node (i.e. a cyclic pointer) can be used instead
of None. This can save the use of an option type, for instance.
Anyway, in the presence of mutable fields, you can't prevent cyclic
structures from appearing, so there is no point in disallowing their
explicit definition.

The situation is different in the case of immutable structures. I
don't know of any situation where immutable, cyclic structures are
useful.

-- 
François Pottier
Francois.Pottier@inria.fr
http://pauillac.inria.fr/~fpottier/
-------------------
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] 11+ messages in thread

* Re: [Caml-list] Breaking out of iterative loops
  2002-05-02  2:18     ` John Prevost
@ 2002-05-02  8:33       ` Markus Mottl
  2002-05-02  9:14         ` Francois Pottier
                           ` (2 more replies)
  0 siblings, 3 replies; 11+ messages in thread
From: Markus Mottl @ 2002-05-02  8:33 UTC (permalink / raw)
  To: John Prevost; +Cc: OCaml Mailing list

On Wed, 01 May 2002, John Prevost wrote:
> The drawback to allowing:
> 
> let rec ones = 1 :: ones
> 
> and such expressions is that when looking at the definition of, for
> example, 'a list and length, one would expect it to be guaranteed that
> length terminates.  Since you can't prevent recursive use of
> constructors, well, you can no longer guarantee that.

I second this. Does anybody here really benefit from such cyclic
structures?

I haven't found a single practical case where this was useful, but would
assume that some future program transformation tools that use proofs by
induction would have an easier life if this were disallowed...

Regards,
Markus Mottl

-- 
Markus Mottl                                             markus@oefai.at
Austrian Research Institute
for Artificial Intelligence                  http://www.oefai.at/~markus
-------------------
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] 11+ messages in thread

* Re: [Caml-list] Breaking out of iterative loops
  2002-05-02  0:57   ` John Max Skaller
@ 2002-05-02  2:18     ` John Prevost
  2002-05-02  8:33       ` Markus Mottl
  0 siblings, 1 reply; 11+ messages in thread
From: John Prevost @ 2002-05-02  2:18 UTC (permalink / raw)
  To: OCaml Mailing list

>>>>> "js" == John Max Skaller <skaller@ozemail.com.au> writes:

    js> the particular example that bugs me the most is this one:

    js> List.fold_left (&&) true (List.map2 pred a b)

    js> What is the input data were infinite?  Hmmm .. in an eager
    js> language, the usual functional decomposition is useless.

    js> CPS is looking better every day :-)

Another way to handle this is to use a datastructure that's meant to
work in this situation, rather than lists.  (To be honest, I somewhat
dislike the ability to define recursive datastructures in O'Caml for
this reason.)

module Stream =
  struct

    type 'a t = unit -> 'a cell
     and 'a cell = Nil | Cons of 'a * 'a t

    let decons s = s ()

    let cons h t = fun () -> Cons (h, t)

    let rec append a b = fun () ->
      match decons a with
        | Nil -> decons b
        | Cons (h, t) -> Cons (h, append t b)

    let rec map f l = fun () ->
      match decons l with
        | Nil -> Nil
        | Cons (h, t) -> Cons (f h, map f t)

    (* ... etc ... *)

  end

A smarter implementation (I just threw this off the top of my head)
would include remembering already accessed values and the like (lazy
evaluation).  With such a data structure, designed for infinities,
processing infinite values is easier.

The drawback to allowing:

let rec ones = 1 :: ones

and such expressions is that when looking at the definition of, for
example, 'a list and length, one would expect it to be guaranteed that
length terminates.  Since you can't prevent recursive use of
constructors, well, you can no longer guarantee that.

John.
-------------------
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] 11+ messages in thread

* Re: [Caml-list] Breaking out of iterative loops
  2002-04-30 21:38 ` Johan Baltié
@ 2002-05-02  0:57   ` John Max Skaller
  2002-05-02  2:18     ` John Prevost
  0 siblings, 1 reply; 11+ messages in thread
From: John Max Skaller @ 2002-05-02  0:57 UTC (permalink / raw)
  To: Johan Baltié; +Cc: OCaml Mailing list

Johan Baltié wrote:

>
>Think you should look for exception handling.
>I do not use anything that looks like a "continue" and "break" as i generally 
>avoid loop in my code and i do not think there is any.
>
>break:
>try
>  for ... do
>    raise End_Loop
>  done
>with End_Loop ->
>
>
>But please, for my soul sake, avoid such things unless you do really need an 
>exception
>
the particular example that bugs me the most is this one:

List.fold_left (&&) true (List.map2 pred a b)

What is the input data were infinite?
Hmmm .. in an eager language, the usual
functional decomposition is useless.

CPS is looking better every day :-)


-- 
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] 11+ messages in thread

* Re: [Caml-list] Breaking out of iterative loops
  2002-04-30 20:27 Vincent Foley
@ 2002-04-30 21:38 ` Johan Baltié
  2002-05-02  0:57   ` John Max Skaller
  0 siblings, 1 reply; 11+ messages in thread
From: Johan Baltié @ 2002-04-30 21:38 UTC (permalink / raw)
  To: OCaml Mailing list

Le Mardi 30 Avril 2002 22:27, Vincent Foley a écrit :
> What are the equivalents (if any) of C's 'continue' and 'break' in
> O'Caml (respectively, start another iteration and quit the loop without
> further processing)?

Think you should look for exception handling.
I do not use anything that looks like a "continue" and "break" as i generally 
avoid loop in my code and i do not think there is any.

break:
try
  for ... do
    raise End_Loop
  done
with End_Loop ->


continue:
  for ... do
try
    raise Next_Loop
with Next_Loop ->
  ....
  done

But please, for my soul sake, avoid such things unless you do really need an 
exception

-- 
Ciao

Jo

-------------------
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] 11+ messages in thread

* [Caml-list] Breaking out of iterative loops
@ 2002-04-30 20:27 Vincent Foley
  2002-04-30 21:38 ` Johan Baltié
  0 siblings, 1 reply; 11+ messages in thread
From: Vincent Foley @ 2002-04-30 20:27 UTC (permalink / raw)
  To: OCaml Mailing list

What are the equivalents (if any) of C's 'continue' and 'break' in
O'Caml (respectively, start another iteration and quit the loop without
further processing)?

Mes voeux de bonheur les plus sinceres avec des p'tites filles en tutu
avec un sucon,

  Vincent

-- 

Vincent Foley-Bourgon
Email: vinfoley@iquebec.com
Homepage: http://darkhost.mine.nu:81
-------------------
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] 11+ messages in thread

end of thread, other threads:[~2002-05-02 15:40 UTC | newest]

Thread overview: 11+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2002-05-02 13:15 [Caml-list] Breaking out of iterative loops Krishnaswami, Neel
2002-05-02 13:34 ` Markus Mottl
  -- strict thread matches above, loose matches on Subject: below --
2002-04-30 20:27 Vincent Foley
2002-04-30 21:38 ` Johan Baltié
2002-05-02  0:57   ` John Max Skaller
2002-05-02  2:18     ` John Prevost
2002-05-02  8:33       ` Markus Mottl
2002-05-02  9:14         ` Francois Pottier
2002-05-02  9:50           ` Alain Frisch
2002-05-02 14:35         ` Alessandro Baretta
2002-05-02 15:40         ` John Max Skaller

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