adrien changed the topic of #ocaml to: Discussions about the OCaml programming language | http://www.ocaml.org | Upcoming OCaml MOOC: https://huit.re/ocamlmooc | OCaml 4.03.0 release notes: http://ocaml.org/releases/4.03.html | Try OCaml in your browser: http://try.ocamlpro.com | Public channel logs at http://irclog.whitequark.org/ocaml
silver_ has quit [Quit: rakede]
bruce_r has joined #ocaml
shinnya has quit [Ping timeout: 276 seconds]
kamog has joined #ocaml
mcc has joined #ocaml
<kamog> Why is the second tail-recursive version 3 times slower than the first one with a for-loop? https://gist.github.com/anonymous/c3e9700e439c60dd7fda0990137aa4f1
<pierpa> I don't know, but I'd look at the generated asm if I wanted to know
<kamog> ocamlopt's generated assembly is too overwhelming for my basic skills!
<pierpa> hmmm, then wait for some expert to chime in :)
<pierpa> or try with a simpler loop, with only one integer op
<kamog> hmm, and two float accumulators as references?
<pierpa> try it
<pierpa> in theory I think it should be slower, but in theory your versions should be the same, but they aren't, so the only way to know is trying.
<pierpa> *your two versions
<kamog> well, it's strange. That version with tail-recursive only integer arguments is the fastest.
<pierpa> hmmm
<pierpa> maybe is related to float arrays, which have a specialized representation
<kamog> it's actually faster than everything else
<pierpa> could be that in the TR version accumulators are boxed and unboxed at every cycle?
<kamog> including fortran
<kamog> maybe, but I thought it would have unboxed floating point arguments for functions.
<pierpa> I don't know, actually
<pierpa> "Function arguments are always boxed. (Unless the function is inlined, of course.)"
<kamog> but an internal function is a good candidate for inlining?
<pierpa> yes, that's it. It is explicitly mentioned here: http://caml.inria.fr/pub/old_caml_site/ocaml/numerical.html
<Drup> kamog: try with flambda and -O3
<pierpa> around half-page, where it says "iterate with for and while loops instead of recursive functions. "
<kamog> oh, thanks, now I see
<Drup> pierpa: just want to point out that this page is old.
<pierpa> I was just going to ask
<pierpa> if the page was still current
<Drup> (I mean, it's even written in the url)
<pierpa> yeah
<Drup> apparently, it's 2002
<pierpa> but what kamog found out experimentally seems to agree with what the page says?
<Drup> Yeah, except tail rec functions are turned into basically for loops. I don't remember if the old inliner can unbox floats there, I wouldn't be surprised if flambda can
<Drup> (well, flambda doesn't unbox, really, but still)
<kamog> Drup: hmm -O3 -unbux-closures doesn't seem to change anything (4.03.0)
<Drup> you need the switch 4.03.0+flambda
<Drup> not regular 4.03.0
<kamog> probably, it has flambda enabled already (I haven't compiled it, though) but the compiler has flambda related verbosity flags
pierpa has quit [Ping timeout: 276 seconds]
kv has joined #ocaml
<Heasummn> How does Batteries BatSet handle creation from enums or lists?
<Heasummn> nvm
FreeBirdLjj has joined #ocaml
cross has quit [Ping timeout: 276 seconds]
f[x] has quit [Ping timeout: 265 seconds]
cross has joined #ocaml
Heasummn has quit [Quit: Leaving]
bitbckt has quit [Ping timeout: 250 seconds]
bitbckt has joined #ocaml
j0sh has quit [Ping timeout: 260 seconds]
j0sh has joined #ocaml
nicholasf has quit [Remote host closed the connection]
nicholasf has joined #ocaml
MercurialAlchemi has joined #ocaml
sdothum has quit [Quit: ZNC - 1.6.0 - http://znc.in]
tmtwd has joined #ocaml
kushal has quit [Quit: Leaving]
struk|desk has joined #ocaml
kamog has quit [Remote host closed the connection]
MercurialAlchemi has quit [Ping timeout: 244 seconds]
ggole has joined #ocaml
bruce_r has quit [Ping timeout: 258 seconds]
mcc has quit [Quit: Connection closed for inactivity]
MercurialAlchemi has joined #ocaml
Xizor has joined #ocaml
copy` has quit [Quit: Connection closed for inactivity]
adelbertc has joined #ocaml
ANTI-torture has joined #ocaml
Simn has joined #ocaml
clockish has quit [Ping timeout: 264 seconds]
clockish has joined #ocaml
hackwaly has joined #ocaml
ANTI-torture has quit [Quit: http://www.kiwiirc.com/ - A hand crafted IRC client]
<hackwaly> The Num module doc say "Numbers (type num) are arbitrary-precision rational numbers, plus the special elements 1/0 (infinity) and 0/0 (undefined).". But I don't find how to build num 1/0 or 0/0.
<hackwaly> I tried this code `print_endline (string_of_num ((num_of_int 1) // (num_of_int 0)))`. When run it errors `Fatal error: exception Failure("create_ratio infinite or undefined rational number"`
hackwaly has quit [Client Quit]
hackwaly has joined #ocaml
<hackwaly> I found the answer http://caml.inria.fr/mantis/view.php?id=6290
tmtwd has quit [Ping timeout: 240 seconds]
nicholasf has quit []
hackwaly has quit [Quit: Page closed]
tmtwd has joined #ocaml
zpe has joined #ocaml
zpe has quit [Remote host closed the connection]
Rome has quit [Ping timeout: 264 seconds]
f[x] has joined #ocaml
infinity0_ has joined #ocaml
infinity0_ has quit [Read error: Connection reset by peer]
infinity0 has quit [Ping timeout: 258 seconds]
infinity0 has joined #ocaml
Rome has joined #ocaml
Xizor has quit [Read error: Connection reset by peer]
infinity0 has quit [Remote host closed the connection]
infinity0 has joined #ocaml
infinity0 has quit [Remote host closed the connection]
infinity0 has joined #ocaml
tmtwd has quit [Ping timeout: 265 seconds]
_whitelogger has joined #ocaml
_andre has joined #ocaml
xvw_ has joined #ocaml
GemmaG has quit [Quit: http://www.kiwiirc.com/ - A hand crafted IRC client]
GemmaG has joined #ocaml
ontologiae has joined #ocaml
ia0 has quit [Quit: reboot]
ia0 has joined #ocaml
ghtdak has left #ocaml ["WeeChat 1.3"]
ontologiae has quit [Ping timeout: 260 seconds]
_whitelogger has joined #ocaml
d0nn1e has quit [Ping timeout: 240 seconds]
d0nn1e has joined #ocaml
thizanne has joined #ocaml
thizanne_ has quit [Ping timeout: 276 seconds]
kushal has quit [Quit: Leaving]
jwatzman|work has quit [Quit: jwatzman|work]
thizanne has quit [Ping timeout: 244 seconds]
rgrinberg has joined #ocaml
flux has quit [Ping timeout: 264 seconds]
<sspi> out of curiosity where do basic type keywords (string, int, etc) from OCaml come from - when I look at the lexer I don't see these keywords defined
<pierpa> these are not keywords, are type names
<pierpa> so, the lexer need not have special knowledge about them
<ggole> They're done there
<sspi> @pierpa: thanks for correcting me @ggole: thanks for the link!
ryan_mckenize has joined #ocaml
<haesbaert> is there a way to refer to an infix operator ?
<haesbaert> something like Int32.one Int32.(+) Int32.one
GemmaG has quit [Quit: http://www.kiwiirc.com/ - A hand crafted IRC client]
copy` has joined #ocaml
jbrown has quit [Quit: Leaving]
<zozozo> haesbaert: Int32.(one + one)
<haesbaert> I see, thanks
GemmaG has joined #ocaml
GemmaG has quit [Client Quit]
GemmaG has joined #ocaml
GemmaG has quit [Client Quit]
rpip has quit [Ping timeout: 250 seconds]
GemmaG has joined #ocaml
rpip has joined #ocaml
GemmaG has quit [Client Quit]
flux has joined #ocaml
<mg-> I have a file, somefile.ml, that starts with "open Someotherfile". How can i #use "somefile.ml" in utop? I get the error: Unbound module Someotherfile"
ryan_mckenize has quit [Remote host closed the connection]
ryansiddle__ has joined #ocaml
<ggole> Load the other module first
<ggole> Or #load_rec instead of #use
ryansiddle__ has left #ocaml [#ocaml]
<mg-> ggole: hm, even if I #use "someotherfile.ml" before #use "somefile.ml" I get the same problem
<mg-> Or did you mean use #load on bytecode?
<lyxia> #mod_use "someotherfile.ml"
<ggole> Yeah, either of those
<ggole> #use does not make a module available, it's like pasting that source file
<mg-> aha, thanks!
GemmaG has joined #ocaml
GemmaG has quit [Client Quit]
GemmaG has joined #ocaml
mg- has quit [Ping timeout: 250 seconds]
GemmaG has quit [Client Quit]
kushal has joined #ocaml
<tormen> nice :) ... goes straight into /learn/it/ocaml/utop.load_vs_use_vs_mod_use_load_rec :)
shinnya has joined #ocaml
<tormen> I have a Functor taking an input module M with a Variant type t. In the functor I say "type t = M.t".
<tormen> module Foo = Make ( M );; Foo.Variant --> Error: Unbound constructor :(
<tormen> but in Make I said that Foo should have a type t = the variant_type...
GemmaG has joined #ocaml
<tormen> Can one access something like the runtime variable __MODULE__ of another module ? e.g. Some_Module.__MODULE__ ??
GemmaG has quit [Client Quit]
<mrvn> yes
<mrvn> anything mentioned in the mli file can be accessed
<mrvn> or everything if no mli exists
<def`> __MODULE__ is not a variable though, so it cannot
<mrvn> # module M = struct let __MODULE__ = "M" end;;
<mrvn> module M : sig val __MODULE__ : string end
<mrvn> # M.__MODULE__;;
<mrvn> - : string = "M"
<mrvn> def`: works fine
<def`> lol
<mrvn> I guess one could add some ppx magic to automatically add a variable __MODULE__
<def`> tormen: you have to bind it to a variable explicitly
<def`> let __MODULE__ = __MODULE__;;
<mrvn> *ugh*? There is a __MODULE__ variable predefined?
<def`> (and __MODULE__ actually refers to the unit name or top-level module)
<mrvn> looks like __MODULE__ actuzall
<mrvn> actually is __FILE__ from C
<def`> mrvn: yes
<def`> well no
<def`> it really is the unit name
<mrvn> module M = struct module N = struct let __MODULE__ = __MODULE__ end end;;
<def`> __FILE__ also exists
<mrvn> # M.N.__MODULE__;;
<mrvn> - : string = "//toplevel//"
<mrvn> I figures M.__MODULE__ should be "//toplevel//.M" and M.N.__MODULE__ "//toplevel//.M.N" or so
<def`> unit name >_<
<mrvn> So something like this: module M = struct let __MODULE__ = __MODULE__ ^ ".M" end;;
<mrvn> tormen: is that what you wanted?
<mrvn> def`: is __FILE__ ever different from __MODULE__?
<def`> mrvn: yes, __MODULE__ is __FILE__ capitalized and without extension
<mrvn> ahh, so just toplevel has them the same.
<def`> it actually corresponds to the mapping between ML namespace and file system
<mrvn> when you build an foo.mly file does it set __FILE__ to foo.mly?
<def`> but I strongly disapprove that __MODULE__ is just that and not the full path as in your example
kushal has quit [Ping timeout: 260 seconds]
<mrvn> def`: yeah, __MODULE__ should be the current module, not the unit. Call that __UNIT__
<def`> yes for mly
<mrvn> nice.
<def`> it uses the filename from the parstree location
yegods has joined #ocaml
<def`> which is computed by the lexer which understands the line control directives
malc_ has joined #ocaml
<mrvn> 0006857: __MODULE__ doesn't give the current module with -o
MercurialAlchemi has quit [Ping timeout: 260 seconds]
yegods has quit [Client Quit]
GemmaG has joined #ocaml
<tormen> mrvn: Thanks ! You answered my question. I'll put let name = __MODULE__ in my Functor input module :)
Trou has left #ocaml [#ocaml]
<tormen> Otherwise about my Variant question, I perpared this little demo :) https://paste.debian.net/hidden/f043e589/
GemmaG has quit [Client Quit]
<tormen> The question: WHY does let b = My_M.Foo (* yield a "Error: Unbound constructor My_M.Foo" *) ? :(
<tormen> ... My_M is supposed to share the type t with M ... so My_M shoul also know Foo, no ?
<mrvn> tormen: because you didn't pass the type through the functor.
kv has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
<def`> tormen: only the type, not the constructors
<tormen> hmm. but I said type t = M.t ...
<tormen> so why do I need to pass the type ?
<mrvn> tormen: tormen module My_M = Make_M ( M with t = M.t = | Foo | Bar )
<def`> not correct syntax :)
<mrvn> tormen: the functor normaly creates a new internal type for each invokation. You have to use "with" to tell it to pass the type through. And the syntax sucks.
yegods has joined #ocaml
<def`> tormen: you cannot achieve what you want
Algebr` has quit [Remote host closed the connection]
<tormen> mrvn: I'll try ;)
Algebr` has joined #ocaml
<mrvn> def`: It kind of sucks that the functor can not say wether it passes the type through or not.
soupault has joined #ocaml
<def`> the functor can export the equality between type constructors, that's all
<def`> (exporting value constructor would be very ambiguous)
<tormen> mrvn: I have this syntax already in my pastebin ... I just wanted to know why I need that and why a type t = M.t is not enough ... I guess it's like "include" versus "open"...
<malc_> def`: include M wouldn't work you are implying?
<def`> malc_: yes
<tormen> by passing the in the type it really gets "copied" into the Functor output module ?
<def`> malc_: you would be including the parameter M, not the functor argument
al-damiri has joined #ocaml
<def`> remember that M is coerced when being passed to the functor, it is not the same module
<malc_> def`: so signature would have to have the full t definition right?
<def`> malc_: yep
<malc_> def`: thanks
Algebr` has quit [Ping timeout: 276 seconds]
yegods has quit []
jwatzman|work has joined #ocaml
<tormen> def`: Hmm. Why ?
<def`> why what ?
<tormen> Why I can't achieve My_M.Foo ?
<tormen> What is ambigous about that ?
<def`> imagine the functor already has a value constructor named Foo.
<tormen> I guess I am asking super stupid questions... I just would like to somehow understand why it's not possible (to not try something impossible the next time around ;))
<def`> What would My_M.Foo means?
<mrvn> def`: whatever the functor says it means
<tormen> hmmm :)
<def`> The signature of My_M is exactly that of the functor codomain with the path referring the argument being substituted.
yegods has joined #ocaml
<mrvn> tormen: think of it this way: You specify the module signature for the functor and that does not include the "Foo". That means the Foo gets hidden.
<tormen> yes I would think the same. Either the Functor has a Foo that this is taken, or it gets a Foo from type t=M.t ... no ? ;)
<tormen> mrvn: hmmm
<def`> try to type Make_M
<mrvn> def`: I'm missing a sig type t = [[%constructors]] end
SpiceGuid has joined #ocaml
<def`> Make_M : functor (M : sig val name : string type t end) -> sig type t = M.t val name : string end
<def`> (I removed the part generated by yojson ppx)
<def`> which gives My_M : sig type t = M.t val name : string end;;
<tormen> ...okey
<tormen> Thanks a lot you two I thiiiink I slowly get it ;)
<def`> mrvn: the problem with that is that either it is not modular, or you would need a much more expressive module system
<def`> tormen: yes, type manifests are a bit confusing.
<def`> You don't "copy" or "export" a type, you export an equality between two paths
<tormen> def`: ok
<tormen> and in my new pastebin the problem is that in the output signature of the functor it only says type t but does NOT mention the Variants... as mrvn pointed out, right ?
<def`> "t" can be used in any place where "M.t" is used. It has nothing to do with the value constructors (or record fields, etc).
<tormen> ok
<tormen> ok
<tormen> Coooooooooool.
<tormen> I will copy + paste this straight into /learn/it/ocaml/functor_type_inheritance :))
<def`> alternatively, if you write module type M_type = sig val name : string type t = Foo deriving (Yojson) end
<def`> then you will be able to refer to Foo in Make_M
<def`> type t = M.t = Foo
<def`> but then your functor is much less general :)
<def`> (next to useless :P)
silver has quit [Read error: Connection reset by peer]
<tormen> yep ... explicitly adding the Foo .. yes ;) Thanks again ! !!! A looooooooooooooot :))))))
<def`> you are welcome
* tormen feels humbled :)
silver has joined #ocaml
<mrvn> def`: so what
<mrvn> 's the right syntax for ... with type t = M.t = Foo?
yegods has quit []
<def`> mrvn: there is none
<def`> if I remember well, the module system doesn't know about signature substitution anyway, it's just syntax sugar
<def`> so it would be a bit less code to write, but it would still be impossible to abstract that
<def`> (e.g. it helps writing shorter code, but not generic code / functors)
<def`> not e.g., pfff, in other words ....
<tormen> ;)
govg has joined #ocaml
SpiceGuid has quit [Quit: ChatZilla 0.9.92 [SeaMonkey 2.40/20160120202951]]
richi235 has quit [Quit: No Ping reply in 180 seconds.]
richi235 has joined #ocaml
agarwal1975 has joined #ocaml
APNG has quit [Ping timeout: 276 seconds]
mal`` has quit [Quit: Leaving]
k1000 has quit [Ping timeout: 265 seconds]
k1000 has joined #ocaml
MercurialAlchemi has joined #ocaml
copy` has quit [Quit: Connection closed for inactivity]
Distortion has quit [Quit: http://www.kiwiirc.com/ - A hand crafted IRC client]
bruce_r has joined #ocaml
mal`` has joined #ocaml
kv has joined #ocaml
xvw_ has quit [Quit: xvw_]
kdas__ has joined #ocaml
kdas__ has quit [Quit: Leaving]
kdas__ has joined #ocaml
Soni has joined #ocaml
nicoo has quit [Ping timeout: 260 seconds]
Soni is now known as APNG
APNG has quit [Remote host closed the connection]
APNG has joined #ocaml
jyc has quit [Ping timeout: 250 seconds]
jyc has joined #ocaml
nicoo has joined #ocaml
FreeBirdLjj has joined #ocaml
ebird has joined #ocaml
bitbckt has quit [Ping timeout: 250 seconds]
mcspud has quit [Ping timeout: 250 seconds]
bitbckt has joined #ocaml
mcspud has joined #ocaml
picolino has quit [Ping timeout: 240 seconds]
larhat has quit [Quit: Leaving.]
picolino has joined #ocaml
kv has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
APNG has quit [Changing host]
APNG has joined #ocaml
Soni has joined #ocaml
Soni has quit [Changing host]
Soni has joined #ocaml
Soni has quit [Remote host closed the connection]
APNG has quit [Quit: Leaving]
Soni has joined #ocaml
thizanne has joined #ocaml
Soni is now known as APNG
Simn has quit [Quit: Leaving]
Simn has joined #ocaml
kdas__ is now known as kushal
kushal has quit [Changing host]
kushal has joined #ocaml
kv has joined #ocaml
kv has quit [Client Quit]
thizanne has quit [Ping timeout: 240 seconds]
thizanne has joined #ocaml
<j0sh> companion_cube: i'm trying to merge your lwt-ppx patch for sqlexpr onto master... nearly done, just have a type error that i can't figure out: https://gist.github.com/j0sh/ba984e6baba6188237c0cb12555b9f84
<j0sh> i'm not sure where the type for `fold` is being constained to `unit` -- i think thats the issue here?
<j0sh> (accumulator type)
<j0sh> ahhh after an hour of staring at it, figured it out right after i asked for help ;)
jwatzman|work has quit [Quit: jwatzman|work]
yunxing has quit [Read error: Connection reset by peer]
yunxing has joined #ocaml
copy` has joined #ocaml
kushal has quit [Quit: Leaving]
FreeBirdLjj has quit [Ping timeout: 252 seconds]
FreeBirdLjj has joined #ocaml
<mfp> j0sh: is that patch what it sounds like (switching from using lwt.syntax to lwt.ppx)?
<mfp> i.e. no externally visible changes? Because I just got not 1 but 3 releases out the door (0.6.1 maintenance branch, 0.7.0 with a bug in the PPX build, 0.7.1. that fixes it)...
<j0sh> mfp: yeah, switching to lwt.ppx internally -- shouldn't be an external/api change but could avoid a camlp4 build-time dependency
<mfp> How stable have PPX extensions been in your experience wrt. compiler changes? I already had to use a preprocessor to get ppx_sqlexpr to build on both 4.02 and 4.03 :-/
<mfp> OTOH in this case it's Lwt's problem :-)
<Drup> mfp: ppx_tools does a bit of work for you, wrt to ocaml versions
<j0sh> yeah the parsetree tends to churn a bit between compilers
<j0sh> iirc that's one reason we have a 4.02.3 minimum for sqlexpr-ppx, something changed with an earlier version (or we introduced a dependency that didnt support earlier compilers)
<mfp> was it ppx_tools? I seem to remember that from a PR or issue discussion
<mfp> but I failed to find it when I searched github
<j0sh> ppx_core, it looks like... https://github.com/mfp/ocaml-sqlexpr/pull/14
<j0sh> but that hasnt been merged
<j0sh> so i guess things should still work on 4.02.2
<mfp> ah right, that PR... I hesitated to merge it, but didn't want to delay the PPX-enabled release even more
<mfp> since code hoisting was not that important performance-wise I just let it aside for the time being
<j0sh> yeah, the PR isn't really necessary for anything
<j0sh> and its still technically incomplete
<mfp> also would need a bit of rebasing after the cppo business to get 4.02 + 4.03 compat
<j0sh> had an issue with top-level bindings i couldnt figure out
<j0sh> yeah, had to do some conflict resolution in git when bringing companion_cube's lwt-ppx up to date
<mfp> btw there isn't anything I can do about https://travis-ci.org/ocaml/opam-repository/jobs/155316503#L1414 (besides patching (ocaml-)sqlite3's opam I'm not exactly sure how), is there? That build failure is likely to delay merging into the OPAM repos.
<mfp> I left a couple comments on the PRs, but that red cross is likely to keep repos maintainers away from the PR :-/
<j0sh> interesting, i guess i updated to sqlite-4.0.5 at some point, don't remember what other external dep it brought in (maybe i already had it?)
kv has joined #ocaml
govg has quit [Quit: leaving]
<mfp> the thing that got me scratching my head is that sqlite3.4.0.5 did pass CI against Xcode https://travis-ci.org/ocaml/opam-repository/builds/137567853
kv has quit [Ping timeout: 244 seconds]
<Drup> hum, how do you guys use ppx's lwt ?
<mfp> but it was building against 4.02, and my CI is against 4.03, so something else must have changed in the env
<mfp> Drup: (Lwt's PPX ? ;) just regular user-level let%lwt and try%lwt stuff, what do you mean?
<Drup> yeah
<Drup> ok, fine
<Drup> (I though you were emiting lwt's ppx stuff inside your own ppx)
<mfp> that... sounds like trouble. sqlexpr's syntax extensions mostly expand SQL statements/(select) expressions into structures representing them; the monadic code that operates on them lies in the lib (that is what uses lwt.syntax)
<Drup> it's not trouble, but there is a good and a bad way to do it, so I was wondering if you were doing it, and how
<Drup> you don't, it's fine :D
<Drup> (the good way is to call Ppx_lwt's mapper directly)
ebird has quit [Remote host closed the connection]
kakadu has joined #ocaml
thizanne has quit [Ping timeout: 276 seconds]
Algebr` has joined #ocaml
jyc has quit [Ping timeout: 250 seconds]
jyc has joined #ocaml
thizanne has joined #ocaml
Orion3k has joined #ocaml
Algebr` has quit [Read error: Connection reset by peer]
Algebr` has joined #ocaml
soupault has quit [Remote host closed the connection]
f[x] has joined #ocaml
ontologiae has joined #ocaml
zpe has quit [Remote host closed the connection]
thizanne has quit [Read error: Connection reset by peer]
thizanne has joined #ocaml
<copy`> I can't type a "0" in ocp-browser
<copy`> Could someone try, so I know my terminal isn't borked?
<Algebr`> trying
<Algebr`> ha, no you can't, but I don't think 0 is a valid beginning of an identifier right
<copy`> I needed it for X509
<copy`> Funny bug
<Algebr`> get the source, find where its not allowing the range, probably something like '1'..'9' and, opam pin it locally
<Algebr`> ask Drup
<copy`> Yep, I'm looking, thanks for checking
Algebr` has quit [Read error: Connection reset by peer]
bruce_r has quit [Ping timeout: 260 seconds]
malc_` has joined #ocaml
<Drup> huh
<Drup> It looks like I did something remarquably stupid, indeed
malc_ has quit [Ping timeout: 244 seconds]
<Drup> I'm amazed nobody noticed before now
Algebr` has joined #ocaml
<copy`> Pull request sent
kakadu has quit []
kakadu has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
<Algebr`> got disconnected, come back and see Pull request sent. yay.
Xizor has joined #ocaml
thizanne has quit [Ping timeout: 276 seconds]
thizanne has joined #ocaml
jbrown has joined #ocaml
bruce_r has joined #ocaml
bruce_r has quit [Ping timeout: 258 seconds]
yunxing has quit [Ping timeout: 264 seconds]
mrallen1 has quit [Ping timeout: 264 seconds]
kakadu has quit []
rfv has quit [Ping timeout: 250 seconds]
oldmanistan_ has quit [Ping timeout: 264 seconds]
kakadu has joined #ocaml
NhanH has quit [Ping timeout: 250 seconds]
Sorella has quit [Ping timeout: 260 seconds]
msch has quit [Ping timeout: 250 seconds]
thizanne has quit [Ping timeout: 264 seconds]
thizanne has joined #ocaml
jmct has quit [Ping timeout: 264 seconds]
mbrock has quit [Ping timeout: 260 seconds]
Algebr` has quit [Ping timeout: 258 seconds]
jkni has quit [Ping timeout: 258 seconds]
jbrown has quit [Ping timeout: 244 seconds]
_andre has quit [Quit: leaving]
MercurialAlchemi has quit [Ping timeout: 244 seconds]
Algebr` has joined #ocaml
NhanH has joined #ocaml
oldmanistan_ has joined #ocaml
Algebr` has quit [Ping timeout: 240 seconds]
Xizor has quit [Read error: Connection reset by peer]
thizanne has quit [Ping timeout: 240 seconds]
msch has joined #ocaml
mg has joined #ocaml
rfv has joined #ocaml
<mg> hey, I need some noob-help. Trying to include lwt in my project (only external dependency so far) but I can't seem to find it. "ocamlfind list" says that lwt is installed, what more do I need?
<mg> tried both "ocamlbuild -r -use-ocamlfind -pkgs 'lwt' 'src/main.native'" and using it from utop
<kakadu> you can try to add `true: package(lwt)` into _tags file
mrallen1 has joined #ocaml
<mg> no dice ):
<kakadu> What error do you have and for which piece of code?
ggole has quit []
Sorella has joined #ocaml
<mg> Error: No implementations provided for the following modules:
<mg> Lwt_main referenced from src/main.cmx
<mg> Lwt_io referenced from src/main.cmx
<kakadu> can you give us _build/_log?
<kakadu> IT's weird issue
<kakadu> it seems that it have found lwt while creating .cmx from .ml but it can't find lwt when tries .cmx -> .native
<kakadu> usually happens when we specify `package(lwt)` for <*.ml> and forget to specify for <*.native>
<mg> fwiw, the src/main.ml file is a very simple "let () = Lwt_main.run (Lwt_io.printl "Hello world")"
<smondet_> mg: Lwt_main and Lwt_io are part of the `lwt.unix` pacakge
<mg> aha
<mg> thanks smondet_!
smondet_ is now known as smondet
<mg> adding this: -pkgs 'lwt,lwt.unix' to ocamlbuild worked
<mg> even without _tags file
<smondet> Cool!
<mg> smondet: how can I load it in utop then?
mbrock has joined #ocaml
<kakadu> #require "lwt.unix";;
<smondet> I think the same `#require "lwt.unix";;`
<mg> sweet, thanks guys
jkni has joined #ocaml
thizanne has joined #ocaml
Algebr` has joined #ocaml
jmct has joined #ocaml
Algebr` has quit [Ping timeout: 276 seconds]
yunxing has joined #ocaml
soupault has joined #ocaml
soupault has quit [Remote host closed the connection]
soupault has joined #ocaml
kakadu has quit [Remote host closed the connection]
rwmjones is now known as rwmjones_hols
Algebr` has joined #ocaml
Algebr` has quit [Ping timeout: 244 seconds]
Rome has quit [Changing host]
Rome has joined #ocaml
jbrown has joined #ocaml
Algebr` has joined #ocaml
Algebr` has quit [Ping timeout: 255 seconds]
Heasummn has joined #ocaml
nicoo has quit [Remote host closed the connection]
ontologiae has quit [Ping timeout: 244 seconds]
nicoo has joined #ocaml
hcarty has joined #ocaml
xvw_ has joined #ocaml
thizanne has quit [Remote host closed the connection]
thizanne has joined #ocaml
xvw_ has quit [Client Quit]
Algebr` has joined #ocaml
Algebr` has quit [Ping timeout: 250 seconds]
<hcarty> How can I tell ocamlbuild that some code depends on a static file? I'm using ppx_blob and want to tell ocamlbuild that it needs to copy/'ln -s' the included file
<hcarty> Using dep/deps in myocamlbuild.ml doesn't work because it doesn't know how to build/handle a "foo.txt" file
agarwal1975 has quit [Ping timeout: 276 seconds]
Simn has quit [Quit: Leaving]
mrallen1 has quit [Ping timeout: 255 seconds]
msch has quit [Ping timeout: 250 seconds]
yunxing has quit [Read error: Connection reset by peer]
oldmanistan_ has quit [Read error: Connection reset by peer]
NhanH has quit [Read error: Connection reset by peer]
mbrock has quit [Ping timeout: 260 seconds]
jkni has quit [Read error: Connection reset by peer]
Sorella has quit [Ping timeout: 264 seconds]
rfv has quit [Ping timeout: 250 seconds]
jmct has quit [Read error: Connection reset by peer]
jbrown has quit [Ping timeout: 240 seconds]
<hcarty> copy`: Thanks! I'll give it a try
jbrown has joined #ocaml
<hcarty> copy`: Beautiful, works quite nicely
<hcarty> copy`: Thanks again@
pyon has quit [Quit: fix config]
msch has joined #ocaml
yunxing has joined #ocaml
thizanne has quit [Ping timeout: 255 seconds]
<copy`> Sure, no worries
jbrown has quit [Ping timeout: 255 seconds]
oldmanistan_ has joined #ocaml
pyon has joined #ocaml
rfv has joined #ocaml
Algebr` has joined #ocaml
mbrock has joined #ocaml
Algebr` has quit [Ping timeout: 276 seconds]
mrallen1 has joined #ocaml
jkni has joined #ocaml
oldmanistan_ has quit [Remote host closed the connection]
yunxing has quit [Remote host closed the connection]
msch has quit [Remote host closed the connection]
rfv has quit [Remote host closed the connection]
mbrock has quit [Write error: Connection reset by peer]
mrallen1 has quit [Remote host closed the connection]
jkni has quit [Remote host closed the connection]
M-ErkkiSeppl has quit [Ping timeout: 276 seconds]
M-ErkkiSeppl has joined #ocaml