{-# LANGUAGE FlexibleContexts, FlexibleInstances, ScopedTypeVariables, OverloadedStrings #-} {-# OPTIONS_GHC -Wno-orphans #-} module Main where import Prelude hiding (readFile) import qualified Data.ByteString.Char8 as B import qualified Data.ByteString.Lazy.Char8 as LB import Data.Text.Encoding (encodeUtf8, decodeUtf8With) import Data.Text.Encoding.Error (replace) import Text.PrettyPrint (render) import System.Console.GetOpt import System.IO import System.Environment import System.Directory import System.FilePath import Text.PrettyPrint.GenericPretty (pp, pretty, Out) import Text.Read (readMaybe) import Data.List (sortBy, intercalate, (\\), isSuffixOf) import Data.Ord (comparing) import Data.Char (toLower) import Data.Maybe (listToMaybe, fromMaybe, maybeToList) import Data.Data import Data.Generics.Uniplate.Data import Language.Fortran.ParserMonad (selectFortranVersion, FortranVersion(..), fromRight) import qualified Language.Fortran.Lexer.FixedForm as FixedForm (collectFixedTokens, Token(..)) import qualified Language.Fortran.Lexer.FreeForm as FreeForm (collectFreeTokens, Token(..)) import Language.Fortran.Parser.Any import Language.Fortran.Util.ModFile import Language.Fortran.Util.Position import Language.Fortran.PrettyPrint import Language.Fortran.Analysis import Language.Fortran.AST import Language.Fortran.Analysis.Types import Language.Fortran.Analysis.BBlocks import Language.Fortran.Analysis.DataFlow import Language.Fortran.Analysis.Renaming import Data.Graph.Inductive hiding (trc, mf, version) import qualified Data.IntMap as IM import qualified Data.Map as M import Control.Monad import Text.Printf programName :: String programName = "fortran-src" main :: IO () main = do args <- getArgs (opts, parsedArgs) <- compileArgs args case (parsedArgs, action opts) of ([path], actionOpt) -> do contents <- flexReadFile path let version = fromMaybe (deduceVersion path) (fortranVersion opts) let (Just parserF0) = lookup version parserWithModFilesVersions let parserF m b s = fromRight (parserF0 m b s) let outfmt = outputFormat opts mods <- decodeModFiles $ includeDirs opts let mmap = combinedModuleMap mods let tenv = combinedTypeEnv mods let pvm = combinedParamVarMap mods let runTypes = analyseAndCheckTypesWithEnv tenv . analyseRenamesWithModuleMap mmap . initAnalysis let runRenamer = stripAnalysis . rename . analyseRenamesWithModuleMap mmap . initAnalysis let runBBlocks pf = showBBlocks pf' ++ "\n\n" ++ showDataFlow pf' where pf' = analyseParameterVars pvm . analyseBBlocks . analyseRenamesWithModuleMap mmap . initAnalysis $ pf let runSuperGraph pf | outfmt == DOT = superBBGrToDOT sgr | otherwise = superGraphDataFlow pf' sgr where pf' = analyseParameterVars pvm . analyseBBlocks . analyseRenamesWithModuleMap mmap . initAnalysis $ pf bbm = genBBlockMap pf' sgr = genSuperBBGr bbm let runCompile = encodeModFile . genModFile . fst . analyseTypesWithEnv tenv . analyseRenamesWithModuleMap mmap . initAnalysis let findBlockPU pf astBlockId = listToMaybe [ pu | pu <- universeBi pf :: [ProgramUnit (Analysis A0)] , bbgr <- maybeToList (bBlocks (getAnnotation pu)) , b <- concatMap snd $ labNodes (bbgrGr bbgr) , insLabel (getAnnotation b) == Just astBlockId ] case actionOpt of Lex | version `elem` [ Fortran66, Fortran77, Fortran77Extended, Fortran77Legacy ] -> print $ FixedForm.collectFixedTokens version contents Lex | version `elem` [Fortran90, Fortran2003, Fortran2008] -> print $ FreeForm.collectFreeTokens version contents Lex -> ioError $ userError $ usageInfo programName options Parse -> pp $ parserF mods contents path Typecheck -> let (pf, _, errs) = runTypes (parserF mods contents path) in printTypeErrors errs >> printTypes (extractTypeEnv pf) Rename -> pp . runRenamer $ parserF mods contents path BBlocks -> putStrLn . runBBlocks $ parserF mods contents path SuperGraph -> putStrLn . runSuperGraph $ parserF mods contents path Reprint -> putStrLn . render . flip (pprint version) (Just 0) $ parserF mods contents path Compile -> do let bytes = runCompile $ parserF mods contents path let fspath = path <.> modFileSuffix LB.writeFile fspath bytes DumpModFile -> do let path' = if modFileSuffix `isSuffixOf` path then path else path <.> modFileSuffix contents' <- LB.readFile path' case decodeModFile contents' of Left msg -> putStrLn $ "Error: " ++ msg Right mf -> putStrLn $ "Filename: " ++ moduleFilename mf ++ "\n\nStringMap:\n" ++ showStringMap (combinedStringMap [mf]) ++ "\n\nModuleMap:\n" ++ showModuleMap (combinedModuleMap [mf]) ++ "\n\nDeclMap:\n" ++ showGenericMap (combinedDeclMap [mf]) ++ "\n\nTypeEnv:\n" ++ showTypes (combinedTypeEnv [mf]) ++ "\n\nParamVarMap:\n" ++ showGenericMap (combinedParamVarMap [mf]) ++ "\n\nOther Data Labels: " ++ show (getLabelsModFileData mf) ShowFlows isFrom isSuper astBlockId -> do let pf = analyseParameterVars pvm . analyseBBlocks . analyseRenamesWithModuleMap mmap . initAnalysis $ parserF mods contents path let bbm = genBBlockMap pf case (isSuper, findBlockPU pf astBlockId) of (False, Nothing) -> fail "Couldn't find given AST block ID number." (False, Just pu) | Just bbgr <- M.lookup (puName pu) bbm -> putStrLn $ showFlowsDOT pf bbgr astBlockId isFrom | otherwise -> do print $ M.keys bbm fail $ "Internal error: Program Unit " ++ show (puName pu) ++ " is lacking a basic block graph." (True, _) -> do let sgr = genSuperBBGr bbm putStrLn $ showFlowsDOT pf (superBBGrGraph sgr) astBlockId isFrom ShowBlocks mlinenum -> do let pf = analyseBBlocks . analyseRenamesWithModuleMap mmap . initAnalysis $ parserF mods contents path let f :: ([ASTBlockNode], Int) -> ([ASTBlockNode], Int) -> ([ASTBlockNode], Int) f (nodes1, len1) (nodes2, len2) | len1 < len2 = (nodes1, len1) | len2 < len1 = (nodes2, len2) | otherwise = (nodes1 ++ nodes2, len1) let lineMap :: IM.IntMap ([ASTBlockNode], Int) -- ([list of IDs], line-distance of span) lineMap = IM.fromListWith f [ (l, ([i], lineDistance ss)) | b <- universeBi pf :: [Block (Analysis A0)] , i <- maybeToList . insLabel $ getAnnotation b , let ss = getSpan b , l <- spannedLines ss ] case mlinenum of Just l -> putStrLn . unwords . map show $ fromMaybe [] (fst <$> IM.lookup l lineMap) Nothing -> do let lineBs = B.lines contents let maxLen = maximum (0:map B.length lineBs) forM_ (zip lineBs [1..]) $ \ (line, l) -> do let nodeIDs = fromMaybe [] (fst <$> IM.lookup l lineMap) let nodeStr = B.intercalate "," (map (B.pack . ('B':) . show) nodeIDs) let suffix | null nodeIDs = "" | otherwise = B.replicate (maxLen - B.length line + 1) ' ' <> "!" <> nodeStr B.putStrLn $ line <> suffix _ -> fail $ usageInfo programName options -- List files in dir recursively rGetDirContents :: String -> IO [String] rGetDirContents d = canonicalizePath d >>= \d' -> go [d'] d' where go seen d'' = do ds <- getDirectoryContents d'' fmap concat . mapM f $ ds \\ [".", ".."] -- remove '.' and '..' entries where f x = do path <- canonicalizePath $ d ++ "/" ++ x g <- doesDirectoryExist path if g && notElem path seen then do x' <- go (path : seen) path return $ map (\ y -> x ++ "/" ++ y) x' else return [x] -- List files in dir getDirContents :: String -> IO [String] getDirContents d = do d' <- canonicalizePath d map (d' ) `fmap` listDirectory d' decodeModFiles :: [String] -> IO ModFiles decodeModFiles = foldM (\ modFiles d -> do -- Figure out the camfort mod files and parse them. modFileNames <- filter isModFile `fmap` getDirContents d addedModFiles <- forM modFileNames $ \ modFileName -> do contents <- LB.readFile (d modFileName) case decodeModFile contents of Left msg -> do hPutStrLn stderr $ modFileName ++ ": Error: " ++ msg return emptyModFile Right modFile -> do hPutStrLn stderr $ modFileName ++ ": successfully parsed precompiled file." return modFile return $ addedModFiles ++ modFiles ) emptyModFiles isModFile :: FilePath -> Bool isModFile = (== modFileSuffix) . takeExtension superGraphDataFlow :: forall a. (Out a, Data a) => ProgramFile (Analysis a) -> SuperBBGr (Analysis a) -> String superGraphDataFlow pf sgr = showBBGr (bbgrMap (nmap (map (fmap insLabel))) gr') ++ "\n\n" ++ replicate 50 '-' ++ "\n\n" ++ show entries ++ "\n\n" ++ replicate 50 '-' ++ "\n\n" ++ dfStr gr' where gr' = superBBGrGraph sgr entries = superBBGrEntries sgr dfStr gr = (\ (l, x) -> '\n':l ++ ": " ++ x) =<< [ ("callMap", show cm) , ("entries", show (bbgrEntries gr)) , ("exits", show (bbgrExits gr)) , ("postOrder", show (postOrder gr)) , ("revPostOrder", show (revPostOrder gr)) , ("revPreOrder", show (revPreOrder gr)) , ("dominators", show (dominators gr)) , ("iDominators", show (iDominators gr)) , ("defMap", show dm) , ("lva", show (IM.toList $ lva gr)) , ("rd", show (IM.toList rDefs)) , ("backEdges", show bedges) , ("topsort", show (topsort $ bbgrGr gr)) , ("scc ", show (scc $ bbgrGr gr)) , ("loopNodes", show (loopNodes bedges $ bbgrGr gr)) , ("duMap", show (genDUMap bm dm gr rDefs)) , ("udMap", show (genUDMap bm dm gr rDefs)) , ("flowsTo", show (edges flTo)) , ("varFlowsTo", show (genVarFlowsToMap dm flTo)) , ("ivMap", show (genInductionVarMap bedges gr)) , ("blockMap", unlines [ "AST-block " ++ show i ++ ":\n" ++ pretty b | (i, b) <- IM.toList bm ]) , ("derivedInd", unlines [ "Expression " ++ show i ++ " (IE: " ++ show ie ++ "):\n" ++ pretty e | e <- universeBi bm :: [Expression (Analysis a)] , i <- maybeToList (insLabel (getAnnotation e)) , let ie = IM.lookup i diMap ]) , ("constExpMap", show (genConstExpMap pf)) ] where bedges = genBackEdgeMap (dominators gr) $ bbgrGr gr flTo = genFlowsToGraph bm dm gr rDefs rDefs = rd gr diMap = genDerivedInductionMap bedges gr lva = liveVariableAnalysis bm = genBlockMap pf dm = genDefMap bm rd = reachingDefinitions dm cm = genCallMap pf showGenericMap :: (Show a, Show b) => M.Map a b -> String showGenericMap = unlines . map (\ (k, v) -> show k ++ " : " ++ show v) . M.toList showStringMap :: StringMap -> String showStringMap = showGenericMap showModuleMap :: ModuleMap -> String showModuleMap = concatMap (\ (n, m) -> show n ++ ":\n" ++ (unlines . map (" "++) . lines . showGenericMap $ m)) . M.toList showTypes :: TypeEnv -> String showTypes tenv = flip concatMap (M.toList tenv) $ \ (name, IDType { idVType = vt, idCType = ct }) -> printf "%s\t\t%s %s\n" name (drop 4 $ maybe " -" show vt) (drop 2 $ maybe " " show ct) printTypes :: TypeEnv -> IO () printTypes = putStrLn . showTypes showTypeErrors :: [TypeError] -> String showTypeErrors errs = unlines [ show ss ++ ": " ++ msg | (msg, ss) <- sortBy (comparing snd) errs ] printTypeErrors :: [TypeError] -> IO () printTypeErrors = putStrLn . showTypeErrors data Action = Lex | Parse | Typecheck | Rename | BBlocks | SuperGraph | Reprint | DumpModFile | Compile | ShowFlows Bool Bool Int | ShowBlocks (Maybe Int) deriving Eq instance Read Action where readsPrec _ value = let options' = [ ("lex", Lex) , ("parse", Parse) ] in tryTypes options' where tryTypes [] = [] tryTypes ((attempt,result):xs) = if map toLower value == attempt then [(result, "")] else tryTypes xs data OutputFormat = Default | DOT deriving Eq data Options = Options { fortranVersion :: Maybe FortranVersion , action :: Action , outputFormat :: OutputFormat , includeDirs :: [String] } initOptions :: Options initOptions = Options Nothing Parse Default [] options :: [OptDescr (Options -> Options)] options = [ Option ['v','F'] ["fortranVersion"] (ReqArg (\v opts -> opts { fortranVersion = selectFortranVersion v }) "VERSION") "Fortran version to use, format: Fortran[66/77/77Legacy/77Extended/90]" , Option ['a'] ["action"] (ReqArg (\a opts -> opts { action = read a }) "ACTION") "lex or parse action" , Option ['t'] ["typecheck"] (NoArg $ \ opts -> opts { action = Typecheck }) "parse and run typechecker" , Option ['R'] ["rename"] (NoArg $ \ opts -> opts { action = Rename }) "parse and rename variables" , Option ['B'] ["bblocks"] (NoArg $ \ opts -> opts { action = BBlocks }) "analyse basic blocks" , Option ['S'] ["supergraph"] (NoArg $ \ opts -> opts { action = SuperGraph }) "analyse super graph of basic blocks" , Option ['r'] ["reprint"] (NoArg $ \ opts -> opts { action = Reprint }) "Parse and output using pretty printer" , Option [] ["dot"] (NoArg $ \ opts -> opts { outputFormat = DOT }) "output graphs in GraphViz DOT format" , Option [] ["dump-mod-file"] (NoArg $ \ opts -> opts { action = DumpModFile }) "dump the information contained within mod files" , Option ['I'] ["include-dir"] (ReqArg (\ d opts -> opts { includeDirs = d:includeDirs opts }) "DIR") "directory to search for precompiled 'mod files'" , Option ['c'] ["compile"] (NoArg $ \ opts -> opts { action = Compile }) "compile an .fsmod file from the input" , Option [] ["show-block-numbers"] (OptArg (\a opts -> opts { action = ShowBlocks (a >>= readMaybe) } ) "LINE-NUM") "Show the corresponding AST-block identifier number next to every line of code." , Option [] ["show-flows-to"] (ReqArg (\a opts -> case a of s:num | toLower s == 's' -> opts { action = ShowFlows False True (read num) } b:num | toLower b == 'b' -> opts { action = ShowFlows False False (read num) } num -> opts { action = ShowFlows False False (read num) } ) "AST-BLOCK-ID") "dump a graph showing flows-to information from the given AST-block ID; prefix with 's' for supergraph" , Option [] ["show-flows-from"] (ReqArg (\a opts -> case a of s:num | toLower s == 's' -> opts { action = ShowFlows True True (read num) } b:num | toLower b == 'b' -> opts { action = ShowFlows True False (read num) } num -> opts { action = ShowFlows True False (read num) } ) "AST-BLOCK-ID") "dump a graph showing flows-from information from the given AST-block ID; prefix with 's' for supergraph" ] compileArgs :: [ String ] -> IO (Options, [ String ]) compileArgs args = case getOpt Permute options args of (o, n, []) -> return (foldl (flip id) initOptions o, n) (_, _, errors) -> ioError $ userError $ concat errors ++ usageInfo header options where header = "Usage: " ++ programName ++ " [OPTION...] " instance {-# OVERLAPPING #-} Show [ FixedForm.Token ] where show = unlines . lines' where lines' [] = [] lines' xs = let (x, xs') = break isNewline xs in case xs' of (nl@(FixedForm.TNewline _):xs'') -> ('\t' : (intercalate ", " . map show $ x ++ [nl])) : lines' xs'' xs'' -> [ show xs'' ] isNewline (FixedForm.TNewline _) = True isNewline _ = False instance {-# OVERLAPPING #-} Show [ FreeForm.Token ] where show = unlines . lines' where lines' [] = [] lines' xs = let (x, xs') = break isNewline xs in case xs' of (nl@(FreeForm.TNewline _):xs'') -> ('\t' : (intercalate ", " . map show $ x ++ [nl])) : lines' xs'' xs'' -> [ show xs'' ] isNewline (FreeForm.TNewline _) = True isNewline _ = False flexReadFile :: String -> IO B.ByteString flexReadFile = fmap (encodeUtf8 . decodeUtf8With (replace ' ')) . B.readFile