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!)
jlouis_ has quit [Read error: 110 (Connection timed out)]
<pchiusano> how do you decide when to use let vs. let rec
<ita> pchiusano: when you have recursivity ?
hkBst has quit ["Konversation terminated!"]
<jonafan> you can use it for every function if you want
<pchiusano> okay... why is the distinction needed?
Morphous has joined #ocaml
<pango> because both can be useful
<pchiusano> like, if let rec always works, why not just have one let?
<pango> it always works, but does not do what you want
<ita> pchiusano: to make recursion explicitly defined ?
<jonafan> maybe you want to use the old function by that name in the function body
<pango> a/not/not always/
<pchiusano> jonafan, i see
<pango> some say it has a 'documentation' value too (helpful to list recursive functions if you run into stack overflows ;) )
<pchiusano> hmm
<pchiusano> okay, I am satisfied :)
<pchiusano> what does "Unbound constructor" mean?
<pchiusano> nm
<pchiusano> basically just means "undeclared identifier"
<pchiusano> if I have a module, is there a way I can refer to its members without needing to use fully qualified names?
seafood_ has joined #ocaml
<pango> for identifiers that start with a capital (= constructors or module names)
<pchiusano> pango: i see
<pchiusano> is there a way you can define type aliases?
Morphous_ has quit [Read error: 110 (Connection timed out)]
jlouis has joined #ocaml
<pchiusano> man, ocamlc is FAST
nuncanada has quit ["Leaving"]
<jcpiza> what is the difference between ocamlc and ocamlopt?
<jcpiza> is ocamlopt a replacement of ocamlc?
<jonafan> no
<jonafan> ocamlopt generates machine code
<jonafan> ocamlc just makes bytecode that executes through ocaml
<pango> ocamlc is the bytecode compiler, ocamlopt is the native compiler (where available)
<pango> btw, ocamlc.opt is the natively compiler bytecode compiler, and ocamlopt.opt is the natively compiler native compiler
<pango> mmh natively compiled native compiler, rather
<pango> *.opt versions have strictly the same results as ocamlc and ocamlopt (and are supposed to be slightly faster, specially on large inputs), but ocamlc and ocamlopt have different results
jlouis__ has quit [Read error: 110 (Connection timed out)]
<pchiusano> different results?
<pango> jonafan: that's what I meant by native compilation
<pango> jonafan: thru ocamlrun, to be exact
<jonafan> right
<jonafan> did my chat lag or something
<pango> I'm possibly lagging myself, thanks to tor
<jonafan> ah
<jonafan> well, i said that stuff before you did on my screen
<jonafan> so i wasn't disagreeing or clarifying!
<jonafan> you were the clarifying one
<pango> np
<pango> pchiusano: ocamlc is a bytecode compiler, like Pascal, Java, etc. The files it generates need some kind of low-level interpretation to be executed
<pchiusano> right
<pchiusano> but you would hope that generates the same results as natively compiled code
<jcpiza> a question: does ocamlopt internally "bytecode program" -> "native program" similar to Java's JIT?
<pango> jcpiza: no
<pango> jcpiza: they're separate compilers
<jcpiza> or "source program" -> "native program" directly?
<pchiusano> when doing matching, like match foo with (x, [1,2]), is there a way I can bind (x, [1,2]) to another variable, short of introducing another let?
<madroach> match foo with (x, [1,2]) as bar
<jcpiza> is program.opt in native machine equal garbage collected as program.non-opt in virtual machine?
<pango> compilers use several intermediate representations, and I don't think any intermediate representation used by ocamlopt closely matches bytecode structure; But I'm not an ocaml compilers specialist
<pango> jcpiza: yes, datastructures and memory management is exactly the same
<jcpiza> the speed is the same?
<madroach> jcpiza: ocamlopt will be about 2-10times faster
<pango> jcpiza: speed of execution is obviously different, otherwise there would be no point in having a native compiler
<jcpiza> wow! thanks!
<madroach> but the compilation process will be faster and portable with ocamlc
<jonafan> in my highly informal tests, ocamlopt output is slightly faster than gcc without -O
<jcpiza> jonafan: hehehe, gcc without -O has not garbage collection.
ita has quit ["Hasta luego!"]
madroach has quit [Remote closed the connection]
<pango> jcpiza: so?
<jcpiza> very thanks pango.
pango is now known as pangoafk
pangoafk is now known as pango
pchiusano has quit [Read error: 110 (Connection timed out)]
qpu has joined #ocaml
Bzek has joined #ocaml
Bzek has left #ocaml []
Torment has joined #ocaml
Jedai has quit [Read error: 110 (Connection timed out)]
Associ8or has quit []
Mr_Awesome has joined #ocaml
wy has joined #ocaml
Jeff_123 has joined #ocaml
buluca has quit [Read error: 104 (Connection reset by peer)]
Jomyoot has joined #ocaml
Jeff_123 has quit []
Proteus has joined #ocaml
wy has quit ["Ex-Chat"]
wy has joined #ocaml
Jomyoot has quit []
mordaunt has joined #ocaml
olleolleolle has joined #ocaml
olleolleolle has quit []
olleolleolle has joined #ocaml
kreaturr has quit [Read error: 110 (Connection timed out)]
ikaros has joined #ocaml
olleolleolle has quit []
kreaturr has joined #ocaml
mordaunt has quit [Remote closed the connection]
ikaros has quit ["segfault"]
ttamttam has joined #ocaml
Jeff_123 has joined #ocaml
kreaturr_ has joined #ocaml
seafood_ has quit []
kreaturr has quit [Read error: 110 (Connection timed out)]
ygrek has quit [Remote closed the connection]
ttamttam has left #ocaml []
ttamttam has joined #ocaml
Jeff_123 has quit []
seafood_ has joined #ocaml
olleolleolle has joined #ocaml
qpu has quit []
olleolleolle has quit []
olleolleolle has joined #ocaml
qpu has joined #ocaml
pango has quit [Remote closed the connection]
pango has joined #ocaml
olleolleolle has left #ocaml []
seafood__ has joined #ocaml
buluca has joined #ocaml
qpu has quit []
filp has joined #ocaml
seafood_ has quit [Read error: 110 (Connection timed out)]
brooksbp has joined #ocaml
buluc1 has joined #ocaml
buluca has quit [Nick collision from services.]
buluc1 is now known as buluca
kreaturr_ has quit [calvino.freenode.net irc.freenode.net]
acatout has quit [calvino.freenode.net irc.freenode.net]
tsuyoshi has quit [calvino.freenode.net irc.freenode.net]
zmdkrbou has quit [calvino.freenode.net irc.freenode.net]
kreaturr_ has joined #ocaml
acatout has joined #ocaml
zmdkrbou has joined #ocaml
tsuyoshi has joined #ocaml
Associat0r has joined #ocaml
Associat0r 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]
zmdkrbou has quit [calvino.freenode.net irc.freenode.net]
kreaturr_ has quit [calvino.freenode.net irc.freenode.net]
Associat0r has joined #ocaml
kreaturr_ has joined #ocaml
acatout has joined #ocaml
zmdkrbou has joined #ocaml
tsuyoshi has joined #ocaml
wy__ has joined #ocaml
wy__ has quit [Client Quit]
hkBst has joined #ocaml
brooksbp has quit []
Mr_Awesome has quit ["aunt jemima is the devil!"]
Tetsuo has joined #ocaml
marmottine has joined #ocaml
jlouis_ has joined #ocaml
asmanur has joined #ocaml
jlouis has quit [Read error: 110 (Connection timed out)]
Tetsuo has quit [Remote closed the connection]
rwmjones has quit ["Closed connection"]
rwmjones has joined #ocaml
Yoric[DT] has joined #ocaml
<Yoric[DT]> hi
Yoric[DT] has quit ["Ex-Chat"]
Yoric[DT] has joined #ocaml
Tetsuo has joined #ocaml
madroach has joined #ocaml
FZ has joined #ocaml
ita has joined #ocaml
seafood__ has quit []
Snark has joined #ocaml
jlouis has joined #ocaml
jlouis_ has quit [Read error: 110 (Connection timed out)]
filp has quit ["Bye"]
filp has joined #ocaml
Morphous_ has joined #ocaml
Tetsuo has quit ["Leaving"]
Morphous has quit [Read error: 110 (Connection timed out)]
buluca has quit [Read error: 113 (No route to host)]
ertai has joined #ocaml
* jcpiza is back (gone 37:11:54)
* jcpiza is away: I go away.
RobertFischer has joined #ocaml
pango has quit [Remote closed the connection]
pango has joined #ocaml
bongy has joined #ocaml
wy has quit ["Ex-Chat"]
Yoric[DT] has quit [Read error: 110 (Connection timed out)]
bla has quit [Read error: 110 (Connection timed out)]
RobertFischer has quit ["Trillian (http://www.ceruleanstudios.com"]
RobertFischer has joined #ocaml
bongy has quit [Read error: 110 (Connection timed out)]
Jomyoot has joined #ocaml
<Jomyoot> What's with revised sytnax?
ttamttam has left #ocaml []
filp has quit ["Bye"]
Jomyoot has quit []
ita has quit [Remote closed the connection]
ttamttam has joined #ocaml
rwmjones has quit ["Closed connection"]
buluca has joined #ocaml
ertai has quit [Read error: 113 (No route to host)]
olleolleolle has joined #ocaml
olleolleolle has left #ocaml []
olleolleolle has joined #ocaml
olleolleolle has left #ocaml []
ygrek has joined #ocaml
Tetsuo has joined #ocaml
bluestorm has joined #ocaml
qpu has joined #ocaml
asmanur has quit [Connection timed out]
lde has joined #ocaml
madroach has left #ocaml []
asmanur has joined #ocaml
ita has joined #ocaml
buluca has quit [Read error: 113 (No route to host)]
bluestorm has quit [Remote closed the connection]
qpu has quit []
qpu has joined #ocaml
Snark has quit ["Quitte"]
asmanur has quit [Remote closed the connection]
Mr_Awesome has joined #ocaml
Yoric[DT] has joined #ocaml
paulc has joined #ocaml
<paulc> hi
<paulc> how do I refer to a list of a's in a variant type?
<paulc> like type 'a tree = Leaf of 'a | Branch of ['a]
ygrek has quit [Remote closed the connection]
<pango> type 'a tree = Leaf of 'a | Branch of 'a list ?
<paulc> okay, so list is the named type for []'s
<pango> type 'a list = [] | :: of 'a * 'a list (not actual OCaml code)
<paulc> okay
<pango> that's how it would be defined if [] and :: were 'normal' constructor names
<paulc> right
<pango> plus some syntactic sugar to allow [a; b; c] <=> a :: b :: c :: []
<paulc> can you define variant types whose ctors are infix operators like list?
<pango> they're constructors, not operators
<pango> and no, I don't think it's possible
<pango> (short of defining your own syntax with Camlp4, I guess)
<paulc> okay, I meant, ctors with infix syntax
<paulc> but okay
lde has quit [Remote closed the connection]
ttamttam has left #ocaml []
<paulc> are you not allowed to reference tuples in ctors, like:
<paulc> type 'a foo = Foo of ('a, int) * int
pango has quit [Remote closed the connection]
pango has joined #ocaml
<pango> (stupid network)
<pango> * is how one writes tuples types
<Yoric[DT]> pango: should work with more parenthesis.
<pango> type 'a foo = Foo of 'a * int * int
<Yoric[DT]> er...
<Yoric[DT]> or not
<Yoric[DT]> type 'a foo = Foo of (('a * int) * int);;
<xavierbot> type 'a foo = Foo of (('a * int) * int)
<paulc> hmm
<Yoric[DT]> (or 'a * int * int if you want a triple and not two pairs)
<pango> yes, there's subtle trap... without parenthesis it wouldn't be a tuple
<paulc> Yoric, w/ that def, would you match on Foo(x, y)?
<pango> but a n-ary constructor
<Yoric[DT]> paulc: with 'a * int * int, matching agains Foo(x,y) won't work.
<Yoric[DT]> paulc: with ('a * int) * int, matching agains Foo(x,y) will.
<Yoric[DT]> s/agains/against/g
<paulc> right
<paulc> and what will x be bound to?
<paulc> for the ('a * int) * int
<paulc> will it be a pair with type ('a, int)
<paulc> ... er, is x * y in a variant type equivalent to (x, y)?
<Yoric[DT]> (x,y) is not a type
<Yoric[DT]> (1,2);;
<xavierbot> - : int * int = (1, 2)
<paulc> ah, ok
<Yoric[DT]> (note that the revised syntax actually differentiates between tuples and multi-parameter constructors)
<paulc> why isn't the syntax of ctor definition just the same as tuple definitions?
<Yoric[DT]> What do you mean ?
<paulc> I mean, why not just type 'a foo = Foo((a, int), int)
<paulc> since when you match, you match using Foo(x, y)
<paulc> I guess I am just saying it would make sense to me if the ctor definition mirrored the pattern you will use to match against it
<paulc> (or maybe i am not making sense!)
<Yoric[DT]> Well, it would be possible.
<Yoric[DT]> You can write a Camlp4 extension if you wish :)
olleolleolle has joined #ocaml
<paulc> hehe
<pango> pattern matching syntax is more closely related to be syntax used for writing value litteral than to the syntax used to write types
<pango> even without using tuples, you're not using 'of' in patterns or litteral values, for example; only when defining variant types
<pango> I suppose it could be done, as Yoric[DT] said... For now it's just a fact of life that type definitions syntax is different
<pango> (at least the syntax is not as horrible as C or C++ ;) )
<Yoric[DT]> :)
<Yoric[DT]> I guess it's just the matter of removing "of" and replacing "*" by ",".
<Yoric[DT]> And perhaps adding a few parenthesis here and there.
<Yoric[DT]> Looks quite feasible with Camlp4.
<Yoric[DT]> Maybe you should submit the query to the mailing-list.
paulc has quit [Read error: 104 (Connection reset by peer)]
olleolleolle has quit []
krypt1 has joined #ocaml
ita has quit [Remote closed the connection]
krypt1 has quit ["Leaving."]
marmottine has quit ["Quitte"]
seafood_ has joined #ocaml
jlouis_ has joined #ocaml
qpu has quit []
jlouis__ has joined #ocaml
<Yoric[DT]> Well, goodnight everyone.
Yoric[DT] has quit ["Ex-Chat"]
qpu has joined #ocaml
jlouis has quit [Read error: 110 (Connection timed out)]
jlouis has joined #ocaml
jlouis_ has quit [Read error: 110 (Connection timed out)]
loufoque has joined #ocaml
<loufoque> how can I know the max size of an int?
<loufoque> it's pow(2, 30)-1 on 32-bits platforms but pow(2, 62)-1 on 64-bits ones
jlouis__ has quit [Read error: 110 (Connection timed out)]
<pango> max_int ;;
<xavierbot> - : int = 4611686018427387903
<pango> Sys.word_size ;;
<xavierbot> Characters 1-14:
<xavierbot> Sys.word_size ;;
<xavierbot> ^^^^^^^^^^^^^
<xavierbot> Unbound value Sys.word_size
hkBst has quit ["Konversation terminated!"]