caml-list - the Caml user's mailing list
 help / color / mirror / Atom feed
* Ocamlbuild with findlib + camlp4
@ 2008-03-05 13:41 Dario Teixeira
  2008-03-05 15:08 ` [Caml-list] " Romain Bardou
  0 siblings, 1 reply; 22+ messages in thread
From: Dario Teixeira @ 2008-03-05 13:41 UTC (permalink / raw)
  To: caml-list

Hi,

I'm trying to create an Ocamlbuild plugin for an application that uses
PG'OCaml.  This library relies on a Camlp4 syntax extension, and comes by
default with a META file for findlib that enables one to simply type on the
command line:

ocamlfind ocamlc -package pgocaml.statements -syntax camlp4o -c test.ml

I still don't grok Ocamlbuild quite enough to automate this behaviour.
The best I have so far is the plugin below; it adds support for findlib, and
creates a "use_pgocaml" tag that explicitly loads all the modules required by
the syntax extension.  Note that "use_pgocaml" makes no use of the findlib
support; while it works, this is of course hackish and ugly.  Ideally,
"use_pgocaml" should simply tell ocamlbuild to use findlib to automatically
load all the modules.

Any ideas on how this could be achieved?  (And incidentally, I vote for
"built-in findlib support" as my #1 wish for Ocamlbuild).

Thanks in advance!
Dario Teixeira


##############################################################################

open Ocamlbuild_plugin
open Command

let ocamlfind x =
        let packages = "pcre,extlib,lwt,ocsigen,pgocaml,json-wheel" in
        S[A"ocamlfind"; x; A"-package"; A packages];;

dispatch begin function

        | Before_options ->
                Options.ocamlc := ocamlfind & A"ocamlc";
                Options.ocamlopt := ocamlfind & A"ocamlopt";
                Options.ocamldep := ocamlfind & A"ocamldep"

        | After_rules ->
                flag ["ocaml"; "link"] (A"-linkpkg");

		let root = "/home/dario/.godi/lib/ocaml/" in
                let str = root ^ "std-lib/str.cma"
                and pcre = root ^ "pkg-lib/pcre/pcre.cma"
                and extlib = root ^ "pkg-lib/extlib/extLib.cma"
                and calendar = root ^ "pkg-lib/calendar/calendar.cma"
                and csv = root ^ "pkg-lib/csv/csv.cma"
                and pgocaml = root ^ "site-lib/pgocaml/pgocaml.cma"
                and pa_pgsql = root ^ "site-lib/pgocaml/pa_pgsql.cmo" in
                flag ["ocaml"; "pp"; "use_pgsql"] (S[A str; A pcre; A extlib; A
calendar; A csv; A pgocaml; A pa_pgsql])

        | _ -> ()
end;;

##############################################################################





      ___________________________________________________________ 
Rise to the challenge for Sport Relief with Yahoo! For Good  

http://uk.promotions.yahoo.com/forgood/


^ permalink raw reply	[flat|nested] 22+ messages in thread

* Re: [Caml-list] Ocamlbuild with findlib + camlp4
  2008-03-05 13:41 Ocamlbuild with findlib + camlp4 Dario Teixeira
@ 2008-03-05 15:08 ` Romain Bardou
  2008-03-06 15:31   ` Dario Teixeira
  0 siblings, 1 reply; 22+ messages in thread
From: Romain Bardou @ 2008-03-05 15:08 UTC (permalink / raw)
  To: Dario Teixeira; +Cc: caml-list

Hello,

> 		let root = "/home/dario/.godi/lib/ocaml/" in
>                 let str = root ^ "std-lib/str.cma"
>                 and pcre = root ^ "pkg-lib/pcre/pcre.cma"
>                 and extlib = root ^ "pkg-lib/extlib/extLib.cma"
>                 and calendar = root ^ "pkg-lib/calendar/calendar.cma"
>                 and csv = root ^ "pkg-lib/csv/csv.cma"
>                 and pgocaml = root ^ "site-lib/pgocaml/pgocaml.cma"
>                 and pa_pgsql = root ^ "site-lib/pgocaml/pa_pgsql.cmo" in
>                 flag ["ocaml"; "pp"; "use_pgsql"] (S[A str; A pcre; A extlib; A
> calendar; A csv; A pgocaml; A pa_pgsql])

It seems to me that this lines are useless if you use ocamlfind, because 
you:
- changed the ocamlc, ocamlopt and ocamldep variables
- added the -linkpkg option when linking
So normally you shouldn't even have to deal with cma files. Well, at 
least if they have META files.

Moreover, these lines mean that packages str and so on will only be used 
when your files are tagged with use_pgsql. Is it really what you want?

You did nothing to add the "-syntax camlp4o" option.

I have no experience of ocamlbuild with camlp4 extensions but I guess in 
your case I would list all packages correctly in the "let packages = 
..." definition (unless you don't want to add the -package option for 
every file?), tag my files which use the camlp4 extension with 
"use_pgsql", and add a flag such as:

flag ["ocaml"; "use_pgsql"] (S[A "-syntax"; A "camlp4o"])

You could also add the package pgocaml.statements only when using this flag:

flag ["ocaml"; "use_pgsql"] (S[A "-package"; A "pgocaml.statements"])

If you do this you don't have to add the pgocaml.statements package in 
the "let packages = ..." definition of your plugin.

Basically I think what you need is a combination of the two following 
examples from the Wiki:
http://brion.inria.fr/gallium/index.php/A_plugin_for_camlp4_syntax_extension_%28pa_openin%29
http://brion.inria.fr/gallium/index.php/Using_ocamlfind_with_ocamlbuild

-- 
Romain Bardou


^ permalink raw reply	[flat|nested] 22+ messages in thread

* Re: [Caml-list] Ocamlbuild with findlib + camlp4
  2008-03-05 15:08 ` [Caml-list] " Romain Bardou
@ 2008-03-06 15:31   ` Dario Teixeira
  2008-03-06 15:46     ` Pietro Abate
  2008-03-07  9:26     ` Romain Bardou
  0 siblings, 2 replies; 22+ messages in thread
From: Dario Teixeira @ 2008-03-06 15:31 UTC (permalink / raw)
  To: Romain Bardou; +Cc: caml-list

Hi,

And thanks for the reply.

> Moreover, these lines mean that packages str and so on will only be used 
> when your files are tagged with use_pgsql. Is it really what you want?

Yes.

> I have no experience of ocamlbuild with camlp4 extensions but I guess in 
> your case I would list all packages correctly in the "let packages = 
> ..." definition (unless you don't want to add the -package option for 
> every file?), tag my files which use the camlp4 extension with 
> "use_pgsql", and add a flag such as:

I've been mucking around with the myocamlbuild.ml plugin but still haven't
managed to achieve what I want.  And judging from a previous message by
Nicolas Pouillard, it may be altogether impossible with the current version
of Ocamlbuild.

Anyway, ideally one should be able to specify in the _tags file the findlib
packages that each ml file depends upon.  Suppose that by default you wanted
your ml files to use the "extlib,lwt,ocsigen,pgocaml" packages, but you also
had a "database.ml" file that used the PG'OCaml syntax extension, and therefore
should be preprocessed using the instructions in the "pgocaml.statements"
package.  I could define a _tags file as something like this:

true: pkg(extlib,lwt,ocsigen,pgocaml)
<database.ml>: camlp4, pkg(pgocaml.statements)

Any thoughts on how this could be achieved?  (I'm not even sure if
Ocamlbuild's tags can be parameterised).  This would go a long way
towards simplifying the use of syntax extensions that we've been
discussing in the OSR thread.

Thanks in advance,
Dario Teixeira



      __________________________________________________________
Sent from Yahoo! Mail.
The World's Favourite Email http://uk.docs.yahoo.com/nowyoucan.html


^ permalink raw reply	[flat|nested] 22+ messages in thread

* Re: [Caml-list] Ocamlbuild with findlib + camlp4
  2008-03-06 15:31   ` Dario Teixeira
@ 2008-03-06 15:46     ` Pietro Abate
  2008-03-06 19:45       ` Dario Teixeira
  2008-03-07  9:26     ` Romain Bardou
  1 sibling, 1 reply; 22+ messages in thread
From: Pietro Abate @ 2008-03-06 15:46 UTC (permalink / raw)
  To: caml-list

On Thu, Mar 06, 2008 at 03:31:53PM +0000, Dario Teixeira wrote:
> Any thoughts on how this could be achieved?  (I'm not even sure if
> Ocamlbuild's tags can be parameterised).  This would go a long way
> towards simplifying the use of syntax extensions that we've been
> discussing in the OSR thread.

not tested, but I've a piece of code that has a similar mix...

what's about:

_tags:
<database.ml>: camlp4o, pgocaml.statements

and 

(almost verbatim from camlp4 docs) myocamlbuild.ml:

-----------------
open Ocamlbuild_plugin;;
open Command;;

let packages = "extlib,lwt,ocsigen,pgocaml";;

let ocamlfind x = S[A"ocamlfind"; x; A"-package"; A packages];;

dispatch begin function
| Before_options ->
    Options.ocamlc := ocamlfind& A"ocamlc";
    Options.ocamlopt := ocamlfind& A"ocamlopt";
| After_rules ->
    flag ["ocaml"; "link"] (A"-linkpkg")
    flag ["ocaml"; "pp"; "pgocaml.statements"] (A"pgocaml.statements.cmo");
    dep  ["ocaml"; "ocamldep"; "pgocaml.statements"] ["pgocaml.statements.cmo"];
 | _ -> ()

| _ -> ()
end;;
---------------------

not an expert ...

:)
p


^ permalink raw reply	[flat|nested] 22+ messages in thread

* Re: [Caml-list] Ocamlbuild with findlib + camlp4
  2008-03-06 15:46     ` Pietro Abate
@ 2008-03-06 19:45       ` Dario Teixeira
  2008-03-06 22:14         ` Pietro Abate
  0 siblings, 1 reply; 22+ messages in thread
From: Dario Teixeira @ 2008-03-06 19:45 UTC (permalink / raw)
  To: Pietro Abate, caml-list

> not tested, but I've a piece of code that has a similar mix...

Hi,

Thanks for the help.  I see -- essentially you're just telling Ocamlbuild
to ignore findlib when dealing with syntax extensions.  Unfortunately
it's not working: the database.ml file never seems to be compiled.  Moreover,
the core of the problem remains: if we're ever going to simplify the use of
syntax extensions, we must somehow tell Ocamlbuild to use findlib.  Any
other thoughts?

Kind regards,
Dario Teixeira



      ___________________________________________________________ 
Rise to the challenge for Sport Relief with Yahoo! For Good  

http://uk.promotions.yahoo.com/forgood/


^ permalink raw reply	[flat|nested] 22+ messages in thread

* Re: [Caml-list] Ocamlbuild with findlib + camlp4
  2008-03-06 19:45       ` Dario Teixeira
@ 2008-03-06 22:14         ` Pietro Abate
  0 siblings, 0 replies; 22+ messages in thread
From: Pietro Abate @ 2008-03-06 22:14 UTC (permalink / raw)
  To: caml-list

On Thu, Mar 06, 2008 at 07:45:05PM +0000, Dario Teixeira wrote:
> Thanks for the help.  I see -- essentially you're just telling Ocamlbuild
> to ignore findlib when dealing with syntax extensions.  Unfortunately
> it's not working: the database.ml file never seems to be compiled.  Moreover,
> the core of the problem remains: if we're ever going to simplify the use of
> syntax extensions, we must somehow tell Ocamlbuild to use findlib.  Any
> other thoughts?

bar.ml is your database module that uses a syntax extension and str 
is loaded via ocamlfind in foo.ml. I guess there is a better way to
use ocamlfind more selectively. For example I don't need to use ocamlfind
to compile the syntax extension.

hope this helps.

pietro

#####$cat _tags 
"pa_float.ml": use_camlp4, pp(camlp4of)
"bar.ml": camlp4o, use_float

#####$cat bar.ml 
let x = Float.( 3/2 - sqrt (1/3) )
let f x =
  Float.( 
    let pi = acos(-1) in
    x/(2*pi) - x**(2/3)
  )

#####$cat foo.ml 

open Str
let x = Bar.x

#####$cat myocamlbuild.ml 
open Ocamlbuild_plugin;;
open Command;;

let packages = "str";; 
 
let ocamlfind x = S[A"ocamlfind"; x; A"-package"; A packages];;
 
dispatch begin function
| Before_options ->
    Options.ocamlc := ocamlfind& A"ocamlc";
    Options.ocamlopt := ocamlfind& A"ocamlopt";

| After_rules ->
    flag ["ocaml"; "pp"; "use_float"] (A"pa_float.cmo");
    flag ["ocaml"; "link"] (A"-linkpkg");
    dep  ["ocaml"; "ocamldep"; "use_float"] ["pa_float.cmo"];
| _ -> ()
end;;

#####$cat pa_float.ml 
module Id = struct
  let name = "pa_float"
  let version = "1.0"
end

open Camlp4

module Make (Syntax : Sig.Camlp4Syntax) = struct
  open Sig
  include Syntax

  class float_subst _loc = object
    inherit Ast.map as super
    method _Loc_t _ = _loc
    method expr =
      function
      | <:expr< ( + ) >> -> <:expr< ( +. ) >>
      | <:expr< ( - ) >> -> <:expr< ( -. ) >>
      | <:expr< ( * ) >> -> <:expr< ( *. ) >>
      | <:expr< ( / ) >> -> <:expr< ( /. ) >>
      | <:expr< $int:i$ >> ->
        let f = float(int_of_string i) in <:expr< $`flo:f$ >>
      | e -> super#expr e
  end;;

  EXTEND Gram
    GLOBAL: expr;

    expr: LEVEL "simple"
    [ [ "Float"; "."; "("; e = SELF; ")" -> (new float_subst _loc)#expr e ]
    ]
    ;
  END
end

let module M = Register.OCamlSyntaxExtension Id Make in ()

#####$ocamlbuild foo.byte -classic-display
/usr/bin/ocamlopt -I /usr/lib/ocaml/3.10.0/ocamlbuild unix.cmxa /usr/lib/ocaml/3.10.0/ocamlbuild/ocamlbuildlib.cmxa myocamlbuild.ml /usr/lib/ocaml/3.10.0/ocamlbuild/ocamlbuild.cmx -o myocamlbuild
/usr/bin/ocamldep -modules foo.ml > foo.ml.depends
/usr/bin/ocamldep -pp camlp4of -modules pa_float.ml > pa_float.ml.depends
ocamlfind ocamlc -package str -c -I +camlp4 -pp camlp4of -o pa_float.cmo pa_float.ml
/usr/bin/ocamldep -pp 'camlp4o pa_float.cmo' -modules bar.ml > bar.ml.depends
ocamlfind ocamlc -package str -c -pp 'camlp4o pa_float.cmo' -o bar.cmo bar.ml
ocamlfind ocamlc -package str -c -o foo.cmo foo.ml
ocamlfind ocamlc -package str -linkpkg bar.cmo foo.cmo -o foo.byte


^ permalink raw reply	[flat|nested] 22+ messages in thread

* Re: [Caml-list] Ocamlbuild with findlib + camlp4
  2008-03-06 15:31   ` Dario Teixeira
  2008-03-06 15:46     ` Pietro Abate
@ 2008-03-07  9:26     ` Romain Bardou
  2008-03-07 14:46       ` Dario Teixeira
  2008-03-11 10:41       ` Nicolas Pouillard
  1 sibling, 2 replies; 22+ messages in thread
From: Romain Bardou @ 2008-03-07  9:26 UTC (permalink / raw)
  To: Dario Teixeira; +Cc: Romain Bardou, caml-list

> Anyway, ideally one should be able to specify in the _tags file the findlib
> packages that each ml file depends upon.

Well, doesn't the following plugin do what you want?

###########################
open Ocamlbuild_plugin
open Command

(* list of packages *)
let packages = ["nums"; "str"; "unix"]

(* ocamlfind command *)
let ocamlfind x = S[A"ocamlfind"; x]

let _ = dispatch begin function
   | Before_options ->
       Options.ocamlc := ocamlfind & A"ocamlc";
       Options.ocamlopt := ocamlfind & A"ocamlopt";
       Options.ocamldep := ocamlfind & A"ocamldep";
       Options.ocamldoc := ocamlfind & A"ocamldoc"
   | After_rules ->
       flag ["ocaml"; "link"; "linkpkg"] & A"-linkpkg";
       List.iter
	(fun pkg -> flag ["ocaml"; "pkg_"^pkg] & S[A"-package"; A pkg])
	packages
   | _ -> ()
end
###########################

This tells Ocamlbuild to use ocamlfind, and also defines some tags:
* The "linkpkg" tag, which adds the "-linkpkg" flag when linking. Tag 
your output files with it (your .byte or .native files), not the source 
files.
* The "pkg_nums", "pkg_str", and "pkg_unix" tags (simply add packages to 
the "packages" list if you need other packages) which add the "-package 
nums", "-package str" and "-package unix" options respectively. Tag your 
source files with the -package options they should use when compiling, 
and your output files with the -package options they should use when 
linking.

As an exercise you could even add a tag "ocamlfind" which would allow 
you to use ocamlfind only when you want to.

Now you should be able to use ocamlfind with different options depending 
on tags.

Disclaimer:
* I know it compiles but I didn't have time to construct a dummy project 
which would allow me to test this extension.
* It does nothing to handle camlp4, but you should be able to add the 
correct options yourself.

Please tell me if it is what you needed or not :)

-- 
Romain Bardou


^ permalink raw reply	[flat|nested] 22+ messages in thread

* Re: [Caml-list] Ocamlbuild with findlib + camlp4
  2008-03-07  9:26     ` Romain Bardou
@ 2008-03-07 14:46       ` Dario Teixeira
  2008-03-07 15:01         ` Nicolas Pouillard
  2008-03-11 10:41       ` Nicolas Pouillard
  1 sibling, 1 reply; 22+ messages in thread
From: Dario Teixeira @ 2008-03-07 14:46 UTC (permalink / raw)
  To: Romain Bardou; +Cc: caml-list

Hi,

Thanks for your help.  I think we're getting closer to creating a generic
Ocamlbuild plugin that adds support for Findlib.  However, I'm also beginning
to suspect that actually getting there -- creating a true generic solution --
might not be at all possible with the current Ocamlbuild.


> * The "pkg_nums", "pkg_str", and "pkg_unix" tags (simply add packages to 
> the "packages" list if you need other packages) which add the "-package 
> nums", "-package str" and "-package unix" options respectively. Tag your 
> source files with the -package options they should use when compiling, 
> and your output files with the -package options they should use when 
> linking.

Your idea can be extended to create a plugin that supports any of the
packages available through Findlib.  Just query Findlib for a list of
packages:

let packages =
        Findlib.init ();
        Fl_package_base.list_packages ()


While in theory this should work, it's still a brute force approach.
Mind you, my initial idea was that when finding a tag of the form
"pkg_foobar" (the actual syntax could be "pkg(foobar)" or something
like that), Ocamlbuild would dynamically add a new rule for that
package.  Your solution statically adds all possible rules at the
time the plugin is compiled  (and the patch I suggest above is even
more extreme in this regard).

Now, if you ask what's so bad about explicitly listing all packages in
myocamlbuild.ml, the answer is that it forces users to write a plugin
if they want to use findlib.  Personally, I think that findlib support
is so essential that one shouldn't be forced to write plugins in order
to use it.


> * It does nothing to handle camlp4, but you should be able to add the 
> correct options yourself.
> 
> Please tell me if it is what you needed or not :)

I'm finding that adding camlp4 support is where things get messy:
Ocamlbuild's default rules conflict with findlib's.  I am yet to
find a solution that manages to integrate the three successfully.

Kind regards,
Dario Teixeira



      __________________________________________________________
Sent from Yahoo! Mail.
The World's Favourite Email http://uk.docs.yahoo.com/nowyoucan.html


^ permalink raw reply	[flat|nested] 22+ messages in thread

* Re: [Caml-list] Ocamlbuild with findlib + camlp4
  2008-03-07 14:46       ` Dario Teixeira
@ 2008-03-07 15:01         ` Nicolas Pouillard
  2008-03-07 16:12           ` Dario Teixeira
  0 siblings, 1 reply; 22+ messages in thread
From: Nicolas Pouillard @ 2008-03-07 15:01 UTC (permalink / raw)
  To: Dario Teixeira; +Cc: romain.bardou, Caml_mailing list

[-- Attachment #1: Type: text/plain, Size: 1103 bytes --]

Excerpts from Dario Teixeira's message of Fri Mar 07 15:46:56 +0100 2008:
> Hi,
> 
> Thanks for your help.  I think we're getting closer to creating a generic
> Ocamlbuild plugin that adds support for Findlib.  However, I'm also beginning
> to suspect that actually getting there -- creating a true generic solution --
> might not be at all possible with the current Ocamlbuild.
> 
> > * The "pkg_nums", "pkg_str", and "pkg_unix" tags (simply add packages to 
> > the "packages" list if you need other packages) which add the "-package 
> > nums", "-package str" and "-package unix" options respectively. Tag your 
> > source files with the -package options they should use when compiling, 
> > and your output files with the -package options they should use when 
> > linking.
> 
> Your idea can be extended to create a plugin that supports any of the
> packages available through Findlib.  Just query Findlib for a list of
> packages:
> 
> let packages =
>         Findlib.init ();
>         Fl_package_base.list_packages ()

Great idea!

Does these functions exists?

-- 
Nicolas Pouillard aka Ertai

[-- Attachment #2: signature.asc --]
[-- Type: application/pgp-signature, Size: 286 bytes --]

^ permalink raw reply	[flat|nested] 22+ messages in thread

* Re: [Caml-list] Ocamlbuild with findlib + camlp4
  2008-03-07 15:01         ` Nicolas Pouillard
@ 2008-03-07 16:12           ` Dario Teixeira
  2008-03-08 11:36             ` Nicolas Pouillard
  0 siblings, 1 reply; 22+ messages in thread
From: Dario Teixeira @ 2008-03-07 16:12 UTC (permalink / raw)
  To: Nicolas Pouillard; +Cc: romain.bardou, Caml_mailing list

> > 
> > let packages =
> >         Findlib.init ();
> >         Fl_package_base.list_packages ()
> 
> Great idea!
> 
> Does these functions exists?

Hi,

Of course!  The following is a valid Ocaml programme that will
list all packages available via findlib:  (you must link in
findlib.cma of course)

let () =
        Findlib.init ();
        let pkgs =  Fl_package_base.list_packages () in
        List.iter print_endline pkgs

Cheers,
Dario



      ___________________________________________________________ 
Rise to the challenge for Sport Relief with Yahoo! For Good  

http://uk.promotions.yahoo.com/forgood/


^ permalink raw reply	[flat|nested] 22+ messages in thread

* Re: [Caml-list] Ocamlbuild with findlib + camlp4
  2008-03-07 16:12           ` Dario Teixeira
@ 2008-03-08 11:36             ` Nicolas Pouillard
  2008-03-10 15:33               ` Dario Teixeira
  0 siblings, 1 reply; 22+ messages in thread
From: Nicolas Pouillard @ 2008-03-08 11:36 UTC (permalink / raw)
  To: Dario Teixeira; +Cc: romain.bardou, Caml_mailing list

[-- Attachment #1: Type: text/plain, Size: 780 bytes --]

Excerpts from Dario Teixeira's message of Fri Mar 07 17:12:16 +0100 2008:
> > > 
> > > let packages =
> > >         Findlib.init ();
> > >         Fl_package_base.list_packages ()
> > 
> > Great idea!
> > 
> > Does these functions exists?
> 
> Hi,
> 
> Of course!  The following is a valid Ocaml programme that will
> list all packages available via findlib:  (you must link in
> findlib.cma of course)
> 
> let () =
>         Findlib.init ();
>         let pkgs =  Fl_package_base.list_packages () in
>         List.iter print_endline pkgs

Nice!  Apart  the link with findlib.cma that is not supported yet and could be
with  the  multiple-plugins support in ocamlbuild. I think that one can easily
build a generic plugin for ocamlfind packages.

-- 
Nicolas Pouillard aka Ertai

[-- Attachment #2: signature.asc --]
[-- Type: application/pgp-signature, Size: 194 bytes --]

^ permalink raw reply	[flat|nested] 22+ messages in thread

* Re: [Caml-list] Ocamlbuild with findlib + camlp4
  2008-03-08 11:36             ` Nicolas Pouillard
@ 2008-03-10 15:33               ` Dario Teixeira
  2008-03-10 16:15                 ` Romain Bardou
                                   ` (2 more replies)
  0 siblings, 3 replies; 22+ messages in thread
From: Dario Teixeira @ 2008-03-10 15:33 UTC (permalink / raw)
  To: Nicolas Pouillard; +Cc: Caml_mailing list

> Nice!  Apart  the link with findlib.cma that is not supported yet and could
> be with  the  multiple-plugins support in ocamlbuild. I think that one can
> easily build a generic plugin for ocamlfind packages.

Hi,

I hope so too.  However, note that no one has managed yet to provide a solution
to my original question, namely of integrating Ocamlbuild with findlib *and*
camlp4.  Perhaps I should have explained better what this entails:

Suppose you are using the Sexplib syntax extension.  This syntax extension
depends on Sexplib itself and on another syntax extension, offered by the
Type-conv package.  The META package for Sexplib should contain the following:
(note that the version currently shipping with GODI is incomplete)

###############################################################
name="sexplib"
version="3.0.0"
description="Sexplib - automated S-expression conversions"
requires="bigarray"
archive(byte)="sexplib.cma"
archive(native)="sexplib.cmxa"

package "statements" (
  requires = "sexplib,type-conv.statements,camlp4"
  version = "3.0.0"
  description = "Syntax extension for Sexplib"
  archive(syntax,preprocessor) = "pa_sexp_conv.cmo"
  archive(syntax,toploop) = "pa_sexp_conv.cmo"
  )
###############################################################


To compile with Findlib a data.ml file that makes use of the Sexplib syntax
extension is very simple.  You just have to specify the "sexplib.statements"
package, and findlib will *automatically* take care of also loading libraries
or even other syntax extensions needed by sexplib.statements:

ocamlfind ocamlc -package sexplib.statements -syntax camlp4o -c data.ml


Why am I insisting on this?  Because when we manage to integrate these
three tools, we will essentially have solved the very common request of
providing easy access to common syntax extensions (just last week there was
an OSR on this subject).  All that will be required to compile a file such as
data.ml using the Sexplib syntax extension will be to add a line "<data.ml>:
use_sexplib.statements" to the _tags file.  You won't even need to create
a custom Ocamlbuild plugin or anything, because this findlib support could
be provided by a default plugin (living on $HOME/.ocamlbuild or something).

So, Nicolas, is this altogether feasible with the current Ocamlbuild?
(And if so, could you lent us a hand -- you are of course the most
competent person to do so).

Kind regards,
Dario



      ___________________________________________________________ 
Rise to the challenge for Sport Relief with Yahoo! For Good  

http://uk.promotions.yahoo.com/forgood/


^ permalink raw reply	[flat|nested] 22+ messages in thread

* Re: [Caml-list] Ocamlbuild with findlib + camlp4
  2008-03-10 15:33               ` Dario Teixeira
@ 2008-03-10 16:15                 ` Romain Bardou
  2008-03-10 21:13                   ` Dario Teixeira
  2008-03-10 19:56                 ` Arnaud Spiwack
  2008-03-11 10:37                 ` Nicolas Pouillard
  2 siblings, 1 reply; 22+ messages in thread
From: Romain Bardou @ 2008-03-10 16:15 UTC (permalink / raw)
  To: Dario Teixeira; +Cc: Nicolas Pouillard, Caml_mailing list

> ocamlfind ocamlc -package sexplib.statements -syntax camlp4o -c data.ml

To me it seems the only difference here with the case without camlp4 is 
the "-syntax camlp4o" option. If you add something like:

After_rules ->
   flag ["ocaml"; "pkg_sexplib.statements"] (S[A"-syntax"; A"-camlp4o"]);

to your myocamlbuild.ml, and tag your files with 
"pkg_sexplib.statements", and use the plugin I wrote which declares the 
"pkg_*" tags, does it work? (ocamldep might still not work so you might 
need to tweak it a bit with tags "compile", "link" and "doc").

Anyway, I don't think you need to modify Ocamlbuild to make it work 
(unless you don't want to use a plugin) if it is just a matter of adding 
"-syntax camlp4o" at the right moment. For the "-package" option, my 
previous solution should work.

That being said, once Ocamlbuild handles multiple plugins, it will be 
easy to write your own, standard, generic plugin in your .ocamlbuild 
directory and use it in all of your projects :)

-- 
Romain Bardou


^ permalink raw reply	[flat|nested] 22+ messages in thread

* Re: [Caml-list] Ocamlbuild with findlib + camlp4
  2008-03-10 15:33               ` Dario Teixeira
  2008-03-10 16:15                 ` Romain Bardou
@ 2008-03-10 19:56                 ` Arnaud Spiwack
  2008-03-10 21:15                   ` Dario Teixeira
  2008-03-11 10:37                 ` Nicolas Pouillard
  2 siblings, 1 reply; 22+ messages in thread
From: Arnaud Spiwack @ 2008-03-10 19:56 UTC (permalink / raw)
  To: Dario Teixeira; +Cc: Nicolas Pouillard, Caml_mailing list

Hi,

I happen to have an *almost* generic ocamlbuild plugin that calls upon 
camlp4 and findlib. Actually it is meant at compiling ulex files. But it 
is mostly the idea. However, it is still messy and need to be cleaned up 
before being put on the wiki.

The general idea is that it does *not* use ocamlfind ocamlc bar.ml 
-syntax foo. It actually proceeds in two parts. The first part consists 
in querying with ocamlfind query (using the shell, so it is not much of 
a clean part) to get the list of files to pass to the preprocessor, then 
uses camlp4 with the marshalled AST printer (there is also a target to 
build a pretty printed OCaml file from the file with syntax extension. 
This is mostly useful for debugging your own syntax extensions though). 
The second part consists in compiling this marshalled AST (using Findlib 
again to locate the .cm{i,o,a} that need to be linked or used at typing 
time).

I'll try to get that online ASAP.



Arnaud Spiwack

Dario Teixeira a écrit :
>> Nice!  Apart  the link with findlib.cma that is not supported yet and could
>> be with  the  multiple-plugins support in ocamlbuild. I think that one can
>> easily build a generic plugin for ocamlfind packages.
>>     
>
> Hi,
>
> I hope so too.  However, note that no one has managed yet to provide a solution
> to my original question, namely of integrating Ocamlbuild with findlib *and*
> camlp4.  Perhaps I should have explained better what this entails:
>
> Suppose you are using the Sexplib syntax extension.  This syntax extension
> depends on Sexplib itself and on another syntax extension, offered by the
> Type-conv package.  The META package for Sexplib should contain the following:
> (note that the version currently shipping with GODI is incomplete)
>
> ###############################################################
> name="sexplib"
> version="3.0.0"
> description="Sexplib - automated S-expression conversions"
> requires="bigarray"
> archive(byte)="sexplib.cma"
> archive(native)="sexplib.cmxa"
>
> package "statements" (
>   requires = "sexplib,type-conv.statements,camlp4"
>   version = "3.0.0"
>   description = "Syntax extension for Sexplib"
>   archive(syntax,preprocessor) = "pa_sexp_conv.cmo"
>   archive(syntax,toploop) = "pa_sexp_conv.cmo"
>   )
> ###############################################################
>
>
> To compile with Findlib a data.ml file that makes use of the Sexplib syntax
> extension is very simple.  You just have to specify the "sexplib.statements"
> package, and findlib will *automatically* take care of also loading libraries
> or even other syntax extensions needed by sexplib.statements:
>
> ocamlfind ocamlc -package sexplib.statements -syntax camlp4o -c data.ml
>
>
> Why am I insisting on this?  Because when we manage to integrate these
> three tools, we will essentially have solved the very common request of
> providing easy access to common syntax extensions (just last week there was
> an OSR on this subject).  All that will be required to compile a file such as
> data.ml using the Sexplib syntax extension will be to add a line "<data.ml>:
> use_sexplib.statements" to the _tags file.  You won't even need to create
> a custom Ocamlbuild plugin or anything, because this findlib support could
> be provided by a default plugin (living on $HOME/.ocamlbuild or something).
>
> So, Nicolas, is this altogether feasible with the current Ocamlbuild?
> (And if so, could you lent us a hand -- you are of course the most
> competent person to do so).
>
> Kind regards,
> Dario
>
>
>
>       ___________________________________________________________ 
> Rise to the challenge for Sport Relief with Yahoo! For Good  
>
> http://uk.promotions.yahoo.com/forgood/
>
> _______________________________________________
> Caml-list mailing list. Subscription management:
> http://yquem.inria.fr/cgi-bin/mailman/listinfo/caml-list
> Archives: http://caml.inria.fr
> Beginner's list: http://groups.yahoo.com/group/ocaml_beginners
> Bug reports: http://caml.inria.fr/bin/caml-bugs
>
>   


^ permalink raw reply	[flat|nested] 22+ messages in thread

* Re: [Caml-list] Ocamlbuild with findlib + camlp4
  2008-03-10 16:15                 ` Romain Bardou
@ 2008-03-10 21:13                   ` Dario Teixeira
  0 siblings, 0 replies; 22+ messages in thread
From: Dario Teixeira @ 2008-03-10 21:13 UTC (permalink / raw)
  To: Romain Bardou; +Cc: Nicolas Pouillard, Caml_mailing list

Hi Romain,

> to your myocamlbuild.ml, and tag your files with 
> "pkg_sexplib.statements", and use the plugin I wrote which declares the 
> "pkg_*" tags, does it work? (ocamldep might still not work so you might 
> need to tweak it a bit with tags "compile", "link" and "doc").
 
Thanks for the reply.  Well, the devil is in the details.  At first
I also thought this should be a trivial problem, but Ocamlbuild's
builtin rules always conflict with findlib.

Perhaps the solution that Arnaud just posted to this list (not using
ocamlfind directly but rather to query it) might be the way to go.
Anyway, if someone manages to get ocamlbuild+findlib+camlp4 to work
together I will be glad to hear from them...


> That being said, once Ocamlbuild handles multiple plugins, it will be 
> easy to write your own, standard, generic plugin in your .ocamlbuild 
> directory and use it in all of your projects :)

Yeap, that was the idea.

Cheers,
Dario



      __________________________________________________________
Sent from Yahoo! Mail.
The World's Favourite Email http://uk.docs.yahoo.com/nowyoucan.html


^ permalink raw reply	[flat|nested] 22+ messages in thread

* Re: [Caml-list] Ocamlbuild with findlib + camlp4
  2008-03-10 19:56                 ` Arnaud Spiwack
@ 2008-03-10 21:15                   ` Dario Teixeira
  0 siblings, 0 replies; 22+ messages in thread
From: Dario Teixeira @ 2008-03-10 21:15 UTC (permalink / raw)
  To: Arnaud Spiwack; +Cc: Nicolas Pouillard, Caml_mailing list

Hi Arnaud,

> The general idea is that it does *not* use ocamlfind ocamlc bar.ml 
> -syntax foo. It actually proceeds in two parts. The first part consists 
> in querying with ocamlfind query (using the shell, so it is not much of 
> a clean part) to get the list of files to pass to the preprocessor, then 

To make this code cleaner, you can query Findlib directly instead of
parsing "ocamlfind query" via the shell (I posted on this list a few
days ago a small code sample that does precisely this).  I am not sure,
however, how easy it is to use external libs ocamlbuild plugins.


> uses camlp4 with the marshalled AST printer (there is also a target to 
> build a pretty printed OCaml file from the file with syntax extension. 
> This is mostly useful for debugging your own syntax extensions though). 
> The second part consists in compiling this marshalled AST (using Findlib 
> again to locate the .cm{i,o,a} that need to be linked or used at typing 
> time).

So in a sense if you have to replicate a lot of the work that ocamlfind
already does.  Not ideal, but at the moment I also don't see another
solution.

Cheers,
Dario




      ___________________________________________________________ 
Rise to the challenge for Sport Relief with Yahoo! For Good  

http://uk.promotions.yahoo.com/forgood/


^ permalink raw reply	[flat|nested] 22+ messages in thread

* Re: [Caml-list] Ocamlbuild with findlib + camlp4
  2008-03-10 15:33               ` Dario Teixeira
  2008-03-10 16:15                 ` Romain Bardou
  2008-03-10 19:56                 ` Arnaud Spiwack
@ 2008-03-11 10:37                 ` Nicolas Pouillard
  2008-03-11 13:49                   ` Romain Bardou
  2008-03-11 17:32                   ` Dario Teixeira
  2 siblings, 2 replies; 22+ messages in thread
From: Nicolas Pouillard @ 2008-03-11 10:37 UTC (permalink / raw)
  To: Dario Teixeira; +Cc: Caml_mailing list

[-- Attachment #1: Type: text/plain, Size: 5392 bytes --]

Excerpts from Dario Teixeira's message of Mon Mar 10 16:33:56 +0100 2008:
> > Nice!  Apart  the link with findlib.cma that is not supported yet and could
> > be with  the  multiple-plugins support in ocamlbuild. I think that one can
> > easily build a generic plugin for ocamlfind packages.
> 
> Hi,

Hi,

> 
> I hope so too.  However, note that no one has managed yet to provide a solution
> to my original question, namely of integrating Ocamlbuild with findlib *and*
> camlp4.  Perhaps I should have explained better what this entails:
> 
> Suppose you are using the Sexplib syntax extension.  This syntax extension
> depends on Sexplib itself and on another syntax extension, offered by the
> Type-conv package.  The META package for Sexplib should contain the following:
> (note that the version currently shipping with GODI is incomplete)
> 
> ###############################################################
> name="sexplib"
> version="3.0.0"
> description="Sexplib - automated S-expression conversions"
> requires="bigarray"
> archive(byte)="sexplib.cma"
> archive(native)="sexplib.cmxa"
> 
> package "statements" (
>   requires = "sexplib,type-conv.statements,camlp4"
>   version = "3.0.0"
>   description = "Syntax extension for Sexplib"
>   archive(syntax,preprocessor) = "pa_sexp_conv.cmo"
>   archive(syntax,toploop) = "pa_sexp_conv.cmo"
>   )
> ###############################################################
> 
> 
> To compile with Findlib a data.ml file that makes use of the Sexplib syntax
> extension is very simple.  You just have to specify the "sexplib.statements"
> package, and findlib will *automatically* take care of also loading libraries
> or even other syntax extensions needed by sexplib.statements:
> 
> ocamlfind ocamlc -package sexplib.statements -syntax camlp4o -c data.ml
> 
> 
> Why am I insisting on this?  Because when we manage to integrate these
> three tools, we will essentially have solved the very common request of
> providing easy access to common syntax extensions (just last week there was
> an OSR on this subject).  All that will be required to compile a file such as
> data.ml using the Sexplib syntax extension will be to add a line "<data.ml>:
> use_sexplib.statements" to the _tags file.  You won't even need to create
> a custom Ocamlbuild plugin or anything, because this findlib support could
> be provided by a default plugin (living on $HOME/.ocamlbuild or something).
> So, Nicolas, is this altogether feasible with the current Ocamlbuild?
> (And if so, could you lent us a hand -- you are of course the most
> competent person to do so).

First  I  would  like  thanks  everyone that participated in also helping you.
Keep up!

Currently  we  must  add  a  myocamlbuild.ml  file  in  your  project  because
ocamlbuild  does  not support multiple plugins (allowing $HOME/.ocamlbuild for
instance).

However  one  can  have  a  reusable  myocamlbuild.ml file. Here is a starting
point:

###################################
open Ocamlbuild_plugin
open Command (* no longer needed for OCaml >= 3.10.2 *)

(* these functions are not really officially exported *)
let run_and_read = Ocamlbuild_pack.My_unix.run_and_read
let blank_sep_strings = Ocamlbuild_pack.Lexers.blank_sep_strings

(* this lists all supported packages *)
let find_packages () =
  blank_sep_strings &
    Lexing.from_string &
      run_and_read "ocamlfind list | cut -d' ' -f1"

(* this is supposed to list available syntaxes, but I don't know how to do it. *)
let find_syntaxes () = ["camlp4o"; "camlp4r"]

(* ocamlfind command *)
let ocamlfind x = S[A"ocamlfind"; x]

let _ = dispatch begin function
   | Before_options ->

       (* override default commands by ocamlfind ones *)
       Options.ocamlc   := ocamlfind & A"ocamlc";
       Options.ocamlopt := ocamlfind & A"ocamlopt";
       Options.ocamldep := ocamlfind & A"ocamldep";
       Options.ocamldoc := ocamlfind & A"ocamldoc"

   | After_rules ->

       (* When one link an OCaml library/binary/package, one should use -linkpkg *)
       flag ["ocaml"; "link"] & A"-linkpkg";

       (* For each ocamlfind package one inject the -package option when
       	* compiling, computing dependencies, generating documentation and
       	* linking. *)
       List.iter begin fun pkg ->
         flag ["ocaml"; "compile";  "pkg_"^pkg] & S[A"-package"; A pkg];
         flag ["ocaml"; "ocamldep"; "pkg_"^pkg] & S[A"-package"; A pkg];
         flag ["ocaml"; "doc";      "pkg_"^pkg] & S[A"-package"; A pkg];
         flag ["ocaml"; "link";     "pkg_"^pkg] & S[A"-package"; A pkg];
       end (find_packages ());

       (* Like -package but for extensions syntax. Morover -syntax is useless
       	* when linking. *)
       List.iter begin fun syntax ->
         flag ["ocaml"; "compile";  "syntax_"^syntax] & S[A"-syntax"; A syntax];
         flag ["ocaml"; "ocamldep"; "syntax_"^syntax] & S[A"-syntax"; A syntax];
         flag ["ocaml"; "doc";      "syntax_"^syntax] & S[A"-syntax"; A syntax];
       end (find_syntaxes ());

   | _ -> ()
end
###################################

Then  consider  that  I want to compile yahoo.ml that requires the json-static
syntax extension, plus json-wheel and netclient.

$ cat _tags
<yahoo.*>: pkg_json-static, pkg_netclient, syntax_camlp4o

$ ocamlbuild yahoo.byte -- ocaml
...


Best regards,

[1]: http://martin.jambon.free.fr/yahoo.ml

-- 
Nicolas Pouillard aka Ertai

[-- Attachment #2: signature.asc --]
[-- Type: application/pgp-signature, Size: 194 bytes --]

^ permalink raw reply	[flat|nested] 22+ messages in thread

* Re: [Caml-list] Ocamlbuild with findlib + camlp4
  2008-03-07  9:26     ` Romain Bardou
  2008-03-07 14:46       ` Dario Teixeira
@ 2008-03-11 10:41       ` Nicolas Pouillard
  1 sibling, 0 replies; 22+ messages in thread
From: Nicolas Pouillard @ 2008-03-11 10:41 UTC (permalink / raw)
  To: romain.bardou; +Cc: Dario Teixeira, Caml_mailing list

[-- Attachment #1: Type: text/plain, Size: 1441 bytes --]

Excerpts from romain.bardou's message of Fri Mar 07 10:26:35 +0100 2008:
> > Anyway, ideally one should be able to specify in the _tags file the findlib
> > packages that each ml file depends upon.
> 
> Well, doesn't the following plugin do what you want?

Just to propagate my fixes...

> ###########################
> open Ocamlbuild_plugin
> open Command
> 
> (* list of packages *)
> let packages = ["nums"; "str"; "unix"]
> 
> (* ocamlfind command *)
> let ocamlfind x = S[A"ocamlfind"; x]
> 
> let _ = dispatch begin function
>    | Before_options ->
>        Options.ocamlc := ocamlfind & A"ocamlc";
>        Options.ocamlopt := ocamlfind & A"ocamlopt";
>        Options.ocamldep := ocamlfind & A"ocamldep";
>        Options.ocamldoc := ocamlfind & A"ocamldoc"
>    | After_rules ->
>        flag ["ocaml"; "link"; "linkpkg"] & A"-linkpkg";

The  linkpkg  tag  is  in the way. This does not really make sense to restrict
the  injection  of  -linkpkg  only when the linkpkg tag is present. We want to
put -linkpkg at every ocaml link command.

>        List.iter
>     (fun pkg -> flag ["ocaml"; "pkg_"^pkg] & S[A"-package"; A pkg])

This  too  much,  you  will inject -package pkg also for preprocessing options
for  instance  (-pp  "-package  ...").  You  need  to  restrict  the  scope by
specifying phases (compile,deps,link,doc).

>     packages
>    | _ -> ()
> end
> ###########################

-- 
Nicolas Pouillard aka Ertai

[-- Attachment #2: signature.asc --]
[-- Type: application/pgp-signature, Size: 194 bytes --]

^ permalink raw reply	[flat|nested] 22+ messages in thread

* Re: [Caml-list] Ocamlbuild with findlib + camlp4
  2008-03-11 10:37                 ` Nicolas Pouillard
@ 2008-03-11 13:49                   ` Romain Bardou
  2008-03-11 15:03                     ` Romain Bardou
  2008-03-11 17:32                   ` Dario Teixeira
  1 sibling, 1 reply; 22+ messages in thread
From: Romain Bardou @ 2008-03-11 13:49 UTC (permalink / raw)
  To: Nicolas Pouillard; +Cc: Caml_mailing list

> (* these functions are not really officially exported *)
> let run_and_read = Ocamlbuild_pack.My_unix.run_and_read
> let blank_sep_strings = Ocamlbuild_pack.Lexers.blank_sep_strings

Wow, for a moment I thought I could use this hack to access the Log module:

   After_options ->
     (* Automatic -classic-display when not in a terminal *)
     if Sys.getenv "TERM" = "dumb" then
       Ocamlbuild_pack.Log.classic_display := false

But it has no effect. Maybe moving classic_display to the Options module 
would be great, if it has not been done already (I'm still in 3.10.1) ^^

-- 
Romain Bardou


^ permalink raw reply	[flat|nested] 22+ messages in thread

* Re: [Caml-list] Ocamlbuild with findlib + camlp4
  2008-03-11 13:49                   ` Romain Bardou
@ 2008-03-11 15:03                     ` Romain Bardou
  0 siblings, 0 replies; 22+ messages in thread
From: Romain Bardou @ 2008-03-11 15:03 UTC (permalink / raw)
  To: Romain Bardou; +Cc: Nicolas Pouillard, Caml_mailing list

Nicolas Pouillard wrote:
> Try to do it Before_options, because here it's too late the ref has been consulted.

Thanks, it works Before_options (by replacing "false" by "true" too ^^) 
except when compiling myocamlbuild.ml (indeed: the plugin is not loaded 
yet), which is why I thought it didn't work at first.

I don't think there is a way to force classic-display = true for 
myocamlbuild.ml and then switch to classic-display = false in a plugin, 
but, well, a single weird line in emacs is fine I guess :)

-- 
Romain Bardou


^ permalink raw reply	[flat|nested] 22+ messages in thread

* Re: [Caml-list] Ocamlbuild with findlib + camlp4
  2008-03-11 10:37                 ` Nicolas Pouillard
  2008-03-11 13:49                   ` Romain Bardou
@ 2008-03-11 17:32                   ` Dario Teixeira
  2008-03-11 20:17                     ` Richard Jones
  1 sibling, 1 reply; 22+ messages in thread
From: Dario Teixeira @ 2008-03-11 17:32 UTC (permalink / raw)
  To: Nicolas Pouillard; +Cc: Caml_mailing list

> First  I  would  like  thanks  everyone that participated in also helping
> you. Keep up!
> 
> Currently  we  must  add  a  myocamlbuild.ml  file  in  your  project 
> because ocamlbuild  does  not support multiple plugins (allowing
> $HOME/.ocamlbuild for instance).
> 
> However  one  can  have  a  reusable  myocamlbuild.ml file. Here is a
> starting point:

Hi,

Thanks for your help.  I have tried the new "Ultimate Ocamlbuild Plugin"(tm)
you suggested and it seems to work fine.  So I guess that one long-standing
request from the community -- streamlining the use of syntax extensions --
has now been satisfied!

All that we need now is GODI packages for the most requested syntax
extensions, and to make sure that packagers build compliant META files
(I have noticed that not all GODI packages ship with findlib+camlp4
compliant META files).  Soon, I will write down an OSR formalising
this latter aspect.

Kind regards,
Dario Teixeira



      __________________________________________________________
Sent from Yahoo! Mail.
The World's Favourite Email http://uk.docs.yahoo.com/nowyoucan.html


^ permalink raw reply	[flat|nested] 22+ messages in thread

* Re: [Caml-list] Ocamlbuild with findlib + camlp4
  2008-03-11 17:32                   ` Dario Teixeira
@ 2008-03-11 20:17                     ` Richard Jones
  0 siblings, 0 replies; 22+ messages in thread
From: Richard Jones @ 2008-03-11 20:17 UTC (permalink / raw)
  To: Dario Teixeira; +Cc: Nicolas Pouillard, Caml_mailing list

On Tue, Mar 11, 2008 at 05:32:48PM +0000, Dario Teixeira wrote:
> All that we need now is GODI packages for the most requested syntax
> extensions, and to make sure that packagers build compliant META files
> (I have noticed that not all GODI packages ship with findlib+camlp4
> compliant META files).  Soon, I will write down an OSR formalising
> this latter aspect.

Yes, getting good META files is important.  Debian require them and
have done so for ages, and just today I changed the Fedora guidelines
so that META files are no longer optional but are required, must be
checked by reviewers _and_ must be submitted to upstream developers.
I hope this will improve the quality of META files.

Rich.

-- 
Richard Jones
Red Hat


^ permalink raw reply	[flat|nested] 22+ messages in thread

end of thread, other threads:[~2008-03-11 20:17 UTC | newest]

Thread overview: 22+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2008-03-05 13:41 Ocamlbuild with findlib + camlp4 Dario Teixeira
2008-03-05 15:08 ` [Caml-list] " Romain Bardou
2008-03-06 15:31   ` Dario Teixeira
2008-03-06 15:46     ` Pietro Abate
2008-03-06 19:45       ` Dario Teixeira
2008-03-06 22:14         ` Pietro Abate
2008-03-07  9:26     ` Romain Bardou
2008-03-07 14:46       ` Dario Teixeira
2008-03-07 15:01         ` Nicolas Pouillard
2008-03-07 16:12           ` Dario Teixeira
2008-03-08 11:36             ` Nicolas Pouillard
2008-03-10 15:33               ` Dario Teixeira
2008-03-10 16:15                 ` Romain Bardou
2008-03-10 21:13                   ` Dario Teixeira
2008-03-10 19:56                 ` Arnaud Spiwack
2008-03-10 21:15                   ` Dario Teixeira
2008-03-11 10:37                 ` Nicolas Pouillard
2008-03-11 13:49                   ` Romain Bardou
2008-03-11 15:03                     ` Romain Bardou
2008-03-11 17:32                   ` Dario Teixeira
2008-03-11 20:17                     ` Richard Jones
2008-03-11 10:41       ` Nicolas Pouillard

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for NNTP newsgroup(s).