mfurr changed the topic of #ocaml to: OCaml 3.08.2 available! | Archive of Caml Weekly News: http://sardes.inrialpes.fr/~aschmitt/cwn/ | A free book: http://cristal.inria.fr/~remy/cours/appsem/ | Mailing List: http://caml.inria.fr/bin/wilma/caml-list/ | Cookbook: http://pleac.sourceforge.net/
CosmicRay_ has joined #ocaml
CosmicRay has quit [Remote closed the connection]
CosmicRay_ is now known as CosmicRay
CosmicRay has quit [Remote closed the connection]
CosmicRay has joined #ocaml
Sonarman has joined #ocaml
jewel has joined #ocaml
vezenchio has quit ["I live in a yurt on the steppes of Sheepfuckistan. That's why."]
monochrom has joined #ocaml
CoolPops has joined #ocaml
<CoolPops> How can I link in a .so file? (ocamlopt)
<CoolPops> nm. spoke too soon.
CosmicRay has quit ["Leaving"]
jewel has quit [Read error: 110 (Connection timed out)]
CoolPops has left #ocaml []
cjohnson has joined #ocaml
jewel has joined #ocaml
jewel_ has joined #ocaml
jewel has quit [Connection timed out]
jeff2 has joined #ocaml
jewel_ is now known as jewel
cjohnson has quit ["KVIrc 3.2.0 'Realia'"]
jewel_ has joined #ocaml
jewel has quit [Connection timed out]
razorclaw has joined #ocaml
jewel_ is now known as jewel
zzorn has joined #ocaml
a-zwei has joined #ocaml
a-zwei has quit ["leaving"]
a-zwei has joined #ocaml
a-zwei has quit [Client Quit]
a-zwei has joined #ocaml
a-zwei has quit [Client Quit]
CLxyz has joined #ocaml
a-zwei has joined #ocaml
Sonarman has quit ["leaving"]
Snark has joined #ocaml
a-zwei has quit [Read error: 60 (Operation timed out)]
monochrom has quit ["me!"]
zzorn is now known as zzorn_away
<razorclaw> anyone know any good books on ocaml ?
<mlh> i liked jason hickey's but it's a little out of date
<mlh> book or tutorial?
<mlh> (and i presume you've read the topic and looked at the caml site, and the oreilly book
mlh has quit [Client Quit]
eyda|mon_afk has joined #ocaml
<eyda|mon_afk> anyone have the o'reilly book in html format as a tarball?
eyda|mon_afk is now known as eyda|mon
eyda|mon has left #ocaml []
<Nutssh> I believe its on the website in that format already.
nlv11757__ has joined #ocaml
<jewel> On slashdot someone said this should use a Hash table / dictionary instead:
<jewel> (* Set up an associative list for memoization *)
<jewel> let lookup key table = List.assoc key !table;;
<jewel> let insert key value table = table := (key, value) :: !table;;
<jewel> How does one do that?
<Nutssh> Hashtbl.find Hashtbl.mem See the docs for the standard library. Note that hash tables aren't functional. You can also use Map, which is based around red-black trees which is functional.
Herrchen has joined #ocaml
<jewel> Yes I think in this case a non-functional impl is desirable
Banana_ has joined #ocaml
Banana has quit [Read error: 110 (Connection timed out)]
pango__ has quit [Read error: 104 (Connection reset by peer)]
<mflux> btw, in that specific case you could just use a three-dimensional array
<mflux> or one-dimensional could be even a bit faster
<jewel> takes 7 minute on my laptop
<Nutssh> Use what's clear. Performance doesn't matter unless its too slow. (And, with array-size limits, a 3d array can scale nicer.)
<Nutssh> Profile.
<mflux> well, I incorporated the hashtable and with default parameters the runtime dropped from 2.2 seconds to 0.3 seconds
<mflux> I'm not quite sure how to reproduce the '16 minute' time quoted in /.
<Nutssh> Profile Profile Profile!
<Nutssh> What is this you're running?
<mflux> well, I got it to into solving 7 by 3, but it still takes ages. I would almost suspect a bug in the implementation..
<Nutssh> Can you DCC me your code?
<mflux> url is not sufficient? http://minorgems.sf.net/Garden.ml
<jewel> mflux, you have set the columns and rows to 7 and 3
<mflux> oh, _my_ code
<Nutssh> Thanks for the URL.
<mflux> that's the original code
<mflux> my changes were trivial though
<mflux> the main loop was also changed
<mflux> oops, I think I infact just made a copyright infringement :-o
<Nutssh> Major problem with the code is that you're comparing an abstract type.
<mflux> that's a good point, however does it matter with hashes?
<mflux> (and do note that it's not my code ;))
<Nutssh> When 87% of the runtime is in the C code at compare_value and caml_compare, yes.
<Nutssh> How about your code with the hash tables?
ejt has joined #ocaml
<mflux> so you were profiling the original?
<Nutssh> Yes. Using oprofile.. I'm doing camlprof now.
<mflux> the hashtabled version still uses 47% of its time in compare_val
<mflux> but maybe it is doing some other comparisons than only for that memoization table
<mflux> caml_compare takes 6.4%
<mflux> hash_aux 10%
<Nutssh> Strange. Its running a whole lot faster now for me.
<Nutssh> Oh, I ran at (5,20), that is signifigantly faster.
<mflux> compare_val is btw called 637k times (with the default parameters)
<Nutssh> For me, the default paramaters are too low to profile easily.
<Nutssh> Too low to measure easily either.
<mflux> if I increase the default parameters, to, say, 10x10, it seems to stall a long time in the first step (10 by 2), infact so long I haven't bothered waiting it ;)
<Nutssh> Notice, it says the algo takes time == 2^(columnsize)
<Nutssh> Incidently, going from list.assoc to hashtable is a 20x improvement.
<Nutssh> I suspect thats because its using cell list, not cell array, which makes comparing two lists in the hashtbl mush slower.
<Nutssh> The program is also pretty bad style. A hell of a lot of the stuff there is replacable with List.fold/Array.fold.
<mflux> funny, I increased the number of columns to 6, and now the majority of time is spent in caml_int64_shift_left
<mflux> and nativeint_deserialize, caml_int64_compare
<mflux> oh, apparently my original test set was clearly too small
<Nutssh> Your gmon.out is a mismatch to your binary.
<mflux> ah ;)
<mflux> the thought did cross my mind I abstent-mindedly thought it would warn me
<mflux> (no, I don't profile much)
<Nutssh> let printCells cells = String.concat "" (List.map printCell cells)
<Nutssh> I'm a fervent believer in profiling. I profile constantly. During, and after development.. Nothing like making it two-five times faster. to make the Edit-compile-run cycle go faster.
<mflux> no wonder if the source was even longer than the c-version
<mflux> well, I suppose it depends on what you write
<mflux> infact I think I've only written one ocaml-program in which performance mattered (that is, everything wasn't io/network-bound)
<Nutssh> The guy doesn't know what he's doing.
smimou has joined #ocaml
<Nutssh> And he's comparing lists to arrays.. He should be whapped over the head with, what was that article about how new users to lisp use lists, then accuse the language of being slow? When arrays are available.
<ejt> are you talking about the article on slashdot by any chance ?
<mflux> yes
<ejt> good, I wondered if anyone was looking at it
<jewel> yep
<Nutssh> Half of the functions are manually written versions of fold. He's comparing lists to arrays.. He should be whapped over the head with, what was that article about how new users to lisp use lists, then accuse the language of being slow? When arrays are available.
<ejt> lol
<mflux> no wonder his c++-version was shorter
<ejt> is anyone writing a cleaned up version ? I'd help
<mflux> when a lot of the 4-7 functions in the ocaml-version could be replaced with a folds/maps
<mflux> s/ functions/-line functions/
<mflux> oh, infact he reimplemented List.filter too
<mflux> except non-tailrecursively
<Nutssh> And using a linked list instead of a hash table, wonder why its slow.
<Nutssh> Lol.
<Nutssh> I've taken off 20 lines without even any real effort.
<Nutssh> Stylistically, its got problems. And using lists instead of hashtables (20x speedup) and lists instead of instead of either a bitvector or an array.
<ejt> hmm, there must be a better alg.
<Nutssh> No, I think he's right with the right algo.
<Nutssh> But he's using the wrong hammer, imho. Lists and pattern matching suit some problems, but not others.
tintin has quit [Read error: 104 (Connection reset by peer)]
<Nutssh> The 'took 14 minutes and didn't produce a result' is now <6 minutes. (compared to about .1 seconds, true..)
<ejt> that still sounds horribly slow
<Nutssh> True, but thats comparing lists to an implementation using arrays.
<ejt> oh, I thought you'd removed the lists, sorry
<Nutssh> Nontrivial to do that.
<nlv11757__> is there some kind of debug statement in ocaml for outputting
<ejt> nlv11757__: I normally just define a 'trace' function that outputs to stderr
<nlv11757__> hmmm shouldnt a eprintf show up in my screen regardless :S
<Nutssh> Eh, 20x isn't bad. :)
kinners has joined #ocaml
<Nutssh> Interesting. Someone else did a reimplementation of the C++ code. Performance is 1.4 seconds vs 1.1
<Nutssh> For me, ocaml is more than fast enough. I do the low level stuff slightly grotty, and the rest I do at the highest level.
<ejt> I had a chance to use ocaml in my day job last autumn, it was _so_ productive compared to C++
<Nutssh> :)
<Nutssh> Its great.. Higher order functions are a godsend, especially combined with type inference when you're altering the stuff you're sending data between components.
<ejt> C++ers look blank when I start talking about proper type systems :)
<Nutssh> :)
<Nutssh> My program is doing analysis of ~120 million measurements of network RTT time. I could probably be two-three times faster, but the program would be much more inflexible and harder to modify. For this, I write it and it *works*.
<nlv11757__> ok im flipping, whenever cil encounters a eprintf....it should print the thing out rigth? no matter the application?
<nlv11757__> it cant supress it or something like that right?
<kinners> flush stderr
<kinners> try that
<nlv11757__> ty
<nlv11757__> is there an easy way to obtain a trace of the methods that were called without explicitly adding the eprinfs myself
Snark has quit ["Leaving"]
<kinners> nlv11757__: I don't know of any easy way to do that
mlh_ has joined #ocaml
jewel has quit [Read error: 110 (Connection timed out)]
<mflux> someone rewrote the garden-problem, http://wwwfun.kurims.kyoto-u.ac.jp/~garrigue/garden2.ml looks already much nicer
<ejt> y, it does, have you run it ?
<Nutssh> Thats what I did. Its 15% slower than the C version.
<ejt> :)
<Nutssh> And really, this is the sort of problem where imperative, or a combination of imperative&functional probably is the right choice.
<mlh_> that seemed like a bad ocaml impl even to a newbie like me
<Nutssh> It is. He reimplemented map, filter, length. He also opencoded about 8 functions that could be done with map/fold_left.
<Nutssh> And used a linked list to implement a hash table. :)
<mlh_> and the string concatenation. when the c++ impl just printfs!
<Nutssh> String concatenation is a red herring, IMHO.
<Nutssh> Profiler says most of the time is in the hash table lookup. its roughtly an ( int list * int list * int list, ....) Hashtbl.t
<Nutssh> I draw the following conclusion. He managed to find a problem where pattern-matching, lists, and such are the wrong tool. Unfortunately, this is preaching to the choir. People won't realize what a poor test he did and think that the features are useless.
<mrvn> The point of a hashtbl is to have a small hash that can be compared quickly before having to check the full object.
<mrvn> int list * int list * int list certainly isn't a good choice for that.
<Nutssh> I know.
<mlh_> so what should have used instead of Hashtbl.
<mrvn> you should create a hash from the int list * int list * int list and use that as key.
<Nutssh> Hashtbl is certainly better than an association list!
<Nutssh> mrvn: Huh?
<mlh_> huh2. he doesn't use Hashtbl
<mrvn> an association list would be the first mistake.
<Nutssh> We know.. Worth a 20x performance degradation.
<mrvn> yeah, you already said that so i considered that topic dealt with
<nlv11757__> association list is not a very nice structure to do lookups on right?
<Nutssh> The real irony is that it should probably be a bitvector -- if the width is <26, which it effectively has to be, store it in an int.
<nlv11757__> maybe if it is implemented as a hashtable :P
<mrvn> an assoc list ist a plain list of pairs.
<Nutssh> Not if there's more than a handful of items, no.
<nlv11757__> mrvn: i was affraid of that :D
<mrvn> It's just a wrapper to access list of pairs simpler.
<nlv11757__> so much for fast search times :P
<Nutssh> Yup.. It is not a bad choice if you've only got a handful of items. A lot less memory than a hash table.
<mflux> and lists are functional too ;)
<mflux> well, immutable
<mrvn> They are nice if you only append (at the front) or iterate over them under normal cases and a few searches in rare cases.
kinners has quit ["leaving"]
cmeme has quit ["Client terminated by server"]
cmeme has joined #ocaml
<mlh_> assoc suggests a faster lookup to people coming from perl and awk and other languages. it was a surprise to me that it was only linear
_JusSx_ has joined #ocaml
<vincenz> what is the garden problem?
<nlv11757__> hehehe, a C kid trying to throw punches at functional people
Submarine_ has joined #ocaml
kuribas has joined #ocaml
<vincenz> is his point valid?
<kuribas> has anyone seen the slashdot post?
<kuribas> http://developers.slashdot.org/article.pl?sid=05/03/14/2258219&tid=156&tid=8
<kuribas> That gardner problem doesn't look NP-complete to me
<nlv11757__> he probably coded some crappy functional version to make it look bad
<kuribas> Yeah. Is it really such a hard problem? I would think there could be a pretty easy solution to it ...
<mflux> nlv11757__, well, maybe I'm just thinking best of the people, but maybe he didn't really have that much of ml-background, and maybe didn't think that for example how slow that List.assoc is in that usage pattern..
<kuribas> mflux: I think so. But then why did he have to post on slashdot? :/
<mflux> some slight cluelessness maybe? it would go well in hand with the obvious missing of the fact that there is something seriously wrong with his implementation..
<ejt> like the way beginner C coders often think they've found a bug in the compiler
cjohnson has joined #ocaml
<nlv11757__> mflux, that's another possibility of cours
<nlv11757__> e
* vincenz grins
<ejt> Another nice bit of ocaml advocacy:
<ejt> I've just implemented a scheme interpreter in ocaml based on chapter 6 of 'lisp in small pieces'
<ejt> it's < 2000 lines of code
<ejt> and runs 3 times faster than guile :)
<ejt> I haven't even started optimising it yet
<vincenz> ooh
<vincenz> can I take a look?
<ejt> it's _very_ rough
<vincenz> no worries
<ejt> I've only added enough primitives to get the fib benchmark working
<ejt> vincenz: do you want me to email it to you ?
<mrvn> does it allow for callcc?
<mflux> ejt, but here's a lisp-interpreter in 500 lines, written in C! http://www.modeemi.cs.tut.fi/~chery/lisp500/
<mflux> ..albeit it might not be quite as clear code to read ;)
<ejt> wow, that's impressive
<vincenz> why lispM
<vincenz> scheme is better
<ejt> hmmm, lisp500 just segfaults for me
<ejt> I am using a 64 bit machine though
Submarine_ is now known as Submarine
<mflux> works on my 32-bit machine
karryall has joined #ocaml
cjohnson has quit [Read error: 110 (Connection timed out)]
kuribas has left #ocaml []
mrvn_ has joined #ocaml
yakker has joined #ocaml
mrvn has quit [Read error: 60 (Operation timed out)]
<yakker> is there some way of making or mimicking closures in caml without using objects.
<yakker> eg. i have a function called lpSolver objective_function coefficients
<karryall> that's a funny question
<yakker> and it's like to turn this into lpSolver objective
<yakker> where objective's a closure.
<mflux> you mean like let func z = z + 42 in let lpSolver foo = foo 42 in lpSolver func?-o
<mflux> or like let func foo bar z = foo + bar + z in .. .. lpSolver (func 5 6) ?
<yakker> hm. the first. that works very well thanks:)
<mflux> you might find that that (and the latter) mechanism are very useful
<mflux> infact, they could be called one fundamental feature of functional languages ;)
<mflux> (of course not all functional programming languages do partial evaluation)
<nlv11757__> huh, what char is ^@
<nlv11757__> im processing text but encounter this character :S
<mflux> ascii 0
<mflux> you may generate this character (on unix) by pressing ctrl-space
<mflux> so chances are you're processing binary ;)
<nlv11757__> :O
<nlv11757__> no way
<nlv11757__> eek
<mflux> or not taking the fact that read&friends don't set the target string length into account..
<mflux> (I did that mistake once)
<nlv11757__> can you explain that last sentence?
<mflux> say if Unix.read fd str 0 42 returns less than 42 characters, the rest of the string will remain unmodified
<mflux> Unix.read fd str 0 0 42 actually
<mflux> and Pervasives.input behaves similarly
<nlv11757__> ok but the length will still denote 42
<mflux> the strings length will remain unmodified
<nlv11757__> so 42?
<nlv11757__> or am i misunderstanding here/
<nlv11757__> ?
<mflux> my common usage pattern is let s = String.create 1024 in Unix.read fd s 0 0 (String.length s)
<nlv11757__> your point is doing a unix.read of 42 doesnt necessarily return a 42 length string?
<mflux> yes
<nlv11757__> ok, but how does that relate to bumping into a ^@ char while reading a file
<mflux> is the code available?
<mflux> although I'm just about to leave
<mflux> but I'll be back in a couple of hours &
<nlv11757__> hehe wellll im using CIL that reads in a C file and apparently CIL sees a ^@ char somewhere because in the AST of that C file is a node representing a Char constant with ^@ as the value...
Skal has joined #ocaml
vdrab has joined #ocaml
MirrorLynx_ has joined #ocaml
gim has quit [Read error: 110 (Connection timed out)]
gim has joined #ocaml
vdrab has quit [Read error: 60 (Operation timed out)]
MirrorLynx_ has quit [zelazny.freenode.net irc.freenode.net]
cmeme has quit [zelazny.freenode.net irc.freenode.net]
cognominal has quit [zelazny.freenode.net irc.freenode.net]
rossberg has quit [zelazny.freenode.net irc.freenode.net]
shrimpx has quit [zelazny.freenode.net irc.freenode.net]
noj has quit [zelazny.freenode.net irc.freenode.net]
Hadaka has quit [zelazny.freenode.net irc.freenode.net]
calvin_ has quit [zelazny.freenode.net irc.freenode.net]
Naked has joined #ocaml
noj has joined #ocaml
cmeme has joined #ocaml
vezenchio has joined #ocaml
Naked is now known as Hadaka
MirrorLynx_ has joined #ocaml
rossberg has joined #ocaml
_JusSx_ has quit [Read error: 110 (Connection timed out)]
shrimpx has joined #ocaml
cognominal has joined #ocaml
calvin_ has joined #ocaml
karryall has quit ["ERC Version 5.0.1 $Revision: 1.726.2.3 $ (IRC client for Emacs)"]
<vincenz> ejt: one big isuse
<vincenz> I just took a brief look at it
<vincenz> don't use ^ str ^ str ... in a recursive call
<vincenz> it's SLOW
<vincenz> you're rebuilding a new string, lots of unnecessary allocations
<vincenz> use a buffer for such
<yakker> let rec eval p c = function | (cars::cdrs,carc::cdrc)->float(carc) /. float(cars) + eval cdrs cdrc
<yakker> this gives a type error for the float expression (is float, used with int)
<yakker> can someone explain why?
<ejt> vincenz: thx, I'll look ....
zzorn_away is now known as zzorn
nlv11757__ has left #ocaml []
<ejt> vincenz: ^ seems to be only used on error paths, and not recursively
<det> Inrai's Ocaml website is a lot nicer now
<mlh_> but all the links are broken :-(
<vincenz> ejt: no...you use it for printg
<vincenz> not only are the links broken
<vincenz> they refer to 3.07 manual
<vincenz> not the 3.08 they had
<ejt> vincenz: yes, so I am ... I'm not sure how to convert that to use buffers
<vincenz> just use a buffer
<ejt> and return a buffer from string_of_list ?
<vincenz> nono
<vincenz> A real buffer
<ejt> we're talking about module Buffer here right ?
<vincenz> yes
MirrorLynx_ has quit [zelazny.freenode.net irc.freenode.net]
vezenchio has quit [zelazny.freenode.net irc.freenode.net]
yakker has quit [zelazny.freenode.net irc.freenode.net]
mrvn_ has quit [zelazny.freenode.net irc.freenode.net]
juhammed has quit [zelazny.freenode.net irc.freenode.net]
MirrorLynx_ has joined #ocaml
vezenchio has joined #ocaml
yakker has joined #ocaml
juhammed has joined #ocaml
juhammed_ has joined #ocaml
CosmicRay has joined #ocaml
MirrorLynx_ has quit [zelazny.freenode.net irc.freenode.net]
yakker has quit [zelazny.freenode.net irc.freenode.net]
juhammed has quit [zelazny.freenode.net irc.freenode.net]
vezenchio has quit [zelazny.freenode.net irc.freenode.net]
mrvn has joined #ocaml
MirrorLynx_ has joined #ocaml
vezenchio has joined #ocaml
yakker has joined #ocaml
mrvn_ has joined #ocaml
pango has joined #ocaml
MirrorLynx_ has quit [zelazny.freenode.net irc.freenode.net]
mrvn has quit [zelazny.freenode.net irc.freenode.net]
yakker has quit [zelazny.freenode.net irc.freenode.net]
vezenchio has quit [zelazny.freenode.net irc.freenode.net]
mrvn has joined #ocaml
MirrorLynx_ has joined #ocaml
vezenchio has joined #ocaml
yakker has joined #ocaml
_JusSx_ has joined #ocaml
joey_ has joined #ocaml
<vincenz> something like that
<vincenz> but UGH
<vincenz> get an editor that replaces your ^I's properly
* vincenz mutters
mrvn has quit [Connection timed out]
Snark has joined #ocaml
yakker has quit [Read error: 145 (Connection timed out)]
<ejt> vincenz: heh, too much time as a kernel hacker where ^Is are mandatory :)
MirrorLynx_ has quit [zelazny.freenode.net irc.freenode.net]
vezenchio has quit [zelazny.freenode.net irc.freenode.net]
juhammed_ is now known as ooo
Submarine has quit ["Leaving"]
Msandin has joined #ocaml
ejt has quit [Read error: 110 (Connection timed out)]
Herrchen has quit ["bye"]
jeff2 has left #ocaml []
Darkbaron has joined #ocaml
<Darkbaron> bonjour tous le monde :)
Snark has quit ["Leaving"]
<Msandin> The fact that the new ocaml website doesn't work in IE is a serious problem, hum?
<Riastradh> I don't think there are many OCaml users bothered by it.
MirrorLynx_ has joined #ocaml
<Msandin> Well, I am bothered, and honestly, mostly because I want a lot of people using OCaml, and this makes it look more like and academic curiosity than it really is:-/
<mflux> ooh, but it's pretty
* mflux hadn't noticed the new site before
<mflux> I would imagine patches to html/css could be incorporated if one were to produce those
<Msandin> One would hope...=)
Submarine has joined #ocaml
<mflux> and www.ocaml.org points to the site too, ooh
<Msandin> But honestly, the people who need a prettier/more pro looking website is probably much the same ppl who it misses by not working in IE...
<mflux> hump got a facelift too I see
<Msandin> Ohh... gotta see that=)
* Msandin approves of the fact that it looks like a part of the site, looking all nice=)
<Msandin> And it now links Tywith:-P
<mflux> and there are two kinds of classifications for projects (well, third one too, licenses, but that should be an additional search criteria)
<Msandin> All in all, the new page is a great improvement, but I sure hope the IE situation is being adressed:)
joey_ has quit [Read error: 60 (Operation timed out)]
Msandin has left #ocaml []
vezenchio has joined #ocaml
yakker has joined #ocaml
zzorn has quit ["They are coming to take me away, ha ha"]
<yakker> sigh, i have a syntax error i've been staring at for quite some time...
<yakker> let val1=expr1 and val2=expr2 and val3=expr3 in Printf ""
<yakker> gives a syntax error at 'in'.
<yakker> dunno why.
Darkbaron is now known as D-dodo-N
D-dodo-N has left #ocaml []
<j_n> you probably need Printf.printf
<yakker> nope, i have open Printf
<j_n> then lowercase printf
<j_n> ?
<yakker> j_n: any ideas?
<j_n> yakker, yeah, i don't think you can declare stuff like that simulataneous
<j_n> simultaneously*
<j_n> "A simultaneous declaration declares different symbols at the same level. They won't be known until the end of all the declarations."
<j_n> (from the caml book)
<j_n> the function fn isn't defined
<yakker> j_n: it gives the error even when i change the second and into an in
<j_n> you also need parenthesis around (g 7)
znutar has joined #ocaml
<yakker> j_n: done, still the error...:-|
<j_n> what do you have now?
<yakker> same link
<j_n> heh, you're missing a few 'lets'
<j_n> try
<j_n> let x1=4
<j_n> and fn x y = x+8+y in
<j_n> let g y = fn 4 y
<j_n> in
<j_n> Printf.printf "%d\n" (g 7)
<j_n> gotta go home, hope that helps!
<yakker> j_n: thanks. silly me, but thanks anyway:)
_JusSx_ has quit ["leaving"]
<mrvn_> how wastefull. let g = fn 4 in
mlh has joined #ocaml
Zaius has joined #ocaml
<Zaius> (how) can i convert an arbitrary exception to a string?
<mattam> Exc.to_string IIRC
<mattam> hmm no, there's not even an Exception module :p
<mattam> oh Printexc
Skal has quit ["Client exiting"]
<Zaius> oh! printing exceptions ... :) i ever thought it was for handling exceptions in printing functions
<Zaius> thanks
<vincenz> re
CosmicRay has quit ["Client exiting"]
smimou has quit ["?"]
kinners has joined #ocaml
KrispyKringle has joined #ocaml
yakker has quit [Read error: 60 (Operation timed out)]