Yurik changed the topic of #ocaml to: http://icfpcontest.cse.ogi.edu/ -- OCaml wins | http://www.ocaml.org/ | http://caml.inria.fr/oreilly-book/ | http://icfp2002.cs.brown.edu/ | SWIG now supports OCaml| Early releases of OCamlBDB and OCamlGettext are available
malc has quit [Read error: 110 (Connection timed out)]
redcrosse has quit []
<mrvn> Somehow it feels like ocaml wastes a lot of ram. My AST of a C preprocessor takes 2000 times the size of the source.
<Smerdyakov> Tell it to garbage collect sooner....
<mrvn> I think I have to convert some x@[y] into y::x and List.rev the result
<whee> or do some profiling to see what it's doing
<Smerdyakov> mrvn, that shouldn't have much effect on memory usage, just runtime.
<Smerdyakov> On live memory usage, that is.
<mrvn> x@[y] creates a new list each time, y::x just creates another node.
<mrvn> or not?
<mrvn> Wow, that brought the ram useage down from 800 MB to <20 MB and the input file as char list and as token stream together are already 19MB. It now also parses within seconds
<Smerdyakov> It creates a new list each time, but the old lists become garbage very quickly.
<mrvn> Appending a 15000 items long list item by item realy isn't a good idea.
<whee> x @ [y] is a lot more expensive than y :: x, that's fofsure
<whee> probably linear overhead
<whee> where adding an element to the head is constant time
<whee> and I hate my cab le connection, always dying
<mrvn> Does ocaml catch a segfault cause by out of memory and tries to GC more often?
<mrvn> s/cause/caused/
<mrvn> The 800 MB must be just because the GC can't keep up fast enough.
<mrvn> I think I see why the @ wastes so much ram:
<mrvn> let rec loop l tokens =
<mrvn> try
<mrvn> let (part, tokens) = parse_group_part tokens in
<mrvn> with Parse_error -> (l, tokens)
<whee> I'd avoid using @ and go for :: and a reverse (if order matters)
<mrvn> {+ before the with} loop (l@[part]) tokens
<mrvn> The old list is still bound to l because it will be used in the "with" case. So as long as the recursion runs all lists would be alive.
<mrvn> or not?
<mrvn> How do I tell ocaml to let the GC run?
<mattam> look at module Gc
<mrvn> somehow Gc.major ();; doesn't realy free any memory.
<mrvn> Is memory only freed when the GC compacts?
<mrvn> looks like it. Gc.compact ();; cleaned up nicely.
<emu> oh cool, we teased Riastradh into helping out the crazy cons cell person
<whee> I don't think I want to know.
mattam has quit ["new kernel..."]
Kinners has joined #ocaml
palomer has quit [Remote closed the connection]
Sonarman has joined #ocaml
skylan has quit [Read error: 60 (Operation timed out)]
skylan has joined #ocaml
Sonarman has left #ocaml []
lament has joined #ocaml
palomer has joined #ocaml
palomer has quit [Remote closed the connection]
lament has quit ["Did you know that God's name is ERIS, and that He is a girl?"]
mattam has joined #ocaml
lament has joined #ocaml
Kinners has left #ocaml []
Zadeh has quit [Read error: 104 (Connection reset by peer)]
async has joined #ocaml
async_ has quit [Remote closed the connection]
lament has quit ["Did you know that God's name is ERIS, and that He is a girl?"]
<pattern_> "There is a joke about American engineers and French engineers. The American team brings a prototype to the French team. The French team's response is: 'Well, it works fine in practice; but how will it hold up in theory?'"
foxen has quit [Read error: 104 (Connection reset by peer)]
Kinners has joined #ocaml
TachYon26 has joined #ocaml
<Kinners> is there some code somewhere to perform a small checksum (30/32 bit)?
<Kinners> nm :)
docelic|sleepo is now known as docelic
TachYon26 has quit [Read error: 60 (Operation timed out)]
docelic is now known as docelic|away
xxd_ has quit ["EOF"]
TachYon26 has joined #ocaml
async_ has joined #ocaml
async has quit [Read error: 54 (Connection reset by peer)]
<mattam> pattern_: :)
<mrvn> Kinners: openssl has good checksums.
xxd has joined #ocaml
TachYon26 has quit [Read error: 60 (Operation timed out)]
mellum has quit [Read error: 110 (Connection timed out)]
mellum_ has joined #ocaml
systems has joined #ocaml
steele has joined #ocaml
<steele> hi
mellum_ is now known as mellum
systems has quit [Read error: 110 (Connection timed out)]
TachYon26 has joined #ocaml
Kinners has left #ocaml []
merriam has quit [leguin.freenode.net irc.freenode.net]
merriam has joined #ocaml
<mellum> Can somebody give me an example of Scanf?
<mellum> I want to read lines, each consisting of an int and a float...
<Smerdyakov> Didn't you ask that here before, or was it someone else?
<mellum> Hm, not sure, I think I didn't ask before :)
<Smerdyakov> Someone did, and so I'll answer using knowledge gleaned only from the reply the last time it was asked.
<Smerdyakov> Scanf.scanf "%d %f" (function n f -> (n, f))
<mellum> thanks
<Smerdyakov> It is an interesting phenomenon that I'm able to answer questions here despite never having used OCaml =)
<mellum> Well, the answer was slightly wrong :)
<Smerdyakov> That's OK. I use an iterative approximation algorithm for becoming an OCaml expert without ever using it. ;)
<Smerdyakov> (What was wrong?)
<mellum> You need fun, not function
<Riastradh> Yes, one 'function' alone can't create curried functions, while 'fun' can.
<Smerdyakov> I
<Smerdyakov> I'm astounded that 'function' is used for such a common purpose in OCaml.
<Riastradh> ?
<Smerdyakov> That's a lot of typing over \ in Haskell =)
<Smerdyakov> Or fn in SML
<Riastradh> No, 'fun' is used far more often.
<Smerdyakov> Why is 'function' there?
<Riastradh> 'function' can automatically match its arguments; 'fun' can't.
<Riastradh> function [] -> "nil" | x :: xs -> x
<Smerdyakov> Fancy schmancy. 'fn' does that in SML. :P
<mrvn> Smerdyakov: How do you match "fn x y", i.e. two currified parameters?
<mrvn> Smerdyakov: can you write "fn [] [] -> [] | x [] -> x | [] y -> y | x y -> x@y"?
<mrvn> mellum: Is your tree merging tail-recursive or just recursive?
<Riastradh> mrvn - No, you can't write that, because in SML, its 'fn args => body', not 'fn args -> body'.
<mrvn> can you with =>?
<Riastradh> I dunno. I'd test it but breakfast is waiting.
<Smerdyakov> -> is only used in types in SML.
<Smerdyakov> And there is no currying shortcut with anonymous functions.
<mrvn> That sucks. I love currying
esabb has joined #ocaml
<Smerdyakov> Oh my! fn x => fn y => e is such a hassle!
<mrvn> "fun x y -> e" is just more _fun_
<mrvn> mellum: ping
<mellum> mrvn: pong
<mrvn> mellum: Is your tree merging tail-recursive or just recursive?
<mellum> mrvn: not sure
<mellum> Shouldn't really matter though, since the depth of the trees is <100
<mrvn> If its recursive all temporary bindings will remain alive until the recursion is finished. I noticed that when my pcpp used up 800MB to parse a c.
<mrvn> file
<mellum> Well, it takes only like 200M
<mellum> last graph took 49542s though
<mrvn> mellum: Wenn du beim XO verlierst, machst du dann den verlierenden Zug?
phubuh has quit [Read error: 54 (Connection reset by peer)]
<mellum> mrvn: klar
<mrvn> Waer aber auch erlabut dann garkein board auszugeben, oder?
<mellum> Noe.
<mrvn> Crash, unintelligible output, or failing to make a move within 20 seconds is equivalent to making a losing move.
<mrvn> "unintelligible output"?
<mellum> Nicht parsbar, soll das wohl heissen
<mrvn> nen leeres File faellt da doch wohl druner?
<mellum> Achso. Was dann der Score ist, ist allerdings unklar.
<mrvn> das selbe als wenn man XX setzt.
<mellum> Weiss nicht. Lohnt sich irgendwie nicht, das extra einzubauen...
<mrvn> ich schau mir halt nur gueltige Zuege an und dann findet er keinen.
<mellum> Die beste Loesung ist es, einfach nie zu verlieren ;)
<mrvn> geht nicht
<mellum> Mist
<mrvn> Wo liegt denn dein code?
<mrvn> Kann das ein 4x4 Board komplett durchspielen wenn man den timer killt?
<mellum> Moeglich
<mrvn> Wow, sogar halbwegs schnell. Nach 3 halbzuegen brauchts keine Zeit mehr
<mrvn> Es merkt aber nicht wenn das Spiel schon verloren ist :(
docelic|away is now known as docelic
<mrvn> mellum: Bei 4x4 verliert X bei dir gegen dich.
<mellum> Hmm.
<mellum> Kill halt das Limit.
<mrvn> hab ich
<mellum> Ja? Dann ist da wohl ein Bug.
<mellum> Pech.
<mrvn> 4 4
<mrvn> OXOX
<mrvn> -OXO
<mrvn> X-OX
<mrvn> -XXO
<mrvn> Da ist nen Bug irgendwo:
<mrvn> 4 4
<mrvn> XO-O
<mrvn> OX-X
<mrvn> XOXO
<mrvn> OXOX
<mrvn> 4 4
<mrvn> XO-O
<mrvn> OXXX
<mrvn> XOXO
<mrvn> OXOX
<mrvn> Der Zug war doch garnicht noetig.
redcrosse has joined #ocaml
TachYon26 has quit [Remote closed the connection]
<mrvn> mellum: Hast du mal nicht quadratische Spiele ausprobiert?
<mrvn> 4 3
<mrvn> ----
<mrvn> ----
<mrvn> ----
<mrvn> 4 3
<mrvn> -X-
<mrvn> ---
<mrvn> ---
<mrvn> +++
systems has joined #ocaml
docelic is now known as docelic|away
<mellum> mrvn: du denkst, dass das nicht schlau ist/
<mrvn> mea culpa. Die specs sagen das es "hoehe breite" ist und ich hatte "breite hoehe"
<mrvn> mellum: Aber bei fehlerhafter Eingabe haette man ja auch abbrechen koennen
<mrvn> mellum: Aber das du verlierst obwohl du nen draw kriegen kannst ist schlecht.
<mellum> mrvn: in der Tat
<mrvn> Kann es sein das der 1. zug egal ist? Irgendwie ziehst du da sonstwohin und mein prog sagt das alle Felder gleich gut waeren (er aber verliert)
<mrvn> Hast du mal nen kleines Testbrett wo X gewinnt?
<mellum> 1 1
<mellum> .
<mrvn> ein nicht triviales
<mrvn> mellum: Noch ein bug:
<mrvn> 3 3
<mrvn> OXO
<mrvn> X+-
<mrvn> -XO
<mrvn> Das haengt sich auf
foxen5 has joined #ocaml
coolduck has joined #ocaml
systems has left #ocaml []
<mellum> mrvn: Hey, ich hab das ja auch nur eben in ein paar Stunden hingehackt :)
coolduck has quit ["Client Exiting"]
mrvn_ has joined #ocaml
mrvn has quit [Read error: 60 (Operation timed out)]
<mrvn_> mellum: Wie rechne ich aus wieviel Steine ein Spieler noch maximal belegen kann?
mrvn_ is now known as mrvn
<mellum> mrvn: du zaehlst die nicht vergifteten Felder
<mrvn> Auf nem leerem 4x4 Feld kann man aber nciht 16 Steine setzen.
systems has joined #ocaml
Hase^^on has joined #ocaml
Hase^^on has left #ocaml []
docelic|away is now known as docelic
systems has quit ["Client Exiting"]
palomer has joined #ocaml
<palomer> hrm, I know this is the third time asking this but...how do I match 2 parameters with a pair?
<palomer> like let x = fun a b match (a,b) with...
<mrvn> let x = fun a b -> match (a,b) with...
<palomer> thx:o
<palomer> whats wrong with this pattern? | (x,x) -> [x]
<Riastradh> x is bound twice.
<palomer> why is that evil?
<whee> which binding should it take?
<mrvn> palomer: thats the same as (_,x)->[x]
<palomer> ahh true
<palomer> not the same!
<whee> let's imagine some language where I can do assignments in parallel, and I say x = 3 and x = 4
<palomer> I want them to be identical
mattam has quit ["branchage dvd :)"]
<whee> what's the value of x after that :P
<whee> (x, y) when x = y
<palomer> hrm
<Riastradh> Like Scheme: (let ((x 3) (x 4)) x)
<mrvn> Riastradh: thats 4
<palomer> we would need a language that states that being equivalent must mean that assignment produces the same result
<Riastradh> No, that's an error.
<whee> is evaulation order defined?
<Riastradh> That expands to: ((lambda (x x) x) 3 4)
<palomer> so how would I do what I want to do?
<whee> palomer: erlang does that
<whee> but that comes from the prologish background, I think
<Riastradh> And since x can't appear twice in parameter lists, it's an error.
<palomer> so how would I do this in ml?
<Riastradh> whee - It doesn't matter if evaluation order is defined (though it's not) because the function takes two arguments instead of being actually curried.
<palomer> I would have to use an if instead?
<whee> palomer: (x, y) when x = y
<whee> if you want to remain doing it in that style, anyway
<palomer> whats wrong with this?
<palomer> let rec interval = fun a b -> match (a,b) with
<palomer> | (x,y) when x = y -> [x]
<palomer> | (a,_) -> a::interval(a+1,b);;
<whee> why use fun and match?
<whee> oh, meh. forgot the original syntax is more restrictive with fun/function
<mrvn> let rec interval a b = if a = b then [a] else a::(interval (a+1) b);;
<whee> but I'd do what mrvn just said, heh
<palomer> so sometimes pattern matching isn't the best solution?
<Riastradh> It's often simpler to use 'if' if there are only two clauses.
<palomer> and what's wrong with my solution?
<mrvn> (a+1,b) is a tuple but interval takes two ints.
<whee> what does the compiler say?
<whee> well, that too :)
<palomer> This expression has type int * int but is here used with type int
<palomer> ahh I see
<mrvn> # let rec interval = fun a b -> match (a,b) with
<palomer> hrm
<mrvn> | (x,y) when x = y -> [x]
<mrvn> | (a,_) -> a::interval (a+1) b;;
<palomer> ohmy
<palomer> seems the first | is wrong
<palomer> which I learned is optional
<mrvn> nothing wrong with it
<palomer> erm, must've done something else
mattam has joined #ocaml
docelic is now known as docelic|sleepo
Hellfried has joined #ocaml
coolduck has joined #ocaml
TachYon has joined #ocaml
esabb has quit [Remote closed the connection]
coolduck has quit ["Client Exiting"]
TachYon has quit ["Client Exiting"]
foxen5 has quit []