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!)
<pango_> what kind of interfaces?
seafood_ has joined #ocaml
<PieRRoMaN> pango_ : my program consists of small objects moving through a graph, the first interface contains display functions, the second is for gameplay functions
hsuh has joined #ocaml
<PieRRoMaN> I created the two .mli files with the values signatures, and defined them in the corresponding modules in two .ml files
<PieRRoMaN> and I don't know how to compile the whole stuff
dmess has left #ocaml []
bluestorm has quit ["Konversation terminated!"]
<pango_> you must first compile the signatures, then the implementations
<PieRRoMaN> separately?
<PieRRoMaN> each .mli compiles perfectly with ocamlc -c foo.mli and it creates the .cmi file
<PieRRoMaN> the .ml files don't compile
<PieRRoMaN> I suspect it's because the types I use don't match
<pango_> what error do you get?
<PieRRoMaN> The implementation affichage.ml does not match the interface affichage.cmi:
<PieRRoMaN> The field `AFFICHAGE' is required but not provided
<PieRRoMaN> (affichage means display)
<PieRRoMaN> the problem is, my program uses 3 types, which I defined as t, u, v in the signature
<PieRRoMaN> how do I make them match the signature in the module?
<PieRRoMaN> because I use them with explicit names, of course
<PieRRoMaN> type noeud = { mutable b : bestiole ref; pos : int * int; mutable succ : noeud list }
<PieRRoMaN> and bestiole = Nil | Bestiole of (noeud * (bestiole ref -> noeud) * int);;
<PieRRoMaN> type graphe = { mutable l : noeud list; }
<PieRRoMaN> that's how I define them in the program
<pango_> they must have the same definition in both. They can be more abstract in the signature ('type t') if you don't want to make their implementation public
<PieRRoMaN> yes, that's precisely what I want to do
<PieRRoMaN> so I used type t, type u, type v in the signatures
seafood_ has quit []
<pango_> anyway the problem seems to come from AFFICHAGE, not noeud, bestiole or graphe
<PieRRoMaN> does it matter if I start the files with "module Affichage : AFFICHAGE = struct"?
<PieRRoMaN> considering I have only one module by file
<pango_> yes, it creates a submodule
<PieRRoMaN> so I just put "struct" at the begining of the file?
buluca has joined #ocaml
<pango_> "Both files define a structure named A as if the following definition was entered at top-level:
<pango_> module A: sig (* contents of file A.mli *) end
<pango_> = struct (* contents of file A.ml *) end;;
<pango_> "
<pango_> no sig, no struct, no end, all this is implicit
<PieRRoMaN> yeah
<PieRRoMaN> ok
<PieRRoMaN> but it still won't work
hsuh has quit [Remote closed the connection]
<PieRRoMaN> there's an improvement though
<pango_> you could move .mli and .cmi away temporarily and try compiling the modules with -i to see inferred signatures
<PieRRoMaN> I have to define the types in both modules, right?
<pango_> yes
<PieRRoMaN> I have type problems because I call functions from the second module in the first one
<pango_> well, you mean, in both modules, or in both files (interface and implementation)?
<PieRRoMaN> I define the abstract types in both interfaces, and define the types also in both .ml files
<pango_> that's never going to work, abstract types are not compatible with anything else
<pango_> also, if you redefine a type, only last definition is visible (it shadows previous definitions)
<PieRRoMaN> so how am I supposed to do?
<pango_> so you're not really redefining types, only hiding previous ones
<PieRRoMaN> I define them once and for all in the signatures, and not in the implementation?
<pango_> that's not possible
<pango_> you can't make visible something you don't define
<PieRRoMaN> that's right
<pango_> why are you trying to redefine types in the other module in the first place?
<PieRRoMaN> I'm not trying to
<PieRRoMaN> but since I'm using the types in both modules, I have to define them twice, don't I? or if not, how can I do this?
<pango_> if the type are declared in the other module's interface, they will be visible, just like everything else in the interface
seafood_ has joined #ocaml
<PieRRoMaN> but they won't be visible in both modules
<pango_> why not
<pango_> seen from other modules they may look abstract, but they'll be visible
<PieRRoMaN> I compile the modules separately, so far
<PieRRoMaN> I want to compile the second module with the -i option to generate the signatures
<PieRRoMaN> and I get a type problem when it reaches a function defined in the other module
<PieRRoMaN> sorry for being slow :s
<PieRRoMaN> but I don't get i
<PieRRoMaN> it
<pango_> what error message do you get that time?
seafood_ has quit []
<PieRRoMaN> This expression has type bestiole ref but is here used with type Affichage.bestiole ref
<PieRRoMaN> at a line where I call a function from Affichage
<pango_> look like a problem with one of your type "redefinitions"
<PieRRoMaN> the right command, is it "ocamlc -i affichage.cmo jeu.ml" or just "ocamlc -i jeu.m"l
<PieRRoMaN> do I have to add a "load Affichage" in jeu.ml ?
<pango_> load is not an ocamlc directive (nor #load, btw)
seafood_ has joined #ocaml
<PieRRoMaN> oops I meant open, not load
<PieRRoMaN> sorry
<pango_> open will add a module name to the list of modules to search for identifiers
<pango_> so it's just a convenience for not writting module name prefixes each time
<PieRRoMaN> yeah
<PieRRoMaN> I'm only trying to solve the type error
<PieRRoMaN> ;)
<pango_> to answer your previous question, ocamlc -c -i jeu.ml should work
<pango_> but in jeu.ml you either have to use open Affichage, or use Affichage. before identifiers that come from that module
<PieRRoMaN> yeah, that I know
<PieRRoMaN> but there is still a problem with the types
ita_ has quit [Remote closed the connection]
<PieRRoMaN> either I redefine them in jeu.ml and I've got the same error as before, or I don't, and then I get an Unbound record field label
<pango_> field names are also defined in modules, so you have to prefix them with module name
<PieRRoMaN> but I've put a load Affichage at the begining of the file, so I shouldn't have to do that, right?
<pango_> modules work as namespaces for types, values, exceptions, field names, submodules,... (did I miss something?)
middayc has joined #ocaml
<pango_> s/load/open/, then yes
<PieRRoMaN> damnit
<PieRRoMaN> yes, open, of course
<PieRRoMaN> why do I keep saying load?
hsuh has joined #ocaml
<pango_> bedtime!
<PieRRoMaN> 'night pango_, thanks for your help
<pango_> np
Jedai has joined #ocaml
Jeff_123 has quit ["Leaving."]
PieRRoMaN has left #ocaml []
thermoplyae has quit ["daddy's in space"]
AxleLonghorn has joined #ocaml
AxleLonghorn has left #ocaml []
AxleLonghorn has joined #ocaml
seafood_ has quit [Read error: 104 (Connection reset by peer)]
seafood_ has joined #ocaml
seafood_ has quit [Client Quit]
seafood_ has joined #ocaml
buluca has quit [Read error: 110 (Connection timed out)]
hsuh has quit [Remote closed the connection]
seafood_ has quit []
rektide has left #ocaml []
AxleLonghorn has left #ocaml []
Mr_Awesome has joined #ocaml
seafood_ has joined #ocaml
dibblego has joined #ocaml
Associat0r has quit []
nashdj has joined #ocaml
netx has quit [Remote closed the connection]
buluca has joined #ocaml
l_a_m has joined #ocaml
thermoplyae has joined #ocaml
nasloc__ has joined #ocaml
netx has joined #ocaml
ttamttam has joined #ocaml
ttamttam has left #ocaml []
Snark has joined #ocaml
thermoplyae has left #ocaml []
ttamttam has joined #ocaml
zenhacker_rouan has joined #ocaml
madroach has joined #ocaml
seafood_ has quit []
kmeyer has quit [Remote closed the connection]
kmeyer has joined #ocaml
zenhacker_rouan has left #ocaml []
kmeyer has quit [Remote closed the connection]
mrsolo has quit ["This computer has gone to sleep"]
kmeyer has joined #ocaml
seafood_ has joined #ocaml
kmeyer has quit [Remote closed the connection]
kmeyer has joined #ocaml
kmeyer has quit [Remote closed the connection]
filp has joined #ocaml
kmeyer has joined #ocaml
middayc has quit [Read error: 110 (Connection timed out)]
Zeros has quit ["Leaving"]
madroach has quit [Remote closed the connection]
rwmjones has joined #ocaml
mrsolo has joined #ocaml
buluca has quit [Read error: 110 (Connection timed out)]
leo037 has joined #ocaml
mrsolo has quit ["Leaving"]
kelaouch1 has joined #ocaml
buluca has joined #ocaml
kelaouchi has quit [Read error: 110 (Connection timed out)]
Snark has quit ["Quitte"]
zmdkrbou has quit [Read error: 110 (Connection timed out)]
hkBst has joined #ocaml
Yoric[DT] has joined #ocaml
<Yoric[DT]> hi
zmdkrbou has joined #ocaml
asmanur has joined #ocaml
buluca has quit [Read error: 110 (Connection timed out)]
jonathanv has joined #ocaml
jonafan has quit [Read error: 110 (Connection timed out)]
bongy has joined #ocaml
love-pingoo has joined #ocaml
seafood_ has quit []
Associat0r has joined #ocaml
jonathanv has quit [calvino.freenode.net irc.freenode.net]
Mr_Awesome has quit [calvino.freenode.net irc.freenode.net]
mordaunt has quit [calvino.freenode.net irc.freenode.net]
yminsky has quit [calvino.freenode.net irc.freenode.net]
ppsmimram has quit [calvino.freenode.net irc.freenode.net]
bla has quit [calvino.freenode.net irc.freenode.net]
blackdog has quit [calvino.freenode.net irc.freenode.net]
JesusChrist2008 has quit [calvino.freenode.net irc.freenode.net]
jonathanv has joined #ocaml
Mr_Awesome has joined #ocaml
mordaunt has joined #ocaml
yminsky has joined #ocaml
bla has joined #ocaml
blackdog has joined #ocaml
ppsmimram has joined #ocaml
JesusChrist2008 has joined #ocaml
bongy has quit [Remote closed the connection]
kelaouchi has joined #ocaml
leo037 has quit [Read error: 104 (Connection reset by peer)]
kelaouch1 has quit [Read error: 110 (Connection timed out)]
dramsay has joined #ocaml
Tetsuo has joined #ocaml
leo037 has joined #ocaml
buluca has joined #ocaml
postalchris has joined #ocaml
pango_ has quit [Remote closed the connection]
marmottine has joined #ocaml
Morphous has joined #ocaml
ttamttam has left #ocaml []
pango_ has joined #ocaml
postalchris has quit [Read error: 113 (No route to host)]
Amorphous has quit [Read error: 110 (Connection timed out)]
bluestorm has joined #ocaml
filp has quit ["Bye"]
jonathanv is now known as jonafah
jonafah is now known as jonafan
pattern has quit [Remote closed the connection]
pattern has joined #ocaml
postalchris has joined #ocaml
marmottine has quit [Remote closed the connection]
jderque has joined #ocaml
<Yoric[DT]> Could anyone look at http://pastebin.mozilla.org/303819 and tell me what they think of lines 31-35 ?
<Yoric[DT]> The question is readability.
<bluestorm> hm
<bluestorm> Yoric[DT]: they are readable
<bluestorm> but i can't connect the with_input use with it's definition : where is the action ?
<Yoric[DT]> that's where the readability is questionable :)
<bluestorm> moreover, if you're interested in "some syntaxic sugar for iteration trough structures", i'd be more interested personally in list comprehensions as a generic iteration syntaxic sugar, than foreach
<Yoric[DT]> The way "for each" works is that it rewrites the whole "do ... done" block as "fun input -> ...".
<bluestorm> (and actually iirc there already is a list comprehension extension)
<bluestorm> hm
<Yoric[DT]> I know, I wrote one of these :)
<bluestorm> i don't think changing the parameters order is a good thing
<bluestorm> hm
<bluestorm> or at least you would have to invert the parameter
<bluestorm> hm
<bluestorm> let with_input file action = ...
buluca has quit [Read error: 110 (Connection timed out)]
<Yoric[DT]> That was the original structure.
<Yoric[DT]> I changed it because, well, that allowed me to reuse "for each".
<bluestorm> hm
<jonafan> There is tea reversed at the edge of the table
<jonafan> gg babelfish
<Yoric[DT]> Indeed.
<Yoric[DT]> The whole point was to get a readable version of line 33.
<bluestorm> where is the reusability gain in this paramater order ?
<bluestorm> -a+e
<Yoric[DT]> Well, I couldn't use the (already existing) "for each" with the different order of arguments.
<bluestorm> (i don't see it for know, and still i think with_input file action would be the natural order, as the "input" part of the name refers primarily to the input derived from file)
<bluestorm> moreover
<jonafan> [1;2::[3;4]] ?????
<bluestorm> with_input (input : in_channel) would make more sense
<bluestorm> jonafan: revised syntax
<bluestorm> so you could do
<bluestorm> with_input stdin, and with_input (open_in "foo.in") as well
<jonafan> that's [1; [2;3;4]] though! nonsense!
<Yoric[DT]> I don't understand what you mean.
<bluestorm> hm
<bluestorm> Yoric[DT]: you impose with_input to read from a file
<Yoric[DT]> jonafan: not in the revised syntax.
<bluestorm> by taking directly an input channel, you could get more reusability
<bluestorm> jonafan: that's 1::2::[3;4]
<Yoric[DT]> bluestorm: oh, that, ok.
<bluestorm> and i agree this seriously sucks
<bluestorm> (a shame the revised syntax has such good things, but such scary things too)
<Yoric[DT]> Most things in the revised syntax I like.
<Yoric[DT]> That kind of thing I can survive.
<Yoric[DT]> There's a gain in coherence in always putting data structures between [ and ] .
<Yoric[DT]> (well, not all data structures, but lists, arrays, streams)
<bluestorm> w.r.t my own style (using | for each cases, even the first one, when there are more than two), [ ] are quite awkward
thermoplyae has joined #ocaml
<bluestorm> what i really like are the types, constructors and functors curryfication
<Yoric[DT]> Well, whenever I have to embed a pattern-matching inside another, [ ] are a blessing.
<bluestorm> type foo 'a 'b = Foo of 'a and 'b is a great idea imho
<Yoric[DT]> I agree.
<bluestorm> Yoric[DT]: i can use ( ) for that when necessary
<Yoric[DT]> I find that much more awkward than [ ].
<bluestorm> :p
<bluestorm> i had
<bluestorm> function
<bluestorm> | A -> ..
<bluestorm> | B -> ...
<bluestorm> know i have something like
<Yoric[DT]> That's actually the foremost reason why I use the revised syntax :)
<bluestorm> function
<bluestorm> [ A -> ...
<bluestorm> | B -> ... ]
<bluestorm> the ] here feels strange
<bluestorm> i don't really like end-of-line keywords, and wouldn't like using one more line for that
<bluestorm> Yoric[DT]: regarding your code
<Yoric[DT]> Yep ?
<bluestorm> hm
<bluestorm> i still don't really get it : how does camlp4 add the bunch of do .. end between with_input and the parameter ?
<bluestorm> (according to your comment, for each foo in func arg do bar done -> func (fun foo -> bar) arg )
<bluestorm> (wouldn't func arg (fun foo -> bar) be easier to understand and to implement ?)
<Yoric[DT]> Because I'm cheating.
<bluestorm> hm
<Yoric[DT]> Because that was the only way to get "for each" to work with "iter" (and "map") in the first place.
<bluestorm> ah, you mean iter _fun_ _struct_ ?
<Yoric[DT]> Yep.
<bluestorm> what about non-cheating and using something like
<Yoric[DT]> "for each" would have been pretty useless if it hadn't been able to generate working "iter".
<bluestorm> let on x f = f x in
<bluestorm> for each foo in on struct iter do ...
<bluestorm> hm
<Yoric[DT]> Doesn't look like that's gonna work.
<bluestorm> see, a "natural" way of changing parameter order of iter/map functions, without adding strangeties to your foreach
<bluestorm> (maybe this one doesn't work, but i'd bet there is a nice one that does)
<Yoric[DT]> Interesting idea, though.
<bluestorm> hm right
<bluestorm> on should be
<bluestorm> let on struct iter func = iter func struct
<bluestorm> wouldn't it work, then ?
<Yoric[DT]> for each foo in on struct List.iter do ... done ?
robyonrails has joined #ocaml
<Yoric[DT]> Doesn't look very readable to me, I'm afraid.
<Yoric[DT]> Let me detail how "for...each" works.
Snrrrub has joined #ocaml
<Yoric[DT]> for each [sequence of patterns] in [Module] [struct] do [body] done => Module.iter (fun patterns -> body) struct
<Yoric[DT]> and
<Yoric[DT]> for each [sequence of patterns] in [not_a_module] [struct] do [body] done => not_a_module (fun patterns -> body) struct
<Snrrrub> Hi, I'm just starting out with OCaml and I came across this code that I don't fully understand: let new_id = let c = ref 0 in fun () -> incr c; c! -- why doesn't the gc collect c after each invocation of new_id?
<Snrrrub> ... that should have been !c
<bluestorm> hm
<bluestorm> Snrrrub:
<bluestorm> that's a "bit of magic" code
* Yoric[DT] will utter the magic word "closure" and let bluestorm do the rest.
<bluestorm> :D
<Snrrrub> Ah. Gotcha.
<Snrrrub> That's an interesting pattern. :) Thanks!
<bluestorm> Yoric[DT]: good spellcaster :p
<bluestorm> Snrrrub: and you can share values with more than one func
<bluestorm> let (f, g) = let c = ref ... in ((....), (....))
<bluestorm> let f, g = let c = ref ... in (....), (....)
<bluestorm> then f and g both share the c reference
<bluestorm> (or any other local value)
<Snrrrub> and presumably the (...), (...) expressions refer to f and g respectively?
<bluestorm> yes they do
<bluestorm> Yoric[DT]:
<bluestorm> i'd feel more natural with something like
<bluestorm> foreach [pattern] in [struct] with [iterfuc] do ... done
<bluestorm> as your [not_a_module] [struct] really reads like application of struct to the not_a_module function
<bluestorm> i think a keywordish separation would be better
<bluestorm> foreach input in (open_in "foo") with input_wrapper do ... done
pranith has joined #ocaml
filp has joined #ocaml
<pranith> http://bitwise.iitkgp.ernet.in/ - an online programming contest in C/C++ with huge prize money, registration has started, this is for information purpose only, not spamming, sorry if you think otherwise
<bluestorm> (let input_wrapper action input = with_input input action, yes i'm stubborn :-' )
filp has quit [Remote closed the connection]
<bluestorm> pranith: how would a C/C++ contest on #ocaml be a valuable information ?
<pranith> bluestorm, hmm. some of you _might_ be interested in participatin?
<pranith> :/
<bluestorm> hm
<bluestorm> i think those who would be interested in such a thing would read both #ocaml and #cpp
<Snrrrub> and ##C++
<pranith> Snrrrub, thanks. ill post it there
<Yoric[DT]> bluestorm: while I agree with the general idea, this specific syntax wouldn't work.
<pranith> bluestorm, thank you
pranith has left #ocaml []
jonathanv has joined #ocaml
bzzbzz has quit ["leaving"]
<Yoric[DT]> That is, I like the idea of (almost) automatically generating "iter" calls, as that is expected to be the main use of this sugar.
<bluestorm> Yoric[DT]: side question, why do you want to separate "each" from the "for" ? this adds a keyword anyway and i don't see this easier to parse with camlp4
<Yoric[DT]> Not very useful, I'll probably remove that in the next version.
<bluestorm> (i'd have thought this would be even more likely to raise conflicts, but you seem to deal with it :p)
<Yoric[DT]> That was experimental, as I was attempting to get a syntax I could use with "iter", "map", "fold_left" and "fold_right", but I have mostly given up on folds.
love-pingoo has quit ["Connection reset by pear"]
<bluestorm> hm
<bluestorm> folding doesn't really follow the "foreach" meme
<bluestorm> and the "do" wording still looks a bit too imperative for "map" too
<Yoric[DT]> Well, it might have.
<bluestorm> let list = foreach x in List [....] do 2*x done ?
<Yoric[DT]> Something like that.
<bluestorm> don't see where is the point in "doing" something here
<Yoric[DT]> I'd actually like to show my students a fold_left / fold_right they would understand quickly.
<Yoric[DT]> No, not much.
<Yoric[DT]> How would you have called that ?
<bluestorm> hm
<bluestorm> "fun" ? :p
<Yoric[DT]> :)
<Yoric[DT]> Note that I already have a syntax for stuff comprehension.
<Yoric[DT]> So "map" is definitely not critical.
<Yoric[DT]> What was more critical was getting both "iter" and "iteri".
<bluestorm> so here you're concentrating on iteration, but looking for a folding solution :-'
<Yoric[DT]> The map was just a side benefit.
<Yoric[DT]> At some point, I was looking for a nice syntax for fold.
<Yoric[DT]> I didn't find it.
<Yoric[DT]> But I'm keeping the syntax for iter :)
pattern has quit [Remote closed the connection]
bzzbzz has joined #ocaml
<bluestorm> Yoric[DT]: on the folding question, i don't think it's a syntaxic problem
<bluestorm> it's more an abstraction question
<Yoric[DT]> I believe that syntax could help things.
<bluestorm> i found it useful to have peoples writing folding code themselve
<Yoric[DT]> I also believe that "for...do..." is not the answer to folding.
<bluestorm> for example, once you've got someone to write let rec rev acc = function [] -> acc | t::q -> rev (t::acc) q by himself, he's much more receptive to fold_left
<Yoric[DT]> Fair enough.
<bluestorm> (and fold_right is even easier : length + flatten, and that's it)
<Snrrrub> Is there a way to bind the nth argument of a routine without also binding n-1?
<bluestorm> Snrrrub: isn't
<Yoric[DT]> I actually intend to teach foldings by getting students to write list sum, list product and list length and get them to factorize everything.
<bluestorm> ocaml routine only have one arugment
<bluestorm> the rest is higher-order functions
<Snrrrub> Okay, thanks!
ita has joined #ocaml
* Yoric[DT] wonders if Snrrrub comes from Fortran or from (Visual) Basic.
jonafan has quit [Nick collision from services.]
<bluestorm> Yoric[DT]: the problem with maths ops is that they tend to be associative
jonathanv is now known as jonafan
<Snrrrub> Yoric[DT], what gives you that idea?
<bluestorm> wich, when you get to "fold_left or fold_right", can get tricky
<Yoric[DT]> Snrrrub: "routine". Am I wrong ?
<Yoric[DT]> bluestorm: fair enough.
<Yoric[DT]> I still need to start somewhere, though.
<bluestorm> hm
<bluestorm> "map" could do the job
<bluestorm> hm
<Yoric[DT]> Anyway, that's for another day.
<Snrrrub> Yoric[DT], I've never played with Fortran or VB. :-) I come from (sigh) the usual suspects: C, C++, Pascal, Assembly.
<bluestorm> actually, coding map with fold_right is a bad idea
<bluestorm> so that's not a good example either
<Snrrrub> I guess the 'routine' comes from the assembly experience.
<Yoric[DT]> Snrrrub: so where did you pickup that "routine" vocabulary ?
<Yoric[DT]> ok
* Yoric[DT] doesn't remember calling anything a "routine" in asm.
* Yoric[DT] didn't do that much asm, though.
<Yoric[DT]> bluestorm: Right now, we were discussing about "for each" and how to improve it.
<bluestorm> :p
<Yoric[DT]> for i in l with List.iter do
<Yoric[DT]> ...
<Yoric[DT]> done
<Yoric[DT]> that's much more complex than what I have for the moment.
<Yoric[DT]> for i in List l do ... done
bzzbzz has quit ["leaving"]
Snark has joined #ocaml
<bluestorm> you could have your same "partial iterfunc guessing" and for i in li with List do
<bluestorm> wich basically only have an added "with"
<Yoric[DT]> I do find that harder to read.
<bluestorm> (could be "using", btw, but it's longer)
<Yoric[DT]> I mean, adding "List" in the middle of the sentence still sounds like English.
Morphous_ has joined #ocaml
<Yoric[DT]> Pushing it away doesn't.
<bluestorm> but that doesn't scale to functions
yminsky has quit [Read error: 110 (Connection timed out)]
<Yoric[DT]> True.
<Yoric[DT]> But I'm trying to optimize readability of the most common case :)
<bluestorm> what you could do is a quite modular way
<bluestorm> for i in [module] li [with func] do .. done
<bluestorm> where the [ ] parts are optional
<Yoric[DT]> I considered that.
<mbishop> for each i use List do ... done ?
<Yoric[DT]> Now, my problem is: what do I do if I have both the module and func ?
<bluestorm> mbishop: where is the actual list ?
<bluestorm> Yoric[DT]:
<bluestorm> Module.func ? :p
<Yoric[DT]> Now, that's irregular :)
<bluestorm> hm
<bluestorm> seems ok to me
<bluestorm> for i in List li with map
yminsky has joined #ocaml
<Yoric[DT]> What about "for i in List li with List.map" ?
<bluestorm> then you've got List.List.map
<Yoric[DT]> What does the poor user do when he sees the error message telling him that "List.List.map" doesn't exist ?
<mbishop> Users read error messages?
<Yoric[DT]> Well, they get confused by these.
<bluestorm> Yoric[DT]: i guess he tries to remove one of the two List
<bluestorm> to only have one left
* Yoric[DT] guesses he could print a warning in that case.
<bluestorm> hm
<bluestorm> yes, a warning if the two modules are equal would be nice
<bluestorm> a bit ad-hoc but hey, warning always are
<Yoric[DT]> Any suggestion for a keyword or symbol more suited than "with" ?
<Yoric[DT]> "traverse" ?
<bluestorm> using ?
<bluestorm> mbishop suggested "use"
<bluestorm> i prefer "using" as it feels more "descriptive"
<Yoric[DT]> I prefer "using".
<Yoric[DT]> "use" will be confusing with "do".
* mbishop nods
thermoplyae has quit ["daddy's in space"]
<Yoric[DT]> What about
<Yoric[DT]> for [patt] in [func] through [struct] do ... done ?
<bluestorm> "in" ?
<Yoric[DT]> with "[func] through" being replaceable by a module name to get standard "iter"
<Yoric[DT]> ?
<bluestorm> hm
Snrrrub__ has joined #ocaml
<bluestorm> Yoric[DT]: what do you want to emphasize on : the data or the function ?
<Yoric[DT]> I'm not sure, why ?
<bluestorm> because it should determine the order
pattern has joined #ocaml
<Yoric[DT]> I'm still not sure.
Morphous has quit [Read error: 110 (Connection timed out)]
<bluestorm> seems you'd like to have a default func in the "usual use" case
<Yoric[DT]> indeed
<bluestorm> if so, i think it would be a good idea to put the function part at the end
<bluestorm> so that the beginning doesn't change too much
<bluestorm> (i think people are used to "static" beginning of syntaxic constructs, eg. else is optional, then isn't)
<Yoric[DT]> ok
<Yoric[DT]> I'll try with this "through", though.
<Yoric[DT]> To see how it works.
<bluestorm> "Fair enough."
<Associat0r> #F# needs people
<Yoric[DT]> ...
* Yoric[DT] will think about it a little.
* Yoric[DT] might even dine before that.
buluca has joined #ocaml
Snrrrub has quit [Success]
<bluestorm> Associat0r: #ocaml needs too, and the ocaml distribution is not patent-encumbered :)
<Associat0r> true
ita has quit ["Hasta luego!"]
middayc has joined #ocaml
leo037 has quit ["Leaving"]
buluca has left #ocaml []
nashdj has quit [Read error: 110 (Connection timed out)]
ygrek has joined #ocaml
Bzek has joined #ocaml
ttamttam has joined #ocaml
<mbishop> Hmm
<mbishop> there used to be one or two people in #fsharp
asmanur has quit [Remote closed the connection]
middayc has quit []
<rwmjones> I assume everyone knows about ^^ ?
<rwmjones> if you are intending to come, please add yourself to the list so we know numbers
<rwmjones> that is to say, the list under the Participants heading ...
<jonafan> haha i should try to convince my boss to send me
<jonafan> he's sent people to paris before!
rjones has joined #ocaml
rjones is now known as rwmjones_ltp
<bluestorm> rwmjones: do you think there may be an interest in coming there "spectator only" ?
Bzek has quit ["Morkvit."]
<rwmjones_ltp> bluestorm, of course why not ... it's free and open to anyone
<bluestorm> hm
<bluestorm> i'll see, then
zepard has joined #ocaml
<zepard> hi, does chamo editor code completion?
<bluestorm> zepard: http://home.gna.org/cameleon/chamo.en.html, doesn't seems so
<bluestorm> but you might add that feature if you want, it's caml
<zepard> thx but just starting with Ocaml and functional
<zepard> programming
<bluestorm> hm
<bluestorm> do you know either emacs or vim ?
<bluestorm> they've got more than decent OCaml support
<bluestorm> if you're into "modern" stuff, there is an Eclipse mode too
<bluestorm> but i haven't tried it yet
<pango_> never managed to start cameleon2
<zepard> I tried emacs but never autocompleting thingy with it (it would be a good exercise though)
<bluestorm> hm
<bluestorm> emacs does have numerous ways to do autocompletion
<zepard> yes eclipse but too heavy, I know every body says the same: you want something fast and light but with heavy features in it
<zepard> bluestorm, realy
<pango_> $ cameleon2.byte -e "open_view /work/cameleon2 modules"
<pango_> Unknown option -e.
<bluestorm> i don't use code completion myself
<zepard> thx i'll try this and will see
<flux> snrrrub__, you can however use labeled arguments and functions such as let flip f a b = f b a to the same effect (when suitable)
<bluestorm> but i think for a first try, you should have a look at dabbrev
<bluestorm> simple to use, and "enough" in most cases
<flux> dabbrev is excellent
<bluestorm> (and it isn't limited to code)
<zepard> it's for abreviations? :)
<bluestorm> hm
<flux> however lately I've noticed that tuareg mode's completion and help for modules is nice when you work with modules you don't quite know yet
<flux> ..or have forgotten..
<bluestorm> zepard: it's dynamic completion, related to the other words in the buffer(s)
<flux> C-c TAB on a symbol finds completions, C-c C-h finds documentation
<bluestorm> so that isn't "abbreviation" really
<bluestorm> flux: i've seen quite interesting things based on toplevel patches too
<ttamttam> flux: excellent. I did not notice C-c TAB. Only C-c h. Thanks, I will check.
<zepard> touareg mode is an emacs mode?
<bluestorm> tuareg
<bluestorm> yes it is
<zepard> I guess you can link librarires or doc like in eclipse to find completion
<ttamttam> bluestorm: Thanks to you for this interesting link too!
<flux> and of course, there is the ever-useful C-c C-t..
<flux> it'd be nice (as I discussed some time ago) if ocamlc was able to proceed after one error.
<flux> could make a nice addition to emacs with fly-mode etc..
<flux> (disclaimer: I haven't actually tried fly-mode)
<bluestorm> hm
<bluestorm> if you're speaking about pymake
<zepard> I tried C-c TAB with print_string and have no results?
buluca has joined #ocaml
AxleLonghorn has joined #ocaml
<bluestorm> i guess using camlp4 only for syntax checking would make sense
<zepard> what does mean completion for pervasives?
filp has joined #ocaml
<flux> zepard, works for me
<zepard> hum :(
<flux> zepard, wait, you typed in print_string and pressed C-c TAB?
<zepard> no typed : print_ and C-c TAB
<pango_> aha, after reinstallation it works. I suspect prelinks breaks ocaml bytecode programs :/
<pango_> s/prelinks/prelink/
<flux> zepard, I guess it doesn't complete ambigious strings
<zepard> ?
<zepard> ambigus ok
<flux> hm, actually, maybe it's a bug :-)
<zepard> your righrt
<flux> the underscore must confuse it or something
<flux> pri[C-c tab] works
<zepard> or not designed for that
<zepard> oh
<flux> but after it expands to print_, it doesn't anymore
<zepard> print_i works for me
<zepard> look : print doesn't work but pri works!!!!
<flux> yes..
rwmjones_ltp has quit ["This computer has gone to sleep"]
<zepard> I should lokk to pervasivs thing
jderque has quit [Read error: 113 (No route to host)]
seafood_ has joined #ocaml
<zepard> I know it's a taste question but , should I use emacs or chamo?
<zepard> or something else
postalchris has quit [No route to host]
<flux> I use xemacs. I never managed to make chameleon work.
<flux> could be good, for all I know
<pango_> flux: do you use prelink?
<zepard> ok go to emacs for a little while
<flux> I don't think so
<pango_> mmmh ok
rwmjones_ltp has joined #ocaml
<zepard> what is prelink?
<pango_> "The prelink package contains a utility which modifies ELF shared libraries and executables, so that far fewer relocations need to be resolved at runtime and thus programs come up faster."
<zepard> hum
<zepard> and there is an ocaml package for prelinking
<zepard> ?
<pango_> nope. prelink breaks bytecode-compiled OCaml programs
<pango_> hence my question
<zepard> ah
<Yoric[DT]> In my experience, prelinking broke my station.
<Yoric[DT]> So no prelinking for me :)
<Yoric[DT]> bluestorm: thinking back about your suggestion regarding with_input and with_output, I believe that you're actually wrong.
<Yoric[DT]> Closing stdin and stdout is probably a bad idea.
pattern has quit [Remote closed the connection]
<bluestorm> "closing" ?
thermoplyae has joined #ocaml
<Yoric[DT]> What you suggested is taking as argument a in_channel (respectively out_channel).
<Yoric[DT]> (instead of a file name)
<Yoric[DT]> Which means that you can take stdin (respectively stdout).
<Yoric[DT]> Since the whole point of the function is to close the channel after executing the embedded function (or in case of error), we end up closing stdin/stdout.
<bluestorm> aah, see :p
ygrek has quit [Remote closed the connection]
<bluestorm> so you want to get a channel that somewhat is local to the wrapper
Oatschool has quit ["Leaving"]
<bluestorm> with this point of view, the file restriction is a good idea
rwmjones_ltp has quit ["Leaving"]
<Yoric[DT]> That was the whole point.
Snark has quit ["Quitte"]
<bluestorm> Yoric[DT]: we could think of a more general way (e.g. we may want to use sockets instead of files, too), but then we basically end up with a let with_wrapper opener closer action = ...
<Yoric[DT]> Indeed.
<Yoric[DT]> Also called try...finally...
<bluestorm> :p
Tetsuo has quit ["Leaving"]
bzzbzz has joined #ocaml
jlouis_ has quit [Remote closed the connection]
jlouis has joined #ocaml
marmottine has joined #ocaml
jlouis has quit [Remote closed the connection]
jlouis has joined #ocaml
RobertFischer has joined #ocaml
pattern has joined #ocaml
ttamttam has left #ocaml []
jlouis has quit [Remote closed the connection]
jlouis has joined #ocaml
zepard has quit ["Leaving"]
postalchris has joined #ocaml
bzzbzz_ has joined #ocaml
marmottine has quit ["Quitte"]
bzzbzz has quit [Read error: 110 (Connection timed out)]
robyonrails has quit ["Leaving"]
Torment has joined #ocaml
seafood_ has quit []
bluestorm has quit ["Konversation terminated!"]
hkBst has quit ["Konversation terminated!"]
Jedai has quit [Read error: 110 (Connection timed out)]
middayc has joined #ocaml
ita has joined #ocaml
RobertFischer has quit ["Trillian (http://www.ceruleanstudios.com"]
Snrrrub__ has quit [Read error: 110 (Connection timed out)]
hsuh has joined #ocaml
dramsay has quit [Read error: 110 (Connection timed out)]
seafood_ has joined #ocaml
Smerdyakov has joined #ocaml
Yoric[DT] has quit ["Ex-Chat"]
dramsay has joined #ocaml
lbc has joined #ocaml