vect changed the topic of #ocaml to: OCaml 3.07 ! -- Archive of Caml Weekly News: http://pauillac.inria.fr/~aschmitt/cwn, ICFP'03 http://www.icfpcontest.org/, 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
mimosa has quit ["I like core dumps"]
gim has quit ["dodo"]
mattam has quit [tolkien.freenode.net irc.freenode.net]
Smerdyakov has quit [tolkien.freenode.net irc.freenode.net]
wuuru has quit [tolkien.freenode.net irc.freenode.net]
lam has quit [tolkien.freenode.net irc.freenode.net]
mw has quit [tolkien.freenode.net irc.freenode.net]
Hadaka has quit [tolkien.freenode.net irc.freenode.net]
det has quit [tolkien.freenode.net irc.freenode.net]
brwill_work has quit [tolkien.freenode.net irc.freenode.net]
rt has quit [tolkien.freenode.net irc.freenode.net]
rt has joined #ocaml
mattam has joined #ocaml
Smerdyakov has joined #ocaml
mw has joined #ocaml
Hadaka has joined #ocaml
brwill_work has joined #ocaml
wuuru has joined #ocaml
det has joined #ocaml
lam has joined #ocaml
mattam has quit [tolkien.freenode.net irc.freenode.net]
wuuru has quit [tolkien.freenode.net irc.freenode.net]
lam has quit [tolkien.freenode.net irc.freenode.net]
Smerdyakov has quit [tolkien.freenode.net irc.freenode.net]
rt has quit [tolkien.freenode.net irc.freenode.net]
mw has quit [tolkien.freenode.net irc.freenode.net]
Hadaka has quit [tolkien.freenode.net irc.freenode.net]
det has quit [tolkien.freenode.net irc.freenode.net]
brwill_work has quit [tolkien.freenode.net irc.freenode.net]
rt has joined #ocaml
mattam has joined #ocaml
Smerdyakov has joined #ocaml
mw has joined #ocaml
Hadaka has joined #ocaml
brwill_work has joined #ocaml
wuuru has joined #ocaml
det has joined #ocaml
lam has joined #ocaml
malc has quit [Read error: 60 (Operation timed out)]
Kinners has joined #ocaml
<XolClaus> okay...
<XolClaus> This expression has type term but is here used with type term
<XolClaus> that's helfpul
<XolClaus> helpful*
<Kinners> are you using modules?
<XolClaus> no
<XolClaus> it complains at this:
<XolClaus> and parse_expression tokens =
<XolClaus> let t = parse_term tokens in
<XolClaus> Exp (t, parse_exp2 tokens)
<XolClaus> type exp = Exp of term * exp2
<XolClaus> and exp2 = Exp2 of addop * term * exp2 | ENull
<XolClaus> and term = Term of factor * term2
<XolClaus> and term2 = Term2 of mulop * factor * term2 | TNull
<XolClaus> are the types
<XolClaus> ah
<XolClaus> my first let didn't have a rec
<lms> can someone hook me up with the 3.07 ocaml win32 distro? :(
<teratorn> isn't it on the site?
<lms> yeah, but the site is dead, has been for like two days
<teratorn> install a proper OS then!
<teratorn> anything sensible will have packages for ocaml, and lots of mirror servers
<lms> oh hush :)
<teratorn> so you'll never be left out in the cold like Windows is prone to do ;)
<teratorn> poor lms
<lms> I figured it out, I got googles cache of the distrib page, and found a mirror: http://wwwfun.kurims.kyoto-u.ac.jp/soft/caml-light/ocaml-3.07
* lms is a genius ;D
<teratorn> you solved an unnecessary problem, horray! ;)
<Riastradh> Bah! Just get CVS!
<lms> now, to find a mirror of the manual =)
<lms> ahh, looks like it's on that .jp site =)
<XolClaus> okay
<XolClaus> tuareg says "syntax error" when I C-c C-b my buffer
<XolClaus> it has the 'ope' part of 'open Printf' (the very first statement) highlighted
<XolClaus> Okay...
<XolClaus> ocamlopt now says 'unbound constructor statement' on this line:
<XolClaus> type program = Program of assignment list * statement list
brwill_work is now known as brwill
brwill is now known as brwill_zzz
<XolClaus> Can someone tell me a quick/simple way to read an entire file into one string?
rt has quit ["ircII EPIC4-1.0.1 -- Are we there yet?"]
brwill_zzz has quit [Read error: 104 (Connection reset by peer)]
brwill has joined #ocaml
brwill is now known as brwill_zzz
Kinners has left #ocaml []
Herrchen has quit [Read error: 60 (Operation timed out)]
<smkl> XolClaus: let string_of_file fname = let ic = open_in fname in let len = (Unix.stat fname).Unix.st_size in let buf = String.create len in really_input ic buf 0 len; close_in ic; buf
<Maddas> Nice, gotta keep that around.
Herrchen has joined #ocaml
<wuuru> smkl: hi :-)
JX is now known as stir1balle
stir1balle is now known as stire1balle
gim has joined #ocaml
phubuh has joined #ocaml
<smkl> hello wuuru
<wuuru> smkl: we have not seen eachother a plenty of time, do you remember? :-)
<smkl> yes
<wuuru> :-)
<wuuru> smkl: have you done much with FP since then? :-)
<smkl> i don't remember. but i haven't done anything this year
<wuuru> neither have I :-)
mellum has joined #ocaml
<mellum> hi
<smkl> hello
__buggs has joined #ocaml
buggs|afk has quit [Read error: 60 (Operation timed out)]
Kinners has joined #ocaml
<wuuru> who knows about how dangerous is using -rectypes, i.e., why is it not enabled by default?
<wuuru> mellum: just had read it before asking the question :-)
<wuuru> mellum: are there any other precautions? :-)
<mellum> wuuru: I don't know, I never needed it
<wuuru> I need a type 'a t = 'a -> 'a t :-)
<mellum> Why?
<wuuru> and feel it to weird to define it as type 'a t = T of ('a -> 'a t) which is also allowed without -rectypes :-)
<wuuru> mellum: for modelling a finite-state automaton type fsa = char -> fsa
<wuuru> mellum: which is then used in the form let new_fsa_state = fsa_state 'a'
<mellum> Why can't you just have a function which takes a fsa and a char and returns another fsa?
<wuuru> too long :-)
<mellum> Try Perl, then :P
<wuuru> :-)
mimosa has joined #ocaml
<mellum> I guess in the time you wasted by now, you could have typed the longer version about 533 times :)
<wuuru> mellum: consider (((fsa 'a') 'b') 'c') 'd') and (f (f (f (f fsa 'a') 'b') 'c') 'd') -- which one looks more elegant eand easier to understand?
<mellum> I'd write a function fsa_chars ['a'; 'b'; 'c'] for that
<wuuru> :-)
<Demitar> wuuru, how do you bootstrap that type anyway? (I might have had too little sleep though.)
<wuuru> Demitar: let rec fsa1 c = match c with 'a' -> fsa1 | 'b' -> raise (FSA_FINAL fsa1);;
<wuuru> Demitar: this works with -rectypes :-)
<Demitar> Ah, rectypes would explain the typing madness. =)
<wuuru> :-)
<wuuru> a more complete example is
<wuuru> type fsa_state = char -> fsa and
<wuuru> fsa = FSA of fsa_state;;
<wuuru> exception FSA_FINAL of fsa_state;;
<wuuru> let rec fsa1 c = match c with 'a' -> FSA fsa1 | 'b' -> raise (FSA_FINAL fsa1);;
<wuuru> oops
<wuuru> not this one
<wuuru> this one is for working without -rectypes
<mellum> You are really willing to give up simplicity and performance for a minor syntactic advantage?
<wuuru> mellum: quite on the conrary, I fight for simplicity :-)
<Demitar> And if the syntactic advantage is all you want go use camlp4. ;-)
<wuuru> no, I want semantic simplicity too
<wuuru> what can be more simple than type fsa = char ->fsa ?
<Demitar> type fsa = char
<wuuru> Demitar: but this won't permit to implement a fsa :-)
<Demitar> I thought simplicity was the primary aspect. ;-)
<wuuru> :-) :-)
<Demitar> You can always use an object since it carries it's state with it.
<wuuru> of course
<wuuru> but I want a pure functional solution :-)
<Demitar> So use functional objects.
<wuuru> objects are not as simple as plain functions :-)
<Demitar> Then use -rectypes.
<wuuru> yes, this is what am thinking about :-)
<Demitar> Or wait! That's not simple enough! ;-)
<wuuru> how?
<wuuru> what is more simple? :-)
rox has quit ["Client exiting"]
karryall has joined #ocaml
rox has joined #ocaml
gene9 has joined #ocaml
gene9 has quit []
Kinners has left #ocaml []
carm has quit [Read error: 54 (Connection reset by peer)]
wazze has quit ["If we don't believe in freedom of expression for people we despise, we don't believe in it at all -- Noam Chomsky"]
__buggs has quit [Connection timed out]
phubuh has quit [Remote closed the connection]
clog has quit [^C]
clog has joined #ocaml
_JusSx_ has joined #ocaml
<_JusSx_> wuuru : heya
clog has quit [^C]
clog has joined #ocaml
gim|570 has joined #ocaml
dogee_home has joined #ocaml
buggs has joined #ocaml
karryall has quit ["go"]
systems has joined #ocaml
systems has left #ocaml []
dogee_home has quit ["..."]
mattam_ has joined #ocaml
mattam has quit [Read error: 110 (Connection timed out)]
det has quit [Connection timed out]
stire1balle has quit [Read error: 110 (Connection timed out)]
stire1balle has joined #ocaml
karryall has joined #ocaml
gim has quit ["++"]
mattam_ is now known as mattam
Hipo has quit ["leaving"]
_JusSx_ has quit ["[BX] Reserve your copy of BitchX-1.0c19 for the Nintendo Gameboy today!"]
XolClaus has quit [Read error: 104 (Connection reset by peer)]
malc has joined #ocaml
gim has joined #ocaml
malc has quit [Read error: 60 (Operation timed out)]