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!)
bluestorm has quit ["Konversation terminated!"]
LordMetroid has quit ["Leaving"]
|Catch22| has joined #ocaml
<thelema> rwmjones: for sets and maps with keys = int and contiguous ranges, the camomille library has iSet and iMap.ml
Kopophex has joined #ocaml
fasd has quit [Remote closed the connection]
hkBst has quit ["Konversation terminated!"]
jonafan_ has joined #ocaml
darinm has joined #ocaml
seafood_ has joined #ocaml
jonafan has quit [Read error: 110 (Connection timed out)]
seafood_ has left #ocaml []
hsuh has joined #ocaml
dlomsak has joined #ocaml
dlomsak has quit [Remote closed the connection]
hsuh has quit [""ati driver testing..""]
hsuh has joined #ocaml
hsuh has quit [Remote closed the connection]
^authentic has joined #ocaml
authentic has quit [Read error: 110 (Connection timed out)]
^authentic is now known as authentic
darinm has quit []
mikeX_ has joined #ocaml
mikeX has quit [Read error: 110 (Connection timed out)]
derenrich has joined #ocaml
<derenrich> if I have a type defined by "type box = int array array" how d I use it
<derenrich> ?
<thelema> you don't have to do anything to use it.
<thelema> Just use an int array array.
<derenrich> Iah, so I can only use it for pattern matching?
<thelema> if you want to specify a signature for a function, you can use "box" instead of "int array array"
<thelema> no, when you match, you only get one type.
<derenrich> ic
<thelema> type declarations are necessary for records and variant types, and just udeful as abbreviations for everything else.
<thelema> *useful
|Catch22| has quit ["To the best of my knowledge, I guess that I'm fresh"]
derenrich has quit [Read error: 110 (Connection timed out)]
alexyk has quit []
Kopophex has quit [Read error: 110 (Connection timed out)]
Kopophex has joined #ocaml
alexyk has joined #ocaml
Demitar has quit [Read error: 110 (Connection timed out)]
Demitar has joined #ocaml
ozzloy has quit [Read error: 110 (Connection timed out)]
Kopophex has quit [Remote closed the connection]
bluestorm has joined #ocaml
ikaros has joined #ocaml
filp has joined #ocaml
seafood_ has joined #ocaml
seafood_ has left #ocaml []
seafood_ has joined #ocaml
seafood_ has quit [Client Quit]
evn has joined #ocaml
Yoric[DT] has joined #ocaml
OChameau has joined #ocaml
hkBst has joined #ocaml
authentic has quit [Read error: 110 (Connection timed out)]
coucou747 has joined #ocaml
authentic has joined #ocaml
alexyk has quit []
alexyk has joined #ocaml
<flux> one annoying thing about universal quantifiers with object methods is that they don't get inferred; you need to always annotate explicitly the parameter type
<flux> obviously with records it works fine, because they can be inferred by the field name to be from that certain record type
<flux> any suggestions on a workaround?
<tsuyoshi> universal quantifiers?
<flux> class a = object method foo : 'a.'a -> 'a end
<flux> well, add = fun a -> a to that and you've got working code ;)
<Yoric[DT]> :)
<flux> and then: let bar f = ignore (f#foo "42")
<flux> bar (new a) won't work
<flux> also, you can't write let bar f = ignore (f#foo "42"); ignore (f#foo 42)..
<flux> but it works if you annotate the type of f
<Yoric[DT]> mmmhhh...
<Yoric[DT]> The files xxx.cmi and stream.cmi make inconsistent assumptions over interface Stream .
<tsuyoshi> ah.. the hell are you trying to do, anyway?
<Yoric[DT]> Which is somewhat coherent, as I have two different Stream modules.
<tsuyoshi> how useful is it to ignore the result of a polymorphic function
<flux> it's not
<flux> however, I have an environment class which I pass around, which has functions like with_db
<tsuyoshi> oh I see
<flux> with signature like: object method with_db: 'a.(Db.handle -> 'a) -> 'a end
<flux> actually it's slightly more complicated than that with my new shiny cps-based system, but the idea is the same
<tsuyoshi> huh.. does that work with records or do you get the same problem?
<flux> it would work with records
<tsuyoshi> oh yeah, you already said that
<flux> infact, it has worked, I used to have a record with a bunch of functions I passed around..
authentic has quit [Remote closed the connection]
* Yoric[DT] 's brilliant build system is obviously a failure.
* Yoric[DT] needs to find a backup plan which doesn't completely screw ocamldoc.
<flux> yoric[dt], darn. I hate when it happens. I build something great. but then it doesn't work.
<Yoric[DT]> yep
<bluestorm> you get used to it eventually :-'
authentic has joined #ocaml
<Yoric[DT]> Especially when it seems I've just hit a limitation of ocamlc.
<bluestorm> Yoric[DT]: i was wondering yesterday, should i change de code of extensions that do not use the functor layer ?
<bluestorm> (ie. add it, wich is not very difficult indeed)
<Yoric[DT]> bluestorm: I'd say "yes".
<bluestorm> i think it's a good idea too, the problem is that about 90% of extensions out there don't use them :p
<Yoric[DT]> At the moment, I'm trying to find a way to extract modules out of extlib and give them a different structure... preferably without making the source code incompatible with extlib along the way.
<Yoric[DT]> And without screwing ocamldoc.
<bluestorm> actually it's not a real problem, i'm just afraid to feel like i have to mail the extension authors saying "here is the pedantic guy, and i attach you the modified extension"
<Yoric[DT]> bluestorm: is that a problem ?
* Yoric[DT] enjoys sounding pedantic.
<bluestorm> hm, i suppose i'll do that eventually :p
yangsx has quit [Read error: 110 (Connection timed out)]
<bluestorm> concerning your own problem : is it really important to have files with the stdlib names ?
<Yoric[DT]> At the moment, I'm assuming we're replacing the stdlib (at least from the point of view of the end-user).
<bluestorm> as far as i'm concerned, the extlib way (different names, with the overriding module instead) is fine, even if it ask for an explicit "open"
<Yoric[DT]> So if the end-user wants list features, the module ought to be called List .
<Yoric[DT]> Now, it could be Something.List .
<tsuyoshi> I think the best thing is to require one open at the beginning
<Yoric[DT]> Now, however, the extlib way has several Something: ExtList, ExtString, ExtEtc.
<tsuyoshi> like "open NewStdLib"
<tsuyoshi> and then just replace everything
<bluestorm> i think too : python users cope with those "from ... import ..." well
<Yoric[DT]> That's not the problem.
<Yoric[DT]> I was planning to have a few modules anyway. Just organized differently from ExtLib.
<tsuyoshi> I don't normally like open, because it's impossible to figure out which identifier came from which module
<Yoric[DT]> Containers.List, Containers.Stream, Containers.Array, bla.
<bluestorm> i see
<flux> tsuyoshi, however it would be excellent if the -dannot switch produced that information too
<Yoric[DT]> Data.Char, Data.Int, Data.Int32, etc.
<bluestorm> Haskell (GHC at least) as those, plus a standard prelude
<Yoric[DT]> Now, it's quite easy to write container.ml/container.mli and fill it with "module List = ExtList.List", "module Stream = ExtStream.Stream", etc.
<flux> tsuyoshi, actually there's a workaround I hadn't considered.. a global function with_db with the proper signature would remove the type annotations from user code.
<tsuyoshi> why put them into another module? what's wrong with just List, Array, etc.?
<Yoric[DT]> tsuyoshi: because it ends up not working: "the files bla and bla make inconsistent assumptions over interface Stream".
authentic has quit [Remote closed the connection]
* tsuyoshi checks backsrcoll
<tsuyoshi> backscroll
<Yoric[DT]> My problem is, if I do what I just wrote, if I want to a) package everything in a library b) extract documentation with ocamldoc, I need to write one huge container.mli, containing essentially list.mli, stream.mli, string.mli *with the ocamldoc comments*.
<tsuyoshi> oh.. why not fix ocamldoc?
<Yoric[DT]> My oh-so-smart-but-not-working build system used ocamlc's -pack (actually ocamlbuild's .mlpack) to avoid that.
alexyk_ has joined #ocaml
<Yoric[DT]> I started by rewriting extlist.ml into a extlist.mlpack including my own module List, which itself used somewhere internally Inrialib.List (Inrialib being a library defined trivially from OCaml's current standard library).
<Yoric[DT]> However, in that case, I eventually get bitten by these "inconsistent assumptions".
<Yoric[DT]> tsuyoshi: how would I do that ?
<Yoric[DT]> I mean, what should the semantics of ocamldoc be, then ?
<Yoric[DT]> I guess I'd need to change the semantics of ocamlbuild itself somewhere along the way.
<tsuyoshi> I think I need more sleep.. I'm not really understanding your problem at all
<tsuyoshi> I think that's the last time I take a night bus
<Yoric[DT]> :)
authentic has joined #ocaml
alexyk has quit [Read error: 110 (Connection timed out)]
authentic has quit [Read error: 104 (Connection reset by peer)]
LordMetroid has joined #ocaml
authentic has joined #ocaml
bla has quit [Read error: 110 (Connection timed out)]
* Yoric[DT] starts to wonder if the easiest technique wouldn't be to write a custom documentation generator.
bla has joined #ocaml
<Yoric[DT]> Does anyone have any experience with ocamldoc custom documentation generators ?
^authentic has joined #ocaml
asmanur has joined #ocaml
authentic has quit [Read error: 110 (Connection timed out)]
^authentic is now known as authentic
mikeX_ is now known as mikeX
jlouis has joined #ocaml
kornerr has left #ocaml []
jules_ has joined #ocaml
Linktim has joined #ocaml
<Yoric[DT]> ertai: ping
<thelema> Yoric[DT]: hi
svenl has quit [Remote closed the connection]
svenl has joined #ocaml
<Yoric[DT]> hi
<Yoric[DT]> thelema: I haven't had time to look at your code yet.
<Yoric[DT]> Do you agree with my idea of re-mapping packages onto a hierarchy ?
<jules_> Some time ago I saw a paper on combining compiler passes automatically, instead of running them one after the other. I think the researchers used OCaml to implement it. Does anyone know the name of the paper?
<Yoric[DT]> thelema: where exactly did you put your work on ropes ?
LordMetroid has quit ["Leaving"]
mfp has quit [Read error: 104 (Connection reset by peer)]
<thelema> Yoric[DT]: the work on ropes is in the community/ropes branch.
<Yoric[DT]> ok, thanks
<Yoric[DT]> How much merging is there with the stdlib ?
<thelema> as to making a superpackage, I don't see any problem.
<thelema> Yoric[DT]: the way I've done UTF-8 ropes is:
<Yoric[DT]> Oh, I hadn't seen that you had branches.
<thelema> 1) UChar - a Unicode char type (= int)
* Yoric[DT] wonders how to checkout branches.
<thelema> git co community/ropes
<thelema> 2) UTF8 - the type for UTF-8 strings (= string, but with two types of position indicators)
<thelema> err, UTF8 is raw utf8 strings
<thelema> and 3) rope.ml - immutable, high-level Unicode strings - this is where all the fun functions should go.
<Yoric[DT]> Ok.
<Yoric[DT]> Encoding-independent ?
<thelema> the big thing that I don't have working is Rope.of_latin1 to convert a raw byte string into a UTF-8 rope.
<Yoric[DT]> Could you give me the full command-line to checkout community/ropes ?
* Yoric[DT] isn't familiar with git.
<thelema> rope strings are always represented as UTF-8. When you iterate over them, you either iterate over UChars or over UTF8.t
<thelema> Yoric[DT]: step 1 - clone the whole repo: git clone git://github.com/thelema/ocaml-community.git
<Yoric[DT]> I've done that.
<thelema> Yoric[DT]: step2: (within the repository, anywhere) git co community/ropes
<Yoric[DT]> $ git checkout community/ropes
<Yoric[DT]> error: pathspec 'community/ropes' did not match any file(s) known to git.
<Yoric[DT]> Did you forget to 'git add'?
RobertFischer has joined #ocaml
<Yoric[DT]> I'll restart from scratch.
<thelema> what do you get when you type [git branch]?
<Yoric[DT]> dl in progress
<thelema> git branch should list all existing branches.
<Yoric[DT]> Too late, I've removed the directory.
<Yoric[DT]> By the way, unrelated question.
<Yoric[DT]> So far, for exceptionless error-management, I've used suffix "_exn".
<Yoric[DT]> I'm wondering if prefix "may_" would not be clearer.
<thelema> i.e. List.may_find xxx?
<thelema> as opposed to List.find_exn xxx?
<Yoric[DT]> indeed
<thelema> I think _exn makes it plainer that _exn functions throw exceptions. may_find would likely return an option type.
<Yoric[DT]> Fair enough.
<Yoric[DT]> Can you think of some other prefix/postfix which would be nicer ?
<bluestorm> if you're considering using may_ prefix for option types, and keeping the exceptionfun names unchanged, i think that would be quite appreciated
<thelema> to indicate x will throw the exception?
<bluestorm> (because i'm pessimistic and i think people generally won't have to change, and the one fond enough of option types will be happy to have them and thus not protest again an added prefix)
<bluestorm> s/won't have/won't like/
Linktim has quit [Read error: 110 (Connection timed out)]
<jlouis> Yoric[DT], you should run 'git branch -r' in that case since it looks like community is a remote branch
<jlouis> Yoric[DT], you might have it named as origin/ropes
<Yoric[DT]> aha, origin/community/ropes
<Yoric[DT]> thelema: yeah.
<Yoric[DT]> bluestorm: it does make sense, but it's also a bit self-defeating.
<Yoric[DT]> The idea is that someone who doesn't use a function named [insert here some clever prefixing/postfixing/pattern-matching/whatever] should be sure that they won't need to handle any exception they haven't thrown themselves.
<bluestorm> hm
<RobertFischer> For The Room: What's the preferred way to do graphics in Ocaml?
rodge has quit [Read error: 110 (Connection timed out)]
<hcarty> RobertFischer: What sort of graphics?
<bluestorm> i've got the feeling that option/either/monads are aimed to more "educated" people; in that setting it's quite logical to have the not-perfect-but-simple-solution simple, and the requiring-advanced-tools-and-experience a prefix ahead for people who care
<flux> depends: for bit map graphics I prefer SDL, for vector based OpenGL, for GUI-stuff lablgtk2
<flux> at some of these can be combined
<RobertFischer> I just got a snippet of Java code which displays a frame with a button in it, and someone asked me how it would look in Ocaml. I've never done anything like that in Ocaml, though.
<flux> lablgtk2, then
<RobertFischer> GUI stuff is what I'm looking for.
<RobertFischer> Cool.
<bluestorm> with a bit of luck we may have a Qt binding too next year
<Yoric[DT]> lablgtk2 is nice
<Yoric[DT]> I'd really like to be able to use Chris King's functional reactive GUI, though.
<hcarty> Yoric[DT]: I second bluestorm's comments regarding using may_* for the option-returning functions and leaving the exception-throwing functions as is
<Yoric[DT]> thelema: what's the relation between your UChar and Camomile ?
<hcarty> s/as is/as they are/
<Yoric[DT]> hcarty: well, I might do that, then.
<thelema> Yoric[DT]: UChar comes pretty straight out of camomile. Same with UTF8, although I made changes there.
<Yoric[DT]> thelema: the comments make it look like they come out of ExtLib.
<Yoric[DT]> Am I wrong ?
<Yoric[DT]> Or does ExtLib contain bits of Camomile ?
<thelema> huh? the comments on my uChar.ml say "(* Copyright 2002, 2003 Yamagata Yoriyuki. distributed with LGPL *)
<thelema> which is definitely camomile
<Yoric[DT]> (*
<Yoric[DT]> * UChar - Unicode (ISO-UCS) characters
<Yoric[DT]> * Copyright (C) 2002, 2003 Yamagata Yoriyuki
<Yoric[DT]> *)
<Yoric[DT]> ...from extlib
mfp has joined #ocaml
<thelema> so extlib took that from camomile
<thelema> (I think)
<Yoric[DT]> Well, a short diff shows that the files are mostly identical.
<Yoric[DT]> I thought Camomile needed plenty of external files ?
<Yoric[DT]> camomile/locales/*
jules_ has left #ocaml []
<thelema> it does. That's what the unicode/ dir will be for (once I can get that working)
<Yoric[DT]> camomile/database/*
<Yoric[DT]> ok
<thelema> It needs external files for the character conversions.
<thelema> I've *not quite* got that part working.
<Yoric[DT]> I'll place that inside batlib once you've got it to work.
<Yoric[DT]> Btw, I've contacted the author of MissingLib, who informed me that he's not maintaining it anymore.
<thelema> fair enough.
<thelema> Yes, I have permission from him to use his code as LGPL2.1 w/ linking exception.
<Yoric[DT]> Nice.
<Yoric[DT]> I've also contacted the author of AnnexLib, but I haven't received an answer yet.
<Yoric[DT]> I'll work on the integration of MissingLib, if you want.
<thelema> it's already under the right license. I don't recall whether I contacted him yet.
<thelema> I have gone over missinglib, and there doesn't seem lots of value (IIRC)
<Yoric[DT]> ok
<thelema> sadly, I must pack for flight right now.
<Yoric[DT]> I checked yesterday and it didn't have the linking exception.
<Yoric[DT]> Have a nice flight.
Linktim has joined #ocaml
<thelema> thanks. Good job w/ library.
<Yoric[DT]> thanks
delamarche has joined #ocaml
|Catch22| has joined #ocaml
<RobertFischer> thelema: Sounds like Community Ocaml is coming along nicely.
catch22 has joined #ocaml
|Catch22| has quit [Read error: 113 (No route to host)]
schme has quit [Remote closed the connection]
thelema has quit [Read error: 110 (Connection timed out)]
schme has joined #ocaml
schme has quit [Remote closed the connection]
schme has joined #ocaml
schme has quit [Remote closed the connection]
schme has joined #ocaml
chacun has joined #ocaml
<Yoric[DT]> RobertFischer: he's probably in the plane by now :)
<chacun> anyone heard of efforts to build ocaml -bytecode and opt compilers- in 64 bit mode (x86_64) on 64 bit intel macosx?
<Yoric[DT]> ok, extGenlex now implemented.
catch22 has quit [Read error: 113 (No route to host)]
filp has quit ["Bye"]
filp has joined #ocaml
^authentic has joined #ocaml
authentic has quit [Read error: 110 (Connection timed out)]
^authentic is now known as authentic
<Yoric[DT]> mmmhhh....
<Yoric[DT]> Does anyone know the set of chars ?
<delamarche> Uh, what? :)
<rwmjones> is anyone using tuareg-mode with *.annot files?
Modius_ has joined #ocaml
Modius_ has quit [Read error: 104 (Connection reset by peer)]
Modius_ has joined #ocaml
<flux> I am
<flux> they're great!
dlomsak has joined #ocaml
Modius__ has joined #ocaml
dlomsak has left #ocaml []
<rwmjones> flux, you're using tuareg-mode with *.annot files? how do you get it to work / do anything at all?
<rwmjones> I've compiled everything with -dtypes
<rwmjones> and got annot files
<rwmjones> but tuareg-mode ignores them afaict
naufraghi has joined #ocaml
<naufraghi> Hello ocamlers
<naufraghi> I have developed a small backprop neural net in ocaml, just as an exercise
<naufraghi> http://ocaml.pastebin.com/m6fe89d0 <-- the bpnn
<naufraghi> but... it doesen't converge... so, 2 questions... ocaml best pratices to find a bug?
<naufraghi> (ups... I have to go... I'll post the question again in half an hour...)
naufraghi has left #ocaml []
<delamarche> well, i can tell you that ocamldebug is probably not the way to go :D
<delamarche> in my experience
Modius has quit [Connection timed out]
niraj1234 has joined #ocaml
niraj1234 has quit [Remote closed the connection]
<hcarty> bluestorm: re: our module vs class discussion yesterday: I did a test comparing a grid module with a grid class, with the grid elements made up of histograms. The difference turns out to be small-to-none, with the class implementation generally being very slightly quicker than the module implementation.
<hcarty> The actions applied were the same in both cases.
Modius_ has quit [Read error: 110 (Connection timed out)]
<hcarty> So for this case at least, the difference really does seem to come down to "do you need subtyping?" and what looks prettier.
<hcarty> bluestorm: Sorry, the grid elements were floats, not histograms
<petchema> rwmjones: do you also have installed ocaml-mode? tuareg-mode relies on it to implement *.annot support
<rwmjones> hmmm
<flux> yes, it uses caml-types.el
<rwmjones> no I don't ... I'll try it, thanks
<flux> I had the same problem on za host, until I finally took the effort to track it down..
ikaros has quit [Read error: 110 (Connection timed out)]
ikaros has joined #ocaml
<flux> maybe tuareg mode should document that dependency so that the tidbit would show at the time on invoking the feature..
<Yoric[DT]> mmmhhhh....
* Yoric[DT] is having problems with the forge.
<petchema> flux: it must be documented somewhere, I don't remember finding it the hard way :)
<flux> pft, documentation.. ;)
<rwmjones> yup, it works
<rwmjones> that should be a dependency on tuareg-mode then ...
<petchema> Recommends: ocaml, ocaml-mode
<rwmjones> in fedora, of course
<Yoric[DT]> Is anyone around here using the forge ?
postalchris has joined #ocaml
RobertFischer has quit []
pango_ has quit [Remote closed the connection]
pango_ has joined #ocaml
gim has quit [Read error: 110 (Connection timed out)]
ppsmimou has quit [Read error: 110 (Connection timed out)]
rodge has joined #ocaml
gim has joined #ocaml
ppsmimou has joined #ocaml
jonafan has joined #ocaml
<rwmjones> is anyone using reins (http://ocaml-reins.sourceforge.net/api/Reins.html)?
<rwmjones> implementing AVL trees for linear ranges is making my head hurt ...
<delamarche> Man, I've never been on an IRC channel where a discussion of AVL trees comes up every day :)
<delamarche> I love it here.
<delamarche> Wasn't reins the result of a janes capital summer project?
<rodge> lol, that's what the page says :)
<delamarche> I suppose i could have just clicked on the link :)
<delamarche> Hmmn, I've been working on a suffix array module for ocaml, maybe I'll contribute it if it doesn't suck
jonafan_ has quit [Connection timed out]
<jlouis> rwmjones, CLRS has a chapter on that, I think
<jlouis> at least the 2nd edition
naufraghi has joined #ocaml
postalchris has quit [Success]
<Yoric[DT]> delamarche: what do you mean "suffix array" ?
<delamarche> quick way of searching all substrings of a string
<delamarche> used heavily in comp bio
<delamarche> i was surprised to see them mentioned at the end of the 2nd edition of programming pearls
<delamarche> kinda like what a trie would be used for, but awesomer than a trie
<delamarche> better locality properties, much easier to understand, etc
<delamarche> construction is a bit tricky, but exciting
<delamarche> heh
Modius__ is now known as Modius
asmanur has quit [Remote closed the connection]
<bluestorm> hcarty: i have to admit i never considered any other difference :p
<naufraghi> Hello ocamlers
<bluestorm> rwmjones: i'm quite interested in your "matches" extension, do you have a recent source or is bit i saw on the mailing-list the only one ?
<naufraghi> I have developed a small backprop neural net in ocaml, just as an exercise in ocaml (coming from python)
<naufraghi> http://ocaml.pastebin.com/m6fe89d0 <-- the bpnn
<naufraghi> but... it doesen't converge... so, 2 questions... ocaml best pratices to find a bug?
<hcarty> bluestorm: I am crunching through 10 years of satellite data, so performance is something of an issue. And to my eyes, there is very little difference between the two methods... they are both clean and nicely type-inferenced.
<hcarty> naufraghi: lots of printf statements, compile with debugging symbols, run with OCAMLRUNPARAM=b to get backtraces on uncaught exceptions...
<naufraghi> OCAMLRUNPARAM sounds good!
<naufraghi> hu, and comments on the code are wellcome, this is my second programm in ocaml
<hcarty> naufraghi: In general, I would avoid using "let _ = ..." as it can cover up subtle errors
<hcarty> Either "statement;" or "let () = ... in" if you are performing a side-effect only operation
<naufraghi> ... that was to avoid the warning... i'd like a return value in the toplevel, but no warnings once built...
<bluestorm> hm
<naufraghi> ... say, compiling
<bluestorm> ocaml
<bluestorm> [18:37:46] <hcarty> naufraghi: In general, I would avoid using "let _ = ..." as it can cover up subtle errors
<bluestorm> [18:38:55] <hcarty> Either "statement;" or "let () = ... in" if you are performing a side-effect only
<bluestorm> eerk
<bluestorm> next_layer.inputs <- curr_layer.outputs;
<bluestorm> next_layer.delta_inputs <- curr_layer.delta_outputs;
<bluestorm> are you sure those two lines won't cause unnecessary side-effects ?
<naufraghi> i'd like the stricture to be shared
<bluestorm> hm, ok
<naufraghi> is this the way?
<bluestorm> yes, array get copied "by reference"
<naufraghi> ach, so the bug is elsewere...
<bluestorm> hm
<bluestorm> i'm afraid the only thing i can tell by looking at caml code right now is "which syntax extension you could use" -__-
<naufraghi> bluestorm: what does "which syntax extension you could use" means?
<bluestorm> hm
<bluestorm> i've been toying with camlp4 syntax extension ( an ocaml preprocessor ) for two/three days, and now i think "ah, one could use ty_constr there" instead of focusing on the real problem
<naufraghi> eheh
<hcarty> naufraghi: What is the problem you are having with this code?
<naufraghi> a bug, but perhaps algoritmic... if the mutable game is ok, I cannot hope in an "ocalmization" bug...
<rwmjones> bluestorm, pong
<bluestorm> :p
<rwmjones> bluestorm, there's a slightly newer version, just a few extra helper functons
<rwmjones> functions
<rwmjones> you want me to upload it?
<bluestorm> i'd be interested
<bluestorm> (i'm also considering sharing code with my pa_refutable extension)
<rwmjones> two secs
OChameau has quit ["Leaving"]
<rwmjones> bluestorm, sorry, I'm now confusing pa_bitmatch with matches :-(
<rwmjones> the version of _matches_ isn't even a version, I just posted it on the list & forgot about it, so you can take it
* rwmjones might as well release bitmatch 0.6 anyway
<bluestorm> :p
<bluestorm> bitmatch is interesting too, but i wouldn't consider including in my osr_camlp4 attempt right now, because it needs run-time library support
pango_ has quit [Remote closed the connection]
pango_ has joined #ocaml
filp has quit ["Bye"]
<bluestorm> do you know if .cmx/.cmxa are shared ?
<orbitz> does the example of multiple inheritenc here actually show multiple inheritencE? i only see one inherit
<bluestorm> the two lines before the inherit may have replaced "inherit colored_point y c"
<orbitz> is it a mistake in the documentaiton?
postalchris has joined #ocaml
Demitar has quit [Read error: 110 (Connection timed out)]
Demitar has joined #ocaml
delamarche has quit []
Snark has joined #ocaml
pango_ has quit ["I shouldn't really be here - dircproxy 1.0.5"]
delamarche_ has joined #ocaml
delamarche_ has quit [Remote closed the connection]
netx has quit ["Leaving"]
delamarche_ has joined #ocaml
postalchris has quit [Connection timed out]
pango has joined #ocaml
szell has quit [Connection timed out]
Linktim_ has joined #ocaml
naufraghi has quit []
evn_ has joined #ocaml
<Yoric[DT]> bluestorm: I've just integrated your numeric stuff to batteries.
<bluestorm> ha
<bluestorm> i thought about it yesterday, when i came across something really similar in annexlib
Linktim has quit [Read error: 110 (Connection timed out)]
* Yoric[DT] now needs to remember how darcs works.
<bluestorm> heh, darcs is easy at least
evn_ has left #ocaml []
<bluestorm> (weren't you using git ? switching DCVS so often might be bad for health :-' )
<Yoric[DT]> Not using git yet.
<Yoric[DT]> thelema is
psnively has joined #ocaml
<Yoric[DT]> At the moment, I'm waiting for either the forge's svn to start working or for the forge's admin to give me a git.
<psnively> svn or git. Ugh.
<hcarty> What is the "numeric stuff"? Sounds interesting
<rwmjones> ch***, I'm having an argument with the "all garbage collectors are bad" brigade
<bluestorm> hcarty: nothing really exciting : http://bluestorm.info/ocaml/numeric/numeric.mli.html
<psnively> rwmjones: I would have thought that you knew better. ;-)
<rwmjones> it's tempting to say that they're all idiots, but to be fair the most frequently used garbage collectors _are_ bad
<psnively> That doesn't stop them from being idiots.
<psnively> Anymore than most static type systems being lame stop the dynamic typing crowd from being idiots.
* psnively shrugs.
<psnively> Life is too short to edumacate the willfully ignorant.
<Yoric[DT]> mmmh....
<bluestorm> (javascript guy spotted)
<rwmjones> this one guy thinks that no GC releases memory back to the system (because it's impossible - how could it deal with internal fragmentation?) .... arrrrr
<Yoric[DT]> ok, found the problem with the forge
* Yoric[DT] now needs to wait a few hours for cron.
<Yoric[DT]> rwmjones: where is that ?
<Yoric[DT]> (the trollfest, that is)
<psnively> rwmjones: step away from the monkey-boys.
<rwmjones> oh, it's internal company discussions
<psnively> rwmjones: quit hiring fools. ;-)
<Yoric[DT]> :)
<Yoric[DT]> bluestorm: I'll show you your code tomorrow :)
<Yoric[DT]> (I've added a few things somewhere along the way)
<Yoric[DT]> By the way, I have a question.
<Yoric[DT]> Does anyone know why num, str and bigarray are kept as separate libraries ?
<hcarty> (speculation) Maybe because they rely more on C?
<hcarty> I think all three of those have a fair amount of C code at their core
<tsuyoshi> num and str originally had license issues iirc
szell has joined #ocaml
<tsuyoshi> bigarray I don't know.. it's pretty well integrated with the compiler internals
<jonafan> plus the str library is silly
<Yoric[DT]> What do you mean ?
<jonafan> i don't like the way a lot of the functions are tied to the previous call to string_match
<tsuyoshi> oh yeah.. not functional at all
<tsuyoshi> I wouldn't even code it that way in c
<jonafan> right
<jonafan> still, can't live without regexp
<tsuyoshi> there's a couple other regex libraries though
<hcarty> Pcre is much nicer to use
<jonafan> they should include that in ocaml then
<hcarty> The core devs don't want to add more to the basic OCaml distribution
<hcarty> Which is why Yoric[DT], thelema, bluestorm and others are working on a community distribution
<jonafan> cool
<hcarty> With the blessing of Xavier Leroy (and I suppose the rest of the core team)
<psnively> I see there's a SoC effort to replace the GC/runtime, too.
coucou747 has quit [Read error: 113 (No route to host)]
<Yoric[DT]> That looks nice, too.
<Yoric[DT]> Does anyone know how cross-platform PCRE is ?
<psnively> Very.
ozzloy has joined #ocaml
Amorphous has joined #ocaml
<Yoric[DT]> Does anyone see any objection to putting PCRE inside Batteries Included ?
<flux> well, it is not a small dependency?
<flux> what other big c library dependencies are there?
Amorphous has quit [Connection timed out]
Amorphous has joined #ocaml
Snark has quit [Remote closed the connection]
<Yoric[DT]> You mean inside Batteries Included ?
<Yoric[DT]> At the moment, nothing.
* Yoric[DT] is trying to decide what the value of min_num and max_num should be for big integers.
<delamarche_> hehehe
<bluestorm> Yoric[DT]: there isn't, wich is a bit problematic :p
<Yoric[DT]> :)
<bluestorm> i had a similar problem, and found a way to encode infinity in Num
<delamarche_> well
<delamarche_> yeah there you go
<bluestorm> i'm not sure num_of_big_int can translate infinity to big_int actually
* Yoric[DT] is trying to understand how to encode infinity with num.
<bluestorm> hm
<bluestorm> basically 1 / 0
<Yoric[DT]> # Ratio.create_ratio unit_big_int zero_big_int;;
<Yoric[DT]> Exception: Failure "create_ratio infinite or undefined rational number".
<bluestorm> aah yes
<bluestorm> there was that ugly thing
<bluestorm> Arith_status.set_error_when_null_denominator false;
<bluestorm> :-'
<Yoric[DT]> ugly indeed
<bluestorm> Exception: Failure "big_int_of_ratio".
<bluestorm> heh
<Yoric[DT]> Not very useful, then.
<bluestorm> Yoric[DT]: maybe we should remove max_num and min_num from the Numeric signature
<Yoric[DT]> Which leaves us with two choices: either remove min_num/max_num from the definition of numbers...
occc has joined #ocaml
<occc> greatings!
<Yoric[DT]> or write in the documentation that it only has a meaning for those numbers which do have a min and a max value.
<Yoric[DT]> greetings occc
<bluestorm> you could keep them in the capable module declaration, and even add a BoundedNum interface, wich i'm not sure is necessary
<mbishop> infinity : RR64 = 1.0 / 0.0
<Yoric[DT]> RR64 ?
<mbishop> that's from Fortress heh
<Yoric[DT]> tsss
<occc> any one can tell me how i can find the minimum of a list [3;2;1;0] by using same function in function (rec)
<Yoric[DT]> What's a nat, again ?
<Yoric[DT]> occc: I beg your pardon ?
<occc> what?
<Yoric[DT]> everybody-involved-in-the-previous-conversation: where is type nat defined ?
<Yoric[DT]> occc: what exactly is your question ?
* Yoric[DT] is pretty sure occc is looking for someone to help him with his exercises, but still.
<Yoric[DT]> s/exercises/homework/
<occc> im exercising myself
<occc> :)))))
<bluestorm> Yoric[DT]: otherlibs/num/nat.mli
<Yoric[DT]> Thanks.
<bluestorm> they're not in the documentation, i don't know why
<bluestorm> arith_status isn't either
<bluestorm> occc: so this is not a class homework ?
<Yoric[DT]> That's one of the problems with the documentation.
delamarche_ has quit [Read error: 104 (Connection reset by peer)]
delamarche has joined #ocaml
<Yoric[DT]> A number of modules are missing.
<occc> nop
<delamarche> just to pipe in here
<delamarche> technical difficulties aside, I think it would make sense for max_num to be +inf and min_num to be -inf
<Yoric[DT]> Indeed.
<delamarche> but barring that, removing them altogether seems like a reasonable alternative
<Yoric[DT]> Unfortunately, there doesn't seem to be a +inf or -inf here.
<delamarche> what do i know really, though
<Yoric[DT]> Especially since my next stop will be complex numbers :)
<delamarche> well, i don't really know much about how you're implementing this
<delamarche> but why wouldn't variant types serve here?
<Yoric[DT]> I'm just adding a layer on top of Big_int.
<delamarche> keep in mind that i'm an idiot
<delamarche> hahaha
occc has quit []
<Yoric[DT]> I'm not planning to reimplement it.
<jlouis> ah! occc is doing homework!
* Yoric[DT] remains convinced that occc was looking for someone to do homework.
naufraghi has joined #ocaml
* jlouis high-fives Yoric[DT]
<delamarche> i suddenly envisioned the both of you as ninja turtles
<delamarche> "come on bro, gimme three!"
<Yoric[DT]> :)
<Yoric[DT]> "pizza time!"
<delamarche> wise man says forgiveness is divine
<delamarche> but never pay full price for late pizza
<delamarche> Anyhow, Yoric[DT], if you don't mind me continuing my stupid blathering
<delamarche> my question is, if you're adding a layer on Big_int
<delamarche> why could you not define a new variant type defined in terms of the existing Big_int type?
<delamarche> so like, type my_new_bigint = PosInf | NegInf | BigInt of [old bigint type]
* delamarche has likely just effectively demonstrated that he is, in fact, quite stupid.
<bluestorm> delamarche: your demonstration was not really convincing, you sure can do better
<bluestorm> such a layer would work fine, except it may impact performances
<bluestorm> the question is "do we care ?"
<bluestorm> i personally think we could drop those min_num , max_num stuff
<delamarche> Well, my answer to that would be, have other bigint libraries cared?
<delamarche> heavily used ones
<delamarche> I suspect the same as you, it could easily be dropped
<bluestorm> cared about performance ? certainly
<delamarche> No, I mean about the absence of min and max
<bluestorm> in my experience min_int and max_int are used for sentinels
<delamarche> Performance is certainly an issue, since it's almost certainly numerical comp or simulation people using bignum libraries
<delamarche> those guys get sticky over cycles :)
<bluestorm> as in let minimum = ref max_int in
<bluestorm> wich can be avoided using more clever methods
<bluestorm> (using an option type, the first element, etc.)
<delamarche> There's your answer then, I guess. If there's a common use case for it that has a simple workaround
<delamarche> don't bother with it, and just document the workaround in the API docs
<bluestorm> Yoric[DT]: do you see a real need for min_num / max_num ?
<Yoric[DT]> Not really.
<delamarche> For the record
<delamarche> I know how much we love java here
<delamarche> but in the Java API
<delamarche> BigInteger inherits directly from Number
<delamarche> and does not have MAX_VALUE or MIN_VALUE constants
<delamarche> Whereas Integer also inherits directly from number, and has those constants
<delamarche> so it looks like they faced the same conundrum, and decided that the idea of min/max values doesn't make sense for bignums. And with that, I am officially shutting up
<bluestorm> we could remove them from the interface, and keep them in implementation were it makes sense
<Yoric[DT]> Sounds like the est idea.
<Yoric[DT]> s/est/best/
<Yoric[DT]> Of course, now, the next issue is modulo.
<Yoric[DT]> While modulo might have a meaning for integers and floats, it doesn't look quite meaningful for complex numbers.
<Yoric[DT]> I also don't remember exactly how to computer arbitrary powers inside the realm of C.
<delamarche> Do you guys have a project page for this batteries included thing?
<Yoric[DT]> Not yet.
<Yoric[DT]> We should make one :)
<delamarche> great name
<delamarche> My initial OCaml learning effort was supposed to be so I could make a 'batteries included' ocaml distribution
<delamarche> lofty goal
<delamarche> and now you guys are doing it!
<delamarche> best possible scenario for me :D
<delamarche> hahaha
<Yoric[DT]> :)
<Yoric[DT]> Feel free to join :)
<delamarche> I was just going to say, I have some spare mental capacity right now
<delamarche> so if there are places where I think I can be useful, I'll chime in
<bluestorm> hmm Yoric[DT]
<bluestorm> z^z' = e^z' ln z ?
<Yoric[DT]> Not much easier, as you need to define ln for complex numbers :)
<Yoric[DT]> Which, iirc, is not possible.
<bluestorm> Complex.log already exists
<bluestorm> it must not be defined on R-
<Yoric[DT]> (well, anyway, Complex.pow already exists)
<bluestorm> ah, yes :D
<Yoric[DT]> Actually, there's an infinite number of possible definitions.
<Yoric[DT]> You just need to remove one half-[droite ? what's the term in English ? infinite segment ?] from 0.
<bluestorm> but the one without R- may be the most natural to most people
<Yoric[DT]> Probably.
<bluestorm> and it actually does not have to be a droite/segment
delamarche has quit []
<Yoric[DT]> Doesn't it ?
sporkmonger has joined #ocaml
<bluestorm> any unbounded connected region with 0 should do the job
<Yoric[DT]> Probably.
<Yoric[DT]> A bit weird, though :)
<bluestorm> :]
delamarche has joined #ocaml
psnively has quit []
* Yoric[DT] starts to wonder whether Complex should be a Number.
<pango> Yoric[DT]: those functions are defined on C domain using the limit of series (just like in R)
<Yoric[DT]> Yeah.
postalchris has joined #ocaml
<Yoric[DT]> But it's slightly tricky to get from these definitions to implementations :)
* Yoric[DT] also wonders what to do for Complex.compare.
<Yoric[DT]> Pervasives.compare or assert false ?
<Yoric[DT]> Probably Pervasives.compare, although it's mathematically meaningless.
psnively has joined #ocaml
delamarche has quit []
<pango> it may not be "canonical", or maybe complexes lack canonical compare, but it's not meaningless; it should still be a total order over C
jlouis has quit ["Leaving"]
jlouis has joined #ocaml
<Yoric[DT]> Fair enough.
* Yoric[DT] is now faced with a mysterious unbound constructor.
comglz has joined #ocaml
<Yoric[DT]> Most of the contents are inside extlib (it's extlib-1.5.1 + thelema's work on ropes + your work on numeric + lazy lists + SDFlow + improvements to enum + other utilities)
sporkmonger has quit [Read error: 110 (Connection timed out)]
Linktim_ has quit [Remote closed the connection]
Demitar has quit [Read error: 110 (Connection timed out)]
<gildor_> Yoric[DT]: do you still need a git on forge.ocamlcore.org
<Yoric[DT]> « The repository is already existing
<Yoric[DT]> but need to install git into the chroot. »
<Yoric[DT]> So I believe it's coming.
<Yoric[DT]> Oh.
* Yoric[DT] hadn't identified you :)
<gildor_> yeah, it is coming
<Yoric[DT]> Well, I believe it would be best.
<Yoric[DT]> I'm using the svn for now, mostly for backup purposes.
<gildor_> but since you inject your project into svn...
<gildor_> ok
<Yoric[DT]> If git is too much trouble, of course, I'll continue using svn.
<Yoric[DT]> It's not a big deal.
<gildor_> i don't know exactly how much time it will take to setup something working
<Yoric[DT]> No emergency.
<Yoric[DT]> The important point was to be able to backup.
znutar has quit ["leaving"]
<gildor_> with darcs i get something after 24 hours, but i know darcs, and i don't (yet) know git
<Yoric[DT]> Git would be nice to use the same system as thelema.
<Yoric[DT]> I have never used git, I must admit.
<Yoric[DT]> It's just to uniformize.
<gildor_> so it will be a great discover for everyone
<gildor_> you will also need to help me debug the installation
<gildor_> when it will be finished, i will allow anyone to use git
<jlouis> git is indeed not a bad idea
<psnively> Why not use darcs 2?
<hcarty> As I understand, darcs does not, by default, keep a clear history of when things happened. It's a strength in some cases, a weakness in others.
<psnively> As stated, I will claim that that's false.
<psnively> But perhaps a use-case would clarify things.
<bluestorm> i think the main reason to choose git is that thelema use git
<hcarty> "As I understand" - so I may be wrong
<psnively> Thelema?
<Yoric[DT]> Edgar Friendly.
* psnively is lost. :-)
<Yoric[DT]> <thelema> sadly, I must pack for flight right now.
* Yoric[DT] may not have understood the question.
<bluestorm> we have to choose something anyway; i agree darcs seems more easy to use, but a lot of people learned git recently and they're not dead yet
<bluestorm> hmm
<Yoric[DT]> :)
<psnively> git just seems like... I dunno. A whole lotta tool to learn for not much benefit.
<bluestorm> on the other hand, a lot of people learned git recently *and* code in C everyday, and are not dead yet
<hcarty> I learned it recently and feel more alive than ever! Clearly, this is due to learning git.
<bluestorm> maybe the'yre especially resilient
<psnively> ==bluestorm
<psnively> lol
<Yoric[DT]> Maybe it's some form of inoculation ?
<hcarty> psnively: darcs and git seem pretty similar to me
<psnively> hcarty: hm.
<hcarty> The recent versions of git seem to be pretty reasonable with respect to the quality of the interface
<hcarty> darcs has the benefit of fitting in to one binary, but the "git" wrapper hides the multitude of tools used by git
<hcarty> They both have chunk-by-chunk commit, which was the killer darcs feature for me when I first learned of it
<psnively> Yeah. For me it's still cherry-picking with history-sensitive merging.
<hcarty> I think they can both do that as well, though I don't know how the interfaces compare
<psnively> Yeah. I'm just kibbitzing; y'all should use whatever makes sense to you.
<hcarty> I hope to get the time to check out darcs again now that v2 is out. Its command line interface is very nice.
<psnively> So far, v2 seems like a huge improvement on the 1.x pain points, but subjectively seems appreciably slower on day-to-day operation.
<hcarty> I picked up git instead because C and Perl are more common than GHC
<hcarty> And the in-place-checkout seemed ridiculously cool
<psnively> Yeah, but who builds their VCS from source? :-)
<hcarty> Someone who doesn't have root access to a CentOS 4 server
alexyk_ has quit []
<hcarty> Though there are probably statically compiled darcs binaries that would work... that was what I used in the past, linked from the main darcs site
<psnively> Right.
<psnively> Again, just thinking out loud. I looked at git, and my impression was: ugh.
sporkmonger has joined #ocaml
<jlouis> psnively, have another look then. It's pretty clever
<jlouis> But admitted, you won't get everything packed and wrapped up nicely inside a monad
<psnively> Heh.
znutar has joined #ocaml
structured has joined #ocaml
<gildor_> the big difference between darcs and git (from an admin point of view) is that darcs from time to time end up eating all the cpu
<gildor_> this is not cool and lead to many problems
<gildor_> in particular, on a server shared by different user, who don't have root access and can't kill a darcs launched by another user
<psnively> I think 2.0 no longer snarfs all CPU.
<gildor_> yep, i will maybe upgrade darcs of forge.ocamlcore.org to 2.0
<gildor_> but i need to be sure that it is ok
<gildor_> for now darcs process is killed automatically after 2minutes of processing
<psnively> Right. Maybe worth testing. Maybe not. If you have enough happy git users, great.
<psnively> Indeed.
<gildor_> well, in fact i use darcs everyday and i think git is too complicated
<gildor_> i prefer darcs over git
<psnively> I do too, but when you're hosting a shared service, it's important that it be well-behaved. :-)
<gildor_> BUT i recognize that there is problem with darcs (which is not cool)
<psnively> I think 2.0 is worth investigating, for small values of time spent investigating.
seafood_ has joined #ocaml
<gildor_> indeed, forge.o.o will be a good place to test darcs on a shared server
<psnively> There you go.
* Yoric[DT] is going to wish everyone a good night.
<Yoric[DT]> Be reading you.
Yoric[DT] has quit ["Ex-Chat"]
seafood_ has quit []
RobertFischer has joined #ocaml
<rwmjones> bluestorm, thanks
<rwmjones> post to list?
<bluestorm> didn't
<bluestorm> feel free to do that ^^
<bluestorm> (the source file is http://bluestorm.info/camlp4/pa_matches.ml )
Demitar has joined #ocaml
derenrich has joined #ocaml
postalchris has quit ["Leaving."]
<palomer> hello
<palomer> my makefile looks like this:
<palomer> ocamlc file1.ml .... file15.ml
<palomer> it takes _ages_ to compile
<palomer> but I don't want to create a task for every file
<palomer> what should I do?
comglz has quit ["AddToFunc ExitFunction I Exec exec sudo halt"]
bluestorm has quit ["Konversation terminated!"]
derenrich has quit [Connection timed out]