gildor changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | OCaml 3.12.1 http://bit.ly/nNVIVH
sepp2k has quit [Remote host closed the connection]
ulfdoz has quit [Read error: Operation timed out]
ulfdoz has joined #ocaml
rsc` has joined #ocaml
barronax` has quit [Remote host closed the connection]
rsc` has quit [Client Quit]
sroyc has joined #ocaml
sroyc has quit [Quit: bored]
madroach has quit [Ping timeout: 265 seconds]
lazythunk has joined #ocaml
lazythunk has quit [Client Quit]
madroach has joined #ocaml
<dsheets> type-level distributive product operator? have to use type-conv or some other camlp4 thing?
<dsheets> like 'a ref over {arbitrary record}?
emmanuelux has quit [Remote host closed the connection]
<thelema> dsheets: I don't understand your question. 'a ref works on arbitrary record types
<dsheets> thelema: I want to distribute the 'a ref type function into each constituent element of type products (tuples, records)
<dsheets> so type r = { foo : int; bar : string } becomes type r' = { foo : int ref; bar : string ref }
<thelema> oh, you want to make each field of a record mutable?
<thelema> type r' = {mutable foo : int; mutable bar : string}
<thelema> but as an operator, so...
<dsheets> sure, but can I do it automatically?
<thelema> type r = {foo : int; bar:string} mutable
<thelema> is the same as r'
<thelema> (this is not actual ocaml syntax)
<thelema> just a representation of what you want, right?
<dsheets> yes, that is something like what I want
<thelema> no, no way to do this automatically.
<thelema> camlp4 or some pre-processor
<thelema> why do you want to do this?
<thelema> you can simulate this with Obj
<dsheets> to construct freezable records for, say, Arg
<dsheets> I have a collection of equivalent command serializations that I would like to keep in sync
<thelema> freezable records... use two type definitions and copy from one type to the other
hyperboreean has quit [Ping timeout: 265 seconds]
hyperboreean has joined #ocaml
<dsheets> this is what i have now and it feels bad
<dsheets> perhaps it is best to be most explicit, though
gnuvince has joined #ocaml
cabbagebot has joined #ocaml
<cabbagebot> Hello everyone
<cabbagebot> I'm learning ocaml, and I've got a strange problem that doesn't work as I thought it would
<cabbagebot> would anyone mind taking a look?
<cabbagebot> For whatever reason, the example I give in the comment of that paste always returns 4...
<_habnabit> cabbagebot, could it because you wrote countX instead of countNum?
<cabbagebot> Ah, whoops. Somewhere in changing the function name I must have forgotten to change the calls to it.
<cabbagebot> I'll fix that up and see what happens, heh, thanks
<cabbagebot> Alright, this is what I'm actaully using. It still doesn't behave as I thought it would though.
<_habnabit> how so?
ankit9 has joined #ocaml
<_habnabit> also, you typically don't define all functions as being unary with a tuple as the argument
<_habnabit> i.e. let rec countNum lst soFar num =
<cabbagebot> It returns 4 when I call it as countNum ([1;1;2;3],0,1) when I would expect it to return 2
<_habnabit> or, even better, let rec countNum soFar num = function
<cabbagebot> Right, that's actually something a professor is having us do...
<_habnabit> oh, gross
<cabbagebot> I'd written some F# before and thought it was sort of silly.
<_habnabit> yeah, it's very silly
<_habnabit> anyway, when you do `num::xs`, that's not checking if the item of the head of the list is the same as num
<cabbagebot> I think it's because he's trying to make it a lot like pure lambda calculus or something.
<cabbagebot> ah, is it binding it to num?
<_habnabit> you need e.g. x :: xs when x = num ->
<_habnabit> yes
<cabbagebot> ohhh
<cabbagebot> alright, thanks
<_habnabit> you can only match literals
<cabbagebot> that makes much more sense
<cabbagebot> okay
<_habnabit> I've had this problem before because `infinity` is a variable and not a language construct, haha
<_habnabit> I was trying to match `infinity :: xs` or some such
<cabbagebot> ah haha
<cabbagebot> Alright, I changed it to that and now it works perfectly
<cabbagebot> Thanks much!
<_habnabit> no problem
cabbagebot has quit [Read error: Operation timed out]
cabbagebot has joined #ocaml
cabbagebot has quit [Quit: leaving]
Yoric has joined #ocaml
Yoric has quit [Ping timeout: 246 seconds]
ankit9 has quit [Quit: Leaving]
Fnar has joined #ocaml
BiDOrD_ has joined #ocaml
BiDOrD has quit [Ping timeout: 264 seconds]
hyperboreean has quit [Ping timeout: 244 seconds]
ftrvxmtrx has quit [Quit: Leaving]
hyperboreean has joined #ocaml
pango is now known as pangoafk
djcoin has joined #ocaml
thomasga has joined #ocaml
ftrvxmtrx has joined #ocaml
ankit9 has joined #ocaml
Ptival has quit [Read error: Connection reset by peer]
cago has joined #ocaml
<Drakken> If foo is a polymorphic function that takes a polymorphic function bar as a parameter, how do you specify in the signature of foo that bar is polymorphic?
<Drakken> The parser doesnt' seem to like ('c. ...)
mika1 has joined #ocaml
Ptival has joined #ocaml
<_habnabit> Drakken, what's the signature you want?
mfp has quit [Read error: Connection reset by peer]
<Drakken> _habnabit the body of the outer function defines a local function that uses the functions in the parameter list.
<Drakken> I put an explicity signature in the local function and the type checker says the body is "less general" than the signature.
<_habnabit> okay, but that doesn't answer my question
<Drakken> the type is complicated.
<Drakken> Do you really want to see the whole thing?
<_habnabit> you can't make a simplified example?
<Drakken> I'll try. just a sec.
<Drakken> _habnabit maybe something like 'a. 'a -> ('b. 'b -> int) -> int
<Drakken> or 'a. 'a tree -> ('b. 'b -> int) -> int
<_habnabit> fwiw i was able to do:
<_habnabit> # let f: 'a -> ('b -> int) -> int = fun x y -> y (Obj.magic x);;
<_habnabit> val f : 'a -> ('b -> int) -> int = <fun>
<_habnabit> (I'm not sure how else your second polymorphic type can enter this unless there's some global)
<_habnabit> well, not even then. hm.
<Drakken> This is for dealing with phantom types polymorphically.
Cyanure has joined #ocaml
<Drakken> I want one function to deal with all variants in any situations where the different types are processed in the same way.
<Drakken> not variants, all the possible types, based on the phantom type arguments
mfp has joined #ocaml
<Drakken> The whole point is to have the safety of phantom types without duplicating functions, so I'll pass on Obj.magic :)
err404 has joined #ocaml
chambart has joined #ocaml
Cyanure has quit [Quit: Quitte]
ontologiae has joined #ocaml
err404 has quit [Remote host closed the connection]
ocp has joined #ocaml
milosn has quit [Ping timeout: 246 seconds]
rwmjones_hols has joined #ocaml
chambart has quit [Ping timeout: 244 seconds]
_andre has joined #ocaml
Yoric has joined #ocaml
sepp2k has joined #ocaml
chambart has joined #ocaml
rixed has joined #ocaml
ontologiae has quit [Read error: Connection reset by peer]
ontologiae has joined #ocaml
gnuvince has quit [Ping timeout: 272 seconds]
Kakadu has joined #ocaml
<hcarty> thelema: It looks like oasis already supports querying _oasis files out of the fbox
<hcarty> s/fbox/box/
<hcarty> thelema: For example - oasis query -oasis _oasis 'library("imagelib").builddepends'
<hcarty> thelema: That prints "graphics, lablgtk2"
<hcarty> thelema: 'oasis query -help' has more options
ontologiae has quit [Read error: Connection reset by peer]
ontologiae has joined #ocaml
<thelema> hcarty: aha.
gnuvince has joined #ocaml
<thelema> not quite what I wanted, as projects with many libraries involve a bunch of processing... but it could work
Yoric has quit [Ping timeout: 252 seconds]
ankit9 has quit [Quit: Leaving]
Yoric has joined #ocaml
Yoric has quit [Ping timeout: 248 seconds]
r126f has quit [Remote host closed the connection]
Tobu has quit [Remote host closed the connection]
Tobu has joined #ocaml
Yoric has joined #ocaml
Tobu has quit [Remote host closed the connection]
fx_ is now known as f[x]
Tobu has joined #ocaml
<pr> any news on 'real world ocaml'?
barronax has joined #ocaml
<barronax> I'm confused by the parsing of my code here (http://codepad.org/wQDyUREG), could someone tell me if I'm write this code in a bad style, and possibly suggest an alternative?
<f[x]> barronax, quite good, minor tweaks -> http://codepad.org/exG0LHw8
<Qrntz> barronax, your style is mostly okay, but you had issues with grouping
<Qrntz> see my version at http://codepad.org/jdKJCkUP
<Qrntz> if you are not parenthesizing a pattern captured by «as», the latter tries to cling to as much of the former as it can
gnuvince has quit [Quit: Remember when men were men and regular expressions recognized regular languages?]
<barronax> f[x], Qrntz: Thank you very much for the corrections!
<barronax> I find it quite confusing that Cell d as m, (Note the comma) is OK, but Cell d as m -> seems to require special care. Maybe I should just group all such instances for safety.
<Qrntz> (I tried to only minimally touch your style so it would be still within widespread usage)
<Qrntz> e. g. a space before a semicolon is used in quite some OCaml code, but parenthesizing entire lines isn't as widespread and isn't really necessary
<barronax> Mm, I was using them as a more stuning visual indication of mutation. But I think I will change that style now :-)
<Qrntz> «Cell d as m» is right because the «as» only captures the first element of the tuple, as opposed to all of the preceding ones, it's how its grouping works
<Qrntz> err, «Cell d as m,»
<barronax> Ah, I see. Oh well.
<Qrntz> as an example, «match (1, 2, 3) with (x, y as tpl, z) -> tpl» will give you an error for it expects to match ((x, y as tpl), z) which is against common intuition
<Qrntz> a bit, anyway
<Qrntz> or, even, (((x, y) as tpl), z)
<barronax> Also, by setting the next and prev pointers to Empty, can the OCaml compiler garbage collect them? I'm guessing it can't tell that Empty = NULL, and if that is the case, how can I avoid cluttering the heap with removed cells?
<barronax> (Or should I even concern myself with this? :-))
<Qrntz> there is no explicit notion of pointers in OCaml, but it will collect the unreferenced anymore fragments so yes, you don't really have to worry about that
<barronax> Cool, thanks Qrntz.
<Qrntz> you're welcome
leoncamel has joined #ocaml
djcoin has quit [Read error: Operation timed out]
djcoin has joined #ocaml
emmanuelux has joined #ocaml
Yoric has quit [Ping timeout: 252 seconds]
Yoric has joined #ocaml
mika1 has quit [Quit: Leaving.]
ocp has left #ocaml []
cago has quit [Ping timeout: 240 seconds]
osa1 has joined #ocaml
cago has joined #ocaml
<companion_cube> if a Lazy.t has been evaluated, is calling Lazy.force on it again fast?
<yezariaely> companion_cube: it will not be evaluated again, if you mean that.
<companion_cube> I know this, but is there some other overhead compared to just returning the value?
<companion_cube> in other words, is a Lazy.t which result is a as fast to evaluate as a itself?
<thizanne> companion_cube: is there an overhead when you call "id x" instead of just writing "x" ?
<companion_cube> (with just a test or something added)
<yezariaely> companion_cube: I assume it has to check if it is a evaluated value or a lazy value? so this test may take "some" tiem
<yezariaely> time
<yezariaely> but that is only a rough guess...
<companion_cube> ok
<Qrntz> yes, it takes more time than just returning a value would
<Qrntz> I benchmarked this
<Qrntz> when I did (on 3.12.0), thunks also seemed to be a bit faster than the Lazy module, but things might've changed with 4.00 (or might've not)
<companion_cube> Qrntz: how much slower?
cago has quit [Read error: Connection reset by peer]
<Qrntz> companion_cube, I don't think I still have the exact results, sorry
<Qrntz> don't want to deceive you :-p
<companion_cube> that's ok, I may benchmark it as some point then...
<Qrntz> I could benchmark now, but then you might do this as well in a way you wish to
<companion_cube> yes, don't bother yourself with that :)
<djcoin> companion_cube: do you need _that_ much perf or is it curiosity ? :)
<companion_cube> it's part curiosity, and part because I was thinking of using lots of lazy thunks at some point
ftrvxmtrx has quit [Quit: Leaving]
<djcoin> kk
sepp2k1 has joined #ocaml
sepp2k has quit [Ping timeout: 276 seconds]
osa1 has quit [Quit: Konversation terminated!]
leoncamel has quit [Ping timeout: 268 seconds]
emmanuelux has quit [Remote host closed the connection]
<hcarty> There were a handful of improvements to the performance of lazy values in the last year or two. However, I don't remember if they are in 3.12.x or 4.x.
djcoin has quit [Quit: WeeChat 0.3.7]
<companion_cube> is there something that makes Lazy.t more complicated than a bool flag and a closure?
<Qrntz> there exists the Obj.lazy_tag which could imply they're handled differently by the GC
<Qrntz> but it seems the tag is only applied to lazified closures
<Qrntz> I suppose there is
<thelema> let x1 = lazy (20 * 30)
<thelema> let ro = ref (-1)
<thelema> let x2 = fun () -> if !ro = (-1) then ro := (20 * 30); !ro
<thelema> comparing these two, I get:
<thelema> closure (5.29 ns) is 41.2% faster than
<thelema> lazy (8.98 ns)
* companion_cube does not see why Lazy.t is not implemented this way, then :D
<hcarty> thelema: Out of curiosity - which version of OCaml?
ontologiae has quit [Ping timeout: 240 seconds]
<thelema> The Objective Caml toplevel, version 3.12.1
<thelema> (not actually in the toplevel, just pasting `ocaml -version`)
<thelema> one sec, switching to 4.00
<hcarty> Ah ok - I expect that native vs bytecode could be different. Not sure in which direction though.
<thelema> ... need to rebuild some libraries...
barronax` has joined #ocaml
<f[x]> lazy values can be propagated after evaluation
ftrvxmtrx has joined #ocaml
barronax has quit [Ping timeout: 246 seconds]
<thelema> grr, broken cairo2 still in oasis-db
osa1 has joined #ocaml
<hcarty> thelema: Does the latest bzr revision build under 4.00.0? I thought it didn't but I may not have tested it.
<thelema> well, I still run into the configure problem caused by their tweaks to oasis configure step
<thelema> ERROR: Could not compile a test program. The cairo library flags "-lcairo" are likely incorrect. Set them in config.ml.
<thelema> maybe if you have an old enough binutils, it'll work
<thelema> I see your bug on their tracker
<hcarty> Yeah... I think I tried to hack their build system changes into something that worked for me without luck. I didn't have much time for it though.
<hcarty> I was able to get camlimages to build with oasis, which removes my need for omake. And I'm quite happy about that.
<thelema> quite nice.
<hcarty> thelema: imagelib in oasis-db/odb's unstable
<hcarty> There are other changes as well, primarily in the form of packing the library so that it doesn't bring in so many generic module names.
osa1 has quit [Quit: Konversation terminated!]
gnuvince has joined #ocaml
<thelema> f[x]: should I benchmark another possibility?
<f[x]> hcarty, https://github.com/ermine/camlimages uses oasis
<thelema> hcarty: the cairo2 oasis doesn't even regenerate properly under oasis0.3
<f[x]> thelema, ?
chambart has quit [Ping timeout: 276 seconds]
<thelema> f[x]: regarding your comment about lazy propogation
<thelema> or maybe I didn't understand your comment
<hcarty> thelema: That's what I was trying to fix when I looked at it last.
<thelema> hcarty: for OCaml4.00, I get comparable results; actually worse results for closure:
<thelema> closure (6.34 ns) is 29.6% faster than
<thelema> lazy (9.00 ns)
<hcarty> thelema: Lots of BaseFoo -> OASISFoo module renames are required from what I saw.
<hcarty> thelema: Cool. Thanks for testing + sharing.
gnuvince has quit [Ping timeout: 240 seconds]
<hcarty> f[x]: Clearly I should have looked around first :-)
<thelema> odd, I thought tags were one byte; how to have a tag of 1000?
<f[x]> ints don't have tags
<f[x]> its pure virtual
<hcarty> f[x]: My implementation is similar - https://github.com/hcarty/imagelib
Yoric has quit [Ping timeout: 246 seconds]
<thelema> hmm, maybe I'll add a Gc.compact()
pangoafk is now known as pango
<hcarty> f[x]: Different defaults (everything defaults to off), different base version (4.0.1+hg), packed modules with stub functions if a particularly format isn't included
<thelema> nope, after Gc.compact, lazy is still slow
gpolitis has joined #ocaml
Yoric has joined #ocaml
<f[x]> hcarty, tbh, I didn't look at it, just know that it exists
<f[x]> thelema, compact influences only evaluated lazy - and it should make it equal to normal value
eni has joined #ocaml
<thelema> f[x]: yes, I'm running my full benchmark, then compacting, then running it again
<thelema> the second time lazy actually takes longer
<thelema> (8.98 ns -> 9.32 ns)
<f[x]> something is wrong
* f[x] runs away
<adrien> it takes the same time =)
<thelema> adrien: the 95% confidence intervals for each estimate are actually quite tiny, meaning that it's taking a different amount of time
<thelema> mean: 8.98 ns, 95% CI: (8.98 ns, 8.98 ns)
<thelema> mean: 9.32 ns, 95% CI: (9.32 ns, 9.33 ns)
<adrien> hmm, indeed
<thelema> the advantage of fast functions is that one can get a lot of samples quickly (of course running in batches of many iterations to not run into clock resolution problems
gnuvince has joined #ocaml
<thelema> hmm, it's never being promoted to a plain value:
<thelema> Lazy tag: 246
<thelema> Lazy tag: 250
<thelema> Lazy tag: 250
<thelema> Lazy tag: 250
<thelema> (before and after each round of benchmarking; Gc.compact() between 2nd and 3rd)
Ptival has quit [Ping timeout: 244 seconds]
<thelema> although if I run f[x]'s code in the interpreter... maybe a difference between native and bytecode?
Yoric has quit [Ping timeout: 246 seconds]
Yoric has joined #ocaml
Ptival has joined #ocaml
<thelema> nope, same behavior for bytecode... odd
osa1 has joined #ocaml
Kakadu has quit [Quit: Konversation terminated!]
err404 has joined #ocaml
ChristopheT has joined #ocaml
gnuvince has quit [Ping timeout: 252 seconds]
<ousado> thelema: where's the Bench module from?
<ousado> oh.. batteries
<thelema> ousado: actually, it's an independent project
<thelema> there's a copy of bench.ml in batteries' benchsuite/, but it's not part of batteries
<ousado> oic it's remarkably hard to google for
<thelema> yes, I'll bet.
<thelema> 'ocaml bench' pulls up my github page, which has the bench repo listed
<ousado> oh yes
<ousado> Edgar Fiendly
<ousado> *Edgar Friendly
<ousado> I didn't see thelema there
<thelema> thelema (Edgar Friendly)
<ousado> yes
pango has quit [Quit: enabling coolbits]
Yoric has quit [Ping timeout: 244 seconds]
<ousado> thelema: looks like I should start using a package manager
pango has joined #ocaml
<wmeyer> ousado: reading you I reckon you are ready for odb I suppose
<ousado> hehe
<ousado> yes, reading the README right now
* thelema smiles as `odb https://github.com/thelema/bench.git` just works.
gnuvince has joined #ocaml
<ousado> thanks
pango has quit [Remote host closed the connection]
pango has joined #ocaml
xaimus has joined #ocaml
<thelema> ousado: if you're willing to try something a bit edgier, try the precomp branch of odb; it tries to precompute all dependencies before starting the build process
Fnar has quit [Read error: Connection reset by peer]
<ousado> thelema: ok
<thelema> of course, if you have any problems let me know so I can fix them. if no problems, also let me know so I can be more confident about making that branch the default
<ousado> alright
_andre has quit [Quit: leaving]
Submarine has joined #ocaml
smondet has quit [Ping timeout: 260 seconds]
smondet has joined #ocaml
thomasga has quit [Quit: Leaving.]
gnuvince has quit [Quit: Remember when men were men and regular expressions recognized regular languages?]
sivoais has quit [Ping timeout: 255 seconds]
eni has quit [Quit: Leaving]
js3 has joined #ocaml
<js3> quit
js3 has quit [Quit: WeeChat 0.3.8]
Christop` has joined #ocaml
ChristopheT has quit [Ping timeout: 246 seconds]
osa1 has quit [Quit: Konversation terminated!]
Submarine has quit [Quit: Leaving]
Christop` has quit [Ping timeout: 240 seconds]
rwmjones_hols has quit [Read error: Operation timed out]
err404 has quit [Read error: Connection reset by peer]
sivoais has joined #ocaml
rwmjones_hols has joined #ocaml
jonathandav__ has quit [Read error: Connection reset by peer]
jonathandav has joined #ocaml
smondet has quit [Remote host closed the connection]
<wmeyer> thelema: So the odb.ml https://github.com/thelema/bench.git
<wmeyer> # Cannot find findlib package archimedes
<thelema> wmeyer: yes?
<wmeyer> oc course
<wmeyer> because oasis to boottrap _oasis needs archimedes
<thelema> odb.ml archimedes
<wmeyer> what we can do is to parse the error messages ;)
<thelema> hmm, I don't think it needs archimedes to bootstrap _oasis
<wmeyer> yes, I know, but i wanted this to just work
<wmeyer> no no, the bench repostiory needs to do oasis setup
<thelema> it doesn't work with full dep detection
<wmeyer> and since arhimedes is not there
<wmeyer> (i know i should do odb.ml archimedes)
<wmeyer> then it will fail
<thelema> dep detection from _oasis files isn't implemented; we don't depend on oasis, so we can't use the oasis library
<wmeyer> right
<thelema> hcarty had some command-line ways to use the oasis executable to query _oasis files
<wmeyer> yes, i am aware about it :(
<wmeyer> this is long standing thing
<thelema> if you want to implement, I'll merge your code.
<wmeyer> ok, thanks
<wmeyer> currently i am a bit destroyed by the amounts of things i need to do however
<wmeyer> i can try
<thelema> wmeyer: pick one thing and get it done. Repeat.
targetron has joined #ocaml
<targetron> what's the type of "[[None]]"?
olle has joined #ocaml
<olle> hello
<nicoo> targetron: 'a option list list
<nicoo> You can find it by typing « [[None]] » in the ocaml interpreter
emmanuelux has joined #ocaml