From 260550c791342d574a9fcdc08949f4ed3c153663 Mon Sep 17 00:00:00 2001 From: Dominic Orchard Date: Thu, 15 Aug 2024 17:09:58 +0100 Subject: [PATCH 01/28] topological sort of dependency graph --- src/Language/Fortran/Analysis/ModGraph.hs | 12 +++++++++++- 1 file changed, 11 insertions(+), 1 deletion(-) diff --git a/src/Language/Fortran/Analysis/ModGraph.hs b/src/Language/Fortran/Analysis/ModGraph.hs index 297b0dfa..f2381dae 100644 --- a/src/Language/Fortran/Analysis/ModGraph.hs +++ b/src/Language/Fortran/Analysis/ModGraph.hs @@ -1,6 +1,6 @@ -- | Generate a module use-graph. module Language.Fortran.Analysis.ModGraph - (genModGraph, ModGraph(..), ModOrigin(..), modGraphToDOT, takeNextMods, delModNodes) + (genModGraph, ModGraph(..), ModOrigin(..), modGraphToList, modGraphToDOT, takeNextMods, delModNodes) where import Language.Fortran.AST hiding (setName) @@ -108,6 +108,16 @@ modGraphToDOT ModGraph { mgGraph = gr } = unlines dot (labNodes gr) ++ [ "}\n" ] +-- Provides a topological sort of the graph, giving a list of filenames +modGraphToList :: ModGraph -> [String] +modGraphToList mg + | nxt <- takeNextMods mg + , not (null nxt) = + let mg' = delModNodes (map fst nxt) mg + in [ fn | (_, Just (MOFile fn)) <- nxt ] ++ modGraphToList mg' +modGraphToList _ = [] + + takeNextMods :: ModGraph -> [(Node, Maybe ModOrigin)] takeNextMods ModGraph { mgModNodeMap = mnmap, mgGraph = gr } = noDepFiles where From 8e285f0548d613bc2dc6b3ed04c857cf2c8f8b4e Mon Sep 17 00:00:00 2001 From: Dominic Orchard Date: Thu, 15 Aug 2024 18:20:02 +0100 Subject: [PATCH 02/28] add command line argument for showing the dependency list --- app/Main.hs | 10 +++++++++- 1 file changed, 9 insertions(+), 1 deletion(-) diff --git a/app/Main.hs b/app/Main.hs index 85e7123f..89d2b63f 100644 --- a/app/Main.hs +++ b/app/Main.hs @@ -59,6 +59,10 @@ main = do paths' <- expandDirs paths mg <- genModGraph (fortranVersion opts) (includeDirs opts) (cppOptions opts) paths' putStrLn $ modGraphToDOT mg + (paths, ShowMakeList) -> do + paths' <- expandDirs paths + mg <- genModGraph (fortranVersion opts) (includeDirs opts) (cppOptions opts) paths' + mapM_ putStrLn (modGraphToList mg) -- make: construct a build-dep graph and follow it (paths, Make) -> do let mvers = fortranVersion opts @@ -328,7 +332,7 @@ printTypeErrors = putStrLn . showTypeErrors data Action = Lex | Parse | Typecheck | Rename | BBlocks | SuperGraph | Reprint | DumpModFile | Compile - | ShowFlows Bool Bool Int | ShowBlocks (Maybe Int) | ShowMakeGraph | Make + | ShowFlows Bool Bool Int | ShowBlocks (Maybe Int) | ShowMakeGraph | ShowMakeList | Make deriving Eq instance Read Action where @@ -423,6 +427,10 @@ options = ["show-make-graph"] (NoArg $ \ opts -> opts { action = ShowMakeGraph }) "dump a graph showing the build structure of modules" + , Option [] + ["show-make-list"] + (NoArg $ \ opts -> opts { action = ShowMakeList }) + "dump a list of files in build dependency order (topological sort from the dependency graph)" , Option [] ["show-block-numbers"] (OptArg (\a opts -> opts { action = ShowBlocks (a >>= readMaybe) } From 446f7e976e707941c56e052ddb92cb98b0a6bc07 Mon Sep 17 00:00:00 2001 From: Dominic Orchard Date: Thu, 15 Aug 2024 18:20:46 +0100 Subject: [PATCH 03/28] move some useful helper functions from Main to Utils so easier to reuse elsewhere --- app/Main.hs | 32 ------------------------ src/Language/Fortran/Util/Files.hs | 40 ++++++++++++++++++++++++++++-- 2 files changed, 38 insertions(+), 34 deletions(-) diff --git a/app/Main.hs b/app/Main.hs index 89d2b63f..7d6bad42 100644 --- a/app/Main.hs +++ b/app/Main.hs @@ -209,38 +209,6 @@ main = do _ -> fail $ usageInfo programName options _ -> fail $ usageInfo programName options --- | Expand all paths that are directories into a list of Fortran --- files from a recursive directory listing. -expandDirs :: [FilePath] -> IO [FilePath] -expandDirs = fmap concat . mapM each - where - each path = do - isDir <- doesDirectoryExist path - if isDir - then listFortranFiles path - else pure [path] - --- | Get a list of Fortran files under the given directory. -listFortranFiles :: FilePath -> IO [FilePath] -listFortranFiles dir = filter isFortran <$> listDirectoryRecursively dir - where - -- | True if the file has a valid fortran extension. - isFortran :: FilePath -> Bool - isFortran x = map toLower (takeExtension x) `elem` exts - where exts = [".f", ".f90", ".f77", ".f03"] - -listDirectoryRecursively :: FilePath -> IO [FilePath] -listDirectoryRecursively dir = listDirectoryRec dir "" - where - listDirectoryRec :: FilePath -> FilePath -> IO [FilePath] - listDirectoryRec d f = do - let fullPath = d f - isDir <- doesDirectoryExist fullPath - if isDir - then do - conts <- listDirectory fullPath - concat <$> mapM (listDirectoryRec fullPath) conts - else pure [fullPath] compileFileToMod :: Maybe FortranVersion -> ModFiles -> FilePath -> Maybe FilePath -> IO ModFile compileFileToMod mvers mods path moutfile = do diff --git a/src/Language/Fortran/Util/Files.hs b/src/Language/Fortran/Util/Files.hs index b4bd1ce2..acdd71b1 100644 --- a/src/Language/Fortran/Util/Files.hs +++ b/src/Language/Fortran/Util/Files.hs @@ -3,6 +3,9 @@ module Language.Fortran.Util.Files , runCPP , getDirContents , rGetDirContents + , expandDirs + , listFortranFiles + , listDirectoryRecursively ) where import qualified Data.Text.Encoding as T @@ -10,11 +13,11 @@ import qualified Data.Text.Encoding.Error as T import qualified Data.ByteString.Char8 as B import System.Directory (listDirectory, canonicalizePath, doesDirectoryExist, getDirectoryContents) -import System.FilePath (()) +import System.FilePath ((), takeExtension) import System.IO.Temp (withSystemTempDirectory) import System.Process (callProcess) import Data.List ((\\), foldl') -import Data.Char (isNumber) +import Data.Char (isNumber, toLower) -- | Obtain a UTF-8 safe 'B.ByteString' representation of a file's contents. -- -- Invalid UTF-8 is replaced with the space character. @@ -68,3 +71,36 @@ runCPP (Just cppOpts) path = do let ls = B.lines contents let ls' = reverse . fst $ foldl' processCPPLine ([], 1) ls return $ B.unlines ls' + +-- | Expand all paths that are directories into a list of Fortran +-- files from a recursive directory listing. +expandDirs :: [FilePath] -> IO [FilePath] +expandDirs = fmap concat . mapM each + where + each path = do + isDir <- doesDirectoryExist path + if isDir + then listFortranFiles path + else pure [path] + +-- | Get a list of Fortran files under the given directory. +listFortranFiles :: FilePath -> IO [FilePath] +listFortranFiles dir = filter isFortran <$> listDirectoryRecursively dir + where + -- | True if the file has a valid fortran extension. + isFortran :: FilePath -> Bool + isFortran x = map toLower (takeExtension x) `elem` exts + where exts = [".f", ".f90", ".f77", ".f03"] + +listDirectoryRecursively :: FilePath -> IO [FilePath] +listDirectoryRecursively dir = listDirectoryRec dir "" + where + listDirectoryRec :: FilePath -> FilePath -> IO [FilePath] + listDirectoryRec d f = do + let fullPath = d f + isDir <- doesDirectoryExist fullPath + if isDir + then do + conts <- listDirectory fullPath + concat <$> mapM (listDirectoryRec fullPath) conts + else pure [fullPath] From 8eaa50f25ff6529bfbb33b91225c9631db0d97f9 Mon Sep 17 00:00:00 2001 From: Dominic Orchard Date: Thu, 15 Aug 2024 18:22:06 +0100 Subject: [PATCH 04/28] add test for module graph --- fortran-src.cabal | 5 ++++ test-data/module/leaf.f90 | 4 +++ test-data/module/mid1.f90 | 4 +++ test-data/module/mid2.f90 | 4 +++ test-data/module/top.f90 | 5 ++++ .../Language/Fortran/Analysis/ModGraphSpec.hs | 25 +++++++++++++++++++ 6 files changed, 47 insertions(+) create mode 100644 test-data/module/leaf.f90 create mode 100644 test-data/module/mid1.f90 create mode 100644 test-data/module/mid2.f90 create mode 100644 test-data/module/top.f90 create mode 100644 test/Language/Fortran/Analysis/ModGraphSpec.hs diff --git a/fortran-src.cabal b/fortran-src.cabal index 25f8e6fd..647e8d44 100644 --- a/fortran-src.cabal +++ b/fortran-src.cabal @@ -27,6 +27,10 @@ extra-source-files: CHANGELOG.md test-data/f77-include/foo.f test-data/f77-include/no-newline/foo.f + test-data/module/leaf.f90 + test-data/module/mid1.f90 + test-data/module/mid2.f90 + test-data/module/top.f90 test-data/rewriter/replacementsmap-columnlimit/001_foo.f test-data/rewriter/replacementsmap-columnlimit/001_foo.f.expected test-data/rewriter/replacementsmap-columnlimit/002_other.f @@ -276,6 +280,7 @@ test-suite spec other-modules: Language.Fortran.Analysis.BBlocksSpec Language.Fortran.Analysis.DataFlowSpec + Language.Fortran.Analysis.ModGraphSpec Language.Fortran.Analysis.RenamingSpec Language.Fortran.Analysis.SemanticTypesSpec Language.Fortran.Analysis.TypesSpec diff --git a/test-data/module/leaf.f90 b/test-data/module/leaf.f90 new file mode 100644 index 00000000..3a333cac --- /dev/null +++ b/test-data/module/leaf.f90 @@ -0,0 +1,4 @@ +module leaf + implicit none + real :: constant = 0.1 +end module \ No newline at end of file diff --git a/test-data/module/mid1.f90 b/test-data/module/mid1.f90 new file mode 100644 index 00000000..50bad448 --- /dev/null +++ b/test-data/module/mid1.f90 @@ -0,0 +1,4 @@ +module mid1 + implicit none + use leaf +end module \ No newline at end of file diff --git a/test-data/module/mid2.f90 b/test-data/module/mid2.f90 new file mode 100644 index 00000000..b4924aee --- /dev/null +++ b/test-data/module/mid2.f90 @@ -0,0 +1,4 @@ +module mid2 + implicit none + use leaf +end module \ No newline at end of file diff --git a/test-data/module/top.f90 b/test-data/module/top.f90 new file mode 100644 index 00000000..22eba01e --- /dev/null +++ b/test-data/module/top.f90 @@ -0,0 +1,5 @@ +module top + implicit none + use mid1 + use mid2 +end module \ No newline at end of file diff --git a/test/Language/Fortran/Analysis/ModGraphSpec.hs b/test/Language/Fortran/Analysis/ModGraphSpec.hs new file mode 100644 index 00000000..df1f93e5 --- /dev/null +++ b/test/Language/Fortran/Analysis/ModGraphSpec.hs @@ -0,0 +1,25 @@ +module Language.Fortran.Analysis.ModGraphSpec (spec) where + +import Test.Hspec +import TestUtil + +import Language.Fortran.Analysis.ModGraph +import Language.Fortran.Util.Files (expandDirs) +import Language.Fortran.Version + +spec :: Spec +spec = + describe "Modgraph" $ + it "Dependency graph and topological sort on small package" $ + testDependencyList + +-- A simple test on a simple module structure to check that +-- we are understanding this correctly (via the dependency graph +-- and then its topological sort). +testDependencyList = do + paths' <- expandDirs ["test-data/module"] + mg <- genModGraph (Just Fortran90) ["."] Nothing paths' + let list = modGraphToList mg + let files = ["leaf.f90", "mid1.f90", "mid2.f90", "top.f90"] + let filesWithPaths = map ("test-data/module/" ++) files + list `shouldBe` filesWithPaths From 3a2ca1da337800266309e9c1faaac08d6149c630 Mon Sep 17 00:00:00 2001 From: Dominic Orchard Date: Thu, 15 Aug 2024 18:22:27 +0100 Subject: [PATCH 05/28] better error handling when there are parsing issues when building make file graph --- src/Language/Fortran/Analysis/ModGraph.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Language/Fortran/Analysis/ModGraph.hs b/src/Language/Fortran/Analysis/ModGraph.hs index f2381dae..e9ad1699 100644 --- a/src/Language/Fortran/Analysis/ModGraph.hs +++ b/src/Language/Fortran/Analysis/ModGraph.hs @@ -85,12 +85,16 @@ genModGraph mversion includeDirs cppOpts paths = do let version = fromMaybe (deduceFortranVersion path) mversion mods = map snd fileMods parserF0 = Parser.byVerWithMods mods version - parserF fn bs = fromRight' $ parserF0 fn bs + parserF fn bs = + case parserF0 fn bs of + Right x -> return x + Left err -> do + error $ show err forM_ fileMods $ \ (fileName, mod) -> do forM_ [ name | Named name <- M.keys (combinedModuleMap [mod]) ] $ \ name -> do _ <- maybeAddModName name . Just $ MOFSMod fileName pure () - let pf = parserF path contents + pf <- parserF path contents mapM_ (perModule path) (childrenBi pf :: [ProgramUnit ()]) pure () execStateT (mapM_ iter paths) modGraph0 From 12c3fab67d5fcd35099cea7103c376470d640401 Mon Sep 17 00:00:00 2001 From: Dominic Orchard Date: Thu, 15 Aug 2024 19:25:11 +0100 Subject: [PATCH 06/28] make test platform agnostic --- test/Language/Fortran/Analysis/ModGraphSpec.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/test/Language/Fortran/Analysis/ModGraphSpec.hs b/test/Language/Fortran/Analysis/ModGraphSpec.hs index df1f93e5..75e28f5f 100644 --- a/test/Language/Fortran/Analysis/ModGraphSpec.hs +++ b/test/Language/Fortran/Analysis/ModGraphSpec.hs @@ -6,6 +6,7 @@ import TestUtil import Language.Fortran.Analysis.ModGraph import Language.Fortran.Util.Files (expandDirs) import Language.Fortran.Version +import System.FilePath (()) spec :: Spec spec = @@ -21,5 +22,5 @@ testDependencyList = do mg <- genModGraph (Just Fortran90) ["."] Nothing paths' let list = modGraphToList mg let files = ["leaf.f90", "mid1.f90", "mid2.f90", "top.f90"] - let filesWithPaths = map ("test-data/module/" ++) files + let filesWithPaths = map (("test-data" "module") ) files list `shouldBe` filesWithPaths From 2767ef608a1cfe9bb68923c7180cb51fdf4dd4a5 Mon Sep 17 00:00:00 2001 From: Dominic Orchard Date: Thu, 15 Aug 2024 21:37:45 +0100 Subject: [PATCH 07/28] make test platform agnostic (missed a case) --- test/Language/Fortran/Analysis/ModGraphSpec.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/test/Language/Fortran/Analysis/ModGraphSpec.hs b/test/Language/Fortran/Analysis/ModGraphSpec.hs index 75e28f5f..dd2528db 100644 --- a/test/Language/Fortran/Analysis/ModGraphSpec.hs +++ b/test/Language/Fortran/Analysis/ModGraphSpec.hs @@ -18,7 +18,7 @@ spec = -- we are understanding this correctly (via the dependency graph -- and then its topological sort). testDependencyList = do - paths' <- expandDirs ["test-data/module"] + paths' <- expandDirs ["test-data" "module"] mg <- genModGraph (Just Fortran90) ["."] Nothing paths' let list = modGraphToList mg let files = ["leaf.f90", "mid1.f90", "mid2.f90", "top.f90"] From d9ebee959f1a8d2e6216b89f858bdd171ec43317 Mon Sep 17 00:00:00 2001 From: Dominic Orchard Date: Fri, 23 Aug 2024 14:14:16 +0100 Subject: [PATCH 08/28] remove any duplicates --- src/Language/Fortran/Analysis/ModGraph.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Language/Fortran/Analysis/ModGraph.hs b/src/Language/Fortran/Analysis/ModGraph.hs index e9ad1699..3ae18500 100644 --- a/src/Language/Fortran/Analysis/ModGraph.hs +++ b/src/Language/Fortran/Analysis/ModGraph.hs @@ -97,7 +97,10 @@ genModGraph mversion includeDirs cppOpts paths = do pf <- parserF path contents mapM_ (perModule path) (childrenBi pf :: [ProgramUnit ()]) pure () - execStateT (mapM_ iter paths) modGraph0 + execStateT (mapM_ iter (removeDuplicates paths)) modGraph0 + +removeDuplicates :: Eq a => [a] -> [a] +removeDuplicates = foldl (\ acc x -> if x `elem` acc then acc else x : acc) [] modGraphToDOT :: ModGraph -> String modGraphToDOT ModGraph { mgGraph = gr } = unlines dot From eb111e7b35f6942093da2c2d499833f5eff68874 Mon Sep 17 00:00:00 2001 From: Dominic Orchard Date: Fri, 23 Aug 2024 14:23:51 +0100 Subject: [PATCH 09/28] keep first occurence when removing duplicates --- src/Language/Fortran/Analysis/ModGraph.hs | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/src/Language/Fortran/Analysis/ModGraph.hs b/src/Language/Fortran/Analysis/ModGraph.hs index 3ae18500..a3ef9d60 100644 --- a/src/Language/Fortran/Analysis/ModGraph.hs +++ b/src/Language/Fortran/Analysis/ModGraph.hs @@ -99,8 +99,13 @@ genModGraph mversion includeDirs cppOpts paths = do pure () execStateT (mapM_ iter (removeDuplicates paths)) modGraph0 +-- Remove duplicates from a list preserving the left most occurrence. removeDuplicates :: Eq a => [a] -> [a] -removeDuplicates = foldl (\ acc x -> if x `elem` acc then acc else x : acc) [] +removeDuplicates [] = [] +removeDuplicates (x:xs) = + if x `elem` xs + then x : removeDuplicates (filter (/= x) xs) + else x : removeDuplicates xs modGraphToDOT :: ModGraph -> String modGraphToDOT ModGraph { mgGraph = gr } = unlines dot From d1a4004477a8e47a8caf0403bb5a7d358ab487f2 Mon Sep 17 00:00:00 2001 From: Dominic Orchard Date: Mon, 2 Sep 2024 16:30:19 +0100 Subject: [PATCH 10/28] filepath consistency --- src/Language/Fortran/Util/Files.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Language/Fortran/Util/Files.hs b/src/Language/Fortran/Util/Files.hs index acdd71b1..7cee0325 100644 --- a/src/Language/Fortran/Util/Files.hs +++ b/src/Language/Fortran/Util/Files.hs @@ -39,11 +39,11 @@ rGetDirContents d = canonicalizePath d >>= \d' -> go [d'] d' fmap concat . mapM f $ ds \\ [".", ".."] -- remove '.' and '..' entries where f x = do - path <- canonicalizePath $ d ++ "/" ++ x + 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' + return $ map (\ y -> x y) x' else return [x] -- | Run the C Pre Processor over the file before reading into a bytestring From 921f8f768880a2c3816209d96aa55db950317f93 Mon Sep 17 00:00:00 2001 From: Dominic Orchard Date: Mon, 2 Sep 2024 16:36:26 +0100 Subject: [PATCH 11/28] remove duplicates after processing to a list --- src/Language/Fortran/Analysis/ModGraph.hs | 16 +++++++++------- 1 file changed, 9 insertions(+), 7 deletions(-) diff --git a/src/Language/Fortran/Analysis/ModGraph.hs b/src/Language/Fortran/Analysis/ModGraph.hs index a3ef9d60..930e1538 100644 --- a/src/Language/Fortran/Analysis/ModGraph.hs +++ b/src/Language/Fortran/Analysis/ModGraph.hs @@ -97,7 +97,7 @@ genModGraph mversion includeDirs cppOpts paths = do pf <- parserF path contents mapM_ (perModule path) (childrenBi pf :: [ProgramUnit ()]) pure () - execStateT (mapM_ iter (removeDuplicates paths)) modGraph0 + execStateT (mapM_ iter paths) modGraph0 -- Remove duplicates from a list preserving the left most occurrence. removeDuplicates :: Eq a => [a] -> [a] @@ -122,12 +122,14 @@ modGraphToDOT ModGraph { mgGraph = gr } = unlines dot -- Provides a topological sort of the graph, giving a list of filenames modGraphToList :: ModGraph -> [String] -modGraphToList mg - | nxt <- takeNextMods mg - , not (null nxt) = - let mg' = delModNodes (map fst nxt) mg - in [ fn | (_, Just (MOFile fn)) <- nxt ] ++ modGraphToList mg' -modGraphToList _ = [] +modGraphToList m = removeDuplicates $ modGraphToList' m + where + modGraphToList' mg + | nxt <- takeNextMods mg + , not (null nxt) = + let mg' = delModNodes (map fst nxt) mg + in [ fn | (_, Just (MOFile fn)) <- nxt ] ++ modGraphToList' mg' + modGraphToList' _ = [] takeNextMods :: ModGraph -> [(Node, Maybe ModOrigin)] From 31a3e0652a1251f251eed7a4b66e66a8b2fcc288 Mon Sep 17 00:00:00 2001 From: Dominic Orchard Date: Tue, 3 Sep 2024 13:22:53 +0100 Subject: [PATCH 12/28] some helpers for working with constant expression evaluator --- CHANGELOG.md | 4 ++++ fortran-src.cabal | 2 +- src/Language/Fortran/Repr/Value/Machine.hs | 14 ++++++++++++++ src/Language/Fortran/Repr/Value/Scalar/Machine.hs | 2 +- 4 files changed, 20 insertions(+), 2 deletions(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index 20e431db..8d1164b8 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -1,3 +1,7 @@ +### 0.16.0 (2024) + * Added `--show-make-list` option + * Some robustness improvements around mod files + ### 0.15.1 (Jun 22, 2023) * remove unused vector-sized dependency diff --git a/fortran-src.cabal b/fortran-src.cabal index 647e8d44..0dcfb6dc 100644 --- a/fortran-src.cabal +++ b/fortran-src.cabal @@ -1,6 +1,6 @@ cabal-version: 1.12 --- This file has been generated from package.yaml by hpack version 0.35.2. +-- This file has been generated from package.yaml by hpack version 0.36.0. -- -- see: https://github.com/sol/hpack diff --git a/src/Language/Fortran/Repr/Value/Machine.hs b/src/Language/Fortran/Repr/Value/Machine.hs index f885c4cb..ac1c13b8 100644 --- a/src/Language/Fortran/Repr/Value/Machine.hs +++ b/src/Language/Fortran/Repr/Value/Machine.hs @@ -2,6 +2,8 @@ module Language.Fortran.Repr.Value.Machine where +import Language.Fortran.Repr.Value.Scalar.Real +import Language.Fortran.Repr.Value.Scalar.Int.Machine import Language.Fortran.Repr.Value.Scalar.Machine import Language.Fortran.Repr.Type @@ -18,3 +20,15 @@ data FValue = MkFScalarValue FScalarValue fValueType :: FValue -> FType fValueType = \case MkFScalarValue a -> MkFScalarType $ fScalarValueType a + +fromConstInt :: FValue -> Maybe Integer +fromConstInt (MkFScalarValue (FSVInt a)) = Just $ withFInt a +fromConstInt _ = Nothing + +fromConstReal :: FValue -> Maybe Double +-- convert Float to Double +fromConstReal (MkFScalarValue (FSVReal (FReal4 a))) = Just $ floatToDouble a + where + floatToDouble :: Float -> Double + floatToDouble = realToFrac +fromConstReal (MkFScalarValue (FSVReal (FReal8 a))) = Just $ a diff --git a/src/Language/Fortran/Repr/Value/Scalar/Machine.hs b/src/Language/Fortran/Repr/Value/Scalar/Machine.hs index 2a0a0e4a..33f58cb5 100644 --- a/src/Language/Fortran/Repr/Value/Scalar/Machine.hs +++ b/src/Language/Fortran/Repr/Value/Scalar/Machine.hs @@ -55,4 +55,4 @@ fScalarValueType = \case FSVReal a -> FSTReal $ fKind a FSVComplex a -> FSTComplex $ fKind a FSVLogical a -> FSTLogical $ fKind a - FSVString a -> FSTString $ fromIntegral $ Text.length a + FSVString a -> FSTString $ fromIntegral $ Text.length a \ No newline at end of file From 2240b9d478abb2532a0fd8dbdbbaa95568754c71 Mon Sep 17 00:00:00 2001 From: Dominic Orchard Date: Tue, 3 Sep 2024 13:25:19 +0100 Subject: [PATCH 13/28] remoev comment --- src/Language/Fortran/Repr/Value/Machine.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Language/Fortran/Repr/Value/Machine.hs b/src/Language/Fortran/Repr/Value/Machine.hs index ac1c13b8..27bd188b 100644 --- a/src/Language/Fortran/Repr/Value/Machine.hs +++ b/src/Language/Fortran/Repr/Value/Machine.hs @@ -26,7 +26,6 @@ fromConstInt (MkFScalarValue (FSVInt a)) = Just $ withFInt a fromConstInt _ = Nothing fromConstReal :: FValue -> Maybe Double --- convert Float to Double fromConstReal (MkFScalarValue (FSVReal (FReal4 a))) = Just $ floatToDouble a where floatToDouble :: Float -> Double From a21e1463cdc8d208e282b8bb235b41ce7ef7184e Mon Sep 17 00:00:00 2001 From: Dominic Orchard Date: Tue, 3 Sep 2024 13:26:09 +0100 Subject: [PATCH 14/28] feature for tagging in module maps whether names are defined loal or via imports --- src/Language/Fortran/Analysis.hs | 26 ++++++++++++++++-- src/Language/Fortran/Analysis/Renaming.hs | 33 ++++++++++++++--------- src/Language/Fortran/Util/ModFile.hs | 12 ++++++--- 3 files changed, 53 insertions(+), 18 deletions(-) diff --git a/src/Language/Fortran/Analysis.hs b/src/Language/Fortran/Analysis.hs index c339dd7d..34f10a76 100644 --- a/src/Language/Fortran/Analysis.hs +++ b/src/Language/Fortran/Analysis.hs @@ -6,7 +6,8 @@ module Language.Fortran.Analysis ( initAnalysis, stripAnalysis, Analysis(..) , varName, srcName, lvVarName, lvSrcName, isNamedExpression , genVar, puName, puSrcName, blockRhsExprs, rhsExprs - , ModEnv, NameType(..), IDType(..), ConstructType(..) + , ModEnv, NameType(..), Locality(..), markAsImported, isImported + , IDType(..), ConstructType(..) , lhsExprs, isLExpr, allVars, analyseAllLhsVars, analyseAllLhsVars1, allLhsVars , blockVarUses, blockVarDefs , BB, BBNode, BBGr(..), bbgrMap, bbgrMapM, bbgrEmpty @@ -77,10 +78,31 @@ type TransFunc f g a = (f (Analysis a) -> f (Analysis a)) -> g (Analysis a) -> g type TransFuncM m f g a = (f (Analysis a) -> m (f (Analysis a))) -> g (Analysis a) -> m (g (Analysis a)) -- Describe a Fortran name as either a program unit or a variable. -data NameType = NTSubprogram | NTVariable | NTIntrinsic deriving (Show, Eq, Ord, Data, Typeable, Generic) +data Locality = + Local -- locally declared + | Imported -- declared in an imported module + deriving (Show, Eq, Ord, Data, Typeable, Generic) + +data NameType = NTSubprogram Locality | NTVariable Locality | NTIntrinsic + deriving (Show, Eq, Ord, Data, Typeable, Generic) + instance Binary NameType instance Out NameType +instance Binary Locality +instance Out Locality + +-- Mark any variables as being imported +markAsImported :: NameType -> NameType +markAsImported (NTVariable _) = NTVariable Imported +markAsImported (NTSubprogram _) = NTSubprogram Imported +markAsImported x = x + +isImported :: NameType -> Bool +isImported (NTVariable Imported) = True +isImported (NTSubprogram Imported) = True +isImported _ = False + -- Module environments are associations between source name and -- (unique name, name type) in a specific module. type ModEnv = M.Map String (String, NameType) diff --git a/src/Language/Fortran/Analysis/Renaming.hs b/src/Language/Fortran/Analysis/Renaming.hs index 69fecfc0..79468deb 100644 --- a/src/Language/Fortran/Analysis/Renaming.hs +++ b/src/Language/Fortran/Analysis/Renaming.hs @@ -120,7 +120,7 @@ programUnit (PUFunction a s ty rec name args res blocks m_contains) = do blocks3 <- mapM renameDeclDecls blocks2 -- handle declarations m_contains' <- renameSubPUs m_contains -- handle contained program units blocks4 <- mapM renameBlock blocks3 -- process all uses of variables - let env = M.singleton name (name', NTSubprogram) + let env = M.singleton name (name', NTSubprogram Local) let a' = a { moduleEnv = Just env } -- also annotate it on the program unit popScope let pu' = PUFunction a' s ty rec name args' res' blocks4 m_contains' @@ -133,7 +133,7 @@ programUnit (PUSubroutine a s rec name args blocks m_contains) = do blocks2 <- mapM renameDeclDecls blocks1 -- handle declarations m_contains' <- renameSubPUs m_contains -- handle contained program units blocks3 <- mapM renameBlock blocks2 -- process all uses of variables - let env = M.singleton name (name', NTSubprogram) + let env = M.singleton name (name', NTSubprogram Local) let a' = a { moduleEnv = Just env } -- also annotate it on the program unit popScope let pu' = PUSubroutine a' s rec name args' blocks3 m_contains' @@ -230,10 +230,16 @@ initialEnv blocks = do mMap <- gets moduleMap modEnv <- fmap M.unions . forM uses $ \ use -> case use of (BlStatement _ _ _ (StUse _ _ (ExpValue _ _ (ValVariable m)) _ _ Nothing)) -> - return $ fromMaybe empty (Named m `lookup` mMap) + let + env = fromMaybe empty (Named m `lookup` mMap) + -- mark as imported all the local things from this module + in return $ M.map (\ (v, info) -> (v, markAsImported info)) env + (BlStatement _ _ _ (StUse _ _ (ExpValue _ _ (ValVariable m)) _ _ (Just onlyAList))) | only <- aStrip onlyAList -> do let env = fromMaybe empty (Named m `lookup` mMap) + -- mark as imported all the local things from this module + env <- return $ M.map (\ (v, info) -> (v, markAsImported info)) env -- list of (local name, original name) from USE declaration: let localNamePairs = flip mapMaybe only $ \ r -> case r of UseID _ _ v@(ExpValue _ _ ValVariable{}) -> Just (varName v, varName v) @@ -253,7 +259,7 @@ initialEnv blocks = do -- Include any mappings defined by COMMON blocks: use variable -- source name prefixed by name of COMMON block. - let common = M.fromList [ (v, (v', NTVariable)) + let common = M.fromList [ (v, (v', NTVariable Local)) | CommonGroup _ _ me1 alist <- universeBi blocks :: [CommonGroup (Analysis a)] , let prefix = case me1 of Just e1 -> srcName e1; _ -> "" , e@(ExpValue _ _ ValVariable{}) <- universeBi (aStrip alist) :: [Expression (Analysis a)] @@ -325,9 +331,9 @@ getFromEnvsIfSubprogram :: String -> Renamer (Maybe String) getFromEnvsIfSubprogram v = do mEntry <- getFromEnvsWithType v case mEntry of - Just (v', NTSubprogram) -> return $ Just v' - Just (_, NTVariable) -> getFromEnv v - _ -> return Nothing + Just (v', NTSubprogram _) -> return $ Just v' + Just (_, NTVariable _) -> getFromEnv v + _ -> return Nothing -- Add a renaming mapping to the environment. addToEnv :: String -> String -> NameType -> Renamer () @@ -372,10 +378,10 @@ renameSubPUs (Just pus) = skimProgramUnits pus >> Just <$> mapM programUnit pus -- to the environment. skimProgramUnits :: Data a => [ProgramUnit (Analysis a)] -> Renamer () skimProgramUnits pus = forM_ pus $ \ pu -> case pu of - PUModule _ _ name _ _ -> addToEnv name name NTSubprogram - PUFunction _ _ _ _ name _ _ _ _ -> addUnique_ name NTSubprogram - PUSubroutine _ _ _ name _ _ _ -> addUnique_ name NTSubprogram - PUMain _ _ (Just name) _ _ -> addToEnv name name NTSubprogram + PUModule _ _ name _ _ -> addToEnv name name (NTSubprogram Local) + PUFunction _ _ _ _ name _ _ _ _ -> addUnique_ name (NTSubprogram Local) + PUSubroutine _ _ _ name _ _ _ -> addUnique_ name (NTSubprogram Local) + PUMain _ _ (Just name) _ _ -> addToEnv name name (NTSubprogram Local) _ -> return () ---------- @@ -394,7 +400,8 @@ renameGenericDecls = trans renameExpDecl -- declaration that possibly requires the creation of a new unique -- mapping. renameExpDecl :: Data a => RenamerFunc (Expression (Analysis a)) -renameExpDecl e@(ExpValue _ _ (ValVariable v)) = flip setUniqueName (setSourceName v e) `fmap` maybeAddUnique v NTVariable +renameExpDecl e@(ExpValue _ _ (ValVariable v)) = + flip setUniqueName (setSourceName v e) `fmap` maybeAddUnique v (NTVariable Local) -- Intrinsics get unique names for each use. renameExpDecl e@(ExpValue _ _ (ValIntrinsic v)) = flip setUniqueName (setSourceName v e) `fmap` addUnique v NTIntrinsic renameExpDecl e = return e @@ -407,7 +414,7 @@ renameInterfaces = trans interface interface :: Data a => RenamerFunc (Block (Analysis a)) interface (BlInterface a s (Just e@(ExpValue _ _ (ValVariable v))) abst pus bs) = do - e' <- flip setUniqueName (setSourceName v e) `fmap` maybeAddUnique v NTSubprogram + e' <- flip setUniqueName (setSourceName v e) `fmap` maybeAddUnique v (NTSubprogram Local) pure $ BlInterface a s (Just e') abst pus bs interface b = pure b diff --git a/src/Language/Fortran/Util/ModFile.hs b/src/Language/Fortran/Util/ModFile.hs index 5d353948..5b44cd62 100644 --- a/src/Language/Fortran/Util/ModFile.hs +++ b/src/Language/Fortran/Util/ModFile.hs @@ -55,7 +55,7 @@ module Language.Fortran.Util.ModFile , moduleFilename , StringMap, extractStringMap, combinedStringMap , DeclContext(..), DeclMap, extractDeclMap, combinedDeclMap - , extractModuleMap, combinedModuleMap, combinedTypeEnv + , extractModuleMap, combinedModuleMap, localisedModuleMap, combinedTypeEnv , ParamVarMap, extractParamVarMap, combinedParamVarMap , genUniqNameToFilenameMap , TimestampStatus(..), checkTimestamps @@ -217,6 +217,9 @@ decodeModFiles' = fmap (map snd) . decodeModFiles combinedModuleMap :: ModFiles -> FAR.ModuleMap combinedModuleMap = M.unions . map mfModuleMap +localisedModuleMap :: FAR.ModuleMap -> FAR.ModuleMap +localisedModuleMap = M.map (M.filter (not . FA.isImported . snd)) + -- | Extract the combined module map from a set of ModFiles. Useful -- for parsing a Fortran file in a large context of other modules. combinedTypeEnv :: ModFiles -> FAT.TypeEnv @@ -244,13 +247,16 @@ moduleFilename = mfFilename -------------------------------------------------- -- | Create a map that links all unique variable/function names in the --- ModFiles to their corresponding filename. +-- ModFiles to their corresponding *originating* filename (i.e., where they are declared) genUniqNameToFilenameMap :: ModFiles -> M.Map F.Name String genUniqNameToFilenameMap = M.unions . map perMF where - perMF mf = M.fromList [ (n, fname) | modEnv <- M.elems (mfModuleMap mf) + perMF mf = M.fromList [ (n, fname) | modEnv <- M.elems localModuleMap , (n, _) <- M.elems modEnv ] where + -- Make sure that we remove imported declarations so we can + -- properly localise declarations to the originator file. + localModuleMap = localisedModuleMap $ mfModuleMap mf fname = mfFilename mf -------------------------------------------------- From 04c497ab6ac09d0f87018476f5c2e66d24aa82ae Mon Sep 17 00:00:00 2001 From: Dominic Orchard Date: Tue, 3 Sep 2024 13:31:42 +0100 Subject: [PATCH 15/28] improve error reporting if syntax error with mod file --- app/Main.hs | 8 ++++++-- src/Language/Fortran/Analysis/ModGraph.hs | 1 - 2 files changed, 6 insertions(+), 3 deletions(-) diff --git a/app/Main.hs b/app/Main.hs index 7d6bad42..ed6abb2e 100644 --- a/app/Main.hs +++ b/app/Main.hs @@ -217,8 +217,12 @@ compileFileToMod mvers mods path moutfile = do mmap = combinedModuleMap mods tenv = combinedTypeEnv mods runCompile = genModFile . fst . analyseTypesWithEnv tenv . analyseRenamesWithModuleMap mmap . initAnalysis - parsedPF = fromRight' $ (Parser.byVerWithMods mods version) path contents - mod = runCompile parsedPF + parsedPF <- + case (Parser.byVerWithMods mods version) path contents of + Right pf -> return pf + Left err -> do + fail $ "Error parsing " ++ path ++ ": " ++ show err + let mod = runCompile parsedPF fspath = path -<.> modFileSuffix `fromMaybe` moutfile LB.writeFile fspath $ encodeModFile [mod] return mod diff --git a/src/Language/Fortran/Analysis/ModGraph.hs b/src/Language/Fortran/Analysis/ModGraph.hs index 930e1538..adb32ac8 100644 --- a/src/Language/Fortran/Analysis/ModGraph.hs +++ b/src/Language/Fortran/Analysis/ModGraph.hs @@ -16,7 +16,6 @@ import Data.Data import Data.Generics.Uniplate.Data import Data.Graph.Inductive hiding (version) import Data.Maybe -import Data.Either.Combinators ( fromRight' ) import qualified Data.Map as M -------------------------------------------------- From 100ee4ca7f60b6ca7e5c5b11638b4a401e8d7e67 Mon Sep 17 00:00:00 2001 From: Dominic Orchard Date: Tue, 3 Sep 2024 14:24:03 +0100 Subject: [PATCH 16/28] mod file spec test --- test/Language/Fortran/Analysis/ModFileSpec.hs | 46 +++++++++++++++++++ 1 file changed, 46 insertions(+) create mode 100644 test/Language/Fortran/Analysis/ModFileSpec.hs diff --git a/test/Language/Fortran/Analysis/ModFileSpec.hs b/test/Language/Fortran/Analysis/ModFileSpec.hs new file mode 100644 index 00000000..5c37eac5 --- /dev/null +++ b/test/Language/Fortran/Analysis/ModFileSpec.hs @@ -0,0 +1,46 @@ +module Language.Fortran.Analysis.ModFileSpec (spec) where + +import Test.Hspec +import TestUtil + +import Language.Fortran.Util.ModFile +import Language.Fortran.Util.Files (expandDirs, flexReadFile) +import Language.Fortran.Version +import System.FilePath (()) +import qualified Data.Map as M +import qualified Language.Fortran.Parser as Parser +import qualified Data.ByteString.Char8 as B +import Language.Fortran.AST +import Language.Fortran.Analysis +import Language.Fortran.Analysis.Renaming +import Language.Fortran.Analysis.BBlocks +import Language.Fortran.Analysis.DataFlow + +spec :: Spec +spec = + describe "Modfiles" $ + it "Test module maps for a small package" $ + testModuleMaps + +pParser :: String -> IO (ProgramFile (Analysis A0)) +pParser name = do + contents <- flexReadFile name + let pf = Parser.byVerWithMods [] Fortran90 name contents + case pf of + Right pf -> return $ rename . analyseBBlocks . analyseRenames . initAnalysis $ pf + Left err -> error $ "Error parsing " ++ name ++ ": " ++ show err + +-- A simple test that checks that we correctly localise the declaration +-- of the variable `constant` to the leaf module, whilst understanding +-- in the `mid1` and `mid2` modules that it is an imported declaration. +testModuleMaps = do + paths <- expandDirs ["test-data" "module"] + -- parse all files into mod files + pfs <- mapM (\p -> pParser p) paths + let modFiles = map genModFile pfs + -- get unique name to filemap + let mmap = genUniqNameToFilenameMap modFiles + -- check that `constant` is declared in leaf.f90 + let Just leaf = M.lookup "leaf_constant_1" mmap + leaf `shouldBe` "test-data/module/leaf.f90" + From 10a45ca22da354971841f8c0de25bc3ee9401c5e Mon Sep 17 00:00:00 2001 From: Dominic Orchard Date: Tue, 3 Sep 2024 14:38:45 +0100 Subject: [PATCH 17/28] add modfilespec to cabal --- fortran-src.cabal | 1 + 1 file changed, 1 insertion(+) diff --git a/fortran-src.cabal b/fortran-src.cabal index 0dcfb6dc..35946536 100644 --- a/fortran-src.cabal +++ b/fortran-src.cabal @@ -280,6 +280,7 @@ test-suite spec other-modules: Language.Fortran.Analysis.BBlocksSpec Language.Fortran.Analysis.DataFlowSpec + Language.Fortran.Analysis.ModFileSpec Language.Fortran.Analysis.ModGraphSpec Language.Fortran.Analysis.RenamingSpec Language.Fortran.Analysis.SemanticTypesSpec From 4d028b73e7fd932de7d6fa7ea0174626a39dfabf Mon Sep 17 00:00:00 2001 From: Dominic Orchard Date: Tue, 3 Sep 2024 14:46:32 +0100 Subject: [PATCH 18/28] more robust test --- test/Language/Fortran/Analysis/ModGraphSpec.hs | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/test/Language/Fortran/Analysis/ModGraphSpec.hs b/test/Language/Fortran/Analysis/ModGraphSpec.hs index dd2528db..bb6169ff 100644 --- a/test/Language/Fortran/Analysis/ModGraphSpec.hs +++ b/test/Language/Fortran/Analysis/ModGraphSpec.hs @@ -21,6 +21,10 @@ testDependencyList = do paths' <- expandDirs ["test-data" "module"] mg <- genModGraph (Just Fortran90) ["."] Nothing paths' let list = modGraphToList mg - let files = ["leaf.f90", "mid1.f90", "mid2.f90", "top.f90"] - let filesWithPaths = map (("test-data" "module") ) files - list `shouldBe` filesWithPaths + -- we should have two possible orderings + let files1 = ["leaf.f90", "mid1.f90", "mid2.f90", "top.f90"] + let filesWithPaths1 = map (("test-data" "module") ) files1 + -- or in a different order + let files2 = ["leaf.f90", "mid2.f90", "mid1.f90", "top.f90"] + let filesWithPaths2 = map (("test-data" "module") ) files2 + shouldSatisfy list (\x -> x == filesWithPaths1 || x == filesWithPaths2) From 001abaf57a9e0d593486fc504f2bc9e27cdf9ac6 Mon Sep 17 00:00:00 2001 From: Dominic Orchard Date: Tue, 3 Sep 2024 15:02:19 +0100 Subject: [PATCH 19/28] os agnostic test --- test/Language/Fortran/Analysis/ModFileSpec.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/test/Language/Fortran/Analysis/ModFileSpec.hs b/test/Language/Fortran/Analysis/ModFileSpec.hs index 5c37eac5..aef0ba52 100644 --- a/test/Language/Fortran/Analysis/ModFileSpec.hs +++ b/test/Language/Fortran/Analysis/ModFileSpec.hs @@ -42,5 +42,5 @@ testModuleMaps = do let mmap = genUniqNameToFilenameMap modFiles -- check that `constant` is declared in leaf.f90 let Just leaf = M.lookup "leaf_constant_1" mmap - leaf `shouldBe` "test-data/module/leaf.f90" + leaf `shouldBe` ("test-data" "module" "leaf.f90") From e1dc768a99c7ee7b308425f164d2ba24b01f663f Mon Sep 17 00:00:00 2001 From: Dominic Orchard Date: Wed, 4 Sep 2024 16:58:35 +0200 Subject: [PATCH 20/28] --version functionality --- app/Main.hs | 12 +++++++++++- 1 file changed, 11 insertions(+), 1 deletion(-) diff --git a/app/Main.hs b/app/Main.hs index ed6abb2e..6e39d369 100644 --- a/app/Main.hs +++ b/app/Main.hs @@ -50,11 +50,16 @@ import qualified Language.Fortran.Parser.Free.Lexer as Free programName :: String programName = "fortran-src" +showVersion :: String +showVersion = "0.16.0" + main :: IO () main = do args <- getArgs (opts, parsedArgs) <- compileArgs args case (parsedArgs, action opts) of + (paths, ShowMyVersion) -> do + putStrLn $ "fortran-src version: " ++ showVersion (paths, ShowMakeGraph) -> do paths' <- expandDirs paths mg <- genModGraph (fortranVersion opts) (includeDirs opts) (cppOptions opts) paths' @@ -305,6 +310,7 @@ printTypeErrors = putStrLn . showTypeErrors data Action = Lex | Parse | Typecheck | Rename | BBlocks | SuperGraph | Reprint | DumpModFile | Compile | ShowFlows Bool Bool Int | ShowBlocks (Maybe Int) | ShowMakeGraph | ShowMakeList | Make + | ShowMyVersion deriving Eq instance Read Action where @@ -333,7 +339,11 @@ initOptions = Options Nothing Parse Default Nothing [] Nothing False options :: [OptDescr (Options -> Options)] options = - [ Option ['v','F'] + [ Option [] + ["version"] + (NoArg $ \ opts -> opts { action = ShowMyVersion }) + "show fortran-src version" + , Option ['v','F'] ["fortranVersion"] (ReqArg (\v opts -> opts { fortranVersion = selectFortranVersion v }) "VERSION") "Fortran version to use, format: Fortran[66/77/77Legacy/77Extended/90]" From 8776f07327a73f2716211477bfaa857e3baa6be9 Mon Sep 17 00:00:00 2001 From: Dominic Orchard Date: Wed, 4 Sep 2024 16:58:41 +0200 Subject: [PATCH 21/28] package update --- CHANGELOG.md | 3 ++- fortran-src.cabal | 2 +- package.yaml | 2 +- 3 files changed, 4 insertions(+), 3 deletions(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index 8d1164b8..b7687408 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -1,6 +1,7 @@ ### 0.16.0 (2024) * Added `--show-make-list` option - * Some robustness improvements around mod files + * Some robustness improvements around mod files [#286](https://github.com/camfort/fortran-src/pull/286) + * Helpers to work with the partial evaluation representation [#285](https://github.com/camfort/fortran-src/pull/285) ### 0.15.1 (Jun 22, 2023) * remove unused vector-sized dependency diff --git a/fortran-src.cabal b/fortran-src.cabal index 35946536..e8127366 100644 --- a/fortran-src.cabal +++ b/fortran-src.cabal @@ -5,7 +5,7 @@ cabal-version: 1.12 -- see: https://github.com/sol/hpack name: fortran-src -version: 0.15.1 +version: 0.16.0 synopsis: Parsers and analyses for Fortran standards 66, 77, 90, 95 and 2003 (partial). description: Provides lexing, parsing, and basic analyses of Fortran code covering standards: FORTRAN 66, FORTRAN 77, Fortran 90, Fortran 95, Fortran 2003 (partial) and some legacy extensions. Includes data flow and basic block analysis, a renamer, and type analysis. For example usage, see the @@ project, which uses fortran-src as its front end. category: Language diff --git a/package.yaml b/package.yaml index 1cdac3f0..20d22e16 100644 --- a/package.yaml +++ b/package.yaml @@ -1,5 +1,5 @@ name: fortran-src -version: '0.15.1' +version: '0.16.0' synopsis: Parsers and analyses for Fortran standards 66, 77, 90, 95 and 2003 (partial). description: >- Provides lexing, parsing, and basic analyses of Fortran code covering From 1fde26a68528a8278c613ba40359a4894df990d4 Mon Sep 17 00:00:00 2001 From: Dominic Orchard Date: Wed, 4 Sep 2024 18:20:24 +0200 Subject: [PATCH 22/28] add missing fall through case --- src/Language/Fortran/Repr/Value/Machine.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Language/Fortran/Repr/Value/Machine.hs b/src/Language/Fortran/Repr/Value/Machine.hs index 27bd188b..0829ce44 100644 --- a/src/Language/Fortran/Repr/Value/Machine.hs +++ b/src/Language/Fortran/Repr/Value/Machine.hs @@ -31,3 +31,4 @@ fromConstReal (MkFScalarValue (FSVReal (FReal4 a))) = Just $ floatToDouble a floatToDouble :: Float -> Double floatToDouble = realToFrac fromConstReal (MkFScalarValue (FSVReal (FReal8 a))) = Just $ a +fromConstReal _ = Nothing \ No newline at end of file From 5bd841fa5b2ca26925092e4f79f7f897c9f5b7c7 Mon Sep 17 00:00:00 2001 From: Dominic Orchard Date: Wed, 4 Sep 2024 18:20:24 +0200 Subject: [PATCH 23/28] add missing fall through case --- src/Language/Fortran/Repr/Value/Machine.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Language/Fortran/Repr/Value/Machine.hs b/src/Language/Fortran/Repr/Value/Machine.hs index 27bd188b..0829ce44 100644 --- a/src/Language/Fortran/Repr/Value/Machine.hs +++ b/src/Language/Fortran/Repr/Value/Machine.hs @@ -31,3 +31,4 @@ fromConstReal (MkFScalarValue (FSVReal (FReal4 a))) = Just $ floatToDouble a floatToDouble :: Float -> Double floatToDouble = realToFrac fromConstReal (MkFScalarValue (FSVReal (FReal8 a))) = Just $ a +fromConstReal _ = Nothing \ No newline at end of file From 3322bd5e3b796d69fe8c526dab2463f7a99ecb2f Mon Sep 17 00:00:00 2001 From: Dominic Orchard Date: Tue, 3 Sep 2024 14:46:32 +0100 Subject: [PATCH 24/28] more robust test --- test/Language/Fortran/Analysis/ModGraphSpec.hs | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/test/Language/Fortran/Analysis/ModGraphSpec.hs b/test/Language/Fortran/Analysis/ModGraphSpec.hs index dd2528db..bb6169ff 100644 --- a/test/Language/Fortran/Analysis/ModGraphSpec.hs +++ b/test/Language/Fortran/Analysis/ModGraphSpec.hs @@ -21,6 +21,10 @@ testDependencyList = do paths' <- expandDirs ["test-data" "module"] mg <- genModGraph (Just Fortran90) ["."] Nothing paths' let list = modGraphToList mg - let files = ["leaf.f90", "mid1.f90", "mid2.f90", "top.f90"] - let filesWithPaths = map (("test-data" "module") ) files - list `shouldBe` filesWithPaths + -- we should have two possible orderings + let files1 = ["leaf.f90", "mid1.f90", "mid2.f90", "top.f90"] + let filesWithPaths1 = map (("test-data" "module") ) files1 + -- or in a different order + let files2 = ["leaf.f90", "mid2.f90", "mid1.f90", "top.f90"] + let filesWithPaths2 = map (("test-data" "module") ) files2 + shouldSatisfy list (\x -> x == filesWithPaths1 || x == filesWithPaths2) From a3e71c1989f13334ecaeb60f285c41cb40621ca2 Mon Sep 17 00:00:00 2001 From: Dominic Orchard Date: Wed, 4 Sep 2024 22:11:31 +0200 Subject: [PATCH 25/28] comment --- src/Language/Fortran/Util/ModFile.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Language/Fortran/Util/ModFile.hs b/src/Language/Fortran/Util/ModFile.hs index 5b44cd62..139a73f2 100644 --- a/src/Language/Fortran/Util/ModFile.hs +++ b/src/Language/Fortran/Util/ModFile.hs @@ -217,6 +217,8 @@ decodeModFiles' = fmap (map snd) . decodeModFiles combinedModuleMap :: ModFiles -> FAR.ModuleMap combinedModuleMap = M.unions . map mfModuleMap +-- | Inside the module map, remove all imported declarations so that +-- we can properly localise declarations to the originator file. localisedModuleMap :: FAR.ModuleMap -> FAR.ModuleMap localisedModuleMap = M.map (M.filter (not . FA.isImported . snd)) From 0405fad2b1f3cdee001f4b0e8a5cd8e0b5cdfefc Mon Sep 17 00:00:00 2001 From: Dominic Orchard Date: Wed, 4 Sep 2024 22:19:41 +0200 Subject: [PATCH 26/28] Update README.md --- README.md | 11 +++++++++-- 1 file changed, 9 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index 5cbd2e80..056492fb 100644 --- a/README.md +++ b/README.md @@ -39,6 +39,7 @@ for the many other options that can be explored for visualisation purposes. ``` Usage: fortran-src [OPTION...] + --version show fortran-src version -v VERSION, -F VERSION --fortranVersion=VERSION Fortran version to use, format: Fortran[66/77/77Legacy/77Extended/90] -a ACTION --action=ACTION choose the action, possible values: lex|parse -t --typecheck parse and run typechecker @@ -46,10 +47,16 @@ Usage: fortran-src [OPTION...] -B --bblocks analyse basic blocks -S --supergraph analyse super graph of basic blocks -r --reprint Parse and output using pretty printer + --split-long when using pretty printer, split long lines via continuations --dot output graphs in GraphViz DOT format --dump-mod-file dump the information contained within mod files + -C[CPP-OPTS] --cpp[=CPP-OPTS] run the C Pre Processor on the Fortran files first -I DIR --include-dir=DIR directory to search for precompiled 'mod files' - -c --compile compile an .fsmod file from the input + -c --summarise, --compile-mod build an .fsmod file from the input + -o FILE --output-file=FILE name of output file (e.g. name of generated fsmod file) + --make-mods, --make determine dependency order of modules and automatically build .fsmod files + --show-make-graph dump a graph showing the build structure of modules + --show-make-list dump a list of files in build dependency order (topological sort from the dependency graph) --show-block-numbers[=LINE-NUM] Show the corresponding AST-block identifier number next to every line of code. --show-flows-to=AST-BLOCK-ID dump a graph showing flows-to information from the given AST-block ID; prefix with 's' for supergraph --show-flows-from=AST-BLOCK-ID dump a graph showing flows-from information from the given AST-block ID; prefix with 's' for supergraph @@ -70,7 +77,7 @@ via the package `libgmp-dev`. Haskell library dependencies are listed in `package.yaml`. fortran-src supports building with Stack or Cabal. -fortran-src supports **GHC 9.0 through GHC 9.2**. We regularly test at least the +fortran-src supports **GHC 9.0 through GHC 9.4**. We regularly test at least the minimum and maximum supported GHCs. Releases prior to/newer than those may have issues. We welcome fixes that would let us support a wider range of compilers. From 97c556f99d22b8c6646137560658340ac5c056a7 Mon Sep 17 00:00:00 2001 From: Dominic Orchard Date: Wed, 4 Sep 2024 22:25:11 +0200 Subject: [PATCH 27/28] add date to release --- CHANGELOG.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index b7687408..d20c5f65 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -1,4 +1,4 @@ -### 0.16.0 (2024) +### 0.16.0 (Sept 4, 2024) * Added `--show-make-list` option * Some robustness improvements around mod files [#286](https://github.com/camfort/fortran-src/pull/286) * Helpers to work with the partial evaluation representation [#285](https://github.com/camfort/fortran-src/pull/285) From aac5b8752df420898e2cf64cc295bf2d0cf95232 Mon Sep 17 00:00:00 2001 From: Dominic Orchard Date: Wed, 4 Sep 2024 22:27:02 +0200 Subject: [PATCH 28/28] more detail in changelog --- CHANGELOG.md | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index d20c5f65..b2765050 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -1,5 +1,6 @@ ### 0.16.0 (Sept 4, 2024) - * Added `--show-make-list` option + * Added `--show-make-list` option to give a topological sort on the dependency graph for a source tree + * Added `--version` option * Some robustness improvements around mod files [#286](https://github.com/camfort/fortran-src/pull/286) * Helpers to work with the partial evaluation representation [#285](https://github.com/camfort/fortran-src/pull/285)