cpphs-1.18: A liberalised re-implementation of cpp, the C pre-processor.

Copyright2000-2006 Malcolm Wallace
LicenseLGPL
MaintainerMalcolm Wallace <Malcolm.Wallace@cs.york.ac.uk>
Stabilityexperimental
PortabilityAll
Safe HaskellNone
LanguageHaskell98

Language.Preprocessor.Cpphs

Description

Include the interface that is exported

Synopsis

Documentation

cppIfdef Source

Arguments

:: FilePath

File for error reports

-> [(String, String)]

Pre-defined symbols and their values

-> [String]

Search path for #includes

-> BoolOptions

Options controlling output style

-> String

The input file content

-> IO [(Posn, String)]

The file after processing (in lines)

Run a first pass of cpp, evaluating #ifdef's and processing #include's, whilst taking account of #define's and #undef's as we encounter them.

macroPass Source

Arguments

:: [(String, String)]

Pre-defined symbols and their values

-> BoolOptions

Options that alter processing style

-> [(Posn, String)]

The input file content

-> IO String

The file after processing

Walk through the document, replacing calls of macros with the expanded RHS.

macroPassReturningSymTab Source

Arguments

:: [(String, String)]

Pre-defined symbols and their values

-> BoolOptions

Options that alter processing style

-> [(Posn, String)]

The input file content

-> IO (String, [(String, String)])

The file and symbol table after processing

Walk through the document, replacing calls of macros with the expanded RHS. Additionally returns the active symbol table after processing.

data CpphsOptions Source

Cpphs options structure.

Constructors

CpphsOptions 

Fields

infiles :: [FilePath]
 
outfiles :: [FilePath]
 
defines :: [(String, String)]
 
includes :: [String]
 
preInclude :: [FilePath]

Files to #include before anything else

boolopts :: BoolOptions
 

data BoolOptions Source

Options representable as Booleans.

Constructors

BoolOptions 

Fields

macros :: Bool

Leave #define and #undef in output of ifdef?

locations :: Bool

Place #line droppings in output?

hashline :: Bool

Write #line or {-# LINE #-} ?

pragma :: Bool

Keep #pragma in final output?

stripEol :: Bool

Remove C eol (//) comments everywhere?

stripC89 :: Bool

Remove C inline (/**/) comments everywhere?

lang :: Bool

Lex input as Haskell code?

ansi :: Bool

Permit stringise # and catenate ## operators?

layout :: Bool

Retain newlines in macro expansions?

literate :: Bool

Remove literate markup?

warnings :: Bool

Issue warnings?

parseOptions :: [String] -> Either String CpphsOptions Source

Parse all command-line options.

defaultBoolOptions :: BoolOptions Source

Default settings of boolean options.

data Posn Source

Source positions contain a filename, line, column, and an inclusion point, which is itself another source position, recursively.

Constructors

Pn String !Int !Int (Maybe Posn) 

Instances

newfile :: String -> Posn Source

Constructor. Argument is filename.

addcol :: Int -> Posn -> Posn Source

Increment column number by given quantity.

newline :: Posn -> Posn Source

Increment row number, reset column to 1.

tab :: Posn -> Posn Source

Increment column number, tab stops are every 8 chars.

newlines :: Int -> Posn -> Posn Source

Increment row number by given quantity.

newpos :: Int -> Maybe String -> Posn -> Posn Source

Update position with a new row, and possible filename.

cppline :: Posn -> String Source

cpp-style printing of file position

haskline :: Posn -> String Source

haskell-style printing of file position

cpp2hask :: String -> String Source

Conversion from a cpp-style "#line" to haskell-style pragma.

filename :: Posn -> String Source

Project the filename.

lineno :: Posn -> Int Source

Project the line number.

directory :: Posn -> FilePath Source

Project the directory of the filename.