ayrnieu changed the topic of #ocaml to: OCaml 3.08.4 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/
telemakh0s has joined #ocaml
<telemakh0s> wouldn' it be nice if you could use multiple assignment in record constructors...
<telemakh0s> i.e. {myrec with a, b = 3, 4}
<pango> { myrec with a = 3; b = 4 }
<pango> what would be the benefit of that other syntax ?
<telemakh0s> { myrec with a,b = if sometest then 0,0 else myrec.a,myrec.b }
<telemakh0s> current syntax: { myrec with a = if sometest then 0 else myrec.a ; b = if sometest(*again*) then 0 else myrec.b }
<telemakh0s> it would just be sugar, but I think it's reasonable sugar, and it definately would not be a hinderance...
<telemakh0s> i mean, ocaml already has the facilities for multiple assignment, I don't see why it couldn't be extended to apply to record construction...
<pango> the current syntax just sticks with the syntax used to create record values from scratch... but I see your point
<telemakh0s> a more profound example would be using an existing function that returns mutliple values and you want to apply those values to certain members of your record...
<telemakh0s> instead of: let a, b, c = myfunct somearg in { myrec x = a ; y = b ; z = c }
* telemakh0s drops a "with" in there
<pango> sure, because your first example could be written as if sometest then { myrec with a = 0; b = 0 } else myrec
<telemakh0s> well, that's a corner case, what i me example before didn't reassign the same values...
<telemakh0s> youd have to: if sometest then { myrec with a = 0; b = 0 } else { myrec with a = 1; b = 1}
<telemakh0s> anyways, my "instead of:" example above woule become: { myrec with a,y,z = myfunct somearg }
<telemakh0s> wow, my typing skills are bad today... :P
<pango> I was wondering the other day if the order of assignments was dictated in language specs
<telemakh0s> i.e.??
<pango> I suspect they're evaluated in the same order as they're written, like a sequence of instructions, but it's not a given
<telemakh0s> you're talking about in "x,y = 1,2" if x is assigned before y?
<pango> no, in current syntax
<pango> { myrec with a = 3; b = 4 }
<telemakh0s> ahh
<telemakh0s> would it matter?
<pango> is a evaluated before b
<telemakh0s> ahh
<pango> if they're side effects somewhere, it may
<telemakh0s> try: { myrec with a = (print_string "a"; 3) ; b = (print_string "b"; 4) }
<pango> look like it's not
<telemakh0s> yeah, arbitrary order
<pango> since the assignment list isn't a sequence, it's probably better to avoid complex code with large function calls from within record construct if one prefers to avoid surprizes... multiple assignments isn't worse than current situation however (and could be even an improvement from that point of view : order of evaluation no longer matters)
<Smerdyakov> Anyone know how to get compiled native programs to raise exceptions on integer overflow?
<pango> Smerdyakov: afaik not possible without using a lib that redefines integer operators
<telemakh0s> Smerdyakov: ocaml doesn't test for integer overflow?
joeytwiddle has joined #ocaml
<Smerdyakov> telemakh0s, that's right!
<pango> # max_int + 5 ;;
<pango> - : int = -1073741820
<telemakh0s> heh...
<Smerdyakov> I need this for formally verified code, which is verified as if "int" is really integers.
<Smerdyakov> It's actually quite easy for me to call a special function for each arith. operation, but I'd rather avoid defining each one myself.. looks like I'll have to.
<telemakh0s> that reminds me (don't ask how :P) is there a way to have native char support? I.e. chars I can do arith on?
Nutssh has joined #ocaml
<pango> check the last url I gave (Overflow module)
<Smerdyakov> pango, oh, I only followed the 1st. Thanks.
<Smerdyakov> Hm... aren't there any other operations that can overflow? :)
* Smerdyakov thinks
<telemakh0s> i.e. I need chars such that (chr 256) == (chr 0)
<pango> telemakh0s: only int_of_char and char_of_int
<pango> # -1073741824 / -1 ;;
<pango> - : int = -1073741824
<pango> that's the only one I can think of with /
sethk has quit [Remote closed the connection]
sethk has joined #ocaml
telemakh0s has quit [Read error: 110 (Connection timed out)]
mrsolo has quit [Read error: 104 (Connection reset by peer)]
lispy has joined #ocaml
lispy_ has joined #ocaml
lispy has quit [Read error: 110 (Connection timed out)]
lispy_ has quit ["This computer has gone to sleep"]
threeve has quit []
lispy_ has joined #ocaml
lispy_ has quit ["This computer has gone to sleep"]
pango_ has joined #ocaml
pango has quit [Read error: 60 (Operation timed out)]
<revision17_> hi, I'm trying to wrap my mind around functors, and I'm just not getting them; anyone know of a place that has a good explaination of them?
<Nutssh> A functor is a module paramaterized by a module. Its like a template in C++.
<beschmi> there is a comparison between modules/functors and classes in the oreilly book: http://caml.inria.fr/pub/docs/oreilly-book/html/index.html chapter 16
<revision17_> alright, I'm gonna look at that now, thanks
<revision17_> alright, so let me see if I understand it
* revision17_ fires up the interactive shell
<revision17_> ah, yes that makes sense now
<revision17_> thanks
<revision17_> awesome... now on to Monads and other cool sounding programming language terms that I don't understand yet
haakonn has quit [Remote closed the connection]
haakonn has joined #ocaml
<sethk> revision17_, monads aren't as difficult as they first appear.
haakonn has quit [Remote closed the connection]
smimou has joined #ocaml
smimou has quit ["?"]
Snark has joined #ocaml
Smerdyakov has quit [Read error: 104 (Connection reset by peer)]
Smerdyakov has joined #ocaml
Snark has quit [Read error: 113 (No route to host)]
Snark has joined #ocaml
vezenchio has joined #ocaml
pango_ has quit [Remote closed the connection]
ejt has joined #ocaml
mlh has quit ["who are you people and what are you doing in my computer!?"]
mrpingoo has joined #ocaml
vodka-goo has quit [Read error: 110 (Connection timed out)]
Revision17 has joined #ocaml
Schmurtz has joined #ocaml
Schmurtz has quit [Client Quit]
Schmurtz has joined #ocaml
revision17_ has quit [Read error: 110 (Connection timed out)]
<ulfdoz> I don't understand the following code (from ocamllex tutorial):
<ulfdoz> let incr_line_number lexbuf =
<ulfdoz> let pos = lexbuf.Lexing.lex_curr_p in
<ulfdoz> lexbuf.Lexing.lex_curr_p <- { pos with
<ulfdoz> Lexing.pos_lnum + 1;
<ulfdoz> Lexing.pos_bol = pos.Lexing.pos_cnum;
<ulfdoz> }
<ulfdoz> ;;
<ulfdoz> Especially I don't know, what lexbuf.Lexing.lex_curr_p means. Is lexbuf type or identifier and why is the module name in the middle instead of prepended?
<Snark> ulfdoz: you can make a copy of a I-forgot-the-name with only some fields changed
<Snark> that explains the foo <- { something with .. }
<Snark> for the rest I don't know
<ulfdoz> The part inbetween the braces I interpreted as: construct a value of type Lexing.position, name it pos, set the two values and assign it to lexbuf.Lexing.lex_curr_p, while keeping the old values, if not set in pos.
<Snark> no
<Snark> it takes pos and makes a copy of it with some values changed
<Snark> it doesn't change pos itself
<ulfdoz> Ah, I begin understanding.
Skal has joined #ocaml
<ulfdoz> Snark: thx, I think I'll get it now.
<Snark> no problem
pango has joined #ocaml
m3ga has joined #ocaml
m3ga has quit [Client Quit]
threeve has joined #ocaml
lispy_ has joined #ocaml
lispy_ has quit [Client Quit]
__DL__ has joined #ocaml
__DL__ has quit [Client Quit]
smimou has joined #ocaml
Schmurtz has quit [Remote closed the connection]
Schmurtz has joined #ocaml
lispy_ has joined #ocaml
Submarine has joined #ocaml
lispy_ has quit [Client Quit]
petchema_ has joined #ocaml
petchema_ has quit [Client Quit]
ski has joined #ocaml
pango has quit [Remote closed the connection]
mattam_ is now known as mattam
mikeX has joined #ocaml
mrpingoo has quit []
vodka-goo has joined #ocaml
pango has joined #ocaml
mikeX has quit ["Leaving"]
Submarine has quit ["Leaving"]
ski_ has joined #ocaml
ski has quit [Nick collision from services.]
ski_ is now known as ski
UziMonkey has joined #ocaml
ski_ has joined #ocaml
Submarine has joined #ocaml
ski has quit [Nick collision from services.]
ski_ is now known as ski
Schmurtz has quit ["Dodo !"]
joeytwiddle has quit ["Leaving"]
mikeX has joined #ocaml
Schmurtz has joined #ocaml
vezenchio has quit ["Free Tibet with each Asian nation of a lesser or equal value"]
Submarine has quit ["Leaving"]
Skal has quit [Remote closed the connection]
UziMonkey has quit [Remote closed the connection]
batdog is now known as batdog|gone
mikeX has quit ["Leaving"]
Snark has quit ["Leaving"]
Schmurtz has quit ["Dodo !"]
Demitar has quit [Read error: 110 (Connection timed out)]
threeve has quit []
ejt has quit ["Lost terminal"]
smimou has quit ["?"]
mlh has joined #ocaml
threeve has joined #ocaml
lispy_ has joined #ocaml
lispy_ has quit [Client Quit]
lispy_ has joined #ocaml
lispy_ has quit [Client Quit]
* ptolomy wishes he could pick and choose pieces of Haskell and Ocaml.
twobitsprite has joined #ocaml