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
<det> they 170k binary, most of it is ocaml basic stuff
<det> s/y//
<det> I was wondering if I could reloacte it to a shared library
<mrvn> det: use bytecode
<det> for distribution :)
<mrvn> afaik not since ocaml can't produce PIC
<mellum> It can't?
<det> what is PIC ?
<whee> position independent code
<whee> I think :\
<steele> there is http://algol.prosalg.no/~malc/scaml/, but i'm not sure how stable it is
<pattern_> these syntax errors are driving me insane! http://www.rafb.net/paste/results/Y1307425.html
<pattern_> there's a syntax error on line 9, chars 28-32, but i don't know why :(
<pattern_> i've spent hours trying to rewrite this simple recursive function and it's just syntax error after syntax error, with no further explanation.. grr...
<whee> you've got this "let mylist = loop stdin" in the middle of nowhere
<whee> there's no "in ...", or anythin
<whee> g
<pattern_> why should there be an "in" ?
<Riastradh> Line 6 looks bad, too: getline ( input_line input_file ) ... because it looks like getline is applied to the result of applying input_line to input_file.
<whee> you need to define where it's bound
<whee> plus the in serves as a delimiter
<pattern_> riastradh, yes, getline should be applied to the result of applying input_line input_file
<pattern_> whee, i see
<Riastradh> input_line is a function?
<whee> yes
<pattern_> whee, so the "try" does not work like an "in"?
<whee> pattern: try ... with .. -> ...
<Riastradh> let mylist =
<Riastradh> try loop stdin with
<whee> you should be able to remove all of the things related to try, and have it make sense
<Riastradh> End_of_file -> exit 1
<pattern_> whee, but if i remove the things related to try, how do i catch the exception?
<whee> you won't; but the program should be syntactically correct
<whee> you end up with "let mylist = loop stdin" with yours, which is incorrect
<pattern_> but i need to catch the exception to break out of the loop upon reaching the end of the input_file
<steele> pattern_: let .. = .. (without an in only works for toplevel declarations)
<pattern_> riastradh, isn't that what i have?
<pattern_> steele, i see
<steele> what are you trying to do? read lines from stdin and?
<pattern_> read them, and process them... the "foo" -> [ "bar" ] construct is a stand-in for the real processing i'm doing in my program
<pattern_> also, in the real program i won't exit when i get to the end of the file, but use the list resulting from the "loop" function call
<palomer> should I pull my hair out trying to do matrix mutiplication using functional programming or would the gain in knowledge be insignificant compared to the amount of hair pulling?
<whee> well you'd use the Array module, so it wouldn't be that bad
<palomer> true
<palomer> but you can't concatenate with arrays, can you?
<whee> you can create a new array and blit the two
<whee> which happens to be what Array.append does, heh
<palomer> isn't that horribly inefficient?
<mrvn> palomer: let matrix a b c d = fun i j -> if (i=0)&&(j=0) then a else if (i=1)&&(j=0) then b else if (i=0)&&(j=1) then c else d
<whee> they're the same as C arrays
<mrvn> Why arrays?
<palomer> they're more efficient for certain types of calculation
<mrvn> Do you want to do functional programming or programm efficient code? :)
<palomer> hrm
<palomer> I'm an algorithm nut
<pattern_> hmmm... now i'm getting a stack overflow... http://www.rafb.net/paste/results/S2018836.html but i don't see why, since my recursive function (loop) should terminate upon getting an exception at the end of the input_file
<whee> that's not tail recursive
<palomer> ok, so the functional way would be to do the same thing as with lists, meaning it'll multiply in O(n^2)
<steele> there is a problem with your code: evaluation order for :: is not specified (it's right to left actually)
<pattern_> steele, ahh!
<steele> it does the recursive call before reading the line
<whee> that could be it too, hrmf
<pattern_> so if i reverse the expressions on either side of the :: it would work (albeit with a backwards ordering)?
<steele> you would use let l1 = getlist ( input_line input_file ) in l1 :: loop ... or make it tail recursive
det has quit ["ircII EPIC4-1.1.2 -- Are we there yet?"]
<palomer> what's wrong with this syntax: for i=0 to 4 do print_int i;;
<mrvn> =
<mrvn> nothing
<mrvn> done is missing
<pattern_> steele, ah, interesting solution
<palomer> done?
<palomer> ahh, gotcha
<palomer> whats wrong with this:
<palomer> Warning: this expression should have type unit.
<palomer> temp.(i) = v1.(i) * v2.(i) done;;
<palomer> ^^^^^^^^^^^^^^^^^^^^^^^^^^
<Riastradh> temp.(i) <- v1.(i) * v2.(i)
<mrvn> Array.set temp i (v1.(i) * v2.(i))
<palomer> ah, gotcha
lament has joined #ocaml
<pattern_> steele, your solution worked great :)... now i just have to carve that sort of thinking in to my brain... because it definately is not intuitively obvious for me yet
<palomer> b
<palomer> im guessing the gtk bindings rely on side-effects
mellum has quit [Read error: 110 (Connection timed out)]
<palomer> can you match with vectors?
<whee> vectors?
<palomer> [|1;2;3|]
<whee> those are arrays
<palomer> oreilly calls them vectors
<palomer> though other programming languages call vectors resizable arrays
<whee> but yes, you can match with those
<palomer> with the :: operator?
<whee> # [||];
<whee> - : array 'a = [||]
<whee> #
<whee> no, they aren't lists.
<palomer> hrm, so what do i use?
<whee> [| blah |]
<whee> heh
<palomer> im trying to make a subarray function
<palomer> kinda like List.tl
<whee> there's one in Array
<palomer> I'm trying to learn!
<whee> :P
<palomer> doing this in functional programming doesn't seem feasible
<whee> why not?
<whee> you can do it with a for loop
<palomer> thats imperative!
<whee> yes, but you can easily turn that for loop into a tail recursive function
<whee> so why not just use the for loop? heh
<whee> arrays are imperative by their nature
<palomer> so theres no way to do this functionally?
<whee> yes, there is
<whee> convert the for loops to recursion
<palomer> oh I see
<palomer> with a tail recursion
<palomer> that is kinda silly though
<palomer> whew! dot multiplication in O(n^3)!
Kinners has joined #ocaml
<pattern_> "Several researchers have proposed programming languages with intrinsic complexity properties, for instance languages ensuring that all functions representable are PTIME without refering to an explicit time measure. This work follows the same approach."
<pattern_> "By relegating the handling of the complexity property to the type system, the programming task becomes easier, since the programmer is freed from manually providing information needed for the complexity analysis. All well typed programs are PTIME."
<pattern_> hehe
<palomer> hrm
<palomer> im skeptical
<palomer> it's undecidable!
<palomer> if a computer program can figure out if an function will run in PTIME that means it'll know if that function will terminate
<palomer> hence a contradiction
<pattern_> from the discussion ( http://lambda.weblogs.com/discuss/msgReader$5863 ) "By the way, remember our discussion of programs vs. data? I mentioned that a type system can ensure termination, and this caused some concern. This sort of result is even sexier..." ;)
<palomer> a type system can ensure termination?
<palomer> no way!
<palomer> that's the halting problem
<pattern_> i think he is aware of that
<mrvn> palomer: But a type system can tell you that if it terminates it will terminate no matter in what order you evaluate and the result will allways be the same.
<palomer> mrvn: given an input
<mrvn> Which means one can be lazy and evaluate only one part of a&b at first
<palomer> hrm, this is with functional programming where given an input a function will always return the same value
<mrvn> or only one of the if branches
<mrvn> palomer: of cause. strict functional, no sideeffects
<palomer> just because if a&b terminates doesn't mean b&a terminates
<mrvn> palomer: yes it does.
<palomer> say b doesn't terminate, and a is always true
<palomer> well && is a short circuit operator
<mrvn> palomer: oh, no wait. the thing was different: If it terminates the result is allways the same.
<palomer> mrvn: agreed
<palomer> because of no side effects
<mrvn> palomer: Hey, that is quite complex to proof.
<palomer> which means rand is out of the question
<palomer> mrvn: I can imagine
<mrvn> palomer: and the strict functional way has no lazy evaluation for "if" or "||"
<palomer> hrm
<palomer> you lose alot of computing when you take away random numbers
<palomer> I'm guessing this is only for deterministic algorithms
<palomer> in which case I see how this is plausible, though we could probably do it by hand
<palomer> but I see how that can get hard when we hide the implementation of the functions from the user
<whee> haskell is pretty strict functionally and it's lazy evaluation :)
<palomer> hrm
<palomer> this technique wouldn't work for algorithms that use memoization
<palomer> quite frankly, I can't see how I would ever want to use such a system
Hellfried has joined #ocaml
lament has quit ["Did you know that God's name is ERIS, and that He is a girl?"]
mattam has quit [Read error: 110 (Connection timed out)]
Hellfried has quit ["Client Exiting"]
liyang has joined #ocaml
<liyang> 'ullo...
<Riastradh> Hi.
<liyang> Can anyone help me with a ``This kind of expression is not allowed as right-hand side of `let rec''' question, or is everyone asleep now? ^_^;
<whee> liyang: sure
<Riastradh> I'm awake.
<Riastradh> I don't know OCaml too well, but I'll probably be able to help.
<liyang> kay... basically, I've a bunch of mutually recursive functions (let rec yadayada and foobar). Now, suppose I try to do this:
<liyang> let rec ... and primes = { x = 2 ; next = Either next_prime } ;;
<liyang> this works.
<liyang> So I define: let mk fn x' = { x = x' ; next = Either fn } ;;
<liyang> and change the earlier line to: let rec ... and primes = mk next_prime 2 ;;
<liyang> this doesn't. -_- ...
gene9 has joined #ocaml
<liyang> what precisely is the difference between the two?
* liyang can put code up on a HTTP if anyone wants a play with it...
<whee> what's Either?
<liyang> just a type constructor...: type ('a, 'b) alternative = Either of 'a | Or of 'b ;;
<liyang> don't think that's relevant though, is it?
<Riastradh> What error does the 'primes = mk next_prime 2' generate?
<liyang> This kind of expression is not allowed as right-hand side of `let rec'
<Riastradh> Hrm...what's the rest of the let rec like?
<liyang> I've Googled, but can't really see the difference between the two versions myself...
* liyang has been trying to move the lazy list bit out to a separate module... a good two hours wasted so far... <g>
<Kinners> this is talked about in a tutorial/book somewhere
<Kinners> sadly I can't remember which one ;p
<whee> heh
<whee> I can't duplicate it with smaller code snippits :\
<liyang> How much smaller? (without the mutrec?)
<whee> well I haven't tried mutable yet
<liyang> (mutable what? Sorry, I'm a bit new to this O'Caml malarkey...)
<whee> geh, can't duplicate it at all :)
<mrvn> liyang: what are you trying to assign?
<liyang> see the URL... https://mariko.ucam.org/primes.ml
<liyang> (or hold on a sec, I'll get it on a HTTP server...)
<mrvn> liyang: bah, certificate unknown
<whee> errrm, I don't know if I like this source
<whee> hard to tell where it's starting to execute code
* liyang has ears. ^_-
* liyang was a Haskell junkie not so long ago, y'see...
* whee gives up
<whee> heh
<mrvn> and next_prime n = let n' = n + 1 in
<mrvn> if is_prime n' then n' else next_prime n'
<mrvn> and next = Either next_prime
<mrvn> and primes = { x = 2 ; next = next; };;
<mrvn> val is_prime : int -> bool = <fun>
<mrvn> val next_prime : int -> int = <fun>
<mrvn> val next : (int -> int, int t) alternative = Either <fun>
<mrvn> val primes : int t = {x = 2; next = Either <fun>}
<liyang> well, it works if you uncomment the ``(*and primes = { x = 2 ; next = Either next_prime } ;;*)'' line, but I'd like to move the t type out to a separate module, hence the need for the mk function... and that's where the problems begin.
<mrvn> Why do you have the primes = in the let rec?
<mrvn> same with is_prime
<liyang> mrvn: because it depends on next_prime ...
<liyang> (and next_prime depends on is_prime, and is_prime depends on primes.)
<mrvn> ic.
<mrvn> sorry no clue.
<Kinners> change primes into a function
<Kinners> and primes () = ...
gene9 has quit []
<liyang> Kinners: but then I'd end up recalculating all the primes up to sqrt(n), every time I call is_prime n...
* liyang misses his lazily evaluated lists...
<whee> liyang: there's streams
<mrvn> liyang: Use the Lazy module
<liyang> I've looked into both... streams doesn't really help as I'd like to keep all the values I've calculated, and I don't see how I can use Lazy.
<whee> well you don't have to remove items from a stream
<whee> so that would keep all previously calculated values
<liyang> Stream.npeek?
<whee> yes
<whee> you could go and grab n values into a list, then use that list whereever
<liyang> But how would you have recursive streams? I seem to remember having problems with that when I tried using it previously...
<liyang> whee: problem is, I don't know what n should be... there's an upper bound on n, yes, but that's just doing uncecessary work, for example when you call is_prime on an even number.
<whee> if that's helpful at all
<whee> I think I ripped that from a mailing list at some point :\
* liyang tries to remember the incantation required to get ocaml to recognise stream syntax...
<whee> you need to use camlp4
<whee> add -pp camlp4o if you use original syntax
* liyang ponders.
<liyang> Hm. Prime generation aside, I take it we're no further on exactly why one version of my primes.ml works, while the other generates the error? ...
<whee> needs more pixie dust :)
<liyang> or sleep. ^_^;;
<Smerdyakov> Do you know what I hate about pixie dust?
<liyang> Smerdyakov: go on, don't keep us in suspense... ^_-
<Smerdyakov> Well, I was hoping you would know, so you could tell me.
<Kinners> liyang: I think it's to prevent runaway value definitions
<liyang> but oughtn't { x = 2 ; Either next_prime } and mk next_prime 2 be the same? ... I'm honestly having difficulties seeing the difference between those two...
* liyang might try caml-list some time...
<liyang> now though: sleep.
* liyang lurks
<Kinners> maybe the first is easy to prove, the second being a function call could be much harder so it's not allowed at all
<Kinners> you can use constructors but not functions
Kinners has left #ocaml []
foxen has quit [Read error: 104 (Connection reset by peer)]
xxd_ has quit [Remote closed the connection]
xxd_ has joined #ocaml
mellum has joined #ocaml
foxen5 has joined #ocaml
mellum has quit [Read error: 110 (Connection timed out)]
mellum has joined #ocaml
Yurik has joined #ocaml
<Yurik> re
mattam has joined #ocaml
Yurik has quit [Read error: 104 (Connection reset by peer)]
<async> what would be the easiest way to convert an big-endian integer to little-endian
docelic has joined #ocaml
<async> nvm ill just read the bytes and reassemble them
docelic has quit [Read error: 104 (Connection reset by peer)]
docelic has joined #ocaml
<mrvn> htonl/ntohl?
<palomer> how is this possible:
<palomer> let rec insert_vtx v g =
<palomer> match g with
<palomer> [] -> [(v,[])]
<palomer> | (h,_)::_ when h=v -> failwith "existing vertex"
<palomer> ?
<palomer> nevermind...
docelic has quit ["Client Exiting"]
TrOn has joined #ocaml
Rhaaw has joined #ocaml
<palomer> whats wrong with this: let insert_edge_list = fun ls g ->
<palomer> List.fold_right insert_edge ls g;;
<palomer> ?
<whee> compile error, or?
<whee> you also want to use List.fold_left, not fold_right
<whee> fold_left is tail recursive
<palomer> found the error
<palomer> seems insert_edge takes 2 parameters for the edges
<palomer> and not a pair
<palomer> changed it so it takes a pair, makes more sense
<palomer> I don't understand why fold_right is not tail recursive
<whee> look at the definition of it
<whee> ocaml/stdlib/list.ml
<palomer> I'm trying to stick with the ocaml and lisp convention of naming the target second and the parameters first
<palomer> but it should be tail recursive by definition!
<whee> no, it shouldn't
<palomer> hrm, is it because it starts at the last element?
<palomer> I guess so eh
foxen5 has quit [Read error: 54 (Connection reset by peer)]
<mrvn> palomer: If fold_right where tail recursive it would have to reverse the list first.
<mrvn> let tail_fold_right f list init = List.fold_left (fun accu elem -> f elem accu) init (List.rev list);;
<Riastradh> Either fold_right is incredibly speed inefficient (it iterates across the list twice) or it is incredibly space inefficient (it isn't tail recursive).
<mrvn> Riastradh: where is that space inefficient? Its more a problem of limited stack size than pure space.
<mrvn> 8 MB of stack just isn't what it used to be
<Riastradh> OK, not quite 'space' inefficient, but 'stack space inefficient' or something.
<mrvn> I tend to allways reverse lists and fold_left. I just had too many problems with long lists and fold_right.
<mrvn> You design and test your ode with somethig like 100 element long lists and then the real life app comes with 1000 elements and the fold_right crashes. :(
docelic has joined #ocaml
mrvn_ has joined #ocaml
Smerdyakov has quit [Read error: 104 (Connection reset by peer)]
mrvn has quit [Read error: 110 (Connection timed out)]
lament has joined #ocaml
systems has joined #ocaml
systems has left #ocaml []
rox has quit ["Client Exiting"]
rox has joined #ocaml
Smerdyakov has joined #ocaml
<palomer> dfs with functional programming with linked lists isn't the easiest thing:o
<mellum> dfs == depth first search?
<Smerdyakov> It's not _the_ easiest thing, but it _is_ easy. :P
<palomer> hrm
<palomer> in c++ it's a breeze
<Smerdyakov> It's even easier in ML.
<mellum> He said the bad word! ;)
<palomer> the problem comes to applying dfs again to all the vertices you've cultivated
<palomer> if you use List.map you get a 'a list list
<Smerdyakov> Oh, do you have that problem when you use List.map in C++?
<palomer> there does exist a mapping function in c++
<palomer> noone uses it though:o
<palomer> you can have functional programming in c++, but it's more typing
<palomer> and people are lazy
<Smerdyakov> So... how can having List.map available to you make things HARDER?
<Smerdyakov> You don't _have_ to use it.
<mellum> The functional stuff in C++ is really laughable if you know any "real" functional languages... it's only there to impress C programmers
<palomer> so what can I use?
<palomer> is there function that lets me take the union of all lists when applying a function to a list?
<Smerdyakov> You don't seem to understand.
<Smerdyakov> You have no higher order functions to help you in C++.
<Smerdyakov> You can always use the same logic you would use in C++ in ML.
<palomer> sure you do!
<Smerdyakov> So HOW can it be harder in ML?
<palomer> using functional programming
<Smerdyakov> Whatever.
<Smerdyakov> None of the standard list functions are special.
<palomer> I could do it proceduarly without any problem
<Smerdyakov> You can write them all yourself.
<Smerdyakov> You don't need to find ANY existing functions to be able to write this.
<palomer> so is there a map union function?
<Smerdyakov> Maybe there is, or maybe you could spend 10 seconds writing one!
<palomer> :o
<palomer> evil!
<palomer> fine
<Smerdyakov> But I think the best way to do this is with an accumulator parameter, though you haven't yet said what you're doing.
<palomer> accumulator parameter?
<Smerdyakov> Read a tutorial if you don't know it
<pattern_> the fold functions use an accumulator parameter, right?
<whee> yes
<whee> I believe the first argument to the given function is the accumulated value
<mrvn_> Smerdyakov: C++ has higher order functions. They are just not as nice looking and must be named.
<mrvn_> Even C has higher order functions
<whee> as does assembly
<whee> heh
<mrvn_> whee: nah, asm only has data.
<whee> you can simulate the same design patterns that you would with HOFs though
<whee> and it's essentially the same
<palomer> ah, thats what I wanted! fold!
<mrvn_> whee: you can simulate everythin in every other useable language.
<palomer> theres another little nugget about dfs though, and this one I have no idea how to suromunt
<palomer> surmount
<palomer> I have to carry around a list of all vertices seen so far
<mrvn_> palomer: tree or graph searching?
<palomer> Graph
<palomer> if it was a tree I wouldn't need it
<mrvn_> How does your graph look like?
<palomer> then I would just need the last vertex visited
<palomer> no idea
<palomer> I need to take an adjacency list and dfs it
<mrvn_> The graph as matrix of bool?
<palomer> as a array of lists
<mrvn_> Ahh, a list of (i, j) vertexes.
<palomer> where i is an int and j is an int list
<palomer> yes
<palomer> so I need a rec dfs graph seen vertex
<palomer> but if I do that seen is local to the function
<palomer> which means that if another branch finds a vertex then the seen variable is only updated in that branch
<mrvn_> let rec visit f vertices i = f i; let (out, rest) = List.partition (fun (x,y) -> x = i) in let (in, rest) = List.partition (fun (x,y) -> y = i) in List.iter (fun (i, j) -> visit f j rest) out;;
<palomer> thas procedural!
<palomer> isn't it?
<mrvn_> If you see i you get all outgoing eges, all incoming and the rest. You throw away incoming and follow each outgoing with a rest as new graph.
<palomer> ahh
<mrvn_> s/f i;/let () = f i in /
<palomer> now thats a good idea
<palomer> however inefficient
<mrvn_> palomer: Its n^2
<palomer> as opposed to n
<mrvn_> palomer: do you know the size of the graph?
<palomer> I con get the number of vertices with List.Length
<mrvn_> Like its a graph with edges 1 to 10 or something.
<palomer> hrm
<palomer> the edges can be numbered in any which way
<palomer> mrvn: what if you have a cycle in your graph? your solution won't work
<mrvn_> If you have a graph of X edges each with a list of vertices you can do it in N.
<mrvn_> O(N) that is
<mrvn_> Just a list of vertives needs O(n^2)
<palomer> you could do it in O(n) using dynamic programming
<palomer> but getting back to the cycle
<palomer> how do you know theres no cycle?
<mrvn_> palomer: no, I don't think you can.
<palomer> that's what I'm having problems with!
<palomer> I can't see how to do it in fp
<palomer> I could use the procedural aspect of ocaml to do it
<palomer> using references and such
<mrvn_> palomer: You initialize each edge with visited=flase and change that when you visit. If you follow a vertices and the endpoint is already colored you have a circle.
<palomer> mrvn: yes, but where do you keep this array/list?
<mrvn_> palomer: as parameter
<mrvn_> you need mutables or refs to get O(n) speed.
<palomer> so you keep the parameter as a reference?
<mrvn_> arrays are mutable
<palomer> the parameter called seen has to then be a reference, so that every function can update the one and only seen list
<palomer> or array , or whichever
<palomer> if you don't then every function will have it's own local seen variable
<mrvn_> it has to be mutable
<mrvn_> which means, a array, a ref or { mutable something }
<palomer> gotcha
<mrvn_> But you don't absolutely need to.
<palomer> which means theres no way of doing this in pure fp
<mrvn_> yes there is. mutables are just a easier and faster way of doing it.
<palomer> how would you do it in pure fp?
<mrvn_> You can do functional mutables by passing an extra parameter to every function and return it possibly changed.
<palomer> oh, yhea
<palomer> that would be horribly inefficient though
<mrvn_> let visit env i vertices = if List.element i env then () (* circle *) else let env = i::env in visit_neighbours env i vertices
<mrvn_> and visit_neighbours would again return env
<palomer> whoa there buddy
<palomer> I'm an ocaml newb
<mrvn_> lets do a simpler example.
<palomer> I got it! a way to do it in fp
<palomer> have the function return all the vertices visited, and add that to the seen list when it returns
<mrvn_> palomer: ok, you got it.
<palomer> hrm, this gets complicated
<palomer> very fp though
<palomer> thx
<mrvn_> palomer: and not faster than O(n^2)
<mrvn_> The problem isthat you realy do need arrays or mutables to see if an edge has been visited in O(1).
<mrvn_> If you have a list of visited edges you need O(n) to check.
<mrvn_> And you can't make arrays the functional way.
<mrvn_> (with the same speed as imperative arrays)
<palomer> gotcha, which is why it is sometimes good to mix and match paradigms
<mrvn_> Which is why ocaml is so great
mrvn_ is now known as mrvn
rox is now known as rox|heimdienst
<mrvn> can i somehow inherit one type in another?
<mrvn> Or do I need classes for that?
<Riastradh> You probably need to use classes.
<steele> mrvn: what about polymorphic variants?
<mrvn> I want to inherit a record and some functions on that record in a bigger one.
<steele> ok, seems like you need classes
<mrvn> type 'a list = { prev:list; next:list; data:'a; } type data = { data:int } type data_list = data list
<mrvn> Thats roughly what I want
<mrvn> But I hate to use list_elem.data.data all the time.
docelic is now known as docelic|away
Kinners has joined #ocaml
<steele> does that work? data of type data in the first record and int in the second?
<mrvn> steele: no, they shadow each other.
<mrvn> Does anyone have an url for the ocaml source in browsable form?
<steele> that would be an advantage of classes
<whee> heh
<steele> =)
<mrvn> thx