rwmjones changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | Grab Ocaml 3.10.1 from http://caml.inria.fr/ocaml/release.html (featuring new camlp4 and more!)
jlouis has joined #ocaml
jlouis_ has quit [Read error: 110 (Connection timed out)]
l_a_m has quit [Remote closed the connection]
seafood_ has joined #ocaml
mwc has joined #ocaml
ben___ has joined #ocaml
jlouis_ has joined #ocaml
netx has quit ["Leaving"]
netx has joined #ocaml
jlouis has quit [Read error: 110 (Connection timed out)]
netx has quit [Remote closed the connection]
ben___ is now known as ziph
thermoplyae has quit ["daddy's in space"]
coucou747 has quit ["bye ca veut dire tchao en anglais"]
thermoplyae has joined #ocaml
Snrrrub has joined #ocaml
monde has quit ["Leaving."]
<Snrrrub> What's the right way to package a library that calls C code? I have something like: ocamlc -a -o mylib.cma -custom myobject.cmo mystubs.o and then when I try to link other sources to the library, the compiler complains that it can't find the .o file (even if I specify -I).
<Smerdyakov> -I never has anything to do with linking, I think.
<Snrrrub> Smerdyakov, I thought it specifies the directories to search for .cma files (and, presumably, other files that archives refer to)?
<Smerdyakov> Nope. It's for searching for .cmi files.
<Snrrrub> I see. So how do I specify the directories to search for archives and objects?
<Smerdyakov> Maybe -L. That's the gcc convention.
<Smerdyakov> But, really, read the manual.
<Snrrrub> I did... :-/
<Snrrrub> And, sadly, it's not -L. Hm.
jlouis has joined #ocaml
AxleLonghorn has joined #ocaml
AxleLonghor1 has joined #ocaml
<Smerdyakov> I'm guessing you want "-ccopt" for linking directives.
<Smerdyakov> Maybe "-ccopt myfile.o".
jlouis_ has quit [Read error: 110 (Connection timed out)]
<julm> Snrrrub: here is an example of what I do:
<julm> gcc -c my_c.c
<julm> ar rc libmy.a my_c.o
<julm> ocamlc -c my.ml
<julm> ocamlc -a -o my.cma -custom -cclib -lmy my.cmo
<Snrrrub> julm, ah, and then the -L option via -cclib will work since it's an archive and not an object file (.a not .o)
AxleLonghorn has quit [Read error: 110 (Connection timed out)]
<julm> hum, according to man ocamlc, you should give -L via -ccopt
<Snrrrub> julm, noted. Thanks!
<julm> also if your library goes into `ocamlc -where`/my, then it is useless to pass -L`ocamlc -where`/my, because the -I +my will do it automatically IIRC
Optikal__ has quit []
<julm> btw, take care not to have a my.c and a my.ml, because they both lead to the same object: my.o, so when you use ocamlopt, one will overwrite the other...
<julm> or be sure, you actually pack the my.o from my.c into libmy.a before you run ocamlopt -c my.ml
<Snrrrub> julm, yeah, I found that out the hard way. :-)
<julm> xD
seafood_ has quit []
mrsolo has joined #ocaml
mrsolo has quit [Client Quit]
mrsolo has joined #ocaml
Snrrrub has quit [Read error: 104 (Connection reset by peer)]
thelema has quit [Read error: 104 (Connection reset by peer)]
zarvok has joined #ocaml
|Catch22| has joined #ocaml
jlouis_ has joined #ocaml
AxleLonghorn has joined #ocaml
goalieca has joined #ocaml
postalchris has joined #ocaml
jlouis has quit [Read error: 110 (Connection timed out)]
mwc has quit ["Leaving"]
AxleLonghor1 has quit [Read error: 110 (Connection timed out)]
evn has quit []
mrsolo has quit ["This computer has gone to sleep"]
evn has joined #ocaml
mrsolo has joined #ocaml
netx has joined #ocaml
|Catch22| has quit []
postalchris has quit [Read error: 110 (Connection timed out)]
mrsolo has quit ["This computer has gone to sleep"]
thermoplyae has quit ["daddy's in space"]
ry4n_ has joined #ocaml
ry4n__ has joined #ocaml
_shawcable_sucks has joined #ocaml
mrsolo has joined #ocaml
goalieca has quit [Connection timed out]
goalieca has joined #ocaml
ry4n_ has quit [Read error: 110 (Connection timed out)]
ry4n__ has quit [Connection timed out]
_shawcable_sucks has quit [Read error: 110 (Connection timed out)]
mrsolo has quit ["This computer has gone to sleep"]
jderque has joined #ocaml
zarvok has quit ["BitchX-1.1-final -- just do it."]
AxleLonghorn has left #ocaml []
mrsolo has joined #ocaml
seafood_ has joined #ocaml
thelema has joined #ocaml
mrsolo has quit ["This computer has gone to sleep"]
jlouis has joined #ocaml
mrsolo has joined #ocaml
Robdor has joined #ocaml
jlouis_ has quit [Read error: 110 (Connection timed out)]
mrsolo has quit ["This computer has gone to sleep"]
seafood_ has quit []
l_a_m has joined #ocaml
Robdor has quit [Remote closed the connection]
ry4n_ has joined #ocaml
mrsolo has joined #ocaml
jlouis_ has joined #ocaml
jderque has quit [Read error: 113 (No route to host)]
seafood_ has joined #ocaml
ry4n__ has joined #ocaml
jlouis has quit [Read error: 110 (Connection timed out)]
mrsolo has quit ["This computer has gone to sleep"]
goalieca has quit [Read error: 110 (Connection timed out)]
ry4n_ has quit [Read error: 110 (Connection timed out)]
ry4n__ has quit [Read error: 110 (Connection timed out)]
jlouis has joined #ocaml
LordMetroid has joined #ocaml
jlouis_ has quit [Read error: 110 (Connection timed out)]
antares has joined #ocaml
mrsolo has joined #ocaml
brooksbp has joined #ocaml
Linktim has joined #ocaml
brooksbp has quit []
filp has joined #ocaml
Yoric[DT] has joined #ocaml
<Yoric[DT]> hi
<ziph> hiya
lordmetroid_ has joined #ocaml
LordMetroid has quit [Nick collision from services.]
lordmetroid_ is now known as LordMetroid
LordMetroid has quit ["Leaving"]
velco has joined #ocaml
filp has quit [Remote closed the connection]
velco has quit [Client Quit]
filp has joined #ocaml
hkBst has joined #ocaml
coucou747 has joined #ocaml
<coucou747> salut all
<Yoric[DT]> hi
vpalle has joined #ocaml
pango has quit [Remote closed the connection]
pango has joined #ocaml
ziph has quit []
<ikatz> is anyone on who knows ocamlyacc?
<ikatz> i'm trying to construct lists from the input
<ikatz> myPredicate(x1, x2, x3) should be parsed into ("myPredicate", ["x1"; "x2"; "x3"])
<ikatz> but all i get is either a parse error or an infinite loop
postalchris has joined #ocaml
seafood_ has quit []
seafood_ has joined #ocaml
seafood_ has quit [Client Quit]
seafood_ has joined #ocaml
linktim_ has joined #ocaml
<julm> see expr_comma_list for instance
Linktim has quit [Read error: 110 (Connection timed out)]
<ikatz> julm: that's interesting... do you know much about the "terminal case" for parsing a list?
<ikatz> i am doing | term COMMA termlist { $1 :: $3 } | term { $1 :: [] }
<julm> in parser.mly the terminal is: | expr COMMA expr { [$3; $1] }
<ikatz> what if you only get one expr?
<julm> well then, maybe look at expr_semi_list
<julm> expr_semi_list:
<julm> expr { [$1] }
<julm> | expr_semi_list SEMI expr { $3 :: $1 }
<ikatz> hmm, that looks like what i have
<julm> and it does not work?
<ikatz> well... its definitely not working
<julm> maybe the order of the matches matters
<ikatz> but maybe the parser isn't to blame here
<ikatz> lexer?
<ikatz> this thing is supposed to parse first-order logic predicates
<ikatz> "Loves(F3(x3), x3)"
<ikatz> that should turn into:
<ikatz> Predicate ("Loves", [Function ("F3", ["x3"]); "x3"])
<ikatz> State 0: shift to state 1
<ikatz> State 1: read token CAPITALIZED_NAME(Loves)
<ikatz> State 1: shift to state 3
<ikatz> State 3: read token LPAREN
<ikatz> State 3: shift to state 11
<ikatz> State 11: read token CAPITALIZED_NAME(F3)
<ikatz> State 11: shift to state 17
<ikatz> State 17: read token LPAREN
<ikatz> State 17: shift to state 24
<ikatz> State 24: read token LOWERCASE_NAME(x3)
<ikatz> State 24: shift to state 18
<ikatz> State 18: reduce by rule 15
<ikatz> State 21: read token RPAREN
<ikatz> State 21: reduce by rule 11
<ikatz> State 27: shift to state 29
<ikatz> State 29: reduce by rule 13
<ikatz> Fatal error: exception Failure("Mistake in input, line 1")
<ikatz> so it's failing to notice the comma
<ikatz> hold that thought
* ikatz is dumb
<ikatz> maybe i should add the rule for the comma into the lexer :)
<ikatz> works now
<julm> nice :)
thelema has quit [Read error: 110 (Connection timed out)]
bongy has joined #ocaml
crathman has joined #ocaml
<Yoric[DT]> mmmhhh....
* Yoric[DT] is having some difficulties to get his head around Pierce's encoding of existential types.
ita has joined #ocaml
* Yoric[DT] now manages to get information of any type inside an exception.
* Yoric[DT] now has difficulties grabbing that information back from the exception...
crathman has quit ["ChatZilla 0.9.81 [Firefox 2.0.0.12/2008020121]"]
<Yoric[DT]> Does anyone around here have experience with existential types ?
<bla> Just guessing; are /emo/ existential subtypes?
<Yoric[DT]> emo ?
* Yoric[DT] doesn't understand bla.
<bla> Those are existential types.
<Yoric[DT]> ?
mwc has joined #ocaml
<Yoric[DT]> That's a rock band, is it ?
<bla> That's a kind of subculture,
<bla> od people connected with "Romance rock" or similar.
<bla> Very 'existential' way of living.
<bla> ;p
<mwc> hmmm
<mwc> an existential way of living
<Yoric[DT]> :)
<mwc> are you saying that existence and living are distinct and that only our prejudices conflate them?
<mwc> how very zen.
<Yoric[DT]> Well, I'm looking for a hand with OCaml-style existential types :)
<mwc> Yoric[DT], this came up on the mailing list. Ocaml doesn't have them
<Yoric[DT]> Well, it has at least two manners of encoding them.
<Yoric[DT]> Once with 'a.'a and one with objects -- although I've seen people arguing that it's the contrary and that objects are a way of encoding existential types.
<mwc> oh objects ;)
<mwc> Closures are degenerate objects, and objects encode closures
<bla> mwc, maybe polish meaning of existential doesn't fit well with this word.
<mwc> is there any isomorphism object's don't have? :)
<mwc> *are there
<Yoric[DT]> Well, hammers and nails :)
<mwc> actually, s/'//
<mwc> Yoric[DT], indeed.
<mwc> bla, existentialism is a philosophical doctrine (in English usage)
<Yoric[DT]> In French, too.
<mwc> so existential usually denotes something associated with that
<Yoric[DT]> Plus it's supposed to be a humanism, but I wouldn't go as far as pretending I understand anything about it.
<mwc> ie, to have an existential crisis.
<Yoric[DT]> My problem at the moment is that I'd like to be able to put some content inside an existential type (that's easy) and get it back (that's hard).
<Yoric[DT]> On one side, I have my existential type, which hides some type 'a.
<Yoric[DT]> On the other side, I have a phantom type which gives me that type 'a.
<bla> mwc, ;)
<mwc> Yoric[DT], I think you'd have to bundle it with an observer function, 'a -> foo
<Yoric[DT]> I'd like to write a projection from the hidden part to the visible one.
<Yoric[DT]> I can't do that.
<Yoric[DT]> I mean, I don't know "foo" when I write the existential type.
<Yoric[DT]> I only know it later.
<Yoric[DT]> (i.e. the existential type goes inside a library, the observer function is provided by the client)
<mwc> Hmmm
<mwc> what about something like: type 'b myrec = {stuff : 'a . 'a*'a ->'b}
<mwc> with parenthesis to fix my associativity gaff
<Yoric[DT]> I can't have universal types.
<Yoric[DT]> Only existential.
<mwc> could you fake it with a functor?
<mwc> type myrec = {stuff : 'a . 'a*('a -> foo) } where foo comes from a functor argument?
<Yoric[DT]> I'm trying to avoid that.
<mwc> I don't see how else you're going to get a user-provided type in there
<Yoric[DT]> I'll rephrase what's above, just in case.
<Yoric[DT]> I have
<Yoric[DT]> type my_wrapper = exists 'x.{content : 'x} -- or something such
<Yoric[DT]> I have
<Yoric[DT]> type 'y my_projector = exists 'x.{project : 'x ->'y}
<Yoric[DT]> Er... no
antares has quit ["Quitte"]
<Yoric[DT]> I have a phantom type telling me that my_wrapper actually contains information of type 'y.
<Yoric[DT]> And I want to write a function
<Yoric[DT]> my_wrapper -> 'y
<Yoric[DT]> Without resorting to Obj.magic.
<Yoric[DT]> I am willing to use objects, though, if necessary.
thelema has joined #ocaml
bongy has quit ["Leaving"]
delamarche has joined #ocaml
LordMetroid has joined #ocaml
<rwmjones> does anyone have an email address for Xavier Clerc (ocamljava blokey)?
<rwmjones> ok don't worry, found it
<Yoric[DT]> mmmhhh....
<Yoric[DT]> I have a class with a parametric type ['a].
<Yoric[DT]> Is there a way to specify in the type of a function that I only accept objects of that class ?
<Yoric[DT]> (without specifying 'a) ?
<Yoric[DT]> mmhhh...
<Yoric[DT]> Probably.
<Yoric[DT]> But I probably can't hide 'a without resorting to existential types.
<Yoric[DT]> Grrr...
pango has quit [Remote closed the connection]
filp has quit ["Bye"]
Morphous_ has joined #ocaml
<julm> Yoric[DT]: is that what you want:
<julm> module Hide
<julm> (Common: sig type t end) :
<julm> sig
<julm> type t
<julm> val mk : ('e -> Common.t) -> 'e -> t
<julm> val get : t -> Common.t
<julm> end =
<julm> struct
<julm> type t = unit -> Common.t
<julm> let mk c e : t = fun _ -> c e
<julm> let get t = t ()
pango has joined #ocaml
<julm> end
<julm> class ['a] c = object end
<julm> module C = Hide(struct type t = int c end)
<julm> let example (c: C.t) = C.get c
<thelema> julm: something seems wrong about mk's definition: mk c e : t = fun _ -> c e has three parameters, no?
<julm> nope, it's ok, it is a partial evaluation
<julm> I mean, it delays the call to [c e]
seafood_ has quit []
<julm> later [get] calls it
<julm> there is a way to do it with existential too
<julm> but in both cases
<thelema> ah, Common.t is a closure...
<thelema> better then to write fun () -> c e, no?
<julm> Common.t must be known
<julm> yep thelema
<julm> with existential:
<julm> module Hide
<julm> (Common: sig type t end) :
<julm> sig
<julm> type t
<julm> val mk : ('e -> Common.t) -> 'e -> t
<julm> val get : t -> Common.t
<julm> end =
<julm> struct
<julm> type 'e buc = {e : 'e; c : 'e -> Common.t}
<julm> type 'c bucket = {c_of_buc : 'e. 'e buc -> 'c}
<julm> type t = {c_of_bucket : 'c. 'c bucket -> 'c}
<julm> let mk c e = {c_of_bucket = fun buc -> buc.c_of_buc {e=e; c=c}}
seafood_ has joined #ocaml
<julm> let get t = t.c_of_bucket {c_of_buc = fun buc -> buc.c buc.e}
<julm> end
<julm> this was discussed on the caml-list a few weeks ago
* thelema missed tht discussion somehow...
<julm> 13rd of November
<thelema> I found it in my email archive, and vaguely recall it now. I'd say a few months ago instead of a few weeks ago, but it's there...
Morphous has quit [Read error: 113 (No route to host)]
<thelema> the conclusion there was 'just use objects, dammit'
seafood_ has quit []
delamarche has quit []
delamarche has joined #ocaml
delamarche has quit [Client Quit]
<julm> thelema: are you progressing with the stdlib?
* Yoric[DT] is reading julm's code.
* Yoric[DT] will try pasting it somewhere.
<Yoric[DT]> julm: what exactly is the point of class c in the above ?
revax has quit ["Leaving"]
<julm> well you said you had a class so I took class c for example
<Yoric[DT]> oh, ok
<Yoric[DT]> My original query was about existential types in the first place.
<Yoric[DT]> I was just trying to work around my problem by attempting to use Jacques Guarrigue trick http://objectmix.com/ml/175476-ocaml-downcasting.html .
<Yoric[DT]> (and failing)
Mr_Awesome has quit ["aunt jemima is the devil!"]
<julm> Yoric[DT]: you mean that: let l = [(new button :> _ widget); (new label :> _ widget)]
<Yoric[DT]> yep
<Yoric[DT]> I'm currently trying to get a really efficient manner of obtaining polymorphic exceptions, without resorting to Obj.magic.
<Yoric[DT]> I have an efficient implementation with Obj.magic, a much less efficient implementation with references and I'm attempting to find something better.
ita has quit ["Hasta luego!"]
<Yoric[DT]> With existential types, it's easy to put any content inside an exception.
<julm> could we see your code to understand better?
<Yoric[DT]> What is difficult is to get it back.
<Yoric[DT]> Sure, but it's not even a draft.
<julm> no prob
<julm> it will be a start
<Yoric[DT]> That's my work-in-progress.
jderque has joined #ocaml
<Yoric[DT]> Not the Obj.magic version or the references version, mind you.
<Yoric[DT]> ....
* Yoric[DT] should probably add a few functions to make things a tad more clear.
<thelema> julm: yes, I've got a lot more code to merge still.
<julm> Yoric[DT]: well the problem with the existential design is that you must (AFAIK) know what you'll put into the obfuscated type
<Yoric[DT]> I know.
<julm> so why not using exception PolyExn of exn
<Yoric[DT]> My problem is that the existential stuff must go in the library, while the type must be decided by the client.
<Yoric[DT]> I have thought about that.
<Yoric[DT]> We lose type safety if we do that.
<Yoric[DT]> Well, not type safety, but exhaustivity check.
<julm> ah and exhaustivity matters...
<Yoric[DT]> Indeed.
<julm> what is wrong for you with the two Hide modules I've written above?
<julm> I mean with respect to what you wanna do
<Yoric[DT]> Not enough inference.
<Yoric[DT]> I mean, it would work.
<Yoric[DT]> I'm just attempting to find something in which I could take advantage of polymorphic variants to get 100% free-form exception management.
<julm> thelema: great :)
<thelema> julm: if anyone would like to help, I'd like comments on: http://www.pastebin.ca/914132
<julm> ok
<julm> btw, I wonder if for instance #
<julm> let zero, one = 0, 1
<julm> #
<julm> allocates a tuple
<julm> or if ocaml is smart enough
<julm> to avoid it
<thelema> I hope it gets optimized out, but at worst it runs once on program start
<julm> yep
<julm> Yoric[DT]: what is the parser? I tried camlp4orf.cma, but it fails
<Yoric[DT]> camlp4rf
<Yoric[DT]> or camlp4r
<julm> ok thank you
<Yoric[DT]> Well, thank you for trying to help.
<julm> damn it they all fail
<julm> camlp4r.cma:
<julm> # type can_fail 'r 'e = 'r;;
<julm> Parse error: [semi] expected after [str_item] (in [phrase])
<julm> on the second 'r
<Yoric[DT]> ?
<Yoric[DT]> I'm going to translate it to original syntax and repost.
<julm> thank you
<julm> camlp4orf.cma:
<julm> # type can_fail 'r 'e = 'r;;
<julm> type ('a, 'b) can_fail = 'a
<julm> # value return (x:'r) : can_fail 'r 'e = x;;
<julm> Parse error: [str_item] or ";;" expected (in [top_phrase])
<julm> on the second :
<Yoric[DT]> I can only assume we're not using the same version of OCaml/camlp4 .
<julm> me: Camlp4 Parsing version 3.10.2+dev3 (2008-01-29)
<Yoric[DT]> I'm using 3.10.1
<Yoric[DT]> Mhhh... are you using Tuareg ?
<julm> nope, I'm under Vim
jstanley has joined #ocaml
<Yoric[DT]> Ok.
<Yoric[DT]> Well, anyway, it compiles.
<jstanley> what's the best way to throw away the result of a function to avoid "this expression should have type unit" warnings? e.g., List.map print_endline lst generates this in a compound statement.
<Yoric[DT]> ignore
<Yoric[DT]> it has type 'a -> unit
<julm> yep ignore, not let _ =
<jstanley> ah, thanks.
<jstanley> i was hoping there'd be something around like that, but couldn't find it.
<Yoric[DT]> np
<thelema> why use List.map? use List.iter for print_endline
<jstanley> thelema: yeah, even better, i was just using that as an example.
<julm> Yoric[DT]: what does bind do?
<Yoric[DT]> monadic binding
<thelema> julm: monadic dark voodoo
<Yoric[DT]> In practice, it's used only to propagate the phantom types.
kelaouchi has joined #ocaml
monde has joined #ocaml
ita has joined #ocaml
maayhem has joined #ocaml
<maayhem> hello
<Yoric[DT]> hi
<maayhem> I have a question about polymorphic type inference:
<maayhem> do you need more than first order unification to tell that this program is not well typed ?
<Yoric[DT]> I don't see why you would.
<maayhem> its simple
<maayhem> when calling check a and check b
<maayhem> you require that a and b are the same type, that is, the same type as the parm argument of check function.
<maayhem> which is not the case here.
<maayhem> e.g. 1 type variable for a, 1 type variable for b, 1 type variable for parm
<maayhem> with type(a) = type(parm) and type(b) = type(parm)
<Yoric[DT]> No, I mean why more than first order ?
* Yoric[DT] admits he never knows exactly where to place the limit between first order and second order: functions or functors ?
<maayhem> because you might need constraints other than just type_a = type_parm, more like type_a C {type_parm} and type_b C {type_parm}
<julm> Yoric[DT]: you know, this (Obj.magic ex) may harm, for instance this segfault:
<julm> let x =
<julm> match run (fun () -> throw `X) with
<julm> | Fail (`X s) -> print_string s
<julm> | _ -> print_endline "Ok"
<julm> Actually it's to avoid this Obj.magic that I've introduced Common.t
<julm> in the Hide modules.
<Yoric[DT]> maayhem: Shouldn't that be "type_a may be unified with type_parm" and "type_b may be unified with type_parm" ?
<Yoric[DT]> julm: it does ?
<julm> yep
<Yoric[DT]> Strange.
<julm> try it
<julm> nope
<maayhem> Yoric[DT], yes, which means type_a = type_parm and type_b = type_parm, if you are in first order.
<maayhem> but then that makes a constraint : type_a = type_b
<maayhem> which is untrue
<Yoric[DT]> julm: indeed, it does.
<Yoric[DT]> maayhem: ok, I placed the boundaries between first order and higher order at the wrong place.
<julm> AFAIK if you wanna retrieve a value from a packed type you must know the type of this value when you declare the existential type
<Yoric[DT]> julm: mmmhhh.... you're right.
<julm> I mean it must not be a 'a
<julm> hence Common.t
<Yoric[DT]> Is the problem 'a or is that subtyping ?
<jstanley> anyone have problems with the toplevel crashing on subsequent command line invocations of the same function? i'm getting some "hanging" behavior :(
<julm> I do not understand
<julm> what subtyping?
<jstanley> (a) paste buffer into toplevel (b) execute function (works) (c) paste buffer into toplevel again (d) execute function, get hang.
<julm> jstanley: does your function have side-effects?
<Yoric[DT]> mmmhhh.... still segfaults with a closed polymorphic variant.
<jstanley> julm: it does some text output
<julm> jstanley: a lot?
<jstanley> julm: via print_endline
<jstanley> julm: not *tons* but a fair amount.
<julm> could we see the code?
<jstanley> sure, give me a few moments.
<julm> [19:28:44] julm | what subtyping? <--- ok I see now
<julm> jstanley: did you wait a long time when it hung?
<Yoric[DT]> Well, anyway, the problem is indeed not subtyping.
<julm> maybe it's just the GC
<jstanley> julm: i don't have *that* much data around.
<julm> Yoric[DT]: yep
<julm> jstanley: ok
<jstanley> in any case, it only happens after i refresh the entire buffer
<Yoric[DT]> Probably related to the representation of 'a.'a .
<jstanley> julm: like when i redefine the same functions
<julm> jstanley: hum
<jstanley> julm: i can invoke the same function multiple times and get the same verbose output with no real problem
<maayhem> anyone has an idea regarding my question ?
<jstanley> julm: but my emacs development environment edits ocaml code and then sends the buffer contents to the toplevel.
<julm> Yoric[DT]: Probably related to the representation of 'a.'a . <-- well it is related to representation of poly.variants with and without data
<julm> Yoric[DT]: but it's just an example, I could create a segfault with something else
rwmjones has left #ocaml []
<Yoric[DT]> Fair enough.
<Yoric[DT]> Well, I have another implementation, which *is* typesafe but is slowed down a lot by the use of references.
<Yoric[DT]> I came to existentials as a way of finding a way to circumvent references.
<Yoric[DT]> s/circumvent/avoid/
<julm> Yoric[DT]: but existentials are inside a record, like a reference
<julm> jstanley: can you reproduce the hang without using emacs' machinery
<julm> just a fair ocamlc -o out file.ml && ./out
<jstanley> julm: not sure yet. http://pastebin.org/20768 has the code.
<julm> jstanley: or ocaml file.ml
<Yoric[DT]> julm: not that kind of slowdown :)
<Yoric[DT]> I'll pastebin the implementation.
<julm> Yoric[DT]: yep, thanks
<jstanley> julm: if I do: gen_c_header "blah" ffi_bindings from inside the toplevel, i'll get the output expected once.
evn has left #ocaml []
<jstanley> julm: i'll test the command line version now, but since it only happens after repasting into the toplevel i don't expect a hang there.
<julm> jstanley: I'll try to see what's happening, just a few minutes please
<jstanley> julm: no worries, thanks.
kryptt has joined #ocaml
<jstanley> julm: confirmed that the hang does not happen via ocaml file.ml
<julm> jstanley: ok I am able to reproduce the hang inside a custom top-level
<jstanley> julm: that's good that it's reproducible at least. any ideas why it might be happening?
<julm> I'll look forward, but now I must go diner
<jstanley> julm: okay, thanks.
<julm> see you in 20 min
thermoplyae has joined #ocaml
kelaouchi has quit [Read error: 110 (Connection timed out)]
kryptt has left #ocaml []
ygrek has joined #ocaml
jonafan has quit [Nick collision from services.]
jonafan has joined #ocaml
psnively has joined #ocaml
olleolleolle has joined #ocaml
<julm> jstanley: hum, my apologies, it was just hanging on my box because I forgot the final ;;
<julm> funny isn't it
<julm> this said, I am unable to reproduce the hang
<jstanley> julm: doh
<jstanley> julm: alright -- i think it's something with the emacs mode, though. i can just use the toplevel from a shell just fine.
<jstanley> julm: so i'm not going to worry about it. thanks for looking into it though!
<julm> np
<Yoric[DT]> If you still have time, I'm still working on my polymorphic exception stuff :)
<julm> Yoric[DT]: sure, I'm having a glance at http://pastebin.com/m496b6074
<Yoric[DT]> I'm convinced there's a way to do all this without all these lambdas.
<julm> hum, there: [match ((!success), (!failure)) with] I don't think that this time ocaml avoids the allocation of the tuple.
<Yoric[DT]> I can optimize that later.
<Yoric[DT]> That's not really the critical section.
<Yoric[DT]> Now, if the exception could return the result in the first place, I wouldn't need any of this.
<Yoric[DT]> Same thing if I could return a reference to the result.
<Yoric[DT]> At the moment, I propagate a reference to the error pointer.
<Yoric[DT]> s/pointer/result/
<Yoric[DT]> The reference remains unused in case of success, but it still needs to be propagated.
<Yoric[DT]> What I'd like to do would be find a way to use the reference only in case of failure.
<Yoric[DT]> s/use/propagate/
<julm> hum why not using type ('a, 'b) status = | Ok of 'a | Fail of 'b | Empty
<julm> so that there is no need for the success reference
<julm> let run
<julm> (expr : unit -> ('r, 'e) can_fail)
<julm> : ('r, 'e) status =
<julm> let failure = ref Empty in
<julm> try Ok (expr () failure) with
<julm> | PolymorphicException -> !failure
<Yoric[DT]> Yeah, the success reference is useless.
<Yoric[DT]> But it's the failure reference which annoys me.
|Catch22| has joined #ocaml
linktim_ has quit [Read error: 113 (No route to host)]
olleolleolle has left #ocaml []
<Yoric[DT]> My hope was to be able to return a function which would take as argument the failure reference and produce nothing.
<Yoric[DT]> Unfortunately, the type of such a beast would be
<Yoric[DT]> 'a ref -> unit
<Yoric[DT]> which leaves us with an unbound 'a .
<julm> hum I have something
Linktim has joined #ocaml
<julm> but it haves dark magic
<julm> now, is it safe?
<julm> that is the question
<julm> also what is the cost of this local exception
<Yoric[DT]> mmhhh...
<Yoric[DT]> I like the idea of the local exception.
* Yoric[DT] will try and work on that.
<Yoric[DT]> I'm not sure the result is any better than the reference stuff, though.
<Yoric[DT]> Still as much stuff to propagate.
<Yoric[DT]> Why does this Obj.magic work better than the previous version ?
<Yoric[DT]> s/does/should/
|Catch22| has quit [Read error: 113 (No route to host)]
<julm> in the previous there is a failure ref and a Some e inside, here there is just a M.E (Obj.magic e)
<flux> how is Obj.magic being used?
<julm> what?
<flux> I'm just wondering what you guys are talking about
<julm> ah
<julm> well Yoric[DT] try to improve http://pastebin.com/m496b6074
<Yoric[DT]> julm: I mean in the first version.
ofaurax has joined #ocaml
<Yoric[DT]> I haven't tested it to check whether it segfaults, but I'm willing to take your word on this.
<Yoric[DT]> The question being: why ?
ygrek has quit [Remote closed the connection]
<julm> [21:24:16] Yoric[DT] | julm: I mean in the first version. <- which? this one: http://pastebin.com/m110cc8f8 ?
<Yoric[DT]> indeed
<julm> then, first it segfaults, second it uses records for the existential and a few function calls :)
<julm> now
|Catch22| has joined #ocaml
<Yoric[DT]> :)
<julm> now the local exception version, it lighter and I'm looking forward to see if these Obj.magic could be considered harmful
<Yoric[DT]> Yeah, you don't use any existential.
<Yoric[DT]> But why should the Obj.magic work ?
<Yoric[DT]> Plus why should it be faster than the version using references to failures ?
<julm> hum, I do not know if it will actually be faster, but afaics it is a little bit lighter (I mean it requires less memory)
<julm> but I am not expert
<Yoric[DT]> ok
* Yoric[DT] will then keep looking in the Obj.magic-less direction :)
<julm> as you wish
<Yoric[DT]> mmmhhhh....
<Yoric[DT]> How comes I can define a local module but not a local class ?
<julm> put it inside a local module
<Yoric[DT]> Not useful here, local modules can't see type variables from the outside world.
<julm> what?
<julm> I thought it's just that the types they define couldn't escape their scope
<Yoric[DT]> # fun (x:'a) ->
<Yoric[DT]> let module M = struct
<Yoric[DT]> type t = 'a
<Yoric[DT]> end in
<Yoric[DT]> x
<Yoric[DT]> Unbound type parameter 'a
<julm> oh you mean they cannot use a 'a defined before
<julm> yep, hence the use of Obj.magic
<Yoric[DT]> Oops, I forgot one word.
<Yoric[DT]> ...
<Yoric[DT]> No, I didn't :)
<julm> :)
<julm> and could a local object help you?
<Yoric[DT]> Possibly.
<Yoric[DT]> If I use Jacques Garrigue's "instanceof" trick.
<Yoric[DT]> Or maybe not.
* Yoric[DT] starts to be tired after one whole day on this problem.
<julm> I understand
<julm> it is something for the OSR isn't it?
<Yoric[DT]> Might be.
<Yoric[DT]> Actually, I believe that for the OSR, I'll vote for Daniel's simpler suggestion.
<Yoric[DT]> But this doesn't prevent me from trying to get a few steps further :)
* julm hasn't really followed the OSR work.
<julm> "If the function returns either a value or no result, it uses an option type."
<julm> Most of the time I avoid that
<julm> I guess it is my fearing of the useless allocation
<Yoric[DT]> I believe the consensus has become that people may provide several implementations, but at least one should use option types rather than exceptions.
<thelema> julm: you prefer to raise an exception on no result?
<julm> yes, but only when the said function is the kind of function called a lot of times
<julm> after all, I can wrap a function raising an exception without loosing too much, not the reciprocal
<julm> AFAIK of course
<julm> btw, I heard Lisp has a more powerful exception machinery
<julm> for instance in Lisp one could raise an exception, which could then be caught at an outer level, and then from this outer level we can revert the program flow to the raising point of the exception
<julm> anyone knowledgeable on Lisp around?
<flux> julm, exceptions + call/cc?
<flux> I suppose the same could be done with the call/cc-module for ocaml too
<thelema> VB has this "powerful feature", it's called "on error continue"
<thelema> err, "on error resume next"
<julm> also thelema: I have the habit to accurately specify inside commentaries the raises which may occur, so I have not been really harmed by uncaught exception as of now.
psnively has quit []
<julm> thelema: ok
<flux> I wonder how that kind of exception handling could be used efficiently
<julm> flux: don't know :/
<julm> +I
<flux> if you know a function you call can use such exceptions, you could just pass the thing to do on exception as an argument
<julm> indeed
<flux> I mean, don't you need to know quite a lot about a function to provide such services to it?
<flux> maybe a lisper would know differently
<julm> maybe
<flux> btw, regarding those exception systems with Obj.magic, I would personally be very suspicious about them until someone can extract the same code, proven correct, from coq (or prove its usage by other means) :-)
<julm> outch
<thermoplyae> i've only used resuming in exceptions in lisp when i was writing the exception handler into the function itself
<thermoplyae> because, yes, you do need to know quite a bit
psnively has joined #ocaml
<thermoplyae> i'm not enough of a lisper to tell you how they manage to do it efficiently though
<thelema> save the IP on exception and jump back to it on resume
<flux> I didn't mean efficiently in the cpu-time sense, but in the sense that you get useful things done..
<thermoplyae> sounds reasonable
<thermoplyae> you can use it for things like loggers
<thermoplyae> raise an exception, handle the log write, jump back
<flux> so is that mechanism in Common Lisp?
<thermoplyae> maybe that's a useful example
<thermoplyae> yeah
<flux> funny, though, because I thought CL doesn't have a general call/cc mechanism
AxleLonghorn has joined #ocaml
lxuser has joined #ocaml
<Yoric[DT]> julm: actually, with this exception framework, you can do pretty much the same thing in OCaml :)
<lxuser> i get the following error message when trying to build an ocaml app
<lxuser> Camlp4: Uncaught exception: DynLoader.Error ("pa_ifdef.cmo", "file not found in path")
<Yoric[DT]> lxuser: did you write the Makefile ?
<Yoric[DT]> julm: One more reason to improve the performance of this library.
postalchris has quit [Connection timed out]
<lxuser> nope
<Yoric[DT]> lxuser: basically, it's probably suited for OCaml 3.09- and you probably have 3.10+.
<thelema> One would need to program differently - when I raise an exception, it's usually because that function can't continue. If i had to write exceptions that would not guarantee leaving the function, I'd have to if something-bad then raise_exception else do rest of function -- what would get returned if the error handler resumed my function...
<Yoric[DT]> thelema: I was thinking about raising an exception and putting the rest of the function inside the exception constructor.
<Yoric[DT]> lxuser: might work if you install Camlp5.
<Yoric[DT]> I'm not sure how to use it, though.
<Yoric[DT]> thelema: that wouldn't work with imperative loops, but everything else should work.
<thelema> Yoric[DT]: exception Continuable of string * (unit -> 'a)?
<Yoric[DT]> thelema: and to do that, you need to be aware that your exception is going to be used for resumption.
<Yoric[DT]> why string ?
<Yoric[DT]> But yeah, something like this.
<thelema> same reason Failure and Invalid_argument use string
<Yoric[DT]> ok
<lxuser> so what am I supposed to change in the Makefile ? can I just change camlp4 to camlp5 and expect it to work?
<Yoric[DT]> lxuser: I think so -- provided you have Camlp5 installed.
<Yoric[DT]> julm: mmmhhh.... from what I see, it looks like this module not being able to see polymorphic types is a bug.
<Yoric[DT]> And an old one with that.
<julm> Yoric[DT]: what do you mean exactly?
ofaurax has quit ["Leaving"]
<lxuser> can't get it to work
jderque has quit ["leaving"]
<lxuser> Error while loading "pa_ifdef.cmo": file not found in path.
<Yoric[DT]> With camlp5 ?
postalchris has joined #ocaml
smimou has quit ["bli"]
<lxuser> apparently so
postalchris has quit [Client Quit]
<julm> Yoric[DT]: I just see: " They do not have any specific behaviour, but definitions inside them"
<thelema> lxuser: do you have a file pa_ifdef.cmo anywhere on your computer? (find / -name pa_ifdef.cmo)
<julm> have their type variables quantified independently, as you would
<julm> expect if the module were defined at toplevel.
<julm> Yoric[DT]: where's the bug you're talking about?
<Yoric[DT]> > Type declaration flushes the introduced variables:
<Yoric[DT]> >
<Yoric[DT]> > # let f (x : 'a) = let module M = struct type t end in (2 : 'a);;
<Yoric[DT]> > val f : 'a -> int = <fun>
<Yoric[DT]> That one is a bug. Bad one. And not immediate to correct, as type
<Yoric[DT]> variables are reset all over the place.
<Yoric[DT]> Thanks for reporting.
<Yoric[DT]> ...mmhhh...
<Yoric[DT]> No, actually, that's a different stuff.
* Yoric[DT] is probably really too tired to work.
<julm> have a nap man :)
* Yoric[DT] needs a few weeks worth of holidays...
Linktim has quit [Remote closed the connection]
monde has quit ["Leaving."]
<lxuser> thelema: nope
smimou has joined #ocaml
<lxuser> i've got lots of pa_* files under /usr/lib/ocaml/3.10.0/camlp5/ but no pa_ifdef
<thelema> lxuser: that's odd. ifdef should be part of the standard distribution of p5
<thelema> or maybe not, google pulls up nothing on 'camlp5 ifdef'
<thelema> n/m, the bad search was 'ocamlp5 ifdef'
<lxuser> i'm using camlp5 5.06-2 from debian lenny.
<thelema> try changing pa_ifdef to pa_macro
* Yoric[DT] shall return tomorrow.
<Yoric[DT]> cheers
Yoric[DT] has quit ["Ex-Chat"]
Morphous_ has quit ["shutdown"]
Amorphous has joined #ocaml
vpalle_ has joined #ocaml
vpalle has quit [Read error: 110 (Connection timed out)]
lxuser has quit ["Sto andando via"]
rogo has joined #ocaml
<thelema>
ikatz has quit [kornbluth.freenode.net irc.freenode.net]
TaXules has quit [kornbluth.freenode.net irc.freenode.net]
unfo- has quit [kornbluth.freenode.net irc.freenode.net]
jeremiah has quit [kornbluth.freenode.net irc.freenode.net]
svenl has quit [kornbluth.freenode.net irc.freenode.net]
orbitz has quit [kornbluth.freenode.net irc.freenode.net]
mattam has quit [kornbluth.freenode.net irc.freenode.net]
jdavis_ has quit [kornbluth.freenode.net irc.freenode.net]
evn has joined #ocaml
evn has left #ocaml []
orbitz has joined #ocaml
svenl has joined #ocaml
TaXules has joined #ocaml
mattam has joined #ocaml
unfo- has joined #ocaml
jdavis_ has joined #ocaml
jeremiah has joined #ocaml
Snrrrub has joined #ocaml
<Snrrrub> Is there a good place to announce a library for OCaml other than the OCaml Hump?
__suri has quit [kornbluth.freenode.net irc.freenode.net]
__suri has joined #ocaml