Yurik changed the topic of #ocaml to: http://icfpcontest.cse.ogi.edu/ -- OCaml wins | http://www.ocaml.org/ | http://caml.inria.fr/oreilly-book/ | http://icfp2002.cs.brown.edu/ | SWIG now supports OCaml| Early releases of OCamlBDB and OCamlGettext are available
Kinners has joined #ocaml
skylan has quit [Read error: 104 (Connection reset by peer)]
skylan has joined #ocaml
foxen5 has quit [Read error: 104 (Connection reset by peer)]
Kinners has quit [Remote closed the connection]
foxen5 has joined #ocaml
mattam has quit ["nuit"]
mrvn_ is now known as mrvn
<mrvn> ourely functional programs can just simulate callcc with closures.
<mrvn> s/ourely/purely/
<Riastradh> Indeed they can.
systems has joined #ocaml
systems has left #ocaml []
lament has joined #ocaml
TimFreeman has joined #ocaml
<TimFreeman> The ocaml grammar says that <> and <..> are valid type expressions. I don't think ocaml really takes them. Are they useful in some context I don't understand?
<whee> erm, I'm not aware of those
<TimFreeman> Well, <x:int,..> is the type that has all objects with at least a method x. So I suppose <..> would be all objects, and <> would be all objects with no methods.
<TimFreeman> But I can get ocaml to parse "let x (y: <x:int;..>) = 3" but not "let x (y: <..>) = 3" or "let x (y: <>) = 3".
<whee> hrrrm
<TimFreeman> So I think they're just wrong, but it seems weird enough that I'm looking for a sanity check before I throw another bug at them. (This would be my third today...)
<whee> well, that one's entirely new to me :)
<mrvn> mee too
<whee> I don't use the OO at all, though
<whee> which is probably why I never knew
<mrvn> What should (y:<>) be anyway? An object without method seem pretty useless.
Kinners has joined #ocaml
<mrvn> Wouldn't that just be let x _ = 3?
<whee> I'm looking at the camlp4 parser and trying to figure out what it's doing
<whee> hah
<TimFreeman> Well, it wouldn't be any more useful than "let x _ = 3", so far as I can tell, but it would be different because 4 is an int and matches _ but it's not an object that would match y:<>.
<whee> TimFreeman: try let x (y:< >) = 3
<Kinners> whee: still trying to sort out that bf parser?
<whee> Kinners: no, that works :)
<whee> attempting to figure out how ocaml's handling this <bloop doop;..> syntax
<mrvn> TimFreeman: <> is structural unequal. That gets converted into a single token. < > would be two tokens.
<TimFreeman> Hey, whee's right when he msg'd me. let x (y: < >) = 3 works. Thanks.
<whee> # value x (y:< .. >) = 3;
<whee> value x : < .. > -> int = <fun>
<mrvn> Same problem as with 1 =!int_ref
<whee> it's the spacing, then
<mrvn> # let (<..>) = fun x y -> true;;
<mrvn> val ( <..> ) : 'a -> 'b -> bool = <fun>
<mrvn> <..> is an infix operator.
<mrvn> The tokeniser converts it too.
<mrvn> Whats the difference between < x:int > and < x:int;.. >?
<TimFreeman> If an object has a method x with type int and a method y with type char, it's in the second but not the first.
<whee> the type of an object is defined by the methods it has
<mrvn> How does that work? Does it generate a proper virtual tabel and passes that along to the function?
<mrvn> I mean the various methods x could be anywhere inside th objects getting passed, how does it know what to call?
<TimFreeman> Well, I'm sure it's all compiled using type erasure. The type doesn't influence method dispatch.
<mrvn> Is there something equivalent for records?
<TimFreeman> I don't think you get subtyping on records.
<mrvn> I have two records both of which have a next field. Would be great to have a function that could follow the next filed of both records.
<TimFreeman> I think you'd have to promote them to objects to do that.
<TimFreeman> There is a performance hit. I never measured it, though.
<whee> you could get away with polymorphic variants too
<mrvn> yeah, or pass a "next:'a->'a" closure
<mrvn> or with functors.
<TimFreeman> whee: I don't understand the proposed scheme with polymorphic variants. They let you say it's this or that, but mrvn wants to say the object has a next field *and* something else. Can you give more details?
<mrvn> actually, yeah, how do you do it with variants?
<whee> TimFreeman: you can have two polymorphic variants with the same constructor name but different data
<mrvn> you can?
<whee> and using match and #typename do a form of subtyping
<whee> yes
<mrvn> typename?
<TimFreeman> whee: Ya, keep going, I don't see how that helps you yet.
<TimFreeman> Not yet...
<TimFreeman> Um, is this paper saying you can do something clever in ocaml, or saying that you could make some language other than ocaml in which you could do something clever?
<TimFreeman> Never mind. The answer became clear after reading the first 1.5 pages.
<mrvn> I read the examples but I couldn't find any variants with different constructors with the same name.
<whee> mrvn: look at mixev.ml
<whee> they happen to use `Var with the same data, but you don't have to
<TimFreeman> I'm afk for a bit...
<mrvn> type var = [`Var of int];;
<mrvn> let value = function `Var x -> x | _ -> 0;;
<mrvn> type var2 = [ `Var of float ];;
<mrvn> # value (`Var 1.);;
<mrvn> This expression has type [> `Var of float] but is here used with type
<mrvn> [> `Var of int]
<mrvn> Doesn't work with different constructors. The new one just shadows the old one.
<whee> you have to handle them separately
<mrvn> like so?:
<mrvn> # let value = function `Var (x:int) -> x | `Var (x:float) -> 0 | _ -> 0;;
<mrvn> This pattern matches values of type [? `Var of float]
<mrvn> but is here used to match values of type [? `Var of int]
<whee> eeh
<whee> I thought it worked using #
<mrvn> Where is # descirbed?
<whee> I could be wrong
<pattern_> what is syntactically wrong here -> http://www.rafb.net/paste/results/Uv309236.html ? i am getting a "Parse error: 'and' or 'in' expected (in [expr])" on line 24, characters 0-3
<whee> I thought it worked, though :\
<whee> pattern: you're missing an in on line 24
<whee> heh
<whee> that semicolon after exit 0 looks bad
<whee> although that's probably not it
<mrvn> # let value = function #var -> 0 | #var2 -> 1;;
<mrvn> This pattern matches values of type [? `Var of float] = [? `Var of float]
<mrvn> but is here used to match values of type [? `Var of int] = [? `Var of int]
<whee> nuts
<pattern_> whee, i don't think it's the in on line 24, because this works:
<pattern_> let main () = print_string ""
<pattern_> let _ = if !( Sys.interactive ) then () else main ()
<whee> oh
<pattern_> and removing the semicolon after exit 0 doesn't help either
<whee> you've got a semicolon in reverse_list that shouldn't be there
<mrvn> line 12 has an extra ;
<whee> and this is one of the reasons I like the revised syntax ;p
<pattern_> whee, why shouldn't that semicolon be there?
<whee> why should it?
<mrvn> pattern_: because then the "let main" isn't a toplevel let anymore
<pattern_> because it ends the statement? or am i still stuck in c-land?
<whee> ; in ocaml continues a sequence of statements
<TimFreeman> The grammar says you can have two or zero semicolons between toplevel let's.
<mrvn> pattern_: no, ; doesn't end a statement, it creates a sequence of statements.
<whee> you only use it in begin .. end blocks or do {}
<pattern_> timfreeman, that's weird
<mrvn> # let a = 1;2;3;;
<mrvn> Warning: this expression should have type unit.
<mrvn> Warning: this expression should have type unit.
<mrvn> val a : int = 3
<TimFreeman> I agree with mrvn I guess. It's expecting an "in" after the let after the semicolon because the semicolon creates a sequence.
<mrvn> 1;2;3 is a sequence evaluation to1, then 2, then 3 discarding 1 and 2.
<mrvn> pattern_: just reindent the "let main" line. With the ; it should get indented to the match case.
<pattern_> whichh ; ?
<mrvn> line 12
<pattern_> isn't main a toplevel function, though?
<mrvn> no
<pattern_> no?
<whee> not with the semicolon
<mrvn> let rec reverse_list = function
<mrvn> [] -> "\n"
<mrvn> | x::xs -> print_string ( reverse_list xs ) ;
<mrvn> let main () =
<pattern_> but i don't want that
<whee> also, I don't think your code works anyway
<whee> heh
<mrvn> let main is part of the "| x::xs ->"
<pattern_> yeah, but that's another story :P
<whee> you're inputting the string before the user even gets the prompt
<pattern_> i don't want main to be part of rever_list
<pattern_> :(
<pattern_> i had tried it a different way before... let me paste that
<mrvn> just kill that stupid ;
<mrvn> And your reverse lists will just print \n
<pattern_> in here the prompt should come up before i input the string, right?
<mrvn> the main is better, line 12 still has ;
<pattern_> yeah, i'll take out hte ; in line 12 (this is a paste of an older version of my prog)
<pattern_> i'm just curious as to why main is part of reverse_list
<mrvn> This expression has type unit but is here used with type string
<mrvn> You reverse_list is buggy also.
<pattern_> yeah, i know
<pattern_> one thing at a time, though :P
<pattern_> i want main to be a toplevel function that calls reverse_list
<mrvn> and the ; after exit is also bogus
<pattern_> yeah, whee pointed that out too... it'll be gone in my next revision
<mrvn> # main ();;
<mrvn> Please enter a string to reverse: bla
<mrvn> Works fine once you fix the bugs.
<pattern_> yeah, i tried it, i know it works now
<pattern_> i just want to understand why you said that main isn't a toplevel function, and how i can make it one
<mrvn> Allway try to test a function before writeing the next.
<mrvn> +s
<pattern_> i did try to do that, but i got nowhere :(
<pattern_> i knew there was a problem with reverse_list, but i couldn't figure out what
<pattern_> now i see the ;s are the culprits
<TimFreeman> whee: Going back to the polymorphic variant issue, after reading the paper I still don't see how it's a plausible substitute for objects. In fact, they seem very much the opposite of objects. Objects let you extend ...
<TimFreeman> something to have the old stuff and new stuff, and poly. variants let you have the old stuff or new stuff.
<mrvn> TimFreeman: Polymorphic variants lets you extend a enumeration type.
<mrvn> type player = `X | `O
<mrvn> type field = `X | `O | `Block | `Empty
<mrvn> Now you can write a function that can pretty-print a field and a player.
<mrvn> <x:int; ..> would require some interface or losures without objects I think.
<mrvn> s/losures/closures/
<TimFreeman> mrvn wanted to have a "next" method that worked on a variety of things, right?
<mrvn> yes
<TimFreeman> So you want enough information to compute a next whatever, *and* some other useful data in addition. Poly variants say your object can be whatever *or* something else in addition. I don't see how poly variants help you with ...
<TimFreeman> the next method.
<TimFreeman> Is anyone still saying they would?
<mrvn> they don't afaik
<TimFreeman> Okay, I guess I misunderstood the context of the conversation then.
<mrvn> someone suggested they coudl but I don#t see how eigther.
<mrvn> How do you use a signature?
<mrvn> module type X_ABLE =
<mrvn> sig
<mrvn> type
<mrvn> val x : unit -> int
<mrvn> end;;
<mrvn> type x_able = X_ABLE;;
<mrvn> let foo (x:x_able) = x.x ();;
<mrvn> -type
<TimFreeman> You'll lose when compiling "type x_able = X_ABLE". Functors aren't first class values.
<mrvn> Unbound record field label x
<mrvn> How do I write a function that takes a X_ABLE and calls its x() function?
<TimFreeman> But X_ABLE is a module type, not a type. There isn't any value with type X_ABLE.
<TimFreeman> Oh. What's with the word "type" after "sig"?
<TimFreeman> What did you mean there?
<mrvn> wrong cut&paste
<TimFreeman> If I delete the "type" after "sig", I can define the module type X_ABLE, but then I still don't know what you meant to do with it.
<TimFreeman> You'll need a structure, then you can forget information about your structure by casting it to the module type.
<mrvn> I want to call x()
<mrvn> module X1 =
<mrvn> struct
<mrvn> let x () = 1
<mrvn> end;;
<mrvn> like that?
<TimFreeman> Yes, then you can do X1.x ().
<mrvn> But that wouldn#t use the X_ABLE signature.
<mrvn> module X2 =
<mrvn> struct
<mrvn> let x () = 2
<mrvn> end;;
<mrvn> The function should call X1.x or X2.x depending on what the argument realy is.
<mrvn> That would be like <x:int>
<TimFreeman> Modules don't change their value at run time. You need to make a functor to do what you want.
<TimFreeman> I used to know how to write functors in SML. Lemme think for a bit...
<mrvn> Thought so.
<TimFreeman> Here we go:
<TimFreeman> module X1 =
<TimFreeman> struct
<TimFreeman> let x () = 1
<TimFreeman> end;;
<TimFreeman> module X2 =
<TimFreeman> struct
<TimFreeman> let x () = 2
<TimFreeman> end;;
<TimFreeman> module type X_ABLE =
<TimFreeman> sig
<TimFreeman> val x : unit -> int
<TimFreeman> end;;
<TimFreeman> module ANY_X(X:X_ABLE) = struct
<TimFreeman> let z = X.x ();
<TimFreeman> end;;
<TimFreeman> module Z1 = ANY_X(X1);;
<TimFreeman> Z1.z;;
<TimFreeman> module Z2 = ANY_X(X2);;
<TimFreeman> Z2.z;;
<TimFreeman> But I haven't needed to write a functor in ocaml yet.
<mrvn> Thats not a functor yet is it?
<TimFreeman> ANY_X is a functor.
<TimFreeman> A functor is a module that takes module arguments.
<TimFreeman> IIRC they can take type arguments too.
<mrvn> module Set =
<mrvn> functor (Elt: ORDERED_TYPE) ->
<mrvn> Thats how they do functor in the manual.
<TimFreeman> That works too. I think this is equivalent to the ANY_X1 I wrote above:\n module ANY_X1 =
<TimFreeman> functor (X:X_ABLE) -> struct
<TimFreeman> let z = X.x ();
<TimFreeman> end;;
<TimFreeman> Oops, s/ANY_X1/ANY_X/.
<TimFreeman> What do you want to do with this? I have doubts that anyone really needs to use functors in ocaml, since I haven't needed to yuet.
<mrvn> let z = X.x;
<mrvn> end;;
<mrvn> module ANY_X(X:X_ABLE) = struct
<mrvn> let z = X.x;
<mrvn> end;;
<mrvn> let z_list = [ Z1.z; Z2.z];;
<TimFreeman> The new ANY_X shadows the old one, but it doesn't change Z1 or Z2. They still see the old one unless you type them in again.
<mrvn> # List.map (fun x -> x ()) z_list;;
<mrvn> - : int list = [1; 2]
<mrvn> ANY_X would be like <x:int> or <x:int;..>
<mrvn> I think you can do everything with modules that you can do with objects.
<TimFreeman> Sort of. I suppose that's why I wrote functors in SML: no objects.
<mrvn> food calls.
<TimFreeman> Okay, bye for now then. Think about this while eating: objects exist at run time but not functors.
TimFreeman has quit ["ircII/tkirc"]
<pattern_> i finally figured out my string reversing program
<pattern_> yay!
<pattern_> programming by trial and error sucks, though... wish i knew what i was doing
lament has quit [Remote closed the connection]
steele has quit ["ircII EPIC4-1.1.2 -- Are we there yet?"]
<mrvn> pattern_: let str_rev s = let length = String.length s in let r = String.create length in for i = 0 to length-1 do r.[length-1-i] <- s.[i]; done; r;;
<mrvn> # str_rev "Hallo, world!";;
<mrvn> - : string = "!dlrow ,ollaH"
Kinners has left #ocaml []
<pattern_> mrvn, cool! i was just going to ask how i could have better written that
lament has joined #ocaml
polin8 has quit [Read error: 54 (Connection reset by peer)]
polin8 has joined #ocaml
<mrvn> Too bad strings don't have String.init
<pattern_> well, it would be easy to write one, wouldn't it?
<mrvn> yes but thats extra code.
<pattern_> speaking of which, check out: http://pauillac.inria.fr/~aschmitt/cwn/2003.02.25.html
<pattern_> in section 2, "OCaml standard library improvement"
<mrvn> I think that Array and String should have nearly the same interface. String basically being a special cahse of an array (char array but in compackt form)
<pattern_> yeah, definately
<mrvn> neigther
foxen5 has quit [Read error: 110 (Connection timed out)]
<pattern_> :(
<mrvn> They don't even realy solve the problem.
<pattern_> no?
<mrvn> state whether the string contains any spaces
<mrvn> thats a bool
<pattern_> yeah
<pattern_> but i did more!
<mrvn> you are counting how many
<pattern_> i could have easily added a conditional
<pattern_> if ( spaces != 0 )
<pattern_> or, i could have had the empty list pattern default to false, and then modify it based on whether there were spaces
<pattern_> so why are the indenting styles wrong?
<mrvn> let rev_print_space s = List.fold_right (fun x accu -> print_char x; if x = ' ' then true else accu) s false;;
<mrvn> val rev_print_space : char list -> bool = <fun>
<mrvn> # rev_print_space ['H';'a';'l';'l';'o'];;
<mrvn> ollaH- : bool = false
<mrvn> # rev_print_space ['H';'a';'l';'l';'o';' ';'w';'o';'r';'l';'d'];;
<mrvn> dlrow ollaH- : bool = true
<mrvn> pattern_: if a
<mrvn> then b
<mrvn> else c
<mrvn> let space ...
<mrvn> print_char x;...
<mrvn> or even
<mrvn> let spaces = ...
<mrvn> in
<mrvn> print_char ....
<mrvn> Just use xemacs + tuareg-mode and indent with <tab>
<pattern_> not possible
<mrvn> why?
<pattern_> vim
<mrvn> vim sucks and that indentation even more
<pattern_> but i can set up vim to do the same, once i figure out what the correct style is
<pattern_> well, z2401357 is what feels natural to me, and My455085 is what it looks like once i ran my code through camlp4o pr_o.cmo
<pattern_> ignoring the explode function, which i didn't write
<mrvn> let opens an implicit begin, everything after that should be indented more.
<pattern_> let rec reverse_list =
<pattern_> function
<pattern_> is that what you mean?
<mrvn> for example. But I tend to write let foo = function \n
<pattern_> yeah, that's how i wrote it too
<pattern_> camlp4o was the one that put function below the =
<pattern_> maybe i could tweak camlp4o's rules to match my own indenting style... but maybe i should just learn its style, if that's what everyone uses
<mrvn> I don't use it
<pattern_> i used camlp4o on the ocaml examples code, which was horribly indented
mattam has joined #ocaml
<pattern_> but i don't like how camlp4o puts everything so much on one line, like in line 16 of My455085
<pattern_> that same code takes five lines in my style, but i think it's more readable
foxen5 has joined #ocaml
xxd_ is now known as xxd
TrOn has quit [Read error: 110 (Connection timed out)]
chrisb has left #ocaml []
<pattern_> i'm using input_char to read input, but it seems like my program is waiting until i hit ENTER to read the input
<emu> blame UNIX!
<pattern_> :(
<emu> you need to fiddle with terminfo
<emu> tc_setattr
<pattern_> ahh
<emu> um
<emu> turn CANONICAL mode off, I think
<pattern_> stty
<emu> tc_setattr is a C function
* emu highly encourages everyone to BLAME UNIX
<pattern_> si :)
<pattern_> so there's no tc_setattr equivalent in the ocaml libraries?
<emu> I dunno
<emu> might be
<pattern_> ok, i'll look
<emu> it seems plausible
<pattern_> will report biab
<emu> mind you, you are turning off input buffering
<pattern_> yep
<emu> all OS support for that
<emu> just so you nkow
<pattern_> i'll turn it back on after i'm done reading my input
<emu> if you don't, you'll be fined
<pattern_> ok, i pay for breaking invisible laws with invisible money :)
<pattern_> tcsetattr is in the unix module, wouldn't you know
foxen5 has quit [Read error: 104 (Connection reset by peer)]
foxen has joined #ocaml
<pattern_> what's the difference between stdin and Unix.stdin ?
<pattern_> cool! it worked :)
<pattern_> thanks, emu!
<mrvn> stdin is a channel, Unix.stdin is Filedsecriptor
<pattern_> what is the difference between channels and filedescriptors?
<mrvn> type and functionality
<pattern_> what section of the manual do you think might have more information on channels?
lament has quit ["Did you know that God's name is ERIS, and that He is a girl?"]
<mrvn> Index of values -> stdin
xxd has quit ["EOF"]
<pattern_> type in_channel
<pattern_> The type of input channel.
<pattern_> val stdin : in_channel
<pattern_> The standard input for the process.
<pattern_> that's all it seems to have
<mrvn> scroll up and down there.
<pattern_> i see, so channels can be used with all of these functions in pervasives
<pattern_> you know, this ocaml stuff is starting to make some sense :)
xxd has joined #ocaml
TrOn has joined #ocaml
mrvn has quit ["Lost terminal"]
mrvn has joined #ocaml
<mrvn> re
TrOn has quit [Read error: 60 (Operation timed out)]
jcore has quit ["leaving"]
TachYon26 has joined #ocaml
mellum has quit [Read error: 110 (Connection timed out)]
mellum has joined #ocaml
TachYon26 has quit ["bez ki³y nie ma zaliczenia (z prawd studentek AM)"]
polin8 has quit ["Lost terminal"]
polin8 has joined #ocaml
AmRitA has joined #ocaml
AmRitA has left #ocaml []
chrisb has joined #ocaml
Rhaaw has quit [Read error: 104 (Connection reset by peer)]
Rhaaw has joined #ocaml
TachYon26 has joined #ocaml
foxen has quit [Connection timed out]
TachYon26 has quit ["bez ki³y nie ma zaliczenia (z prawd studentek AM)"]
mattam_ has joined #ocaml
chrisb has quit [Read error: 104 (Connection reset by peer)]
mattam has quit [Read error: 110 (Connection timed out)]
chrisb has joined #ocaml
redcrosse has joined #ocaml
lam has quit [Read error: 104 (Connection reset by peer)]
lam has joined #ocaml
docelic has quit ["later"]
<whee> hooray, ocaml CVS has some feature I don't understand
<mellum> what?
<whee> yes
<whee> - Introduction of a new kind of data types: the virtual data types.
<mellum> Uh-huh.
<whee> Virtual types are intended to modelize non free algebraic types that must verified semantic relations that were not enforceable in previously available Caml data types.
<whee> I'll attempt to figure it out and put a demo somewhere ;)
<mellum> Doesn't sound like one would need it very often...
<whee> well, I'm sure it's useful
<whee> hopefully they wouldn't go adding things like that which aren't
<mellum> I use a small subset of the language only anyway...
<whee> well that's interesting
<whee> I can't see any included tests for this
<whee> also looks like it's not supported in camlp4 yet :\
<whee> I could probably add it if I knew what the syntax was, heh
<whee> # type pie = virtual A of int;;
<whee> type pie = virtual A of int
<whee> # A 3;;
<whee> One cannot create values of the virtual type pie
<whee> mmmkay
<whee> well I can't figure out how they work :p
<mellum> Probably only usable for deriving frim?
<whee> the CHanges file says you heed to use some special purpose functions to create them
<whee> but I don't know what to do with that, they'd have to be user specified functions
<mellum> Hmm, is there anything useful new in CVS? ;)
<whee> lots
<whee> some Arg module improvments, printf/scanf have more formats
<whee> and the usual bug fixing
<whee> plus a couple features I don't understand :)
<whee> oh well
<whee> I just hope they keep extending the type system like this, even if I don't know what some of the extensions are :P
<whee> if ocaml had a type system like haskell, it'd completely own
<whee> but this current one seems like it'll be useful in places where you would normally use an object and some get/set methods in an OO language
<whee> instead of going through all of that to store some data, you can just use a type
foxen5 has joined #ocaml
two-face has joined #ocaml
two-face has quit [Client Quit]
CyHawk has joined #ocaml
<CyHawk> hi
<CyHawk> i am going to learn ocaml soon. i have some experience learning languages, but if you can provide me with some brilliant but not obvious pointers, please go ahead!
<Smerdyakov> Don't try to read OCaml code as C code? =)
<CyHawk> i know a bit of sml and lisp, so i am not going to die from the shock of a functional language :)
<CyHawk> how much is it like sml?
<CyHawk> (i know i could just look at a piece of source, but where's the socializing then?)
<CyHawk> (and i'm tired a lot)
<Smerdyakov> It's like SML in every significant way, if you don't use OO stuff.
<CyHawk> i have to admit the code i write in sml or lisp shouts out loud i still think in a procedural way :(
<CyHawk> will practice help with it?
<Smerdyakov> Yes
<Smerdyakov> BTW: LISP SUX HAHA
<CyHawk> are there some special exercises?
<whee> haha
<CyHawk> hey, what's the matter with lisp??
<CyHawk> don't you respect age?
<Smerdyakov> Dynamic typing
<Smerdyakov> If you haven't seen the difference between ML and Lisp yet, then you don't know either of them at all. :P
<CyHawk> well, that might be true :)
<whee> I would go through the manual and the oreilly book
<CyHawk> i've written a total 1000 lines of code tops in them
<CyHawk> okay, i will
<CyHawk> lisp i had to start programming in without knowing anything about it... i have unfortunately missed the first class :)
<CyHawk> and i was taught sml and prolog by the authors of a prolog interpreter, so they concentrated more on prolog
<CyHawk> but now, the time has come, i will learn ocaml! :)
Rhaaw has quit [Read error: 54 (Connection reset by peer)]
<Smerdyakov> Well, it sounds like you actually don't know functional programming after all.
<Smerdyakov> So be prepared for a hard time.
<CyHawk> :) okay, thanks
<CyHawk> why is it that hard?
<Smerdyakov> Don't ask me. It was easy for me to learn.
<Smerdyakov> But university students traditionally find first FP classes among the hardest CS classes.
<CyHawk> i kind of enjoyed the freshness of it
<CyHawk> also i see why it can be efficient (lazy things or what not)
<Smerdyakov> You've taken a course that concentrates on teaching functional programming?
<CyHawk> okay, i learn it and come back tomorrow, okay? :)
<CyHawk> it was called 'declarative programming' and talked about sml and prolog
<Smerdyakov> You said it focused on Prolog.
<Smerdyakov> Have you done much with higher order functions?
<CyHawk> map and the like?
<CyHawk> yes
<Smerdyakov> Have you done _much_? ;D
<CyHawk> no :)
<CyHawk> some
<Smerdyakov> OK, then be wary!
<CyHawk> we have learned how they work, but i don't have a lot of experience with them, you know
<Smerdyakov> Then you haven't learned functional programming. So don't expect much of a head start with OCaml.
<CyHawk> i probably haven't used just one or two of them in actual programming
<CyHawk> it's going to be easy...
<CyHawk> :)
<CyHawk> don't sounds so pessimistic :)
<Smerdyakov> It could be. How old were you when you started programming?
<CyHawk> er
<CyHawk> i didn't write longer programs than 10 lines until i was 9
<CyHawk> that's bad i guess
<CyHawk> but that's why i need to learn ocaml
<CyHawk> open up my mind a bit
<Smerdyakov> That's not too bad.
<Smerdyakov> I think you have a good chance of not having a hard time with it =)
<CyHawk> thanks!
<Smerdyakov> Here, cognitive science majors must take a functional programming class.
<Smerdyakov> I don't think they generally have done programming before uni.
<Smerdyakov> They tend to fail badly =D
<CyHawk> so... why do they want to learn cognitive science if they are not programmers?
<CyHawk> oh, they think it's like thinking?
<CyHawk> (i don't know that cognitive science is either:) )
<CyHawk> (but i hope i'm studying it)
<Smerdyakov> Oh, that's your major?
<CyHawk> it's called 'integrated intelligent systems'
<Smerdyakov> Interesting.
<Smerdyakov> Cog. Sci. is offered by the psychology department here.
<CyHawk> it's all about agents, cooperative didstributed systems, logical inference (fuzzy, neural nets), whatever
<CyHawk> oh
<Smerdyakov> That sounds more like what I'd call "Artificial Intelligence" in the USA>
<CyHawk> yes, yes
<CyHawk> what's the difference? :)
<Smerdyakov> Probably none. Someone in the Anglophone world will just understand you more quickly if you say "AI." =)
<CyHawk> :) i mean between AI and cog.sci?
<Smerdyakov> Well, there is AI that doesn't care about how much systems act like real humans, which is probably what you're studying.
<Smerdyakov> Cog. Sci. cares about understanding how people think.
<CyHawk> why?
<Smerdyakov> Why "why"? Why does physics mean what it does? =) These are just the meanings of the words in common usage.
<CyHawk> :)
<CyHawk> well there can be two reasons. we want to replicate the process in AI, and we want to manipulate human minds too
<CyHawk> also it is interesting to get to understand something so outstandingly brilliant as a human mind
<CyHawk> like mine :)
<CyHawk> do you think your mind could fully understand it's own workings?
<CyHawk> is it possible for an AI to be so sophisticated to understand its source code?
<CyHawk> (i guess the word 'understand' means nothing unfortunately)
<Smerdyakov> Not if it meets the conditions in Goedel's first Incompleteness Theorem.
<Smerdyakov> Which I personally don't think the human mind does, but some do. =)
polin8 has quit ["Now _that's_ a good cup of coffee."]
polin8 has joined #ocaml
<CyHawk> i was taught Goedel's theorem, but i would need to read the complete proof of it to _understand_ it -- which is a bit too lengthy and speckled with german words
polin8 has quit [Client Quit]
polin8 has joined #ocaml
<Smerdyakov> Yes, I took a whole class that led up to it. =)
<CyHawk> it was just mentioned to me in a class entitled 'artificial intelligence' :)
<Smerdyakov> You should take mathematical logic classes. They're easy if you know functional programming ;D
<CyHawk> oh, i took a class that was called 'mathematical logic' :)
<CyHawk> it was a joke
<CyHawk> the only new notion introduced were quantors
<CyHawk> still many have found it hard to pass, i have no idea why
<CyHawk> i find it attractive to learn all kinds of higher mathematics, but i'm not so smart as to do it without any effort, and i think there are areas where my efforts are more rewarding...
<CyHawk> maybe once i get old and all my short term goals are accomplished, i will go to a maths university :)
<CyHawk> oh, what would be a good first program to write in ocaml?
<CyHawk> it can't be a game, can it? :)
<whee> if you want
<whee> there's lablgtk and labltk or lablgl which you could use, depending on what kind of game
<CyHawk> i've seen there is an sdl wrapper for ocaml?
<whee> yes, there is
<CyHawk> well, lets make it a 3d mmorpg :)
systems has joined #ocaml
systems has quit ["Client Exiting"]
foxen5 has quit [Read error: 104 (Connection reset by peer)]
foxen has joined #ocaml
two-face has joined #ocaml
two-face has left #ocaml []
<CyHawk> bye!
CyHawk has quit []
polin8 has quit ["Now _that's_ a good cup of coffee."]
polin8 has joined #ocaml
pattern_ has quit ["..."]
pattern_ has joined #ocaml
polin8 has left #ocaml []
det has joined #ocaml
<det> what is the operator to prepend to a list ?
<Riastradh> ::
<det> thanks
<det> erm, I meant combine 2 lists in the most efficient manner, order being unimportant
<Riastradh> Oh.
<Riastradh> I dunno.
<det> functions using labels _have_ to be called using labels ?
* Riastradh knows not.
<det> what good are you ;)
<whee> you need to use the label, yes
<det> that's no good
<whee> I think
<whee> now I think you don't if the function is entirely applied
<whee> yeah, you don't if you do a full application
<det> Expecting function has type ?bpp:int -> w:int -> h:int -> Sdlvideo.surface
<det> This argument cannot be applied without label
<det> that si with full application :/
redcrosse has quit ["Client exited"]
<det> wonder why the error doesnt mention the flag list argument
<whee> optional arguments need the label
<whee> now I can't remember the rules
<whee> heh
<det> oh
<whee> if you have a function taking all labeled arguments, and an optional, you need to use labels
<det> ?bpp:int means optional ?
<whee> yes
<det> well, that makes sense
<det> whee, any idea how to append or prepend on list to another ?
<whee> you can use @ to combine lists
<whee> slowish, though
<det> that's ok, it is for SDL flags, no other solution
<det> ocamlsdl doesn't let you or masks
<det> requires a list of flags
<det> O(n) isnt too bad
<whee> for small lists, it's good
<det> one last thing, how do you suply to optional argumentin a function,"?bpp=0" ?
<whee> ?bpp:0
<det> ahh, thanks
<det> classes can take optional arguments too ? gives me a syntax error
<whee> yeah, they can
<det> neat, 7 lines to open an OpenGL context and wait for window to be closed
* whee can do it in 0
<whee> of course, not ocaml :)
<det> I have a new lossy compression technique that can compress all information to 0 bits!
<det> ocaml would be so cool if it supported type classes :)
<det> and ditched it's current OO stuff :)
<whee> I'm hoping the type system is eventually just like haskell's
<whee> with both OO and that, there's no way it could get better :P
<det> well, maybe continuations ;)
<whee> they added some "virtual data type" today in CVS, but I don't know how to use them
<whee> basically types where construction is done with functions, so you can enforce invariants
<det> hrmm
<whee> all I can figure out how to do is declare a type as virtual
<whee> haven't figured out the construction part yet :\
<det> "enforce" variants ?
<det> s/va/inva/
<whee> well, say you had a constructor A of int and wanted to enforce that the int was always in the range 0-100
<det> what are the chances of ocaml ever having type classish stuff ?
<whee> instead of doing checks in all functions handling this type, you just make sure that it's never constructed with a value outside of that range
<det> ohh
<det> that's useful
<whee> and there's no way to work around it, since you can only construct inside a function which will check the value
<whee> but I haven't figured out the syntax for it yet; no tests test this in the tree :\
<whee> I doubt ocaml will get type classes
<whee> with the OO and all
<det> but, with the current OO stuff you can't have a Number class without a level of indirection
<det> any class using the generic number class would have to contain a float or inttype
<det> so you'd have to dereference it
<det> too slow
<det> unless ocaml has some way to have a int type accept #add 2 or something
TrOn has joined #ocaml
TrOn has quit [Client Quit]