caml-list - the Caml user's mailing list
 help / color / mirror / Atom feed
* environment idiom
@ 2004-12-09  2:07 HENRIKSON, JEFFREY
  2004-12-09  4:47 ` [Caml-list] " Jacques Garrigue
                   ` (2 more replies)
  0 siblings, 3 replies; 57+ messages in thread
From: HENRIKSON, JEFFREY @ 2004-12-09  2:07 UTC (permalink / raw)
  To: caml-list

caml-list,

I am interested in the idiom of passing a number of parameters by some
kind of "environment" variable.  Think of a web server with hundredes of
functions for processing markup and other things, only 3 of which need
to detect the browser.  It's bad maintainability to explicitly pass
browserid through hundreds of functions which don't use it.  And of
course, we must separate the state of the calling threads so as to not
cheat with global variables or some such thing.

There seem to be two main candidates for such an idiom in Ocaml, objects
and polymorphic variants.  The object way, roughly:

let bar env s =
  env#pear ^ s;;

let foo env s =
  let x = env#apple in
  let y = env#banana in
  bar env (x^y^s);;

As long as we never name the classes the compiler keeps track of which
environment methods the foo call chain has by creating ad hoc classes:

#  val bar : < pear : string; .. > -> string -> string = <fun>
#  val foo :
  < apple : string; banana : string; pear : string; .. > -> string ->
string =
  <fun>

And the polymorphic variant way, roughly:


let h = Hashtbl.create 10;;

Hashtbl.add h `Banana (`Banana "b");;
Hashtbl.add h `Apple (`Apple "a");;
Hashtbl.add h `Pear (`Pear "p");;


let get_apple h =
  try match Hashtbl.find h `Apple with
      `Apple n -> n
    | _ -> failwith "no apple config key"
  with Not_found -> failwith "no apple config key";;

let get_banana h =
  try match Hashtbl.find h `Banana with
      `Banana n -> n
    | _ -> failwith "no banana config key"
  with Not_found -> failwith "no banana config key";;

let get_pear h =
  try match Hashtbl.find h `Pear with
      `Pear n -> n
    | _ -> failwith "no pear config key"
  with Not_found -> failwith "no pear config key";;


let bar env s =
    (get_pear env) ^ s;;
#   val bar : ([> `Pear ], [> `Pear of string ]) Hashtbl.t -> string ->
string =  <fun>

let foo env s =
  let x = get_apple env in
  let y = get_banana env in
  bar env (x^y^s);;
#       val foo :
  ([> `Apple | `Banana | `Pear ],
   [> `Apple of string | `Banana of string | `Pear of string ])
  Hashtbl.t -> string -> string = <fun>

foo h "5";;
# - : string = "pab5"



Each of these idioms has its own advantage:

In the object way the compiler verifies that the functions are passed
objects which contain all their needed configuration keys.  But if I
understand correctly, we must at some point construct an environment
object which has _all_ the keys, even if we don't know them yet.  We can
add by mutation, but we cannot simply leave them out and add them as we
get to functions which need them.  This is because while we can write


object
  method apple = "a"
  method banana = "b"
end;;
- : < apple : string; banana : string > = <obj>


we cannot inherit anonymously:


let add_pear env =
  object
    inherit env
    method pear = "p"
  end;;

#         Characters 40-43:
      inherit env
              ^^^
Unbound class
env


In the pv way the construction can be made incremental.  Ie, if we
changed the hashtable to a list or immutable queue, we could add keys as
we go.  But at least as I have it set up, the variants are not placing
restrictions on the existence of keys in the environment, other than
saying "we can understand at least this many keys," which is of course
meaningless.  Is there a way to turn the typing around to say "we
require at least these keys"?

In general, what are the typing and run-time limitations around each
way?

Regards,


Jeff Henrikson


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

* Re: [Caml-list] environment idiom
  2004-12-09  2:07 environment idiom HENRIKSON, JEFFREY
@ 2004-12-09  4:47 ` Jacques Garrigue
  2004-12-09  6:02   ` Michael Walter
  2004-12-09  9:09 ` Richard Jones
  2004-12-10 10:52 ` [Caml-list] " Andrej Bauer
  2 siblings, 1 reply; 57+ messages in thread
From: Jacques Garrigue @ 2004-12-09  4:47 UTC (permalink / raw)
  To: JEFHEN; +Cc: caml-list

From: "HENRIKSON, JEFFREY" <JEFHEN@safeco.com>

> I am interested in the idiom of passing a number of parameters by some
> kind of "environment" variable.  Think of a web server with hundredes of
> functions for processing markup and other things, only 3 of which need
> to detect the browser.  It's bad maintainability to explicitly pass
> browserid through hundreds of functions which don't use it.  And of
> course, we must separate the state of the calling threads so as to not
> cheat with global variables or some such thing.
> 
> There seem to be two main candidates for such an idiom in Ocaml, objects
> and polymorphic variants.

[...]

> And the polymorphic variant way, roughly:
> let h = Hashtbl.create 10;;
> 
> Hashtbl.add h `Banana (`Banana "b");;
> Hashtbl.add h `Apple (`Apple "a");;
> Hashtbl.add h `Pear (`Pear "p");;

This seems a bit of an overkill: I would rather write directly
  let env = [`Banana "b"; `Apple "a"; `Pear "p"]
Which would give you more or less the same typing.

> Each of these idioms has its own advantage:
> 
> In the object way the compiler verifies that the functions are passed
> objects which contain all their needed configuration keys.  But if I
> understand correctly, we must at some point construct an environment
> object which has _all_ the keys, even if we don't know them yet.  We can
> add by mutation, but we cannot simply leave them out and add them as we
> get to functions which need them.

A common way to do it would be to have a class defining defaults,
and inherit and override it in your environment object.
I'm not sure of how you intend to use your environment.
But you're right that it is difficult to make changes incremental,
since ocaml have no incrementally extendable records.

Note also that while you cannot extend an object, you can extend a
class, and you can use local modules to define classes locally.
Yet, you cannot pass classes (or modules) to functions, so this does not
solve your problem.

> In the pv way the construction can be made incremental.  Ie, if we
> changed the hashtable to a list or immutable queue, we could add keys as
> we go.  But at least as I have it set up, the variants are not placing
> restrictions on the existence of keys in the environment, other than
> saying "we can understand at least this many keys," which is of course
> meaningless.  Is there a way to turn the typing around to say "we
> require at least these keys"?

No: any variant type is a subtype of a variant type containing more
keys, so you would be able to cheat anyway.

> In general, what are the typing and run-time limitations around each
> way?

I think you've described them correctly: objects offer exact typing,
but cannot be extended incrementally, and lists of porlymorphic
variants enforce typing but do not guarantee what keys are defined.

In terms of efficiency, objects generate more code, but performance should
be comparable.

Note that ocaml contains a third way to do that, which in some cases is
more natural. You can use labelled arguments. This means that you must
pass all the arguments explicitly, but you are no longer restricted by
their order. Some arguments may be optional.
Depending on your goal, this may be the safest way to pass parameters.

let bar ~pear s = pear^s
let foo ~apple ~banana ~pear s = bar ~pear (apple^banana^s)

You may look at code in lablgtk2 for clever ways to handle long lists
of parameters this way. (But this doesn't fit your web server
example.)

A last way, which could work very well with your web server example,
is to use records in place of objects, and update them using
with. Then you can use clever typing.

module Option : sig
  type (+'a,+'b) t
  type abs = [`abs|`pre]
  type pre = [`pre]
  val none : ('a, abs) t
  val some : 'a -> ('a, 'b) t
  val get : ('a, pre) t -> 'a
end = struct
  type ('a,'b) t = 'a option
  type abs = [`abs|`pre]
  type pre = [`pre]
  let none = None
  let some x = Some x
  let get = function Some x -> x | None -> assert false
end

open Option

type ('a,'b,'c) env =
  {apple: (string, 'b) t; banana: (string, 'a) t; pear: (string, 'c) t}

# let empty = {apple=none; banana=none; pear=none}
val empty : (abs, abs, abs) env

# let e1 = {empty with pear=some "Williams"}
val e1 : (abs, abs, 'a) env
# let e2 = {e1 with apple=some "Golden"; banana=some "Plantin"}
val e2 : ('a, 'b, 'c) env

# let bar env s =
    get env.pear ^ s
val bar : ('a, 'b, pre) env -> string -> string
# let foo env s =
   bar env (get env.apple ^ get env.banana ^ s)
val foo : (pre, pre, pre) env -> string -> string

# foo e2 "!";;
- : string = "WilliamsGoldenPlantin!"

# foo e1;;
This expression has type (Option.abs, Option.abs, 'a) env
but is here used with type (Option.pre, Option.pre, Option.pre) env
Type Option.abs = [ `abs | `pre ] is not compatible with type
  Option.pre = [ `pre ] 

Polymorphic variants are not essential here.
They just allow one to forget about some fields of the environment
without physically modifying it. For instance:

# let forget_pear env = (env :> (_,_,abs) env);;
val forget_pear : ('a, 'b, [< abs ]) env -> ('a, 'b, abs) env

If you don't need this kind of operation, you could choose a simpler
interface, which would be enough in most cases.
module Option : sig
  type (+'a,+'b) t
  type abs
  type pre
  val none : ('a, abs) t
  val some : 'a -> ('a, 'b) t
  val get : ('a, pre) t -> 'a
end

By the way, I had thought of a clever way to obtain nicer types:
type 'u env =
  {banana: (string, 'a) t; apple: (string, 'b) t; pear: (string, 'c) t}
  constraint 'u = <banana:'a; apple:'b; pear:'c>
But after fiddling with it I discovered a serious bug in the type
checker. Please do not use constraints on type variables that do not
appear in the type itself until this is solved. Sorry for the
inconvenience.

Jacques Garrigue


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

* Re: [Caml-list] environment idiom
  2004-12-09  4:47 ` [Caml-list] " Jacques Garrigue
@ 2004-12-09  6:02   ` Michael Walter
  2004-12-09 11:28     ` Jacques Garrigue
  2004-12-09 20:02     ` pad
  0 siblings, 2 replies; 57+ messages in thread
From: Michael Walter @ 2004-12-09  6:02 UTC (permalink / raw)
  To: Jacques Garrigue; +Cc: JEFHEN, caml-list

Is there such thing as implicit parameters in O'caml, basically
variables with dynamic extent. Could be (partially?) statically
checked, too, no?

Cheers,
Michael


On Thu, 09 Dec 2004 13:47:35 +0900 (JST), Jacques Garrigue
<garrigue@math.nagoya-u.ac.jp> wrote:
> From: "HENRIKSON, JEFFREY" <JEFHEN@safeco.com>
> 
> 
> 
> > I am interested in the idiom of passing a number of parameters by some
> > kind of "environment" variable.  Think of a web server with hundredes of
> > functions for processing markup and other things, only 3 of which need
> > to detect the browser.  It's bad maintainability to explicitly pass
> > browserid through hundreds of functions which don't use it.  And of
> > course, we must separate the state of the calling threads so as to not
> > cheat with global variables or some such thing.
> >
> > There seem to be two main candidates for such an idiom in Ocaml, objects
> > and polymorphic variants.
> 
> [...]
> 
> > And the polymorphic variant way, roughly:
> > let h = Hashtbl.create 10;;
> >
> > Hashtbl.add h `Banana (`Banana "b");;
> > Hashtbl.add h `Apple (`Apple "a");;
> > Hashtbl.add h `Pear (`Pear "p");;
> 
> This seems a bit of an overkill: I would rather write directly
>   let env = [`Banana "b"; `Apple "a"; `Pear "p"]
> Which would give you more or less the same typing.
> 
> > Each of these idioms has its own advantage:
> >
> > In the object way the compiler verifies that the functions are passed
> > objects which contain all their needed configuration keys.  But if I
> > understand correctly, we must at some point construct an environment
> > object which has _all_ the keys, even if we don't know them yet.  We can
> > add by mutation, but we cannot simply leave them out and add them as we
> > get to functions which need them.
> 
> A common way to do it would be to have a class defining defaults,
> and inherit and override it in your environment object.
> I'm not sure of how you intend to use your environment.
> But you're right that it is difficult to make changes incremental,
> since ocaml have no incrementally extendable records.
> 
> Note also that while you cannot extend an object, you can extend a
> class, and you can use local modules to define classes locally.
> Yet, you cannot pass classes (or modules) to functions, so this does not
> solve your problem.
> 
> > In the pv way the construction can be made incremental.  Ie, if we
> > changed the hashtable to a list or immutable queue, we could add keys as
> > we go.  But at least as I have it set up, the variants are not placing
> > restrictions on the existence of keys in the environment, other than
> > saying "we can understand at least this many keys," which is of course
> > meaningless.  Is there a way to turn the typing around to say "we
> > require at least these keys"?
> 
> No: any variant type is a subtype of a variant type containing more
> keys, so you would be able to cheat anyway.
> 
> > In general, what are the typing and run-time limitations around each
> > way?
> 
> I think you've described them correctly: objects offer exact typing,
> but cannot be extended incrementally, and lists of porlymorphic
> variants enforce typing but do not guarantee what keys are defined.
> 
> In terms of efficiency, objects generate more code, but performance should
> be comparable.
> 
> Note that ocaml contains a third way to do that, which in some cases is
> more natural. You can use labelled arguments. This means that you must
> pass all the arguments explicitly, but you are no longer restricted by
> their order. Some arguments may be optional.
> Depending on your goal, this may be the safest way to pass parameters.
> 
> let bar ~pear s = pear^s
> let foo ~apple ~banana ~pear s = bar ~pear (apple^banana^s)
> 
> You may look at code in lablgtk2 for clever ways to handle long lists
> of parameters this way. (But this doesn't fit your web server
> example.)
> 
> A last way, which could work very well with your web server example,
> is to use records in place of objects, and update them using
> with. Then you can use clever typing.
> 
> module Option : sig
>   type (+'a,+'b) t
>   type abs = [`abs|`pre]
>   type pre = [`pre]
>   val none : ('a, abs) t
>   val some : 'a -> ('a, 'b) t
>   val get : ('a, pre) t -> 'a
> end = struct
>   type ('a,'b) t = 'a option
>   type abs = [`abs|`pre]
>   type pre = [`pre]
>   let none = None
>   let some x = Some x
>   let get = function Some x -> x | None -> assert false
> end
> 
> open Option
> 
> type ('a,'b,'c) env =
>   {apple: (string, 'b) t; banana: (string, 'a) t; pear: (string, 'c) t}
> 
> # let empty = {apple=none; banana=none; pear=none}
> val empty : (abs, abs, abs) env
> 
> # let e1 = {empty with pear=some "Williams"}
> val e1 : (abs, abs, 'a) env
> # let e2 = {e1 with apple=some "Golden"; banana=some "Plantin"}
> val e2 : ('a, 'b, 'c) env
> 
> # let bar env s =
>     get env.pear ^ s
> val bar : ('a, 'b, pre) env -> string -> string
> # let foo env s =
>    bar env (get env.apple ^ get env.banana ^ s)
> val foo : (pre, pre, pre) env -> string -> string
> 
> # foo e2 "!";;
> - : string = "WilliamsGoldenPlantin!"
> 
> # foo e1;;
> This expression has type (Option.abs, Option.abs, 'a) env
> but is here used with type (Option.pre, Option.pre, Option.pre) env
> Type Option.abs = [ `abs | `pre ] is not compatible with type
>   Option.pre = [ `pre ]
> 
> Polymorphic variants are not essential here.
> They just allow one to forget about some fields of the environment
> without physically modifying it. For instance:
> 
> # let forget_pear env = (env :> (_,_,abs) env);;
> val forget_pear : ('a, 'b, [< abs ]) env -> ('a, 'b, abs) env
> 
> If you don't need this kind of operation, you could choose a simpler
> interface, which would be enough in most cases.
> module Option : sig
>   type (+'a,+'b) t
>   type abs
>   type pre
>   val none : ('a, abs) t
>   val some : 'a -> ('a, 'b) t
>   val get : ('a, pre) t -> 'a
> end
> 
> By the way, I had thought of a clever way to obtain nicer types:
> type 'u env =
>   {banana: (string, 'a) t; apple: (string, 'b) t; pear: (string, 'c) t}
>   constraint 'u = <banana:'a; apple:'b; pear:'c>
> But after fiddling with it I discovered a serious bug in the type
> checker. Please do not use constraints on type variables that do not
> appear in the type itself until this is solved. Sorry for the
> inconvenience.
> 
> Jacques Garrigue
> 
> 
> 
> _______________________________________________
> Caml-list mailing list. Subscription management:
> http://yquem.inria.fr/cgi-bin/mailman/listinfo/caml-list
> Archives: http://caml.inria.fr
> Beginner's list: http://groups.yahoo.com/group/ocaml_beginners
> Bug reports: http://caml.inria.fr/bin/caml-bugs
>


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

* Re: environment idiom
  2004-12-09  2:07 environment idiom HENRIKSON, JEFFREY
  2004-12-09  4:47 ` [Caml-list] " Jacques Garrigue
@ 2004-12-09  9:09 ` Richard Jones
  2004-12-09 13:12   ` [Caml-list] " Ville-Pertti Keinonen
  2004-12-10 10:52 ` [Caml-list] " Andrej Bauer
  2 siblings, 1 reply; 57+ messages in thread
From: Richard Jones @ 2004-12-09  9:09 UTC (permalink / raw)
  Cc: caml-list

[-- Attachment #1: Type: text/plain, Size: 548 bytes --]

Just an observation here:

The object method seems to be compile-time safe, whereas the hash
method seems to require run-time checks which could fail.  Am I right
in thinking this?  If so, the compile-time safe version is infinitely
preferable.

Rich.

-- 
Richard Jones.  http://www.annexia.org/  http://www.j-london.com/
>>>   http://www.team-notepad.com/ - collaboration tools for teams   <<<
Merjis Ltd. http://www.merjis.com/ - improving website return on investment
http://execellence.co.uk/ - Interim and executive recruitment

[-- Attachment #2: Digital signature --]
[-- Type: application/pgp-signature, Size: 189 bytes --]

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

* Re: [Caml-list] environment idiom
  2004-12-09  6:02   ` Michael Walter
@ 2004-12-09 11:28     ` Jacques Garrigue
  2004-12-09 20:02     ` pad
  1 sibling, 0 replies; 57+ messages in thread
From: Jacques Garrigue @ 2004-12-09 11:28 UTC (permalink / raw)
  To: michael.walter; +Cc: caml-list

From: Michael Walter <michael.walter@gmail.com>

> Is there such thing as implicit parameters in O'caml, basically
> variables with dynamic extent. Could be (partially?) statically
> checked, too, no?

There's no such thing (at least in statically checked form.)
The technic I gave in my previous mail is the closest you can do with
full static check.
There are various encodings for dynamically scoped variables, but this
is another story.

   Jacques Garrigue


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

* Re: [Caml-list] Re: environment idiom
  2004-12-09  9:09 ` Richard Jones
@ 2004-12-09 13:12   ` Ville-Pertti Keinonen
  2004-12-10 11:59     ` Richard Jones
  0 siblings, 1 reply; 57+ messages in thread
From: Ville-Pertti Keinonen @ 2004-12-09 13:12 UTC (permalink / raw)
  To: Richard Jones; +Cc: caml-list

On Thu, 2004-12-09 at 09:09 +0000, Richard Jones wrote:
> Just an observation here:
> 
> The object method seems to be compile-time safe, whereas the hash
> method seems to require run-time checks which could fail.  Am I right
> in thinking this?  If so, the compile-time safe version is infinitely

What run-time checks?  OCaml is statically typed, it has no run-time
type checking.  Only things like array bounds are checked at run-time.
The hash method is typed similarly to the following:

# let x = ref `A;;
val x : _[> `A ] ref = {contents = `A}
# x := `B;;
- : unit = ()
# x;;
- : _[> `A | `B ] ref = {contents = `B}

However, when using such things in real programs you must specify the
final type explicitly (e.g. in the .mli file) in order to give a
definite type for the variable in the module (since the above obviously
isn't safe across compilation units).



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

* Re: [Caml-list] environment idiom
  2004-12-09  6:02   ` Michael Walter
  2004-12-09 11:28     ` Jacques Garrigue
@ 2004-12-09 20:02     ` pad
  2004-12-09 23:11       ` Jacques Garrigue
  1 sibling, 1 reply; 57+ messages in thread
From: pad @ 2004-12-09 20:02 UTC (permalink / raw)
  To: Michael Walter; +Cc: Jacques Garrigue, JEFHEN, caml-list

Michael Walter <michael.walter@gmail.com> writes:

> Is there such thing as implicit parameters in O'caml, basically
> variables with dynamic extent. Could be (partially?) statically
> checked, too, no?

The haskell guys have invented implicit parameter cos they dont have
side effect or global variables.
In O'Caml we have those features  so implicit parameter can easily be 
emulated. The rest is more a syntactic sugar question.





> 
> Cheers,
> Michael
> 
> 
> On Thu, 09 Dec 2004 13:47:35 +0900 (JST), Jacques Garrigue
> <garrigue@math.nagoya-u.ac.jp> wrote:
> > From: "HENRIKSON, JEFFREY" <JEFHEN@safeco.com>
> > 
> > 
> > 
> > > I am interested in the idiom of passing a number of parameters by some
> > > kind of "environment" variable.  Think of a web server with hundredes of
> > > functions for processing markup and other things, only 3 of which need
> > > to detect the browser.  It's bad maintainability to explicitly pass
> > > browserid through hundreds of functions which don't use it.  And of
> > > course, we must separate the state of the calling threads so as to not
> > > cheat with global variables or some such thing.
> > >
> > > There seem to be two main candidates for such an idiom in Ocaml, objects
> > > and polymorphic variants.
> > 
> > [...]
> > 
> > > And the polymorphic variant way, roughly:
> > > let h = Hashtbl.create 10;;
> > >
> > > Hashtbl.add h `Banana (`Banana "b");;
> > > Hashtbl.add h `Apple (`Apple "a");;
> > > Hashtbl.add h `Pear (`Pear "p");;
> > 
> > This seems a bit of an overkill: I would rather write directly
> >   let env = [`Banana "b"; `Apple "a"; `Pear "p"]
> > Which would give you more or less the same typing.
> > 
> > > Each of these idioms has its own advantage:
> > >
> > > In the object way the compiler verifies that the functions are passed
> > > objects which contain all their needed configuration keys.  But if I
> > > understand correctly, we must at some point construct an environment
> > > object which has _all_ the keys, even if we don't know them yet.  We can
> > > add by mutation, but we cannot simply leave them out and add them as we
> > > get to functions which need them.
> > 
> > A common way to do it would be to have a class defining defaults,
> > and inherit and override it in your environment object.
> > I'm not sure of how you intend to use your environment.
> > But you're right that it is difficult to make changes incremental,
> > since ocaml have no incrementally extendable records.
> > 
> > Note also that while you cannot extend an object, you can extend a
> > class, and you can use local modules to define classes locally.
> > Yet, you cannot pass classes (or modules) to functions, so this does not
> > solve your problem.
> > 
> > > In the pv way the construction can be made incremental.  Ie, if we
> > > changed the hashtable to a list or immutable queue, we could add keys as
> > > we go.  But at least as I have it set up, the variants are not placing
> > > restrictions on the existence of keys in the environment, other than
> > > saying "we can understand at least this many keys," which is of course
> > > meaningless.  Is there a way to turn the typing around to say "we
> > > require at least these keys"?
> > 
> > No: any variant type is a subtype of a variant type containing more
> > keys, so you would be able to cheat anyway.
> > 
> > > In general, what are the typing and run-time limitations around each
> > > way?
> > 
> > I think you've described them correctly: objects offer exact typing,
> > but cannot be extended incrementally, and lists of porlymorphic
> > variants enforce typing but do not guarantee what keys are defined.
> > 
> > In terms of efficiency, objects generate more code, but performance should
> > be comparable.
> > 
> > Note that ocaml contains a third way to do that, which in some cases is
> > more natural. You can use labelled arguments. This means that you must
> > pass all the arguments explicitly, but you are no longer restricted by
> > their order. Some arguments may be optional.
> > Depending on your goal, this may be the safest way to pass parameters.
> > 
> > let bar ~pear s = pear^s
> > let foo ~apple ~banana ~pear s = bar ~pear (apple^banana^s)
> > 
> > You may look at code in lablgtk2 for clever ways to handle long lists
> > of parameters this way. (But this doesn't fit your web server
> > example.)
> > 
> > A last way, which could work very well with your web server example,
> > is to use records in place of objects, and update them using
> > with. Then you can use clever typing.
> > 
> > module Option : sig
> >   type (+'a,+'b) t
> >   type abs = [`abs|`pre]
> >   type pre = [`pre]
> >   val none : ('a, abs) t
> >   val some : 'a -> ('a, 'b) t
> >   val get : ('a, pre) t -> 'a
> > end = struct
> >   type ('a,'b) t = 'a option
> >   type abs = [`abs|`pre]
> >   type pre = [`pre]
> >   let none = None
> >   let some x = Some x
> >   let get = function Some x -> x | None -> assert false
> > end
> > 
> > open Option
> > 
> > type ('a,'b,'c) env =
> >   {apple: (string, 'b) t; banana: (string, 'a) t; pear: (string, 'c) t}
> > 
> > # let empty = {apple=none; banana=none; pear=none}
> > val empty : (abs, abs, abs) env
> > 
> > # let e1 = {empty with pear=some "Williams"}
> > val e1 : (abs, abs, 'a) env
> > # let e2 = {e1 with apple=some "Golden"; banana=some "Plantin"}
> > val e2 : ('a, 'b, 'c) env
> > 
> > # let bar env s =
> >     get env.pear ^ s
> > val bar : ('a, 'b, pre) env -> string -> string
> > # let foo env s =
> >    bar env (get env.apple ^ get env.banana ^ s)
> > val foo : (pre, pre, pre) env -> string -> string
> > 
> > # foo e2 "!";;
> > - : string = "WilliamsGoldenPlantin!"
> > 
> > # foo e1;;
> > This expression has type (Option.abs, Option.abs, 'a) env
> > but is here used with type (Option.pre, Option.pre, Option.pre) env
> > Type Option.abs = [ `abs | `pre ] is not compatible with type
> >   Option.pre = [ `pre ]
> > 
> > Polymorphic variants are not essential here.
> > They just allow one to forget about some fields of the environment
> > without physically modifying it. For instance:
> > 
> > # let forget_pear env = (env :> (_,_,abs) env);;
> > val forget_pear : ('a, 'b, [< abs ]) env -> ('a, 'b, abs) env
> > 
> > If you don't need this kind of operation, you could choose a simpler
> > interface, which would be enough in most cases.
> > module Option : sig
> >   type (+'a,+'b) t
> >   type abs
> >   type pre
> >   val none : ('a, abs) t
> >   val some : 'a -> ('a, 'b) t
> >   val get : ('a, pre) t -> 'a
> > end
> > 
> > By the way, I had thought of a clever way to obtain nicer types:
> > type 'u env =
> >   {banana: (string, 'a) t; apple: (string, 'b) t; pear: (string, 'c) t}
> >   constraint 'u = <banana:'a; apple:'b; pear:'c>
> > But after fiddling with it I discovered a serious bug in the type
> > checker. Please do not use constraints on type variables that do not
> > appear in the type itself until this is solved. Sorry for the
> > inconvenience.
> > 
> > Jacques Garrigue
> > 
> > 
> > 
> > _______________________________________________
> > Caml-list mailing list. Subscription management:
> > http://yquem.inria.fr/cgi-bin/mailman/listinfo/caml-list
> > Archives: http://caml.inria.fr
> > Beginner's list: http://groups.yahoo.com/group/ocaml_beginners
> > Bug reports: http://caml.inria.fr/bin/caml-bugs
> >
> 
> _______________________________________________
> Caml-list mailing list. Subscription management:
> http://yquem.inria.fr/cgi-bin/mailman/listinfo/caml-list
> Archives: http://caml.inria.fr
> Beginner's list: http://groups.yahoo.com/group/ocaml_beginners
> Bug reports: http://caml.inria.fr/bin/caml-bugs


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

* Re: [Caml-list] environment idiom
  2004-12-09 20:02     ` pad
@ 2004-12-09 23:11       ` Jacques Garrigue
  2004-12-10  2:30         ` skaller
  0 siblings, 1 reply; 57+ messages in thread
From: Jacques Garrigue @ 2004-12-09 23:11 UTC (permalink / raw)
  To: caml-list

From: pad@ryxa.irisa.fr
> Michael Walter <michael.walter@gmail.com> writes:
> 
> > Is there such thing as implicit parameters in O'caml, basically
> > variables with dynamic extent. Could be (partially?) statically
> > checked, too, no?
> 
> The haskell guys have invented implicit parameter cos they dont have
> side effect or global variables.
> In O'Caml we have those features  so implicit parameter can easily be 
> emulated. The rest is more a syntactic sugar question.

Not exactly. Implicit parameters in Haskell also check that all the
needed definitions are available, which global variables don't (with
global variables there is always a default value). IIRC their
semantics is not exactly that of dynamic scope, but more a statical
scope with a special kind of substitution, which is somewhat cleaner.

But you're right that in practice global variables are in general
sufficient to solve this problem, and they are often used in ocaml for
that. They have of course one disadvantage: they are not reentrant.

Jacques Garrigue


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

* Re: [Caml-list] environment idiom
  2004-12-09 23:11       ` Jacques Garrigue
@ 2004-12-10  2:30         ` skaller
  0 siblings, 0 replies; 57+ messages in thread
From: skaller @ 2004-12-10  2:30 UTC (permalink / raw)
  To: Jacques Garrigue; +Cc: caml-list

On Fri, 2004-12-10 at 10:11, Jacques Garrigue wrote:

> But you're right that in practice global variables are in general
> sufficient to solve this problem, and they are often used in ocaml for
> that. They have of course one disadvantage: they are not reentrant.

Yes but global/local is a relative thing in sane languages
like Ocaml which support nested scopes. One might even
say it is one of *the* fundamental software engineering
design problems, to try to make variables as local
as possible without pointless explicit passing.

Since software changes, this may not be the theoretically
optimal position.

A simple example is an array search in C where the loop variable
needs to be external to the loop to actually return the desired
result. For Ocaml I find often, I have repeated code handling
match cases which share variables and that when I lifted the 
common code into a subroutine, I often want to make it
slightly more global than the scope containing the match,
and in doing so I have to now explicitly pass extra variables.

I often don't actually know what they are -- the compiler
reports unbound variables and I add paramaters until it
compiles, thus discovering something previously hidden.

Occasionally this procedure fails .. in one case I had
used the common Ocaml trick of hiding a more global variable
with a more local one .. and in lifting the code outside
the scope of the local one but still within the scope
of the more global one, I inadvertantly changed the
semantics of the code without breaking it, as my lifting
procedure required.. that bug took hours to find.

The lack of re-entrany Jacques mentions is thus not
limited to absolutely global variables as in C statics.
It not only applies to *all* variables in functional
languages .. it is particularly applicable in Ocaml
which is not referentially transparent.

One final point of some interest is that even 
'absolutely' global variables may not be.
In Pascal, globals are actually just elements
of the deepest stack frame. In Posix C,
some variables can be designated thread local,
such as 'errno'. In Felix, all globals may be
microthread local, since they're collected into
a single struct which is passed explicitly
to all functions or stored in a C static,
depending on a compilation time switch.
I guess in Haskell with monads, global
has yet another meaning, as indeed it does
in with classes in OO languages, which provide explicit 
object construction.

I would argue that data and code are categorical
duals concepts, and localistion is *the* principal
engineering issue of software design. Indeed,
it is central to lambda calculus where 
lambda abstraction is the fundamental operation,
and is nothing more than a way of moving between
a local and global variable -- here the relativity
of the local/global distinction in manifest directly
as a fundamental principle.

Indeed one may say 'languages' lacking abstraction,
such as C, aren't even candidates for consideration
as 'programming' languages -- because it is impossible
to exercise the very design judgements a programmer
must make about locality.

Interestingly, I think Object Orientation -- which as
a complete paradigm I despise -- has made one of the
most important steps forward in language design.
This is because it provides a second construction
for expressing localisation which expands considerably
the programmers choices compared to the localisation
available merely from lambda abstraction (ie. function
closures/stack frames). This is because it allows
one to localise *code* with groups of data, whereas
closures allow one to localise data within a code
structure -- so given the duality of code and
data this capability seems somehow fundamental.

The fact that in Ocaml these two dual constructions
are not syntactically symmetric is an indication
of how poorly this duality is understood.
Compared to functions/lexical scoping classes
in Ocaml seem too 'heavy' -- I think I mean
that the simplicity of changing the the locality
of variables with functions is not present with
classes .. but I don't understand how locality
could be better represented: Ocaml inheritance
is somehow just tricky sugar instead of being
fundamental, as the duality principle says
it should be.

BTW: I think it is a fault to emphasise entirely the
typing theory, which somehow seems more advanced
than the theory of that which it is typing!

-- 
John Skaller, mailto:skaller@users.sf.net
voice: 061-2-9660-0850, 
snail: PO BOX 401 Glebe NSW 2037 Australia
Checkout the Felix programming language http://felix.sf.net




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

* Re: [Caml-list] environment idiom
  2004-12-09  2:07 environment idiom HENRIKSON, JEFFREY
  2004-12-09  4:47 ` [Caml-list] " Jacques Garrigue
  2004-12-09  9:09 ` Richard Jones
@ 2004-12-10 10:52 ` Andrej Bauer
  2004-12-10 12:13   ` Richard Jones
  2004-12-11  2:30   ` skaller
  2 siblings, 2 replies; 57+ messages in thread
From: Andrej Bauer @ 2004-12-10 10:52 UTC (permalink / raw)
  To: caml-list; +Cc: HENRIKSON, JEFFREY

HENRIKSON, JEFFREY wrote:
> 
> I am interested in the idiom of passing a number of parameters by some
> kind of "environment" variable.  Think of a web server with hundredes of
> functions for processing markup and other things, only 3 of which need
> to detect the browser.  It's bad maintainability to explicitly pass
> browserid through hundreds of functions which don't use it.

I have had some experience with precisely this sort of task. I expected,
as you do, that explicit passing of arguments would be bad. So I came up
with a solution that is a bit like your lists of polymorphic variants.
It worked out ok, but was a bit hairy.

However, I was wrong. Later I also implemented another web application
in which I explicitly passed around arguments (I used labels because so
many arguments were strings that it was too easy to mix them up).
Contrary to my expectations, the code was neater and cleaner, not to
mention that it was type-checked at compile time.

All in all, I want to convey my experience: in sane programming
languages it is ok to pass around arguments explicitly, even if it looks
like there will be a lot of uncessary passing. In fact, this is an
illusion. The language  forces you to organize your code neatly and you
will end up passing just the right things to just the right functions.

A good compromise turned out to be the following. I used the ocamlnet
library which has the "cgi" object that encapsulates everything that
needs to be known about the HTTP/CGI request. Passing this object around
when needed, rather than passing little pieces of it (such as browser
id), turned out to be the right way. To be honest, you'll never pass
around "Bananas" and "Apples" but actual info that came from the
HTTP/CGI request. All the info is already known at the beginning, it is
neatly wrapped up in the cgi object (if you use ocamlnet), and you will
never wish to add anything to it. So you can forget about "extending
objects/records incrementally" because you don't need that (try to come
up with a realistic example). If you do wish to pass around additional
arguments, then you just pass them explicitly, and leave alone the
object that encodes the request you're handling.

Perhaps one piece of information that you want to pass around, and is
not stored in the object describing the cgi request, is database info.
You want to know what database you're connected to. Since my application
is not multi-threaded, I cheated and used a global variable for that.
You may want to pass around database info.

In my experience, you should always pass precisely the arguments a given
function needs, and no others. If you think "I will always pass the cgi
and database arguments, because I do not know who will need them, and my
code will achieve grandiose uniformity" you are likely to make a
mistake. You _should_ know who needs the cgi and database info in the
first place, and so should the compiler. So be as strict as possible--it
pays off in smaller and more managable code.

I tried it. It works.

Best regards,

Andrej


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

* Re: [Caml-list] Re: environment idiom
  2004-12-09 13:12   ` [Caml-list] " Ville-Pertti Keinonen
@ 2004-12-10 11:59     ` Richard Jones
  0 siblings, 0 replies; 57+ messages in thread
From: Richard Jones @ 2004-12-10 11:59 UTC (permalink / raw)
  Cc: caml-list

[-- Attachment #1: Type: text/plain, Size: 1078 bytes --]

On Thu, Dec 09, 2004 at 03:12:25PM +0200, Ville-Pertti Keinonen wrote:
> On Thu, 2004-12-09 at 09:09 +0000, Richard Jones wrote:
> > Just an observation here:
> > 
> > The object method seems to be compile-time safe, whereas the hash
> > method seems to require run-time checks which could fail.  Am I right
> > in thinking this?  If so, the compile-time safe version is infinitely
> 
> What run-time checks?  OCaml is statically typed, it has no run-time
> type checking.  Only things like array bounds are checked at run-time.
> The hash method is typed similarly to the following:
[...]

I was talking about the use of the Hashtbl.  Hashtbl.find can throw a
Not_found error at runtime if the environment happens not to contain
the required data.  This is a sort of runtime check.

Rich.

-- 
Richard Jones.  http://www.annexia.org/  http://www.j-london.com/
>>>   http://www.team-notepad.com/ - collaboration tools for teams   <<<
Merjis Ltd. http://www.merjis.com/ - improving website return on investment
http://winwinsales.co.uk/ - CRM consultancy

[-- Attachment #2: Digital signature --]
[-- Type: application/pgp-signature, Size: 189 bytes --]

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

* Re: [Caml-list] environment idiom
  2004-12-10 10:52 ` [Caml-list] " Andrej Bauer
@ 2004-12-10 12:13   ` Richard Jones
  2004-12-10 23:35     ` Jacques Garrigue
  2004-12-11  2:30   ` skaller
  1 sibling, 1 reply; 57+ messages in thread
From: Richard Jones @ 2004-12-10 12:13 UTC (permalink / raw)
  Cc: caml-list, HENRIKSON, JEFFREY

[-- Attachment #1: Type: text/plain, Size: 2464 bytes --]

The specific data that Jeff wants to pass around are:

cgi    - The CGI environment
r      - The Apache request_rec (in fact, cgi#request == request,
         but sometimes it's slightly more convenient to have it as
         a separate parameter)
dbh    - The database handle
hostid - The host ID (COCANWIKI supports multiple virtual hosts)
host   - The "host object" which contains other host-related info
user   - The "user object" which contains info on the logged-in user

In theory one can derive all of the above from just cgi and dbh, but
it's very inefficient to do this because it would require making
database requests.  For practical and efficiency reasons COCANWIKI
derives the hostid, host and user with just 2 database queries at the
beginning of every HTTP request.

COCANWIKI is fairly modular.  For instance it has a library function
to handle the parsing of the Wiki markup, prototyped (currently) as:

  Wikilib.xhtml_of_content : Dbi.connection -> int (*hostid*) ->
    string (*markup*) -> string (*XHTML*)

The reason that this function needs a database handle and hostid is
because parsing Wiki markup is sensitive to the content of the
database.  If someone writes [[Page]] we need to write different
things depending on whether there is a page in the database called
"Page".

Jeff wants to extend xhtml_of_content in a way that also requires
browser sniffing (ie. fetching the User-Agent header from the Apache
request_rec object).  So we need another parameter.  But
xhtml_of_content is far from being a monolithic function at the
moment.  It is, in fact, divided up into many many smaller functions
which handle different parts of the parsing, and for various (wrong)
reasons those are written as separate, not nested functions.

The same problem of needing to pass around chains of extra
"environment" arguments occurs all over in these libraries.

Personally I really like Jeff's "anonymous object" trick, because the
compiler works out for you which "environment" bits are needed by the
library function, and you can just make the right object on the fly
when calling the function.

Rich.

-- 
Richard Jones.  http://www.annexia.org/  http://www.j-london.com/
>>>   http://www.team-notepad.com/ - collaboration tools for teams   <<<
Merjis Ltd. http://www.merjis.com/ - improving website return on investment
http://subjectlink.com/ - Lesson plans and source material for teachers

[-- Attachment #2: Digital signature --]
[-- Type: application/pgp-signature, Size: 189 bytes --]

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

* Re: [Caml-list] environment idiom
  2004-12-10 12:13   ` Richard Jones
@ 2004-12-10 23:35     ` Jacques Garrigue
  0 siblings, 0 replies; 57+ messages in thread
From: Jacques Garrigue @ 2004-12-10 23:35 UTC (permalink / raw)
  To: rich; +Cc: caml-list, JEFHEN

From: Richard Jones <rich@annexia.org>

> The specific data that Jeff wants to pass around are:
> 
> cgi    - The CGI environment
> r      - The Apache request_rec (in fact, cgi#request == request,
>          but sometimes it's slightly more convenient to have it as
>          a separate parameter)
> dbh    - The database handle
> hostid - The host ID (COCANWIKI supports multiple virtual hosts)
> host   - The "host object" which contains other host-related info
> user   - The "user object" which contains info on the logged-in user
> 
> In theory one can derive all of the above from just cgi and dbh, but
> it's very inefficient to do this because it would require making
> database requests.  For practical and efficiency reasons COCANWIKI
> derives the hostid, host and user with just 2 database queries at the
> beginning of every HTTP request.

But you could also make an object with all the methods, and caching
the information it retrieves from the database. This way you have no
efficiency problem.
Andrej's point was that it is generally enough to collect all common
information in one object, and you have not so much to move around
after that. I think this is reasonable.
If this is not the case, then it may mean that you really need to add
information dynamically to your environment. In that case an approach
like the one I suggested with records might provide more flexibility.

Jacques Garrigue


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

* Re: [Caml-list] environment idiom
  2004-12-10 10:52 ` [Caml-list] " Andrej Bauer
  2004-12-10 12:13   ` Richard Jones
@ 2004-12-11  2:30   ` skaller
  2004-12-11 14:31     ` Andrej Bauer
  1 sibling, 1 reply; 57+ messages in thread
From: skaller @ 2004-12-11  2:30 UTC (permalink / raw)
  To: Andrej Bauer; +Cc: caml-list, HENRIKSON, JEFFREY

On Fri, 2004-12-10 at 21:52, Andrej Bauer wrote:

> All in all, I want to convey my experience: in sane programming
> languages it is ok to pass around arguments explicitly, even if it looks
> like there will be a lot of uncessary passing. In fact, this is an
> illusion. The language  forces you to organize your code neatly and you
> will end up passing just the right things to just the right functions.

IMHO the issue is not whether to pass arguments explicitly,
there is clearly no alternative. The question is how
to organise them.

For example you can use several actual arguments, but
at some point there are too many for sanity and
you need to, for example, pass a smaller number
of records.

However this provides no abstraction.

> Perhaps one piece of information that you want to pass around, and is
> not stored in the object describing the cgi request, is database info.
> You want to know what database you're connected to. Since my application
> is not multi-threaded, I cheated and used a global variable for that.

Hah -- at least you're admitting you cheated -- LOL!
So how would you fix this?

> In my experience, you should always pass precisely the arguments a given
> function needs, and no others. 

IMHO you are almost right but not quite. The reason is
that code gets changed.

If you pass exactly the arguments needed, your calls
would be very long winded and even a minor change
in implementation details or code structure would
propagate to every caller, direct or indirect,
of that function.

So that isn't even a marginally viable option
in an unstable code base, and in a stable one
information hiding serves no purpose.

Instead of 'precisely', change the requirement
to 'roughly'. What does that mean? It means you need
to factor your argument sets so you pass precisely
the argument classes needed by each function,
even if the function doesn't need all the members
of each set.

Now if you make a detail change to the code,
you have a *buffer* of 'a few extra arguments
you might or might not need when you change the code'
which will dampen the propagation shock wave caused
by a small reorganisation.

The 'classic' example of this affecting a massive
number of programs and programmers is the
const-propagation phenomena in C/C++ when you take
a program not using 'const' typing, and try
to adapt it to provide the extra type safety
'const' makes available.

Doing this was made mandatory by the ISO C committee,
since they decided that some library functions
should be const exact -- in particular return
const pointers where previously only non-const
ones were returned.

Modularity, then, provides some protection
against this. 'Correct' structure is not
something you can determine for an unstable
code base. If you could, that would be an admission
the requirements were stable. (In that case
there is no point refactoring the code to make
it prettier.. unless you are just researching
or intend to publish it ..)

I'll add my data point: in the Felix compiler
I used to pass individual arguments around.
However the lookup in particular consists
of a large number of mutually recursive
functions all with slightly different
needs, which are the sum of both what they
need, but also any function they call .. 
and worse, they're combined with 'let rec'
which is basically not expressive enough to
reflect the true call graph (but the alternatives
such as open recursion have other problems
like adding to the number of parameters ..)

I did three things to try to fix this. 
(1) I grouped some of the data into a record
(2) I forward defined a couple of functions at
    the expense of passing extra arguments.
(3) I simplified the requirements in one case,
   and totally dropped a whole section of
   functionality

The current situation is still FAR from satisfactory however.
most of the function require about 10 arguments -- still
too many. The *problem* is that i AM calling the functions
with 'exactly the required number of arguments* and it
makes changing the code very hard.

-- 
John Skaller, mailto:skaller@users.sf.net
voice: 061-2-9660-0850, 
snail: PO BOX 401 Glebe NSW 2037 Australia
Checkout the Felix programming language http://felix.sf.net




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

* Re: [Caml-list] environment idiom
  2004-12-11  2:30   ` skaller
@ 2004-12-11 14:31     ` Andrej Bauer
  2004-12-11 18:13       ` Markus Mottl
  2004-12-11 23:29       ` skaller
  0 siblings, 2 replies; 57+ messages in thread
From: Andrej Bauer @ 2004-12-11 14:31 UTC (permalink / raw)
  To: caml-list; +Cc: skaller

It seems that John Skaller and I have different experiences, which is to
be expected (unless compilers are like web applications, which I doubt).

Clearly, as John and others pointed out, we can usually predict that
certain sets of related arguments will be needed frequently, so it makes
sense to make an exception to the "pass exactly what is needed" rule and
bundle such sets together (as objects/records describing cgi request,
host info, database connection, user-session etc). To repeat myself:
this is what I did in my second attempt, and the results were better
than the first attempt, when I stuck everything in a lookup table.

John claims things get complicated in my proposed solution when code is
unstable and requires lots of changes. He offers a C/C++ example of the
const pointers. I am not convinced that ocaml and C/C++ are comparable
in this respect. I habitually abuse the ocaml compiler to tell me
precisely what needs to be changed in the following way: I change a type
or value definition (say, change the arguments to a function) and keep
running the compiler until it reports errors, fixing them as they come
up. Had I used conglomerate lookup tables instead of arguments, or any
other form of argument passing that the compiler cannot analyze, the
compiler would be of little help. You would just postpone the problem to
runtime.

But don't get me wrong. I definitely agree with John that having 10
arguments to a functions sounds like too many, and something needs to be
done in such cases. It's just that in my web application (and I suspect
in most) I don't have 10 arguments all over the code, but more like 3 or
4, which is ok. Certainly different types of programs require different
solutions.

Best regards,

Andrej


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

* Re: [Caml-list] environment idiom
  2004-12-11 14:31     ` Andrej Bauer
@ 2004-12-11 18:13       ` Markus Mottl
  2004-12-11 23:56         ` skaller
  2004-12-11 23:29       ` skaller
  1 sibling, 1 reply; 57+ messages in thread
From: Markus Mottl @ 2004-12-11 18:13 UTC (permalink / raw)
  To: Andrej Bauer; +Cc: caml-list, skaller

On Sat, 11 Dec 2004, Andrej Bauer wrote:
> But don't get me wrong. I definitely agree with John that having 10
> arguments to a functions sounds like too many, and something needs to be
> done in such cases. It's just that in my web application (and I suspect
> in most) I don't have 10 arguments all over the code, but more like 3 or
> 4, which is ok. Certainly different types of programs require different
> solutions.

Another solution would be to use a state monad encapsulating
the environment.  It has operators for getting and setting states.
Instead of passing all arguments from function to function "manually",
you then just need to use the monadic bind operator, which does all that
implicitly - and even purely functionally + in a statically type safe way!

See my IMP-example for a monadic interpreter, which makes
use of a state monad to pass around runtime environments:
http://www.oefai.at/~markus/home/ocaml_sources.html

Regards,
Markus

-- 
Markus Mottl          http://www.oefai.at/~markus          markus@oefai.at


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

* Re: [Caml-list] environment idiom
  2004-12-11 14:31     ` Andrej Bauer
  2004-12-11 18:13       ` Markus Mottl
@ 2004-12-11 23:29       ` skaller
  2004-12-12  0:21         ` Jacques Carette
  1 sibling, 1 reply; 57+ messages in thread
From: skaller @ 2004-12-11 23:29 UTC (permalink / raw)
  To: Andrej Bauer; +Cc: caml-list

On Sun, 2004-12-12 at 01:31, Andrej Bauer wrote:
> It seems that John Skaller and I have different experiences, 

Yes but I came to almost the same conclusion as you.
I agree with your basic premise, I propose only a
minor amendment, possibly more suitable for
'programming-in-the-large'.


> He offers a C/C++ example of the
> const pointers. I am not convinced that ocaml and C/C++ are comparable
> in this respect. 

The principle is quite general, exceeding not only C++/Ocaml,
but applying way beyond programming.  I actually learned
this idea, that one should think about how a code base
will cope with change, in a superb book on Cobol programming.
More recently, Bertrand Meyer stated the Open/Closed principle,
which deals with a related issue.

As an example: this code is fragile:

	for(int i =0; i!=10; ++i)a[i]=b[i];

because it terminates *precisly* at the expected
array length. It will fail for any change in array length.

Fragile coding is good sometimes, and other times you
would prefer your code to be robust. To some extent it
depends on the use of your code and how much money you have
to finish the program. For a quick and dirty program,
you'd make it robust. If it's a library that is intended
to be heavily used, you make it fragile.

> I habitually abuse the ocaml compiler to tell me
> precisely what needs to be changed in the following way: I change a type
> or value definition (say, change the arguments to a function) and keep
> running the compiler until it reports errors, fixing them as they come
> up. 

I do that too. Heavily. Only I don't think of it as abuse :)

Unfortunately some things in a compiler seem to demand
run time checks where you'd much prefer static typing.
However the strongest static typing is very hard to get
exactly right, and is quite verbose. I'd spend more
time fiddling with it when things changed, than modifying
the algorithms which actually do the work.

-- 
John Skaller, mailto:skaller@users.sf.net
voice: 061-2-9660-0850, 
snail: PO BOX 401 Glebe NSW 2037 Australia
Checkout the Felix programming language http://felix.sf.net




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

* Re: [Caml-list] environment idiom
  2004-12-11 18:13       ` Markus Mottl
@ 2004-12-11 23:56         ` skaller
  2004-12-12  2:36           ` William Lovas
  2004-12-12 23:03           ` Thomas Fischbacher
  0 siblings, 2 replies; 57+ messages in thread
From: skaller @ 2004-12-11 23:56 UTC (permalink / raw)
  To: Markus Mottl; +Cc: Andrej Bauer, caml-list

On Sun, 2004-12-12 at 05:13, Markus Mottl wrote:

> Another solution would be to use a state monad encapsulating
> the environment.  It has operators for getting and setting states.
> Instead of passing all arguments from function to function "manually",
> you then just need to use the monadic bind operator, which does all that
> implicitly - and even purely functionally + in a statically type safe way!

There's some illusion here. I had an argument with someone that
functional arrays were impossible: array implies O(1) which implies
mutable. Yet Haskell has them, via monads .. and it's all
'purely functional and referentially transparent'.

Took me a while to figure out why this is NOT the case.
Yet obviously, it cannot be. Consider a more extreme
example: using state transformer monads, you can emulate
the action of any C program in Haskell. So it is quite
clear there's no possibility of this being 'purely functional
and referentially transparent' because C programs are not.

The answer is evident in this example because it is so extreme.
Whether code is 'purely functional' etc or not, is a matter of
your viewpoint. Sure, the *Haskell* encoding is purely functional,
but the code *viewed at the monadic level* is not.

I.e. if you implement an interpreter for a non-transparent
non-functional language in a transparent and functional one,
then the interpreter is purely functional, but what it
interprets is not.

So monadic programming with state transformers is NOT
referentially transparent or purely functional at all.
Because you are NOT encoding in Haskell but using
the extension the monad provides.. and THAT code patently
isn't functional.

So actually all these claims about purely functional I/O
and state transformers are wrong: they miss the fundamental
point that when you use them you're no longer coding
in the base language -- the notion of 'code' is relative.

In the 'C interpreter' monad your code has all the
same properties C has -- in particular it isn't transparent
or purely functional. The fact that the interpreter implementation
retains these properties is only relevant to the correctness 
of the interpeter -- not the use of it.

I think there is a theorem here: when you abstract purely
functional code, there is no guarrantee the result is functional.
The bottom line is that given an environment E

	f: A -> B

is not functional if f fiddles with environment E.
It is absurd then to think that

	f: E * A -> E * B

is suddenly purely functional, just because the environment
is now made explicit. This is the inverse theorem:
you can lift any non-functional code to a purely functional
interpretation. Monads just 'drop' the explicit E,
leaving the orginal f which is not functional by specification.
Contradiction: monadic extensions of Haskell do not
magically allow purely functional arrays.

But it is all just fiddling with the 'level' of the code
you're talking about. Fundamentally the notions of purely
functional and referentially transparent are relative things.
Your Haskell is running on a CPU that clearly isn't functional.

A final example. Ocaml *is* purely functional. As long
as you consider references as values -- rather than what
they refer to. In reality, it's just a state transformer
monad like Haskell, only the encoding is built in to
the language.

-- 
John Skaller, mailto:skaller@users.sf.net
voice: 061-2-9660-0850, 
snail: PO BOX 401 Glebe NSW 2037 Australia
Checkout the Felix programming language http://felix.sf.net




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

* Re: [Caml-list] environment idiom
  2004-12-11 23:29       ` skaller
@ 2004-12-12  0:21         ` Jacques Carette
  0 siblings, 0 replies; 57+ messages in thread
From: Jacques Carette @ 2004-12-12  0:21 UTC (permalink / raw)
  To: skaller, Andrej Bauer; +Cc: caml-list

skaller <skaller@users.sourceforge.net> wrote:
> The principle is quite general, exceeding not only C++/Ocaml,
> but applying way beyond programming.  I actually learned
> this idea, that one should think about how a code base
> will cope with change, in a superb book on Cobol programming.

This idea is indeed quite old.  It is generally credited to David Parnas -- see http://www.acm.org/classics/may96/ 
which refers to
On the Criteria To Be Used in Decomposing Systems into Modules
D.L. Parnas, Communications of the ACM, Vol. 15, No. 12, December 1972 pp. 1053 - 1058

It is the paper that introduces "information hiding" (not to be confused with the much more restricted idea of 'data 
hiding' common to OO languages) as well as the design-for-change principle.

Sadly, the OO craze has so warped the idea of "information hiding" amongst practitioners that few actually understand 
how groundbreaking this sweeping idea really was, and still is.
  
Jacques


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

* Re: [Caml-list] environment idiom
  2004-12-11 23:56         ` skaller
@ 2004-12-12  2:36           ` William Lovas
  2004-12-12  5:33             ` skaller
  2004-12-12 23:03           ` Thomas Fischbacher
  1 sibling, 1 reply; 57+ messages in thread
From: William Lovas @ 2004-12-12  2:36 UTC (permalink / raw)
  To: caml-list

On Sun, Dec 12, 2004 at 10:56:38AM +1100, skaller wrote:
> The bottom line is that given an environment E
> 
> 	f: A -> B
> 
> is not functional if f fiddles with environment E.
> It is absurd then to think that
> 
> 	f: E * A -> E * B
> 
> is suddenly purely functional, just because the environment
> is now made explicit.  [...]

I'm not sure i buy this: if f returns the same result every time it's
called with the same argument, and calling f cannot affect the behavior of
any other part of your progrem, then in what way is f not purely
functional?

> A final example. Ocaml *is* purely functional. As long
> as you consider references as values -- rather than what
> they refer to. In reality, it's just a state transformer
> monad like Haskell, only the encoding is built in to
> the language.

But there exist "functions" in O'Caml whose behavior is not always the same
for a given argument, namely (!).  Does Haskell have such "functions"?

You're blurring some definitions fairly substantially when you say things
like "Haskell is not purely functional, but O'Caml is" :)

cheers,
William


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

* Re: [Caml-list] environment idiom
  2004-12-12  2:36           ` William Lovas
@ 2004-12-12  5:33             ` skaller
  2004-12-12 19:09               ` Michael Walter
  0 siblings, 1 reply; 57+ messages in thread
From: skaller @ 2004-12-12  5:33 UTC (permalink / raw)
  To: William Lovas; +Cc: caml-list

On Sun, 2004-12-12 at 13:36, William Lovas wrote:
> On Sun, Dec 12, 2004 at 10:56:38AM +1100, skaller wrote:
> > The bottom line is that given an environment E
> > 
> > 	f: A -> B
> > 
> > is not functional if f fiddles with environment E.
> > It is absurd then to think that
> > 
> > 	f: E * A -> E * B
> > 
> > is suddenly purely functional, just because the environment
> > is now made explicit.  [...]
> 
> I'm not sure i buy this: if f returns the same result every time it's
> called with the same argument, and calling f cannot affect the behavior of
> any other part of your progrem, then in what way is f not purely
> functional?

It is, my point is simply that the mere recharactisation
of an function modifying its environment, to one accepting
and returning its environment, clearly isn't very useful
in determining how 'nice' the function f is.

Clearly, the encoding of f is unchanged .. the fact is,
in the first typing E is every bit an argument, it just
happens to be implicit.

I mean in general, the input E might be persistent,
in which case the two constructions are semantically
distinct. However if the input E is never reused --
which is guaranteed in the first formulation, they're
the same.

> > A final example. Ocaml *is* purely functional. As long
> > as you consider references as values -- rather than what
> > they refer to. In reality, it's just a state transformer
> > monad like Haskell, only the encoding is built in to
> > the language.
> 
> But there exist "functions" in O'Caml whose behavior is not always the same
> for a given argument, namely (!).  Does Haskell have such "functions"?

Yes it does, inside the state transformer monad for example.
The question is whether monadic code is actually Haskell code,
and of course that's an absurd question .. :)

I have a Scheme interpreter written in Ocaml .. if I 
use to execute Scheme code, is the code Scheme or Ocaml?

I don't want an answer .. the question is rhetorical,
it's obviously BOTH. The real question is about encoding
structure: clearly the meaning of code depends on context
in a subtle way.

> You're blurring some definitions fairly substantially when you say things
> like "Haskell is not purely functional, but O'Caml is" :)

Yes, that indeed is my intention. Basically, any non-transparent
non-function code can be made purely functional and transparent
with a simple transformation, yet it doesn't by this transformation
get any easier to reason about the code.

So taken on its own, 'purely functional' is of no real
importance. Anything is purely functional if you want
to consider it that way.

In order to *actually* make an argument that referential
transparency makes it easier to reason about program semantics,
it seems to me we need some more context.

As another example, there is no difference in the ability
to reason about a purely functional tail recursive exposition
of a loop, and an actual loop construction -- there cannot
possibly be, since they're equivalent -- the best one can
say is the the tail-rec method is *harder* to reason about,
since you need to first establish if a call is tail-rec,
which is manifest in a procedural loop.


A paper on SSA (single assignment form) I read recently
shows that it isn't suprising SSA is easy to work with,
since it can be shown to be equivalent to a purely functional
construction using continuation passing.

So, the many equivalences between stateful and functional
programming suggest functional programming simply does NOT
have a necessary advantage purely from being purely functional,
particularly if you're just emulating procedural code,
as is possible in a Haskell monad. Its clear the monadic code has
no advantage over the emulated procedural code since they're
semantically equivalent.

I'm not saying purely function/referentially transparent
is useless in respect of reasoning ability, I'm saying
it just isn't enough to say 'the code is better because
it is purely functional'. That isn't enough to gain the
advantages .. something more is needed to make this
claim carry through. I don't know exactly what.. :)

Crude example: OCS scheme interpreter (OCaml code) +
Scheme program (Data) --> functional code.
Yet: Scheme interpreter (Ocaml code) + Scheme program 
(Scheme code) => NOT functional. Ie. it depends trivially
on whether you label the Scheme inputs to the interpreter
as data or code. But all data is just an encoding ..

So perhaps the question is more like: given a low level
purely functional code, how far up the abstraction heirarchy
can you push the dividing line between data and code until
the result loses purity/transparency?

This should give a better indication how easy it will
be to reason about semantics: if you lose purity early,
it will be hard, if the whole system is pure all the way,
perhaps it will be easier. The point is there is no longer
any issue of code being 'purely functional' qualitatively, 
instead the question is quantitative.

As an example you might apply this analysis to MetaOcaml
programs. Is MetaOcaml code easier/harder to reason about
if the outermost metalevels of the code are functional,
and any procedural code is reserved for the innermost
(last generated) levels?

Actually, MetaOcaml is a pretty good example of what I'm
talking about since you can say it is functional
for the first several expansions and then becomes procedural,
and actually *count* the number of metalevels.

-- 
John Skaller, mailto:skaller@users.sf.net
voice: 061-2-9660-0850, 
snail: PO BOX 401 Glebe NSW 2037 Australia
Checkout the Felix programming language http://felix.sf.net




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

* Re: [Caml-list] environment idiom
  2004-12-12  5:33             ` skaller
@ 2004-12-12 19:09               ` Michael Walter
  2004-12-13  0:48                 ` skaller
  0 siblings, 1 reply; 57+ messages in thread
From: Michael Walter @ 2004-12-12 19:09 UTC (permalink / raw)
  To: skaller; +Cc: William Lovas, caml-list

On 12 Dec 2004 16:33:29 +1100, skaller <skaller@users.sourceforge.net> wrote:
> Yes, that indeed is my intention. Basically, any non-transparent
> non-function code can be made purely functional and transparent
> with a simple transformation, yet it doesn't by this transformation
> get any easier to reason about the code.
Well, actually monadic I/O makes is easier to reason about code than
languages which allow for non-transparent side effects in functions. I
think you were making a really good argument pro monads yourself -- in
your C interpreter monad you can easily see what's making use of the C
interpreter (any function "in"/lifted to the C interpreter monad), and
what's not. Same for I/O -- you can assume that only functions
"in"/lifted to the IO monad (simply said, every value of type IO a)
are able to do I/O. This clearly allows easier reasoning about code.

- Michael


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

* Re: [Caml-list] environment idiom
  2004-12-11 23:56         ` skaller
  2004-12-12  2:36           ` William Lovas
@ 2004-12-12 23:03           ` Thomas Fischbacher
  2004-12-13  1:26             ` skaller
  1 sibling, 1 reply; 57+ messages in thread
From: Thomas Fischbacher @ 2004-12-12 23:03 UTC (permalink / raw)
  To: skaller; +Cc: Markus Mottl, Andrej Bauer, caml-list


On Sun, 12 Dec 2004, skaller wrote:

> So monadic programming with state transformers is NOT
> referentially transparent or purely functional at all.

Actually, it is. :-)

-- 
regards,               tf@cip.physik.uni-muenchen.de              (o_
 Thomas Fischbacher -  http://www.cip.physik.uni-muenchen.de/~tf  //\
(lambda (n) ((lambda (p q r) (p p q r)) (lambda (g x y)           V_/_
(if (= x 0) y (g g (- x 1) (* x y)))) n 1))                  (Debian GNU)


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

* Re: [Caml-list] environment idiom
  2004-12-12 19:09               ` Michael Walter
@ 2004-12-13  0:48                 ` skaller
  2004-12-13  2:03                   ` Michael Walter
  0 siblings, 1 reply; 57+ messages in thread
From: skaller @ 2004-12-13  0:48 UTC (permalink / raw)
  To: Michael Walter; +Cc: William Lovas, caml-list

On Mon, 2004-12-13 at 06:09, Michael Walter wrote:
> On 12 Dec 2004 16:33:29 +1100, skaller <skaller@users.sourceforge.net> wrote:
> > Yes, that indeed is my intention. Basically, any non-transparent
> > non-function code can be made purely functional and transparent
> > with a simple transformation, yet it doesn't by this transformation
> > get any easier to reason about the code.
> Well, actually monadic I/O makes is easier to reason about code than
> languages which allow for non-transparent side effects in functions. I
> think you were making a really good argument pro monads yourself -- in
> your C interpreter monad you can easily see what's making use of the C
> interpreter (any function "in"/lifted to the C interpreter monad), and
> what's not. Same for I/O -- you can assume that only functions
> "in"/lifted to the IO monad (simply said, every value of type IO a)
> are able to do I/O. This clearly allows easier reasoning about code.


This is a good point, and it seems to support my thesis.

What you seem to be saying is that in mixed monadic/plain code,
the abstraction boundary is plain, which helps reasoning.

So the monadic model is good, because it plainly separates
the 'purely functional' non-monadic code, from the
monadic code, which admits two distinct views -- at the lower
level it is pure, whilst the higher level interpretation
might not be -- depending both on the monad being used,
and also how it is used.

Compare with Ocaml which does not localise non-transparent
code (using references, Hashtbl, etc).

-- 
John Skaller, mailto:skaller@users.sf.net
voice: 061-2-9660-0850, 
snail: PO BOX 401 Glebe NSW 2037 Australia
Checkout the Felix programming language http://felix.sf.net




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

* Re: [Caml-list] environment idiom
  2004-12-12 23:03           ` Thomas Fischbacher
@ 2004-12-13  1:26             ` skaller
  2004-12-13  8:37               ` Thomas Fischbacher
  0 siblings, 1 reply; 57+ messages in thread
From: skaller @ 2004-12-13  1:26 UTC (permalink / raw)
  To: Thomas Fischbacher; +Cc: Markus Mottl, Andrej Bauer, caml-list

On Mon, 2004-12-13 at 10:03, Thomas Fischbacher wrote:
> On Sun, 12 Dec 2004, skaller wrote:
> 
> > So monadic programming with state transformers is NOT
> > referentially transparent or purely functional at all.
> 
> Actually, it is. :-)

Actually it is pointless after I took the trouble
to explain why this is not the case, to make such
a bland statement. 

It seems you missed entirely my point.

In some interpretation of the encoding it is self-evident --
which means it isn't open to question or contradiction --
that the code is NOT transparent.

The issue is to reformulate the meaning of 'encoding'
in such a way that the well-known advantages of transparency
are preserved.

There is no doubt WHAT SO EVER that Haskell programs
doing I/O have side effects, for example. Yet Haskell
per se, doesn't. How can this be? 

The point is to *rescue* the basic conception from
the ridicule which, at the moment, it deserves.
The claims that monadic programming allows side effect 
free transparent purely functional encoding is unquestionably
bogus. It can only be reinstated by more carefully specifying
exactly *which* encodings have those properties.

In particular with monads the combinators themselves
patently admit a higher level of encoding -- combinator
encodings -- which are NOT transparent, even if the terms
they manipulate and the combinator definitions are.

This is a new result for me -- functional code, when abstracted
to a higher level encoding, need not be functional.  Perhaps this
is already known, and if not it will take a real theoretician
to state what I'm trying to say properly, but I have no doubt
at all the intent, though stated vaguely, is correct.

Hmm .. of COURSE it is already known. Indeed, languages like
Ocaml have long been classed as ISWIM-like. Such a language
is purely functional, when the handles of variables are
treated as values, but is not, when the values of the variables
themselves are admitted. The whole *point* of the technique
is to preserve the functional code and provide a clean
dividing line between the functional part and the mutable store.

Indeed I would bet there is a monadic interpretation of this,
which would give Haskell programmers Ocaml like references.

The point here is that *even* in languages like Ocaml where
references are used, lack of absolute transparency does
not make reasoning suddenly impossible. Despite the lack
of absolute transparency, it is still much easier to reason
about Ocaml than C++. Why? Because the core really is
functional, and somehow you can still reason about the
code 'as if' it were functional, and obtain a result pertaining
to correctness of the code, perhaps 'with some caveats'.

In particular, I would gues it is possible to reason the
code is *incorrect* assuming it is purely functional (ignoring
the values of references) and have that result hold, even
if references are used -- but I don't know for sure,
it may be one has to restrict the rules of inference.

Obviously one can show that:

	let f x  = f (1::x) in
	let x = ref 0 in
	f !x

will not terminate since we're invoking, in an eager language,
a nonterminating purely functional function... so the presence
of a reference is irrelevant. Of course this is a trivial
example, perhaps COQ programmers know better how to separate
the mutable fields out.


-- 
John Skaller, mailto:skaller@users.sf.net
voice: 061-2-9660-0850, 
snail: PO BOX 401 Glebe NSW 2037 Australia
Checkout the Felix programming language http://felix.sf.net




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

* Re: [Caml-list] environment idiom
  2004-12-13  0:48                 ` skaller
@ 2004-12-13  2:03                   ` Michael Walter
  2004-12-13  2:05                     ` Michael Walter
  2004-12-13  5:41                     ` skaller
  0 siblings, 2 replies; 57+ messages in thread
From: Michael Walter @ 2004-12-13  2:03 UTC (permalink / raw)
  To: skaller; +Cc: William Lovas, caml-list

On 13 Dec 2004 11:48:55 +1100, skaller <skaller@users.sourceforge.net> wrote:
> So the monadic model is good, because it plainly separates
> the 'purely functional' non-monadic code, from the
> monadic code, which admits two distinct views -- at the lower
> level it is pure, whilst the higher level interpretation
> might not be -- depending both on the monad being used,
> and also how it is used.
It is probably better to say "from the outside it is pure, and inside
it appears impure, relative to its boundary" (thus stressing the point
that your apparent impurity is only a "view" <wink>).

I think the problem is that we are using "pure" twofold here:

a) As an (absolute) property of the language
b) As the property of code (which is relative to its environment)

As you can obviously emulate impurity in a pure language (see State
monad), and code pure in a impure language, it is not much of a
surprise that b) can differ from a).

Cheers,
Michael


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

* Re: [Caml-list] environment idiom
  2004-12-13  2:03                   ` Michael Walter
@ 2004-12-13  2:05                     ` Michael Walter
       [not found]                       ` <877e9a170412121844b633bb8@mail.gmail.com>
  2004-12-13  5:41                     ` skaller
  1 sibling, 1 reply; 57+ messages in thread
From: Michael Walter @ 2004-12-13  2:05 UTC (permalink / raw)
  To: skaller; +Cc: William Lovas, caml-list

On Sun, 12 Dec 2004 21:03:14 -0500, Michael Walter
<michael.walter@gmail.com> wrote:
> b) As the property of code (which is relative to its environment)
"Environment" as in "surrounding", not the technical term.

Cheers,
Michael


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

* [Caml-list] environment idiom
       [not found]                       ` <877e9a170412121844b633bb8@mail.gmail.com>
@ 2004-12-13  2:45                         ` Michael Walter
  2004-12-13  6:18                           ` skaller
  2004-12-13  8:56                           ` Thomas Fischbacher
  0 siblings, 2 replies; 57+ messages in thread
From: Michael Walter @ 2004-12-13  2:45 UTC (permalink / raw)
  To: caml-list

> The claims that monadic programming allows side effect
> free transparent purely functional encoding is unquestionably
> bogus.
In your view, would claiming that the stream approach allowed that be
bogus as well?

main :: [Response] -> [Request]

In a pure language, main is obviously pure as well. And still, _given
the proper "invocation" from an impure language_, it allows for I/O.

To paraphrase: Does the mere existance of a "magic main invocation"
(whether a streaming-main or an IO monadic-main) make a language
impure, in your concept?

To stretch it further: Suppose an interpreter for an language X with
the simple syntax:
  X-program := (identifier-name '=' integer-literal)+
and semantics that the value of the identifier with the name "main" is
print. It is not allowed to redefine existing definitions (i.e. mutate
state). Hence every "program" in X is pure, but still an X program
such as "main=42" will have a noticable side effect (namely, printing
42 on the screen). How can that be? <0.5-wink>

Again I believe we are talking about different kinds of "purity".
Thomas is obviously right in that the StateTransformer monad (modulo
unsafe conversions) is pure, you are obviously right in the
(different) point that _running_ an IO fragment has side effects.

Generally, I'm not sure whether it's sensible to qualify other
people's statements as "unquestionably bogus". Everything is relative
<wink> :)

Cheers,
Michael


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

* Re: [Caml-list] environment idiom
  2004-12-13  2:03                   ` Michael Walter
  2004-12-13  2:05                     ` Michael Walter
@ 2004-12-13  5:41                     ` skaller
  2004-12-13  9:29                       ` Michael Walter
  1 sibling, 1 reply; 57+ messages in thread
From: skaller @ 2004-12-13  5:41 UTC (permalink / raw)
  To: Michael Walter; +Cc: William Lovas, caml-list

On Mon, 2004-12-13 at 13:03, Michael Walter wrote:

> It is probably better to say "from the outside it is pure, and inside
> it appears impure, relative to its boundary" (thus stressing the point
> that your apparent impurity is only a "view" <wink>).

Perhaps so.

> I think the problem is that we are using "pure" twofold here:

Yes. But this is not all ..

> a) As an (absolute) property of the language
> b) As the property of code (which is relative to its environment)
> 
> As you can obviously emulate impurity in a pure language (see State
> monad), and code pure in a impure language, it is not much of a
> surprise that b) can differ from a).

Consider this example. We have an algorithm, such as:

	Take an array of bool length n initially all false.
	for i = 1 to n do
		if element i is false 
			print i
			set every i'th element true
	
Of course this is the Sieve. Now consider a
procedural and functional implementation.

We can ask: is the implementation *correct*?
In this case, probably it is easier to reason about
the correctness of the procedural implementation than
the functional one (although I wouldn't bet on it :)

We can also ask: is the algorithm correct? (At finding primes).

That's a different question about a different level of the
encoding.

Finally we can ask: are the functional and procedural
programs correct (at finding primes)?

I am desiring to show here that 'the ability to
reason about correctness' depends on what encoding
of what you're asking the question about.

Clearly even a functional encoding of the Sieve
is still a procedural program at the level of
calculating primes. However it is pure at the
detail level. This only helps, and only perhaps
helps, at reasoning if the code faithfully implements
the algorithm -- if you try to reason about it's
ability to calculate primes you inevitably have to 
account for the fact the algorithm isn't functional.

So we're agreeing on the ideas, but we need some
way to *distinguish* in a less informal way,
that a Haskell program may not be as 'pure' at all 
levels as the detailed encoding is. 

Whilst this isn't restricted to Haskell, given
monads it seems we can focus on the monadic parts
to see what higher level abstractions they represent,
and how pure they are, in the abstract, and thus
make -- or find it harder to make -- judgements,
depending on how 'transparent' that abstraction is.

In other words, I guess Haskell monads are good,
because not only do monads localise the code that
needs this special consideration, but the typeclasses
systematically present the structure, so you can
extend your normal inference rules to cover the
monadic code.

It would seem than that for some monads, the extension
inference rules would be harder to use since they don't
include rules that require transparency. The advantage
is that you can still reason about the code, and you can
even say which inference rules can be applied where.

This is probably harder to do in Ocaml, where the
places that transparency is lost aren't so easy to
find, and the effects on the whole program not quite
so easy to isolate.

-- 
John Skaller, mailto:skaller@users.sf.net
voice: 061-2-9660-0850, 
snail: PO BOX 401 Glebe NSW 2037 Australia
Checkout the Felix programming language http://felix.sf.net




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

* Re: [Caml-list] environment idiom
  2004-12-13  2:45                         ` Michael Walter
@ 2004-12-13  6:18                           ` skaller
  2004-12-13  7:08                             ` skaller
  2004-12-13  9:56                             ` Michael Walter
  2004-12-13  8:56                           ` Thomas Fischbacher
  1 sibling, 2 replies; 57+ messages in thread
From: skaller @ 2004-12-13  6:18 UTC (permalink / raw)
  To: Michael Walter; +Cc: caml-list

On Mon, 2004-12-13 at 13:45, Michael Walter wrote:
> > The claims that monadic programming allows side effect
> > free transparent purely functional encoding is unquestionably
> > bogus.
> In your view, would claiming that the stream approach allowed that be
> bogus as well?

I think I am saying something like this: if you claim

	"Mine is bigger"

what would you say? Bigger than what? A comparative needs two
arguments or it is meaningless.

With that idea in mind, any claim that X is transparent is automatically
bogus without context, you really need to say instead

	"X is transparent at the Y level"

Of course I'm not implying a strict stratification by the
use of the word "level", merely ignorance of the proper
way to structure the statement.

> main :: [Response] -> [Request]
> 
> In a pure language, main is obviously pure as well. And still, _given
> the proper "invocation" from an impure language_, it allows for I/O.

I have seen theoretical models of functional languages where
an imperative machine calculates functions -- an interactive
interpreter that is entirely lazy isn't much use :)

So at the top level, the system isn't functional,
but for each individual calculation it is.

However this is a fairly primitive and boring situation.
Monadic Haskell, and Ocaml, are far more interesting
because the interactions are more complex.

Another example is my Felix language. It has both functions
and procedures. Functions aren't allowed to have side effects,
yet they're not pure in the sense the result can depend
on variables which change between (but not during) invocations.
[This has an alarming effect on the optimiser ..]

In addition, you can say that the procedural code is actually
functional, since it works by resumptions, a style of continuation
passing where code executes for a while then returns a new
continuation. In some places, it is the same object, modified,
and in others a clone is made first, so that it really is
purely functional -- with respect to that continuation at least.


> To paraphrase: Does the mere existance of a "magic main invocation"
> (whether a streaming-main or an IO monadic-main) make a language
> impure, in your concept?

If the 'magic main' is part of the semantic specification yes,
otherwise no.. and clearly here the division is quite plain
and well defined. Clearly you can reason about the 
'functional subsystem' using transparency, and then combine
the result with reasoning about the top level 'magic main'
where the program as a whole is not transparent ... and you still
have 'ease of reasoning' in the combination.

> Again I believe we are talking about different kinds of "purity".
> Thomas is obviously right in that the StateTransformer monad (modulo
> unsafe conversions) is pure, you are obviously right in the
> (different) point that _running_ an IO fragment has side effects.

Yes, but that is precisely the point. In wishing to avoid 
the kind of hype normally associated with OO and Java,
I think it is necessary to reconsider exactly what
crude statements like 'it is pure and transparent' actually
mean.

> Generally, I'm not sure whether it's sensible to qualify other
> people's statements as "unquestionably bogus". Everything is relative
> <wink> :)

It was actually *my* statement that I labelled 'unquestionably
bogus', namely that Haskell (including all monadic programming)
is pure and transparent (and side effect free) when clearly
any kind of I/O at the OS level is not.

However the claim is not *wrong*, instead I'm claiming
it isn't a well formed formula: 'pure' is a predicate
that has to be applied to a particular level of encoding,
and then you can reason about that level using that
property -- but that isn't enough to reason about correctness,
since it invariably means checking the program meets some
specification given at a much higher level of abstraction.

So given the utility of transparency for reasoning,
one might find some styles of monad preserved transparency,
even in their higher levels of interpretation, whilst
other did not. And that would be valuable, since it would
be a way to guide the choice of techniques, whereas
a bland 'it is all transparent and pure' fails to
provide sufficient distinctions.

Since I'm not a Haskell programmer it is hard to give examples,
but for Ocaml I'm sure we all know that some uses of 
imperative programming technique feel 'safer' than others.
They threaten purity less. But this is just waffle.
I'd like to have a better guideline.

Obvious example -- references are 'safer' if you keep their
scope local -- for example I do this a lot, and whilst it
isn't pure it is not too bad:

	let f x = 
		let a = ref 0 in
		for i = 1 to x do incr a done;
		!a

Why are localised uses of mutation
less of a threat to reasoning than less localised ones?

Because it's encapsulated in the function .. but that is
a waffle explanation .. how about more general 
theoretical account of this phenomena?

-- 
John Skaller, mailto:skaller@users.sf.net
voice: 061-2-9660-0850, 
snail: PO BOX 401 Glebe NSW 2037 Australia
Checkout the Felix programming language http://felix.sf.net




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

* Re: [Caml-list] environment idiom
  2004-12-13  6:18                           ` skaller
@ 2004-12-13  7:08                             ` skaller
  2004-12-13  9:56                             ` Michael Walter
  1 sibling, 0 replies; 57+ messages in thread
From: skaller @ 2004-12-13  7:08 UTC (permalink / raw)
  To: Michael Walter; +Cc: caml-list

On Mon, 2004-12-13 at 17:18, skaller wrote:

BTW: one reason I'm very interested in the 'transparency'
and 'purity' topic is a practical matter:

> Another example is my Felix language. It has both functions
> and procedures. Functions aren't allowed to have side effects,
> yet they're not pure in the sense the result can depend
> on variables which change between (but not during) invocations.
> [This has an alarming effect on the optimiser ..]


Crudely the optimiser simply inlines everything,
perhaps an improved version will do usage checks
to cache results..

This must work fine if functions are pure.
But as noted, they're not, because they can access variables
that change with time, and so the place of calling a
function, which is related to when it is evaluated,
makes a difference.

To fix this I need to be able to do something crude
like designate a function as 'pure' -- this has been
discussed for Ocaml too.

That isn't the only possible technique, and it isn't
clear how to carry this information through for
function variables, unless the type system is involved.
EG you have two arrows:

	a -> b  pure function
	a +> b  can refer to variables

which raises questions about unification, overloading,
subtyping, etc.

However if a function isn't pure, when you evaluate
it matters .. but that doesn't tell you when to evaluate it.
Instead of saying 'strict' or 'lazy', one could annotate
function arguments:

	let f (g:lazy) (h:eager) (k:pure) x  = ..

which tells the compiler that to evaluate h 'before
the call', g precisely when needed, possibly twice
with different results, and k anytime convenient.
 
Well that seems to impact the type system too.. :)

At present I use a trick to distinguish procedures:
they have the type

	'a -> void

which prevents them being used in a context where
the sequence of evaluation is indeterminate (i.e. in
expressions). 

Well now I seem to need more than just procedures
and functions, I need at least pure and impure
functions (where impure does NOT mean side-effects,
but rather non-parametricity, which has the same
negative effect on transparency).

So I have a pragmatic interest in finding a theoretical model
that says something more about how pure/impure/lazy/eager/etc etc
code interacts: with the optimiser switched on, I'm the only
person that can predict what a Felix program will do,
and my own optimiser has caught me out several times already :)


-- 
John Skaller, mailto:skaller@users.sf.net
voice: 061-2-9660-0850, 
snail: PO BOX 401 Glebe NSW 2037 Australia
Checkout the Felix programming language http://felix.sf.net




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

* Re: [Caml-list] environment idiom
  2004-12-13  1:26             ` skaller
@ 2004-12-13  8:37               ` Thomas Fischbacher
  2004-12-13 10:53                 ` skaller
  0 siblings, 1 reply; 57+ messages in thread
From: Thomas Fischbacher @ 2004-12-13  8:37 UTC (permalink / raw)
  To: skaller; +Cc: Markus Mottl, Andrej Bauer, caml-list


On Mon, 13 Dec 2004, skaller wrote:

> > > So monadic programming with state transformers is NOT
> > > referentially transparent or purely functional at all.
> > 
> > Actually, it is. :-)
> 
> Actually it is pointless after I took the trouble
> to explain why this is not the case, to make such
> a bland statement. 

Then let me re-formulate it in other words:

I think you do not yet fully appreciate the key point concerning the 
monadic approach.

Or in still other words: could you please show me a piece of haskell 
code that uses monads but is not referentially transparent (assuming you 
do not use "unofficial" features such as, in particular, unsafePerformIO)?

What I want to see in particular is a few lines of haskell, where X=Y 
holds, but the semantics of the program change if I substitute the 
definition of X with that of Y.


-- 
regards,               tf@cip.physik.uni-muenchen.de              (o_
 Thomas Fischbacher -  http://www.cip.physik.uni-muenchen.de/~tf  //\
(lambda (n) ((lambda (p q r) (p p q r)) (lambda (g x y)           V_/_
(if (= x 0) y (g g (- x 1) (* x y)))) n 1))                  (Debian GNU)


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

* Re: [Caml-list] environment idiom
  2004-12-13  2:45                         ` Michael Walter
  2004-12-13  6:18                           ` skaller
@ 2004-12-13  8:56                           ` Thomas Fischbacher
  2004-12-13  9:21                             ` Jacques Garrigue
                                               ` (2 more replies)
  1 sibling, 3 replies; 57+ messages in thread
From: Thomas Fischbacher @ 2004-12-13  8:56 UTC (permalink / raw)
  To: Michael Walter; +Cc: caml-list


On Sun, 12 Dec 2004, Michael Walter wrote:

> Again I believe we are talking about different kinds of "purity".
> Thomas is obviously right in that the StateTransformer monad (modulo
> unsafe conversions) is pure, you are obviously right in the
> (different) point that _running_ an IO fragment has side effects.

The key issue is: by not doing I/O, but talking about plans how to do I/O, 
you go to a higher level of abstraction that allows you to do magic with 
such plans which you just plainly miss if you only know the imperative 
ways. It's just like everyone knows how to add (i.e. arithmetics), but 
once you learned to talk about properties of addition (i.e. algebra), you 
have a much richer point of view that allows you to do quite miraculous 
things.

Of course, it's possible to just forget about all that and fall back to 
transliterating imperative code to IO monad code, but it is just as well 
possible to find the sum of all the numbers from 1 to 1000 using the 
following piece of Maple code:

> proc sum_n(k)
> local result,i;
> for i from 1 to k do result:=result+i: od: result;
> end;
>
> sum_n(1000);

One surely can do this, and many people work in such a way to solve 
such problems, as they are used to it, but considering the power that 
Maple offers you, this is nothing but gross abuse of the system.

It's just the same with Haskell and the IO monad.


-- 
regards,               tf@cip.physik.uni-muenchen.de              (o_
 Thomas Fischbacher -  http://www.cip.physik.uni-muenchen.de/~tf  //\
(lambda (n) ((lambda (p q r) (p p q r)) (lambda (g x y)           V_/_
(if (= x 0) y (g g (- x 1) (* x y)))) n 1))                  (Debian GNU)


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

* Re: [Caml-list] environment idiom
  2004-12-13  8:56                           ` Thomas Fischbacher
@ 2004-12-13  9:21                             ` Jacques Garrigue
  2004-12-13 10:05                               ` Michael Walter
  2004-12-13 10:20                               ` Thomas Fischbacher
  2004-12-13 10:11                             ` Michael Walter
  2004-12-13 11:46                             ` skaller
  2 siblings, 2 replies; 57+ messages in thread
From: Jacques Garrigue @ 2004-12-13  9:21 UTC (permalink / raw)
  To: Thomas.Fischbacher; +Cc: caml-list

From: Thomas Fischbacher <Thomas.Fischbacher@Physik.Uni-Muenchen.DE>
> On Sun, 12 Dec 2004, Michael Walter wrote:
> > Again I believe we are talking about different kinds of "purity".
> > Thomas is obviously right in that the StateTransformer monad (modulo
> > unsafe conversions) is pure, you are obviously right in the
> > (different) point that _running_ an IO fragment has side effects.
> 
> The key issue is: by not doing I/O, but talking about plans how to do I/O, 
> you go to a higher level of abstraction that allows you to do magic with 
> such plans which you just plainly miss if you only know the imperative 
> ways. It's just like everyone knows how to add (i.e. arithmetics), but 
> once you learned to talk about properties of addition (i.e. algebra), you 
> have a much richer point of view that allows you to do quite miraculous 
> things.
> 
> Of course, it's possible to just forget about all that and fall back to 
> transliterating imperative code to IO monad code, but it is just as well 
> possible to find the sum of all the numbers from 1 to 1000 using the 
> following piece of Maple code:

You make me curious. Most of the code I've seen using the IO monad (or
the state transformer monad) was just transliterating imperative to
monadic code. Of course using closures, but not that much, and you can
certainly do that in an impure functional language also.

So what is so incredible about the IO monad?

By the way, if you want an example of non referentially code, this
looks easy:

   do
     x <- readInt
     y <- readInt
     return (x-y)

(The syntax and functions may be wrong but you get the idea.)
Of course according to your definition this contains nothing that is
not referentially transparent once you've taken the syntactic sugar.
But looking at the code, it looks like readInt is executed twice
returning different results, i.e. this function does not always return
0.
So I suppose this is just an instance of what you see is _not_ what
you get, but wasn't referencial transparency about avoiding that?

    Jacques Garrigue


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

* Re: [Caml-list] environment idiom
  2004-12-13  5:41                     ` skaller
@ 2004-12-13  9:29                       ` Michael Walter
  2004-12-13 12:30                         ` skaller
  0 siblings, 1 reply; 57+ messages in thread
From: Michael Walter @ 2004-12-13  9:29 UTC (permalink / raw)
  To: skaller; +Cc: William Lovas, caml-list

On 13 Dec 2004 16:41:23 +1100, skaller <skaller@users.sourceforge.net> wrote:
> [...]
> I am desiring to show here that 'the ability to
> reason about correctness' depends on what encoding
> of what you're asking the question about.
Agreed.

> Clearly even a functional encoding of the Sieve
> is still a procedural program at the level of
> calculating primes. However it is pure at the
> detail level. This only helps, and only perhaps
> helps, at reasoning if the code faithfully implements
> the algorithm -- if you try to reason about it's
> ability to calculate primes you inevitably have to
> account for the fact the algorithm isn't functional.
What is "the detail level"? Like the "language level" in contrast to
the level of the current abstraction (for instance, State monad)?

Different note: I think you are missing out an important property of
the functional encoding, which is its purity wrt composability.
Suppose one of the few obvious types of the sieve, for instance:
  sieve :: Integer -> [Integer]
You can clearly see that the sieve is a pure function, and actually
the type system proves this for you (modulo cheating, err,
unsafePerformIO et al). This makes it very easy and safe to use the
function (and also to test it, btw!).

In constrast, in a language such as C++ you cannot assume that..
  vector<unsigned> sieve(unsigned);
has no side effects.

Also consider the "print" part of your algorithm, which I ignored so
far. In C++ it would be very easy to add it to sieve() thus making the
function virtually useless to use but in the special case where you
want to print the number instantly.

In Haskell, you *could* have a sieve :: Integer -> IO [Integer], but
what you would really do is to decouple the sieve and I/O (and this is
made kinda "attractive" by the expressiveness of the language and the
type system). So what you would do is something like:
  printPrimes :: Integer -> IO ()
  printPrimes :: mapM_ print . sieve
(modulo obvious types made at 4 AM :-)

There is also an interesting point about algorithms which I'm sure you
are aware of. Often when analyzing algorithms for their correctness,
you reason about the state before and after a certain step in the
algorithm. That is, you make the state and its change explicit. Sounds
like sieveStep :: State -> State, huh? :-) I think that is also what
makes monads in Haskell attractive. They are very nice to use from a
programmer's perspective (IMO), but they also allow good reasoning (as
they are usually purely defined or at least definable).

> This is probably harder to do in Ocaml, where the
> places that transparency is lost aren't so easy to
> find, and the effects on the whole program not quite
> so easy to isolate.
Yep! Monads actually allow nice embedding of many paradigms, not only
the imperative.

4:29 AM-ly yours,
Michael


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

* Re: [Caml-list] environment idiom
  2004-12-13  6:18                           ` skaller
  2004-12-13  7:08                             ` skaller
@ 2004-12-13  9:56                             ` Michael Walter
  2004-12-13 12:59                               ` skaller
  1 sibling, 1 reply; 57+ messages in thread
From: Michael Walter @ 2004-12-13  9:56 UTC (permalink / raw)
  To: skaller; +Cc: caml-list

On 13 Dec 2004 17:18:36 +1100, skaller <skaller@users.sourceforge.net> wrote:
> On Mon, 2004-12-13 at 13:45, Michael Walter wrote:
> > > The claims that monadic programming allows side effect
> > > free transparent purely functional encoding is unquestionably
> > > bogus.
> > In your view, would claiming that the stream approach allowed that be
> > bogus as well?
> [..]
> With that idea in mind, any claim that X is transparent is automatically
> bogus without context, you really need to say instead
> 
>         "X is transparent at the Y level"
Right. But very often (such as in "mine is bigger" <0.5 wink>), the
comparison argument ("the context") is obvious and/or has a typical
meaning: If you say that "monadic programming allows side effect free
transparent purely functional encoding of state", most people will
understand what you are talking about (the State monad allows apparent
stateful computations, but can be purely functionally encoded).

You are stressing a different but no less obvious point of monads, in
this example that a State monad models state (i.e. you have apparent
statefulness *inside* the monad).

> Another example is my Felix language. It has both functions
> and procedures. Functions aren't allowed to have side effects,
> yet they're not pure in the sense the result can depend
> on variables which change between (but not during) invocations.
> [This has an alarming effect on the optimiser ..]
Can I read about the reasoning behind this on felix.sf.net?

> [...] Clearly you can reason about the
> 'functional subsystem' using transparency, and then combine
> the result with reasoning about the top level 'magic main'
> where the program as a whole is not transparent ... and you still
> have 'ease of reasoning' in the combination.
Indeed (and Monads give you an attractive way to partly do this the
other way around).

> Yes, but that is precisely the point. In wishing to avoid
> the kind of hype normally associated with OO and Java,
> I think it is necessary to reconsider exactly what
> crude statements like 'it is pure and transparent' actually
> mean.
Are there specific statements, for instance on the Haskell home page,
which you dislike? Or do you dislike that fact that for instance in
the statement "Monads allow for sideeffect free encoding of stateful
computations" everyone is assuming that "encoding" refers to the
encoding in the target language?

> It was actually *my* statement that I labelled 'unquestionably
> bogus', namely that Haskell (including all monadic programming)
> is pure and transparent (and side effect free) when clearly
> any kind of I/O at the OS level is not.
Okay, I was thinking (along the lines of the paragraph above) that you
were unhappy about the way that people are talking about monads.

> However the claim is not *wrong*, instead I'm claiming
> it isn't a well formed formula: 'pure' is a predicate
> that has to be applied to a particular level of encoding,
> and then you can reason about that level using that
> property.
Okay. So far I have never been confused by such statements about
monads -- it was usually pretty clear what "pure" was referring to (Of
course stateful computations deal with state, that is the very point
of them. But OTOH it is very obvious that calling the State monad
"pure" does not talk about computations *inside* the State monad, but
about the *outside* view -- if you run a computation in the State
monad, the result _purely_ depends on the arguments of runState).

> ... but that isn't enough to reason about correctness,
> since it invariably means checking the program meets some
> specification given at a much higher level of abstraction.
Sure.


> Since I'm not a Haskell programmer it is hard to give examples,
> but for Ocaml I'm sure we all know that some uses of
> imperative programming technique feel 'safer' than others.
> They threaten purity less. But this is just waffle.
> I'd like to have a better guideline.
I'm not an O'Caml programmer but I think I know what you mean.

> Why are localised uses of mutation
> less of a threat to reasoning than less localised ones?
> 
> Because it's encapsulated in the function .. but that is
> a waffle explanation .. how about more general
> theoretical account of this phenomena?
Yep. This also seems very natural -- the more localized the (potential
and actual) effects, the easier to reason about (you can reason about
smaller chunks of code, so to say).

4;56 AM-ly yours,
Michael


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

* Re: [Caml-list] environment idiom
  2004-12-13  9:21                             ` Jacques Garrigue
@ 2004-12-13 10:05                               ` Michael Walter
  2004-12-13 10:29                                 ` Thomas Fischbacher
  2004-12-13 10:20                               ` Thomas Fischbacher
  1 sibling, 1 reply; 57+ messages in thread
From: Michael Walter @ 2004-12-13 10:05 UTC (permalink / raw)
  To: Jacques Garrigue; +Cc: Thomas.Fischbacher, caml-list

On Mon, 13 Dec 2004 18:21:17 +0900 (JST), Jacques Garrigue
> You make me curious. > By the way, if you want an example of non referentially code,
> this looks easy:
> 
>    do
>      x <- readInt
>      y <- readInt
>      return (x-y)
> 
> (The syntax and functions may be wrong but you get the idea.)
> Of course according to your definition this contains nothing that is
> not referentially transparent once you've taken the syntactic sugar.
>
> But looking at the code, it looks like readInt is executed twice
> returning different results, i.e. this function does not always return
> 0.
Ah no, the key point is that this is not a function but a computation.
In order to be not referentially transparent, you would have to run
it. But you cannot do that -- the key point about the IO monad is that
you can just compose computations involving I/O, but the only time
those computations are actually executed is when "main" is invoked by
the runtime.

> So I suppose this is just an instance of what you see is _not_ what
> you get, but wasn't referencial transparency about avoiding that?
No, besides referential transparency having a definite technical
meaning, you can clearly see what you are getting by simply looking at
the type (IO Int).

Cheers,
Michael


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

* Re: [Caml-list] environment idiom
  2004-12-13  8:56                           ` Thomas Fischbacher
  2004-12-13  9:21                             ` Jacques Garrigue
@ 2004-12-13 10:11                             ` Michael Walter
  2004-12-13 11:46                             ` skaller
  2 siblings, 0 replies; 57+ messages in thread
From: Michael Walter @ 2004-12-13 10:11 UTC (permalink / raw)
  To: Thomas Fischbacher; +Cc: caml-list

On Mon, 13 Dec 2004 09:56:55 +0100 (CET), Thomas Fischbacher
<Thomas.Fischbacher@physik.uni-muenchen.de> wrote:
> On Sun, 12 Dec 2004, Michael Walter wrote:
> 
> > Again I believe we are talking about different kinds of "purity".
> > Thomas is obviously right in that the StateTransformer monad (modulo
> > unsafe conversions) is pure, you are obviously right in the
> > (different) point that _running_ an IO fragment has side effects.
> 
> The key issue is: by not doing I/O, but talking about plans how to do I/O,
> you go to a higher level of abstraction that allows you to do magic with
> such plans which you just plainly miss if you only know the imperative
> ways. It's just like everyone knows how to add (i.e. arithmetics), but
> once you learned to talk about properties of addition (i.e. algebra), you
> have a much richer point of view that allows you to do quite miraculous
> things.
Fully agreed.

> Of course, it's possible to just forget about all that and fall back to
> transliterating imperative code to IO monad code, but it is just as well
> possible to find the sum of all the numbers from 1 to 1000 using the
> following piece of Maple code:
> [...]
> One surely can do this, and many people work in such a way to solve
> such problems, as they are used to it, but considering the power that
> Maple offers you, this is nothing but gross abuse of the system.
> 
> It's just the same with Haskell and the IO monad.
Yeah exactly. That's also similar to what I was trying to say in
another post above -- idiomatic monadic I/O lends itself to
composition.

Cheers,
Michael


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

* Re: [Caml-list] environment idiom
  2004-12-13  9:21                             ` Jacques Garrigue
  2004-12-13 10:05                               ` Michael Walter
@ 2004-12-13 10:20                               ` Thomas Fischbacher
  2004-12-13 12:09                                 ` Jacques Garrigue
  2004-12-13 13:22                                 ` skaller
  1 sibling, 2 replies; 57+ messages in thread
From: Thomas Fischbacher @ 2004-12-13 10:20 UTC (permalink / raw)
  To: Jacques Garrigue; +Cc: caml-list


On Mon, 13 Dec 2004, Jacques Garrigue wrote:

> > Of course, it's possible to just forget about all that and fall back to 
> > transliterating imperative code to IO monad code, but it is just as well 
> > possible to find the sum of all the numbers from 1 to 1000 using the 
> > following piece of Maple code:
> 
> You make me curious. Most of the code I've seen using the IO monad (or
> the state transformer monad) was just transliterating imperative to
> monadic code. Of course using closures, but not that much, and you can
> certainly do that in an impure functional language also.

First, I should perhaps mention that in my point of view, John does have a 
valid point in what he says. It's only that he expressed it in a way I 
just *cannot* agree with.

> So what is so incredible about the IO monad?

There is nothing "in-credible" about it. It is just plainly nothing else 
as working with values that describe "plans" to do IO. We do have a magic 
place that can bring such plans to life, causing them to be executed, but 
from the pure Haskell point of view this is not relevant. All we do is to 
construct plans how to do IO.

> By the way, if you want an example of non referentially code, this
> looks easy:
> 
>    do
>      x <- readInt
>      y <- readInt
>      return (x-y)


> (The syntax and functions may be wrong but you get the idea.)

Okay. Let's see. Well, readInt is

Prelude> :type readInt
readInt :: Integral a => a -> (Char -> Bool) -> (Char -> Int) -> ReadS a

so this is indeed not monadic. Let's instead talk about, say

>    do
>      x <- getLine
>      y <- getLine
>      return (y++x)

Which, I suppose, conveys the very same idea you had in mind.

> Of course according to your definition this contains nothing that is
> not referentially transparent once you've taken the syntactic sugar.

Precisely. To go a bit more into detail:

Referential transparency is about the substitution of definitions. 
Evidently, x <- ... is _not_ a definition. But according to e.g. the 
haskell98 tutorial, this do-syntax actually is nothing more but an 
abbreviation. Let me cite:

>>
   The do syntax provides a simple shorthand for chains of monadic 
   operations. The essential translation of do is captured in the
   following two rules:
     do e1 ; e2      =        e1 >> e2
     do p <- e1; e2  =        e1 >>= \p -> e2
<<

So the "official" notation of what is written in shorthand above is:

main =
    getLine >>= (\x -> (getLine >>= \y -> putStr (">> "++y++x)))

Okay?

The notion of "substitution" of course only makes sense for this 
"official" form. It's not quite clear what one might want to substitute 
here, but everything that one could imagine just works. For example:

main =
    let plan_to_read = getLine
    in
      plan_to_read >>= (\x -> (plan_to_read >>= \y -> putStr (">> "++y++x)))

In a certain sense, this "do" notation - which is NOT a special extension 
of the powers of pure, functional haskell but only a short-hand notation 
for things that can be spelled out explicitly - is "poison" that allows 
one to "just hack one's imperative thoughts into haskell without 
even having know about the abstract point of view". This is a bit like 
FORTRAN programmers asked to adjust themselves to C showing the attitude 
that "at least, they can forget all that for/while/etc. mumbo-jumbo and 
do everything with goto, as they are used to".

> But looking at the code, it looks like readInt is executed twice
> returning different results, i.e. this function does not always return
> 0.

Well, as I said, if one looks at the code in such a way, one just grossly 
misreads what actually is written down. The code is about combining 
plans, not about "executing something twice".

> So I suppose this is just an instance of what you see is _not_ what
> you get, but wasn't referencial transparency about avoiding that?

So, yes, "do" notation is a tool that exists in order to help you to 
misread code, or let your code be misread. In an ideal world, it would 
certainly not be here to stay. But considering the large mass of
present and future C programmers that yet has to make this transition to 
a much more abstract point of view, this is bound to (1) stay for 
quite a while, and (2) give many people (especially those depending on 
functional code written by that fraction of imperative programmers that 
have problems adjusting to abstract ideas, I fear) a major headache 
during the next thirty years.


Coming back to the original question, which was whether one may "just 
stick in some monadic stuff to get a notion of an `environment'", I'm 
inclined to say that from the purely functional point of view, this 
perhaps is not a good idea, as this is not just "a minor change to the 
code" but changes pretty much anything of its original properties.


-- 
regards,               tf@cip.physik.uni-muenchen.de              (o_
 Thomas Fischbacher -  http://www.cip.physik.uni-muenchen.de/~tf  //\
(lambda (n) ((lambda (p q r) (p p q r)) (lambda (g x y)           V_/_
(if (= x 0) y (g g (- x 1) (* x y)))) n 1))                  (Debian GNU)


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

* Re: [Caml-list] environment idiom
  2004-12-13 10:05                               ` Michael Walter
@ 2004-12-13 10:29                                 ` Thomas Fischbacher
  2004-12-13 21:16                                   ` Michael Walter
  0 siblings, 1 reply; 57+ messages in thread
From: Thomas Fischbacher @ 2004-12-13 10:29 UTC (permalink / raw)
  To: Michael Walter; +Cc: Jacques Garrigue, caml-list


On Mon, 13 Dec 2004, Michael Walter wrote:

> No, besides referential transparency having a definite technical
> meaning, you can clearly see what you are getting by simply looking at
> the type (IO Int).

Hm, I think Klaus would strongly object to any statement of the form

> you can clearly see what you are getting by simply looking at
> the type (IO Int).

as every type will contain junk:

  (x::IO Int) where x = x >>= return

-- 
regards,               tf@cip.physik.uni-muenchen.de              (o_
 Thomas Fischbacher -  http://www.cip.physik.uni-muenchen.de/~tf  //\
(lambda (n) ((lambda (p q r) (p p q r)) (lambda (g x y)           V_/_
(if (= x 0) y (g g (- x 1) (* x y)))) n 1))                  (Debian GNU)


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

* Re: [Caml-list] environment idiom
  2004-12-13  8:37               ` Thomas Fischbacher
@ 2004-12-13 10:53                 ` skaller
  2004-12-13 11:38                   ` Martin Berger
  2004-12-13 12:01                   ` Thomas Fischbacher
  0 siblings, 2 replies; 57+ messages in thread
From: skaller @ 2004-12-13 10:53 UTC (permalink / raw)
  To: Thomas Fischbacher; +Cc: Markus Mottl, Andrej Bauer, caml-list

On Mon, 2004-12-13 at 19:37, Thomas Fischbacher wrote:

> I think you do not yet fully appreciate the key point concerning the 
> monadic approach.

I think most of the theoreticians don't either.

> Or in still other words: could you please show me a piece of haskell 
> code that uses monads but is not referentially transparent (assuming you 
> do not use "unofficial" features such as, in particular, unsafePerformIO)?

I can't do enough Haskell yet, give me a few days :)

Consider this language:

	Registers R0-R15,PC
	Three address form: R1=R2 op R3
	Some conditionals ..

I.e. a simplified Assembler.

Is assmebler code functional?

No of course not!

Yes of course it is! Is is nothing more
than a function from registers to registers where
the instructions guarrantee you can't access the prior state.
That's just the state monad .. :)

The point really is: what do you mean by purely functional?
I think the answer depends on context.

I'm sure you can implement this machine using the ST monad...

-- 
John Skaller, mailto:skaller@users.sf.net
voice: 061-2-9660-0850, 
snail: PO BOX 401 Glebe NSW 2037 Australia
Checkout the Felix programming language http://felix.sf.net




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

* Re: [Caml-list] environment idiom
  2004-12-13 10:53                 ` skaller
@ 2004-12-13 11:38                   ` Martin Berger
  2004-12-13 13:33                     ` skaller
  2004-12-13 12:01                   ` Thomas Fischbacher
  1 sibling, 1 reply; 57+ messages in thread
From: Martin Berger @ 2004-12-13 11:38 UTC (permalink / raw)
  To: skaller, caml-list

it is quite simple: of course the monadic IO that has been discussed
has side-effects. hence it is not funcitonal. but -- and that's a big
but -- what the monadic types do is: LIMIT composability in a way that
no typable context can OBSERVE the statefulness of the monadic code.
an external observer, not bound to the typing discipline, can observe
the stateful behaviour.

more generally: the question of whether a code fragment is  functional
or not is meaningless without specifying the class of admissable
observations, i.e. the class of admissible context. any programming
language becomes functional for example if the class of contexts is
generated by

    C[.] ::= SKIP | x := n | [.]

or something silly like that.

martin


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

* Re: [Caml-list] environment idiom
  2004-12-13  8:56                           ` Thomas Fischbacher
  2004-12-13  9:21                             ` Jacques Garrigue
  2004-12-13 10:11                             ` Michael Walter
@ 2004-12-13 11:46                             ` skaller
  2 siblings, 0 replies; 57+ messages in thread
From: skaller @ 2004-12-13 11:46 UTC (permalink / raw)
  To: Thomas Fischbacher; +Cc: Michael Walter, caml-list

On Mon, 2004-12-13 at 19:56, Thomas Fischbacher wrote:
> On Sun, 12 Dec 2004, Michael Walter wrote:
> 
> > Again I believe we are talking about different kinds of "purity".
> > Thomas is obviously right in that the StateTransformer monad (modulo
> > unsafe conversions) is pure, you are obviously right in the
> > (different) point that _running_ an IO fragment has side effects.
> 
> The key issue is: by not doing I/O, but talking about plans how to do I/O, 
> you go to a higher level of abstraction that allows you to do magic with 
> such plans which you just plainly miss if you only know the imperative 
> ways. It's just like everyone knows how to add (i.e. arithmetics), but 
> once you learned to talk about properties of addition (i.e. algebra), you 
> have a much richer point of view that allows you to do quite miraculous 
> things.
> 
> Of course, it's possible to just forget about all that and fall back to 
> transliterating imperative code to IO monad code,

Right. So, how can you distinguish these two ways of programming?

I'm not claiming purity, transparency, or monads are bad,
contrarily it's great stuff! But as usual, with greater power
you lose something.

> It's just the same with Haskell and the IO monad.

So again the question is -- can you *characterise* better,
the good uses and the bad ones? Perhaps you can do this
by examining the higher order abstraction being implemented
and see if that is transparent or not?

With Haskell you have a *formalised* system for building
combinators (unlike Ocaml where you can still make them,
but it's a technique, not a language feature).

Given that you can probably formalise the properties
of the machinery you can build with them. The ST monad
is so powerful it provides a general way to do procedural
programming .. IMHO that isn't at all bad. Not all procedural
code is bad :) But the same caveats probably apply to both
ordinary procedural code and a monadic version.

The main diffence is probably that *todays* Haskell programmers
will probably use the monad sparingly, making as much code
ordinary functional code as possible.

But if you go around yelling 'FP is the magic bullet'
and then 'Haskell can do procedural programming too -- but
it is magical, when you do it is makes procedural code
referentially transparent' .. then what happens?

You'll get people that literally translate C code into
ST monadic Haskell mechanically and claim their code
is better now .. :)

Anyhow I don't wish to argue that monads or FP is bad,
contrarily, I would like to learn more how to properly
characterise properties like transparency -- the ST monad
(and IO) clearly show that you can simultaneously have
and not have transparency, purity, etc depending on 
your view. So perhaps you can help define what I mean
by view .. because I only have a vague intuition what
it means.

-- 
John Skaller, mailto:skaller@users.sf.net
voice: 061-2-9660-0850, 
snail: PO BOX 401 Glebe NSW 2037 Australia
Checkout the Felix programming language http://felix.sf.net




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

* Re: [Caml-list] environment idiom
  2004-12-13 10:53                 ` skaller
  2004-12-13 11:38                   ` Martin Berger
@ 2004-12-13 12:01                   ` Thomas Fischbacher
  2004-12-13 13:41                     ` skaller
  1 sibling, 1 reply; 57+ messages in thread
From: Thomas Fischbacher @ 2004-12-13 12:01 UTC (permalink / raw)
  To: skaller; +Cc: Markus Mottl, Andrej Bauer, caml-list


On Mon, 13 Dec 2004, skaller wrote:

> I.e. a simplified Assembler.
> 
> Is assmebler code functional?
> 
> No of course not!
> 
> Yes of course it is! Is is nothing more
> than a function from registers to registers where
       ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
> the instructions guarrantee you can't access the prior state.
  ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
> That's just the state monad .. :)

That's not quite how I would describe the state monad to work.

However solid the mental picture which you have of a brick may be,
you will not be able to hit real people with it as with a real brick. You 
can, of course, have a solid mental picture of solidly hitting real people 
with a solid real brick. This transformation of "mental picture of a solid 
brick" to "real brick in a mental picture of something that involves a 
brick" is just monadic binding.

I know all this may sound a bit hairsplitting, but it is precisely the 
necessity of this hairsplitting that makes it so difficult for beginners 
that have been poisoned by the imperative side of the force(TM) to get the 
idea behind the monadic approach.

Back to the question:

> Is assmebler code functional?

After all, "code" can mean very different things here: a string that can 
be parsed in a given grammar, a sequence of instructions that are to be 
fed into a processor, an actually running programm, etc. Some people work 
hard to get the fine distinctions one has to make here into other people's 
heads. My impression is that your statements just work against these 
distinctions other people try to establish.


> The point really is: what do you mean by purely functional?
> I think the answer depends on context.

I think the answer depends on properly wording the question!

Can one express transformations on sequences of machine instructions in a 
functional language? ("Language" in the much broader sense than just 
"functional programming language, especially haskell"; rather: "using 
proper mathematical reasoning".) Sure, and this is in many aspects 
perhaps the best way to talk about such transformations.

Do sequences of machine instructions of the type

   Ra = foo Rb Rc

respect some "naive" substitution properties like e.g.

   Ra = foo Rb Rc
   Ra = foo Rb Rc
-->
   Ra = foo Rb Rc

The answer is, of course, that no one would expect this.

These questions could not be any more different! What irks me is when such 
very different things are subsumed under a statement of the form "depends 
whether you ask this question in the outer or inner context". As it is a 
very different question you are asking! It does not depend on "context", 
but actually on the meaning you connect with the words which you use.

So, can one do array mutation in haskell? Certainly not. Can one use 
haskell to talk about doing array mutations? For sure. But nothing more. 
Well, systems like hugs will actually behave in funny ways if especially 
plans to do IO appear in certain magical places, but this is an entirely 
different story.



My point is that with statements like

> Yes, that indeed is my intention. Basically, any non-transparent
                                               ^^^^^^^^^^^^^^^^^^^
> non-function code can be made purely functional and transparent
  ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
> with a simple transformation, yet it doesn't by this transformation
  ^^^^^^^^^^^^^^^^^^^^^^^^^^^^
> get any easier to reason about the code.

you are trying to "hit real people with mental bricks".


> I'm sure you can implement this machine using the ST monad...

I'm sure you can even do without. :-)

-- 
regards,               tf@cip.physik.uni-muenchen.de              (o_
 Thomas Fischbacher -  http://www.cip.physik.uni-muenchen.de/~tf  //\
(lambda (n) ((lambda (p q r) (p p q r)) (lambda (g x y)           V_/_
(if (= x 0) y (g g (- x 1) (* x y)))) n 1))                  (Debian GNU)


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

* Re: [Caml-list] environment idiom
  2004-12-13 10:20                               ` Thomas Fischbacher
@ 2004-12-13 12:09                                 ` Jacques Garrigue
  2004-12-13 12:48                                   ` Thomas Fischbacher
  2004-12-13 14:09                                   ` skaller
  2004-12-13 13:22                                 ` skaller
  1 sibling, 2 replies; 57+ messages in thread
From: Jacques Garrigue @ 2004-12-13 12:09 UTC (permalink / raw)
  To: Thomas.Fischbacher; +Cc: caml-list

From: Thomas Fischbacher <Thomas.Fischbacher@Physik.Uni-Muenchen.DE>
> On Mon, 13 Dec 2004, Jacques Garrigue wrote:
> 
> > > Of course, it's possible to just forget about all that and fall back to 
> > > transliterating imperative code to IO monad code, but it is just as well 
> > > possible to find the sum of all the numbers from 1 to 1000 using the 
> > > following piece of Maple code:
> > 
> > You make me curious. Most of the code I've seen using the IO monad (or
> > the state transformer monad) was just transliterating imperative to
> > monadic code. Of course using closures, but not that much, and you can
> > certainly do that in an impure functional language also.
> 
> First, I should perhaps mention that in my point of view, John does have a 
> valid point in what he says. It's only that he expressed it in a way I 
> just *cannot* agree with.

OK, so probably we almost agree.
Three days ago I was about to answer John that indeed he has a good
point, but he seems to ignore completely the other advantages of
monads, like the fact you can cleanly mix stateful code with pure
code, keeping the two separate.

> > So what is so incredible about the IO monad?
> 
> There is nothing "in-credible" about it. It is just plainly nothing else 
> as working with values that describe "plans" to do IO. We do have a magic 
> place that can bring such plans to life, causing them to be executed, but 
> from the pure Haskell point of view this is not relevant. All we do is to 
> construct plans how to do IO.

So maybe the problem goes back to the compositional vs. pointwise view
of things. While the compositional view is nice, at some level of
detail I find it simpler to reason pointwise (even when purely
functional).
My real curiosity was about the kind of compositional abstractions one
would use with stateful computations. It seems to me that the presence
of state itself makes it more difficult to compose cleanly. At least,
types help you less: they let you now that there is state around, but
not the detail of how this state is used (maybe I'm not up-to-date
with recent Haskell.)

> > Of course according to your definition this contains nothing that is
> > not referentially transparent once you've taken the syntactic sugar.
> 
> Precisely. To go a bit more into detail:

No need to explain: I know this is referentially transparent :-)
My only point was that it doesn't _look_ so.

> In a certain sense, this "do" notation - which is NOT a special extension 
> of the powers of pure, functional haskell but only a short-hand notation 
> for things that can be spelled out explicitly - is "poison" that allows 
> one to "just hack one's imperative thoughts into haskell without 
> even having know about the abstract point of view". This is a bit like 
> FORTRAN programmers asked to adjust themselves to C showing the attitude 
> that "at least, they can forget all that for/while/etc. mumbo-jumbo and 
> do everything with goto, as they are used to".

I wonder whether this is really so.
Some programs without the do notation would be much harder to read.
Do you really think they can all be rewritten to cleaner alternative
code?

> Coming back to the original question, which was whether one may "just 
> stick in some monadic stuff to get a notion of an `environment'", I'm 
> inclined to say that from the purely functional point of view, this 
> perhaps is not a good idea, as this is not just "a minor change to the 
> code" but changes pretty much anything of its original properties.

Having worked on parameterization systems a long time ago, I can only
agree.
The trouble with the monadic view of environment is that you quickly
end up making all your functions monadic, introducing some
sequentiality which may have no reason to be. While being no expert of
the question, this seems to be a tendency of monads: they are
so comfortable that they tend to pollute everything, diluting the
advantage of knowing exactly what is functional. But how can you stop
people from going the easy way?

       Jacques Garrigue


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

* Re: [Caml-list] environment idiom
  2004-12-13  9:29                       ` Michael Walter
@ 2004-12-13 12:30                         ` skaller
  2004-12-13 13:49                           ` Martin Berger
  0 siblings, 1 reply; 57+ messages in thread
From: skaller @ 2004-12-13 12:30 UTC (permalink / raw)
  To: Michael Walter; +Cc: William Lovas, caml-list

On Mon, 2004-12-13 at 20:29, Michael Walter wrote:

> What is "the detail level"? Like the "language level" in contrast to
> the level of the current abstraction (for instance, State monad)?

Yes, that's the idea.

> Different note: I think you are missing out an important property of
> the functional encoding, which is its purity wrt composability.

Oh no, I'm not missing that! I'm very happily missing
the ugly warts of C++ that *stop* me composing things
transparently! 

The fact that Ocaml (and Felix) still allow procedural
code means I'm not forced to use functional techniques,
but Ocaml at least doesn't prevent me .. and C++ certainly did.

> In constrast, in a language such as C++ you cannot assume that..
>   vector<unsigned> sieve(unsigned);
> has no side effects.

Indeed. I am not missing the advantages of transparency,
the point I'm making is that even in an FP, when you're
considering your code at a higher level than the ground
syntax .. you may still lose the functional nature and
its advantages.

To avoid that I want to know far more precisely how to
characterise things . I know what a function is, so the
problem is that I do NOT know exactly what 'code' is :)

> Also consider the "print" part of your algorithm, which I ignored so
> far. In C++ it would be very easy to add it to sieve() thus making the
> function virtually useless to use but in the special case where you
> want to print the number instantly.
> 
> In Haskell, you *could* have a sieve :: Integer -> IO [Integer], but
> what you would really do is to decouple the sieve and I/O 

And you'd do that in C++ too. Only it would be harder ..

> (and this is
> made kinda "attractive" by the expressiveness of the language and the
> type system). 

Yes. I'm not saying monads are bad or anything, I'm saying
that the dang things are so powerful there is danger of
just doing bad old procedural programming with them.

And conversely, people hyping FP like OO: I believe
a language has to support stateful and functional programming
in a balanced way. The fact this is NOT currently the case
is due to a deficiency of theory -- it isn't because FP
is intrinsically better (just that FP is better understood).


-- 
John Skaller, mailto:skaller@users.sf.net
voice: 061-2-9660-0850, 
snail: PO BOX 401 Glebe NSW 2037 Australia
Checkout the Felix programming language http://felix.sf.net




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

* Re: [Caml-list] environment idiom
  2004-12-13 12:09                                 ` Jacques Garrigue
@ 2004-12-13 12:48                                   ` Thomas Fischbacher
  2004-12-13 14:09                                   ` skaller
  1 sibling, 0 replies; 57+ messages in thread
From: Thomas Fischbacher @ 2004-12-13 12:48 UTC (permalink / raw)
  To: Jacques Garrigue; +Cc: caml-list


On Mon, 13 Dec 2004, Jacques Garrigue wrote:

> > In a certain sense, this "do" notation - which is NOT a special extension 
> > of the powers of pure, functional haskell but only a short-hand notation 
> > for things that can be spelled out explicitly - is "poison" that allows 
> > one to "just hack one's imperative thoughts into haskell without 
> > even having know about the abstract point of view".
>
> I wonder whether this is really so.
> Some programs without the do notation would be much harder to read.
> Do you really think they can all be rewritten to cleaner alternative
> code?

Deep in my stomach I have the feeling that precisely this is the case, and 
it might well involve some additional syntactic sugar. The problem is 
perhaps that the imperative way of coding - which (if we admit it) we all 
are at least somewhat used to - blocks our view onto more reasonable ways
to tackle this issue. As one says, a genius is someone who is the first to 
do something obvious in the right way, and it will perhaps take a genius 
to find the proper way to express IO plan composition in a strikingly 
beautiful way which in particular does not suffer from naive imperative 
mis-interpretation.

At present, it seems as if there were problems of both types: those where 
most of the desired functionality can be easily expressed in a purely 
functional way, which is hooked into an otherwise small IO plan, and those 
where a large and highly sophisticated IO plan makes use of only very 
few and small purely functional helpers. Somehow, this disparity "feels" 
quite strange.

These are just a few random thoughts on an issue that is perhaps not yet 
sufficiently well understood to reach a final conclusion. Considering that 
the monadic point of view only entered the scene quite recently, I hope 
that in a few years, we have a much better understanding of all these 
things.


-- 
regards,               tf@cip.physik.uni-muenchen.de              (o_
 Thomas Fischbacher -  http://www.cip.physik.uni-muenchen.de/~tf  //\
(lambda (n) ((lambda (p q r) (p p q r)) (lambda (g x y)           V_/_
(if (= x 0) y (g g (- x 1) (* x y)))) n 1))                  (Debian GNU)


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

* Re: [Caml-list] environment idiom
  2004-12-13  9:56                             ` Michael Walter
@ 2004-12-13 12:59                               ` skaller
  0 siblings, 0 replies; 57+ messages in thread
From: skaller @ 2004-12-13 12:59 UTC (permalink / raw)
  To: Michael Walter; +Cc: caml-list

On Mon, 2004-12-13 at 20:56, Michael Walter wrote:

> > Another example is my Felix language. It has both functions
> > and procedures. Functions aren't allowed to have side effects,
> > yet they're not pure in the sense the result can depend
> > on variables which change between (but not during) invocations.
> > [This has an alarming effect on the optimiser ..]
> Can I read about the reasoning behind this on felix.sf.net?

No, I haven't really spent enough time on documenting
rationale yet. At least one excuse is that the system
is experiemental, and another is that, in fact, this
particular division of labour proves to have a major
deficiency.

A crude reason is: procedures don't use the machine stack,
which is a requirement for the microthreading to work.
Felix can run 1Meg threads on a small Linux box with
O(1) context switching.

OTOH, I decided functions should not be allowed to have
side-effects, for the usual reasons: referential transparency,
optimisation, etc. But they use the machine stack: two reasons
being performance and ability to integrate with C code.

The problem is that side-effect free is only equal to
pure in the total absence of any procedural code.
Otherwise you have two kinds of functions -- pure ones
that don't look at variables, and dirty ones that do.

Dirty functions are of course quite useful -- accessors
for objects for example, and freedom from side-effects
is still useful. But I have to separate the two kinds
or the optimiser can't work, and I can't define any sane
semantics.

> > [...] Clearly you can reason about the
> > 'functional subsystem' using transparency, and then combine
> > the result with reasoning about the top level 'magic main'
> > where the program as a whole is not transparent ... and you still
> > have 'ease of reasoning' in the combination.
> Indeed (and Monads give you an attractive way to partly do this the
> other way around).

Yes Indeed!! Duality!

> Are there specific statements, for instance on the Haskell home page,
> which you dislike? 

I haven't looked :)

> Or do you dislike that fact that for instance in
> the statement "Monads allow for sideeffect free encoding of stateful
> computations" everyone is assuming that "encoding" refers to the
> encoding in the target language?

Yes, that's roughly the thing. The point being that this
really isn't enough. 

The problem isn't isolated to monads. That's only
syntactic sugar after all -- the issue relates to 
*all* functional programming, it's just clearer
to see with monads, particularly if you compare
monadic code with a more conventional interpreter
(eg a Haskell interpreter for Perl .. when you 
execute the Perl is it functional or procedural).

The thing is that high level language are 'just syntactic
sugar' for assembler .. the point being it just isn't
enough to talk about 'the program is functional', 
rather you need to say 'the encoding is functional
at the Haskell level and also at the first major
abstraction level but stateful at the third level'
or something like that .. and the question is,
how should I *really* say that?
.
> Okay, I was thinking (along the lines of the paragraph above) that you
> were unhappy about the way that people are talking about monads.

I am, because it confuses me! Their claims are clearly
both right and wrong! But I don't have the intellectual
apparatus to explain how this can be precisely.

Or even crudely :)

> Okay. So far I have never been confused by such statements about
> monads -- it was usually pretty clear what "pure" was referring to 

Yeah, but that's the problem: the implication is that
it is enough to just refer to the detail level.

But that isn't so, because a heavy user of the ST monad
might just as well stick with C. They may think they're
gaining something that they're not gaining.

But there is a converse! Not all stateful code
is hard to reason about. In fact by duality,
some ways of stateful programming -- yet to be understood --
are just as good as functional coding.

Which ones? I don't know but monads seem to offer clue!
Crudely, if your stateful program is turned into a Haskell
one using 'the least possible ST monadic code', your program
is probably sweet. You were probably emulating functional
code in procedural code :))

-- 
John Skaller, mailto:skaller@users.sf.net
voice: 061-2-9660-0850, 
snail: PO BOX 401 Glebe NSW 2037 Australia
Checkout the Felix programming language http://felix.sf.net




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

* Re: [Caml-list] environment idiom
  2004-12-13 10:20                               ` Thomas Fischbacher
  2004-12-13 12:09                                 ` Jacques Garrigue
@ 2004-12-13 13:22                                 ` skaller
  2004-12-13 16:54                                   ` Marcin 'Qrczak' Kowalczyk
  2004-12-13 18:44                                   ` Thomas Fischbacher
  1 sibling, 2 replies; 57+ messages in thread
From: skaller @ 2004-12-13 13:22 UTC (permalink / raw)
  To: Thomas Fischbacher; +Cc: Jacques Garrigue, caml-list

On Mon, 2004-12-13 at 21:20, Thomas Fischbacher wrote:


> Referential transparency is about the substitution of definitions. 
> Evidently, x <- ... is _not_ a definition. 

But this is a bit circular. It is suspect to use the Haskell
definition of 'definition' and then say Haskell is referentially
transparent, a property depending on the definition of 'definition',
because you cannot apply that definition to any other language.

C also has 'definitions' but they're not at all the same
as Haskell ones.

When I first read the text of Barbara Liskov's Substitution
Principle I fell over laughing. The text makes so many
assumptions about the kind of language it is dealing
with it is useless. You could rewrite it for C++,
using *initialisation* instead of substitution, for example.

So when you're looking at monadic Haskell that contains

	x <- ...

you can claim it isn't a definition.. but it surely
looks like one.. more precisely it looks like an assignment.

It's like me trying to argue -- repeatedly and heatedly --
that no matter what the C++ Standard says, there is no
such type as 'const int'. There really isn't <g> even though
the grammar has a production which makes that a valid type
specifier it doesn't denote a type distinct from int.
Of course people argued I was wrong -- the Standard said so.

> The notion of "substitution" of course only makes sense for this 
> "official" form. 

Right. But consider for a moment a meta-system with
enough well thought out sugar that it had a calculus
of its own. Just because the reduced form is transparent
doesn't mean the sugar calculus is.

I guess that's my point, badly stated. The sugar level *counts*.
Just as Haskell counts, even though GHC generates C which generates
assembler .. semantics and its relation to syntax -- such as
exhibited by the referential transparency property of purely
functional code appears to be a 'multilevel' phenomena.

> This is a bit like 
> FORTRAN programmers asked to adjust themselves to C showing the attitude 
> that "at least, they can forget all that for/while/etc. mumbo-jumbo and 
> do everything with goto, as they are used to".

Good point.

> Coming back to the original question, which was whether one may "just 
> stick in some monadic stuff to get a notion of an `environment'", I'm 
> inclined to say that from the purely functional point of view, this 
> perhaps is not a good idea, as this is not just "a minor change to the 
> code" but changes pretty much anything of its original properties.

However clearly the ST monad is sometimes useful.. 
can you explain when that is?

-- 
John Skaller, mailto:skaller@users.sf.net
voice: 061-2-9660-0850, 
snail: PO BOX 401 Glebe NSW 2037 Australia
Checkout the Felix programming language http://felix.sf.net




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

* Re: [Caml-list] environment idiom
  2004-12-13 11:38                   ` Martin Berger
@ 2004-12-13 13:33                     ` skaller
  0 siblings, 0 replies; 57+ messages in thread
From: skaller @ 2004-12-13 13:33 UTC (permalink / raw)
  To: Martin Berger; +Cc: caml-list

On Mon, 2004-12-13 at 22:38, Martin Berger wrote:
> it is quite simple: of course the monadic IO that has been discussed
> has side-effects. hence it is not funcitonal. but -- and that's a big
> but -- what the monadic types do is: LIMIT composability in a way that
> no typable context can OBSERVE the statefulness of the monadic code.
> an external observer, not bound to the typing discipline, can observe
> the stateful behaviour.

AH! Thank you. No *typable* context can *observe*...

Now we're getting closer to a more general characterisation...

> more generally: the question of whether a code fragment is  functional
> or not is meaningless without specifying the class of admissable
> observations,

Yay! Yes! Spot on! <lol>


-- 
John Skaller, mailto:skaller@users.sf.net
voice: 061-2-9660-0850, 
snail: PO BOX 401 Glebe NSW 2037 Australia
Checkout the Felix programming language http://felix.sf.net




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

* Re: [Caml-list] environment idiom
  2004-12-13 12:01                   ` Thomas Fischbacher
@ 2004-12-13 13:41                     ` skaller
  0 siblings, 0 replies; 57+ messages in thread
From: skaller @ 2004-12-13 13:41 UTC (permalink / raw)
  To: Thomas Fischbacher; +Cc: Markus Mottl, Andrej Bauer, caml-list

On Mon, 2004-12-13 at 23:01, Thomas Fischbacher wrote:

> > The point really is: what do you mean by purely functional?
> > I think the answer depends on context.
> 
> I think the answer depends on properly wording the question!

Of course :) I hardly need to point out that in all likelihood
if I could do that, I'd probably already know the answer :)

> My point is that with statements like
> 
> > Yes, that indeed is my intention. Basically, any non-transparent
>                                                ^^^^^^^^^^^^^^^^^^^
> > non-function code can be made purely functional and transparent
>   ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
> > with a simple transformation, yet it doesn't by this transformation
>   ^^^^^^^^^^^^^^^^^^^^^^^^^^^^
> > get any easier to reason about the code.
> 
> you are trying to "hit real people with mental bricks".

LOL! Over the Internet too :)

-- 
John Skaller, mailto:skaller@users.sf.net
voice: 061-2-9660-0850, 
snail: PO BOX 401 Glebe NSW 2037 Australia
Checkout the Felix programming language http://felix.sf.net




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

* Re: [Caml-list] environment idiom
  2004-12-13 12:30                         ` skaller
@ 2004-12-13 13:49                           ` Martin Berger
  0 siblings, 0 replies; 57+ messages in thread
From: Martin Berger @ 2004-12-13 13:49 UTC (permalink / raw)
  To: skaller; +Cc: caml-list

> To avoid that I want to know far more precisely how to
> characterise things . I know what a function is, so the
> problem is that I do NOT know exactly what 'code' is :)

in my opinion, what you want can only been obtained -- and has
been obtained by now -- when you leave functional thinking
behind. the problem with functional thinking, and there are
good historical and sociological reasons for its preponderance,
is that it starts from functional behaviour, realises that
there's certain areas it cannot adequatly deal with (eg state,
jumps and concurrency) and adds them as an afterthough later,
for example by way of monads.

we know much better now that concurrency is indeed fundamental
and state, jumps and functional behaviour are but well
behaved special cases of concurrency. The good thing is that these
very well behaved special cases of concurrency can be characterised
by types and the types for the functional fragment of concurrency
stand out in that they are the only known types where every type is
either a data flow source or a data flow sink. this is at the heart
of why functional programming is much easier than stateful programming,
but also the cause of its limitations.

this viewpoint has been explored powerfully in

   Noninterference through Flow Analysis
   http://www.doc.ic.ac.uk/~yoshida/paper/noninterference.ps

this new typing discipline and its refinemend into types for secure
information flow give a very finegrained partitioning of programs
into parts that depend or do not depend on each other, but in a unified
way. the degree of finegrainedness can be tune to the programmer's needs
by the choice of security lattice (although speaking about security in
this context maybe a bit misleading as it's really about uniform
type-based specifications of program dependencies). This is very
powerful and has been applied to a wide range of language in

   A Uniform Type Structure for Secure Information Flow
   http://www.doc.ic.ac.uk/~yoshida/paper/ifa_long.ps

Francois Potter and Vincent Simonet have applied some of these ideas to ML, cf

   Information flow inference for ML
   http://pauillac.inria.fr/~fpottier/publis/fpottier-simonet-toplas.ps.gz

so these ideas are beginning to trickle down, but it's still mostly on the
drawing board.

martin


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

* Re: [Caml-list] environment idiom
  2004-12-13 12:09                                 ` Jacques Garrigue
  2004-12-13 12:48                                   ` Thomas Fischbacher
@ 2004-12-13 14:09                                   ` skaller
  2004-12-13 21:39                                     ` Michael Walter
  1 sibling, 1 reply; 57+ messages in thread
From: skaller @ 2004-12-13 14:09 UTC (permalink / raw)
  To: Jacques Garrigue; +Cc: Thomas.Fischbacher, caml-list

On Mon, 2004-12-13 at 23:09, Jacques Garrigue wrote:
> From: Thomas Fischbacher <Thomas.Fischbacher@Physik.Uni-Muenchen.DE>

> OK, so probably we almost agree.
> Three days ago I was about to answer John that indeed he has a good
> point, but he seems to ignore completely the other advantages of
> monads, like the fact you can cleanly mix stateful code with pure
> code, keeping the two separate.

I'm ignoring them only in the sense this particular discussion
isn't about that.

> My real curiosity was about the kind of compositional abstractions one
> would use with stateful computations. It seems to me that the presence
> of state itself makes it more difficult to compose cleanly.

I would contend that is just a lack of theoretical understanding
of how to do stateful programming.

If you consider streams, and more generally, coinductive 
types to be stateful, then you can look at a
symmetrical integration of the two concepts in a 
programming language -- Google for Charity.

The language is weak -- functions aren't first class and it
isn't Turing complete, but on the flip side all Charity
programs are sure to terminate.

>  While being no expert of
> the question, this seems to be a tendency of monads: they are
> so comfortable that they tend to pollute everything, diluting the
> advantage of knowing exactly what is functional. But how can you stop
> people from going the easy way?

You already know the answer I suspect -- better theory.
It's one thing, for example, to find an FP is easier to use,
and then to learn the superior compositional properties
are the reason, and they depend on transparency .. but another
to finally see a *theoretical* account of why this is so.
This makes it easier to calculate a good solution where
previously it looked hard -- i.e. you can't stop people
going the easy way, so make the right way easier :)

[BTW: Isn't Haskell slated to get Arrows to replace monads?]

-- 
John Skaller, mailto:skaller@users.sf.net
voice: 061-2-9660-0850, 
snail: PO BOX 401 Glebe NSW 2037 Australia
Checkout the Felix programming language http://felix.sf.net




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

* Re: [Caml-list] environment idiom
  2004-12-13 13:22                                 ` skaller
@ 2004-12-13 16:54                                   ` Marcin 'Qrczak' Kowalczyk
  2004-12-13 18:44                                   ` Thomas Fischbacher
  1 sibling, 0 replies; 57+ messages in thread
From: Marcin 'Qrczak' Kowalczyk @ 2004-12-13 16:54 UTC (permalink / raw)
  To: caml-list

skaller <skaller@users.sourceforge.net> writes:

>> Referential transparency is about the substitution of definitions. 
>> Evidently, x <- ... is _not_ a definition. 
>
> But this is a bit circular.

But it's true. Referential transparency is relative to what is
considered a definition. It's not an absolute property if we don't
agree about the mapping between abstract concepts like "definition"
or "equality" and the features visible in the language.

Similarly, whether a function is considered pure depends on what do we
mean to "apply" a function, and what is a "side effect". For example
Haskell IO actions don't break purity if we consider Haskell's
function application as the operation which determines purity, but
they are impure if we treat IO and functions together. And a function
which returns a modified state is pure if we treat the state as one of
the arguments and a part of the result, yet it's impure if we consider
only other arguments as "real" arguments and treat state threading as
a part of the calling protocol. It's all relative.

-- 
   __("<         Marcin Kowalczyk
   \__/       qrczak@knm.org.pl
    ^^     http://qrnik.knm.org.pl/~qrczak/


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

* Re: [Caml-list] environment idiom
  2004-12-13 13:22                                 ` skaller
  2004-12-13 16:54                                   ` Marcin 'Qrczak' Kowalczyk
@ 2004-12-13 18:44                                   ` Thomas Fischbacher
  1 sibling, 0 replies; 57+ messages in thread
From: Thomas Fischbacher @ 2004-12-13 18:44 UTC (permalink / raw)
  To: skaller; +Cc: Jacques Garrigue, caml-list


> On Mon, 2004-12-13 at 21:20, Thomas Fischbacher wrote:
> 
> 
> > Referential transparency is about the substitution of definitions. 
> > Evidently, x <- ... is _not_ a definition. 
> 
> But this is a bit circular. It is suspect to use the Haskell
> definition of 'definition' and then say Haskell is referentially
> transparent, a property depending on the definition of 'definition',
> because you cannot apply that definition to any other language.

Haskell differs from other languages in the one important point that 
Haskell definitions have all the properties of what a mathematician
would call a definition (maybe mod typeclass subtleties).

And this is what referential transparency is about: is the notion of 
"definition" that a programming language gives you just the same as that 
in mathematics or not?

> C also has 'definitions' but they're not at all the same
> as Haskell ones.

Precisely. And they do not behave like mathematical definitions, so C is 
not reftransparent.

> So when you're looking at monadic Haskell that contains
> 
> 	x <- ...
> 
> you can claim it isn't a definition.. but it surely
> looks like one.. more precisely it looks like an assignment.

Well, the C statement

 x=x+1;

may also look like an equation to the uninitiated, but everyone would 
perhaps agree with me that this is just a misinterpretation of symbols.

> However clearly the ST monad is sometimes useful.. 
> can you explain when that is?

Good question...

-- 
regards,               tf@cip.physik.uni-muenchen.de              (o_
 Thomas Fischbacher -  http://www.cip.physik.uni-muenchen.de/~tf  //\
(lambda (n) ((lambda (p q r) (p p q r)) (lambda (g x y)           V_/_
(if (= x 0) y (g g (- x 1) (* x y)))) n 1))                  (Debian GNU)


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

* Re: [Caml-list] environment idiom
  2004-12-13 10:29                                 ` Thomas Fischbacher
@ 2004-12-13 21:16                                   ` Michael Walter
  0 siblings, 0 replies; 57+ messages in thread
From: Michael Walter @ 2004-12-13 21:16 UTC (permalink / raw)
  To: Thomas Fischbacher; +Cc: Jacques Garrigue, caml-list

On Mon, 13 Dec 2004 11:29:05 +0100 (CET), Thomas Fischbacher
> Hm, I think Klaus would strongly object to any statement of the form
> 
> > you can clearly see what you are getting by simply looking at
> > the type (IO Int).
> 
> as every type will contain junk:
> 
>   (x::IO Int) where x = x >>= return
Sure. You can include the "junk" into your reasoning (and also take
the fact that you might never actually get anything into account).

Anyway, my statement was more of a pun at the WYSIWYG mentioned by the
poster I was replying to, than a definite theoretical statement.

Cheers,
Michael


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

* Re: [Caml-list] environment idiom
  2004-12-13 14:09                                   ` skaller
@ 2004-12-13 21:39                                     ` Michael Walter
  0 siblings, 0 replies; 57+ messages in thread
From: Michael Walter @ 2004-12-13 21:39 UTC (permalink / raw)
  To: skaller; +Cc: Jacques Garrigue, Thomas.Fischbacher, caml-list

On 14 Dec 2004 01:09:57 +1100, skaller <skaller@users.sourceforge.net> wrote:
> [BTW: Isn't Haskell slated to get Arrows to replace monads?]
It's more generalization than replacement.

Good morning-ly yours,
Michael


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

end of thread, other threads:[~2004-12-13 21:39 UTC | newest]

Thread overview: 57+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2004-12-09  2:07 environment idiom HENRIKSON, JEFFREY
2004-12-09  4:47 ` [Caml-list] " Jacques Garrigue
2004-12-09  6:02   ` Michael Walter
2004-12-09 11:28     ` Jacques Garrigue
2004-12-09 20:02     ` pad
2004-12-09 23:11       ` Jacques Garrigue
2004-12-10  2:30         ` skaller
2004-12-09  9:09 ` Richard Jones
2004-12-09 13:12   ` [Caml-list] " Ville-Pertti Keinonen
2004-12-10 11:59     ` Richard Jones
2004-12-10 10:52 ` [Caml-list] " Andrej Bauer
2004-12-10 12:13   ` Richard Jones
2004-12-10 23:35     ` Jacques Garrigue
2004-12-11  2:30   ` skaller
2004-12-11 14:31     ` Andrej Bauer
2004-12-11 18:13       ` Markus Mottl
2004-12-11 23:56         ` skaller
2004-12-12  2:36           ` William Lovas
2004-12-12  5:33             ` skaller
2004-12-12 19:09               ` Michael Walter
2004-12-13  0:48                 ` skaller
2004-12-13  2:03                   ` Michael Walter
2004-12-13  2:05                     ` Michael Walter
     [not found]                       ` <877e9a170412121844b633bb8@mail.gmail.com>
2004-12-13  2:45                         ` Michael Walter
2004-12-13  6:18                           ` skaller
2004-12-13  7:08                             ` skaller
2004-12-13  9:56                             ` Michael Walter
2004-12-13 12:59                               ` skaller
2004-12-13  8:56                           ` Thomas Fischbacher
2004-12-13  9:21                             ` Jacques Garrigue
2004-12-13 10:05                               ` Michael Walter
2004-12-13 10:29                                 ` Thomas Fischbacher
2004-12-13 21:16                                   ` Michael Walter
2004-12-13 10:20                               ` Thomas Fischbacher
2004-12-13 12:09                                 ` Jacques Garrigue
2004-12-13 12:48                                   ` Thomas Fischbacher
2004-12-13 14:09                                   ` skaller
2004-12-13 21:39                                     ` Michael Walter
2004-12-13 13:22                                 ` skaller
2004-12-13 16:54                                   ` Marcin 'Qrczak' Kowalczyk
2004-12-13 18:44                                   ` Thomas Fischbacher
2004-12-13 10:11                             ` Michael Walter
2004-12-13 11:46                             ` skaller
2004-12-13  5:41                     ` skaller
2004-12-13  9:29                       ` Michael Walter
2004-12-13 12:30                         ` skaller
2004-12-13 13:49                           ` Martin Berger
2004-12-12 23:03           ` Thomas Fischbacher
2004-12-13  1:26             ` skaller
2004-12-13  8:37               ` Thomas Fischbacher
2004-12-13 10:53                 ` skaller
2004-12-13 11:38                   ` Martin Berger
2004-12-13 13:33                     ` skaller
2004-12-13 12:01                   ` Thomas Fischbacher
2004-12-13 13:41                     ` skaller
2004-12-11 23:29       ` skaller
2004-12-12  0:21         ` Jacques Carette

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