2008-07-24

<pippijn> camlp4?
<Smerdyakov> pippijn, camlp4
<pango_> hence you should use camlp4 package
<pango_> actually there's camlp4 and camlp5 (pre-3.10 compatible camlp4)
<pippijn> camlp4 - Pre-Precessor-Pretty-Printer for OCaml
<pippijn> I see lots of camlp4 stuff.. is it part of ocaml base?
<pippijn> camlp4
<bluestorm> (though it can get a little bit painful, specifically for float computations : there is ongoing work on camlp4 extensions to make it easier)
<flux> (but, look who's talking: I really should take a deep look on camlp4 programming some day..)
<asmanur> Here is a small camlp4 extension to handle haskell's syntaxic sugar for infix operators (for instance (>= 0)) : http://paste.pocoo.org/show/80225/
<mfp> significant whitespaces sounds hard to do with camlp4
<bluestorm> (but the camlp4 hacking may be quite fun)
<bluestorm> i'm planning to try a camlp4 extension for the F# #light syntax

2008-07-21

<flux> yes can, with camlp4

2008-07-18

<pango_> the only think that may be missing (that I can think of), is that if you're using camlp4 3.10 extensions, you can provide them to otags so it supports your modified syntax
<Jeff_123> I think so, unless someone has figured out how to extend the lexer with the new camlp4

2008-07-17

<rwmjones> making anything more complicated is quite hard, given camlp4 etc

2008-07-14

<bluestorm> whereas camlp4 is quite comfortable in that aspect
<bluestorm> osr_camlp4 is this work (the name was hype-suggested and i'm not so serious about it)
<gildor> what is the difference between osr_camlp4 and p4ck ?
<gildor> because in description.txt "Those extension are camlp4>=3.10 extensions"
<bluestorm> most of martin jambon p4ck extensions are not camlp4 >= 3.10 compatible
<gildor> i am not sure to understand however, all the syntax extension work with OCaml camlp4 >= 3.10
<bluestorm> it already provides most of the extension this page was considering for camlp4-misc
<bluestorm> about a month ago, i worked on a preliminary version of a "camlp4 extension pack"

2008-07-13

<bluestorm> that is, you put the definition you want to inline in a separate file, wich is compiled to a .cmo and the given to camlp4
<bluestorm> kig: if you wanted to, it would not be too difficult to create an extension that would inline operators, provided they are given at camlp4-time
<kig> all i need now is a camlp4 extension that transforms combinators into optimized recursions

2008-07-11

<rwmjones> jynxzero, yes and no ... I still get some inconsistencies in locations even with the latest camlp4
<jynxzero> Does the new camlp4 play nicely with the debugger? I've had problems in the past with the debugger not pointing to the correct place in the source code when camlp4 was involved.

2008-07-10

<msinhore> Camlp4: Uncaught exception: DynLoader.Error ("/usr/lib/ocaml/3.10.2/bitmatch/pa_bitmatch.cmo", "error while linking /usr/lib/ocaml/3.10.2/bitmatch/pa_bitmatch.cmo.\nReference to undefined global `Bitmatch'")

2008-07-08

<hcarty> I don't know how useful my minimal camlp4 would be in their significantly more ambitious project :-)

2008-07-04

<bluestorm> use camlp4 and #INCLUDE

2008-07-01

<bluestorm> rwmjones: my camlp4 code outputted an extract_remainder instead of extract_bitstring, and the test suite didn't complain (wich is not really surprising because this kind of error must be hard to catch)

2008-06-29

<bluestorm> on the other hand, it may have its own qualities (i've never used pre-3.10 camlp4 or camlp5 so i couldn't say), and certainly has a value for pre-3.10 camlp4 compatibility (interesting for projects like Coq maybe)
<bluestorm> (but it's about an earlier version of camlp4, the syntax was slightly modified since that tutorial)
<bluestorm> you have to use camlp4, and hm.

2008-06-26

<bluestorm> flux: "plans to" is nice, but in practice i'm not aware of any work in that direction. The current state (independent but camlp4-friendly preprocessor, line numbers preserved) is quite a good compromise, though.
<flux> bluestorm, I suppose you know of Patterns? however twt doesn't currently use camlp4, although it plans to
<bluestorm> I don't know F# enough, but i've been interested in the "active patterns" feature, and the #light syntax; and actually, i think both could be reasonably imitated in pure OCaml with some camlp4 preprocessing

2008-06-25

<RobertFischer> Yeah, it's camlp4-tastic.

2008-06-24

<Smerdyakov> No one knows that stuff but camlp4 users, and there aren't many camlp4 users.

2008-06-23

<Yoric[DT]> For the moment, I can't think of any better way than Camlp4-style module registration.
<bluestorm> could you not include the camlp4 AST and do the traverse.ml generation at compile time ?
<yallop> I'm looking for help with using a custom lexer in Camlp4
<Yoric[DT]> instead of calling bind, I have camlp4 replace bind (fun p -> e) with match m with p -> e
<Yoric[DT]> It's annoying not to be able to look-up modules and find out if functions exist at Camlp4-time.

2008-06-21

<jbms> Hello, is there any sort of coroutine/micro-thread library for OCaml that provides convenient syntax, e.g. via camlp4?

2008-06-19

<Smerdyakov> camlp4 comes with OCaml, and "pretty printer" is 2 of the 4 p's.
<hcarty> Yoric[DT]: Ok, thanks. I'm just curious, wondering what what affect making a pa_includein camlp4 extension vs pa_openin camlp4 extension would have

2008-06-18

<hcarty> I wrote a simple camlp4 extension to do it, and Zheng Li did as well
<flux> well, overloading or type classes will never happen with camlp4 magic
<Yoric[DT]> We have something without Camlp4 in Batteries Included, for the usual types.
<orbitz> people are tryign to do camlp4 trick, like the math one in teh SOC
<bluestorm> pango: '>>' would be a bad operator choice anyway, as it conflicts with camlp4 quotation syntax

2008-06-17

<flux> the archives didn't yet get to the point of discussing using camlp4 for deforestation
<bluestorm> flux: have you seen the idea on the mailing-list to use camlp4 to basically do the deforestation optimisation ?
<asmanur> chessguy: the only code that I know which use the OO features is Camlp4 and the bindings to OO library such as gtk
<hcarty> I think there was some chatter on the mailing list about it being possible, with camlp4 3.10+, to do the same thing using camlp4. I don't know if anything has started with that.
<hcarty> No camlp4
<orbitz> Yoric[DT]: oh no i was just wondering if you were refering to functors when saying youc an generate libraries at compiel tiem or camlp4
<Yoric[DT]> So, yeah, the Camlp4 module may be functorized, but that's hardly exceptional.
<Yoric[DT]> It's Camlp4.

2008-06-13

<rwmjones> bluestorm, the overuse of functors in camlp4 confuses me deeply .. however if you want to submit a patch ....
<rwmjones> I really would like to know why camlp4 cannot locate error messages properly all the time .. I just spent an hour debugging an error in some code, only to realise that the camlp4 error message was pointing to the wrong location

2008-06-12

<flux> I was thinking that the camlp4 is a slightly more intimate part of the system than the standard libraries, so they could've been licensed with a more strict license
<bluestorm> __LOCATION__ returns a Loc.t, but that suppose you link the user code with the camlp4 libs
<bluestorm> and iirc it's already in the official camlp4 distribution
<bluestorm> it's easy to do with camlp4
<flux> I'd like to produce log-information which I could just use for jumping around in the source. so I would like to output __FILE__:__LINE__ in my code. I suppose camlp4 is the way?
<flux> hmm.. 1) generate type-annotated ocaml-code (with -dtypes and a simple program) from an ml-file 2) put such ocaml-code to camlp4 and generate something fancy with the type information 3) ???? 4) Profit!

2008-06-09

<bluestorm> i just did a quite funny bit of camlp4 hacking (although i don't intend the result to be useful) : pa_letmemo

2008-06-06

<flux> because camlp4 cannot access the type-level information, or other information defined in other modules
<bluestorm> (and you can have a camlp4 extension puking conversion functions from records in about 10 minutes)

2008-06-04

<bluestorm> flux: what kind of things do you do ? could it not be helped by some camlp4 hackery ?
<RobertFischer> jdh30: And re: static typing/database -- it's definitely possible. You would have to leverage some metaprogramming (read: camlp4) to do it, but you should be able to type it.

2008-06-02

<flux> I wonder if that would be good language to pick for a camlp4 frontend
<mfp> flux: yup, it's essentially an encoding of the relational algebra with existential types + a heavy camlp4 extension for convenience
<flux> I think atleast this should be a good excuse to look into camlp4 :-)

2008-05-27

<bluestorm> (and i'm not sure it will stay forever at that place, but anyway i found it useful when trying to understand the camlp4 stuff)
<bluestorm> i just uploaded my self-generated camlp4 doc

2008-05-26

<bluestorm> ocaml -I +camlp4 camlp4lib.cma
<bluestorm> ocamlc -I +camlp4 camlp4lib.cma -pp camlp4of.opt -c test.ml
<arrakis_> however my code was compiled using: ocamlc -I +camlp4 camlp4lib.cma -pp camlp4of.opt pa_pi.ml
<bluestorm> (however, some nasty camlp4 bugs may remain)
<bluestorm> but overall the camlp4 parsing should be fine
<bluestorm> actually i'm not sure ocamlyacc is simpler. There are differences because camlp4 is more or less recursive-descent while ocamlyacc is LR, and some grammars are nicer to work with in one of those setup
<bluestorm> so it's the new camlp4 :]
<bluestorm> what camlp4 are you speaking about ? what is your ocaml version ? >= 3.10 ?
<bluestorm> camlp4 is probably a good tool to write a parser in
<arrakis_> I was looking around for a way to implement a parser and I stumbled across camlp4, maybe it isn't the right tool at all
<bluestorm> why did you choose camlp4 ?
<arrakis_> hello, is there someone who can help me with a camlp4 grammar and related ASTs?

2008-05-24

<pango_> ulfdoz: it's a standard extension of camlp4

2008-05-19

<orbitz> is it a camlp4?
<Yoric[DT]> I guess. I'm not 100% sure about the semantics of Camlp4 in that case.

2008-05-18

* rwmjones wonders if there's a 'string_of_patt' function or 'string_of_expr' function in camlp4 ...

2008-05-17

<pango> hsuh: looks like streams... they still exists in OCaml, but as a camlp4 syntax extension
<flux> camlp4?

2008-05-15

<munga> well... no... I need to extend the camlp4_token ... otherwise the camlp4 machinery will get lost ... don't know. I don't understand it enough...
<bluestorm> it's a general token type that is used in the ocaml-grammar-handling part of camlp4, but i think you can use your own token type instead, as the Token signature do not recommend any specific type
<bluestorm> munga: i think that you do not have to use this camlp4_token type for your tokens
<munga> it's in Camlp4.PreCast.ml .... that btw has a line like : type camlp4_token = Sig.camlp4_token == [ KEYWORD of string ... ];
<munga> yep. but the I also have to define a new camlp4_token with my tokens ... correct ?
<munga> so I don't want to extend the ocaml grammar... I just want to learn how to write a super simple parser with the camlp4 machinery
<flux> (I personally haven't diven into camlp4 yet)
<munga> In the old camlp4 I could create a new lexer with Plexer.gmake ... can I do something similar in the new camlp4 ?
<munga> I want to parse regexp with camlp4 ... how can I convince the lexer to tokenize chars and not strings ?

2008-05-14

<munga> I'm looking at the camlp4 wiki atm...
<munga> hi all, how can I user camlp4 to create a pretty printer ? For example, do you know of a small "arithmetic expression" example to parser and pretty print an expression ?

2008-05-08

<qwr> you wont get line numbers, though. that seems to be some compiler magic. ok you could get those too with camlp4, i think...

2008-05-07

<flux> would be a bug in the compiler, not camlp4, unless camlp4 produces something unreasonable?
<bluestorm> (i thought it was a camlp4-time problem)
<bluestorm> profiling might help, although i wouldn't know how to build a custom camlp4 with profiling enabled
<hcarty> If you try to import a function which does not exist in Foo, it would be a post-camlp4 compile time error
<hcarty> So camlp4 could remain completely ignorant of the contents of Foo
<hcarty> Inclusion does not require camlp4 to know anything about the module
<orbitz> maye i'll try to learn camlp4 for that and hope i dont' shoot myself inteh foot
<hcarty> Though you could probably write a camlp4 extension to effectively bring only certain functions in to scope
<hcarty> I looked through the OCaml camlp4 syntax a year or so ago to see how that worked

2008-05-06

<bluestorm> actually the tiny point of relevance of that file (apart from showing my elite camlp4 skillz) is that the post-processed definition are put in the order of occurence of the first defining line
<bluestorm> however it's a very heavy extension (but it's probably not implemented right, i was very new to camlp4 at that time) and wouldn't cooperate well with others in the current state (redefine "implem" and clear "str_item")

2008-05-05

<bluestorm> say, i wrote a context_foo.cmo that is loaded with the camlp4 modules after pa_context.cmo
<bluestorm> the simplest way would be to make that happen at camlp4-time
<bluestorm> not bad, the problem is that you can't know at camlp4-time if Foo.Infix is defined
<bluestorm> that an additionnal .cmo, inserted by the user at camlp4-time, could use
<hcarty> Is it possible to do with camlp4?
<hcarty> If I knew enough camlp4 to write my own rather than just hacking up others' code, I would base this on pa_openin and maybe avoid the code duplication.

2008-05-02

<hcarty> orbitz: Unless there are other libraries and/or camlp4 extensions used

2008-05-01

<hcarty> struk_Atwork: Have you used a camlp4 extension before? I have not relied on them much because they can cause problems with OCaml 3.10.x+'s toplevel
<hcarty> The camlp4 syntax extension I linked earlier is meant to provide a subset of their final product because I read their proposal and thought "Cool!"
<hcarty> Their project will be implemented using camlp4 (mostly, I think)
<struk_Atwork> hcarty, I'm not clear as to what the fundamental differences of their project and camlp4 is
<struk_Atwork> hcarty, very cool stuff..just looked over your code and the camlp4 project
<hcarty> struk_atwork2: I have a very very simple extension to the Float.() example on the camlp4 wiki if you are interested
<orbitz> they have enough polar opinions just for camlp4 suggestiosn
<orbitz> I kind of wish ocaml would introduce something so we can overload operators. I guess that camlp4 hign for mathematical expressions will be good enough

2008-04-30

<bluestorm> bitmatch is interesting too, but i wouldn't consider including in my osr_camlp4 attempt right now, because it needs run-time library support
<bluestorm> i've been toying with camlp4 syntax extension ( an ocaml preprocessor ) for two/three days, and now i think "ah, one could use ty_constr there" instead of focusing on the real problem

2008-04-29

<bluestorm> i should probably dive deeper into the camlp4 sources to have a clear idea of that, but i think it's the idea
<bluestorm> camlp4 question : do you consider important that camlp4 extensions use the proper functor registering procedure, instead of extending PreCast ?
<bluestorm> actually, i was even thinking of providing a "Camlp4 utilities library", and type-conv has a bit of that
<bluestorm> yes, distributing type-conv on camlp4 side totally makes sens
<Yoric[DT]> By the way, I believe type-conv should be distributed on the camlp4 side, don't you think ?

2008-04-28

<bluestorm> tsuyoshi: there is a camlp4-compatible (< 3.10 i'm afraid) scheme syntax for ocaml

2008-04-27

<bluestorm> hcarty: camlp4 is a good way to learn about ocaml features you never used :-'
<bluestorm> hcarty: you know that <:foo< bar >> expressions expand to camlp4 AST terms ?
<hcarty> I emailed the student and metor for the Delimited Overloading project and updated the Camlp4 wiki with my changes to the pa_float code
<hcarty> I can't be certain as I don't have access to camlp4 < 3.10. But I am fairly certain I had the problem with 3.09.x. I just assumed it was my fault since I was very new to OCaml at that point.
<bluestorm> so this is not camlp4>=3.10 specific ? strange :p
<hcarty> Two #use toplevel commands give "I/O error: Bad file descriptor" when camlp4 is in use
<hcarty> I was thinking of the #use bug when camlp4 extensions are loaded
<bluestorm> unfortunately, camlp4 documentation is sparse and quite harsh
<bluestorm> camlp4 also provides AST transformation tools (mapping, folding)
<bluestorm> (don't be afraid with the strange camlp4 code, you eventually get used to it)
<bluestorm> camlp4 might help you
<hcarty> Not something that will compete with the OSP project, but a working hack of an existing camlp4 extension at least
<thelema> bah, the second camlp4 is just too redundant for me. camlp4/stdext
<bluestorm> the camlp4 directory naming conventions are more like Camlp4Parsers and Camlp4Filters so far
<bluestorm> thelema: the extensions i've included so far could go in the camlp4/ subpart, for example a camlp4/Camlp4SyntaxExtension directory
<thelema> bluestorm: any ideas how to integrate osr_camlp4 into the ocaml source tree?
<bluestorm> in case you're interested, here is my draft of "OSR camlp4 extensions packaging"

2008-04-26

<hcarty> bluestorm wrote a camlp4 extension
<bluestorm> other camlp4 extensions could generate such identifiers
<bluestorm> another question : from the http://martin.jambon.free.fr/p4ck.list.html list, wich one would you like to see ported to camlp4>=3.10 first ?
<bluestorm> Camlp4: Uncaught exception: DynLoader.Error ("./pa_holes.cmo", "interface mismatch on Camlp4")
<bluestorm> i found it in Yoric's comprehension package, and it's an adaptation of the camlp4 foreach tutorial ( http://www.ocaml-tutorial.org/camlp4_3.10/foreach_tutorial )
<bluestorm> (there a lot more camlp4 extensions out there but the difficulty is to find the camlp4>=3.10 ones, or to port the others)
<bluestorm> i'm trying to create a bundle of camlp4 extensions that would be part of the OSR distribution effort

2008-04-25

<bluestorm> i may have found a camlp4 bug
<bluestorm> anyway, i'd be a bit more interested in your "camlp4 extension list" :]

2008-04-24

<Yoric[DT]> Oh, and bluestorm, it seems to me that it would be quite easy to have a syntax for parser combinators with Camlp4.
<hcarty> Oh, how I would love to... but camlp4 breaks #use in the toplevel, so I tend to avoid it when developing new code
<alexyk> there was a thread on ocaml-list saying #light is very hard in camlp4 for some reason
<bluestorm> (and i don't see why we couldn't emulate #light, using twt or camlp4)

2008-04-23

<bluestorm> it should not be difficult to write a camlp4 attr_accessor extension

2008-04-21

<olegfink> is there any camlp4 3.10 regexp sugar?

2008-04-20

<bluestorm> Yoric[DT]: considering the camlp4 extensions to put in your "bundle" project, i have the feeling that we ought to have two different places : one whith a structured hierarchy of modules that make sens and behave well altogether, and one with only an extension list with an homogenous presentation
<bluestorm> (if you're considering a quite complex new software function, i think you should not begin with the camlp4 syntaxic sugar)
<bluestorm> i don't see the common point between a litteral yacc-program inclusion, and the stream parser syntax (wich is a quite heavy syntax extension, in the sense that it performs a lot of camlp4-time manipulations)
<bluestorm> Yoric[DT]: on the camlp4 side there is a quite good structure proposition that was discussed on the mailing list
<bluestorm> Yoric[DT]: i might be willing to help on the camlp4 side
<Yoric[DT]> In a few words: should I handle the library and Camlp4 and you handle the whole dist ?

2008-04-18

<bluestorm> orbitz: the camlp4 proposal goes quite far indeed, but if it's done in a modular/layered way, i don't think the overall complexity would hurt the simple use case

2008-04-16

<Yoric[DT]> Camlp4 contains Visitor-like code inside the pretty-printer.

2008-04-15

<sanxiyn> Otherwise, I guess someone could integrate camlp4 to F#.
<flx> camlp4-based solution would work as a preprocessor to the code
<sanxiyn> flx: What would be the camlp4 based solution?
<flx> hm, I was expecting a camlp4 -based solution

2008-04-13

<pango_> you get pattern matching over streams by using camlp4

2008-04-11

<pango_> I guess the next keyword is "camlp4"...
<thelema> RobertFischer: don't ask me about camlp4 - that font is dry.

2008-04-10

<bluestorm> then, after the syntaxic transformation (that removed the _ in the "good places"), i use a filter to spot any abusive use of _ outside my defined syntax, and fail at camlp4-time
<hcarty> Does this seem like a reasonable undertaking for a person new to camlp4
<RobertFischer> Somewhere there's a variable interpolation camlp4 script kicking around. Anyone have it?
<Jeff_123> the official camlp4 manual is out of date
<Jeff_123> Is anyone here who could give me some pointers in camlp4?

2008-04-09

<bluestorm> (may there be compilation-time performance issues with inlining complex types at camlp4 time instead of creating aliases as it is done now ?)
<bluestorm> seeing these type d1234 = foo d1 d2 d3 d4 things, i was considering a camlp4 extension to automatically generate the type-level boilerplate code

2008-04-06

<gildor> you can maintain a camlp4 outside ocaml
<thelema> One part of my vision for community-ocaml includes standard camlp4
<bluestorm> you should have a look at the camlp4 extension listed above
<thelema> to define a new object - no, that's as good as it gets. you could camlp4 something for yourself if you like.

2008-04-04

<bluestorm> there is a emacs framework for that (flymake iirc) and camlp4 could probably provide the necessary capacities
<bluestorm> i've done something a bit like #light with camlp4 when learning it, but i'm not satisfied with it, it's not usable as-is, and i did that as a proof of concept anyway
<alexyk> yes, saw that and also threads on fa.caml to the effect that #light is somehow very hard even with camlp4
<hcarty> No one has written one. There is ocaml+twt, but it is a preprocessor separate from camlp4
<alexyk> so why can't ocaml get a #light syntax with camlp4?

2008-04-03

* thelema is wary of any non-trivial camlp4

2008-04-02

<bluestorm> i wrote a camlp4 extension snippet once, that would allow one to do haskell-like function definitions

2008-04-01

<rwmjones> well, it's camlp4-preprocessed code

2008-03-31

<rwmjones> ocamlc -I +camlp4 camlp4lib.cma -pp camlp4of.opt -c pa_bitmatch.ml -o pa_bitmatch.cmo
<rwmjones> ok, here's another camlp4 question ...
<bluestorm> btw, camlp4 pr_o.cmo would work too
<rwmjones> ah ha, camlp4o instead of camlp4
<rwmjones> camlp4 pa_bitmatch.cmo -printer pr_o.cmo foo.ml
<rwmjones> first is an error message, second is a camlp4 fragment

2008-03-28

<bluestorm> it seems there is no need for it to lay at the camlp4 level
<bluestorm> i think that providing camlp4 support for declaring a bunch of variables, associated with lengths using a specified read method would not be difficult

2008-03-26

<bluestorm> (i've spent some time in understanding the basics of the camlp4 system, now i need to practice to get some Return on Investment :p )
<bluestorm> RobertFischer: if you need some simple camlp4 magic, i might help you
<thelema> RobertFischer: what unit testing system uses camlp4?
<bluestorm> RobertFischer: if you consider using camlp4, i strongly advise you to generate an ocamldoc outpout from the camlp4/Camlp4/Sig.ml file
<RobertFischer> thelema: You'd compile the unit test file using camlp4, yeah.
<thelema> RobertFischer: testing requiring camlp4?
* thelema has succeeded at avoiding camlp4 entirely
<bluestorm> but it assumes you already know 3.09 camlp4
<bluestorm> RobertFischer: beware that martin jambon's site use camlp4 3.09, wich is not totally compatible to the >=3.10 camlp4
<RobertFischer> rwmjones: Thanks for the link. We were chatting about possible syntax extensions to make unit testing easier the other day, so I'm just now about to dive into CamlP4.
<rwmjones> sporkmonger, there's a camlp4 extension that lets you interpolate $variables into strings

2008-03-22

<flux> although at times you may find yourself modifying the actual tree. I don't know a lot of this, though, bluestorm's done a lot of camlp4-stuff..

2008-03-21

<rwmjones> all I need now is to build a binary of the camlp4 preprocessor and I'm done
<rwmjones> bluestorm, I'm trying to fix sylvain's gettext to work with camlp4 3.10.x
* rwmjones is (still) in a twisty maze of camlp4 modules, all alike
<rwmjones> ocamlc -I +camlp4 -I /usr/lib64/ocaml/camlp4/Camlp4Parsers -pp camlp4of.opt camlp4lib.cma test.ml -o test.cmo
<Yoric[DT]> I also open Camlp4 and Camlp4.Precast.
* rwmjones is in a twisty maze of camlp4 modules, all alike

2008-03-20

<flux> I suppose if that were fixed, there would be no actual reason to use records.. bluestorm up for a camlp4 extension?-)

2008-03-15

<bluestorm> it would be quite a hack, but i think it might even be possible to do that without changing the extension code (by mimicking the camlp4 extension registration mechanism)
<thelema> because camlp4 extensions are programs, and not just data for the camlp4 program to use in processing its input.
<thelema> would a camlp4 extension be able to load other extensions?
<Smerdyakov> That's the way Coq does it, and camlp4 was more or less invented to use to implement Coq. :-)
<thelema> One advantage of cpp over camlp4 is that the instructions on how to process are inside the file being processed.
<bluestorm> why would camlp4 have to handle build system issues ?
<thelema> i.e. something outside camlp4 has to take care of determining what camlp4 engines get applied... :(
<bluestorm> thelema: at the camlp4-runtime level, "#load pa_macro1" should do the job
<thelema|away> does anyone know of a way to do the equivalent of "#include pa_macro1" in camlp4?

2008-03-14

<hcarty> You can assign priority with camlp4 though I think
<bluestorm> (no camlp4 needed)
<hcarty> flux: I know it exists for camlp4 3.09 (and maybe works with camlp5?). And I think you are correct - each module/file would have to be preprocessed and declare the infix locally
<hcarty> Does the "any function as infix" camlp4 extension exist for OCaml 3.10?
<hcarty> I have had good results going from 3.09 to 3.10 with non-camlp4'd things. But I am sure that is largely due to the libraries I use

2008-03-11

<hcarty> Adding array support would open it up a lot, but probably add a significant amount of complexity to the camlp4.
<WatersOfOblivion> Prolly could be done with CamlP4

2008-03-10

<evn_> mainly cause i haven't managed to get camlp4 to work in a toplevel properly
<hcarty> evn_: Using camlp4 in a toplevel breaks the #use "foo.ml";; command
<hcarty> All of these interesting new camlp4 extensions make related toplevel problems even more unfortunate
<flux> this lists a bunch of camlp4 extensions: http://caml.inria.fr/cgi-bin/hump.en.cgi?sort=0&browse=92
* Yoric[DT] did the trick using Camlp4, but will convert it to type-conv whenever he finds time.
<Yoric[DT]> ziph: actually, type-conv should be easier than Camlp4 for that task.
<ziph> Hmm, ta, the news article looks like it'll do the trick. I'll have to play with Camlp4, it seems to be a common answer to my questions. ;)
<Yoric[DT]> (and consider implementing that with Camlp4, I'm probably going to do it at some point).
<Yoric[DT]> If it's Camlp4, it's built-in.
<Yoric[DT]> In Camlp4 or your own AST ?

2008-03-09

<bluestorm> i think there isn't, with camlp4 at least
<bluestorm> Smerdyakov: i'm using camlp4, and (with my limited knowledge) i can't implement that kind of things easily

2008-03-07

<bluestorm> i'm not sure the ocaml community really *want* those tiny camlp4 scripts
<bluestorm> (except from a few notable exceptions as ulex, where the camlp4 is part of a big package that people want)
<bluestorm> for now it seems that the only user of a camlp4 is the one that wrote it
<thelema> Yoric[DT]: you think a collection of quality camlp4 scripts would have value?
<bluestorm> trying to keep them coherent, documented, and camlp4 3.10 (and more) ready
<thelema> for use in a 'best-of' camlp4 extension
<flux> bluestorm, btw, since you're so on fire with camlp4, when are you going to write that scheme/lisp (cut (bar _ 42)) extension?-)

2008-03-06

<bluestorm> (the foo.cmo has to be added as a camlp4 parameter, of course : camlp4oof fooc.mo test.ml works )
<bluestorm> the idea is that antiquotation parsing is actived when the Camlp4_config variable is set to true
<bluestorm> on camlp4, i might have a fix
<bluestorm> camlp4
<mattam> Are you using camlp4 or camlp5 ?
<bluestorm> so this is a camlp4-specific issue ?
<mattam> Okay. Can you do it in a camlp4 file now ?

2008-03-05

<bluestorm_> Yoric[DT]: actually i do think that one utility of the forge would be to get a list of decent (or not) camlp4 extension in a common gircs/dat repository, and ensuring they approximately follow the same conventions, and can be used together
* Yoric[DT] could create an camlp4 extension for auto-arguing on the mailing-list.
<bluestorm_> (camlp4 extensions deserve self-promotion :-')
<bluestorm> during the impl. of that extension, i ran into something that looks like a camlp4 bug
<bluestorm> the code outputted by camlp4 after the transformation is syntaxically incorrect :)
<bluestorm> given that you'd have to provide the signature and the structure, the syntaxic overhead of the non-camlp4 solution is the module + include, and eventually the sig/end struct/end
<bluestorm> i might be able to make you a little camlp4 extension to generate that kind of code
<bluestorm> you can't (reasonably) generate a whole module signature from camlp4
<flux> bluestorm feels his camlp4 urges raising?-)
<hcarty> This may be possible with camlp4, but if so it's far beyond my experience with it
<hcarty> Oh, on the camlp4 section. I was looking through ocamlbuild.
<evn> oh that is the front page of the camlp4 section

2008-03-04

<Yoric[DT]> (including a Camlp4 syntax extension)
<mfp> hmm you'd need to use camlp4 to expand the cases in order to dispatch to the appropriate function in the generated (a union b -> 'a) func

2008-03-03

<bluestorm> it would be interesting to have it more integrated with camlp4, but that's not something so easy to do, so i guess it'll have to wait a little bit
<flux> then there is the issue that doesn't camlp4 reduce the quality of error messages?
<flux> ocamlfind has some support for camlp4 extensions, but I've never managed to use it..
<bluestorm> if two camlp4 extension conflicts, you can't write code using both of them
<thelema> I hear some camlp4 extensions conflict
<bluestorm> actually i'd be more interested in an extension of ocamlfind to handle camlp4 too