module Language.Preprocessor.Cpphs.HashDefine
( HashDefine(..)
, ArgOrText(..)
, expandMacro
, parseHashDefine
, simplifyHashDefines
) where
import Data.Char (isSpace)
import Data.List (intercalate)
data HashDefine
= LineDrop
{ name :: String }
| Pragma
{ name :: String }
| AntiDefined
{ name :: String
, linebreaks :: Int
}
| SymbolReplacement
{ name :: String
, replacement :: String
, linebreaks :: Int
}
| MacroExpansion
{ name :: String
, arguments :: [String]
, expansion :: [(ArgOrText,String)]
, linebreaks :: Int
}
deriving (Eq,Show)
symbolReplacement :: HashDefine
symbolReplacement =
SymbolReplacement
{ name=undefined, replacement=undefined, linebreaks=undefined }
data ArgOrText = Arg | Text | Str deriving (Eq,Show)
expandMacro :: HashDefine -> [String] -> Bool -> String
expandMacro macro parameters layout =
let env = zip (arguments macro) parameters
replace (Arg,s) = maybe ("") id (lookup s env)
replace (Str,s) = maybe (str "") str (lookup s env)
replace (Text,s) = if layout then s else filter (/='\n') s
str s = '"':s++"\""
checkArity | length (arguments macro) == 1 && length parameters <= 1
|| length (arguments macro) == length parameters = id
| otherwise = error ("macro "++name macro++" expected "++
show (length (arguments macro))++
" arguments, but was given "++
show (length parameters))
in
checkArity $ concatMap replace (expansion macro)
parseHashDefine :: Bool -> [String] -> Maybe HashDefine
parseHashDefine ansi def = (command . skip) def
where
skip xss@(x:xs) | all isSpace x = skip xs
| otherwise = xss
skip [] = []
command ("line":xs) = Just (LineDrop ("#line"++concat xs))
command ("pragma":xs) = Just (Pragma ("#pragma"++concat xs))
command ("define":xs) = Just (((define . skip) xs) { linebreaks=count def })
command ("undef":xs) = Just (((undef . skip) xs))
command _ = Nothing
undef (sym:_) = AntiDefined { name=sym, linebreaks=0 }
define (sym:xs) = case xs of
("(":ys) -> (macroHead sym [] . skip) ys
ys -> symbolReplacement
{ name=sym
, replacement = concatMap snd
(classifyRhs [] (chop (skip ys))) }
macroHead sym args (",":xs) = (macroHead sym args . skip) xs
macroHead sym args (")":xs) = MacroExpansion
{ name =sym , arguments = reverse args
, expansion = classifyRhs args (skip xs)
, linebreaks = undefined }
macroHead sym args (var:xs) = (macroHead sym (var:args) . skip) xs
macroHead sym args [] = error ("incomplete macro definition:\n"
++" #define "++sym++"("
++intercalate "," args)
classifyRhs args ("#":x:xs)
| ansi &&
x `elem` args = (Str,x): classifyRhs args xs
classifyRhs args ("##":xs)
| ansi = classifyRhs args xs
classifyRhs args (s:"##":s':xs)
| ansi && all isSpace s && all isSpace s'
= classifyRhs args xs
classifyRhs args (word:xs)
| word `elem` args = (Arg,word): classifyRhs args xs
| otherwise = (Text,word): classifyRhs args xs
classifyRhs _ [] = []
count = length . filter (=='\n') . concat
chop = reverse . dropWhile (all isSpace) . reverse
simplifyHashDefines :: [HashDefine] -> [(String,String)]
simplifyHashDefines = concatMap simp
where
simp hd@LineDrop{} = []
simp hd@Pragma{} = []
simp hd@AntiDefined{} = []
simp hd@SymbolReplacement{} = [(name hd, replacement hd)]
simp hd@MacroExpansion{} = [(name hd++"("++intercalate "," (arguments hd)
++")"
,concatMap snd (expansion hd))]