module System.Plugins.Parser (
parse, mergeModules, pretty, parsePragmas,
HsModule(..) ,
replaceModName
) where
#include "../../../config.h"
import Data.List
import Data.Char
import Data.Either ( )
#if defined(WITH_HSX)
import Language.Haskell.Hsx
#else
import Language.Haskell.Parser
import Language.Haskell.Syntax
import Language.Haskell.Pretty
#endif
parse :: FilePath
-> String
-> Either String HsModule
parse f fsrc =
#if defined(WITH_HSX)
case parseFileContentsWithMode (ParseMode f) fsrc of
#else
case parseModuleWithMode (ParseMode f) fsrc of
#endif
ParseOk src -> Right src
ParseFailed loc _ -> Left $ srcmsg loc
where
srcmsg loc = "parse error in " ++ f ++ "\n" ++
"line: " ++ (show $ srcLine loc) ++
", col: " ++ (show $ srcColumn loc)++ "\n"
pretty :: HsModule -> String
pretty code = prettyPrintWithMode (defaultMode { linePragmas = True }) code
mergeModules :: HsModule ->
HsModule ->
HsModule
mergeModules (HsModule l _ _ is ds )
(HsModule _ m' es' is' ds')
= (HsModule l m' es'
(mImps m' is is')
(mDecl ds ds') )
replaceModName :: HsModule -> String -> HsModule
replaceModName (HsModule l _ es is ds) nm = (HsModule l (Module nm) es is ds)
mImps :: Module ->
[HsImportDecl] ->
[HsImportDecl] ->
[HsImportDecl]
mImps plug_mod cimps timps =
case filter (!~ self) cimps of cimps' -> unionBy (=~) cimps' timps
where
self = ( HsImportDecl undefined plug_mod undefined undefined undefined )
mDecl ds es = let ds' = filter (not.typeDecl) ds
in sortBy decls $! unionBy (=~) ds' es
where
decls a b = compare (encoding a) (encoding b)
typeDecl :: HsDecl -> Bool
typeDecl (HsTypeSig _ _ _) = True
typeDecl _ = False
encoding :: HsDecl -> Int
encoding d = case d of
HsFunBind _ -> 1
HsPatBind _ _ _ _ -> 1
_ -> 0
class SynEq a where
(=~) :: a -> a -> Bool
(!~) :: a -> a -> Bool
n !~ m = not (n =~ m)
instance SynEq HsDecl where
(HsPatBind _ (HsPVar n) _ _) =~ (HsPatBind _ (HsPVar m) _ _) = n == m
(HsTypeSig _ (n:_) _) =~ (HsTypeSig _ (m:_) _) = n == m
_ =~ _ = False
instance SynEq HsImportDecl where
(HsImportDecl _ m _ _ _) =~ (HsImportDecl _ n _ _ _) = n == m
parsePragmas :: String
-> ([String],[String])
parsePragmas s = look $ lines s
where
look [] = ([],[])
look (l':ls) =
let l = remove_spaces l'
in case () of
() | null l -> look ls
| prefixMatch "#" l -> look ls
| prefixMatch "{-# LINE" l -> look ls
| Just (Option o) <- matchPragma l
-> let (as,bs) = look ls in (words o ++ as,bs)
| Just (Global g) <- matchPragma l
-> let (as,bs) = look ls in (as,words g ++ bs)
| otherwise -> ([],[])
data Pragma = Option !String | Global !String
matchPragma :: String -> Maybe Pragma
matchPragma s
| Just s1 <- maybePrefixMatch "{-#" s,
Just s2 <- maybePrefixMatch "OPTIONS" (remove_spaces s1),
Just s3 <- maybePrefixMatch "}-#" (reverse s2)
= Just (Option (reverse s3))
| Just s1 <- maybePrefixMatch "{-#" s,
Just s2 <- maybePrefixMatch "GLOBALOPTIONS" (remove_spaces s1),
Just s3 <- maybePrefixMatch "}-#" (reverse s2)
= Just (Global (reverse s3))
| otherwise
= Nothing
remove_spaces :: String -> String
remove_spaces = reverse . dropWhile isSpace . reverse . dropWhile isSpace
prefixMatch :: Eq a => [a] -> [a] -> Bool
prefixMatch [] _str = True
prefixMatch _pat [] = False
prefixMatch (p:ps) (s:ss) | p == s = prefixMatch ps ss
| otherwise = False
maybePrefixMatch :: String -> String -> Maybe String
maybePrefixMatch [] rest = Just rest
maybePrefixMatch (_:_) [] = Nothing
maybePrefixMatch (p:pat) (r:rest)
| p == r = maybePrefixMatch pat rest
| otherwise = Nothing