ML programmers often use nested auxiliary functions or separate functions to
handle base cases. For example, writing rev in terms of rev_append:
# let rec rev_append l1 l2 = match l1 with
| [] -> l2
| a :: l -> rev_append l (a :: l2);;
val rev_append : 'a list -> 'a list -> 'a list = <fun>
# let rev l = rev_append l [];;
val rev : 'a list -> 'a list = <fun>
Provided performance is unimportant, you can make the accumulator implicit in
OCaml by specifying the default value in an optional argument instead of
having a separate function:
# let rec rev ?(back=[]) = function
| [] -> back
| h::t -> rev ~back:(h::back) t;;
val rev : ?back:'a list -> 'a list -> 'a list = <fun>
When you don't want the auxiliary (rev_append) function, I think this style
results in shorter and clearer code. I used it in the "search" function of my
Sudoku solver, for example:
let rec search ?(x=0) ?(y=0) f accu = match x, y with
9, y -> search ~x:0 ~y:(y+1) f accu (* Next row *)
| 0, 9 -> f accu (* Found a solution *)
| x, y ->
if m.(y).[x] <> '0' then search ~x:(x+1) ~y f accu else
fold (fun accu n ->
let n = Char.chr (n + 48) in
if invalid x y n then accu else
(m.(y).[x] <- n;
let accu = search ~x:(x+1) ~y f accu in
m.(y).[x] <- '0';
accu)) accu 1 10
and it crops up quite a lot in addition to all of the "conventional" uses of
optional arguments.
--
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
The OCaml Journal
http://www.ffconsultancy.com/products/ocaml_journal/?e
_______________________________________________
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
>
> I can't find the thread where we were talking about design patterns
> recently
> but I'd like to note a design pattern that works nicely in OCaml.
> I'll call
> it "The Implicit Accumulator".
>
> ML programmers often use nested auxiliary functions or separate
> functions to
> handle base cases. For example, writing rev in terms of rev_append:
>
> # let rec rev_append l1 l2 = match l1 with
> | [] -> l2
> | a :: l -> rev_append l (a :: l2);;
> val rev_append : 'a list -> 'a list -> 'a list = <fun>
> # let rev l = rev_append l [];;
> val rev : 'a list -> 'a list = <fun>
>
> Provided performance is unimportant, you can make the accumulator
> implicit in
> OCaml by specifying the default value in an optional argument
> instead of
> having a separate function:
>
> # let rec rev ?(back=[]) = function
> | [] -> back
> | h::t -> rev ~back:(h::back) t;;
> val rev : ?back:'a list -> 'a list -> 'a list = <fun>
Could you be more specifics about the performance hit?
> When you don't want the auxiliary (rev_append) function, I think
> this style
> results in shorter and clearer code. I used it in the "search"
> function of my
> Sudoku solver, for example:
It's funny that you speak about this, because I recently (few days
ago) used
a pattern similar to yours, but to actually improve performances.
I had something like that (which is quite different than my actual
code, but
the idea is the same):
let encrypt str =
let len = String.length str in
let encrypted = String.create len in
(* ... *)
encrypted
(*...*)
for i = 0 to 10000000 do
let encrypted = encrypt str in
(* do something on the result *)
done
Which is slow due to the string allocation happening each time we
call "encrypt"
So I rewrote it like that:
let encrypt ?encrypted str =
let len = String.length str in
let result = match encrypted with
| None -> String.create len
| Some s -> s
in
(* ... *)
result
(* ... *)
let encrypted = String.create (String.length str) in
for i = 0 to 1000000000 do
let encrypted = encrypt ~encrypted str in
(* ... *)
done
Which gave me more than a 2x speedup while still being able to call a
simple:
let encrypted = encrypt str
during normal usage
I was quite happy with this solution, but maybe there is something
more elegant to do?
(I'm still in the process of learning good optimization patterns in
ocaml which preserve readability)
--
Best Regards,
Quôc
> It's funny that you speak about this, because I recently (few days ago)
> used
> a pattern similar to yours, but to actually improve performances.
> I had something like that (which is quite different than my actual
> code, but
> the idea is the same):
>
> let encrypt str =
> let len = String.length str in
> let encrypted = String.create len in
> (* ... *)
> encrypted
vs.
> let encrypt ?encrypted str =
> let len = String.length str in
> let result = match encrypted with
> | None -> String.create len
> | Some s -> s
> in
> (* ... *)
> result
> Which gave me more than a 2x speedup while still being able to call a
> simple:
> let encrypted = encrypt str
> during normal usage
I use this strategy a lot and found that it eventually pays to use
uniform conventions for that: all my functions that can benefit from
having space pre-allocated where to write a result to use ?target
as their very first named optional argument (and also return that
target buffer afterwards).
However, unless I am mistaken, I fear that this also does introduce
some intrinsic/unavoidable inefficiency, as providing a ?target
argument will (presuambly?) require dynamic consing of a <thingy>
option cell - so not a good idea for a very small function that is
called very very often.
There are many many way more advanced tricks one would want to play
with the idea of "allocating buffers at the appropriate time". For
example, if this were LISP, one could often use dynamically scoped (in
the sense of (declare (dynamic-extent buffer-stack))) contextual
variables for great benefit (and these gory details often can also be
hidden quite conveniently under a few (maybe even in-place macrolet)
macros...), but unfortunately, OCaml does not support anything like
that. Of course, re-entrantness of your code may always become an
issue if you move buffers to higher scopes.
One thing OCaml can do better than, say, CMU CL, is to define globally
visible functions that depend on some otherwise inaccessible context,
as in the following example:
let float_factorial =
let _known_factorials = ref [|1.0;1.0;2.0;6.0;24.0;120.0;720.0|] in
(fun n ->
let known_factorials = !_known_factorials in
let nr_known = Array.length known_factorials in
if n < nr_known
then
known_factorials.(n)
else
let new_known_factorials = Array.make (n+1) 0.0 in
begin
for i=0 to nr_known-1 do
new_known_factorials.(i) <- known_factorials.(i)
done;
(let rec fill f_pos pos =
if pos > n then ()
else
let () = new_known_factorials.(pos) <- f_pos in
fill (f_pos *. (float_of_int (pos+1))) (pos+1)
in
fill (known_factorials.(nr_known-1)*.(float_of_int nr_known)) nr_known);
_known_factorials := new_known_factorials;
new_known_factorials.(n)
end)
;;
A corresponding
(let ((buffer (make-array ...)))
(defun float-factorial (n)
...))
just plainly does not work with CMU CL/SBCL. :-(
Other advanced optimization techniques that can be used for benefit
in very specialized situations include (explicit) continuation coding:
rather than returning a value (e.g. a tuple), you take as an argument
a function to which you then pass on your return value(s). This is quite
useful whenever "execution flow branches out into multiple paths that
have to be taken", and may sometimes (though rarely) also be used for
good as a poor man's VALUES/MULTIPLE-VALUE-BIND substitute.
--
best regards,
Thomas Fischbacher
t...@functionality.de
Actually, no. I have no quantitative results but I remember that it is
significant.
> I was quite happy with this solution, but maybe there is something
> more elegant to do?
Nice. :-)
> (I'm still in the process of learning good optimization patterns in
> ocaml which preserve readability)
I was going to mention symbol tables to Raj B for his Python JIT compiler but
he hasn't gotten back to me yet.
Basically, you memoize strings:
# let symbol =
let m = Hashtbl.create 1 in
fun string ->
try Hashtbl.find m string with Not_found ->
Hashtbl.add m string string;
string;;
val symbol : '_a -> '_a = <fun>
This is another trick I learned whilst writing my Mathematica interpreter (so
many tricks, so little time). This function looks totally pointless, like a
no-op, but if you pipe your identifiers through it (e.g. when building the
AST during parsing) then all structurally-equal strings are the same physical
string. If you're careful, this lets you use physical equality for string
comparison and that is a lot faster.
You might do something similar by memoizing temporary strings of different
lengths.
--
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
The OCaml Journal
http://www.ffconsultancy.com/products/ocaml_journal/?e
_______________________________________________
> Basically, you memoize strings:
>
> # let symbol =
> let m = Hashtbl.create 1 in
> fun string ->
> try Hashtbl.find m string with Not_found ->
> Hashtbl.add m string string;
> string;;
> val symbol : '_a -> '_a = <fun>
..which is, of course, just a consequence of the OCaml drawback that
there is no proper "symbol" data type (which actually would be useful,
in particular in conjunction with proper EQ hash tables)...
By the way, the Perl interpreter does the same thing with
script-constant strings, also using this to provide
"effective almost-symbols".
--
best regards,
Thomas Fischbacher
t...@functionality.de
_______________________________________________
> Quôc Peyrot wrote:
[...]
> > let encrypt ?encrypted str =
> > let len = String.length str in
> > let result = match encrypted with
> > | None -> String.create len
> > | Some s -> s
> > in
> > (* ... *)
> > result
>
>> Which gave me more than a 2x speedup while still being able to
>> call a simple:
>> let encrypted = encrypt str
>> during normal usage
>
> I use this strategy a lot and found that it eventually pays to use
> uniform conventions for that: all my functions that can benefit from
> having space pre-allocated where to write a result to use ?target
> as their very first named optional argument (and also return that
> target buffer afterwards).
Ah, thanks, I was actually trying to find a common name too, but
didn't really like "result". "target" is nice :p
> However, unless I am mistaken, I fear that this also does introduce
> some intrinsic/unavoidable inefficiency, as providing a ?target
> argument will (presuambly?) require dynamic consing of a <thingy>
> option cell - so not a good idea for a very small function that is
> called very very often.
>
> There are many many way more advanced tricks one would want to play
> with the idea of "allocating buffers at the appropriate time". For
> example, if this were LISP, one could often use dynamically scoped (in
> the sense of (declare (dynamic-extent buffer-stack))) contextual
> variables for great benefit (and these gory details often can also be
> hidden quite conveniently under a few (maybe even in-place macrolet)
> macros...), but unfortunately, OCaml does not support anything like
> that. Of course, re-entrantness of your code may always become an
> issue if you move buffers to higher scopes.
I didn't get that part, but I'm not familiar with Lisp.
> One thing OCaml can do better than, say, CMU CL, is to define globally
> visible functions that depend on some otherwise inaccessible context,
> as in the following example:
>
> let float_factorial =
> let _known_factorials = ref [|1.0;1.0;2.0;6.0;24.0;120.0;720.0|] in
> (fun n ->
I encountered this pattern today while reading extlib's OptParse.Opt
code:
let value_option metavar default coerce errfmt =
let data = ref default in
{
option_metavars = [metavar];
option_defhelp = None;
option_get = (fun _ -> !data);
option_set_value = (fun x -> data := Some x);
(*...*)
I was a little bit surprised at first that we could do that
(let ...ref... in) but it's really nice.
To me it seems that the common feature which enables us to do all
these tricks is the fact that we have a garbage collector (correct me
if I am wrong). It's really powerful, and I find it fascinating.
I mean, for someone like me, with quite some experience in the asm/c/c
++ world (i.e. a garbage collector-less world) but not much in other
languages, it's easy to naively think of a garbage collector as a
fancy feature to prevent from having to call "free/delete". But I'm
starting to realize there is a whole new set of powerful design
patterns which come along. It has been said multiple times on this
mailing list, but I think we really miss a book about these design
patterns and optimization tricks often specific to a given (or a set
of) feature (functional, lazy computations, garbage collector...).
I find it ironical that high-level languages (such as ocaml) are
intended (of course that's my interpretation of it) to hide low-level
details and give you more expressiveness in your code, which should
naively make you more productive, and make it easier to program
something. But requires therefore tons of new knowledges and deep
understanding of advanced concepts to be able to actually code
efficient (runtime and memory-wise) code.
I mean, in asm/c/c++ there isn't much feature to learn, you pretty
much do everything yourself. It's therefore quite easy (comparing to
OCaml) to actually see what is efficient and what is not. OCaml is so
high-level, and is doing so much for you, that you really need to
learn a lot more about compilation theory to be able to actually feel
at ease when you are looking for efficiency without giving up too
much code elegance. But don't get me wrong, I love it, it's
fascinating, but still ironical from my point of view.
> Other advanced optimization techniques that can be used for benefit
> in very specialized situations include (explicit) continuation coding:
> rather than returning a value (e.g. a tuple), you take as an argument
> a function to which you then pass on your return value(s). This is
> quite
> useful whenever "execution flow branches out into multiple paths that
> have to be taken", and may sometimes (though rarely) also be used for
> good as a poor man's VALUES/MULTIPLE-VALUE-BIND substitute.
I didn't get that part at all. I think I would need an example to
understand
why it is interesting to pass the function instead of just returning
the tuple
and processing it.
--
Best Regards,
Quôc
[...]
> I was going to mention symbol tables to Raj B for his Python JIT
> compiler but
> he hasn't gotten back to me yet.
>
> Basically, you memoize strings:
>
> # let symbol =
> let m = Hashtbl.create 1 in
> fun string ->
> try Hashtbl.find m string with Not_found ->
> Hashtbl.add m string string;
> string;;
> val symbol : '_a -> '_a = <fun>
>
> This is another trick I learned whilst writing my Mathematica
> interpreter (so
> many tricks, so little time). This function looks totally
> pointless, like a
> no-op, but if you pipe your identifiers through it (e.g. when
> building the
> AST during parsing) then all structurally-equal strings are the
> same physical
> string. If you're careful, this lets you use physical equality for
> string
> comparison and that is a lot faster.
It's a really nice trick indeed.
--
Best Regards,
Quôc
This seems to be something that Lisp uses to allocate data structures on the
stack rather than the heap. Why would you want that?
> let float_factorial =
> let _known_factorials = ref [|1.0;1.0;2.0;6.0;24.0;120.0;720.0|] in
> (fun n ->
> let known_factorials = !_known_factorials in
> let nr_known = Array.length known_factorials in
> if n < nr_known
> then
> known_factorials.(n)
> else
> let new_known_factorials = Array.make (n+1) 0.0 in
> begin
> for i=0 to nr_known-1 do
> new_known_factorials.(i) <- known_factorials.(i)
> done;
> (let rec fill f_pos pos =
> if pos > n then ()
> else
> let () = new_known_factorials.(pos) <- f_pos in
> fill (f_pos *. (float_of_int (pos+1))) (pos+1)
> in
> fill (known_factorials.(nr_known-1)*.(float_of_int nr_known)) nr_known);
> _known_factorials := new_known_factorials;
> new_known_factorials.(n)
> end)
I can't quite follow that. Is it doing something cleverer than this:
let float_factorial =
let m = ref [||] in
fun n ->
try (!m).(n) with _ ->
let m' = Array.make (n + 1) 1. in
for i=1 to n do
m'.(i) <- float i *. m'.(i - 1)
done;
m := m';
m'.(n);;
> Other advanced optimization techniques that can be used for benefit
> in very specialized situations include (explicit) continuation coding:
> rather than returning a value (e.g. a tuple), you take as an argument
> a function to which you then pass on your return value(s). This is quite
> useful whenever "execution flow branches out into multiple paths that
> have to be taken",
Are you referring to CPS?
> and may sometimes (though rarely) also be used for
> good as a poor man's VALUES/MULTIPLE-VALUE-BIND substitute.
Weren't values and multiple-value-bind completely superceded by pattern
matching?
--
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
The OCaml Journal
http://www.ffconsultancy.com/products/ocaml_journal/?e
_______________________________________________
Nice, but perhaps it should return a different type to avoid accidentally
comparing an interned string with a non-interned one?
We would need an accessor to extract the string from an abstract type but
I suppose that would be inlined.
Robert Fischer
IT Firefighter
Smokejumper Consulting
No, (==) : 'a -> 'a , so this would work:
module Sym : sig
type t
val symbol : string -> t
val str : t -> string
end = struct
type t = string
let symbol =
let m = Hashtbl.create 1 in
fun s ->
try Hashtbl.find m s
with Not_found -> (Hashtbl.add m s s; s)
let str s = s
end;;
# "toto" == "alpha" ;;
- : bool = false
# Sym.symbol "alpha" == Sym.symbol "alpha" ;;
- : bool = true
# Sym.symbol "alpha" == "alpha" ;;
Characters 22-29:
Sym.symbol "alpha" == "alpha" ;;
^^^^^^^
This expression has type string but is here used with type Sym.t
The cost is a slightly clumsier use of symbols as strings (Symbol.str),
but my feeling is that the extra safety is worth it.
This is an excellent idea. I'll write an OCaml Journal article on design
patterns! :-)
> > Other advanced optimization techniques that can be used for benefit
> > in very specialized situations include (explicit) continuation coding:
> > rather than returning a value (e.g. a tuple), you take as an argument
> > a function to which you then pass on your return value(s). This is
> > quite
> > useful whenever "execution flow branches out into multiple paths that
> > have to be taken", and may sometimes (though rarely) also be used for
> > good as a poor man's VALUES/MULTIPLE-VALUE-BIND substitute.
>
> I didn't get that part at all. I think I would need an example to
> understand
> why it is interesting to pass the function instead of just returning
> the tuple
> and processing it.
I think Thomas is referring to continuation passing style (CPS). That isn't an
optimization though (it slows things down) but it does let you abstract away
mutation. However, it is not entirely safe in the absence of linear types.
For example, the immutable Map and mutable Hashtbl both map keys to values. If
you wrap them with an API written in CPS then you can switch between Maps and
Hashtbls transparently:
module type MAP = sig
type t
val create : unit -> t
val add : string -> string -> t -> (t -> 'a) -> 'a
val remove : string -> t -> (t -> 'a) -> 'a
val copy : t -> (t * t -> 'a) -> 'a
end;;
module Pure : MAP = struct
module Map = Map.Make(String)
type t = string Map.t
let create() = Map.empty
let add k v m f = f(Map.add k v m)
let remove k m f = f(Map.remove k m)
let copy m f = f(m, m)
end;;
module Impure : MAP = struct
type t = (string, string) Hashtbl.t
let create() = Hashtbl.create 1
let add k v m f =
Hashtbl.replace m k v;
let f_m = f m in
Hashtbl.remove m k;
f_m
let remove k m f =
let v = Hashtbl.find m k in
Hashtbl.remove m k;
let f_m = f m in
Hashtbl.add m k v;
f_m
let copy m f = f(m, Hashtbl.copy m)
end;;
However, this is not completely safe because you might erroneously return a
map or hash table from the continuation "f" passed to these functions.
Enforcing this statically requires linear types.
--
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
The OCaml Journal
http://www.ffconsultancy.com/products/ocaml_journal/?e
_______________________________________________
Robert Fischer
IT Firefighter
Smokejumper Consulting
Ahem. The comparison fails for "alpha" == "alpha" as well (which I
meant to write). Sorry.
>> There are many many way more advanced tricks one would want to play
>> with the idea of "allocating buffers at the appropriate time". For
>> example, if this were LISP, one could often use dynamically scoped (in
>> the sense of (declare (dynamic-extent buffer-stack))) contextual
>> variables for great benefit (and these gory details often can also be
>> hidden quite conveniently under a few (maybe even in-place macrolet)
>> macros...), but unfortunately, OCaml does not support anything like
>> that. Of course, re-entrantness of your code may always become an
>> issue if you move buffers to higher scopes.
>
> I didn't get that part, but I'm not familiar with Lisp.
One example: what you can do quite easily in LISP is to introduce
a global lookup thingy MEMOIZATIONS (say, a list of hash tables
or something like that) and define macros WITH-LOCAL-MEMORY and
MEMOIZING where WITH-LOCAL-MEMORY defines a new dynamic
memoization scope, and MEMOIZING wraps up a few functions in such
a way that they use memoization. Result: we can have both
memoization on functions as well as defined behaviour with respect
to when memoized values are being forgotten again (namely, when
we are finished with the evaluation of the form
(WITH-LOCAL-MEMORY ...)).
Note that functions dynamically called from functions lexically scoped
inside this construct will ALSO use the same local memoization table!
In other words, when control flow exits the WITH-LOCAL-MEMORY block
(in whatever way it does so), our memoizing information is returned to
precisely the state it was in before we entered that block. That is
the magic of dynamic scoping.
In code:
(defvar *MEMOIZATIONS* '())
(defun _LOOKUP-MEMO (sym-f args)
(let ((f-args (cons sym-f args)))
(labels
((walk (rest-memo)
(if (null rest-memo)
(values nil nil)
(let ((h (car rest-memo)))
(multiple-value-bind (entry was-present)
(gethash f-args h)
(if was-present
(values entry t)
(walk (cdr rest-memo))))))))
(walk *MEMOIZATIONS*))))
(defmacro WITH-LOCAL-MEMORY (&body body)
`(let ((*MEMOIZATIONS*
(cons (make-hash-table :test 'equal)
*MEMOIZATIONS*)))
(declare (dynamic-extent *MEMOIZATIONS*))
. ,body))
(defmacro MEMOIZING (funs &body body)
(let* (($args (gensym "args-"))
($key (gensym "key-"))
($val (gensym "val-"))
($have (gensym "have-"))
(wrap-funcall
(lambda (sym)
`(,sym (&rest ,$args)
(let ((,$key (cons ',sym ,$args)))
(multiple-value-bind (,$val ,$have)
(_LOOKUP-MEMO ',sym ,$args)
(if ,$have ,$val
(let ((,$val (apply #',sym ,$args)))
(setf (gethash ,$key (car *MEMOIZATIONS*)) ,$val)
,$val))))))))
`(flet ,(mapcar wrap-funcall funs)
. ,body)))
;; Example:
(labels
((foo (x) (+ 1 (* 3 x)))
(bar (x) (/ x 2)))
(memoizing (foo bar)
(labels
((check-3x+1 (n nr-steps)
(cond
((= n 1) nr-steps)
((evenp n) (check-3x+1 (bar n) (+ 1 nr-steps)))
(t (check-3x+1 (foo n) (+ 1 nr-steps))))))
(do ((j 1 (+ 1 j))) ((= j 100))
(with-local-memory
(print (cons j (check-3x+1 j 0))))))))
> I mean, for someone like me, with quite some experience in the asm/c/c
> ++ world (i.e. a garbage collector-less world) but not much in other
> languages, it's easy to naively think of a garbage collector as a fancy
> feature to prevent from having to call "free/delete". But I'm starting
> to realize there is a whole new set of powerful design patterns which
> come along. It has been said multiple times on this mailing list, but I
> think we really miss a book about these design patterns and
> optimization tricks often specific to a given (or a set of) feature
> (functional, lazy computations, garbage collector...).
Two comments about this: First, one should not think along the lines of
"design patterns" here, as if this were Something Universally Good(TM).
Rather, a "design pattern" very often is the equivalent of a clever way
to open a tin with a pair of scissors: an "industry best practice"
workaround that deals with a problem created by the language that should
not be there in the first place! (Paul Graham wrote a nice article on
this.)
Whenever you discover a "design pattern" in your work, it pays to think
about it like this: why does such a pattern occur? Is it because I try
to work around a problem such as wanting to tell the machine about X but
not being able to express it the way I like to think about it myself?
If so, it is often a good idea to consider introducing a language
extension (quite simple if your language provides you with some
meta-linguistic capabilities, ideally: dirty macros plus a code-walker)
to deal with this evidently linguistic limitation.
This brings me to my second comment: it does take a lot of experience
to advance to the level of a language-shaping wizard: there are many
pitfalls and things that at first look as if they may work, but have
subtle undesired implications. One has to develop a strong sense for
important invariants under code transformations to get that bit right.
With this, I suppose, a proper book on both "functional optimization
strategies" and "ideas that help you to overcome mental barriers with
respect to what's possible when one can shape the language" would be
useful, not so much to "teach specific patterns", but to teach people
how to overcome their mental blockades and learn how to use their
phantasy to do marvelous things by shaping language. In the
Permaculture community, there is this proverb that "yield is
limited only by imagination". I think this holds just as much for
functional and in particular metalinguistic programming.
(I have been planning for years to eventually write up some
lengthier introductory text on metalinguistic techniques, but so
far only managed to write a few articles and give some short courses
on the subject...)
> I find it ironical that high-level languages (such as ocaml) are
> intended (of course that's my interpretation of it) to hide low-level
> details and give you more expressiveness in your code, which should
> naively make you more productive, and make it easier to program
> something. But requires therefore tons of new knowledges and deep
> understanding of advanced concepts to be able to actually code
> efficient (runtime and memory-wise) code.
Languages such as OCaml are not "intended to hide low-level details".
Rather, there are (at least) two very different notions of "programming"
around:
(1) Putting information into a mechanically behaving system in order
to get some desired behaviour. (This is what asm/C/C++ is about,
but actually, this even is a much broader notion that also includes
e.g. this: http://amasci.com/amateur/mirror.html)
(2) Formalizing some "mental process" in such a way that one can
then use stringent reasoning to analyze its properties. (This is
what, in essence, functional programming is about.)
Evidently, the more advanced you get, the more important the second
point of view becomes. But, with people being hedonistic and out for
quick results, we will keep on re-inventing simple instruction-based
programming systems over and over again, redoing all the historic
mistakes of unstructured goto programming, inappropriate checks for
exceptional conditions (such as overflows), not paying attention to
dynamical resource management at the level of the framework,
etc. etc. in novel designs till the dusk of the computing epoch.
>> Other advanced optimization techniques that can be used for benefit
>> in very specialized situations include (explicit) continuation coding:
>> rather than returning a value (e.g. a tuple), you take as an argument
>> a function to which you then pass on your return value(s). This is quite
>> useful whenever "execution flow branches out into multiple paths that
>> have to be taken", and may sometimes (though rarely) also be used for
>> good as a poor man's VALUES/MULTIPLE-VALUE-BIND substitute.
>
> I didn't get that part at all. I think I would need an example to
> understand
> why it is interesting to pass the function instead of just returning
> the tuple
> and processing it.
Exercise: Write a program that takes as an argument an integer N and
spits out a string that is a piece of C code which looks as follows
for N=2:
void sort(int x1, int x2, int *buffer)
{
if(x1>x2)
{
buffer[0]=x1;
buffer[1]=x2;
}
else
{
buffer[0]=x2;
buffer[1]=x1;
}
}
This should be generalized to higher N, where the constraints are:
* The generated piece of code must only contain ifs, </> comparisons,
and assignments to the buffer.
* In the end, buffer must hold the input variables in sorted order.
* The code must use the minimal number of comparisons.
If you do this exercise, you will discover that the idea of continuation
coding can be very, very helpful.
--
best regards,
Thomas Fischbacher
t...@functionality.de
_______________________________________________
> This seems to be something that Lisp uses to allocate data structures on the
> stack rather than the heap. Why would you want that?
In order to avoid dynamic memory management and get dynamically scoped
pre-allocated "implicit context" buffers to which I can refer as if they
were ordinary variables.
Well, it avoids some of the computations in your example, which re-does
all the array whenever it has to be extended.
>>Other advanced optimization techniques that can be used for benefit
>>in very specialized situations include (explicit) continuation coding:
>>rather than returning a value (e.g. a tuple), you take as an argument
>>a function to which you then pass on your return value(s). This is quite
>>useful whenever "execution flow branches out into multiple paths that
>>have to be taken",
>
> Are you referring to CPS?
Yes, but not the call/cc implicit CPS, but explicitly passing around
continuations.
>>and may sometimes (though rarely) also be used for
>>good as a poor man's VALUES/MULTIPLE-VALUE-BIND substitute.
>
> Weren't values and multiple-value-bind completely superceded by pattern
> matching?
No. :-) Pattern matching requires constructors, which cons. I am talking
about dynamical memory management avoidance techniques. There are a lot.
--
best regards,
Thomas Fischbacher
t...@functionality.de
_______________________________________________
> Basically, you memoize strings:
>
> # let symbol =
> let m = Hashtbl.create 1 in
> fun string ->
> try Hashtbl.find m string with Not_found ->
> Hashtbl.add m string string;
> string;;
> val symbol : '_a -> '_a = <fun>
It should be pointed out that this trick, known as hash-consing, is
not limited to strings. Basically for a given type you create a
single value representing all values that are structurally
equivalent. It allows to compare values structurally by using
physical equality. This paper [1] shows how to abstract the design
pattern.
Daniel
[1]
Jean-Christophe Filliātre, Sylvain Conchon, Type-safe modular hash-
consing, Proceedings of the 2006 workshop on ML.
http://www.lri.fr/~filliatr/ftp/publis/hash-consing2.ps.gz
_Purely functional data structures_ by Chris Osaki might interest you.
It's a very good book, covering lazy evaluation and persistent
amortized data structures (among other things). Moreover, it does
insist on optimizations (often left as exercises to the reader, with
enough hints to be easy to figure out).
Regards,
--
Gabriel
That is certainly an excellent book and is recommended reading for any
OCamler, but it isn't specific to the OCaml language and doesn't cover many
of the things that I would consider to be OCaml design patterns (like the one
I just posted).
--
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
The OCaml Journal
http://www.ffconsultancy.com/products/ocaml_journal/?e
_______________________________________________
That is exactly what I did. Also, you cannot pattern match over the Sym.t but
I believe the OCaml compiler doesn't optimize pattern matches over strings
anyway.
Incidentally, can we add this to the list of wanted optimizations: O(log n)
matching of strings, arrays and polymorphic variants.
--
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
The OCaml Journal
http://www.ffconsultancy.com/products/ocaml_journal/?e
_______________________________________________
Do you mean something like this:
let dt() =
let start = ref (time()) in
fun () ->
let time' = time() in
let dt = time' -. !start in
start := time';
dt
Call dt() to get a new delta timer, call the delta timer to get the time since
it was last called:
# let dt1 = dt();;
val dt1 : unit -> float = <fun>
# let dt2 = dt();;
val dt2 : unit -> float = <fun>
# dt1();;
- : float = 4.66352200508117676
# dt2();;
- : float = 4.48727107048034668
# dt1();;
- : float = 3.36179709434509277
# dt2();;
- : float = 2.09420299530029297
You could call this a factory pattern.
> > let float_factorial =
> > let m = ref [||] in
> > fun n ->
> > try (!m).(n) with _ ->
> > let m' = Array.make (n + 1) 1. in
> > for i=1 to n do
> > m'.(i) <- float i *. m'.(i - 1)
> > done;
> > m := m';
> > m'.(n);;
>
> Well, it avoids some of the computations in your example, which re-does
> all the array whenever it has to be extended.
On "float_factorial 1000000", my original implementation was >2x faster. If
you call for slowly increasing arguments then you can do much better still by
doubling the length of the array to amortize allocation:
let float_factorial3 =
let n = ref 0 in
let m = ref [||] in
fun j ->
if j <= !n then (!m).(j) else
if j < Array.length !m then begin
let m' = !m in
for i = !n to j do
m'.(i) <- float i *. m'.(i - 1)
done;
m := m';
m'.(j)
end else begin
n := j;
let m' = Array.make (2 * j + 1) 1. in
for i=1 to j do
m'.(i) <- float i *. m'.(i - 1)
done;
m := m';
m'.(j)
end
This is ~7x faster for 1 .. 20000.
> >>Other advanced optimization techniques that can be used for benefit
> >>in very specialized situations include (explicit) continuation coding:
> >>rather than returning a value (e.g. a tuple), you take as an argument
> >>a function to which you then pass on your return value(s). This is quite
> >>useful whenever "execution flow branches out into multiple paths that
> >>have to be taken",
> >
> > Are you referring to CPS?
>
> Yes, but not the call/cc implicit CPS, but explicitly passing around
> continuations.
Yes, that's very useful in OCaml.
> >>and may sometimes (though rarely) also be used for
> >>good as a poor man's VALUES/MULTIPLE-VALUE-BIND substitute.
> >
> > Weren't values and multiple-value-bind completely superceded by pattern
> > matching?
>
> No. :-) Pattern matching requires constructors, which cons.
Here is a pattern match without constructors:
let x = 3
Here is a pattern match that doesn't cons:
let f(x, y) = x + y in
f 3 4
Here is a pattern match with constructors that doesn't cons:
type t = A | B
let f = function
| A -> 0
| B -> 1
What exactly are you having trouble implementing in OCaml? It sounds as if
you're still trying to work around the inefficiencies of Lisp and the beauty
of OCaml is that you don't have to. :-)
Incidentally, the ray tracer is a good demonstration of this. The performance
of the Lisp implementations is crippled by very slow allocation and
deallocation. Juho Snellman tried to circumvent this problem using
multiple-value-bind in a macro:
(defmacro def ((name params &body body)
(mname &rest mparams)
(wname &rest wparams))
`(progn
(declaim (inline ,name ,wname))
(defun ,name ,params
(declare (type double-float ,@params))
,@body)
(defmacro ,mname ,(mapcar #'car mparams)
,(loop with inner = (list name)
with body = ``,',inner
with all-names = nil
for (form count) in (reverse mparams)
for names = (loop repeat count collect (gensym))
do
(setf all-names (append all-names names))
(setf body ``(multiple-value-bind ,',(reverse names)
,,form ,,body))
finally
(setf (cdr inner) (reverse all-names))
(return body)))
(defun ,wname ,(mapcar #'car wparams)
(,mname ,@(mapcar #'cadr wparams)))))
While this greatly improves the performance of the Lisp, it remains far slower
than most other languages.
The equivalent optimization in OCaml is to pass multiple arguments in curried
form, exploiting ocamlopt's big step semantics without losing the
expressiveness of a functional style.
--
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
The OCaml Journal
http://www.ffconsultancy.com/products/ocaml_journal/?e
_______________________________________________
>On Wednesday 27 June 2007 16:48:44 Mattias Engdegård wrote:
>
>
>>The cost is a slightly clumsier use of symbols as strings (Symbol.str),
>>but my feeling is that the extra safety is worth it.
>>
>>
>
>That is exactly what I did. Also, you cannot pattern match over the Sym.t but
>I believe the OCaml compiler doesn't optimize pattern matches over strings
>anyway.
>
>Incidentally, can we add this to the list of wanted optimizations: O(log n)
>matching of strings, arrays and polymorphic variants.
>
>
>
Actually, what I'd like is a more powerful regular expression engine-
one where I can give multiple different patterns with constant values,
and create a single regular expression that if the first pattern is
matched, the first constant value is matched, etc. Something with a
signature like:
type 'a regex_t
val compile : (string * 'a) -> default:'a -> 'a regex_t
val re_match : 'a regex_t -> string -> 'a
Which would allow me to do stuff like:
let re = compile [ ("foo", 1); ("bar", 2); ("baz", 3) ] ~default:(-1);;
let f str =
match re_match re str with
| 1 -> (* it's a foo *)
| 2 -> (* it's a bar *)
| 3 -> (* it's a baz *)
| -1 -> (* it didn't match *)
;;
In other words, something like ocamllex, except dynamic.
Brian
I'm not sure I understand why we can't do it in ocaml, but I
would probably need to try to implement it to see why.
I mean if we implement something along the lines:
let memo f =
let hash = ...
then can't we have the same feature using "let in" ?
let memoized_f = memo f in
let memoized_f = memo f in
(* when we leave this scope, we should get back the first table *)
>> I mean, for someone like me, with quite some experience in the asm/
>> c/c ++ world (i.e. a garbage collector-less world) but not much in
>> other languages, it's easy to naively think of a garbage
>> collector as a fancy feature to prevent from having to call "free/
>> delete". But I'm starting to realize there is a whole new set of
>> powerful design patterns which come along. It has been said
>> multiple times on this mailing list, but I think we really miss a
>> book about these design patterns and optimization tricks often
>> specific to a given (or a set of) feature (functional, lazy
>> computations, garbage collector...).
[...]
> With this, I suppose, a proper book on both "functional optimization
> strategies" and "ideas that help you to overcome mental barriers with
> respect to what's possible when one can shape the language" would be
> useful, not so much to "teach specific patterns", but to teach people
> how to overcome their mental blockades and learn how to use their
> phantasy to do marvelous things by shaping language. In the
> Permaculture community, there is this proverb that "yield is
> limited only by imagination". I think this holds just as much for
> functional and in particular metalinguistic programming.
I wanted to prevent from reducing my comment to the "functional" part.
The design patterns discussed in this thread has more to do with ocaml
itself (or the garbage collector for my example). I've seen plenty of
tutorials
and articles about functional languages but they often expose the same
things and lack (from my point of view again, please keep in mind
that runtime/memory efficiency is important to me) on the efficiency
side
(especially the memory one, often ignoring as well the big runtime
hit you
can have due to the allocations).
Writing concise and elegant code is very important to me, really. I hate
dirty ugly code, but I'm not willing to sacrifice the efficiency.
That's why
I really like OCaml, it is very powerful but allows us to efficient
code...
as long as you actually do understand how the compiler is going to
process your code. And that's the book I wish I could have. We can call
that design pattern or industry best practices. I just want to be
able to
write real-life code (and not necessarily scientific-oriented code,
sorry
Jon Harrop ;) ) without having to re-discover all these best practices
(which might be very natural for someone with a deeper understanding
of all the different features a specific language provides). I don't
think
the only subtle part of OCaml is the fact that it is a functional
language.
There is really more to it, IMHO.
> (I have been planning for years to eventually write up some
> lengthier introductory text on metalinguistic techniques, but so
> far only managed to write a few articles and give some short courses
> on the subject...)
Keep us posted ;)
>> I find it ironical that high-level languages (such as ocaml) are
>> intended (of course that's my interpretation of it) to hide low-
>> level details and give you more expressiveness in your code,
>> which should naively make you more productive, and make it easier
>> to program something. But requires therefore tons of new
>> knowledges and deep understanding of advanced concepts to be able
>> to actually code efficient (runtime and memory-wise) code.
>
> Languages such as OCaml are not "intended to hide low-level details".
Sorry, I'm not really good with words, I indeed wanted to talk about (2)
>
> Rather, there are (at least) two very different notions of
> "programming"
> around:
>
> (1) Putting information into a mechanically behaving system in order
> to get some desired behaviour. (This is what asm/C/C++ is about,
> but actually, this even is a much broader notion that also
> includes
> e.g. this: http://amasci.com/amateur/mirror.html)
>
> (2) Formalizing some "mental process" in such a way that one can
> then use stringent reasoning to analyze its properties. (This is
> what, in essence, functional programming is about.)
>
>
> Evidently, the more advanced you get, the more important the second
> point of view becomes.
(2) is very important to me, but as said earlier, I often found while
reading
articles (functional programming) that highly category-2 oriented people
tend not to care at all (or barely) about real-life runtime of the
program.
Writing correct code is not good enough, I need to be able to execute it
within my life-time (I know, I'm a bit provocative here ;) )
We often oppose category-2 oriented people with category-1 oriented
people.
I think we can meet somewhere in a middle, and the book we talked about
would certainly help.
But yes, I agree that, sometimes, the design pattern is here to solve
a problem
the language itself should solve, but that's not always the case.
--
Best Regards,
Quôc
I have this book in my TOREAD list (for a long time now, my bad)
I must admit I don't use very often pure functional datastructures in
OCaml.
My main concern with functional programing has always been the
runtime hit
you get due to the extra memory allocations (which can be significant).
But yes, I should definitely read this book, thanks for reminding me :p
> On Wednesday 27 June 2007 18:16:33 Gabriel Kerneis wrote:
>> _Purely functional data structures_ by Chris Osaki might interest
>> you.
>> It's a very good book, covering lazy evaluation and persistent
>> amortized data structures (among other things). Moreover, it does
>> insist on optimizations (often left as exercises to the reader, with
>> enough hints to be easy to figure out).
>
> That is certainly an excellent book and is recommended reading for any
> OCamler, but it isn't specific to the OCaml language and doesn't
> cover many
> of the things that I would consider to be OCaml design patterns
> (like the one
> I just posted).
I totally agree with that. We really need this missing book.
by the way, any news about "Ocaml for experienced programmer"?
I don't even know its table of content :(
--
Best Regards,
Quôc
>
> On Jun 27, 2007, at 7:16 PM, Gabriel Kerneis wrote:
>
>> Le Wed, 27 Jun 2007 17:06:51 +0200, Quôc Peyrot <cho...@lrde.epita.fr>
>> a écrit :
>>
>>> It has been said multiple times on this
>>> mailing list, but I think we really miss a book about these design
>>> patterns and optimization tricks often specific to a given (or a set
>>> of) feature (functional, lazy computations, garbage collector...).
>>
>>
>> _Purely functional data structures_ by Chris Osaki might interest you.
>> It's a very good book, covering lazy evaluation and persistent
>> amortized data structures (among other things). Moreover, it does
>> insist on optimizations (often left as exercises to the reader, with
>> enough hints to be easy to figure out).
>
>
> I have this book in my TOREAD list (for a long time now, my bad)
> I must admit I don't use very often pure functional datastructures in
> OCaml.
> My main concern with functional programing has always been the
> runtime hit
> you get due to the extra memory allocations (which can be significant).
In Ocaml, allocations are relatively cheap- a cost similiar to that of
allocating on the stack. Which is why when you tell long-time Ocaml
programmers that you want to avoid an allocation cost by allocating on
the stack, they tend to go "um, why?"
Mutable data structures have their cost as well. When you assign a
pointer into an object old enough to be in the major heap, Ocaml kicks
off a minor collection. For small N, this can often make O(log N)
purely functional structures faster than their O(1) imperative counterparts.
No to mention the correctness advantages, plus other advantages.
Brian
> Actually, what I'd like is a more powerful regular expression engine-
> one where I can give multiple different patterns with constant values,
> and create a single regular expression that if the first pattern is
> matched, the first constant value is matched, etc. Something with a
> signature like:
> let re = compile [ ("foo", 1); ("bar", 2); ("baz", 3) ]
> ~default:(-1);;
>
> let f str =
> match re_match re str with
> | 1 -> (* it's a foo *)
> | 2 -> (* it's a bar *)
> | 3 -> (* it's a baz *)
> | -1 -> (* it didn't match *)
> ;;
>
> In other words, something like ocamllex, except dynamic.
I think you can do this now? it's just messy: use
"(foo)|(bar)|(baz)"
and check which group 1, 2 or 3 matches.
--
John Skaller <skaller at users dot sf dot net>
Felix, successor to C++: http://felix.sf.net