gildor changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | OCaml 3.12.0 http://bit.ly/aNZBUp
<_habnabit> http://paste.pound-python.org/show/JQDHr1XBIxjXnufeVwft/ <- this is saying "tree must occur on both sides of this | pattern".
<_habnabit> But... it does.
lamawithonel has quit [Remote host closed the connection]
q[mrw] has joined #ocaml
philtor has quit [Ping timeout: 276 seconds]
lopex has quit []
grettke has joined #ocaml
grettke has quit []
fraggle_ has quit [Ping timeout: 240 seconds]
fraggle_ has joined #ocaml
jamii has joined #ocaml
oriba has left #ocaml []
<thelema> _habnabit: fun tree -> match tree with Leaf i | Node (i,_) -> i, tree
<_habnabit> thelema, yeah, that's what I did
<_habnabit> thelema, but this error doesn't make a whole lot of sense to me
<thelema> I'm surprised by it too.
<thelema> you could also decompose further - let get_i = function Leaf i | Node (i,_) -> i in (fun tree -> get_i tree, tree)
<thelema> # function (Leaf i as tree) | (Node (i,_) as tree) -> i, tree;;
<thelema> it seems to be a precedence issue
<_habnabit> Oh, that does a thing?
<tomprince> Would function (Leaf i | Node (i,_)) as tree -> ... work then?
<thelema> # function (Leaf i | Node (i,_)) as tree -> i, tree;;
<thelema> - : stree -> int * stree = <fun>
<thelema> tomprince: unexpectedly, yes
<_habnabit> Hah!
<_habnabit> That's neat.
ymasory has quit [Quit: Leaving]
ymasory has joined #ocaml
<tomprince> Well, if it is a precedence issue, then the it was parsing the original as ((Leaf i as tree) | Node (i,_)) as tree :)
<tomprince> Which clearly has unbalanced bindings of tree.
joewilliams is now known as joewilliams_away
smrz has joined #ocaml
__marius__ has joined #ocaml
jamii has quit [Ping timeout: 240 seconds]
smrz has quit [Quit: Computer has gone to sleep.]
q[mrw] has quit [Quit: Page closed]
jamii has joined #ocaml
vivanov has joined #ocaml
jamii has quit [Ping timeout: 240 seconds]
jamii has joined #ocaml
hto has quit [Ping timeout: 252 seconds]
ymasory has quit [Quit: Leaving]
dnolen has quit [Quit: dnolen]
ulfdoz has joined #ocaml
enthymeme has quit [Ping timeout: 248 seconds]
hto has joined #ocaml
jamii has quit [Ping timeout: 276 seconds]
jamii has joined #ocaml
eye-scuzzy has joined #ocaml
sun28 has joined #ocaml
eye-scuzzy has quit [Disconnected by services]
sun28 is now known as eye-scuzzy
eye-scuzzy has quit [Quit: leaving]
eye-scuzzy has joined #ocaml
ygrek has joined #ocaml
ikaros has joined #ocaml
ikaros has quit [Client Quit]
ikaros has joined #ocaml
philtor has joined #ocaml
jderque has joined #ocaml
mcclurmc_ has joined #ocaml
ulfdoz has quit [Ping timeout: 240 seconds]
seafood_ has joined #ocaml
seafood_ has quit [Ping timeout: 240 seconds]
avsm2 has quit [Read error: Operation timed out]
avsm2 has joined #ocaml
Cyanure has joined #ocaml
Associat0r has joined #ocaml
__marius__ has quit [Ping timeout: 260 seconds]
philtor has quit [Read error: Operation timed out]
larhat has joined #ocaml
Cyanure has quit [Remote host closed the connection]
edwin has joined #ocaml
seafood_ has joined #ocaml
seafood_ has quit [Client Quit]
ftrvxmtrx has joined #ocaml
hto has quit [Ping timeout: 260 seconds]
Cyanure has joined #ocaml
Associat0r has quit [Quit: Associat0r]
vivanov has quit [Quit: Lost terminal]
eikke has joined #ocaml
seafood_ has joined #ocaml
seafood_ is now known as seafood
vivanov has joined #ocaml
seafood has quit [Quit: seafood]
PiepScuim has joined #ocaml
mcclurmc has joined #ocaml
mnabil has joined #ocaml
avsm has joined #ocaml
munga has joined #ocaml
jderque has quit [Quit: leaving]
avsm has quit [Quit: Leaving.]
avsm has joined #ocaml
jamii has quit [Ping timeout: 248 seconds]
zorun has quit [Ping timeout: 240 seconds]
jderque has joined #ocaml
Rolands has joined #ocaml
lopex has joined #ocaml
vivanov has quit [Ping timeout: 248 seconds]
munga has quit [Read error: Operation timed out]
andre_ has joined #ocaml
fraggle_ has quit [Remote host closed the connection]
_andre has quit [Disconnected by services]
pdhborges has joined #ocaml
andre_ has quit [Remote host closed the connection]
_andre has joined #ocaml
fraggle_ has joined #ocaml
vivanov has joined #ocaml
vivanov has quit [Client Quit]
dnolen has joined #ocaml
temoto has joined #ocaml
<temoto> How to call some function N times (for side-effects)?
ygrek has quit [Ping timeout: 246 seconds]
<flux> if that is the only requirement, I'd just use a for loop
<flux> if you want to do it in some tricky fashion, you could use Array.make and Array.iter
<flux> or, there is some mechanism for that in batteries as well, something akin to Enum.iter (fun _ -> f ()) (1 -- 42)
<temoto> Do they use _ in Ocaml to denote that variable is not used as in for _ = 1 to N do ...
<temoto> ?
<flux> they do, in pattern matching situation. apparently that is not one, though.
<flux> also similarly you can prefix your names with _ to indicate that the compiler should not warn if they are not used
vivanov has joined #ocaml
<temoto> Thanks.
ygrek has joined #ocaml
<temoto> How to read a pair of integers from stdin, separated by a single space char?
<pdhborges> Scanf.scanf "%d%d" (fun a b -> a, b)
<temoto> i'm thinking somewhere about read_line $ split $ map string_to_int
<temoto> Oh thanks.
<pdhborges> that returns a tuple
<flux> you need a space between %d's
<pdhborges> with both numbers
<flux> but that's nice, I wouldn't have remembered to suggest that
<pdhborges> flux no
<flux> pdhborges, well, I just tried it..
<pdhborges> impossible
<pdhborges> O.o
<pdhborges> sec
_andre has quit [Quit: leaving]
<pdhborges> flux you are right
<pdhborges> this doens't match C's scanf
<kaustuv> scanf and printf are exactly dual in OCaml
munga has joined #ocaml
<pdhborges> kaustuv: dual? A scanf with blank characters ignores every blank just like C
jderque has quit [Quit: leaving]
boscop has joined #ocaml
<temoto> Is there a simple way to heal ocaml interactive interpreter to provide history and completion?
<pdhborges> rlwrap
<temoto> Thanks.
<pdhborges> it also supports completions but you will have to create a file with every completion you want
<kaustuv> pdhborges: I meant that (sprintf fmt) o (sscanf fmt) (where o is function composition composition) is the identity
<kaustuv> but I see that that doesn't actually hold, so never mind
Associat0r has joined #ocaml
pdhborges has quit [Quit: Leaving.]
oriba has joined #ocaml
<temoto> How to printf array of integers?
ecc has quit [Quit: Client exiting]
pdhborges has joined #ocaml
dnolen has quit [Read error: Connection reset by peer]
pdhborges has quit [Quit: Leaving.]
pdhborges has joined #ocaml
<orbitz> temoto: loop over it and printf
<orbitz> temoto: List.iter (Printf.printf "%d ") my_list
<flux> I usually map them into strings and concatenate with String.concat
<flux> doesn't work that easily with arrays, though
<flux> needs a conversion to list in some phase
<orbitz> oh durh an array
<orbitz> temoto: List.iter (Printf.printf "%d ") (Array.to_list my_list)
<temoto> String.concat ", " (Array.to_list (Array.map string_of_int xs))
<orbitz> err that is an array.iter right?
<temoto> works for me, but somethink like that must be builtin
<orbitz> Array.iter (Printf.printf "%d ") my_array
<pdhborges> Does anyone have an example with batteries?
<orbitz> temoto: Ocaml's stdlib is fairly aenmic, you should probably choose Core or Battery's fairly early
bzzbzz has joined #ocaml
<flux> something like this can be helpful (untested): let array f chan xs = ignore (Array.fold_left (fun sep x -> Printf.fprintf chan "%s%s" sep (f x); " ") "" xs)
<orbitz> I don't think Core has anythign in partifular for this
<flux> then this might work: Printf.printf "array of integers: %a" (array string_of_int) [|1; 2|]
<temoto> What's ignore?
<orbitz> 'a -> unit
<flux> it ignores the return value, making the function return unit instead of a string
<thelema> pdhborges: you want an example of printing an int array using batteries?
<flux> (similar could be achieved with %t as well, I often go with that, or just converting into a string)
<thelema> pdhborges: Array.print Int.print stdout [0;2;4;8]
<flux> bzzt, not an array :)
<temoto> flux, array string_of_int says array is not bound
<flux> temoto, um, the let array .. defines array, it should be bound
<thelema> pdhborges: Array.print Int.print stdout [|0;2;4;8|]
<flux> whaddayouknow, it works, the first time I pasted into ocaml toplevel :-o
<temoto> flux, let array = what?
<flux> temoto, the line that starts like: "something like this can be.."
<temoto> ahh
<pdhborges> thelema: thanks. I finnaly understood the printf fnction signaure
<pdhborges> s/printf/print
<thelema> pdhborges: it's not obvious at first, but it turns out to be exactly what's needed
<flux> what is its signature, btw?
<pdhborges> ?first:string -> ?last:string -> ?sep:string -> ('a BatIO.output -> 'b -> unit) -> 'a BatIO.output -> 'b t -> unit
<temoto> I need binary search over sorted array.
<pdhborges> the separators
<pdhborges> the function to print eah element
<pdhborges> followed by the stream and the array
<flux> temoto, I guess you need to implement that yourself
<temoto> Now that's unexpected. :)
<thelema> pdhborges: btw, I do things like: printf "Array: %a\n" (Array.ptint Int.print) [|2;7|]
<flux> I think the only language with binary search on custom sequences in its standard library is c++ :)
<flux> thelema, hey, that seems familiar :)
<temoto> Python, bisect module in stdlib.
<temoto> Also, i'd be happy with 3rd party module as well.
<flux> thanks, I learned something new :)
<flux> it should not be a long algorithm to implement. you know, these are called _programming_ languages ;)
<temoto> Sure.
<thelema> temoto: convert the array to a set, and 'find' automatically does a binary search. :)
<flux> although, binary search is easy to get wrong as well
<temoto> thelema, unfortunately, i need binary search on custom condition, not equality to x.
<temoto> i need >= x
<pdhborges> temoto: that is the lower_bound function on C++
<flux> well, set gives that as well
<thelema> if your array is sorted, just test the last element... oh, you want the first element that's >= x
<flux> of course, the creation of the set takes some time
<flux> standard version of binary search wouldn't find that element anyway
<flux> (does python bisect?)
barismetin has joined #ocaml
<thelema> temoto: tweak this for your purposes
<temoto> flux, yes, it finds an insertion point to maintain order
<pdhborges> watch out that is the overflowing mid version!
<temoto> 'overflowing mid' ?
<pdhborges> mid = (low + high) / 2
<pdhborges> :(
<temoto> should be (low/2) + (high/2) ?
<flux> pdhborges, not really an issue in ocaml..
<thelema> temoto: see "extra credit" at the end of the intro on that page.
<flux> I guess it gets more complicated
<thelema> flux: overflow is an issue for ocaml still.
<flux> you need to handle the last bit separately at least
<pdhborges> low + ((high - low) / 2 temoto
<flux> thelema, but you can only have 16M elements on 32-bit platforms, and on 64 bit platforms it is extremely likely you are able to find hardware to overflow it with
<flux> UNlikely
<thelema> or on most platforms: (low + high) lsr 1
<temoto> :)
<thelema> flux: true.
<flux> heh, my version didn't work I guess, or atleast it just raised Not_found if low = high
<pdhborges> looks like it is also true on 64bits
<pdhborges> max_int is 4611686018427387903
<pdhborges> maxarrlen is 18014398509481983
<flux> actualyl maybe not
<flux> that version uses a version where high indicates the last position, while mine indicates the last+1
<pdhborges> I must be doing something wrong
<pdhborges> I installed batteries 1.3
<pdhborges> then require it on the top level
<pdhborges> opened Batteries but then I can't open, for example Array
<temoto> flux, when you said that set gives that as well, did you mean Set.split?
<flux> temoto, yes
<pdhborges> actually I can open Array
<pdhborges> but when I try to use a function from array it spits Reference to undefined global `Batteries'
<flux> temoto, well, actually, a set only has one of each equal value
<flux> temoto, so if you have multiple equal values in the original set, you are in trouble
<temoto> Yeah, that's fine for me.
<flux> oh, ok
<temoto> How to load my module into interpreter and play with function i've defined via 'let'?
<flux> there are two ways
<flux> either, you can do exactly what you wanted, with #load "foo.cmo";;
<flux> or, you can include the source code with "#use "foo.ml";;
<flux> in the former situation, your module is called Foo
<flux> temoto, btw, you don't happen to use emacs perchance?
<temoto> flux, nah, i use gvim.
<thelema> pdhborges: try opening Batteries_uni instead
<flux> there is some vim support as well, but I don't know if they have "run toplevel, copy-paste current function into toplevel"-kind of functionality
<flux> temoto, in any case, it is a good idea to look into vim support. at least it has the type throwback-feature, ie. if you've compiled the source code with -dtypes, you can go over any expression and retrieve its type.
<flux> it'll be useful at times.
<thelema> pdhborges: the right way to use batteries in the toplevel is to put the code in batteries' ocamlinit in your own ~/.ocamlinit, and batteries will autoload
<pdhborges> thelema: it worked
<pdhborges> thanks
lopex has quit []
larhat has quit [Quit: Leaving.]
trch has joined #ocaml
trch has left #ocaml []
ChristopheT has joined #ocaml
Cyanure has quit [Remote host closed the connection]
hnrgrgr has quit [Remote host closed the connection]
Rolands has quit [Read error: Operation timed out]
pdhborges has left #ocaml []
hnrgrgr has joined #ocaml
jderque has joined #ocaml
__marius__ has joined #ocaml
<temoto> How to use Map module?
<temoto> Map.Make Int gives error
<temoto> unbound constructor
<rixed> Int is not a module from stdlib, is it?
ChristopheT has quit [Ping timeout: 260 seconds]
<rixed> Why not "Map.Make(struct type t=int let compare=compare end)
<temoto> cheesus
<temoto> module IntMap = Map.Make (int);; syntax error
<rixed> module IntMap = Map.Make(struct type t=int let compare=compare end);; -> works allright
<temoto> Thank you.
<temoto> Amazing how much boilerplate is required for a simple dictionary.
<rixed> temoto: yes. Would be simpler if there were actualy an Int module. Maybe in batteries?
<temoto> Batteries claim to have Map.IntMap already defined.
<temoto> There should be some way to write something to ~/.ocamlsomething to autoload batteries, right?
joewilliams_away is now known as joewilliams
<temoto> okay i found it
<temoto> Is there something like import Map.IntMap as IntMap ?
<temoto> Map.IntMap.add x y m does not seem nice
<rossberg> structure IntMap = Map.IntMap
ulfdoz has joined #ocaml
<temoto> unbound value structure
<rossberg> sorry, "module" instead of "structure" 8-}
<temoto> Thanks.
jderque has quit [Ping timeout: 248 seconds]
yezariaely has joined #ocaml
<temoto> I need to fill Map inside a side-effect for-loop. Do i need to use 'ref' or something? Can't find an example.
yezariaely has quit [Client Quit]
<temoto> okay, wires <- IntMap.add x y !wires seems to work
jderque has joined #ocaml
munga has quit [Quit: Ex-Chat]
<f[x]> thelema, I guess it was a temporary problem and I blame java :)
<f[x]> now it fails some unit test
eikke has quit [Ping timeout: 246 seconds]
<temoto> Is there a shortcut for result <- result + ... ?
<temoto> result <- !result + ...
<f[x]> let (+=) x y = x := !x + y
<temoto> How := is different from <- ?
<f[x]> # (:=);;
<f[x]> - : 'a ref -> 'a -> unit = <fun>
<f[x]> <- is syntax to specify modification of mutable record fields
<f[x]> := is a function over one specific record type - 'a ref
<flux> and ref is type 'a ref = { mutable contents : 'a }
<f[x]> let (:=) x y = x.contents <- y;;
<temoto> So where should i use each of them?
<flux> when you have your own records that have mutable fields (rare)
<flux> then you use <-
<flux> if you use the ref-type, you use :=
<temoto> Thanks.
<flux> (or, when you have objects with mutable fields, those use <- as well)
<temoto> Is there a syntax for partial application of operators?
PiepScuim has quit [Quit: Ex-Chat]
bzzbzz has quit [Quit: leaving]
zorun_ has joined #ocaml
ftrvxmtrx has quit [Quit: Leaving]
bzzbzz has joined #ocaml
<thelema> temoto: (+) 3
pdhborges has joined #ocaml
mnabil has quit [Remote host closed the connection]
<temoto> thelema, thanks.
<thelema> be aware that [(-) 4] is (fun x -> 4 - x)
Cyanure has joined #ocaml
jderque has quit [Quit: Leaving.]
<temoto> of course
<temoto> Haskell has neat syntax for specifying operands at particular side of infix operators.
<temoto> afair
<bitbckt> Haskell allows `` around any prefix fn to allow use as an infix operator.
<bitbckt> and () around infix operators to convert to prefix operators.
<temoto> And what is said as a third option.
<temoto> s/is/i/
* bitbckt nods
<temoto> Okay, i actually need it to be second operand. Is there builtin flip?
<temoto> flip (f a b) -> f b a
jderque has joined #ocaml
<pdhborges> temoto: what are you doing?
<temoto> pdhborges, counting elements <= x in array.
<temoto> Hey, i can use (>=)x
Modius has joined #ocaml
avsm2 has quit [Quit: avsm2]
zorun_ is now known as zorun
<thelema> temoto: you mean (>) x
<temoto> yeah
<thelema> there's only flip in batteries, not in the stdlib
lopex has joined #ocaml
emmanuelux has joined #ocaml
Cyanure has quit [Ping timeout: 248 seconds]
eikke has joined #ocaml
<_habnabit> When I get an error like "this expression has type X but an expression was expected of type Y", how can I tell /why/ it's supposed to be type Y?
<flux> _habnabit, no, but that would be great. infact there is research on the area.
<_habnabit> Dang. :(
<flux> _habnabit, the basic strategy for debugging such issues is as follows:
<flux> 1) go through the source and use emacs (or vim) type throwback
<flux> 2) when you find a type that isn't what you think it should be, annotate the value
<flux> 3) compile
<flux> 4) 1()
<temoto> How to unpack value from constructor?
<flux> temoto, in a generic way: match Foo 42 with Foo a -> a | Bar b -> b
<temoto> let Just x in some := x is syntax error
<temoto> ah match, thanks.
<flux> if there is only one constructor (rare), you can use: let Foo x = Foo 42
<flux> it works with multiple constructors as well, but you get a warning about non-exhaustiveness
<temoto> Yeah, exactly what i need.
<temoto> except it is still a syntax error
<temoto> let Just idx = Just (array_find pair bx) in idx_b := idx
<flux> hmm
<flux> if Just your own type?
<flux> (constructor)
<flux> and just not something you've mixed up with Haskell..
<flux> because in O'Caml land it's called Some
<temoto> type maybe_int = None | Just of int;;
<flux> oh, ok
<temoto> But yeah, i should do as romans.
<flux> it is not a syntax error in my toplevel
<flux> it fails in "array_find" with me (not a syntax error)
<temoto> Yeah i skipped ; in previous line.
<_habnabit> flux, do you personally use emacs?
<temoto> Compile-time printf is very nice.
avsm has quit [Quit: Leaving.]
<temoto> i mean % args checking
<pdhborges> also a bit compiler hack
<pdhborges> :X
pdhborges has left #ocaml []
<flux> _habnabit, yes
<_habnabit> flux, with tuareg-mode ? How are you seeing the type of an expression?
<thelema> _habnabit: compile with -annot anc then do C-c C-t
<thelema> s/anc/and/
vivanov has quit [Ping timeout: 240 seconds]
<_habnabit> thelema, hm, but will it still -annot if the types are disagreeing?
<flux> _habnabit, yes. 1) compile with -dtypes 2) have ocaml-mode around as well (its caml-types.el is used) 3) go over an expression, press C-c C-t
<thelema> yes, up to the point that types agree
<thelema> flux: -dtypes is the old way
<flux> hmph
<flux> what is the new way? I haven't manually written that for a while..
<flux> -annot?
<thelema> yes
pdhborges has joined #ocaml
eikke has quit [Ping timeout: 258 seconds]
impy has quit [Read error: No route to host]
philtor has joined #ocaml
<temoto> How to use String.concat with BatEnum?
<pdhborges> temoto: I guess you could use List.of_enum
<temoto> pdhborges, works, thanks.
pdhborges has quit [Quit: Leaving.]
ankit9 has quit [Read error: Connection reset by peer]
ygrek has quit [Ping timeout: 246 seconds]
<temoto> ocamlfind ocamlc -package batteries main.ml gives Reference to undefined global `Batteries` ( i have open Batteries line )
<adrien> missing -linkpkg ?
<temoto> ocamlfind ocamlc -package batteries -linkpkg main.ml gives same error
<temoto> (That's Ubuntu 10.10 with batteries from apt)
ankit9 has joined #ocaml
<temoto> Also, i'd like to just run the file, without explicit compilation.
<temoto> Is it possible with batteries?
ecc has joined #ocaml
pdhborges has joined #ocaml
ymasory has joined #ocaml
hto has joined #ocaml
oriba_ has joined #ocaml
<_habnabit> Hm, neither tuareg-mode nor caml-mode has a C-c C-t.
oriba has quit [Ping timeout: 258 seconds]
oriba_ is now known as oriba
sku has joined #ocaml
ulfdoz has quit [Ping timeout: 260 seconds]
nantralien has joined #ocaml
<nantralien> adrien i could'nt parametrize my parser with a module
<nantralien> so i had to throw away my functors to go with plain modules
<thelema> temoto: 'ocamlfind ocaml -package batteries foo.ml'?
<temoto> thelema, my ocamlfind doesn't recognize 'ocaml' as valid command.
<pdhborges> temoto:
<pdhborges> type ocaml
<_habnabit> thelema, are you sure that it's C-c C-t in caml-mode/?
<pdhborges> then #use "topfind"
<pdhborges> then #require "batteries"
<temoto> uhm, that succeeds silently
<pdhborges> what happens when you use #list;;
<temoto> It prints a lot of packages. Batteries amongst.
jderque has quit [Quit: leaving]
pdhborges has left #ocaml []
boscop_ has joined #ocaml
boscop has quit [Ping timeout: 240 seconds]
sku has quit [Quit: Leaving]
boscop_ is now known as boscop
sgnb has quit [Read error: Operation timed out]
<thelema> temoto: hmm...
<_habnabit> thelema, seriously, though, what major mode are you using that has C-c C-t? I've just tried tuareg-mode, caml-mode, and ocaml-mode
<thelema> _habnabit: yes, sure. do you have a foo.annot file?
stephanewustner_ has quit [Ping timeout: 248 seconds]
<thelema> there's a separate file for it, iirc, but it's installed by default
<_habnabit> thelema, I don't have any keybindings for C-c C-t
<thelema> do you have a caml-types.el file anywhere?
<_habnabit> I did at one point. Do I need to require 'caml-types ?
stephanewustner has joined #ocaml
<thelema> it should be loaded automatically, I think
<thelema> or not... my emacs has it required...
<thelema> (require 'caml-types)
<thelema> (add-to-list 'auto-mode-alist '("\\.ml\\w?" . tuareg-mode))
<_habnabit> aha
oriba has left #ocaml []
<_habnabit> There. I got caml-mode to have a C-c C-t binding, but now it doesn't have font-lock.
<_habnabit> woooo, annotations
Associat0r has quit [Quit: Associat0r]
emmanuelux has quit [Quit: =>[]]
temoto has left #ocaml []
emmanuelux has joined #ocaml
impy has joined #ocaml
nantralien has quit [Quit: Vision[0.9.7-H-090423]: i've been blurred!]
emmanuelux has quit [Remote host closed the connection]
emmanuelux has joined #ocaml
ftrvxmtrx has joined #ocaml
bzzbzz_ has joined #ocaml
bzzbzz has quit [Ping timeout: 276 seconds]
edwin has quit [Remote host closed the connection]
barismetin has quit [Remote host closed the connection]
ikaros has quit [Quit: Leave the magic to Houdini]
Tianon has quit [Read error: Operation timed out]
jld has quit [Ping timeout: 260 seconds]
Tianon has joined #ocaml
Tianon has quit [Changing host]
Tianon has joined #ocaml
jld has joined #ocaml
pdhborges has joined #ocaml
pdhborges has quit [Quit: Leaving.]
dnolen has joined #ocaml
Amorphous has quit [Ping timeout: 276 seconds]
eikke has joined #ocaml
bzzbzz_ has quit [Quit: leaving]
Amorphous has joined #ocaml
bzzbzz has joined #ocaml