mbishop changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | Grab Ocaml 3.10.0 from http://caml.inria.fr/ocaml/release.html (featuring new camlp4 and more!)
love-pingoo has quit ["Connection reset by pear"]
cpst has joined #ocaml
Cygal has joined #ocaml
buluca has joined #ocaml
abez has quit ["leaving"]
bluestorm has quit ["Konversation terminated!"]
crabstick_ has joined #ocaml
seafoodX has quit []
Cygal has quit [Remote closed the connection]
crabstick has quit [Read error: 110 (Connection timed out)]
crabstick has joined #ocaml
crabstick_ has quit [Read error: 110 (Connection timed out)]
netx has quit ["Leaving"]
seafoodX has joined #ocaml
Smerdyakov has quit ["Leaving"]
grirgz has joined #ocaml
<grirgz> hi
<grirgz> i have defined a double hashtbl with : type t = ('a, 'b) Hashtbl.t * ('b, 'a) Hashtbl.t;;
<xavierbot> Characters 1-2:
<xavierbot> i have defined a double hashtbl with : type t = ('a, 'b) Hashtbl.t * ('b, 'a) Hashtbl.t;;
<xavierbot> ^
<xavierbot> Unbound value i
<xavierbot> Characters 33-37:
<xavierbot> Parse error: illegal begin of top_phrase
<grirgz> euh
<grirgz> and i hava an error : Unbound type parameter 'a
<grirgz> but i saw in the hashtbl.ml source file the same type of declaration
<pango> type ('a, 'b) t = ...
<grirgz> arf
<grirgz> i am tired =)
<grirgz> thank you
<pango> np
tty56_ has joined #ocaml
tty56 has quit [Read error: 60 (Operation timed out)]
netx has joined #ocaml
<seafoodX> Anyone know of a dictionary implementation in OCaml?
<seafoodX> I should be more precise. By dictionary I mean essentially an associative array where the indices can be things other than integers.
<authentic> also known as hashtables?
<tsuyoshi> yeah you can do that with either the hash tables or maps in the standard library
ednarofi has joined #ocaml
<seafoodX> tsuyoshi: Maps are exactly what I was looking for.
<seafoodX> THanks
<grirgz> the compiler says the type _[> `adjectif | `article ] lexique contains type variables that cannot be generalized. I dont understand what should i do to help it to generalize
buluca has quit [Read error: 113 (No route to host)]
Smerdyakov has joined #ocaml
Hadaka has quit [Read error: 60 (Operation timed out)]
seafoodX has quit []
|Jedai| has joined #ocaml
jedai has quit [Read error: 110 (Connection timed out)]
ednarofi has quit [Read error: 110 (Connection timed out)]
schme` has joined #ocaml
ednarofi has joined #ocaml
Smerdyakov has quit ["Maybe he is doomed."]
schme has quit [Read error: 110 (Connection timed out)]
ednarofi has quit [Read error: 104 (Connection reset by peer)]
ednarofi has joined #ocaml
ednarofi has quit [Connection timed out]
crabstick_ has joined #ocaml
slipstream-- has joined #ocaml
crabstick has quit [Read error: 110 (Connection timed out)]
seafoodX has joined #ocaml
crabstick_ has quit [Read error: 110 (Connection timed out)]
seafoodX has quit [Client Quit]
slipstream has quit [Read error: 110 (Connection timed out)]
slipstream-- has quit [Read error: 104 (Connection reset by peer)]
slipstream has joined #ocaml
seafoodX has joined #ocaml
rwmjones has joined #ocaml
bluestorm has joined #ocaml
Tetsuo has joined #ocaml
ygrek has joined #ocaml
authentic has quit [Read error: 110 (Connection timed out)]
pango has quit [Remote closed the connection]
pango has joined #ocaml
authentic has joined #ocaml
slipstream-- has joined #ocaml
<mattam> grirgz: you probably need to ascribe a type to a lexique object which you put in a reference somewhere. Look at this: http://caml.inria.fr/resources/doc/faq/core.en.html#weak-type-variables
seafoodX has quit []
slipstre1m-- has joined #ocaml
slipstream has quit [Read error: 110 (Connection timed out)]
slipstream has joined #ocaml
slipstream-- has quit [Read error: 110 (Connection timed out)]
slipstre1m-- has quit [Read error: 110 (Connection timed out)]
piggybox_ has joined #ocaml
slipstream-- has joined #ocaml
piggybox has quit [Connection timed out]
slipstream has quit [Read error: 110 (Connection timed out)]
love-pingoo has joined #ocaml
Demitar has quit [Read error: 113 (No route to host)]
seafoodX has joined #ocaml
piggybox_ is now known as piggybox
Cygal has joined #ocaml
seafoodX has quit []
joshcryer has quit [Read error: 113 (No route to host)]
schme`` has joined #ocaml
schme` has quit [Read error: 110 (Connection timed out)]
xavierbot has quit [Remote closed the connection]
xavierbot has joined #ocaml
Cygal is now known as Cygaal
Cygaal has quit [Remote closed the connection]
ednarofi has joined #ocaml
ygrek has quit [Remote closed the connection]
Naked has joined #ocaml
Naked is now known as Hadaka
|Jedai| is now known as jedai
<flux> is it required in Ocaml to Thread.join a thread that has been Thread.created? the documentation doesn't suggest anything like that, so I guess not..
<flux> slight testing suggests that this aspect is automatic
pango has quit [Excess Flood]
<tsuyoshi> yeah, probably the garbage collector takes care of that
<flux> i think it is handled even before gc
pango has joined #ocaml
<tsuyoshi> really?
<flux> because the thread disappears immediately
<flux> say the thread does Unix.sleep 10 it disappears after 10 seconds
<tsuyoshi> what do you mean by "disappears"
<flux> from the process list, ps -eLf
<tsuyoshi> oh, that's not the same as being joined though
<flux> I was thinking that from the aspect of unix processes, which become zombies unless they are wait()ed on (or other trickery performed)
<tsuyoshi> like.. joining a thread frees the return value
<flux> yes, I think that should be handled by gc (although ocaml threads don't have a return value)
<tsuyoshi> I'm thinking in terms of pthread_join()
<flux> and I think normal pthreads need to be joined too, unless they are detached threads?
<flux> or no?
<tsuyoshi> in c you need to join every thread
<tsuyoshi> I don't know how it would work in ocaml exactly.. never used threads in ocaml
rwmjones has left #ocaml []
seafoodX has joined #ocaml
ednarofi has quit [Remote closed the connection]
ednarofi has joined #ocaml
piggybox_ has joined #ocaml
buluca has joined #ocaml
|Jedai| has joined #ocaml
joshcryer has joined #ocaml
piggybox has quit [Connection timed out]
piggybox_ is now known as piggybox
piggybox_ has joined #ocaml
piggybox has quit [Nick collision from services.]
piggybox_ is now known as piggybox
jedai has quit [Read error: 110 (Connection timed out)]
olegfink has joined #ocaml
<olegfink> hi
<olegfink> is there anything like 'static' variables from C?
<olegfink> I want to make an interface for writing bits (not bytes) to files, so I need to implement some sort of buffering
<olegfink> or am I going the wring way maybe?
<flux> olegfink, well, you can do this:
<flux> let function_with_static_state = let state = ref 0 in let actual_function () = incr state; !state in actual_function;;
<xavierbot> val function_with_static_state : unit -> int = <fun>
<flux> function_with_static_state ();;
<xavierbot> - : int = 1
<flux> function_with_static_state ();;
<xavierbot> - : int = 2
<olegfink> aha
<olegfink> but is it the right way of doing buffered I/O?
<flux> but if you're having an interface, how about something like having type t = { buffer : string; buffer_at : int; } etc?
<flux> type t contents would then be hidden by the interface mechanism
<olegfink> hm
<olegfink> I'm doing very simple thing
<flux> if a single function is enough of an interface, I suppose it's ok to do that trick: have a function that creates a new state and returns a function that manipulates that state
<olegfink> I think I just need functions output_bits nofbits value and input_bits nofbits, that's all
<flux> something like this then perhaps: let input_bits_func stream = let state = ... in let get_bits n = .. use state and stream .. in get_bits
<bluestorm> flux:
<bluestorm> you can even do
<bluestorm> let fun1, fun2, fun3 = let state = ... in let fun1 = .. in ... (fun1, fun2, fun3)
<bluestorm> no "single function" restriction
<olegfink> okay, thank, will try to implement this
<flux> true, it requires more effort to use that kind of construct however
<olegfink> *thanks
<flux> especially if you want to change the set of functions later
<flux> but, you can use.. tada! the object system too :)
<bluestorm> hm
<flux> (or return a record with functions)
<flux> actually I suppose the object system is something that is designed exactly for this case..
<olegfink> theres no built-in bitwise shift in ocaml, right?
<danderson> there is, in Pervasives
<danderson> lsl;;
<xavierbot> lsl;;
<xavierbot> ^^^
<xavierbot> Characters 1-4:
<xavierbot> Parse error: illegal begin of top_phrase
<danderson> uh
<bluestorm> fun a b -> a lsl b;;
<xavierbot> - : int -> int -> int = <fun>
<bluestorm> :-'
<danderson> oh
<danderson> (lsl);;
<xavierbot> (lsl);;
<xavierbot> ^
<xavierbot> Characters 1-2:
<xavierbot> Parse error: illegal begin of top_phrase
<danderson> oh well
<flux> hey, that's a new one
<olegfink> aha, were looking for the names (<<) and (>>)
<danderson> I definitely suck at ocaml :)
<danderson> I thought (operator) would return the function for that operator.
<bluestorm> danderson: that's not your fault
<flux> let _ = (lsl)
<flux> let _ = (lsl);;
<xavierbot> let _ = (lsl);;
<xavierbot> ^
<xavierbot> Characters 9-10:
<xavierbot> Parse error: [expr] expected after "=" (in [let_binding])
<olegfink> danderson: () is just parantheses, nothing more
<danderson> (+);;
<xavierbot> - : int -> int -> int = <fun>
<flux> hm, obviously () doesn't work for lsl
<flux> well, s/obviously/for some reason/
<bluestorm> it's an ugly exception of the grammar
<bluestorm> but
<bluestorm> ( lsl );;
<xavierbot> ( lsl );;
<xavierbot> ^
<xavierbot> Characters 1-2:
<xavierbot> Parse error: illegal begin of top_phrase
<flux> hmm, why does (lsl) work for me
<bluestorm> hm
<danderson> bzzt :)
<flux> old version of ocaml?
<bluestorm> xavierbot may use camlp4
<danderson> the exception is understandable for ( * )
<danderson> to tell the operator apart from comments
<bluestorm> yes but lsl, lor and so on are ad-hoc exceptions hardcoded into the grammar
<bluestorm> so you shouldn't expect them to behave nicely
<bluestorm> seems the default ocaml parser accept (lsl), and the camlp4 one doesn't
puks has joined #ocaml
<danderson> aren't they 'exceptions' on the same level that + is?
<bluestorm> h
<danderson> but, I can see why the parser would barf, kinda.
<olegfink> one more question;
<olegfink> what is the easiest way to compute the bit-width of the specified number?
<olegfink> something like log(number)/log(2)?
<flux> let rec count_bits n = if n > 0 then 1 + count_bits (n / 2) else 0
<danderson> from memory, ceiling of the binary logarithm should do it
<flux> you can get relatively fast too by doing a binary search by using bit masks
<danderson> let nbits x = ceil ((log (float_of_int x))/.(log 2.));;
<xavierbot> val nbits : int -> float = <fun>
<bluestorm> :p
<danderson> let nbits x = int_of_float (ceil ((log (float_of_int x))/.(log 2.)));;
<xavierbot> val nbits : int -> int = <fun>
<danderson> there, that should work.
<danderson> note that depending on the architecture, you may have a much, much easier way of finding out for native integers
<danderson> some cpus have a 'MSSB' opcode, that returns the most significant set bit in a given register
<danderson> (iirc the arm9 has that)
love-pingoo has quit ["Connection reset by pear"]
twobitsprite has joined #ocaml
<twobitsprite> hello
<twobitsprite> is it possible to write an ocaml program that will run on the bare metal?
<danderson> define bare metal?
<danderson> ocaml can be compiled to native machine code
<twobitsprite> no underlying OS
<danderson> dunno if it can be run without OS support
<zmdkrbou> twobitsprite: yes, but it's complicated
<danderson> my guess is that you'll probably need a small chunk of bootstrap code in C and asm
<danderson> to set up a C-friendly environment in the machine
<danderson> then branch into the ocaml program's main()
<twobitsprite> I didn't think ocaml was dependant on C
<zmdkrbou> ocaml isn't, but you can't boot a machine without using asm
<danderson> by C friendly environment, I mean a C-style stack set up
<zmdkrbou> and you can't use asm inside ocaml
<danderson> and various crap like resetting core peripherals, copying data into ram off static storage...
<zmdkrbou> and you need to write a dummy libc to use ocaml without an OS
<danderson> you can probably get away with using uclibc
<danderson> except for one killer, memory management
<danderson> ocaml needs a working memory allocator, so you need a memory manager in C before you can boot ocaml code
<twobitsprite> or, at least a memory manager in machine code... shouldn't have to be in c
<danderson> and unless you're on an embedded system, that also implies virtual memory management, and support for swapping
<flux> do you need to implement free also?-)
<danderson> which requires a disk driver
<danderson> which requires a scheduler
<danderson> and at that point you have a basic OS in C, just to support ocaml :)
<flux> I don't think that _requires_ a scheduler
<bluestorm> hm
<flux> what about the os-written-in-ocam project..
<flux> +l
<bluestorm> projects
<danderson> flux: if you want fair performance, I think you do need to have a runnable task to handle i/o
<danderson> but strictly speaking, no, you don't need a scheduler for that
<danderson> you can do everything interrupt-driven style
<olegfink> flux: danderson: so what would be the best way? log, recursive divide or bitmask search?
<flux> here's one os in ocaml: http://dst.purevoid.org/
<flux> olegfink, I suppose it depends on what you want to optimize on. I guess log or bitmask search are the fastest contenders
<olegfink> or look at http://home.gna.org/funk
<flux> nbits 0;;
<xavierbot> - : int = 0
<flux> nbits 42;;
<xavierbot> - : int = 6
<flux> looks like that one works :)
<olegfink> okay, will go with it
<olegfink> it is my first ever binary-dealing program
<flux> I actually would trust more my version, as I don't know if it would be possible for the division to result in a number that would be rounded down too much..
<flux> (assuming it even works, heh)
pango has quit [Remote closed the connection]
<flux> but perhaps the division is guaranteed to never result in such a number.. I don't know the intricacies of floating point arithmetics, other than be very careful when wanting an exact result ;)
<danderson> the division is so that the expression is equivalent to the binary logarithm
<danderson> and the binary logarithm, informally, tells you how many bits you need to store the input number
<danderson> but it gives it to you in fractional bits, so you round it up to the nearest int
<danderson> I believe the ceil(binary_log(x)) thing is solid, and empirically this is true
<olegfink> yeah, that was my original thought
<danderson> but computing logs is unlikely to be the fastest thing in the world.
<olegfink> let rec count_bits n = if n > 0 then 1 + count_bits (n / 2) else 0;;
<xavierbot> val count_bits : int -> int = <fun>
<olegfink> count_bits 42;;
<xavierbot> - : int = 6
<olegfink> hm
<danderson> that definition is also sound
<danderson> integer division truncates, doesn't round, so it's always approximated in the right direction, no matter if the input is even or odd
<flux> it could be replaced with lsr 1 to better convey the meaning I suppose
<flux> count_bits (-42);;
<xavierbot> - : int = 0
<flux> nbits (-42);;
<xavierbot> - : int = 0
<danderson> heh
<danderson> bork bork
<flux> both fail with negative numbers ;)
<danderson> negative numbers is easy
<danderson> if n < 0 then sizeof(integer_on_your_platform)
<danderson> because of the sign bit
<danderson> well, unless you find an architecture that doesn't use two's complement for negative ints...
<olegfink> I will only need positive numbers fortunately
<danderson> add an assertion anyway
<danderson> if n < 0 then failwith "No negative integers!"
<flux> or simply assert (n >= 0)
* danderson takes note
<flux> it serves as documentation also :)
<olegfink> does this look sane: http://rafb.net/p/StGC2n73.html
pango has joined #ocaml
<olegfink> oops, it doesn't compile
<olegfink> okay, now: http://rafb.net/p/1sdTJc48.html
crabstick has joined #ocaml
seafoodX has quit []
aij has quit [Read error: 104 (Connection reset by peer)]
crabstick has left #ocaml []
aij has joined #ocaml
aij has quit [Read error: 104 (Connection reset by peer)]
aij has joined #ocaml
piggybox_ has joined #ocaml
Demitar has joined #ocaml
crabstick has joined #ocaml
<olegfink> well, int is usually 4 bytes
<olegfink> but I don't have any knowledge about the order of those 4 bytes
<olegfink> so how can I output a large number (>255) on a byte-by-byte basis?
piggybox has quit [Success]
<flux> pick the order you like? or use network byte order, that is, the most significant byte first
<flux> you shift it right the amount of bits you like and then land with 0xff
<olegfink> it loops and I can't get why
<olegfink> also and don't have any kind on 'flush' support
<olegfink> *of 'flush'
<bluestorm> why do you need such low-level things ?
<olegfink> well, I want to to pack binary tree leafs data as compact as I can
<bluestorm> hm
<bluestorm> not sure the "time spent" / "gain over output_value" will be very interesting but maybe that's important for you :p
<olegfink> it's not a real life thing
<olegfink> I need maximum compression, and I don't care about time/memory used :D
<bluestorm> hm
<bluestorm> it'll be funny to compare your code with a output_value + zip/gzip/bzip2 :p
<olegfink> hehe
<danderson> heh
<olegfink> actually it's LZW what I'm trying to implement
<danderson> an interesting investment, if you end up giving up and using zlib
<danderson> is to come up with your own zlib dictionary
<danderson> that is adapted to the data you're feeding it
<olegfink> nah
<olegfink> yet_to_write:=value lsl (8-width);
ednarofi has quit ["leaving"]
<danderson> whatever. I've seen what it can do :-)
<olegfink> this line looks completely wrong to me
<olegfink> after drinking a cup of tea
<olegfink> yet_to_write should never exceed one byte
<olegfink> how does 0xf look in an int field?
<olegfink> like 0x0000000f ?
<olegfink> well
<olegfink> I really can't understand where it loops when I call output_bits fd 0xf
<olegfink> it should simply assign 0xf to yet_to_write
buluca has quit [Read error: 113 (No route to host)]
<olegfink> it shouldn't write anything to the file, as it's not a complete byte (we can write 4 more bits to this byte)
ygrek has joined #ocaml
Smerdyakov has joined #ocaml
piggybox_ is now known as piggybox
piggybox_ has joined #ocaml
piggybox has quit [Success]
twobitsprite has quit ["Lost terminal"]
piggybox has joined #ocaml
piggybox_ has quit [Connection timed out]
<mbishop> When I saw olegfink I thought "the" oleg was here :P
crathman has joined #ocaml
<bluestorm> smimou: are you here ?
<bluestorm> a friend of mine is trying to use your irc library, and he has some problems
<smimou> bluestorm: pong
<bluestorm> :p
<bluestorm> that may be the solution to the problem as well
<smimou> pong was the solution ? ;)
<bluestorm> hm, probably a part of the solution
<bluestorm> he manage to connect to Freenode
<bluestorm> but his server (irc.epiknet.org) doesn't accept the bot
<smimou> what do you have in the logs ?
asmanur has joined #ocaml
<smimou> ah yes you have to answer to ping
<smimou> I think that the object version does that by default
<bluestorm> hm
<bluestorm> (first : the object version is not in your ocamldoc page)
<bluestorm> i had a look and i tought the module version answered to ping too
<bluestorm> do the object version handle the int parameter ?
<smimou> I think so
<bluestorm> ok, thanks
<mbishop> where is this irc library?
<smimou> btw if you want the latest version of the lib it's here: http://savonet.svn.sourceforge.net/viewvc/savonet/trunk/ocaml-irc/src/
<mbishop> nice
<bluestorm> heh, seems wiewvc in not very good at highlighting ocaml syntax :p
buluca has joined #ocaml
piggybox_ has joined #ocaml
tty56_ has quit [Read error: 104 (Connection reset by peer)]
tty56 has joined #ocaml
mwc has joined #ocaml
piggybox has quit [Connection timed out]
slipstream-- has quit [Read error: 104 (Connection reset by peer)]
slipstream has joined #ocaml
olegfink has quit [Read error: 113 (No route to host)]
olegfink has joined #ocaml
buluca has quit [Read error: 113 (No route to host)]
ygrek has quit [Remote closed the connection]
buluca has joined #ocaml
jlouis has quit [Read error: 110 (Connection timed out)]
mwc has quit ["Lost terminal"]
G_ has joined #ocaml
jlouis has joined #ocaml
piggybox_ is now known as piggybox
G has quit [Connection timed out]
jlouis has quit ["leaving"]
olegfink has quit [Read error: 101 (Network is unreachable)]
jlouis has joined #ocaml
piggybox_ has joined #ocaml
piggybox has quit [Nick collision from services.]
piggybox_ is now known as piggybox
|Jedai| is now known as jedai
piggybox_ has joined #ocaml
jonathanv has joined #ocaml
<jonathanv> cool
piggybox has quit [Read error: 110 (Connection timed out)]
<lde> smimou: You should also have generic channel/user modes, since some servers support additional ones.
<smimou> lde: patches are welcome ;)
<lde> e.g. freenode
<lde> it told me: CHANMODES=bdeIq,k,lfJD,cgijLmnPQrRstz
<lde> well, a freenode server told me, not freenode, to be exact :-)
asmanur has quit [Remote closed the connection]
<lde> Cool, anyway.
<smimou> thanks, I'll try to think of modes when I have some time
<lde> I was starting to write an irc library myself.
<jonathanv> so how awesome is ocaml
olegfink has joined #ocaml
rwmjones_ has joined #ocaml
<rwmjones_> xavierbot, hello
<rwmjones_> xavierbot, help
<xavierbot> hello rwmjones_, I am xavierbot 0.7, an OCaml toplevel
<xavierbot> expr ;; evaluate expr in toplevel and print result
<xavierbot> help help message
<xavierbot> restart restart the toplevel
<xavierbot> sleep go to sleep
<xavierbot> wake wake me up from sleep
<rwmjones_> let x1 = fun x -> (x,x) in
<rwmjones_> let x2 = fun y -> x1 ( x1 y ) in
<rwmjones_> let x3 = fun y -> x2 ( x2 y ) in
<rwmjones_> let x4 = fun y -> x3 ( x3 y ) in
<rwmjones_> let x5 = fun y -> x4 ( x4 y ) in
<rwmjones_> let x6 = fun y -> x5 ( x5 y ) in
<rwmjones_> let x7 = fun y -> x6 ( x6 y ) in
<rwmjones_> x7 ( fun z -> z ) ;;
<xavierbot> Characters 1-3:
<xavierbot> x7 ( fun z -> z ) ;;
<xavierbot> ^^
<xavierbot> Unbound value x7
<bluestorm> o_O
<pango> lines not terminated by ;; aren't interpreted by xavierbot...
<rwmjones_> let x1 = fun x -> (x,x) in let x2 = fun y -> x1 ( x1 y ) in let x3 = fun y -> x2 ( x2 y ) in let x4 = fun y -> x3 ( x3 y ) in let x5 = fun y -> x4 ( x4 y ) in let x6 = fun y -> x5 ( x5 y ) in let x7 = fun y -> x6 ( x6 y ) in x7 ( fun z -> z ) ;;
<xavierbot> Objective Caml version 3.10.0
<xavierbot> Camlp4 Parsing version 3.10.0
<rwmjones_> xavierbot can't really cope with multi-line input
<mbishop> xavierbot: shut the hell up
<xavierbot> xavierbot goes to sleep (do 'xavierbot wake' to wake)
<rwmjones_> hang on ...
<mbishop> I like that :P
<rwmjones_> xavierbot wake up (I'll put him back to sleep in a moment)
<xavierbot> xavierbot wakes up
<rwmjones_> let pair = fun x -> (fun y -> (fun z -> ((z x) y))) in let x1 = fun y -> (pair y) y in let x2 = fun y -> x1 (x1 y) in let x3 = fun y -> x2 (x2 y) in let x4 = fun y -> x3 (x3 y) in let x5 = fun y -> x4 (x4 y) in x5 (fun y -> y) ;;
<xavierbot> Fatal error: out of memory.
<xavierbot> Objective Caml version 3.10.0
<xavierbot> Camlp4 Parsing version 3.10.0
<rwmjones_> interesting
<Tetsuo> trying to stress the type inference ? ^^
<rwmjones_> yes, see caml-list recent postings
<rwmjones_> ok, back to serious stuff ... anyone using ocaml on solaris?
<rwmjones_> I'm wondering what you use to install ocaml (eg. blastwave.org, or something else)
schme`` is now known as schme
<jonathanv> sooooo
piggybox has joined #ocaml
mbishop has quit [Read error: 113 (No route to host)]
rwmjones has joined #ocaml
mwc has joined #ocaml
<mwc> Anybody have logs of this channel?
<mwc> Trying to solve something I figured out a few weeks ago
<mwc> and alas, I deleted that code
leo037 has joined #ocaml
crathman has quit [Read error: 110 (Connection timed out)]
piggybox__ has joined #ocaml
piggybox_ has quit [Success]
Tetsuo has quit ["Leaving"]
ita has joined #ocaml
<ita> awesome, virtual methods
piggybox_ has joined #ocaml
bluestorm has quit ["Konversation terminated!"]
piggybox has quit [Connection timed out]
mbishop has joined #ocaml
piggybox__ has quit [Connection timed out]
martin_ has joined #ocaml
martin_ is now known as mbishop_
rwmjones_ has quit ["Leaving"]
mbishop has quit [Nick collision from services.]
mbishop_ is now known as mbishop
zmdkrbou has quit [Read error: 110 (Connection timed out)]