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
yezariaely has quit [Read error: Operation timed out]
yezariaely has joined #ocaml
oriba has quit [Quit: oriba]
ftrvxmtrx has quit [Ping timeout: 244 seconds]
djcoin has quit [Quit: WeeChat 0.3.2]
<Drakken> Suppose I wanted to write a function that can return any kind of tuple, with any types and any number of values.
<Drakken> Is there any kind of static type system that could do that?
<thelema> Drakken: an array of variant types?
<thelema> you say "any type", but even dynamic type systems have a... vocabulary of types
<Drakken> thelema any typeS in the tuple.
<Drakken> hmm. maybe that _is_ any type if the tuple can have only one element.
<Drakken> I mean any type in the type(s) in the type system.
<Drakken> I'm thinking of sequence parsers. They usually take any number of individual parsers of any type.
<Drakken> It would be natural to return a tuple.
<thelema> or for each parser to bind a new identifier to that sub-parser's result
<Drakken> that's the norm.
<Drakken> Maybe it's more of a metaprogramming thing.
<thelema> ok, each value has to have some information describing what "kind" of value it is - an int, float, string, etc
<thelema> if you don't have this information, there's only the C way of dealing with it 0 treat it as a bitstring of some width
<Drakken> every parser has a type.
<thelema> ok, maybe not fair to C - the assembly way
<Drakken> I was just wondering what it would take to make an all-purpose sequence parser that can automatically bind all the items in the sequence.
<Drakken> even with ML, maybe a metaprogramming system could generate a new function with the right type for each call to the sequence metafunction.
<Drakken> maybe that's the only alternative to dynamic typing.
<thelema> probably not in OCaml, as the type system would have to generate code
<Drakken> but in a preprocessor
<thelema> but you'd have to know types, and at least camlp4 doesn't know types
<Drakken> hmm. so you would need a typed preprocessor.
lamawithonel has quit []
<Drakken> or type-aware or whatever the appropriate term is.
<thelema> You'd have to produce an ocaml parse tree, apply HM type inference, and then modify that parse tree
<Drakken> cool!
<thelema> and then make sure that the result still type-checks
<Drakken> hey thelema, did you see my new Ometa clone on github?
<thelema> You'd probably need a modification on the type system to allow it to be "soft" around the new syntax
<thelema> I haven't looked at it; I'm not too interested in metaprogramming
<Drakken> that's okay
<Drakken> well, that sounds like more than I can handle right now.
<Drakken> I'll remember it though. Typed preprocessing.
<thelema> yes, it would be a big project
<Drakken> alright, thanks for the ideas.
gnuvince has quit [Ping timeout: 250 seconds]
gnuvince has joined #ocaml
destrius has joined #ocaml
sepp2k1 has quit [Remote host closed the connection]
tbrady has joined #ocaml
tbrady has quit [Quit: tbrady]
ankit9 has joined #ocaml
absz has joined #ocaml
BiDOrD_ has joined #ocaml
BiDOrD has quit [Ping timeout: 248 seconds]
xcombelle has joined #ocaml
Progster has quit [Ping timeout: 244 seconds]
diego_diego has joined #ocaml
absz has quit [Quit: absz]
Xizor has joined #ocaml
ftrvxmtrx has joined #ocaml
Cyanure has joined #ocaml
Xizor has quit []
pango is now known as pangoafk
diego_diego has quit [Quit: diego_diego]
diego_diego has joined #ocaml
diego_diego has quit [Client Quit]
Snark has joined #ocaml
eni has joined #ocaml
thomasga has joined #ocaml
Cyanure has quit [Remote host closed the connection]
SecretFire has joined #ocaml
ftrvxmtrx has quit [Quit: Leaving]
djcoin has joined #ocaml
djcoin has quit [Read error: Connection reset by peer]
edwin has joined #ocaml
djcoin has joined #ocaml
djcoin has quit [Read error: Connection reset by peer]
djcoin has joined #ocaml
Cyanure has joined #ocaml
djcoin has quit [Read error: Connection reset by peer]
gnuvince has quit [Ping timeout: 250 seconds]
gnuvince has joined #ocaml
ftrvxmtrx has joined #ocaml
xcombelle_ has joined #ocaml
xcombelle_ has quit [Remote host closed the connection]
Kakadu has joined #ocaml
xcombelle has quit [Ping timeout: 245 seconds]
<Kakadu> #join ipad
<Kakadu> sorry, not here
silver_ has joined #ocaml
edwin has left #ocaml []
djcoin has joined #ocaml
cago has joined #ocaml
mika1 has joined #ocaml
ankit9 has quit [Quit: Leaving]
jlouis has joined #ocaml
ivan\ has quit [Quit: ERC Version 5.3 (IRC client for Emacs)]
ankit9 has joined #ocaml
avsm has joined #ocaml
josch has left #ocaml []
Kakadu has quit [Quit: Page closed]
ivan\ has joined #ocaml
thomasga has quit [Quit: Leaving.]
cdidd has quit [Ping timeout: 264 seconds]
cdidd has joined #ocaml
Obfuscate has quit [Ping timeout: 260 seconds]
Obfuscate has joined #ocaml
mort___ has joined #ocaml
eni has quit [Ping timeout: 248 seconds]
destrius has quit [Quit: Leaving.]
Cyanure has quit [Remote host closed the connection]
Cyanure has joined #ocaml
_andre has joined #ocaml
eikke has joined #ocaml
xcombelle has joined #ocaml
cago has quit [Quit: Leaving.]
Reventlov has quit [Ping timeout: 246 seconds]
xcombelle has quit [Quit: I am a manual virus, please copy me to your quit message.]
sepp2k has joined #ocaml
cdidd has quit [Read error: Operation timed out]
cdidd has joined #ocaml
Progster has joined #ocaml
Progster has quit [Ping timeout: 248 seconds]
ankit9 has quit [Remote host closed the connection]
gnuvince has quit [Ping timeout: 250 seconds]
vext01 has joined #ocaml
<vext01> hi guys, im trying to get my head around the various methods of using findlib
<vext01> i have some code that uses findlib and builds byte and opt code
<vext01> to allow the same code to be interpreted, I have added some preprocessor stuff
<vext01> #use "topfind";;
<vext01> #require "batteries";;
<vext01> #require "batteries.syntax";;
<vext01> #camlp4o;;
<vext01> this breaks byte and opt building and does not seem to work as a script either
<adrien> I'm not aware of a satisfactory way get the exact same code to work both in the toplevel and as a source file for ocamlc/ocamlopt
<flux> I don't think many people do that, interpret same scripts they compile
<flux> mayeb a simple preprocessor to filter out the #s out of the source code would do..
<flux> could be as simple as grep -v '^#'
<flux> not sure how easy it's to integrate with campl4 though
<adrien_oww> I'd rather do it the other way round
<adrien_oww> have a file that parses with ocamlc and ocamlopt, and when needed with "ocaml", add these lines
<flux> I think for single-file projects it'd be great if ocamlc/ocamlopt just supported those flags.
<flux> well, "pragmas"
<adrien_oww> but then you're shifting the issue to non-single file projects
<flux> well, it's not going to work with ocaml easily anyway
<adrien_oww> also, this can "invoke" camlp4 _after_ the parsing has started, which is definitely how it's currently done
<flux> well, you could have a master .ml that #uses stuff
smondet has joined #ocaml
<flux> it wouldn't be the 'grown up' way of doing stuff, but it would be nice sometimes.
<vext01> oh
<vext01> so how come sthis code does not interpret?
<flux> oh, I didn't notice that part of the question
<flux> I've never really used syntax extensions with "script.ml's"
<vext01> im at a openbsd hackathon, i'm trying to get ocaml batteries in ports, but i need to test the interpreted findlib invoke :P
<vext01> doesnt help im really new to ocaml
<adrien_oww> vext01: #camlp4o _before_ the syntax extension
<adrien_oww> loading the syntax extension support after loading the syntax extension doesn't sound very reliable
hongboz has joined #ocaml
<vext01> nope
<vext01> it chokes on a list comprehension
<adrien_oww> I mean:
<adrien_oww> #camlp4o;;
<adrien_oww> #require "batteries.syntax";;
<adrien_oww> not the other way round
<vext01> adrien_oww: that is what i have
<vext01> ah i have to go for a while
<vext01> ill be back later
<vext01> if you know the answer, please pm me :)
<vext01> thanks
<hcarty> flux: It's not an actual mix of toplevel + compiled, but ocamlscript provides a simplified compilation approach for single-file projects
<hcarty> flux: It supports programs with multiple source files as well, although it's not as reliable in knowing when to rebuild the program.
<hcarty> * Not as reliable for multi-file programs as it is for a single file program
Asmadeus has quit [Ping timeout: 246 seconds]
diego_diego has joined #ocaml
mika1 has quit [Quit: Leaving.]
warlockwinning has joined #ocaml
<warlockwinning> Hello all
<warlockwinning> I've a question about the syntax used in ml's trie implementation
<warlockwinning> I'm attempting to port this to F#, but am having trouble understanding the module stuff
cdidd has quit [Remote host closed the connection]
<warlockwinning> first question is - what does the + mean in the expression "type +'a t"
cdidd has joined #ocaml
Asmadeus has joined #ocaml
gnuvince has joined #ocaml
Reventlov has joined #ocaml
ankit9 has joined #ocaml
Cyanure has quit [Ping timeout: 245 seconds]
<f[x]> variance
cdidd has quit [Remote host closed the connection]
cdidd has joined #ocaml
Hodapp has quit [Ping timeout: 252 seconds]
Hodapp has joined #ocaml
cdidd has quit [Remote host closed the connection]
eni has joined #ocaml
<warlockwinning> ah, thank you
<warlockwinning> another thing I don't understand is this expression - "type key = M.key list"
<thelema> warlockwinning: just creates a type alias
<warlockwinning> does it specify a list of value of whatever type M.key is?
<thelema> instead of typing "M.key list", one can type "key"
<thelema> yes
<warlockwinning> so "M.key list" == "key"
<thelema> yes
Cyanure has joined #ocaml
<warlockwinning> hurts my brain
<thelema> just like "type foo = int list"
<warlockwinning> it seems like it doesn't make sense
<warlockwinning> does it boil down to type key = key list?
<thelema> no, M.key is not key
<warlockwinning> I don't understand the use of M.key here
djcoin has quit [Quit: WeeChat 0.3.2]
<thelema> M.key is the key type from module M
<warlockwinning> I guess I don't understand the relationship between type S and the struct
cdidd has joined #ocaml
<thelema> I'm guessing that this trie uses functors, and f# doesn't support them... or most of the goodness of ocaml's module system
<warlockwinning> right, that's what is making the port hard
<warlockwinning> I need to understand the nuances of the module system first
<warlockwinning> however
<thelema> module type S is the "signature" of the functor argument to Make
<warlockwinning> I don't see use of the word "functor" anywhere in this file
<thelema> Think of Make as a function that takes a module as parameter and returns a module
<warlockwinning> so I'm confused if it really is one
<thelema> the functor is implied by the use of a module as a parameter
<thelema> it is one.
<warlockwinning> ah
<thelema> M is the parameter module, and S is its type
<thelema> if it helps, the line that defines make is equivalent to "module Make = functor (M:S) -> struct"
<warlockwinning> ok
<warlockwinning> definitely helpful for noobs like me :)
<thelema> the input must be a module with type key and polymorphic type t
<thelema> with a bunch of functions in terms of those types
<warlockwinning> So S is not a sig for a trie, but rather a sig for a key?
<thelema> S is the sig for M, the module that the trie is built from.
<thelema> although it turns out that it's also the sig for a trie
<thelema> the last line says that the functor "Make" takes as argument a module M of type S and returns a module of type S where the key is "M.key list"
<warlockwinning> it confuses me how M.key is not key, and how 'a t is not M.t
<thelema> ok, think about a concrete application - one thing you could use as M is an integer map.
<thelema> this has key = Int and 'a M.t = maps from ints to 'a
<thelema> when you apply Trie.Make to this, you get a module where key is "int list", and 'a t is a trie structure mapping int lists to 'a
<warlockwinning> how can 'a M.t do any mapping? is it a function?
<thelema> it's a type, just as 'a array is a type
<warlockwinning> so by integer map, do you mean Map int?
<thelema> if that's how it's written in f#, then yes
<warlockwinning> I thought the trie was suppoed to handle the mapping?
<thelema> in ocaml, one creates it with another functor; Map.Make(Int)
<thelema> the trie handles the mapping from int list to 'a, but this implementation is parameterized on an implementation that is int to 'a
<thelema> (or whatever your key is)
<thelema> maybe a different example would be useful - one common use of tries is in dictionaries
<thelema> each node has 256 children, one for each ascii code
<warlockwinning> ok
<thelema> instead of using a Map, one can use a 256 entry array
<thelema> so M.key is char
<warlockwinning> ok
<thelema> and 'a M.t is 'a array
Cyanure has quit [Remote host closed the connection]
<thelema> the rest of the functions have to be defined so that they work on this array
<thelema> but only for a single character
<warlockwinning> how are those functions defined?
<warlockwinning> with a new struct?
<thelema> then, one applies the Trie.Make functor to the module with key=int, 'a t='a array
<warlockwinning> ok
<thelema> in ocaml, one uses a module for them
<thelema> module CharArray = type key = char type 'a t = 'a option array let empty = Array.create 256 None let is_empty a = Array.find (not null) a ... end
<warlockwinning> so I understand now how to create a Trie of the correct type parameters, but I don't understand how to give the function definitions for how to work on that specifical type
<warlockwinning> ok, keep going
<thelema> in ocaml, one defines a module that holds types and values
<thelema> hmm, actually the array example won't work for this S because the signatures won't end up matching
<thelema> but anyway...
<thelema> Maybe you need to start with a simpler functor example
<thelema> have a look at this - it's the definition of sets from the ocaml stdlib
cdidd has quit [Remote host closed the connection]
<thelema> In this example, S is the output type of the functor and OrderedType is the input type
<thelema> (module type)
<warlockwinning> well, I think I almost got it
<warlockwinning> say that the CharArray module worked, how would we pass it as a parameter to the functor?
<thelema> ocaml doesn't use objects or structs for carrying functions along with types, it uses modules and functors
<warlockwinning> i thought ocaml used structs
<thelema> module CharTrie = Trie.Make(CharArray)
<warlockwinning> (not like F# structs)
<thelema> ocaml has records, which I think correspond to structs better than modules
<warlockwinning> ya, I mean the actual struct keyword in ocaml
<warlockwinning> module Make(Ord: OrderedType) =
<warlockwinning> struct
<thelema> yes, struct just begins a module definition
<warlockwinning> ya
<thelema> just as "sig" begins a module type definition
<thelema> but it defines a module, not a struct
<warlockwinning> ya, I understood that :)
<warlockwinning> so, could we make Trie with some type of CharTrie?
<warlockwinning> that is, could we make its signatures match?
<warlockwinning> I don't understand why your signatures didn't match - was it just an accident?
<thelema> my signatures aren't going to match because 1) the variance annotation; arrays are not covariant, iirc
<thelema> and 2) the definition of empty - "val empty : 'a t"; using arrays either requires copying the array each time you perform an operation or creating different arrays and mutating them; the first is inefficient and the second is (unit -> 'a t)
<warlockwinning> ya, I'm trying to keep it persistent
<warlockwinning> so instead of an array I would use a list
<thelema> so then you just use a persistent structure
mort___ has quit [Quit: Leaving.]
<warlockwinning> ya
<warlockwinning> unfortunately list has slow look up
<warlockwinning> perhaps I should use a Map
<thelema> yup, so the best is a Map
<warlockwinning> ok, now I think I get it ;)
<warlockwinning> thank you thelema
<thelema> you're welcome
Cyanure has joined #ocaml
mrm has joined #ocaml
eni has quit [Ping timeout: 248 seconds]
diego_diego has quit [Quit: diego_diego]
diego_diego has joined #ocaml
silver_ has quit [Read error: Connection reset by peer]
diego_diego has quit [Client Quit]
mcclurmc has quit [Read error: Connection reset by peer]
Yoric has joined #ocaml
xcombelle has joined #ocaml
err404 has joined #ocaml
mcclurmc has joined #ocaml
avsm has quit [Quit: Leaving.]
Yoric has quit [Ping timeout: 265 seconds]
Yoric has joined #ocaml
mrm has quit [Read error: Operation timed out]
Submarine has joined #ocaml
Submarine has quit [Changing host]
Submarine has joined #ocaml
ftrvxmtrx has quit [Quit: Leaving]
_andre has quit [Ping timeout: 265 seconds]
Yoric has quit [Ping timeout: 250 seconds]
_andre has joined #ocaml
ftrvxmtrx has joined #ocaml
pangoafk is now known as pango
err404 has quit [Remote host closed the connection]
avsm has joined #ocaml
Reventlov has quit [Remote host closed the connection]
_andre_ has joined #ocaml
<fasta> ===> PCRE not found
<fasta> Consider adding GODI_BASEPKG_PCRE=yes to godi.conf
<fasta> How can that be fixed besides adding what it says to godi.conf?
<orbitz> Is there a specific reason you'r elookign to not do the obvious solution?
<fasta> orbitz: well, I would like to know what the programmer was thinking.
<fasta> orbitz: because I don't see how he could have messed this up.
<orbitz> messed what up/
<fasta> It's not exactly rocket science.
<fasta> Finding PCRE.
_andre has quit [Ping timeout: 250 seconds]
<fasta> So, either it exists, or he should say 'it doesn't exist, please install it'.
<fasta> Or it should just auto fall back to whatever that option says.
<orbitz> what are you installing?
<fasta> orbitz: I am bootstrapping godi.
<avsm> godi has a builtin version of pcre
<avsm> or you can use the system pcre
<avsm> and the option sets which one is in use. whats the issue?
<fasta> avsm: yes, that's what that variable says.
<fasta> avsm: the issue is that it doesn't work out of the box.
<avsm> well, do you have a system pcre installed?
<orbitz> what doesn't work? does the bootstrap fail or is it just letting you knwo PCRE wasn't found so it'll use the builtin?
<fasta> orbitz: full error: http://paste.kde.org/516218/
<fasta> avsm: If I don't have a system PCRE, it should inform me of that.
<adrien> fasta: you just have to install the libpcre-dev packages
<adrien> also, german people speak english but with weird ideas
<fasta> adrien: who is German?
<orbitz> If you set teh variable does it use the the installed oned?
<adrien> godi's author
<fasta> adrien: better than people who still write manuals in German.
<fasta> Just out of interest: how do you manage your development machines?
<fasta> I.e., how do you make sure that they have similar packages, etc.?
<adrien> godi_console -> update
<fasta> No, beyond godi.
<fasta> Unless you only use Ocaml.
<adrien> when the distribution packages have changed and I need a rebuild, godi_console -> rebuild
<fasta> Let's say someone destroys your machine, can you get up and running with the push of a button?
<orbitz> fasta: I imagine most of us here don't manage machines
<orbitz> In place I have worked we use chef, puppet, or cfengine
<adrien> reinstall linux distribution, reinstall godi or ocaml packages from the distribution, copy back the few bits of configuration; so, "yes" but I'm not sure I'm the general case
<fasta> orbitz: well, often developers get root.
<orbitz> Honestly I haven't had much luck with godi, I make scripts to install what I want from the internet or use odb
<orbitz> fasta: having root doesn't make you a sysadmin
<fasta> orbitz: it does when the system admins lag.
<fasta> orbitz: if doing it myself takes 5 minutes and asking the system admin takes hours, then it's quite easy what is going to happen.
<orbitz> Maybe, in any reasonable sized organismaiton devs don't have root
<orbitz> I can't even get to our prod machines
<orbitz> fasta: I also install ocaml to its own dir, and all deps in there, so as long as I know all the machines are teh same, i can just tarball that and push it everywhere
<fasta> orbitz: I think the best is some combination of tools.
<fasta> orbitz: e.g. use puppet for whatever they have already automated quite well.
<fasta> orbitz: and custom scripts for the rest which might or might not be called from puppet.
<orbitz> fasta: With teh tarball thing, chef can just install the tarball i made
Reventlov has joined #ocaml
<fasta> orbitz: I think a full workstation requires thousands of packages.
<fasta> orbitz: which is something chef, etc. generally doesn't do.
<fasta> It's more targeted at managing a bunch of servers.
<fasta> You can make it do other things, of course, but the tools themselves only help when you can make use of existing scripts.
<fasta> Or recipes or whatever they call it :P
<fasta> I would always call my next tool Shit and running a program would be called eating.
<fasta> Eating Shit works really well!
<fasta> er almost
<orbitz> fasta: I'm not sure hwy chef can not handle thosuands of packaegs
<fasta> orbitz: sure, it can, but it wouldn't help anything.
<orbitz> fasta: you would setup a workstateion role in teh chef server and ocne you boostrap it to running chef it will just isntall all of it
<orbitz> what wouldn't it help?
<fasta> orbitz: what does it more dan apt-get -q=2 install $(cat list_of_packages) ?
<fasta> than*
<adrien> btw, my linux distribution is slackware: installs are "full", i.e. I don't have only runtime stuff but also developer tools and files, and servers
<adrien> saves a lot of time
<orbitz> fasta: doing that would be sufficient, if you have a workstation role it is nice to have all of them be the same, and when you add a new package you can push out changes trivially to all of them. But chef also has a lot of support for playing with config files on the fly
<fasta> orbitz: I wrote scripts to setup my usb over ethernet networking for example.
<fasta> orbitz: I think such things are much harder to setup in Chef.
<orbitz> I don't see why
<orbitz> Chef is really just a wrapper around ruby
<fasta> orbitz: so how could that be done then?
<fasta> orbitz: or do you mean to just write something custom in ruby?
<fasta> orbitz: it's basically a matter of just called 'sed' for lots of these things.
<fasta> calling*
<orbitz> fasta: I'm not sure what the exact problem is, clearly you need a network connecitn touse chef, but a chef recipe is jus ta ruby script so I don't see why it would not be possible to implement our USB setup thing in it
<fasta> orbitz: ok, so then it is possible, but does it do anything better than scripts?
<orbitz> It depends on your use case obviously
<orbitz> a Chef server isn't that useful for me on my home laptop, but if I were managing 1000 workstations it is
<fasta> orbitz: for example, I would like to install godi in multiple chroots.
<fasta> orbitz: or I would like to have the latest ruby installed and have Debian's standard ruby pointing at this latest version.
avsm has quit [Quit: Leaving.]
<fasta> Debian doesn't have any way to automate that via an API.
<orbitz> fasta: Like any tool its specific viability depends on specifics. Chef is made for managing hosts, not a host. So if your usecase falls inot that area then chef is probably useful, if not it ins't
<fasta> Speaking of OCaml: is it possible to write a parallel accessible data structure in OCaml?
<fasta> AFAIK, the answer is basically 'no'.
<thelema> fasta: parallel as in accessed by threads running on different processors?
<fasta> thelema: is there any other kind?
<fasta> thelema: because the data is in some in memory data structure.
<fasta> thelema: if you want to synchronize that, I don't think you can do that in any other way.
<thelema> ocaml can do this by having processes share memory
Reventlov has quit [Quit: leaving]
<fasta> thelema: Ok, but isn't that much slower than the way Haskell does things?
<thelema> but of course the right way is to use message passing
<fasta> I.e. MVars or TVars.
* thelema looks up the haskell way
<orbitz> The Haskell way?
<orbitz> You mean teh 50 Haskell ways?
<fasta> An MVar is the kind of abstraction you learn first in your concurrency classes at university.
<orbitz> MVar is one of 100 Haskell ways to do apralelism
<orbitz> You can also use Concurrent Haskell whihc uses channels
<fasta> Or data-par..
<orbitz> Asking if osmething is faster isr eally thew rong question when it comes to abstractions anyways
<fasta> MVar is just a run-off-the mill simple abstraction which does what it is supposed to do.
<fasta> Ok, that's true.
<thelema> fasta: there's a number of data-parallel libraries for ocaml
<fasta> thelema: yeah, but I am more interested in MVar like abstractions ;)
<Qrntz> MVar strongly reminds me of jocaml…
<fasta> I read about jocaml, but it wasn't clear whether it actually added any useful property.
<fasta> Likely it does, because of the calculus associated with it.
<Qrntz> e. g. see the reference cell example from the jocaml manual — it basically is an MVar as I understand it
<fasta> But I never studied it in detail.
<fasta> It looks a lot like Linda spaces.
<fasta> er tuple spaces.
<fasta> in Linda.
<Qrntz> join-calculus is based on message-passing, as are pi-calculus and the actor model
<Qrntz> I am not familiar with linda
<fasta> An MVar can be considered a message too.
<fasta> How you call it doesn't matter in the end.
<fasta> The question is how well it performs.
<fasta> OpenMPI certainly performs.
<orbitz> If you havea perforamcne question your only option is to perform experiments
<fasta> orbitz: well, I figured that all the experts would already be here.
<fasta> orbitz: and I had expected a fight about what was faster ;)
<fasta> orbitz: not these overly reasonable people.
<orbitz> fasta, Well, Jon Harrop isn't here so
<Qrntz> what I know is that jocaml performed rather well in the wide finder project
<Qrntz> you might consider looking that up
<Qrntz> it gets way less attention overall than it deserves though (imo)
<fasta> I think a huge disadvantage of Haskell is that something which looks reasonable doesn't actually perform.
<orbitz> Haskell has many pros and cons, like Ocaml
<fasta> Even things which don't look reasonable are still relatively slow. With C++ I have never written a slow program the first time.
<fasta> Part of it are the abstractions.
<thelema> fasta: me neither - C++ crashes very quickly
<orbitz> C++'s goal is to have a realtively Reasoningable cost structure
<orbitz> it somewhat fails at it
<fasta> If you write 'runMyMonadTransformerStack' in Haskell you get lots of conditionals.
<adrien> thelema: :p
<fasta> More than you would otherwise ever write, likely.
<fasta> So, it's really flexible, but also not really needed.
<orbitz> Maybe
<fasta> thelema: well, crashes are easily found in my experience.
<adrien> same with landmines
<adrien> you only need a hundred sheeps
<fasta> Too bad all the widefinder URLs are dead.
<thelema> fasta: mfp did a number of ocaml implementations of widefinder
<orbitz> What is Wide Finder?
<thelema> orbitz: read Qrntz's first link
<orbitz> Hrm, I think I get it
<fasta> Perl wins.
ankit9 has quit [Ping timeout: 264 seconds]
<adrien> but I haven't been able to reach eigenclass.org for the past couple days ='(
<thelema> fasta: followed closely by jocaml
<fasta> adrien: thewaybackmachine works.
<adrien> fasta: true but not very practical
<fasta> A paralell tree insertion and deletion implementaion would be cool to see in JoCaml.
<adrien> and I'm sure that mfp will wave a magic wand and have everything fixed :P
<fasta> What's mfp's name?
<fasta> Never mind
<fasta> Is he sort of well known?
<adrien> eigenclass.org is his domain
<orbitz> fasta: He does a lot of nice stuff
<orbitz> I use his MQ a lot
<fasta> Is that the one with a Zero?
<orbitz> No
xcombelle has quit [Quit: I am a manual virus, please copy me to your quit message.]
ankit9 has joined #ocaml
osa1 has joined #ocaml
Reventlov has joined #ocaml
eikke has quit [Ping timeout: 250 seconds]
ivan\ has quit [Ping timeout: 246 seconds]
ivan\ has joined #ocaml
eikke has joined #ocaml
warlockwinning has quit [Ping timeout: 248 seconds]
mort___ has joined #ocaml
mathieui has left #ocaml []
Cyanure has quit [Read error: Connection reset by peer]
Cyanure has joined #ocaml
Cyanure has quit [Remote host closed the connection]
Cyanure has joined #ocaml
sepp2k1 has joined #ocaml
sepp2k has quit [Ping timeout: 264 seconds]
Snark has quit [Quit: Quitte]
phizyx has joined #ocaml
hongboz has quit [Remote host closed the connection]
sepp2k1 has quit [Quit: Leaving.]
sepp2k has joined #ocaml
<fasta> thelema: jocaml doesn't use multiple OS threads either.
ankit9 has quit [Ping timeout: 250 seconds]
<thelema> fasta: yes, I know.
<thelema> it uses ocaml's GC, which is single-core.
<fasta> On programs where finer-grained parallelism is required (which
<fasta> is most real programs), OCaml and JoCaml are completely useless.
<fasta> According to Dr Jon Harrop.
<thelema> yup, he's made his wants for parallel support in ocaml clear.
<thelema> which is why he's migrated to using F#
<adrien> I'm quite unhappy with the current GC in Mono I think
<adrien> OpenRA has severe lags which are quite likely caused by the GC
gnuvince has quit [Ping timeout: 245 seconds]
<fasta> adrien: as in: the game?
<adrien> yes
<fasta> adrien: that ran great on a 200MHz machine
<adrien> OpenRA, not RA
<fasta> adrien: isn't it just programmed really, really bad?
<adrien> OpenRA is in C#
<fasta> adrien: yes, I understand.
<fasta> adrien: or does it do things differently?
<adrien> Using resolution: 1600x900
<adrien> that's already a big difference
<fasta> adrien: and modern graphics?
<adrien> yes and no
<adrien> it's not terrific but it doesn't hurt the eyes like RA would do if you played it on a bigger screen
<adrien> it also has a couple fancy effects (smokes, fires, trails)
osa1 has quit [Ping timeout: 245 seconds]
Progster has joined #ocaml
mort___ has quit [Quit: Leaving.]
err404 has joined #ocaml
smondet has quit [Quit: Bye]
warlockwinning has joined #ocaml
eikke has quit [Ping timeout: 246 seconds]
gnuvince has joined #ocaml
warlockwinning has quit [Ping timeout: 246 seconds]
Cyanure has quit [Remote host closed the connection]
gnuvince has quit [Ping timeout: 244 seconds]
err404 has quit [Remote host closed the connection]
cdidd has joined #ocaml
Tobu has quit [Remote host closed the connection]