mbishop 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!)
Kopophex has quit [Read error: 110 (Connection timed out)]
Kopophex has joined #ocaml
|jeremiah has quit ["KVIrc 3.2.6 Anomalies http://www.kvirc.net/"]
mibX has joined #ocaml
<mibX> just wandering anyone done any large projects in ocaml?
<mibX> also why is haskell more popular? whats the difference between the two?
smimou has quit [Read error: 110 (Connection timed out)]
mibX has quit ["http://www.mibbit.com ajax IRC Client"]
dlomsak has left #ocaml []
eelte has quit ["bye ca veut dire tchao en anglais"]
smimou has joined #ocaml
jknick has joined #ocaml
Kopophex has quit [Read error: 110 (Connection timed out)]
Kopophex has joined #ocaml
yziquel has quit [Read error: 104 (Connection reset by peer)]
ziph has joined #ocaml
fremo has quit [Remote closed the connection]
hsuh has joined #ocaml
fremo has joined #ocaml
ziph has quit []
det has joined #ocaml
paganini123 has joined #ocaml
paganini123 has quit [Client Quit]
postalchris has joined #ocaml
postalchris has quit [Client Quit]
alexyk has joined #ocaml
|Catch22| has quit ["To the best of my knowledge, I guess that I'm fresh"]
alexyk has quit []
mbishop_ has joined #ocaml
alexyk has joined #ocaml
dibblego has joined #ocaml
mbishop has quit [Read error: 110 (Connection timed out)]
<palomer_> when should I use class types versus virtual classes?
<flux> I haven't really understood that. but I've just used virtual classes when I actually do inheritance, and class types for declaring interfaces.
alexyk has quit []
<palomer_> interfaces?
<palomer_> for example?
<flux> "virtual classes" with no method implementions
<flux> I grepped and found this: class type obj = object method step : float -> unit method render : unit -> unit end
<flux> also I've used class type for working around the lack of mutual module recursion
<flux> so I have two classes which need to refer to each other, but they are defined in different modules
<flux> so I will have a module which defines the types for both classes
<flux> (using mutual recursion)
<palomer_> right now I'm declaring virtual classes with no implementations
<palomer_> and then I'm inheriting from those classes
<palomer_> how would I do that with class types?
<palomer_> btw, what characters can ocaml identifiers have?
<palomer_> (letter∣ _) { letter∣ 0…9∣ _∣ ' }
bluestorm has joined #ocaml
alexyk has joined #ocaml
schme has joined #ocaml
yziquel has joined #ocaml
Kopophex has quit [Read error: 110 (Connection timed out)]
travisbemann has joined #ocaml
naufraghi has joined #ocaml
ikaros has joined #ocaml
<det> I thought Ocaml had mutually recusive modules.
<travisbemann> not to my knowledge at least
<travisbemann> (i myself wish it allowed recursive modules...)
<flux> det, yes, but not when they are in different files
<det> Ahh, I just made an example but now I see what you mean.
<travisbemann> how do you declare two modules to be mutually recursive then?
<palomer_> it does!
<palomer_> travisbemann, they have to be in different files
<palomer_> OR, if their signatures aren't mutually recursive, you can fake it with functors
<palomer_> flux, how do you use an interface?
<travisbemann> okay, that is of little use... (considering that i tend to often use submodules a lot to essentially closely associate functions with types)
<det> Yeah, I tend to use submodules in the same way.
<travisbemann> part of it is that i honestly don't really like the ocaml object system, and prefer to use the module system to provide modularity alone
<bluestorm> i think that in general it is often a good idea to decouple such dependencies to have a non-cyclic dependency tree
<bluestorm> by trying to do that you'll often have insights on how to simplify, or generalize, your design
<det> travisbemann, I think the object system can be useful to express generic interfaces. You can use closures instead, but that means your initialization is linear to the number of record members (or "methods") instead of O(1) with objects.
<bluestorm> (for example switching the common part in a little submodule can ease the reuse of this part in the future)
<travisbemann> det: i would be more inclined to use the ocaml object system if it were something more along the lines of CLOS, such that it would be intrinsically centered around multiple method dispatch as opposed to dispatched methods belonging to particular objects
<det> Same with space.
lety has joined #ocaml
<det> I'd prefer type classes.
<bluestorm> i don't think type classes and the ocaml object system are equivalent at all, or even intended to the same purpose
<travisbemann> for a static language like ocaml, a more haskellish type class system might be more appropriate, but one way or another i strongly favor using methods which do not actually belong to particular objects
<det> type classes can express the part of the ocaml object system that I think is useful.
dibblego has quit ["Leaving"]
<bluestorm> travisbemann: i think you can use this type of programming within the ocaml object system
<bluestorm> # let use_foo_object obj = obj#foo;;
<bluestorm> val use_foo_object : < foo : 'a; .. > -> 'a = <fun>
<travisbemann> that's part of why i prefer to just use a module-system based approach rather than actually using the object system
<travisbemann> even if i have to go and use closures to gain the actual functionality of the object system
<bluestorm> (i may not understand what you mean, as i'm quite unfamiliar with object systems in general, but that doesn't look like belonging to any object/class)
<travisbemann> but at an implementation level that really still is using a method belonging to an object
<bluestorm> hmm
<travisbemann> as opposed to with true multiple dispatch, where methods really do not belong to objects and where methods can be added by the programmer after the fact rather than being intrinsically declared with classes
<lety> just wandering does ocaml have bindings to win32 api?
<bluestorm> lety: i've seen some
<bluestorm> look at the hump
<lety> the hump?
<lety> thanks
<lety> the list looks really short
<lety> 10 or so libs
* travisbemann wonders, though, how you would actually implement multiple dispatch within an ocaml-like model....
<lety> thats a bit sad
<lety> haskell has at least 100
<bluestorm> lety: wich list ?
<lety> the one you gave me a link to
<det> I think you are confusing "latest updates" with "complete list of ocaml libraries".
<lety> oh
<alexyk> GODI installs things into pkg-lib/ alongside std-lib/ and site-lib/, so if I want to add extlib.cmxa I have to give this funny path to ocamlopt: -I +../pkg-lib/extlib
<alexyk> anything better?
<bluestorm> you could use ocamlfind
<alexyk> yeah, but bare knuckles -- is there an environment variable pointing to the root of std-lib/ or std-lib?
<bluestorm> ocamlc -where ?
<alexyk> right-right... so GODI basically assumes you'll use ocamlfind to get pkg-lib stuff I see, no nice manual way to add it as with -I +blah
<det> -I `ocamlfind query extlib` isn't that bad, is it?
<alexyk> looks good, especially after aliasing "ocamlfind query" to oq or something
<bluestorm> then oq ocamlc -package extlib -linkpkg foo.ml should not be that bad either
znutar has left #ocaml []
fremo has quit [Read error: 104 (Connection reset by peer)]
fremo has joined #ocaml
yangsx has left #ocaml []
lety has quit ["http://www.mibbit.com ajax IRC Client"]
<alexyk> what environment variable increases recursion stack size?
<bluestorm> alexyk: iirc you can tweak it if "ulimit -s"
<alexyk> tried that -- strangely, a DynArray-based program sefaults where Array-based one works
<bluestorm> bytecode or nativecode ?
<alexyk> I remember setting some CAMLBLAH... both
<alexyk> both byte and opt segfault with DynArray with no more explanation at the array size about 30000 ints
<alexyk> the only thing I do differently there is insert in sorted order
<alexyk> and it works on small inputs
<alexyk> when I had a too deep recursion stack I set something a month ago and it extended, and it was an environment variable
<bluestorm> ah
<bluestorm> CAMLRUNPARAM ?
<alexyk> ulimit doesnt cu it
<alexyk> yes!
<bluestorm> this is bytecode-specific iirc
<alexyk> ah
<bluestorm> hm actually (O)CAMLRUNPARAM is used by ocamlopt too, but the stacksize-related option is ignored
<bluestorm> because native code use the OS/kernel/native/whatever call stack
schme has quit [Remote closed the connection]
<bluestorm> alexyk: could you show your code ?
schme has joined #ocaml
<alexyk> bluestorm -- 1 sec
<alexyk> Array version is cookin' right as we speak
<alexyk> it reads triplets (movie,customer,rating) where customers are not in order
<bluestorm> hm btw
<alexyk> maps them onto consecutive 1..N range and reprints triplets
<bluestorm> i just noticed that you can tweak GC parameter with OCAMLRUNPARAM, this will be useful in the future
<bluestorm> indirect thanks to alexyk :]
<alexyk> bluestorm: beginner's luck :)
<flux> palomer_, whenever I would need to use an actual object, I can accept an argument with the interface type
<bluestorm> hm
<bluestorm> alexyk: it might come from List.map
<bluestorm> the standard List.map is not tail-recursive
<bluestorm> try to use Extlib's List.map instead
<bluestorm> or, if your problem allows it, List.rev_map
<bluestorm> hmm
<alexyk> my lines are all triplets very short
<bluestorm> actually it seems your List.map use is very specific to short lines
<bluestorm> yes
<alexyk> so that List.map just breaks a line into 3 numbers
<bluestorm> this part is not very elegant btw
<bluestorm> maybe you could do with
<flux> alexyk, does it produce a core dump?
<bluestorm> Scanf.sscanf " %d %d %d" ?
<flux> you could use gdb to find out where it crashes
<flux> (if that was the problem)
<alexyk> bluestorm -- yes, cool
<bluestorm> (wich is waiting for a (int -> int -> int -> 'a) function
<bluestorm> )
<bluestorm> hm
<alexyk> flux: no core dump! zsh says segfault or bus error
<bluestorm> and why don't you use a dichotomy/bisection instead of your linear search ?
<flux> alexyk, ulimit -c unlimited
<alexyk> after I tweaked the script
<alexyk> bluestorm: hacked after midnight for a quick result!
<bluestorm> :D
<bluestorm> (let infinity = max_int might suit your needs)
<alexyk> btw -- why can't I define two functions with let prescan = ... and renumber = ... ?
<alexyk> I can `and' two values but not two functions?
<bluestorm> yes you can
<bluestorm> but not "and rec"
<bluestorm> "rec" is a global property to the whole "... and ... and .." declaration
<bluestorm> so you only put one after the let
<alexyk> so my prescan and renumber are rec each but not mutually
<bluestorm> hm
<alexyk> will it know what to do?
<bluestorm> you should not use "and" if your functions are not mutually recursive
<bluestorm> it will works, but confuse the reader and may induce strange behavior if you're not careful
naufraghi has left #ocaml []
<alexyk> but then I have to do let f1 = ... in let f2 = ... while f2 i not uding f1
<bluestorm> (eg. if you use a previously-defined variable named "renumber" in the prescan declaration)
<alexyk> using
<bluestorm> yes, what's the problem with that ?
<alexyk> syntax hints we define some vars for subsequent use in the rest; so I'd rather define mutually independent things with and
<bluestorm> another trick (this time not applicable to functions) is let a, b = ... , ..... Can be nice for example in let xlen, ylen = 800, 600 in (even more readable than "and" imho)
<alexyk> ah nice
<bluestorm> alexyk: ocaml programmers are used to a list of "let .. in" , that won't disturb them
<bluestorm> while using "and" will have them looking for mutual recursion
<alexyk> ...that's why I so much prefer #light syntax of F#! :)
<alexyk> no meaningless "in"s
<bluestorm> hm
<bluestorm> if you want light syntax, you could begin with taking the ";;" away
<alexyk> it's just glue then, not var-body
<bluestorm> btw, you could use TWT
<alexyk> yeah, unnatural to tuareg
<bluestorm> and finally, the revised syntax (wich is not perfect unfortunately) provides a "where" construct
<bluestorm> wich is quite nice imho
<bluestorm> hmm
<bluestorm> the intended URL was http://people.csail.mit.edu/mikelin/ocaml+twt/
<alexyk> F# rocks, ocaml has no choice to emulate #light imho
<bluestorm> hm
<alexyk> when my neighboring MSFT geeks get on F# bandwagon en masse
<bluestorm> alexyk: the TWT page provides some emacs tweaking
<alexyk> (no choice but)
<bluestorm> aren't they ok ?
<alexyk> I feel I need to learn the ugly in's first :)
<alexyk> prettifying after learning
<bluestorm> (and i don't see why we couldn't emulate #light, using twt or camlp4)
<bluestorm> i never had any problem with "in" with are a quite minor syntaxic issue
<alexyk> there was a thread on ocaml-list saying #light is very hard in camlp4 for some reason
<alexyk> in any case... Array version finished fine, so DynArray hits some limit or a bug -- will hunt tmrw... night!
<bluestorm> alexyk: if you have the URL of that #light discussion, i'd be interested
<bluestorm> btw
<bluestorm> if you have an idea of your final array length
<bluestorm> DynArray is not necessary at all
<alexyk> 500000
<alexyk> yeah, I just practice DynArray
<bluestorm> why not :p
<alexyk> but when I practice and it fails, it bugs me!
<alexyk> and it works on any short inputs... will hunt tmrw -- no coredump in sight either
<flux> alexyk, ulimit didn't help?
<alexyk> flux: ah! will cook some dumps tmrw, thx!
<alexyk> btw -- how do I debug ocamlopt binaries, compiling with -g and gdb as usual C?
<tsuyoshi> ocamldebug
<alexyk> ah
<tsuyoshi> you can debug the c parts of a program with gdb but not the ocaml parts
<alexyk> okok nighty-night US Pacific shores...
alexyk has quit []
Linktim has joined #ocaml
OChameau has joined #ocaml
Yoric[DT] has joined #ocaml
jonafan_ has joined #ocaml
LordMetroid has joined #ocaml
magthe has joined #ocaml
jonafan has quit [Read error: 110 (Connection timed out)]
jonafan has joined #ocaml
jonafan_ has quit [Read error: 110 (Connection timed out)]
jknick has quit ["Lost terminal"]
Demitar has quit [Read error: 110 (Connection timed out)]
LordMetroid has quit [Read error: 110 (Connection timed out)]
Yoric[DT] has quit ["Ex-Chat"]
jonafan_ has joined #ocaml
jonafan has quit [Read error: 110 (Connection timed out)]
jonafan has joined #ocaml
jonafan_ has quit [Read error: 110 (Connection timed out)]
m3ga has joined #ocaml
Linktim_ has joined #ocaml
jonafan_ has joined #ocaml
Linktim has quit [Read error: 110 (Connection timed out)]
coucou747 has joined #ocaml
schme has quit [Connection timed out]
jonafan has quit [Read error: 110 (Connection timed out)]
Linktim_ has quit [Read error: 110 (Connection timed out)]
hkBst has joined #ocaml
hsuh has left #ocaml []
det has quit [Remote closed the connection]
r0bby has quit [Client Quit]
rwmjones has quit [Success]
Linktim has joined #ocaml
filp has joined #ocaml
<flux> cool, this works: class type a = object method a : int end class type b = object method b : int end let a ((a:#a):#b) = () - dunno what use it is, though :)
<bluestorm> you mean, specifying several contraints ?
<flux> it's not actually a constraint, it folds open to type <a : int; b: int; ..>
<flux> (well I suppose it is? but it doesn't really look like multiple constraints)
<bluestorm> that's a constraint somehow, "must contain ..."
<bluestorm> in case of multiple inheritance maybe ?
LordMetroid has joined #ocaml
magthe has quit ["Ex-Chat"]
<flux> I sort of like ocaml's object system, although I must admit it is complicated and often requires explicit annotation of types
<flux> but I have that explicit annotation problem anyway as I have functions like with_db : (db_handle -> 'a) -> 'a which I need to pass as a parameter
<travisbemann> /exit
travisbemann has quit ["leaving"]
det has joined #ocaml
jonafan has joined #ocaml
pango_ has quit [Remote closed the connection]
pango_ has joined #ocaml
Linktim_ has joined #ocaml
Linktim has quit [Read error: 110 (Connection timed out)]
jonafan_ has quit [Read error: 110 (Connection timed out)]
rwmjones has joined #ocaml
magthe has joined #ocaml
LordMetroid has quit [Read error: 110 (Connection timed out)]
LordMetroid has joined #ocaml
postalchris has joined #ocaml
ikaros_ has joined #ocaml
Yoric[DT] has joined #ocaml
TychoBrahe has quit ["KVIrc 3.2.6 Anomalies http://www.kvirc.net/"]
TychoBrahe has joined #ocaml
ikaros has quit [Read error: 110 (Connection timed out)]
Linktim- has joined #ocaml
delamarche has joined #ocaml
pango_ has quit [Remote closed the connection]
Linktim_ has quit [Read error: 110 (Connection timed out)]
Linktim_ has joined #ocaml
pango_ has joined #ocaml
<kig> camltemplate native compiled is ~10x faster than bytecode ocsigen's xhtml.m, which is nice
<bluestorm> does camltemplate provide static output verification ?
<hcarty> What is the name for a type like: type 'a foo_t = { contents : 'a array } ? Is this a phantom type? I am unsure of the terminology
Linktim_ has quit [Read error: 110 (Connection timed out)]
Linktim- has quit [Read error: 110 (Connection timed out)]
<tsuyoshi> a phantom type would be like type 'a foo = int
<tsuyoshi> where the 'a is irrelevant in the end
<tsuyoshi> that foo_t would be a polymorphic type I guess
<kig> bluestorm: no.
<hcarty> tsuyoshi: Ok, thank you.
* Yoric[DT] agrees with hcarty.
* Yoric[DT] agrees with tsuyoshi, sorry.
<bluestorm> hcarty: incidentally, { contents : ... } is used by the "ref" type
<hcarty> bluestorm: Very good point...
<bluestorm> hm
<hcarty> The actual type is more along the lines of : { grid_contents : 'a array array ; missing : 'a ; resolution : float ; ... }
<bluestorm> seems there is no risk of conflicts anyway
<bluestorm> as implicitly, ref is { Pervasive.contents : 'a } while yours is { Mymodule.contents : ... }
<hcarty> Record name collisions are part of why I did my initial implementation of this code using classes.
<hcarty> It also provided an excuse to learn something about how to use OCaml classes and how they work
<bluestorm> :p
<bluestorm> i don't think record name collisions are so much of a problem
<hcarty> My concern came mainly from having segements of code like a.Foo.field.Bar.other
<bluestorm> btw, i just learned about an intriguing syntax extension that may be related to your problem : http://www.math.nagoya-u.ac.jp/~garrigue/code/ocaml.html, Polymap
<bluestorm> hm
<bluestorm> hcarty: then use pa_openin :]
<bluestorm> Yoric[DT]: have you asked for a git/darcs repository yet ?
<Yoric[DT]> svn for now
<hcarty> Oh, how I would love to... but camlp4 breaks #use in the toplevel, so I tend to avoid it when developing new code
<Yoric[DT]> I have never used git, I'm afraid.
<hcarty> Both the OO and Polymap extensions seem very nice though
<bluestorm> Yoric[DT]: could be a nice way to try
<hcarty> Yoric[DT]: I really enjoy git. darcs as well, but git a bit more
<Yoric[DT]> And I haven't looked at support for git/darcs in the Forge yet -- I'm in holidays, I'm afraid.
<Yoric[DT]> How is it different from darcs, for instance ?
<bluestorm> (i myself have only used darcs a bit, and quite like the distributed model)
<bluestorm> Yoric[DT]: faster, more complex, less sexy
<hcarty> I really like the in-place checkouts in git
<bluestorm> (and probably "more powerful" for some command-line-guru sense of powerful)
<hcarty> No need to create separate directories for new branches
<hcarty> The GUI tools for git are very nice as well (git-gui and gitk)
<Yoric[DT]> Well, as thelema is using git, I'm probably going to do so, too.
<Yoric[DT]> Let's keep some simplicity somewhere :)
<bluestorm> :p
<petchema> hcarty: type 'a foo_t = { contents : 'a array } is a parametric type
<petchema> (iirc)
<Yoric[DT]> Oh, and bluestorm, it seems to me that it would be quite easy to have a syntax for parser combinators with Camlp4.
<bluestorm> git is fine
Amorphous has joined #ocaml
<Yoric[DT]> Just reuse the stream parser syntax but use ExtLib's Enum.t instead of Stream.t .
<Yoric[DT]> Most functions even have the same name.
<bluestorm> hm
<bluestorm> so that you would have streams, without implicit update ?
<Yoric[DT]> You "just" need to invoke Enum.clone from time to time.
Linktim has joined #ocaml
<Yoric[DT]> Well, so that you could clone the streams.
<Yoric[DT]> Of course, doing it with lazy lists might be even easier.
* Yoric[DT] is currently reworking his lazy lists to integrate them to ExtLib.
<bluestorm> heh, interesting
* Yoric[DT] is also rewriting Genlex to get it to work with Enum and lazy lists.
<bluestorm> that's holydays for sure :]
<Yoric[DT]> :)
<Yoric[DT]> Well, I'm offline most of the time.
<Yoric[DT]> But when my fiancée is working, I have to work, lest I develop remorse.
<Yoric[DT]> Anyway, running out of batteries.
<Yoric[DT]> I have to go.
<Yoric[DT]> Cheers.
Yoric[DT] has quit ["Ex-Chat"]
<petchema> (mmmh ocaml-tutorial says polymorphic, or parametrized)
<bluestorm> i'd say a parametrized type and a polymorphic function
coucou747 has quit ["bye ca veut dire tchao en anglais"]
<bluestorm> would anyone know of an "UDP with OCaml" example ?
Morphous has quit [Read error: 110 (Connection timed out)]
det has quit [Remote closed the connection]
<flux> no, but should be essentially the same as in C
<bluestorm> that's what i told him
filp has quit ["Bye"]
Kopophex has joined #ocaml
coucou747 has joined #ocaml
psnively has joined #ocaml
munga has joined #ocaml
evn_ has joined #ocaml
<delamarche> Oh man lazy lists / better streams in Extlib would be brilliant.
<bluestorm> there are available as separate libraries
<delamarche> thanks bluestorm !
<bluestorm> s/there/they/
Linktim has quit [Read error: 104 (Connection reset by peer)]
<delamarche> oh my
<bluestorm> ( those are yoric's lazylists, but there are other impl. out there )
<delamarche> that's quite the subdomain
Linktim has joined #ocaml
<delamarche> thanks again :D
<bluestorm> :]
<bluestorm> last time i asked him to publish lazy lists as a library separated from his comprehension bundle, he said that was in progress, i guess he'll eventually do that for extlib integration
psnively has quit []
Kopophex has quit [Read error: 110 (Connection timed out)]
szell has quit [Read error: 110 (Connection timed out)]
magthe has quit ["Ex-Chat"]
filp has joined #ocaml
yziquel has quit [SendQ exceeded]
yziquel has joined #ocaml
yziquel has quit [Client Quit]
yziquel has joined #ocaml
OChameau has quit ["Leaving"]
rwmjones_ has joined #ocaml
kotarak has joined #ocaml
fremo has quit [Read error: 104 (Connection reset by peer)]
munga has quit ["Leaving"]
Linktim_ has joined #ocaml
evn_ has quit []
delamarche has quit []
jonafan_ has joined #ocaml
postalchris has quit ["Leaving."]
Linktim has quit [Read error: 110 (Connection timed out)]
<yziquel> Hello. Is there a command equivalent to objdump -x blahblah.o that can be executed on .cmo files?
<hcarty> yziquel: I don't know if it works with .cmo files, but ocamlbrowser provides a GUI for browsing OCaml interfaces. It may do what you want.
fremo_ has joined #ocaml
<yziquel> What I want is to check if my .cma (sorry, not .cmo) file has been compiled with the correct binding to some .o object file. That's why I'd like to check it with something similar to objdump or nm.
<flux> yziquel, there is objinfo, but I don't know if it does what objdump -x does
<yziquel> flux: Well, that seems nice. I'll have a look. Thanks.
yziquel has quit ["TinyIRC 1.1"]
yziquel has joined #ocaml
fremo_ has quit ["leaving"]
psnively has joined #ocaml
rodge has quit ["Leaving"]
jonafan has quit [Connection timed out]
jonafan_ is now known as jonafan
ygrek has joined #ocaml
<palomer_> is there a function like haskell's repeat?
<palomer_> of type int -> 'a -> 'a list
<flux> well.. no.. but let repeat n v = Array.to_list (Array.create n v) is an non-performant-but-simple way to do it
<hcarty> palomer_: Array.make perhaps?
<flux> I must confess after seeing the trick I've used that a lot, instead of writing/referring to another function written to do that. (although Array.init is much more useful)
yziquel has quit ["TinyIRC 1.1"]
<hcarty> I always have to look up which of those is deprecated...
<hcarty> make and create seem to both be used throughout the stdlib
szell has joined #ocaml
<palomer_> oomph
<bluestorm> h
<palomer_> I haven't used arrays in ages
<palomer_> how do I transform an int to a string ? (Int32 only works with int32s)
<bluestorm> let rec repeat x = let rec xs = x::xs in xs
<palomer_> bluestorm, yeah, that's what I implemented
<bluestorm> a bit dangerous, however
<hcarty> string_of_int
<bluestorm> hmm
<bluestorm> the first "rec" was unnecessary, of course
yziquel has joined #ocaml
yziquel has quit [SendQ exceeded]
yziquel has joined #ocaml
Linktim- has joined #ocaml
<palomer_> err, that's an infinite list
<palomer_> is that even useful?
<palomer_> I have to say, exceptions make my life easier
<flux> could be, in a rare case :)
<flux> (I don't think I've ever used them)
<palomer_> infinite lists?
ygrek has quit [Remote closed the connection]
<bluestorm> aaah, i thought you wanted an infinite list
<bluestorm> as the original haskell function
<bluestorm> flux: i've seen one use case for infinite lists
<bluestorm> for some implementation of the eratosthene seed, you can use a "wheel" that gives you the index to skip (for example if you want to ignore the multiples of, say, 2, 3, 5 and 7), wich can be neatly represented as an infinite list
<bluestorm> the problem becomes "how can i create a cycle : 'a list -> 'a list, turning a list into an infinite list ?"
<bluestorm> and is a bit more tricky
Linktim_ has quit [Read error: 110 (Connection timed out)]
<jlouis> tie the knot!
postalchris has joined #ocaml
alexyk has joined #ocaml
psnively has quit []
alexyk has quit []
r0bby has joined #ocaml
gene9 has joined #ocaml
gene9 has left #ocaml []
alexyk has joined #ocaml
rwmjones_ has quit [Read error: 104 (Connection reset by peer)]
rwmjones_ has joined #ocaml
alexyk has quit []
schme has joined #ocaml
robozni has joined #ocaml
sporkmonger has joined #ocaml
schme has quit [Remote closed the connection]
schme has joined #ocaml
mbishop_ is now known as mbishop
schme has quit [Remote closed the connection]
schme has joined #ocaml
sporkmonger_ has joined #ocaml
sporkmonger has quit [Read error: 104 (Connection reset by peer)]
bluestorm has quit [Read error: 113 (No route to host)]
LordMetroid has quit [Connection timed out]
kotarak_ has joined #ocaml
sporkmonger_ has quit [Read error: 110 (Connection timed out)]
kotarak_ has quit ["Xaide, leka nosht."]
Demitar has joined #ocaml
kotarak has quit [Read error: 110 (Connection timed out)]
ygrek has joined #ocaml
ikaros_ has quit ["segfault"]
alexyk has joined #ocaml
Demitar_ has joined #ocaml
delamarche has joined #ocaml
<alexyk> what's the idiom for Array.iter/iteri on a subrange of indices from m to n?
<alexyk> apart from writing a let rec iter_range :)
filp has quit ["Bye"]
Linktim- has quit [Remote closed the connection]
rwmjones_ has quit ["Closed connection"]
schme has quit [Connection timed out]
<delamarche> uh, if you don't mind copying you could do the iter on an Array.sub
<delamarche> or just check the bounds in the lambda you pass to iteri
<delamarche> i'd imagine if you're doing an iter you're trying to mutate the array, so the latter solution is probably what you want
alexyk has quit []
sporkmonger has joined #ocaml
sporkmonger has quit [Client Quit]
ygrek has quit [Remote closed the connection]
<jonafan> man, i wrote a parallelized mergesort in C# because we have an 8 core computer
hkBst has quit ["Konversation terminated!"]
<jonafan> The built in sort is faster (presumably because it calls C) but only works one core
<jonafan> rip off!
authentic has quit ["Reconnecting"]
authentic has joined #ocaml
<jonafan> 8 threads on my sort run about twice as fast as 1 thread
<jonafan> and worst of all, ocaml is much slower than all cases
<mbishop> try F#? :)
RobertFischer has joined #ocaml
<jonafan> nah
<jonafan> i'm really surprised that ocaml generated machine code is slower than .net
<RobertFischer> Mutable data much?
<jonafan> i'm using arrays in both cases
<RobertFischer> If you have a more purely functional approach (less mutable data), Ocaml is much faster.
<jonafan> you mean in both languages
<jonafan> meaning, functional style C# would be slow
<jonafan> (and incredibly ugly)
<pango_> ocaml GC is protected by a global mutex, so threaded ocaml programs don't benefit from multiple cores
<jonafan> yeah i know
<RobertFischer> Yeah. Mutable data solutions and some threaded solutions are faster in F# than in Ocaml. Immutable data, list manipulation, and tail recursion solutions are faster in Ocaml.
<mbishop> I wonder, how come there are a number of SML compilers, but only one for OCaml? has no one bothered to make their own?
<jlouis> mbishop, lack of specification hampers it
<jlouis> besides, it takes serious balls to write a compiler in production quality class
<RobertFischer> It's the difference in GC between the CLR and Ocaml.
<jonafan> so basically, forget about fast sorting algorithms in ocaml
<RobertFischer> And it's the big problem with porting Ocaml to the JVM.
<RobertFischer> You can sort fast in Ocaml. You just do it in a functional, not imperative way.
<jonafan> Array.sort is a lot faster than List.sort ...
<RobertFischer> Or, you do what you probably should be doing from the start and store things into a sorted data structure.
<RobertFischer> Do you have numbers for that? I'll buy it.
<RobertFischer> But I'm just curious how true that assertion is.
<jonafan> i can make some up pretty fast!
<jonafan> okay i have two programs
<jonafan> one generates 4125000 random ints in a list, the other in an array, and both then sort the array
<jonafan> i compiled them both to machine code and bytecode and i'm timing them
<jonafan> List took 13.2 s as machine code and 44.1 s as bytecode
<qwr> RobertFischer: one problem is also, that ocaml OO doesn't map very well into jvm classes
* qwr suspects that's also reason why F# has only C# style OO implemented
<jonafan> wow, array's bytecode is taking forever
<RobertFischer> qwr: Yeah. Abandon the approach of mapping Ocalm OO onto JVM classes in any kind of direct means...have an "Ocaml Class" concept, like Groovy has their "Groovy class".
<jonafan> Array: 10.8s and 1m15.1s
<jonafan> sooooo
<RobertFischer> jonafan: That's weird. Something went south with your benchmarking.
<jlouis> less than 3 seconds in difference from the list
<jlouis> pretty good
<jonafan> yeah i'm surprised at the results in several ways
<RobertFischer> And this is just a handwave assertion, but I bet if you pass around and match and work with lists instead of arrays, you'll recoup the sort cost pretty fast.
<jlouis> In ML, you don't win by brute force. You win by being clever
<jlouis> In C you often win by brute-force because clever takes forever in implementation time
<kig> i hear that all the time in ruby performance discussions
<jonafan> waaaait i messed something up
<kig> "ruby isn't slow, you just need to use it smartly. and btw performance doesn't matter!"
<jonafan> gotta rerun the array test
<qwr> ml is still quite good at brute-force, when compared to other high-level languages ;)
<jonafan> Array: 7.7s and 58.1s
<yziquel> Hi. After running ocamlc -c -cc "gcc -fPIC -o stub.o" stub.c and running nm famstubs.o
<jonafan> List took 13.2 s as machine code and 44.1 s as bytecode
<yziquel> I get U caml_alloc_custom
<yziquel> Is it supposed to be so?
<jlouis> kig, the difference is that in Ruby, everything is slow no matter how clever you are.
<kig> yes, with the final copout of "implement the bottlenecks as C extensions"
<jlouis> Implementing via C-extensions is fail ;)
<jonafan> http://ocaml.paste.f-box.org/51 if you wanna look at my test code
<jlouis> You do want to be able to call C through a FFI when someone has invested years on some code in C.
Kopophex has joined #ocaml
* qwr looked at shootout ocaml vs mlton... and their about equal
* qwr would have hoped more from mltons full-program analysis... ;)
<jlouis> qwr, yes for that kind of small problems.
<RobertFischer> Okay, my drugs are getting to me (in the hospital for post-deviated septum surgery). See you later.
<qwr> jlouis: meaning that ocaml also inlines there enough?
<jlouis> qwr, ocaml can't inline or monomorphise across 2 different compilation units
<jlouis> mlton can
<jlouis> in fact, mlton monomorphises *any* polymorphic function
<pango_> ocaml does inline across compulation units
<pango_> s/compulation/compilation/
<jlouis> oh!
postalchris has quit [Read error: 110 (Connection timed out)]
<mbishop> so a new ubuntu came out today, ocaml 3.10 should finally be in apt :)
<pango_> I think for short functions it keeps some intermediate code version in the module, but I'm not sure
<jlouis> 3.10.0-8 mbishop ;)
<mbishop> jlouis: :P
<mbishop> My update is still going, the mirrors are getting hammered heh
<RobertFischer> jlouis: How does the "monomorphizing" work?
<qwr> mbishop: has been some time in debian testing ;)
<jlouis> mbishop, I cheat. I always update a day or 3 before the release
<RobertFischer> If I take a value from stdin, and if that value is 1, then it uses class A, but if the value is 2, then it uses class B (which inherits from A), how does it know downstream which to use?
<jlouis> RobertFischer, given a polymorphic function, track it's call-sites and make a version with monomorphic types where needed
<jlouis> since the compiler is whole-program you know all call-sites so it is a dead easy pass
<jlouis> "dead easy" I may add
<RobertFischer> So, in my scenario, every downstream call will be replaced with something like "if A, then call A#foo; if B, then call B#foo"?
<jlouis> RobertFischer, SML has no objects
<jlouis> or classes
<RobertFischer> Oh. So it just dumps the concept of inheritance.
<jlouis> yes, there is no subtyping in SML
<RobertFischer> I'll take Ocaml's solution. Sometimes inheritance is nice. :)
<jlouis> I should probably take up compiler hacking again and hack an SSA-PRE pass for mlton :)
<RobertFischer> Anyway, I'm crashing hard. See you all later.
RobertFischer has left #ocaml []