systems 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 | Caml Weekly news http://pauillac.inria.fr/~aschmitt/cwn/
systems has quit ["Client Exiting"]
jao has quit ["sleep"]
reltuk has joined #ocaml
pattern_ has joined #ocaml
docelic has quit [No route to host]
reltuk has quit [Read error: 104 (Connection reset by peer)]
lament is now known as lameAFK
lameAFK is now known as lament
Kinners has joined #ocaml
docelic has joined #ocaml
reltuk has joined #ocaml
themus has quit ["Client Exiting"]
wax has quit [Remote closed the connection]
wax has joined #ocaml
themus has joined #ocaml
Smerdyakov has quit []
docelic has quit [No route to host]
mattam has joined #ocaml
walters has joined #ocaml
<walters> does ocaml have any kind of lazy list or generator?
<walters> ah, /me sees the Lazy module
<Kinners> there are streams and you can do things with the Lazy module
<walters> i recently learned about generators in python, and since then i've been using them a lot in my python code. now i'm writing some OCaml and there's a bit of code that would be nicely expressed using generators
<walters> basically i want to iterate over the lines of a file efficiently
<Kinners> there's an extension to the stdlib being worked on that has support for that sort of style
<walters> cool
<walters> as long as i'm wishing, any word on Unicode/UTF-8 support?
lus|wazze has quit ["Programming today is a race between software engineers striving to build bigger and better idiot-proof programs, and the Univ]
<Kinners> some of the xml parsers have utf8 support so maybe
<walters> let rec readlines_lazy f =
<walters> (lazy (input_line f))::(readlines_lazy f);;
<walters>
<walters> does that make sense?
<walters> it doesn't seem like quite what i want though
<walters> ah, yeah, it stack overflows :)
<walters> ah, it looks like I really want to use Streams
<walters> i missed your earlier reference to that
<walters> hm
<walters> looks like i would have to do all my own bookkeeping to implement a line stream
<walters> programming in ocaml is weird. sometimes it feels really high level, like when i'm writing these functions to manipulate sets using the Set module. other times it feels really low level, like when I have to manually resize arrays
<Kinners> let make_option f = try Some (f ()) with _ -> None;;
<Kinners> let readlines s = make_option (fun () -> input_line s);;
<walters> ok
<walters> but how can i iterate over that functionally?
<Kinners> let process_stream f = function Some line -> ignore (f line) | None -> ();;
<Kinners> something like that
<Kinners> or not
<Kinners> let rec process_stream f s = match (readlines s) with Some line -> f line; process_stream f s | None -> ();;
<walters> right, that's basically a while loop
<walters> i think
<walters> yeah
<walters> i need to return a value
<Kinners> that should be called process_channel actually
<walters> ok, got it
<walters> let rec stream_of_lines f =
<walters> let curcount = ref 0 in
<walters> let cursize = ref 64 in
<walters> let curlines = ref (Array.make !cursize "") in
<walters> let streamfn i =
<walters> if i > !cursize then
<walters> (let tem = Array.make !cursize "" in
<walters> curlines := Array.append !curlines tem;
<walters> cursize := !cursize * 2);
<walters> try
<walters> while !curcount <= i do
<walters> Array.set !curlines !curcount (input_line f);
<walters> curcount := !curcount + 1
<walters> done;
<walters> Some (!curlines).(i)
<walters> with End_of_file -> None in
<walters> Stream.from streamfn;;
<walters>
<walters> no need for it to be rec, actually.
<walters> whee. that felt so dirty and non-functional :)
<walters> now back to my problem, which i can now express functionally
<walters> grr
<walters> actually
<walters> Stream doesn't have a fold_left function.
lam has joined #ocaml
<walters> let rec stream_fold_left f init strm =
<walters> try
<walters> stream_fold_left f (f init (Stream.next strm)) strm
<walters> with Stream.Failure -> init
<walters> ;;
<walters> whee
<walters> now i can say like:
<walters> stream_fold_left (fun x r -> String.concat "" [x;r]) "" (stream_of_lines (open_in "/tmp/apache2_2.0.46-1.dsc"));;
<Kinners> walters: do you need all the array machinery in stream_of_lines?
<walters> Kinners: what do you suggest instead?
<Kinners> walters: I don't think you need to use the count passed to your function
<walters> Kinners: you're right in that i probably don't, but it would kind of be a dirty hack to just ignore the count
<Kinners> why?
<walters> because the stream api includes the count :)
<walters> hm, wait
<walters> there's no way to directly access an object at a particular position in a stream?
<Kinners> it can buffer values for you (afaik) so you don't have to worry about peeking ahead screwing everything up
<walters> ah
<walters> well yes that would definitely make things simpler
rhil is now known as rhil_zzz
d-bug has joined #ocaml
lament has quit ["I WILL NOT SKATEBOARD IN THE HALLS"]
Kinners has left #ocaml []
reltuk has quit [Read error: 104 (Connection reset by peer)]
walters has quit [Remote closed the connection]
d-bug is now known as d-lunch
systems has joined #ocaml
systems has quit ["Client Exiting"]
mrvn_ has joined #ocaml
mrvn has quit [Read error: 60 (Operation timed out)]
reltuk has joined #ocaml
d-lunch is now known as d-burp
Yurik has joined #ocaml
Zadeh has quit [Connection reset by peer]
docelic has joined #ocaml
__DL__ has joined #ocaml
docelic is now known as docelic|away
<mellum> Is there any function with signature 'a -> 'b?
<Riastradh> raise is probably the closest to that -- exn -> 'a or something.
<mellum> let f x = f x also is 'a -> 'b, but it is not useful... I guess no useful function like that exists
lam has quit [Read error: 60 (Operation timed out)]
<mrvn_> mellum: Hashtbl.map would be 'a -> 'b
Smerdyakov has joined #ocaml
<mrvn_> or not, never mind.
clog has quit [^C]
clog has joined #ocaml
docelic|away is now known as docelic
mrvn_ is now known as mrvn
clog has quit [^C]
clog has joined #ocaml
smklsmkl has quit ["bbl"]
smkl has joined #ocaml
lam has joined #ocaml
d-burp has quit []
mkfort has quit ["Download Gaim [http://gaim.sourceforge.net/]"]
rhil_zzz is now known as rhil_work
<mrvn> Whats better in ocaml?
<mrvn> class foo = object val bla = 1 end
<mrvn> class foo = let bla = 1 in object end
<mrvn> class foo = object val bla = 1 end
<mrvn> class foo = let bla = 1 in object end
<mrvn> ups, once too often.
<Riastradh> 'let' defines class variables; 'val' defines instance variables.
<mrvn> whats the difference?
<mrvn> Can I access val through inheritance but not let?
<Riastradh> Class variables are allocated once -- every instance shares them.
<mrvn> # class foo (x:int) = let a = x in object method foo = a end;;
<mrvn> class foo : int -> object method foo : int end
<mrvn> How is the "a" shared there?
<Riastradh> class foo =
<Riastradh> let class_var = ref [0] in
<Riastradh> object
<Riastradh> method get_cv = class_var
<Riastradh> end;;
<mrvn> I can see how that works, but with the "a" above?
<Riastradh> let obj1 = new foo;;
<Riastradh> (obj1#get_cv) := 3 :: (!obj1#get_cv);;
<Riastradh> let obj2 = new foo;;
<Riastradh> !obj2#get_cv;;
<Riastradh> Er, parentheses should be around !(obj[12]#get_cv), but you get the idea.
<Riastradh> The last expression evaluates to [1;0].
<mrvn> I understand the concept and how it would work with a ref [0]. But not with the "a" in my example.
<Riastradh> It's just better style to use 'val,' I guess.
<Riastradh> OH! I see what you're asking.
<mrvn> The problem is that I have some temporary values that I need during the creaion of a class. If I make them values they waste memory. Does ocaml free them when i use let?
<Riastradh> I dunno.
mattam_ has joined #ocaml
mattam has quit [Connection timed out]
b-fast has joined #ocaml
lsr has quit [Remote closed the connection]
<mrvn> If I have 2 classes that depend on each other do I realy have to stick them in two files and make *.mli files?
lus|wazze has joined #ocaml
<async> can't you just put them both in one file?
<mrvn> Then the first clss won't know about the second class and fail.
<mrvn> # class foo = object method foo = new bar end;;
<mrvn> Unbound class bar
<Riastradh> There's no 'and' in class declarations?
<mrvn> not that I see
<Riastradh> class foo =
<Riastradh> object
<Riastradh> method make_bar = new bar
<Riastradh> end
<Riastradh> and bar =
<Riastradh> object
<Riastradh> method make_foo = new foo
<Riastradh> end;;
<Riastradh> ...works for me.
<mrvn> ahh, without the class before bar.
Zadeh has joined #ocaml
<Riastradh> Hi.
<Zadeh> hi?
b-fast is now known as d-bug
d-bug has quit ["brb"]
Smerdyakov has quit ["bye"]
<mrvn> How do i get __FILE__ and __LINE__ in ocaml?
Smerdyakov has joined #ocaml
<mrvn> Smerdyakov: How do i get __FILE__ and __LINE__ in ocaml?
<Smerdyakov> Ouch. I bet you use that p3 thinger.
<Smerdyakov> If there is a way at all :)
<mellum> you mean p4?
<Smerdyakov> Sure.
<Smerdyakov> :-)
<mellum> You probablt confused it with the bar from Charmed.
<mrvn> I hate try match [] with _::_ -> () with Match_error (a,b,c) -> raise (My_exception (a,b,c));
<mrvn> And you can't even put that into a function cause then the line number would be wrong.
TachYon has joined #ocaml
docelic has quit [Read error: 54 (Connection reset by peer)]
docelic has joined #ocaml
noss has joined #ocaml
drlion has quit [Read error: 110 (Connection timed out)]
TachYon has quit [Remote closed the connection]
tootalltimmy has joined #ocaml
Smerdyakov has quit ["eat"]
tootalltimmy has left #ocaml []
mattam_ has quit ["zZz"]
<noss> is the *. and * difference there to make people give information to the type inferencing or is there some other practical reason to avoid polymorphic operators?
<Riastradh> It's probably difficult to make the compiler generate efficient code for when they're called.
<noss> hmm, comparasion operators are polymorphic.
<lus|wazze> # let ( *: ) x y = x :: y;;
<lus|wazze> val ( *: ) : 'a -> 'a list -> 'a list = <fun>
<lus|wazze> hey there i defined a polymorphic operator
<lus|wazze> it has nothing to do with operators
<lus|wazze> an operator can have all of the same types any other variable can
<mrvn> * is for int, *. for float.
<lus|wazze> yep
<lus|wazze> so what?
<mrvn> How else should ocaml know which of those to infer?
<lus|wazze> exactly
<lus|wazze> thats why you cant have overloading
<lus|wazze> but what does that have to do with operators?
<lus|wazze> nothing
<lus|wazze> :: for example is a polymorphic built-in operator .......
<noss> that's some relatively uninteresting answers.
<mrvn> because :: operates on abstract types.
<lus|wazze> well it seems you dont even know exactly what polymorphism is is the problem
<lus|wazze> well thats what (parametric) polymorphism IS? 8)
<mrvn> * and *. operate on a specific type.
<lus|wazze> apparently you two seem to confuse polymorphism with overloading
<mrvn> ask noss if he does. I don#t.
<noss> apparently C++ is your other language.
<lus|wazze> whose? mine? i loathe c++ like no other language
<Riastradh> Not even like Perl?
<lus|wazze> i dont know enough perl to be able to really hate it :)
<mrvn> can perl even be considered a language?
<lus|wazze> well if cobol can then so can perl
<lus|wazze> take that as you will
<Riastradh> Actually, I just wrote some pretty clean Perl code -- but it must be because I was using functional stuff like closures and anonymous functions for the most part.
<mellum> Riastradh: Perl still sucks ;)
<Riastradh> mellum, yeah, it does -- I'm not disagreeïng -- but at least it has a couple of -slightly redeeming features.
<mellum> Probably one for each gross of mind-boggling misfeatures.
<Riastradh> Er, I count two redeeming features -- anonymous functions and closures.
<Riastradh> (you could have closures without anonymous functions -- local functions)
<mellum> Huh? Nearly any languages has that.
<lus|wazze> ?
<Riastradh> Name some other mainstream languages that have anonymous functions -and- closures.
<mellum> well, maybe not nearly any, but at least 50%
<lus|wazze> hm i could list lots of languages thatz dont
<mellum> Riastradh: I was not talking about *mainstream* languages.
<Riastradh> mellum, well, I was, so THERE!
<mellum> Riastradh: Okay, you win. Here's a cookie.
* Riastradh chows.
<mellum> Well, I'll go to bed now... bye
<Riastradh> Bye.
<mrvn> Riastradh: name one ascii character that doesn't have a special meaning in per when preceeded by $.
<mrvn> $<on char long var> doesn#t count as special.
<Riastradh> ~, maybe?
<mrvn> nah, thats used.
<Riastradh> *?
<Riastradh> No, that's used, too.
<mrvn> $a, $b even is used.
<Riastradh> How about (?
<mrvn> Hmm, () and {} are probably not special. Ok.
<Riastradh> Hah!
<Riastradh> But anyways, I'm not advocating Perl.
<mrvn> but $1, $2, $3, $!, $", $$, $%, $&, $/, $_, $?, $*, $a, $b, $', ....
<Riastradh> $[?
<Riastradh> $:?
<mrvn> : should be.
<mrvn> $~ : Mnemonic: brother to $^
<noss> what is the order of the size of an ocaml hello world native binary?
<Zadeh> order of the size?
<noss> or more interesting, does it have a costly startup time like most garbage collected languages seem to have?
<Zadeh> not that I've noticed, but I'm an ocaml newb ;)
<mrvn> mrvn@dual:~% time ./foo
<mrvn> Hallo World!
<mrvn> ./foo 0.01s user 0.00s system 146% cpu 0.007 total
<mrvn> Hallo World!
<mrvn> ./foo_in_c 0.01s user 0.00s system 358% cpu 0.003 total
<mrvn> ~ half as fast as c
<mrvn> mrvn@dual:~% ocamlopt -o foo foo.ml
<mrvn> mrvn@dual:~% time ./foo
<mrvn> Hallo World!
<mrvn> ./foo 0.00s user 0.01s system 267% cpu 0.004 total
<mrvn> compiled ocaml is just as fast as c
<Zadeh> negligable
<mrvn> Nice system times though.
<noss> how do uncaught exceptions make the program die? there is an example of a standalone fibonacci program in the introduction. they parse with int_of_string and never demonstrate a run with errornous input.
<mrvn> Any exception is thrown upwards till a execption handler matches it and the default handler outputs those messages and dies.
* Zadeh has wondered why it's called int_of_string ...wth?
<mrvn> It generates an in out of a string.
<mrvn> +t
<Zadeh> why not string_to_int?
<mrvn> The normal functions are all x_of_y.
<noss> watch out, you'll get the answer that you can do "let string_to_int = int_of_string;;"
<Zadeh> hehe
<mrvn> Only in modules you have bla_to_module and bla_of_module
<mrvn> or rather Module.to_bla and Module.of_bla.
<Zadeh> the naming with an _ seems kinda weird too ;)
<mrvn> Array.of_list or Array.to_list
<mrvn> Zadeh: What else woul you use?
<Zadeh> mrvn: I dunno. Just something that stood out to me while reading a tutorial
<mrvn> upper case is used for constructors.
<mrvn> intOfString might look like a constructor then.