adrien changed the topic of #ocaml to: Discussions about the OCaml programming language | http://www.ocaml.org | OCaml 4.07.1 release notes: https://caml.inria.fr/pub/distrib/ocaml-4.07/notes/Changes | Try OCaml in your browser: http://try.ocamlpro.com | Public channel logs at http://irclog.whitequark.org/ocaml | Due to ongoing spam, you must register your nickname to talk on the channel
groovy2shoes has quit [Excess Flood]
groovy2shoes has joined #ocaml
pierpal has quit [Ping timeout: 245 seconds]
pierpal has joined #ocaml
pierpal has quit [Ping timeout: 252 seconds]
keep_learning has joined #ocaml
mfp has quit [Ping timeout: 240 seconds]
caente has quit [Quit: Konversation terminated!]
Jeanne-Kamikaze has joined #ocaml
caente has joined #ocaml
tormen_ has joined #ocaml
tormen has quit [Ping timeout: 252 seconds]
malina has joined #ocaml
malina has quit [Remote host closed the connection]
caente has quit [Ping timeout: 240 seconds]
jbrown has quit [Ping timeout: 252 seconds]
JimmyRcom has quit [Ping timeout: 240 seconds]
jbrown has joined #ocaml
notnotdan has quit [Ping timeout: 252 seconds]
clog has quit [Ping timeout: 246 seconds]
clog has joined #ocaml
Jeanne-Kamikaze has quit [Remote host closed the connection]
steenuil has quit [Remote host closed the connection]
metreo has left #ocaml [#ocaml]
syme2 has joined #ocaml
syme2 has quit [Killed (Sigyn (Spam is off topic on freenode.))]
mildtaste has joined #ocaml
nsuperbus20 has joined #ocaml
nsuperbus20 has quit [Remote host closed the connection]
refp24 has joined #ocaml
refp24 has quit [Killed (Sigyn (Spam is off topic on freenode.))]
malina has joined #ocaml
malina has quit [Ping timeout: 252 seconds]
orbifx has joined #ocaml
<xvilka> is it possible to use Lwt_preemptive.detach inside of another Lwt_preemptive.detach?
<xvilka> seems like it got stuck instead
orbifx has quit [Ping timeout: 244 seconds]
Haudegen has joined #ocaml
sagotch has joined #ocaml
rotsix has joined #ocaml
<flux[m]> xvilka, but the function returns Lwt.t, why would you want that from outside the monad?
<flux[m]> maybe you can combine it with Lwt.run_in_main?
Haudegen has quit [Remote host closed the connection]
Haudegen has joined #ocaml
cods has quit [Changing host]
cods has joined #ocaml
themsay has joined #ocaml
<xvilka> flux[m]: it was used somewhere deep inside the function called from function, etc
<xvilka> anyway, already started refactoring of that piece
<xvilka> just curious now
pierpal has joined #ocaml
mfp has joined #ocaml
sagotch has quit [Ping timeout: 252 seconds]
nahra has joined #ocaml
sagotch has joined #ocaml
rotsix has quit [Remote host closed the connection]
Haudegen has quit [Remote host closed the connection]
_andre has joined #ocaml
ggole has joined #ocaml
MadcapJake has quit [Quit: MadcapJake]
themsay has quit [Ping timeout: 252 seconds]
themsay has joined #ocaml
themsay has quit [Ping timeout: 244 seconds]
caente has joined #ocaml
nullifidian has joined #ocaml
AltGr has joined #ocaml
<hannes> in the Mirage module (from the mirage package):
<hannes> string option Mirage.Key.key = string option Functoria_key.key
<hannes> We get: Error: This expression has type
<hannes> code: let keys = List.map Key.abstract [ http_port ; https_port ; admin_password ]
<hannes> but an expression was expected of type
<hannes> int option Mirage.Key.key = int option Functoria_key.key
<hannes> Type string is not compatible with type int
<hannes> http_port and https_port are of type "int option Key.t", admin_password "string option Key.t".
<hannes> How to prevent getting Key.abstract specialized to "int option Key.t"?
<hannes> we tried to specify a type for Key.abstract by having a local binding: let abstract : type a . a Key.key -> Key.t = Key.abstract in -- but this leads to the same error
<octachron> hannes, where is the error raised? At the function application or inside the list literal?
AltGr has left #ocaml [#ocaml]
<ggole> (List.map Key.abstract [http_port; https_port])::[Key.abstract admin_password], perhaps
<Armael> you cannot put them in the same list, since they have different types, right?
JimmyRcom has joined #ocaml
<hannes> octachron: at the function application (the List.map of Key.abstract applied to admin_password)
<hannes> Armael: they all have "'a key"
<Armael> ah
<hannes> we use now: [ Key.abstract http_port ; Key.abstract https_port ; Key.abstract admin_password ] as a _workaround_!
<hannes> ggole: so we came up with a similar workaround as you :D
<ggole> Right.
<ggole> It's that or an existential wrapper, I think.
<ggole> And the first is the easiest way by far.
<hannes> ggole: thanks, how would an existential wrapper look like in this case?
<xvilka> strange bug I meet today - Core is installed and latest, but can't find "Core.Command.Let_syntax" module, anyone is familiar with this issue? it is available through "utop" though.
<xvilka> s/meet/met/ ofc
<octachron> hannes, if they have all type forall 'a. 'a key, where does the string/int type comes from?
<ggole> type any_key = Any : 'a Key.key -> any_key [@@unboxed] let keys = List.map (fun (Any k) -> Key.abstract k) [Any http_port; Any https_port; Any admin_password]
kakadu has joined #ocaml
<hannes> octachron: from the definition of http_port for example:
<hannes> let http_port =
<hannes> Key.(create "http_port" Arg.(opt (some int) None doc))
<hannes> let doc = Key.Arg.info ~doc:"Listening HTTP port." ["http"] ~docv:"PORT" in
<hannes> ggole: thanks!
<ggole> Actually, that's not so bad since you don't need to mess about with polymorphic fields for this example.
<octachron> hannes, in this case all elements don't have a type 'a. 'a key, and you cannot put them together in a standard list.
caente has quit [Ping timeout: 264 seconds]
<octachron> Honestly, your workaround is the simplest solution
<hannes> ggole: it does not work with [@@unboxed] (OCaml complains that it may contain both float and non-float values)
<hannes> octachron: thanks :)
<ggole> You can remove it then, it's just a performance hack
<ggole> Hmm, I suppose that's because the compiler does not know the representation?
<ggole> Oh, hmm. merlin doesn't report that one.
<hannes> ggole: yes
* ggole wonders what the hell [@@ocaml.boxed] is
<octachron> ggole, there is a compiler flag "-unboxed-types" for setting the default to the unboxed representation, then [@@boxed] tells the compiler to use the boxed one
<ggole> I see. The compiler error suggests "You should annotate it with [@@ocaml.boxed]", but that seems unnecessary.
<ggole> Unless this code won't compile with -unboxed-types?
<ggole> Aha! Indeed it doesn't.
<ggole> Now I properly understand the warning.
<ggole> octachron: thanks.
<octachron> Indeed the warning is here to make the code future-proof in case of change of default, which could happen at the project level
JimmyRcom has quit [Ping timeout: 268 seconds]
<ggole> Maybe the warning should say as much? Or at least mention something about -unboxed-types.
waleee has joined #ocaml
<octachron> Indeed, adding more context might be nice here
JimmyRcom has joined #ocaml
Guest18004 has joined #ocaml
mildtaste has quit [Remote host closed the connection]
jao has joined #ocaml
mengu has joined #ocaml
waleee has quit [Quit: WeeChat 2.2]
pierpal has quit [Quit: Poof]
pierpal has joined #ocaml
jao has quit [Ping timeout: 244 seconds]
mengu has quit [Quit: Leaving...]
hannes has quit [Remote host closed the connection]
nullifidian has quit [Remote host closed the connection]
zv has joined #ocaml
tane has joined #ocaml
nullifidian has joined #ocaml
Guest18004 has quit [Remote host closed the connection]
sagotch has quit [Quit: Leaving.]
malina has joined #ocaml
RalfJ has quit [Ping timeout: 264 seconds]
RalfJ has joined #ocaml
barockobamo has joined #ocaml
jnavila has joined #ocaml
hannes has joined #ocaml
RalfJ has quit [Ping timeout: 252 seconds]
RalfJ has joined #ocaml
Haudegen has joined #ocaml
RalfJ has quit [Ping timeout: 252 seconds]
jnavila_ has joined #ocaml
jnavila has quit [Remote host closed the connection]
snhmib has joined #ocaml
bartholin has joined #ocaml
ggole has quit [Quit: ggole]
barockobamo has quit [Quit: Page closed]
steenuil has joined #ocaml
jnavila_ has quit [Ping timeout: 246 seconds]
snhmib has quit [Read error: Connection reset by peer]
jnavila_ has joined #ocaml
tane has quit [Quit: Leaving]
zolk3ri has joined #ocaml
RalfJ has joined #ocaml
rotsix has joined #ocaml
jao has joined #ocaml
orbifx has joined #ocaml
jao has quit [Ping timeout: 240 seconds]
jao has joined #ocaml
sagax has joined #ocaml
Haudegen has quit [Read error: Connection reset by peer]
malina has quit [Ping timeout: 252 seconds]
rotsix has quit [Remote host closed the connection]
jnavila_ has quit [Remote host closed the connection]
themsay has joined #ocaml
themsay has quit [Ping timeout: 244 seconds]
themsay has joined #ocaml
malina has joined #ocaml
jao has quit [Ping timeout: 240 seconds]
themsay has quit [Read error: Connection reset by peer]
themsay has joined #ocaml
bartholin has quit [Ping timeout: 244 seconds]
zv has quit [Ping timeout: 252 seconds]
themsay has quit [Ping timeout: 268 seconds]
themsay has joined #ocaml
Guest46032 has joined #ocaml
Guest46032 has quit [Remote host closed the connection]
zolk3ri has quit [Quit: Lost terminal]
zv has joined #ocaml
carlosdagos has quit [Quit: Connection closed for inactivity]
loli has quit [Quit: WeeChat 2.3]
Rucikir has joined #ocaml
<Rucikir> Hello, the ocamlbuild package is behind one version on opam, could you consider pushing the new version?
<Armael> Rucikir: I just opened an issue on the bugtracker https://github.com/ocaml/ocamlbuild/issues/291
<Armael> hopefully this will motivate Gabriel to make a new release :)
<Armael> err, opam package
loli has joined #ocaml
orbifx has quit [Ping timeout: 240 seconds]
kakadu has quit [Remote host closed the connection]
jbrown has quit [Ping timeout: 252 seconds]
malina has quit [Remote host closed the connection]
jbrown has joined #ocaml