[Haskell-cafe] Parsec Vs. src exts
Patrick Pelletier
code at funwithsoftware.org
Sun Feb 3 19:57:14 CET 2013
On 2/3/13 12:27 AM, Stephen Tetley wrote:
> Haskell-src-exts parses real Haskell - including most (if not all?)
> GHC extensions. If you were wanting to analyze 'in the wild' Haskell
> projects you might also want to use CPPHS as many Haskell projects use
> the CPP preprocessor.
That was something that surprised me when I first started using
haskell-src-exts. Since haskell-src-exts parses language pragmas
(including the CPP pragma), and since the haskell-src-exts package
depends on the cpphs package, I'd made the assumption it would run the C
preprocessor if the source file asked for the CPP language extension.
So, I was surprised when it didn't; it might be worth documenting that
it doesn't run CPP for you. (From reading the source, I discovered the
reason it depends on the cpphs package is to run the unlit preprocessor,
but not to run cpp itself.)
I'm still a beginning Haskeller, so this code might be ugly, but I wrote
a little bit of code to determine whether the C preprocessor was
requested by the source file, and run it if necessary:
stripShebang :: String -> String
stripShebang ('#':'!':rest) = tail $ dropWhile (/= '\n') rest
stripShebang s = s
-- extension ".lhs" is same criterion haskell-src-exts uses to decide unlit
perhapsUnlit fn contents =
if ".lhs" `isSuffixOf` fn then unlit fn contents else contents
parseFileWithCpp :: Maybe CpphsOptions -> Maybe ParseMode -> FilePath ->
IO (ParseResult (Module SrcSpanInfo, [Comment]))
parseFileWithCpp chopts pmode fn = do
contents <- readFile fn
let pmode' = fromMaybe (ParseMode fn [] False False (Just
baseFixities)) pmode
exts = fromMaybe [] $ readExtensions $ perhapsUnlit fn $
stripShebang contents
pmode'' = if ignoreLanguagePragmas pmode'
then pmode'
else pmode' { extensions = nub (exts ++ extensions pmode'),
-- since we already read language pragmas...
ignoreLanguagePragmas = True }
wannaCpp = CPP `elem` extensions pmode''
chopts' = fromMaybe defaultCpphsOptions chopts
-- haskell-lang-exts already handles unlit itself, so defer to that
chopts'' = chopts' { boolopts = (boolopts chopts') { literate =
False } }
doCpp = if wannaCpp then runCpphs else (\_ _ -> return)
contents' <- doCpp chopts'' fn contents
return $ parseFileContentsWithComments pmode'' contents'
Although this is fairly short, it isn't entirely trivial, and since it
seems like using haskell-src-exts together with cpphs is something many
people would want to do, I'm wondering if I should contribute a small
module to Hackage ("haskell-src-exts-cpp", perhaps) with this function
and perhaps a few other functions I've discovered are useful when using
haskell-src-exts.
Also, just a meta-question: if I encounter bugs or want to suggest
features for a package like haskell-src-exts, am I better off bringing
them up on a mailing list such as this one, or should I just email the
author directly? (Since haskell-src-exts, according to its Hackage
page, doesn't have a bug tracker or real home page, just a darcs
repository.)
--Patrick
More information about the Haskell-Cafe
mailing list