ChanServ changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | http://www.ocaml.org | OCaml 4.01.0 announce at http://bit.ly/1851A3R | Logs at http://irclog.whitequark.org/ocaml
thomasga has quit [Quit: Leaving.]
<cody__> recursive functors do exist in Ocaml
<cody__> a bit tricky to use sometimes though
<lgm> What's the syntax for declaring it?
<lgm> Is there an online example?
<cody__> basically you make NOMINAL a functor that depends on TERM and vice versa
<cody__> then you instantiate with module rec
sh1ken has joined #ocaml
<Drup> cody__: you don't even need that, see backlog
philtor_ has joined #ocaml
<Drup> lgm: I will check your specific case later, pretty sure you can decompose it
<lgm> i have an alternative decomposition that is less flexible than the one i pasted.
<Drup> lgm: in the case you posted, however, you don't have values, so you are defining only the type, so only signatures, is that intended ?
<lgm> cody__: check out http://pastebin.com/QsVs9FSP
<lgm> The example in the URL is slightly different in the decomposition.
eikke__ has joined #ocaml
claudiuc has joined #ocaml
Estivate has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
Estivate has joined #ocaml
happy4crazy has quit []
t4nk785 has joined #ocaml
<t4nk785> Hi, I'm trying to use js_of_ocaml to build a web-based OCaml toplevel with OCaml values in file Foo.ml available
<t4nk785> That is, Foo.ml contains let foo x = x + 1, and I'd like to build a js/web-based toplevel that has foo defined
sh1ken has quit [Quit: leaving]
<lgm> Drup: i was defining both signatures and modules/values, simultaneosly
sh1ken has joined #ocaml
<t4nk785> I thought I just had to compile Foo.ml to input_file.byte (using the usual ocamlfind ocamlc -package js_of_ocaml ... Foo.ml incantation), and then use js_of_ocaml -toplevel input_file.byte to generate the toplevel
<t4nk785> But, this doesn't work
<t4nk785> Is anyone here a js_of_ocaml expert?
<lgm> i was able to get it to work by having the types the recursive declarations be projections and then instantiate them with mutually recursive calls.
ontologiae has joined #ocaml
BitPuffin has quit [Ping timeout: 264 seconds]
hhugo has quit [Quit: Leaving.]
<lgm> well, actually, the instantiation line doesn't work.
pyx has joined #ocaml
pyx has quit [Client Quit]
rgrinberg has quit [Quit: Leaving.]
<lgm> so, this works: http://pastebin.com/9XHRuB6D
travisbrady has joined #ocaml
<lgm> but then this doesn't http://pastebin.com/TLkDphKk
<lgm> ah, i see, i have to relax the typing in the recursive declaration, too. So, this works: http://pastebin.com/1MYa8xfp
eikke__ has quit [Ping timeout: 272 seconds]
claudiuc has quit [Quit: Leaving...]
<pyon> Is there any standard library similar to Int32 or Int64, but for the default int type?
<pyon> Using Int64.to_int and Int64.of_int all over the place is killing me.
<Drup> pyon: there is no predefined Int module
<Drup> pyon: why do you want one ?
<Drup> t4nk785: have you looked at the example in js_of_ocaml sources ?
<t4nk785> Hi, Drup: Yes, but I will gladly look again. One thing I don't understand is what the js_of_ocaml -toplevel option does. Do you know?
<pyon> Drup: I am implementing a mapping between ints (de Bruijn indices) and strings (variable names). It is a record { size: int ; indices: string M.t ; names : S.t }, where "module M = Map.Make (???)" and "module S = Set.Make (String)".
<Drup> what prevents you to define a module Int that will respect Map.Make requirement ? :p
<t4nk785> (I was hoping I could simply do "js_of_ocaml -toplevel input_file.byte" - but it doesn't work, alas. )
<pyon> Drup: Laziness! But I guess I have no choice.
<Drup> t4nk785: I don't know the details, during european daylight, you can ask hhugo here
<t4nk785> Drup: great idea, thank you
rgrinberg has joined #ocaml
<Drup> pyon: it's quite short :)
<bernardofpc> firefox's builtin pdf.js is faster than xpdf/poppler -> but it's bloateder and slower than mupdf (and having a 512 M RAM / sub-GHz computer reminds you everytime of that)
<pyon> "Map.Make (struct type t = int let compare = (-) end)", right?
<Drup> don't do compare = (-), it doesn't behave well with under/overflows
<bernardofpc> (or maybe it has gotten faster recently, last time I tried, it was *painfully* slow on a 100-page pdf even on a Core i7-3rd gen)
<pyon> Drup: Oh, right!
<Drup> pyon: "let compare (x:int) (y:int) = compare x y" is correct
<pyon> Drup: Actually, it even accepted "let compare = compare" :-)
<Drup> yes, but my version is more efficient
jwatzman|work has quit [Quit: jwatzman|work]
<whitequark> screw this trend of rewriting everything in javascript
<pyon> Drup: Why is it so? :-O
<whitequark> screw javascript too, while we're at it
t4nk785 has quit [Ping timeout: 246 seconds]
<whitequark> and computers in general
<pyon> Drup: Boxing?
<pyon> Drup: I mean, are values boxed when using the default compare function? Or what?
<Drup> no
<pyon> Then?
rgrinberg has quit [Quit: Leaving.]
<Drup> the default comparaison function is polymorphic, it will do runtime magic to find out the type and then compare
<Drup> if you specialize it, the compiler can use the right comparison functions directly
<pyon> Ah!
rgrinberg has joined #ocaml
troutwine is now known as troutwine_away
lordkryss has quit [Quit: Connection closed for inactivity]
Estivate has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
ontologiae has quit [Ping timeout: 240 seconds]
ontologiae has joined #ocaml
njcomsec has quit [Quit: KVIrc 4.2.0 Equilibrium http://www.kvirc.net/]
johnnydiabetic has joined #ocaml
q66 has quit [Quit: Leaving]
shinnya has quit [Ping timeout: 260 seconds]
jprakash has quit [Ping timeout: 255 seconds]
<pyon> How do I compile a module as a library, rather than as a standalone executable?
bytbox has quit [Remote host closed the connection]
philtor_ has quit [Ping timeout: 250 seconds]
_twx_ has joined #ocaml
ontologiae has quit [Ping timeout: 260 seconds]
warrick has quit [Quit: leaving]
englishm has joined #ocaml
<lgm> does anybody here use oasis?
<lgm> i generated a project with it and now would like to add a source file
<lgm> the documentation doesn't seem to cover that.
pyon has quit [Quit: Fiat justitia ruat caelum.]
bytbox has joined #ocaml
pyon has joined #ocaml
leowzukw has quit [Ping timeout: 240 seconds]
leowzukw has joined #ocaml
samrat has joined #ocaml
samrat has quit [Client Quit]
samrat has joined #ocaml
johnnydiabetic has quit [Ping timeout: 240 seconds]
johnnydiabetic has joined #ocaml
johnnydiabetic has quit [Client Quit]
bytbox has quit [Remote host closed the connection]
pyon has quit [Quit: brb]
pyon has joined #ocaml
voila has joined #ocaml
leowzukw has quit [Ping timeout: 250 seconds]
leowzukw has joined #ocaml
troutwine_away is now known as troutwine
samrat has quit [Quit: Computer has gone to sleep.]
troutwine is now known as troutwine_away
darkf_ has joined #ocaml
darkf has quit [Ping timeout: 250 seconds]
philtor_ has joined #ocaml
travisbrady has quit [Quit: travisbrady]
darkf_ is now known as darkf
koderok has joined #ocaml
koderok has quit [Client Quit]
siddharthv_away is now known as siddharthv
studybot_ has joined #ocaml
philtor_ has quit [Ping timeout: 240 seconds]
WraithM has joined #ocaml
MercurialAlchemi has joined #ocaml
voila has quit [Quit: Page closed]
samrat has joined #ocaml
WraithM has quit [Ping timeout: 245 seconds]
studybo__ has joined #ocaml
studybot_ has quit [Ping timeout: 264 seconds]
yacks has quit [Ping timeout: 240 seconds]
ggole has joined #ocaml
yacks has joined #ocaml
lgm has quit [Ping timeout: 255 seconds]
cago has joined #ocaml
AltGr has joined #ocaml
_0xAX has joined #ocaml
Simn has joined #ocaml
maattdd_ has joined #ocaml
claudiuc has joined #ocaml
bezirg has joined #ocaml
englishm has quit [Remote host closed the connection]
englishm has joined #ocaml
thomasga has joined #ocaml
eikke__ has joined #ocaml
leowzukw has quit [Quit: leaving]
leowzukw has joined #ocaml
leowzukw has quit [Quit: leaving]
kizzx2 has joined #ocaml
bartbes has quit [Quit: No Ping reply in 180 seconds.]
bartbes has joined #ocaml
Kakadu has joined #ocaml
freling has quit [Quit: Leaving.]
<hyperboreean> hey, I'm having some trouble setting up ocp-indent in emacs, I keep getting "no such file or directory: ocp-indent" even though the load-path is set up ok. Anyone has any ideas on how to debug this ?
lordkryss has joined #ocaml
rgrinberg has quit [Quit: Leaving.]
kakadu_ has joined #ocaml
Kakadu has quit [Ping timeout: 246 seconds]
vjmp has joined #ocaml
<hyperboreean> sorry for the noise, .opam/system/bin wasn't in the path ...
thomasga has quit [Quit: Leaving.]
thomasga has joined #ocaml
maattdd_ has quit [Ping timeout: 272 seconds]
freling has joined #ocaml
maattdd_ has joined #ocaml
studybo__ is now known as studybot
ewd has joined #ocaml
BitPuffin has joined #ocaml
kizzx2 has quit [Quit: Leaving.]
BitPuffin has quit [Ping timeout: 255 seconds]
studybot has quit [Remote host closed the connection]
ontologiae has joined #ocaml
studybot_ has joined #ocaml
studybot_ is now known as studybot
badon has joined #ocaml
dsheets has joined #ocaml
hhugo has joined #ocaml
elspru_ has joined #ocaml
elspru has quit [Ping timeout: 245 seconds]
BitPuffin has joined #ocaml
leowzukw has joined #ocaml
Estivate has joined #ocaml
dmbaturin has quit [Ping timeout: 245 seconds]
_0xAX has quit [Read error: Connection reset by peer]
dmbaturin has joined #ocaml
thomasga has quit [Quit: Leaving.]
hhugo has quit [Quit: Leaving.]
leowzukw_ has joined #ocaml
leowzukw has quit [Ping timeout: 260 seconds]
hhugo has joined #ocaml
samrat has quit [Quit: Computer has gone to sleep.]
maattdd_ has quit [Ping timeout: 260 seconds]
thomasga has joined #ocaml
thomasga has quit [Quit: Leaving.]
_0xAX has joined #ocaml
_andre has joined #ocaml
papna has quit [Ping timeout: 244 seconds]
papna has joined #ocaml
siddharthv is now known as siddharthv_away
siddharthv_away is now known as siddharthv
njcomsec has joined #ocaml
siddharthv is now known as siddharthv_away
badon_ has joined #ocaml
badon has quit [Ping timeout: 260 seconds]
badon_ is now known as badon
BitPuffin has quit [Ping timeout: 255 seconds]
thomasga has joined #ocaml
sepp2k has joined #ocaml
badon has quit [Ping timeout: 245 seconds]
badon has joined #ocaml
hhugo has quit [Quit: Leaving.]
thomasga has quit [Quit: Leaving.]
fold has quit [Ping timeout: 255 seconds]
SethTisue has joined #ocaml
SethTisue has quit [Client Quit]
samrat has joined #ocaml
siddharthv_away is now known as siddharthv
samrat has quit [Client Quit]
yacks has quit [Ping timeout: 245 seconds]
samrat has joined #ocaml
yacks has joined #ocaml
thomasga has joined #ocaml
cody__ has quit [Quit: Leaving]
freling has quit [Remote host closed the connection]
zpe has joined #ocaml
englishm has quit [Read error: Connection reset by peer]
samrat has quit [Quit: Computer has gone to sleep.]
axiles has quit [Ping timeout: 272 seconds]
siddharthv is now known as siddharthv_away
axiles has joined #ocaml
darkf has quit [Quit: Leaving]
thomasga has quit [Quit: Leaving.]
jprakash has joined #ocaml
Hannibal_Smith has joined #ocaml
samrat has joined #ocaml
samrat has quit [Client Quit]
Estivate has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
samrat has joined #ocaml
samrat has quit [Quit: Computer has gone to sleep.]
bytbox has joined #ocaml
Gorgon has joined #ocaml
<Gorgon> Hello!
<Gorgon> I'm currently translating a program from Haskell to Ocaml.
<Gorgon> It's a bit rough.
<Gorgon> I'd like to show the result of a computation, and then print a new line
<mrvn> That is a side effect, haskell has no side effects
<Gorgon> in Haskell it's like this: main = do; interact calc; putStrLn ""
<Gorgon> "interact calc" prints something to the console
<mrvn> print_newline ()
<Gorgon> in Ocaml there is 'print_endline ""'
<Gorgon> but how do I make both calls in a more imperative manner?
<mrvn> or Printf.printf "\n" or "\n%!" to also flush the output
<mrvn> how much more imperative do you want to be?
<kakadu_> what is type of interact?
<Gorgon> well, I want to print the output of "interact calc" to the console, which is part of that function, followed by printing a new line
<mrvn> so just do it
<Gorgon> how do I put both commands in one function so that they're executed one after the other?
<mrvn> interact calc; print_newline ()
<ggole> let f () = cmd1 (); cmd2 ()
<Gorgon> Kakadu_: it has the unit type; it doesn't return anything, just prints to the console
<ggole> So, uh, what's the difficulty?
<Gorgon> ggole: the Haskell mindset ;P
<ggole> Ah, that. :)
<Gorgon> I wasn't aware this is so trivial to do in OCaml
<adrien> :)
<mrvn> you can also do let () = cmd1 () in let () = cmd2 () in ....
<Gorgon> ...but that's not strictly necessary? In other words: why would I do that when I can just make those calls one after the other?
<ggole> The Haskell mindset?
* ggole coughs
<mrvn> you might have a command in the middle of other let statements
<mrvn> or something not returning unit
<ontologiae> By experience, it's syntactically more flexible to write let () = cmd1 () in let () = cmd2 () in .... when you write a big amount of code
<ontologiae> for the reason mrvn is explaining
<ontologiae> /reason/reasons/g
<ontologiae> but it's strictly equivalent
<def`> (up to the [-strict-sequence] flag)
<mrvn> cmd1 (); cmd2 () has undefined order while let is defined?
<def`> mrvn: order is defined
<def`> sequences evaluate left-to-right :]
<mrvn> Oh, you just ment that "let () = not_unit () in" is an error but "not_unit (); ..." is just a warning
<def`> or, more surprisingly, in [let f g h x = g x; h x], the type checker might not infers the type you expect for [g]
<def`> (without warning)
<ggole> That's a bit of a wart.
<mrvn> val f : ('a -> 'b) -> ('a -> 'c) -> 'a -> 'c = <fun>
leowzukw_ has quit [Ping timeout: 260 seconds]
leowzukw has joined #ocaml
<mrvn> # let f g h x = let () = g x in h x;;
<mrvn> val f : ('a -> unit) -> ('a -> 'b) -> 'a -> 'b = <fun>
<ggole> Particularly since application to not enough arguments will silently do nothing.
<def`> Not necessarily, but it might do nothing when you expect something to happen :)
<mrvn> ggole: The type system can't say: 'a -> 'b but 'b must not be a function
<ggole> Yes, the type system can't catch the error. If it inferred a type of 'a -> unit, it could.
<ggole> That's the complaint.
<ggole> Anyway, -strict-sequence is there so I'm not bitching too much.
zpe has quit [Remote host closed the connection]
_0xAX has quit [Remote host closed the connection]
leowzukw has quit [Quit: leaving]
Hannibal_Smith has quit [Ping timeout: 255 seconds]
ontologiae has quit [Ping timeout: 245 seconds]
travisbrady has joined #ocaml
bezirg has quit [Ping timeout: 255 seconds]
frankjeager has joined #ocaml
maattdd_ has joined #ocaml
travisbrady has quit [Quit: travisbrady]
jprakash has quit [Ping timeout: 260 seconds]
travisbrady has joined #ocaml
whirm has joined #ocaml
<whirm> hi ya
ewd has quit [Quit: leaving]
frankjeager has left #ocaml ["Quitte"]
samrat has joined #ocaml
cago has quit [Quit: cago]
eikke__ has quit [Ping timeout: 260 seconds]
shinnya has joined #ocaml
ontologiae has joined #ocaml
sad0ur has quit [Ping timeout: 240 seconds]
claudiuc has quit [Read error: Connection reset by peer]
claudiuc has joined #ocaml
sad0ur has joined #ocaml
pminten has joined #ocaml
Gorgon has quit [Ping timeout: 246 seconds]
jprakash has joined #ocaml
ollehar has joined #ocaml
octahcron has joined #ocaml
gasche_ has quit [Ping timeout: 272 seconds]
whirm has quit [Quit: WeeChat 0.4.3]
gasche has joined #ocaml
eikke__ has joined #ocaml
WraithM has joined #ocaml
maattdd_ has quit [Ping timeout: 245 seconds]
ontologiae has quit [Ping timeout: 250 seconds]
maattdd_ has joined #ocaml
slash^ has joined #ocaml
samrat has quit [Quit: Computer has gone to sleep.]
hhugo has joined #ocaml
sgnb has quit [Read error: Connection reset by peer]
sgnb has joined #ocaml
philtor_ has joined #ocaml
samrat has joined #ocaml
shinnya has quit [Ping timeout: 246 seconds]
oriba has joined #ocaml
zpe has joined #ocaml
zpe has quit [Remote host closed the connection]
zpe has joined #ocaml
zpe has quit [Ping timeout: 240 seconds]
pminten has quit [Quit: KVIrc 4.2.0 Equilibrium http://www.kvirc.net/]
vjmp has quit [Quit: Leaving]
jwatzman|work has joined #ocaml
kakadu_ has quit [Quit: Page closed]
cite-reader has joined #ocaml
MercurialAlchemi has quit [Remote host closed the connection]
MercurialAlchemi has joined #ocaml
thomasga has joined #ocaml
badon_ has joined #ocaml
travisbrady has quit [Quit: travisbrady]
travisbrady has joined #ocaml
badon has quit [Disconnected by services]
badon_ is now known as badon
philtor_ has quit [Ping timeout: 245 seconds]
philtor_ has joined #ocaml
travisbrady has quit [Quit: travisbrady]
girrig_ has quit [Ping timeout: 260 seconds]
_0xAX has joined #ocaml
elspru has joined #ocaml
elspru_ has quit [Ping timeout: 250 seconds]
rand000 has joined #ocaml
troutwine_away is now known as troutwine
girrig has joined #ocaml
maattdd_ has quit [Ping timeout: 250 seconds]
octahcron has quit [Quit: Page closed]
q66 has joined #ocaml
yacks has quit [Ping timeout: 240 seconds]
yacks has joined #ocaml
thomasga has quit [Quit: Leaving.]
travisbrady has joined #ocaml
rgrinberg has joined #ocaml
ollehar has quit [Ping timeout: 246 seconds]
yearzero has joined #ocaml
<yearzero> hi
<yearzero> I'm going through the OCaml/LLVM tutorial
zpe has joined #ocaml
<yearzero> and ran into a compilation error
<yearzero> could anyone please point out the syntax error in this line:
<yearzero> let rec lex = parser (* Skip any whitespace. *) | [< ' (' ' | '\n' | '\r' | '\t'); stream >] -> lex stream
pminten has joined #ocaml
<yearzero> the compiler reports that characters 2-3, i.e. [< are incorrect
<yearzero> file lexer.ml
maattdd_ has joined #ocaml
<ggole> That's a camlp4 extension iirc
zpe has quit [Ping timeout: 245 seconds]
<ggole> I imagine the fix is to fiddle with your build system to get it to use camlp4
Kakadu has joined #ocaml
<yearzero> ah
<yearzero> thanks, I'll look into that
ollehar has joined #ocaml
tg has joined #ocaml
dsheets has quit [Ping timeout: 240 seconds]
bezirg has joined #ocaml
badon_ has joined #ocaml
pminten has quit [Quit: KVIrc 4.2.0 Equilibrium http://www.kvirc.net/]
badon has quit [Ping timeout: 250 seconds]
badon_ is now known as badon
englishm has joined #ocaml
sepp2k has quit [Quit: Konversation terminated!]
zpe has joined #ocaml
AltGr has left #ocaml [#ocaml]
maattdd_ has quit [Ping timeout: 245 seconds]
zpe has quit [Remote host closed the connection]
zpe has joined #ocaml
maattdd_ has joined #ocaml
_weykent is now known as weykent
zpe has quit [Ping timeout: 250 seconds]
_0xAX has quit [Remote host closed the connection]
fold has joined #ocaml
dsheets has joined #ocaml
zpe has joined #ocaml
njcomsec has quit [Ping timeout: 256 seconds]
cite-reader has quit [Quit: leaving]
rgrinberg has quit [Quit: Leaving.]
nlucaroni has quit [Quit: leaving]
rgrinberg has joined #ocaml
maattdd_ has quit [Ping timeout: 272 seconds]
maattdd has joined #ocaml
BitPuffin has joined #ocaml
thomasga has joined #ocaml
eikke__ has quit [Ping timeout: 240 seconds]
hhugo has quit [Quit: Leaving.]
lordkryss has quit [Quit: Connection closed for inactivity]
philtor_ has quit [Ping timeout: 245 seconds]
mcclurmc has quit [Remote host closed the connection]
mcclurmc has joined #ocaml
mcclurmc has quit [Remote host closed the connection]
Submarine_ has joined #ocaml
Thooms has joined #ocaml
Submarine has quit [Ping timeout: 260 seconds]
mcclurmc has joined #ocaml
zpe_ has joined #ocaml
zpe has quit [Read error: Connection reset by peer]
zpe_ has quit [Read error: Connection reset by peer]
zpe has joined #ocaml
zpe has quit [Remote host closed the connection]
zpe has joined #ocaml
jao has joined #ocaml
jao has quit [Changing host]
jao has joined #ocaml
zpe has quit [Ping timeout: 240 seconds]
philtor_ has joined #ocaml
badon_ has joined #ocaml
badon has quit [Disconnected by services]
badon_ is now known as badon
thomasga has quit [Quit: Leaving.]
philtor_ has quit [Ping timeout: 240 seconds]
samrat has quit [Quit: Computer has gone to sleep.]
jao has quit [Ping timeout: 240 seconds]
_andre has quit [Quit: leaving]
ggole has quit []
slash^ has quit [Read error: Connection reset by peer]
yearzero has quit [Ping timeout: 246 seconds]
badon_ has joined #ocaml
philtor_ has joined #ocaml
travisbrady has quit [Quit: travisbrady]
Submarine_ is now known as Submarine
badon has quit [Ping timeout: 250 seconds]
badon_ is now known as badon
vanila has joined #ocaml
Hannibal_Smith has joined #ocaml
zpe has joined #ocaml
Kakadu has quit [Quit: Konversation terminated!]
zpe has quit [Ping timeout: 250 seconds]
badon_ has joined #ocaml
ollehar has quit [Ping timeout: 245 seconds]
maattdd has quit [Ping timeout: 246 seconds]
badon has quit [Ping timeout: 264 seconds]
badon_ is now known as badon
elspru has quit [Ping timeout: 246 seconds]
Submarine has quit [Remote host closed the connection]
bezirg has quit [Quit: Leaving.]
SHODAN has joined #ocaml
SHODAN has quit [Changing host]
SHODAN has joined #ocaml
hhugo has joined #ocaml
jprakash has quit [Ping timeout: 250 seconds]
ollehar has joined #ocaml
philtor_ has quit [Ping timeout: 264 seconds]
ollehar has quit [Quit: ollehar]
Simn has quit [Quit: Leaving]
MercurialAlchemi has quit [Ping timeout: 246 seconds]
studybot has quit [Ping timeout: 264 seconds]
NoNNaN has quit [Ping timeout: 264 seconds]
dsheets has quit [Ping timeout: 240 seconds]
philtor_ has joined #ocaml
studybot has joined #ocaml
Hannibal_Smith has quit [Quit: Sto andando via]
NoNNaN has joined #ocaml
WraithM has quit [Quit: Lost terminal]
rand000 has quit [Quit: leaving]
eikke__ has joined #ocaml
englishm has quit [Remote host closed the connection]
studybot_ has joined #ocaml
englishm has joined #ocaml
studybot has quit [Ping timeout: 264 seconds]
englishm has quit [Ping timeout: 260 seconds]
badon_ has joined #ocaml
philtor_ has quit [Ping timeout: 240 seconds]
pyon has quit [Ping timeout: 272 seconds]
badon has quit [Disconnected by services]
badon_ is now known as badon
philtor has joined #ocaml
thomasga has joined #ocaml
rgrinberg has quit [Quit: Leaving.]
shinnya has joined #ocaml
badon_ has joined #ocaml
pyon has joined #ocaml
badon has quit [Disconnected by services]
badon_ is now known as badon
troutwine is now known as troutwine_away
darkf has joined #ocaml
enquora has joined #ocaml
eikke__ has quit [Ping timeout: 260 seconds]
troutwine_away is now known as troutwine
jprakash has joined #ocaml
madroach has quit [Ping timeout: 250 seconds]
madroach has joined #ocaml
NoNNaN has quit [Remote host closed the connection]
NoNNaN has joined #ocaml
badon_ has joined #ocaml