smkl changed the topic of #ocaml to: OCaml 3.07 ! -- Archive of Caml Weekly News: http://pauillac.inria.fr/~aschmitt/cwn, 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
cmeme has quit [Connection timed out]
Smerdyakov has quit [Read error: 110 (Connection timed out)]
Smerdyakov has joined #ocaml
gl has quit [Read error: 110 (Connection timed out)]
The-Fixer has quit [Connection timed out]
cjohnson has joined #ocaml
Banana_ has joined #ocaml
The-Fixer has joined #ocaml
The-Fixer has quit [Client Quit]
Banana_ has quit [Client Quit]
The-Fixer has joined #ocaml
Banana[Home] has joined #ocaml
Banana[Home] has quit [Client Quit]
Banana has quit [Read error: 110 (Connection timed out)]
Banana has joined #ocaml
mattam_ has joined #ocaml
mattam has quit [Connection timed out]
Kinners has joined #ocaml
<pattern> i'm getting stack overflows on large inputs, but my program works for small inputs -> http://nopaste.snit.ch:8001/640
<pattern> what it does is transpose a matrix, converting rows to columns... so that this matrix:
<pattern> a,b,c
<pattern> d,e,f
<pattern> g,h,i
<pattern> gets transformed in to:
<pattern> a,d,g
<pattern> b,e,h
<pattern> c,f,i
<pattern> works just fine for this small example matrix, but when i have a large matrix (~70k rows), with 10 cols (with each col containing up to 20 chars) i get a stack overflow :(
Smerdyakov has quit [Read error: 110 (Connection timed out)]
Smerdyakov has joined #ocaml
<Hadaka> you have a case of non-tail recursion there
<pattern> my plan is to write a little script that creates arbitrary sized matrixes so that i can determine at exactly what sized matrix i get a stack overflow
<Smerdyakov> That is "matrices."
<Hadaka> several places actually
<pattern> cool
wazze has quit ["Learning about how the end letters on French words are just becoming more and more silent, I conclude that one day the French]
<pattern> smerdyakov, thanks
<pattern> hadaka, where?
<Hadaka> if you are building lists - h :: t -> something :: recfun t is not tail recursive
<Hadaka> it needs to evaluate the value of the function before it can cons the list element
<pattern> even if "something" is h?
<Hadaka> almost every function, starting from splitlines
<Hadaka> even if something is h, because it needs to build a new element
<Kinners> and recursive calls inside a try-with block aren't tail recursive
<pattern> ah
<pattern> :(
<pattern> so how can i build a list recursively while making the function tail recursive if i can't do: something :: recfun t
<pattern> ?
<Smerdyakov> Ever heard of "an accumulator parameter"?
<Hadaka> how you can avoid such stuff is that you build the list in reverse - and give the reversed list up to that point as a parameter to the recursive function - and then in the end reverse the list
<Hadaka> if you can't naturally build it in reverse
<pattern> i see
<pattern> reversing the list is expensive, though :(
<Smerdyakov> No.
<pattern> isn't it O(n*n) ?
<Kinners> no, Just O(n)
<pattern> cool
<pattern> well, i'll see if i can work on this, then
<Smerdyakov> Kinners, it is also O(n*n). :P
<pattern> and how about exceptions? what's to be done there?
<Hadaka> well, lists in general do not work too well with matrix stuff
<pattern> yeah
<pattern> the natural thing to do is to use an array, obviously
<pattern> but i wanted to see if i could just use lists
<Hadaka> ah, okay
<Kinners> Smerdyakov: what do you mean?
<Smerdyakov> Kinners, I mean that list reversal runs in O(n*n) time.
<Hadaka> I can't recall what was the best solution to the try/catch problem...
<Smerdyakov> Kinners, do you know what O() means?
<pattern> hadaka, i guess i can just leave the recursive function itself without a try/with block, but catch the exception one level up instead
<Kinners> Smerdyakov: generally, but I'm not a comp sci student :)
<Smerdyakov> Kinners, so you didn't know that anything that runs in O(n) time also runs in O(n*n) time?
<Hadaka> pattern: yup
mattam_ is now known as mattam
<mattam> Smerdyakov: playing tricks ?
<liralen> Smerdy - anything of O(n) complexity has O(n^2) complexity? That seems odd.
<Smerdyakov> mattam, what?
<Smerdyakov> liralen, it isn't odd, since O() is an _upper_bound_....
<mattam> sure anything of O(x) < O(y) runs in O(y) too
<liralen> Smerdy - oh, OK.
<mattam> except if you mean mean-complexity by O
<Smerdyakov> mattam, even for mean-complexity.
<mattam> i'm not sure
<pattern> so which is it? O(n) or O(n^2) ?
<liralen> Smerdy - so we could say that {1+2} in C takes O(N^(N^N)) complexity if we like, just for fun -- except that it abuses the verb 'takes', just a little.
<Kinners> Smerdyakov: do you mean upto but not including?
<Smerdyakov> mattam, well, I am. Average case complexity is just a different way of creating a function that expresses a property of a program. O() notation has the same meaning over all functions.
<mattam> Smerdyakov: oh right, that's not the problem
<Smerdyakov> liralen, I never see anyone use "takes" like that.
<Smerdyakov> Kinners, what?
<Smerdyakov> liralen, you would say {1+2} runs in O(N^(N^N)) time.
<Kinners> Smerdyakov: nevermind
<mattam> i meant, if we have O-mean(x) < O-mean(y) it doesn't necessarily implies O-max(x) < O-max(y)
<Smerdyakov> liralen, and I would prefer to say {1+2} runs in O(\N -> N^(N^N)) time. :P
<liralen> Smerdy - I would prefer 'has' when talking about algorithms -- and 'has' gets abused in the same manner as 'takes' in my example.
<liralen> Smerdy - ooh, OK =)
<Smerdyakov> liralen, I think this is missing the point. If you don't want to talk about upper bounds, don't use O(). :P
<Smerdyakov> pattern, it is both O(n) and O(n^2).
<pattern> and O(infinity)?
<Smerdyakov> pattern, no, since "infinity" has no meaning here.
<pattern> but infinity surely contains O(n) and O(n^2)
<Smerdyakov> pattern, however, list reversal is Omega(n) but not Omega(n^2).
<Smerdyakov> I told you. "Infinity" has no meaning, so we can't discuss it.
<mattam> O generally means maximal, and everybody uses the lowest upper bound (called Omega i guess)
<Smerdyakov> mattam, no, Omega is just "lower bound," not "lowest upper bound."
<mattam> oh
<Smerdyakov> mattam, if you want equivalence classes, you use Theta().
<liralen> I'd guess that I've always seen Omega(N) written as O(N), then.
<Smerdyakov> liralen, no.
<mattam> we haven't seen this notations, i miss them now :)
<Smerdyakov> You haven't? Have you taken an analysis of algorithms class?
<mattam> yep
liralen has left #ocaml []
<mattam> but we used french words to designate the different complexities
<Smerdyakov> Well, these are Greek letters. No more reason for you to Frenchize them than for us to Anglicize them. :P
<mattam> and i've not read any paper using other things than O yet
<Smerdyakov> O() is generall abused by almost everybody in CS.
<mattam> Smerdyakov: the reason is probably the prof. being incompetent in the matter, or the level being to low.
<Smerdyakov> mattam, do you know the definition of O(), then?
<mattam> so, let me resume: Omega(N) is lower bound and O() is upper bound, and Theta() is exact complexity ?
<Smerdyakov> That sounds about right. I feel like Theta() should divide all functions into equivalence classes, but I don't exactly remember a proof of that.
<mattam> i see
gl has joined #ocaml
<pattern> hadaka, you said: how you can avoid such stuff is that you build the list in reverse - and give the reversed list up to that point as a parameter to the recursive function - and then in the end reverse the list
<pattern> i have: # let rec revlist = function
<pattern> [] -> []
<pattern> | x::xs -> ( revlist xs ) @ [x] ;;
<pattern> val revlist : 'a list -> 'a list = <fun>
<pattern> so how can i "give the reversed list up to that point as a parameter to the recursive function"?
<Smerdyakov> pattern, what source are you using to learn functional programming?
<mattam> let revlist =
<Smerdyakov> pattern, because the idea of "accumulators" is very fundamental, and it's probably best if you just read a standard treatment of it.
<mattam> let rec aux reversed_list =
<mattam> ???
<pattern> smerdyakov, i understand how you create an accumulator, i just don't see how it applies here
<mattam> in aux []
<Smerdyakov> pattern, then you don't understand accumulators.
<pattern> i understand them, i just can't come up with one
<pattern> there's a difference
<mattam> pattern: you can write reverse with the skeleton i wrote
<pattern> mattam, that just seems to me like putting the whole of revlist in the aux function
<Smerdyakov> Well, I mean to say that you don't understand the way to use accumulators, then, which includes coming up with how to use them.
<mattam> not exactly, aux has an accumulator as first argument
<pattern> obviously this is the case
<pattern> (that was to smerdyakov, btw)
<Smerdyakov> If you know how to code this in an imperative language, you should know how to code it functionally.
<Smerdyakov> Mutable variables all become function arguments.
<pattern> smerdyakov, this isn't helpful
<mattam> pattern: what would be the second argument of aux ?
<pattern> mattam, aux has a second argument?
<mattam> yeah, aux [] is a partial application
<mattam> you need to use the list to reverse somewhere!
<pattern> hmm
<Smerdyakov> pattern, can you explain in words the strategy to write a list reverse that runs in linear time?
<pattern> i need to perform the recursive step last
<Smerdyakov> So you can't explain the strategy in English in a vague way?
<pattern> even vauger than i already did?
<Smerdyakov> Than you already did where?
<pattern> that was a joke :)
<Hadaka> pattern: let rec splitlines ll acc = match ll with [] -> List.rev acc | x::xs -> let splitline = Str.split ( Str.regexp delimiter ) x in splitlines xs ( splitline :: acc )
<Hadaka> might be full of mistakes and typos
<pattern> thanks, hadaka
<Hadaka> pattern: but I suggest you listen to Smerdyakov - learning to use accumulators properly is a very important thing
<pattern> yeah, that's what i mean to do
<Hadaka> I had many nice moments when trying to come up with the "optimal" implementation of List.remove_nth
<Hadaka> the naive implementation ofcourse isn't tail recursive
<pattern> so my strategy for writing a list reverse in linear time would be to pass the tail element of the list to an accumulator function, which then accumulates the reversed list up to that time, and then take this value and recursively call the accumulator function
<pattern> i guess
<pattern> no, i don't even know
<pattern> it accumulates the reversed list so far, that much i know... but what do i do with it? and how is calling an accumulator function any more tail recursive than just calling the regular function?
<pattern> let rec revlist l =
<pattern> let rec aux reversed_list = function
<pattern> [] -> []
<pattern> | x::xs -> ( aux [x] xs ) @ reversed_list
<pattern> in
<pattern> aux [] l
<pattern> but this doesn't even work right
<pattern> # revlist [1;2;3];;
<pattern> - : int list = [2; 1]
<Smerdyakov> The accumulator is not a function.
<Hadaka> pattern: and '@' is not tail-recursive
<Smerdyakov> This is how you reverse a list in linear time:
<pattern> i meant auxiliary function
<Smerdyakov> Keep an intermediate list.
<pattern> with an accumulator
<Smerdyakov> Step through the elements of the input list in order.
<Smerdyakov> As you hit each one, add it to the front of the intermediate list.
<Smerdyakov> When you're done, return the intermediate list.
<pattern> if you add each element of the list to the **front** of the intermediate list aren't you just creating the same list in the same order?
<pattern> oh, nevermind
<Hadaka> *bling*, lightbulb :)
<pattern> :)
<pattern> i still have to write this... but the verbal description does make it easier
<pattern> thanks, smerdyakov
<Smerdyakov> :)
<pattern> let rec revlist l =
<pattern> let rec aux reversed_list = function
<pattern> [] -> reversed_list
<pattern> | x::xs -> aux ( x::reversed_list ) xs
<pattern> in
<pattern> aux [] l
<pattern> # revlist [1;2;3];;
<pattern> - : int list = [3; 2; 1]
<Hadaka> pattern: yup - except that your revlist doesn't need to be a recursive function anymore as you can see :)
<pattern> oh,right
<pattern> thanks for your help, everyone
<Hadaka> no problem :)
<pattern> i'm going to get some food and then i'll try to tackle the rest of my functions to make them tail recursive
cjohnson has quit ["Drawn beyond the lines of reason"]
buggs^z has joined #ocaml
buggs has quit [Read error: 60 (Operation timed out)]
Kinners has left #ocaml []
cjohnson has joined #ocaml
cjohnson has quit ["Drawn beyond the lines of reason"]
det has quit [orwell.freenode.net irc.freenode.net]
clog has joined #ocaml
ejt has joined #ocaml
async has joined #ocaml
rox has joined #ocaml
TheDracle has joined #ocaml
Etaoin has joined #ocaml
buggs^z has joined #ocaml
lam has joined #ocaml
Vjaz has joined #ocaml
phubuh has joined #ocaml
pattern has joined #ocaml
themus has joined #ocaml
Hadaka has joined #ocaml
Banana has joined #ocaml
smkl has joined #ocaml
Nutssh has joined #ocaml
Riastradh has joined #ocaml
mattam has joined #ocaml
anpanman has joined #ocaml
<pattern> how can i implement this function tail recursively?
<pattern> let rec channel2lines channel = try
<pattern> let line = input_line channel in
<pattern> line :: channel2lines channel
<pattern> with
<pattern> End_of_file -> []
<pattern> try...with constructs can't be made tail recursive, i am told
<pattern> normally i'd just handle the exception one level up
<pattern> but here it is integral to the function
<Nutssh> Use an accumulator -- you'll get the list in reverse order, so you'll need to reverse it at the end.
<pattern> but an accumulator isn't enough, as i need to know when i reach the end of file
<pattern> and that requires catching an exception
<pattern> i found something about this on the mailing list, though...
<Hadaka> pattern: was just writing up a similar example
<Smerdyakov> You don't need to catch the exception through any recursive calls, though.
<Hadaka> my version looks like this:
<Hadaka> let channel2lines channel =
<Hadaka> let rec aux acc =
<Hadaka> let line = try Some (input_line channel)
<Hadaka> with End_of_file -> None in
<Hadaka> match line with
<Hadaka> Some x -> aux (x :: acc)
<Hadaka> | None -> acc in
<Hadaka> List.rev (aux []);;
Nutssh has quit [Client Quit]
<Hadaka> though, in such cases, being imperative might just be easiest
<pattern> functional programming is not about being easy
<pattern> it's about being hard! ;)
<Hadaka> bah
<pattern> hehe
<Smerdyakov> I think input_line should return string option in the first place.
<pattern> yeah, that would make sense
<pattern> maybe writing a function to do that would work as a stop-gap measure
<Smerdyakov> Reaching the end of a file is hardly an exceptional condition.
<pattern> input_lineo
* Riastradh agrees, too.
* Hadaka doesn't agree.
<Riastradh> Well, you're wrong, then, duh!
<Hadaka> :)
<Riastradh> On a serious note, why don't you agree?
<Hadaka> well, take for example the toplevel loop
<Hadaka> it reads lines from input and operates on them
<Hadaka> getting end of file is about as exceptional as getting Interrupt
<Hadaka> besides, I don't enjoy an interface that needlessly complicates the successful fetching of a line just because there might not be a line waiting
<Hadaka> (or, end of file reached, as it is)
<Smerdyakov> I don't follow.
<Smerdyakov> In most situations, you're needlessly complicated by needing an exception handler.
<Smerdyakov> With the difference that the compiler won't remind you if you forget it.
<Hadaka> the decision what to do while processing lines has hardly anything to do what to do when the end of input is reached
<Hadaka> end of file is a toplevel decision, like interrupt is
<Smerdyakov> That doesn't make much sense to me. This involves what to do when processing series of elements that either indicate new lines or absences thereof.
<Riastradh> Interrupts are _very_ different from EOFs.
<Hadaka> well, normally you get some lines, and then you get an EOF - and then that channel is closed, nothing more - it's not an alternating situation that sometimes there are lines, sometimes not
<Riastradh> Should getting to the end of a list signal an exception, too?
<Hadaka> well, a function 'input_elem list' should throw an exception No_more_elements at the end of the list
<Hadaka> (if list reading would be destructive, that is)
<Riastradh> Right, but when simply writing a recursive list processor, should the destructurer of the list signal an exception when you get to the end?
<Riastradh> It's not like an alternating situation!
<Riastradh> EOF & empty list (or 'EOL') are _much_ more analogous than EOF & interrupt.
<Hadaka> um, I'm not sure what you are referring to by destructurer - but the function getting the next list element should throw an exception - and if the destructurer uses that, then yeah, it should do that
<Riastradh> Pattern matcher.
<Hadaka> but pattern matching isn't destructive
<Riastradh> match list with [] -> ... | (x::y) -> ...
<Riastradh> The term 'destructive' has nothing to do with the term 'destructure.'
<Hadaka> I mean that if you match x::y on a list, that doesn't remove x from the list
<Hadaka> input_line channel removes a line from the channel, so to speak
<Riastradh> For the rest of the iteration, it _has_ removed x from the list. The only difference is that the list hasn't _externally_ changed.
<Hadaka> let (input_elem : 'a list ref -> 'a) l = match !l with h :: t -> l := t; h | [] -> End_of_list;;
<Riastradh> ...er, what does that have to do with anything?
<Hadaka> well, don't you agree that that is a rather natural way to implement input_elem? or would you rather have it return Some h and None instead of End_of_list exceptoin?
<Hadaka> whops, forgot a raise there
Nutssh has joined #ocaml
<Hadaka> and as for
<Hadaka> try match x with h :: t -> do_something with Match_failure -> do_something_else; or something similar
<Hadaka> is ofcourse horribly ugly, but it is a sane way to write a function if the end of the list is has nothing to do with the list processing
jdmarshall has joined #ocaml
<Hadaka> well anyway, opinions differ, I guess
<Riastradh> I don't understand why you would possibly want such functions.
<Riastradh> [[match input_line channel with Some line -> ... | None]] for an input loop is equivalent to [[match list with head :: tail -> ... | [] -> ...]] for a list processing loop, except that the state for input_line is implicit.
<Hadaka> if input_line would return None at end of file - you still would need to handle it exceptionally, since you can't just keep reading values from there, you have to stop reading from it
<Riastradh> Rather, it's _already_ equivalent; you don't need a convoluted extra function such as your input_elem.
<Hadaka> but in the None branch you have to break the loop or recursion in which you are reading input_lines
<Riastradh> Do you honestly write recursive list processing functions that _always_ signal exceptions at the end of the list? (Certainly if some condition were not satisfied by the end of the list an exception would make sense, of course -- that's why I specify 'always' --.)
<Hadaka> well certainly not always!
<Riastradh> Do you write them to use destructurers that signal exceptions rather than just using conditional destructuring?
<Hadaka> I have written more destructurers that use conditional destructuring
<Riastradh> So why are you suggesting that recursive line input processing functions _always_ deal with exceptions?
<Hadaka> Why are you suggesting that recursive line input processing functions _always_ return optional values?
<Riastradh> ?
<Riastradh> Please answer my question first, actually.
<Hadaka> If input_line throws exceptions, you have to wrap it in a Some / None generator
<Hadaka> if input_line returns Some / None, I have to throw an exception when None is returned
<Riastradh> The _exact_same_thing_ is true with lists.
<Riastradh> But do you object to using match instead of something like [[function [] -> raise End_of_list | head :: tail -> (head, tail)]]?
<Riastradh> Indeed, that function there itself uses match! (implicitly)
<Hadaka> I am not advocating against not using matches in such operations? And yes, every function can be seen to be a match if we go that far even
<Hadaka> Urh. Let's take a code example
<Hadaka> straight from toploop
<Hadaka> let loop ppf =
<Hadaka> let lb = Lexing.from_function refill_lexbuf in
<Hadaka> while true do
<Hadaka> let phr = try !parse_toplevel_phrase lb with Exit -> raise PPerror in
<Hadaka> with
<Hadaka> | End_of_file -> exit 0
<Hadaka> | Sys.Break -> fprintf ppf "Interrupted.@."; Btype.backtrack snap
<Hadaka> done
<Hadaka> (skipped all the boring lines)
<Hadaka> now here, the lexing buffer is read from several different places inside parse_toplevel_phrase - until enough lexing tokens are satisfied to get a complete phrase
<Hadaka> and in all cases, the response to End_of_file is the same
<Riastradh> Sure. It makes perfect sense that parse_toplevel_phrase might signal an exception indicating that it got an unexpected EOF.
<Hadaka> Now, if the lexing input functions would return Some / None
<Riastradh> But that's definitely not the same as input_char or input_line signalling EOF.
<Hadaka> then all the places were stuff is read would need to match (input lb) with Some x -> do something | None -> raise End
<Hadaka> s/were/where/
<Riastradh> Just as one of your list processors might signal an End_of_list, but _in_the_processor_ you destructure with match and don't use an exception-based destructurer, parse_toplevel_phrase might signal End_of_file, but it needn't be based on a destructurer that signals exceptions to indicate different cases.
<Hadaka> No, it doesn't _need_ to be
<Riastradh> Do you agree with the first half of that sentence?
<Hadaka> Yes
<Riastradh> Then why do you object to having s/needn't be/isn't/1 in the second half of the sentence?
<Riastradh> (if that question makes sense...)
<Hadaka> I tried to explain it above
<Hadaka> because if that is so, then all the places reading the input need to either use a wrapper for the function - or handle None specially
<Riastradh> Wrong. I am _not_ suggesting that any function that performs input on a channel use [['a option]]. I am suggesting that the _base_ functions use them and the processors _atop_ them use exceptions.
<Hadaka> The base function _is_ input_line - most people can use that without wrapping it into a separate function to perform input - where as if it returned None, then they would need to wrap it in a function to use it effectively
<Riastradh> What do you mean 'wrap it in a function?'
<Hadaka> Okay, code example time again
Herrchen has joined #ocaml
<Hadaka> match (input_line stdin) with
<Hadaka> "foo" -> ( match (input_line stdin) with
<Hadaka> "bar" -> "hellurei"
<Hadaka> | _ -> "hallurei" )
<Hadaka> "gah" -> ( match (input_line stdin) with
<Hadaka> "bar" -> "kukkuu"
<Hadaka> | _ -> "puppuu" )
<Hadaka> now consider that if input_line returned string option
<Riastradh> match input_line stdin with
<Riastradh> Some "foo" -> match input_line stdin with ...
<Riastradh> ...
<Hadaka> this whole match block would naturally be surrounded by a while true loop, and a try clause above that
<Hadaka> you skipped the None cases
<Riastradh> _ -> raise Input_failed
<Riastradh> ...or whatever.
<Hadaka> yes, so you have to write the raises inside those matches, which bloats up the code
<Riastradh> Not by much.
<Riastradh> It's unlikely that you'd use those kinds of matches anyways.
<Riastradh> And why couldn't you just catch the Match_failure exception, anyways?
<Hadaka> You see, when a function returns Some / None, it forces the calling function to deal with the option cases right away - when you use an exception, you give the possibility for _any_ parent to do the code
<Hadaka> because depending on Match_failures is mucho ugly
<Riastradh> It's _no_different_ from using End_of_file exceptions.
<Hadaka> And I am saying most of the code that uses input_line is more or less what is written there
<Riastradh> try (... match input_line with Some x -> ... | Some y -> ... ...)
<Riastradh> with Match_failure -> ...
<Riastradh> versus
<Riastradh> try (... match input_line stdin with x -> ... | y -> ... ...)
<Riastradh> with End_of_file -> ...
<Riastradh> (er, I missed a 'stdin' in that first one)
<Hadaka> Oh come on, if there's a complex program and you catch exceptions near the top loop, a Match_failure can result from *anything*
<Hadaka> where as End_of_file results from only end of input
<Riastradh> Uh, the same can be said of End_of_file.
<Hadaka> Well, that's the point
<Hadaka> you catch any End_of_files, from where-ever in the code they may happen
<Hadaka> and you catch them all in the same place, without bloating the other function with that code
<Riastradh> Compiler warnings can alert you of points where match may fail, too, and you can ignore them in such places as these. Can't say that of EOFs.
<Hadaka> Well, if the only function of EOF is to terminate your program, you don't even need to catch it
<Riastradh> ...but then it might be caught higher up. The same can be said of match failures.
<Hadaka> If End_of_file gets caught higher up, then usually that's a good thing - if Match_failure gets caught higher up, then something is usually awry
<Hadaka> an End_of_file is not a locally processed event in most cases
<Riastradh> If End_of_file gets caught higher up, how is that a good thing? You've suddenly caught an End_of_file, you have no clue where it was raised from, and you don't even have an idea what channel received an EOF.
<Hadaka> End_of_files are usually caught at the level of the loop on the channel - and the actual input operations often happen somewhere several levels lower
<Hadaka> in the case of a program reading only stdin, the loop most probably is the mainloop the program runs in
<Riastradh> Also, you haven't given me anything beyond a contrived example of where an End_of_file exception [doesn't actually] simplify things.
<Hadaka> Let me find an example from the book or something
<Hadaka> though I think the interactive toplevel loop is a good example already
<Riastradh> No, it's not.
<Riastradh> The parse_toplevel_frobnication example demonstrates a function where an unexpected EOF is indeed an _exception_ to the ordinary flow of the parsing; it does _not_ demonstrate that this is the same behaviour that the _base_ input functions should have.
<Riastradh> Is the example in that URL you just posted the translation function used in the loop in go?
<Hadaka> yes, the input_char used there
<Riastradh> OK. The _ONLY_ change you'd make to use an input_char that instead returned [[char option]] would be to change all cases but the last in the match expression in translation to use Some.
<Hadaka> okay, so what is done with the None case?
<Riastradh> Er, and you'd add a None case that tells the calculator to exit.
<Riastradh> (Or raise Key_off, in other words.)
<Hadaka> So you end up writing that handling to where the input is read, instead of just having a simple input without a match and then catching the end of file at the same level Key_off is caught
<Hadaka> when you are reading a key from the input, you are interested on what you wish to do with the key - the end of input case is what you are interested in while coding the toplevel loop of the program
<Riastradh> Actually, you wouldn't even do that; the current calculator doesn't handle EOFs at all, and you'd preserve those semantics by adding no cases for None!
<Hadaka> well, sure the example omits End_of_file handling entirely - which would be an extra line next to Key_off match
<Hadaka> Hmm...
<Hadaka> I think what might be a contributing factor in the argument is that I consider throwing an exception or return Some / None completely interchangeable - you can make one from the other - and neither is more _base_ operation than the other
<Hadaka> and the only thing dictating the choice would be what the common usage is
<Riastradh> If you're using [[match (try Some (frobozz garglemumph) with End_of_file -> None) with Some x -> ... | None -> ...]] frequently -- as examples such as pattern's do --, the original frobozz API should probably have used the option type.
<Hadaka> but then again, if you are throwing exceptions from the None results frequently, shouldn't the API normally throw an exception then?
<Riastradh> Not necessarily. If the _abstractions_ atop that API -- in the list analogy, general functions such as fold, map, and filter -- tend to raise exceptions, then probably; but if not, and only your _specific_ code -- in the toplevel loop example, parse_toplevel_furblinity -- tends to raise such exceptions, then the API should use option.
<Hadaka> but in this case, exceptions should be raised whenever End_of_file is encountered, whereever
<Riastradh> No, just as list processing functions don't raise End_of_list all over the place.
<Hadaka> but they are completely interchangeable - depending on which one is needed more
<Hadaka> let input_line_from_exc channel = try Some (input_line channel) with End_of_line -> None;;
<Hadaka> let input_line_from_option channel = match (input_line channel) with Some x -> x | None -> raise End_of_file;;
<Hadaka> and the deciding factor can be either number of character in code, or code clarity, or consistence, or whatever
<Hadaka> List.hd throws an exception as well
jdmarshall has quit ["ChatZilla 0.9.35 [Mozilla rv:1.5/20031007]"]
<Hadaka> should List.hd return Some / None?
<Riastradh> List.{hd,tl} are two of how many abstractions?
<Hadaka> List.hd is pretty damn close to input_line in my opinion on how it is used
<Hadaka> (with the difference that input_line eats from the channel, which we already discussed)
<Riastradh> The _point_ of List.{hd,tl} is to say 'I want its head, NOW.' Something is obviously wrong if the head isn't there.
<Hadaka> No.
<Hadaka> Something is _exceptional_ if the head isn't there.
<pattern> wow, you've been going at it for an hour and 20 mins... kudos!
<Hadaka> :)
<Riastradh> The difference between option and exceptions is locality. Abstractions & the basis should focus on being more 'local,' whereas your specific operations are specific to your program, over which you have global control, and for which it is more convenient to handle the condition elsewhere.
<Riastradh> Using option is like saying 'is it x? -- ok, do this; fine then, it isn't: do that.' Using exceptions is saying 'do this...oops, something went wrong; hey, exception handler! do something about it!.'
<Riastradh> s/went wrong/is exceptional/1 if you insist.
<Hadaka> Well here we agree mostly
<Hadaka> Just that I think if the condition happening from the function is most often _not_ handled locally, the interface should throw an exception
<Riastradh> In the base functions and the abstractions, it's not necessarily known which one the clients want; the latter is a _subset_ of the former (conceptually), though, so they should therefore use options.
<Hadaka> Neither is the subset of either - they are interchangeable, like the two lines I pasted bit up there
<Riastradh> (Er, 'latter' & 'former' there refer to 'exception' & 'option,' respectively.)
<Riastradh> That's why I said _conceptually_.
<Riastradh> 'Is it x? -- ok, do this; fine then, it isn't: something went exceptional; hey, exception handler! do something about it!'
<Hadaka> Well ofcourse - exceptions are nothing more than glorified return value passing from things
<Hadaka> but I don't think that makes a difference - I think the common usage makes the difference
<Riastradh> Right: and when the common usage of the base & abstractions over the basis are typically used with the former mentality, _regardless_ of whether they _really_ use option or exception, they ought to use option.
<Riastradh> It doesn't matter how your own application-specific routines, such as parse_toplevel_gobbledigook, perform abstractions; that's an entirely different class of operation than input_char or input_line.
<Hadaka> hmmh, that was a bit hard to parse - but if I got it right, then I do agree with that - but I also think that in the case of input_line, the common usage of base & abstractions is to just raise / let the exception pass through, hence the function should already throw an exception
<Riastradh> Can you cite a majority of examples where input_line is used more frequently with the exception mentality than the option mentality?
<Riastradh> Er.
<Riastradh> Let me rephrase..
<Riastradh> Can you cite a set of examples where the subset such that input_line is used with the exception mentality has a majority over the subset such that input_line is used with the option mentaliyt?
<Riastradh> Mentality, even.
<Riastradh> s/such that/wherein/g
<Hadaka> Well, I haven't seen a single example from you yet where input_line wouldn't be used with the exception mentality - all the examples I have given so far have used input functions with the mentality that they throw exceptions
<Riastradh> That's because I rarely write OCaml code, and I don't like the design of its API anyways -- I'd prefer much more control over it, anyways; cf. http://www.bloodandcoffee.net/campbell/code/crlf-io.scm for line I/O over which the programmer has good control --; you've given only a couple examples so far, both of which fall under those application-specific abstractions.
<Hadaka> well, there we have our disagreement - I would say 90% of the programs that end up using input_line do use it mostly in the ways of the examples I wrote
<Hadaka> (reading the link)
<Riastradh> (READ-STRICT-CRLF-LINE's LOSE argument could be converted into raising a condition object instead; the idea is to use it with the exception mentality.)
<Hadaka> that looks like a rather nice interface - but it also looks lower level and more fine-grained than something like input_line - more akin to 'input' and so
<Riastradh> That's why READ-{STRICT,LENIENT}-CRLF-LINE exist: for when you don't need that fine granularity.
<Hadaka> well, even those are more fine grained than input_line
<Riastradh> (Actually, it suddenly occurs to me that READ-LENIENT-CRLF-LINE ought to report whether it got a line ending or an EOF.)
<Hadaka> oof, time for me to head to bed, gnight all
<Riastradh> Me too.
pattern has quit [Read error: 113 (No route to host)]
pattern has joined #ocaml
Nutssh has left #ocaml []
pattern has quit ["Reconnecting to server - dircproxy 1.1.0"]
pattern has joined #ocaml
Herrchen has quit [Read error: 110 (Connection timed out)]
_JusSx_ has quit ["[BX] Elvis has left the building"]
<pattern> how do i pipe something to the stdin of a program being run under ocamldebug?
<Banana> set arguments < input-file
<Banana> (according to section 16.8.1 of the manual).
<pattern> cool :)
Kinners has joined #ocaml
<pattern> i looked at that, but i assumed that arguments did not include pipes
<Banana> To debug programs that read from standard input, it is recommended to redirect their input from a file (using set arguments < input-file)
<pattern> this is interesting...
<pattern> ahh
<pattern> missed that
<pattern> (ocd) run
<pattern> Loading program... done.
<pattern> Lost connection with process 16011 (active process)
<pattern> between time 3730000 and time 3740000
<pattern> Trying to recover...
<pattern> Time : 3730000 - pc : 26000 - module String
<pattern> 41 <|b|>if ofs < 0 || len < 0 || ofs > length s - len
<pattern> why would it "lost the connection" with the process?
<Banana> so either you can write the input in a file before running the program either you make input-file a named pipe and echo command into it.
<pattern> yeah, that makes sense, banana.. thank you
<pattern> well, after i run my program under the debugger it runs for a while and then complains about losing the connection with the process, and then stops somewhere in the string module
<pattern> but i haven't set any breakpoints
<pattern> so i'm confused about why it's losing the connection with the process (or exactly what it means by that), and why it would stop even though i set no breakpoints, and it doesn't seem to have terminated either
<pattern> or maybe it did terminate in the string module... hmmm
det has joined #ocaml
<Banana> pattern: your program might have ended with an error like accessing String or array out of bound.
<Banana> (if compiled with -unsafe).
<pattern> i didn't use -unsafe
<pattern> but now i'm seeing there's a stack overflow somewhere
<pattern> is List.map tail recursive?
<Banana> yes.
<pattern> no, actually it's not
<pattern> i just looked in the mli
<Banana> ho ?
<pattern> "Not tail-recursive."
<Banana> ok.
<Banana> I mistake it with something else.
<Banana> like rev_map.
<pattern> yeah
<pattern> i just saw that
<pattern> ok, that was it
<pattern> weird that rev_map didn't seem to reverse my list
<pattern> ahhh
<pattern> rev_map only reverses the returned list
<Banana> yes.
<pattern> i guess application to each element of the list is still done in the same order as regular map
<Banana> yes.
<pattern> ok
<pattern> that's cool... i don't use the returned list anyway
<Banana> ?
<Banana> you print something ?
<pattern> i just use it to print
<pattern> yeah
<Banana> then List.iter
<pattern> ahh
<pattern> is that tail recursive?
<Banana> it's tail rec and in the right order.
<pattern> nice
<pattern> :)
<Banana> (and doesn't alloc a new list that goes to garbage anyway :) )
<pattern> perfect
<pattern> tracing down all of these stack overflows is kind of annoying
<pattern> seems to be one of the tradeoffs for using recursion vs iteration
<pattern> don't have the off by one errors, but have to be careful to make the routines tail recursive
<pattern> at least the stack overflows are obvious
<pattern> off by one errors could lead to more subtle bugs
<Banana> yeah.
<Banana> it reminds me of a story, of a student who wanted to detect cycles in a graph.
<Banana> he did use a recursive (non tail) function to inspect the graph and catch the StackOverflow exception.
Herrchen has joined #ocaml
<pattern> on purpose?
<Banana> yes.
<pattern> kind of makes sense
<Banana> yeah but pretty ugly.
<pattern> of course, just because it overflows the stack doesn't mean that it would never have terminated
<Banana> you can just keep track of the traversed vertexes.
<pattern> maybe increasing the stack size would have have allowd it to terminate
<Banana> but it seemed bold and brave to me to have such an idea.
<pattern> yeah
<pattern> it's cool
<Banana> well in fact it's terribly ineficient and realy ugly programming style but...
<pattern> it's a hack
<Banana> yes.
<Banana> what are you programming by the way ?
<pattern> oh, something i've already implemented in perl
<pattern> i wanted to do it in ocaml, as practice
<Banana> he he.
<pattern> and i wanted to use lists, instead of arrays, though arrays would be more natural
<pattern> the final problem is to calculate the zscores of a series of numbers which are in a column in a comma seperated file, and then put the zscores back in, either substituting the original column or adding a new column
<Banana> zscores ?
<pattern> so what i just finished doing was creating a matrix using a list of lists, representing rows and columns
<pattern> zscores are a statistical measure
<Banana> ok.
<pattern> and one of my functions makes sure every row has the same number of columns as the first row
<pattern> but it's overflowing the stack for some reason
<pattern> the only thing i can see is that it's using List.fold_left, but that's supposed to be tail recursive
<pattern> at least there's no warning that it's not tail recursive in the mli
<pattern> the zscore of a value tells you how many standard deviations you are away from the average value in a series
<Banana> why not use List.lenght instead of countcols ?
<pattern> probably because i haven't really started reading through what ocaml's libraries have to offer :)
<Kinners> pattern: enclose the else block in begin/end or () ?
<Banana> and just this piece of code Stack_overflows ?
<Banana> how big are your matrices ?
<pattern> good eyes, kinners!
<pattern> bannana, 70k+ rows, 9 columns, up to 20 chars per column
<pattern> so what was going on with that function? what did ocaml think i meant with that dangling exit?
<Banana> it put it in sequence after the match with.
<Banana> because ; has a low priority.
<pattern> interesting
<pattern> i actually remember something about a warning to put complex if/then/else clauses in begin/end blocks, but forgot
<pattern> thanks for your help, guys
<pattern> now, here's a logistics question... my program is shaping up to be a collection of all sorts of mostly unrelated functions
<pattern> so it's turning in to a big messy file
<Banana> hum just thinking but you could use a failwith "blah" instead of print and exit.
<pattern> i'd create a module if i had enough related functions, but what do i do with all of these miscellaneous functions?
<Banana> well I see some logic in your program...
<pattern> banana, yeah, i'd have to think of a good way to do that, because a recursive call within a try/with block isn't tail recursive
<pattern> yes, there is logic
<Banana> a module Parse which reads the file.
<pattern> it's just that there are too many little functions everywhere
<Banana> a module Stat or something which compute the values.
<Banana> and a main.ml
<pattern> that's a good idea
<Banana> pattern: dont put the try catch in this function.
<pattern> why not?
<Banana> put the try catch in your main and exit the program there...
<pattern> oh yeah
<pattern> i was doing that for some other exceptions
<pattern> just got a bit confused because of a function which recursively read lines from a file used the exception to detect eof, and that had to be in the function itself
<pattern> but with this one you're absolutely right, i could just catch it one level up
<Kinners> one technique is to do, match (try Some (foo x) with End_of_file -> None) with Some x -> ... | None -> ...
<pattern> ocaml's so much more fun when there're more people involved :)
<pattern> kinners, yeah, that's what i wound up doing
<Banana> using exception for eof and so is necessary because you don't have null pointers or thing like this
<pattern> thank goodness
<Banana> he he.
<pattern> so actually, my perl implementation of this wasn't all perl... it was actually a bunch of perl scripts linked by a shell script that wound up creating a huge mess of intermediary directories because i didn't want to deal with a ton of associative arrays in perl
<pattern> this should be somewhat cleaner
<pattern> so what are you guys working on?
<Banana> actually i'm not on heavy dutty with ocaml. I use Coq mainly.
<pattern> what's that?
<Banana> Coq is a proof assistant written in ocaml.
<pattern> ahh
<pattern> i've heard ML was originally designed as a metal language for a theorem prooving engine
<pattern> meta
<Banana> it's syntax is similar to ml in many ways though
<pattern> cool
<Banana> what is nice in coq is that, if you give a proof of a property, then it can extract the Ocaml code that computes that property.
<Banana> (ex : you give a proof of quick sort and you have the ocaml function quicksort ready).
<Kinners> Full Metal Language!
<Banana> ;)
<pattern> at the end of ML for the Working Programmer they implement a theorem proover... but i have a looooong way to go before i get there
<pattern> apocalypse caml
<Banana> one of my teacher spent a month recoding the Set module of ocaml using Coq and found a bug :)
<Banana> (that has been corrected).
<pattern> nice
<Banana> there was a problem in the rebalacing of the tree.
<pattern> so you can use the theorem prover on code?
<Banana> well not excatly you have to translate the code into a theorem (which is easy for purely functional programs).
<pattern> i see
<Banana> there is an assistant to do that but there is still many to do.
<Banana> An interresting subject is writing a compiler directly in coq (or give a proof of the compiler in coq).
<pattern> that sounds fun
<mattam> that sounds like a whole life's work :)
<Banana> that's Xavier Leroy new objective, within the Concert project.
<Banana> ^_^
<pattern> to write a compiler with coq?
<Banana> yeah something like that.
<Banana> the main problem is that you have to write your compiler in a purely functionnal style.
<pattern> just to be sure it was foolproof?
<pattern> or full of proof? ;)
<Banana> to ensure that it doesn't introduce any bugs while translating from C to Asm for exemple.
<pattern> interesting
<Banana> more thant that, to ensure that the semantic of your program is kept.
<Banana> (so you have to define the semantic of a C program and the nightmare starts here :)
<pattern> that's definitely far beyond me
<pattern> i'm not even sure how semantics translate between languages
<Banana> nobody is, that's the problem :)
<pattern> well, at least they can understand the problem, if not the solution
<Banana> pattern: don't worry the theorem proover exercise is not that hard.
<pattern> so if they're not sure, then is what xavier is working on even possible?
<Banana> that's what is written on the description of the summer intership with Inria : the aim is to determine WHETER or NOT it is possible to give full proof of a compiler.
<pattern> cool
<Banana> (and actually wether or not there is a phd thesis for guys like me after ;) )
<pattern> you're going to be working there?
<Banana> but they have strong arguments to think it's feasable.
<Banana> maybe.
<pattern> awesome!
<Banana> waiting for the answer.
<pattern> good luck, banana!
lordjim has joined #ocaml
<Banana> yeah. it's a pretty stressing time, just after you meet people and wait for answers.
<pattern> yeah, i hate looking for work
<Banana> well. it'll work out someout.
<pattern> very stressful
<pattern> yeah, at least if you have the chance to get in there you must be really good
<pattern> so you should have lots of options even if inria doesn't work out
<Banana> pattern: well that's not true...
<Banana> i was only the first to ask for a stage ;)
<pattern> a stage?
<Banana> internship
<pattern> ah
<Banana> (stage is the french word, sorry).
<pattern> were there many applicants?
<pattern> how popular is ocaml in france, btw?
<Banana> not when I went (we were 3 on the list) but.
<mattam> very popular among CS programming students.
<Banana> pattern: in universities it's widely used as a teaching langage.
<Banana> and some industrials like Matra or Dassault uses it.
<pattern> do you think it has a future as a mainstream language there?
<mattam> INRIA is comparable to the MIT or Berkeley's research laboratories i think.
<Banana> pattern: in industries you mean ?
<pattern> i mean in general
<pattern> as not just a niche language
<Banana> well in general i think yes because there are more and more libraries available.
<Banana> the only thing is to learn people functionnal programming.
<Banana> and teaching in france has evolved that way.
<Banana> (10 years ago, the compilation lecture was using C to implement the compiler.... now it's Ocaml).
<pattern> yeah, i have a good feeling about it too... but it could be just wishful thinking
<Banana> i think there is just need for some "big flashy applications" to lead the way.
<pattern> right, ocaml definitely is very highly regarded as a language for writing compilers and the like... that is one of the niches where it is successful
<pattern> like what?
<Banana> mldonkey ?
<Banana> :D
<pattern> :)
* mattam goes back to writing a killer app in o'caml :)
<Banana> just kidding.
<pattern> that's been out for a while, though
<Demitar> And unison. :)
<Banana> yes.
<mattam> unison is great
<pattern> i was wondering what could be useful for a beginning programmer to contribute
<Banana> I think a web browser (a good one, not like the mmm prototype) entirely written in ocaml could be great.
<Demitar> Well do you have any applications that need to be created, we could do them in ocaml instead. :)
<Demitar> Banana, I think a web browser would be a horrible choice. We don't need yet-another-web-browser to fall into disrepair.
<pattern> i was looking at somethign called PLEAC... where they've taken the Perl Cookbook, and implement it in various languages, including ocaml... it's only 7% done for ocaml, i think... and the snippets look simple enough... don't know how many people would actually use it, though
<Demitar> Consider gwml and efuns.
<Banana> Demitar: the problem is that we don't have any decent web browser.
<pattern> opera
<Demitar> Banana, we don't? I'm happy with epiphany/galeon. :)
<pattern> i love opera
<Banana> not free.
<mattam> konqui rules them all
<pattern> opera is free if you accept ads
<Banana> yeah galeon is the best but lack a few things...
<pattern> and i have an ad blocker ;)
<Demitar> pattern, not Free.
<pattern> yes, true
<pattern> but it is great
<Banana> what I meant was an end-user application.
<pattern> maybe i'd even pay for it
<Banana> like A flashy Desktop Environment in ocaml ;)
<pattern> just because i appreciate the work they put in to making such a high quality product
<mattam> Banana: that would be great
<pattern> desktop environment? like kde or gnome?
<Banana> with opengl resizing of windows and flash animation when moving the cursor and 3D p1x3l shadding when reading mail :DDD
<pattern> that's a huge project, though
<Demitar> Banana, well I have two applications I've been pondering. First a presentation application and second a dtp program. Both for gnome naturally. :)
<Banana> naturally :)
<mattam> *grin*
<Banana> mattam: i don't want to hear anythin :p
<Banana> arf
<Banana> :)
<pattern> a presentation application? like powerpoint?
<Demitar> pattern, yes, but better. :)
<pattern> cool
<mattam> we already have advi
<Banana> well there is advi, which is pretty good (and written in ocaml).
<Demitar> Banana, I had some plans to investigate how much of a web browser could be pushed onto the opengl pipeline.
<Banana> he he.
<Demitar> Yes, but it's not very useful for /creating/ presentations, now is it?
<Banana> but a front end to advi ala Lyx would be great.
<Demitar> Banana, the interesting part being the programmable interfaces of OpenGL 2.
<mattam> yeah, no in place WYSIWYG modifications
<Demitar> There we have something.
<Demitar> LyX and an advi frontend in ocaml using gnome.
<Banana> something that genereate latex or better directly dvi code.
<mattam> Demitar: there are special purpose interface primitives in OpenGL 2 ?
<Demitar> mattam, I'm probably using the wrong wording, but it's supposed to be more intelligent I think.
<mattam> oh, nice
<Demitar> Something which integrates LyX functionality, advi, HeVeA and HaChA into a single frontend.
<Banana> there is also the cairo/ocaml binding which i'm looking forward to.
<Banana> the problem is that cairo itself isn't that advanced, but it has a cool todo list ;)
<Demitar> Banana, ooh, cool vapourware? ;-)
<Banana> no, the guys at freedestop are pretty serious.
<Banana> but i'm waiting for the OpenGL backend to do the rendering, then it will be very nice.
<Banana> I also thought of a native gui for ocaml like AWT in java, but it's a huge work.
<Demitar> "Native" guis is evil. Go use gtk+. :)
<pattern> there must be some applicatoins which are popular but really suck, and that people don't mind using binaries for instead of compiling from source
<Demitar> pattern, sounds like java to me. :)
<pattern> those would probably be prime targets for writing better versions of in ocaml
<pattern> heh
<Banana> Demitar: i use/like gtk+ but it's steal a bit slow, I'm waiting for 2.4 version of gtk.
<pattern> well, maybe someone should write a jvm in ocaml
<Banana> still.
<Banana> pattern: it's already done i think.
<pattern> and java still sucks?
<Banana> yeah.
<pattern> bummer
<Banana> because the JVM is a STACK machine, not a register one.
<Banana> it's a technology inherited for year 1960. :|
<Banana> from year.
<pattern> well, silicon valley was always full of old hippies
<Banana> ;)
<Banana> I always wanted to do a cool WM in ocaml also.
<Demitar> Do any of you have some examples of really good ocaml library interfaces?
<pattern> oooh... how about an ocaml journal?
<pattern> people could write short articles for it... mini tutorials, reviews, rants...
<Banana> pattern: I think there was an Ocaml letter before but not anymore.
<Demitar> I'm making an interface to a dynamically typed protocol and providing typed interfaces.
<pattern> demitar, how about the standard ocaml library?
<Banana> I think I will recode something like metacity in ocaml. (I juste HATE Gnome UI guidelines, dammit let me use my desktop as I want )
<Banana> sorry.
<pattern> i just use fluxbox
<Demitar> Basically what I intend to do is: register_callback : (event -> 'a) -> ('a -> ()) -> id
<Banana> Demitar: maybe the GTK+/ocaml interface can help you to implement that.
<Banana> i mean reading their code can help.
<Demitar> Banana, actually metacity is quite foolish. There is no such thing as a "correct" behaviour in a window manager.
<Banana> yes that's why I think things should be more customisable like sawfish.
<Banana> but metacity themes are SO cool !
<Demitar> Banana, the annoying thing is that I'll end up with using classes simply to get the syntactic sugar.
<Banana> hum...
<Banana> you can uses modules instead no ?
<Demitar> I can but the additional typing would be unacceptable.
<Demitar> That is I *will* use modules, but I'll return classes to get a more convenient syntax.
<Banana> you want the native library to call a ocaml function ?
<Demitar> Hmm?
<Banana> your register_callback ?
<Banana> what's the problem ?
jesse_ has joined #ocaml
<Demitar> There is not much of a problem. :)
<Banana> ha ok.
<Demitar> Just a slight annoyance that the /only/ reason I'll use classes is to get the syntax.
<Demitar> Which is the only thing I ever use classes for in ocaml anyway.
<Demitar> Guess it's like polymorphic variants, sacrificing error reporting for convenient syntax.
<Banana> well I don't use either feature too often but... they have to be handy for someone :)
_JusSx_ has joined #ocaml
<Demitar> Well foo#bar is a lot more convenient than foo.Talk.bar and/or (Talk.bar foo).
<pattern> open talk ;)
<Demitar> pattern, will conflict, otherwise I would.
<pattern> well, is there a way to transform the names in the module to some other names?
<Banana> pattenr no.
buggs^z is now known as buggs
<pattern> hmm
<Banana> it's ugly to use open.
<Banana> never ever.
<pattern> yeah, that's why the ;)
<Banana> ha.
<Demitar> The real problem with Talk.bar foo is that I remember too late I want to use it's result in another function and need to skip back to add the opening parenthesis.
<Demitar> Banana, except in some corner cases where you specifically provide a separate interface for that purpose. :)
<Demitar> MyModule.Pervasives. :)
<_JusSx_> e tu allora perche' non sei a nanna?
* Demitar hides from the italian?
<_JusSx_> sorry :) : wrong channel
<pattern> well, that sounds like a way of renaming the names in a module
<Banana> Demitar: don't.
<Banana> I'm.
<Banana> :D
<Banana> (half i mean).
<Demitar> pattern, you can always do let foo = ModuleWithAVeryVeryVeryLongAndAnnoyingName.foo in
<pattern> yeah
<pattern> so why not?
<Demitar> pattern, or entirely module M = ModuleWithAVeryVeryVeryLongAndAnnoyingName;;
<Demitar> pattern, since it defeats the purpose of being convenient, it's not convenient if I have to work around it.
<pattern> well, you'd only have to do it once, right?
<Demitar> Once in every file I use it. :) And I plan on having a lot of those modules.
<Banana> ok that's it lunchtime and afterthat the WM coding session begins >_<
Banana is now known as Banana[AFK]
<pattern> why not import a module like your MyModule.Pervasives example where the translations are done?
<Banana[AFK]> see you.
<pattern> bye, banana
<Demitar> pattern, since they will conflict, anyway this discussion is getting irrelevant. I should go use classes and get over it. :)
<pattern> heh
<pattern> well, i don't see how they'd conflict if you renamed them to what you want... but, i should get going myself
<pattern> it's almost 5 in the morning here... i should sleep
<pattern> good luck, demitar!
<Demitar> pattern, oh, I'm likely to share lots of attribute names in the different records.
<pattern> ah
<pattern> that's a problem
<Demitar> And just perhaps I could actually make use of inheritance. :) But I did it once and I got a 3000 line file which took minutes to compile and the .cmi used megabytes. Not to mention it took a *lot* of time to even start the application.
<pattern> yuck
<pattern> sounds like java
<Demitar> Switching all those over to a single class getting passed a record of values fixed all that. :) But the interface is really clunky and not extensible.
<Demitar> Which is the reason I'm investigating this other approach.
<pattern> well, it does sound like you need it
<pattern> i haven't learned oo yet, much less ocaml's oo features, so i don't really understand how it'd help, but i'll take your word on it :)
<pattern> anyway, i'm off to sleep
<pattern> see you
<Demitar> Well the fact that I'm using a dynamically typed protocol greatly complicates the interface. :)
<Demitar> Goodnight.
<pattern> night
<Demitar> Or morning? :)
<pattern> i've lost track
* det arrives
<det> Demitar: hi, what advatage do classes offer you that you cannot use modules ?
<mattam> hmm, modules do not have late-binding, right ? (if i redefine a function that is called in the original module, it won't get called instead of the original definition)
<det> you cannot do this with classes, no ?
<det> besides, you would use a reference for that
<mattam> yes you can, it's the default behavior
<det> oh, how can you redefine a class's function?
<det> or do you mean, inheritance ?
<Demitar> det, for me personally the only advantage I make use of is the neater syntax. :)
<det> Demitar: example ?
<Demitar> LongModuleName.foo obj; versus obj#foo;
<det> oh, that seems silly :)
<mattam> like 'class a = object(self) method a = self#b method b : int = raise Not_implemented;; class b = object(self) inherit a; method b = 0 end;; (new b)#b == 0'
<Demitar> I personally don't have much use of virtual functions actually.
<det> mattam: oh, you can use a record of closures for that
<Demitar> det, but can you restrict the type of a record of closures?
<det> Demitar: I dont understand
<Demitar> (complexObj :> simpleType)
<Demitar> Basically making functions accept different types of objects as long as they implement the same (partial) interface.
<det> sure, in fact it can be type infered
<det> well
<det> partial ..
<det> you must expicitly convert
<Demitar> Well you technially can do everything using modules but for some things classes simply are a better fit. (Not that I have much use for them.)
<det> I dont think it is much more difficult
<det> and you receive many benefits
<Demitar> Well I personally prefer modules but sometimes the interfaces just get too clunky.
<det> are they not clunky for classes as well ?
<Demitar> If we had polymorphic record labels just like we have polymorphic union types I'd be using more modules.
<det> Demitar: what would that be like ?
<Demitar> I don't know how it would be implemented but if I could avoid all those pesky record label clashes I would be very happy.
<det> If you factor out the interface code, everything else is nice and clean
<det> oh, I see
<Demitar> What complicates things is that I'm providing an interface to a dynamically typed protocol. So I want to export the well defined typed values while providing an interface to the backend values.
<det> you can have a module per interface, you can simple call Interface.function and the type is nice and infered
<det> instead of simple doing foo#function
<det> and using some overloading english term and get poor type inference
<det> Demitar: the the set of dynamic types finite ? Can you use a unoin type, or are you guarenteed only and interface ?
<det> s/and/an/
<Demitar> I have a union type backing already. But that's too clunky to use in the actual interface. And typing it provides some safety against typos.
<det> what protocol is this ?
<Demitar> Atlas (not the algebraic library). The protocol used by WorldForge.
<det> when you recieve a value, what information you do you know ?
<det> a interface it supports ?
<Demitar> Well I have the network layer in place already.
<Demitar> So I get a Map which contains types of the union: type atlas = Map atlas map | List atlas list | String | Int | Float
<Demitar> The map is a string -> atlas mapping.
<det> how do you encode this using classes ?
<Demitar> I don't.
<det> oh, for what problem do you intend to use classes ?
<Demitar> I'm trying to make a good interface at the message layer so that I can implement the object layer in a good fashion.
<Demitar> What I'm pondering is the interface the message layer provides.
<Demitar> Thus I make good assumptions of what types the various members will have an provide a statically typed interface.
<Demitar> And to save some typing I'm considering using classes rather than records.
<det> oh, I see now
<det> save some (finger) typing, lose some (program) typing :p
<Demitar> Exactly. :) And I won't lose the typing anyway since the interface will provide enough typing infomation anyway.
<Demitar> I guess I have another thing to ponder, these messages can have arguments with various types. But I guess I need to parse those at the object layer anyway.
<det> when the compiler sees "foo#bar" it only knows that foo must support a method named foo
<Demitar> Yes and thus the typing errors get a real mess.
Kinners has left #ocaml []
<det> when it sees "Network.foo bar" it knows everything staticly!
<Demitar> I'd really want it to say, method bar is missing rather than barfing two huge types at me and only tell me they're different. ;-)
<det> how can the extra ~5 characters make up for this ambigiouity <sp> ?
<Demitar> 2 reasons.
<Demitar> 1. It's 5*n not 5.
<Demitar> 2. The second most annoying thing is to discover at Module.foo bar <- here, that you really want to call another function on the result and need to backtrack to add a parentheses at the beginning too. I tend to do that quite often in real code.
<det> It's not ambigiouity, ambigiouity*n! :p
<Demitar> Happends a lot when passing arguments as labels too.
<det> I dont understand the 2nd point
<Demitar> Consider this:
<Demitar> foo ~bar:baz ();;
<Demitar> Then I change it to:
<Demitar> foo ~bar:Fnurglewitz.quux |baz ();; when my cursor is there I discover I need to enclose the whole thing in parentheres.
<Demitar> Which takes a bit more time than I'd like and generally distracts me from what I was doing.
<det> what is |baz ?
<det> you realize you dont need ;; is source code, yes ?
<Demitar> | denotes the cursor position. :)
<det> erm, or do you with classes, I forget ?
<det> ohh
<Demitar> det, yes, but that was a single statement and most likely would be typed at the toplevel. :)
<Demitar> With a class I'd simply do foo ~bar:baz#quux (); and no extras needed.
<det> maybe you should be using let anyways :)
<Demitar> Well this usually happends as iterate the functionality, I eventually move the arguments out into let statements but before that I extend the function call a few times.
<det> why do you need parens in the first example and not the second ?
<Demitar> Soon I'll probably argue for the perl if (x) { foo; } and { foo; } if (x); although I don't really like perl anyway. :)
<det> Demitar: how confusing :)
<Demitar> det, I want the value of (Fnurglewitz.quux baz) otherwise ocaml will think I'm passing two arguments, one labeled function and one value.
<det> oh, I see
<det> how do you not know before hand?
<Demitar> I technically could figure that out but in practice I'm busy thinking about which function I should be calling at all.
<det> what editor do you use ?
<Demitar> By the way, the thing I really like about ocaml is that it allows me to write code and get away with it. :)
<Demitar> det, emacs, but my wm tends to eat M-.
<det> mayve you need some kind of easy binding to enter a pareen seeking back to the last ':' ;)
<Demitar> Or rather, it used to do that so I never got into using M-b/f :)
<Demitar> det, M-b should do just that.
<Demitar> That is, just a word each keypress.
<Demitar> s/just/jump/
<det> what wm do you use ?
<det> you can change emac's meta, yes ?
<det> do you have an unused windows menu key ? :)
<Demitar> Part of the problem is the pesky Alt Gr key which won't work as a real Alt.
<det> Alt Gr ?
<Demitar> Swedish keyboard.
<Demitar> (Although I do use the us layout when coding.)
<det> oh
<Demitar> It's the right meta key.
<det> I see
<det> have you looked at SML
<Demitar> No, why?
<det> sorry, was half a statement
<det> went afk for a second
<det> for it's record handling
whiskas has joined #ocaml
Nutssh has joined #ocaml
cjohnson has joined #ocaml
<_JusSx_> hye cjohnson
<Nutssh> Hi
<Maddas> Demitar: is {foo;} if (x) valid Perl code?
<Maddas> I think it is not\
<whiskas> Crap, I wouldn't have thought I'd see perl in here.
<cjohnson> howdy, _JusSx_
<Demitar> Maddas, well I don't know if it's syntactically correct but I think the general case holds true.
<Maddas> Demitar: no. It's EXPR if EXPR, not BLOCK if EXPR :)
<Maddas> (unless you meant that by syntax)
<Demitar> Yes, I'm not deep into perl grammar. :)
<Maddas> Neither am I
wazze has joined #ocaml
<Demitar> Well, knowing that it's supposed to be an expressions rather than a block when doing a reverse if shows that you have more than passing knowledge at least. :)
<Maddas> heh
<Maddas> Demitar: I just tried it.
<Demitar> Could I still have a print statement in there somehow?
<Maddas> Yes, but I don't know of any nice way :-)
karryall has joined #ocaml
<Demitar> Maddas, it's perl I don't think it's supposed to be "nice". ;-) (Wii! Let's start a language war by inviting a few perl coders!)
<Maddas> You've got a point there :)
whiskas has quit ["Leaving"]
<Nutssh> I wonder if ocaml could be given the syntax of perl.
<Demitar> Nutssh, go mad with camlp4. ;-)
<Nutssh> :) I was joking! Only a loon would try that. :)
cjohnson has quit ["Drawn beyond the lines of reason"]
_JusSx_ has quit ["BitchX: it won't get you laid"]
Nutssh has quit ["Client exiting"]
cmeme has joined #ocaml
cjohnson has joined #ocaml
sproctor has joined #ocaml
<sproctor> hello
<Demitar> Greetings sproctor, welcome to our humble channel.
<sproctor> thank you
<sproctor> I'm kind of stuck on some networking problem, but I came across some weird behavior of Unix.shutdown
cjohnson has quit [Client Quit]
<sproctor> if I do Unix.shutdown SHUTDOWN_SEND on some sockets, my program just dies.
<Demitar> How does it die?
<sproctor> it doesn't raise an exception or give me any notification of what's going on... just death.
<Demitar> Tried running it with gdb?
<sproctor> I tried running it with ocamldebug, but that just hangs before I get to this point.
<Demitar> Well I think gdb would be of more interest in this case since you're probably recieving a wild signal (I'm guession of course :).
<sproctor> okay, I'll try it.
<Demitar> Well I successfully shut down a socket now, let me see what happends if I send some data.
<sproctor> it doesn't die when I run it through GDB
<sproctor> but it does when I run it normally.
<Demitar> Ah, a classic. :)
<sproctor> yeah, I love that...
<Demitar> Well it seems very weird, I can do a shutdown successfully using the toplevel.
<Demitar> Have you added some magic debugging statements around the particular area?
<lordjim> what's the result of the ackerman function on 3 and 4 ?
<Demitar> Ie print_endline and flush.
<smkl> why not prerr_endline ?
<Demitar> smkl, since I'm not thinking straight? :)
<Demitar> lordjim, ask google: http://www.kosara.net/thoughts/ackermann.html
<lordjim> oki thanks
<lordjim> :)
<sproctor> what would I put in these debug statements? just to mark where it dies? I've done that.
<Demitar> sproctor, so you're positive that's what kills it? That is you're flushing them.
<sproctor> they're on stderr
<sproctor> unless stderr is somehow buffered, then yes.
<Demitar> That's no guarantee that they're getting flushed.
Nutssh has joined #ocaml
<Demitar> Never ever assume things get flushed when things go wrong.
<Demitar> And generally speaking I think all io channels are buffered somehow.
<sproctor> stderr is stderr?
<smkl> prerr_endline should always flush
<Nutssh> stderr usually isn't buffered.
<Banana[AFK]> yeah. stderr is unbufferred.
Banana[AFK] is now known as Banana
<Demitar> Oh, neat. ;-)
Herrchen has left #ocaml []
<Demitar> sproctor, now then, what kind of evil are you doing with the socket to cause this behaviour?
<Demitar> Is the source availiable somewhere?
<sproctor> I don't know if it's on the web, but I can make it so.
<smkl> nope, stderr is buffered, at least in version 3.06 which i'm still using
<Demitar> It's not your app?
<Demitar> Well then, go add those flush statements first. ;-)
<sproctor> why would stderr be buffered?
<sproctor> I did add the flush statements, didn't change things.
<Demitar> Ok, good, or something. :)
<smkl> sproctor: probably it's just easy to do everything the same way
<sproctor> buffering stderr seems like a bad idea.
<sproctor> it is my app, but I'm not sure if I have it on the web yet.
<smkl> but prerr_endline will always flush, unlike print_endline
<Demitar> sproctor, well whatever is simplest for you, dcc, mail, http.
<sproctor> http://rottenvegetable.org/~sproctor/mud/ relevant files are server.ml and connection.ml sorry, the app is a little bit complicated.
pflanze has joined #ocaml
<pflanze> Hello.
<Maddas> Heh
<Demitar> Gah, wget respects robots.
<Maddas> Hi, pflanze
<Maddas> pflanze: don't I know you from axkit (dahut)? :)
<pflanze> Maddas: yep
<Maddas> Ok, thought it sounds familiar.
<pflanze> :)
<sproctor> wget respects robots? why??
<pflanze> What are you doing with ocaml, Maddas?
<Maddas> pflanze: Nothing useful. Playing around, learning it for the knowledge. :)
<Maddas> (I don't really do anything useful in any programming language.)
<Maddas> pflanze: What do you do with LISP? :)
<Maddas> (And with which?)
<pflanze> Playing around as well :)
<lordjim> Maddas: try ackerman function on 45 and 75
<Maddas> Heh.
<pflanze> (sbcl, clisp)
<lordjim> it's not useful at all
<Maddas> lordjim: Hmm?
LittleDan has joined #ocaml
<LittleDan> With type inference, why do you ever need to explicitly declare types in OCaml?
<Maddas> LittleDan: Where do you need to do that?
<Smerdyakov> Do you know about lists in OCaml, LittleDan?
<LittleDan> Smerdyakov: They are linked lists, I don't konw much else. Do you need to declare their types?
<Maddas> LittleDan: What does your question refer to?
<LittleDan> Why does OCaml have syntax to declare types?
<Smerdyakov> LittleDan, what is the type of this expression? []
<sproctor> LittleDan: it's useful for clarity
<LittleDan> sproctor: Thanks
<Maddas> LittleDan: You can do it to improve efficiency in some cases.
<Maddas> Signatures come to mind, too.
<Smerdyakov> Type annotations are absolutely in some cases that don't even use the module system..
<phubuh> Smerdyakov: [a] ?
<Smerdyakov> s/absolutely/absolutely necessary
<Smerdyakov> phubuh, yeah, if you translate that to an OCaml type. :)
<Maddas> phubuh: Haskell? :)
<Demitar> sproctor, to begin with. How come you only call Unix.close if there has been an exception?
<Smerdyakov> LittleDan, do you understand now why you would need type annotations? (There is actually more to it, but what I said should explain the basic reason.)
<phubuh> Oh. Whoops. a list. :)
<sproctor> Demitar, I don't. that's after the exception is caught. but that bit of code is very broken.
<LittleDan> Smerdyakov: Not really, but is it the kind of thing that I'll know that I need it when I need it?
<Demitar> sproctor, your scoping seems to be broken then. You should see what happends with proper indentation. :)
<Smerdyakov> LittleDan, it's the kind of thing you'll be extremely confused by if you ever run into it. :)
<Smerdyakov> phubuh, 'a list
<Demitar> try ... with _ -> foo (); bar (); baz (); <- all of those are within the "with" scope.
<phubuh> Bah.
<Maddas> haha
<sproctor> Demitar, are you positive?
<sproctor> Demitar, I'm pretty sure that's a false statement.
<Maddas> Hm. The type interference basically works by solving equations involving the types, right?
<Demitar> sproctor, it works exactly as match ... with _ -> ...
<Banana> Maddas: yes.
<Maddas> Ok.
<Smerdyakov> LittleDan, if you would like to be confused sooner rather than later, try creating a module containing this definition: let r = ref []
<sproctor> Demitar, okay, let's ignore that for now anyway, because that section doesn't do what I want regardless.
<LittleDan> Sherdyakov: Would that cause an error?
* Maddas laughs
<pflanze> Has anyone ever written a lisp to ocaml translator/compiler?
<LittleDan> Smerdyakov: What would that do?
<LittleDan> besides make a reference to an empty list
<Demitar> sproctor, well if you temporarily disable the disable in robots.txt or tarball it I can do a bit more testing. :)
<Banana> LittleDan: what do you think the type of ref [] is ?
<LittleDan> 'a list ref or something like that? The toplevel puts an underscore between the ' and the a for some reason. Why is that?
<Banana> call it a weak type variable.
<LittleDan> Banana: And that makes things unpredictable?
<Banana> no, that doesn't typecheck.
<sproctor> Demitar, thanks a lot, btw.
<Banana> the typechecker cannot generalise the variable '_a.
<LittleDan> why does it use '_a and not 'a?
<Banana> there is a clean explanaion here :
<LittleDan> so their type is determined the first time you call them or something?
<Banana> yes.
<LittleDan> I thought all type information was lost at compiletime
<Banana> it is.
<LittleDan> So then when is it determining the type of that function?
<Banana> when it is applied to something.
<Banana> you can try this in a toplevel :
<Banana> let a = ref [];;
<Smerdyakov> And if it can't determine when it is applied to something at "compile time," then you get an error.
<Banana> let b = ref (List.tl [1]);;
<Banana> a=b;;
<Banana> now a has type int list ref instead of '_a list ref
<LittleDan> Banana: So all of that analysis is done at compiletime?
<Banana> yes.
<Maddas> Yes.
<Demitar> sproctor, I get this when it breaks in gdb: 0x40031a2b in write () from /lib/libpthread.so.0
<Demitar> sproctor, is this threaded?
<sproctor> Demitar, yes.
<Demitar> Well it would seem to me that you have a threading bug, see what happends if you do this in unithread mode if you can.
<sproctor> no, it's a gdb thing.
<sproctor> you need libc with debugging symbols to run threaded apps.
<sproctor> well, it could be a thread issue...
<sproctor> I know when I was debugging one of my other apps I'd get crashes in gdb because of the threading until I installed debug version of libc
LittleDan has left #ocaml []
<Demitar> My suggestion is to trace all use of the connection object.
<sproctor> how do I do that?
<Demitar> prerr in all functions. :)
<Demitar> That should make it pretty obvious if someone tries to use it, and by the way if multiple threads can use it you need a mutex anyway.
<sproctor> why would I need a mutex?
<Demitar> Can multiple threads use the connection object?
<sproctor> I thought the Unix module was thread-safe?
* Demitar looks.
<sproctor> yeah, there should be 3 threads using it.
<Demitar> sproctor, no, ThreadUnix should be.
<sproctor> I thought ThreadUnix was deprecated because Unix was made thread-safe?
<Demitar> Sorry, you're right. :)
<Demitar> But still, is Unix.shutdown thread safe?
<sproctor> if it's not, that's a bug, right?
* Demitar investigates.
<karryall> sproctor: how do you test your program ?
<sproctor> karryall, by running it?
<karryall> since it's a server, not really
<sproctor> run it, telnet in.
<smkl> what ThreadUnix made, and now is added to actual Unix module, is that waiting calls don't block all threads
<karryall> and how do you make it crash ?
<Demitar> sproctor, with debuglevel 10 it doesn't crash.
LittleDan has joined #ocaml
<sproctor> karryall, Unix.shutdown sock Unix.SHUTDOWN_SEND;
<Demitar> Which *really* suggests to me that it's a threading issue.
<smkl> otherwise they just call the unix sys-calls, i don't know how threadsafe they are
<LittleDan> This isn't really a bad thing, but why doesn't let rec recurse () = recurse ();; recurse ();; use up all of the system resources?
<Demitar> Since it's probably blocking the tiny amount of time needed to make it work.
<Smerdyakov> LittleDan, tail recursion.
<Smerdyakov> LittleDan, which is optimized to constant stack usage by all functional language compilers.
<Demitar> LittleDan, in the toplevel it uses all my cpu. :)
<LittleDan> Smerdyakov: But doesn't it still loop infinitely?
phubuh has quit [Remote closed the connection]
<Smerdyakov> LittleDan, sure, but why should looping infinitely use up resources?
<LittleDan> Smerdyakov: I just assumed that unless it was recognized, it would use up everything (that's what happens in other languages)
<Smerdyakov> LittleDan, do you think this C code uses up all resources? while(1) {}
<LittleDan> Smerdyakov: No, that makes a core dump, but that's different.
<Banana> ?
<karryall> sproctor: I can't make it crash but the server uses all the cpu
<Smerdyakov> LittleDan, it doesn't make a core dump.
<Banana> it cores dump ?
<Smerdyakov> LittleDan, it just goes on forever, happily looping.
<Banana> would be strange.
<LittleDan> On my computer it does
<Smerdyakov> LittleDan, a C program with an empty infinite loop?
<sproctor> karryall, that's weird.
<LittleDan> Smerdyakov: Not any infinite loop; an infinite loop that doesn't do anything and never breaks.
<karryall> oh no sorry, it does crash
<Smerdyakov> LittleDan, right, an empty infinite loop.
phubuh has joined #ocaml
Nutssh has quit ["Client exiting"]
<Smerdyakov> LittleDan, if such a C program causes a core dump on your computer, your compiler, OS, etc., is broken./
<LittleDan> Smerdyakov: Yes. My computer must be very messed up.
<sproctor> oh, I think I see something.
<Smerdyakov> LittleDan, honestly, I don't even believe you that that causes a core dump. I'd have to see it to believe it.
<LittleDan> Well, I'd expect it to use up all the system resources it was given if it didn't dump core.
<sproctor> I'm calling input_line in one thread, then Unix.shutdown in another.
<LittleDan> Ok, I'll just pretend it doesn't
<Banana> LittleDan: if it cores dump i suspect your memory to be corrupted.
<karryall> sproctor: it doesn't leave a core dump, just reports a broken pipe
<Smerdyakov> LittleDan, what resources do you think it would use up?
<LittleDan> So why doesn't it use up all of the system resources allocated to it?
<Smerdyakov> LittleDan, (I am talking about in empty while loop in C now.)
<Banana> LittleDan: mainly because there are no system ressources allocated ;)
<LittleDan> Smerdyakov: Any system resources it has access to.
LittleDan has left #ocaml []
<Smerdyakov> LittleDan, OK. So if your printer is connected, you think it would print until you ran out of ink or paper?
<Banana> Smerdyakov: would be fun.
<Banana> programmer would become good in no time :D
<Demitar> sproctor, blocking in input () is bound to give you problems naturally.
<Demitar> sproctor, you're better off using stateful programming and communicating with the connections using some thread safe mechanism I'd say.
<Demitar> Or do it the completely stateful way.
<karryall> some might say, you're better off dropping threads completely
<sproctor> yeah, I think you're right, karryall
<sproctor> well, I'll probably go to fewer threads anyway.
<Demitar> I only use threads to do inherently blocking stuff, such as dns queries and connect().
<Smerdyakov> You'd be better off using Concurrent ML. :D
<Maddas> Smerdyakov: He left again.
<karryall> sproctor: yes, at least try not to do IO on a connection through different threads
<Riastradh> Low-level threads are yucky.
<Maddas> Err, I'm lagging too.
<Smerdyakov> Maddas, talking to sproctor...
<sproctor> okay, time to start rewriting things... yuck.
<Maddas> Smerdyakov: Yes, sorry. But your *previous* statement arrived here after LittleDan left. :-)
<sproctor> it would still be nice if Unix.shutdown raised an exception rather than crashing. ;)
<Smerdyakov> Maddas, I knew that at the time, but it was too funny to not send after I had typed it. ;)
<sproctor> thanks a lot, Demitar karryall
<Smerdyakov> sproctor, ever seen Concurrent ML?
<sproctor> Smerdyakov, nope
<Smerdyakov> sproctor, it's an extension to Standard ML that makes multi-threaded stuff very nice.
<karryall> sproctor: see the Event module in ocaml
<Smerdyakov> sproctor, about as close to pure functional as you can get with threads and still have a convenient API./
<sproctor> Smerdyakov, I don't use much with threads in this app, mostly OO
<Demitar> sproctor, the unix module could use an overhaul generally I'd say, too much is just a direct interface to the lowlevel unix stuff, python is a good example in this case, makes socket programming a real breeze.
<phubuh> Smerdyakov: Is it anything like Erlang's model of concurrency?
<Demitar> Which reminds me that the unix module is missing htonl with friends.
<sproctor> Demitar, I've never done python programming. I'm going to write a small app in it soon I think.
<Smerdyakov> phubuh, I think it is very similar. Almost a typed version of it.
<phubuh> Ooh. Cool.
<karryall> Demitar: why would you need htonl ?
<Smerdyakov> And it looks like the Event module in the threads library for OCaml provides the same capabilities, as suggested by karryall.
<Demitar> karryall, implemented a network protocol in ocaml.
<Demitar> sproctor, how about a webserver? :) import BaseHTTPServer, SimpleHTTPServer; BaseHTTPServer.HTTPServer(('', 8081), SimpleHTTPServer.SimpleHTTPRequestHandler).serve_forever()
<sproctor> Demitar, huh?
<sproctor> Demitar, you mean for the app to write in python?
<Demitar> Yes, the fun webserver-using-two-lines-of-code example. :)
<sproctor> Demitar, it would be educational, I'm sure.
<Smerdyakov> That's nothing. I can write a one-line-of-code webserver with a shell script that starts Apache.
Nutssh has joined #ocaml
<Demitar> Smerdyakov, yes, it's of no real value beyond showing off the standard library. :)
<Maddas> Smerdyakov: I can do it without pressing any key.
<Smerdyakov> Maddas, so can I, on my PDA! :D
<Maddas> Haha
<Maddas> Actually, I meant launching the webserver, not writing a script that does it. That takes a bit more.
<Demitar> You don't have an any key?
<Maddas> Smerdyakov: Ok, without physical contact with my laptop.
<Riastradh> Demitar, why on earth would you include a complete HTTP server in the standard library?
<Demitar> Riastradh, because you can? :) It's quite trivial and more useful than you'd think actually. But it does encourage placing functionality where it does not belong. ;-)
<Maddas> Heh.
<Maddas> Sounds like you'll have a terribly overloaded standard library.
<Demitar> Maddas, it's definitely competing with java. :) But it's not much added code when you have a SocketServer class which makes a lot more sense to have in the standard library. And most of the parsing code is already in there in other parts where it's more relevant.
* Smerdyakov laughs at the idea that a SocketServer should have a significant amount of code associated with it.
<Demitar> But the extensive standard library is a big reason writing applications in python is as swift as it is.
<Smerdyakov> Demitar, are you a Python fan?
<Demitar> I used to hack a lot in it. But what eventually bit me was the lack of static typing. When you're tossing data all around in a 10k loc application the pure testing and chasing typing errors becomes a real hassle.
<Demitar> That's when I found OCaml, and now I'm stuck. :)
<Smerdyakov> OK, so you wouldn't choose to use Python anymore?
<Demitar> I still use python from time to time when doing quick prototyping. Or other smaller scripts.
<Demitar> (When I need a bit more power than a shell script.)
<Smerdyakov> Bah. Why not use OCaml for that?
<Riastradh> Bah. Why not use scsh for that?
<Riastradh> (scsh even performs static type analysis!)
<Demitar> Smerdyakov, I still know how to toss together a python script faster than an OCaml program. :)
<Smerdyakov> Demitar, that's strange. I don't think that's based on intrinsic properties of the languages.
<Demitar> Neither do I, but when writing such small scripts I suspect you need to calculate with syntax too.
<Riastradh> scsh has much more convenient syntax for sh-like tasks than either Python or OCaml.
<Smerdyakov> But OCaml allows you to define your own syntax much more easily than Python does.
<Demitar> python slicing is a lot more powerful than anything I've seen in OCaml so far.
<Riastradh> scsh allows it far more easily than that.
<Demitar> By the way:
<Demitar> 20K /usr/lib/python2.3/SocketServer.py
<karryall> slicing ?
<Smerdyakov> What does it do, Demitar?
<Demitar> 24K /usr/lib/python2.3/BaseHTTPServer.py
<Demitar> 8,0K /usr/lib/python2.3/SimpleHTTPServer.py
<Demitar> You can slice any sequence like this: seq[0] or seq[0:] or seq[4:7] or seq[-2:-1] or seq[-4:] etc
<Riastradh> Um. A trivial array slicing syntax makes Python wicked powerful?
<karryall> ah yes, the syntactic sugar for String.sub
<Demitar> Riastradh, we're talking about how fast you write working code here.
<Nutssh> Syntatic sugar can be real convenient sometimes.
<Demitar> And slicing is one of the most useful things is python, along with the fact that everything is an object.
<Riastradh> Demitar, it's the difference between [[seq[a:b]]] and [[array_slice seq (Some a) (Some b)]].
* Smerdyakov rolls his eyes at more "everything is an object." :P
<Smerdyakov> "Everything is an object" reads to me as "almost everything is too complicated."
<Demitar> Well we should probably account a lot of it to that it's closer to how I'm used to thinking.
<Riastradh> What benefit do you gain from it?
<Demitar> Don't underestimate the power of the cursor being closes to the spot you need to add the code to when you figure out you need to do it. :)
<Riastradh> ???
<Demitar> I commonly find I need to backtrack a bit to add parentheses around stuff to pass it to another function in ocaml.
<Riastradh> By 'it' I'm referring to the 'everything is a Smalltalk-style object' bit.
<Demitar> Oh, what I mean is the benefit of everything being an object is that you commonly do: foo.do_this()
<Nutssh> I don't usually. Too many parenthesis usually means one should do a 'let .. in ..'
<Demitar> Say "hello all".capitalize()
<Riastradh> Why is that better than [[capitalize "hello all"]]?
<karryall> or String.capitalize "hello all" :)
<Demitar> Riastradh, since I remember I need to call capitalize about "hello a <- here. :)
<Demitar> Nutssh, sure, and that's probably since I still have used python more than OCaml.
<Riastradh> Gee. You have to type C-b a few times.
<Demitar> Riastradh, by the time I'm done with that I've written three more statements in python. :)
<Demitar> In general any Cish syntax is easier for me since I've used that a lot longer than MLish syntax.
<Riastradh> C-ish syntax? What does that have to do with Python?
<Demitar> It pretty much looks the same as any C++ really.
* Riastradh gives Demitar a very queer look.
<Demitar> But you should know that when I a while back wrote a script in python, one thing bit me repeatedly. For some stupid reason you have to write "return" to pass a value back from a function. I really can't understand why anyone would want that.
<Maddas> Interesting....
<Etaoin> because statements aren't expressions
<Demitar> Etaoin, I know "why" but I don't know why anyone would want that. :)
<Demitar> The functional way is a lot more convenient there. :)
<Etaoin> I agree
<Maddas> Is that inherently 'functional'?
<Demitar> Maddas, probably not, but I'm sloppy today. :)
<Demitar> (In perl that is true too I think.)
<Demitar> Riastradh, well if you ignore the * -> . dance that is. :)
<Etaoin> but I guess it's hard to merge that idea with whitespace importance without making the parser very complex
<Demitar> Etaoin, I've heard the parser is a mess anyway. :)
como has joined #ocaml
Nutssh has quit ["Client exiting"]
Nutssh has joined #ocaml
<mattam> do someone knows of a somewhat feature-complete abstract layer for accessing databases in ocaml ?
<Smerdyakov> Hm. "Do someone knows" is pretty bad English. ;)
<Demitar> mattam, what are you looking for? Rdbms?
<mattam> yep
<mattam> do anybody knows ?
<Demitar> And how abstract should it be? dbforge or one of the postgre/mysql interfaces?
<Smerdyakov> "Does someone know of a ...?"
<mattam> someone does know of ...
<Smerdyakov> Or more likely "Doees anyone know of a ...?"
<mattam> right
<Demitar> Smerdyakov, picky today? ;-)
<Riastradh> Smerdyakov is picky every day.
<Smerdyakov> Demitar, "do someone knows" is particularly jarring to a native English speaker. :P
<mattam> Demitar: dbforge is not about giving an interface to db's is it ?
<Demitar> mattam, not a generic interface (afaik).
<mattam> yeah, that's what i've found too.
<Demitar> Smerdyakov, well I've mostly turned off my grammar verification in favour of understanding what people say, could be that I'm tired though. :)
<mattam> so i will have to write one.
lordjim has quit [Read error: 104 (Connection reset by peer)]
<Demitar> mattam, how generic does it have to be? I assume the postgre interface doesn't suit your needs?
<Banana> mattam: this has been discussed on the mailing list, i think, a generic interface for many DB backends isn't that easy to write.
<Demitar> Yes, sql quirkiness isn't too uncommon iirc.
<mattam> i just want the intersection of ocaml-mysql and ocaml-pgsql
<mattam> that shouldn't be too hard :)
<Banana> well if it's just these two, it might be feasable.
<Smerdyakov> Does anyone know what governs orderings of people in Orkut friends lists?
<mattam> randomness ?
<Banana> hum... i wonder.
<Smerdyakov> Then how come I'm the first on the lists for 90+% of my friends?
<Banana> Smerdyakov: not in all ?
<Smerdyakov> That's right.
Nutssh has quit ["Client exiting"]
<Smerdyakov> I used to think it sorted by number of friends, but that is disproven by many examples.
<Banana> well i'm first for all my friends.
<Smerdyakov> How many people are you connected to?
<Banana> 22.
<Banana> 18 in fact.
<Maddas> 22?
<Banana> 4 pending.
<Smerdyakov> You must be Kim.
<Smerdyakov> Am I right?
<Banana> indeed i am.
<Smerdyakov> (Looking at mattam's list)
<Maddas> Smerdyakov: What do you mean with 'connected to'?
<Banana> I meant friend.
<Smerdyakov> Maddas, it shows the number on your Orkut main page.
<Smerdyakov> Maddas, it says "You are connected to X people."
<Smerdyakov> Banana, that is not how many people you are connected to. That is just your friend count.
<Banana> no connected to 11371 people.
<Banana> yeah my mistake.
<Smerdyakov> OK, I will add Banana to try to absorb some of his eliteness.
<Maddas> That's what I meant :-)
<Banana> haaa, damn orkut.
<Banana> stop reminding me of valentine's day.
<Smerdyakov> Maddas, are you on Orkut?
<Maddas> Yes
<mattam> Banana ?
<Smerdyakov> Maddas, what name?
<Banana> what ?
<Maddas> Smerdyakov: Markus Ziegler
<Banana> did I say that loud ?
<mattam> what about your valentine's day
<Banana> nothing.
<mattam> yeah, you actually wrote it on IRC.
<mattam> wait a minute, Maddas you're the one that took over postgresql-ocaml right ?
<Maddas> Me?!?
<Maddas> Hell no. :)
<Banana> I think you've got the wrong Markus mattam
<mattam> yep, it seems.
<Banana> it was Markus Mottl actualy.
<Smerdyakov> Maddas's Orkut profile says he mostly programs Perl!!
<Maddas> oh, ok. I already thought I copied somebodies nick accidentally.
<mattam> aye!!!
* Maddas runs for cover
<Maddas> Actually, that isn't true anymore. I should update it, I guess.
<Smerdyakov> Guys, if you are true hackers, you should join #hprog!
<Riastradh> Things changed in the two weeks Orkut has been around?
<Maddas> Riastradh: Something like that. :)
<Banana> hey there is another GO community ???
<Maddas> (Actually, they didn't change, it was wrong when I entered it already.)
<Banana> with more people.
<Banana> let's go (muah ha ha).
<Smerdyakov> Hm. I guess you guys are not Real Hackers!! ;P
<Banana> thank you.
<Banana> :p
<Smerdyakov> There is still hope! All you have to do is join #hprog!
<Maddas> There is still hope? Does that imply that by joining we _become_ Real Hackers? :-)
<Smerdyakov> Yes!
<Banana> The Fellowship of Hobbyist Programmers ?
<Smerdyakov> That is right.
<Banana> Dear God grant us Divine protection.
<Smerdyakov> What you say??
<Banana> just kidding.
<Banana> here i come.
<Smerdyakov> Hm. Our topic became empty. I will set it.
<Maddas> All your base^Wcode are belong to us!
<Maddas> Sheesh. Editing profile doesn't work anymore, since around 20 seconds.
<Smerdyakov> Well, now I am listed first on Banana's friends list. :P
<Banana> yeah.
<Maddas> Haha
<Maddas> Sounds like something to be proud of! :)
* Demitar realizes he left his eom code in a state of ui disrepair.
<Smerdyakov> Demitar, P.S., join #hprog!
<Demitar> Eeep!
<Banana> Smerdyakov: you get paid for that, right ?
<Smerdyakov> Banana, only in quality conversation. :)
<Banana> ;)
<Demitar> Smerdyakov, I can't fit more channels without having to resort to the dreaded scroll arrows. :)
<phubuh> Demitar: Use ERC! :)
<Smerdyakov> Maybe phubuh should join #hprog, too.
* Maddas tries to get happy with emacs
<Smerdyakov> Emacs should make you happy automatically.
<Maddas> What's the shortcut for that? :-)
<phubuh> With about 1000 lines of .emacs, I'm beginning to get comfortable. :D
<Maddas> haha
<Maddas> maybe that's the problem. My .emacs file has one line.
<phubuh> Wow.
<Maddas> haha
<Maddas> phubuh: Either I already reached Nirvana, or I've still got a looong way to go.
Nutssh has joined #ocaml
<phubuh> :D
<Maddas> I did have way more once, but that file is gone and I've been without emacs for a long time, so I wouldn't remember what the stuff did anyway.