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
docelic has quit ["brb"]
<Riastradh> If I have a module M, and in it a type 't' which is defined to be 'float', would the expression: 1.0 not be able to be considered an expression of type M.t?
Kinners has joined #ocaml
docelic has joined #ocaml
docelic has quit [Remote closed the connection]
merriam has quit [Remote closed the connection]
docelic has joined #ocaml
docelic has left #ocaml []
malc has joined #ocaml
merriam has joined #ocaml
lament has joined #ocaml
malc has quit ["no reason"]
<pattern> i am told there is an implicit "begin" after an "in"
<pattern> where does the implicit "end" go?
<Kinners> begin expr end or let foo = bar in expr
<pattern> no, i mean an implicit "begin" and "end"
<pattern> let ic = open_in name in
<pattern> count_channel ic;
<pattern> close_in ic
<pattern> mellum told me that the "ic" after the semicolon was ok, because there's an implicit "begin" after the "in"
<pattern> otherwise, wouldn't "ic" only be valid before the semicolon?
<Kinners> the way I think it is, begin expr end is a way to create a single expression, (where expr can be expr; expr), but for an if construct, if foo then expr; expr, the if operator has a higher priority than the ;, which you might want to use begin expr end for (if foo then begin expr end)
<pattern> yes, i understand how explicit begin and end expressions work... they work just like {} in c
<pattern> what i don't understand is how implicit begin and end expressions work
<pattern> the code i quoted above does not make sense to me, unless there's an implicit (invisible) begin and end
<Kinners> with 'let ... in expr; expr, the semicolon has higher priority than let, so you don't need a begin/end like you do with the if
<pattern> what do you mean it has a higher priority then let?
<pattern> i thought priority only had to do with which expression a token bound to
<pattern> semicolons terminate statements, do they not?
<Kinners> yes
<pattern> then isn't the expression after "in" bounded by the semicolon?
<Kinners> no
<pattern> what is it bounded by?
<Kinners> unless I'm misunderstanding what you mean by bounded
<pattern> i mean
<pattern> when you say "let x = expression1 in expression2", then "x" only has meaning in expression2, and no further, right?
<Kinners> right
<pattern> so when does expression2 end?
<pattern> i thought it ended when there was a semicolon
<pattern> in c it's simple, you have a block enclosed within {}
<pattern> in ocaml i'm missing something
<Kinners> no, an expression can be made up of expressions seperated by semicolons
<pattern> so when does ocaml consider the expression to whole, where no more expressions seperated by semicolons are part of it
<Kinners> so the end of the expression is where you would put the end if you explicitly used a begin
<pattern> hmmm
<pattern> that makes sense for the code i quoted above, because it ends right after "close_in ic" with a ";;"
<Kinners> the priority comes in when you consider an if, if expr1 then expr2 [else expr3]
<pattern> but i'm confused about where the implicit begin would be in this snippet: http://pastecode.net/index.php?tag=189
<pattern> does "count Inside_word in" end the previous implicit "begin ... end" block?
<Kinners> if the expr2 was actually subexpr1; subexpr2 (if ... then ...; ... [else ...]) it is treated like (if ... then ...); ... [else ...]
<Kinners> which would be a syntax error because the else is hanging in mid air
<pattern> yes, that makes sense
<pattern> that's how it works in c, too
<pattern> so you're saying that there wouldn't be an implicit "begin" and "end"... that "if ... then ...; ... else ..." would _not_ be implicitly made in to "if ... then begin ...; ... end else ..."
<Kinners> right
<pattern> doesn't that contradict what you said earlier?
<pattern> <Kinners> so the end of the expression is where you would put the end if you explicitly used a begin
<pattern> and <Kinners> no, an expression can be made up of expressions seperated by semicolons
<pattern> ?
<Kinners> that first one is for a let .. in .. construct, the second one is true
<pattern> ok, so the implicit begin and end only work for let ... in ... constructs
<pattern> there is no implicit begin and end in if ... then ... else constructs
<Kinners> an if construct has higher priority over the semicolon, so you need to use begin ... end to group several semicolon seperated expressions into a single expression
<pattern> right?
<pattern> got it
<pattern> thanks, kinners
<Kinners> got there in the end, I'm still learning too :)
<pattern> :)
<pattern> so i have another question, related to this... but you've already spent a lot of time answering this one, so you don't have to get in to this with me if you don't want to...
<Kinners> might as well ask
<pattern> i have a code snippet here: http://pastecode.net/index.php?tag=189
<pattern> is "count Inside_word in" inside the implicit "begin ... end" of the "let c = input_char in_channel in" construct?
<pattern> it's indented as if it is, but is it really? (not that it matters here, but if it, say, refered to "c", then it would matter)
<Kinners> I think the end would be just before the in
<pattern> not before the "count"?
<Kinners> let c = ... begin ... count Inside_word end in ...
<pattern> so it could have said:
<pattern> let c = ... count c in ...
<Riastradh> Is there a 'false-or' type or something in OCaml?
<Kinners> pattern: I'm not sure what you mean, c is a char, count takes a type (which would be something like type word = Inside_word | Outside_word I guess)
<pattern> i just meant for argument's sake... if c was of the right type
<Kinners> yes
<pattern> like if we had:
<pattern> ok
<pattern> so why does it use "in" anyway?
<pattern> why not just say:
<pattern> let c = ... count Inside_word ;
<whee> you have to know when to stop parsing
<whee> heh
<pattern> do you mean that it's done so that an implicit "end" gets put before the "in" ?
<whee> eh?
<Kinners> pattern: it's just being used to introduce a local variable (or let-binding)
<pattern> which local variable?
<whee> c in that case
<whee> and it's technically a binding, not a variable
<pattern> whee, i'm actually referring to http://pastecode.net/index.php?tag=189
<whee> what about it
<pattern> there's a lot more in "..." in "let c = ... count Inside_word ;" than it appears
<pattern> because that "..." expands to already include an "in"
<whee> I'm not following you
<whee> everything before the in is for bindings, after are more statements
<pattern> ok, forget the "let" statement i quoted above
<Kinners> pattern: are you wondering whether that function could be simplified?
<pattern> in the pastcode snippet above, just look at this:
<pattern> count Inside_word in
<pattern> try
<pattern> count Outside_word
<pattern> with End_of_file -> ()
<pattern> why does it say "count Inside_word in" instead of "count Inside_word ;"
<pattern> Inside_word doesn't get used in the "try" construct, so why have the "in"?
<whee> because that in is referring to "let rec count status"
<whee> not the "let c = ..."
<whee> it may or may not be obvious with that indentation style
<pattern> aaahh
<pattern> yes, that indentation style is super ugly
* Riastradh pokes people: is there a 'false-or' type or something in OCaml?
<whee> you might want to run code through camlp4 to fix it up if it's bad indentation
<pattern> is that easy to do? can an utter clueless novice like me do it?
<whee> yeah
<pattern> :)
<pattern> i'll check it out
<whee> camlp4o pr_o.cmo file.ml (if you're using the original syntax
<pattern> where do i get the pr_o.cmo ?
<whee> it's included with camlp4, just run it like that
<pattern> cool
<pattern> thanks, whee
<whee> change pr_o to pr_r to see how it would look in revised syntax (what I use)
<whee> either way it'll make it obvious what the code structure really is
lament has quit ["Did you know that God's name is ERIS, and that He is a girl?"]
<pattern> if anyone's curious, camlp4o turned http://pastecode.net/index.php?tag=189 in to http://pastecode.net/index.php?tag=190
<pattern> much much better, imo :)
<whee> indeed :)
<pattern> now i'm going to run the rest of the ocaml examples through it
<pattern> you guys have all been great, btw
<steele> Riastradh: what do you mean by false-or type?
<pattern> very helpful... and none of the attitude of efnet's #c... where i would have been told to rtfm for asking someing so basic
<whee> pattern: I can change that
<whee> ;)
<pattern> on the other hand, there're a lot many fm's for c, compared to ocaml
<pattern> yes, please change it... i haven't had my daily insults yet :)
<Riastradh> steele - For example, a variable of type 'string false_or' or something would be able to point to 'false' or string.
<steele> ah, you mean like None | Some a?
<Riastradh> i.e.: let x : string false_or ref = ref false; (* this should be ok *)
<Riastradh> x := ref "foobar" (* this should be ok too *)
<Riastradh> That might work.
<steele> it's called Option
<whee> yes, the option type sounds like what you want
<Riastradh> How do I use it?
<steele> let x = ref None .. x := ref Some "foo" ..
<Riastradh> Is it just "'a option"?
<Riastradh> Oh, I do it myself?
<Riastradh> i.e.: type myType = None | Some myOtherType
<whee> no, it already exists
<steele> no Some and and None are the type constructors
<Riastradh> Er, what, then, is the type?
<whee> option
<Riastradh> 'a option or just option?
<steele> None;;
<whee> well, 'a option I guess
<steele> - : 'a option = None
<whee> heh
<Riastradh> OK, thanks.
<Riastradh> Is it possible to declare how '=' works on values of a type I defined?
<whee> to do what?
<Riastradh> To test equality.
<whee> oh, compare, heh
<whee> no
<Riastradh> Blah.
<Riastradh> Oh well.
<whee> er, well
<whee> for variants you'll get a basic equality over all the data
<whee> but you can't go and overload any operators
<pattern> hmmm... i'm having a problem with camlp4o... i get the following error on some .ml files in the examples collectoin:
<pattern> File "l.ml", line 1, characters 0-19:
<pattern> Parse error: bad directive
<whee> what's that line?
<pattern> where the lines are:
<pattern> #use "spir-bw.ml";;
<pattern> print_string "To run: spir();;"; print_newline();;
<whee> yes, #use is only for the toplevel
<pattern> so should i filter out the files that contain "#use" ?
<whee> I suppose
<pattern> cool
<pattern> that works
<pattern> i was just wondering if it was something i could fix in the file, or if i should just not try to reformat it with camlp4o
<pattern> and i'll just skip it
<pattern> all done! now all examples are nicely formatted :)
* steele wonders if it's hard to add `` for infix functions (like in haskell) via camlp4
<whee> steele: that'd be rather trivial
<whee> hardest part would be learning enough to do it :)
<steele> hmm, going to look after that tomorrow
<whee> I went and did haskell's composition (.) operator in camlp4 to learn it
<steele> i have a good excuse for looking at camlp4 then ;)
<whee> and $ and some other things I came up with
rox has quit ["Client Exiting"]
<whee> now I feel like relearning and trying that, heh
<steele> i need some sleep first, good night
Kinners has left #ocaml []
mattam_ has joined #ocaml
<whee> .. interesting
<whee> my old camlp4 one doesn't compile anymore
<whee> ah, forgot a module :\
<pattern> i just tried it with the revised syntax
<pattern> what a difference!
<whee> heh, I like revised syntax a lot
<whee> less ambiguities
<pattern> unfortunately, my vim syntax hilighting doesn't seem to like the revised syntax
<pattern> so i guess i'll have to stick to the classic syntax
<whee> I have syntax highlighting for vim
<whee> (for revised and original)
<pattern> for the revised?
<pattern> cool
<whee> grab it from there
<whee> that guy wrote an indent file too, but I don't use that
<pattern> the ocaml.vim works for both?
mattam has quit [Read error: 60 (Operation timed out)]
<whee> yeah, you just have to set a variable in vim based on what syntax you're using
<steele> map <F4> :let ocaml_revised=1<CR>:syntax clear<CR>:syntax on<CR>
<pattern> oh, maybe that's what i have to do now
<steele> map <F3> :unlet ocaml_revised<CR>:syntax clear<CR>:syntax on<CR>
<steele> thats what i use
<pattern> i have the syntax hilighting for ocaml htat came with vim
<whee> I don't think they're the same
<whee> this one is a bit newer
<pattern> cool
<pattern> thanks whee & steele
<pattern> i'll try that
<pattern> btw, do you think it'll be harder to learn the revised syntax? i'm learning from the online tutorials and ocaml book, and i have a real book coming
<whee> hah, done already :)
<pattern> i haven't seen "value" in either of them yet... do they even cover the revised syntax?
<whee> steele: it's about six lines of camlp4, where only 1 really does the work :)
<steele> cool =)
<whee> although I don't know if I'd use ` now that I think about it
<whee> that could interfere with polymorphic variants
<whee> pattern: the only coverage of the revised syntax is on http://caml.inria.fr/camlp4/
<whee> there's some in the tutorial and reference
<whee> easiest way to learn is to read the section regarding that, and using camlp4 to translate some original to revised so you see what's different
<pattern> so i should probably learn the classic syntax first before i try to make sense of the revised, no?
<whee> yeah
<whee> it's good to know both if you want to use revised
<pattern> yeah, i'll definately check out the revised once i feel i'm able to understand the differences
<pattern> i was really discouraged the other day about ever understanding ocaml, but looking at some real sample code has me hoping again
<pattern> at least in the first few example programs i've looked at, it looks very similar to c
<steele> you should keep in mind that this similarity is sometimes a bit misleading
<whee> heh
<pattern> i can handle the ; and implicit begin and end weirdness... it was all that type inference stuff that was driving mad the other day
<pattern> and i have yet to really start thinking recursively
<steele> that's what i meant, in ocaml every expression returns a value, unless its ignored
<whee> ocaml isn't as strict as some functional languages in that, though; there's still side-effects in ocaml
<steele> and let x = 4 in a;b;c;d doesn't specify an execution order
<pattern> i can understand the concepts behind type inference... but just working out the types for a complex statement that just makes my brain hurt
<whee> steele: actually it does
<whee> in that case, anyway
<steele> but not always?
<whee> let a = f 1 and b = g 3 in .. doesn't specify execution order
<whee> but when using begin a; b; c end or do { a; b; c }, it's specified
<whee> it'll go sequentially there
<steele> i'm not sure about that
<whee> I am :)
<whee> otherwise, there'd be no way to express imperative code
<whee> which there obviously is via those types of statements
<steele> i remember having to use let () = a in let () = b .. somewhere
<steele> but maybe that was something different
<whee> code in a begin .. end block is really only written when there's a side-effect
<whee> and in the presence of side-effects, you need to preserve order
<whee> you would convert something like let a = f () and b = g() in .. to let a = f() in let b = g() in .. if you need to enforce the execution of f before g
<steele> oh, you're right it wasn't a sequence
<steele> it was something like let a = side1 () + side2 ()
<steele> sorry for the confusion
<whee> yeah, in that case it's not known
<whee> I think it's right to left at the moment, though
<pattern> but just because order of execution is not specified doesn't mean order of execution is not important, right? for example, f() could delete a file and g() could create the same file... which order that happens in is important
<whee> pattern: where it's important you need to make sure it happens that way
<whee> it doesn't come up that often, anyway
<steele> pattern: you have the same problem in languages like c. isn't the order of g and e in f(g(),e()); unspecified there
<pattern> yep
<pattern> but it doesn't happen often in c either :)
<whee> # [f (); g ()];
<whee> g! f!
<whee> right to left there :)
<steele> if you specify to much you and up with a language like java that doesn't perform
<whee> java, heh
<whee> qbasic of yesterday :)
<pattern> ahh... if only i could prove java's lack of performance to my java snob friends :)
<pattern> there's a flamewar on advogato about java performance right now
<whee> performance is stupid to argue about, it always ends up in a flamewar
<whee> as does any language discussion :\
<pattern> and one of my friends dismissed it by saying that you don't know if those people who's code didn't perform did anything stupid because you can't see their code
<whee> haha
<pattern> yeah, sometimes you learn something, though
<whee> I'm extremely happy I don't have to deal with java anymore
<whee> 3 courses dealing with that, I'm tired of it :P
<pattern> i've avoided having to deal with it myself
<pattern> but i have to deal with developers who use it and swear by it
<pattern> can't avoid them
<whee> I hate the design patterns that java forces on programmers
<whee> they never quite fit the actual problem
<pattern> as one of the guys in the advogato flamewar said, the dice job board comes up with the following listings:
<pattern> Java: 2842
<steele> and simple examples don't fit on a screen =)
<pattern> C++: 2206
<pattern> Perl: 839
<pattern> C#: 322
<pattern> Tcl: 86
<pattern> Python: 71
<pattern> Lisp: 12
<pattern> Ruby: 5
<whee> well jobs are a different matter
<whee> java's the language of the year
<whee> but if you restrict yourself to discussing the actual language features, java's behind
<pattern> yep... and they had another good point... that java was helped to popularity by the internet and netscape's contract with sun
<whee> and this is exactly why I didn't go for a CS degree :)
<whee> languages used in industry tend to suck
<pattern> those are some pretty unique events that would have helped any minor language in such a priveledged position
<pattern> managers doing the hiring go too often by buzzwords
Daverz has joined #ocaml
<emu> wow, there are some real fun ones in that flamewar
<emu> clueless about GC
<emu> ``maybe adopt the Ruby GC''
<emu> <-- simple mark/sweep
<emu> ``GC is bad because you don't free objects for a while, and this destroys cache'' <-- someone never heard of a copying GC
<pattern> yeah, i was hoping that someone who had a clue about ocaml had an advogato account and could reply intelligently on the GC issue
<emu> dan was replying, he has a clue
<emu> whether he got thru I have yet to see
<pattern> they did mention ocaml briefly in one of the posts... (the short statement post)
<pattern> but they didn't really differentiate it from the likes of python even
Daverz has left #ocaml []
pokcjai has joined #ocaml
pokcjai has left #ocaml []
<emu> Wake up! It's 21st century! C++ is dead, long live ocaml!
<emu> is that good enough for you?
<pattern> hehe
<pattern> it's good enough for me
<pattern> but, unfortunately, that'll sound less than convincing to anyone who isn't already convinced of ocaml's merits
<Zadeh> I'm impressed with ocaml's merits, but I don't think C++ is dead.
<Zadeh> Speaking of which, does anyone know what kind of optimization techniques the compiler uses? Kind of register allocator, etc?
<emu> Zadeh: I guess we need to beat it some more
* Zadeh pictures emu in a michael jackson video
<emu> hentai
foxster has quit [Read error: 60 (Operation timed out)]
async has quit [leguin.freenode.net irc.freenode.net]
Zadeh has quit [leguin.freenode.net irc.freenode.net]
gl has quit [leguin.freenode.net irc.freenode.net]
xtrm has quit [leguin.freenode.net irc.freenode.net]
xkb has quit [leguin.freenode.net irc.freenode.net]
pattern has quit [leguin.freenode.net irc.freenode.net]
skylan has quit [leguin.freenode.net irc.freenode.net]
smkl has quit [leguin.freenode.net irc.freenode.net]
gl has joined #ocaml
skylan has joined #ocaml
Zadeh has joined #ocaml
smkl has joined #ocaml
xtrm has joined #ocaml
pattern has joined #ocaml
async has joined #ocaml
xkb has joined #ocaml
foxster has joined #ocaml
whee has quit [Remote closed the connection]
pattern is now known as pattern_
mrvn_ has joined #ocaml
<mrvn_> moin
<mellum> moin moin
mrvn has quit [Read error: 60 (Operation timed out)]
rox has joined #ocaml
Riastradh has quit ["Lost terminal"]
mellum has quit [Read error: 60 (Operation timed out)]
mellum has joined #ocaml
Rumsy_Cauchy has joined #ocaml
Rumsy_Cauchy has left #ocaml []
smklsmkl has joined #ocaml
smkl has quit [Remote closed the connection]
TachYon26 has joined #ocaml
esb has joined #ocaml
esb has quit [Client Quit]
asqui has joined #ocaml
rox is now known as rox|peacemarch
smklsmkl is now known as smkl
whee has joined #ocaml
TachYon26 has quit ["bez ki³y nie ma zaliczenia (z prawd studentek AM)"]
mrvn_ has quit ["reconnect"]
mrvn has joined #ocaml
rox|peacemarch is now known as rox
karryall has joined #ocaml
karryall has quit []
lament has joined #ocaml
<pattern_> # let rec sum = function
<pattern_> [] -> 0
<pattern_> | i :: l -> i + sum l ;;
<pattern_> val sum : int list -> int = <fun>
<pattern_> # sum [1; 2; 3; 4];;
<pattern_> - : int = 10
<pattern_> is "i" the first element in the list, and "l" the rest?
<whee> yes
<pattern_> what if i have:
<pattern_> "i :: l :: m"
<whee> # value sum = List.fold_left (\+) 0;
<whee> value sum : list int -> int = <fun>
<whee> # sum [1; 2; 3; 4];
<whee> - : int = 10
<whee> :)
<mellum> Why \+?
<pattern_> is would "i" then be the first, "l" the 2nd, and "m" the rest?
<mellum> (+) should dl
<whee> mellum: revised syntax
<mellum> do even
<mellum> whee: Oh. Never looked at that.
<mellum> Ocaml's syntax sucks anyway :)
<pattern_> them is fightin words
<whee> pattern: I don't even know if that pattern is valid
<whee> that's how it would be if it is, though
<pattern_> ok
<pattern_> thanks, whee
<whee> well, okay it is (in the original syntax)
<whee> in revised you write it as either [i::[l::m]] or [i; l :: m]
<whee> the second form is what I'm used to
<mrvn> Those are two different things.
<whee> which are?
<mrvn> # let f a = [a::[1::[]]];;
<mrvn> val f : int list -> int list list list = <fun>
<mrvn> # let f a = [a;1::[]];;
<mrvn> val f : int list -> int list list = <fun>
<whee> you're using the revised syntax?
<whee> that's not the revised if you're using let :P
<whee> # value f a = [a; 1 :: []];
<whee> value f : int -> list int = <fun>
<whee> # value g a = [a :: [1 ::[]]];
<whee> value g : int -> list int = <fun>
<mrvn> is the revised [] like () now?
<whee> eh?
<mrvn> whee: what type does your :: have?
<mellum> :: is not an operator, it's magic
<whee> it'd be the same type
<whee> there's no reason it would change
<mrvn> 1 ::[] would then be int list, right?
<mrvn> [1 ::[]] is then int list list
<whee> [1 :: []] yes
<mrvn> a :: [1 ::[]] is still int list list
<mrvn> [a :: [1 ::[]]] is thus int list list list
<whee> in the original syntax, maybe
<whee> but not in revised
<mellum> Well, the outmost [] have a different color
<mrvn> so reviced [] must be somewhat like () now. ignorable.
<mellum> I don't like it, either...
<whee> I do :D
<mrvn> Ah, normal :: is [_::_] revised
<mrvn> revised sucks, takes away a lot of fun
<phubuh> where in Pcaml do I find the definition of match_case?
<whee> I don't believe that exists
<whee> er, wait. it does
<whee> but not in there :)
<phubuh> oh, I see
<phubuh> if I wanted to extend the pattern matching so as to allow this: (match "foo" with x ^ xs -> x) = 'f'
<phubuh> do I just add a rule to Pcaml.patt?
<whee> well you'd have to find out what rule corresponds to that
<whee> err, what level
<whee> then insert something at that level to generate a <:patt<>> to handle it
<whee> brb, dinner D:
<phubuh> alright
<phubuh> as far as I can see, Pcaml.patt only has one level
<phubuh> just kidding, it has tons
<whee> heh
<whee> I would look at pa_r.ml in the meta/ dir to get an idea of how that works
<phubuh> where is this meta/ dir?
<whee> camlp4/meta/
<whee> well I guess etc/pa_o.ml if you're using original
<phubuh> i am :) thanks
<phubuh> oh, i guess i need to download the source code
<whee> yeah, that would help :)
<whee> it's easier to figure out where to insert rules if you know what it's doing for everything else
<whee> you want to use pa_extend to add something to handle that
phubuh has quit [Read error: 54 (Connection reset by peer)]
karryall has joined #ocaml
phubuh has joined #ocaml
<phubuh> I accidentally switched an extension cord off =(
<phubuh> poof goes my uptime
<whee> D:
<whee> how are you going to handle ^?
<phubuh> I don't know, I'm very new to camlp4
<whee> match blah with [ a ^ b ^ c -> ... ] gets turned into match blah with [ x when x.[0] = a and x.[1] = b -> let c = String.blit meh I don't konw
<whee> syntactically, I mean
<whee> now actually I think you'd be better off doing it differently than that, but I'm not sure how patterns work anymore :\
systems has joined #ocaml
<phubuh> is it not possible to extend unlabeled levels?
<whee> don't think it is
<phubuh> ok
<whee> not sure though, pa_extend might have something
<whee> I don't know how you would refer to a rule that waasn't in some level
<phubuh> hmm, this is going to be tough. especially if I need to handle stuff like match foo with a ^ "foo" ^ b ^ c ^ "bar" -> ...
<whee> well I don't think it would be that difficult, but I'm not familiar with doing patterns :\
<whee> you'll end up using LIST0 or LIST1 and using ^ as the seperator, then doing some sort of work with that list
<phubuh> yeah
jameson has joined #ocaml
pedroxxx has joined #ocaml
<pedroxxx> hi
<whee> hola
<pedroxxx> oi
<pedroxxx> falas espanhol?
<whee> I don't know :(
<whee> heh
<jameson> I'm trying to remote-assist Win32 (only familiar with the UNIXish world myself). Is there a "simple" and "convenient" way to edit/compile/run (or load into the interpreter) O'Caml programs with the Win32 distribution?
<whee> jameson: doubt it, being windows :)
<whee> I believe you need some sort of linker, either msvc or mingw or cygwin's gcc
TimFreeman has joined #ocaml
TimFreeman has quit [Remote closed the connection]
<jameson> Hrm. Doesn't sound good.
<systems> linker ???
<whee> yes, a linker
<systems> ocaml uses a linker ?
<systems> i thought is a c thing
<whee> ocamlopt produces assembly, which would require a linker
<systems> s/is/its
<jameson> systems: Even if it did compile to C, it would still require the C linker ;-)
<whee> err, I think ocamlopt uses as and ld
pedroxxx has quit ["|®NinJa 4.5®| --> Feito para você. Disponível em www.ninjascript.com.br"]
<emu> um
<systems> whee linking is not done on assembly its dont on object code
<emu> you don't need a linker
<whee> systems: yeah, I know; it uses as and then links that
<emu> "technically" speaking
<emu> I'm not gonna argue whether ocamlopt makes use of one or not
<whee> emu: it's hell of a lot easier to leave that up to the OS
<whee> by the OS I mean the tools provided by it
<emu> only if what the OS provides is suitable
<phubuh> emu: all you need is a way to get an empty file and the ability to write arbitrary bytes to it
<whee> all unixes provide usable tools
<emu> haha
<emu> do unixes provide decent runtime support for applications?
<emu> I think they might cover the program's grave when it dies
<whee> eh?
<emu> Segmentation fault, core dumped
<whee> entirely not following you :P
<emu> I'm saying that unix does not provide very suitable tools =)
<emu> if you want to do more than write C programs
<emu> which crash when something goes wrong
<whee> that still doesn't quite make sense
<emu> why not?
<systems> yea i cant follow either
<whee> language is independent of the OS
<whee> in this case the OS being a unix
<emu> sigh
<emu> no
<emu> it's not
<emu> languages need runtime support
<pattern_> applications don't crash on other operating systems?
<emu> Unix provides C runtime support
<whee> and other languages can run on top of it
<emu> but may choose not to
<systems> cause unix is writen in c !!!
<emu> because C runtime support is rather crappy, as I've been pointing out humorously
<emu> so you cannot assume that ocamlc.opt would use ld
<whee> okay, and how does that make the tools unix provides insufficent for linking?
<whee> heh
<pattern_> it would be nice to have an os written in ocaml... and there are a couple of projects along those lines
<systems> pattern there is such a project
<jameson> emu: You do have a point there. But for all practical purposes, not making use of the C runtime system provided by libc etc. makes it considerably harder to make use of all the ugly impure stuff.
<whee> it uses as and gcc for linking, under a unix using gnu tools
<whee> you can assume it will always use some form of C based tools for doing these things
<emu> no, you can't
<emu> why would you?
<whee> do you see another unix not using C?
<emu> look
<emu> you can avoid using ld and related tools if you want
<whee> but there's no point in doing that, why reinvent the wheel?
<emu> and use your own machine code conventions
<emu> because C sucks! heh
<whee> it does what it does rather well
<whee> heh
<emu> many high performance Lisp implementations do this because they can't fit within the C straitjacket well
<emu> yes, it does sucking rather well
<pattern_> i think a specific example would be nice
<whee> maybe they need to write their own lisp based OS and stop complaining :p
<emu> It's already been done
<whee> problem solved!
<emu> if you've never heard of Lisp machines, or Genera, this is a good time to start reading
<whee> I have, but where are they today? :P
<pattern_> i think CompUSA sells a few models
<emu> they were a product of the times when general purpose hardware was slow
<emu> nowadays, they would be too expensive
<emu> that doesn't mean they didn't do a lot of things better than are being done today, in some cases
<emu> Lisp machines had graphical user interfaces before MS-DOS
<emu> ever existed
<jameson> whee: There have been Modula-3 based UNIX-style kernels (well, one, at least) for PC-style HW, with very good performance (and much better static typechecking).
<pattern_> there are a lot of esoteric architectures which do a variety of things nicer than general purpose hardware