systems changed the topic of #ocaml to: OCaml 3.07 ! -- Archive of Caml Weekly News: http://pauillac.inria.fr/~aschmitt/cwn , A tutorial: http://merjis.com/richj/computers/ocaml/tutorial/ , A free book: http://cristal.inria.fr/~remy/cours/appsem, Mailing List (best ml ever for any computer language): http://caml.inria.fr/bin/wilma/caml-list
wazze has quit ["--- reality is that which, when you stop believing in it, doesn't go away ---"]
kinners has joined #ocaml
gim has quit ["dodo -h now"]
mimosa has quit ["J'ai fini."]
Nutssh has joined #ocaml
olczyk has joined #ocaml
<olczyk> In a toplevel, is there a way to ask for a list of all loaded modules?
Smerdyakov has quit [Read error: 60 (Operation timed out)]
<Riastradh> olczyk, why don't you ask the mailing list?
Smerdyakov has joined #ocaml
<olczyk> Yeah, yeah. I've already asked the beginners group and comp.lang.functional.
olczyk has quit [Read error: 104 (Connection reset by peer)]
Nutssh has quit ["Client exiting"]
Nutssh has joined #ocaml
kinners has quit [Read error: 113 (No route to host)]
rox has quit [Read error: 60 (Operation timed out)]
mlh has joined #ocaml
Nutssh has quit ["Client exiting"]
rox has joined #ocaml
Nutssh has joined #ocaml
bk__ has quit ["I'll be back"]
buggs^z has joined #ocaml
buggs has quit [Read error: 110 (Connection timed out)]
mlh has quit ["ni!"]
Nutssh has quit ["Client exiting"]
srv has quit [Remote closed the connection]
srv has joined #ocaml
kinners has joined #ocaml
andrewb has joined #ocaml
Nutssh has joined #ocaml
mimosa has joined #ocaml
whiskas has joined #ocaml
gim has joined #ocaml
Nutssh has quit ["Client exiting"]
Banana has joined #ocaml
whiskas has quit ["Pa / Bye."]
Demitar has quit [Read error: 110 (Connection timed out)]
Demitar has joined #ocaml
buggs^z is now known as buggs
<pattern> Random.self_init ()
<pattern> let i = Random.int 200
<pattern> let _ = print_endline( string_of_int i )
<pattern> why does this keep printing the same number when i run it?
<ejt> same random seed ?
<pattern> it shouldn't be
<pattern> i've even tried Random.init 1, followed by Random.init 2 and got the same number
<pattern> ahhhh, maybe Random.self_init isn't being run
<pattern> since it's not in let _
<ejt> it's not compiling 'i' to be a constant is it ?
<ejt> through over agressive optimisation
<pattern> shouldn't matter
<pattern> i'm talking about outputting the same number between runs of my program
<pattern> now it's working
<ejt> what did you change /
<ejt> ?
<pattern> it was, as i suspected, that Random.self_init (or Random.init) were written in my program outside of let _
<pattern> so they were never being executed
<ejt> ah
<Demitar> Shouldn't matter. Toplevel statements are run as they are come across. However this is looks like a bad mix of functional and imperative programming.
<Demitar> That is, I suspect the evaluation order isn't guaranteed.
kinners has quit ["leaving"]
<pattern> well, it does seem to matter
<Demitar> Yes, because you're forcing the evaluation order in the latter case. How did you structure it exactly?
<pattern> with ; in let _
<Demitar> And still that works just fine here...
<Demitar> demitar@bubbles:~$ ./foo
<Demitar> 1
<Demitar> demitar@bubbles:~$ ./foo
<Demitar> 1
<Demitar> demitar@bubbles:~$ ./foo
<Demitar> 92
<Demitar> ...
<Demitar> demitar@bubbles:~$ cat foo.ml
<Demitar> Random.self_init ()
<Demitar> let i = Random.int 200
<Demitar> let _ = print_endline( string_of_int i )
<pattern> well, it doesn't here.. just keep printing 119
<Demitar> What OCaml version are you using?
<pattern> 3.06
<Demitar> And what platform?
<pattern> linux
<Demitar> Well, it looks weird to me, perhaps 3.06 behaves differently (using 3.07+2 here).
<pattern> as soon as i put the Random.self_init in to the let _ it started working
<Demitar> Yes, the ";" forces evaluation order so if that's the issue it should start to work.
<Demitar> How about not moving the line but adding a let () = Random.self_init () instead?
<Demitar> That should also force evaluation order.
<pattern> that worked
<pattern> what's the difference between let _ and let () ?
<Demitar> Well then that was the issue it seems.
<Demitar> let _ = allows any result rhs, let () = matches only unit. In general let _ is dangerous since it doesn't catch partial applications, ignore is better for that.
<pattern> let () = Random.self_init ()
<pattern> let i = Random.int 200
<pattern> ignore print_endline( string_of_int i )
<pattern> "This function is applied to too many arguments" for Random.int
<pattern> but with "let _" instead of "ignore" it works
<pattern> i mean "let _ ="
<Demitar> That's a syntax error.
<pattern> why?
<Demitar> You need to terminate the let with a ;; toplevel.
<Demitar> It automagically does that when it sees another let.
<pattern> ahh
<pattern> same error when i use ;;
<pattern> let () = Random.self_init ()
<pattern> let i = Random.int 200 ;;
<pattern> ignore print_endline( string_of_int i )
<Demitar> Yes, that's because ignore is 'a -> unit.
<Demitar> You need to enclose print_endline ... in ().
<Demitar> But in this case ignore isn't relevant since you already evaluate to unit.
<pattern> cool
<Demitar> What you probably want to do is to wrap it all in a function and only run one toplevel.
<Demitar> Say: let main () = Random.self_init (); let i = Random.int 200 in print_endline( string_of_int i ) ;; main ()
<pattern> well, i'm trying to figure out what the ideal toplevel should be
<pattern> usually i use let _
<pattern> but you recommended ignore instead
<Demitar> Yes, let _ = is commonly used in places where ignore is more relevant. That is, to ignore the return argument.
<pattern> but let () matched only unit.. that would require that main evaluate to unit, which it may not always do... thus isn't let _ better?
<Demitar> No, you should really use ignore (...) explicitly when you don't care for the returned value.
<Demitar> The danger of let _ = is that it doesn't catch partial applications.
<Demitar> Thus you might simply be forgetting to pass the last argument to a function and you all of the sudden don't have a clue why your program doesn't do anything.
<pattern> i understand
<Demitar> Good, so you don't want an example then? :)
<pattern> i'm still a bit confused about foo ()
<Demitar> foo ()?
<pattern> wait
<Demitar> main ()?
<pattern> i was confusing your main () with let ()
<Demitar> Ah, and remember that main just happends to be a convenient name of the main function, it's not run magically like in C.
<pattern> so main () just takes a unit argument, but can evaluate to anything, while let () must evalutate to unit?
<Demitar> main () is simply a function.
<pattern> yes
<Demitar> let () = is a pattern matching expression.
<pattern> but what is it matching?
<Demitar> () is the only value the type unit can have.
<Demitar> A completely unuseful example: let "foo" | "bar" | _ as x = "bar";;
<pattern> in "let foo x = match x with ..." foo is called with some argument that is used in the pattern match... what is let () called with? or is it?
<Demitar> let () isn't a function.
<Maddas> pattern: you can also say let foo 10 = ....
<Demitar> It's a pattern match that matches the value () and doesn't bind the value to any name.
<pattern> maddas, yes
<pattern> oh, i see
<Demitar> let () as foo = would bind the value to the name foo.
<Maddas> pattern: () is the only value the type unit can have, so () is an exhaustive match
<pattern> right
<Maddas> err, an exhaustive pattern
<pattern> so about your earlier foo/bar example, maddas...
<pattern> why does that evaluate to "bar"?
<Demitar> Sometimes it feels like I can do all kinds of irrelevant stuff in OCaml. ;-)
<pattern> what happened to "foo" ? and why doens't "foo" have a -> ?
<Maddas> Surely you mean Demitar :-)
<Demitar> That you can do it doesn't mean it makes sense... :)
<pattern> i meant demitar
<pattern> sorry
<andrewb> I always though "let 42 = 43" was an interesting ocaml brain-stretch.
<pattern> heh
<Demitar> pattern, I believe match x with [pattern match] -> [do this] is valid.
<pattern> it is
<pattern> that i understand
<Demitar> That is the -> part has nothing to do with the pattern matching expression, but with the match ... with construct.
<pattern> i shouldn't there be a -> after let "foo" in your example?
<Maddas> pattern: For example, you can say: type bar = Baz;; let foo Baz = 100;; -- the function foo will take any value of the type bar (There is only one value something of the type Bar can have!)
whiskas has joined #ocaml
<pattern> maddas, yes, that makes sense, i think
<Maddas> you can also say type myunit = ();;, so that works along the same lines
<Demitar> pattern, as I said the example was completely useless since there is no way to do anything different depending on what string you actually match.
<pattern> maddas, yes, i understand that
<Maddas> let foo () = 100 is the same as saying let foo (x : unit) = 100
<pattern> yes
<Maddas> Ok, hope it helped :-)
<pattern> demitar, but i still want to understand it
<pattern> maddas, yes it did... i understand that now
<Demitar> The case where it's really useful is in the case of tuples.
<Demitar> let (x, y) = get_bounds ()
<Demitar> And such.
<pattern> that makes sense
<pattern> but i still don't understand your foo/bar example :(
<Demitar> What don't you understand?
<pattern> as i understand pattern matching there must be somehting that the match evaluates to when it matches
<pattern> so "foo" is the pattern
<Demitar> It either matches "foo" or "bar" or any string and binds that value to the name foo.
<pattern> but where is the value it evaluats to?
<Demitar> s/name foo/name x/
<Demitar> The *value* is evaluates is "bar" the *name* it binds to is x. let "foo" | "bar" | _ as x = "bar";;
<pattern> but what happended to "foo"?
<Demitar> let x = "bar" or let _ as x ="bar" are equivalent.
<pattern> right
<pattern> i'm still confused about what role "foo" plays here, though
<Demitar> pattern, it's simply a case which "could" happend but never will.
<pattern> ahh
<Demitar> It's completely and utterly useless.
<Demitar> Except for the possible obfuscation value. ;-)
<pattern> but even though it never happens shouldn't it have a value to evalute to? thus, shouldn't it have a ->
<pattern> let "foo" -> "baz" | _ as x = "bar" ;;
<Demitar> No, you can't have an action happend inside a let ... = construct.
<pattern> or somehting
<pattern> hmm
<Demitar> That has nothing to do with pattern matching.
<pattern> what doesn't?
<Demitar> It's part of the match ... with construct (or function for that matter).
<pattern> but doesn't match ... with do pattern matching?
<Demitar> Yes, it contains pattern matching expressions. But those are contained in between the with [pattern match] ->
<pattern> right
<Demitar> And subsequent expressions | ... ->
<pattern> so i'm used to seeing the [pattern match] followed by ->
<pattern> thus my confusion at your ->less "foo"
<Demitar> Yes, that happends with exception handling too.
<Demitar> Yes, there are reasons OCaml is scary at first sight. :)
<pattern> heh
<Demitar> At least when coming from a Cish background.
<pattern> # let "foo" | "bar" | _ as x = "bar";;
<pattern> val x : string = "bar"
<pattern> # let "foo" | _ = "bar" ;;
<pattern> #
<pattern> what happened here?
<pattern> why didn't it evalute to "bar"?
<Demitar> It did, but the value wasn't bound to any name.
<pattern> shouldn't ocaml still report it? as _ maybe?
<pattern> val _ : string = "bar" ?
<Demitar> the first expression didn't evaluate to anything toplevel. But bound "bar" to a name.
<pattern> ahh
<pattern> so toplevel expressions don't evaluate to anything?
<Demitar> Sure they do. But not the let expressions.
<pattern> i see
<Demitar> Try "bar";;
<pattern> ahh
<pattern> right
<pattern> hmm
<pattern> # let "foo" = "bar" ;;
<pattern> Warning: this pattern-matching is not exhaustive.
<pattern> Here is an example of a value that is not matched:
<pattern> ""
<pattern> Exception: Match_failure ("", 4, 9).
<pattern> so what is it that is being matched?
<Demitar> You are trying to match "bar" against an incomplete pattern match which only matches "foo".
<Demitar> Incomplete pattern matches are inherently evil.
<pattern> yes
<pattern> so the pattern match is an entity in and of itself... it need not be "filled" with anything as x in "let foo x = match x with" is "filled" with a value when foo is called
<pattern> the pattern match stands on its own in a "let [pattern match] = ..." expression, right?
<pattern> or maybe "tested against" is a better term than "filled"
<Demitar> That sounds sensible. *goes back to doing his laundry*
<pattern> thanks, demitar
<Banana> it allows you to do nasty things like try let 0 | 1 | 2 | 3 = "small" with Match_failure -> "not small"
<Banana> erf
<pattern> why would you do that?
<Banana> let ... = f() in "small" I meant.
whiskas has quit ["Pa / Bye."]
<Banana> either way you shouldn't match values but only constructors, like true | false | () | A(x) ....
<Banana> some weird guys will say that integers are constant constructors, but don't believe them !!!
<pattern> hmm
<pattern> # let f () = 9 ;;
<pattern> val f : unit -> int = <fun>
<pattern> # try let 0 | 1 | 2 | 3 = f() in "small" with Match_failure x -> "not small" ;;
<pattern> Warning: this pattern-matching is not exhaustive.
<pattern> Here is an example of a value that is not matched:
<pattern> 4
<pattern> - : string = "not small"
<pattern> so how does this work?
<Banana> well it's easy.
<pattern> doesn't it let ... here always fail to match?
<Banana> yes.
<Demitar> Banana, matching against values can be useful in the case of stream parsers.
<pattern> # let f () = 0 ;;
<pattern> val f : unit -> int = <fun>
<pattern> # try let 0 | 1 | 2 | 3 = f() in "small" with Match_failure x -> "not small" ;;
<pattern> Warning: this pattern-matching is not exhaustive.
<pattern> Here is an example of a value that is not matched:
<pattern> 4
<pattern> - : string = "small"
<Banana> well in that case i admit that it's more concise that using a bunch of x -> if x = ... then
<pattern> but here it seemed to match
<Banana> pattern: it's easy, the pattern matching are compiled as some kind of big (switch) (like in C).
<Banana> and there is a "default" clause added that raise Match_failure with the unmatched argument.
<pattern> but the left hand side of the = is the pattern match, no?
<pattern> the right hand side is what the matched pattern should evaluate to, right?
<Banana> this notation is strictly equivalent to try match f() with 0 | 1 | 2 | 3 -> "small" with Match_failure x -> "not small"
<pattern> weird
<pattern> well, that definitely is not what i'm used to understanding = to mean
<Banana> i think this is more or less a "side effect" of the let "pattern" = foo in blah.
<Banana> to allow things like let (x,y) = getpos() in ... which are usefull.
<pattern> let (x,y) = getpos() i understand
<Banana> you have to allow any kind of pattern expression on the left side of the =
<Banana> and 0 | 1 | 2 is a valid pattern.
<Banana> so you can write it too.
<pattern> the lhs of the = i understand
<pattern> it's the f() on the rhs of the = in your example that is weird
<Banana> well to understant that you simply have to take the real meaning of let.
<pattern> i'm used to thinking what's on the rhs is what the pattern match will evalute to, not what it is tested against
<Banana> let is a binder, so let res = f() in ... is natural ok ?
<pattern> yes
<Banana> but then let res1,res2 = f() in ... would also be natural.
<pattern> yes
<pattern> ok, i think i understand
<pattern> i was getting all confused with -> and =
<pattern> makes perfect sense now
<pattern> # let "foo" | "bar" | _ as x = "bar";;
<pattern> val x : string = "bar"
<pattern> but here why would x be bound to "bar" when "bar" matches "bar"?
<Banana> let ("foo" | "bar" | _) as x = "bar"
det has quit [kornbluth.freenode.net irc.freenode.net]
<Banana> that's the right associativity.
<pattern> ah
det has joined #ocaml
<pattern> so there it does match "bar"
<Banana> if not, your x would be non linear (that is ) there would be times when x is not binded to anything.
<pattern> yes
<pattern> i think that added to my confusion
<pattern> but now it too makes sense
<Banana> hence let "foo" | _ as x = "bar" in print_endline x;; would not make any sense.
<pattern> right
<pattern> thanks for clearing that up for me
<pattern> would be handy if ocaml printed parenthesis like you just did
<Banana> as Demitar says earlier, matching over values can be usefull (especialy on string or chars) but it's better to use the match construct for this and add a _ -> case.
<pattern> right
<Banana> the let should only be used to deconstruct structural values, like tuples, records and so on.
* pattern nods
<Demitar> Yes, I wouldn't do that in a let construct, that'd be pure evil. =)
<pattern> why is the let keyword there for things like let 0 | 1 = f() ?
<pattern> why not just allow: 0 | 1 = f()
<pattern> since it's not bound to anything
<Banana> let 0 | 1 = f() is only a side effect of allowing let (x,y) = f().
<pattern> you mean a special case?
<Banana> yes.*
* pattern nods
<pattern> i guess that's true
<pattern> but they could require binding with let
<Banana> otherwise there is need to redefine a special "variable only" pattern class and it's rather difficult...
<pattern> and then allow an expression without let
<pattern> well, if it's difficult i understand
<pattern> just trying to think of a clearer syntax
<pattern> as to me let does imply binding
<Banana> well you could turn this around by saying it's an empty binding.
<Banana> (which is a binding :D )
<pattern> heh
<pattern> i guess you can say that binding to nothing is a binding :)
<pattern> but i think that's an abuse of the term binding... conceptually when you bind you expect to bind to something, not nothing :P
<pattern> but semantically, you'd be adding nothing by allowing: 0 | 1 = f()
<pattern> it's just syntactic sugar
<pattern> would just make it easier for beginners like me to grasp :)
<Banana> hum... it doesn't make sense to have only 0|1 = f().
<Banana> what do you do if it matches ?
<pattern> 0 | 1 = f() in "small"
<pattern> remember?
<Demitar> But that's an evil abuse of pattern matching anyway!
<pattern> why?
<Banana> yo don't match over values.
<Demitar> Since it's an incomplete match!
<Banana> you.
<pattern> demitar, yes, he used an exception for the default case
<pattern> it is ugly
<Banana> pattern: the exception is a "moindre mal".
<Banana> that is there is no cleaner other way to handle that.
<pattern> but as long as it is allowed semantically you might as well have it be as clear as possible syntactically :)
<Banana> the let ... in is clear to me...
<Demitar> pattern, that it's possible doesn't mean it's good coding practice and thus should be encouraged.
<pattern> banana, yesh i can see how it'd be clear to you since you're an expert... the syntactic sugar would really only help beginners like me
<pattern> demitar, that's true
<Banana> "expert" ...
<pattern> then if it's bad coding practice, why allow it at all?
<pattern> there must be some cases where it makes sense to use it, right? or if not, why not eliminate it?
<Demitar> Since you don't want to place arbitrary limitations "just because" it's bad style. It might make sense at times.
<pattern> well, if it might make sense sometimes then why not allow a clearer syntax?
<Banana> because it would be difficult to separate good pattern matching from bad ones...
<Demitar> pattern, it would greatly complicate the language at dubious gain.
<pattern> i see
<Banana> erf
<Banana> I only say crap...
<Banana> it's feasable since the compiler detect when a matching is not exhaustive :D
<pattern> yes
<pattern> thank god for that
<pattern> or thank inria :)
<Banana> the proper way is to use ocamlc -warn-error S
<pattern> what does that do?
<Banana> so that non exhaustive match are turned into error and not warning.
<Banana> or better -warn-error A
<pattern> that's not even in my man page
<Banana> all warning are turned into compilation error.
<pattern> cool
skylan has quit [Read error: 60 (Operation timed out)]
bk__ has joined #ocaml
bk__ has quit ["I'll be back"]
cjohnson has quit ["Drawn beyond the lines of reason"]
ptolomy has joined #ocaml
<Smerdyakov> ptolomy, hey! How long have you been interested in OCaml? Or are you just spying? :)
<ptolomy> Mm? Oh, a little of both. I've been interested for a few months now. Learned about it, and have been messing around with it until I get good enough to make it my primary language. :_
<Smerdyakov> Super.
<Smerdyakov> Are you graduating this spring?
<ptolomy> Heh. Not likely.
<ptolomy> I should be, but I'm gonna go a full 4 year instead.
<ptolomy> Odd full circle I've come, though. From absurd assembly enthusiast to ocaml proponent.
<Smerdyakov> Eh, I did the same thing. :)
<ptolomy> Rather, a "180". Not full circle.
<ptolomy> I think it's a natural progression, really.
<Smerdyakov> I'm sure you won't find much argument here. :)
<ptolomy> Oh. that reminds me..
<Smerdyakov> I was just talking with some people yesterday about how my advisor has gotten a huge chunk of local people into OCaml by simply providing really useful OCaml tools and libraries in his research, and teaching a class where OCaml was required and useful things were made. :)
<ptolomy> I actually started with it because of a course taught in it.
<ptolomy> Good way to get going.
<ptolomy> I know Ocaml has that very detailed formatting guide, and I have been thinking, 'Hey, it would be fun to make a program that does that for me, a la gnu ident'. But it would seem that such a thing would already exist. Any idea?
<Smerdyakov> Sure. At least two emacs modes.
<Hadaka> Puuh... that space wasting thread does *really* seem to be a bait for everybody who wishes to restate old ideas
<ptolomy> Damn. Even more indication that I'm gonna have to move away from vim someday.
<ptolomy> Hadaka, Which thread is this?
<Hadaka> ptolomy: you don't want to know
<Hadaka> and that comment was on the wrong channel, so it might've been a *bit* out of context :)
<ptolomy> Ah. Heh. Okay.
Defcon7 has quit [Read error: 54 (Connection reset by peer)]
<Smerdyakov> ptolomy, would you like to join us in #hprog?
<ptolomy> What is 'hprog'?
<Smerdyakov> TPU successor
<ptolomy> Sure.
Defcon7 has joined #ocaml
wazze has joined #ocaml
<pattern> vim can auto-indent for you
<pattern> and you can also reformat blocks of text in vim, if you like
<ptolomy> This is true.
<ptolomy> but I've grown samefully astyle/indent dependent in other languages, so I'm looking for any easy out. :)
<pattern> what exactly do you want to do?
<ptolomy> Well, I figured it'd be a good exercise in Ocaml/parsing to write a 'Automatically make your ocaml code compliant with the official style specification' program. However, if it's been done, I probably won't.
<pattern> camlp4o pr_o.cmo mysource.ml
<pattern> try that
<ptolomy> well now. that's a thing a beauty.
<pattern> :)
<ptolomy> thanks.
<pattern> np
* ptolomy reads more on this camlp4
<pattern> in vim i have:
<pattern> map <F4> :!ocaml.reformat
<pattern> % cat ocaml.reformat
<pattern> #!/bin/sh
<pattern> #
<pattern> TEMP_FILE=/tmp/temp.ocaml.reformat.ml
<pattern> cat > $TEMP_FILE
<pattern> camlp4o pr_o.cmo $TEMP_FILE
<pattern> rm $TEMP_FILE
<pattern> then i can hilight a block of text in vim, hit F4, and it gets automatically reformatted
<ptolomy> That's pretty great. I am going to steal that.
<pattern> please
<pattern> spread the word :)
<pattern> the TEMP_FILE variable can probably be created better, so that it's unique
<pattern> not the variable, i mean the filename
<ptolomy> right.
<pattern> and by "hilight" i meant "select"
Nutssh has joined #ocaml
<pattern> discussion of "a fault tolerant scripting language" on slashdot -> http://developers.slashdot.org/developers/04/03/15/0051221.shtml?tid=126&tid=156
<ptolomy> I'm going to make my girlfriend learn Ocaml. She wants to learn how to program, but she knows little about computer and much about math. Seems like a decent path to take.
<pattern> yeah, if she knows lambda calculus then she practically knows ocaml already
<pattern> and the concepts relating to sets and functions in general carry over very well
<whee> my gf is ending up learning c++ as a first language (required college course); it's going to be fun helping her with that :/
<whee> although she seemed pretty interested in the whole thing, I could probably get her learning another language on the side too :P
<pattern> i wish i knew math better
<pattern> all this stuff is new to me
<whee> you don't need to know much math to handle languages like ocaml though
<pattern> well, "much math" is relative :)
<pattern> i definitely need much more than to handle imperative languages
<whee> I don't have much math background other than the typical practical knowledge
<ptolomy> I've never really associated ocaml with math.. what kind of math needs to be known?
<pattern> you don't "need" to know it ahead of time... learning ocaml = learning math, imo
<whee> all the math I know is engineering oriented, so I get differentials and tings of that nature which don't have any basis for programming really
<whee> I odn't see where math comes in at all :P
<pattern> well, all of this function applicaiton stuff *is* lambda calculus
<ptolomy> Heh. then again, I don't really consider (internally) lambda calculus to be math either, so my estimation of ocaml's mathiness may be skewed.
<pattern> sets, functions... that's all math
<whee> you don't need a background in the lambda calculus to understand how to use it, though
<pattern> no, as you learn lambda calculus by learning ocaml
* ptolomy think of APL.
<pattern> and vice versa
<pattern> and type systems are math... there's a section on types in this discrete math book i just got... so it must be math :P
<ptolomy> Yeah. Ocaml infers types. That is fun.
* ptolomy had to write a type-infering thing.. tricky tricky.
<Nutssh> I've done it too. Not too bad.
<pattern> logic, propositional calculus... both used in the manipulation of boolean values is math
<pattern> of course, that's not used just in ocaml but in all programming
<pattern> same with trees and graphs
* ptolomy is really itching to write some ocaml/openGL stuff. Man, that'll be sweet.
<pattern> yeah, that sounds like fun
<Nutssh> :)
<ptolomy> So beautifully suited.
<whee> I just don't see those things as math I guess
<ptolomy> articulated motion with trees, functional callbacks... *Homer-style Mmmm*
<ptolomy> My theory is that is because math is taught wrong.
<whee> probably :P
* ptolomy was taught until about maybe the age of 16 that math == arithmatic.
<pattern> they're all in my math books, so they have to be math :)
Nutssh has quit ["Client exiting"]
<whee> my problem is that I've taken so many courses aimed at presenting solutions to practical problems, that there isn't much theory behind what I ulearn and use
<whee> well there's theory, but I don't care about it
<whee> engineering isfun :P
<pattern> yeah, i like practical stuff too
<pattern> but on the other hand, i like solving problems in general
<whee> indeed
<pattern> so there's theory stuff that i find interesting as well
<whee> I have tons of fun designing with languages that don't suck
amayil has joined #ocaml
<ptolomy> I'm wasting precious studying time by creating benchmarks for ocaml, C, and C++ in which ocaml wins.
amayil has left #ocaml []
<ptolomy> I can't make it work if gcc uses any optimization though.
async has joined #ocaml
cjohnson has joined #ocaml
<pattern> ptolomy, have you seen the great computer language shootout?
buggs has quit [Read error: 110 (Connection timed out)]
Nutssh has joined #ocaml
buggs has joined #ocaml
<Maddas> ptolomy: Are you selectively creating benchmarks just so that O'Caml wins?
<Nutssh> How about working on an optimization pass for the ocaml compiler? From looking at its output, value numbering should be a huge win.
<Nutssh> I started that, then found out that the internal structure of the AST's in ocaml isn't amenable to it quickly. I was hoping it'd be a one-day project.
async has quit [Remote closed the connection]
<Riastradh> They should just use CPS and simplify everything dramatically.
yella has joined #ocaml
Nutssh has quit ["Client exiting"]
Nutssh has joined #ocaml
mr_jim has joined #ocaml
buggs has quit [Read error: 54 (Connection reset by peer)]
cjohnson has quit [Read error: 60 (Operation timed out)]
mr_jim has quit ["Leaving"]
Nutssh has quit ["Client exiting"]
Smerdyakov has quit [Read error: 60 (Operation timed out)]
mattam_ has joined #ocaml
mattam has quit [Read error: 60 (Operation timed out)]
mlh has joined #ocaml
skylan has joined #ocaml
ptolomy has quit [Read error: 104 (Connection reset by peer)]
gim has quit ["Zzz."]