gildor changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | OCaml 3.12.0+beta1 http://permalink.gmane.org/gmane.comp.lang.caml.inria/49168
iratsu has quit [Ping timeout: 240 seconds]
sepp2k has quit [Quit: Leaving.]
iratsu has joined #ocaml
jakedouglas has quit [Quit: Leaving.]
derdon has quit [Ping timeout: 260 seconds]
joewilliams_away is now known as joewilliams
alexyk has joined #ocaml
alexyk has quit [Quit: alexyk]
Edward__ has quit []
joewilliams is now known as joewilliams_away
alexyk has joined #ocaml
alexyk has quit [Quit: alexyk]
joewilliams_away is now known as joewilliams
alexyk has joined #ocaml
optimality has joined #ocaml
optimality has quit [Quit: optimality]
elehack has quit [Quit: not a typewriter]
jakedouglas has joined #ocaml
Associat0r has joined #ocaml
psnively has joined #ocaml
psnively has quit [Client Quit]
Associat0r has quit [Quit: Associat0r]
joewilliams is now known as joewilliams_away
caligula__ has joined #ocaml
caligula_ has quit [Ping timeout: 264 seconds]
aja has joined #ocaml
ulfdoz has joined #ocaml
Amorphous has quit [Ping timeout: 248 seconds]
alexyk has quit [Quit: alexyk]
Amorphous has joined #ocaml
jakedouglas has quit [Quit: Leaving.]
coucou747 has joined #ocaml
aja has quit [Read error: Connection reset by peer]
ygrek has joined #ocaml
ikaros has joined #ocaml
hyperboreean has quit [*.net *.split]
alpounet has quit [*.net *.split]
svenl has quit [*.net *.split]
adrien has quit [*.net *.split]
alpounet has joined #ocaml
hyperboreean has joined #ocaml
adrien has joined #ocaml
svenl has joined #ocaml
oriba has joined #ocaml
adrien has quit [Quit: leaving]
adrien has joined #ocaml
seafood has joined #ocaml
ygrek has quit [Ping timeout: 245 seconds]
adrien has quit [Quit: leaving]
adrien has joined #ocaml
oriba has quit [Quit: Verlassend]
Yoric has joined #ocaml
sepp2k has joined #ocaml
<gildor> adrien: indeed, if you put your source in src/ you would not have seen the bug, this is what I do and that's the reason why I don't spotted the bug before release 0.1.0
<gildor> adrien: You can perfectly create an _oasis file with printf. Do you have a look at OASIS -quickstart to write your _oasis file?
<adrien> gildor: ok, good, I only put the files in the toplevel folder because I was testing oasis, I won't be impacted by this problem
<adrien> and I played with -quickstart, it looked straight-forward but I was wondering if there could be a catch somewhere, good to know there's none ;-)
Associat0r has joined #ocaml
derdon has joined #ocaml
ikaros_ has joined #ocaml
derdon has quit [Client Quit]
derdon has joined #ocaml
ikaros has quit [Ping timeout: 265 seconds]
_unK has joined #ocaml
seafood has quit [Quit: seafood]
ygrek has joined #ocaml
seafood has joined #ocaml
alexyk has joined #ocaml
alexyk has quit [Quit: alexyk]
psnively has joined #ocaml
psnively has left #ocaml []
seafood has quit [Quit: seafood]
ikaros_ has quit [Quit: Leave the magic to Houdini]
seafood has joined #ocaml
seafood has quit [Client Quit]
seafood has joined #ocaml
Yoric has quit [Quit: Yoric]
dandelions has joined #ocaml
dandelions has left #ocaml []
ygrek has quit [Ping timeout: 245 seconds]
seafood has quit [Quit: seafood]
ygrek has joined #ocaml
alexyk has joined #ocaml
elehack has joined #ocaml
<hcarty> Has anyone here successfully built OCaml Editor? I'd like to try it out under GODI but I haven't been successful so far.
<derdon> nope, I haven't
<hcarty> A Not_found exception is raised, but the compilation script is a .ml run with ocaml, so it doesn't give a backtrace
<derdon> hcarty: why didn't you try to contact the developer of the program?
<hcarty> derdon: It's on my todo list :-)
<hcarty> I'm hoping to get at least a basic GODI package for PLplot together this weekend.
<elehack> hcarty: I tried to build it yesterday, but with no success.
<elehack> I got past the Not_found error by setting the OCAMLLIB environment variable (on Ubuntu, to /usr/lib/ocaml)
<elehack> but then had further build errors.
<hcarty> elehack: Thanks, setting OCAMLLIB fixed the Not_found error for me too
<hcarty> I set OCAMLLIB to `ocamlc -where` and put symlinks for lablgtk2 (already exists) and xml-light in `ocamlc -where`
<hcarty> elehack: With the symlink I was able to get it to compile
<hcarty> elehack: It doesn't seem to work fully, but it edits files and does syntax highlighting.
<thelema> open BatteriesL (* batteries w/ extra labels *)
<thelema> open BatteriesE (* batteries w/ fewer exceptions *)
ecc has quit [Quit: Leaving]
<elehack> hcarty: did you get any cannot-find-module errors?
<elehack> I see things like "Unbound module Project"
<elehack> err, might be because my OCaml source tree is unbuilt.
<hcarty> elehack: I built the OCaml source tree, so that may be part of it
<hcarty> thelema: That sounds appealing.
<thelema> hcarty: almost done, testing now
<thelema> there's not that many modules with exceptionless
<elehack> I currently have the OCaml source tree building, hopefully that will fix it.
<derdon> thelema: and this is good because we all love exceptions! :)
<elehack> What impact will the various flavors (exceptionless, labelled, standard) of Batteries have on the general readability of OCaml code?
<elehack> will e.g. List.find behave differently based on which 'open' is at the top of the file? and is this a good thing for sharing code between authors and between modules?
<thelema> Yes, List.find will behave differently depending on which open is at the top, the compiler will raise issues on any incompatibility between expected and actual open
<thelema> this is a minor problem, and would be the same if people opened the exceptionless modules themselves at the top of the file
<elehack> yes, this is true. and the compiler catching it mitigates many of the effects.
<elehack> it's mostly the human aspect I'm thinking about: one can't just say "this code uses Batteries, I can use it."
<elehack> you have to figure out which flavor it uses, and adapt it to the flavor you're using if it's different.
<elehack> which is unavoidable to a certain extent.
<thelema> or just open the correct flavor before it and reopen your previous flavor after
<elehack> true.
<thelema> lots more exceptionless to write...
<thelema> and it's all pretty straightforward code, just lots of it
* elehack wonders if it would be possible to generate some of it
<elehack> generation should definitely be possible if a wrapper that catches the exception and returns appropriately is sufficient. a bit harder if it should be a true exceptionless implementation.
<elehack> (although stubs with helper functions might be sufficiently easy and involve less work than writing an exceptionless preprocessor.
<thelema> looking for exceptions, catching them and returning an option...
<thelema> this is easy: let choose t = try Some (choose t) with Not_found -> None
<derdon> thelema: but why do you write it? I mean, the user of the lib could cath the exception himself
<elehack> yeah, and can be abstracted with a function easily.
<thelema> this might be trickier: let find k t = try Some (find k t) with Not_found -> None
metasyntax has joined #ocaml
<thelema> elehack: iirc, we have taht function already (somewhere)
<thelema> derdon: almost all of batteries could be easily written by the user. Which is why it's not in stdlib.
<elehack> a quick perusal of the value index doesn't reveal it :-/
<derdon> thelema: hm. but are the exceptionless* modules really necessary?
<thelema> derdon: they're a convenience. some people like option types being returned
<elehack> I seem to remember a discussion a while ago about Exceptionless vs. introducing, say, find_opt alongside find.
<derdon> thelema: ok. probably, it depends on the problem
<elehack> (I think it was on the OCaml mailing list, as the Batteries project was first being birthed).
<thelema> elehack: core takes the second strategy, so far we're on track for the first. There's no reason we can't have both.
* elehack likes the find_opt strategy
<hcarty> IIRC, core does the reverse - find and find_exn
<thelema> as you use the code, anytime you want a *_opt function, write it and add it to batteries.
<elehack> ok.
<thelema> hcarty: yes, true. we're keeping backwards compatibility, so we can't do that in general.
Yoric has joined #ocaml
<thelema> Yoric: do you remember why Exceptionless modules > foo_exn/foo_opt?
drunK has joined #ocaml
<hcarty> thelema: Yes, I think that, if the Exceptionless modules are dropped, then find and find_opt would be the better choice for Batteries
<hcarty> s/I think/I agree/
* Yoric doesn't fully understand the question.
* Yoric will have to go, though.
<Yoric> Still, hi everybody :)
<thelema> Yoric: hi and bye
<hcarty> Yoric: Hello
Yoric has quit [Client Quit]
_unK has quit [Ping timeout: 260 seconds]
<elehack> I think that dropping Exceptionless and using find/find_opt would have the benefit of allowing a reader to look at a piece of code, knowing only that it uses Batteries, and immediately understand its behavior.
<elehack> If Batteries is going to be a standard base for OCaml, I think one aspect of that is providing a standard basis for people to communicate about OCaml code.
<thelema> I agree this is a good thing.
<mfp> any news about the issue with camomile?
<thelema> none I know of
<mfp> it's the reason why I've found myself using extlib instead of batteries
<mfp> when I wanted self-contained executables
<derdon> only windows-users and java-developers want self-contained executables
<derdon> especially the latter
<mfp> and people who want to deploy stuff w/o installing devel pkgs on servers
<flux> I must say I've liked self-contained executables when dealing with random hosts and I like to run my tools on them
alexyk has quit [Quit: alexyk]
<hcarty> elehack: I use the Exceptionless modules in Batteries heavily, but I agree that *_opt would provide an easier to parse interface
<hcarty> BatteriesL and BatteriesE still also sound appealing to me though - makes it harder to accidentally let an exception slip through.
<hcarty> BatteriesE does that is.
alexyk has joined #ocaml
jeddhaberstro has joined #ocaml
<thelema> in general, it should be pretty obvious whether a piece of code is using labels or not. Similarly, if there's exception handling code nearby or opt matching code nearby, you can tell whether that code is exceptionless
<hcarty> thelema: Using exceptionless modules provides a nice tool for refactoring, but that may not be a good enough reason to keep it around.
<elehack> For labels, I agree; it is obvious. For exceptions, it's not difficult to tell, but requires a deeper inspection. I like reducing cognitive load.
itewsh has joined #ocaml
<mfp> anybody interested in a minimalistic syntax extension for easier sqlite usage?
<mfp> # insert db sql"insert into test(name, age, some_binary_data) values(%s, %d, %a)";;
<mfp> - : string -> int -> ('_a -> string) -> '_a -> int64 = <fun>
<thelema> mfp: mmm, very nice
<mfp> # select db sql"select @s{name},@s?{age} from test where id=%d";;
<mfp> - : int -> list (string * option string) = <fun>
<mfp> @d?{age} even :)
<thelema> lazy list/enum output possible?
<mfp> yes, trivially
<thelema> hmm, I wonder how well this'd fit into batteries... probably the same as pcre - external dependency chain... :(
<mfp> depends on sqlite3
<mfp> which includes C bindings
<thelema> that's the problem...
<mfp> hmmm
<mfp> in fact the syntax extension itself does not depend on sqlite3
<mfp> the generated code does, obviously
<thelema> maybe the way to handle this is to work on the unified installer for ocaml + batteries + needed libraries
<thelema> well, the syntax extension seems like it'd fit in well with estring...
<mfp> indeed, it's implemented atop estring :)
<thelema> naturally
<elehack> pcre is easily installable with godi, and presumably will be with OASIS; sqlite is also easily installed (albeit perhaps not quite so easily).
<elehack> is that sufficient ease to make it workable?
<hcarty> mfp: That sounds really useful. How easy would it be to extend to Mysql?
<thelema> Since there's no dependency to compile and only runtime dependency if it's used, I think it'd be fine to add to batteries
<hcarty> Is it a good idea to add something with an external dependency which could so easily get out of sync
<hcarty> ?
<mfp> hcarty: /me taking a look at the MySQL C API...
<thelema> hcarty: out of sync how?
<thelema> hcarty: the ocaml-sqlite library?
<hcarty> thelema: Yes
alexyk has quit [Quit: alexyk]
<thelema> hmm... We already have to deal with ocaml itself changing under us, and that's not so bad. how difficult could it be for ocaml-sqlite?
<hcarty> thelema: It seems like something that would be better either as a full dependency or an add-on to the sqlite bindings
<thelema> how would depending on ocaml-sqlite help things?
<hcarty> There are a number of modules which would benefit Batteries - camlzip, Sqlite3...
<mfp> hcarty: it's quite doable in fact. MySQL's API has only val exec : dbd -> string -> result (no separate functions to prepare a statement and bind params, unlike sqlite), so it'd have to go through a string
<hcarty> thelema: Testing
<thelema> our test harness could depend on sqlite
ygrek has quit [Ping timeout: 245 seconds]
<mfp> thelema: the generated code does depend on sqlite3, but also on some lib code which would have to be compiled + installed when batteries is built
<mfp> ... which leads me to ask, was there any previous discussion about optional dependencies?
<mfp> for instance, the above syntax extension + lib could only be built if sqlite3 is found at build time
<mfp> the same could be done for the camlzip-dependent functionality
Anarchos has joined #ocaml
<thelema> I'd really prefer avoiding them. if you have batteries, you should have a consistent set of functionality
<hcarty> mfp: BatZip and BatSqlite3, but no inclusion in Batteries
<mfp> this requires that the optional parts be independent
<mfp> hcarty: well, batteries.ml could be generated at compile time to include the optional modules that were built
<mfp> thelema: the problem is that this limits enormously the scope of batteries
<mfp> and brings it down to the lowest common denominator = uh windows?
<mfp> "everybody" else can install easily with apt-get or yum etc.
<thelema> is there even a rpm package for batteries?
<hcarty> mfp: Batteries becomes poorly defined at that point
<mfp> google does return some results for ocaml batteries rpm, but it doesn't seem to be in fedora https://admin.fedoraproject.org/pkgdb/acls/list/o*?_csrf_token=a6fb23a7065994a98d59118229fac1ed2a745837
<hcarty> That seems like a bad idea
<mfp> you can define batteries as the superset of all the available Bat* modules, with "graceful degradation"
<hcarty> It would be a much cleaner solution to either make these modules true dependencies or keep the external dependency modules as Bat* stand-alones.
<mfp> so the diff is that they wouldn't be in the Batteries.* hierarchy?
<hcarty> mfp: What happens when a user tries to compile Batteries + Sqlite3 code against vanilla Batteries?
<hcarty> mfp: Yes
jakedouglas has joined #ocaml
<hcarty> Without a constant Batteries, there is no external way to verify if the user has the relevant dependencies.
<mfp> he gets unbound values and has got to ocaml-install sqlite3 and rebuild batteries
<mfp> it can depend on the batteries.xxx subpackages
<hcarty> mfp: But that doesn't work for the deb, rpm or GODI case
<mfp> right
<hcarty> mfp: batteries.sqlite3 could pull in BatSqlite3, which would presumably work
<mfp> would have to compose batteries.cmo somehow at (package) install time if we want to have a single hierarchy
<mfp> .cma (.cmxa) and .cmi even
<hcarty> Which doesn't seem like it would work nicely with OS package management
<mfp> sounds hard indeed
<hcarty> But if the modules with external dependencies are provided outside of the Batteries hierarchy then the problem is alleviated.
<mfp> reminds me of Yoric[DT]'s proposal for extensible namespaces
<mfp> which received essentially no answer on caml-list :-|
<hcarty> They would be nice to have. Perl's namespace handling is nice for things like this.
<elehack> one "extensible namespace" kind of thing that could be done: a syntax extension that adds a "use Batteries" syntax of some kind and sets up the requested modules with their dependencies.
<elehack> so you can do "use Batteries {UTF8 Enum IO}"
<elehack> and it lets you have the convenience of "open Batteries" without the executable bloat, and allows for batteries add-ons/subpackages (batteries.sqlite, etc.)
<thelema> I'd be up for it except it'd pretty much require camlp4 for batteries, and I want batteries default usability w/o camlp4
<elehack> maybe keep the existing Batteries module, and make this an optional feature if you are OK with camlp4 and want to reduce binary size?
<thelema> I'd be fine with that.
<elehack> on dependencies: so far, the two dependencies that have come up (PCRE and sqlite3) should be fully usable with relatively little effort on Windows. Does that impact their suitability as dependencies?
<mfp> - [use List] to open all the modules registered as providing namespace [List]
<mfp> - [import List] to locally rebind [List] to a module obtained by including all the modules registered as providing namespace [List]
<elehack> for things like sqlite3, though, I would also be thrilled if other libraries such as the sqlite3 bindings would start using Batteries and providing e.g. Enum interfaces themselves.
<thelema> elehack: yes, it makes them more possibly mandatory dependencies
<mfp> thelema: what's the reason for "I want batteries default usability w/o camlp4"? Cannot camlp4 be assumed to be available everywhere where OCaml is to be found?
<thelema> yes, but many (myself included) find it a bad fit for where it's not needed. kinda like not using objects everywhere even though they're available.
<mfp> to me, some hypothetical syntax extension to manage namespaces is no different from open Batteries at the top of the file
<mfp> in particular, it differs from objects in that it doesn't "contaminate" other code
<mfp> so you are not forced to use camlp4 just because something else did
<hcarty> Didn't the original Batteries include a syntax extension doing something like this?
<hcarty> Something along the lines of module List = List with Exceptionless, Labels
<mfp> yes, it had an extension that added open Batteries automatically at the top of the file
<thelema> hcarty: previous batteries had a syntax extension that added [open batteries] to the top of the file
<mfp> I don't like that implicit magic
<hcarty> thelema, mfp: That too, but I'm thinking of the module building one
<mfp> but the proposal from Yoric[DT] (orig by David Allsopp) looks good to me
<hcarty> Very similar to what elehack propoised
<thelema> mfp: I appreciate that camlp4 doesn't contaminate other code. but it contaminates the code it's being used on badly enough, and there's no indication in the source what's going on.
<hcarty> proposed
<thelema> mfp: I really dislike the compile-time changes needed for camlp4
<mfp> thelema: well, it would in this case --- -> use List <- but I see where you're going (lack of in-file pp flags)
<elehack> camlp4 can make the build system really hairy sometimes...
alexyk has joined #ocaml
<mfp> anyway it's up to the devel to choose, isn't it?
<mfp> if he doesn't mind -package namespaces -syntax camlp4o (for instance) in his build system, he can use use List
alexyk has quit [Client Quit]
<mfp> if he dislikes it, he's got to open the ExtList_from_lib_foo modules himself
<mfp> in fact, such an extension is more "optional" than e.g. batteries's pa_string.syntax
<mfp> <- how do you define p"%d" without the syntax extension?
<hcarty> elehack: Your "use Batteries {UTF8 Enum IO}" idea was in the original Batteries
<elehack> hcarty: I should go dig for that code. Could save the effort (albeit minimal) of writing it from scratch.
<mfp> you cannot really use Batteries.Print without pa_string, can you?
<thelema> mfp: I find myself doing fine with List.print and co.
<mfp> only as long as it doesn't involve format strings
<metasyntax> Is there a semi-standard module for testing OCaml code? Something like *unit in many other languages perhaps?
<thelema> I use fprintf "%a" a lot
<elehack> metasyntax: I usually use oUnit
<elehack> there are a few others, such as FORT.
<mfp> iow. when you can just reuse an existing BatInnerIO.output 'a -> 'b -> unit function
<mfp> thelema: Batteries'?
<mfp> thelema: Print.fprintf "%a";; Error: This expression has type string but an expression was expected of type BatInnerIO.output 'a
<metasyntax> elehack: Thanks, I'll check them out.
<thelema> Printf.fprintf oc "Stuff: %a" print_stuff stuff
<mfp> you really want p"%a" OR Printf.fprintf which means... not using Batteries
<mfp> haha
<mfp> that proves it then, you cannot use Batteries' Print module easily without pa_string
<thelema> let index_print print_v oc i v = fprintf oc "#%d) %a\n" i print_v v
<thelema> maybe I should try pa_string sometime, but I seem to do fine w/o it.
<thelema> adding Pair.print helped a lot
* elehack has also gotten along w/o pa_string until recently, when he needed to write UTF8 strings in test cases
<elehack> but I also haven't yet used BatPrint.
<hcarty> BatPrint + syntax is excellent.
<thelema> so I hear
<hcarty> Particularly with named parameters and how easy it is to extend.
<hcarty> (Print.printf p"And the we print %{My_module.t}" my_module_t_val) is worth its weight in code
<thelema> I'll see if I can convert some of my existing prints over to that
Yoric has joined #ocaml
<hcarty> Could work well for building SQL statements in a semi-sane manner.
derdon has quit [Ping timeout: 240 seconds]
<elehack> hcarty: I can't seem to find that syntax support. pa_batteries in the last beta just adds a couple of open lines.
<hcarty> elehack: I think it's in pa_openin
<hcarty> elehack: In Batteries' pa_openin that is
<hcarty> elehack: Yes, it's in src/syntax/pa_openin/
<elehack> OK, looking at the documentation that doesn't seem to be quite what I was thinking of.
sepp2k1 has joined #ocaml
<elehack> although the 'module E = Enum with...' construct is similar.
sepp2k has quit [Ping timeout: 265 seconds]
<hcarty> elehack: That's the part I was referring to
<hcarty> elehack: IIRC, that syntax was selected because it added the fewest keywords
<hcarty> Or something along those lines
<hcarty> "with" was the only thing new, and pa_with was already provided with Batteries
<elehack> kk. it seems to require a bit more work on the client end (the resulting module then may need to be opened, etc.)
<hcarty> elehack: "module E = Enum with Exceptionless" will give you "module E = struct include Enum include Exceptionless end"
<elehack> yes, but then I would need to say "module E = List with BatList" to use Batteries' list.
<elehack> Easier than the alternative for not using "open Batteries"
<elehack> but still seems to be not as convenient as saying "give me these Batteries components"
<hcarty> elehack: I agree
<hcarty> I would prefer something simpler. Could this pa_openin material be used for that purpose?
<elehack> probably. I haven't sufficiently digested pa_openin to know what all it's doing.
<elehack> I'm thinking, though, that this will need some more sophistication.
<elehack> to automatically handle, for example, the composition of List and BatList that the Batteries module does.
<elehack> Perhaps a config file in the batteries directory that specifies the importable modules, along with whatever modules need to be merged with them.
<elehack> then the extension could use findlib to locate the config file and do its magic.
<elehack> it winds up being very similar to the namespaces proposal, but a bit more fine-tuned to batteries.
<hcarty> elehack: It's probably reasonable to assum a naming convention
<hcarty> *assume
<hcarty> List = List + BatList, Array = Array + BatArray
<elehack> yes, that works for merges with the stdlib modules.
<elehack> but it shouldn't get confused on IO.
<elehack> or anything else not in the stdlib.
<hcarty> Very true
<elehack> so maybe "use batteries [List; IO; Enum]"
<elehack> and it goes and looks up the "batteries" findlib package to get the config file (failing if there is no config file)
<elehack> and the config file says
<elehack> List = BatList + List
<elehack> or something simple like that.
<elehack> err, it'd need to be the other order.
<elehack> Eventually, it could be good to have these things composable, but that's not needed in the first edition.
<hcarty> It may be a good idea to use "open" or "include" to avoid stepping on existing code with values named use
<elehack> yeah
<elehack> and the package name probably needs to be a string rather than a symbol to handle a wider variety of packages.
<hcarty> It sounds like a very handy syntax though, particularly if it's usable by any module
<elehack> I'll throw it in the Batteries bug tracker tagged 'wishlist' to capture the concept.
<hcarty> elehack: One big downside is that this requires a findlib package install to work. It might be nice to allow this for local modules as well.
* Yoric likes the idea of "use batteries [List; IO; Enum]"
<hcarty> "use mylib [List; Array]" with mylibList.ml and mylibArray.ml in the current directory for example.
<elehack> yes, doing it without the findlib install could be beneficial.
<elehack> If the config file is 'modules', perhaps it could also look for 'pkg/modules' and 'pkg.modules' in the current directory.
* elehack has now logged this as issue 68
Tianon has quit [Ping timeout: 260 seconds]
derdon has joined #ocaml
Tianon has joined #ocaml
Tianon has quit [Changing host]
Tianon has joined #ocaml
Yoric has quit [Quit: Yoric]
Yoric has joined #ocaml
Yoric_ has joined #ocaml
Yoric has quit [Read error: Connection reset by peer]
Yoric_ is now known as Yoric
<Yoric> I personally believe that any attempt to duplicate the mechanisms of findlib is probably not a good idea
<hcarty> Yoric: Findlib doesn't help with modules which have not been installed (ex. modules which are part of the project you are working on)
<elehack> hcarty: you can set OCAMLPATH to the root of your source tree to have findlib search it for uninstalled modules. would that be sufficient?
<elehack> I have done it successfully in one of my codebases.
<hcarty> elehack: That seems reasonable, at least for a first version
<flux> hcarty, hm, how does findlib work with the project one is working on?
<hcarty> Experience using the actual syntax may indicate how local modules can be handled better.
<hcarty> flux: It doesn't as far as I know
<elehack> flux: it doesn't do anything in particular for it. You can force it to by organizing your source tree carefully and setting `OCAMLPATH` in your build system.
<flux> it would be a fine feature to have, though. like automatically finding META-files in PWD or some parameter/environment-directed location.
<flux> findlib has been pretty much perfect for quite some time, though..
<hcarty> Is anyone here on GODI interested in testing an experimental GODI-installable PLplot?
<elehack> what does PLplot do?
<hcarty> elehack: It's a plotting package - line/point/contour/etc. plots
<flux> I have GODI on one local host, but I haven't upgraded it for a long time.
<adrien> gildor: with oasis, trying to build a project with C: the .c file #include's a .h file but it doesn't get copied in _build/ and isn't not found later on: adding it to CSources isn't enough (I can easily work-around that if needed)
<hcarty> elehack: http://plplot.sf.net/
<elehack> that sounds potentially useful, but I won't be around a combination of GODI and potential need for such a package until this fall.
<elehack> I could test the build scripts on my GODI install though, if you just need installation tests.
<hcarty> elehack: If you don't mind, I would appreciate it
<elehack> sure. where do I get the scripts to test?
<hcarty> It requires having cmake installed, having the requirements for ocaml-cairo installed, and adding a path to LD_LIBRARY_CONF after the install to test
<elehack> kk
<hcarty> elehack: Add the line "GODI_BUILD_SITES += http://0ok.org/ocaml/godi/3.11/" to $GODI_BASE/etc/godi.conf
<hcarty> Then it _should_ be a matter of updating the GODI package list and building + installing the godi-plplot package
<hcarty> It worked on my system, but as one of the developers for the library and the OCaml bindings I'm not a very good test of usability.
<elehack> building now
<hcarty> elehack: Thank you!
<elehack> and plplot looks like it could be a valuable addition to my arsenal this fall.
<elehack> I use ocaml for lots of my data processing and algorithm implementation at school; being able to generate nice plots from that could be quite useful.
<hcarty> I wrote the OCaml bindings so that I could do my graduate research plotting from OCaml
<hcarty> I hope that others find it useful as well
<elehack> I've encountered one build problem, but it isn't your fault: ocaml-cairo failed to install with lablgtk2 support disabled.
<hcarty> I need to add a configuration option to not require ocaml-cairo. The Cairo support is provided through a separate module.
<hcarty> If the ocaml-cairo GODI package doesn't build with lablgtk2 then that should be fixed as well at some point.
<elehack> yeah
* elehack has reported the godi-cairo failure in GODI's bugtracker
* elehack is currently rebuilding GODI to try to clear up a bizarre lablgtk2 build failure
<hcarty> elehack: I need to go, but if you have time please leave a message here and/or email me with the results. I appreciate the testing!
<hcarty> If you try to use PLplot and it gives you external function not available errors then you can "export LD_LIBRARY_PATH=$GODI_BASE/plplot/lib:$LD_LIBRARY_PATH"
<hcarty> There is a brief tutorial in the PLplot manual in the OCaml chapter as well
<elehack> OK, will do.
skrewla has left #ocaml []
derdon has quit [Ping timeout: 248 seconds]
jakedouglas has quit [Quit: Leaving.]
Associat0r has quit [Quit: Associat0r]
ulfdoz has quit [Ping timeout: 240 seconds]
Yoric has quit [Quit: Yoric]
Yoric has joined #ocaml
Yoric has quit [Remote host closed the connection]
Yoric has joined #ocaml
<Yoric> hcarty: "Findlib doesn't help with modules which have not been installed (ex. modules which are part of the project you are working on)" -- ok, good remark
thieusoai has joined #ocaml
thieusoai has quit [Client Quit]
thieusoai has joined #ocaml
thieusoai has quit [Client Quit]
thieusoai has joined #ocaml
itewsh has quit [Quit: o/]
jeddhaberstro_ has joined #ocaml
<gildor> adrien: you are right, please submit a bug with your work around, I will try to find a way to implement it
<gildor> adrien: about OASIS and .h files
jeddhaberstro has quit [Ping timeout: 264 seconds]
jeddhaberstro_ is now known as jeddhaberstro
derdon has joined #ocaml
Yoric has quit [Quit: Yoric]
jakedouglas has joined #ocaml
jakedouglas has quit [Quit: Leaving.]
Anarchos has quit [Quit: Vision[0.9.7-H-090423]: i've been blurred!]