adrien changed the topic of #ocaml to: Discussions about the OCaml programming language | http://www.ocaml.org | OCaml 4.08 release notes: https://caml.inria.fr/pub/distrib/ocaml-4.08/notes/Changes | Try OCaml in your browser: http://try.ocamlpro.com | Public channel logs at http://irclog.whitequark.org/ocaml
bitwinery has quit [Quit: Leaving]
jao has quit [Ping timeout: 245 seconds]
AtumT has quit [Quit: AtumT]
arbipher has quit [Remote host closed the connection]
kvda has joined #ocaml
ziyourenxiang has quit [Ping timeout: 245 seconds]
ziyourenxiang has joined #ocaml
ziyourenxiang has quit [Remote host closed the connection]
ziyourenxiang has joined #ocaml
kvda has quit [Quit: Textual IRC Client: www.textualapp.com]
kvda has joined #ocaml
___laika has quit [Ping timeout: 246 seconds]
___laika has joined #ocaml
count3rmeasure has joined #ocaml
mfp has quit [Ping timeout: 272 seconds]
tristero has joined #ocaml
dareme7 has joined #ocaml
count3rmeasure has quit [Remote host closed the connection]
lopex has quit [Quit: Connection closed for inactivity]
tormen has joined #ocaml
bitwinery has joined #ocaml
tormen_ has quit [Ping timeout: 272 seconds]
dareme7 has quit [Quit: dareme7]
liberiga has joined #ocaml
liberiga has quit [Ping timeout: 260 seconds]
count3rmeasure has joined #ocaml
sonologico has quit [Remote host closed the connection]
count3rmeasure has quit [Quit: Leaving]
barockobamo has joined #ocaml
zolk3ri has joined #ocaml
lobo has quit [Ping timeout: 248 seconds]
barockobamo has quit [Remote host closed the connection]
jao has joined #ocaml
Anarchos has joined #ocaml
jao has quit [Ping timeout: 244 seconds]
barockobamo has joined #ocaml
count3rmeasure has joined #ocaml
Anarchos has quit [Quit: Vision[0.10.3]: i've been blurred!]
lobo_ has joined #ocaml
lobo_ is now known as lobo
kvda has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
lopex has joined #ocaml
bitwinery has quit [Quit: Leaving]
regnat[m] has quit [Remote host closed the connection]
sepp2k has quit [Remote host closed the connection]
rgr[m] has quit [Remote host closed the connection]
otini has quit [Write error: Connection reset by peer]
aspiwack[m] has quit [Read error: Connection reset by peer]
isaachodes[m] has quit [Remote host closed the connection]
flux[m] has quit [Write error: Connection reset by peer]
smondet[m] has quit [Write error: Connection reset by peer]
hdurer[m] has quit [Remote host closed the connection]
copy` has quit [Read error: Connection reset by peer]
aecepoglu[m] has quit [Remote host closed the connection]
Virgile[m] has quit [Remote host closed the connection]
stan[m] has quit [Remote host closed the connection]
peddie has quit [Read error: Connection reset by peer]
jimt[m] has quit [Write error: Connection reset by peer]
dl3br[m] has quit [Write error: Connection reset by peer]
Haudegen[m] has quit [Write error: Connection reset by peer]
jave has quit [Ping timeout: 272 seconds]
jave has joined #ocaml
Anarchos has joined #ocaml
aspiwack[m] has joined #ocaml
mfp has joined #ocaml
dl3br[m] has joined #ocaml
flux[m] has joined #ocaml
copy` has joined #ocaml
peddie has joined #ocaml
smondet[m] has joined #ocaml
Haudegen[m] has joined #ocaml
hdurer[m] has joined #ocaml
jimt[m] has joined #ocaml
otini has joined #ocaml
aecepoglu[m] has joined #ocaml
regnat[m] has joined #ocaml
isaachodes[m] has joined #ocaml
sepp2k has joined #ocaml
stan[m] has joined #ocaml
Virgile[m] has joined #ocaml
rgr[m] has joined #ocaml
Anarchos has quit [Quit: Vision[0.10.3]: i've been blurred!]
Anarchos has joined #ocaml
count3rmeasure has quit [Ping timeout: 268 seconds]
gahr has quit [Quit: Reconnecting]
gahr has joined #ocaml
Anarchos has quit [Quit: Vision[0.10.3]: i've been blurred!]
count3rmeasure has joined #ocaml
Anarchos has joined #ocaml
dimitarvp has joined #ocaml
Anarchos has quit [Client Quit]
count3rmeasure has quit [Quit: Leaving]
AtumT has joined #ocaml
ggole has joined #ocaml
Anarchos has joined #ocaml
count3rmeasure has joined #ocaml
kakadu has quit [Ping timeout: 245 seconds]
oni-on-ion has joined #ocaml
FreeBirdLjj has joined #ocaml
Anarchos has quit [Read error: Connection reset by peer]
FreeBirdLjj has quit [Ping timeout: 258 seconds]
Netsu has joined #ocaml
<Netsu> A question abount 'type contraint' here: how can I use same type signature with same convenience and expressiveness at let binding? https://gist.github.com/Pitometsu/632154f60eecb1312e285d266ea7ecbc
<Netsu> I trying to use it like let in on type level
<ggole> constraint can only be used in some kinds of definitions iirc
<ggole> In those definitions it can indeed be used as a let-type construct
<octachron> inside type expressions, you can use `(a_very_long_type_expression as 'type_name)`
<ggole> Oh, that's clever
<ggole> I never thought of that.
<Netsu> octachron: but that is not possible to reuse that `'type_name` inside same type expression not in the type definition, is it?
<ggole> Kinda ugly though, since you have to pick a use of the variable and put the definition there
<Netsu> I thinking of reducing some code duplication. Just for convenience.
<ggole> let f : unit -> ((int * int as 'a) * 'a) = fun () -> assert false
<octachron> Netsu, you can? I sometimes write `let binary_op_transformer : ( (a long type expression as 'ty) -> 'ty ) -> ('ty -> 'ty)`
<ggole> Yeah, a type variables is in scope within a top level definition iirc
<ggole> (Unless you bind it with the 'a. forall syntax or the (type a) forms, perhaps)
<Netsu> oh, not bad. However I forced to use it at the expression at least the first time, and reuse then. Constraint kinda split it out.
<Netsu> in case of verbose type it convenient
<Netsu> it would be good to do something like `long_type_exp as 't in ...`
<Netsu> or `.` instead of `in` here (in forall way)
<octachron> This is also one of the use case for `type t := ... ` in signature
<Netsu> `type t` is explicit type, while constraints allowed for type variables only afaik. Or did I misunderstood you?
<ggole> You can use type t := ... to do substitution, more or less allowing t to be used as a variable
vicfred has quit [Quit: Leaving]
spew has joined #ocaml
jao has joined #ocaml
tane has joined #ocaml
Anarchos has joined #ocaml
rosterok has joined #ocaml
Anarchos has quit [Quit: Vision[0.10.3]: i've been blurred!]
barockobamo has quit [Remote host closed the connection]
ziyourenxiang has quit [Ping timeout: 244 seconds]
philtor has quit [Ping timeout: 248 seconds]
philtor has joined #ocaml
Serpent7776 has joined #ocaml
dimitarvp has quit [Quit: Bye]
zolk3ri has quit [Remote host closed the connection]
___laika has quit [Ping timeout: 246 seconds]
cantstanya has quit [Remote host closed the connection]
cantstanya has joined #ocaml
tane_ has joined #ocaml
amiloradovsky has joined #ocaml
tane_ has quit [Remote host closed the connection]
sapristi has joined #ocaml
___laika has joined #ocaml
<sapristi> hello
<sapristi> I have a question about Lwt
<sapristi> Is using Lwt_main.run the normal way to "unpack" a Lwt.t value ?
<Drup> no :p
<sapristi> ok, so Lwt_main.run should only be used once inside the program, right ?
<Drup> pretty much, yes
jao has quit [Remote host closed the connection]
<sapristi> ok thank you Drup
<dmbaturin> Unpacking it is against the ancient monadic law.
jao has joined #ocaml
oni-on-ion has quit [Ping timeout: 264 seconds]
jnavila has joined #ocaml
kakadu has joined #ocaml
<sapristi> well I don't know of any monadic law
<dmbaturin> sapristi: Well, since Lwt.t is a promise to eventually produce a value (or not), any 'a -> 'a Lwt.t function is effectively one way: there is no guarantee that at any time, there's actually any value there.
AtumT has quit [Ping timeout: 248 seconds]
<dmbaturin> * no guarantee that there's any value there
<sapristi> oh ok, so running Lwt_main.run on an a never fullfiling
<sapristi> oh ok, so running Lwt_main.run on an a never fulfilling promise would block the program
<sapristi> thanks
AtumT has joined #ocaml
keep_learning has quit [Quit: Ping timeout (120 seconds)]
<dmbaturin> With promises, it doesn't really matter if it's organized as a monad or not, your program is "addicted" to it in any case. :)
AtumT_ has joined #ocaml
AtumT has quit [Ping timeout: 245 seconds]
<sapristi> ok, thank you dmbaturin, I think I'm starting to grasp it
<dmbaturin> sapristi: I made this example for linking to it: https://baturin.org/code/lwt-counter-server/
oni-on-ion has joined #ocaml
gravicappa has quit [Ping timeout: 245 seconds]
AtumT has joined #ocaml
AtumT_ has quit [Ping timeout: 245 seconds]
oni-on-ion has quit [Ping timeout: 264 seconds]
sonologico has joined #ocaml
mk__ has joined #ocaml
<mk__> Why this snippet runs lwt threads concurrently?let p1 = f () inlet p2 = g () inlet%lwt () = p1 inlet%lwt () = p2 in
<mk__> let p1 = f () in let p2 = g () in let%lwt () = p1 in let%lwt () = p2 in
<mk__> But this one sequentially: let%lwt () = f () in let%lwt () = g () in
sapristi has quit [Remote host closed the connection]
jnavila has quit [Ping timeout: 246 seconds]
sapristi has joined #ocaml
<zozozo> mk__: that's actually because the let%lwt is translated into a bind, which waits for the given promise to evaluate (in your second snipet that would be "f ()"), before calling the "body" of the let
nicoo has quit [Remote host closed the connection]
nicoo has joined #ocaml
<zozozo> whereas in your first snippet, you create both lwt promises first, and then only bind the result of each one, so that before the first let%lwt, the promises can be resolved independently (at least I think, Im' not really an Lwt expert)
<mk__> zozozo: isn't p1 = f() in the first code simply a name binding for the thread? I'm assuming that let%lwt () = p1 is syntactically the same as let%lwt () = f ().
<zozozo> mk__: it's not (as far as i know), let%lwt x = y in e, is the same as "Lwt.bind y (fun x -> e)"
<zozozo> if I understand correctly (and I might not, particularly given I'm sleepy), in your first snippet you creat both promises (rather than threads), and then wait on the first one to finish, and then wait on the second one. But since when you wait for the first one, the second one has already been created, nothing prevents it from finishing before the first one
<zozozo> whereas in the second snippet, you wait for the first promise to be finished befroe creating the second one, thus obviously ensuring the second one can't finish before the first one
jnavila has joined #ocaml
<mk__> zozozo: makes sense. I guess the second snippet is actually the same as a join, isn't it?
<zozozo> I don't think so, I'd say rather sequential composition
<zozozo> Lwt has joins (Lwt.join I think ?)
Netsu has quit [Ping timeout: 260 seconds]
<zozozo> If any, your first snippet is a join (i.e. it waits for both promises to finish in any order)
sonologico has quit [Ping timeout: 244 seconds]
<mk__> Yes, Lwt has join. I mean, behaviorally, the second acts like join, specially since it runs threads concurrently
<mk__> (sorry zozozo, I'm keeping you out of bed)
<zozozo> mk__: don't worry, ^^
jnavila has quit [Remote host closed the connection]
sonologico has joined #ocaml
<Fardale> I would say the same, in the first snippet f and g are started then you way for f then for g, in the second case you start f then wait for it then g and wait for it
<Fardale> if you want a concurrent version of the second, you could use, let%lwt () = f () and () = g () in
ggole has quit [Quit: Leaving]
<mk__> Ah, sorry, I was using wrong order of the snippets, I agree with both
amiloradovsky has quit [Ping timeout: 272 seconds]
tane has quit [Quit: Leaving]
Serpent7776 has quit [Quit: leaving]
sapristi has quit [Remote host closed the connection]
ohama has quit [Ping timeout: 248 seconds]
ohama has joined #ocaml
spew has quit [Quit: going home]
___laika has quit [Quit: WeeChat 2.4]
___laika has joined #ocaml
___laika has quit [Client Quit]
kakadu has quit [Read error: Connection reset by peer]
ziyourenxiang has joined #ocaml
cantstanya has quit [Ping timeout: 260 seconds]
sonologico has quit [Ping timeout: 248 seconds]
cantstanya has joined #ocaml
sonologico has joined #ocaml
bitwinery has joined #ocaml
ygrek has joined #ocaml
keep_learning has joined #ocaml