adrien changed the topic of #ocaml to: Discussions about the OCaml programming language | http://www.ocaml.org | Current MOOC: https://huit.re/ocamlmooc | OCaml 4.04.0 release notes: http://ocaml.org/releases/4.04.html | Try OCaml in your browser: http://try.ocamlpro.com | Public channel logs at http://irclog.whitequark.org/ocaml
tobiasBora has joined #ocaml
_y has joined #ocaml
_y has quit [Ping timeout: 264 seconds]
fre has quit [Ping timeout: 250 seconds]
_y has joined #ocaml
jao has quit [Remote host closed the connection]
_y has quit [Ping timeout: 250 seconds]
programo has joined #ocaml
_y has joined #ocaml
jao has joined #ocaml
infinity0 has quit [Ping timeout: 268 seconds]
infinity0 has joined #ocaml
_y has quit [Ping timeout: 250 seconds]
_y has joined #ocaml
tobiasBora has quit [Ping timeout: 265 seconds]
tobiasBora has joined #ocaml
infinity0 has quit [Remote host closed the connection]
infinity0 has joined #ocaml
infinity0 has quit [Remote host closed the connection]
infinity0 has joined #ocaml
tobiasBora has quit [Ping timeout: 250 seconds]
_y has quit [Ping timeout: 245 seconds]
_y has joined #ocaml
tobiasBora has joined #ocaml
silver has quit [Read error: Connection reset by peer]
wu_ng has quit [Ping timeout: 258 seconds]
jlongster has joined #ocaml
jlongster has quit [Ping timeout: 245 seconds]
jlongster has joined #ocaml
FreeBirdLjj has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
wu_ng has joined #ocaml
FreeBird_ has joined #ocaml
FreeBirdLjj has quit [Read error: Connection reset by peer]
pierpa has quit [Ping timeout: 256 seconds]
mfp has quit [Ping timeout: 252 seconds]
averell has quit [Ping timeout: 240 seconds]
zozozo has quit [Ping timeout: 240 seconds]
Sorella has quit [Ping timeout: 240 seconds]
M-pesterhazy has quit [Ping timeout: 240 seconds]
zozozo_ has joined #ocaml
M-pesterhazy1 has joined #ocaml
jlongster has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
Sorella has joined #ocaml
djellemah_ has quit [Ping timeout: 240 seconds]
djellemah_ has joined #ocaml
sz0 has quit [Ping timeout: 240 seconds]
moei has joined #ocaml
sz0 has joined #ocaml
\h has quit [Ping timeout: 240 seconds]
wu_ng has quit [Read error: Connection reset by peer]
wu_ng has joined #ocaml
malina has joined #ocaml
tmtwd has joined #ocaml
zirman has quit [Remote host closed the connection]
\h has joined #ocaml
zirman has joined #ocaml
zirman has quit [Ping timeout: 258 seconds]
FreeBird_ has quit [Remote host closed the connection]
copy` has quit [Quit: Connection closed for inactivity]
FreeBirdLjj has joined #ocaml
unbalanced has quit [Ping timeout: 258 seconds]
zirman has joined #ocaml
malina has quit [Quit: Throwing apples of Montserrat]
zirman has quit [Ping timeout: 264 seconds]
jao has quit [Ping timeout: 250 seconds]
FreeBirdLjj has quit [Remote host closed the connection]
nomicflux has quit [Quit: nomicflux]
programo has quit [Read error: Connection reset by peer]
ryanartecona has joined #ocaml
infinity0 has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
average has quit [Quit: leaving]
infinity0 has joined #ocaml
zirman has joined #ocaml
infinity0 has quit [Remote host closed the connection]
infinity0 has joined #ocaml
zirman has quit [Ping timeout: 248 seconds]
rgrinberg has quit [Ping timeout: 260 seconds]
Mercuria1Alchemi has joined #ocaml
djellemah_ is now known as djellemah
zirman has joined #ocaml
zirman has joined #ocaml
zirman has quit [Changing host]
zirman has quit [Ping timeout: 265 seconds]
ryanartecona has quit [Quit: ryanartecona]
argent_smith has joined #ocaml
maattdd has joined #ocaml
maattdd has quit [Ping timeout: 258 seconds]
Simn has joined #ocaml
jnavila has joined #ocaml
infinity0 has quit [Remote host closed the connection]
infinity0 has joined #ocaml
fre has joined #ocaml
maattdd has joined #ocaml
trepta7 has quit [Ping timeout: 268 seconds]
dhil has joined #ocaml
obadz has quit [Ping timeout: 265 seconds]
obadz has joined #ocaml
infinity0 has quit [Remote host closed the connection]
infinity0 has joined #ocaml
dhil has quit [Ping timeout: 258 seconds]
larhat has joined #ocaml
AltGr has joined #ocaml
infinity0 has quit [Remote host closed the connection]
infinity0 has joined #ocaml
larhat has quit [Quit: Leaving.]
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
FreeBirdLjj has quit [Ping timeout: 250 seconds]
larhat has joined #ocaml
zirman has joined #ocaml
zirman has quit [Ping timeout: 264 seconds]
raphinou has joined #ocaml
raphinou has quit [Client Quit]
raphinou has joined #ocaml
<raphinou> I thought Lwt.bind and >>= were equivalent, but here is code which behaves differently: http://pastebin.com/d8xR1wUP . Where am I wrong?
<Armael> >>= is exactly Lwt.bind, so I suspect the issue is just some mixup with ; and parenthesis
<Armael> do you have a self-contained example?
tmtwd has quit [Ping timeout: 250 seconds]
<Armael> btw, I don't think you're supposed to ignore the result of Lwt_io.printf
<raphinou> the problem comes from the fact that with >>= I didn't enclose the function in parenthesis (fun a -> ) vs fun a ->
<Armael> rather, you should chain it using >>= like any other function returning a Lwt.t
<Armael> ah, yes, I guess so
<flux> the ppx extension makes that rather easier than using >>= directly
<raphinou> Armael: what should I do with the result of Lwt_io.printf? This is a major question I have. For the moment I add lots of ignore, but I guess this is not the way to go...
<Armael> Lwt_io.printf "hello" >>= fun () ->
<flux> Lwt_io.printf ... >>= fun () -> .. etc
<Armael> Lwt_io.printf "world" >>= fun () ->
<Armael> ...
<raphinou> ok, thank you both :-)
<flux> or, with the ppx extension: let%lwt _ = Lwt_io.printf .. in - I guess not much shorted ;-)
<Armael> as pointed out by flux, it's indeed a bit nicer with the ppx extension
<raphinou> for multi lines functions defined by 'fun a ->', should I enclose it with parenthesis each time '( fun a -> ...)' or is there another way? (begin/end, ...)
tmtwd has joined #ocaml
<companion_cube> begin end works, too
* companion_cube still prefers ( )
<companion_cube> although for lwt you don't need parenthesis at all
<companion_cube> x >>= fun y-> … >>= fun z-> … does the right thing
tmtwd has quit [Ping timeout: 256 seconds]
<raphinou> ok, thanks companion_cube
<flux> actually with >>= fun .. one doesn't usually need parenthesis at all, of course there are reasons to use them at times
wu_ng has quit [Ping timeout: 268 seconds]
kakadu has joined #ocaml
<raphinou> flux, can you take a look at http://pastebin.com/d8xR1wUP ? I had to add parenthesis around the function used after >>= to get it working
<flux> raphinou, I think in isolation that works fine, but you may have some other code there that is actually involved though it isn't apparent..
<flux> well, barring the fact that the monad isn't chained through Lwt_io.printf
_andre has joined #ocaml
<Armael> doesn't Lwt_unix.close return a Lwt.t too?
<Leonidas> I use >>= and @@ like crazy to avoid parens
<flux> I was assuming that it doesn't, because Unix.close doesn't block
<flux> well, I don't think you can at least Unix.select on it..
<Leonidas> to the point where I reorder match clauses to allow me to avoid parens
<Armael> - : Lwt_unix.file_descr -> unit Lwt.t = <fun>
<Armael> it does apparently
<flux> well, in that case Lwt.return was wrong already :)
<flux> so that should be >>= fun () -> instead of ;
<flux> or the last line could be elided completely
<flux> (and the preceding ;)
Guest70 has joined #ocaml
Guest70 has quit [Client Quit]
fre has quit [Quit: WeeChat 1.4]
<raphinou> Trying to change my code, I get to this, but it doesn't work:
<raphinou> readall fd >>= fun a -> Lwt_io.printf "readall result\n %s%n%!" a >>= fun () -> Lwt_unix.close fd ;
<companion_cube> the trailing `;` is probably wrong
<companion_cube> it will expect a `unit` on the left
<raphinou> at the Lwt_io.printf I have an error: This expression has type int -> unit Lwt.t but an expression was expected of type 'a Lwt.t
<companion_cube> ah, you give one argument, but it expects two
<companion_cube> (a string then an int)
greeny___ has joined #ocaml
infinity0 has quit [Remote host closed the connection]
<raphinou> ho yes, thanks. I still need to interpret errors correctly. which in this case I still can't, even with your explanation....
<companion_cube> well
<companion_cube> the expression has type `int -> …`
<companion_cube> so it's a function, because the printf lacks an argument
<companion_cube> and it expected a `'a Lwt.t` because of >>=
infinity0 has joined #ocaml
<raphinou> ok, thanks. I missed the reasoning "so it's a function, because..."
<raphinou> but now, it's lwt_unix.close that gives me "Warning 10: this expression should have type unit."
<companion_cube> because of `;`
<companion_cube> left-hand side of `;` should be of type `unit`
<companion_cube> here you should not put a `;`
<raphinou> but then I get This function has type Lwt_unix.file_descr -> unit Lwt.t
<raphinou> It is applied to too many arguments; maybe you forgot a `;'.
f[x] has quit [Ping timeout: 258 seconds]
mfp has joined #ocaml
<companion_cube> is the error at the same place?
<companion_cube> what do you have after this piece of code?
<jnavila> raphinou: you need a let statement at the line "Lwt.bind..."
<raphinou> It is complaining about "Lwt_unix.close". Here is the complere function: http://pastebin.com/CkXRxmCg
<companion_cube> ah, well, add `>>= fun () ->` after
<companion_cube> in general, in Lwt code, replace `;` by `>>= fun () ->`
<companion_cube> same goes for the `ignore` above (you are cheating by ignoring the result)
<jnavila> Otherwise the parser thinks that the line is continuing with addtional arguments to Lwt_unix.close
infinity0 has quit [Remote host closed the connection]
<companion_cube> raphinou: sth like: https://paste.isomorphis.me/0np
<companion_cube> Lwt.bind is the same as >>= btw
<raphinou> jnavila: what do you put in the 'in section' ?
infinity0 has joined #ocaml
<raphinou> companion_cube: I will check my code but it seems the functionality is then broken: the program doesn't handle a second connection after the first one is closed
<companion_cube> ah, then you' re looking for Lwt.async, not Lwt.bind
<companion_cube> (imho Lwt.bind is mostly useless, you almost always want the infix version >>=)
<jnavila> recursive calls with lwt.bind :-/ Not sure how it is handled
<companion_cube> Lwt.async (fun () -> some_lwt_computation); some_other_computation
<companion_cube> because Lwt.bind/>>= explicitely blocks until the left argument is evaluated
<jnavila> Anyway, why would you want to recursively call accept ?
<companion_cube> jnavila: to accept several connections
<companion_cube> raphinou: https://paste.isomorphis.me/5x7
infinity0 has quit [Ping timeout: 252 seconds]
<jnavila> companion_cube: you usually use recursive call to listen, not to accept (I don't know how it works with lwt, but this does not match to libc standard)
<companion_cube> ah!
<companion_cube> maybe the name is ill-chosen.
<companion_cube> anyway : https://ocsigen.org/lwt/2.6.0/api/Lwt_io (search "establish_server") is simpler
<raphinou> well, I have 2 versions working, but the last version is not: http://pastebin.com/Amj2hPPP
greeny___ has quit [Quit: Bye.]
<raphinou> jnavila: I started with that but then translated to using Lwt :-)
<companion_cube> how do you mean "does not work"?
<companion_cube> raphinou: `;` + `ignore` is totally wrong
<companion_cube> you're not using lwt there, just fighting it
<companion_cube> have you looked at my versions?
infinity0 has joined #ocaml
<raphinou> companion_cube: the last version is not handling a second connection before the first is closed. The other 2 versions do that correctly (because the recursive call is done before the socket of the first connection is closed?)
<companion_cube> look at what I pasted -_-
<raphinou> I had looked at your vesion, but not closely enough it seems. Looking again
<companion_cube> the answer is Lwt.async
<companion_cube> NOT ignore
<companion_cube> `ignore (Lwt.fprintf fd "foo"); Lwt.close fd` is wrong, because the `close` might run before the `printf` (which will fail)
<companion_cube> it's a race condition waiting to happen
<raphinou> ok, got it.
<raphinou> but the version at https://paste.isomorphis.me/0np also has the problem of not handling the second connection before the first is closed (and doesn't use Lwt.async). Did I look at the wrong snippet?
<companion_cube> oth `Lwt.async (fun () -> foo); bar` will run `foo` and `bar` simultaneously, you indicate this way that there are no dependencies
<companion_cube> (hope it will do, I'm going to have lunch :p)
<raphinou> enjoy your lunch, and thx for the help
<raphinou> your last snippet works as needed companion_cube :-)
zirman has joined #ocaml
zirman has quit [Ping timeout: 258 seconds]
zozozo_ is now known as zozozo
zozozo has quit [Quit: WeeChat 1.5]
zozozo has joined #ocaml
Algebr``` has joined #ocaml
Algebr``` has quit [Ping timeout: 264 seconds]
fedruantine has joined #ocaml
d0nn1e has quit [Ping timeout: 250 seconds]
d0nn1e has joined #ocaml
dhil has joined #ocaml
jao has joined #ocaml
jonasen has joined #ocaml
copy` has joined #ocaml
silver has joined #ocaml
sillyotter has joined #ocaml
sillyotter has quit [Client Quit]
<companion_cube> \o/
jao has quit [Ping timeout: 258 seconds]
zirman has joined #ocaml
zirman has quit [Ping timeout: 268 seconds]
janmi has joined #ocaml
chindy has joined #ocaml
freusque has joined #ocaml
ziyourenxiang has joined #ocaml
infinity0 has quit [Ping timeout: 240 seconds]
al-damiri has joined #ocaml
infinity0 has joined #ocaml
zirman has joined #ocaml
zirman has quit [Remote host closed the connection]
zirman has joined #ocaml
zirman has quit [Changing host]
zirman has joined #ocaml
zirman has quit [Remote host closed the connection]
zirman has joined #ocaml
dhil has quit [Ping timeout: 258 seconds]
infinity0 has quit [Remote host closed the connection]
infinity0 has joined #ocaml
zirman has quit [Quit: Leaving...]
zirman has joined #ocaml
Flerex has joined #ocaml
<sspi> are there already examples of add_hook (from the new -plugins command line option)?
scitesy has quit [Read error: Connection reset by peer]
agarwal1975 has quit [Quit: agarwal1975]
freusque has quit [Read error: Connection reset by peer]
AlexDenisov has joined #ocaml
kofno has joined #ocaml
Flerex has quit [Ping timeout: 264 seconds]
AlexDeni_ has joined #ocaml
AlexDenisov has quit [Ping timeout: 250 seconds]
dhil has joined #ocaml
AlexDeni_ has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
sh0t has joined #ocaml
freusque has joined #ocaml
pierpa has joined #ocaml
agarwal1975 has joined #ocaml
larhat has quit [Quit: Leaving.]
ciniglio has quit [Remote host closed the connection]
tobiasBora has quit [Ping timeout: 268 seconds]
Algebr``` has joined #ocaml
infinity0 has quit [Remote host closed the connection]
infinity0 has joined #ocaml
larhat has joined #ocaml
_y has quit [Ping timeout: 268 seconds]
shinnya has joined #ocaml
infinity0 has quit [Remote host closed the connection]
rgrinberg has joined #ocaml
infinity0 has joined #ocaml
ski has quit [Ping timeout: 250 seconds]
freusque has quit [Read error: No route to host]
_y has joined #ocaml
yomimono has joined #ocaml
raphinou has quit [Quit: WeeChat 1.4]
_y has quit [Ping timeout: 245 seconds]
ryanartecona has joined #ocaml
Mercuria1Alchemi has quit [Ping timeout: 258 seconds]
freusque has joined #ocaml
freusque has quit [Ping timeout: 265 seconds]
chindy has quit [Remote host closed the connection]
_y has joined #ocaml
govg has joined #ocaml
rgrinberg has quit [Remote host closed the connection]
AlexDenisov has joined #ocaml
dario9 has joined #ocaml
<dario9> Hello everyone! Does anyone have any experience with OBus for interfacing with DBus-based daemons?
tobiasBora has joined #ocaml
<companion_cube> sorry, not me
nomicflux has joined #ocaml
jonasen has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
<johnelse> dario9: I've used it a little bit
<johnelse> mainly to control media players
<dario9> I'm trying to use it to contact the Bluez (Bluetooth) daemon.
<dario9> I'm getting runtime errors, however.
<dario9> And I'm not sure if it's just cause I'm a DBUS noob or if there's an actual issue with OBus...
<dario9> (Most likely the former...)
<johnelse> what errors are you getting?
<dario9> Here's one example:
<dario9> Fatal error: exception OBus_error.Unknown_method("Method \"Get\" with signature \"ss\" on interface \"org.freedesktop.DBus.Properties\" doesn't exist\n")
ciniglio has joined #ocaml
<dario9> I'm using obus-introspect to generate the client.mli and interface.mli modules.
<dario9> I've invoked it with "obus-introspect -system -rec org.bluez /org/bluez"
<dario9> I also add to tweak the generated client.mli module because OBus auto-generates a function named "class"... :-)
rgrinberg has joined #ocaml
rgrinberg has quit [Remote host closed the connection]
<johnelse> silly question, are you connecting to the system bus?
Algebr``` has quit [Ping timeout: 248 seconds]
<dario9> Not a silly question at all... :-) But yes, I'm connecting to the system bus:
<dario9> let%lwt bus = OBus_bus.system ()
<johnelse> ok cool :)
<dario9> One doubt came up, though. I'm using "org.bluez" for the peer and ["org"; "bluez"] for the proxy. I wonder if these are the correct values...
<johnelse> I think that's right for the peer, might or might not be right for the proxy
<johnelse> the proxy is generally an interface identifier, so it's often something more generic
<johnelse> if you have a GUI then d-feet is quite useful for inspecting what's available
<johnelse> although...it's timing out trying to connect to org.bluez for me
<dario9> Thanks johnelse, that was it: the proxy is actually ["org"; "bluez"; "hci0"]... :-)
<johnelse> aha :)
<dmbaturin> In ounit, is there a way to access the test context (specifically, the path, and, even more specifically, the test data dir) from outside the tests? I have a suite that loads a data file and tests multiple functions against it, and I would like to avoid loading it in every test.
<companion_cube> I think there is some setup/teardown mechanism, maybe?
ziyourenxiang has quit [Quit: Leaving]
<dmbaturin> Logically, there should be, but I can't find it. :)
<johnelse> bracket ? I'm not sure if there's a way to use that to wrap an entire suite rather than just a test though
<companion_cube> hmm, not sure
shinnya has quit [Ping timeout: 268 seconds]
infinity0 has quit [Ping timeout: 246 seconds]
<companion_cube> a possibility is to thread a context around the whole set of test
<companion_cube> let testsuite ctx = "foo" >::: (… use ctx …)
<companion_cube> and then in the main, use bracket to build the context
<companion_cube> this way things will live for the entire duration of tests, but no longe
<companion_cube> r
infinity0 has joined #ocaml
<dmbaturin> companion_cube: Wait. >::: is string -> test list -> test, I don't get how to pass anything between those tests in a list.
<companion_cube> the test list would be constructed dynamically, is what I mean
<companion_cube> let test_foo ctx () = …
tane has joined #ocaml
<companion_cube> then `let testsuite ctx = "foo" >::: […; test_foo ctx;…]`
<dmbaturin> Well... And? :)
<companion_cube> so hmm, where is the problem?
Khady_ has joined #ocaml
<dmbaturin> The context is shared indeed, but it won't help me pass the shared data I made from that context to the tests, other than through modifying a mutable reference.
Khady has quit [Ping timeout: 248 seconds]
Flerex has joined #ocaml
troydm has quit [Ping timeout: 248 seconds]
Algebr``` has joined #ocaml
gargawel has quit [Ping timeout: 248 seconds]
gargawel has joined #ocaml
troydm has joined #ocaml
dinosaure has quit [Ping timeout: 248 seconds]
<dmbaturin> Or, wait. johnelse, do you have or know of any example that uses that bracket thing?
<companion_cube> you can if tests are closures over this shared data
<johnelse> I have a few that use it, but not like you want to use it - they setup and teardown before and after each test
<dmbaturin> I see that it registers teardown functions in the context, but I don't see when one should call it, and how one is supposed to access the data is creates.
<dmbaturin> Thanks, let me see.
<johnelse> actually that's also using ounit 1 style...
<dmbaturin> On a side note, the homepage on ocamlforge that opam description refers to has links to dead darcs repos, and not to the current repository on github.
<dmbaturin> I guess I should open an issue about it... Somewhere.
<companion_cube> the migration was recent, I believe
dhil has quit [Ping timeout: 250 seconds]
_y has quit [Ping timeout: 240 seconds]
tobiasBora has quit [Ping timeout: 240 seconds]
govg has quit [Ping timeout: 250 seconds]
_y has joined #ocaml
abeaumont has joined #ocaml
larhat has quit [Quit: Leaving.]
_y has quit [Ping timeout: 260 seconds]
cdidd has quit [Remote host closed the connection]
jonasen has joined #ocaml
tobiasBora has joined #ocaml
dinosaure has joined #ocaml
dario9 has quit [Quit: Konversation terminated!]
tobiasBora has quit [Ping timeout: 268 seconds]
tobiasBora has joined #ocaml
pierpa` has joined #ocaml
RalfJ has quit [Remote host closed the connection]
RalfJ has joined #ocaml
pierpa has quit [Ping timeout: 250 seconds]
tobiasBora has quit [Ping timeout: 246 seconds]
unbalanced has joined #ocaml
jnavila has quit [Quit: It was time]
jao has joined #ocaml
cdidd has joined #ocaml
isd has joined #ocaml
isd has quit [Remote host closed the connection]
kofno has quit [Quit: Page closed]
slash^ has joined #ocaml
isd has joined #ocaml
MercurialAlchemi has quit [Ping timeout: 252 seconds]
ryanartecona has quit [Quit: ryanartecona]
isd has quit [Read error: Connection reset by peer]
infinity0 has quit [Ping timeout: 246 seconds]
isd has joined #ocaml
averell has joined #ocaml
infinity0 has joined #ocaml
FreeBirdLjj has joined #ocaml
johnelse is now known as johnel_away
AlexDenisov has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
johnel_away has quit [Quit: Lost terminal]
johnelse has joined #ocaml
zirman has quit [Remote host closed the connection]
govg has joined #ocaml
infinity0 has quit [Ping timeout: 258 seconds]
infinity0 has joined #ocaml
ryanartecona has joined #ocaml
dhil has joined #ocaml
koala_man has left #ocaml ["I'm gonna win SETI@home"]
maattdd has quit [Ping timeout: 265 seconds]
infinity0 has quit [Remote host closed the connection]
unbalanced has quit [Quit: WeeChat 1.6]
infinity0 has joined #ocaml
average has joined #ocaml
abeaumont has quit [Remote host closed the connection]
infinity0 has quit [Remote host closed the connection]
infinity0 has joined #ocaml
rand__ has joined #ocaml
jnavila has joined #ocaml
MercurialAlchemi has joined #ocaml
dhil has quit [Ping timeout: 256 seconds]
tyoverby has joined #ocaml
<tyoverby> I'm trying to use ocaml FFI, but I'm getting a weird compiler error. My code is simply "open Ctypes \n open Foreign"
<tyoverby> and the invocation is "ocamlfind ocamlc -package ctypes,ctypes.foreign hello.ml -o hello"
<tyoverby> error message: "Error: Required module `Ctypes' is unavailable"
<tyoverby> I have both Ctypes *and* Ctypes.Foreign installed, so I don't see why it says that the module is unavailable
jlongster has joined #ocaml
janmi has quit [Ping timeout: 260 seconds]
Algebr``` has quit [Remote host closed the connection]
zirman has joined #ocaml
kakadu has quit [Quit: Konversation terminated!]
infinity0 has quit [Remote host closed the connection]
infinity0 has joined #ocaml
f[x] has joined #ocaml
infinity0 has quit [Ping timeout: 265 seconds]
infinity0 has joined #ocaml
trepta7 has joined #ocaml
tyoverby has quit [Ping timeout: 260 seconds]
rossberg has quit [Ping timeout: 246 seconds]
AlexDenisov has joined #ocaml
govg has quit [Ping timeout: 250 seconds]
AltGr has quit [Ping timeout: 240 seconds]
AlexDeni_ has joined #ocaml
AlexDenisov has quit [Ping timeout: 250 seconds]
<Leonidas> works for me
<Leonidas> thought I'd post that for posterity
ryanartecona has quit [Quit: ryanartecona]
rossberg has joined #ocaml
demonimin has quit [Ping timeout: 248 seconds]
zirman has quit [Read error: Connection reset by peer]
demonimin has joined #ocaml
demonimin has quit [Changing host]
demonimin has joined #ocaml
zirman has joined #ocaml
govg has joined #ocaml
kakadu has joined #ocaml
smondet has joined #ocaml
_andre has quit [Quit: \]
jonasen has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
freusque has joined #ocaml
tane has quit [Quit: Leaving]
infinity0 has quit [Ping timeout: 268 seconds]
fraggle-boate has quit [Ping timeout: 265 seconds]
zirman has quit [Remote host closed the connection]
infinity0 has joined #ocaml
argent_smith1 has joined #ocaml
argent_smith has quit [Ping timeout: 245 seconds]
octachron has joined #ocaml
trepta7 has quit [Remote host closed the connection]
zirman has joined #ocaml
zirman has quit [Remote host closed the connection]
zirman has joined #ocaml
argent_smith has joined #ocaml
freusque has quit [Ping timeout: 260 seconds]
argent_smith1 has quit [Ping timeout: 248 seconds]
Algebr has joined #ocaml
jonasen has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
slash^ has quit [Read error: Connection reset by peer]
ryanartecona has joined #ocaml
maattdd has joined #ocaml
freusque has joined #ocaml
maattdd has quit [Ping timeout: 240 seconds]
de has joined #ocaml
de is now known as Guest81789
jlongster has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
jonasen has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
Guest81789 has quit [Quit: Page closed]
desmond has joined #ocaml
<desmond> kind peeps: I did "opam install opal" (parser lib), and can do "open Opal;;" in utup after #require "opal";;
<desmond> what is the equivalent magic in my foo.ml file (e.g. for ocamlc)? I get "Error: Unbound module Opal" at the "open Opal;;"
<companion_cube> it's an argument to ocamlc, not something you write in foo.ml
<companion_cube> ocamlfind ocamlc -package opal foo.ml
<desmond> thank you! ... does ocamlbuild do this automatically?
<smondet> desmond: yes with the `-use-ocamlfind` option (I think)
APNG has quit [Quit: Leaving]
<companion_cube> ocamlbuild does it after a bit of explanations
<companion_cube> you need to tell it which packages, and indeed add -use-ocamlfind
<desmond> thanks, that should definitely tide me over for now ... :-)
desmond has quit [Ping timeout: 260 seconds]
jlongster has joined #ocaml
Soni has joined #ocaml
maattdd has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
Soni is now known as APNG
maattdd has quit [Ping timeout: 250 seconds]
freusque has quit [Ping timeout: 250 seconds]
nomicflux has quit [Quit: nomicflux]
trepta7 has joined #ocaml
orbifx has joined #ocaml
govg has quit [Ping timeout: 265 seconds]
jnavila has quit [Remote host closed the connection]
kakadu has quit [Remote host closed the connection]
zirmann has joined #ocaml
rand__ has quit [Quit: leaving]
zirman has quit [Ping timeout: 245 seconds]
zirmann has quit [Ping timeout: 265 seconds]
desmond has joined #ocaml
FreeBirdLjj has joined #ocaml
FreeBirdLjj has quit [Ping timeout: 264 seconds]
orbifx has quit [Quit: WeeChat 1.6]
nomicflux has joined #ocaml
MercurialAlchemi has quit [Ping timeout: 240 seconds]
infinity0 has quit [Remote host closed the connection]
Flerex has quit [Quit: My iMac has gone to sleep. ZZZzzz…]
infinity0 has joined #ocaml
AlexDeni_ has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
trepta7 has quit [Remote host closed the connection]
trepta7 has joined #ocaml
argent_smith has quit [Quit: Leaving.]
octachron has quit [Quit: Leaving]
nomicflux has quit [Quit: nomicflux]
FreeBirdLjj has joined #ocaml
nomicflux has joined #ocaml
abeaumont has joined #ocaml
ryanartecona has quit [Quit: ryanartecona]
jao has quit [Disconnected by services]
jao has joined #ocaml
jao has quit [Remote host closed the connection]
jao has joined #ocaml
agarwal1975 has quit [Quit: agarwal1975]
jlongster has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
zirman has joined #ocaml
Simn has quit [Quit: Leaving]