flux changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | Grab OCaml 3.10.2 from http://caml.inria.fr/ocaml/release.html (featuring new camlp4 and more!)
jeremiah has quit [Remote closed the connection]
Axioplase is now known as Axioplase_
Jeff_123 has joined #ocaml
bluestorm_ has quit [Remote closed the connection]
Myoma has quit ["Leaving"]
ikatz has joined #ocaml
palomer has joined #ocaml
<palomer> http://pastebin.eu/pastebin.php?show=11301 <--this program gives me an error
<palomer> it should open firefox
<palomer> tells you how to compile it
<thelema|away> hi palomer
thelema|away is now known as thelema
<thelema> "Error: no display specified"?
<thelema> let (in_c,out_c,err_c) = open_process_full str (Unix.environment ()) in
<thelema> now it works.
<palomer> cool!!
<palomer> doubly cool
<thelema> X programs need the environment to find their display.
<thelema> and 2 minutes of googling found that line of code elsewhere.
<palomer> what did you googl?
<palomer> google
<thelema> "open_process_full" -- result 7 or so.
<thelema> savonet.rastageeks.org/changeset/5103
<palomer> ahh, gotcha
<palomer> I usually google the error
<palomer> that's triply cool
<palomer> now I don't need to do silly stuff like export PATH=/usr/bin
cmeme has quit [zelazny.freenode.net irc.freenode.net]
sbok has quit [zelazny.freenode.net irc.freenode.net]
hnr has quit [zelazny.freenode.net irc.freenode.net]
ulfdoz has quit [zelazny.freenode.net irc.freenode.net]
Amorphous has quit [zelazny.freenode.net irc.freenode.net]
shortc|desk has quit [zelazny.freenode.net irc.freenode.net]
det has quit [zelazny.freenode.net irc.freenode.net]
hcarty has quit [zelazny.freenode.net irc.freenode.net]
jdev has quit [zelazny.freenode.net irc.freenode.net]
bacam has quit [zelazny.freenode.net irc.freenode.net]
Hadaka has quit [zelazny.freenode.net irc.freenode.net]
flux has quit [zelazny.freenode.net irc.freenode.net]
sporkmonger has quit [zelazny.freenode.net irc.freenode.net]
coucou747 has quit [zelazny.freenode.net irc.freenode.net]
TaXules has quit [zelazny.freenode.net irc.freenode.net]
ertai has quit [zelazny.freenode.net irc.freenode.net]
mwhitney has quit [zelazny.freenode.net irc.freenode.net]
Smerdyakov has quit [zelazny.freenode.net irc.freenode.net]
munga has quit [zelazny.freenode.net irc.freenode.net]
Amorphous has joined #ocaml
hcarty has joined #ocaml
jdev has joined #ocaml
det has joined #ocaml
ulfdoz has joined #ocaml
bacam has joined #ocaml
shortc|desk has joined #ocaml
flux has joined #ocaml
Hadaka has joined #ocaml
sporkmonger has joined #ocaml
coucou747 has joined #ocaml
TaXules has joined #ocaml
cmeme has joined #ocaml
ertai has joined #ocaml
mwhitney has joined #ocaml
sbok has joined #ocaml
hnr has joined #ocaml
Smerdyakov has joined #ocaml
munga has joined #ocaml
bluestorm has joined #ocaml
travisbemann has joined #ocaml
shortc|desk has quit [K-lined]
coucou747 has quit ["bye ca veut dire tchao en anglais"]
jeddhaberstro has quit []
Lalu has quit [Read error: 110 (Connection timed out)]
Snark has joined #ocaml
Kopophex has quit [Read error: 110 (Connection timed out)]
Kopophex has joined #ocaml
ygrek has joined #ocaml
netx has joined #ocaml
Associat0r has quit []
code17 has joined #ocaml
code17 has quit [Remote closed the connection]
code17 has joined #ocaml
code17 has quit [Remote closed the connection]
code17 has joined #ocaml
seafood has joined #ocaml
Jeff_123 has quit []
ygrek has quit [Remote closed the connection]
ygrek has joined #ocaml
Jeff_123 has joined #ocaml
Jeff_123 has quit []
seafood_ has joined #ocaml
seafood has quit [Read error: 104 (Connection reset by peer)]
fremo has joined #ocaml
seafood_ has quit [Read error: 104 (Connection reset by peer)]
seafood has joined #ocaml
mishok13 has joined #ocaml
munga_ has joined #ocaml
asmanur has joined #ocaml
hkBst has joined #ocaml
asmanur has quit ["Lost terminal"]
asmanur has joined #ocaml
test has joined #ocaml
test is now known as Asmadeus
Kopophex has quit ["Leaving"]
ygrek has quit [Remote closed the connection]
Demitar has joined #ocaml
Demitar_ has joined #ocaml
Demitar has quit [Connection timed out]
seafood has quit []
Demitar has joined #ocaml
guillem_ has joined #ocaml
Demitar_ has quit [Read error: 110 (Connection timed out)]
seafood has joined #ocaml
code17 has quit [Remote closed the connection]
Yoric[DT] has joined #ocaml
seafood has quit []
code17 has joined #ocaml
<Camarade_Tux> hi
<Camarade_Tux> I've written a Patricia tree over strings and am happy with performance (about the same as Hashtbl) but I need to test it more and for this, I need big data sets
<Camarade_Tux> I need strings with lots of words, until now I've used the bible but it happens that out of 975_000 words, only 22_000 are unique
<mfp> Camarade_Tux: maybe the Reuters-21578 corpus? http://www.daviddlewis.com/resources/testcollections/reuters21578/
<mfp> you could also look for the TREC corpora
<bluestorm> Camarade_Tux: could you not randomly generate a corpus ?
<mfp> + project gutemberg
<bluestorm> or maybe you could hm
<bluestorm> shuffle the characters of the bible words ?
<mfp> bluestorm: if he's going to use it for real text, something with a realistic distribution is better
<bluestorm> you've got plenty of permutations, you could reuse the text several times
<mfp> oops *Gutenberg
seafood has joined #ocaml
Camarade_Tux_ has joined #ocaml
Camarade_Tux has quit [Read error: 110 (Connection timed out)]
travisbemann has quit ["leaving"]
<flux> camarade_tux_, running linux? find /usr/share/doc | xargs bzcat > corpus :)
lde has quit [Remote closed the connection]
lde has joined #ocaml
<Camarade_Tux_> flux, yeah, that's a pretty good idea, the corpus is currently sufficient though ;p (it's spending at least 60% of the time in the GC ! :argh: )
<Camarade_Tux_> and it seems I was disconnected before being able to reply :
<Camarade_Tux_> bluestorm: patricia trees are not meant for random data, of course they can handle it as well but it's better to use real word things
<flux> camarade_tux_, try tuning gc parameters
<Camarade_Tux_> mfp, I've download the corpus and am using it, that makes a nice test
<bluestorm> the default gc parameters are not aimed at fast-growing long-lived big data structures
<Camarade_Tux_> flux, I have GC settings at the beginning of my test file but I'd prefer not having to tweak the GC
<flux> camarade_tux_, yes, but for high performance, it can be unavoidable. performance might not matter that much, though
<bluestorm> can't you tweak the GC from the command-line parameters ?
<flux> you can
<bluestorm> this is more flexible as the tweaking will need to be adjusted to do real-case input data
<bluestorm> (do you really intend to use that much data for your patricia tree ?)
<Camarade_Tux_> well, I also think I can improve my program to reduce allocations so I'll try but then I'll probably change the GC settings before adding lots of data to the tree and then restore them
<Camarade_Tux_> bluestorm, no of course, I just need the mime types so less than 100k entries, but I'm playing with it ;)
<flux> coincidentally a guy on #c++/IRCNet also wrote a patricia tree implementation, I wonder how the performance compares :)
<Camarade_Tux_> well, I can add all the corpus in about 4.4s =)
<Camarade_Tux_> (with gc tweaked)
<flux> that 21578-corpus?
<Camarade_Tux_> yes ;p
<Camarade_Tux_> the bible only took 0.8s (with the gc untweaked I think), that's why I needed something bigger =P
<bluestorm> you mean, 0.8 with profiling enabled ?
<Camarade_Tux_> no, without profiling enabled, I'm using top so it only measure cpu-time but it's rather accurate
Camarade_Tux_ is now known as Camarade_Tux
<Camarade_Tux> it's only slightly slower with profiling
<flux> 'using top'?
bohanlon has joined #ocaml
<thelema> Camarade_Tux: 'time'?
<thelema> let time_f f x = let t0 = Sys.time () in let fx = f x in (Sys.time () -. t0, fx)
<Camarade_Tux> thelema, top lets me monitor memory usage which is important too and I've put some Sys.command "read" in my code so I can measure add/find perf for various structures
<Camarade_Tux> flux, top, as in /usr/bin/top
<thelema> but how do you get the final CPU time? if I monitor with top, the entry disappears when the program quits
<flux> camarade_tux, /usr/bin/time might give you memory stats
<Camarade_Tux> I also have a Sys.command "read" at the end of the program ;)
seafood has quit [Read error: 104 (Connection reset by peer)]
<Camarade_Tux> flux, I don't have the memory stats : " (0avgtext+0avgdata 0maxresident)k"
seafood has joined #ocaml
Anarchos has joined #ocaml
<flux> maybe you can multiply minor page faults with 4?-)
seafood has quit [Client Quit]
<flux> I'm not sure if that stuff even works on linux
<thelema> ah... maybe "let _ = read_line ()" would be useful for you - no spawning external processes.
<flux> atleast %K doesn't work
hkBst has quit [Read error: 104 (Connection reset by peer)]
hkBst has joined #ocaml
<Camarade_Tux> thelema, that was really a quick-and-dirty thing I probably wrote at 1am, the time taken by Sys.command is really small but you're right, I should change it
<Camarade_Tux> also, top lets me check my system is otherwise idle, especially because of this stupid firefox when gmail is not in "simplified interface", it can take 20% of one cpu when idling :cough:
<thelema> com: but if you measure cpu time, why would idle matter?
l_a_m has joined #ocaml
<Camarade_Tux> I'm not specifically trying to mesure cpu time, but it happens that top shows that and that top is the most-straightforward way to measure both cpu and memory usage
Anarchos has quit ["Vision[0.8.5-0418]: i've been blurred!"]
Anarchos has joined #ocaml
Myoma has joined #ocaml
Jedai has joined #ocaml
coucou747 has joined #ocaml
marmotine has joined #ocaml
bla has quit [Read error: 110 (Connection timed out)]
Associat0r has joined #ocaml
comglz has joined #ocaml
Anarchos has quit ["Vision[0.8.5-0418]: i've been blurred!"]
bla_ has joined #ocaml
pango_ has quit [Remote closed the connection]
<hcarty> rwmjones: ping
<rwmjones> hcarty, pong
<hcarty> I'm not sure if your "plotting points" blog post was simply venting some steam, but the PLplot bindings may be useful for a task like you mentioned
<rwmjones> heh, yes
jeddhaberstro has joined #ocaml
<rwmjones> top 10 in reddit at the moment though
<hcarty> One of the plotting devices supported in PLplot is Cairo, and the C library allows you to provide a Cairo context to the plotting routines - this could allow for embedding in a Gtk+ app and is on my eventual TODO list for the bingings
bla_ has quit [Read error: 60 (Operation timed out)]
pango_ has joined #ocaml
bla has joined #ocaml
jeddhaberstro has quit []
coucou747 is now known as Agent_Rouge
Agent_Rouge has quit ["bye ca veut dire tchao en anglais"]
Agent_Rouge has joined #ocaml
Agent_Rouge is now known as coucou747
jeddhaberstro has joined #ocaml
munga_ has quit ["Ex-Chat"]
Axioplase_ is now known as Axioplase
bluestorm has quit ["Leaving"]
Asmadeus has quit ["brb"]
Asmadeus has joined #ocaml
jlouis has joined #ocaml
lde has quit [Connection timed out]
sporkmonger has quit []
rwmjones has quit ["Closed connection"]
lde has joined #ocaml
l_a_m has quit [Remote closed the connection]
rwmjones has joined #ocaml
rwmjones has quit [Client Quit]
mishok13 has quit [Connection timed out]
sporkmonger has joined #ocaml
rwmjones has joined #ocaml
ygrek has joined #ocaml
pango_ has quit [Remote closed the connection]
fy___ has joined #ocaml
pango_ has joined #ocaml
bluestorm has joined #ocaml
* Yoric[DT] is experiencing the joys of boss-siting.
<Yoric[DT]> My boss will grasp *any* vague pretense to stop working and start complaining instead.
<Yoric[DT]> (by opposition to me, who can easily complain while working)
<palomer> boss-siting?
ygrek has quit [Remote closed the connection]
<palomer> sounds french
<Yoric[DT]> Well, it really feels like baby-sitting.
<Yoric[DT]> Except the big fat ugly rotten baby is replaced by the boss.
<palomer> mmmm
<palomer> rotten babies
<palomer> btw, how do I create a cma file?
<Yoric[DT]> -a
<palomer> and then I can use the cma file to compile anything that depends on that module?
<Yoric[DT]> You still need the cmi.
<palomer> oh my
<palomer> so how do I set up my build environment in make?
<Yoric[DT]> With blood and sweat.
<palomer> seriously
<palomer> :P
<Yoric[DT]> Or you can use ocamlbuild or OCamlMakeFile or omake.
<palomer> how do I compile each module seperately?
<Yoric[DT]> I have switched to ocamlbuild, personally.
<palomer> ocamlbuild is built on omake, no?
<bluestorm> isn't
<Yoric[DT]> nope
<Yoric[DT]> No relation whatsoever.
<mbishop> ocamlbuild is newer
<palomer> and better?
<bluestorm> more caml-specific
<palomer> easier to use?
<Yoric[DT]> I like ocamlbuild.
<Yoric[DT]> It's imperfect but it's easy to use.
<palomer> imperfect as in not general enough?
* Yoric[DT] should return to proof-reading a PhD.
<Yoric[DT]> It can be customized with OCaml-based plug-ins.
<bluestorm> i've only tried it once, with the ocamlfind plugin, and it's nice
<Yoric[DT]> But you can only have one plug-in at a time.
<Yoric[DT]> The next version should fix that, though.
<Yoric[DT]> Plus it's general enough to be used in the official distribution to compile OCaml.
<bluestorm> (does it compile the whole distribution, or only parts relying on the oldschool system in other places ? i'm not sure actually)
<Yoric[DT]> I haven't checked.
* Yoric[DT] should really return to proof-reading a PhD.
<palomer> off the top of the head, is the signal the widget emits when you click on the x symbol on the top right called "destroy" ?
<palomer> top of _your_ head
<bluestorm> no idea
Asmadeus has quit ["Lost terminal"]
Asmadeus has joined #ocaml
asmanur has quit [Read error: 110 (Connection timed out)]
seanl has joined #ocaml
seanl has left #ocaml []
Snark has quit ["Ex-Chat"]
Snark has joined #ocaml
Snark has quit [Read error: 104 (Connection reset by peer)]
fy___ has quit [Connection timed out]
hkBst has quit ["Konversation terminated!"]
seafood has joined #ocaml
Amorphous has quit [Read error: 110 (Connection timed out)]
seafood has quit []
seafood has joined #ocaml
Amorphous has joined #ocaml
mgodshall has joined #ocaml
Demitar has quit [Read error: 110 (Connection timed out)]
seafood has quit []
Asmadeus has quit ["cya !"]
guillem_ has quit [Remote closed the connection]
seafood has joined #ocaml
seafood has quit [Client Quit]
det has quit [Remote closed the connection]
Yoric[DT] has quit ["Ex-Chat"]
roy_hu has quit [Read error: 104 (Connection reset by peer)]
det has joined #ocaml
<palomer> can someone remind me the guard syntax in ocaml
<bluestorm> | ... when ... ->
<bluestorm> | n when n < 0 -> ...
<palomer> whoa, same as haskell
<bluestorm> nope
code17 has quit [Remote closed the connection]
<bluestorm> iirc haskell is | n < 0 == ... or something like that
<bluestorm> while the OCaml guards are a supplement to pattern matching
<bluestorm> you still have a pattern (wich i don't think Haskell guards have), so the use is a little different
<palomer> for example?
<bluestorm> hmm
<bluestorm> you can use it as Lisp's cond (wich is more or less what haskell guards is about iirc), but it is not the main use case : you mostly use it to affine your clause selection in a pattern matching
<bluestorm> -is+are
<bluestorm> eg.
<bluestorm> let rec insert x li = function [] -> [x] | (hd::_) as li when hd > x -> x::li | hd::tl -> hd :: insert x tl
<bluestorm> ("as" is the reversed haskell @)
<palomer> you can't write that code in haskell?
<Myoma> of course you can
<bluestorm> but differently
<bluestorm> (again, i haven't checked just now, and i'm a Haskell reader, not writer, so i may have forgotten something)
code17 has joined #ocaml
<bluestorm> i guess the haskell version would be like
<bluestorm> insert x [] = [x]
marmotine has quit ["mv marmotine Laurie"]
<bluestorm> insert x li@(hd:tl) | hd <= x = x:li | otherwise = hd : insert x tl
<bluestorm> wich is quite different because guards don't match anything
<palomer> call me thick, but those two pieces of code look very much alike
<bluestorm> well, guards as a language features aren't used the "same" way, that's all i was saying
<Myoma> palomer: that's because they both do the same thing in the same way in similar languages
<Myoma> (except for using <= instead of >)
<bluestorm> ocaml guards are used in conjuction with the matching itself
<bluestorm> Haskell guards could be seen as a nice sugar over if ... else if ... else if ...
<bluestorm> (nice, nice; i hate that confusing syntax)
<Myoma> you can view it as syntax sugar for eliminator calls too
jeddhaberstro has quit []
<bluestorm> what are eliminators ?
<Myoma> actually I'm not sure how guards would be fit into that
<Myoma> for list, elimList nil cons = function [] -> nil | x::xs -> cons x xs;;
<Myoma> so you can compile down pattern matching into nests of these
<Myoma> but do guards fit into it ?
<bluestorm> hm
<palomer> but, erm, aren't ocaml guards also just sugar over if ... else if ... else if ...
<bluestorm> they are not
<Myoma> palomer: everything can a
<bluestorm> hm
<bluestorm> i mean, there is not trivial translation
<Myoma> be thought of as sugar for lambda , or so on
<bluestorm> you can do quite sophisticated things
<palomer> bluestorm, for example?
<bluestorm> such as | a::_ when pred1 a -> ... | a::b::_ when pred2 c -> ... | (0::li) | li when pred3 li -> ...
<bluestorm> i do sophisticated in-list lookup based on the former guards results
<bluestorm> of course, it is also possible to abuse guards and write unreadable code (these tools can turn dangerous)
<Smerdyakov> Guards are trivial to compile to guard-free code with a local function definition for each original body.
code17 has quit [Remote closed the connection]
<Smerdyakov> It's only a matter of 1) code-size savings and 2) following the programmer's train of thought linearly.
code17 has joined #ocaml
<bluestorm> Smerdyakov: you mean the 'a -> 'b option functional representation of clauses ?
<palomer> bluestorm, but the corresponding haskell code would be identical!
<palomer> unless I"m missing something
code17 has quit [Remote closed the connection]
code17 has joined #ocaml
code17 has quit [Client Quit]
<bluestorm> hm
<Myoma> anyway diffing against the language you previously knew isn't a good way to learn
<bluestorm> palomer: one of us two is certainly missing something
<bluestorm> i encourage you to go and write the Haskell version