Skip to content

Commit d5d68b5

Browse files
committed
finish fixing various tests
1 parent 0d7f406 commit d5d68b5

File tree

25 files changed

+378
-179
lines changed

25 files changed

+378
-179
lines changed

fortran-src.cabal

Lines changed: 7 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -65,6 +65,7 @@ library
6565
Language.Fortran.Analysis
6666
Language.Fortran.Analysis.BBlocks
6767
Language.Fortran.Analysis.DataFlow
68+
Language.Fortran.Analysis.ModGraph
6869
Language.Fortran.Analysis.Renaming
6970
Language.Fortran.Analysis.SemanticTypes
7071
Language.Fortran.Analysis.Types
@@ -75,7 +76,6 @@ library
7576
Language.Fortran.Intrinsics
7677
Language.Fortran.LValue
7778
Language.Fortran.Parser
78-
Language.Fortran.Parser.Common
7979
Language.Fortran.Parser.Fixed.Fortran66
8080
Language.Fortran.Parser.Fixed.Fortran77
8181
Language.Fortran.Parser.Fixed.Lexer
@@ -86,6 +86,7 @@ library
8686
Language.Fortran.Parser.Free.Lexer
8787
Language.Fortran.Parser.Free.Utils
8888
Language.Fortran.Parser.LexerUtils
89+
Language.Fortran.Parser.Monad
8990
Language.Fortran.PrettyPrint
9091
Language.Fortran.Rewriter
9192
Language.Fortran.Rewriter.Internal
@@ -135,6 +136,7 @@ library
135136
, containers >=0.5 && <0.7
136137
, deepseq ==1.4.*
137138
, directory >=1.2 && <2
139+
, either
138140
, fgl ==5.*
139141
, filepath ==1.4.*
140142
, mtl >=2.2 && <3
@@ -179,6 +181,7 @@ executable fortran-src
179181
, containers >=0.5 && <0.7
180182
, deepseq ==1.4.*
181183
, directory >=1.2 && <2
184+
, either
182185
, fgl ==5.*
183186
, filepath ==1.4.*
184187
, fortran-src
@@ -201,7 +204,6 @@ test-suite spec
201204
Language.Fortran.AnalysisSpec
202205
Language.Fortran.AST.BozSpec
203206
Language.Fortran.AST.RealLitSpec
204-
Language.Fortran.Parser.CommonSpec
205207
Language.Fortran.Parser.Fixed.Fortran66Spec
206208
Language.Fortran.Parser.Fixed.Fortran77.IncludeSpec
207209
Language.Fortran.Parser.Fixed.Fortran77.ParserSpec
@@ -212,6 +214,7 @@ test-suite spec
212214
Language.Fortran.Parser.Free.Fortran90Spec
213215
Language.Fortran.Parser.Free.Fortran95Spec
214216
Language.Fortran.Parser.Free.LexerSpec
217+
Language.Fortran.Parser.MonadSpec
215218
Language.Fortran.PrettyPrintSpec
216219
Language.Fortran.Rewriter.InternalSpec
217220
Language.Fortran.RewriterSpec
@@ -255,6 +258,7 @@ test-suite spec
255258
, containers >=0.5 && <0.7
256259
, deepseq ==1.4.*
257260
, directory >=1.2 && <2
261+
, either
258262
, fgl ==5.*
259263
, filepath ==1.4.*
260264
, fortran-src
@@ -303,6 +307,7 @@ benchmark bench
303307
, criterion ==1.5.*
304308
, deepseq ==1.4.*
305309
, directory >=1.2 && <2
310+
, either
306311
, fgl ==5.*
307312
, filepath ==1.4.*
308313
, fortran-src

package.yaml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -63,6 +63,7 @@ dependencies:
6363
- deepseq >=1.4 && <1.5
6464
- filepath >=1.4 && <1.5
6565
- temporary >=1.2 && <1.4
66+
- either # TODO
6667

6768
# --pedantic for building (not used for stack ghci)
6869
ghc-options:
Lines changed: 147 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,147 @@
1+
{-# LANGUAGE ScopedTypeVariables #-}
2+
3+
-- | Generate a module use-graph.
4+
module Language.Fortran.Analysis.ModGraph
5+
(genModGraph, ModGraph(..), ModOrigin(..), modGraphToDOT, takeNextMods, delModNodes)
6+
where
7+
8+
import Language.Fortran.AST hiding (setName)
9+
import qualified Language.Fortran.Parser as Parser
10+
import Language.Fortran.Version
11+
import Language.Fortran.Util.ModFile
12+
import Language.Fortran.Util.Files
13+
14+
import Prelude hiding (mod)
15+
import Control.Monad
16+
import Control.Monad.State.Strict
17+
import Data.Data
18+
import Data.Generics.Uniplate.Data
19+
import Data.Graph.Inductive hiding (version)
20+
import Data.Maybe
21+
import Data.Either.Combinators ( fromRight' )
22+
import qualified Data.ByteString.Lazy.Char8 as LB
23+
import qualified Data.Map as M
24+
import System.IO
25+
import System.FilePath
26+
27+
--------------------------------------------------
28+
29+
data ModOrigin = MOFile FilePath | MOFSMod FilePath
30+
deriving (Eq, Data, Show)
31+
32+
instance Ord ModOrigin where
33+
MOFSMod _ <= MOFSMod _ = True
34+
a <= b = a == b
35+
36+
data ModGraph = ModGraph { mgModNodeMap :: M.Map String (Node, Maybe ModOrigin)
37+
, mgGraph :: Gr String ()
38+
, mgNumNodes :: Int }
39+
deriving (Eq, Data)
40+
41+
modGraph0 :: ModGraph
42+
modGraph0 = ModGraph M.empty empty 0
43+
44+
type ModGrapher a = StateT ModGraph IO a
45+
46+
maybeAddModName :: String -> Maybe ModOrigin -> ModGrapher Node
47+
maybeAddModName modName org = do
48+
mg@ModGraph { mgModNodeMap = mnmap, mgGraph = gr, mgNumNodes = numNodes } <- get
49+
case M.lookup modName mnmap of
50+
Just (i, org') | org <= org' -> pure i
51+
| otherwise -> do
52+
let mnmap' = M.insert modName (i, org) mnmap
53+
put $ mg { mgModNodeMap = mnmap' }
54+
pure i
55+
Nothing -> do
56+
let i = numNodes + 1
57+
let mnmap' = M.insert modName (i, org) mnmap
58+
let gr' = insNode (i, modName) gr
59+
put $ mg { mgModNodeMap = mnmap', mgGraph = gr', mgNumNodes = i }
60+
pure i
61+
62+
addModDep :: String -> String -> ModGrapher ()
63+
addModDep modName depName = do
64+
i <- maybeAddModName modName Nothing
65+
j <- maybeAddModName depName Nothing
66+
mg@ModGraph { mgGraph = gr } <- get
67+
put $ mg { mgGraph = insEdge (i, j, ()) gr }
68+
69+
genModGraph :: Maybe FortranVersion -> [FilePath] -> [FilePath] -> IO ModGraph
70+
genModGraph mversion includeDirs paths = do
71+
let perModule path pu@(PUModule _ _ modName _ _) = do
72+
_ <- maybeAddModName modName (Just $ MOFile path)
73+
let uses = [ usedName | StUse _ _ (ExpValue _ _ (ValVariable usedName)) _ _ _ <-
74+
universeBi pu :: [Statement ()] ]
75+
forM_ uses $ \ usedName -> do
76+
_ <- maybeAddModName usedName Nothing
77+
addModDep modName usedName
78+
perModule path pu | Named puName <- getName pu = do
79+
_ <- maybeAddModName puName (Just $ MOFile path)
80+
let uses = [ usedName | StUse _ _ (ExpValue _ _ (ValVariable usedName)) _ _ _ <-
81+
universeBi pu :: [Statement ()] ]
82+
forM_ uses $ \ usedName -> do
83+
_ <- maybeAddModName usedName Nothing
84+
addModDep puName usedName
85+
perModule _ _ = pure ()
86+
let iter :: FilePath -> ModGrapher ()
87+
iter path = do
88+
contents <- liftIO $ flexReadFile path
89+
fileMods <- liftIO $ decodeModFiles includeDirs
90+
let version = fromMaybe (deduceFortranVersion path) mversion
91+
mods = map snd fileMods
92+
parserF0 = Parser.byVerWithMods mods version
93+
parserF fn bs = fromRight' $ parserF0 fn bs
94+
forM_ fileMods $ \ (fileName, mod) -> do
95+
forM_ [ name | Named name <- M.keys (combinedModuleMap [mod]) ] $ \ name -> do
96+
_ <- maybeAddModName name . Just $ MOFSMod fileName
97+
pure ()
98+
let pf = parserF path contents
99+
mapM_ (perModule path) (childrenBi pf :: [ProgramUnit ()])
100+
pure ()
101+
execStateT (mapM_ iter paths) modGraph0
102+
103+
modGraphToDOT :: ModGraph -> String
104+
modGraphToDOT ModGraph { mgGraph = gr } = unlines dot
105+
where
106+
dot = [ "strict digraph {\n"
107+
, "node [shape=box,fontname=\"Courier New\"]\n" ] ++
108+
concatMap (\ (i, name) ->
109+
[ "n" ++ show i ++ "[label=\"" ++ name ++ "\"]\n"
110+
, "n" ++ show i ++ " -> {" ] ++
111+
[ " n" ++ show j | j <- suc gr i ] ++
112+
["}\n"])
113+
(labNodes gr) ++
114+
[ "}\n" ]
115+
116+
takeNextMods :: ModGraph -> [(Node, Maybe ModOrigin)]
117+
takeNextMods ModGraph { mgModNodeMap = mnmap, mgGraph = gr } = noDepFiles
118+
where
119+
noDeps = [ (i, modName) | (i, modName) <- labNodes gr, null (suc gr i) ]
120+
noDepFiles = [ (i, mo) | (i, modName) <- noDeps
121+
, (_, mo) <- maybeToList (M.lookup modName mnmap) ]
122+
123+
delModNodes :: [Node] -> ModGraph -> ModGraph
124+
delModNodes ns mg@ModGraph { mgGraph = gr } = mg'
125+
where
126+
mg' = mg { mgGraph = delNodes ns gr }
127+
128+
--------------------------------------------------
129+
130+
decodeModFiles :: [FilePath] -> IO [(FilePath, ModFile)]
131+
decodeModFiles = foldM (\ modFiles d -> do
132+
-- Figure out the camfort mod files and parse them.
133+
modFileNames <- filter isModFile `fmap` getDirContents d
134+
addedModFiles <- fmap concat . forM modFileNames $ \ modFileName -> do
135+
contents <- LB.readFile (d </> modFileName)
136+
case decodeModFile contents of
137+
Left msg -> do
138+
hPutStrLn stderr $ modFileName ++ ": Error: " ++ msg
139+
return [(modFileName, emptyModFile)]
140+
Right mods -> do
141+
hPutStrLn stderr $ modFileName ++ ": successfully parsed precompiled file."
142+
return $ map (modFileName,) mods
143+
return $ addedModFiles ++ modFiles
144+
) [] -- can't use emptyModFiles
145+
146+
isModFile :: FilePath -> Bool
147+
isModFile = (== modFileSuffix) . takeExtension

0 commit comments

Comments
 (0)