mbishop changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | Grab Ocaml 3.10.0 from http://caml.inria.fr/ocaml/release.html (featuring new camlp4 and more!)
tree has quit [Read error: 104 (Connection reset by peer)]
tree has joined #ocaml
pants1 has joined #ocaml
noteventime has quit ["Leaving"]
Mr_Awesome has quit ["...and the Awesome level drops"]
yminsky has joined #ocaml
yminsky has quit []
Mr_Awesome has joined #ocaml
Mr_Awesome has quit ["...and the Awesome level drops"]
Mr_Awesome has joined #ocaml
seafoodX has joined #ocaml
chs_ has joined #ocaml
Mr_Awesome has quit ["...and the Awesome level drops"]
chs_ has quit []
pants1 has quit [Read error: 110 (Connection timed out)]
david_koontz has quit ["Leaving"]
visage has quit []
chs_ has joined #ocaml
visage has joined #ocaml
visage has quit [Remote closed the connection]
chs_ has quit [Read error: 110 (Connection timed out)]
chs_ has joined #ocaml
pants1 has joined #ocaml
bluestorm_ has joined #ocaml
ayrnieu has quit [Remote closed the connection]
bluestorm_ has quit [Remote closed the connection]
ygrek has joined #ocaml
ygrek has quit [Remote closed the connection]
ygrek has joined #ocaml
ygrek has quit [Client Quit]
love-pingoo has joined #ocaml
ygrek has joined #ocaml
__mattam__ is now known as mattam
Submarine has quit [Remote closed the connection]
vital304 has quit ["Leaving."]
love-pingoo has quit ["Connection reset by pear"]
ygrek has quit [Remote closed the connection]
ygrek has joined #ocaml
screwt8 has quit [Remote closed the connection]
m3ga has joined #ocaml
screwt8 has joined #ocaml
joshcryer has quit [Client Quit]
m3ga has quit ["disappearing into the sunset"]
mikeX has joined #ocaml
screwt8 has quit [Remote closed the connection]
chs_ has quit []
screwt8 has joined #ocaml
joshcryer has joined #ocaml
mikeX has quit ["leaving"]
noteventime has joined #ocaml
danly_ has quit [Remote closed the connection]
visage has joined #ocaml
ygrek has quit [Remote closed the connection]
seafoodX has quit []
noteventime has quit [Remote closed the connection]
noteventime has joined #ocaml
eumenides has joined #ocaml
descender has quit ["Elegance has the disadvantage that hard work is needed to achieve it and a good education to appreciate it. - E. W. Dijkstra"]
_blackdog has joined #ocaml
kelaouchi has joined #ocaml
eumenides has quit [Read error: 113 (No route to host)]
EliasAmaral has quit [Read error: 54 (Connection reset by peer)]
love-pingoo has joined #ocaml
LeCamarade has joined #ocaml
vincenz has joined #ocaml
<visage> Pardon my ignorance, but I am coming from the land of SML and have a question: can you pattern match on objects?
<visage> or only datatypes?
<vincenz> only datatype
<vincenz> and polymorphic variants
<LeCamarade> visage: Try it like this:
<vincenz> iirc
<visage> Herm. I wish there were a language that was the demon spawn of the bastardized marriage of ocaml and ruby.
<visage> I would be a happy camper.
<visage> Maybe throw in erlang's built in distribution capabilities.
<LeCamarade> visage: Okay. Look.
<LeCamarade> let fn = function 0 -> "zero" | x -> "not zero";;
<LeCamarade> That is a pattern match.
* LeCamarade was supposed to build statement evaluator for this channel. It is somewhere on my box ...
<visage> Right. I know what a pattern match is.
<rwmjones> visage, I'm pretty sure you can't match on objects ... out of interest though, what do you need to use objects for?
<LeCamarade> visage: And that is how to do it.
<rwmjones> IME, using objects is mostly a mistake
<vincenz> visage: you can patternmatch in the sense of patternmatching against a datatype with 1 element
<vincenz> visage: aka, with a variable
<visage> rwmjones, I prefer the idea of having an object perform an action, rather than having an action performed on an object.
<visage> So instead of having modules of functions, I prefer to have methods with objects
<vincenz> visage: but for the rest, I am not sure I see how you would like to patternmatch objects. The whole idea of dispatching with objects i methods
<vincenz> s/\<i\>/is
<visage> so I was hoping there was a way to define an Object as a datatype with different methods associated with it.
<rwmjones> but the point of ML is to manipulate data structures ... so start by defining the data, and operating on it.
<rwmjones> the compiler helps you out a lot because if you change the data structure, it'll tell you all the parts of code which need to be updated
<LeCamarade> rwmjones: Is it you? The COCAN guy?
<visage> So like "class Tree: 'a as Leaf of 'a | Node of Tree*'a*Tree"
<rwmjones> the guy who set up cocan.org yet
<rwmjones> yes
<LeCamarade> :o)
<visage> That would be my ideal right there.
cjeris has joined #ocaml
<visage> I guess things get sticky with inhertiance ...
<visage> *inheritance and polymorphism...
<flux> I've found objects convenient at times
<flux> ..at the times when one wants polymorphism and inheritance..
<flux> but imo one rarely does in ML. definitely not quite as often as one'd use them in c++ or java.
* vincenz agrees with flux
<visage> certainly. I just like the higher order messaging paradigm, which is fairly OO
<vincenz> visage: you dont need oop for tha (the tree example)
<vincenz> a simple ADT will do
<visage> vincenz: true, but it was a simple example.
_blackdog has quit [Read error: 54 (Connection reset by peer)]
Submarine has joined #ocaml
pango_ has quit [Remote closed the connection]
pango_ has joined #ocaml
love-pingoo has quit ["Leaving"]
apfelmus has joined #ocaml
<apfelmus> Hello, I've got a question about eager evaluation.
<apfelmus> To what extend are arguments of function type evaluated?
<apfelmus> Normal form? Head normal form? Not at all?
<apfelmus> I mean, given a higher order function like map that takes a function f to map over a list of values, to what extend will f be evaluated?
<apfelmus> before being applied to the list elements themselves that is
visage has quit [Read error: 110 (Connection timed out)]
<haelix> apfelmus: let inc x = x+1;;
<haelix> List.map inc [1;3;5];;
<haelix> inc can't be evaluated, right ?
<haelix> it is evaluated once for each of the list element
<haelix> or
<haelix> rather
<apfelmus> Well, in this case not.
<haelix> the result of the application of each eleemnt is evaluated
<LeCamarade> I certainly should get back to building that statement evaluator for this channel.
<haelix> :)
<LeCamarade> Maybe it should be tonight's hacking.
<haelix> LeCamarade: where are you with it ?
<apfelmus> but consider let inc2 x = (1+1)+x
<haelix> ok
<haelix> it seems to me you're more into compiler optimisation
<apfelmus> no
<apfelmus> i mean, in lambda calculus, every expression has a normal form
<apfelmus> so does inc2
<LeCamarade> haelix: Well, it is a bot, actually. It has an evaluator module, which is a bit buggy. Many modules there were a bit buggy (result of coding past midnight), so I put it all aside.
<LeCamarade> I can just take the bot code and make an evaluator, and we can be running.
<apfelmus> inc2 = \x.(1+1)+x
<apfelmus> (\ = \lambda)
<apfelmus> this expression has a redex, namely (1+1)
<haelix> a what ??
<vincenz> apfelmus: it depends, typically outside ini
<apfelmus> redex = reducible expression
<vincenz> apfelmus: left hand topmost
<vincenz> apfelmus: but for LC, the nice property is that no matter how you reduce it, the answer will be the same
<vincenz> (cause you have no side-effects)
<apfelmus> haelix: something that you can replace with its definition
<haelix> apfelmus: you must be right, _but_
<haelix> it seems to me that, in term of obersvable behavior
<haelix> (and yes, I know, SML is defined, and not Ocaml... ;)
<haelix> it won't make a difference for your program
<vincenz> haelix: indeed
<haelix> except maybe on execution time
<vincenz> which is not a propert of LC
<vincenz> though
<apfelmus> yeah, the execution time is what I'm interested in :)
<vincenz> apfelmus: (1+1)+x
<vincenz> doesn't exist
<apfelmus> \x. (very expensive) + x
Demitar has quit [Read error: 60 (Operation timed out)]
<vincenz> apfelmus: execution time is not modeled by LC, so you get to choose how you want it
<vincenz> apfelmus: either do outermost first, or not
<apfelmus> vincenz: well, number of reductions
<haelix> apfelmus: so you're bothering yourself with compielr internals
<vincenz> apfelmus: it'll prolly depend
<haelix> I was right
* haelix won !!!
* vincenz gives haelix a lambda-cookie
<haelix> apfelmus: basically,
<haelix> if you're concerned about execution time
<haelix> the line of the party is to use SML
<haelix> and compile with MLTon
<apfelmus> haelix: hehe, that's not how I mean it :)
<haelix> although some will say that Ocamlopt performance is already plenty good
<apfelmus> i'm interested in "theoretical execution time" :)
<vincenz> apfelmus: o.O
<vincenz> apfelmus: that doesn't exist
<vincenz> apfelmus: unless you mean O-notation
<vincenz> and in that case
<vincenz> it's the same
<vincenz> even if you call expensive often or not
<vincenz> the O-notation is N
<vincenz> for that map
<haelix> vincenz: it truly doesn't exist ?
<vincenz> oh
<vincenz> well that's a broad claim
<vincenz> but
<vincenz> I can't come up with anything off the top of my head
<haelix> say, the minimal step of computation performed by a brainfuck interpreter souds like a good enough measure to me
<haelix> of course... there's not implicit parallelization and pipeline prefetching, but...
<apfelmus> vincenz: well, I think the O-notation claim is wrong
<vincenz> the issue is this
<apfelmus> I mean, not in this case
<vincenz> apfelmus: yes it is the same
<vincenz> loko
<vincenz> simple example
<apfelmus> but consider foo xs = let f = \y -> expensive xs + y in map f xs
<vincenz> map (\x -> expensive + x) list
<vincenz> ok
<apfelmus> here, expensive depends on xs
<apfelmus> and we can make this as O-bad as we want :)
<vincenz> apfelmus: right
<vincenz> apfelmus: but
<vincenz> apfelmus: expensive also depends on something else
<vincenz> which you're too easily brushing over
<apfelmus> namely?
<vincenz> well it's surrounding expression really
<vincenz> namely
<vincenz> you have a function depending on y and xs
<vincenz> that always dpeends the same way on those xs
<vincenz> which is not always a given
<vincenz> what if it was
<vincenz> \y -> lookup y xs
<vincenz> so
<vincenz> it's O(n^2)
<vincenz> we're just lucky
<vincenz> in this case
<vincenz> the top function is a +
<vincenz> and we can memoize
<vincenz> but that's not always the cae
<vincenz> so you're using function-specific knowledge
<vincenz> that's far outside of LC imho
<apfelmus> yes, we sure can memoize z = expensive xs and lift it out of the y
<vincenz> it relies on commutativity associativity, etc,etc
<vincenz> apfelmus: you're missing my point
<vincenz> apfelmus: the reason you can do that
<vincenz> is cause + behaves so nicely
<vincenz> what if it was
<vincenz> \y -> lookup y (epensive xs)
<vincenz> instead of
<vincenz> + y (expensive xs)
<vincenz> now it's O(n^2) again
<vincenz> you're using information of the '+' function
<vincenz> which is very case-by case
<apfelmus> eh?
<vincenz> the function you're applying to xs
<vincenz> is not expensive
<apfelmus> lookup y (expensive xs) is no different
<vincenz> it's
<apfelmus> i mean, you can memoize expensive xs
<vincenz> apfelmus: yes
<vincenz> apfelmus: but you might still always get O(n^2)
<apfelmus> and it's a redex in \y.lookup y (expensive xs)
<vincenz> apfelmus: the complexity does not change
<vincenz> you rely on knowledge regarding the toplevel
<vincenz> if epneisve xs
<vincenz> returns a list
<vincenz> \y -> lookup y (enxpensive xs)
<vincenz> has complexity N
<vincenz> even if you memoize expensive
<vincenz> you're not relying on info regarding expensive
<vincenz> you're relying on info regarding behaviour of '+'
<vincenz> so no matter how expensive
<vincenz> your complexity in this case is
<vincenz> O(n^2)
<vincenz> replace cheap by expensive
<vincenz> complexity remains the same
<vincenz> that's my point
<apfelmus> yes. but in the + case, it's the difference between O(n) and O(n^2) (say)
<vincenz> (as long as type signature doesn't change)
<vincenz> apfelmus: right, so you want a general logic
<vincenz> which based itself on the information of specific functions
<vincenz> (+ vs lookup)
<apfelmus> no, that's not what i want ...
<vincenz> hardly seems like something generalizayble
<vincenz> maybe in typed LC
<vincenz> bt definitly not in plain LC
<apfelmus> my point is that (expensive xs) is a redex
<vincenz> apfelmus: running sub-redexes can cause hanging of something that might not hang
<vincenz> \x -> if x then
<vincenz> \x -> if x then _|_ else 1
<vincenz> for x = false
<vincenz> it's a tricky art of optimiations
<vincenz> requiring heuristics
<vincenz> there's no given formal rule
<apfelmus> well, this example has no redex inside
<vincenz> yes it does
<vincenz> _|_ stands for some redex that does not terminate
<apfelmus> ah, ok
<vincenz> sorry
<vincenz> bit tired
<apfelmus> nevermind :)
<vincenz> so I apparently contradicted myself
<vincenz> I earlier said order of evaluation does not matter
<vincenz> apparently it does :)
<apfelmus> actually, i'd like to know the exact definition of "eager evaluation"
<vincenz> outermost leftfirst
<vincenz> and eager = evaluate arguments before entering function
<vincenz> again
<apfelmus> eh? I thought innermost?
<vincenz> outermost leftfirst
<vincenz> no
<apfelmus> outermost leftfirst was normal order reduction?
<vincenz> then you can hang
<haelix> vincenz: I think innermost :)
<vincenz> haelix: eh?
<vincenz> but then you hang on _|_ in that if
<apfelmus> innermost leftfirst was applicative order reduction?
eumenides has joined #ocaml
<vincenz> oh
<vincenz> right
<vincenz> innermost
<vincenz> left first
<apfelmus> vincenz: yeah, eager evaluation can hang :)
<vincenz> as long as it's outside any \
<vincenz> apfelmus: but not that case
<vincenz> (\x -> if x then _|_ else 1) should not hang on input false
<vincenz> even in eager
<apfelmus> that's a speciality of the if-statement
<vincenz> not particularly
<vincenz> or wait
<vincenz> yes, sorry :)
<vincenz> and in pure LC
<vincenz> ...
<haelix> vincenz: yes it is :)
<vincenz> an if is a function so you'd evaluate |_
<vincenz> yep ;)
<vincenz> sowwy
<apfelmus> hm, indeed
<haelix> that makes it impossibl eto implement "if" as a function in a non-lazy language
<haelix> well
<vincenz> indee
<vincenz> d
<haelix> possible, but not useful :)
<vincenz> that's the reason you need macros in eager languages :D
<apfelmus> :)
<vincenz> why are wea talkking here
<vincenz> and not in haskell
<vincenz> or oasis
<haelix> subtle one :)
<haelix> what's oasis ?
<haelix> (no I won't google for that word)
<apfelmus> i'm not eager about it, but I wanted to talk in ocaml ;)
<vincenz> the Pl-agnostic PL-discussion channel here on IRC
<vincenz> #oassi
<vincenz> #oasis even
<vincenz> name is purely historical
<vincenz> apfelmus: you're talking in english
<haelix> oh
<haelix> did'nt know this one
<apfelmus> vincenz: ok, you got me :)
<vincenz> often quite silent
<haelix> better talk in XML,
<vincenz> but lots of interelligent people in it
<haelix> as it's so easyy to parse !
<vincenz> and somtimes we get interesting discussions
<vincenz> haelix: yes, especially for human EYS
* vincenz feels the cuts from those sharp < ARRRGH
<haelix> yes
<vincenz> I wonder why they felt the need to reinvent lisp
<apfelmus> actually, i'm still unsure about evaluation of function arguments
<haelix> somebody's just come along and throw a random topic in the air
<apfelmus> so, ML does, unlike LC, leave every function argument as it is?
<apfelmus> no redex evaluation under lambdas?
kelaouchi has quit ["leaving"]
<apfelmus> *redex reduction
<haelix> there are no lambda forms in ML
<haelix> (best that I know)
<vincenz> function's
<haelix> however, familiarity with LC sure helps
<vincenz> (function x -> x + 2) == lambda
<mbishop> function and fun, in ocaml, and fn in SML
<haelix> I know that
<vincenz> what bugs me about ML (or at least ocaml) is that dataconst are not firstclass
<vincenz> that so pisses me off at times
<haelix> but there's no lambda form transformation
<haelix> not specified
<haelix> and especially not in term of "optimized form" :)
<haelix> apfelmus: once again, in term of observable behavior,
<haelix> the arguments are left unmodified
<haelix> (unless they held mutable stuff)
<apfelmus> hm. actually, I'm looking for a theorem that says: lazy evaluation takes less reduction steps than any other reduction sequence that does not reduce under lambdas
<apfelmus> that's what everybody implicitly assumes
<apfelmus> but i've so far been unable to locate a formal proof
<apfelmus> i think that a theorem "lazy takes less reductions than eager" exists and i know wonder whether eager reduces under lambdas
* haelix watch the birds fly
<apfelmus> *now
<haelix> grabbing the pieces
<haelix> I don't think eager evaluation reduces undes lambdas
<vincenz> map (function x -> DataConst x) [1;2;3;4;5]
<vincenz> ARGH!
<haelix> (natural language: it evaluate arguments firts)
<haelix> vincenz: try SML :)
<apfelmus> yes, it seems that eager eval doesn't reduce under lambdas
<apfelmus> but applicative order does ...
<apfelmus> from which eager is derived
<haelix> vincenz: anyway, you need to make a wrapping function, so it is not an horrible death
<vincenz> haelix: I never got that limitation, seems like a pretty small syntactical thing
<vincenz> haelix: I prefer haskell then :)
<vincenz> map Just [1..10]
<haelix> apfelmus: that last one totally lost me :)
<apfelmus> haelix: i mean, eager evaluation is (said to be) (like) applicative order reduction
<haelix> ok
LeCamarade has quit ["ExitStatus 27"]
<apfelmus> appllicative order = innermost leftmost
<haelix> argl
<haelix> I now understand
<haelix> and eager evaluation would then be
<haelix> innermost, left most
<haelix> but not too innermost
<haelix> (please stop at lambda boundaries)
<haelix> am I wrong ?
<apfelmus> yes, that's what I mean
<haelix> (sorry, newcomer on these grounds - I hardly resist the temptation to say "applicative order: inline everything first, then think" :)
<apfelmus> :)
<haelix> well
<haelix> another question
<haelix> what's the LC version of if ?
<haelix> eta ?
<haelix> zeta ?
<haelix> nu reduction ?
<vincenz> alpha
<haelix> crums !
<vincenz> you mean shortcutting if?
<haelix> yes
<vincenz> don't think that'll ever happen
<apfelmus> well, in LC, true and false are there own if-expressions
<vincenz> riht
<haelix> hmm
<apfelmus> *their
<vincenz> but they evaluate arguments, being functions and all that
<haelix> that's lambda x y -> x
<vincenz> there's only functions
<haelix> actually
<apfelmus> True := \xy.x; False = \xy.y
<vincenz> haelix: yeah, but...you're evaluating y
<vincenz> one option would be
<vincenz> to wrap both arguments in function
<vincenz> that toss their argument
<haelix> I'd say it depends on evaluation order :)
<apfelmus> If x Then a Else b := x a b
<vincenz> if a b c = a[b][c][dummy]
<vincenz> where both b and c take a dummy argument
LeCamarade has joined #ocaml
bluestorm_ has joined #ocaml
<apfelmus> well, the dummy argument only prevents _|_ if you don't evaluate under lambdas :)
<haelix> bluestorm_: you obviously mean a blue tidal wave, instead :)
<bluestorm_> ( ? )
apfelmus has quit []
<haelix> proxad.net => France => last elections results
<bluestorm_> :p
ygrek has joined #ocaml
<haelix> vincenz: did that kill the discussion ?
kelaouchi has joined #ocaml
_blackdog has joined #ocaml
benny has joined #ocaml
<vincenz> haelix: hmm
<vincenz> apparently
<haelix> too bad
<haelix> I'll have to leave, too, though
<haelix> bye
smimou has joined #ocaml
benny_ has quit [Read error: 110 (Connection timed out)]
xleroy has joined #ocaml
xleroy has quit [Remote closed the connection]
jlouis_ has joined #ocaml
jlouis_ has quit [Client Quit]
jlouis_ has joined #ocaml
jlouis has quit [Read error: 110 (Connection timed out)]
chs_ has joined #ocaml
danly has joined #ocaml
danly has quit [Client Quit]
Mr_Awesome has joined #ocaml
danly has joined #ocaml
<kelaouchi> hello #ocaml
<rwmjones> hello
<kelaouchi> where can i get a PDF version of http://www.pps.jussieu.fr/Livres/ora/DA-OCAML/index.html ?
<rwmjones> that's the French O'Reilly book?
<rwmjones> http://caml.inria.fr/pub/docs/oreilly-book/ might be the place
<kelaouchi> i meant a french PDF version...
xleroy has joined #ocaml
<LeCamarade> testing ...
xleroy has quit [Remote closed the connection]
<mbishop> kelaouchi: what operating system?
eumenides has quit [Read error: 110 (Connection timed out)]
<mbishop> debian/ubuntu has it (not sure if it's a pdf), but you can do "apt-get install ocaml-book-fr"
<kelaouchi> mbishop NetBSD :/
<lamby> I apologise, that's not a PDF.
<LeCamarade> kelaouchi: You want the OCaml manual in PDF?
<mbishop> Yeah, there's only an html version of the french version, apparently
<LeCamarade> Oh, French.
<LeCamarade> Sorry.
<kelaouchi> this one : http://www.pps.jussieu.fr/Livres/ora/DA-OCAML/index.html but in PDF format
<mbishop> All I can say is I've got the pdf of the english version, and it says it was made with 'dvipdfm'
xleroy has joined #ocaml
xleroy has quit [Remote closed the connection]
<kelaouchi> mbishop dvipdfm - Produce PDF files directly from DVI files
pango_ has quit [Excess Flood]
<kelaouchi> but the only PDF version it contains is in english :/
<kelaouchi> french only concerns HTML files
<LeCamarade> kelaouchi: I think because HeVeA translates to HTML as policy (it seems).
<kelaouchi> to HTML yes
<kelaouchi> from .tex
<LeCamarade> I mean, the guys who did the translation ...
<kelaouchi> but i need to translate to PDF from HTML
<LeCamarade> kelaouchi: Hmm.
xleroy has joined #ocaml
<LeCamarade> You know of a program to do that?
xleroy has quit [Remote closed the connection]
<kelaouchi> no i don't
<rwmjones> kelaouchi, path of least resistance is probably Firefox -> Print page -> Save as Postscript (if you've got a Unix box, that is)
<kelaouchi> ok thx rwmjones
<rwmjones> & the second half of that is to use ps2pdf
<kelaouchi> sure
xleroy has joined #ocaml
xleroy has quit [Remote closed the connection]
xleroy has joined #ocaml
<LeCamarade> Need to sleep ...
xleroy has quit [Remote closed the connection]
<LeCamarade> OCaml's string philosophy feels obtrusive sometimes.
<rwmjones> extlib has an extensive supplemental library for strings
xleroy has joined #ocaml
<xleroy> I
<LeCamarade> rwmjones: Is it standard?
<LeCamarade> Nope.
<xleroy> I
<xleroy> I
<rwmjones> well, it's in extlib - what do you mean by "standard"?
<xleroy> I
xleroy has quit [Remote closed the connection]
<rwmjones> was that the xleroy?
<LeCamarade> Sorry, that xleroy is a bot I'm writing.
<rwmjones> ah
<LeCamarade> Sorry, sorry/
<LeCamarade> He;s supposed to be evalutating statem,ents
<LeCamarade> OCaml statements.
<rwmjones> he's written in ocaml?
<LeCamarade> Named after Xavier Leroy.
<LeCamarade> yes. Dirty OCaml.
<LeCamarade> Very dirty, because I wrote many parts when I was a n00b, and then I abandoned the project for a while.
<bluestorm_> hm
<bluestorm_> maybe xleroy is a bit confusig name
<LeCamarade> Tomorrow, I'll finish him. I promise. Okay, any name suggestions?
<bluestorm_> "desertbot" was better :-°
<bluestorm_> hum
<bluestorm_> LeCamarade:
<bluestorm_> sandbot ?
<bluestorm_> desert, camels, security
<LeCamarade> bluestorm_: Yeah, but he's no longer a bot. For now, he will be an evaluator.
<bluestorm_> hm
<rwmjones> xavierbot or xleroybot
<bluestorm_> Sandy ? :-°
<rwmjones> should have bot in the name really
<LeCamarade> Heh. xavierbot.
<LeCamarade> sandy.
<LeCamarade> Yeah. There should be a `bot' somewhere.
<LeCamarade> It's just a conf file away, anyway. Everything is confed.
<rwmjones> cool, you'll have to release the source so I can put the bot on Red Hat's internal IRC chans :-) piss people off ...
<LeCamarade> :o)
<LeCamarade> The source could make you puke - some parts. I'll clean up before putting it out there. I had a whole list of modules, by the way, for desterbot.
<LeCamarade> rwmjones: I've always wanted to ask. That Wiki preview on COCAN and the tutorial ... is it a Java applet?
<rwmjones> javascript
<rwmjones> view source on the page, you'll see how it works
<LeCamarade> With 4j4x?
<rwmjones> well, javascript, but it makes a request to the server to do the actual formatting
<LeCamarade> Ah.
<rwmjones> well, it uses XMLHTTPRequest, which is apparently now known as "ajax", yes
<LeCamarade> :o)
<LeCamarade> Gone home.
<LeCamarade> rwmjones, By the way, I am that guy who does F# and bugs you with the question about mutually-recursive funcs. :o)
LeCamarade has left #ocaml []
pango_ has joined #ocaml
ygrek has quit [Remote closed the connection]
tcr has joined #ocaml
<tcr> I'm wondering why equality test operators like > &c seem to be type overloaded, but the arithmetic operators are not. Could anyone clarify what's the difference between those two kinds that make it (seemingly) easily possible for one kind but not the other?
chs_ has quit []
<mbishop> tcr: http://pauillac.inria.fr/~aschmitt/cwn/2002.12.03.html#2 might hold your answer
mnemonic has quit ["leaving"]
mnemonic has joined #ocaml
<tcr> mbishop: I'm aware of the problems of operator overloading and type inference, but I'm wondering how it's managed to get it for > &c.
<mbishop> probably because they always return boolean types?
<tcr> Heh, how true. :)
zmdkrbou has quit ["prout"]
Demitar has joined #ocaml
malc_ has joined #ocaml
<malc_> Am i the only one who receives huge amount of duplicate messages from the mailing list?
mnemonic has quit ["leaving"]
cjeris has quit [Read error: 104 (Connection reset by peer)]
<lucca> malc_: not seeing duplicates here
<malc_> lucca: i'm getting on few hundreds a day..
<malc_> -on
tcr has quit ["Leaving."]
<mbishop> I just get the digest
noteventime has quit ["Leaving"]
kfor has joined #ocaml
smimou has quit ["bli"]
screwt8 has quit [Read error: 104 (Connection reset by peer)]
kfor has quit ["Leaving"]