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!)
psnively has quit []
hkBst has quit ["Konversation terminated!"]
middayc has quit []
mbishop has quit ["brb"]
Yoric[DT] has quit ["Ex-Chat"]
ita has quit [Read error: 110 (Connection timed out)]
mbishop has joined #ocaml
jeremiah has quit [Read error: 104 (Connection reset by peer)]
hsuh has joined #ocaml
jeremiah has joined #ocaml
AxleLonghorn has joined #ocaml
seafood_ has joined #ocaml
AxleLonghorn has quit [Read error: 110 (Connection timed out)]
AxleLonghorn has joined #ocaml
brooksbp has joined #ocaml
brooksbp has quit [Remote closed the connection]
jlouis_ has quit [Remote closed the connection]
qwr has joined #ocaml
jlouis has joined #ocaml
seafood_ has quit []
yminsky has quit []
<kbidd> I'm having trouble with the rules about where to use ";"... does anyone know any good guides for beginners to ocaml?
seafood_ has joined #ocaml
Snrrrub__ has joined #ocaml
<qwr> kbidd: ; is sequencing operator
<qwr> kbidd: like , in C
<qwr> kbidd: a; b means evaluate a, ignore its value, evaluate b and return b's value
<qwr> kbidd: a; b; c is same as (a; b); c
<kbidd> and when do you use ;;?
<cygnus_> to separate things
<qwr> kbidd: ;; is toplevel definition separator
<qwr> kbidd: and ;; is optional before type/let/open definitions
<qwr> (maybe there are some more rules that i'm not aware...)
<kbidd> is ; needed after a defining a local variable? I was reading some example code, and they seemed to be leaving it out.
<qwr> kbidd: no.
<qwr> kbidd: you define local "variables" or bindings using let a = value in ...
<qwr> where a will be defined only in the scope after in
<kbidd> where does a go out of scope? ;;?
<qwr> yes. or )
<qwr> ... or end as begin ... end is equivalent to ( ... )
<kbidd> ok, thanks
<kbidd> its a pain to learn ocaml ruby and python all at the same time... I keep mixing up the syntaxes :P
Snrrrub has quit [Read error: 110 (Connection timed out)]
<qwr> ocaml has more consistent syntax imho ;)
<qwr> (although, python has also quite ok syntax)
<kbidd> its just obnoxious trying to keep the rules straight when you're just starting out on more than one language, and not familiar with any of them
<kbidd> im not sure why they dont just teach us one language at a time
<AxleLonghorn> Best class I ever had was a class that used several different language
<AxleLonghorn> *languages
<AxleLonghorn> we did scheme, ocaml, and prolog. It was a good class though because it was basically "understand functional programming, go!".
mbishop has quit ["brb"]
jlouis_ has joined #ocaml
yangsx has left #ocaml []
kmeyer has quit [Read error: 104 (Connection reset by peer)]
kmeyer has joined #ocaml
mbishop has joined #ocaml
jlouis has quit [Read error: 110 (Connection timed out)]
jlouis has joined #ocaml
jlouis_ has quit [Read error: 110 (Connection timed out)]
AxleLonghorn has left #ocaml []
Theq629 has joined #ocaml
jderque has joined #ocaml
<flux> I'm building ocamlnet 2.2.9 on solaris, and it fails to compile file rpc_key_service.ml
<flux> the file contains line: let default_connector = tirpc_connector
<flux> but tirpc_connector is nowhere to be seen
<flux> and the file doesn't "open" or "include" other modules
<flux> it's line 39, so I really should see it if it were there..
<flux> I wonder if the file is usually compiled, because godi-boostrap when fine with linux
<flux> ("tirpc_connector": zero hits on google!)
<mbishop> mentions it, at least
<flux> ah, "only with -with-rpc-auth-dh"
<flux> thanks!
<flux> should've searched only for tirpc
<mbishop> apparently it's rpc-xti, which is in "camlrpc"
<flux> maybe the support isn't working anymore, but nobody compiles it on solaris to find out
<flux> I was at ocamlnet-2.2.9/src/rpc-auth-dh
<flux> aha, the file .ml -file is generated
<flux> default_connector is defined in rpc_key_service.mlp
<flux> which says: @CONNECTOR@_connector
<flux> now I wonder how I tell godi to compile ocamlnet with special switches..
<flux> ah, found
<flux> it explicitly says: CONFIGURE_ARGS+=-with-nethttpd -with-rpc-auth-dh
madroach has joined #ocaml
ttamttam has joined #ocaml
mikmik has joined #ocaml
seafood_ has quit []
madroach has quit [Remote closed the connection]
Theq629 has quit [Client Quit]
ttamtta1 has joined #ocaml
ttamtta1 has left #ocaml []
mikmik has quit []
jderque has quit [Read error: 113 (No route to host)]
<thermoplyae> it's amazing how quickly 'applied' things or even applied ways of thinking get me out of #math
ttamttam has quit [Read error: 110 (Connection timed out)]
maayhem has joined #ocaml
<maayhem> 'lo
<maayhem> how can I print the key of a Map ?
thermoplyae has left #ocaml []
<maayhem> is there any way to create the Map given a printing handler parameter ?
<mfp> you know which type t you passed to Map.Make, so just use the pertinent func (e.g. print_endline)
<mfp> unless you mean something like module Map'(O : sig include Map.OrderedType val string_of_key : t -> string end) = struct include Map.Make(O) let string_of_key = O.string_of_key end;;
hsuh has quit [Remote closed the connection]
Tetsuo has joined #ocaml
<maayhem> mfp, ok thanks
maayhem has left #ocaml []
rwmjones has joined #ocaml
ygrek has joined #ocaml
alexp has joined #ocaml
munga has joined #ocaml
ygrek has quit [Remote closed the connection]
shafty has joined #ocaml
Yoric[DT] has joined #ocaml
jonafan has quit [Read error: 110 (Connection timed out)]
_andre has joined #ocaml
middayc has joined #ocaml
<_andre> hello
<_andre> is it possible to have a function in a C extension that takes a hash table as a parameter, and to iterate over the hash's contents in C ?
madroach has joined #ocaml
<flux> I think that is possible, but difficult: you need to call back to ocaml from C also
<flux> I suppose it's not an option for you to iterate in ocaml?
<_andre> unfortunately not (long story...)
madroach has quit [Remote closed the connection]
<_andre> i'll try to find out how to call ocaml from C then... never tried that
SIGVTALRM has joined #ocaml
mfp has quit [Read error: 110 (Connection timed out)]
jonathanv has joined #ocaml
<_andre> i'm used to ruby's C api, but ocaml's still new to me :)
<_andre> btw, i exported a C function with one of its parameters being optional, and i noticed that when i call the function without that parameter, its value is 0x1
SIGVTALRM is now known as mfp
<flux> it's like any other optional value
<_andre> is that always the case? is there some "parameter_given()" macro which i can use to test that safely?
<flux> if there aren't macros for testing if it's optional, you can use something like Is_long or somesuch (I don't remember exactly)
<flux> if it's not "None", it's "Some x", and that is expressed as a pointer to the value
StoneNote has quit []
<mfp> _andre: you get Some x or None; the latter happens to be encoded as 0x01, so use Is_block etc
<_andre> mfp: thanks (and btw thanks again for rocaml :)
<mfp> flux was faster :-)
<_andre> oh didn't see that
<_andre> thanks flux :)
gabriel__ has joined #ocaml
middayc has quit []
seafood_ has joined #ocaml
middayc has joined #ocaml
<_andre> ok, i managed to do a Hashtbl.find from C... now Hashtbl.iter is going to be harder...
<_andre> any idea on how to pass a C function to iter?
<flux> pass an ocaml function that knows how to call the C function..
rwmjones has left #ocaml []
<_andre> ok, let me try that...
seafood_ has quit []
<petchema> interesting... I'm getting an exception Invalid_argument("Str.matched_group") by using Str.string_match on a set of "hash consed" strings
<petchema> I suspect some internal datastructure in Str used to associate matched groups to strings gets confused
<Yoric[DT]> Mmhhhh.....
<Yoric[DT]> Does anyone know what the syntax 'a.'a means ?
<gabriel__> let matched_group n txt =
<gabriel__> let n2 = n + n in
<gabriel__> if n < 0 || n2 >= Array.length !last_search_result then
<gabriel__> invalid_arg "Str.matched_group"
<gabriel__> (from str.ml)
<gabriel__> Yoric[DT]: yes
<Yoric[DT]> What is it ?
<gabriel__> it is a universal quantifier (or is it existential)?
<gabriel__> in typed languages, you can use either universal or existential quantifiers (aka free variables)
<gabriel__> ocaml chose to default to one of them for type inference
<gabriel__> so you have to use 'a. to specify the other
<Yoric[DT]> mmmhhhh....
<gabriel__> (can't remember the details but I have an exam on this in one week so...)
<Yoric[DT]> iirc, existential quantifiers mean that you have to provide a type for the type expression to be complete, doesn't it ?
<Yoric[DT]> Let me rephrase
<Yoric[DT]> type universal = { is : 'a.'a } ;;
<Yoric[DT]> What's an inhabitant of this type ?
<flux> yoric[dt], let id a = a
<flux> uh
<flux> never mind
<flux> (failwith "")
<flux> not very useful, mind you :)
<Yoric[DT]> :)
<flux> Obj.magic 42 also..
<Yoric[DT]> Or, rephrased, how can I use that type without Obj.magic ?
<flux> that exact type?
<flux> or another type with 'a. ?
<gabriel__> I know how (and when) to use 'a. in objects
<Yoric[DT]> I don't know, I'm just trying to understand exactly what it means.
<gabriel__> but in that cas...
<flux> yoric[dt], the most useful use I've had thus far has been embedding for example iter-like functions inside records
<Yoric[DT]> mmmhhh....
<flux> maybe not the perfect design, but it fit
<Yoric[DT]> Ok.
<Yoric[DT]> I'm starting to understand.
<Yoric[DT]> (I think)
<Yoric[DT]> In my trivial example, I could have written
<flux> it's great to have when you encounter the need :-)
<Yoric[DT]> type 'a universal = { is : 'a }
<Yoric[DT]> and obtained the same result, isn't it ?
<flux> not really, because int universal and float universal are different types
<Yoric[DT]> Ok.
<Yoric[DT]> I'm getting it.
<Yoric[DT]> Thanks for the example of iter-like functions :)
<flux> I actually use it with field "with_db"
<flux> which is like type .. { with_db = 'a. (db_handle -> 'a) -> 'a }
<flux> s/=/:/
<flux> so someone who gets that record passed can get use the db with rec.with_db (fun db -> db_code_here)
<gabriel__> it's exactly the same in objects (for methods in objects can't be polymorphic unless explicitly stated)
<Yoric[DT]> I'm currently working on getting polymorphic exceptions ( and a fast exception monad for the same price ) into OCaml and I encountered this 'a.'a in an example.
<Yoric[DT]> Actually, there are two of us working on it and I didn't want to sound like an idiot in front of the other guy :)
<gabriel__> sounds reasonable ;-)
<gabriel__> well, I can't see any way to instantiate your universal type
<Yoric[DT]> Still, it seems that both of us have working versions of this.
<Yoric[DT]> He's using Obj.magic anyway.
<Yoric[DT]> He just wanted to force that to be a reference.
<Yoric[DT]> Because OCaml tends to inspect a bit exceptions as they're unrolling the stack, presumably for debugging purposes, so he can't Obj.magic his exception into everything he wants.
<gabriel__> I like this IRC channel, I think I'll come back :-)
<gabriel__> I've got to go right now anyway
<gabriel__> see you later
gabriel__ has quit ["leaving"]
<mfp> are there any plans to implement rank-2 polymorphism? (not that I have anything in mind that needs it :)
* mfp would like to know what typing magic the INRIA wizards are working on
<mfp> I used to believe that they were working on adding typeclasses, but some recent msgs on the ML seem to indicate it's not the case
kbidd has quit [Remote closed the connection]
lbc has joined #ocaml
Mr_Awesome has quit [Read error: 110 (Connection timed out)]
Mr_Awesome has joined #ocaml
AxleLonghorn has joined #ocaml
filp has joined #ocaml
hkBst has joined #ocaml
bluestorm has joined #ocaml
_KS has joined #ocaml
mikmik has joined #ocaml
mikmik has left #ocaml []
olleolleolle has joined #ocaml
AxleLonghorn has left #ocaml []
asmanur has joined #ocaml
AxleLonghorn has joined #ocaml
AxleLonghorn has left #ocaml []
pango has quit [Remote closed the connection]
<bluestorm> Yoric[DT]: your exceptions work seems interesting
<bluestorm> do you have a pointer ?
olleolleolle has left #ocaml []
<Yoric[DT]> Not yet.
shafty has quit ["leaving"]
<bluestorm> Yoric[DT]: is it something like an abstract data type, with monadic operators, relying on exceptions under the hood ?
<Yoric[DT]> yep
pango has joined #ocaml
<bluestorm> i'm not sure about the current exceptions debate
<bluestorm> the proposed spec in quite constraining, and it seems most propositions are
<bluestorm> on the other hands
<bluestorm> we have OCamlExc that seems (never used it) able to provide the safety informations
<Yoric[DT]> My personal problem with the current handling exceptions is that I'd quite prefer if querying a data structure returned an 'a option rather than either something or an exception.
<bluestorm> but it's easier to add option on top of exceptions than the other way
<bluestorm> an Extlib something could do that
<bluestorm> (anyway you'll *need* some additional lib if you want to handle 'a option easily)
<Yoric[DT]> Well, anyway, I've just posted a third version of this exception monad :)
<bluestorm> on a completely different topic, i've been thinking of something.. strange, lately
<Yoric[DT]> (combining the ease-of-use and safety of mine and the speed of Arnaud Spiwack's, barring any bug, of course)
<Yoric[DT]> How strange ?
<bluestorm> i might try to adapt a Haskell parser to generate a caml AST
<bluestorm> that is, a Haskell syntax for OCaml
<bluestorm> do you think anyone other than me would even look at it ? :p
<bluestorm> (already have a *great* name, haskaml :-')
<bluestorm> (where was your exception monad posted ?)
<Yoric[DT]> No, I mean by e-mail to that other guy.
<Yoric[DT]> It needs a bit of testing before being released :)
<Yoric[DT]> (especially since his version uses Obj.magic and mine uses references)
<bluestorm> :D
<Yoric[DT]> mmmhhh....
<Yoric[DT]> Gasp.
<Yoric[DT]> Of course, I can't leave the world of monads and produce an exception myself.
jonathanv is now known as jonafan
dramsay has joined #ocaml
<hcarty> Yoric[DT]: Do you know which is faster, an option type or an exception?
<Yoric[DT]> I haven't experimented.
<bluestorm> i guess the exception is faster
<bluestorm> as it's lower-level
<bluestorm> (option type requires boxing/unboxing, and so on)
<bluestorm> the question is to know if options are worth it
<bluestorm> in some case they really are easier to manipulate (when you've got a good Option lib)
<bluestorm> but i'm not sure it's the average case
mwc has joined #ocaml
Morphous has joined #ocaml
_KS has quit []
jderque has joined #ocaml
Morphous_ has quit [Read error: 110 (Connection timed out)]
munga has quit ["Leaving"]
marmottine has joined #ocaml
Yoric[DT] has quit ["Ex-Chat"]
alexp has quit ["Leaving"]
jderque has quit [Read error: 113 (No route to host)]
dramsay has quit [Read error: 110 (Connection timed out)]
<hcarty> Is there a way to get around the "I/O error: Bad file descriptor" error when using a camlp4 extension in the toplevel?
<hcarty> Sorry, I didn't explain - the error comes up when "#use"ing more than one .ml file
<hcarty> The first will load without issue
<hcarty> Any following give that error
jderque has joined #ocaml
Yoric[DT] has joined #ocaml
<bluestorm> hcarty: looks like a bug
<bluestorm> hm Yoric[DT]
<Yoric[DT]> Yes ?
<bluestorm> i just found a mailing-post that may be of interest to you
<bluestorm> (if you haven't read it yet)
<bluestorm> (i know, it's dreadful :-')
<Yoric[DT]> :)
<hcarty> bluestorm: Ok, thanks. I'll check Mantis to see if it's been reported
<hcarty> It makes testing camlp4 extensions much more difficult
jnkm has joined #ocaml
postalchris has joined #ocaml
jlouis has quit ["leaving"]
jlouis has joined #ocaml
rwmjones has joined #ocaml
<rwmjones> bluestorm, I just reverted that edit to ocaml-tutorial.org, because the quote was actually what Brian Hurt said, so shouldn't be modified
<bluestorm> hmm
<bluestorm> imho that's not a very good idea to have non-editable comment on the wiki
<bluestorm> s/comment/content/
<bluestorm> but i may add my version after his comment, for now
<rwmjones> ah well ... was originally a static web page you see
<bluestorm> :p
<bluestorm> would it be possible to rework that part, to get rid of his quote, while keeping the content ?
<bluestorm> (of course i'd not do that alone, as it seems there is a possible disagreement on that point, but i think we could agree on something less confusing for users that "is ; a function or not ?")
ttamttam has joined #ocaml
ita has joined #ocaml
<rwmjones> should make it more "quote like" really ... possibly use <html><blockquote> around it?
<rwmjones> like
<rwmjones> <html>
<rwmjones> <blockquote>
<rwmjones> the quote ...
<rwmjones> </blockquote>
<rwmjones> </html>
<rwmjones> just a sec, let me do that
filp has quit ["Bye"]
<bluestorm> :p
<rwmjones> bluestorm, try that version
<bluestorm> yes, that looks more like a integral quote
ygrek has joined #ocaml
ygrek has quit [Remote closed the connection]
ygrek has joined #ocaml
<Yoric[DT]> Gasp, I can't give the same interface to my three implementations of the module monad.
<Yoric[DT]> At least not without a big penalty cost.\
<Yoric[DT]> :/
* qwr . o O ( what wiki? )
<bluestorm> Yoric[DT]: 'a option does not give enough information
<Yoric[DT]> Yeah, usually doesn't.
<Yoric[DT]> What did I write ?
<bluestorm> you can't do a "drop-in exceptions remplacement" with maybe only
<bluestorm> hm
<bluestorm> (say, suffix "_maybe")
<bluestorm> +" "
<bluestorm> i quite liked the polymorphic variant suggestion
<bluestorm> but it can raise some subtle typing issues
<bluestorm> if not carefully used
<bluestorm> (on the other hand, plainly specifying the polymorphic variant used in the signature is a good way to protect functions from baroque inferred types. The problem is with non-interfaced-functions during the development phase)
* Yoric[DT] concurs.
asmanur has quit [Remote closed the connection]
<Yoric[DT]> mmmhhh....
<Yoric[DT]> Maybe I shouldn't go for one single interface.
<Yoric[DT]> Just similar modules.
<bluestorm> Yoric[DT]:
<bluestorm> your idea of ErrorMechanism parametrization won't fit
thermoplyae has joined #ocaml
<bluestorm> as the code structure using exceptions and option/variant is not the same
<bluestorm> that would basically force everyone to use a monad
<bluestorm> wich is not what the "exceptions supporters" want
<Yoric[DT]> I don't think so.
<bluestorm> hm
<bluestorm> how would you formulate eg. for i = 0 to len - 1 do .... if foo then raise Invalid_item i; ... done wich your functor ?
<bluestorm> i can't see a way of having it working with option/variants without deep changes to the code
<Yoric[DT]> I'm not completely sure yet ?
<Yoric[DT]> I'm not completely sure yet :)
<Yoric[DT]> I mean, there's a problem, but I'm not sure it can't be solved.
<bluestorm> hm
<Yoric[DT]> I may be wrong, of course.
<Yoric[DT]> I mean, in any case we will need something like 'a option.
<bluestorm> i'd say that if there was an easy way to make monadic code looks like non-monadic code, Haskellers might have found it since 1992 :-'
<Yoric[DT]> (More likely ('a, 'b) result )
<Yoric[DT]> :)
<Yoric[DT]> What I mean is that I envision monad-like stuff only at the boundary of modules anyway.
<bluestorm> so as wrappers over exception-raising functions ?
<bluestorm> i think you'll need a "local" monadic toolkit anyway
<Yoric[DT]> Indeed.
<Yoric[DT]> Indeed to the first sentence that was.
<bluestorm> if you don't use it inside your module
<Yoric[DT]> Possibly.
<bluestorm> users will need it
<bluestorm> eg. we do not currently have the tool to effortlessly manipulate a Map.find : ('a, 'b) map -> 'a -> 'b option function
<Yoric[DT]> Er... what would that function do ?
<bluestorm> hm
<bluestorm> 'lookup' ?
<Yoric[DT]> ah, ok
<Yoric[DT]> And what do you mean by effortlessly ?
<bluestorm> hm
<bluestorm> without try "match foo with None -> ... | Some f -> ..." per line
<bluestorm> s/try/three/ -__-
<Yoric[DT]> :)
<bluestorm> Yoric[DT]: for example, "fetch all the indexes in the list foo and give me the result back, failing if one of them fail" is easy to do with exceptions *now*
<bluestorm> while it isn't with 'a option
<Yoric[DT]> Fair enough.
<bluestorm> of course, it could be fixed with an additional library
_andre has quit ["leaving"]
<bluestorm> but i think you'd need that additional library in all case, even if your option/variant stuff is "only at the end of some exported definitions"
<flux> apparently ocamlexc is not quite full-features compared to the current language.. too bad, because I for one could have use for it :)
<bluestorm> Yoric[DT]: Failure is not polymorphic
<bluestorm> exceptions are not polymorphic
jderque has quit [Read error: 113 (No route to host)]
<Yoric[DT]> I know.
<bluestorm> hm
<Yoric[DT]> Well, I have polymorphic exceptions under the hand, but that's a different story :)
<flux> I wonder what would ocaml look like if it had typeof-operator, wic
<Yoric[DT]> Oh, perhaps I should have chosen a different name than Failure, is that it ?
<flux> which could be used to instantiate modules
<flux> (infact, I think that would be one logical extension to the type system)
<flux> I wonder if it would render the type system turing complete..
<bluestorm> hmm
<Yoric[DT]> flux: yeah, that would be nice.
<bluestorm> Yoric[DT]: so in your code
<bluestorm> | Failure of 'e (**The operation was a failure*)
<bluestorm> exc -> Failure exc
<bluestorm> isn't it "Failure of exn" ?
<flux> btw, whatcha guys been talking about?-)
<Yoric[DT]> bluestorm: mmmhh... Yeah, exn would have been sufficient.
<flux> hmm.. let (!!) f a = match f with None -> failwith "error" | Some x -> x
<bluestorm> Yoric[DT]: i think you and Andrej where not talking about the same thing
<bluestorm> he was referring to the specific case of tail-recursion
<flux> (just wondering if you could just composite functions to avoid having two versions of everything)
<Yoric[DT]> Well, I was asnwering Daniel, so that's ok :)
<bluestorm> :p
<bluestorm> flux: Yoric[DT] is gonna propose you a nice camlp4 extension to automate the proccess :-'
<Yoric[DT]> :)
<bluestorm> value foo = .... with monadic_counterpart
ttamttam has left #ocaml []
<bluestorm> ;
<Yoric[DT]> mmmhh....
<Yoric[DT]> Error in the magic monad.
<Yoric[DT]> But the bug is unrelated to Obj.magic :)
<Yoric[DT]> Bug fixed.
kbidd has joined #ocaml
thermoplyae has quit ["daddy's in space"]
jstanley has joined #ocaml
<jstanley> Can anyone point me to a reasonably straightforward example of using OCaml's FFI to invoke ocaml functions from C? There are a lot of examples for going the other way, but I can't find any that demonstrate how to deal with heap-allocated ocaml objects, for instance.
<kbidd> whats the 'and' keyword do in ocaml? is it another way to write && or does it mean something else?
<kbidd> (i would google, but looking up "and" makes it kinda hard :P)
<jstanley> kbidd: conjuncted type declarations, for one. e.g. type Blah = ... and Foo = ...
<jstanley> (IIRC)
<kbidd> awesome... ive been looking for a way to do that
<hcarty> kbidd: You can also do let foo = ... and blah = ...
<hcarty> jstanley: Someone posted a tutorial link on one of the lists recently... I'm trying to find the link
<jstanley> hcarty: awesome, thanks much. most examples i've seen just demonstrate how to make an ocaml binding for a C lib. I want to do the opposite and need to make sure that there's nothing funky going on with heap mgmt.
<jstanley> I can trivially invoke ocaml functions from C, but the marshaling semantics aren't as clear as they could be from the one document on the FFI in the ocaml manual.
<hcarty> http://www.linux-nantes.org/~fmonnier/OCaml/ocaml-wrapping-c.php -- That's the link, but I was mistaken. I don't think it has what you want.
<jstanley> alight, cool, thanks anyway. more example code can't hurt.
<jstanley> yeah i seem to be in the rare situation where i want code re-use from a large ocaml api rather than the other way around.
<hcarty> The function ml_plotter is used as a callback
<jstanley> thanks
<hcarty> in C
<jstanley> so...a general question. say i obtain a caml closure via caml_named_value() and invoke via caml_callback().
<jstanley> that works for the primitive caml functions i've used
<jstanley> but say that the ocaml function in question creates a new object and returns that...any idea how i ensure that the caml GC won't get rid of it once i leave the C function that receives the value?
<kbidd> probably not the best solution, but make a global ref, and have the function in question set the ref to the object before returning it?
<kbidd> dont know if that would work though... i just started learning ocaml yesterday
<jstanley> it might...but yeah, yuck.
<kbidd> so feel free to ignore me if thats a stupid idea :P
<hcarty> jstanley: Do you have the OCaml GC running in your program? I haven't used an OCaml lib from a pure-C program, so I don't know the details of how that works.
<jstanley> and i'd have to have a global data structure to hold onto all of the dynamically allocated stuff, etc.
<jstanley> hcarty: yeah, because the main() in the C program invokes the caml runtime which just uses Callback.register on a lot of caml functions.
<hcarty> Ah, ok
<hcarty> That makes sense
<hcarty> I think if you declare it as a value type, and return it as such, then it should work?
<jstanley> so e.g., caml code would look something like: let make_blah = new blah () ... let _ = Callback.register "make_blah" make_blah; ...
<jstanley> hmm...
<hcarty> But I don't know if there is an equivalent to the CAMLlocal macros for this
<jstanley> right...which would really suck ;)
<hcarty> CAMLreturn may do the magic for you
<hcarty> Since the object should have a C type of value
<hcarty> I do not know how you would signal the GC to say "I'm done with this one" though
<jstanley> right, that is the bigger issue, i think. the normal "wrap a C lib" approach uses CAMLreturn to say 'here, you manage this" because it's being handed off to the caml RT
<jstanley> whereas in my situation, i'm doing something like:
<jstanley> value new_solver()
<jstanley> {
<jstanley> CAMLlocal1 (result);
<jstanley> static value* new_solver_closure = 0;
<jstanley> if (!new_solver_closure)
<jstanley> new_solver_closure = caml_named_value("new_solver");
<jstanley> result = caml_callback(*new_solver_closure, Val_unit);
<jstanley> CAMLreturn (result);
<jstanley> }
<jstanley> and so yeah, the normal semantics would be to pin down returned values inside the caml RT as being GC'able when caml references drop to 0, etc.
<jstanley> whereas here...i'm really wanting some kind of forced no-GC option
<jstanley> don't even know if the caml RT supports such a thing.
<hcarty> If you handle the return value of new_solver() with CAMLlocal it should be ok
<hcarty> Then (perhaps?) the GC should Do The Right Thing
<jstanley> alright, good idea. time to do some biology experiments. ;P
<jstanley> thanks.
<hcarty> Since the CAMLparam, CAMLlocal and CAMLreturn macros are (from what I understand) what keep an OCaml value alive
<hcarty> Good luck!
<jstanley> thanks ;)
<kbidd> whats the correct syntax to write something like this:
<kbidd> let testval =
<kbidd> if condition then
<kbidd> object#function;
<kbidd> ret_val
<kbidd> else
<kbidd> ret_val2
<kbidd> in
<hcarty> You need () around the stuff between "then" and "else"
<kbidd> ah... thanks!
<hcarty> You are welcome
<jstanley> or you could use a begin...end there i think.
<hcarty> That too
<hcarty> Or let () = object#function in
<hcarty> I think it's a precedence issue
jlouis has quit [Read error: 110 (Connection timed out)]
Tetsuo has quit ["Leaving"]
jlouis has joined #ocaml
mbishop_ has joined #ocaml
ygrek has quit [Remote closed the connection]
ita has quit ["Hasta luego!"]
StoneNote has joined #ocaml
bluestorm has quit ["Konversation terminated!"]
mbishop has quit [Read error: 113 (No route to host)]
<jstanley> hcarty: yeah, the reasonable approach with CAMLparam0/CAMLlocal1 to hold a resulting object ref value, and CAMLreturn isn't cutting it -- let me know if you feel like peeking at my code and seeing if you can see anything amiss.
<jstanley> I asked this a bit earlier, but here goes again just in case I'm more clear now. =) Is there a fully-functional way to invoke arbitrary OCaml code *from C* via the OCaml FFI implementation? Registering an OCaml closure via the Callback.register mechanism and obtaining that closure from the C side (via caml_named_value()) works just fine, as does invoking simple functions from the C side. However, I'm not having any luck carrying OCa
<mfp> carrying OC... ?
<mfp> OCaml values [...] ?
<jstanley> ...carrying OCaml object references around on the C side of the world.
<jstanley> I can't yet tell if the way I'm using the FFI is just dead wrong though.
<mfp> sounds like you want caml_register_global_root (assuming you're placing the return values from a Caml function in some global structure in C)
hkBst has quit ["Konversation terminated!"]
<jstanley> ah, that's the mechanism where i can hang values between function calls?
<mfp> you don't need that normally
<mfp> how are you using the values returned by OCaml?
<jstanley> hmm. sounds like overkill for what i want to do; really, i just want to propagate some value-ified ocaml object reference
<jstanley> and pass it to another ocaml function that i have obtained the callback for.
<mfp> if you're using CAMLparam, CAMLlocal and CAMLreturn properly, everything should be fine
<jstanley> e.g. value res = caml_callback(*some_closure_that_returns_obj_ref, Val_unit);
<jstanley> okay, or using those.
<Yoric[DT]> If anybody's interested, a first version of my Monadic Exceptions for OCaml is available here http://dutherenverseauborddelatable.wordpress.com/downloads/exception-monads-for-ocaml/ .
<jstanley> so CAMLparam0(); CAMLlocal1(result); ... result = caml_callback(...);
<mfp> do CAMLlocal1(res); .... res = caml_callback(...); ...
<jstanley> yup yup
<mfp> yep
<jstanley> then in the same function
<jstanley> int x = someOtherFunc(result);
<jstanley> where someOtherFunc takes a value, and uses CAMLparam1(s);
<mfp> yes, exactly
<jstanley> can I use caml_callback(*some_other_closure, s)?
<jstanley> that's where i'm getting the bus error.
<jstanley> that is, i thought i'd taken all the steps to preserve this stuff, but that second caml_callback is failing.
<mfp> caml_named_value can return NULL...
<jstanley> blech, okay, to be fair, i didn't check for that.
<jstanley> brb ;)
<mfp> the **value you get can be reused; its value will be modified by the GC, which is why you have to dereference it for each caml_callback
<jstanley> *nod*
<jstanley> alright, i feel sheepish -- that caml_named_value result was null.
<mfp> Yoric[DT]: downloading :)
<jstanley> my bad :P i just assumed it was something to do with that propogated value being outside the heap.
<Yoric[DT]> mfp: :)
<Yoric[DT]> Just a first try.
<jstanley> mfp: thanks for your help :P
<mbishop_> Yoric[DT]: nice, but you should fix your code to be indented properly
<Yoric[DT]> mfp: my first venture in the world of monads.
<mbishop_> on the blog, that is
<Yoric[DT]> mbishop_: limitation of the blog engine, it seems :(
<Yoric[DT]> Well, I guess I could fill it with &nbsp; .
<mfp> jstanley: np
<mfp> omg revised syntax! so the camlp4 sources aren't the only place where it's used ;-))
<Yoric[DT]> :)
<Yoric[DT]> I like that syntax.
<mfp> Yoric[DT]: what about value bind = continue; in order to use pa_monad?
<Yoric[DT]> I need to check how pa_monad works.
<Yoric[DT]> If I only need to call my function bind, then it should be a breeze.
<mfp> that's about it really :)
<Yoric[DT]> :)
* Yoric[DT] admits that he used a custom operator in his test :)
<mfp> you can specify the bind func, but if you call it bind the end-user will only need to open SimpleMonad .... perform x <-- dowhatever; ...
<Yoric[DT]> I guess you can't mix several monads at once, can you ?
<mfp> it uses one bind per perform expr
<mfp> but then you need monad transformers and stuff I don't really know, I guess?
<Yoric[DT]> I suppose.
<Yoric[DT]> I need to learn more about monads yet.
marmottine has quit ["Quitte"]
<Yoric[DT]> Oh, btw, the .tgz has been updated to use bind instead of continue.
jstanley has left #ocaml []
<mfp> Yoric[DT]: test_original.ml using pa_monad http://rafb.net/p/BFInOH75.html
<mfp> same output as test_original (haven't actually read the code ;)
middayc_ has joined #ocaml
middayc has quit [Read error: 104 (Connection reset by peer)]
jlouis has quit ["leaving"]
jlouis has joined #ocaml
jlouis has quit [Client Quit]
jlouis has joined #ocaml
kmeyer has left #ocaml []
mwc has quit [Read error: 110 (Connection timed out)]
jlouis_ has joined #ocaml
mbishop_ is now known as mbishop
jlouis_ has quit ["Changing server"]
jlouis_ has joined #ocaml
ManarD- has joined #ocaml