[Haskell-cafe] Conditional compilation for different versions of GHC?

Jinjing Wang nfjinjing at gmail.com
Sun Nov 28 04:16:22 CET 2010


Hi Antoine, Thanks for pointing out, it did work.

By using a record style constructor, the code can be made to support
both version, something like

    here = QuasiQuoter
      {
        quoteExp = (litE . stringL)
      , quotePat = (litP . stringL)
      }

in GHC7 there's a warning:

       Warning: Fields of `QuasiQuoter' not initialised: quoteType, quoteDec

So far it works without problem.


On Sun, Nov 28, 2010 at 10:38 AM, Jinjing Wang <nfjinjing at gmail.com> wrote:
> Hi Michael, you are absolutely correct, cabal did set the flags automatically.
>
> To sum up, here's what needs to be done:
>
> * add `flag ghc7` as a field in cabal
> * add:
>
>    if flag(ghc7)
>        build-depends:   base                      >= 4.3      && < 5
>        cpp-options:     -DGHC7
>    else
>        build-depends:   base                      >= 4        && < 4.3
>
>   in library field in cabal
>
> * add `{-# LANGUAGE CPP #-}` in source file
> * add
>
>    #if GHC7
>    x
>
>    #else
>    y
>
>    #endif
>
>
>  Hi Antonine, I don't know how to not set those fields in the
> constructor.. as a QQ noob, I'm just hacking on some legacy code. This
> code doesn't compile in GHC7, so I have to do this trick.
>
> * https://github.com/nfjinjing/mps/blob/master/src/MPS/TH.hs
>
> Best,
>
> On Sun, Nov 28, 2010 at 3:48 AM, Michael Snoyman <michael at snoyman.com> wrote:
>> On Sat, Nov 27, 2010 at 9:41 PM, Antoine Latter <aslatter at gmail.com> wrote:
>>> On Sat, Nov 27, 2010 at 10:59 AM, Jinjing Wang <nfjinjing at gmail.com> wrote:
>>>> Dear list,
>>>>
>>>> >From ghc 7.0.1 release notes:
>>>>
>>>>> The Language.Haskell.TH.Quote.QuasiQuoter type has two new fields: quoteType and quoteDec.
>>>>
>>>> Some of my code needs to be conditionally compiled to support both
>>>> version 6 and 7, what is the recommended way to do it?
>>>>
>>>> ref:
>>>>
>>>> * http://new-www.haskell.org/ghc/docs/7.0.1/html/users_guide/release-7-0-1.html
>>>
>>> Can you just not set those fields? Then the code should work as-is for
>>> both versions. You'll get warnings for GHC 7, I think.
>>
>> Sorry Jinjing, I didn't read your original email carefully enough.
>> Antoine is absolutely correct, this is the better way to deal with
>> defining a quasiquoter. My suggestion is only necessary if you want to
>> *use* a quasiquoter.
>>
>> Michael
>>
>
>
>
> --
> jinjing
>



-- 
jinjing


More information about the Haskell-Cafe mailing list