flux changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | 3.11.0 out now! Get yours from http://caml.inria.fr/ocaml/release.html
mihamina1 has quit [Read error: 104 (Connection reset by peer)]
seafood has joined #ocaml
Amorphous has quit [Read error: 104 (Connection reset by peer)]
Amorphous has joined #ocaml
Ched has quit [Read error: 60 (Operation timed out)]
Ched has joined #ocaml
Yoric[DT] has quit [Remote closed the connection]
m3ga has joined #ocaml
zstars has quit [Client Quit]
seafood has quit []
jeddhaberstro has quit []
Associat0r has quit []
<thelema> http://scienceblogs.com/goodmath/2006/11/the_c_is_efficient_language_fa.php -> "Caml code did some really clever stuff - it basically did something like local constant propagation that were based on
<thelema> be able to identify relations between subscripts used to access different arrays, and having done that, it could do some dramatic code rewriting that made it possible to merge loops, and hoist some local constants out of the restructured merged loop." ??
<thelema> this is odd - I thought the ocaml compiler didn't do this crazy of rewriting...
<m3ga> thelema: i was a little surprised by that too
olegfink has quit ["WeeChat 0.2.6.2"]
Yoric[DT] has joined #ocaml
Yoric[DT] has quit [Remote closed the connection]
sporkmonger has quit []
kaustuv has joined #ocaml
willb has quit [Read error: 110 (Connection timed out)]
seafood has joined #ocaml
mihamina has joined #ocaml
lutter has quit ["Leaving."]
<mihamina> hi all
<m3ga> err, hi
Camarade_Tux has joined #ocaml
Hadaka has quit [Read error: 60 (Operation timed out)]
<mihamina> with just the Ocaml release, is there a module to find (no fixed depth) files from a directory?
<mihamina> I'm running 3.10
<flux> mihamina, not anything that would come with ocaml
<mihamina> no batteries (not yet officially packaged
<mihamina> )
<flux> mihamina, there might be other libraries with your distribution, perhaps they have one
<flux> writing one isn't too difficult, as long as you take care of not following symbolic links, or have other means of detecting loops
Naked has joined #ocaml
Naked is now known as Hadaka
<mihamina> flux: Writing one wrapping the "find" on the system?
<mihamina> yes it's easy
<mihamina> is it a clean way to do it?
<mihamina> or should I use a lower level tool?
<flux> oh, I didn't remember that
<flux> well, to avoid symbolic links you may need to use the Unix module
<flux> something that doesn't think of those: type directory_entry = File | Dir of directory and directory = string * directory_entry let rec find dir = let dirs, files = List.partition Sys.is_directory (Array.to_list (Sys.readdir dir)) in List.map (fun d -> d, Dir (find dir ^ "/" ^ d)) dirs @ List.map (fun f -> f, File)
<flux> also it's not best of the world due to other reasons (lots of concatenations for one), but perhaps it'll help :). (it might also not compile, I didn't try)
<flux> hm, directory should be instead (string * directory_entry) list
<flux> I guess it could be much straight-forwarder without that partitioning step
<flux> with a simple map that maps entries either to directories or files
<flux> in any case, it would need to use Unix.stat instead of Sys.is_directory to skim out symlinks. or if you don't skip symlinks, it would need to have an additional argument that knew the visited directories by their device and inode (from Unix.stat)
Camarade_Tux has quit ["Leaving"]
komar_ has joined #ocaml
<mihamina> ok
<mrvn> I would also have a more fold_left like interface. Call a callback with an accumulator and the path to the next dir/file for each entry.
<mrvn> With that one can build a list or a tree or just iterate over the entries.
komar_ has quit [Read error: 60 (Operation timed out)]
komar_ has joined #ocaml
m3ga has quit ["disappearing into the sunset"]
Yoric[DT] has joined #ocaml
rumbleca_ has quit [Read error: 110 (Connection timed out)]
rjack has joined #ocaml
s4tan has joined #ocaml
<gildor> mihamina: there is ocaml-fileutils
<gildor> mihamina: note that I am working on a new version with more simple interface
<gildor> mihamina: in your case "find" is what you are looking for
<mihamina> gildor: "find", the one on the system?
komar_ has quit [Read error: 60 (Operation timed out)]
sOpen has quit [Read error: 110 (Connection timed out)]
<gildor> mihamina: no FileUtil.StrUtil.find
<gildor> the one from the OCaml library fileutils
komar_ has joined #ocaml
_zack has joined #ocaml
rumbleca has joined #ocaml
<mihamina> on ubuntu, the package is libfileutils-ocaml-dev ... would you know why it's -dev appended?
<gildor> because it is only for developper
<gildor> mihamina: you don't need to ship it with your final exec
<mihamina> aaaaaah. ok
heltav has joined #ocaml
<heltav> is caml not used anymore?
<mihamina> AFAIK, you may use caml in ocaml, but I might be wrong
<heltav> what is the difference between caml and ocaml?
<gildor> 1-letter
Alpounet has joined #ocaml
<mihamina> it's more than that when strings are expanded
<mihamina> :-P
jamii has quit [Remote closed the connection]
heltav has left #ocaml []
jamii has joined #ocaml
jamii has quit [Remote closed the connection]
jamii has joined #ocaml
Yoric[DT] has quit [Read error: 113 (No route to host)]
Yoric[DT] has joined #ocaml
hkBst has joined #ocaml
naufraghi has joined #ocaml
naufraghi has left #ocaml []
naufraghi has joined #ocaml
jeanbon has joined #ocaml
mihamina has quit [Read error: 110 (Connection timed out)]
ulfdoz has joined #ocaml
robocop has joined #ocaml
<robocop> hello
<robocop> do you know how I can improve this function ?
<robocop> Because i find it not very cute :o
<robocop> Is there a better syntax ?
biv_ has joined #ocaml
<flux> .. | { ename = (FTYPE ftype) as ename }::_ when ename = s -> ftype | _::xs -> find_f s xs
<robocop> okey thanks.
<robocop> hum
<robocop> I've got this error : The constructor FTYPE expects 2 argument(s),
<robocop> but is here applied to 1 argument(s)
<flux> source?
<robocop> yes
<robocop> on line 36.
komar_ has quit [Read error: 54 (Connection reset by peer)]
komar_ has joined #ocaml
<flux> because of how FTYPE is defined, there's no quite as elegant syntax.. it's the difference between type t = Foo of int * int and type t = Foo of (int * int) - I always to the latter myself
jeanbon has quit [Read error: 113 (No route to host)]
<flux> so you need to something like .. ( ename = (FTYPE (ftype'a, ftype'bb)) as ename } .. -> (ftype'a, ftype'b)
Guest74466 is now known as fremo
<robocop> hum, okey flux, you right
<robocop> do you think the better is that I separate variable and function in 2 array, or I do as now, with this type ?
<mrvn> flux: In both cases would you write Foo(1,2)?
<mrvn> The Foo of (int * int) should be slower and use more memory.
<Alpounet> It is indeed better to define Foo of int * int
<Alpounet> it's explained on some deep and lost pages of the Caml manual
komar_ has quit [Read error: 54 (Connection reset by peer)]
<mrvn> I would prefer (Foo 1 2) though. And Foo : int -> int -> t
komar_ has joined #ocaml
<mrvn> Alpounet: The interfacing with C part describes the memory layout. Foo of int * int is a single block with tag Foo and 2 ints. Foo of (int * int) is a block with tag Foo and a pointer to a block of size 2 containing 2 ints.
<Alpounet> okay, sounds logical.
Jedai has joined #ocaml
biv_ has quit ["Ухожу я от вас (xchat 2.4.5 или старше)"]
<flux> better and better: if your goal is top performance, then yes :)
<Alpounet> otherwise ? :p
<flux> if your goal is to make matching on (FTYPE a) work, then it's not better..
mihamina has joined #ocaml
komar_ is now known as nekomar
sporkmonger has joined #ocaml
sporkmonger_ has joined #ocaml
rjack has quit ["leaving"]
sporkmonger has quit [Connection timed out]
mishok13 has quit ["Stopping IRC chat... [OK]"]
nekomar is now known as komar_
th5 has joined #ocaml
ulfdoz has quit [Read error: 60 (Operation timed out)]
ulfdoz has joined #ocaml
<th5> Is anyone aware of an environment for OCaml (or other languages) that works like CTCoq/Proof General/CoqIDE? I'd really like to have the "up/down arrows". Something in between a toplevel and just compiling source files. Basically interactive sources...
mishok13 has joined #ocaml
<Alpounet> th5, $ ledit ocaml
<Alpounet> ?
<Alpounet> (under Unix)
<th5> i use ledit / rlwrap a lot
<th5> but with proof general you see the source of your program/script and you can run each statement one at a time (and go backwards)
<Yoric[DT]> I don't know of any such environment.
<Yoric[DT]> But it would be nice.
<Alpounet> If there was such an environment for OCaml, we may know about it...
<Alpounet> would know*
<th5> i find myself having emacs open with my sources and also having a toplevel open to interact
<thelema> th5: I think emacs will push an expression from your source file into an embedded toplevel
<th5> thanks anyway - i didn't think anything like that existed - i'd never heard this kind of thing until Coq
<Alpounet> but emacs can execute portions of code
<Alpounet> not sure, though
<flux> it can indeed
<flux> you can have the toplevel open in a buffer, and C-c C-r stuff from a region into it
<flux> or the current expression etc
<flux> it's been very useful for me
itewsh has joined #ocaml
<th5> thanks - thats very helpful actually - i mostly just use C-c C-t and the insanely helpful C-c C-; (ocaml spotter)
<flux> man, I really need to build ocaml spotter too :)
<th5> you have to try it - its a must for poking around a big project
<flux> I suppose 30k is big enough for the benefits
<th5> ha
dejj has joined #ocaml
<det-> rlwrap is better than ledit in my experience
<th5> for me they are about the same - i like how rlwrap saves your history though
<kaustuv> M-x tuareg-run-caml
<det-> Yeah, history is why I prefer it.
<det-> ledit requires extra parameters to save history
<th5> by the way, what mode does everyone use? is tuareg-mode very different from caml-mode ?
<flux> tuareg for me.
<Alpounet> tuareg for me, too.
<th5> oh ok - if i remember right i'm using tuareg but with a couple files form the other mode (i think to support C-c C-t) - i'll definitely check out the other parts of tuareg though (right now i just use it for syntax highlighting, etc
<kaustuv> tuareg uses caml-mode's C-c C-t by default
<th5> hmm - maybe i'm mixed up then
<flux> I don't anymore remember the differences, but iirc :) I prefer tuareg's indentation
Jedai has quit ["KVIrc Insomnia 4.0.0, revision: , sources date: 20090115, built on: 2009/03/07 00:45:02 UTC http://www.kvirc.net/"]
deadc0de has joined #ocaml
rjack has joined #ocaml
itewsh has quit [Read error: 110 (Connection timed out)]
Ariens_Hyperion has joined #ocaml
<mihamina> tuareg for me too
itewsh has joined #ocaml
<mihamina> but I just use 1 feature over the n of it...: syntax color
<mihamina> :-P
bombshelter13_ has joined #ocaml
s4tan has quit [Connection timed out]
deadc0de has left #ocaml []
robocop has quit [Remote closed the connection]
robocop has joined #ocaml
seafood has quit []
palomer has joined #ocaml
<palomer> hrmph, tuareg-mode no longer highlights my code
_andre has joined #ocaml
<palomer> Alpounet, you here?
willb has joined #ocaml
palomer has quit [Read error: 104 (Connection reset by peer)]
Alpounet has quit [Remote closed the connection]
sporkmonger has joined #ocaml
ulfdoz has quit [Read error: 110 (Connection timed out)]
palomer has joined #ocaml
<palomer> hrmph
willb1 has joined #ocaml
Alpounet has joined #ocaml
willb2 has joined #ocaml
peddie has joined #ocaml
willb has quit [Read error: 113 (No route to host)]
willb2 is now known as willb
sporkmonger_ has quit [Read error: 110 (Connection timed out)]
jamii has quit [Remote closed the connection]
willb1 has quit [Read error: 113 (No route to host)]
_zack has quit ["Leaving."]
lutter has joined #ocaml
Ariens_Hyperion has quit []
hto has quit ["Lost terminal"]
_zack has joined #ocaml
Ariens_Hyperion has joined #ocaml
komar_ has quit [Read error: 54 (Connection reset by peer)]
nimred has quit ["leaving"]
AlpMestan_ has joined #ocaml
Alpounet has quit [Read error: 110 (Connection timed out)]
<robocop> I've you got an exemple of Hashtbl ?
itewsh has quit [Connection timed out]
<robocop> let a = Hashtbl.create 122;;
<robocop> Hashtbl.add a 6 5;;
<robocop> but, what's the utilitie of this module ?
itewsh has joined #ocaml
<robocop> Ha, I think I have understand :o
<palomer> hashtbl is great
<kaustuv> palomer: be careful when you say that or some Haskellers might think you're a troll.
<palomer> functional fundamentalists
<palomer> I've resisted hashtbl for far too long
Camarade_Tux has joined #ocaml
* palomer is still resisting obj.magic though
<palomer> ill give in one of these days
th5 has quit []
<robocop> haha Hashtbl bug ><
<robocop> He says to me : "syntax error on line 10"
<robocop> what's the matter ?
<aij> robocop: actually, line 2-3 looks not so good to me
<robocop> why aij ?
_zack has quit ["Leaving."]
<aij> robocop: because the let doesn't end where you might think it does
jeanbon has joined #ocaml
<robocop> aij: I don't understand
<aij> robocop: as for why you're getting a syntax error on line 10, I suspect it is expecting an "in" after line 6, which is still being parsed as the expression for the let on line 2
<robocop> but why a "in" ?
<robocop> if I do let a = []
<robocop> I havn't got any problems
willb has quit [Read error: 110 (Connection timed out)]
<robocop> I've got : File "tcheck.ml", line 60, characters 29-37:
<robocop> Error: Unbound value var_list
_andre has quit [wolfe.freenode.net irc.freenode.net]
sgnb has quit [wolfe.freenode.net irc.freenode.net]
Asmadeus has quit [wolfe.freenode.net irc.freenode.net]
maskd has quit [wolfe.freenode.net irc.freenode.net]
gl has quit [wolfe.freenode.net irc.freenode.net]
maxote has quit [wolfe.freenode.net irc.freenode.net]
brendan has quit [wolfe.freenode.net irc.freenode.net]
aij has quit [wolfe.freenode.net irc.freenode.net]
thelema has quit [wolfe.freenode.net irc.freenode.net]
r0bby has quit [wolfe.freenode.net irc.freenode.net]
Ariens_Hyperion has quit [wolfe.freenode.net irc.freenode.net]
lutter has quit [wolfe.freenode.net irc.freenode.net]
palomer has quit [wolfe.freenode.net irc.freenode.net]
bebui has quit [wolfe.freenode.net irc.freenode.net]
Amorphous has quit [wolfe.freenode.net irc.freenode.net]
fremo has quit [wolfe.freenode.net irc.freenode.net]
Pepe_ has quit [wolfe.freenode.net irc.freenode.net]
sgwizdak has quit [wolfe.freenode.net irc.freenode.net]
mal`` has quit [wolfe.freenode.net irc.freenode.net]
mellum has quit [wolfe.freenode.net irc.freenode.net]
javax has quit [wolfe.freenode.net irc.freenode.net]
Mr_Awesome has quit [wolfe.freenode.net irc.freenode.net]
mrvn has quit [wolfe.freenode.net irc.freenode.net]
smimou has quit [wolfe.freenode.net irc.freenode.net]
delroth has quit [wolfe.freenode.net irc.freenode.net]
itewsh has quit [wolfe.freenode.net irc.freenode.net]
AlpMestan_ has quit [wolfe.freenode.net irc.freenode.net]
rumbleca has quit [wolfe.freenode.net irc.freenode.net]
sbok has quit [wolfe.freenode.net irc.freenode.net]
gildor has quit [wolfe.freenode.net irc.freenode.net]
prigaux has quit [wolfe.freenode.net irc.freenode.net]
munga has quit [wolfe.freenode.net irc.freenode.net]
mfp has quit [wolfe.freenode.net irc.freenode.net]
rjack has quit [wolfe.freenode.net irc.freenode.net]
dejj has quit [wolfe.freenode.net irc.freenode.net]
haelix_ has quit [wolfe.freenode.net irc.freenode.net]
mattam has quit [wolfe.freenode.net irc.freenode.net]
jonafan has quit [wolfe.freenode.net irc.freenode.net]
bohanlon has quit [wolfe.freenode.net irc.freenode.net]
peddie has quit [wolfe.freenode.net irc.freenode.net]
mbishop has quit [wolfe.freenode.net irc.freenode.net]
ertai has quit [wolfe.freenode.net irc.freenode.net]
xcthulhu has quit [wolfe.freenode.net irc.freenode.net]
mrvn has joined #ocaml
itewsh has joined #ocaml
rjack has joined #ocaml
dejj has joined #ocaml
rumbleca has joined #ocaml
prigaux has joined #ocaml
sbok has joined #ocaml
gildor has joined #ocaml
munga has joined #ocaml
mfp has joined #ocaml
haelix_ has joined #ocaml
mattam has joined #ocaml
<robocop> flood §§
<robocop> any idea aij ?
Amorphous has joined #ocaml
fremo has joined #ocaml
Pepe_ has joined #ocaml
sgwizdak has joined #ocaml
mal`` has joined #ocaml
mellum has joined #ocaml
xcthulhu has joined #ocaml
thelema has joined #ocaml
peddie has joined #ocaml
mbishop has joined #ocaml
ertai has joined #ocaml
Ariens_Hyperion has joined #ocaml
lutter has joined #ocaml
palomer has joined #ocaml
bebui has joined #ocaml
javax has joined #ocaml
brendan has joined #ocaml
aij has joined #ocaml
maxote has joined #ocaml
gl has joined #ocaml
maskd has joined #ocaml
Asmadeus has joined #ocaml
sgnb has joined #ocaml
_andre has joined #ocaml
sgnb has quit [wolfe.freenode.net irc.freenode.net]
Asmadeus has quit [wolfe.freenode.net irc.freenode.net]
sgnb has joined #ocaml
Asmadeus has joined #ocaml
<aij> robocop: if you said anything during the netsplit, I missed it
jonafan has joined #ocaml
bohanlon has joined #ocaml
<aij> oh, apparently you missed what I said just before the netsplit
<aij> 12:38:00 < aij> ocaml is a bit funny about using a let expression in the middle of an expression
<aij> 12:38:19 < aij> eg: let a = []; let b = 1 let c = 2 (* it won't like the last let in this expression *)
<aij> 12:38:52 < aij> robocop: but, going back to your original problem, try to figure out where the first let ends
<aij> 12:39:26 < aij> robocop: keep in mind that newlines are the same as any other whitespace
<robocop> yes aij.
Mr_Awesome has joined #ocaml
<robocop> hum, I don't understant where the let finish.
<robocop> this does'nt work :
<robocop> let a = ref []
<robocop> a:=[5];
<robocop> let b = 2
delroth has joined #ocaml
<aij> robocop: the let finishes at the end of the expression
<aij> so, in that example, you're passing too many arguments to the ref function
<aij> also, ; doesn't end an expression, it joins two of them together
<robocop> but why this code finish at the end, and not this : "let a = 2 ...code"
<aij> but the thing after it isn't an expression
<aij> robocop: I'm not sure what you mean by "finish at the end"... let a = ref [] a:=[5]; let b = 2 doesn't even parse
<robocop> aij: but, how I can do for my problem ?
<robocop> what's the solution ?
<aij> there are several solutions... you could use let ... in and make lines 2-4 a single expression, or you could use ;; to end the first definition and a top level expression after it
rjack has quit ["leaving"]
Alpounet has joined #ocaml
th5 has joined #ocaml
<aij> robocop: out of curiosity, what language are you coming from?
th5 has quit [Client Quit]
<robocop> aij: I'm french.
<robocop> Sorry, my english sucks
<aij> oh, heh, I meant programming language
<robocop> aij: Ha, heu, I started with php
<robocop> (I know, it's a pathetic language :-°)
<aij> It's been about 8 years since I used it... and I really don't miss it. :)
Elrood has joined #ocaml
hto has joined #ocaml
itewsh has quit [Connection timed out]
itewsh has joined #ocaml
<Alpounet> I'm still studying and I'm "obliged" to write some PHP for earning some money ...
willb has joined #ocaml
_andre has quit ["Lost terminal"]
_andre has joined #ocaml
Elrood has left #ocaml []
komar_ has joined #ocaml
itewsh has quit [Connection timed out]
itewsh has joined #ocaml
smimou has joined #ocaml
_andre has quit ["leaving"]
<robocop> thanks for your help aij, now it's good.
<robocop> *kljmypj
<robocop> yoyt) nujànèepçàk-((((((((((((-(((çà-t-hode'
sOpen has joined #ocaml
<palomer> Alpounet, you there?
<Alpounet> yeah
<palomer> still want to see my project at work?
<Alpounet> robocop, dog, cat ?
<Alpounet> palomer, of course !
<palomer> ok, one sec, youtube is processing my video
<robocop> Alpounet: little brother :D
<Alpounet> palomer, great
itewsh has quit [Connection timed out]
itewsh has joined #ocaml
Camarade_Tux has quit [Read error: 110 (Connection timed out)]
naufraghi has quit [Remote closed the connection]
monadic_kid has joined #ocaml
itewsh has quit [Read error: 60 (Operation timed out)]
itewsh has joined #ocaml
itewsh has quit [SendQ exceeded]
itewsh has joined #ocaml
willb1 has joined #ocaml
robocop has left #ocaml []
willb has quit [Read error: 113 (No route to host)]
willb has joined #ocaml
willb1 has quit [Read error: 113 (No route to host)]
Yoric[DT] has quit [Read error: 104 (Connection reset by peer)]
r0bby has joined #ocaml
Yoric[DT] has joined #ocaml
<aij> mrvn: you around?
itewsh has quit [Connection timed out]
itewsh has joined #ocaml
<mrvn> sometimes
<palomer> it happens
<aij> mrvn: I managed to make a fairly small example that breaks unification http://paste.debian.net/35437/
<aij> some things that seem like they should be irrelevant actually cause it to stop breaking
<aij> eg, getting rid of either use of functors
itewsh has quit [Connection timed out]
itewsh has joined #ocaml
dejj_ has joined #ocaml
<mrvn> aij: Looks to me like '_a is not compatible with '_b LM.t
<mrvn> let (w1 : ('a->'b) -> ('a, 'c LM.t) pcfg -> 'b) = fun f x -> f x.g
<mrvn> That makes it work.
<mrvn> val w1 : ('a -> 'b) -> ('a, 'c LM.t) pcfg -> 'b
<mrvn> val nb_vertex : ('_a, '_b LM.t) pcfg -> '_a
<aij> but why isn't it compatible?
<mrvn> I don't know.
<aij> so, one amusing thing is that changing LM to module LM = Map.Make(Int64) also makes it compatible
<aij> (that really makes no sense to me)
<mrvn> aij: I don't realy get why '_b and '_b LM.t behave different when force to int LM.t.
dejj has quit [Read error: 110 (Connection timed out)]
<mrvn> hunger
itewsh has quit [Connection timed out]
itewsh has joined #ocaml
Yoric[DT] has quit ["Ex-Chat"]
willb1 has joined #ocaml
Ariens_Hyperion has left #ocaml []
willb has quit [Read error: 113 (No route to host)]
Yoric[DT] has joined #ocaml
ulfdoz has joined #ocaml
<Alpounet> must go, bye.
Alpounet has quit ["Ex-Chat"]
Jedai has joined #ocaml
<palomer> hrmph
<palomer> my project has external dependencies
<palomer> how do I ocamldoc it?
sporkmonger has quit [Read error: 60 (Operation timed out)]
jeanbon has quit [Connection timed out]
hkBst has quit [Read error: 104 (Connection reset by peer)]
willb1 has quit [Read error: 110 (Connection timed out)]
Associat0r has joined #ocaml
bombshelter13_ has quit [Client Quit]
itewsh has quit ["There are only 10 kinds of people: those who understand binary and those who don't"]
Associat0r has quit []
<palomer> hrmph
<palomer> what's the easiest way to find out if string s matches regexp r?
<brendan> Str.string_match
nimred has joined #ocaml
<palomer> righto
<palomer> I remember it being much more complicated with pcre
Yoric[DT] has quit ["Ex-Chat"]
<palomer> wait
<palomer> string_match returns true if a substring matches too
Yoric[DT] has joined #ocaml
Yoric[DT] has quit ["Ex-Chat"]
ulfdoz_ has joined #ocaml
seafood has joined #ocaml
ulfdoz has quit [Read error: 101 (Network is unreachable)]
m3ga has joined #ocaml
seafood_ has joined #ocaml
seafood has quit [Read error: 110 (Connection timed out)]
seafood has joined #ocaml
dejj_ has quit ["Leaving..."]
rhar has joined #ocaml
seafood_ has quit [Read error: 110 (Connection timed out)]
seafood has quit [Read error: 60 (Operation timed out)]
seafood has joined #ocaml
monadic_kid has quit ["Leaving"]