<douglarek>
it is :Exercise: association list keys [?????????]
<douglarek>
it says: "We know of one solution that needs only a single line of code and does not use any user-defined functions, only library functions."; but I only thought a general method: let keys lst = List.map (fun (a, _) -> a) lst
<douglarek>
does anyone have a better method ?
<reynir>
douglarek: There's already a function that does (fun (a, _) -> a) :-)
nicoo has quit [Remote host closed the connection]
nicoo has joined #ocaml
ddd has joined #ocaml
sgronblo has quit [Ping timeout: 240 seconds]
<douglarek>
reynir: thanks; I am new to OCaml
sgronblo has joined #ocaml
<douglarek>
reynir: and my method can not ensure keys are unique
<Leonidas>
"We know of one solution that needs only a single line of code" well, that is easy to do in ocaml, since you can just write everything in one line
<reynir>
hehe
agravier has quit [Quit: agravier]
<def`>
Leonidas: 50 columns :)
<flux>
or paraphrasing prof. farnsworth: Yes, a single line of code, laced with nothing more than a few newlines.
freusque has quit [Ping timeout: 255 seconds]
threshold has quit [Ping timeout: 276 seconds]
threshold has joined #ocaml
freusque has joined #ocaml
AltGr has joined #ocaml
<Leonidas>
I have 43 chars but it is kinda "wrong" in a way
alfredo has quit [Ping timeout: 260 seconds]
kevinqiu` has joined #ocaml
jimt_ is now known as jimt
zpe has joined #ocaml
zpe has quit [Remote host closed the connection]
kevinqiu` has quit [Ping timeout: 255 seconds]
zpe has joined #ocaml
zpe_ has joined #ocaml
zpe has quit [Read error: Connection reset by peer]
zpe_ has quit [Remote host closed the connection]
zpe has joined #ocaml
cranmax has joined #ocaml
vramana_ has quit [Quit: vramana_]
zpe has quit [Read error: Connection reset by peer]
<douglarek>
ok; I just tried: let keys lst = let (a, _) = List.split lst in List.sort_uniq compare a
<douglarek>
does anyone have a better way ?
freusque has quit [Quit: WeeChat 1.7.1]
zpe has joined #ocaml
<reynir>
I think that's reasonable. There's a function you can use that I hinted at earlier
<douglarek>
reynir: which function ?
<reynir>
fun (a, _) -> a
malina has joined #ocaml
<douglarek>
reynir: ok; but I can not use user define functions
<douglarek>
only library functions allowed
<reynir>
Yea, sorry, I meant that there's already a function that does this
<douglarek>
but how can I avoid `let in`
argent_smith has joined #ocaml
<douglarek>
ok ; done
kevinqiu` has joined #ocaml
malina has quit [Ping timeout: 260 seconds]
<douglarek>
a better way: let keys lst = lst |> List.split |> fst |> List.sort_uniq compare
<companion_cube>
l |> List.map fst |> List.sort_uniq compare
kevinqiu` has quit [Ping timeout: 260 seconds]
fre has joined #ocaml
<douglarek>
companion_cube: cool; but how can I only use let keys = ... ?
<douglarek>
ignore lst argument
<companion_cube>
why would you want to do that?
<douglarek>
just want to do like `let xxx = function ` do
<companion_cube>
you'd need a composition operator, which is not standard
<companion_cube>
this is not Haskell…
dhil has joined #ocaml
barcabuona has quit [Ping timeout: 258 seconds]
<douglarek>
ok; is `function` in `let xxx = function` just for pattern match ?
<flux>
companion_cube, @@ is in standard library
<companion_cube>
flux: that's not composition
<companion_cube>
douglarek: yes, and you'll need to bind a variable anyway
<companion_cube>
but there really is no point in avoiding `let keys l = …`
<douglarek>
ok; thanks;
barcabuona has joined #ocaml
malina has joined #ocaml
<douglarek>
xit
douglarek has quit [Quit: WeeChat 1.9]
barcabuona has quit [Ping timeout: 240 seconds]
barcabuona has joined #ocaml
sgronblo_ has joined #ocaml
cranmax_ has joined #ocaml
sgronblo has quit [Ping timeout: 240 seconds]
richi238 has joined #ocaml
razwelles has joined #ocaml
chelfi1 has joined #ocaml
rixed_ has joined #ocaml
j0sh has joined #ocaml
Asmadeus_ has joined #ocaml
qmm has joined #ocaml
xaimus_ has joined #ocaml
shakalaka_ has joined #ocaml
cranmax has quit [*.net *.split]
CcxWrk has quit [*.net *.split]
richi235 has quit [*.net *.split]
qmmm has quit [*.net *.split]
Soni has quit [*.net *.split]
nullifidian has quit [*.net *.split]
shakalaka has quit [*.net *.split]
Exagone313 has quit [*.net *.split]
chelfi has quit [*.net *.split]
j0sh_ has quit [*.net *.split]
Asmadeus has quit [*.net *.split]
xaimus has quit [*.net *.split]
rixed has quit [*.net *.split]
razwelle1 has quit [*.net *.split]
robertc`` has quit [*.net *.split]
cranmax_ is now known as cranmax
Exagone314 has joined #ocaml
CcxWrk has joined #ocaml
Exagone314 is now known as Exagone313
nullifidian has joined #ocaml
Soni has joined #ocaml
kakadu_ has joined #ocaml
sgronblo_ has quit [Read error: Connection reset by peer]
kakadu has joined #ocaml
kakadu_ has quit [Ping timeout: 268 seconds]
kevinqiu` has joined #ocaml
kevinqiu` has quit [Ping timeout: 246 seconds]
mfp__ has joined #ocaml
Asmadeus_ is now known as Asmadeus
silver has joined #ocaml
samrat_ has quit [Ping timeout: 240 seconds]
alfredo_ has joined #ocaml
dhil has quit [Ping timeout: 240 seconds]
jao has joined #ocaml
kevinqiu` has joined #ocaml
kevinqiu` has quit [Ping timeout: 268 seconds]
alfredo_ has quit [Read error: Connection reset by peer]
alfredo__ has joined #ocaml
sgronblo has joined #ocaml
dhil has joined #ocaml
alfredo__ has quit [Read error: No route to host]
alfredo_ has joined #ocaml
samrat_ has joined #ocaml
alfredo__ has joined #ocaml
ihavelotsoffries has joined #ocaml
alfred___ has joined #ocaml
alfredo_ has quit [Ping timeout: 260 seconds]
alfredo_ has joined #ocaml
alfredo__ has quit [Read error: Connection reset by peer]
alfred___ has quit [Ping timeout: 240 seconds]
agravier has joined #ocaml
jao has quit [Ping timeout: 268 seconds]
al-damiri has joined #ocaml
malc_ has joined #ocaml
<companion_cube>
hmmm, anyone knows how to make threaded programs die properly when receiving SIGTERM during a mutex acquisition?
<companion_cube>
(instead of just waiting)
<malc_>
companion_cube: got an example?
<companion_cube>
hmm not a one-liner, but typically the main thread waits for a lock for a long time (waiting for a big computation to finish); all signals received in the mean time seem to be ignored
sepp2k has joined #ocaml
kakadu_ has joined #ocaml
kakadu__ has joined #ocaml
kakadu has quit [Ping timeout: 258 seconds]
kakadu_ has quit [Ping timeout: 276 seconds]
nomicflux has joined #ocaml
rdutra has joined #ocaml
ziyourenxiang has joined #ocaml
benmachine has quit [Ping timeout: 246 seconds]
kevinqiu` has joined #ocaml
fre has quit [Ping timeout: 255 seconds]
minn has quit [Ping timeout: 246 seconds]
nomicflux has quit [Quit: nomicflux]
kevinqiu` has quit [Ping timeout: 260 seconds]
nomicflux has joined #ocaml
kakadu has joined #ocaml
cranmax has quit [Quit: Connection closed for inactivity]
agravier has quit [Quit: agravier]
freusque has joined #ocaml
kakadu_ has joined #ocaml
kakadu__ has quit [Ping timeout: 276 seconds]
agravier has joined #ocaml
agravier has quit [Client Quit]
agravier has joined #ocaml
agravier has quit [Client Quit]
agravier has joined #ocaml
agravier has quit [Client Quit]
kakadu has quit [Ping timeout: 268 seconds]
agravier has joined #ocaml
kakadu has joined #ocaml
agravier has quit [Client Quit]
kakadu_ has quit [Ping timeout: 260 seconds]
kakadu_ has joined #ocaml
samrat_ has quit [Ping timeout: 276 seconds]
<Leonidas>
companion_cube: haha, I have exactly the same sort_uniq compare solution :)
cranmax has joined #ocaml
kakadu has quit [Ping timeout: 240 seconds]
freusque has quit [Ping timeout: 276 seconds]
kakadu has joined #ocaml
kakadu_ has quit [Ping timeout: 246 seconds]
benmachine has joined #ocaml
freusque has joined #ocaml
nomicflux has quit [Quit: nomicflux]
ihavelotsoffries has left #ocaml [#ocaml]
maarhart has joined #ocaml
TheLemonMan has joined #ocaml
maarhart has quit [Client Quit]
TheLemonMan has quit [Client Quit]
kevinqiu` has joined #ocaml
jlam__ has joined #ocaml
jlam_ has quit [Ping timeout: 246 seconds]
sh0t has joined #ocaml
samrat_ has joined #ocaml
freusque has quit [Ping timeout: 240 seconds]
kevinqiu has joined #ocaml
freusque has joined #ocaml
maarhart has joined #ocaml
maarhart has quit [Remote host closed the connection]
sepp2k has quit [Quit: Leaving.]
MercurialAlchemi has quit [Ping timeout: 260 seconds]
<companion_cube>
rgrinberg: heh, now I'm more willing to move zipperposition and containers to jbuilder ;)
<companion_cube>
(I probably need to figure out a few things first, but well)
kevinqiu has quit [Quit: ERC (IRC client for Emacs 24.5.1)]
kevinqiu` has quit [Quit: ERC (IRC client for Emacs 24.5.1)]
<Drup>
companion_cube: what changed ?
kevinqiu has joined #ocaml
<companion_cube>
I tried it on some small project
<companion_cube>
it's nice
<companion_cube>
(still, I'm a bit afraid of preprocessing…)
<zozozo>
companion_cube: how do you handle the multiple dir problem ? or did you flatten your project structure ?
<companion_cube>
I flattened it
<companion_cube>
because I don't are at all about that
<companion_cube>
otoh I'd have to check how the move pack->alias goes…
<zozozo>
oh, in that case I'll wait a bit, I really don't want to flatten my projects (and, for most of them, flattenning things would make the main folder a big mess)
<companion_cube>
the main source folder, you mean?
<companion_cube>
wait, you can still have several folders, one per sub-lib
<companion_cube>
if I understood correctly
<zozozo>
right, i'll try and see if it works for me (I think I recall some of my projects where some dependencies goes both way between directories)
<companion_cube>
eeek
<zozozo>
I'm not sure it still happens
dhil has quit [Ping timeout: 276 seconds]
samrat_ has quit [Ping timeout: 260 seconds]
ryanartecona has joined #ocaml
sepp2k has joined #ocaml
minn has joined #ocaml
hashpuppy has quit [Quit: Connection closed for inactivity]
zpe has quit [Remote host closed the connection]
zpe has joined #ocaml
enterprisey has joined #ocaml
zpe has quit [Ping timeout: 276 seconds]
malina has quit [Ping timeout: 240 seconds]
MercurialAlchemi has joined #ocaml
vgrocha has joined #ocaml
sh0t has quit [Ping timeout: 276 seconds]
sh0t has joined #ocaml
<rgrinberg>
companion_cube: I knew you'd come around. Its just a matter of time really. Jbuilder is just that much better than everything else :)
kakadu has left #ocaml ["Konversation terminated!"]
kakadu has joined #ocaml
zpe has joined #ocaml
mfp__ has quit [Ping timeout: 260 seconds]
mfp__ has joined #ocaml
FreeBirdLjj has joined #ocaml
xaimus_ is now known as xaimus
rwmjones is now known as rwmjones|holiday
ryanartecona has quit [Quit: ryanartecona]
ti77zyra has joined #ocaml
<ti77zyra>
hi is there in ocaml something like the haskell like pattern guards ?
<ti77zyra>
the only thing I know of is using pattern matching with "when"
<ti77zyra>
I mean just guards ...
<companion_cube>
rgrinberg: well I'm still a bit afraid of touching, like, cppo and qtest
<ti77zyra>
so the only thing that would basically be the same is a wildcard match followed by a "when" statement
dhil has joined #ocaml
silver_ has joined #ocaml
silver has quit [Ping timeout: 240 seconds]
minn has quit [Ping timeout: 260 seconds]
ryanartecona has joined #ocaml
<companion_cube>
rgrinberg: also I'm sad that colored messages are not available.
copy_ has joined #ocaml
zpe has quit [Remote host closed the connection]
zpe has joined #ocaml
<flux>
haskell pattern guard
<flux>
oops
<flux>
ti77zyra, I'm unsure what you're missing
<flux>
ocaml has pattern guards in form of 'when' :)
<flux>
it doesn't have 'pattern guards that return non-booleans', though at some situations you might use laziness for that
<ti77zyra>
flux: but afaik I first have to do a pattern match and after that I can use when
<ti77zyra>
like this (wait a second):
PigDude has joined #ocaml
PigDude has joined #ocaml
PigDude has quit [Changing host]
zpe has quit [Ping timeout: 258 seconds]
<PigDude>
hi, what is the recommended way to manage project-specific dependencies in ocaml, so that another developer can easily reproduce your environment?
<ti77zyra>
flux: ok I know this one is a non sense example ...
<ti77zyra>
let rec bla (n : int) (m : int) : int =
<PigDude>
I thought there was some way to do this with switches but I'm not seeing the option to name a switch now (so you can have multiple switches for the same version)
<zozozo>
PigDude: just create an opam file in your repo contianing all dependencies for your project and anyone can pin it using opam
<ti77zyra>
flux: it just seems a bit redundant to make a wildcard pattern match so I can use the guard
<PigDude>
an nevermind I found the docs
<PigDude>
sorry for the silly questions thanks!
jlam__ has quit [Ping timeout: 255 seconds]
<flux>
ti77zyra, that's actually a pattern for avoiding multiple uses of 'if'. usually pattern guards are used for, well, guarding the pattern..
<ti77zyra>
the problem is when I want to have multiple branches, (imho) the if then else construct doesn't look not so nice
<ti77zyra>
flux: so it is ok the way I use it ?
<flux>
yes
<flux>
how is it done in Haskell, btw?
<ti77zyra>
flux: one sec
<ti77zyra>
p01_12 :: Int -> Int -> Int
<ti77zyra>
p01_12 n m
<ti77zyra>
| n > m = n
<ti77zyra>
| otherwise = m
<ti77zyra>
flux: like this
<flux>
so you are pattern matching n and m
<ti77zyra>
flux: ahm ok , I think you mean the "n" and "m" after p01_12 , right ?
<flux>
I don't think there's quite that succinct way in OCaml. perhaps the closest, but still different in particular about the input parameters, is, let foo = function (n, m) when n > m -> n | (_, m) -> m
<flux>
but function cannot do multiple arguments (why not? sounds like a reasonable enhancement?), so that requires a tuple argument
<ti77zyra>
flux: yes that looks (more) like what I'm looking for
<ti77zyra>
flux: is it possible to have several "when"
<ti77zyra>
like this :
<flux>
there's one "when" per top-level value to match
MercurialAlchemi has quit [Ping timeout: 260 seconds]
<ti77zyra>
let foo = function (n, m) when n > m -> n | when m = 5 -> m | _ -> n
<ti77zyra>
flux: I'm not (too) sure what that means , sorry ....
<flux>
:-)
PigDude has quit [Quit: PigDude]
<Drup>
flux: multi argument matching was in caml light. That was splitted in fun (multi argument, but no matchin) and function (one argument, but no matching)
<Drup>
mostly for syntax reasons, afaik
<flux>
ambiguity? it seems like function a b -> .. would be possible, but perhaps not then..
<zozozo>
flux: let f = function A B -> true, does that mean two arguments or 1 argumentw whose contructor A takes a B ?
ryanartecona has quit [Quit: ryanartecona]
<flux>
how does it work in haskell? it requires parens always?
<flux>
so 'fun' requires parens in that case while 'function' does not
<flux>
so the logical conclusion is that we can extend 'fun' to have pattern matching?-)
toolslive has joined #ocaml
<zozozo>
flux: not without breaking retro-compatibility
<ti77zyra>
flux: in haskell when you pattern match and you want to show that you have for example a constructor which takes one argument you have to put paranthesis around it
<ti77zyra>
like this functionName (A x) = ...
shinnya has joined #ocaml
<ti77zyra>
flux: I hope that was what you wanted to know about haskell ...
<toolslive>
hm, I have a x.ml which compiles, and the whole program compiles. now I let the compiler spit out the corresponding x.mli . now the program no longer compiles. it barfs over this: type ('a, 'b) result = ('a, 'b) result = Ok of 'a | Error of 'b. I need to manually adapt it to type ('a, 'b) result = ('a, 'b) Pervasives.result = Ok of 'a | Error of 'b in the .mli
<octachron>
toolslive, generated mli's do not always mirror exactly compiler inferred interface, there can be some accident
<toolslive>
even if the type abbreviation in the module refers to Pervasives.result, the .mli has no referrence to Pervasives anymore. Is this a bug?
<toolslive>
it seems the order of lookup in scope is wrong.
<octachron>
toolslive, in this case, I think that I may have fixed this specific problem in 4.06
dtornabene has joined #ocaml
<octachron>
but yes, previous version of the compiler will ellide the "Pervasives." prefix even in situation where this ellision is incorrect
<toolslive>
now. This 'accident' is easy for me to understand and fix, but there are other cases that confuse me.
ryanartecona has joined #ocaml
<def`>
type nonrec ('a, 'b) result = ...
cthuluh has quit [Ping timeout: 240 seconds]
<octachron>
toolslive, some typical problems with inferred mli's come from shadowing some type paths, making them unamable.
cthuluh has joined #ocaml
<toolslive>
well, the x.ml typicaly does things like module List = struct include List .... end
ti77zyra has left #ocaml ["WeeChat 1.6"]
kevinqiu has quit [Remote host closed the connection]
<def`>
(there is no syntax that solves the shadowing problem so... some interfaces are not printable)
kevinqiu has joined #ocaml
ollehar1 has joined #ocaml
<octachron>
toolslive, if you are lost enough to be willing to resort to experimental compiler plugins, 4.06.0+pr1120 might be able to pinpoint the location of (some of?)these accidents
handlex has joined #ocaml
<octachron>
otherwise, you might have to looking manually for type redefinitions
kevinqiu has quit [Ping timeout: 260 seconds]
<toolslive>
now the point is that :" type ('a, 'b) result = ('a, 'b) result = Ok of 'a | Error of 'b" is not a line in the x.ml file, but it's generated by the compiler in the .mli file.
zv has quit [Ping timeout: 246 seconds]
cranmax has quit [Quit: Connection closed for inactivity]
<octachron>
toolslive, the .mli file generated by the compiler from ml is not guaranted to be valid
kevinqiu has joined #ocaml
cranmax has joined #ocaml
<octachron>
citing man ocamlc -i: "Also, since the output follows the syntax of interfaces, it *can help* in writing an explicit interface (.mli file)"
<toolslive>
that's a bit subawesome.... if it's not guaranteed to be valid it might as well spit out garbage.
<Leonidas>
jerith: I feel like doing something. How about I release the next breaking change version of Slacko and then iterate on making it less broken? I think I haven't made a release in way too long.
<Leonidas>
maybe I can incorporate flux' RTM feature afterwards :)
handlex has quit [Quit: handlex]
dhil has quit [Ping timeout: 258 seconds]
<flux>
I found memory issues with the my RTM codes :-o
Anarchos has joined #ocaml
<flux>
so I haven't yet debugged it..
<flux>
segmentation faults from ocaml programs are always fun
<jeroud>
Leonidas: I've been devoured by work recently, but I'm taking some time off work at the end of next month.
<jeroud>
I'm happy for you to do a release now, though. :-)
<Leonidas>
jeroud: Ok. Just wanted to double check, not that I release something while you have something in the pipeline that you'd like to get in first :)
sgronblo has quit [Ping timeout: 240 seconds]
MercurialAlchemi has joined #ocaml
minn has joined #ocaml
<toolslive>
ah. different types with the same name in nested modules also confuses the .mli generator
<toolslive>
nested iso shadowing
toolslive has quit [Remote host closed the connection]
minn has quit [Ping timeout: 255 seconds]
zv has joined #ocaml
fraggle-boate has joined #ocaml
<jeroud>
Leonidas: I have a thing in the pipeline, but it'll be a couple of weeks before I can do it properly.
fraggle-boate has quit [Quit: Quitte]
<jeroud>
I'm already using it in my "bot", though.
<jeroud>
It's the file upload thing.
FreeBirdLjj has quit [Remote host closed the connection]
MercurialAlchemi has quit [Ping timeout: 240 seconds]
fraggle-boate has joined #ocaml
Simn has quit [Ping timeout: 240 seconds]
fraggle-boate has quit [Remote host closed the connection]
richi238 is now known as richi235
jlam__ has joined #ocaml
jlam_ has quit [Ping timeout: 246 seconds]
ollehar1 has quit [Quit: ollehar1]
ryanartecona has quit [Quit: ryanartecona]
Simn has joined #ocaml
FreeBirdLjj has joined #ocaml
MercurialAlchemi has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
slash^ has joined #ocaml
enterprisey has quit [Ping timeout: 240 seconds]
samrat_ has quit [Ping timeout: 240 seconds]
enterprisey has joined #ocaml
raphinou has joined #ocaml
raphinou has quit [Client Quit]
raphinou has joined #ocaml
raphinou has quit [Client Quit]
snowcrshd has joined #ocaml
malc_ has quit [Remote host closed the connection]
ryanartecona has joined #ocaml
minn has joined #ocaml
rightfold has left #ocaml [#ocaml]
ryanartecona has quit [Quit: ryanartecona]
minn has quit [Ping timeout: 240 seconds]
TheLemonMan has joined #ocaml
jnavila has joined #ocaml
kakadu has quit [Quit: Konversation terminated!]
KeyJoo has joined #ocaml
minn has joined #ocaml
nicooo has joined #ocaml
nicoo has quit [Ping timeout: 248 seconds]
ygrek_ has joined #ocaml
AltGr has left #ocaml [#ocaml]
<minn>
Is it possible to use deriving in the toplevel? For example, load a file containing a deriving declaration for testing purposes?
<minn>
Oh, nevermind. I was being dumb.
barcabuona has quit [Ping timeout: 255 seconds]
ryanartecona has joined #ocaml
slash^ has quit [Read error: Connection reset by peer]
barcabuona has joined #ocaml
moei has quit [Quit: Leaving...]
_andre has quit [Quit: leaving]
MercurialAlchemi has quit [Ping timeout: 240 seconds]
barcabuona has quit [Ping timeout: 246 seconds]
ryanartecona has quit [Quit: ryanartecona]
kakadu has joined #ocaml
ryanartecona has joined #ocaml
fraggle_ has quit [Quit: -ENOBRAIN]
barcabuona has joined #ocaml
snowcrshd has quit [Remote host closed the connection]
minn has quit [Ping timeout: 268 seconds]
pierpa has joined #ocaml
enterprisey has quit [Read error: Connection reset by peer]
Murmus has joined #ocaml
malc_ has joined #ocaml
daniel_ has joined #ocaml
daniel_ has quit [Read error: Connection reset by peer]
daniel_ has joined #ocaml
dtornabene has quit [Read error: Connection reset by peer]
rdutra has quit [Quit: Leaving.]
daniel_ has quit [Ping timeout: 246 seconds]
TheLemonMan has quit [Quit: "It's now safe to turn off your computer."]
jlam_ has joined #ocaml
snowcrshd has joined #ocaml
jlam__ has quit [Ping timeout: 240 seconds]
kakadu_ has joined #ocaml
kakadu has quit [Ping timeout: 260 seconds]
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]
minn has joined #ocaml
dtornabene has joined #ocaml
jnavila has quit [Ping timeout: 240 seconds]
malc_ has quit [Quit: ERC (IRC client for Emacs 25.0.50.2)]
moei has joined #ocaml
dtornabene has quit [Quit: Leaving]
dtornabene has joined #ocaml
sz0 has quit [Quit: Connection closed for inactivity]
malina has joined #ocaml
Simn has quit [Read error: Connection reset by peer]
SpiceGuid has joined #ocaml
dtornabene has quit [Read error: Connection reset by peer]
dtornabene has joined #ocaml
enterprisey has joined #ocaml
olibjerd has quit [Ping timeout: 268 seconds]
dtornabene has quit [Read error: Connection reset by peer]
dtornabene has joined #ocaml
andreas_ has quit [Quit: Connection closed for inactivity]
jlam__ has joined #ocaml
jlam_ has quit [Ping timeout: 260 seconds]
KeyJoo has quit [Ping timeout: 268 seconds]
zv has quit [Ping timeout: 255 seconds]
argent_smith has quit [Quit: Leaving.]
kevinqiu has quit [Ping timeout: 260 seconds]
enterprisey has quit [Remote host closed the connection]
sepp2k has quit [Ping timeout: 268 seconds]
dtornabene has quit [Quit: Leaving]
Muzer has quit [Ping timeout: 255 seconds]
sgronblo has joined #ocaml
fraggle_ has joined #ocaml
ryanartecona has quit [Quit: ryanartecona]
average has joined #ocaml
minn has quit [Ping timeout: 276 seconds]
zv has joined #ocaml
Leandr has joined #ocaml
Leandr has left #ocaml [#ocaml]
sh0t has quit [Ping timeout: 255 seconds]
Muzer has joined #ocaml
sgronblo has quit [Read error: Connection reset by peer]
kevinqiu has joined #ocaml
kevinqiu has quit [Ping timeout: 260 seconds]
SpiceGuid has quit [Quit: ChatZilla 0.9.92 [SeaMonkey 2.46/20161213183751]]