flux changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | 3.11.0 out now! Get yours from http://caml.inria.fr/ocaml/release.html
Ched has quit [Remote closed the connection]
Ariens_Hyperion has joined #ocaml
<Ariens_Hyperion> hi, has anyone managed to install ocsigen in leopard?
jeddhaberstro has joined #ocaml
hsuh has joined #ocaml
<hsuh> hm. i cant find out how to iterate for each char on a string
Ariens_Hyperion has quit []
<hsuh> help?
<brendan> String.iter
<hsuh> tks
carletonb has joined #ocaml
carletonb has left #ocaml []
chahibi has quit [Remote closed the connection]
verte has joined #ocaml
Narrenschiff has left #ocaml []
seafood has joined #ocaml
verte has quit ["http://coyotos.org/"]
<thelema_> hsuh: for i = 0 to String.length s - 1 do f s.[i]; done;
vuln has joined #ocaml
vuln has quit ["leaving"]
hsuh has quit [Remote closed the connection]
Hhhhh has joined #ocaml
seafood has quit [Read error: 110 (Connection timed out)]
AxleLonghorn has joined #ocaml
Hhhhh has quit ["K-lined"]
wsmith84 has joined #ocaml
AxleLonghorn has left #ocaml []
AxleLonghorn has joined #ocaml
wsmith84 has quit ["Leaving"]
wsmith84 has joined #ocaml
<wsmith84> quick ocaml question: I want to bind the first few entries of a list compactly, as if it were a tuple, i.e. similar to "let (a, b) = mytup" to a tuple I do "let a::b::_ = mylist" for a list. I know for a fact that the list contains exactly two elements. The compiler issues a warning because the pattern is not exhaustive (i.e. it does not match a list of zero or 1 elements). Is there a more compact form to do this cleanly than t
<wsmith84> o split it in two lines?
<flux> there is a language extension iirc bluestorm wrote to overcome that, but I don't remember where to find it from
<wsmith84> thx flux
<wsmith84> I haven't used camlp4 yet, seems like a bit much just to get a little bit of syntactic sugar :-)
RowanD has joined #ocaml
<wsmith84> I suppose I could write a couple of handy little functions that return a fixed tuple of a few of the list's first elements.
<wsmith84> Is there a way I could do that polymorphically?
<wsmith84> let taketup2 l =
<wsmith84> match l with
<wsmith84> | a :: b :: _ -> (a, b)
<wsmith84> | _ -> ('a, 'a);;
<wsmith84> (doesn't compile, for obvious reasons, just not sure how to do it polymorphically)
<thelema_> wsmith84: what would such a function return if given the empty list?
<wsmith84> It would raise an exception!
<wsmith84> I get your point though, it would have to know how to construct a default value for any given type.
<wsmith84> Not possible.
<thelema_> let take2 = function a::b::_ -> (a,b) | _ -> invalid_arg "not enough elements"
<RowanD> You could take the default as an extra argument.
<wsmith84> oh thelema, never mind, it works fine.
<wsmith84> I just raise in the catchall.
<wsmith84> it works.
<thelema_> wsmith84: oddly enough, f# has a function that, given a type, it returns some sort of
<thelema_> 'default value'
<wsmith84> So I can have my syntactic sugar for the case with small n., e.g. 1,2, 3, 4, 5,
<wsmith84> without camlp4
<RowanD> thelema: Yeah? What's it called? (I'm teaching F# currently.)
<wsmith84> Is there a classic name for this function?
<thelema_> not that I know. C# has a similar function, with a really different name
<thelema_> RowanD: give me a bit to look it up
<wsmith84> Hey guys, with the current explosion in FP, wouldn'it be worthwhile at some point to come up with a normalized set of commo function names, at least for all of the basic operations that you seem to find in every one of these languages?
<wsmith84> e.g. "map" is pretty much map everywhere, but "iter" is "foreach" in other langs
<wsmith84> It seems to me a good set of basic names should exist and become in use, it's not even a language thing, just a matter of choice and easing the switching between langs.
<thelema_> C#: default(T), F#: Unchecked.defaultof<int>
<thelema_> wsmith84 map != foreach -- one is functional, the other imperative
<thelema_> wsmith84: and ocaml has a bigger problem than function names: (!) doesn't mean not.
<RowanD> iter in Haskell isn't really the same thing. The language affects what you want in the libraries.
<wsmith84> thelema: I chose a bad example. That's really just a matter of rewriting anyway.
<RowanD> And, in a practical sense, getting people to agree on library names, argument order, etc is about as easy as getting them to all use the same language.
<wsmith84> Rowan: Haskell is a special case IMO, but I think that several of the basic function names could be generalized for a lot of the other languages.
<wsmith84> even the variants of LISP.
<wsmith84> e.g. Clojure.
AxleLonghorn has left #ocaml []
<wsmith84> Haskell's semantics are quite different because of the prevalent laziness everywhere, so perhaps that doesn't make sense in all cases, but for many of the functions thereis an analog.
<wsmith84> Rowan: I agree it would be difficult, but isn't it silly? So many of the concepts are the same. So we'll have LISP all over again. Lovely.
<RowanD> Well - new languages do tend to follow one of the existing languages.
<RowanD> E.g., Lisp, CAML, SML, Haskell
<RowanD> I agree people shouldn't invent everything from scratch for a new language.
<wsmith84> Well, the concepts are just reimplemented in many cases, but the name choices vary, because there isn't a well-established set.
seafood has joined #ocaml
<wsmith84> It would be interesting to draw a comparison table for 100 most common functions.
<RowanD> Sure. Sometimes people build libraries that just rename everything to how they are used to - you could do that for the main languages to produce something consistent. But, I doubt you'd convince many people to use it.
<wsmith84> Like Esperanto.
<RowanD> thelema: thanks for the defaultof pointer. I won't be showing my students that though - because I've already emphasized that using option types avoids allowing nulls everywhere.
<RowanD> I guess that still holds as long as you don't use "unchecked" things.
<RowanD> wsmith: yeah, good analogy.
Komar_ has quit [Read error: 113 (No route to host)]
<mrvn> RowanD: I prefer exceptions to option types though.
<mrvn> match List.tl list with None -> ... | Some x -> ... is just stupid for example. I could just match the list directly.
<RowanD> mrvn: yeah, for returning things sometimes they are better. Although performance of F# exceptions is sometimes considered poor. For optional arguments, option types are the right thing.
<mrvn> RowanD: What is expensive about exceptions in F#? Throwing them or the try construct? If try is expensive then that sucks.
<mrvn> exceptions are good to signal exceptional things.
<RowanD> They are expensive whether you catch them or not.
<mrvn> RowanD: even if you don't throw them?
<RowanD> Oh - I think it's only if you throw them. Not sure actually.
<mrvn> In C++ exceptions only cost time when you throw them. So when you only use them for exceptional situations they are perfect. If youmisues them for common things then you pay for it.
<mrvn> How expensive are exceptions in ocaml?
<RowanD> Yeah - just checked. The issue is only when you actually throw an exception.
<flux> they say exceptions are pretty cheap in ocaml. apparently the language shootout doesn't benchmark them, though
<RowanD> Yeah - Xavier once said about the same time as 2 function calls for raising an exception, about 1 function call to install a handler.
<RowanD> The trouble in F# is that it uses .NET exceptions which in turn are based on windows exceptions - which are heavyweight. Generally you don't want to use them for control flow. I guess instead you end up using option types or explicit continuations or similar.
<mrvn> Doesn't it depend on how many stack frames have to be freed between the raise and the try?
<mrvn> Or does the try record the stack position so it can just jump back to it?
pierre_m has joined #ocaml
ygrek has joined #ocaml
pants1 has joined #ocaml
itewsh has joined #ocaml
hto has joined #ocaml
jeddhaberstro has quit []
verte has joined #ocaml
wsmith84 has quit [Read error: 110 (Connection timed out)]
pierre_m has left #ocaml []
Camarade_Tux_ has joined #ocaml
Camarade_Tux has quit [Read error: 104 (Connection reset by peer)]
<RowanD> mrvm: The stack position is recorded, so the frames don't have to be freed one by one in ocaml.
hto has quit ["leaving"]
hto has joined #ocaml
hto has quit [Client Quit]
hto has joined #ocaml
_zack has joined #ocaml
itewsh has quit [Success]
itewsh has joined #ocaml
itewsh has quit [Client Quit]
Camarade_Tux_ has quit [Read error: 110 (Connection timed out)]
Camarade_Tux has joined #ocaml
seafood has quit []
slash_ has quit [Client Quit]
Yoric[DT] has joined #ocaml
hto has quit ["leaving"]
hto has joined #ocaml
marmottine has joined #ocaml
Ched has joined #ocaml
H0lyD4wg has joined #ocaml
<H0lyD4wg> n00b question: can i have a 10^12-long bigarray on a 32-bit platform?
_zack has quit ["Leaving."]
jeanbon has joined #ocaml
<flux> h0lyd4wg, no
<flux> (and that's language-independant)
<H0lyD4wg> ok, thanks.
H0lyD4wg has left #ocaml []
ttamttam has joined #ocaml
marmottine has quit [Read error: 110 (Connection timed out)]
pants1 has quit [Read error: 113 (No route to host)]
hkBst has joined #ocaml
ttamttam has left #ocaml []
rwmjones_ has joined #ocaml
ygrek has quit [Remote closed the connection]
bluestorm has joined #ocaml
kaustuv_ has quit [Read error: 113 (No route to host)]
ygrek has joined #ocaml
_zack has joined #ocaml
jedai has quit [Read error: 110 (Connection timed out)]
itewsh has joined #ocaml
_zack has quit [Read error: 110 (Connection timed out)]
seafood has joined #ocaml
xevz has quit [Remote closed the connection]
xevz has joined #ocaml
verte has quit ["http://coyotos.org/"]
_zack has joined #ocaml
xevz has quit [Read error: 131 (Connection reset by peer)]
xevz has joined #ocaml
mishok13 has quit [Read error: 110 (Connection timed out)]
seafood has quit [Read error: 110 (Connection timed out)]
ttamttam has joined #ocaml
xevz_ has joined #ocaml
xevz has quit [Read error: 54 (Connection reset by peer)]
xevz__ has joined #ocaml
xevz__ is now known as xevz
xevz_ has quit [Read error: 104 (Connection reset by peer)]
itewsh has quit ["There are only 10 kinds of people: those who understand binary and those who don't"]
xevz has quit [Remote closed the connection]
xevz_ has joined #ocaml
xevz_ is now known as xevz
xevz has quit [Remote closed the connection]
xevz has joined #ocaml
ttamttam has left #ocaml []
_zack has quit [Read error: 110 (Connection timed out)]
xevz_ has joined #ocaml
xevz has quit [Read error: 104 (Connection reset by peer)]
<kaustuv> I've been playing with bluestorm's pa_holes, but think it is a bit too verbose for the common case and not flexible enough. I have an alternative proposal: http://www.msr-inria.inria.fr/~kaustuv/misc/pa_underscore.ml -- comments welcome.
xevz_ has quit [Connection reset by peer]
Bacta has joined #ocaml
<Bacta> You guys?
<Bacta> Seriously
xevz__ has joined #ocaml
<thelema_> Bacta: pong
xevz__ is now known as xevz
<thelema_> kaustuv: interesting. Let's not overuse "syntax error" - if we can, make it an "arity error", with a meaningful message instead of the near-useless "you typed it wrong" = "syntax error"
AxleLonghorn2 has joined #ocaml
<kaustuv> thelema_: camlp4 is already much better than ocaml in signalling the reasons for syntax errors. How does one signal an arity error? I am a camlp4 noob, so I'm quite happy to receive instructions on how to do anything better.
<thelema_> you've done a good job with explaining the syntax error.
AxleLonghorn2 has quit [Read error: 60 (Operation timed out)]
xevz has quit [Remote closed the connection]
xevz has joined #ocaml
<Bacta> is this a functional language?
mikeX has left #ocaml []
xevz has quit [Remote closed the connection]
AxleLonghorn has joined #ocaml
mishok13 has joined #ocaml
xevz has joined #ocaml
<hcarty> Bacta: Yes?
Camarade_Tux has quit [Read error: 110 (Connection timed out)]
Camarade_Tux has joined #ocaml
wsmith84 has joined #ocaml
<flux> kaustuv, is %(42) valid and if so, what does it mean?
Bacta has quit ["Leaving"]
<flux> kaustuv, when we were discussing with bluestorm about his extension, I think an idea of that meaning (fun () -> 42) was mentioned.. but it would be a special case.
<thelema_> special casing arity 0 == unit -> foo ?
<flux> yes
<flux> because that is useful at times. more useful I think just handling it as arity 0 == foo I suppose?
<flux> s/I think // :)
<bluestorm> kaustuv: I dislike numbered underscores because they are valid ocaml identifiers
<flux> I've never seen them been used in valid ocaml programs, though
<bluestorm> I think it is better practice to use \n instead, although admittedly a bit uglier
<bluestorm> flux: it i
<flux> bluestorm, what?-)
<bluestorm> it is standard practice in erlang program to name unusued parameters
<flux> well, not in ocaml :)
<bluestorm> using a _foo syntax
<bluestorm> well it might become :-'
<bluestorm> but i agree that _3 would be a really weird name
<flux> well that is often in ocaml too, but it follows that because normal identifiers can't begin with integers, it is not common to have _[0-9] prefixed identifiers either..
<bluestorm> I still think we shouldn't use it
<hcarty> I don't know how this applies to keyboards in other regions, but the lazy typist in me likes that fact that \ doesn't require hitting shift, while _ does
<flux> \ requires a shift in Finland, but so does _.
<flux> in any case coders like me use US keyboard layout ;)
<thelema_> bluestorm: can't we only interfere with _\d identifiers within the (% ) bounds?
xevz has quit [Read error: 54 (Connection reset by peer)]
<bluestorm> thelema_: well we can
<bluestorm> let's say it kinda disrupt some aesthetic feeling about syntax extensions :-'
<bluestorm> thelema_: for example, what do you expect the meaning of this to be :
<flux> before seeing the example, I would expect nobody to write code like that :-)
AxleLonghorn has left #ocaml []
<bluestorm> let _4 = 2 in %3 (_1 + _2 + _3 + _4)
<bluestorm> (in kaustuv's proposition, %3(foo) instead of %(foo) means that the function is 3-ary)
<flux> bluestorm, so given that extension, how often would you expect to find that or similar code?
<flux> while the extensions can give tools for obfuscating code, well, I hope that coder can be trusted atleast _a bit_
<bluestorm> hm
<flux> although if I were to write - or fork :) - that kind of extension, I would just make all suspicious cases invalid
<flux> that would probably include mixing numbered and unnumbered bindings inside %()..
<bluestorm> kaustuv: there is also a problem with using "%" wich is a valid infix operator
<thelema_> bluestorm: it's an error, that's pretty clear
<bluestorm> well
<thelema_> I don't see a lot of use for %n( ), but I don't see it causing too many problems.
thelema_ is now known as thelema
<bluestorm> it could be worked around by slightly modifying the lexer to differentiate % (..) and %(...)
<bluestorm> it can be done reasonably nicely (a good idea from Jérémie Dimino), though the %n(..) thing would complexify the code a bit
<bluestorm> I don't see the problem with my (\ ...), however
<bluestorm> (wich also looked like the Haskell lambda operator)
Amorphous has quit [Read error: 110 (Connection timed out)]
<bluestorm> all in all
<thelema> I prefer the (\ ... ), but with _\d inside
<bluestorm> _\d, you mean \d or _d, or _\d literraly ?
<thelema> assuming no technical reason in implementation that
<thelema> 'll make one safer
<thelema> _ _1 _2 _3
<bluestorm> ah
<thelema> (I'm using \d as regex)
<bluestorm> got that
<bluestorm> well
<bluestorm> you want pa_words, with _k instead of \k, and the "unnumbered variable" we toyed with but I didn't implemented
Amorphous has joined #ocaml
<bluestorm> hm
<bluestorm> pa_holes, sorry
<thelema> alternately, pa_underscore with (\ ) instead of %( )
<bluestorm> yes
<hcarty> Is \( ... ) possible? That would avoid (\\1) clashes in the current pa_holes - assuming they exist as-is
<thelema> I don't know enough p4 to judge the implementations - are they effectively the same?
<kaustuv> <flux> kaustuv, is %(42) valid and if so, what does it mean?
<kaustuv> In my case it is just the same as 42
<thelema> kaustuv: would a special case be reasonable?
<bluestorm> hcarty: would be possible
<kaustuv> <bluestorm> kaustuv: I dislike numbered underscores because they are valid ocaml identifiers
<kaustuv> Heh. I like them for exactly that reason.
<bluestorm> kaustuv: yes, I saw that in your implementation
<bluestorm> for i = 1 to last do vs := ("_" ^ string_of_int i) :: !vs done ;
<bluestorm> that's quite clever actually
<bluestorm> may even change my mind
<bluestorm> hcarty: \(...) would probably be possible
<kaustuv> That's what I had at first, but tuareg mode throws a fit with \(.
<bluestorm> hm
<hcarty> bluestorm: It reads a little clearer IMHO -- but tuareg problems carry a lot of weight in this community :-)
<bluestorm> i see
<flux> you know, you could just provide patches to tuareg :)
<bluestorm> but hcarty
<bluestorm> in the presence of _1 instead of \1, is (\ ..) still an issue ?
<hcarty> bluestorm: I still find it easier to spot
<bluestorm> hm
<hcarty> A leading \ makes it stick out a bit more
<hcarty> Which I think may be somewhat important, since the language changes inside of that delimiter
<kaustuv> In my version it doesn't really, except that a new identifier _ is added.
<bluestorm> kaustuv: there still is an implicit part
* thelema prefers (\ .. ) to \( .. )
<kaustuv> The only problem is that in my version [fun _1 -> %( _1 )] is different from [fun _0 -> %( _0 )].
<kaustuv> But alpha equivalence across %() seems like a tall order
<hcarty> Would (\_2) work?
<bluestorm> what I like with \ is the idea that the parenthesis only delimiters, not part of the syntax propper
<thelema> and we should put big warnings on this: any "holed" expressions more than ~20 characters should probably be written in full.
<hcarty> Versus \(_2) (if the leading _ is going to be used)
<thelema> kaustuv: why would someone do [fun _\d -> ...] ?
<bluestorm> hcarty: (\_2) would work if you use _2
<bluestorm> thelema: it's valid
<hcarty> thelema: They could be stacking extensions
<bluestorm> btw kaustuv, aren't there any nesting issues ?
<bluestorm> hcarty: i got it first :-'
<kaustuv> bluestorm: none I'm aware of
<thelema> yes, but I thought we basically decided that _\d+ was 1) rare outside our extension and 2) not a problem, since it only means something inside our extension?
<kaustuv> And, fwiw, the reason I prefer underscores is that the most common case is a left to right numbering of the holes.
<kaustuv> And the analogy with patterns...
<hcarty> (\_ + \3) if you want to mix everything up terribly
<thelema> does anyone want to allow both _n and \n?
<bluestorm> i don't think so :D
<kaustuv> I would be fine with _ and \n.
<bluestorm> hm
<kaustuv> That would even allow (\_), where (\ ) is as in bluestorm's code, to be fine
<bluestorm> I could (or you could) easily add _ handling to pa_holes
<thelema> so we have _ for unnumbered "holes" and \n for numbered holes
<kaustuv> Sure. To be clear, I think the main improvement in my version is the ability to specify a particular arity, not the underscores as such.
<hcarty> Yes, my intent with the above is that _ alone and \n, but not _n
<hcarty> I don't know if that is a good idead though
<thelema> kaustuv: what do you gain from specifying arity?
<kaustuv> the ability to write the K combinator :)
<kaustuv> %2(_1)
<thelema> the ability to eat extra parameters?
<bluestorm> i'm not convinced by that arity thing either
<bluestorm> it seems me rather arcane and not so much more expressive
<thelema> I think that kind of thing should probably be written out (and commented), not hidden by slick syntax
<bluestorm> not sure the "complexity vs. power" balance is so interesting on that one
<kaustuv> Well, using expressions with holes is rather arcane from the get go. The only reason to use it is incurable sloth
<kaustuv> (which I do suffer from, greatly)
<thelema> I understand the sloth argument - I'm guilty too. But it should make common and straightforward code easier to read and write
<bluestorm> google define:sloth "is the common name for any of the slow-moving, New World arboreal mammals comprising the families Megalonychidae (two-toed sloths)"
<thelema> making the k combinator easier to write seems to have the downside that it's harder to read than (fun x _ -> x)
<bluestorm> i'm not sure any of those extension are gonna enter the hall of fame, but that new english word made my day
<thelema> bluestorm: synonym: laziness
<kaustuv> thelema: imagine [List.fold_left %2(_1 + 1) 0] which is the same as List.length. This is hard to do without the %2
<kaustuv> Of course you won't write that when you want to write List.length, but it's an example of the kind of use you can put it to
<thelema> ignoring arguments seems like something that should be made more explicit.
<bluestorm> I would rather use (\ ignore \2; \1 )
<thelema> (fun x _ -> x+1)
<bluestorm> :]
<kaustuv> bluestorm: your code has more characters than thelema's, which defeats the whole point of using holes
<bluestorm> agreed
<thelema> kaustuv: I see the additional difficulty of reading functions with %n( ) not worth the benefit.
<thelema> having to count the number of used arguments, and then compare to n... seems excessive...
<kaustuv> Disallowing things like [%2(_1 + _3)] is also a nice syntactic check caught at preprocess time rather than at type checking time, with a very simple error message. You can think of %n as a kind of arity type like Prolog's /n
<thelema> otoh, instead of setting arity, what about having %n( ) mean to ignore n extra arguments
<thelema> so that K combinator becomes %1(_1)
<thelema> take the first argument, drop one more.
<kaustuv> That's fine as long as you are ignoring arguments at the end. But what if you want to print the elements of the list? [fold_left %2(print_int _2) ()].
<kaustuv> (Granted in this case %2 is superfluous)
<thelema> kaustuv: then you don't need the %2 -- %(print_int _2) does that.
|jedai| has joined #ocaml
<bluestorm> i like the thelema idea
wsmith84 has quit [Read error: 104 (Connection reset by peer)]
<bluestorm> ( btw kaustuv you could use GNU source-highlight and upload colored code on your website, wich would immediately make them insanely cool)
|jedai| is now known as jedai
<kaustuv> I might do that eventually, but there's the sloth issue again.
<kaustuv> By the way, check out http://www.msr-inria.inria.fr/~kaustuv/misc/pa_concurry.ml which was the original problem I was going to solve
<kaustuv> But I don't like the result at all
* thelema isn't impressed by currying constructors
<kaustuv> bluestorm: Yes, I tried something like that at first, but (a) I didn't like the excess code, and (b) I wanted to use it for types whose definitions I don't control such as 'a option.
<bluestorm> well
<kaustuv> ('a option is just an example. In my case, I have an AST type with 172 constructors!)
<bluestorm> in my wildest dream, there is a third ocaml syntax, wich is basically like the standard syntax, plus the curried constructor and types from the revised
<thelema> kaustuv: with batteries, we control the definition of 'a option :)
<bluestorm> (wich excess code ?)
<kaustuv> It adds code to the module that may never be used. Since ocaml doesn't garbage collect useless functions, the binary just grows fat
rwmjones_ has quit ["Closed connection"]
<kaustuv> By the way, one important feature is the ability to say, eg. [3!`Whatever]. This is great if you are parsing things with a tagged return type.
<bluestorm> could the syntax be added in the pattern side as well ?
<kaustuv> bluestorm: not in my case, but hmm... interesting question.
<kaustuv> I think if the ocaml language were to be extended, it should be fairly simple for a constructor of type [s and t and u] to be usable as a function at type [s -> t -> u -> _] with the necessary coercion added by the type checker.
<bluestorm> kaustuv: that was the case in caml light
<bluestorm> the feature was removed as "inessential"
<bluestorm> (btw, if it's not indiscrete, were do you work at INRIA ?)
<bluestorm> s/were/where/
<kaustuv> At the MSR-INRIA joint lab at Orsay. (Near the Ecole Polytechnique and far away from Rocquencourt)
<bluestorm> "arcane topics of demonstration theory", says the ~kaustuv page :p
<kaustuv> bluestorm: are you sure it was removed as inessential or because there was some back and forth on whether constructors should be variadic or tupled?
<bluestorm> i'm not sure
<kaustuv> Because at least from my experience with SML it is pretty useful when present
<bluestorm> agreed
<bluestorm> I'm pretty confident it should be variadic, and the pattern syntax could be changed to be curryfied too (as in the revised syntax)
marmottine has joined #ocaml
<kaustuv> Yes, that is my feeling also. Indeed, there is not even a problem with the way the ocaml elaborator handles higher-order functions because because constructors can never be applied to more arguments than specified.
animist has quit [Read error: 110 (Connection timed out)]
marmottine has quit [Read error: 110 (Connection timed out)]
<flux> btw, regarding code that's not under one's control: there should be a way to save stuff from camlp4 and load it when compiling others. of course, there's nothing (?) stopping one from doing this already.. but it would be nice to find the files just in the same way .cmi-files and .cmo-files are found by the compiler.
<flux> I imagine that would allow compiling bunch of foreign .ml-files with the extensions without making modifications to them, and still using for example constructor currying from another .ml
<flux> so you wouldn't actually generate any new functions in that case
<kaustuv> It would be enough, i think, if we could have a post-processor that works on a partially typed AST that has already resolved such things as identifier references and constructor arities.
<bluestorm> sounds very complex to me
<thelema> "save stuff from camlp4" - what stuff?
<mrvn> hcarty: \ requires hitting alt-gr
<kaustuv> Another alternative is to make the type inference engine support "plugins" that handle certain type constraints specially. The price will be principal typing, but the modern trend in ML dialects seems to be giving up principal typing when the benefits are large enough
<flux> (actually the same in here (not shift as I said))
xevz has joined #ocaml
<mrvn> Why do people want to write (\ ...) instead of (fun ...)? Is that little extra typing really that bad?
<mrvn> takes all the fun out of it.
<thelema> mrvn: it's not the two character difference "\" vs "fun", it's the arguments as well...
<thelema> (\ _ * _ + _) instead of (fun x y z -> x * y + z)
<mrvn> way too perlish.
<totom> if perlish is a synonym for unreadable, yes :-)
<mrvn> It might be readbale for such a short example but now consider a 10 line closure using that.
<thelema> perlish is a synonym for "looks like line noise" - too many symbols in a row
<thelema> mrvn: of course it shouldn't be abused in that way. My rule above was < 20 characters.
<mrvn> Or (\ _ + _ + (\ _ * _ + _) _ _ _)
<kaustuv> No one every uses functions of that nature
<kaustuv> It's more common to repeat arguments
<thelema> (\ _1 * _1 + _2)
<flux> hand-picked samples from a project: (fun device -> device#start) (fun ci -> ci.Db.connection_serial) (fun s -> s ()) (fun i -> i) (fun trig xs -> trig::xs) (fun ev -> ev.D.event_id, ev)
<flux> some of them could make use of some predefined functions such as identity and cons, though..
<flux> but then again I found only 0.6% of rows to be candidates for that
<mrvn> flux: I hate that (::) isn't valid.
<flux> (I used cat *.ml | grep -c '(fun [a-z].*)$' to get that number)
ttamttam has joined #ocaml
<mrvn> flux: I miss member pointer a bit: (fun x -> x.foo) and (fun x -> x#foo).
<flux> well, that extension works nicely for those cases
<flux> actually my grep is likely missing some cases that should be counted
<mrvn> (\ _#foo)?
<flux> yes
<mrvn> In those cases I would rather like .foo and #foo.
<kaustuv> % grep '(fun [a-z].*)' **/*.ml | wc -l
<kaustuv> 1343
<kaustuv> (on the ocaml-3.11.0 sources)
<flux> kaustuv, did you look if they were valid-looking cases?
<mrvn> Thething is that if something can be abused it will be abuse. Just look at how obfuscated general perl code is.
<flux> mrvn, (.foo), (#foo) would be ok, but, I don't think it's a good idea to add too much special syntax!
<kaustuv> flux: no, it included things like
<kaustuv> typing/typetexp.ml: (fun name (ty, loc) ->
<mrvn> flux: why ()?
palomer has quit [Remote closed the connection]
<flux> mrvn, well how would it work then?
<flux> mrvn, I'm thinking ambiguities
<flux> foo.bar.baz vs foo.bar (.baz), different things, no?
<flux> foo.bar .baz?
<mrvn> .baz foo.bar
<flux> ah, so you could apply field names
<mrvn> .baz : foo.bar -> 'a
<flux> I wonder if that has any ambiguities. it might not.
<mrvn> fun x -> x.bar
<mrvn> .baz / #bat is a closure that takes an x and returns x.baz/x#baz.
<kaustuv> How would you parse: [(fun x y -> ()) 2. baz]?
<mrvn> Only confusion could be with (a : #foo)
ttamttam has left #ocaml []
<mrvn> kaustuv: ('a -> 'b -> unit) (float as 'a) 'b
<mrvn> kaustuv: so alltogether: unit list
<flux> mrvn, would would foo.baz, foo .baz, foo. baz and foo . baz be parsed?
<mrvn> flux: syntax error, function (foo) taking a function (fun x -> x.baz) as argument, syntx error and syntax error.
<flux> btw, all those are valid at the moment
<mrvn> or is "foo. baz" currently valid?
<mrvn> aeh, foo.baz just like now, not syntax error
<flux> as I said, all they are
<kaustuv> [expr -> expr DOT expr] is a valid production in both grammars
<kaustuv> Err, no, I lied.
<mrvn> # t .x;;
<mrvn> - : int = 1
<mrvn> the spaces really do seem to get ignored.
<kaustuv> yes, but the things to the right of a . are more restricted. They can be field projections or ModulePath.field projections
<mrvn> That is a problem then. (.foo) would be needed.
<kaustuv> (Or .(expr) and .[expr], obviously)
<flux> besides think plain .foo would be even too succinct. atleast (.foo) would clearly look like something different
<mrvn> foo # bar is allowed too. so (#bar) as well.
<flux> however I still think that if there ia a (\_#bar) extension around, it's already succinct enough
<mrvn> flux: too cryptic looking.
<mrvn> (#bar) looks like (+) or (*) to me.
<flux> that's a good point
<mrvn> and you couldn't about (#bar) like (\_ ...)
<flux> how often is that used? well, two of my hand-picked problems would be covered by that..
<mrvn> Not sure. Just had that a ton of times lately since I played around with module stuff using (fun x -> x#foo) specifically.
<kaustuv> The ocaml source has many cases like:
<kaustuv> typing/typecore.ml: iter_pattern (fun pat -> generalize_expansive env pat.pat_type) pat
<mrvn> kaustuv: and I like that it has a name there.
<kaustuv> but it conflates the outer and inner pat because they couldn't be bothered to name it pat' or something
<kaustuv> this is a notorious source of bugs
<kaustuv> compare to: iter_pattern (\ generalize_expansive _.pat_type) pat
<mrvn> you will get new cases with iter_patter (\ generalize_expansive env _1.pat_type) _1
<flux> the cases don't come out of nothingness, they need to be written :)
<mrvn> Maybe it would be better for the compiler to warn about temporarily shadowing a binding.
<flux> for example, kaustuv's code is clear, while indeed your sample isn't
<mrvn> let x = 1 in let x = 2 in .... is ok, but let x = 1 in begin let x = 2 in ... end; x is bad.
vuln has joined #ocaml
<flux> well, perhaps these kinds of points would be better suitable for an ocaml lint project
Smerdyakov has joined #ocaml
<thelema> okay, maybe I take back what I said about _ being better - in the "iter_patter" example above, _ mixes in with the middle of variables.
<kaustuv> The compiler shouldn't presume to know what I'm doing better than me. Shadowing warnings are pure nannycruft.
<mrvn> kaustuv: then don't complain about people using it. :)
<flux> mrvn, so if a computer isn't allowed to complain, so shouldn't a human being either?-)
<flux> I think humans can show much, much better judgement on case-by-case-basis than computers :)
<mrvn> flux: who says kaustuv is a humand being? :)
<flux> well, if it's an AI of that level, I think he still has the right to complain :)
<kaustuv> More importantly, who says humans aren't computers.
|jedai| has joined #ocaml
<mrvn> Imho (\ ...) just adds obfuscation except for the verry verry short cases. But people would never restrict the use to just them.
<mrvn> Plus you duplicate functionality.
<flux> mrvn, let's compare this to perl. you can use $1 or $2 in functions, or you can give them names.
<flux> it happens I always give names except for the shortest (lambda) functions
<mrvn> The fact alone that you use perl as a comparison says it all. :)
<flux> and I might give them names in even those cases too
<flux> well, it has a similar construct, $_[2] etc
<kaustuv> Well, I doubt anyone's proposing adding (\ ) to the core ocaml grammar. It's strictly for people who are rapidly losing the ability to use their wrists due to carpal tunnel syndrome. (Me, unfortunately.)
<mrvn> kaustuv: then add a makro that translates (\ ...) into (fun ....)
<kaustuv> i.e., a camlp4 syntax extension?
<mrvn> If the (\ ...) really make up a sizeable portion of your code then maybe you are doing something wrong. I don't think I would have it that often.
<flux> mrvn, that's exactly what has been done?-)
jedai has quit [Nick collision from services.]
|jedai| is now known as jedai
<mrvn> I ment a makro in the editor so the typing is less. Not the resulting source.
<flux> yeah, in total it will affect possibly 0.05% to code size
<flux> mrvn, well, I'm not sure the verbiage is better for reading, really
<mrvn> (fun x y -> x + y) isn't hard to read.
<flux> (fun r -> map (new db_result r)) vs (\ map (new db_result \1)) (fun r -> int_of_string r#cmd_tuples) vs (\ int_of_string \1#cmd_tuples)
<kaustuv> I think their use will be limited to arguments of things like fold and build. That's what I plan to use them for anyhow.
<flux> plus the position of the argument is obvious that it needs to be a one-argument function
<flux> (namely it's the 'result')
<mrvn> flux: Now I have to scan the whole funtion to see if there is any \2 hidden somewhere.
<flux> mrvn, I think it's basically one glance to see the whole function
<mrvn> People will misuse it for larger functions.
<flux> complain to them, then
<flux> I can write obtuse and difficult-to-read functions now
<mrvn> but only one way, not two ways.
<mrvn> Is (\ int_of_string \2#cmd_tuples) valid?
<kaustuv> it has a different type
<flux> it is, but in my opinion it shouldn't be
<mrvn> or (fun _ x _ -> x)?
<mrvn> how would you write that as (\ ...)?
<flux> I could choose to use one-letter in all my functions. heck, I could use also one-letter function names too :)
<flux> (one-letter arguments I meant to say)
<kaustuv> mrvn: (fun _ x -> x) is just (\ _2). If you want to ignore a trailing sequence of arguments, it's not possible with the current (\ ... ) syntax.
<kaustuv> or make that (\ \2)
<mrvn> flux wants (\ \2) to be invalid.
<flux> btw, of the examples I gave, none of them would've even used two arguments
<flux> and even if I did find such examples, I don't think I would find one that would ignore one of such arguments
<flux> in any case, there should be functions such as cons, const, identity, flip, compose etc around
<mrvn> flux: yes. I think thatwould take care of most cases that arent (.x) and (#x).
<kaustuv> thing is, flip and compose make the code HARD to understand, not to mention add runtime costs
<mrvn> kaustuv: wouldn't they inline?
Smerdyakov has quit ["Leaving"]
<flux> (OfDb.bool @. get_hh) -pattern seems quite common in the code base I'm watching: convert the first value of result set to a boolean
<flux> actually @. appears almost in one percent of the lines in that database module
<flux> flip can be annoying, but at times it's nice. it's not hard when you recognize the pattern.
<kaustuv> Database munging is almost at the diametrically opposite end of the kind of code I write, which tends to be higher order and combinatorial. We may therefore have different tastes.
<flux> I imagine for example a web-app would have almost no function compositions (but perhaps I should take a look at some web-related ocaml code first)
<flux> atleast there are none in the small url-logging irc-bot and corresponding web page :)
<flux> kaustuv, the database module has a lot of conversion chains, and function composition is nice for those
<kaustuv> This discussion is interesting, but I have to go afk. Will read it later.
Alpounet has joined #ocaml
ygrek has quit [Remote closed the connection]
itewsh has joined #ocaml
ygrek has joined #ocaml
Associat0r has joined #ocaml
jeanb-- has joined #ocaml
jeanbon has quit [Nick collision from services.]
hsuh has joined #ocaml
ygrek has quit [Remote closed the connection]
pklbham has joined #ocaml
slash_ has joined #ocaml
jedai has quit [Read error: 110 (Connection timed out)]
|jedai| has joined #ocaml
Associat0r has quit [Client Quit]
pants1 has joined #ocaml
Associat0r has joined #ocaml
jeanb-- is now known as jeanbon
Associat0r has quit [Client Quit]
jeddhaberstro has joined #ocaml
jamii__ has joined #ocaml
Alpounet has quit ["Quitte"]
Alpounet has joined #ocaml
komar_ has joined #ocaml
Alpounet has quit ["Ex-Chat"]
Alpounet has joined #ocaml
komar__ has joined #ocaml
slash_ has quit [Client Quit]
Camarade_Tux has quit ["Leaving"]
komar_ has quit [Read error: 113 (No route to host)]
Camarade_Tux has joined #ocaml
Camarade_Tux has quit ["Leaving"]
seafood has joined #ocaml
<hcarty> Oh my, this is unfortunate... the lead BitC person is apparently leaving the project
pklbham has quit ["ERC Version 5.3 (IRC client for Emacs)"]
Camarade_Tux has joined #ocaml
jeanb-- has joined #ocaml
seafood_ has joined #ocaml
jeanbon has quit [Read error: 110 (Connection timed out)]
seafood__ has joined #ocaml
seafood has quit [Read error: 110 (Connection timed out)]
itewsh has quit ["There are only 10 kinds of people: those who understand binary and those who don't"]
Alpounet has quit ["Quitte"]
komar__ has quit [Remote closed the connection]
seafood_ has quit [Read error: 110 (Connection timed out)]
seafood has joined #ocaml
hkBst has quit [Read error: 104 (Connection reset by peer)]
seafood__ has quit [Connection timed out]
seafood_ has joined #ocaml
seafood has quit [Connection timed out]
verte has joined #ocaml
nwardez has joined #ocaml
Yoric[DT] has quit ["Ex-Chat"]
nwardez has left #ocaml []
jeanb-- has quit [Read error: 110 (Connection timed out)]
bluestorm has quit [Remote closed the connection]