Copyright | 2000-2006 Malcolm Wallace |
---|---|
License | LGPL |
Maintainer | Malcolm Wallace <Malcolm.Wallace@cs.york.ac.uk> |
Stability | experimental |
Portability | All |
Safe Haskell | None |
Language | Haskell98 |
Include the interface that is exported
- runCpphs :: CpphsOptions -> FilePath -> String -> IO String
- runCpphsPass1 :: CpphsOptions -> FilePath -> String -> IO [(Posn, String)]
- runCpphsPass2 :: BoolOptions -> [(String, String)] -> FilePath -> [(Posn, String)] -> IO String
- runCpphsReturningSymTab :: CpphsOptions -> FilePath -> String -> IO (String, [(String, String)])
- cppIfdef :: FilePath -> [(String, String)] -> [String] -> BoolOptions -> String -> IO [(Posn, String)]
- tokenise :: Bool -> Bool -> Bool -> Bool -> [(Posn, String)] -> [WordStyle]
- data WordStyle
- macroPass :: [(String, String)] -> BoolOptions -> [(Posn, String)] -> IO String
- macroPassReturningSymTab :: [(String, String)] -> BoolOptions -> [(Posn, String)] -> IO (String, [(String, String)])
- data CpphsOptions = CpphsOptions {}
- data BoolOptions = BoolOptions {}
- parseOptions :: [String] -> Either String CpphsOptions
- defaultCpphsOptions :: CpphsOptions
- defaultBoolOptions :: BoolOptions
- data Posn = Pn String !Int !Int (Maybe Posn)
- newfile :: String -> Posn
- addcol :: Int -> Posn -> Posn
- newline :: Posn -> Posn
- tab :: Posn -> Posn
- newlines :: Int -> Posn -> Posn
- newpos :: Int -> Maybe String -> Posn -> Posn
- cppline :: Posn -> String
- haskline :: Posn -> String
- cpp2hask :: String -> String
- filename :: Posn -> String
- lineno :: Posn -> Int
- directory :: Posn -> FilePath
- cleanPath :: FilePath -> FilePath
Documentation
runCpphsPass1 :: CpphsOptions -> FilePath -> String -> IO [(Posn, String)] Source #
runCpphsPass2 :: BoolOptions -> [(String, String)] -> FilePath -> [(Posn, String)] -> IO String Source #
runCpphsReturningSymTab :: CpphsOptions -> FilePath -> String -> IO (String, [(String, String)]) Source #
:: 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.
tokenise :: Bool -> Bool -> Bool -> Bool -> [(Posn, String)] -> [WordStyle] Source #
tokenise is, broadly-speaking, Prelude.words, except that: * the input is already divided into lines * each word-like "token" is categorised as one of {Ident,Other,Cmd} * #define's are parsed and returned out-of-band using the Cmd variant * All whitespace is preserved intact as tokens. * C-comments are converted to white-space (depending on first param) * Parens and commas are tokens in their own right. * Any cpp line continuations are respected. No errors can be raised. The inverse of tokenise is (concatMap deWordStyle).
Each token is classified as one of Ident, Other, or Cmd: * Ident is a word that could potentially match a macro name. * Cmd is a complete cpp directive (#define etc). * Other is anything else.
:: [(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 #
:: [(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 BoolOptions Source #
Options representable as Booleans.
BoolOptions | |
|
parseOptions :: [String] -> Either String CpphsOptions Source #
Parse all command-line options.
defaultCpphsOptions :: CpphsOptions Source #
Default options.
defaultBoolOptions :: BoolOptions Source #
Default settings of boolean options.
Source positions contain a filename, line, column, and an inclusion point, which is itself another source position, recursively.