gildor changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | OCaml 3.12.0 http://bit.ly/aNZBUp
alexyk has quit [Quit: alexyk]
lamawithonel_ has quit [Ping timeout: 264 seconds]
<thelema_> is this commonly used by anyone: let mod_if b f x = if b then f x else x
joewilliams is now known as joewilliams_away
joewilliams_away is now known as joewilliams
Associat0r has quit [Quit: Associat0r]
Associat0r has joined #ocaml
lamawithonel_ has joined #ocaml
<mrvn> you mean let x = if something then change x else x in ...?
boscop has quit [Quit: OutOfTimeException: Allocation of TimeFrame failed due to lack of time. Terminating...]
joewilliams is now known as joewilliams_away
alexyk has joined #ocaml
oriba has quit [Quit: Verlassend]
kaustuv_ has joined #ocaml
joewilliams_away is now known as joewilliams
alexyk has quit [Read error: Connection reset by peer]
lamawithonel_ has quit [Ping timeout: 255 seconds]
<_habnabit> I feel like there's some fundamental inversion of logic I haven't quite gotten yet. If I'm trying to execute code only if an exception is /not/ raised, how could I do that?
elehack has joined #ocaml
alexyk has joined #ocaml
<alexyk> why does specifying a default value defeat polymorphism?
<kaustuv_> _habnabit: what do you mean by 'exception is not raised'?
<_habnabit> kaustuv_, if running some code doesn't raise an exception
alexyk has quit [Read error: Connection reset by peer]
<kaustuv_> let _ = some code () in some_other_code ()
<_habnabit> kaustuv_, ah
<_habnabit> kaustuv_, but I also want to handle the exception if it /is/ raised
<_habnabit> kaustuv_, but not if it's raised by some_other_code
<kaustuv_> match try Some (some_code ()) with _ -> None with Some _ -> some_other_code () | None -> handle_exception ()
<kaustuv_> Might need to wrap the ... in try ... with Some _ in parens
<_habnabit> kaustuv_, awesome, thanks
mdmkolbe has left #ocaml []
<kaustuv_> err, I meant the ... in match ... with Some _
lamawithonel_ has joined #ocaml
alexyk has joined #ocaml
alexyk has quit [Read error: Connection reset by peer]
grettke has joined #ocaml
mbac has joined #ocaml
alexyk has joined #ocaml
joewilliams is now known as joewilliams_away
alexyk has quit [Read error: Connection reset by peer]
grettke has quit []
elehack has quit [Ping timeout: 272 seconds]
elehack has joined #ocaml
elehack has quit [Ping timeout: 245 seconds]
alexyk has joined #ocaml
alexyk has quit [Client Quit]
elehack has joined #ocaml
jamii has joined #ocaml
joewilliams_away is now known as joewilliams
pheredhel has quit [Read error: Operation timed out]
pheredhel has joined #ocaml
mnabil has quit [Ping timeout: 240 seconds]
Amorphous has quit [Ping timeout: 272 seconds]
tautologico has joined #ocaml
Amorphous has joined #ocaml
joewilliams is now known as joewilliams_away
elehack has quit [Quit: Farewell, programs.]
joewilliams_away is now known as joewilliams
myu2 has quit [Remote host closed the connection]
lamawithonel_ has quit [Ping timeout: 264 seconds]
tautologico has quit [Quit: tautologico]
jamii has quit [Quit: Leaving]
jamii has joined #ocaml
lamawithonel_ has joined #ocaml
jamii has quit [Ping timeout: 276 seconds]
sepp2k has quit [Quit: Leaving.]
strlen has quit [Ping timeout: 265 seconds]
lamawithonel_ has quit [Ping timeout: 255 seconds]
lamawithonel_ has joined #ocaml
lamawithonel_ has quit [Ping timeout: 264 seconds]
alexyk has joined #ocaml
<alexyk> hey thelema_
arubin has quit [Quit: arubin]
<alexyk> why does a default parameter restrict polymorphism? https://gist.github.com/808895
<mbac> isn't it obvious?
<alexyk> is there a way to specify it and still be able to pass another type as in the no-default version?
<alexyk> mbac: my parameter is any output function; if none is given, an Int.print should be used. But I might give a floatPrint.
<alexyk> I try to specify the type of that function generally in the type declaration, which doesn't help.
<mbac> oops, i misunderstood :)
<alexyk> np
<mbac> hmm, so what's the simplest case
alexyk has quit [Read error: Connection reset by peer]
Snark has joined #ocaml
<flux> alpounet, I guess it's because ocaml cannot have one function have more than one signatures
<flux> I've encountered the same issue
alexyk has joined #ocaml
mnabil has joined #ocaml
alexyk has quit [Client Quit]
<mbac> it doesn't have anything to do with optional arguments
<mbac> which is peculiar
<mbac> let show_table to_s xs = let to_s = match to_s with Some f -> f | None -> string_of_int in List.iter (fun x -> Printf.printf "%s\n" (to_s x)) xs
<mbac> has the same problem
<mbac> show_table None [1; 2; 3]; works but show_table string_of_float [1.; 2.; 3] gives the type error
<mbac> er, show_table (Some string_of_float) [1.; 2.; 3.]
<flux> well, it is the same as the optional argument, but implemented manually
<flux> you need to ask yourself "what is the type of this value?" when reading through the code
<flux> for example, what is the type of to_s?
<flux> is it 'a -> string or int -> string? well, any 'a -> string doesn't fit int -> string, but int -> string does. therefore, it is int -> string.
<mbac> right
<mbac> i don't understand how val show_table : ('a -> string) -> 'a list -> unit is all that different from val show_table : ('a -> string) option -> 'a list -> unit
<mbac> do you?
<flux> you can write the latter function by replacing to_s with let to_s = match to_s with Some f -> f | None -> assert false in ..
<flux> and those signatures indeed aren't all that different
<flux> the thing is that your version binds the type of xs
<mbac> well, should it?
<mbac> isn't it wrong to do that, in this case?
ulfdoz has joined #ocaml
<flux> not at all, but that loses the polymorphicity
myu2 has joined #ocaml
<mbac> yes. that's the wrong part. :)
mnabil has quit [Ping timeout: 240 seconds]
<mbac> let value x = ignore (match x with Some x -> x | None -> 0) ;;
<mbac> value (Some 0.) ;;
<mbac> expresses the same phenomena
<mbac> i guess binding an explicit type to any name inside of a function immediately collapses the possibility of parameterizing them
ulfdoz has quit [Ping timeout: 240 seconds]
ftrvxmtrx has quit [Ping timeout: 250 seconds]
eye-scuzzy has quit [Quit: leaving]
eye-scuzzy has joined #ocaml
joewilliams is now known as joewilliams_away
ftrvxmtrx has joined #ocaml
edwin has joined #ocaml
ygrek has joined #ocaml
myu2 has quit [Remote host closed the connection]
myu2 has joined #ocaml
ftrvxmtrx has quit [Ping timeout: 240 seconds]
eye-scuzzy has quit [Quit: leaving]
ftrvxmtrx has joined #ocaml
eye-scuzzy has joined #ocaml
Yoric has joined #ocaml
Yoric has quit [Quit: Yoric]
ttamttam has joined #ocaml
mnabil has joined #ocaml
ikaros has joined #ocaml
myu2 has quit [Remote host closed the connection]
Yoric has joined #ocaml
myu2 has joined #ocaml
kaustuv_ has left #ocaml []
cyanure has quit [Remote host closed the connection]
ikaros has quit [Quit: Leave the magic to Houdini]
_andre has joined #ocaml
avsm has joined #ocaml
myu2 has quit [Remote host closed the connection]
hyperboreean has joined #ocaml
avsm has quit [Quit: Leaving.]
mnabil has quit [Ping timeout: 255 seconds]
<kaustuv> Wow, never seen this style of printing types before:
<kaustuv> > Error: This expression has type t/1217 but an expression was expected of type 'a t/1040
Associat0r has quit [Quit: Associat0r]
<mfp> kaustuv: is that some 3.12.1 pre-release version?
mnabil has joined #ocaml
<adrien> kaustuv: I see that in the topevel when I redefine a type but not the functions using that type
<adrien> type t = { a : int };; let f t = t.a;; type t = { a : int };; let g (t : t) = f t
<adrien> something like that
<adrien> nope, works :P
<flux> you need to paste them one-by-one
<flux> everything after ;; is discarded
<adrien> ok, if you paste it all at once, it works, but if you use each "sentence" separately, you get "Error: This expression has type t/1046 but an expression was expected of type t/1041"
<flux> which I'm not sure if it's a bug or not :)
ygrek has quit [Remote host closed the connection]
<adrien> flux: oh, right, had probably never paste anything on one line, well, anything typed on irc on a single that worked on the first try ;-)
ygrek has joined #ocaml
cyanure has joined #ocaml
mnabil has quit [Ping timeout: 240 seconds]
alexyk has joined #ocaml
alexyk has quit [Read error: Connection reset by peer]
<edwin> well thats still better than what I get with 3.11.2: "Error: This expression has type t but an expression was expected of type t"
mnabil has joined #ocaml
ikaros has joined #ocaml
<kaustuv> "t" is not a good name for practically any type. I hope that with signature substitution we will gradually start to see it disappear from non-library code
<thelema_> kaustuv: t is only good as Foo.t?
<mrvn> don't open modules with type t :)
edwin has quit [Read error: Connection reset by peer]
edwin has joined #ocaml
edwin has quit [Read error: Operation timed out]
<kaustuv> What would be truly awesome is if we could rename the abstract types in a module when importing it. Something like: open Set with 'a t := 'a set
<kaustuv> well, Set is a bad example. open Buffer with type t := buffer
<mrvn> open Buffer with type buffer = t rather
<kaustuv> I'm using the analogy with signature substitution. I want all the ts replaced with buffers
<mrvn> then signature substitutions are the wrong way around too.
<mrvn> :)
<kaustuv> Your opinion is objectively incorrect and you should feel bad for having it!
<kaustuv> :)
<mrvn> type new_name = old_name; let new_value = old_value :)
<flux> I happend to think t is a great type name :)
<flux> provided you have a single-type module
<flux> or rather, single-main-type module
<mrvn> nice and short.
<mrvn> I would hate to have to type Buffer.buffer
<flux> indeed
<kaustuv> I would rather see an error message saying "x has type buffer when I was expecting it to have type fluffer", rather than "x has type t/1024 when I was expecting it to have type t/2048"
ygrek has quit [Ping timeout: 240 seconds]
<flux> how about ..has type Buffer.t.. ?
<flux> because it does that, you know ;) - unless you open it, which I avoid
<kaustuv> Right, the type printer is easily confused by open. I think open is a Good Thing.
<flux> I've found open to be detrimental to reading code. it's more difficult to say where the symbols originate from.
<flux> I suppose it's more of a tooling issue though
<flux> I prefer project-wide or local module aliases
ccasin has joined #ocaml
<adrien> I often keep full "paths", I tend to do mostly "let sprintf = Printf.sprintf"
<flux> for example let's say one has examples of eliom code
<flux> with a bunch of opens in the end
<flux> learning where to actually find the definitions can be a bit of work
<flux> and then it also leads to prefixing record fields so that they are more open-compatible
<kaustuv> For things like Lwt or even List and Printf, keeping the path is OK, but try writing Bigarray.Array1 a dozen times.
<flux> for those I use aliases
Derander has quit [Ping timeout: 246 seconds]
<adrien> same here: module A (* or Array) = Bigarray.Array1
<flux> and preferably the same aliases for the whole project, ie. I have module Common.ml with a few includes etc
<adrien> well, I skipped half the syntax
edwin has joined #ocaml
sepp2k has joined #ocaml
<kaustuv> I should probably know this, but do module aliases interact well with the inliner?
<f[x]> "learning where to actually find the definitions can be a bit of work" <- compiler + editor does that for me
Derander has joined #ocaml
<flux> f[x], ocamlspot works great, but less great on a web page :)
<f[x]> -annot is enough
<flux> annot tells function origination these days?
<f[x]> web page with many many modules with long paths?
<flux> simply browsing said eliom examples on the web
<f[x]> -annot was doing that for ages iirc
<f[x]> ok, but I find it pointless to optimize code to be readable on the web :)
<flux> how about optimizing to be readable without relying on specific tools?-)
<kaustuv> OK, -dlambda shows that module projections are inlined, but the module aliases still persist in the generated structure
alexyk has joined #ocaml
<f[x]> maybe
<kaustuv> Also, there is a difference between reading finished code and debugging code in flux. When I'm simply exploring an idea, I have a very low tolerance for module bureaucracy. Sadly, this is the very code that the type checker often takes issue with.
<flux> well, for me, using single-letter module aliases is sufficient, and avoids all those issues
<flux> and it even lets me rename the alias later easily, if so so wish
<mrvn> B.t is still less to type than buffer. :)
<kaustuv> The point is I would write neither B.t nor buffer. The compiler can fill in types for me.
<mrvn> unless you need to specify a signature somewhere
<mrvn> or a type t = Buffer.t :)
<alexyk> ok, a repeat from yesterday. Why does a default value bind a parameter to a specific type? https://gist.github.com/808895
<mrvn> because it is syntactic suggar for let printShowTable tex verbose = let verbose = match verbose with None -> false | _ -> verbose in ....
<mrvn> because it is syntactic suggar for let printShowTable tex verbose = let verbose = match verbose with None -> false | Some v -> v in ....
<alexyk> those are OK. I'm talking about printOne
<mrvn> same thing.
<flux> alexyk, it doesn't need to, btw: let foo ?(a=fun x->x) x = a x
<alexyk> when I drop the default, I can pass in floatPrint
<flux> but that's now what you want :)
<flux> noT
<kaustuv> alexyk: what type would you expect "printShowTable2 tex ~verbose floatTable name" to have?
<mrvn> flux: that still sets the type to that of "fun x -> x". That is just polymorphic.
<alexyk> if I specify default Int.print, I can only pass in ...-> int -> unit
<alexyk> kaustuv: that won't typecheck
<alexyk> against Int.print
<kaustuv> alexyk: why not?
<kaustuv> (note, typechecking happens by instantiating type variables, not by looking up function definitions)
<alexyk> kaustuv: because it will invole printTable which will use Int.print to print every element of floatTable
<mrvn> Because the "None -> Int.print" clause determines the type.
<alexyk> aha
<alexyk> so default parameters screw up polymorphism
<alexyk> this is a deficiency
<kaustuv> No, they don't
<kaustuv> You are misunderstanding what polymorphism is
<mrvn> alexyk: no. They just are syntactic suggar and you have to look at the code they represent.
<alexyk> we disagree about the sugar
<alexyk> I consider a default as a mere convenience
<alexyk> it must not affect the typing
<mrvn> think of it as a makro that is expanded before the compiler infers types.
<alexyk> Int.print satisfies the general requirement of a more general type of printOne I explicitly specify
<kaustuv> A default must *always* be an acceptable parameter, and therefore must determine the type.
<kaustuv> Hence, why Int.print is not an acceptable parameter for floatTable
<alexyk> kaustuv: default will then always restrict the type
<mrvn> alexyk: yes
<alexyk> hmm
<alexyk> kaustuv: I see your point, but it's jumping the shark -- I'd rather it to consider the default last and not use it in inference at least when I *give* the type above
<mrvn> alexyk: The problem is that the type would differ depending on wether you pass the extra arg or not.
<mrvn> alexyk: or worse, the optional arg could be come not optional due to the first arg you apply.
mnabil has quit [Ping timeout: 240 seconds]
<kaustuv> alexyk: The point is that the typechecker *does not know* how the function is defined. Imagine if it came from some code for which you don't have the source. What type signature would you give to your more relaxed notion of default arguments?
<flux> alexyk, internally I believe code like let foo ?(a=string_of_int) b = b a is expanded into something in effect let foo a b = let a'val = match a with None -> string_of_int | Some a in b a
<flux> alexyk, can you tell what the type of the signature of the latter function should be?
<alexyk> flux: which latter?
<flux> let foo a b = let a'val = match a with None -> string_of_int | Some a in b a'val
<flux> argh
<mrvn> foo: int -> string | ('a -> string) -> 'a -> string :))
<flux> let foo a b = let v = match a with None -> string_of_int | Some a -> a in b v
<mrvn> flux: if you look at the asm that produces that is exactly what the compiler makes of optional args
<alexyk> flux: value foo : option (int -> string) -> ((int -> string) -> 'a) -> 'a
<alexyk> :)
<alexyk> (in Batteries)
<flux> alexyk, but you would want it to be.. ?
<thelema_> alexyk: try duplicating the body of your function, one for each path
<alexyk> ok I see. So the default is much more than a default. It's used in expansion and typecheck. I'd prefer the explicit type I give to dominate and make the default secondary convenience, to be substituted into a defined type if given...
<thelema_> and I think it's time to get rid of the camlp4 bug by releasing batteries 1.3... in about 8 hours, after work
<mrvn> It's time to get a hair cut.
<mrvn> now.
<alexyk> mrvn: programmers don't do haircuts!
<alexyk> thelema_: I like Battieries types! They are postfix and read well :)
<kaustuv> alexyk: the "explicit type" you give is not polymorphic enough. You need to explicitly mark the polymorphic variables (not doable in OCaml < 3.12).
<alexyk> kaustuv: I am in 3.12! How'd I be explicit enough?
<kaustuv> let printShowTable2: 'a 'b 'c. tex -> ?verbose:bool -> ~printOne:('a BatInnerIO.output -> 'b -> unit) -> 'c list list -> string -> unit =
<kaustuv> (and it won't typecheck then)
<alexyk> aha
<kaustuv> btw, you shouldn't use ~foo:t in type signatures as that is deprecated. Just say foo:t
<kaustuv> (IIRC)
lamawithonel_ has joined #ocaml
<alexyk> kaustuv: trying to compile in 3.12 gives error: let printShowTable2: 'a 'b 'c. tex -> ?verbose:bool -> Error: Parse error: [ctyp] expected after "->" (in [ctyp]), the last -> -- why?
alexyk has quit [Quit: alexyk]
alexyk has joined #ocaml
<alexyk> kaustuv: I oscillated, now am back :)
avsm has joined #ocaml
<kaustuv> alexyk: that sounds like a camlp4 error. The syntax I wrote was native ocaml.
<kaustuv> This works for me: let f : 'a 'b. 'a -> 'b = fun 1 -> failwith "undefinable" ;;
<kaustuv> (where "worrks" means type error, not syntax error)
<alexyk> yep
<kaustuv> Ah, the ~foo:t form is required in revised syntax. Are you using revised syntax perchance?
<kaustuv> You must be since your option type was prefix instead of postfix
<alexyk> kaustuv: I am in Batteries, nothing else
<alexyk> Batteries prints types in postfix
<alexyk> but takes them in prefix
<alexyk> until thelema fixes it tonight :)
<kaustuv> No, postfix is OCaml's default. Prefix is only in revised syntax, I believe, which means you must be using a syntax extension.
<kaustuv> thelema_: before releasing 1.3, can you merge my change to BatHeap that switches insert and add so that add has the same semantics as in Set, Map, etc.?
gmarik has joined #ocaml
alexyk has quit [Quit: alexyk]
<thelema_> kaustuv: no problem
alexyk has joined #ocaml
edwin has quit [Ping timeout: 246 seconds]
gl has quit [Read error: Connection reset by peer]
alexyk has quit [Client Quit]
edwin has joined #ocaml
lamawithonel_ has quit [Ping timeout: 255 seconds]
ymasory has joined #ocaml
joewilliams_away is now known as joewilliams
boscop has joined #ocaml
alexyk has joined #ocaml
mnabil has joined #ocaml
lamawithonel_ has joined #ocaml
jlenormand has joined #ocaml
<jlenormand> I have an omake question
<jlenormand> how do I get omake to print out every command that it runs?
<kaustuv> --no-S ?
<hcarty> alexyk: Batteries should have that toplevel printing error fixed in git
alexyk has quit [Quit: alexyk]
ikaros has quit [Quit: Leave the magic to Houdini]
<jlenormand> isn't --no-S the default?
<jlenormand> -s "Never not [sic] print commands as they are executed"
myu2 has joined #ocaml
jm has joined #ocaml
jm has left #ocaml []
ikaros has joined #ocaml
kaustuv_ has joined #ocaml
<kaustuv_> jlenormand: My omake --help says that -S is the default...
kaustuv has quit [Disconnected by services]
kaustuv_ is now known as kaustuv
ttamttam has quit [Remote host closed the connection]
alexyk has joined #ocaml
alexyk has quit [Read error: Connection reset by peer]
lamawithonel_ has quit [Ping timeout: 255 seconds]
ftrvxmtrx_ has joined #ocaml
ftrvxmtrx has quit [Disconnected by services]
alexyk has joined #ocaml
ftrvxmtrx_ is now known as ftrvxmtrx
ymasory has quit [Read error: Operation timed out]
ymasory has joined #ocaml
alexyk has quit [Read error: Connection reset by peer]
Yoric has quit [Quit: Yoric]
alexyk has joined #ocaml
oriba has joined #ocaml
ymasory has quit [Ping timeout: 276 seconds]
ftrvxmtrx has quit [Read error: Connection reset by peer]
alexyk has quit [Read error: Connection reset by peer]
ftrvxmtrx has joined #ocaml
smerz has joined #ocaml
ymasory has joined #ocaml
alexyk has joined #ocaml
ygrek has joined #ocaml
ulfdoz has joined #ocaml
alexyk has quit [Read error: Connection reset by peer]
alexyk has joined #ocaml
alexyk has quit [Quit: alexyk]
boscop_ has joined #ocaml
boscop has quit [Ping timeout: 240 seconds]
boscop_ is now known as boscop
oriba has quit [Quit: Verlassend]
alexyk has joined #ocaml
alexyk has quit [Read error: Connection reset by peer]
alexyk has joined #ocaml
alexyk has quit [Read error: Connection reset by peer]
<_habnabit> Is there a function application operator like haskell's $ ?
<_habnabit> Basically 'stop interpreting things as arguments and apply this function'
alexyk has joined #ocaml
Associat0r has joined #ocaml
<hcarty> _habnabit: Nothing pre-defined
Yoric has joined #ocaml
<thelema_> _habnabit: let (<|) f x = f x
<thelema_> it doesn't have the right associativity, but it works often enough
<hcarty> Some code uses ( & ) for that
<hcarty> But that stops working with JoCaml
_andre has quit [Quit: leaving]
alexyk has quit [Read error: Connection reset by peer]
avsm has quit [Read error: Connection reset by peer]
alexyk has joined #ocaml
DimitryKakadu has joined #ocaml
alexyk has quit [Read error: Connection reset by peer]
avsm has joined #ocaml
lamawithonel_ has joined #ocaml
Pepe_ has quit [Remote host closed the connection]
lamawithonel_ has quit [Read error: Connection reset by peer]
lamawithonel has joined #ocaml
Snark has quit [Quit: Ex-Chat]
lamawithonel has quit [Read error: Connection reset by peer]
lamawithonel has joined #ocaml
ftrvxmtrx_ has joined #ocaml
ftrvxmtrx has quit [Ping timeout: 255 seconds]
ymasory has quit [Remote host closed the connection]
ftrvxmtrx has joined #ocaml
ftrvxmtrx_ has quit [Quit: Leaving]
Casaubon has joined #ocaml
edwin has quit [Remote host closed the connection]
Casaubon has left #ocaml []
ftrvxmtrx has quit [Read error: Connection reset by peer]
ftrvxmtrx has joined #ocaml
seafood has joined #ocaml
ccasin has quit [Quit: Leaving]
ftrvxmtrx has quit [Client Quit]
alexyk has joined #ocaml
Pepe_ has joined #ocaml
arubin has joined #ocaml
ulfdoz has quit [Read error: Operation timed out]
elehack has joined #ocaml
<kaustuv> thelema_: the pre-aaa era TODO file still in the root of the batteries source tree is kind of misleading. As github has become the semi official issue tracker, maybe it ought to be removed?
<thelema_> kaustuv: agreed
<thelema_> pushed
ymasory has joined #ocaml
<elehack> anyone know what OCaml machinery leads to a process terminating with status code 127 w/o any output?
<thelema_> elehack: that's an impressive error. Never got that one.
<elehack> I've wrapped the main code in a try...with that exits with code 5, so it doesn't seem to be an exception thing...
<elehack> and if it were a segfault, then the parent should see a signal, not an exit status...
<thelema_> huh, unix.ml has some exit 127's
<elehack> ahh.
<elehack> perhaps it isn't in my subprocess then...
<elehack> (the parent is doing fork-exec)
<thelema_> seems to be the exit code of a failed create process
<elehack> interesting.
<elehack> thanks for digging that up.
<thelema_> yup, lots of "exit 127" in error handlers around forks and execvs
<elehack> I wish I knew *why* it was failing...
<ygrek> man bash?
<thelema_> you could hack your unix to backtrace instead of exit 127
<elehack> I could... wouldn't be the first time I've patched OCaml.
<ygrek> Sys.command "qqq" will have return code 127
<thelema_> path problems?
<elehack> possibly.
<elehack> however, it successfully runs the program the first few hundred times.
<thelema_> lol
<elehack> and then fails without warning or explanation.
<thelema_> ulimit -a
<elehack> no particularly onerous looking limits.
<elehack> 71K processes
<elehack> 1024 file descriptors, but I believe that's per-process, not per-process-tree.
<elehack> unless I'm leaving a file descriptor open somehow.
seafood has quit [Quit: seafood]
ygrek has quit [Ping timeout: 240 seconds]
<elehack> ahh, here's the problem.
<elehack> I think.
<elehack> BatUnix.in_channel_of_descr sets autoclose to false.
<elehack> so I'm leaking a file descriptor every fork.
<elehack> not sure why it shows up in the child process and not the parent, but that's probably the problem.
ftrvxmtrx has joined #ocaml
<kaustuv> create_process calls pipe(2)
Yoric has quit [Quit: Yoric]
<elehack> that'd do it.
<elehack> I wonder why this machinery fails rather than raising Unix_error?
<thelema_> maybe *very* old code
Casaubon has joined #ocaml
<kaustuv> well, the exec() calls are in the child process, and there is no alternative but to exit if that call fails
<elehack> why can't the child die with an exception?
ftrvxmtrx has quit [Quit: Leaving]
<kaustuv> It does exactly that. The exception just isn't propagated to the parent because there is no facility for that
ftrvxmtrx has joined #ocaml
<elehack> yes, but I would expect the runtime in the child process to print the standard "unhandled exception" message before exiting
<elehack> I suppose that would somewhat break the abstraction of create_process by allowing parent exception handlers to run in a child process on failed exec.
ftrvxmtrx has quit [Read error: Connection reset by peer]
agarwal1975 has joined #ocaml
<elehack> Now that I'm (hopefully) no longer leaking file descriptors, maybe it will finish now.
<elehack> thanks for helping track this down.
<thelema_> shallow many eyes
<elehack> thelema_: is there a particular reason BatUnix.in_channel_of_descr sets autoclose to false? near as I can tell tracing the C sources for stdlib's unix, the standard version does auto-close the FD.
<kaustuv> elehack: the child doesn't print a message because its stderr might not be the same as the parent's stderr, so there is no guarantee that the message ever gets seen
<elehack> out_channel_of_descr leaves autoclose alone
<elehack> kaustuv: true.
<thelema_> elehack: no reason I know of.
<elehack> thelema_: OK, then I'll push a patch to fix that sometime here.
<thelema_> elehack: wouldn't hurt to git blame that code to see its history, just in case
<thelema_> the patch is welcome anyway
<agarwal1975> Hi. Just posted to the batteries-devel list, but I'll ask here too. Getting a build error with batteries-included
<agarwal1975> Makefile determines camomile version by running ocamlfind list | grep camomile | grep -o "[0-9\.]*"
groovy2shoes has joined #ocaml
<thelema_> agarwal1975: can you update - I changed that code just recently
<kaustuv> agarwal1975: the devel version of batteries requires camomile 0.8+
<kaustuv> Or am I wrong?
<thelema_> kaustuv: I don't think so - it autodetects all the way back to 0.7
<thelema_> something is wierd with his grep, but f[x] pointed out a way to call ocamlfind to get the version directly instead of hacking it out of the response
<agarwal1975> well, godi-camomile is only up to 0.7.1. Guess i can install camomile manually too.
<thelema_> fixed in commit 9c03c47f
<thelema_> 29 hours ago
<agarwal1975> However, is that the issue. Makefile does ocamlfind list | grep camomile | grep -o "[0-9\.]*", which in fact returns the empty string.
<thelema_> well, the new code will run 'ocamlfind query -format %v camomile' which should return the version directly
<thelema_> agarwal1975: what os are you running?
<agarwal1975> Mac OS X.
<thelema_> apparently grep -o does something different there.
<thelema_> can you update to latest git?
<kaustuv> I am pretty sure \ is not needed inside [] in posix regexp
ftrvxmtrx has joined #ocaml
<agarwal1975> I tried it on a redhat also. Same behavior.
<thelema_> ok, I guess I have a particularly friendly grep under ubuntu
<agarwal1975> Also, why does it work when installing via godi? Isn't the godi package using the same Makefile.
<kaustuv> On a linux, I think grep needs -E in addition to -o.
<thelema_> the godi package is quite old, and doesn't have any auto-detection
<kaustuv> (Anyway, the issue is fixed by tossing grep out)
<thelema_> yes, I'm happy to toss grep out
<agarwal1975> kaustuv: which commit is that in. I just pulled from master and grep is still there.
<elehack> agarwal1975: if you want a newer Batteries on GODI, set the GODI_BATTERIES_VCS_CHECKOUT option to yes
<kaustuv> agarwal1975: <thelema_> fixed in commit 9c03c47f
<thelema_> agarwal1975: where are you pulling from?
<kaustuv> agarwal1975: apparently in branch release-1.3, not master
<thelema_> oops
<thelema_> well, it'll get merged back into master soon enough
<thelema_> can anyone verify that ocaml removes [if false then ... ] from executable?
<agarwal1975> I'm not a git pro yet. Is it okay for me to just merge in commit 9c03c47f? Or should I be tracking the release-1.3 branch instead of master?
<thelema_> agarwal1975: git co release-1.3
<thelema_> but yes, it's okay for you to cherry pick that commit, and probably even merge release-1.3 into master
ftrvxmtrx has quit [Ping timeout: 246 seconds]
<agarwal1975> Do you know how to change the remote branch being tracked by a local branch?
<kaustuv> thelema_: ocamlopt -dcmm confirms that [if false then e] is removed
<agarwal1975> not critical, just wondering.
<thelema_> kaustuv: thanks, that's important for what I'm just doing
<thelema_> agarwal1975: edit your .git/config file
<agarwal1975> perfect. thanks!
<kaustuv> thelema_: note, the bytecode compiler doesn't go through the Cmm phase, so the bytecodes are not removed (checked with ocamlc -dinstr)
<elehack> thelema_: I found the offending commit (it's from Feb. 2009, with some added stuff for cleaning up inherited IO channels), but don't see a particular reason for changing the autoclose setting.
oriba has joined #ocaml
<elehack> should the fix go on the release-1.3 or master branch?
<thelema_> elehack: put it in 1.3, if someone complains, we'll fix it in 2.0. I don't see much harm in autoclosing extra
<thelema_> kaustuv: got it. Luckily I'm not doing my time critical code in bytecode
<kaustuv> Why on earth is the autoclose knob exposed? When does it make sense to keep an input or output open when its underlying channel is closed?
<elehack> kaustuv: the issue is when you wrap a file descriptor in a channel. when you close the channel, does it close the underlying file descriptor?
<kaustuv> depends on what owns the fd, but if multiple higher abstractions are sharing an fd then the code is doing something bizarre
ymasory has quit [Remote host closed the connection]
<elehack> I agree. Not sure what the use case for non-autoclosing channels is (thus the default is autoclosing).
ftrvxmtrx has joined #ocaml
<kaustuv> also, unless I am reading the docs wrong, the meaning of ~autoclose is that if the underlying thing closes then close self, not if close self then close underlying thing. (The latter seems to be the ~cleanup parameter)
<elehack> patch pushed to release-1.3.
<elehack> kaustuv: hrm, interesting.
<elehack> I might have just patched the wrong thing then.
<elehack> in which case I still have a bug on my hands.
<kaustuv> do double check my interpretation with what the actual code does
* elehack should read better.
<elehack> I can try to, but the IO logic is a maze of twisty passages all alike sometimes.
<agarwal1975> now compiling release-1.3 but get: + ocamlfind ocamlopt -shared -linkall -package camomile,num,str -o src/batteries_uni.cmxs src/batteries_uni.cmxa
<agarwal1975> ld: warning: -read_only_relocs cannot be used with x86_64
<agarwal1975> ld: codegen problem, can't use rel32 to external symbol _caml_negf_mask in .L101 from src/batteries_uni.a(batFloat.o)
DimitryKakadu has quit [Remote host closed the connection]
<thelema_> agarwal1975: really? that's an interesting one.
<agarwal1975> is it maybe because I installed camomile thru godi?
<thelema_> unlikely
<elehack> agarwal1975: it's a known Mac issue.
<elehack> turn off native shared libraries (there's a Make flag, and a GODI option as well)
ikaros has quit [Quit: Leave the magic to Houdini]
<agarwal1975> that did it!
<agarwal1975> I've never had to set this flag via godi.
<elehack> kaustuv: looks like your interpretation is correct, and my patch is incorrect.
<elehack> which means I still have a bug.
Casaubon has quit [Remote host closed the connection]
<kaustuv> release notes for 3.11.2 state (in fixed bugs section)
<kaustuv> > - PR#4867, PR#4760: ocamlopt -shared fails on Mac OS X 64bit
<kaustuv> Do you have an OCaml older than that?
<agarwal1975> that could be it. I had started using ocaml 3.12, but reverted to 3.11 just for batteries devel.
* elehack has now pushed a reversion to the previous autoclose change
<thelema_> agarwal1975: batteries works with 3.12
<agarwal1975> is that recommended? I'm assuming I should test my batteries contributions against 3.11 since we're not yet officially supporting 3.12.
<thelema_> test against 3.12. Just because I'm still using 3.11 (for some unknown reason) doesn't mean 3.12 isn't fully supported
<agarwal1975> ok, but is it legitimate to use new 3.12 features?
<thelema_> no
<thelema_> not for a while - there's still a lot of people out there with 3.11.
<kaustuv> is there a sunset clause for <= 3.11 support?
<kaustuv> Like say circa 2015?
<thelema_> if the next stable ubuntu includes 3.12, we can drop 3.11 support
<thelema_> err, not stable, LTE
<adrien> LTS* ;-)
<thelema_> LTS? hwatever the long term support thins
<thelema_> :)
<elehack> I expect it will - it isn't due for another year.
<elehack> RHEL6, on the other hand...
* elehack is not proposing that we maintain 3.11 compatibility for the lifetime of RHEL6.
alexyk has quit [Quit: alexyk]
<kaustuv> Maybe with 2.0 you can be justified in breaking backwards compatibility with both earlier versions of batteries and earlier versions of ocaml
<elehack> that's what I'm thinking.
<elehack> esp. if first-class modules let us clean up some APIs (which I think they will)
<thelema_> that would be a good time to do it. Although I don't want to artificially couple backwards-incompatible changes with ocaml version expiration
<thelema_> I hope those two go together, but I don't plan on making 2.0 come early or late just so the two co-incide
<elehack> thelema_: agreed, it shouldn't set schedule. we can always release another bug-fix release or two of the 1.x series for people who can't upgrade OCaml, even after 2.0 is released.
<thelema_> that's a good solution
<elehack> in fact, it may be worthwhile to see if we can time things to have 2.0 ready before the next LTS freeze.
<elehack> but that probably shouldn't be a very hard deadline - better to have an awesome 2.0 than a 2.0 in Ubuntu 12.04.
<elehack> And it's time to go home... tomorrow will tell whether adding autoclose will fix my bug or not.
elehack has quit [Quit: bus-hunting]
groovy2shoes has quit [Quit: groovy2shoes]
gmarik has quit [Quit: Leaving.]
agarwal1975_ has joined #ocaml
agarwal1975 has quit [Read error: Connection reset by peer]
agarwal1975_ is now known as agarwal1975
<hcarty> Does OCaml ever treat 0.0 as distinct from (-0.0)?
<hcarty> Aside from classify_float
lamawithonel has quit [Ping timeout: 255 seconds]
boscop has quit [Ping timeout: 240 seconds]
<kaustuv> hcarty: Marshal.to_string 0.0 [] = Marshal.to_string (-0.0) [] ==> false
lamawithonel has joined #ocaml
<kaustuv> Heck, string_of_float 0.0 <> string_of_float (-0.0)
<kaustuv> is there an implementation of IEEE 754 decimal floating points in ocaml?
alexyk has joined #ocaml
arubin has quit []
<hcarty> kaustuv: Ah, fair point. Thanks.
<hcarty> It was my understanding that the native code floating point handling in OCaml follows IEEE 754
<hcarty> But not in bytecode
kaustuv has quit [Remote host closed the connection]
ftrvxmtrx has quit [Ping timeout: 272 seconds]