module Language.C.System.Preprocess (
Preprocessor(..),
CppOption(..),
CppArgs(..),rawCppArgs,addCppOption,addExtraOption,
runPreprocessor,
isPreprocessed,
)
where
import Language.C.Data.InputStream
import System.Exit
import System.Directory
import System.FilePath
import System.Environment
import System.IO
import Control.Exception
import Control.Monad
import Data.List
class Preprocessor cpp where
parseCPPArgs :: cpp -> [String] -> Either String (CppArgs, [String])
runCPP :: cpp -> CppArgs -> IO ExitCode
preprocessedExt :: String
preprocessedExt = ".i"
data CppOption =
IncludeDir FilePath
| Define String String
| Undefine String
| IncludeFile FilePath
data CppArgs = CppArgs {
cppOptions :: [CppOption],
extraOptions :: [String],
cppTmpDir :: Maybe FilePath,
inputFile :: FilePath,
outputFile :: Maybe FilePath
}
cppFile :: FilePath -> CppArgs
cppFile input_file = CppArgs { cppOptions = [], extraOptions = [], cppTmpDir = Nothing, inputFile = input_file, outputFile = Nothing }
rawCppArgs :: [String] -> FilePath -> CppArgs
rawCppArgs opts input_file =
CppArgs { inputFile = input_file, cppOptions = [], extraOptions = opts, outputFile = Nothing, cppTmpDir = Nothing }
addCppOption :: CppArgs -> CppOption -> CppArgs
addCppOption cpp_args opt =
cpp_args { cppOptions = opt : (cppOptions cpp_args) }
addExtraOption :: CppArgs -> String -> CppArgs
addExtraOption cpp_args extra =
cpp_args { extraOptions = extra : (extraOptions cpp_args) }
runPreprocessor :: (Preprocessor cpp) => cpp -> CppArgs -> IO (Either ExitCode InputStream)
runPreprocessor cpp cpp_args = do
bracket
getActualOutFile
removeTmpOutFile
invokeCpp
where
getActualOutFile :: IO FilePath
getActualOutFile = maybe (mkOutputFile (cppTmpDir cpp_args) (inputFile cpp_args)) return (outputFile cpp_args)
invokeCpp actual_out_file = do
exit_code <- runCPP cpp (cpp_args { outputFile = Just actual_out_file})
case exit_code of
ExitSuccess -> liftM Right (readInputStream actual_out_file)
ExitFailure _ -> return $ Left exit_code
removeTmpOutFile out_file = maybe (removeFile out_file) (\_ -> return ()) (outputFile cpp_args)
mkOutputFile :: Maybe FilePath -> FilePath -> IO FilePath
mkOutputFile tmp_dir_opt input_file =
do tmpDir <- getTempDir tmp_dir_opt
mkTmpFile tmpDir (getOutputFileName input_file)
where
getTempDir (Just tmpdir) = return tmpdir
getTempDir Nothing = getTemporaryDirectory
getOutputFileName :: FilePath -> FilePath
getOutputFileName fp | hasExtension fp = replaceExtension filename preprocessedExt
| otherwise = addExtension filename preprocessedExt
where
filename = takeFileName fp
mkTmpFile :: FilePath -> FilePath -> IO FilePath
mkTmpFile tmp_dir file_templ = do
(path,file_handle) <- openTempFile tmp_dir file_templ
hClose file_handle
return path
isPreprocessed :: FilePath -> Bool
isPreprocessed = (".i" `isSuffixOf`)