[Haskell] Does GHC support the standard CPP functionalities?
haihualin
haihualin at 163.com
Sat Nov 22 04:33:38 EST 2008
Hi,
I tried to compile the following program by GHC
{-# LANGUAGE CPP #-}
module Packer where
#define FLASH_APP_START 1
#define FLASH_APP_END 2
#define INSERT_SECTION(x) (#x, (FLASH_##x##_START, FLASH_##x##_END))
import qualified Data.Map as M
import Data.Tuple
import System.IO as Sys
type Name = String
type Boundary = (Int, Int)
boundaryList = [INSERT_SECTION(APP)]
main = Sys.print boundaryList
But failed with
test.hs:16:17: Not in scope: `#'
test.hs:16:17:
A section must be enclosed in parentheses thus: (# APP)
test.hs:16:18: Not in scope: data constructor `APP'
test.hs:16:24: Not in scope: data constructor `FLASH_'
test.hs:16:30: Not in scope: `##'
test.hs:16:32: Not in scope: data constructor `APP'
test.hs:16:35: Not in scope: `##'
Seems GHC does support macro like #x a##b. Is that true? If not, how to resolve?
Thanks alot.
Haihua
More information about the Haskell
mailing list