flux changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | 3.11.0 out now! Get yours from http://caml.inria.fr/ocaml/release.html
ramenboy has quit [Remote closed the connection]
jonasb has quit [Remote closed the connection]
Camarade_Tux has quit [""skiiiiii on tomorrow ! \ ( ^ _ ^ ) /""]
seafood has joined #ocaml
slash_ has quit [Client Quit]
sporkmonger has joined #ocaml
comglz has quit ["Lost terminal"]
patronus has joined #ocaml
oriba has quit ["Verlassend"]
sgnb has quit [Read error: 104 (Connection reset by peer)]
sgnb` has joined #ocaml
tar_ has quit []
tar_ has joined #ocaml
ched_ has joined #ocaml
ched has quit [Read error: 110 (Connection timed out)]
<tsuyoshi> the docs say it's supposed to work
<tsuyoshi> haven't tried it on osx yet, but on linux I had to install famd before it would work
ched_ has quit [Remote closed the connection]
pango_ has joined #ocaml
pango has quit [Remote closed the connection]
AxleLonghorn has joined #ocaml
<AxleLonghorn> would anyone be willing to help me make this code better?
<AxleLonghorn> the problem is that OCaml warns about the fact that ``List.fold_left (aux context) p rest'' returns a value when it should return ().
<AxleLonghorn> Is there any way I could refactor the code to make that go away? (the warnings thrown by the compiler are annoying, but I'd rather not turn them off in case it's a legitimate warning
sporkmonger has quit []
<AxleLonghorn> in case I get a legitimate warning later, that is
<tsuyoshi> you can change List.fold_left (aux context) p rest ;
<tsuyoshi> to either
<tsuyoshi> let _ = List.fold_left (aux context) p rest in
<tsuyoshi> or
<tsuyoshi> ignore (List.fold_left (aux context) p rest);
<AxleLonghorn> the compiler doesn't warn about unused variables if you do _?
<sanguinev> AxleLonghorn: _ is used for results/matches/values you want to aknowledge but do not care what the result is.
<AxleLonghorn> what is ignore exactly? a keyword? built-in function?
<AxleLonghorn> also thanks both of you, I didn't think this was solvable
<sanguinev> AxleLonghorn: No problem. I assume "ignore" means ignore the result but is procedural. So use ignore when you want to execute some code, where as "_" can be usd in matching as well.
* sanguinev is happy for someone more knowledgable about "ignore" to correct/comment if the assumption is wrong...
<AxleLonghorn> weird, I'm trying to find somewhere that details this, but google is not too much of a help... hell, it's even on the wikipedia page in an example. No word of anyone saying "this is what it does"
<sanguinev> AxleLonghorn: I can't find anything too helpful either (maybe time to invest in a Ocaml textbook), but I suspect the difference is:
<sanguinev> "ignore (stuff);" is the same as "let _ = stuff in", the utility of _ is that you can write code such as "let (left,_) = stuff_pair in" or "match stuff_pair with (_,right) -> "
<AxleLonghorn> it's good to know
sporkmonger has joined #ocaml
<mrvn> The difference between 'ignore expr;' and 'let () = expr in' (or _) is that ignore does not cause in extra indentation in your editor.
<sanguinev> mrvn: In which editors?
<purple_> they should have called 'functional' languages 'data manipulation' languages. 'functional' sounds abstract and arcane and doesnt suggest usefulness. algebraic data types, trees, pattern matching, parametric polymorphism are just so incredibly good at manipulating data. OO as a paradigm tries to address the structuring code and doesnt actually help with the expressiveness and getting things done.
<flux> he means inside a sequence a of lets
<flux> sanguinev, atleast in (x)emacs
<purple_> sorry just rant in my head
<sanguinev> flux: Ok, doesn't seem to effect Notepad++ or vim (not sure if I have autoindenting on in vim though).
<mrvn> sanguinev: In any editor that handles indentation for you.
<mrvn> foo; \n let () = bar in \n baz; causes baz to be indented more than foo.
<mrvn> purple_: I think it is called functional because functions are allowed as first type arguments.
<mrvn> first class
<flux> well, you could reconfigure emacs (atleast in theory) to not to indent after 'ignore' ;). actually I wished there was a (preferably commonly used) language for expressing how a language is to be intended
<flux> this way language authors could provide that information directly to all editors supporting the scheme
<mrvn> purple_: I find OO gives me 2 nice things: namespaces and an hierachy.
<mrvn> flux: ingore foo; does not add indenting.
<mrvn> flux: Would be nice if there were such a meta description.
<sanguinev> mrvn: Doesn't add indentations in Notepad++ or vim...
<flux> let foo () = \n let a = 42 in \n ignore a; \n let b = 42 in \n ignore b does lead to a staircase effect in my emacs
<mrvn> sanguinev: does any let statement add indentation in your vim?
<flux> if I replaced ignores with let _ = .., it would not
<sanguinev> mrvn: Looks like not...
<mrvn> flux: yes. Special case. consequtive let statements are not staircased.
<mrvn> sanguinev: then you plain just have no auto indent.
<flux> mrvn, and wasn't that the whole point when you compared let to ignore..
<mrvn> flux: no. try it with foo; let () = bar in baz;
<purple_> mrvn: yes I realize this and its probably the defining feature - I guess I am just very frustrated professionally that a lot of the problems I encountered in my last job lend themselves so well to ML like features. visitor patterns on oo trees rather than adt are just a mess
<purple_> that kind of thing
<sanguinev> purple_: The naming of "functional" is AFAIK like flux commented, however "data manipulation" is already somewhat taken by things like SQL, XPath, XQuery, etc.
<mrvn> And I find data manipulation doesn't fit at all. Every language manipulates data anyway.
<mrvn> you have procedural, functional and relational languages.
<sanguinev> If you are interested in programming languages limitations and how to combine the best features of all you may find the following interesting: www-staff.it.uts.edu.au/~cbj/Publications/multi-polymorphism.pdf
<mrvn> relational probably doesn't fit data manipulation.
<mrvn> flux: I tend to used let () and ignore depending on which causes no indentation.
<AxleLonghorn> does anyone know where ignore is documented?
<mrvn> must be compiler buildin. I don't see a deklaration for it in the source.
<AxleLonghorn> man, inria needs to fix that kind of thing if they ever want this language to become popular
<AxleLonghorn> no byte code specification, undocumented compiler builtin
<mrvn> file:///usr/share/doc/ocaml/docs/ocaml.html/libref/Pervasives.html#VALignore
<mrvn> val ignore : 'a -> unit
<purple_> mrvn I take your point - I suppose I am a bit influenced by this article http://flint.cs.yale.edu/cs421/case-for-ml.html about ML (eg Meta Language) for compiler writing and think data structure manipulation.
<mrvn> Discard the value of its argument and return (). For instance, ignore(f x) discards the result of the side-effecting function f. It is equivalent to f x; (), except that the latter may generate a compiler warning; writing ignore(f x) instead avoids the warning.
<mrvn> AxleLonghorn: It is fully documented.
<purple_> sanguinev: article looks interesting, its getting added to my collection of open pdf documents about languages !
<sanguinev> purple_: Doing research into the area?
<AxleLonghorn> I see that now, and in pervasives no less.
<mrvn> Isn't the best argeument for ocaml that it can not accidentally segfault?
<mrvn> No memory leaks, no uninitialized pointers, no buffer over/underflows.
<sanguinev> mrvn: It's a great argument, the problem is that you need to find coders who see it as a good thing and also humble enough to admit they cause segfaults. ;)
<purple_> no unfortunately - i dont have the formal background, but am reading everything I can at the moment
<sanguinev> purple_: How much formal background do you think you need?
<purple_> well i find lots of interesting type theory stuff - but i struggle with it and havent managed to crack category theory although i can work with monads haskell style etc
* sanguinev sometimes wishes he could teach OCaml to students instead of Java.
<purple_> I guess i wish i can manage a transition from c/c++/c# programmer to academic where i could mess around all day writing compilers ;-)
<sanguinev> purple_: What is stopping you?
<purple_> well I did a law degree and only got a minor in comp-sci, so it would be a big commitment time/money and feel like am starting again. I am thinking about it seriously though
<sanguinev> purple_: I don't know where you are in the world, but around these parts you could go back and do honours and fast track yourself to PhD/academia that way.
<purple_> sanguinev thanks for that, I was wondering about fast track to honors (i have some things in my favour). I probably need to talk to uni admin and see if they might be flexible
<sanguinev> purple_: I strongly suggest talking to the relevent professor/supervisor and course/degree coordinator before you talk to administration section. Chances are administration will just tell you the official way, academics are likely to tell you what other options there are and also how to get around the administration red tape/requirements if they turn out to be a problem. ;)
<purple_> sanguinev this sounds like good advice - if there was one thing i learned at uni it was to always approach everybody until someone said 'yes' ;-)
<mrvn> purple_: the order matters too. Once someone said no they might not overlook it when someone else says yes.
<sanguinev> purple_: No problem, good luck with the process.
<purple_> mrvn, sanguinev - thanks, if i follow through i will approach faculty supervisor first
<sanguinev> purple_: Any time*, I recommend spending a little time to find out which school/faculty/lab is doing the stuff you want too, demonstrate your ability to research them prior to meeting and they will think more highly of you as a potential student. ;) */msg me any time, but I am idle the majority, so no promises about rapid response. ;)
xah_lee has joined #ocaml
<xah_lee> is there a function something like type_of?
<mrvn> what is that supposed to give you?
<purple_> sanguinev - a little bit of my hesitation is that i didnt see specialization by academics in PL theory and it was very java orientated at least at undergraduate level with the one obligatory 'programming paradigms' course. So I might need to poke other schools but am geographically isolated at the moment after working overseas. in any case thanks
<xah_lee> mrvn: i wanted it to print the type of a thing
<xah_lee> sorry prob stupid question.
<mrvn> xah_lee: so you would need val type_of : 'a -> string
<xah_lee> umm... i just started learning yesterday. Sorry i don't quite understand?
<mrvn> A function that takes any type and returns a string, specificaly a string representing that type. And no, doesn't exist.
<xah_lee> oh i see. thx
<mrvn> Proble is how to implement it for polymorphic functions: let foo x = print_string (type_of x); ...
<AxleLonghorn> xah_lee, where else on freenode have I seen you?
<xah_lee> what does the type_of there return?
<mrvn> There foo can take any tpye. How should the compiler know what (type_of x) should be there?
<mrvn> xah_lee: type_of is your hypothetical function that gives the string of a type.
<xah_lee> AxleLonghorn maybe on lisp or something.
<xah_lee> mrvn: kk. got it.
<AxleLonghorn> emacs?
<mrvn> xah_lee: Best you could get in that case is "'a" and then type_of is rather useless. So nobody has implemented one.
<xah_lee> what does 'a mean?
<mrvn> xah_lee: it is a placeholder.
<AxleLonghorn> it's the polymorphic type
<xah_lee> ah k.
<AxleLonghorn> 'b, 'c, etc
<AxleLonghorn> printing makes me wish OCaml had type classes
<mrvn> For network protocols I would like to have a "val type_of : 'a -> Hash.t" so one could add type safety.
<mrvn> I hate having to maintain a pair of id and version for each packet type.
<flux> you could use camlp4 for that, generating an id for each record
<flux> actually I think someone did just that
AxleLonghorn has left #ocaml []
sgnb` has quit [Read error: 104 (Connection reset by peer)]
sgnb`` has joined #ocaml
pango_ has quit [Remote closed the connection]
xah_lee_ has joined #ocaml
<mrvn> flux: yeah.
xah_lee has quit [Read error: 110 (Connection timed out)]
xah_lee_ has quit ["banned in #emacs by johnsu01 (john sullivan)"]
Camarade_Tux has joined #ocaml
cygnus__ has quit [Read error: 113 (No route to host)]
Snark has joined #ocaml
gaja has quit ["Lost terminal"]
ygrek has joined #ocaml
ygrek has quit [Remote closed the connection]
seafood has quit []
pierre- has joined #ocaml
sgnb``` has joined #ocaml
sgnb`` has quit [Read error: 104 (Connection reset by peer)]
vovkaii has joined #ocaml
sgnb``` is now known as sgnb
_zack has joined #ocaml
ygrek has joined #ocaml
marmotine has joined #ocaml
Camarade_Tux has quit ["ski"]
seafood has joined #ocaml
ched has joined #ocaml
fschwidom has joined #ocaml
ikaros has joined #ocaml
Yoric[DT] has joined #ocaml
<Yoric[DT]> hi
Stefan_vK has joined #ocaml
ikaros has quit [".quit"]
gim_ has joined #ocaml
sgnb has quit [Read error: 104 (Connection reset by peer)]
Stefan_vK1 has quit [Read error: 110 (Connection timed out)]
gim has quit [Read error: 110 (Connection timed out)]
pango has joined #ocaml
vixey has joined #ocaml
kig has joined #ocaml
ppsmimou has quit [Read error: 110 (Connection timed out)]
gim_ has quit [Read error: 110 (Connection timed out)]
|jedai| has joined #ocaml
gim has joined #ocaml
ppsmimou has joined #ocaml
purple_ has quit ["Leaving"]
_zack has quit ["Leaving."]
seafood has quit []
pierre_ has joined #ocaml
<pierre_> hi
pierre_ is now known as PierreN
sgnb has joined #ocaml
itewsh has joined #ocaml
sgnb has quit [Read error: 104 (Connection reset by peer)]
sgnb` has joined #ocaml
|jedai| has quit [Read error: 110 (Connection timed out)]
|jedai| has joined #ocaml
Snark has quit [Read error: 113 (No route to host)]
sgnb` has quit [Read error: 104 (Connection reset by peer)]
hkBst has joined #ocaml
ppsmimou has quit [Read error: 110 (Connection timed out)]
gim has quit [Read error: 110 (Connection timed out)]
ppsmimou has joined #ocaml
gim has joined #ocaml
jlouis has joined #ocaml
|jedai| has quit [Read error: 110 (Connection timed out)]
|jedai| has joined #ocaml
Associat0r has joined #ocaml
AxleLonghorn has joined #ocaml
jlouis has quit [Remote closed the connection]
|jedai| has quit [Read error: 110 (Connection timed out)]
|jedai| has joined #ocaml
patronus_ has joined #ocaml
<Yoric[DT]> Does anyone know of a locale system for OCaml?
patronus_ has quit [Connection reset by peer]
patronus_ has joined #ocaml
<mrvn> gettext?
patronus1 has joined #ocaml
<Yoric[DT]> Thanks.
AxleLonghorn has left #ocaml []
patronus_ has quit [Connection reset by peer]
pango has quit [Remote closed the connection]
patronus has quit [Read error: 111 (Connection refused)]
pango has joined #ocaml
|jedai| has quit [Connection timed out]
|jedai| has joined #ocaml
|jedai| has quit [Read error: 60 (Operation timed out)]
|jedai| has joined #ocaml
thelema has joined #ocaml
<thelema> hi
ygrek has quit ["Leaving"]
TaXules has quit [Read error: 60 (Operation timed out)]
TaXules has joined #ocaml
patronus1 is now known as patronus
patronus is now known as ghost
ghost is now known as Guest7120
Guest7120 is now known as patronus
|jedai| has quit [Read error: 110 (Connection timed out)]
|jedai| has joined #ocaml
patronus has quit ["leaving"]
<thelema> Yoric[DT]: could we have a debate on the merits of |> vs. <** ??
jlouis has joined #ocaml
patronus has joined #ocaml
<Yoric[DT]> thelema: sure
patronus has quit [Client Quit]
patronus has joined #ocaml
<thelema> |> visually looks right -- data |> function
<thelema> <** looks backwards
<thelema> data <** function
itewsh has quit ["There are only 10 kinds of people: those who understand binary and those who don't"]
<mrvn> What do they do and where do you use them?
<vixey> they are F#isms
<thelema> mrvn: let (|>) x f = f x
<thelema> same definition for <**
<Yoric[DT]> thelema: I concur that there's a problem.
<Yoric[DT]> Now, it's the only way I've found so far of getting the right associativity.
<thelema> of course, the right fix is to use camlp4 (I think it should be possible) to fix the associativity of <|
<thelema> well, don't break |> to fix <|
<hcarty> thelema: If/when pa-do is added, it allows changing the associativity of ( <| )
<thelema> hcarty: great.
<Yoric[DT]> thelema: I agree that the right fix is Camlp4.
<thelema> Yoric[DT]: objections to reverting <** and fixing with pa-do?
<Yoric[DT]> I also believe that we should add pa-do.
<Yoric[DT]> thelema: no objection at all.
<Yoric[DT]> I'd rather not do it myself, though.
<thelema> maybe pa-do after alpha-3
<thelema> understood. Thanks for putting in the time you did.
<thelema> my apologies for not even noticing what you did last sunday until today.
<Yoric[DT]> No problem, thanks for your own work.
<Yoric[DT]> I'll revert <** now.
<thelema> no rush.
pixel_ has quit [SendQ exceeded]
<Yoric[DT]> Well, I was editing the code anyway.
<thelema> oh, great.
<thelema> it seems like an interesting git exercise to revert just the right patches, and I think it'd be possible with the good checkins you've been making.
patronus has quit [Remote closed the connection]
bluestorm has joined #ocaml
<Yoric[DT]> thelema: arf, well, seems just as easy to revert it manually.
<thelema> hi bluestorm, we were just talking about p4
<bluestorm> hum
<thelema> yup, not too hard.
<thelema> bluestorm: have you worked with pa-do much?
<bluestorm> i've just sync'ed the tree, and fixed a build problem in extPervasives
<bluestorm> no i haven't
<bluestorm> ( (@/) and (/@) were swapped in the .ml file)
vixey has quit [No route to host]
<Yoric[DT]> bluestorm: my bad.
patronus has joined #ocaml
<thelema> bluestorm: that's odd, my checkout from an hour or so ago compiles...
<thelema> wait, n/m, I didn't switch branches
<thelema> grr, must merge 3.11 branch each time
<thelema> stupid change to Gc.control
<thelema> bluestorm: I don't see your fix on ocamlcore
fschwidom has quit [Remote closed the connection]
<Yoric[DT]> By the way, for information, I'm working on Unicode transcoding.
<Yoric[DT]> thelema: what happened with Gc.control?
<thelema> they added a field. look at the diff between the ocaml311 branch and master
vixey has joined #ocaml
* Yoric[DT] doesn't see anything.
<Yoric[DT]> In ExtGc?
<Yoric[DT]> Ah, you mean a change in OCaml 3.11, is that it?
<thelema> yes
<thelema> in OCaml 3.11, they added a field [mutable allocation_policy: int;] to Gc.control
<Yoric[DT]> ok
<thelema> if you do [git diff ocamlcore/ocaml311 ocamlcore/master] (on current ocamlcore), you'll see the simple fix
<Yoric[DT]> I'll take a look when I'm finished with this encoding stuff.
<mrvn> I consider changing the associativity of an operator a verry bad idea. It will just confuse people.
<thelema> mrvn: do you know (without consulting the big table) whether operators beginning with % are left or right associative?
<bluestorm> left
<bluestorm> and i agree with mrvn on that point
<bluestorm> i think changing the standard operator associativity or precedence is a bad idea
<mrvn> thelema: Say I do consult the big table and then you changed it. What then?
<thelema> raise your hand if you've memorized the associativity table of operators?
<bluestorm> well, only @ and ^ are right-associative iirc.
<bluestorm> not very difficult to memorize
<mrvn> Would it even matter for those two?
<thelema> mrvn: most ocaml users don't even know that table exists. And there'll be big warning notes in the docs for this function that it doens't follow the normal rules (so that it functions as expected)
* thelema was thinking of the table infix vs. prefix vs. operator chars
<thelema> infix vs. prefix
<bluestorm> i think people reading the code should not have to refer to the doc to parse it correctly
<mrvn> thelema: Pick a new operator. Don't change an old operator some of the time.
<bluestorm> there *is* an ocaml standard in that matter and we should stick to it
<thelema> **... is right associative
<thelema> (even though * is left)
<bluestorm> ah, yes
<bluestorm> hence the **>
<bluestorm> **> is a good choice as ** has a quite high precedence
<bluestorm> btw.
<bluestorm> regarding @/ and /@ operators (i didn't know where there come from, the answer is http://forge.ocamlcore.org/tracker/index.php?func=detail&aid=129&group_id=17&atid=342 )
<bluestorm> would it be possible not to put them in the default namespace but in an Infix submodule (eg Enum.Infix) ?
<bluestorm> hm
<thelema> I dunno, camlp4 usually doesn't do things like that (working or not working based on declarations at the top of the file)
<bluestorm> hm, how is it camlp4-related ?
<thelema> oh, you're not talking about the right-associativity of <|
<thelema> sorry. yes, we can make a module Enum.Infix. I think that it'd be good to be able to do [open Enum with Infix]
<bluestorm> hm
<bluestorm> thelema: with the current pa_openin, open Enum, Infix would do the job
<thelema> yes, but that doesn't indicate that Infix comes from Enum - it could be some other module's Infix
<bluestorm> yes
<bluestorm> open Enum, Enum.Infix ?
<bluestorm> you probably want open Enum.Infix without opening Enum itself, actually
<thelema> s/want/won't/ ?
<bluestorm> i suppose "want"
<bluestorm> open Enum.Infix is essential to use the infix names, but open Enum clutter the namespace quite a bit
<thelema> you're right.
* thelema makes Enum.Infix
<bluestorm> (i try to avoid opening big modules; module E = Enum is nearly as short to use and better practice imho)
|jedai| has quit [Read error: 110 (Connection timed out)]
<thelema> Yoric[DT]: any objections to Enum.Infix?
|jedai| has joined #ocaml
<bluestorm> thelema: i like the general Module.Infix idea; an other decision could be to have a global Infix module (in extPervasives maybe) with infix names used through the whole Batteries
<bluestorm> a bit more clumsy but possibly less cumbersome to the user
<bluestorm> i prefer the specific Infix modules though
<thelema> We could easily include all specific infixes into a global infix
<thelema> assuming no clashes
<bluestorm> (there better be no clashes :D)
<thelema> it's just --, ---, ~~, and //, right?
<bluestorm> and @/ and /@ so far
<thelema> in Enum?
<bluestorm> it's in extPervasives right now
<bluestorm> more might come later, but i'm generally very suspicious of new infix operators
<bluestorm> ah
<thelema> why?
<thelema> I agree with perl's idea of hamming-coding common syntax (so it's short and easy to use)
<bluestorm> because people often find it handy to define infix operators themselves for domain-specific operations, and it can be frustrating for them than most easy/short choices are "already taken"
<bluestorm> eg. i often do not dare to rebind (@) while it would be a good choice
<bluestorm> of course, if we have them in non-opened-by-default Infix modules, the situation is much better
<bluestorm> (a specific trick i've discovered recently is let rec recursive_function arg1 arg2 = let (!) = recursive_function arg1 arg2 in function .... )
* thelema has never bound (!)
<bluestorm> well it can be quite nice
<thelema> It'd probably be good to survey -devl on this, at worst we're spreading a good practice to those (including me) for which it's new.
PierreN has quit ["Changing server"]
tar_ has quit []
<mrvn> bluestorm: what exactly is the trick there?
|jedai| has quit [Read error: 110 (Connection timed out)]
|jedai| has joined #ocaml
<mrvn> bluestorm: All I see there is an endless recursion causing a stack overflow.
<bluestorm> mrvn: in function ...
<bluestorm> that's a readability trick
<bluestorm> mrvn: http://pastebin.be/16275
<bluestorm> (the code actually does not compile and is probably wrong)
<bluestorm> the idea is to use (!) for "recurse the usual way" and it's actually much more readable and less error-prone
<mrvn> You are overloading an operator with a totaly new meaning. bad idea.
<bluestorm> locally
<bluestorm> i could use (!!), but who use references anyway ?
Associat0r has quit [Connection timed out]
* mrvn
<mrvn> bluestorm: I find that code a bit unreadable with the delayed function.
<mrvn> maybe let rec (!) = safe_expr env and safe_expr env = function ...?
<bluestorm> well that's probably not perfect, and a personal idiom (i'm not advocating this style taking over the world), but i'm generally happy when i use it :]
<flux> delayed function? you mean the keyword 'function'?
<bluestorm> mrvn: the problem is you need to capture the "env" parameter for it to be useful
<mrvn> flux: having another let between the let declaring the name and the function you bind
<mrvn> bluestorm: right.
<bluestorm> let rec safe_expr env expr = let (!) = ... in match expr with ... is a possible solution
<flux> I've done it a few times. function kwd in itself is useful at times, and so is let bindings with that scope.
<mrvn> let rec safe_expr env expr = let (!) ... in match expr with
<bluestorm> :]
<mrvn> Still odd in my eyes.
<mrvn> flux: I usualy only have let foo = function .... Nothing inbetween the let and the function.
<flux> yes, usually that is the case
<bluestorm> one (short) line is acceptable though
<mrvn> The problem with the paste I see is that it is not clear that safe_expr takes 2 arguments. That is a bit hidden.
<bluestorm> agreed.
<mrvn> Somehow I always find it easier not to use function values but to spell out all the arguments even if that means writing let foo x y = bar x y kind of repeats.
<mrvn> But that might just be me.
pango has quit [Remote closed the connection]
<bluestorm> iirc that taste is recorded somewhere in the guidelines
<bluestorm> so it must not be only you
<mrvn> I think that is partly a problem of not having a good ide. One should just be able to hover over values with the mouse and get a bubble help with the type.
<bluestorm> well post-3.10 versions provide that ability
<bluestorm> it's in the emacs caml-mode iirc
<bluestorm> (you have to compile the file for annotation to work though)
<flux> post 3.10? the capability to retrieve type information in emacs has been there a long time
<bluestorm> you probably know about the ocaml-wizard and ocaml-spotter projects
<bluestorm> flux: weren't the .annot files new in 3.10 ?
<mrvn> I've been totally ignorant on ocaml news these last years
<flux> bluestorm, no
<bluestorm> my mistake then :p
<mrvn> does that work if the compile fails?
<flux> it works up to the point where typing fails
gim has quit [Read error: 60 (Operation timed out)]
<bluestorm> mrvn: http://ocamlwizard.lri.fr/ , it's quite young though
<flux> usually that's good enough
<mrvn> n8
|jedai| has quit [Connection timed out]
<flux> hmm, I need to try out that ocamlwizard
<flux> it looks like it has advanced since the last time I took a look at it
|jedai| has joined #ocaml
<flux> I'm especially interested in the refactoring part, and also if new refactorings can be incorporated with relative ease
<flux> and emacs integration is another important thing for me
<flux> apparently doesn't compile with my ocamlgraph, pft
gim has joined #ocaml
<flux> nope, not even with ocamlgraph 1.0, it says: File "/opt/stow/godi/lib/ocaml/std-lib/ocamlgraph/path.mli", line 26, characters 13-27: Error: Unbound module type Sig.COMPARABLE
<flux> I don't know why it is ocamlwizard's business going around and compiling .mli-files in std lib locations, though..
pango has joined #ocaml
|jedai| has quit [Connection timed out]
|jedai| has joined #ocaml
<bluestorm> well ocamlwizard is probably a bit young
<bluestorm> and possibly suffering from the post-summer project death malediction
<flux> quite possibly, but I consired it an impediment if I can't, with average effort, even compile it :). but it could well be an issue with my environment, maybe it would work with debian's ocaml (not godi w/ 3.11)
<bluestorm> Yoric[DT]: i've just built the new documentation and must say i'm quite impressed
<flux> is it browsable somewhere online?
pierre- has quit [Read error: 110 (Connection timed out)]
ikaros has joined #ocaml
jlouis has quit [Remote closed the connection]
seafood has joined #ocaml
<Yoric[DT]> bluestorm: thanks
ppsmimou has quit [Read error: 110 (Connection timed out)]
pierre- has joined #ocaml
ppsmimou has joined #ocaml
gim has quit [Read error: 110 (Connection timed out)]
seafood has quit []
ppsmimou has quit [Read error: 110 (Connection timed out)]
|jedai| has quit [Read error: 60 (Operation timed out)]
|jedai| has joined #ocaml
<hcarty> thelema: What build command(s) do you use to build the Batteries ocaml311 branch?
<hcarty> And does it build for you on a clean checkout?
Associat0r has joined #ocaml
psnively has joined #ocaml
<bluestorm> Yoric[DT]: is the batteries myocamlbuild.ml centralized ?
<bluestorm> i have to change it to add a new syntax extension, i edited tests/myocamlbuild.ml and it works fine, i suppose i should mirror the changes to the other ones ?
psnively has quit []
<Yoric[DT]> tests/myocamlbuild.ml is not the same as the myocamlbuild.ml used to build Batteries itself.
ikaros has quit [Remote closed the connection]
<bluestorm> Yoric[DT]: so i should also update ./myocamlbuild.ml and doc/../myocamlbuild.ml (the user one) ?
<Yoric[DT]> Well, if your change is something you need to build Batteries, you should update ./myocamlbuild.ml .
<bluestorm> ah, understood, i probably don't need that then
<Yoric[DT]> If it's something you need to build code which uses Batteries, you should update doc/../myocamlbuild.ml (on my file system, it's a link to tests/myocamlbuild.ml but I don't know if that gets through git).
<bluestorm> ok
<bluestorm> (on mine it's not)
<Yoric[DT]> ok
ppsmimou has joined #ocaml
gim has joined #ocaml
<bluestorm> Yoric[DT]: is the html doc for extensions handwritten, or generated from a texte file somewhere ?
slash_ has joined #ocaml
<bluestorm> Yoric[DT]: pa_comprehension pushed
<bluestorm> (quite tight on the "before sunday" bound)
seafood has joined #ocaml
<bluestorm> (first git commit ever)
vixey` has joined #ocaml
marmotine has quit ["mv marmotine Laurie"]
vixey` has quit [Client Quit]
|jedai| has quit [Operation timed out]
|jedai| has joined #ocaml
gim has quit [Read error: 110 (Connection timed out)]
ppsmimou has quit [Read error: 110 (Connection timed out)]
<Yoric[DT]> bluestorm: handwritten.
<Yoric[DT]> bluestorm: and congratulations :)
jonasb has joined #ocaml
pierre- has quit [Read error: 60 (Operation timed out)]
<Yoric[DT]> Well, time to call it a night.
<Yoric[DT]> Cheers.
Yoric[DT] has quit ["Ex-Chat"]
|jedai| has quit [Read error: 110 (Connection timed out)]
|jedai| has joined #ocaml
Palace_Chan has joined #ocaml
itewsh has joined #ocaml
Amorphous has quit [Success]
itewsh has quit ["Quitte"]
bluestorm has quit [Remote closed the connection]
Amorphous has joined #ocaml
vixey has quit ["There exists an infinite set!"]