dylan changed the topic of #ocaml to: OCaml 3.09.1 available! Archive of Caml Weekly News: http://sardes.inrialpes.fr/~aschmitt/cwn/ | A free book: http://cristal.inria.fr/~remy/cours/appsem/ | Mailing List: http://caml.inria.fr/bin/wilma/caml-list/ | Cookbook: http://pleac.sourceforge.net/
mrsolo_ has quit [Connection reset by peer]
mrsolo_ has joined #ocaml
<jer> twobitsprite, it's not uncommon ... my name for example is 'jeremy' (but that was already taken)
mrsolo_ has quit [Read error: 104 (Connection reset by peer)]
mrsolo_ has joined #ocaml
gim has quit [Read error: 110 (Connection timed out)]
mrsolo_ has quit [Read error: 104 (Connection reset by peer)]
mrsolo_ has joined #ocaml
mrsolo_ has quit [Connection reset by peer]
mrsolo_ has joined #ocaml
<dark_light> abs min_int;; don't works! - : int = -4611686018427387904 :[
<twobitsprite> dark_light: abs (min_int + 1);; does
<dark_light> and why?
<dark_light> aaaah!
<twobitsprite> you can always count one further in the negative direction than you can in the positive...
<twobitsprite> try applying two's complement on 111111111111111111
<dark_light> abs min_int is larget than max_int
<twobitsprite> bingo
<twobitsprite> you said it better than I could :P
<dark_light> twobitsprite, i am doing an simple program that calculates how many bytes int uses
<twobitsprite> it looks like you're on a 64 bit machine... no?
<dark_light> yes i am
<twobitsprite> wouldn't it be 8 bytes?
<dark_light> no, it's 63 bytes
<dark_light> log(2.0 *. float max_int +. 1.0) /. log 2.0;;
<dark_light> on 32bits machines, it's 31 bytes
<twobitsprite> maybe I just need some sleep, but that doesn't sound right...
<dark_light> yeah..
<dark_light> the last bit is used for something else
<dark_light> or the first
<twobitsprite> I think you're confusing bits with bytes
<twobitsprite> or vice versa
<dark_light> yeah, how many _bits_
<dark_light> twobitsprite, i am doing it for my professor of.. programming concepts and techniques.. using max_int e min_int would be better, on the sum
<dark_light> instead of doing 2*maxint+2, i could use maxint+|minint|+1
<twobitsprite> right... doesn't ocaml use C longs for ints?
<dark_light> long ints? no
<dark_light> ocaml uses signed ints.. i mean.. a bit is used for sign (+ or -)
<twobitsprite> right... but aren't they signed long ints?
<dark_light> i dunno
<twobitsprite> you should probably double check, lest you fail your homework assignment
<twobitsprite> I'm pretty sure it uses longs/doubles/whatever, not actual "int"s like in C
<dark_light> twobitsprite, some ppl said the ocaml really uses 31/63bits for ints
<twobitsprite> (er, doubles are floats, longs are ints...)
<twobitsprite> dark_light: right... and a C int uses 16 bits, right?
<twobitsprite> ask in ##C
<dark_light> twobitsprite, right, but, why? ahahahha.. it doesn't matter now
<twobitsprite> well... ocaml uses 30 bits to store an int... in a 32 bit word, one bit is used to signify the sign (+/-), one more to signify if its a pointer, and 30 to store the number... right?
<dark_light> yes
<twobitsprite> I think that's how it works... I wish less people were idling, someone else in here could answer this much better than I...
<dark_light> twobitsprite, "if its a pointer"? i don't understand. if it stores a number or a memory address?
<twobitsprite> dark_light: correct
<dark_light> twobitsprite, why use the same type for pointers and ints?
<twobitsprite> dark_light: well... at the machine level, there is no such thing as "types"... types are implemented by compilers... to the computer its all bits...
<dark_light> so why use the same meaning for two things that can be separated?
<twobitsprite> which is why when you program in C you can use an int as a pointer and vice versa, the compiler would normally just give you a warning...
<twobitsprite> dark_light: what's the difference between a three letter string and an integer?
<dark_light> twobitsprite, at machine level there are no difference, but if i use a three letter string as a number, the compiler will say that's wrong
<dark_light> right?
<twobitsprite> i.e. the string is three 8-bit chunks ("characters") followed by an 8-bit zero (i.e. 00000000, "null")... it's just 16 bits, just like an integer...
<twobitsprite> dark_light: exactly, it's the compiler that knows, the computer doesn't
<dark_light> so why make the compiler know it?
<dark_light> ops
<dark_light> so why make the computer know it?
<dark_light> the computer doesn't need to know that an int is a pointer or a number
<twobitsprite> I'm not completely sure why ocaml needs that specific functionality, but it probably has something to do with the way it handles references...
<dark_light> well
<twobitsprite> again, I'm not the best person to ask these questions... I just remember reading somewhere on the ocaml page that it uses 30 bits for integers...
<dark_light> ahahahaha
<dark_light> :)
<twobitsprite> ?
<dark_light> twobitsprite, you seems to know a lot for someone that isn't the best person to ask these questions
<dark_light> ^^
ski has quit [Read error: 110 (Connection timed out)]
<dark_light> float abs(succ min_int);;
<dark_light> , it don't works.. but abs(succ min_int) is an int. the interpreter says This function is applied to too many arguments, maybe you forgot a `;'
<twobitsprite> well... its been a long time since I've actually looked into how ocaml handles ints and pointers, so I'm just not entirely sure...
<dark_light> twobitsprite, i never tried to do it, so yes you know a lot
<twobitsprite> dark_light: try float (abs (succ min_int))
<twobitsprite> you were trying to apply the function "float" to the two arguments "abs" and "(succ min_int)"...
<dark_light> thx
<dark_light> twobitsprite, hmmmmmmmm.. yeah
<Demitar> Did you ever get to the part of why ocaml needs a bit to determine if it's an int or a block (pointer if you wish)?
<dark_light> o.o
<twobitsprite> Demitar: I don't know why, do you?
* twobitsprite would love a more indepth explanation himself...
<Demitar> Well, it's due to the garbage collector, it needs to know what type an address is so it knows how much data it should free (and similar).
<twobitsprite> I can't even remember where I read that...
<twobitsprite> ahh hah... that makes sense
<twobitsprite> I was thinking maybe it had something to do with refs...
<Demitar> Also, only using a bit to determine that for ints is an optimization. Other values use two words (IIRC) (forming a block header) to determine the type.
<dark_light> Hmm
<Demitar> Sorry they're not called blocks, the proper terminology is boxed and unboxed values.
<twobitsprite> Demitar: ahh... you were confusing me with the block thing... :P
<dark_light> but, i don't understand really. how knowing the type would help to knowing how much data free? o.o
<Demitar> dark_light: How well versed are you in how a garbage collector works?
<dark_light> Demitar, i know that it helps lazy programmers to don't last things on memram
<dark_light> ... :)
<twobitsprite> dark_light: because when the garbage collector realises that a particular point in memory no long needs to be used, it will either simply free that spot, or follow the pointer and free whatever it points to as well... right Demitar?
<twobitsprite> ack... 2:18am... time for bed, I'll check the logs for an answer...
mrsolo_ has quit [Read error: 104 (Connection reset by peer)]
<twobitsprite> ahh..
* twobitsprite bookmarks
<twobitsprite> anyways, night
<Demitar> Especially section 18.2
<Demitar> Night.
<dark_light> twobitsprite, bye
mrsolo_ has joined #ocaml
<dark_light> and thanks a lot
<dark_light> =)
mrsolo_ has quit [Read error: 104 (Connection reset by peer)]
mrsolo_ has joined #ocaml
kryptt has joined #ocaml
mrsolo_ has quit [Read error: 104 (Connection reset by peer)]
mrsolo_ has joined #ocaml
mrsolo_ has quit [Connection reset by peer]
mrsolo_ has joined #ocaml
ski has joined #ocaml
ski_ has joined #ocaml
ski has quit [Nick collision from services.]
ski_ is now known as ski
perspectivet has quit [Read error: 110 (Connection timed out)]
<pango> <dark_light> why use the same type for pointers and ints?
<pango> because it cannot always be determined at compile time whether code will manipulate values stored only in one form or the other (mainly, I think, polymorphic functions)
<dark_light> hmm
<dark_light> i didn't knew about polymorhic functions
<dark_light> polymorpich
<dark_light> er
<dark_light> p-o-l-y-m-o-r-p-h-i-c
<dark_light> :)
<pango> # let make_tuple a b = (a, b) ;;
<pango> val make_tuple : 'a -> 'b -> 'a * 'b = <fun>
<pango> # (3, "hello") ;;
<pango> - : int * string = (3, "hello")
<pango> # (3.14, (3, "hello")) ;;
<pango> - : float * (int * string) = (3.14, (3, "hello"))
<dark_light> !!!
<dark_light> i am just beginning
<pango> # let id a = a ;;
<pango> val id : 'a -> 'a = <fun>
<pango> # id 3 ;;
<pango> - : int = 3
<pango> # id "blah" ;;
<pango> - : string = "blah"
<pango> if 'a' a boxed or unboxed value ? answer is "it depends"
<pango> s/if/is/
<pango> if both use a "word" of memory, id function code doesn't need to know
<pango> it just passes that word along, and it's done
<dark_light> hmmmmmmmmm....
<dark_light> oi
<dark_light> interesting
<dark_light> (hey, how can i verify if a value is int, string..?)
<pango> you usually don't need to at runtime, because ocaml is strongly typed... type is determined during compilation
joshcryer has quit ["'night"]
<pango> # let id a = a ;;
<pango> val id : 'a -> 'a = <fun>
<pango> # (id "hello") + 3 ;;
<pango> This expression has type string but is here used with type int
<dark_light> ??? o.o
<dark_light> ... o.o
<dark_light> the result if (id "hello") + 3 is.. ?
<dark_light> of*
<dark_light> there are any result?
kryptt has quit [Read error: 110 (Connection timed out)]
<pango> example using interpreter may not be very demonstrative, because compilation and evaluation are back-to-back... but the error message above comes from compilation phase, evalutation didn't even take place
<pango> you can check that by trying to compile it instead
<dark_light> i will try print_int((id "hello") + 3)
<pango> id is 'a -> 'a, which means a function that takes an argument of any type ('a is a "type variable"), and returns a value of that same type
<pango> so during compilation, it can already be determined that id "hello" value is a string, and + cannot be applied to strings. Compilation fails.
<dark_light> yeah, but..
<dark_light> if i receive an arbitrary argument, and i am trying to realize if it's a number or not.. (but, hmm.. yeah, an arbitrary argument will ever be a string)
<pango> # let add3 a = a + 3 ;;
<pango> val add3 : int -> int = <fun>
<pango> compilation has determined that add3 takes ints
<dark_light> i thinked about regexes, like ^[0-9]+$, but must be something more fast, specific for numbers
<pango> # add3 "hello" ;;
<pango> This expression has type string but is here used with type int
<pango> again, compilation error
<dark_light> pango, yeah i got it
<pango> the idea is to use types to avoid receiving values that you won't be able to handle later
<pango> of course it's not always possible, and that's were exceptions come handy
<dark_light> hm, yeah
<pango> # let div3 a = 3 / a ;;
<pango> val div3 : int -> int = <fun>
<pango> # div3 0 ;;
<pango> Exception: Division_by_zero.
<dark_light> i would better ask "there are any safe way to verify if a string could be an integer, or float.."
<pango> either parse it, as you suggested, or try int_of_string on it, and be ready to catch an exception
<pango> # int_of_string "hello" ;;
<pango> Exception: Failure "int_of_string".
<pango> that's beyond what types alone can handle
<dark_light> how could i parse the exception?
<pango> # let numericp a = try ignore(int_of_string a); true with Failure "int_of_string" -> false ;;
<pango> see try ... with ... flow control construct
<dark_light> o.o
<dark_light> true with Failure is part of the ocaml code?o.o
<pango> actually it's read as
<pango> # let numericp a =
<pango> try
<pango> ignore(int_of_string a);
<pango> true
<pango> with
<pango> Failure "int_of_string" -> false ;;
jo_l_apache has joined #ocaml
<pango> try/with construct allows to catch exceptions raised in the enclosed code ignore(int_of_string a); true
<dark_light> hmm o.o
Snark has joined #ocaml
<pango> and the evaluate other thing(s) based on the caught exception
<dark_light> ahm-ahm
<dark_light> pango, i would like someday really understand and think the way ocaml does the things
<pango> haven't started yet ;)
<dark_light> who, me?
<dark_light> yeah, you are right
<dark_light> :P
<fluxx> those sentences usually refer to the speaker ;)
<pango> if some ocaml code had to handle values that are either int or random non-numeric strings, the way to go would probably be to use sum types
<pango> # type i_dont_know = Numeric of int | NonNumeric of string ;;
<pango> type i_dont_know = Numeric of int | NonNumeric of string
<pango> # let analyse a = try Numeric (int_of_string a) with Failure "int_of_string" -> NonNumeric a ;;
<pango> val analyse : string -> i_dont_know = <fun>
<dark_light> O______O
<dark_light> you created a type i_dont_know that is like int or string?
<dark_light> O_O
<fluxx> I've found it useful to have a function 'valuefy' which wraps function's return value and exceptions into one sum type
<pango> dark_light: yes, something like that
<pango> # analyse "42" ;;
<pango> - : i_dont_know = Numeric 42
<pango> # analyse "hello" ;;
<pango> - : i_dont_know = NonNumeric "hello"
<dark_light> :~~~~~~~~~~~~~~~~
<dark_light> ocaml is very beautiful, but i just can't figure out a large program written on ocaml
<dark_light> (err.. i dont know exactly what is "figure out", hahaah.. for me it means "even imagine"..)
<dark_light> yeah, i know that it's possible, but i can't just imagine how the program would be
<pango> brb
pango is now known as pangoafk
pangoafk is now known as pango
<Demitar> dark_light: A fine mix of imperative and functional constructs hopefully. :)
<dark_light> it's easy to define when you know these constructs:)
<ski> twobitsprite : no call/cc, just tail-eval and exception-catching (though some SML impls have callCC)
m3ga has quit ["disappearing into the sunset"]
Revision17 has quit [Read error: 110 (Connection timed out)]
JohGro has joined #ocaml
<pango> twobitsprite: http://caml.inria.fr/pub/ml-archives/caml-list/2006/02/8fc9c1a56c497b9743515a5e3432d704.fr.html looks like a superset, from what I understand; Only works in bytecode however
jo_l_apache has quit ["leaving"]
smimou has joined #ocaml
_fab has joined #ocaml
_JusSx_ has joined #ocaml
descender has quit [Remote closed the connection]
<JohGro> My program becomes slower when compiling with the -unsafe option. Does anyone know what can be the problem?
__DL__ has joined #ocaml
<Demitar> Out of curiosity, how do you measure it?
gim has joined #ocaml
Skal has joined #ocaml
llama32 has joined #ocaml
<llama32> does compiled ocaml allow dynamic loading for plugins and such?
<JohGro> demita: "time ./a.out" with only this process taking significant amount of CPU (sorry for late reply).
jo_l_apache has joined #ocaml
<Demitar> JohGro: Is your application doing enough work to make that information reliable? (And the charm of IRC is the ability to keep a single conversation across several days. ;-)
<JohGro> Demitar: ocamlopt allAtom2d_array.ml && time ./a.out
<JohGro> real 2m14.006s
<JohGro> user 2m11.688s
<JohGro> sys 0m0.181s
<JohGro> ocamlopt -unsafe allAtom2d_array.ml && time ./a.out
<JohGro> real 2m27.159s
<JohGro> user 2m23.021s
<JohGro> sys 0m0.212s
<Demitar> That is indeed quite curious... :)
<JohGro> I used bigarrays first, and read that unsafe operations are available for arrays but not bigarrays, so I switched. Now I do not know what to expect.
<mellum> Might be noise due to different cache mapping.
<JohGro> I do not uderstand what that means :(
* Demitar <- too tired to come up with such wondrous speculation as mellum. :)
<JohGro> Do iI use my L2 cache in one of them, but not the other?
<mellum> Depending on which absolute addresses you use, there might be more or less conflicts between addresses in a not fully associative cache.
<mellum> Other than that, I don't see how -unsafe could possibly make code slower.
<JohGro> Could this be excluded if I run the program several times and get the same behaviour?
<mellum> Only if your OS does page coloring.
<mellum> erm. what I mean is only if the OS does page coloring, this effect would be consistent
<JohGro> The same effect is there when running with fewer iterations, but running the executable 10 times.
<JohGro> ocamlopt allAtom2d_array.ml && time for ((ix=0; ix<10; ix++ )) do { ./a.out; }; done
<JohGro> real 2m5.889s
<JohGro> user 2m1.817s
<JohGro> sys 0m0.222s
<JohGro> ocamlopt -unsafe allAtom2d_array.ml && time for ((ix=0; ix<10; ix++ )) do { ./a.out; }; done
<JohGro> real 2m23.927s
<JohGro> user 2m20.629s
<JohGro> sys 0m0.253s
<mellum> Weird. Did you try another machine with another architecture or OS? Or profiling?
<JohGro> No I have not. I have: uname -a
<JohGro> Linux shallow-blue 2.6.12-10-386 #1 Mon Feb 13 12:13:15 UTC 2006 i686 GNU/Linux
<JohGro> ocamlopt -v
<JohGro> The Objective Caml native-code compiler, version 3.08.3
<JohGro> Standard library directory: /usr/lib/ocaml/3.08.3
* pango wonders if http://www.cs.cornell.edu/Courses/cs612/2001SP/projects/ocaml-arrays/OCaml.pdf made it to the official compiler since 2001
<mellum> I don't think so. gcc does this now, though :)
JKnecht has quit ["leaving"]
JKnecht has joined #ocaml
jo_l_apache has quit ["leaving"]
mrsolo_ has quit [Connection reset by peer]
mrsolo_ has joined #ocaml
<JohGro> When I run on a different machine, the difference in times is only around 1%, but the unsafe program is still slower.
<JohGro> ocamlopt -unsafe allAtom2d_array.ml && time for ((ix=0; ix<10; ix++ )) do { ./a.out; }; done
<JohGro> real 1m30.487s
<JohGro> user 1m30.443s
<JohGro> sys 0m0.033s
<JohGro> ocamlopt allAtom2d_array.ml && time for ((ix=0; ix<10; ix++ )) do { ./a.out; }; done
<JohGro> real 1m29.893s
<JohGro> user 1m29.864s
<JohGro> sys 0m0.021s
<mellum> JohGro: is the program available somewhere?
llama32 has quit [Connection timed out]
__DL__ has quit ["Bye Bye"]
<JohGro> Not very well commented I am afraid :(
mrsolo_ has quit [Connection reset by peer]
mrsolo_ has joined #ocaml
<mellum> JohGro: for me, it's 8% faster with -unsafe
<mellum> but on an i386 system, it's also slower. So it is probably some i386 weirdness
<JohGro> Strange. I will ask on the ocaml-beginners list.
dop182 has joined #ocaml
dop182 has left #ocaml []
dark_light has quit ["dormir"]
jo_l_apache has joined #ocaml
<twobitsprite> hmmm... so, I can return from a function by falling off the end of the execution chain, or by raising an exception... is there any other way to return or "break out" of a function that doesn't involve exceptions? (i.e. continuation-passing style, etc...)
jo_l_apache has quit ["leaving"]
<zmdkrbou> "falling of the end of the execution chain" ?
<zmdkrbou> you mean tail-recursion ?
<mellum> twobitsprite: no
Smerdyakov has joined #ocaml
_fab has quit [Remote closed the connection]
mikeX has joined #ocaml
aleksi_ has joined #ocaml
paolino has joined #ocaml
<paolino> hi, on freebsd ledit doesn't compile with 3.09 and does with 3.08 .Any clue or suggestion?
<Smerdyakov> What error?
<paolino> File "pa_local.ml", line 19, characters 0-1:
<paolino> Unbound value _loc
<Smerdyakov> Try 'dummy_loc' instead of '_loc'.
<pango> smells like a -loc _loc missing
<paolino> does it make sense the fact it does compile in 3.08 ?
<pango> once you read the changelog, yes
<paolino> I hope I undestand it , as I don't speak ocaml at all
slipstream-- has joined #ocaml
slipstream-- has quit [Read error: 104 (Connection reset by peer)]
aleksi_ has quit ["Leaving"]
<paolino> I'm bad tripping this is the line I have to change I suppose
<paolino> $(PP) pa_extend.cmo q_MLast.cmo pa_local.ml -o pa_local.ppo
<paolino> $(COMP) -I `camlp4 -where` -c -impl pa_local.ppo
<paolino> who needs the -loc loc ?
slipstre1m-- has joined #ocaml
<pango> I guess $(PP) is camlp4, so just after $(PP) I'd say
<paolino> PP=camlp4r
<pango> The command camlp4r is a shortcut for:
<pango> camlp4 pa_r.cmo pa_rp.cmo pr_dump.cmo
<pango> so that's ok
slipstream has quit [Connection timed out]
<paolino> nothing, thanks anyway
<paolino> I'll try to use mldonkey.el
<pango> fighting with ledit ?
<paolino> yes
<pango> you could also try rlwrap
<pango> an alternative is to use, say, Debian patches... http://ftp.debian.org/debian/pool/main/l/ledit/ledit_1.11-7.diff.gz
<paolino> eh :)
pango is now known as pangoafk
pangoafk is now known as pango
paolino has quit [Read error: 110 (Connection timed out)]
bluestorm has joined #ocaml
jo_l_apache has joined #ocaml
khaladan_ has joined #ocaml
gim has quit [Read error: 110 (Connection timed out)]
khaladan has quit [Read error: 110 (Connection timed out)]
khaladan_ is now known as khaladan
jo_l_apache has quit ["leaving"]
Snark has quit ["Leaving"]
mrsolo_ has quit [Read error: 104 (Connection reset by peer)]
mrsolo_ has joined #ocaml
mrsolo_ has quit [Connection reset by peer]
mrsolo_ has joined #ocaml
mrsolo_ has quit [Connection reset by peer]
mrsolo_ has joined #ocaml
mrsolo_ has quit [Read error: 104 (Connection reset by peer)]
mrsolo_ has joined #ocaml
mrsolo_ has quit [Read error: 104 (Connection reset by peer)]
mrsolo_ has joined #ocaml
mrsolo_ has quit [Read error: 104 (Connection reset by peer)]
mrsolo_ has joined #ocaml
Plex|bday has joined #ocaml
Bigb[a]ng is now known as Bigbang
cookoo has left #ocaml []
<twobitsprite> why are there a lot of functions in the stdlib that aren't tail recursive?
<zmdkrbou> because they can't be written tail-recursively
<twobitsprite> I'm pretty sure I can write List.map tail-recursively...
<zmdkrbou> nope :)
<zmdkrbou> give it a try
<jer> Round 1: FIGHT!
<jer> =]
<zmdkrbou> :)
<zmdkrbou> in List.map you don't reverse the list, and you *must* keep it in order
<zmdkrbou> you can process it tail-recursively with List.fold_left ...
<zmdkrbou> and then you need List.rev :)
<jer> finish him! =D
<zmdkrbou> twobitsprite: the people who wrote the standard library *really* know how to code
<twobitsprite> zmdkrbou: ahh... I had just finished writing it when I came back to this window and see you say that...
<zmdkrbou> so what's your result ?
<twobitsprite> so... it _can_ be writen tail-recursively, you'd just have to reverse the list...
<zmdkrbou> yes but if you reverse the list then you need to tell the user
<zmdkrbou> and that's not a very friendly feature for a mapping function
<twobitsprite> er...
<twobitsprite> I have an error
<zmdkrbou> it's List.rev
<twobitsprite> the second call to helper should be a call to f
<twobitsprite> that too :P
<twobitsprite> (obviously, I didn't test it)
<twobitsprite> I'm pretty sure scheme's map function doesn't preserve the order of the results...
<twobitsprite> or is that for-each...?
<twobitsprite> no, for-each doesn't return results...
* twobitsprite shrugs
<zmdkrbou> twobitsprite: you just can't do a mapping function tail-recursively without reversing the list :)
<zmdkrbou> i mean theoritically
<twobitsprite> zmdkrbou: so your original statement was incorrect... I win :P
<zmdkrbou> it was not precise enough yes :)
<twobitsprite> but I do get your point... it's more efficient for small-to-reasonably sized lists to just do it non-tail recursively...
<twobitsprite> er... does ocaml rely on the C stack for function calls?
<zmdkrbou> what do you mean C stack ?
<zmdkrbou> there no relation beetwen ocaml and C
<zmdkrbou> between*
<twobitsprite> er... I'm used to python lingo... c stack means, i.e. using the asembler "call" statement...
<zmdkrbou> it's all about the stack in functionnal languages yes
bluestorm has quit [Remote closed the connection]
<zmdkrbou> that's why tail-recursivity is so good : you don't get any stack overflow
<twobitsprite> aren't there allocation problems with using "call"? i.e. aren't the c-centric OSs conservative with allowing deep recursion?
<zmdkrbou> the OS doesn't care about how you use the space he gave you
flux__ has joined #ocaml
<smimou> zmdkrbou: I've just read what you wrote, every function can be written tail-recursively (that's called the continuation passing style transformation)
* twobitsprite always thought of Linux as a she.... :P
fluxx has quit [niven.freenode.net irc.freenode.net]
<twobitsprite> smimou: can map be writen tail-recursively without then reversing a list at the end?
<zmdkrbou> smimou: yes ....
<zmdkrbou> smimou: but not in the "normal" usual way
<smimou> twobitsprite: yes
jer has quit ["Reconnecting"]
<zmdkrbou> they couldn't force everybody to use continuations
Smerdyakov has quit [niven.freenode.net irc.freenode.net]
JohGro has quit [niven.freenode.net irc.freenode.net]
Banana has quit [niven.freenode.net irc.freenode.net]
Amorphous has quit [niven.freenode.net irc.freenode.net]
ertai has quit [niven.freenode.net irc.freenode.net]
ellisonch has quit [niven.freenode.net irc.freenode.net]
knobo_ has quit [niven.freenode.net irc.freenode.net]
mattam has quit [niven.freenode.net irc.freenode.net]
det has quit [niven.freenode.net irc.freenode.net]
<twobitsprite> smimou: then I re-pose my question... why isn't List.map tail-recursive?
ulfdoz has quit [niven.freenode.net irc.freenode.net]
cmeme has quit [niven.freenode.net irc.freenode.net]
mellum has quit [niven.freenode.net irc.freenode.net]
jer has joined #ocaml
<zmdkrbou> twobitsprite: because you don't make a programmer-friendly stdlib by using continuation passing style
<smimou> twobitsprite: for efficiency reasons
<smimou> zmdkrbou: no
<zmdkrbou> smimou: you mean doing it in CPS and giving it away in a "wrapper" ?
<smimou> yes
<twobitsprite> don't a lot of scheme libs use continuations internally? You can had all that in the imlpementation of your program...
<twobitsprite> s/had/hise
<twobitsprite> hide*!
ellisonch has joined #ocaml
cmeme has joined #ocaml
ulfdoz has joined #ocaml
mellum has joined #ocaml
det has joined #ocaml
<twobitsprite> how is it more ineficient to use CPS?
ulfdoz has quit [niven.freenode.net irc.freenode.net]
det has quit [niven.freenode.net irc.freenode.net]
mellum has quit [niven.freenode.net irc.freenode.net]
cmeme has quit [niven.freenode.net irc.freenode.net]
ellisonch has quit [niven.freenode.net irc.freenode.net]
slipstre1m-- has quit [niven.freenode.net irc.freenode.net]
mikeX has quit [niven.freenode.net irc.freenode.net]
Skal has quit [niven.freenode.net irc.freenode.net]
ski has quit [niven.freenode.net irc.freenode.net]
dylan has quit [niven.freenode.net irc.freenode.net]
twobitsprite has quit [niven.freenode.net irc.freenode.net]
Demitar has quit [niven.freenode.net irc.freenode.net]
flux__ has quit [niven.freenode.net irc.freenode.net]
_JusSx_ has quit [niven.freenode.net irc.freenode.net]
pango has quit [niven.freenode.net irc.freenode.net]
Bigbang has quit [niven.freenode.net irc.freenode.net]
chimikal has quit [niven.freenode.net irc.freenode.net]
Hadaka has quit [niven.freenode.net irc.freenode.net]
jer has quit [niven.freenode.net irc.freenode.net]
khaladan has quit [niven.freenode.net irc.freenode.net]
dvekravy has quit [niven.freenode.net irc.freenode.net]
TaXules has quit [niven.freenode.net irc.freenode.net]
Oatmeat|umn has quit [niven.freenode.net irc.freenode.net]
Poopsmith has quit [niven.freenode.net irc.freenode.net]
alch` has quit [niven.freenode.net irc.freenode.net]
mrsolo_ has quit [niven.freenode.net irc.freenode.net]
JKnecht has quit [niven.freenode.net irc.freenode.net]
CLxyz has quit [niven.freenode.net irc.freenode.net]
sieni_ has quit [niven.freenode.net irc.freenode.net]
skylan has quit [niven.freenode.net irc.freenode.net]
pattern has quit [niven.freenode.net irc.freenode.net]
skylan has joined #ocaml
pattern has joined #ocaml
CLxyz has joined #ocaml
twobitsprite has joined #ocaml
ellisonch has joined #ocaml
clog has joined #ocaml
JKnecht has joined #ocaml
CLxyz has joined #ocaml
Skal has joined #ocaml
Hadaka has joined #ocaml
khaladan has joined #ocaml
Bigbang has joined #ocaml
pango has joined #ocaml
slipstream has joined #ocaml
shrimpx has joined #ocaml
Plex|bday has joined #ocaml
Demitar has joined #ocaml
mrsolo_ has joined #ocaml
_JusSx_ has joined #ocaml
TaXules has joined #ocaml
Oatmeat|umn has joined #ocaml
pattern has joined #ocaml
twobitsprite has joined #ocaml
<twobitsprite> it's like a roller coast *throws hands in air and yells*
<twobitsprite> coaster*
sieni has joined #ocaml
smimou has joined #ocaml
dvekravy has joined #ocaml
ski has joined #ocaml
Smerdyakov has joined #ocaml
JohGro has joined #ocaml
flux__ has joined #ocaml
jer has joined #ocaml
alch` has joined #ocaml
skylan has joined #ocaml
Amorphous has joined #ocaml
knobo has joined #ocaml
mikeX has joined #ocaml
chimikal has joined #ocaml
zmdkrbou has joined #ocaml
<zmdkrbou> apfffff freenode
<jer> world is rehubbing, please stand by
<jer> =D
* twobitsprite braces in anticipation of after-quakes
mattam has joined #ocaml
Banana has joined #ocaml
ertai has joined #ocaml
Poopsmith has joined #ocaml
dylan has joined #ocaml
_JusSx_ has quit ["leaving"]
smimou has quit ["bli"]
gim has joined #ocaml
Skal has quit ["Client exiting"]
Bigbang is now known as Bigb[a]ng
dark_light has joined #ocaml
Plex|bday has quit [Read error: 104 (Connection reset by peer)]
mikeX has quit ["zzz"]
joshcryer has joined #ocaml
Smerdyakov has quit ["Leaving"]
Smerdyakov has joined #ocaml
mrsolo_ has quit [Read error: 104 (Connection reset by peer)]
mrsolo_ has joined #ocaml
mrsolo_ has quit [Read error: 104 (Connection reset by peer)]
mrsolo_ has joined #ocaml
mrsolo_ has quit [Read error: 104 (Connection reset by peer)]
mrsolo_ has joined #ocaml