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
yegods has quit [Remote host closed the connection]
yegods has joined #ocaml
tmtwd has joined #ocaml
bruce_r has joined #ocaml
kakadu has quit [Remote host closed the connection]
anti-Mossad has joined #ocaml
anti-Mossad has quit [Quit: http://www.kiwiirc.com/ - A hand crafted IRC client]
Ravana has joined #ocaml
Stalkr^ has joined #ocaml
Stalkr_ has quit [Ping timeout: 244 seconds]
bruce_r has quit [Ping timeout: 265 seconds]
bruce_r has joined #ocaml
bruce_r has quit [Ping timeout: 260 seconds]
pierpa has quit [Ping timeout: 276 seconds]
minn has quit [Ping timeout: 250 seconds]
manizzle has joined #ocaml
minn has joined #ocaml
ldopa has quit [Quit:]
ldopa has joined #ocaml
Stalkr^ has quit [Quit: Leaving...]
ygrek has joined #ocaml
bruce_r has joined #ocaml
Submarine has quit [Ping timeout: 265 seconds]
nicholasf has quit [Remote host closed the connection]
nicholasf has joined #ocaml
<Bluddy[m]> anyone have any idea why utop chokes on '#use "Str.cma"'?
<Bluddy[m]> Error: illegal character (\000)
<Bluddy[m]> ocaml 4.03+flambda
<Bluddy[m]> ok my bad. Haven't use the repl in a while
nicholasf has quit [Remote host closed the connection]
<evhan> Bluddy[m]: cma files are binary, #use will be expecting source. I guess you want #load instead.
<evhan> Oh, you got it. nm.
<Bluddy[m]> yeah thanks though
<Bluddy[m]> ok now I was able to #load_rec my module, but I can't see anything in it. Do I need to open it? It's not bound
nicholasf has joined #ocaml
<Heasummn> How can I compile code for a target different than my current architecture?
rowocaml has joined #ocaml
<rowocaml> Can someone help explain to me why this example from ROW does not compile? http://pastebin.com/BsuePVkU
<rowocaml> lol oh wait, it does
<rowocaml> my bad
manizzle has quit [Read error: Connection timed out]
manizzle has joined #ocaml
Muzer has quit [Ping timeout: 255 seconds]
rowocaml has quit [Ping timeout: 264 seconds]
MercurialAlchemi has joined #ocaml
Muzer has joined #ocaml
yegods has quit [Remote host closed the connection]
_whitelogger has joined #ocaml
AlexDenisov has joined #ocaml
FreeBirdLjj has joined #ocaml
sdothum has quit [Quit: ZNC - 1.6.0 - http://znc.in]
sdothum has joined #ocaml
FreeBirdLjj has quit [Ping timeout: 260 seconds]
MercurialAlchemi has quit [Ping timeout: 240 seconds]
FreeBirdLjj has joined #ocaml
MercurialAlchemi has joined #ocaml
bungoman has joined #ocaml
sdothum has quit [Quit: ZNC - 1.6.0 - http://znc.in]
sdothum has joined #ocaml
ggole has joined #ocaml
xaimus has quit [Remote host closed the connection]
sdothum has quit [Quit: ZNC - 1.6.0 - http://znc.in]
sdothum has joined #ocaml
bruce_r has quit [Ping timeout: 264 seconds]
sdothum has quit [Quit: ZNC - 1.6.0 - http://znc.in]
ggole_ has joined #ocaml
ggole has quit [Ping timeout: 244 seconds]
Heasummn has quit [Ping timeout: 252 seconds]
ggole__ has joined #ocaml
tmtwd has quit [Ping timeout: 240 seconds]
ggole_ has quit [Ping timeout: 265 seconds]
nicholasf has quit [Remote host closed the connection]
Submarine has joined #ocaml
Submarine has joined #ocaml
Submarine has quit [Changing host]
Reshi has joined #ocaml
soupault has joined #ocaml
nicholasf has joined #ocaml
AlexDenisov has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
Simn has joined #ocaml
ggole__ has quit [Ping timeout: 265 seconds]
minn has quit [Ping timeout: 264 seconds]
lyxia has quit [Quit: WeeChat 1.5]
FreeBirdLjj has quit []
lyxia has joined #ocaml
Algebr`` has joined #ocaml
mcc has quit [Quit: Connection closed for inactivity]
orbifx has joined #ocaml
<infinity0> could someone help me with this https://paste.debian.net/806855/
<infinity0> i'm trying to define State.run_until to be an alias for State.OfMonoid.run_until where the monoid is a list
ggole has joined #ocaml
<infinity0> "The parameter cannot be eliminated in the result type.
<infinity0> Please bind the argument to a module identifier." a bit unclear which parameter it's talking about
<infinity0> same error when i write e.g. let run_until (type a') = let module SList = OfMonoid (ListMonoid(struct type a = a' end)) in SList.run_until
<infinity0> ok i fixed that by defining an intermediate module but now the error is "The type constructor ListM.t would escape its scope" :(
kakadu has joined #ocaml
<lyxia> infinity0: make ListMonoid export the definition of t
<ggole> But this doesn't quite work either
<ggole> Hmm, just eta-expanding seems to be enough
<infinity0> now i have a different error https://paste.debian.net/806876/
<ggole> Yeah, that's the issue I just mentioned
<infinity0> ggole: i added a : Monoid with type blah to ListMonoid as well
<ggole> That also works
<ggole> (I just removed the annotation.)
<infinity0> lyxia: still says "contains type variables that cannot be generalized" :(
<ggole> Again, just eta-expand
<ggole> (The ML curse!)
<infinity0> which part do i expand :/
<ggole> Like in my second gist
<infinity0> your second gist still gives that error for me
<ggole> Oh, let me double check
<infinity0> although i'm still on 4.02.3
<infinity0> oh, your second gist is fine
<ggole> I'm on 4.03, but I'm not aware of any change
<ggole> Ah, OK
<ggole> Yeah, the first one is busted too
<lyxia> oh indeed I forgot that
<infinity0> ah, you added extra "f" to run_until ok
<infinity0> that is weird why that works
<infinity0> (i thought eta-expansion was the other thing)
<ggole> infinity0: ML has side effects, so generalising partial applications is unsound in general
<infinity0> i see
<lyxia> eta-reduction is the other way around
copy` has quit [Quit: Connection closed for inactivity]
<Algebr``> infinity0: can you post a debian paste with the fully correct, working cut?
rand__ has joined #ocaml
<infinity0> Algebr``: ggole's second gist works, https://gist.github.com/987d613b0c1b6af3fdf8afc028ee6dc6
<Algebr``> thanks
FreeBirdLjj has joined #ocaml
axiles has quit [Ping timeout: 244 seconds]
axiles has joined #ocaml
manizzle has quit [Ping timeout: 260 seconds]
Reshi has quit [Ping timeout: 265 seconds]
manizzle has joined #ocaml
kolko has quit [Quit: ZNC - http://znc.in]
kolko has joined #ocaml
silver has joined #ocaml
ygrek has quit [Ping timeout: 244 seconds]
nicholasf has quit [Remote host closed the connection]
nicholasf has joined #ocaml
adelbertc has quit [Quit: Connection closed for inactivity]
Algebr`` is now known as Algebr`
Stalkr_ has joined #ocaml
govg has joined #ocaml
AlexDenisov has joined #ocaml
orbifx has quit [Ping timeout: 240 seconds]
nicholasf has quit [Ping timeout: 258 seconds]
nicholasf has joined #ocaml
govg has quit [Quit: leaving]
TheLemonMan has joined #ocaml
zpe has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
cube_bot has joined #ocaml
yegods has joined #ocaml
chsn has left #ocaml [#ocaml]
<adrien> hmmm, anyone else has received spam from smtp.ocamlcore.org ?
Submarine has quit [Ping timeout: 265 seconds]
Xizor has joined #ocaml
freusque has joined #ocaml
<Leonidas> can anyone explain to me how Lwt_pool works? I don't see how the 'a make it into the underlying queue
<Leonidas> there is only one call to Queue.push and that's in Lwt_pool.release
<companion_cube> I didn't look at the code, sorry
<companion_cube> I suppose there is a queue of re-usable resources
<companion_cube> but if the queue is empty, a new object is directly created and use
<companion_cube> d
<Leonidas> oh, I see, it does not seem to feed the items into the queue but reuses it directly
<Leonidas> so the Queue inside is just for the case where noone is waiting on the resource
<Leonidas> that's pretty cool
<Leonidas> thanks companion_cube :-)
nicholasf has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
nicholasf has joined #ocaml
nicholas_ has joined #ocaml
hnrgrgr_ has joined #ocaml
hnrgrgr_ has quit [Client Quit]
FreeBirdLjj has quit [Ping timeout: 255 seconds]
nicholasf has quit [Ping timeout: 250 seconds]
manizzle has quit [Ping timeout: 276 seconds]
freusque has quit [Ping timeout: 250 seconds]
AlexDenisov has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
d0nn1e has quit [Ping timeout: 265 seconds]
orbifx has joined #ocaml
d0nn1e has joined #ocaml
govg has joined #ocaml
orbifx has quit [Ping timeout: 244 seconds]
sdothum has joined #ocaml
Reshi has joined #ocaml
zpe has quit [Remote host closed the connection]
<companion_cube> ^^
<ggole> Hmm, it turns out to be quite easy to stick a map into a hash table as a fallback to avoid the linear worst case
<ggole> Except I don't remember seeing this being done
<companion_cube> I think Core uses this trick
<ggole> Ah, they've got a compare in there
<ggole> Actually, that's a bit nicer than what I've done, which is to have both equal and compare
pierpa has joined #ocaml
<ggole> companion_cube: ah, they use an avl tree per bucket
<ggole> I have basic chains and overflow into the map when they get too long
<ggole> Wonder which is faster.
<ggole> Huh, they're mutable. What an ugly (but I suspect, practical) approach.
copy` has joined #ocaml
kdas_ has joined #ocaml
kdas_ has quit [Read error: Connection reset by peer]
kdas_ has joined #ocaml
vramana has joined #ocaml
kdas_ has quit [Read error: Connection reset by peer]
vramana has quit [Client Quit]
kushal has joined #ocaml
Reshi has quit [Quit: WeeChat 1.5]
axiles has quit [Ping timeout: 244 seconds]
nicholas_ has quit [Remote host closed the connection]
nicholasf has joined #ocaml
<copy`> So, I made an implementation of that websocket benchmark game: https://gist.github.com/copy/8f71a129e9b7ff64c262cbabf191e2a5
<copy`> However on my machine it's faster than the cpp version, so I'm a bit sceptical
nicholasf has quit [Remote host closed the connection]
troydm has quit [Ping timeout: 244 seconds]
shinnya has quit [Ping timeout: 265 seconds]
silver_ has joined #ocaml
silver has quit [Ping timeout: 250 seconds]
tmtwd has joined #ocaml
companion_square has joined #ocaml
companion_cube has quit [Ping timeout: 258 seconds]
govg has quit [Ping timeout: 265 seconds]
TheAuGingembre has quit [Ping timeout: 276 seconds]
TheAuGingembre has joined #ocaml
cube_bot has quit [Ping timeout: 250 seconds]
companion_cube has joined #ocaml
Submarine has joined #ocaml
Submarine has quit [Changing host]
Submarine has joined #ocaml
FreeBirdLjj has joined #ocaml
<chelfi> Make sure it does not drop messages :p
<chelfi> (there is quite a lot of noise around the Haskell version)
AlexDenisov has joined #ocaml
FreeBirdLjj has quit [Ping timeout: 250 seconds]
axiles has joined #ocaml
companion_square has quit [Quit: WeeChat 1.5]
Xizor has quit [Ping timeout: 244 seconds]
bruce_r has joined #ocaml
Xizor has joined #ocaml
malc_ has joined #ocaml
malc_ has quit [Client Quit]
FreeBirdLjj has joined #ocaml
troydm has joined #ocaml
govg has joined #ocaml
tane has joined #ocaml
freusque has joined #ocaml
mcc has joined #ocaml
govg has quit [Ping timeout: 244 seconds]
govg has joined #ocaml
freusque has quit [Ping timeout: 276 seconds]
tmtwd has quit [Ping timeout: 258 seconds]
freusque has joined #ocaml
bitbckt has quit [Ping timeout: 250 seconds]
j0sh has quit [Ping timeout: 250 seconds]
bruce_r has quit [Ping timeout: 250 seconds]
<infinity0> Algebr`: was it you that compiled ocamlc using js_of_ocaml?
<infinity0> does it (the compiled javascript ocamlc) generate js directly or x86 assembly
<Algebr`> I didn't do that, I didn't realize it would be possible to compile ocamlc with jsoo, maybe if someone went through the trouble of the C code stubs
j0sh has joined #ocaml
<infinity0> oh, someone mentioned it to me but i can't remember if they meant "a nice idea" or "it exists"
<infinity0> i thought i remembered you saying something like that in marrakesh but i guess i remembered that wrong too
<Algebr`> probably nice idea
<Algebr`> I guess it would be possible, just all that C code needs to be stubbed out
bitbckt has joined #ocaml
freusque has quit [Ping timeout: 252 seconds]
thizanne has joined #ocaml
thizanne has quit [Client Quit]
thizanne has joined #ocaml
yegods has quit [Remote host closed the connection]
shinnya has joined #ocaml
copy` has quit [Quit: Connection closed for inactivity]
agarwal1975 has joined #ocaml
agarwal1975 has quit [Client Quit]
tmtwd has joined #ocaml
ollehar has joined #ocaml
Xizor has quit []
ygrek has joined #ocaml
copy` has joined #ocaml
zedik has joined #ocaml
bungoman has quit [Read error: Connection reset by peer]
shinnya has quit [Ping timeout: 264 seconds]
bungoman has joined #ocaml
bungoman has quit [Max SendQ exceeded]
soupault has quit [Ping timeout: 250 seconds]
zedik has quit [Client Quit]
Submarine has quit [Ping timeout: 265 seconds]
tmtwd has quit [Ping timeout: 250 seconds]
soupault has joined #ocaml
tmtwd has joined #ocaml
yegods has joined #ocaml
yegods has quit [Read error: Connection reset by peer]
yegods has joined #ocaml
<adrien> infinity0: without additional steps, the ocamlc compiled with jsoo would still generate the same output
agarwal1975 has joined #ocaml
MercurialAlchemi has quit [Ping timeout: 258 seconds]
AlexDenisov has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
Xizor has joined #ocaml
orbifx has joined #ocaml
yegods has quit [Remote host closed the connection]
abeaumont_ has joined #ocaml
orbifx has quit [Ping timeout: 250 seconds]
ydl has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
ygrek has quit [Ping timeout: 250 seconds]
pyon has quit [Quit: Fix config.]
pyon has joined #ocaml
pyon has quit [Client Quit]
yegods has joined #ocaml
pyon has joined #ocaml
soupault has quit [Remote host closed the connection]
ydl has quit [Ping timeout: 250 seconds]
SpaceSheep has joined #ocaml
sepp2k has joined #ocaml
ydl has joined #ocaml
ydl has quit [Ping timeout: 255 seconds]
thizanne_ has joined #ocaml
thizanne_ has quit [Client Quit]
ydl has joined #ocaml
ydl` has joined #ocaml
sepp2k has quit [Quit: Leaving.]
adelbertc has joined #ocaml
ydl has quit [Ping timeout: 244 seconds]
ydl` has quit [Ping timeout: 252 seconds]
ydl` has joined #ocaml
Xizor has quit []
ydl` has left #ocaml ["ERC (IRC client for Emacs 24.5.1)"]
ydl has joined #ocaml
ggole has quit []
<ydl> has the community completely rallied behind core at this point? if not is there an up-to-date comparison of core vs batteries (vs other standard libraries I haven't seen)? or some system to choose by?
<companion_cube> it's not rallied, no
<ydl> is there some list of perferred choices by intended application/domain then?
tmtwd has quit [Ping timeout: 264 seconds]
<companion_cube> I don't think so; after all, they are both generalist standard libraries
<ydl> ok, thanks! i'm still a bit reluctant to pick one completely at random, is there some recent canonical comparison (of features or philosophy/overarching goals or both)?
malparti has joined #ocaml
<ydl> or at least some recorded discussion by experienced users of both?
malparti has quit [Client Quit]
tmtwd has joined #ocaml
<companion_cube> hmmmm
<companion_cube> not that I'm aware of
<companion_cube> maybe on the mailing list
<companion_cube> my personal take: batteries looks like a bigger version of the stdlib, is maintained by the community, but moves a bit slowly those days
<Drup> pretty sure there is a reddit thread
<companion_cube> core moves faster but has a larger overhead and belongs to janestreet; also not compatible with the stdlib
<companion_cube> !stdlibs
<Drup> hey, I'm even in there x)
<Drup> hum, it's not precisely up to date
<companion_cube> w.r.t this? not too bad, I find
<companion_cube> (core is still quite heavyweight)
<Drup> yeah, but the jsoo support is better now, and the comment about codesize is still not solved, even for recent ocaml :/
<Drup> (and containers have seen 2 years of use, so it's not so new anymore)
<Drup> (wow, 2 years ...)
<ydl> what do you think is wrong/needs to be reworked about BatEnum? looking at its implementation and interface makes it seem like really the only way to build such a thing. i would actually consider it a positive for batteries
<ydl> it seems the creator of the containers library thinks the same thing, which means i am probably missing something
Stalkr_ has quit [Ping timeout: 258 seconds]
<companion_cube> it's slow and very complicated
<companion_cube> (I'm the author of containers, btw)
<ydl> Enum is slow? how could anything be faster? it's just a wrapper over an update function
<Drup> Eh
<Drup> let me find a link to my old mail to the batteries mailing list
<ydl> encapsulating this kind of iteration is important to me, so i'd be interested in potentially more efficient solutions. it looks like Core's alternative (Sequence in Core_kernel or Lazy_sequence in core_extended) carries around a state, making it a little bet less performant in inner loops than enums that avoid carrying the state? (of course the overall design may be a bit cleaner from some point of view, but i'm not arguing that)
<companion_cube> Enum has some overhead because it has, imho, too many features (e.g. clone or count)
<companion_cube> it's also very complicated because of those operations, which are hard to test
<ydl> companion_cub, Drup: thanks very much! i am looking through the benchmarks code in the github thread now to try to understand, but maybe you can explain in a bit more detail how sequence (or anything) can be faster than Enum? also isn't Enum basically gen?
<Drup> The implementation is slightly insane, too, it has some Obj.magic ...
<ydl> companion_cube, Drup: i also noticed that instead of exceptions (like Enum) gen uses option, which I would also think is more generic (and faster, but maybe that's where the difference in benchmarks comes from...)
<Drup> ydl: look at what sequence is, it's basically an iter function. Enum does a lot lot more stuff
<Drup> (consider the "append" implementation, it will give you a good idea of how much more work enum does)
<ydl> is there a comparable function for sequence?
<Drup> append :)
bruce_r has joined #ocaml
<companion_cube> ydl: enum is like gen, but with additional features (clone, count), which add to the complexity
<ydl> i see, so the claim is what makes enum less efficient than sequence is the memory usage from carrying clone and count and the overhead of keeping them updated?
<ydl> incidentally, it seems that clone might be a serious piece of upkeep, but i think count and the fast_count property make sense (although this is motivated by my own common usecases :)
<companion_cube> that's what I think, yes (compared to gen; sequence is really a different beast)
SpaceSheep has quit [Ping timeout: 244 seconds]
<companion_cube> indeed, count can be useful, but it's not always easy to implement (e.g. when iterating on the lines of a file; no way to know unless you read the file whole)
<companion_cube> got to sleep, sorry
<Drup> ydl: you can provide clone-like facilities externally (see Gen.Persistent).
<ydl> companion_cube: thanks very much for your explanations! i'm still wondering why sequence is performing better if it's not for the clone/count overhead, but i'll ask again another time.
tane has quit [Read error: Connection reset by peer]
<ydl> ah wait i see
<ydl> sequence basically does inline fusion
<Drup> Gen too, but gen will allocate more at each step (because of the option) and the compiler is much better at optimized sequence (with flambda, the pile of closure is going to be turned into basically a for-loop)
<Drup> sequence is fast because it does very little :)
tane has joined #ocaml
<ydl> actually I am now wondering if sequence has any limitations apart from counting/cloning? otherwise it seems the superior choice in any case (including over something like 'gen'). I was planning to write some fusion library over Enum but this seems to make that obselete.
<Drup> ydl: look at the second message in the github thread
nicholasf has joined #ocaml
tane has quit [Quit: Verlassend]
<Drup> (rather https://github.com/c-cube/olinq/ , in fact)
nicholasf has quit [Remote host closed the connection]
nicholasf has joined #ocaml
<ydl> Drup: thanks. sequence (ironically) is only limited in combining sequences (the only operatino it can ever do on two is essentially a cartesian product since once you start processing a sequence you can't stop), so i guess the most generic/performant combination would be to use gen to generate a "sequence"-type iterator and then do as much processing as possible in sequence
chsn has joined #ocaml
<chsn> how does one write fmap in ocaml?
ollehar has quit [Quit: ollehar]
<ydl> chsn: what do you mean? i will assume you want to replicate Haskell behavior since there is a common functoin called fmap. you would just have a module with (sub-)signature "sig type 'a t val fmap : ('a -> 'b) -> 'a t -> 'b t end" and then use that as an argument to a functor or a first-class module
sepp2k has joined #ocaml
bruce_r has quit [Ping timeout: 264 seconds]
TheLemonMan has quit [Quit: "It's now safe to turn off your computer."]
Simn has quit [Quit: Leaving]
bruce_r has joined #ocaml
agarwal1975 has quit [Ping timeout: 258 seconds]
nicholasf has quit []
nicholasf has joined #ocaml
kakadu has quit [Remote host closed the connection]
bruce_r has quit [Ping timeout: 255 seconds]
ydl has quit [Ping timeout: 250 seconds]
ydl has joined #ocaml
ydl has left #ocaml [#ocaml]
shinnya has joined #ocaml
sepp2k has quit [Quit: Leaving.]
rand__ has quit [Quit: leaving]