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 | OcamlBDB will be released soon
Begbie_ has joined #ocaml
Begbie_ is now known as Begbie
malc has quit ["no reason"]
<Arav> hm. Probably should have makred myself away
* Arav cackles, "Anyone else seen Purely Functional Data structures?"
<whee> dude I've been trying to contact you all day! my dinner is overcooked, my cat is starving, I haven't moved for hours, I still need to take outthe garbage, and I didn't get the mail
<whee> thanks a lot
<whee> :D
* Arav weeps in shame, "I'm so sorry! I will now light myself on fire in penance"
<whee> and I think I need to read that book. sounds interesting
<Arav> I just got it
* Arav cackles.
<Arav> mine all mine
<whee> they have it at the library here, but I found an online pdf :D
<Arav> but the book is MINE
<whee> pfft
<Arav> i hope to be doing grad work in this field
<Arav> and, I mean, I am not getting out of college with three books on imperitive data structures and none on functional
<whee> heh my college programming courses do nothing but remind me of how much I hate languages like c/c++/java for standard applications
<whee> I'm always reaching for map or filter or fold or something but it's just not there :
<Arav> I actually like c++ a lot... I learned on it, and is very cool in many ways.
<whee> my first language was c++ too
<Arav> soo much niver htan java
<Arav> jicer
<Arav> nicer
<whee> I just hate using it though
<whee> I'd kill to go to a university that taught ocaml
<whee> just so I could not have to jump back and forth between c++ with school projects and ocaml for my hobbies
<Arav> mine teaches it for some classes. I've had two classes in C++, oen in ocaml, one in lisp,
<whee> supposedly we have some smalltalk and lisp courses here, but I don't know which
<whee> I loved using lisp when I first picked it up
<Arav> *shudder* I hated it. It is very beautifull and mathematically pure, but I HATE using it
<Arav> I got to it after ocaml
<whee> I learned lisp before ocaml, it was one of the more functional languages I've used
<whee> (at that time)
<whee> learned ocaml after that, haven't touched any other languages unless I've been forced to :D
<Arav> Couldn't stand lisp.
<whee> heh
<whee> I was thinking of getting into scheme lately but I talked myself out of it :D
<Arav> ocaml is good enough fer me
<whee> that was pretty much my conclusion
<whee> there's nothing I can't do already
<Arav> well, that's true of basic
<Arav> I'd probably learn smalltalk (should for a class) and then haskell
<Arav> maybe eifel
<whee> I wanted to learn haskell but I couldn't get ghc going :\
<Arav> *grumbles* want easy way to play with ocaml interpreter
<whee> eh?
<Arav> want an easy way to get back what I've previously typed
<whee> you could use ledit in conjunction with the toplevel
<whee> ftp://ftp.inria.fr/INRIA/Projects/cristal/Daniel.de_Rauglaudre/Tools/
<Arav> aha
<whee> there should be more utilities that do things like this elsewhere
<Arav> *noddles*
<Arav> sweet. that's perfect
<Arav> ledit | ocaml, right?
<Arav> ledit ocaml works too
<mr_bubbs> whose wserver?
graydon has quit ["xchat exiting.."]
karryall_ has joined #ocaml
<mrvn_> I have a record with default settings default = { a=0; b=0; c=0;} and now I want variations of that like "default with { a = 2; }". Whats the syntax for that?
mrvn_ is now known as mrvn
<karryall_> mrvn: that's { default with a = 2 }
<mrvn> thx
Submarine has joined #ocaml
<Submarine> Wow. OCaml is awfully popular.
<mrvn> more and more so
Submarine has quit ["Client Exiting"]
xkb_ has joined #ocaml
<xkb_> hi
<xkb_> are there any reports/papers on the implementation of exceptions in ocaml?
Demitar has joined #ocaml
cleverdra has joined #ocaml
<xkb_> is ocaml lazy?
<cleverdra> no.
<xkb_> ah
<xkb_> ok
systems has joined #ocaml
ayrnieu has joined #ocaml
Yurik has joined #ocaml
smklsmkl has joined #ocaml
smkl has quit [Remote closed the connection]
<Yurik> re
smklsmkl is now known as smkl
<smkl> hi
Yurik has quit [Read error: 54 (Connection reset by peer)]
<xkb_> does ocaml have map build in?
<ayrnieu> List.map
<xkb_> ah.. thats why I could not find it :)
<xkb_> and prefix functions?
<xkb_> I want to do something like this:
<xkb_> map *somefunctionreturningint [1;2;3]
<ayrnieu> I don't know what that means, xkb.
<ayrnieu> (It's a syntax error; are you trying to mix C and OCaml syntax?)
<xkb_> perhaps
cleverdra has quit [Read error: 113 (No route to host)]
<xkb_> I just want to apply the function *3 to each element of a list
<xkb_> with *3 being "times 3"
<ayrnieu> List.map (*3) [1;2;3]
<xkb_> List.map (*mult_list[1;2;3;4]) [1;2;3;4];;
<xkb_> that returns nothing
<ayrnieu> Please stop that.
<xkb_> what? pasting
<ayrnieu> You'd do better to ask your questions in a natural language, I think. What is 'mult_list'?
<xkb_> a function that multiplies each element with the next.
<ayrnieu> Why do you say that it 'returns nothing'?
<ayrnieu> oh, oops.
<xkb_> I get a *
<xkb_> instead of a #
systems has quit ["Client Exiting"]
<ayrnieu> Yes, (* is a comment.
<xkb_> ahhh
<xkb_> that explains alot!
<ayrnieu> let mult x = x*3 in List.map mult [1;2;3]
* ayrnieu frowns.
<xkb_> so no prefix functions?
<ayrnieu> List.map (( * ) 3) [1;2;3]
<ayrnieu> You don't have to have the spaces with any other operator.
<ayrnieu> except for .* , that is
<xkb_> aha. thanks for the help
<xkb_> and all this just to figure out the exception handling
<xkb_> btw: how does ocmal handle heap and stack errors?
<ayrnieu> Also, I don't know what a 'prefix function' is.
<xkb_> a prefix function is a function in hongarian notation
<xkb_> operants in front of arguments
ayrnieu has quit [Read error: 104 (Connection reset by peer)]
<xkb_> like + 3 2 == 3 + 2
<smkl> isn't that polish notation
cleverdra has joined #ocaml
<xkb_> darn
<xkb_> youre right
<xkb_> wrong country
cleverdra has quit [Client Quit]
cleverdra has joined #ocaml
<cleverdra> I'd speak of 'curried functions', perhaps.
<cleverdra> Last thing I saw: <ayrnieu> Also, I don't know what a 'prefix function' is.
<xkb_> Does anyone here know how ocaml handles heap or stack errors?
<cleverdra> xkb - are you the person who asked about how Erlang handled exceptions?
<xkb_> yes :)
<xkb_> Im now up to the next language :)
<xkb_> I just finished Erlang
<cleverdra> OK.
<xkb_> not really satisfied yet though.. The details are still quite unclear to me
<xkb_> and so far, the ocaml implementation seems much more "natural" to use
<cleverdra> Satisfied with what?
<smkl> xkb_: it will throw an exception, except in native code stack error, in which case it will just crash i think
<xkb_> satisfied by what I wrote
<xkb_> smkl: aha.. that is comparable to Erlang behaviour
<cleverdra> xkb - what alternative behaviors would you expect?
<xkb_> Out of what Ive read so far, I think there is no alternative behaviour
<xkb_> Its quite hard to back out of such errors
<xkb_> IE to continue computation in some way
<xkb_> every language I looked at sort of crashes on heap errors. Usually throwing some system exception in the process
<Demitar> The native version also raises Stack_overflow (just tested it).
<cleverdra> heap errors are something that should be dealt with on the OS side.
<Demitar> s/raises/throws/ (too much python)
<Demitar> Hmm, ocaml uses raise too. ;-)
<xkb_> Demitar: could you msg me the code you used?
<xkb_> so I can use it as an example
<Demitar> let aux x = x :: aux [] in aux []
<Demitar> Very simple. ;-)
<Demitar> oops, let rec aux I mean
<xkb_> thanks
<Demitar> Just make sure to keep some kind of allocation so you don't end up with something tail-recursive. ;-)
<xkb_> ahhhh.. recursion loops
<xkb_> hmm.. are there any other lazy functional programming languages besides clean and haskell?
graydon has joined #ocaml
<cleverdra> Miranda, I think.
<xkb_> Ill check that out
<smkl> xkb_: some, but they only have historical importance
<xkb_> Im esp. interessted in the exception mechanisms they use, if at all
<cleverdra> Haskell, at least, hask exception handling in the IO monad.
<xkb_> Haskell has exception handling
<xkb_> even general exception handling
<xkb_> anyway. Thank you all for the help.
<xkb_> I think im going to pay the library a visit now :)
xkb_ has quit ["I like core dumps"]
zack has joined #ocaml
<Demitar> Hello zack.
<zack> hi
* zack is away: I'm busy
systems has joined #ocaml
gl has joined #ocaml
Dalroth has joined #ocaml
cleverdra has quit ["Leaving"]
<systems> is there any web application frameworks writen for ocaml
<Demitar> There are the cgi interfaces of course.
<karryall_> see wdialog
systems has quit ["Client Exiting"]
Demitar has quit [card.freenode.net irc.freenode.net]
pnou has quit [card.freenode.net irc.freenode.net]
mr_bubbs has quit [card.freenode.net irc.freenode.net]
emu has quit [card.freenode.net irc.freenode.net]
lam has quit [card.freenode.net irc.freenode.net]
Demitar has joined #ocaml
mr_bubbs has joined #ocaml
lam has joined #ocaml
pnou has joined #ocaml
emu has joined #ocaml
systems has joined #ocaml
merriam has joined #ocaml
Demitar has quit ["Bubble OS"]
systems has quit [Read error: 104 (Connection reset by peer)]
zack has quit ["Client Exiting"]
Yurik has joined #ocaml
<Yurik> re
Dybbuk has joined #ocaml
<Yurik> Dybbuk: hi
<Dybbuk> Yurik: Howdy!
Yurik_ has joined #ocaml
Yurik has quit [Read error: 104 (Connection reset by peer)]
Yurik_ is now known as Yurik
Yurik has quit [Client Quit]
nerdlor_ has joined #ocaml
Yurik has joined #ocaml
Yurik has quit [Read error: 104 (Connection reset by peer)]
gl has quit [Read error: 113 (No route to host)]
gl has joined #ocaml
nerdlor_ has quit ["ChatZilla 0.8.10 [Mozilla rv:1.2b/20021016]"]
mrvn_ has joined #ocaml
Miwong has joined #ocaml
<Miwong> hello
<whee> hi~
<whee> acm presentations or whatever they call them are fun to read
<whee> got some nifty ideas for a program to write that'll do something related to parsing c++ and finding my stupid errors heh
mrvn has quit [Read error: 110 (Connection timed out)]
two-face has joined #ocaml
<two-face> hi
sfogarty has joined #ocaml
malc has joined #ocaml
<sfogarty> Ello
<malc> lo
<sfogarty> currendly fiddling with fifo's to try and replace ledit with vim :)
<malc> uh-oh
* sfogarty cackles.
mrvn has joined #ocaml
<two-face> do you have smart indentation with vim?
<sfogarty> arou?
<two-face> ?
<sfogarty> autoindent, you mean?
<two-face> yes
<sfogarty> usually, yes
<two-face> how do you trigger it?
<sfogarty> um, :set autoindent?
<sfogarty> will turn it on
<sfogarty> and :set noautoindent will turn it off
<two-face> ok
<two-face> let's try
* sfogarty is confused, "try what?"
<two-face> what is it meant to do?
<sfogarty> um, maintains tabbing between lines
<sfogarty> so, if I tab over 5 times on one line, and hit enter, I'm tabbed over five times already
<sfogarty> deletion works as expected
<two-face> hmm
mrvn_ has quit [Read error: 60 (Operation timed out)]
<two-face> bye
two-face has left #ocaml []
<sfogarty> is there an equivalent to sml's as in ocaml? something like let foo bar as x::xs =?
<malc> sure let foo (x::xs as moo) =
<sfogarty> er, (moo as x::xs) or (x::xs as moo?)
<sfogarty> the pattern for the name first?
<mrvn> Doesn#t that complain that it doesn't match all cases ([])?
<gl> x::xs as moo, and match moo with x::xs -> bla
<malc> mrvn: sure it will
<sfogarty> k. so I can do a let rec aux(list as x::y::xs) == aux(x+y)::list?
<sfogarty> (ignoring the fact that this doesn't end)
<sfogarty> (and single equal)
<gl> no
<gl> err, yes
<gl> :/
<sfogarty> er, sorry (x::y::xs as list)
<gl> that's the point
<sfogarty> gimmie sec, trying out
<gl> i understood this
<sfogarty> *grumbles* bad ledit, screwing up my inputs
<malc> # let rec aux (x::y::xs as list) = aux ((x+y)::list);;
<malc> Warning: this pattern-matching is not exhaustive.
<malc> Here is an example of a value that is not matched:
<malc> []
<malc> val aux : int list -> 'a = <fun>
<malc> # aux [1;2];;
<malc> Interrupted.
<sfogarty> the function doesn't actually work, it goes on forever
<malc> well duh
<sfogarty> was just an exmaple
<malc> sure it goes on
<malc> you are never exhausting the list
<mrvn> let rec aux = function [] -> () | x::xs as bar -> aux xs
<mrvn> That would be better
<sfogarty> I know.. was just seeing if syntax was right
<sfogarty> it' something like
<sfogarty> let fib n =
<sfogarty> let rec aux(list as x::y::xs) = function
<sfogarty> 0 -> x
<sfogarty> |_ -> aux (x+y)::list n-inin
<sfogarty> aux [0;1] (n-1);;
<sfogarty> let fib n =
<sfogarty> let rec aux(list as x::y::xs) = function
<sfogarty> 0 -> x
<sfogarty> |_ -> aux (x+y)::list n-1 in
<sfogarty> aux [0;1] (n-1);;
<sfogarty> er, wrong window
<mrvn> Thats pretty much an endless loop for fib 0
<sfogarty> yup
<mrvn> and also gives a result thats 1 off
<sfogarty> I'll get it to work first :)
<sfogarty> then fix it
<sfogarty> it thinks x has a type 'a list
<mrvn> and _ -> aux (list (x+y) x) (n-1) in would be better.
<sfogarty> is list a reserved word?
<mrvn> list makes a list of all its arguments
<mrvn> list a b c d == a::(b::(c::d))
<sfogarty> ah
<sfogarty> let fib n = function
<sfogarty> 0 -> 0
<sfogarty> |_ ->
<sfogarty> let rec aux(l as x::y::xs) = function
<sfogarty> 0 -> x
<sfogarty> |_ -> aux (x+y)::l n-1 in
<sfogarty> aux [0;1] (n-1);;
<mrvn> no
<sfogarty> nope
<sfogarty> doesnt' like x still
<mrvn> use aux [0;1] n;;
<sfogarty> doesn't like the (x+y)::l
<sfogarty> oh ! it doesn't like l
<sfogarty> ahhh. my as is not correct
zack has joined #ocaml
<mrvn> let fib n =
<mrvn> let rec aux (x::(y::xs) as l) = function
<mrvn> 0 -> x
<mrvn> |_ -> aux ((x+y)::l) (n-1) in
<mrvn> aux [0;1;] n;;
<whee> wouldnt it be easier to just use pattern matching to split the list up into elements
<sfogarty> nope, not right
<mrvn> but somehow it doesn't terminate for fib 2;;
<sfogarty> n is an outside varaible
<sfogarty> n is what fib takes in
<sfogarty> we need |s -> (s-1)
<mrvn> ah, jes. s/_/n/
<sfogarty> that'd work
<sfogarty> or not
<mrvn> let fib n =
<mrvn> let rec aux (x::(y::xs) as l) = function
<mrvn> 0 -> x
<mrvn> | n -> aux ((x+y)::l) (n-1) in
<mrvn> aux [0;1;] n;;
<mrvn> fib 2;;
<mrvn> - : int = 1
<sfogarty> now it works
<sfogarty> mmm. as is nice
<sfogarty> although it does complain
<sfogarty> well, let me try this
<mrvn> # let l = ref [] in for i = 10 downto 0; do l := (fib i)::!l done; !l;;
<mrvn> - : int list = [0; 1; 1; 2; 3; 5; 8; 13; 21; 34; 55]
<sfogarty> no, doesn't like that
<sfogarty> oh, there are smipler ways of doing fib
<mrvn> much simpler
<sfogarty> let fib n = let aux curN lastN = function 0 -&gt curn |_ -> aux curn+lastn curn n-2
<sfogarty> something like that
<sfogarty> let fib n = let rec aux curn lastn = function
<sfogarty> 0 -> curn
Miwong has quit ["."]
<sfogarty> |s -> aux curn+lastn curn s-1
<sfogarty> ;;
<sfogarty> but, anyway. next question. any way to define something like sml's fun merge(h, E) = h | merge (E, h) = h | merge(h1, h2) = foo
<mrvn> # let rec fib ?(curr = 0) ?(next = 1) = function 0 -> curr | n -> fib ~curr:next ~next:(next+curr) (n-1);;
<mrvn> val fib : ?curr:int -> ?next:int -> int -> int = <fun>
<whee> I think I saw a nifty implementation of fib using streams too
<mrvn> sfogarty: h is a variable and E a type?
<mrvn> let merge = function (h,E) | (E,h) -> h | (h1,h2) -> foo
<sfogarty> assume something like datatype T = E | x:;T
<sfogarty> aah
<sfogarty> function
<mrvn> fun a b c == function a -> function b -> function c ->
<mrvn> function 0 -> 1 | 1 -> 2 == fun x -> match x with 0 ->1 | 1 -> 2
<sfogarty> hm
<mrvn> fun combines multiple variables and function can pattern match
<sfogarty> yup. works.
<sfogarty> let rec rank = function [] -> 0 | x::xs -> 1+rank xs;;
<sfogarty> yay
<sfogarty> I'm trying to implement code ina book using ml in ocaml
<mrvn> Ever seen multitasking in ml?
<sfogarty> nope
<sfogarty> hm.
<mrvn> type task = Idle | Tasks of (task -> unit) * task;;
<mrvn> let next = function Idle -> () | Tasks(task1, task2) -> task1 task2;;
<mrvn> let rec add task = function Idle -> Tasks(task, Idle) | Tasks(task1, task2) -> Tasks(task1, add task task2);;
<mrvn> let make_task tasks f min max =
<mrvn> let rec t x tasks =
<mrvn> f x;
<mrvn> next (if x < max then (add (t (x + 1)) tasks) else tasks)
<mrvn> in add (t min) tasks;;
<mrvn> let tasks = Idle;;
<mrvn> let tasks = make_task tasks (fun x -> Printf.printf "Square %d = %d\n" x (x * x)) 2 10;;
<mrvn> let tasks = make_task tasks (fun x -> Printf.printf "Cube %d = %d\n" x (x * x * x)) 5 10;;
<mrvn> let _ = next tasks;;
<whee> looks like a job for the Lazy module
<sfogarty> sweet :)
<sfogarty> I'm going through data structures at the moment
<mrvn> don't forget records and classes
<sfogarty> no classes, as the book uses ML, but lots of records
<sfogarty> hm. so how would you fix the compaint about aux(x::y::xs as l) not matching other things. I should have it raise an error on anything else
<sfogarty> but it doesn't seem to fit into the code
<malc> it wont catch only a::[] and [] .. the rest wont even compile
<sfogarty> well, I need a way of saying let rec aux(x::y::xs as l | [] -> raise error)
<sfogarty> but that isn't right :)
<mrvn> malc: let aux = function [] -> raise Bad_args | _::[] -> raise Bad_args | x::y::_ as l ->
<mrvn> malc: or ignore the warning, it will raise an error
<malc> mrvn: please educate someone who needs it.. in this particular case sfogarty
<mrvn> yeah, -> sfogarty
<mrvn> too late, time for bed.
<sfogarty> problem is that aux is already a function :)
<sfogarty> hm
<sfogarty> that might work
<sfogarty> do I need to define Bad_args?
<sfogarty> hm. I'll just use Invalid_arguments
<sfogarty> nope
<mrvn> exception Bad_args
<mrvn> n8
<sfogarty> yay!
<sfogarty> I ende dup using raise (Invalid_argument "Too few.")
<sfogarty> ([] | _::[]) -> raise (Invalid_argument "Too few.")
<sfogarty> works
<sfogarty> any clue why I'm getting wierdnesses with ledit and ocaml? when I go up a line, it shows a few spaces that aren't there, such that if I edit the lien before doing a ^l, it comes out wrong
<malc> no idea, i dont experience this
<sfogarty> might be putty
<sfogarty> hm. happens with ^x
Dalroth has quit []
<sfogarty> grr. still want a better way of saying
<sfogarty> fun rank([]) = 0
<sfogarty> |rank(_::xs) = 1+rank(xs);;
<zack> sfogarty: what you mean with "a better way"?
<sfogarty> currently I have to take the input past the = and do
<sfogarty> let rec rank = function
<sfogarty> [] -> 0
<sfogarty> |_::xs -> 1+rank(xs);;
<sfogarty> doesn't seem as clean
<zack> ah ok ... you are a SML fellow I suppose ...
<sfogarty> well, in most other things I like ocaml better :)
<sfogarty> that's pretty much the only thing I've encounter that doesn't translate as (or more) nicely
<sfogarty> I'll learn to deal :)
<zack> I can't help here
<zack> the only way that come in to my mind is to define a syntax extension via camlp4
<zack> bye
zack has left #ocaml []
malc has quit [Read error: 110 (Connection timed out)]
sfogarty has quit ["User disconnected"]