gildor changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | OCaml 3.12.0 http://bit.ly/aNZBUp
<EliasAmaral> oh i now know why
lamawithonel__ has joined #ocaml
lamawithonel_ has quit [Ping timeout: 264 seconds]
drunK has quit [Remote host closed the connection]
ikaros has quit [Quit: Leave the magic to Houdini]
<EliasAmaral> > 2*x * (5 + x*test)
<EliasAmaral> 2test^1x^2 + 10x^1
<EliasAmaral> mrvn, it works=) thank you
<adrien> notk.org/~adrien/test_osm.svg =)
<EliasAmaral> (in th end variables were strings)
<EliasAmaral> adrien, what is that?
<mrvn> EliasAmaral: skip the ^1 :)
<adrien> EliasAmaral: map of the center of paris, drawn from openstreetmap data ; only showing the roads
<mrvn> and I recommend " " between elements for readability
<EliasAmaral> yes :) actually i want in all times output in the same syntax i received, so that normalized exprs are fixed points
<EliasAmaral> like 2 test x^2?
<mrvn> yes
myu2 has joined #ocaml
<EliasAmaral> will do something about it @.@ would like to use a better library for pretty-printing
<mrvn> You want Sum [Mul [Num 2; Var "test"; Pow (Var "x", Num 2)]; Mul [Num 10; Var "x"]] to simplify to exactly that data structure?
<EliasAmaral> yes
<EliasAmaral> but the sorting wasn't got exactly
<EliasAmaral> right*
<mrvn> My approach would have been to do everything with the internal types and then "pretty print" it back into an expression.
<EliasAmaral> you mean, pretty-print back into Sum .. ?
<mrvn> EliasAmaral: simplify expr = simplify (simplify expr) should hold true at all times.
<EliasAmaral> yes, that was what i was talking..
<mrvn> EliasAmaral: yes. The same rules you use to print nice you can use to output a nice expr
myu2 has quit [Remote host closed the connection]
<EliasAmaral> I think I will implement a - b with a + (-b), and a / b with a * (1/b)
<adrien> thelema: looks like PXP can take quite a lot of memory...
<mrvn> b^(-1)?
<EliasAmaral> i saw a code from jon harrop doing that
<mrvn> You need code to simplify 1/(a+b) though.
<mrvn> or rather a/(a+b) or (a+b)/(a+b) and such
<mrvn> anyway, I'm too tired to think straight now. n8
accel has quit [Quit: leaving]
<EliasAmaral> oh. forget about / :) (but i think I can decompose, then multiply everyone by an appropriate amount Q, and output this: P / Q)
<EliasAmaral> bye! i am leaving too
ftrvxmtrx has quit [Quit: Leaving]
ftrvxmtrx has joined #ocaml
myu2 has joined #ocaml
EliasAmaral is now known as dark
ftrvxmtrx has quit [Quit: Leaving]
ftrvxmtrx has joined #ocaml
dark has quit [Ping timeout: 240 seconds]
jm has quit [Remote host closed the connection]
thatch has joined #ocaml
lamawithonel__ has quit [Read error: Connection reset by peer]
ulfdoz_ has joined #ocaml
ulfdoz has quit [Ping timeout: 240 seconds]
ulfdoz_ is now known as ulfdoz
dark has joined #ocaml
accel has joined #ocaml
<accel> are camlp4 programms writen in ocaml? So basically, a camlp4 program is a peice of ocaml code that transforms a DSL into ocaml code ?
<dark> accel, they aren't strictly ocaml, but well, usually you can combine many camlp4 extensions in one program
<dark> you can output plain ocaml code if you want to though
<accel> what's a good tutorial on ocamlp4 ?
<accel> I see lots of links but they're all haphazard
Yoric has quit [Quit: Yoric]
<dark> i can barely find a good tutorial on how to compile a camlp4 program u.u
<accel> is camlp4 basically one of thse things
<dark> i almost couldn't compile one i wrote using [< .. >] parsers
<accel> where if you can't figure out how to use it, it's too complciated for you?
<dark> hmm
<dark> more or less
<dark> i used to think it was too complicated, but well i started to use it with pgocaml
<dark> and it is nice
<dark> accel, oh about camlp4 extensions itself being written in ocaml, i don't know that
oriba has quit [Quit: Verlassend]
<dark> but the quasiquote syntax suggests it isn't exactly ocaml
<dark> http://caml.inria.fr/pub/docs/tutorial-camlp4/index.html there is actually a good doc on camlp4
<dark> it's just i'm ignorant
<dark> accel, if you want to see if there is something interesting check out the site of this guy accel, http://martin.jambon.free.fr/extend-ocaml-syntax.html
eaburns has joined #ocaml
<accel> ha, reading the martin.jambon.free.fr right now
<accel> i don't know why he keeps on calling it camlp5 though
<dark> it seems like a new version
<dark> i have no idea about that
<dark> actually
<dark> http://martin.jambon.free.fr/ocaml.html i meant more like this
<dark> http://martin.jambon.free.fr/micmatch.html this definitely is cool
<dark> etc
LeNsTR has quit [Quit: LeNsTR]
Edward__ has quit []
LeNsTR has joined #ocaml
thatch has quit [Remote host closed the connection]
accel has quit [Disconnected by services]
accel has joined #ocaml
accel has quit [Quit: leaving]
charlesno has joined #ocaml
<charlesno> may i ask what some of you use ocaml for?
charlesno has left #ocaml []
infoe has joined #ocaml
accel has joined #ocaml
Amorphous has quit [Ping timeout: 272 seconds]
Amorphous has joined #ocaml
accel has quit [Quit: leaving]
sun28 has joined #ocaml
eye-scuzzy has quit [Read error: Connection reset by peer]
accel has joined #ocaml
<hcarty> dark: camlp5 is a continuation of the old (pre-OCaml 3.10.0) camlp4. A new, incompatible version of camlp4 was introduced in OCaml 3.10.0.
mfp has quit [Ping timeout: 240 seconds]
<accel> hcarty: does this new ocamlp4 post 3.10 have docuemntation anywehre? everything I've seen so far is pre 3.10
accel has quit [Quit: leaving]
mfp has joined #ocaml
edwin has joined #ocaml
ygrek has joined #ocaml
avsm has joined #ocaml
avsm has quit [Client Quit]
Associat0r has joined #ocaml
LeNsTR_ has joined #ocaml
LeNsTR_ has quit [Changing host]
LeNsTR_ has joined #ocaml
LeNsTR has quit [Ping timeout: 240 seconds]
LeNsTR_ is now known as LeNsTR
ygrek has quit [Remote host closed the connection]
Snark has joined #ocaml
Associat0r has quit [Quit: Associat0r]
boscop_ has joined #ocaml
Yoric has joined #ocaml
ygrek has joined #ocaml
ikaros has joined #ocaml
ygrek has quit [Ping timeout: 240 seconds]
<adrien> hcarty: btw: http://mlpost.lri.fr/examples/real_plot.ml.html , mlpost has great features but writing code in order to make plots is something I don't always feel like doing
ygrek has joined #ocaml
myu2 has quit [Remote host closed the connection]
cyanure has joined #ocaml
myu2 has joined #ocaml
Modius has joined #ocaml
ulfdoz has quit [Ping timeout: 255 seconds]
LeNsTR has quit [Quit: LeNsTR]
LeNsTR has joined #ocaml
seafood_ has joined #ocaml
jm_ocaml has joined #ocaml
<adrien> mlpost, great tool, but spend ten times longer trying to get the program to build than to write it, something's wrong: *never* reinvent the wheel when it's a build system
lpereira has joined #ocaml
seafood_ is now known as seafood
seafood has quit [Ping timeout: 240 seconds]
<thelema> adrien: their website says patches welcome - that sounds like something in need.
<thelema> and not so hard to do, usually
<adrien> will probably do later, yeah: I made a simple programm that reads an s-expression and outputs a diagram (text boxes, with arrows in between, *and* automatic positionning of boxes) and I want to use it instead of dia which is not automated, I'll need to fix that because right now, I'm using my shell command history to compile
<adrien> I should explain the issues a bit: it has "magic" to compile, it includes its own option (it'll find its libs itself), and it depends on bitstring, cairo, and bitstring depends on unix, so it add unix.cma to the command-line, but I'm using sexplib which depends on unix.cma, so I got twice "unix.cma"
<adrien> think it cut: so I got twice "unix.cma"
<adrien> you can pass cflags, but not lflags, it has no support for preprocessing and sometimes it seems it just won't do anything when you ask it to build
<edwin> won't ocamlfind deal with that? (dup unix.cma)
<adrien> I tried "ocamlfind ocamlopt -package sexplib unix.cma foo.ml" and it didn't remove the duplicate
<adrien> now, ocamlfind wouldn't manage several libs depending on unix.cma correctly
<adrien> *would*
<adrien> mlpost has an option to use ocamlbuild, and you can pass -use-ocamlfind to it, but that doesn't solve the issue because then mlpost doesn't add some magic things to the build process which makes it hard to use
LeNsTR has quit [Read error: Connection reset by peer]
<thelema> adrien: different usages depending on how it's built? that's magical
<adrien> in foo.ml, you write the core of your program and when you call "mlpost foo.ml", it wraps that core inside something else that gives you a command-line interface (it will accept -svg, -latex, -png, -cairo ...) and it's really handy
<adrien> if you don't use "mlpost(.exe)" or give some switches, you lose that part
LeNsTR has joined #ocaml
drunK has joined #ocaml
jm_ocaml has quit [Ping timeout: 240 seconds]
smerz has joined #ocaml
ftrvxmtrx has quit [Quit: Leaving]
jm_ocaml has joined #ocaml
elehack has joined #ocaml
mbernstein has quit [Remote host closed the connection]
Yoric has quit [Ping timeout: 245 seconds]
thatch has joined #ocaml
Associat0r has joined #ocaml
ulfdoz has joined #ocaml
<dark> was the Ratio module wiped out?
<dark> at least in my ocaml 3.12 docs I can only find Num, with constructor Ratio of Ratio.ratio, but with Ratio.ratio type without link
<dark> maybe the ocamldoc failed to generate Ratio thing?
<adrien> iirc, you don't "access" it directly, only through num
<mfp> # include Ratio;;
<mfp> type ratio = Ratio.ratio ...
<mfp> in 3.12.0
<dark> i have a toy calculator, I want to make it arbitrary-precision like bc, should I use Num?
<dark> I thought about using Ratio
<mfp> Num subsumes Ratio
<dark> I would think that encapsulating with Ratio label wouldn't be a good idea, but, I don't know anything about performance actually ^^
<dark> i think it means (just?) an extra indirection
<mrvn> How does ratios make it arbitrary precision?
<mrvn> You can't even represent all numbers as ratios even if you have arbitrary precision for both parts of the fraction.
<mfp> so what if you can't represent irrational numbers? it's still arbitrary precision
<dark> well, any real number can be arbitrarily approximated by a ratio
<dark> the idea is to handle with symbolic math (like sines and so on) until one wants to escape the completely-precise world and output a float
<dark> i don't know if this is useful, but, actually, uhm
<dark> output a float, no, output a, uhm, ratio. o.o
<dark> I can calculate pi for much more decimal places in bc than i would using float
<mfp> so more than a calculator, you're writing a CAS?
<dark> uhm. i want to handle polynomials as first-class, so, i think yes
<dark> I also want it to be able to solve equations, precisely or numerically. but well. i don't know much about computer algebras..
<dark> and, i don't want to support multiple number types
cyanure_ has joined #ocaml
<dark> if a b (separated by spaces) should be a*b as suggested by mrvn, i don't know how to write a function application. maybe uppercase functions? Sin x. sin(x) wouldn't really work because it is parsed like sin x.. also, 1/3 x should maybe be (1/3) * x, and 1/3x feels like 1/(3*x), and my grammar is getting messier
infoe has quit [Ping timeout: 276 seconds]
cyanure has quit [Ping timeout: 264 seconds]
ski has quit [Ping timeout: 264 seconds]
ski has joined #ocaml
<dark> i want ( expr ) to parse as expr, so <expr>(<expr>) is really <expr><expr>. but don't mind adding a "glue" token at the lexer whenever two exprs follow one another without a whitespace. so 3x is 3 <glue> x and 3 x is 3 x
<dark> so i can distinguish between 1/3 x and 1/3x
<dark> (i think i am confused)
<dark> sin(x) doesn't work because this is the syntax for x(x+y). mathematics syntax is so inconsistent o.O
<dark> maybe uppercase should be only a lexical convention to mark the role of the variable. so all variables are case-insensitive, but I would uppercase the function I'm calling
surikator has joined #ocaml
<dark> sometimes when I remove a singularity i need to mark it in the simplified expression. so x^2 / x can be simplified to x, but only if x is nonzero. so if adding a condition to the expression is first class i could simplify x^2 / x to "x, with x != 0" or something
<dark> sounds too complicated
<mrvn> if you want function application with () or ' ' then use an explicit *.
<dark> i'm strongly against explicit *. it's the whole point of it after all ..
<mrvn> or say x(..) is a function and x (...) a multiplication. But that is confusing.
<dark> in fact i'm starting to dislike any variable above one letter
<mrvn> you could say functions are upper case
<mrvn> or use {} or []
<mrvn> anyway, to parse math syntax you need a human brain.
<dark> i was also thinking about how to solve x^2 = 1. it has two solutions, and the answer should carry the two. i could do something like let x^2 = 1 in x + 5 and it should say 4 or 6
<dark> but i'm really much more tied to syntax than fancy algorithms..
<dark> i want 1/3 x to be (1/3) * x because this is a convenient way to output a large polynomial, like, 1/3 x^2y + 5x - 1
<dark> but this is confusing for 1/3x, and arguably the wrong thing to parse
<mrvn> .oO(You should buy Mathematica)
<mrvn> 1
<mrvn> -x
<mrvn> 3
almaisan-away is now known as al-maisan
<dark> no, i shouldn't
<dark> it's more like an exercise in language design, i can't learn how to design languages buying mathematica =)
<dark> but i could make use of it if i needed a computer algebra itself
al-maisan has left #ocaml []
infoe has joined #ocaml
cyanure_ has quit [Remote host closed the connection]
thatch has quit [Remote host closed the connection]
thatch has joined #ocaml
Snark has quit [Quit: Ex-Chat]
myu2 has quit [Remote host closed the connection]
surikator has quit [Quit: surikator]
<orbitz> Are asserts considered godo practice in Ocaml?
surikator has joined #ocaml
surikator has quit [Client Quit]
<elehack> orbitz: I haven't heard of them being discouraged.
<orbitz> ok
<thelema> orbitz: I approve of them and use them often
charlesno has joined #ocaml
<orbitz> do you generally do: let foo bar = assert (bar ...); ...
<flux> obviously, they should not be used for expected runtime errors
<flux> except for quick hacks :)
<flux> (because you're not supposed to catch Assert_failure)
<thelema> Especially when I cut corners and need to make sure my half solution doesn't get treated as a full solution
<thelema> yes, very bad to catch assert_failure
<orbitz> Yeah I'm in a situation where I'm dealing wiht code that could very eaisly have off by 1 errors (I'm translating numbers between sevearl different coordinate systems) and I just want to run the code throuhg a ton of sample inputs and get errors if i violate some constraints to put my mind at some degree of ease
<thelema> yes, [let foo bar = assert (bar > 0); ...]
<flux> sometimes one can view assertions as runtime-checked comments
<thelema> orbitz: quickcheck
<flux> so they can also tell the reader of the code, what is being assumed
<orbitz> i suppose it's about time i learned quickcheck
thatch has quit [Read error: Connection reset by peer]
<thelema> I don't know how to use it proper, there's a pretty simple version of it in the qtest/ folder in the batteries source
<orbitz> thanks
<thelema> I just add magic annotations to the batteries source and it seems to work out.
<thelema> (L440 is the example use of quickcheck)
Associat0r has quit [Quit: Associat0r]
<orbitz> what is 432 for?
thatch has joined #ocaml
<thelema> the first line of the magic comment that gives the unit test group a name?
<orbitz> that whole seciton
<orbitz> Which tool uses that
<thelema> just some singleton asserts using ounit
<orbitz> ok
<thelema> if you grab the latest git tree and run [make test], you can read the batstring_t.ml file that gets generated to see what you'd want to write without the magic filtering
<thelema> but probably simpler than that is to grab https://github.com/ocaml-batteries-team/batteries-included/blob/master/qtest/quickcheck.ml and skim it quickly
<thelema> oops, I need to fix L42 in quickcheck - it assumes 32-bit ocaml
* elehack should look at quickcheck sometime
<thelema> nevermind though - this code isn't readable.
<thelema> elehack: learn it by writing inline unit tests for batteries?
<elehack> not a bad idea
<thelema> the quickcheck.ml file isn't useful - all the names are terrible, and there's few useful comments and no examples
Yoric has joined #ocaml
smerz has quit [Quit: Ex-Chat]
thatch has quit [Read error: Connection reset by peer]
thatch has joined #ocaml
<orbitz> is try foo with | E p as exc -> process p; raise exc the only wya to do reraises? seem slike information is lost there about the true origin of the exception?
<thelema> yes, it's the only way to do that, I think it keeps the full backtrace, although I can't be certain
charlesno has quit [Quit: Leaving]
<elehack> In my experience, it seems to retain the backtrace in native code.
<thelema> a simple program would quickly confirm, although I know I've seen 'reraised at..." in backtraces
eaburns is now known as Tom_will_see_thi
Tom_will_see_thi is now known as eaburns
<orbitz> thelema: looks lik eit comes close!
<thelema> comes close to a full backtrace?
<orbitz> Yeah, my test is simple. it doesn't look like I get the exact like the original 'raise' came from
<orbitz> but i get th eline in the 'try' the raise came from
<adrien> \hlstd{orl A}\hlsym{, }\hlstd{\#}\hlnum{42}\hlstd{}\hspace*{\fill}\\
<adrien> bluh =P
<orbitz> and then it says re-raised on line foo where i did raise exc
<thelema> close enough for what you need?
<orbitz> Yep
<orbitz> Well, I don't nee dit i was just curious, but seems close enough ot be useful
<orbitz> Actually I'm not sure if that is the same thign youg et without the reraise, checking something..
ymasory has joined #ocaml
<orbitz> Yeah, looks like by default you get the line on the function you called where the exception originated, but this could be because my .ml is so trivial it's just optimizing the middle functions out? I don't know, but it seems consistent at least
<thelema> or it could be a side effect of the implementation, so it tracks even if a different exception is raised
<thelema> and I think you could try with -inline 0
<orbitz> where do i put that?
<thelema> your compile command
<orbitz> ocamlc doesn't seem to like it
<thelema> hmm, only applies to ocamlopt
<thelema> hmm, and inline 0 still allows really small functions to be inlined (ones whose body is smaller than the call site)
<thelema> maybe ocamlc doesn't inline
thatch has quit [Remote host closed the connection]
fraggle_ has quit [Quit: -ENOBRAIN]
joewilliams is now known as joewilliams_away
edwin has quit [Remote host closed the connection]
<mrvn> why should ocamlc inline? It isn't like that would avoid pipeline stalls in the interpreter.
fraggle_ has joined #ocaml
elehack has quit [Ping timeout: 246 seconds]
LeNsTR|away has joined #ocaml
<thelema> mrvn: function calls aren't free in the interpreter
elehack has joined #ocaml
LeNsTR has quit [Quit: LeNsTR]
LeNsTR has joined #ocaml
LeNsTR has quit [Changing host]
LeNsTR has joined #ocaml
LeNsTR has quit [Remote host closed the connection]
LeNsTR has joined #ocaml
LeNsTR has quit [Read error: Connection reset by peer]
LeNsTR has joined #ocaml
LeNsTR has quit [Remote host closed the connection]
LeNsTR|away has quit [Changing host]
LeNsTR|away has joined #ocaml
kaustuv_ has joined #ocaml
Yoric has quit [Quit: Yoric]
<kaustuv_> Another proposed addition to batteries: unifiable references using destructive union-find. http://ln-s.net/8PJb
<kaustuv_> (pretty much a straight port from smlnj-lib)
<thelema> I have a nice union find, although I'm told that using fib heaps is better
<kaustuv_> Better how? Fib heaps only have amortized constant time merge, as opposed to practically constant worst case unions
<ulfdoz> practically, the constant is evil in most cases. ;)
<thelema> maybe my implementation is equivalent to yours: https://gist.github.com/791586
<kaustuv_> ulfdoz: the constant is <= 6 for the known universe. How is that evil?
<thelema> kaustuv_: the growth because of inv. ack. function is <=6, that's not the only constant.
<ulfdoz> kaustuv_: Depends, I'd benchmark, if necessary.
<kaustuv_> thelema: yes, the underlying uf implementation appears to be equivalent, but I think the 'a uref interface is a very friendly one
<ulfdoz> For example, I prefer tree-structures over hash-maps/sets. One is log n, the other constant, in most of the cases, the tree is faster pratical scenarios.
LeNsTR has joined #ocaml
<thelema> ulfdoz: I keep having problems with using large structures as the keys of both.
<ulfdoz> thelema: jupp, comparison or hash-calculation becomes more expensive. However, the hashmap gains advantage, if the hash is a constant.
<thelema> kaustuv_: probably true - I've only used this code for kruskal's algorithm
<ulfdoz> thelema: However, there is a point far below available memory, where I throw a database at it.
<thelema> kaustuv_: my implementation might have a lower constant factor because of its data representation: refs to variants with tuples aren't quite as efficient as records. otoh, your data structure is easier to marshal
* thelema is digesting the [sel] parameter
<thelema> kaustuv_: how do you intend [sel] to be used?
<kaustuv_> when uniting two labelled nodes (in your terminology), the label of the united node is what is produced by the sel parameter
<kaustuv_> moreover, in your case, the united node has an unpredictable label, whereas in my case the sel argument always gets the labels in the right order
<thelema> ah, the label of the root of the set, yes, that's not necessarily predictable. I guess I can imagine cases I'd want it to be the smallest element in the set or something
<thelema> I don't think "by default sel is fst" is correct, isn't fst a pair operation?
<thelema> I think you mean by default it's const
<kaustuv_> Sure.
ygrek has quit [Ping timeout: 240 seconds]
<thelema> Your implementation does allow GC-ing labels for non-root nodes... I'm not sure what I think of that, if there's any use (outside debugging)
<kaustuv_> makign the labels gc-able in your implementation seems fairly trivial.
<thelema> use for keeping the labels
<ulfdoz> I wonder if that's an ocaml-style falmwwar ;)
<thelema> I'm just doing a complete comparison of two functionally equivalent modules
<thelema> kaustuv_: will you be using this code if it gets into batteries?
<kaustuv_> well, given that the last few of my contributions come straight out of the util/ directory of my current project, I would say yes.
<kaustuv_> but the kinds of stuff I write (theorem provers) are not necessarily typical ocaml programs
lpereira has quit [Quit: Leaving.]
<thelema> great. Let's include it (hopefully w/ some tests) and I'll switch my code to it so I have one less piece of code that'll fail me before failing someone else.
<thelema> (probabilistically)
<kaustuv_> I think exposing a 'a uref interface over an underlying generic union-find implementation should be easy, so don't discard your version yet
<ulfdoz> Just for my interest, where are you both employed?
<thelema> ulfdoz: Michigan State University
<kaustuv_> I'm a researcher at INRIA
<ulfdoz> I#m java dev at hygiene supply company. I tried several time, but it does not look like as I would get the chance to make contributions to an open source project.
LeNsTR has quit [Quit: LeNsTR]
LeNsTR has joined #ocaml
LeNsTR has quit [Client Quit]
<thelema> ulfdoz: it seems many contributions to batteries come from people's private projects, but you're more than welcome to find anything that needs work and fix it.
<ulfdoz> However, about 90% of our 3rd-party-components are open source, mostly apache.
<ulfdoz> It is solely a matter of time. After 12hrs of work, there is not really any private project.
<ulfdoz> A nice project would be, to get a full parallel gc into ocaml, but that is definitely not a one-man-show.
<thelema> by private, I mean more like one's major project which you're spending lots of time on
<thelema> private to your company or just for your own personal use
<thelema> which I imagine you don't get to do in ocaml, as you're a java dev.
<thelema> (which has got to suck)
<ulfdoz> doesn't matter, I did ocaml, when I had time for it. I can definitly "restart" it, as I just did C++ last year. I do not think it is hard to learn a language, it is just hard to understand a language.
<ulfdoz> But given, that there are about 10 major programming laguages, it is impossible, to develop an excerise in all of them.
<ulfdoz> s/excerise/expertise/
<dark> ulfdoz, i heard that what prevents that is some kind of performance penalty
<dark> but i would like that too @.@
<dark> i see that ghc has parallel gc
<ulfdoz> dark: How big is the performance penalty if a each 300EUR netbook is a dual core?
<ulfdoz> Single-Core can be detected and done different.
* dark doesn't know
LeNsTR has joined #ocaml
<ulfdoz> Java had dropped the famous "stop-the-world-assumption" during gc-cycles. That was an absolutly big win.
<kaustuv_> thelema: yet another proposed addition to batteries: https://github.com/chaudhuri/batteries-included/commit/aa1cd8e721bd67c6f1b7bbf6335863bccdb04259
<kaustuv_> (sorry to unload so many on you at once...)
<kaustuv_> ((don't merge it yet, I need to clean up the commit message and some comments...)
<ulfdoz> lisp had a full parallel and distributed gc in the 80s. Still one of the fastest known implementations.
jm_ocaml has quit [Remote host closed the connection]
<dark> i once (a bunch of times?) argued for parallel gc and other kind of automatic parallelism here. i forgot which arguments for current ocaml implementation was given, but it seems that most people think that just 2 cores doesn't justify bothering with that
<dark> but there won't be just two cores
<ulfdoz> 2cores + ht makes almost 4. 4 cores physical, no problem.
<ulfdoz> The thing is, it won't get better, I assume, the number of cores will grow, as frequency cannot really anymore.
<ulfdoz> PPC is at 6GHz now, x86 at about 3.5GHz, all of them are multicore.
<ulfdoz> There are other processor designs like Sun T2000, which have 16 cores. I cannot imagine, that a single-threaded gc performs well there.
ftrvxmtrx has joined #ocaml
<thelema> kaustuv_: no relation to cf_lib's functional dequeues?
spicey has joined #ocaml
<thelema> the question isn't whether ocaml will go multicore - that it will. The question is whether it'll go SMP, and the answer seems to be no, as you can't have 16 SMP cores (unless the threeleaf guys succeed)
<kaustuv_> thelema: I wasn't aware of cf_lib. The underlying algorithms are ancient, of course.