Taaus changed the topic of #ocaml to: http://caml.inria.fr/oreilly-book/
exa has joined #ocaml
rik has left #ocaml []
malc has quit ["no reason"]
tmcm has joined #ocaml
samx has quit [Remote closed the connection]
samx has joined #ocaml
libertaire has joined #ocaml
<libertaire> helloooooo
libertaire has quit []
exa has quit ["using sirc version 2.211+KSIRC/1.2.1"]
samx has quit [carter.openprojects.net irc.openprojects.net]
samx has joined #ocaml
Dieb has quit [Read error: 110 (Connection timed out)]
jemfinch has joined #ocaml
<samx> jem
<jemfinch> samx
<samx> i finally sent a bug report in for sml/nj.. the sml/nj version i got installed finally still isn't working too well.. using 'mod' crashes it every time, otherwise it seems ok..
<samx> i think it is some weird issue having to do with me running the freebsd under vmware
<jemfinch> oh, that's gotta be a vmware thing if using mod crashes it.
<samx> perhaps.. but then again other programs don't seem to have any trouble with vmware.. i also have ocaml and moscow ml installed, and both work and do mod just fine
<samx> i'd try to debug it further, but i'm not familiar enough with the unix debugging tools to really know how to go about it
yangsx has joined #ocaml
yangsx has left #ocaml []
* Yurik is back (gone 17:35:30)
Demitar has joined #ocaml
Cryptor has joined #ocaml
Demitar has quit []
Yurik has quit [No route to host]
Yurik has joined #ocaml
AmRitA has joined #ocaml
AmRitA has left #ocaml []
Cryptor has quit ["Leaving"]
Yurik has quit [Read error: 113 (No route to host)]
skylan has quit [Read error: 104 (Connection reset by peer)]
skylan has joined #ocaml
malc has joined #ocaml
gl has joined #ocaml
Demitar has joined #ocaml
<Demitar> Anyone versed in the evil ways of the Obj module? I want to access the raw representation of an Int32.
<malc> Demitar: what for?
<Demitar> I need to serialize it to be sent across a socket, I guess I could Marshal it and bypass the header unless it's still boxed but that seems evil.
<Demitar> Also could I do some magic to pass the representation unboxed to a C function (namely htonl() in this case).
<malc> Demitar: study byterun/ints.c i guess
<Demitar> I currently do this in a C extension but the serialization part is particularly evil.
<Demitar> The point would be to do all this in ocaml to avoid the need of a C compiler.
<malc> lets rehash. you want raw bits of Int32 and thats it basically
<Demitar> Yep.
<malc> the only thing that comes to mind is the old navy way
<malc> break it down to two 16bit words and to_int them, voila you have the bits
<Demitar> Hmm?
<Demitar> (I'm quite annoyed that there are to_string but no to_char_array or whatever with the representation.)
* Demitar goes to look in pervasives...
<Demitar> Ah, char_of_int...
<Demitar> Well I guess I can fix it then, but is there no way to avoid the oneline stubs to htonl/ntohl? (probably doing something evil to the GC btw. return copy_int32(htonl(Int32_val(v)));)
<malc> no idea
<Demitar> It seems it boiled down to this then...
<Demitar> let serialize ip =
<Demitar> let (>>) num n = Int32.shift_right_logical num n in
<Demitar> let (&) a b = Int32.logand a (Int32.of_int b) in
<Demitar> let tc i = (char_of_int (Int32.to_int i)) in
<Demitar> Printf.sprintf "%c%c%c%c" (tc (ip >> 24)) (tc ((ip >> 16) & 0xff)) (tc ((ip >> 8) & 0xff)) (tc (ip & 0xff))
<malc> how extremely ugly :)
<malc> String.make 4 and then set items indvidiually
<Demitar> I know, but it's better than those C functions I had.
<Demitar> I started on that but decided to reuse a function which was beautiful where it was used.. :)
<Demitar> let (>>) num n = Int32.shift_right_logical num n in
<Demitar> let (&) a b = Int32.logand a (Int32.of_int b) in
<Demitar> let dotted_decimal ip =
<Demitar> Printf.sprintf "%lu.%lu.%lu.%lu" (ip & 0xff) ((ip >> 8) & 0xff) ((ip >> 16) & 0xff) (ip >> 24)
<Demitar> There it is quite nice. ;-)
<Demitar> Hope I didn't do something silly...
<malc> heh
<Demitar> (Like encoding those ints in a bad way...)
<malc> You can do it in more hackish ways
<malc> consider this
<malc> # Marshal.to_string (Int32.of_int 12) [Marshal.No_sharing];;
<malc> - : string =
<malc> "\132\149\166\190\000\000\000\008\000\000\000\000\000\000\000\003\000\000\000\003\018_i\000\000\000\000\012"
<malc> last 4 bytes are clearly the value you need
<Demitar> I considered that but it felt a bit too implementation dependant..
<Demitar> I didn't switch to ocaml to put the typesystem out of order all the time. ;-)
<malc> yet you come here asking to blow typesystem with Obj :)
<Demitar> I know, but I hadn't found char_of_int at the time. ;-)
<Demitar> And if it would allow me to keep my htonl wrapper in pure ocaml code I'd blow it up anytime. ;-)
<malc> heh
<Demitar> As I suspected I shouldn't have tossed that encoding around.
<Demitar> I have a feeling the deserizlier will look even worse... ;-)
<malc> just create 4 char long string and put char_of_int'ed elements there byte by byte
<Demitar> No that's what I did, I'll need to add some int32's this time. :)
<Demitar> The old code looks eevil...
<Demitar> let unpack_uint32 pos str =
<Demitar> let up i n =
<Demitar> (setbyte i n (str.[pos+n]))
<Demitar> in
<Demitar> ntohl (up (up (up (up Int32.zero 0) 1) 2) 3)
<malc> bah just move it to C, its where this bit fiddling belongs anyhow
<malc> use netstring it must have all needed primitives methinks
<Demitar> Nah, that's kindof the point, I've already done it in python and done a bit of fiddling with the original C version.
<Demitar> Got it a bit better this time...
<Demitar> let deserialize str pos =
<Demitar> let (<<) num n = Int32.shift_left num n in
<Demitar> let ti i = (Int32.of_int (int_of_char (str.[pos+i]))) << i*8 in
<Demitar> let (+) = Int32.add in
<Demitar> ti 0 + ti 1 + ti 2 + ti 3
<malc> good
<Demitar> I also changed the other function since another person didn't like it either. :)
<Demitar> let str = String.create 4 in
<Demitar> for n=0 to 3 do
<Demitar> str.[n] <- (tc ((ip >> 8*n) & 0xff))
<Demitar> done;
<Demitar> str
<malc> well you know, great minds think alike and shit like that
<Demitar> Well you're all welcome to refactor my code, I would if I cared that much about that part of the code, it's only called about ten times each during a normal run (which is potentially hours each time). ;-)
<malc> Int32.format "08x" <-> Int32.of_string if you dont care, easy as a pie
Yurik has joined #ocaml
<Demitar> And you tell me that *now*? ;-)
<malc> Uh, yeah... why? >B) i thought that was the most obvious way and you already rejected it
* Demitar mutters a bit about the .format functions being at the bottom of the manual...
<Demitar> Hmm.. but that doesn't allow me to pass it to htonl now, does it? So I guess the hassle wasn't without usefulness.
<Demitar> or wait.
<Demitar> I do that on the int32s anyway..
* Demitar mutters a bit more...
* Demitar suspects he is getting tired...
<Demitar> But %08x will pack it in hex, which I don't want... *sigh* I ought to get some sleep soon.
<malc> hex or not hex is irrelevant if we are talking about simple serialization/deserialization
<Demitar> Well, I don't decide the format, which is the issue.
<malc> ta-ta
malc has quit ["no reason"]
Yurik has quit [Connection timed out]
Yurik has joined #ocaml
Yurik has quit [Read error: 113 (No route to host)]
Yurik has joined #ocaml
samx has quit [carter.openprojects.net irc.openprojects.net]
timmy has quit [carter.openprojects.net irc.openprojects.net]
Demitar has quit [carter.openprojects.net irc.openprojects.net]
Yurik has quit [carter.openprojects.net irc.openprojects.net]
skylan has quit [carter.openprojects.net irc.openprojects.net]
gl has quit [carter.openprojects.net irc.openprojects.net]
Taaus has quit [carter.openprojects.net irc.openprojects.net]
gl has joined #ocaml
timmy has joined #ocaml
Taaus has joined #ocaml
Yurik has joined #ocaml
skylan has joined #ocaml
Yurik has quit [carter.openprojects.net irc.openprojects.net]
skylan has quit [carter.openprojects.net irc.openprojects.net]
Yurik has joined #ocaml
skylan has joined #ocaml
samx has joined #ocaml