mbishop changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | Grab Ocaml 3.10.0 from http://caml.inria.fr/ocaml/release.html (featuring new camlp4 and more!)
ertai has quit [Read error: 110 (Connection timed out)]
seafood has quit [Read error: 104 (Connection reset by peer)]
seafood has joined #ocaml
bluestorm has quit ["Konversation terminated!"]
jedai has quit [Read error: 104 (Connection reset by peer)]
seafood_ has quit [calvino.freenode.net irc.freenode.net]
kelaouchi has quit [calvino.freenode.net irc.freenode.net]
Associat0r has quit [calvino.freenode.net irc.freenode.net]
kreaturr1 has quit [calvino.freenode.net irc.freenode.net]
tsuyoshi has quit [calvino.freenode.net irc.freenode.net]
acatout has quit [calvino.freenode.net irc.freenode.net]
acatout has joined #ocaml
tsuyoshi has joined #ocaml
Associ8or has joined #ocaml
seafood_ has joined #ocaml
kelaouchi has joined #ocaml
kreaturr has joined #ocaml
mae has joined #ocaml
<mae> yo
bzzbzz has quit ["Lost terminal"]
seafood_ has quit []
Demitar has quit [Read error: 110 (Connection timed out)]
bzzbzz has joined #ocaml
seafood_ has joined #ocaml
seafood_ has quit []
<orbitz> hello
buluca has quit [Read error: 113 (No route to host)]
mae has left #ocaml []
Associ8or has quit []
mordaunt has joined #ocaml
brooksbp has joined #ocaml
brooksbp has quit [Client Quit]
brooksbp has joined #ocaml
mxc has joined #ocaml
Jeff_123 has joined #ocaml
seafood_ has joined #ocaml
buluca has joined #ocaml
seafood_ has quit []
dibblego has joined #ocaml
buluca has quit [Read error: 113 (No route to host)]
ttamttam has joined #ocaml
Jeff_123 has quit []
kelaouchi has quit ["leaving"]
brooksbp has quit []
asmanur has joined #ocaml
mordaunt has quit [Read error: 104 (Connection reset by peer)]
bluestorm has joined #ocaml
Associat0r has joined #ocaml
asmanur is now known as asma
Demitar has joined #ocaml
jedai has joined #ocaml
richardw has quit [Read error: 104 (Connection reset by peer)]
kelaouchi has joined #ocaml
ertai has joined #ocaml
mxcantor has joined #ocaml
mxc has quit [Read error: 104 (Connection reset by peer)]
mxcantor_ has joined #ocaml
Morphous has joined #ocaml
Amorphous has quit [Nick collision from services.]
Morphous has quit [Read error: 104 (Connection reset by peer)]
Amorphous has joined #ocaml
wy has quit ["Ex-Chat"]
mxcantor has quit [Read error: 113 (No route to host)]
Proteus has joined #ocaml
l_a_m has joined #ocaml
ertai has quit [Read error: 110 (Connection timed out)]
Proteus has quit [Remote closed the connection]
<diosmalo> hi
<diosmalo> Inconsistency detected by ld.so: dl-runtime.c: 76: fixup: Assertion `((reloc->r_info) & 0xff) == 7' failed!
<diosmalo> when i compiled succ_rec and did put 900 MiB for ulimit -s and Gc.stack_limit, and succ_rec(240000000)
<diosmalo> with ocamlopt
ertai has joined #ocaml
<pango_> looks like a problem in the glibc... Maybe it doesn't handle such large stack, or something
mxcantor_ has quit []
kelaouchi has quit [Read error: 104 (Connection reset by peer)]
<pango_> diosmalo: btw, you haven't shown your succ_rec code, nor mentionned on what architecture you're doing this experimentation...
<pango_> but 900MB/240000000 ~ 4 bytes, or one word on a 32 bit arch. That's not much for a stack frame
<diosmalo> i686 and let rec succ_rec = function 0 -> 1 | n -> 1 + succ_rec (n - 1) ;;
<pango_> I hope ocamlopt code only pushes return address on the stack then, there's no room for anything else...
<orbitz> mrning
<orbitz> came across http://www.podval.org/~sds/ocaml-sucks.html yesterday
<orbitz> written by lisp lover which == language snob but i think it does make some valid points
<diosmalo> pango_: it should say "Segmentation Fault" but it said "Inconsistency detected by ld.so: dl-runtime.c: 76: fixup: Assertion ......."
<bluestorm> interesting
<bluestorm> (haven't read it yet)
<orbitz> in the end i woudl say the points it makes for ocaml sucking are true but when you do the cost analysis of that to oher langauges it's not so bad relatively
<bluestorm> orbitz:
<bluestorm> « Another subtle issue (which cuts both ways, of course) is that you cannot easily modify the behavior of a module outside of it. »
<bluestorm> that's right, but the conclusions he draws from it are false
<bluestorm> you can always redefine a new module
<bluestorm> include the old one
<bluestorm> and refine the behaviour
<pango_> diosmalo: actually it should raise an exception, but that doesn't work in all cases on all platforms
<bluestorm> (or at least extend it)
<orbitz> bluestorm: can you call the original function?
<bluestorm> OldModule.func ?
<bluestorm> hm
<orbitz> what if you are overwriting teh Date module
<bluestorm> you could extend it with another name
<orbitz> i think his conclusino is false but perhaps his major complaint is he wishes to redefine the funciton or his new behavior but also call th eold funciton fo rth eold ehavior
<orbitz> is that possible?
<bluestorm> from his Date module
<bluestorm> i would provied an MoreDate module
<bluestorm> with an added function that does what he wants
<bluestorm> MoreDate.date_of_iso_string for example
<bluestorm> i could even call the new module Date too, but that sound tricky for no benefits
<pango_> diosmalo: in this case, I suppose the program even fails to start, because of a problem in the glibc
<orbitz> bluestorm: right, i think that is not what he wants to do though
<bluestorm> (it would be possible to redefine directly the date_of_string in my new module, but that sounds like a bad idea)
<orbitz> bluestorm: but i don't really see how that is a valid argument either way, most language cannot od this
<diosmalo> is the loader that fails, i've not more idea
<bluestorm> the wrapper argument is strange too
<bluestorm> "ok you can do it quite easily, but still i suppose it's not done right"
<diosmalo> pango_: no, no, the program doesn't fail to start
<bluestorm> "Places" is strange too
<diosmalo> it fails "real 0m6.230s" later
<bluestorm> let (+=) aref b = aref := !aref + b
<pango_> weird
<diosmalo> yes, is weird the code generation of ocamlopt with linker and libraries.
<orbitz> bluestorm: that won't work with floats
<orbitz> or Int64's
<diosmalo> is there MPFR wrapper for ocaml?
<bluestorm> let (+.=) aref b = aref := !aref +. b;
<bluestorm> the "no overloading" argument is given after that one
<diosmalo> i want sin(x) of 100 digits
<orbitz> ocaml-tutorials has an argument for + and +.
<pango_> diosmalo: check the hump
<diosmalo> thanks pango_
<orbitz> saying implicitly brinign an int to a float can be expensive andd this allows you to only do the operationg when you need to but i'm not sure i buy that arugetn
<orbitz> you could make + only with on 'a in which case you woudln't ahve implicit conversion of an int to a float
<orbitz> i'm unsure of how i feel about + vs +., i think it's kind of annoying in many ways but i haven't done much numericl work in ocaml
<bluestorm> orbitz: if you need havy float work, you can always rebind (+.) on (+) locally
<bluestorm> +e
<orbitz> what would be nice though is beign able to overlaod + and firends for any arithmetic type you create (rather than Num moudle have +/ // etc)
<bluestorm> there is a syntax extension to do that automagically btw
<orbitz> bluestorm: i could see that working long enough to realize that you DO ned int arithmetic in some specific place and slapping your head fo rit
<orbitz> bluestorm: wha ti sit?
<bluestorm> orbitz: adding generic overloading would add substantial complexity to the language
<bluestorm> orbitz:
<bluestorm> let add = (+) in let (+) = (+.)
<bluestorm> Pervasives.(+) would still work anyway
<bluestorm> but it's a bit heavy
<orbitz> bluestorm: i agree. i'm not sure the win would be worth the loss, but just throwing ideas out
<bluestorm> some peoples have worked on overloading
<orbitz> bluestorm: (you could probably use 'and' there since th redefintion of (+) doens't require add
<bluestorm> orbitz: i could, but that would add some headache
<bluestorm> "are they mutually recursive ?"
<orbitz> no
<orbitz> and bindings dont' exist at that poitn in order ot reference each other do they?
<bluestorm> hn
<bluestorm> the MyInt argument is strange too
<orbitz> thats' why you can do let foo x y = let x = x + y and y = x - y
<bluestorm> looks like he wants to show we lack second-order polymorphism
<orbitz> i'd like to conitnuet his but i have work ufnorutnately!. if you keep on talking i'll hceck the back log tonight
<bluestorm> but the example is really strange
<bluestorm> works well
<bluestorm> and i don't see what additional value he gets from his strange function
<bluestorm> "No dynamic variables" > http://okmij.org/ftp/Computation/dynamic-binding.html (haven't tried it)
<bluestorm> "Order of evaluation" : i think right-to-left evaluation is the natural choice w.r.t curryfication / partial application
filp has joined #ocaml
<bluestorm> hm
<bluestorm> i'd say globally that he criticizes : 1) static typing 2) absence of overloading 3) absence of macros
<bluestorm> i don't think we can do much for 1) and 2)
<bluestorm> concerning the 3) , i think camlp4 (syntaxic approach) and MetaOCaml (code-generation approach) may be enough
<bluestorm> but i don't know lisp, so maybe i ignore some impressive things you can do with macros that aren't available to us ocamlers
<bluestorm> the others points are not very interesting, except maybe for the Standard Library critic : i agree the standard library could be improved
<bluestorm> (there is a point about the error reporting from the compiler : i'm not sure usual type-checking algorithms make the modification he wants so easy to implement)
buluca has joined #ocaml
junis has joined #ocaml
Proteus has joined #ocaml
filp has quit ["Bye"]
kelaouchi has joined #ocaml
buluca has quit [Read error: 113 (No route to host)]
<diosmalo> the problem lisp is the lost laberynth of parentheses!
ttamttam has left #ocaml []
jdavis__ has quit [Read error: 110 (Connection timed out)]
mrpingoo has joined #ocaml
l_a_m has quit [Remote closed the connection]
pango_ has quit [Remote closed the connection]
pango_ has joined #ocaml
kreaturr has quit [calvino.freenode.net irc.freenode.net]
junis has quit [calvino.freenode.net irc.freenode.net]
tsuyoshi has quit [calvino.freenode.net irc.freenode.net]
acatout has quit [calvino.freenode.net irc.freenode.net]
asma has quit [calvino.freenode.net irc.freenode.net]
jonafan has quit [calvino.freenode.net irc.freenode.net]
mbishop has quit [calvino.freenode.net irc.freenode.net]
|Catch22| has quit [calvino.freenode.net irc.freenode.net]
netx has quit [calvino.freenode.net irc.freenode.net]
noj has quit [calvino.freenode.net irc.freenode.net]
flux has quit [calvino.freenode.net irc.freenode.net]
Hadaka has quit [calvino.freenode.net irc.freenode.net]
Demitar has quit [calvino.freenode.net irc.freenode.net]
jedai has quit [calvino.freenode.net irc.freenode.net]
jlouis has quit [calvino.freenode.net irc.freenode.net]
mattam has quit [calvino.freenode.net irc.freenode.net]
Sparkles has quit [calvino.freenode.net irc.freenode.net]
kelaouchi has quit [calvino.freenode.net irc.freenode.net]
seafood has quit [calvino.freenode.net irc.freenode.net]
bebui_ has quit [calvino.freenode.net irc.freenode.net]
Associat0r has quit [calvino.freenode.net irc.freenode.net]
bluestorm has quit [calvino.freenode.net irc.freenode.net]
DerDracle_ has quit [calvino.freenode.net irc.freenode.net]
orbitz has quit [calvino.freenode.net irc.freenode.net]
jeremiah has quit [calvino.freenode.net irc.freenode.net]
jdavis_ has quit [calvino.freenode.net irc.freenode.net]
unfo- has quit [calvino.freenode.net irc.freenode.net]
pattern has quit [calvino.freenode.net irc.freenode.net]
Proteus has quit [calvino.freenode.net irc.freenode.net]
ertai has quit [calvino.freenode.net irc.freenode.net]
bzzbzz has quit [calvino.freenode.net irc.freenode.net]
jnkm has quit [calvino.freenode.net irc.freenode.net]
diosmalo has quit [calvino.freenode.net irc.freenode.net]
pango_ has quit [calvino.freenode.net irc.freenode.net]
Smerdyakov has quit [calvino.freenode.net irc.freenode.net]
cmeme has quit [calvino.freenode.net irc.freenode.net]
eroyf has quit [calvino.freenode.net irc.freenode.net]
dibblego has quit [calvino.freenode.net irc.freenode.net]
smimou has quit [calvino.freenode.net irc.freenode.net]
opening` has quit [calvino.freenode.net irc.freenode.net]
TaXules has quit [calvino.freenode.net irc.freenode.net]
petchema has quit [calvino.freenode.net irc.freenode.net]
hcarty has quit [calvino.freenode.net irc.freenode.net]
svenl has quit [calvino.freenode.net irc.freenode.net]
pango_ has joined #ocaml
kelaouchi has joined #ocaml
Proteus has joined #ocaml
junis has joined #ocaml
ertai has joined #ocaml
jedai has joined #ocaml
Demitar has joined #ocaml
Associat0r has joined #ocaml
bluestorm has joined #ocaml
asma has joined #ocaml
dibblego has joined #ocaml
bzzbzz has joined #ocaml
kreaturr has joined #ocaml
tsuyoshi has joined #ocaml
acatout has joined #ocaml
seafood has joined #ocaml
jnkm has joined #ocaml
jonafan has joined #ocaml
DerDracle_ has joined #ocaml
smimou has joined #ocaml
jlouis has joined #ocaml
mbishop has joined #ocaml
opening` has joined #ocaml
Smerdyakov has joined #ocaml
diosmalo has joined #ocaml
mattam has joined #ocaml
TaXules has joined #ocaml
|Catch22| has joined #ocaml
cmeme has joined #ocaml
bebui_ has joined #ocaml
orbitz has joined #ocaml
netx has joined #ocaml
jeremiah has joined #ocaml
petchema has joined #ocaml
hcarty has joined #ocaml
svenl has joined #ocaml
eroyf has joined #ocaml
jdavis_ has joined #ocaml
unfo- has joined #ocaml
Sparkles has joined #ocaml
pattern has joined #ocaml
Hadaka has joined #ocaml
flux has joined #ocaml
noj has joined #ocaml
<hcarty> Proteus: To answer your question from a day or two ago - I have not tried the JoCaml network setup, just for one system
FZ has joined #ocaml
leo037 has joined #ocaml
leo037 has quit ["Leaving"]
junis has quit [calvino.freenode.net irc.freenode.net]
tsuyoshi has quit [calvino.freenode.net irc.freenode.net]
acatout has quit [calvino.freenode.net irc.freenode.net]
kreaturr has quit [calvino.freenode.net irc.freenode.net]
junis has joined #ocaml
kreaturr has joined #ocaml
tsuyoshi has joined #ocaml
acatout has joined #ocaml
kreaturr_ has joined #ocaml
bzzbzz has quit ["leaving"]
mrpingoo has quit ["Connection reset by pear"]
junis has quit [Connection timed out]
junis has joined #ocaml
kreaturr has quit [Connection timed out]
smimou has quit ["bli"]
richardw has joined #ocaml
jdavis__ has joined #ocaml
buluca has joined #ocaml
asma has quit [Remote closed the connection]
smimou has joined #ocaml
mrsolo_ has quit [Read error: 104 (Connection reset by peer)]
ertai has quit [Read error: 110 (Connection timed out)]
jdavis__ has quit ["Leaving"]
zmdkrbou_ has joined #ocaml
zmdkrbou has quit [Read error: 113 (No route to host)]
diosmalo is now known as malodios
Anarchos has joined #ocaml
bluestorm has quit ["Konversation terminated!"]
bluestorm has joined #ocaml
wy has joined #ocaml
wy has quit [Remote closed the connection]
ertai has joined #ocaml
<jonafan> how do you define a pair as a type...
<jonafan> like
<jonafan> type flimflam = string * string;;
<jonafan> let x = "flim", "flam";;
<jonafan> ocaml would say x is a string * string, but i'd like for it to know i mean it as a flimflam!
<jonafan> i guess i could use a constructor
jeremiah has quit ["KVIrc 3.2.6 Anomalies http://www.kvirc.net/"]
<bluestorm> jonafan:
jhome has joined #ocaml
<bluestorm> you could force the type
<bluestorm> let (x : flimflam) = "flim", "flam"
<bluestorm> but this is considered awkward
<bluestorm> if you're planning to do a multiple-modules application
<bluestorm> you'll be able to specify that in the interface (.mli)
bluestorm has quit ["Konversation terminated!"]
<jonafan> cool, but awkward
<jonafan> i thought i tried this
rayno has joined #ocaml
<Anarchos> jonafan have you tried enumerated types ? Like type flimflam = FlimFlam of string * string;;
bluestorm has joined #ocaml
<jonafan> yeah that works too, but i wanted to get rid of the constructor
<jonafan> i'm not sure which approach is better
<pango_> flimflam is the same as string * string, where you can use one, you can use the other
<bluestorm> if it's a toy code (teaching purposes or something like that), a constructor is not bad
<pango_> ocaml typing is not based on type names
<bluestorm> type flimflam = Flimflam of (string * string)
<bluestorm> on one-constructor types you can use a handy pattern-matching syntax for values and functions declarations
<bluestorm> let name (Flimflam (foo, bar)) = foo
<Anarchos> Strange that two callbacks protected by leave/enter blocking sections enter both at the same time in caml_interprete !!
<jonafan> okay, so forcing the type does nothing for enforcing the type
<jonafan> so i guess a constructor is better for what i was thinking about
<Anarchos> jonafan yes.
jlouis has quit [Remote closed the connection]
jlouis has joined #ocaml
bluestorm has quit [Remote closed the connection]
bluestorm has joined #ocaml
bluestorm has quit [Remote closed the connection]
ertai has quit [Read error: 110 (Connection timed out)]
jeremiah has joined #ocaml
zmdkrbou_ has quit [Read error: 110 (Connection timed out)]
Anarchos has quit ["Vision[0.8.5-0418]: i've been blurred!"]
rayno has quit ["Leaving"]