systems changed the topic of #ocaml to: Archive of Caml Weekly News http://pauillac.inria.fr/~aschmitt/cwn/ | ICFP Programming Contest 2003 http://www.dtek.chalmers.se/groups/icfpcontest/ | A tutorial http://merjis.com/richj/computers/ocaml/tutorial/ | Good free book http://cristal.inria.fr/~remy/cours/appsem/ | Mailing list (best mailing list ever for any computer language) http://caml.inria.fr/bin/wilma/caml-list
_BT has joined #ocaml
<_BT> .
<_BT> tossed that out in case anyone needed a spare dot to do a float addition or something
<Smerdyakov> Whoa, _BT! Your username starts with a [!
vect has joined #ocaml
Xcalibor has quit ["Terminando cliente"]
Riastrad1 is now known as Riastradh
vect has quit [Read error: 110 (Connection timed out)]
vect has joined #ocaml
brwill_busy is now known as brwill
bk_ has joined #ocaml
teratorn has quit [Read error: 110 (Connection timed out)]
teratorn has joined #ocaml
teratorn has quit [Read error: 104 (Connection reset by peer)]
polin8 has quit [Remote closed the connection]
teratorn has joined #ocaml
mrvn_ is now known as mrvn
bk_ has quit ["I'll be back"]
wax has joined #ocaml
srv has joined #ocaml
bk_ has joined #ocaml
mattam has joined #ocaml
foxen has joined #ocaml
mattam_ has quit [Connection timed out]
brwill is now known as brwill_zzz
foxster has quit [Client Quit]
Yurik has joined #ocaml
foxen has quit [Client Quit]
foxster has joined #ocaml
buggs is now known as buggs|afk
polin8 has joined #ocaml
bk_ has quit ["I'll be back"]
phubuh has quit [Read error: 54 (Connection reset by peer)]
phubuh has joined #ocaml
systems has joined #ocaml
_BT has quit ["Client Exiting"]
Yurik has quit ["÷ÙÛÅÌ ÉÚ XChat"]
Yurik has joined #ocaml
bk_ has joined #ocaml
systems has quit ["Client Exiting"]
Anders has joined #ocaml
Anders has quit [Client Quit]
Anders has joined #ocaml
Anders is now known as Demitar
whee has quit ["Leaving"]
srv has quit [Remote closed the connection]
Demitar has quit ["Bubbles everywhere!"]
polin8 has quit [Read error: 104 (Connection reset by peer)]
polin8 has joined #ocaml
<Maddas> hm
<Maddas> anybody around? :)
<Smerdyakov> Oh YEAAAH!
<Maddas> haha :)
<Maddas> What is the highest number that int_of_string successfully converts?
<Maddas> or that an int can hold
<Maddas> I thought it would be 2^31
<Smerdyakov> There's probably a member of Int for that.
<Maddas> Pardon?
<Maddas> I'm just doing something trivial and wondering why int_of_string of 2147483644 returns -4
<Smerdyakov> Because you've overflowed the capacity, like you've guessed, probably.
<Maddas> Ok.
<Smerdyakov> There is probably a member of the Int module that gives the exact highest supported value.
<Maddas> I'll just loop through until I see which value can be held.
<Maddas> ah, I see.
<Smerdyakov> Hm. There doesn't seem to be an Int module in OCaml. Oh well.
<Maddas> :)
<phubuh> # max_int;;
<phubuh> - : int = 1073741823
<Smerdyakov> Shucks. I just found that myself.
<phubuh> # ceil (log (float_of_int max_int) /. log 2.0);;
<phubuh> - : float = 30.
<Maddas> cool, thanks.
<Maddas> so it's 2^30-1, I see
__buggs has joined #ocaml
srv has joined #ocaml
buggs|afk has quit [Read error: 110 (Connection timed out)]
__buggs is now known as buggs
srv has quit [Remote closed the connection]
vegai has joined #ocaml
systems has joined #ocaml
<Maddas> hm
Xcalibor has joined #ocaml
<Xcalibor> hiyas
<Maddas> hi :)
<Xcalibor> hi, whassup?
<Maddas> trying to implement a prime-searching thing that works well :)
matthieu_ has joined #ocaml
systems has quit ["Client Exiting"]
<Xcalibor> ah, nice :)
<Xcalibor> mmm... how do I reverse a string?
<Riastradh> String.rev, maybe?
<Riastradh> Hm, I guess there is no String.rev.
<Xcalibor> i think there's not...
<Xcalibor> there's a String.rindex to move from right to left...
<Riastradh> Well, it's pretty trivial.
<phubuh> it would be more trivial if strings were char lists :~(
<Xcalibor> mmm... I cannot think of a functional way of doing so...
<Xcalibor> is there a range function? like range 1 10 to return [1;2;3;4...;10] ?
<Xcalibor> okay, how to make a list of a string?
<phubuh> here's some old code to do it, which when i look at it now is pretty embarrassing:
<phubuh> let explode s =
<phubuh> let rec aux s l =
<phubuh> match s with
<phubuh> "" -> l
<phubuh> | s -> aux (String.sub s 1 ((String.length s) - 1))
<phubuh> (l @ [(String.get s 0)]) in
<phubuh> aux s []
<Riastradh> Eww, that's horrible.
<phubuh> i agree :)
<Riastradh> Ack, String doesn't export a fold_right!
<Riastradh> (or a fold_left, even)
<phubuh> i strongly dislike ocaml's strings :/
<Riastradh> let fold_right kons knil s =
<Riastradh> let rec loop knil = function
<Riastradh> i when i >= String.length s -> knil
<Riastradh> i -> kons (String.get s i) (loop knil (i + 1))
<Riastradh> in loop knil 0
<Riastradh> let explode s = fold_right (:) [] s
<Xcalibor> Riastradh: i was looking for a folding function...
<phubuh> you probably mean fold_right (::) [] s
<Riastradh> Er, yes, I do.
<Riastradh> And I also forgot vertical bars.
<phubuh> oh :)
<Riastradh> That's funny. It's giving me a syntax error about the (::).
<Xcalibor> same here
<phubuh> that is very odd
<phubuh> (fun a b -> a :: b) will do, but it's very strange that :: isn't slicable
<Xcalibor> nod
<Xcalibor> and now the implode...
<Riastradh> That can't be done functionally -- strings are inherently somewhat imperative --.
<phubuh> here's some equally shitty code:
<phubuh> let implode l =
<phubuh> let buf = Buffer.create 8 in
<phubuh> let rec aux = function
<phubuh> [] -> ()
<phubuh> | x :: xs -> Buffer.add_char buf x; aux xs in
<phubuh> aux l;
<phubuh> Buffer.contents buf
<phubuh> well, slightly less shitty, i guess
<phubuh> also my strings were all about 8 characters long; you probably want to adjust that value :)
<Riastradh> let implode l =
<Riastradh> let rec loop r = function
<Riastradh> i when i < 0 -> r
<Riastradh> Er, oops.
<Riastradh> let implode l =
<Riastradh> let s = String.make (List.length l) in
<Riastradh> let rec loop r = function
<Riastradh> Glerble?
* Riastradh murmbles.
* Riastradh writes it in an Emacs buffer before pasting it.
Yurik has quit [Read error: 110 (Connection timed out)]
<Riastradh> let implode l =
<Riastradh> let k = List.length l in
<Riastradh> let s = String.create k in
<Riastradh> let rec loop i = function
<Riastradh> [] -> s
<Riastradh> | h :: t ->
<Riastradh> String.set s i h;
<Riastradh> Blargle!
* Riastradh snrufglischlates.
<phubuh> :)
<Riastradh> let implode l =
<Riastradh> let s = String.create (List.length l) in
<Riastradh> let rec loop i = function
<Riastradh> [] -> s
<Riastradh> | h :: t ->
<Riastradh> String.set s i h;
<Riastradh> loop (i + 1) t
<Riastradh> in loop 0 l
<Riastradh> Finally!
<phubuh> yay!
<Xcalibor> whoah!
<Xcalibor> shouldn't the loop (i + 1) t be indented with the | ?
<Riastradh> No.
<Riastradh> It should be indented exactly where it is indented.
<Xcalibor> mmm
<Xcalibor> so you loop after setting the string, right?
<Riastradh> After setting a single character in the string, yes.
<Xcalibor> okay, understood :-)
<Xcalibor> if I have a .ml file with all these definitions, how can I read them into my toplevel?
<phubuh> use ocamlc to compile it, and then run ocaml with the cmo file
<phubuh> ocamlc foo.ml && ocaml foo.cmo
<Xcalibor> mmm... isn't there a kind of 'load' for these, like open does?
<Xcalibor> the thing was to write a function that returns the palindrome from an integer...
<phubuh> the palindrome from an integer?
<Xcalibor> yup
<phubuh> 123 -> "321123"?
<Xcalibor> apparently, you can get a palindrome number for every integer by reversing it, summing it with its reverse and, if necessary, repeating this process...
<Xcalibor> for example: 28 -> 28 + 82 -> 110 -> 110 + 011 -> 121 QED
<Riastradh> #load "path/to/file.ml";;
<Xcalibor> it's nice, but it sometimes converge very slowly...
<Xcalibor> Riastradh: File palindrome.ml is not a bytecode object file.
<Xcalibor> thus if the number you are going is rgeater than 10000000 the we should return the special value -1
<Xcalibor> with these functions (implode and explode) I wrote this:
<Xcalibor> let rec palindrome n =
<Xcalibor> let m = int_of_string (implode (List.rev (explode (string_of_int n)))) in
<Xcalibor> if n >= 10000000 then -1 else
<Xcalibor> if n = m then n
<Xcalibor> else palindrome (n + m)
<Riastradh> OK, compile it first and then load the .cmo file.
<Xcalibor> okis
<Xcalibor> # palindrome 196;;
<Xcalibor> Exception: Failure "int_of_string".
<Xcalibor> ???
<Xcalibor> 196 converges really slowly (so far 20,000 digits number and no palindrome found) and it's one of the test cases
<Xcalibor> it should return -1
<Xcalibor> why is it failing?
mrvn_ has joined #ocaml
<Riastradh> Er, why not multiply n by the number of digits in it and then add a reversed n to that larger number?
<Xcalibor> Riastradh: sorry?
<Riastradh> Rather, shift n left in base 10 by the number of digits in it and then add a reversed n to that number.
<Riastradh> n = 92
<Riastradh> n' = 9200
<Riastradh> m = 29
<Riastradh> 9200 + 29
<Riastradh> 9229
<phubuh> that wouldn't be as much of a challenge :) (i imagine this is a homework question)
<Riastradh> Yes, but my algorithm is probably a lot faster.
<Xcalibor> Riastradh: ok, yeah... there are probably thousands of ways of getting a palindrome out of an integer... this theorem says that for all n : Int such as that n is a palindrome, there exist numbers m and c such as m + (reverse m) c times equals n
mrvn has quit [Read error: 110 (Connection timed out)]
<Xcalibor> phubuh: it's actually a TopCoder (www.topcoder.com) round tournament from the past... i solved it in C++ and was trying to exercise my Ocaml and Haskell on it, as I found a recursive solution in C++...
<phubuh> Riastradh, why not int_of_string (n ^ (rev n))? :)
<phubuh> oh
<Xcalibor> phubuh: do you know why it's giving me that error instead of -1 for case 196?
whee has joined #ocaml
<Xcalibor> hi whee
* Xcalibor brb phone
<whee> hola
<whee> fending off a massive headache after a day of work :| heh
srv has joined #ocaml
<Xcalibor> whee: are you around?
srv has quit [Remote closed the connection]
srv has joined #ocaml
<whee> indeed
<whee> waiting for dinner to cook itself here :)
<Xcalibor> okay... we defined functions expande and implode to take a string and return a list, and vice versa, okay?
<whee> mkay
<Xcalibor> then we defined the function nreverse as to take an integer and return it's 'nreverse', ie 123 -> 321
<Xcalibor> and the defined a function to calculate palindrome numbers from a number n by adding the nreversal until a palindrome is found...
<Xcalibor> let palindrome n =
<Xcalibor> if n > 10000000 then ~-1 (* cut condition for very slowly convergence cases *)
<Xcalibor> else if n = nreverse n then n else palindrome (n + (nreverse n))
<Xcalibor> actually there was a let m = nreverse n in in there :-)
<Xcalibor> palindrome 28 returns 121 as expected (and all the rest are working...)
<Xcalibor> 196 is a very slowly converging solution (current result has more than 20,000 digits and still growing) thus palindrome 196 should return .1, but I get an error: # palindrome 196;;
<Xcalibor> Exception: Failure "int_of_string".
<Xcalibor> any idea why?
<phubuh> print the failing string
<whee> yes, I'd do that
<Xcalibor> okay, how?
<whee> I'm guessing you're getting a number that's outside the range of an int type
<Xcalibor> mmm...
<whee> well, catch that failure exception and print it
<whee> or just print out each string as you go and see how far it gets
<whee> but probably not, I don't think that raises an exception
<Xcalibor> agreed
<whee> you could alternatively use the debugger instead of printing the string
<whee> good time to learn it if you don't know how it works :)
<whee> it has the ability to step backwards in time, so you could just run it until it fails and go back
<Xcalibor> if it doesn't work like gdb then I don't :)
<Xcalibor> mmm... okay... i put those functions into a .ml file. ocamlc -i -c palindrome.ml -> get palindrome.cmo
<Xcalibor> #load "palindrome.cmo";;
<Xcalibor> but palindrome 12;;
<Xcalibor> gives an error... (???) namespace problem?
<Xcalibor> # palindrome 12;;
<Xcalibor> Unbound value palindrome
<whee> you probably need to open it still
<whee> or directly address the module
<Xcalibor> how? open palindrome breaks...
<Xcalibor> and palindrome.palindrome 12 gives unbound value as well...
<whee> usually module names start with a capital letter, that might be it
<Xcalibor> ah... mmm let me try
<Xcalibor> yup :)
<Xcalibor> you are absolutely right... Palindrome.palindrome worked... I put debugging prints into the recursion, let me see what happens...
<Xcalibor> mmm... now it returns -1 without problem ???
<whee> haha
<whee> remove the print statements and try that again
<Xcalibor> i see... i was using the old definition in the toplevel instead of the one in the file...
<Xcalibor> silly me
<Xcalibor> now that i started the toplevel from scratch there's no toplevel function to fool me... :-P
<Xcalibor> like a charm now... :-)
<Xcalibor> same problem in haskell (i was actually talking about it there with ria and lunar^ :)
<Xcalibor> same solution (a bit simpler since haskell strings are lists of chars...)
<whee> yeah, that does make it easier for languages that treat strings as lists
<whee> although you should be able to pull off a one liner to reverse strings with something in either the String or Buffer modules
liyang has joined #ocaml
<Xcalibor> however i was thinking in a solution in terms of returning a list of the form n :: (n + (reverse n)) and then applying last? filter is_palindrome ls
<Xcalibor> the idea is how i would solve it 'elegantly' in Scheme, by returning promises...
liyang has left #ocaml []
<whee> you could use streams to lazily construct that list
<Xcalibor> however, although I know it has to work, I don't seem able to write it down so hughs98 like it :-P
<whee> it might look cleaner with streams too, hrm
<Xcalibor> should we go over #haskell and discuss it?
<whee> my haskell knowledge is rusty as hell so I doubt I could do much there :
<Xcalibor> whee: i am sure it is faster and much cleaner and more elegant... it has to be as it is in scheme, but how do I write it?
<Xcalibor> hehe, mine is worse than rusty :-P
<whee> what are you looking to write?
<whee> http://caml.inria.fr/archives/200104/msg00305.html looks like a decent streams example
<Xcalibor> something like this (pseudo haskell) palindrome n = hd . filter is_palindrome (n :: (n + (nreverse)))
<Xcalibor> ie, my result is the first one that satisfies being a palindrome in the list of the form [n, n+(nreverse n), (n + (nreverse n)) + (nreverse (n + (nreverse n))), ...]
<whee> right
<whee> I think that link I pasted above would be helpful
<Xcalibor> or -1 if the number I am in that list is bigger than my cut_limit of 1e8
<whee> it does basically the same thing
<Xcalibor> aha... streams are like lazy list comprehensions?
<whee> a stream in ocaml can be thought of as haskell's lists
<Xcalibor> aha... cool...
<whee> well, almost like them
<whee> there's more things you can do (http://caml.inria.fr/ocaml/htmlman/libref/Stream.html)
<whee> streams are just syntactic sugar for some other fun, though
<Xcalibor> i'll pursue this path tomorrow... :-) so i get a nicer solution both in OCaml and in Haskell... and then I'll try to apply it to the original C++ solution (maybe using FC++?? ;-)
<whee> heh
<whee> C++ is just evil :P
<whee> although I can stand it if I use something like boost as well
<Xcalibor> whee: well, it was a full STL solution the one I found out...
<Xcalibor> and, not very surprisingly, a recursive function :-)
<Xcalibor> that's when I thought 'hey this should be easy in ocaml or haskell' :-)
<whee> iteration is just a subset of recursion, so it should go either way in this case
<Xcalibor> (it is easy easy easy in scheme, so no merit in that :-)
<Riastradh> Hah! SRFIs 40 and 41 are a lot more comprehensive than the measly Stream module!
<Xcalibor> well... cannot think of a way to do it :-P
<Riastradh> Does the Stream module implement even or odd streams, by the way?
<Xcalibor> (iteratively, i mean)
<whee> Riastradh: define even and odd
<Xcalibor> however, i haven't been able to make it tail recursive... the C++ solution smashed the stack after some 250,000 rounds...
<Xcalibor> Riastradh: do you mean filtering out the even or odd elements of the Stream on the run?
<Riastradh> Even: stream_cons a b <=> lazy (a : b)
<whee> Xcalibor: is your ocaml solution tail recursive?
<Riastradh> Odd: stream_cons a b <=> a : lazy b
<whee> you should be able to make it so with an accumulator or something
<Riastradh> Well, that's not quite the right syntax to use, but you get the idea.
<whee> I need to start looking into scheme again :\
<Riastradh> To use a more accurate Scheme syntax:
<Riastradh> Even: (stream-cons a b) <=> (delay (cons a b))
<Xcalibor> whee: no, the ocaml solution so far is similar to the C++ one... i would venture ocaml tail elimination would make it better than c++ sirect stack, but i haven't been able to find out which accumulator to put...
<Riastradh> Odd: (stream-cons a b) <=> (cons a (delay b))
<Xcalibor> Riastradh: ah... i see what you mean... i have absolutely no idea if this is implemented in Streams, sorry...
<whee> I have no idea if it is or not
<whee> heh
<whee> I'm really not sure how evaluation is handled with streams
<Riastradh> I'd look it up, but I don't want to have to bother downloading the whole distribution (I'm short on disk space right now), and CVSWeb is broken.
<whee> Riastradh: just want the stream module?
<Xcalibor> the interface doesn't show anything like it
<Xcalibor> well... getting too late
<Xcalibor> gotta run to bed... thanks for all the help, tomorrow more ;-)
<Riastradh> Ah, thanks.
<Riastradh> Eww. That's a rather ugly implementation.
<Xcalibor> lol
<Riastradh> Yuck yuck yuck yuck.
<Xcalibor> laters!!
<whee> rewrite it :P
Xcalibor has quit ["Terminando cliente"]
<Riastradh> No, I'll just use Scheme.
<whee> and I think I'm going to spend more time with scheme starting tomorrow
<whee> assuming I find a nice implementation (and I remember talking about this before :|)
* Riastradh suggests CHICKEN and Scheme48.
<whee> what's the cmucl or sbcl of scheme? heh
<Riastradh> Er...I don't quite know enough about the CL implementations to say.
<whee> well, the most widely used scheme implementation
<Riastradh> There isn't one.
<whee> :\
<Riastradh> PLT and Bigloo seem to be pretty widely used, but I have an ever-increasing dislike for them.
<Riastradh> They just get hairier and hairier and more and more monstrous as time goes on.
<whee> I've used bigloo before, I didn't really like it
<whee> I'm still leaning towards sisc, but I'm not sure how a java implementation stacks up with something like chicken which goes to C
<whee> what I'm really planning on doing is using scheme to do a lot of automatic system management things on that itx box I'll be building
<Riastradh> What do you mean by 'stacks up with?'
<whee> in terms of speed, srfis supported, debugging capabilities, that sort of thing
<whee> I'm not sure if I'd like to require a jvm for these types of things, for example
<whee> but then again, I'd like to try to use all the exotic features an implementation like sisc supports that others may or may not
<whee> then again I might end up using erlang for this type of thing too, heh
<whee> it'd be nice to be able to tweak things easily at runtime, plus mnesia is nice and easy to work with
<whee> add yaws, and it's perfect :)
matthieu_ has quit ["Client exiting"]