Fw: [Haskell-cafe] A restricted subset of CPP included in a revisionof Haskell 98

Brian Hulley brianh at metamilk.com
Tue Aug 22 04:49:55 EDT 2006


Hi - here is an exchange that was off-list by accident:

---- Original Message ----
From: Brian Smith
To: Brian Hulley
Sent: Tuesday, August 22, 2006 5:50 AM

> (Brian, I see that my last reply only went to you and so I forwarded
> it to the list. Since you replied to me directly, I am responding to
> you directly. Feel free to forward this to the list if you want).  
> 
> 
> On 8/21/06, Brian Hulley <brianh at metamilk.com> wrote:
>> The paper "Template meta-programming for Haskell" suggests
>> that Template Haskell should be able to do everything that CPP
>> is used for at the moment,  such as conditional compilation, macros
>> etc, so this might be a possible option, though I have to admit apart 
>> from reading the paper and doing a few experiments with it I don't 
>> know enough about the current state of TH to know if it would be a 
>> viable replacement at the moment.
> 
> I am very interested in TH and I hope to give it a thorough workout
> on an upcoming project. Until then, I don't know enough about it to
> compare it to CPP. But, I think that in an Editor/IDE, a restricted
> CPP would be much easier to implement than TH.   
> 
> 
>> I've got a feeling that even allowing #define could break the
>> invariant that a module only has one meaning in a program, since 
>> #define changes the state of a symbol that's not yet been mentioned 
>> just as #undef changes the state of a defined symbol eg:
>>
>>
>>     module P where
>>     #define Bar
>>     import R
>> 
>>     module R where
>>     #ifdef Bar
>>             import S
>>     #else
>>             import T
>>     #endif
>> 
>>     module Q where
>>     import R
> 
> I think that this program will only compile if it is split into three
> files, P.hs, R.hs, and Q.hs. There would be two scopes for CPP
> macros: global (each macro is bound to exactly one value for all
> modules, and it cannot be undefined or redefined) and file/module
> (the macro is bound exactly once in a module and that binding is not
> visible to other modules). Except for the "exactly once" part, this
> is how GHC and cpphs already work.      
> 
> So, in your example, let's assume there is no global binding for
> "Bar"--if there was, then there would be a redefinition error in
> P.hs. Then, P.hs defines Bar, but this binding is in scope only
> inside of P.hs--R.hs does not "see" Bar as being defined. Further,
> since R.hs does not contain a binding for "Bar," so module R will
> always import module T and never module S.     
> 
> A more concrete example is this:
> 
> module P where
> #ifdef __GHC__
>     import P.GHC
> #else
>     import P.Haskell98
> #endif
> 
> In your editor/IDE you might want to support multiple Haskell
> implementations. So, sometimes __GHC__ will be defined (when in GHC
> "mode") and sometimes it won't. But, I recommend to handle this in
> the same way that IntelliJ handles the JDK setting. That is, if the
> user wants to switch the implementation he is using (even
> temporarily), then when he does so, the whole program gets
> reanalyzed. If the user wants to work in Hugs mode and GHC mode in
> the same time, then he should create two projects in the IDE. In one
> project, the implementation will be set to GHC, and the other one
> Hugs. He will have to define output paths, etc. such that the two
> project's ouitput files do not overlap even though their sources
> will. Then, analyze each project seperately. This technique also
> allows the user to build a version of the project against, say, HaXml
> 1.14, and other version against 1.15.             
> 
> 
>> Much as I'd like to not have to deal with CPP, I agree that on
>> a practical realistic level it's not going to go away immediately,
>> but at least the guidelines you posted give a good starting point
>> for library authors to gradually try and reduce the dependence
>> on the preprocessor, if they are motivated to (which they
>> probably aren't ;-) )
> 
> Right. Plus, if we follow the guidelines I proposed very strictly,
> then we can more easily picture what is required of a CPP
> replacement. For example, if the guidelines are too prohibitive, then
> we will know we need something more powerful like TH. If the
> guidelines do not result in any practical loss of functionality, then
> we know that we can get by with a much simpler configuaration
> language.      
> 
> 
>> I had a wild idea of a tool to eliminate CPP from a source
>> tree by first generating the set of N pre-processed source trees
>> (ie now pure Haskell) then running some analysis tool over these
>> trees to automatically factor out common code, but this would
>> probably be a major undertaking.
> 
> That would definitely be an interesting project, and it would be
> useful for other things as well (The duplicate code detection part.) 
> 
> 
> 
>> Cabal seems to help a lot - Edison and ByteString both built on
>> my machine with no trouble at all. I think the more everything can
>> be done in Haskell the better it will be.
> 
> I agree. But, I also want it to be easy to reuse C-based libraries
> whenever possible. That way, we can spend more time writing code in
> Haskell that does new things instead of reimplementing old ideas in
> it.   
> 
> 
> You mentioned that library maintainers might not be motivated to make
> such changes. I think that people will modify their libraries if
> there are compelling tools that need those modifications. In fact, I
> think people would even be willing to break previous commitments to
> backwards compatibility if there was any benefit to doing so--I mean,
> who really uses the latest version of HaXml with GHC 5.x or Hugs
> 2002-xx-xx?      
> 
> If there was an IntelliJ-level IDE for Haskell, and people were
> writing "real world" programs in Haskell, then somebody would get
> around to modifying libraries to work for "real world" programs built
> using such a tool. Or, somebody that had a commercial interest (a
> Haskell consultant or an IDE vender) might make these modifications. 
>
> - Brian


More information about the Haskell-Cafe mailing list