lus|wazze has quit ["The Ogre philosopher Gnerdel believed the purpose of life was to live as high on the food chain as possible. She refused to ea"]
Kinners has joined #ocaml
polin8 has joined #ocaml
<jdrake>
any ideas for a command line for my ocaml program? (anything around, or should I just make my own)
<teratorn>
what now?
polin8 has quit [Read error: 104 (Connection reset by peer)]
polin8 has joined #ocaml
lus|wazze has joined #ocaml
brwill is now known as brwill_out
Kinners has left #ocaml []
brwill_out is now known as brwill
lus|wazze has quit ["The Ogre philosopher Gnerdel believed the purpose of life was to live as high on the food chain as possible. She refused to e]
brwill is now known as brwill_zzz
<jdrake>
in a match statement I have a list of valid selections that are specific chars like 'c', or 'q'. How can I provide a default option for anything left? I was thinking a general char might work, but can't figure it out.
<phubuh_>
match c with
<phubuh_>
| 'c' -> foo
<phubuh_>
| c -> something else
<jdrake>
arg!
<jdrake>
so simple too
<brwill_zzz>
or _
<phubuh_>
yeah, use _ if you don't need the actual value of the character
<brwill_zzz>
which is the more idiomatic solution
* brwill_zzz
nods and really goes to bed
<jdrake>
i was doing |c -> printf "Invalid Selection \'%c\'\n" c; menu_selection in
<phubuh_>
night!
<jdrake>
so that I know if it is bad
<jdrake>
hmm
<jdrake>
This kind of expression is not allowed as right-hand side of `let rec'
<phubuh_>
it's very important that the general match comes after all the specific ones, or it'll just hog all the values
<jdrake>
Printf.printf "Menu: [C]reate Game [Q]uit:";
<jdrake>
yeah i kind of figured that part, doing sequential order
ez4 has joined #ocaml
<ez4>
anyone here?
<jdrake>
yes
<teratorn>
hi
<ez4>
hi
<ez4>
how do I resolve nested match statements?
<jdrake>
i have a problem too - i have an input_char right after a printf, but the printf is cached or something. Is there a way of flushing this?
<ez4>
let foo a b = match a with
<ez4>
1 -> match b with
<ez4>
'a' -> ...
<ez4>
| 'b' -> ...
<ez4>
| 2 -> ...
<ez4>
the compiler doesn't know which match statement the vertical bar is associated with
<Xcalibor>
scheme requests for implementations, that is
<Xcalibor>
a community driven growing process for Scheme from r5rs
<systems>
well ocaml beats the crap out of scheme, no matter how it's channel is
<Maddas>
its
<Riastradh>
Yeah, try implementing a MOP in OCaml.
<systems>
MOP ??
<Xcalibor>
systems: mmm... sheme is a cool language... ocaml is as well... i don't think it'0s fair comparing them
<Riastradh>
Meta-Object Protocol.
<Maddas>
systems: no matter if it is or not, a language with too small userbase has a hard time growing
<Maddas>
except in niches, of course
<systems>
I don't know what meta object mean
<Riastradh>
RTF CLOS M.
<Maddas>
haha
<Maddas>
nice acronym :-)
<Riastradh>
Or read AMOP.
<Maddas>
systems: you see, even people who aren't beginners stumble upon questions once in a while, and an active IRC channel can be helpful to answer those.
<systems>
i am a beginner
<systems>
i am possibly less then one
<systems>
but i had a bias for ocaml, it's the best lang i ever saw
<vect>
I'm a fucking beginner too.
<Maddas>
O'Caml repels and attracts me, simultaneously :)
<systems>
and ocaml OO system is very good, and writen in ocaml i think
<Maddas>
I wouldn't call it the best/my favourite language though
<Xcalibor>
systems: OCaml is certainly very nice
* Riastradh
snorts.
<Riastradh>
(at 'the ocaml OO system is very good')
<systems>
??
<Xcalibor>
but saying Scheme has a small user base or is a bad language is a sign of lack of knowledge about scheme
<systems>
elaborate
<mattam>
Riastradh: well it has many good things over 'industrial-strenght' OO languages
<Riastradh>
OK. No first-class classes. No dynamically sending messages (dynamic method dispatch is different).
<mattam>
first-class ... the holy grail
<Riastradh>
No MOP. No dynamically-created classes. Little support.
<systems>
first class, what does this term refer to
<mattam>
manipulating classes
<Riastradh>
It means they're just ordinary values.
<mattam>
you only manipulate object in ocaml today
<Riastradh>
Functions in OCaml are first-class; in many languages they are 'second-class,' i.e. you can't pass them as arguments to functions, return them, et cetera.]
<systems>
ahh, you mean in ocaml you only pass, objects (values) not classes
<mattam>
what sort of messages would you send not related to method invocation Riastradh ?
<Riastradh>
mattam, what do you mean?
<systems>
class code in not data in ocaml , you mean that
<mattam>
you said:No dynamically sending messages (dynamic method dispatch is different)
<Riastradh>
When you send a message, x#foo bar, you know _in_the_code_ that the selector is 'foo'.
<mattam>
yep
<Riastradh>
It is still dynamically dispatched, i.e. the compiled executable or whatever will dynamically look up what _function_ to call when it gets to that message.
<Riastradh>
What you can't do is dynamically _send_ a message, i.e. there's no equivalent to Smalltalk's -perform: or anything; you can't construct a selector, or get passed a selector, and then send it, whatever it be, to an object.
<karryall>
Riastradh: isn't that more or less the usual static/dynamic limitation ?
<karryall>
I mean; it's related to static typing
<mattam>
you mean like saying to an object what method it should perform, the method being a variable right ?
<Riastradh>
There's no way to do something like 'let f o s a = o#s a', which _should_ send a message whose selector is passed to 'f'.
<mattam>
i've never used that :) I remember reading it though
<karryall>
you can't dynamicaly send anything, you have to (staticaly) know the type
<mattam>
it needs reflection to be implemented doesn't it ?
<Riastradh>
Who cares what it needs in order to be implemented besides the compiler writers?
<Riastradh>
There's no multiple dispatch, too.
<mattam>
well, reflection and static typing aren't easily accomodable i think
<Riastradh>
That doesn't change the fact that the object system sucks.
<mattam>
but it would be a great challenge to get that into caml
<mattam>
well, maybe i'll do my thesis on this :)
<karryall>
Riastradh: you can implement a dispatch method yourself :)
<Riastradh>
I'd prefer that they would not waste time working on a craptacular object system but instead add typeclasses.
<karryall>
let f o s a = odispatch s a ;;
<Riastradh>
karryall, nope, because of static typing problems.
<Riastradh>
And in general an overly static object system.
<phubuh_>
Riastradh, i agree. type classes are what caml really needs, not some half-assed oop implementation.
<systems>
Riastradh discuss that in the mailing list, i for sure don't know the subject, but ocaml development process is fairly dynamic
<mattam>
well, maybe the oo impl will better
<Xcalibor>
Riastradh: do you know of any scheme OO implementation that's similar to CLOS?
<systems>
and are very likely to get your wish granted
<phubuh_>
even so, i'm not a very big fan of oop. i think type classes would be more useful on average than a really awesome oop system.
<Riastradh>
Xcalibor, are you asking for a Scheme implementation that supports CLOS, that is build around CLOS, or a Scheme package that implements CLOS?
<systems>
i think objectivec, does that selector thingie
<phubuh_>
i think he just wants something like clos for scheme instead of common lisp
<phubuh_>
systems, indeed
<Xcalibor>
Riastradh: mmm... either a scheme implementation that supports CLOS or a package I can use from MIT Scheme (for example)
<karryall>
actually objects in caml are not really here to support full-oop
<karryall>
it's a complement for modules
<karryall>
a different kind of modularity
<Riastradh>
Xcalibor, MIT Scheme itself has a built-in object system, SOS.
<Xcalibor>
Riastradh: nod... I know it has but I haven't yet studied it... how close is it to CLOS?
<Riastradh>
Xcalibor, I don't know; I've never used it, since I can't use MIT Scheme; what I really hate about it is that it doesn't have a MOP.
<Xcalibor>
Maddas: type classes aren't (O')Caml, so no need to apologize
<Xcalibor>
Riastradh: you cannot use MIT Scheme?
<Maddas>
What language has them implemented nicely, so I can read up on what they do?
<Riastradh>
Xcalibor, nope. It's x86-only.
<Riastradh>
Maddas, Haskell.
<Riastradh>
Maddas, would you like me to try to explain it in a pseudo-OCaml?
<Maddas>
Sure, if you don't mind.
<Riastradh>
OK. It will look a little odd, but oh well.
<Maddas>
It'll give me something more to think about, too :-)
<Riastradh>
Suppose we have a typeclass 'eq'.
<Xcalibor>
Maddas: in Haskell type clasees are somewhat like C++ abtract classes, or Java interfaces... they describe what a data type can do if it's an instance of that class... like type class Eq provides <= operation....
<phubuh_>
it allows for overloading on arbitrary types, sort of. like the show function in haskell turns an object to a string representation of it, and you can make it work on your own type by something like "instance Show MyType where show x = convertMyTypeToString x"
<Riastradh>
typeclass 'a eq =
<Riastradh>
val (==) : 'a -> 'a -> bool
<Riastradh>
end
<Xcalibor>
Maddas: Riastradh knows better, listen to him :)
<Xcalibor>
phubuh_: but show is not due to a type class but to an IO monad...
<Riastradh>
If you want to make (==) work on values of your type -- for example, the list type --:
<phubuh_>
show doesn't have anything to do with the IO monad
<Riastradh>
instance 'a eq => 'a list eq =
<Riastradh>
let (==) = function
<Xcalibor>
phubuh_: mmm... i thought show and read were provided by a monad, not a normal type class...
<Riastradh>
[] -> function [] -> true; _ -> false
<__DL__>
Xcalibor: show and read work with string, not with IO monad.
<Riastradh>
| (x:xs) -> function (y:ys) when x == y -> xs == ys | _ -> false
<Riastradh>
end
<Xcalibor>
__DL__: but you can read a Num
<Riastradh>
(oops, I accidentally wrote 'function [] -> true; _ -> false', which should have been 'function [] -> true | _ -> false')
<Maddas>
I think I get the idea, Riastradh.
<Riastradh>
Now, the part before the '=>' is the 'context.'
<__DL__>
its vconversion between string and wathever.
<Maddas>
That would basically allow "safe" overloading, wouldn't it?
<Riastradh>
The stuff between 'instance' and '=' means: 'for any type 'a that has an instance of eq itself, we define an instance of eq that works on values of the type 'a list.'
<phubuh_>
Maddas, that's exactly what it does :)
<Maddas>
Mmm. :-)
<Xcalibor>
Maddas: remarcably well seen... well done :)
<Riastradh>
Suppose we had an 'int_eq' function already. We could write:
<Riastradh>
instance int eq =
<Riastradh>
let x == y = int_eq x y
<Riastradh>
end
<Maddas>
i see.
<Riastradh>
Now '5 == 3' will return false, '5 == 5' will return true, '[5] == [3]' will return false, and '[5] == [5]' will return true.
<Riastradh>
So yes, it allows for 'sa{f,n}e' overloading.
<Maddas>
haha :)
<Maddas>
Xcalibor: well, I try.
<Xcalibor>
__DL__: mm.... OK, you are right: Main> :type show
<Xcalibor>
show :: Show a => a -> String
<Maddas>
Maybe with that kind of thing you could also make a String be treated like an array?
<Maddas>
By defining accessors
<phubuh_>
indeed
<Riastradh>
The latter two examples work because we previously said 'for any type 'a that has an instance of eq, ...'; the type of [5] is int list; here 'a becomes int, which already has an instance of eq.
<Riastradh>
This sort of thing could let OCaml'ers use monads easily:
<Riastradh>
typeclass 'a monad =
<Riastradh>
Er, better yet:
<Riastradh>
typeclass 'm monad =
<Riastradh>
val return : 'a -> 'a 'm (* the arguments to the typeclass may take arguments themselves! *)
<Riastradh>
val (>>=) : 'a 'm -> ('a -> 'b 'm) -> 'b 'm
<Riastradh>
end
<Xcalibor>
Riastradh: that would be very elegant, indeed
<Maddas>
I guess there's a similarity (if only very distant and not technically related) between this and tieing in Perl
<Xcalibor>
afaik so far monads are really powerful
<phubuh_>
now, repeat this process until you get a faster haskell implementation!
<Riastradh>
Xcalibor, not quite as elegant as Haskell, though.
<Xcalibor>
(eg. in haskell lists are actually monads)
<Riastradh>
Xcalibor, they just happen to have a monad instance.
<phubuh_>
the monadic operators are defined on lists, but it's a stretch to say that lists *are* monads
<Xcalibor>
Riastradh: that's probably due to the strictness of Ocaml... Haskell lazyness must help... i've read in comp.lang.functional people having problems trying to implement monads in C++...
<phubuh_>
oh god
<Maddas>
haha
<Xcalibor>
phubuh_: well, i don't understand *so much* about monads, yet :)
<Riastradh>
Xcalibor, laziness has nothing to do with it.
<mattam>
Riastradh: why is it nicer in haskell ?
<mattam>
would it be in fact :)
<Xcalibor>
Riastradh: I see... anyway people were discussing (related to Functional C++, I think) that eager evaluation makes implementing monads more difficult... (or so it seemed)
<phubuh_>
partly because you don't need to parenthesize its lambda expressions
<phubuh_>
but that's a very minor issue :-)
<Riastradh>
mattam, well, for monads, it's about the same (although Haskell has the 'do' syntax), but for typeclasses in general, Haskell is nicer, because parametrized types in Haskell are curried.
<__DL__>
You have lazyness in ocaml if you want, so one could implement lazy monad in ocaml...
<mattam>
i don't think \x -> x couldn't be added to caml :)
<phubuh_>
in fact, do would be pretty trivial to implement with campl4, would it not?
<mattam>
oh yeah the a b c Monad thingie
<Riastradh>
phubuh, probably, but camlp4 is _way_way_way_ too gross for me to want to have to do anything with it.
* Riastradh
hugs Lisp macros.
<phubuh_>
Riastradh, yeah :~(
<phubuh_>
lisp macros are tauntingly elegant
<Maddas>
So, why don't we just implement typeclasses already?
* Maddas
cheers enthusiastically
<Xcalibor>
phubuh_: scheme macros, however, are hygienic :-)
<phubuh_>
i don't really like scheme macros :/
<Riastradh>
Maddas, ok, tell the OCaml implementors to do it! I'm just not interested enough in OCaml to want to bother.
<Maddas>
Heh.
<systems>
Riastrach i always knew you are a hater
<systems>
now i am certain
<Riastradh>
When I said 'Lisp macros,' I meant 'Lisp' as in 'the family of languages Lisp that includes Common Lisp, Scheme, and elisp.'
<Xcalibor>
Riastradh: ah, okay :-)
<Maddas>
Riastradh: maybe I'll actually ask once, if I learn more about it.
<Riastradh>
phubuh, what don't you like about syntax-rules?
<Xcalibor>
do you include Goo? or is it too different to be included? just curiosity...
<Riastradh>
Xcalibor, sure.
<Maddas>
Maybe I should learn Haskell too, later on.
<Maddas>
Sounds like it isn't that bad after all ;-)
<Xcalibor>
Riastradh: and are you as eager as I am for Paul Graham to release Arc?
<Xcalibor>
Maddas: Haskell is really cool
<Riastradh>
Xcalibor, no.
<systems>
haskell is bad afterall
<Maddas>
I wish you guys could just, like, pick a language and say "This language is really cool and superior to all other languages in every way possible!". That would make learning so much easier :-)
<Riastradh>
Unless you don't like Arc, either.
<Xcalibor>
Maddas: that's hardly unlike.. if you go that, you go to USENet ;-)
<Maddas>
haha
<systems>
i don't like paul graham
<Maddas>
I don't want you to just say it, I want it to be true. But then, that would make everything so much mor eboring.
<Riastradh>
Maddas, well, Scheme, of course!
<phubuh_>
Riastradh, i seem to remember myself being frustrated with them... i don't remember what it was that i disliked, though. :(
<Xcalibor>
Riastradh: i haven't seen but a small example of arc code... i think Graham's reasons for making it are pretty valid, however... and I'd like him to make a public release at last
<systems>
ocaml is superior to all other
<Xcalibor>
anyone going to LL3 this year?
<Xcalibor>
well, Perl, undoubtedly ;-)
* Maddas
loves Perl
<Maddas>
but that's an entirely different story altogether
<Riastradh>
Xcalibor, his reasons for making it may be valid, but it's just another crappily designed Lisp that a few people will follow like the messiah and others will wonder why he bothered.
<Xcalibor>
why crappily? not enough CS behind it?
<systems>
did you read anything by paul
<Riastradh>
There are lots of _really_ annoying style issues (like vector referencing); he puts up a major argument about 'OO,' and then goes on to include some schmucky object system in Arc; et cetera.
systems has quit ["Client Exiting"]
<mattam>
CLOS was designed by chambers ? the one who did cecil ?
<Riastradh>
There wasn't 'one' designer of CLOS.
<mattam>
yeah, sure :)
<mattam>
but he worked on it ?
<Riastradh>
I dunno, maybe.
* Riastradh
doesn't know much about the history of CLOS.
systems has joined #ocaml
karryall has quit [Read error: 104 (Connection reset by peer)]
systems has quit ["Client Exiting"]
__DL__ has quit [Remote closed the connection]
jdrake has joined #ocaml
jdrake has quit [Read error: 104 (Connection reset by peer)]
croesus has left #ocaml []
buggs|afk has joined #ocaml
buggs has quit [Nick collision from services.]
buggs|afk is now known as buggs
noway has joined #ocaml
Xcalibor has quit [orwell.freenode.net irc.freenode.net]
smkl has quit [orwell.freenode.net irc.freenode.net]
brwill_work has quit [orwell.freenode.net irc.freenode.net]
ez4 has quit [orwell.freenode.net irc.freenode.net]
lus|wazze has quit [orwell.freenode.net irc.freenode.net]
Riastradh has quit [orwell.freenode.net irc.freenode.net]
rox has quit [orwell.freenode.net irc.freenode.net]
whee has quit [orwell.freenode.net irc.freenode.net]
buggs has quit [orwell.freenode.net irc.freenode.net]
noway has quit [orwell.freenode.net irc.freenode.net]
polin8 has quit [orwell.freenode.net irc.freenode.net]
teratorn has quit [orwell.freenode.net irc.freenode.net]
Maddas has quit [orwell.freenode.net irc.freenode.net]
wax has quit [orwell.freenode.net irc.freenode.net]
avn has quit [orwell.freenode.net irc.freenode.net]
Smerdyakov has quit [orwell.freenode.net irc.freenode.net]
Hipo has quit [orwell.freenode.net irc.freenode.net]
lam has quit [orwell.freenode.net irc.freenode.net]
srv has quit [orwell.freenode.net irc.freenode.net]
cm has quit [orwell.freenode.net irc.freenode.net]
noway has joined #ocaml
buggs has joined #ocaml
ez4 has joined #ocaml
lus|wazze has joined #ocaml
Xcalibor has joined #ocaml
polin8 has joined #ocaml
smkl has joined #ocaml
Hipo has joined #ocaml
Riastradh has joined #ocaml
teratorn has joined #ocaml
rox has joined #ocaml
brwill_work has joined #ocaml
whee has joined #ocaml
Maddas has joined #ocaml
wax has joined #ocaml
lam has joined #ocaml
avn has joined #ocaml
cm has joined #ocaml
srv has joined #ocaml
Smerdyakov has joined #ocaml
mattam_ has joined #ocaml
mattam has quit [Remote closed the connection]
jdrake has joined #ocaml
lam has quit [Read error: 60 (Operation timed out)]