diff --git a/README.md b/README.md index 034f1deb..94dad5cd 100644 --- a/README.md +++ b/README.md @@ -143,6 +143,16 @@ We support the latest recommended version of Cabal (as of 2021-09-17, Cabal 3.4) cabal build ``` +You can leverage cabal to initialize a ghci session, and call the main function like such: + +```shell +cabal repl + +:load app/Main.hs + +:main --version +``` + ### Testing Unit tests are stored in `test`. Run with `stack test` or `cabal test`. diff --git a/app/Main.hs b/app/Main.hs index 117c85f3..514fbd1c 100644 --- a/app/Main.hs +++ b/app/Main.hs @@ -16,7 +16,7 @@ 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.List (sortBy, intercalate, isSuffixOf, union) import Data.Ord (comparing) import Data.Char (toLower) import Data.Maybe (listToMaybe, fromMaybe, maybeToList) @@ -57,6 +57,7 @@ main :: IO () main = do args <- getArgs (opts, parsedArgs) <- compileArgs args + let compilerOpts = fortranCompilerOptions opts case (parsedArgs, action opts) of (paths, ShowMyVersion) -> do putStrLn $ "fortran-src version: " ++ showVersion @@ -92,7 +93,7 @@ main = do decodeOneModFile modPath CompileFile -> do putStr $ "Summarising " ++ fnPath ++ "..." - mod <- compileFileToMod mvers mods fnPath Nothing + mod <- compileFileToMod mvers (fortranCompilerOptions opts) mods fnPath Nothing putStrLn "done" pure [mod] @@ -108,18 +109,20 @@ main = do (paths, Compile) -> do mods <- decodeModFiles' $ includeDirs opts - mapM_ (\ p -> compileFileToMod (fortranVersion opts) mods p (outputFile opts)) paths + let compilerOpts = fortranCompilerOptions opts + mapM_ (\ p -> compileFileToMod (fortranVersion opts) (fortranCompilerOptions opts) mods p (outputFile opts)) paths (path:_, actionOpt) -> do contents <- runCPP (cppOptions opts) path -- only runs CPP if cppOptions is not Nothing mods <- decodeModFiles' $ includeDirs opts - let version = fromMaybe (deduceFortranVersion path) (fortranVersion opts) - parsedPF = case (Parser.byVerWithMods mods version) path contents of - Left a -> error $ show a - Right a -> a - outfmt = outputFormat opts - mmap = combinedModuleMap mods - tenv = stripExtended $ combinedTypeEnv mods - pvm = combinedParamVarMap mods + let version = fromMaybe (deduceFortranVersion path) (fortranVersion opts) + qualifiedVersion = makeQualifiedVersion version $ fortranCompilerOptions opts + parsedPF = case (Parser.byVerWithMods mods qualifiedVersion) path contents of + Left a -> error $ show a + Right a -> a + outfmt = outputFormat opts + mmap = combinedModuleMap mods + tenv = stripExtended $ combinedTypeEnv mods + pvm = combinedParamVarMap mods let runTypes = analyseAndCheckTypesWithEnv tenv . analyseRenamesWithModuleMap mmap . initAnalysis let runRenamer = stripAnalysis . rename . analyseRenamesWithModuleMap mmap . initAnalysis @@ -137,9 +140,9 @@ main = do , insLabel (getAnnotation b) == Just astBlockId ] case actionOpt of Lex | version `elem` [ Fortran66, Fortran77, Fortran77Extended, Fortran77Legacy ] -> - print $ Parser.collectTokens Fixed.lexer' $ initParseStateFixed "" version contents + print $ Parser.collectTokens Fixed.lexer' $ initParseStateFixed "" qualifiedVersion contents Lex | version `elem` [Fortran90, Fortran2003, Fortran2008] -> - print $ Parser.collectTokens Free.lexer' $ initParseStateFree "" version contents + print $ Parser.collectTokens Free.lexer' $ initParseStateFree "" qualifiedVersion contents Lex -> ioError $ userError $ usageInfo programName options Parse -> pp parsedPF Typecheck -> let (pf, _, errs) = runTypes parsedPF in @@ -215,15 +218,16 @@ main = do _ -> fail $ usageInfo programName options -compileFileToMod :: Maybe FortranVersion -> ModFiles -> FilePath -> Maybe FilePath -> IO ModFile -compileFileToMod mvers mods path moutfile = do +compileFileToMod :: Maybe FortranVersion -> [CompilerOption] -> ModFiles -> FilePath -> Maybe FilePath -> IO ModFile +compileFileToMod mvers opts mods path moutfile = do contents <- flexReadFile path - let version = fromMaybe (deduceFortranVersion path) mvers - mmap = combinedModuleMap mods - tenv = stripExtended $ combinedTypeEnv mods - runCompile = genModFile . fst . analyseTypesWithEnv tenv . analyseRenamesWithModuleMap mmap . initAnalysis + let languageRevision = fromMaybe (deduceFortranVersion path) mvers + qualifiedVersion = makeQualifiedVersion languageRevision opts + mmap = combinedModuleMap mods + tenv = stripExtended $ combinedTypeEnv mods + runCompile = genModFile . fst . analyseTypesWithEnv tenv . analyseRenamesWithModuleMap mmap . initAnalysis parsedPF <- - case (Parser.byVerWithMods mods version) path contents of + case (Parser.byVerWithMods mods qualifiedVersion) path contents of Right pf -> return pf Left err -> do fail $ "Error parsing " ++ path ++ ": " ++ show err @@ -327,17 +331,18 @@ instance Read Action where data OutputFormat = Default | DOT deriving Eq data Options = Options - { fortranVersion :: Maybe FortranVersion - , action :: Action - , outputFormat :: OutputFormat - , outputFile :: Maybe FilePath - , includeDirs :: [String] - , cppOptions :: Maybe String -- ^ Nothing: no CPP; Just x: run CPP with options x. + { fortranVersion :: Maybe FortranVersion + , fortranCompilerOptions :: [CompilerOption] + , action :: Action + , outputFormat :: OutputFormat + , outputFile :: Maybe FilePath + , includeDirs :: [String] + , cppOptions :: Maybe String -- ^ Nothing: no CPP; Just x: run CPP with options x. , useContinuationReformatter :: Bool } initOptions :: Options -initOptions = Options Nothing Parse Default Nothing [] Nothing False +initOptions = Options Nothing [] Parse Default Nothing [] Nothing False options :: [OptDescr (Options -> Options)] options = @@ -434,6 +439,14 @@ options = 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" + , Option [] + ["deprecated-constructs"] + (OptArg (\a opts -> + case a of + Just "dec-structure" -> opts { fortranCompilerOptions = union [DecStructure] (fortranCompilerOptions opts) } + otherwise -> opts -- todo: warning? + ) "DEPRECATED-CONSTRUCTS") + "Support for deprecated constructs. (dec-structure)" ] compileArgs :: [ String ] -> IO (Options, [ String ]) diff --git a/fortran-src.cabal b/fortran-src.cabal index beafcf5e..e99e11c5 100644 --- a/fortran-src.cabal +++ b/fortran-src.cabal @@ -200,8 +200,8 @@ library , pretty >=1.1 && <2 , process >=1.2.0.0 , singletons ==3.0.* - , singletons-base >=3.0 && <3.4 - , singletons-th >=3.0 && <3.4 + , singletons-base >=3.0 && <3.6 + , singletons-th >=3.0 && <3.6 , temporary >=1.2 && <1.4 , text >=1.2 && <2.2 , uniplate >=1.6 && <2 @@ -264,8 +264,8 @@ executable fortran-src , pretty >=1.1 && <2 , process >=1.2.0.0 , singletons ==3.0.* - , singletons-base >=3.0 && <3.4 - , singletons-th >=3.0 && <3.4 + , singletons-base >=3.0 && <3.6 + , singletons-th >=3.0 && <3.6 , temporary >=1.2 && <1.4 , text >=1.2 && <2.2 , uniplate >=1.6 && <2 diff --git a/src/Language/Fortran/Analysis/ModGraph.hs b/src/Language/Fortran/Analysis/ModGraph.hs index fdbe02ae..83f9592b 100644 --- a/src/Language/Fortran/Analysis/ModGraph.hs +++ b/src/Language/Fortran/Analysis/ModGraph.hs @@ -82,8 +82,9 @@ genModGraph mversion includeDirs cppOpts paths = do contents <- liftIO $ runCPP cppOpts path fileMods <- liftIO $ decodeModFiles includeDirs let version = fromMaybe (deduceFortranVersion path) mversion + qualifiedVersion = makeQualifiedVersion version [] mods = map snd fileMods - parserF0 = Parser.byVerWithMods mods version + parserF0 = Parser.byVerWithMods mods qualifiedVersion parserF fn bs = case parserF0 fn bs of Right x -> return x diff --git a/src/Language/Fortran/Parser.hs b/src/Language/Fortran/Parser.hs index 5c2c0811..3bdba4c3 100644 --- a/src/Language/Fortran/Parser.hs +++ b/src/Language/Fortran/Parser.hs @@ -105,7 +105,10 @@ throwIOLeft = \case Right a -> pure a -------------------------------------------------------------------------------- -byVer :: FortranVersion -> Parser (ProgramFile A0) +failUnknownVersion :: String -> FortranVersion -> a +failUnknownVersion who v = error $ who <> ": no parser available for requested version: " <> show v + +byVer :: FortranVersion -> [CompilerOption] -> Parser (ProgramFile A0) byVer = \case Fortran66 -> f66 Fortran77 -> f77 @@ -114,63 +117,69 @@ byVer = \case Fortran90 -> f90 Fortran95 -> f95 Fortran2003 -> f2003 - v -> error $ "Language.Fortran.Parser.byVer: " - <> "no parser available for requested version: " - <> show v - -byVerWithMods :: ModFiles -> FortranVersion -> Parser (ProgramFile A0) -byVerWithMods mods = \case - Fortran66 -> f66Mods mods - Fortran77 -> f77Mods mods - Fortran77Extended -> f77eMods mods - Fortran77Legacy -> f77lMods mods - Fortran90 -> f90Mods mods - Fortran95 -> f95Mods mods - Fortran2003 -> f2003Mods mods - v -> error $ "Language.Fortran.Parser.byVerWithMods: no parser available for requested version: " <> show v - -f66, f77, f77e, f77l, f90, f95, f2003 :: Parser (ProgramFile A0) -f66 = f66Mods [] -f77 = f77Mods [] -f77e = f77eMods [] -f77l = f77lMods [] -f90 = f90Mods [] -f95 = f95Mods [] -f2003 = f2003Mods [] + v -> failUnknownVersion "Language.Fortran.Parser.byVer" v + +modsByVersion :: String -> ModFiles -> FortranVersion -> [CompilerOption] -> Parser (ProgramFile A0) +modsByVersion who mods fv opts = + case fv of + Fortran66 -> f66Mods opts mods + Fortran77 -> f77Mods opts mods + Fortran77Extended -> f77eMods opts mods + Fortran77Legacy -> f77lMods opts mods + Fortran90 -> f90Mods opts mods + Fortran95 -> f95Mods opts mods + Fortran2003 -> f2003Mods opts mods + v -> failUnknownVersion who v + + +byVerWithMods :: ModFiles -> QualifiedFortranVersion -> Parser (ProgramFile A0) +byVerWithMods mods (VanillaVersion version) = modsByVersion "Language.Fortran.Parser.byVerWithMods" mods version [] +byVerWithMods mods (QualifiedVersion version options) = modsByVersion "Language.Fortran.Parser.byVerWithMods" mods version options + + + +f66, f77, f77e, f77l, f90, f95, f2003 :: [CompilerOption] -> Parser (ProgramFile A0) +f66 = flip f66Mods [] +f77 = flip f77Mods [] +f77e = flip f77eMods [] +f77l = flip f77lMods [] +f90 = flip f90Mods [] +f95 = flip f95Mods [] +f2003 = flip f2003Mods [] f66Mods, f77Mods, f77eMods, f77lMods, f90Mods, f95Mods, f2003Mods - :: ModFiles -> Parser (ProgramFile A0) -f66Mods = transformAs Fortran66 f66NoTransform -f77Mods = transformAs Fortran77 f77NoTransform -f77eMods = transformAs Fortran77Extended f77eNoTransform -f77lMods = transformAs Fortran77Legacy f77lNoTransform -f90Mods = transformAs Fortran90 f90NoTransform -f95Mods = transformAs Fortran95 f95NoTransform -f2003Mods = transformAs Fortran2003 f2003NoTransform + :: [CompilerOption] -> ModFiles -> Parser (ProgramFile A0) +f66Mods = transformAs Fortran66 . f66NoTransform +f77Mods = transformAs Fortran77 . f77NoTransform +f77eMods = transformAs Fortran77Extended . f77eNoTransform +f77lMods = transformAs Fortran77Legacy . f77lNoTransform +f90Mods = transformAs Fortran90 . f90NoTransform +f95Mods = transformAs Fortran95 . f95NoTransform +f2003Mods = transformAs Fortran2003 . f2003NoTransform f66NoTransform, f77NoTransform, f77eNoTransform, f77lNoTransform, f90NoTransform, f95NoTransform, f2003NoTransform - :: Parser (ProgramFile A0) -f66NoTransform = makeParserFixed F66.programParser Fortran66 -f77NoTransform = makeParserFixed F77.programParser Fortran77 -f77eNoTransform = makeParserFixed F77.programParser Fortran77Extended -f77lNoTransform = makeParserFixed F77.programParser Fortran77Legacy -f90NoTransform = makeParserFree F90.programParser Fortran90 -f95NoTransform = makeParserFree F95.programParser Fortran95 -f2003NoTransform = makeParserFree F2003.programParser Fortran2003 + :: [CompilerOption] -> Parser (ProgramFile A0) +f66NoTransform = makeParserFixed F66.programParser . makeQualifiedVersion Fortran66 +f77NoTransform = makeParserFixed F77.programParser . makeQualifiedVersion Fortran77 +f77eNoTransform = makeParserFixed F77.programParser . makeQualifiedVersion Fortran77Extended +f77lNoTransform = makeParserFixed F77.programParser . makeQualifiedVersion Fortran77Legacy +f90NoTransform = makeParserFree F90.programParser . makeQualifiedVersion Fortran90 +f95NoTransform = makeParserFree F95.programParser . makeQualifiedVersion Fortran95 +f2003NoTransform = makeParserFree F2003.programParser . makeQualifiedVersion Fortran2003 f66StmtNoTransform, f77StmtNoTransform, f77eStmtNoTransform, f77lStmtNoTransform, f90StmtNoTransform, f95StmtNoTransform, f2003StmtNoTransform - :: Parser (Statement A0) -f66StmtNoTransform = makeParserFixed F66.statementParser Fortran66 -f77StmtNoTransform = makeParserFixed F77.statementParser Fortran77 -f77eStmtNoTransform = makeParserFixed F77.statementParser Fortran77Extended -f77lStmtNoTransform = makeParserFixed F77.statementParser Fortran77Legacy -f90StmtNoTransform = makeParserFree F90.statementParser Fortran90 -f95StmtNoTransform = makeParserFree F95.statementParser Fortran95 -f2003StmtNoTransform = makeParserFree F2003.statementParser Fortran2003 - -byVerStmt :: FortranVersion -> Parser (Statement A0) + :: [CompilerOption] -> Parser (Statement A0) +f66StmtNoTransform = makeParserFixed F66.statementParser . makeQualifiedVersion Fortran66 +f77StmtNoTransform = makeParserFixed F77.statementParser . makeQualifiedVersion Fortran77 +f77eStmtNoTransform = makeParserFixed F77.statementParser . makeQualifiedVersion Fortran77Extended +f77lStmtNoTransform = makeParserFixed F77.statementParser . makeQualifiedVersion Fortran77Legacy +f90StmtNoTransform = makeParserFree F90.statementParser . makeQualifiedVersion Fortran90 +f95StmtNoTransform = makeParserFree F95.statementParser . makeQualifiedVersion Fortran95 +f2003StmtNoTransform = makeParserFree F2003.statementParser . makeQualifiedVersion Fortran2003 + +byVerStmt :: FortranVersion -> [CompilerOption] -> Parser (Statement A0) byVerStmt = \case Fortran66 -> f66StmtNoTransform Fortran77 -> f77StmtNoTransform @@ -179,10 +188,9 @@ byVerStmt = \case Fortran90 -> f90StmtNoTransform Fortran95 -> f95StmtNoTransform Fortran2003 -> f2003StmtNoTransform - v -> error $ "Language.Fortran.Parser.byVerStmt: " - <> "no parser available for requested version: " - <> show v -byVerNoTransform :: FortranVersion -> Parser (ProgramFile A0) + v -> failUnknownVersion "Language.Fortran.Parser.byVerStmt" v + +byVerNoTransform :: FortranVersion -> [CompilerOption] -> Parser (ProgramFile A0) byVerNoTransform = \case Fortran66 -> f66NoTransform Fortran77 -> f77NoTransform @@ -191,16 +199,14 @@ byVerNoTransform = \case Fortran90 -> f90NoTransform Fortran95 -> f90NoTransform Fortran2003 -> f2003NoTransform - v -> error $ "Language.Fortran.Parser.byVerNoTransform: " - <> "no parser available for requested version: " - <> show v + v -> failUnknownVersion "Language.Fortran.Parser.byVerNoTransform" v f90Expr :: Parser (Expression A0) -f90Expr = makeParser initParseStateFreeExpr F90.expressionParser Fortran90 +f90Expr = makeParser initParseStateFreeExpr F90.expressionParser (makeQualifiedVersion Fortran90 []) -- | Obtain a Fortran parser by assuming the version from the filename provided. -byVerFromFilename :: Parser (ProgramFile A0) -byVerFromFilename fn = byVer v fn +byVerFromFilename :: [CompilerOption] -> Parser (ProgramFile A0) +byVerFromFilename opts fn = byVer v opts fn where v = deduceFortranVersion fn -------------------------------------------------------------------------------- @@ -237,13 +243,13 @@ defaultTransformation = \case -------------------------------------------------------------------------------- -type StateInit s = String -> FortranVersion -> B.ByteString -> ParseState s -type ParserMaker ai tok a = Parse ai tok a -> FortranVersion -> Parser a +type StateInit s = String -> QualifiedFortranVersion -> B.ByteString -> ParseState s +type ParserMaker ai tok a = Parse ai tok a -> QualifiedFortranVersion -> Parser a makeParser :: (Loc ai, LastToken ai tok, Show tok) => StateInit ai -> ParserMaker ai tok a -makeParser fInitState p fv fn = fromParseResult . runParse p . fInitState fn fv +makeParser fInitState p qfv fn = fromParseResult . runParse p . fInitState fn qfv makeParserFixed :: ParserMaker Fixed.AlexInput Fixed.Token a makeParserFixed = makeParser initParseStateFixed @@ -252,12 +258,12 @@ makeParserFree :: ParserMaker Free.AlexInput Free.Token a makeParserFree = makeParser initParseStateFree initParseStateFixed :: StateInit Fixed.AlexInput -initParseStateFixed fn fv bs = initParseState fn fv ai - where ai = Fixed.vanillaAlexInput fn fv bs +initParseStateFixed fn qfv bs = initParseState fn qfv ai + where ai = Fixed.vanillaAlexInput qfv fn bs initParseStateFree :: StateInit Free.AlexInput -initParseStateFree fn fv bs = initParseState fn fv ai - where ai = Free.vanillaAlexInput fn bs +initParseStateFree fn qfv bs = initParseState fn qfv ai + where ai = Free.vanillaAlexInput qfv fn bs -- | Initialize free-form parser state with the lexer configured for standalone -- expression parsing. @@ -265,22 +271,22 @@ initParseStateFree fn fv bs = initParseState fn fv ai -- The free-form lexer needs a non-default start code for lexing standaloe -- expressions. initParseStateFreeExpr :: StateInit Free.AlexInput -initParseStateFreeExpr fn fv bs = st +initParseStateFreeExpr fn qfv bs = st { psAlexInput = ai { Free.aiStartCode = Free.StartCode Free.scN Free.Return } } where - ai = Free.vanillaAlexInput fn bs - st = initParseStateFree fn fv bs + ai = Free.vanillaAlexInput qfv fn bs + st = initParseStateFree fn qfv bs -- checked in generated file: 1=assn, 4=iif, 6=st -- 6, 1, 4 seem best in order. Looks like 6 is correct. -- TODO guesswork, relies on internal behaviour :/ initParseStateFixedExpr :: StateInit Fixed.AlexInput -initParseStateFixedExpr fn fv bs = st +initParseStateFixedExpr fn qfv bs = st { psAlexInput = ai { Fixed.aiStartCode = 6 , Fixed.aiWhiteSensitiveCharCount = 0 } } where - ai = Fixed.vanillaAlexInput fn fv bs - st = initParseStateFixed fn fv bs + ai = Fixed.vanillaAlexInput qfv fn bs + st = initParseStateFixed fn qfv bs -- | Convenience wrapper to easily use a parser unsafely. -- @@ -293,10 +299,10 @@ parseUnsafe p bs = Right a -> a -- | Helper for preparing initial parser state for the different lexers. -initParseState :: FilePath -> FortranVersion -> ai -> ParseState ai -initParseState fn fv ai = ParseState +initParseState :: FilePath -> QualifiedFortranVersion -> ai -> ParseState ai +initParseState fn qfv ai = ParseState { psAlexInput = ai - , psVersion = fv + , psVersion = qfv , psFilename = fn , psParanthesesCount = ParanthesesCount 0 False , psContext = [ ConStart ] } @@ -313,32 +319,35 @@ Can be cleaned up and generalized to use for other parsers. f66InlineIncludes, f77InlineIncludes, f77eInlineIncludes, f77lInlineIncludes, f90InlineIncludes, f95InlineIncludes, f2003InlineIncludes :: [FilePath] -> ModFiles -> String -> B.ByteString -> IO (ProgramFile A0) -f66InlineIncludes = byVerInlineIncludes Fortran66 -f77lInlineIncludes = byVerInlineIncludes Fortran77Legacy -f77eInlineIncludes = byVerInlineIncludes Fortran77Extended -f77InlineIncludes = byVerInlineIncludes Fortran77 -f90InlineIncludes = byVerInlineIncludes Fortran90 -f95InlineIncludes = byVerInlineIncludes Fortran95 -f2003InlineIncludes = byVerInlineIncludes Fortran2003 +f66InlineIncludes = byVerInlineIncludes (makeQualifiedVersion Fortran66 []) +f77lInlineIncludes = byVerInlineIncludes (makeQualifiedVersion Fortran77Legacy []) +f77eInlineIncludes = byVerInlineIncludes (makeQualifiedVersion Fortran77Extended []) +f77InlineIncludes = byVerInlineIncludes (makeQualifiedVersion Fortran77 []) +f90InlineIncludes = byVerInlineIncludes (makeQualifiedVersion Fortran90 []) +f95InlineIncludes = byVerInlineIncludes (makeQualifiedVersion Fortran95 []) +f2003InlineIncludes = byVerInlineIncludes (makeQualifiedVersion Fortran2003 []) byVerInlineIncludes - :: FortranVersion -> [FilePath] -> ModFiles -> String -> B.ByteString + :: QualifiedFortranVersion -> [FilePath] -> ModFiles -> String -> B.ByteString -> IO (ProgramFile A0) byVerInlineIncludes version incs mods fn bs = do - case byVerNoTransform version fn bs of + case byVerNoTransform languageRevisison compilerOptions fn bs of Left e -> liftIO $ throwIO e Right pf -> do let pf' = pfSetFilename fn pf pf'' <- evalStateT (descendBiM (parserInlineIncludes version incs []) pf') Map.empty let pf''' = runTransform (combinedTypeEnv mods) (combinedModuleMap mods) - (defaultTransformation version) + (defaultTransformation languageRevisison) pf'' return pf''' + where + languageRevisison = getLanguageRevision version + compilerOptions = getCompilerOptions version -- Internal function to go through the includes and inline them parserInlineIncludes - :: FortranVersion -> [FilePath] -> [FilePath] -> Statement A0 + :: QualifiedFortranVersion -> [FilePath] -> [FilePath] -> Statement A0 -> StateT (Map String [Block A0]) IO (Statement A0) parserInlineIncludes version dirs = go where @@ -363,26 +372,25 @@ f66IncludesNoTransform, f77IncludesNoTransform, f77eIncludesNoTransform, f77lIncludesNoTransform, f90IncludesNoTransform, f95IncludesNoTransform, f2003IncludesNoTransform :: Parser [Block A0] -f66IncludesNoTransform = makeParserFixed F66.includesParser Fortran66 -f77IncludesNoTransform = makeParserFixed F77.includesParser Fortran77 -f77eIncludesNoTransform = makeParserFixed F77.includesParser Fortran77Extended -f77lIncludesNoTransform = makeParserFixed F77.includesParser Fortran77Legacy -f90IncludesNoTransform = makeParserFree F90.includesParser Fortran90 -f95IncludesNoTransform = makeParserFree F95.includesParser Fortran95 -f2003IncludesNoTransform = makeParserFree F2003.includesParser Fortran2003 - -byVerInclude :: FortranVersion -> Parser [Block A0] -byVerInclude = \case - Fortran66 -> f66IncludesNoTransform - Fortran77 -> f77IncludesNoTransform - Fortran77Extended -> f77eIncludesNoTransform - Fortran77Legacy -> f77lIncludesNoTransform - Fortran90 -> f90IncludesNoTransform - Fortran95 -> f95IncludesNoTransform - Fortran2003 -> f2003IncludesNoTransform - v -> error $ "Language.Fortran.Parser.byVerInclude: " - <> "no parser available for requested version: " - <> show v +f66IncludesNoTransform = makeParserFixed F66.includesParser (makeQualifiedVersion Fortran66 []) +f77IncludesNoTransform = makeParserFixed F77.includesParser (makeQualifiedVersion Fortran77 []) +f77eIncludesNoTransform = makeParserFixed F77.includesParser (makeQualifiedVersion Fortran77Extended []) +f77lIncludesNoTransform = makeParserFixed F77.includesParser (makeQualifiedVersion Fortran77Legacy []) +f90IncludesNoTransform = makeParserFree F90.includesParser (makeQualifiedVersion Fortran90 []) +f95IncludesNoTransform = makeParserFree F95.includesParser (makeQualifiedVersion Fortran95 []) +f2003IncludesNoTransform = makeParserFree F2003.includesParser (makeQualifiedVersion Fortran2003 []) + +byVerInclude :: QualifiedFortranVersion -> Parser [Block A0] +byVerInclude qfv = + case getLanguageRevision qfv of + Fortran66 -> f66IncludesNoTransform + Fortran77 -> f77IncludesNoTransform + Fortran77Extended -> f77eIncludesNoTransform + Fortran77Legacy -> f77lIncludesNoTransform + Fortran90 -> f90IncludesNoTransform + Fortran95 -> f95IncludesNoTransform + Fortran2003 -> f2003IncludesNoTransform + v -> failUnknownVersion "Language.Fortran.Parser.byVerInclude" v readInDirs :: [String] -> String -> IO (String, B.ByteString) readInDirs [] f = fail $ "cannot find file: " ++ f diff --git a/src/Language/Fortran/Parser/Fixed/Lexer.x b/src/Language/Fortran/Parser/Fixed/Lexer.x index d39e7014..38fa8054 100644 --- a/src/Language/Fortran/Parser/Fixed/Lexer.x +++ b/src/Language/Fortran/Parser/Fixed/Lexer.x @@ -30,7 +30,7 @@ import Language.Fortran.Parser.Monad import Language.Fortran.Version import Language.Fortran.Util.FirstParameter import Language.Fortran.Util.Position -import Language.Fortran.Parser.LexerUtils ( readIntOrBoz ) +import Language.Fortran.Parser.LexerUtils ( readIntOrBoz, unescapeSpecialChars ) import Language.Fortran.AST.Literal.Boz } @@ -269,13 +269,13 @@ tokens :- -- Predicated lexer helpers -------------------------------------------------------------------------------- -(&&&) :: (FortranVersion -> AlexInput -> Int -> AlexInput -> Bool) - -> (FortranVersion -> AlexInput -> Int -> AlexInput -> Bool) - -> (FortranVersion -> AlexInput -> Int -> AlexInput -> Bool) -f &&& g = \ fv ai1 i ai2 -> f fv ai1 i ai2 && g fv ai1 i ai2 +(&&&) :: (QualifiedFortranVersion -> AlexInput -> Int -> AlexInput -> Bool) + -> (QualifiedFortranVersion -> AlexInput -> Int -> AlexInput -> Bool) + -> (QualifiedFortranVersion -> AlexInput -> Int -> AlexInput -> Bool) +f &&& g = \ qfv ai1 i ai2 -> f qfv ai1 i ai2 && g qfv ai1 i ai2 -formatExtendedP :: FortranVersion -> AlexInput -> Int -> AlexInput -> Bool -formatExtendedP fv _ _ ai = fv `elem` [Fortran77Extended, Fortran77Legacy] && +formatExtendedP :: QualifiedFortranVersion -> AlexInput -> Int -> AlexInput -> Bool +formatExtendedP qfv _ _ ai = getLanguageRevision qfv `elem` [Fortran77Extended, Fortran77Legacy] && case xs of [ TFormat _, _ ] -> False [ TLabel _ _, TFormat _ ] -> False @@ -283,37 +283,37 @@ formatExtendedP fv _ _ ai = fv `elem` [Fortran77Extended, Fortran77Legacy] && where xs = take 2 . reverse . aiPreviousTokensInLine $ ai -implicitType77P :: FortranVersion -> AlexInput -> Int -> AlexInput -> Bool -implicitType77P fv b c d = fortran77P fv b c d && implicitStP fv b c d +implicitType77P :: QualifiedFortranVersion -> AlexInput -> Int -> AlexInput -> Bool +implicitType77P qfv b c d = fortran77P qfv b c d && implicitStP qfv b c d -implicitTypeExtendedP :: FortranVersion -> AlexInput -> Int -> AlexInput -> Bool -implicitTypeExtendedP fv b c d = extended77P fv b c d && implicitStP fv b c d +implicitTypeExtendedP :: QualifiedFortranVersion -> AlexInput -> Int -> AlexInput -> Bool +implicitTypeExtendedP qfv b c d = extended77P qfv b c d && implicitStP qfv b c d -implicitStP :: FortranVersion -> AlexInput -> Int -> AlexInput -> Bool +implicitStP :: QualifiedFortranVersion -> AlexInput -> Int -> AlexInput -> Bool implicitStP _ _ _ ai = checkPreviousTokensInLine f ai where f (TImplicit _) = True f _ = False -extendedIdP :: FortranVersion -> AlexInput -> Int -> AlexInput -> Bool -extendedIdP fv a b ai = fv `elem` [Fortran77Extended, Fortran77Legacy] && idP fv a b ai +extendedIdP :: QualifiedFortranVersion -> AlexInput -> Int -> AlexInput -> Bool +extendedIdP qfv a b ai = getLanguageRevision qfv `elem` [Fortran77Extended, Fortran77Legacy] && idP qfv a b ai -legacyIdP :: FortranVersion -> AlexInput -> Int -> AlexInput -> Bool -legacyIdP fv a b ai = fv == Fortran77Legacy && idP fv a b ai +legacyIdP :: QualifiedFortranVersion -> AlexInput -> Int -> AlexInput -> Bool +legacyIdP qfv a b ai = getLanguageRevision qfv == Fortran77Legacy && idP qfv a b ai -idP :: FortranVersion -> AlexInput -> Int -> AlexInput -> Bool -idP fv ao i ai = not (doP fv ai) && not (ifP fv ao i ai) - && (equalFollowsP fv ai || rParFollowsP fv ai) +idP :: QualifiedFortranVersion -> AlexInput -> Int -> AlexInput -> Bool +idP qfv ao i ai = not (doP qfv ai) && not (ifP qfv ao i ai) + && (equalFollowsP qfv ai || rParFollowsP qfv ai) -doP :: FortranVersion -> AlexInput -> Bool -doP fv ai = isPrefixOf "do" (reverse . lexemeMatch . aiLexeme $ ai) && +doP :: QualifiedFortranVersion -> AlexInput -> Bool +doP qfv ai = isPrefixOf "do" (reverse . lexemeMatch . aiLexeme $ ai) && case unParse (lexer $ f (0::Integer)) ps of ParseOk True _ -> True _ -> False where ps = ParseState { psAlexInput = ai { aiStartCode = st} - , psVersion = fv + , psVersion = qfv , psFilename = "" , psParanthesesCount = ParanthesesCount 0 False , psContext = [ ConStart ] } @@ -330,15 +330,15 @@ doP fv ai = isPrefixOf "do" (reverse . lexemeMatch . aiLexeme $ ai) && TRightPar{} -> lexer $ f (n-1) _ -> lexer $ f n -ifP :: FortranVersion -> AlexInput -> Int -> AlexInput -> Bool -ifP fv _ _ ai = "if" == (reverse . lexemeMatch . aiLexeme $ ai) && +ifP :: QualifiedFortranVersion -> AlexInput -> Int -> AlexInput -> Bool +ifP qfv _ _ ai = "if" == (reverse . lexemeMatch . aiLexeme $ ai) && case unParse (lexer $ f) ps of ParseOk True _ -> True _ -> False where ps = ParseState { psAlexInput = ai { aiStartCode = st} - , psVersion = fv + , psVersion = qfv , psFilename = "" , psParanthesesCount = ParanthesesCount 0 False , psContext = [ ConStart ] } @@ -348,15 +348,15 @@ ifP fv _ _ ai = "if" == (reverse . lexemeMatch . aiLexeme $ ai) && TLeftPar{} -> return True _ -> return False -functionP :: FortranVersion -> AlexInput -> Int -> AlexInput -> Bool -functionP fv _ _ ai = "function" == (reverse . lexemeMatch . aiLexeme $ ai) && +functionP :: QualifiedFortranVersion -> AlexInput -> Int -> AlexInput -> Bool +functionP qfv _ _ ai = "function" == (reverse . lexemeMatch . aiLexeme $ ai) && case unParse (lexer $ f) ps of ParseOk True _ -> True _ -> False where ps = ParseState { psAlexInput = ai { aiStartCode = st} - , psVersion = fv + , psVersion = qfv , psFilename = "" , psParanthesesCount = ParanthesesCount 0 False , psContext = [ ConStart ] } @@ -367,21 +367,21 @@ functionP fv _ _ ai = "function" == (reverse . lexemeMatch . aiLexeme $ ai) && TLeftPar{} -> return True _ -> return False -hollerithP :: FortranVersion -> AlexInput -> Int -> AlexInput -> Bool +hollerithP :: QualifiedFortranVersion -> AlexInput -> Int -> AlexInput -> Bool hollerithP _ _ _ ai = isDigit (lookBack 2 ai) -notToP :: FortranVersion -> AlexInput -> Int -> AlexInput -> Bool +notToP :: QualifiedFortranVersion -> AlexInput -> Int -> AlexInput -> Bool notToP _ _ _ ai = not $ "to" `isPrefixOf` (reverse . lexemeMatch . aiLexeme $ ai) -equalFollowsP :: FortranVersion -> AlexInput -> Bool -equalFollowsP fv ai = +equalFollowsP :: QualifiedFortranVersion -> AlexInput -> Bool +equalFollowsP qfv ai = case unParse (lexer $ f False (0::Integer)) ps of ParseOk True _ -> True _ -> False where ps = ParseState { psAlexInput = ai { aiStartCode = st} - , psVersion = fv + , psVersion = qfv , psFilename = "" , psParanthesesCount = ParanthesesCount 0 False , psContext = [ ConStart ] } @@ -410,15 +410,15 @@ equalFollowsP fv ai = TRightPar{} -> lexer $ f True (n - 1) _ -> lexer $ f True n -rParFollowsP :: FortranVersion -> AlexInput -> Bool -rParFollowsP fv ai = +rParFollowsP :: QualifiedFortranVersion -> AlexInput -> Bool +rParFollowsP qfv ai = case unParse (lexer $ f) ps of ParseOk True _ -> True _ -> False where ps = ParseState { psAlexInput = ai { aiStartCode = st} - , psVersion = fv + , psVersion = qfv , psFilename = "" , psParanthesesCount = ParanthesesCount 0 False , psContext = [ ConStart ] } @@ -427,17 +427,17 @@ rParFollowsP fv ai = TRightPar{} -> return True _ -> return False -commentP :: FortranVersion -> AlexInput -> Int -> AlexInput -> Bool +commentP :: QualifiedFortranVersion -> AlexInput -> Int -> AlexInput -> Bool commentP _ aiOld _ aiNew = atColP 1 aiOld && _endsWithLine where _endsWithLine = (posColumn . aiPosition) aiNew /= 1 -bangCommentP :: FortranVersion -> AlexInput -> Int -> AlexInput -> Bool +bangCommentP :: QualifiedFortranVersion -> AlexInput -> Int -> AlexInput -> Bool bangCommentP _ _ _ aiNew = _endsWithLine where _endsWithLine = (posColumn . aiPosition) aiNew /= 1 -withinLabelColsP :: FortranVersion -> AlexInput -> Int -> AlexInput -> Bool +withinLabelColsP :: QualifiedFortranVersion -> AlexInput -> Int -> AlexInput -> Bool withinLabelColsP _ aiOld _ aiNew = getCol aiOld >= 1 && getCol aiNew <= 6 where getCol = posColumn . aiPosition @@ -449,7 +449,7 @@ atColP n ai = (posColumn . aiPosition) ai == n -- by looking at previous token. Since exponent can only follow a "." or an -- integer token. Anything other previous token will prevent matching the input -- as an exponent token. -exponentP :: FortranVersion -> AlexInput -> Int -> AlexInput -> Bool +exponentP :: QualifiedFortranVersion -> AlexInput -> Int -> AlexInput -> Bool exponentP _ _ _ ai = case aiPreviousTokensInLine ai of -- real*8 d8 is not an exponent @@ -458,18 +458,26 @@ exponentP _ _ _ ai = TDot{} : _ -> True _ -> False -fortran66P :: FortranVersion -> AlexInput -> Int -> AlexInput -> Bool -fortran66P fv _ _ _ = fv == Fortran66 +fortran66P :: QualifiedFortranVersion -> AlexInput -> Int -> AlexInput -> Bool +fortran66P qfv _ _ _ = getLanguageRevision qfv == Fortran66 -fortran77P :: FortranVersion -> AlexInput -> Int -> AlexInput -> Bool -fortran77P fv _ _ _ = fv == Fortran77 || fv == Fortran77Extended || fv == Fortran77Legacy +fortran77P :: QualifiedFortranVersion -> AlexInput -> Int -> AlexInput -> Bool +fortran77P qfv _ _ _ = + case getLanguageRevision qfv of + Fortran77 -> True + Fortran77Extended -> True + Fortran77Legacy -> True + otherwise -> False -extended77P :: FortranVersion -> AlexInput -> Int -> AlexInput -> Bool -extended77P fv _ _ _ = fv == Fortran77Extended || fv == Fortran77Legacy - -legacy77P :: FortranVersion -> AlexInput -> Int -> AlexInput -> Bool -legacy77P fv _ _ _ = fv == Fortran77Legacy +extended77P :: QualifiedFortranVersion -> AlexInput -> Int -> AlexInput -> Bool +extended77P qfv _ _ _ = + case getLanguageRevision qfv of + Fortran77Extended -> True + Fortran77Legacy -> True + otherwise -> False +legacy77P :: QualifiedFortranVersion -> AlexInput -> Int -> AlexInput -> Bool +legacy77P qfv _ _ _ = getLanguageRevision qfv == Fortran77Legacy -------------------------------------------------------------------------------- -- Lexer helpers @@ -886,7 +894,7 @@ data AlexInput = AlexInput , aiCaseSensitive :: Bool , aiInComment :: Bool , aiInFormat :: Bool - , aiFortranVersion :: FortranVersion + , aiFortranVersion :: QualifiedFortranVersion } deriving (Show) instance Loc AlexInput where @@ -897,8 +905,8 @@ instance LastToken AlexInput Token where type LexAction a = Parse AlexInput Token a -vanillaAlexInput :: String -> FortranVersion -> B.ByteString -> AlexInput -vanillaAlexInput fn fv bs = AlexInput +vanillaAlexInput :: QualifiedFortranVersion -> String -> B.ByteString -> AlexInput +vanillaAlexInput qfv fn bs = AlexInput { aiSourceBytes = bs , aiEndOffset = B.length bs , aiPosition = initPosition { posFilePath = fn } @@ -912,7 +920,7 @@ vanillaAlexInput fn fv bs = AlexInput , aiCaseSensitive = False , aiInComment = False , aiInFormat = False - , aiFortranVersion = fv + , aiFortranVersion = qfv } updateLexeme :: Maybe Char -> Position -> AlexInput -> AlexInput @@ -944,16 +952,16 @@ alexGetByte ai -- Skip the continuation line altogether | isContinuation ai && _isWhiteInsensitive = skip Continuation ai -- Skip comment lines "between" continuations - | aiFortranVersion ai >= Fortran77 && _isWhiteInsensitive + | (getLanguageRevision $ aiFortranVersion ai) >= Fortran77 && _isWhiteInsensitive && isNewlineCommentsFollowedByContinuation ai = skip NewlineComment ai -- If we are not parsing a Hollerith skip whitespace | _curChar `elem` [ ' ', '\t' ] && _isWhiteInsensitive = skip Char ai -- Ignore inline comments - | aiFortranVersion ai == Fortran77Legacy && _isWhiteInsensitive + | (getLanguageRevision $ aiFortranVersion ai) == Fortran77Legacy && _isWhiteInsensitive && not _inFormat && _curChar == '!' && not _blankLine = skip Comment ai -- Ignore comments after column 72 in fortran77 - | aiFortranVersion ai == Fortran77Legacy && not (aiInComment ai) + | (getLanguageRevision $ aiFortranVersion ai) == Fortran77Legacy && not (aiInComment ai) && posColumn _position > 72 && _curChar /= '\n' = skip Comment ai -- Read genuine character and advance. Also covers white sensitivity. @@ -1128,7 +1136,7 @@ lexer' = do AlexEOF -> return $ TEOF $ SrcSpan (getPos alexInput) (getPos alexInput) AlexError _ -> do parseState <- get - fail $ psFilename parseState ++ " - lexing failed: " ++ show (psAlexInput parseState) + fail $ psFilename parseState ++ " - lexing failed: " ++ (unescapeSpecialChars $ show (psAlexInput parseState)) AlexSkip newAlex _ -> putAlex newAlex >> lexer' AlexToken newAlex _ action -> do putAlex newAlex @@ -1140,6 +1148,6 @@ lexer' = do return token Nothing -> lexer' -alexScanUser :: FortranVersion -> AlexInput -> Int -> AlexReturn (LexAction (Maybe Token)) +alexScanUser :: QualifiedFortranVersion -> AlexInput -> Int -> AlexReturn (LexAction (Maybe Token)) } diff --git a/src/Language/Fortran/Parser/Free/Fortran90.y b/src/Language/Fortran/Parser/Free/Fortran90.y index 3a52e94a..2530207c 100644 --- a/src/Language/Fortran/Parser/Free/Fortran90.y +++ b/src/Language/Fortran/Parser/Free/Fortran90.y @@ -19,6 +19,7 @@ import Language.Fortran.Parser.Free.Utils import Language.Fortran.AST import Prelude hiding ( EQ, LT, GT ) -- Same constructors exist in the AST +import Data.Maybe ( isNothing, fromJust ) import Data.Either ( partitionEithers ) import qualified Data.List as List @@ -83,6 +84,9 @@ import qualified Data.List as List recursive { TRecursive _ } subroutine { TSubroutine _ } endSubroutine { TEndSubroutine _ } + structure { TStructure _ } + endStructure { TEndStructure _ } + record { TRecord _ } blockData { TBlockData _ } endBlockData { TEndBlockData _ } module { TModule _ } @@ -529,6 +533,27 @@ NONEXECUTABLE_STATEMENT :: { Statement A0 } | format blob { let TBlob s blob = $2 in StFormatBogus () (getTransSpan $1 s) blob } +| DECLARATION_STATEMENT { $1 } + +| structure MAYBE_NAME NEWLINE STRUCTURE_DECLARATIONS endStructure + { StStructure () (getTransSpan $1 $5) $2 (fromReverseList $4) } + +MAYBE_NAME :: { Maybe Name } +: '/' NAME '/' { Just $2 } +| {- empty -} { Nothing } + +STRUCTURE_DECLARATIONS :: { [StructureItem A0] } +: STRUCTURE_DECLARATIONS STRUCTURE_DECLARATION_STATEMENT + { if isNothing $2 then $1 else fromJust $2 : $1 } +| STRUCTURE_DECLARATION_STATEMENT { if isNothing $1 then [] else [fromJust $1] } + +STRUCTURE_DECLARATION_STATEMENT :: { Maybe (StructureItem A0) } +: DECLARATION_STATEMENT MAYBE_COMMENT NEWLINE + { let StDeclaration () s t attrs decls = $1 + in Just $ StructFields () s t attrs decls } +| structure MAYBE_NAME NAME MAYBE_COMMENT NEWLINE STRUCTURE_DECLARATIONS endStructure MAYBE_COMMENT NEWLINE + { Just $ StructStructure () (getTransSpan $1 $9) $2 $3 (fromReverseList $6) } + EXECUTABLE_STATEMENT :: { Statement A0 } : allocate '(' DATA_REFS MAYBE_ALLOC_OPT_LIST ')' { StAllocate () (getTransSpan $1 $5) Nothing (fromReverseList $3) $4 } @@ -960,6 +985,7 @@ TYPE_SPEC :: { TypeSpec A0 } | complex KIND_SELECTOR { TypeSpec () (getSpan ($1, $2)) TypeComplex $2 } | character CHAR_SELECTOR { TypeSpec () (getSpan ($1, $2)) TypeCharacter $2 } | logical KIND_SELECTOR { TypeSpec () (getSpan ($1, $2)) TypeLogical $2 } +| record '/' NAME '/' { TypeSpec () (getSpan ($1, $2)) (TypeCustom $3) Nothing } | type '(' id ')' { let TId _ id = $3 in TypeSpec () (getTransSpan $1 $4) (TypeCustom id) Nothing } diff --git a/src/Language/Fortran/Parser/Free/Lexer.x b/src/Language/Fortran/Parser/Free/Lexer.x index a8f263ed..e8a90613 100644 --- a/src/Language/Fortran/Parser/Free/Lexer.x +++ b/src/Language/Fortran/Parser/Free/Lexer.x @@ -107,6 +107,7 @@ tokens :- "=" { addSpan TOpAssign} "=>" { addSpan TArrow } "%" { addSpan TPercent } + "." / { legacyDECStructureP } { addSpan TPercent } <0,scI> @name / { partOfExpOrPointerAssignmentP } { addSpanAndMatch TId } <0> @name / { constructNameP } { addSpanAndMatch TId } @@ -147,6 +148,11 @@ tokens :- <0> "entry" { addSpan TEntry } <0> "include" { addSpan TInclude } +-- deprecated / non-standard declarations +<0> "structure" / { legacyDECStructureP } { addSpan TStructure } +<0> "end"\ *"structure" / { legacyDECStructureP } { addSpan TEndStructure } +<0> "record". / { legacyDECStructureP } { addSpan TRecord } + -- Type def related <0,scT> "type" { addSpan TType } "type" / { allocateP } { addSpan TType } @@ -338,6 +344,10 @@ tokens :- -- Predicated lexer helpers -------------------------------------------------------------------------------- +legacyDECStructureP :: User -> AlexInput -> Int -> AlexInput -> Bool +legacyDECStructureP (User qfv _) _ _ _ = hasDecStructure qfv + + formatP :: User -> AlexInput -> Int -> AlexInput -> Bool formatP _ _ _ ai | Just TFormat{} <- aiPreviousToken ai = True @@ -397,17 +407,18 @@ opP _ _ _ ai | otherwise = False partOfExpOrPointerAssignmentP :: User -> AlexInput -> Int -> AlexInput -> Bool -partOfExpOrPointerAssignmentP (User fv pc) _ _ ai = +partOfExpOrPointerAssignmentP u@(User qfv pc) pre pos ai = case unParse (lexer $ f False (0::Integer)) ps of ParseOk True _ -> True _ -> False where ps = ParseState { psAlexInput = ai { aiStartCode = StartCode scN Return } - , psVersion = fv + , psVersion = qfv , psFilename = "" , psParanthesesCount = pc , psContext = [ ConStart ] } + legacyDECStructureSupported = legacyDECStructureP u pre pos ai f leftParSeen parCount token | not leftParSeen = case token of @@ -415,6 +426,7 @@ partOfExpOrPointerAssignmentP (User fv pc) _ _ ai = TSemiColon{} -> return False TEOF{} -> return False TPercent{} -> return True + TDot{} -> return legacyDECStructureSupported TArrow{} -> return True TOpAssign{} -> return True TLeftPar{} -> lexer $ f True 1 @@ -425,6 +437,7 @@ partOfExpOrPointerAssignmentP (User fv pc) _ _ ai = TOpAssign{} -> return True TArrow{} -> return True TPercent{} -> return True + TDot{} -> return legacyDECStructureSupported TLeftPar{} -> lexer $ f True 1 TLeftPar2{} -> lexer $ f True 1 _ -> return False @@ -612,7 +625,7 @@ prevTokenConstr :: AlexInput -> Maybe Constr prevTokenConstr ai = toConstr <$> aiPreviousToken ai nextTokenConstr :: User -> AlexInput -> Maybe Constr -nextTokenConstr (User fv pc) ai = +nextTokenConstr (User qfv pc) ai = case unParse lexer' parseState of ParseOk token _ -> Just $ toConstr token _ -> Nothing @@ -620,7 +633,7 @@ nextTokenConstr (User fv pc) ai = parseState = ParseState { psAlexInput = ai , psParanthesesCount = pc - , psVersion = fv + , psVersion = qfv , psFilename = "" , psContext = [ ConStart ] } @@ -880,6 +893,7 @@ data AlexInput = AlexInput , aiStartCode :: {-# UNPACK #-} !StartCode , aiPreviousToken :: !(Maybe Token) , aiPreviousTokensInLine :: !([ Token ]) + , aiFortranVersion :: !QualifiedFortranVersion } deriving (Show) instance Loc AlexInput where @@ -890,8 +904,8 @@ instance LastToken AlexInput Token where type LexAction a = Parse AlexInput Token a -vanillaAlexInput :: String -> B.ByteString -> AlexInput -vanillaAlexInput fn bs = AlexInput +vanillaAlexInput :: QualifiedFortranVersion -> String -> B.ByteString -> AlexInput +vanillaAlexInput qfv fn bs = AlexInput { aiSourceBytes = bs , aiPosition = initPosition { posFilePath = fn } , aiEndOffset = B.length bs @@ -899,7 +913,9 @@ vanillaAlexInput fn bs = AlexInput , aiLexeme = initLexeme , aiStartCode = StartCode 0 Return , aiPreviousToken = Nothing - , aiPreviousTokensInLine = [ ] } + , aiPreviousTokensInLine = [ ] + , aiFortranVersion = qfv + } updateLexeme :: Char -> Position -> AlexInput -> AlexInput updateLexeme !char !p !ai = ai { aiLexeme = Lexeme (char:match) start' p isCmt' } @@ -909,7 +925,7 @@ updateLexeme !char !p !ai = ai { aiLexeme = Lexeme (char:match) start' p isCmt' isCmt' = isCmt || (null match && char == '!') -- Fortran version and parantheses count to be used by alexScanUser -data User = User FortranVersion ParanthesesCount +data User = User QualifiedFortranVersion ParanthesesCount -------------------------------------------------------------------------------- -- Definitions needed for alexScanUser @@ -1194,6 +1210,7 @@ data Token = | TDoubleColon SrcSpan | TOpAssign SrcSpan | TArrow SrcSpan + | TDot SrcSpan | TPercent SrcSpan | TLeftPar SrcSpan | TLeftPar2 SrcSpan @@ -1225,6 +1242,9 @@ data Token = -- Program unit related | TProgram SrcSpan | TEndProgram SrcSpan + | TStructure SrcSpan + | TEndStructure SrcSpan + | TRecord SrcSpan | TFunction SrcSpan | TEndFunction SrcSpan | TResult SrcSpan diff --git a/src/Language/Fortran/Parser/LexerUtils.hs b/src/Language/Fortran/Parser/LexerUtils.hs index 9469ba13..374c0c1f 100644 --- a/src/Language/Fortran/Parser/LexerUtils.hs +++ b/src/Language/Fortran/Parser/LexerUtils.hs @@ -1,5 +1,5 @@ {-| Utils for both lexers. -} -module Language.Fortran.Parser.LexerUtils ( readIntOrBoz ) where +module Language.Fortran.Parser.LexerUtils ( readIntOrBoz, unescapeSpecialChars) where import Language.Fortran.AST.Literal.Boz import Numeric @@ -16,3 +16,17 @@ readIntOrBoz s = do readSToMaybe :: [(a, b)] -> Maybe a readSToMaybe = \case (x, _):_ -> Just x _ -> Nothing + + +-- | Pretty prints exception message that contains things like carriage return, indents, etc. +unescapeSpecialChars :: String -> String +unescapeSpecialChars [] = [] +unescapeSpecialChars ('\\' : c : rest) = + case c of + 'n' -> '\n' : unescapeSpecialChars rest + 't' -> '\t' : unescapeSpecialChars rest + 'r' -> '\r' : unescapeSpecialChars rest + '\\' -> '\\' : unescapeSpecialChars rest + _ -> '\\' : c : unescapeSpecialChars rest +unescapeSpecialChars (c : rest) = + c : unescapeSpecialChars rest diff --git a/src/Language/Fortran/Parser/Monad.hs b/src/Language/Fortran/Parser/Monad.hs index 0fbfc7b7..6c74cb78 100644 --- a/src/Language/Fortran/Parser/Monad.hs +++ b/src/Language/Fortran/Parser/Monad.hs @@ -39,11 +39,11 @@ data Context = deriving (Show, Eq) data ParseState a = ParseState - { psAlexInput :: a + { psAlexInput :: a , psParanthesesCount :: ParanthesesCount - , psVersion :: FortranVersion -- To differentiate lexing behaviour - , psFilename :: String -- To save correct source location in AST - , psContext :: [ Context ] + , psVersion :: QualifiedFortranVersion -- To differentiate lexing behaviour + , psFilename :: String -- To save correct source location in AST + , psContext :: [ Context ] } deriving (Show) @@ -160,7 +160,7 @@ execParse m s = snd (runParseUnsafe m s) -- Parser helper functions ------------------------------------------------------------------------------- -getVersion :: (Loc a, LastToken a b, Show b) => Parse a b FortranVersion +getVersion :: (Loc a, LastToken a b, Show b) => Parse a b QualifiedFortranVersion getVersion = do s <- get return (psVersion s) diff --git a/src/Language/Fortran/Version.hs b/src/Language/Fortran/Version.hs index ea656014..be2a6c92 100644 --- a/src/Language/Fortran/Version.hs +++ b/src/Language/Fortran/Version.hs @@ -2,9 +2,16 @@ module Language.Fortran.Version ( FortranVersion(..) + , QualifiedFortranVersion(..) + , CompilerOption(..) , fortranVersionAliases , selectFortranVersion , deduceFortranVersion + , hasDecStructure + , getLanguageRevision + , addCompilerOption + , makeQualifiedVersion + , getCompilerOptions ) where import Data.Char (toLower) @@ -29,6 +36,41 @@ data FortranVersion = Fortran66 | Fortran2008 deriving (Ord, Eq, Data, Typeable, Generic) +data CompilerOption = DecStructure -- | represents -fdec-structure (gfortran, DEC extensions), also supported in intel fortran + deriving (Show, Ord, Eq, Data, Typeable, Generic) + +data QualifiedFortranVersion = VanillaVersion FortranVersion + | QualifiedVersion FortranVersion [CompilerOption] + deriving (Show, Ord, Eq, Data, Typeable, Generic) + +-- Extract the base Fortran version +getLanguageRevision :: QualifiedFortranVersion -> FortranVersion +getLanguageRevision (VanillaVersion v) = v +getLanguageRevision (QualifiedVersion v _) = v + +getCompilerOptions :: QualifiedFortranVersion -> [CompilerOption] +getCompilerOptions (VanillaVersion _) = [] +getCompilerOptions (QualifiedVersion _ opts) = opts +-- Check if a specific compiler option is enabled +hasCompilerOption :: CompilerOption -> QualifiedFortranVersion -> Bool +hasCompilerOption _ (VanillaVersion _) = False +hasCompilerOption opt (QualifiedVersion _ opts) = opt `elem` opts + +-- Add a compiler option to a QualifiedFortranVersion +addCompilerOption :: CompilerOption -> QualifiedFortranVersion -> QualifiedFortranVersion +addCompilerOption opt (VanillaVersion v) = QualifiedVersion v [opt] +addCompilerOption opt (QualifiedVersion v opts) + | opt `elem` opts = QualifiedVersion v opts -- Avoid duplicates? + | otherwise = QualifiedVersion v (opt : opts) + +-- | Check for Fortran77Legacy language revision or DecStructure compiler option +hasDecStructure :: QualifiedFortranVersion -> Bool +hasDecStructure qfv = getLanguageRevision qfv == Fortran77Legacy || hasCompilerOption DecStructure qfv + +makeQualifiedVersion :: FortranVersion -> [CompilerOption] -> QualifiedFortranVersion +makeQualifiedVersion version [] = VanillaVersion version +makeQualifiedVersion version opts = QualifiedVersion version opts + instance Show FortranVersion where show Fortran66 = "Fortran 66" show Fortran77 = "Fortran 77" diff --git a/test/Language/Fortran/Analysis/BBlocksSpec.hs b/test/Language/Fortran/Analysis/BBlocksSpec.hs index 68056ae5..eb6f39ed 100644 --- a/test/Language/Fortran/Analysis/BBlocksSpec.hs +++ b/test/Language/Fortran/Analysis/BBlocksSpec.hs @@ -15,7 +15,7 @@ import qualified Data.ByteString.Char8 as B pParser :: String -> ProgramFile (Analysis ()) pParser source = - case Parser.f77e "" (B.pack source) of + case Parser.f77e [] "" (B.pack source) of Left err -> error $ show err Right pf -> rename . analyseBBlocks . analyseRenames . initAnalysis $ pf diff --git a/test/Language/Fortran/Analysis/DataFlowSpec.hs b/test/Language/Fortran/Analysis/DataFlowSpec.hs index 36618c1f..5bed2f57 100644 --- a/test/Language/Fortran/Analysis/DataFlowSpec.hs +++ b/test/Language/Fortran/Analysis/DataFlowSpec.hs @@ -28,9 +28,9 @@ data F90 = F90 class Parser t where parser :: t -> String -> ProgramFile A0 instance Parser F77 where - parser F77 = Parser.parseUnsafe Parser.f77e . B.pack + parser F77 = Parser.parseUnsafe (Parser.f77e []) . B.pack instance Parser F90 where - parser F90 = Parser.parseUnsafe Parser.f90 . B.pack + parser F90 = Parser.parseUnsafe (Parser.f90 []) . B.pack pParser :: Parser t => t -> String -> ProgramFile (Analysis ()) pParser version source = rename . analyseBBlocks . analyseRenames . initAnalysis diff --git a/test/Language/Fortran/Analysis/ModFileSpec.hs b/test/Language/Fortran/Analysis/ModFileSpec.hs index 9ea4a245..d0b800a2 100644 --- a/test/Language/Fortran/Analysis/ModFileSpec.hs +++ b/test/Language/Fortran/Analysis/ModFileSpec.hs @@ -25,7 +25,7 @@ spec = pParser :: String -> IO (ProgramFile (Analysis A0)) pParser name = do contents <- flexReadFile name - let pf = Parser.byVerWithMods [] Fortran90 name contents + let pf = Parser.byVerWithMods [] (VanillaVersion Fortran90) name contents case pf of Right pf -> return $ rename . analyseBBlocks . analyseRenames . initAnalysis $ pf Left err -> error $ "Error parsing " ++ name ++ ": " ++ show err diff --git a/test/Language/Fortran/Analysis/RenamingSpec.hs b/test/Language/Fortran/Analysis/RenamingSpec.hs index 3f7ee2b6..5364a4d0 100644 --- a/test/Language/Fortran/Analysis/RenamingSpec.hs +++ b/test/Language/Fortran/Analysis/RenamingSpec.hs @@ -34,7 +34,7 @@ countUnrenamed e = length [ () | ExpValue Analysis { uniqueName = Nothing } _ Va uniE_PF = universeBi fortran90Parser :: String -> ProgramFile A0 -fortran90Parser = Parser.parseUnsafe Parser.f90 . B.pack +fortran90Parser = Parser.parseUnsafe (Parser.f90 []) . B.pack spec :: Spec spec = do diff --git a/test/Language/Fortran/Analysis/TypesSpec.hs b/test/Language/Fortran/Analysis/TypesSpec.hs index e89a4a38..f31886f9 100644 --- a/test/Language/Fortran/Analysis/TypesSpec.hs +++ b/test/Language/Fortran/Analysis/TypesSpec.hs @@ -22,10 +22,10 @@ typedProgramFile :: Data a => ProgramFile a -> ProgramFile (Analysis a) typedProgramFile = fst . analyseTypes . analyseRenames . initAnalysis legacy77Parser :: String -> ProgramFile A0 -legacy77Parser = Parser.parseUnsafe Parser.f77l . B.pack +legacy77Parser = Parser.parseUnsafe (Parser.f77l []) . B.pack fortran90Parser :: String -> ProgramFile A0 -fortran90Parser = Parser.parseUnsafe Parser.f90 . B.pack +fortran90Parser = Parser.parseUnsafe (Parser.f90 []) . B.pack uniExpr :: ProgramFile (Analysis A0) -> [Expression (Analysis A0)] uniExpr = universeBi diff --git a/test/Language/Fortran/AnalysisSpec.hs b/test/Language/Fortran/AnalysisSpec.hs index 8e3fa537..7038d737 100644 --- a/test/Language/Fortran/AnalysisSpec.hs +++ b/test/Language/Fortran/AnalysisSpec.hs @@ -10,7 +10,7 @@ import qualified Language.Fortran.Parser as Parser import qualified Data.ByteString.Char8 as B pParser :: String -> ProgramFile (Analysis A0) -pParser = initAnalysis . Parser.parseUnsafe Parser.f77e . B.pack +pParser = initAnalysis . Parser.parseUnsafe (Parser.f77e []) . B.pack spec :: Spec spec = diff --git a/test/Language/Fortran/Parser/Fixed/Fortran66Spec.hs b/test/Language/Fortran/Parser/Fixed/Fortran66Spec.hs index e42c61a3..a45a3bb9 100644 --- a/test/Language/Fortran/Parser/Fixed/Fortran66Spec.hs +++ b/test/Language/Fortran/Parser/Fixed/Fortran66Spec.hs @@ -14,11 +14,11 @@ import Prelude hiding ( LT ) import qualified Data.ByteString.Char8 as B parseWith :: Parse Fixed.AlexInput Fixed.Token a -> String -> a -parseWith p = parseUnsafe (makeParserFixed p Fortran66) . B.pack +parseWith p = parseUnsafe (makeParserFixed p (VanillaVersion Fortran66)) . B.pack eParser :: String -> Expression () eParser = parseUnsafe p . B.pack - where p = makeParser initParseStateFixedExpr F66.expressionParser Fortran66 + where p = makeParser initParseStateFixedExpr F66.expressionParser (VanillaVersion Fortran66) sParser :: String -> Statement () sParser = parseWith F66.statementParser diff --git a/test/Language/Fortran/Parser/Fixed/Fortran77/ParserSpec.hs b/test/Language/Fortran/Parser/Fixed/Fortran77/ParserSpec.hs index d4cc3bee..0ac28b98 100644 --- a/test/Language/Fortran/Parser/Fixed/Fortran77/ParserSpec.hs +++ b/test/Language/Fortran/Parser/Fixed/Fortran77/ParserSpec.hs @@ -15,7 +15,7 @@ import Data.List ( intercalate ) import qualified Data.ByteString.Char8 as B parseWith :: FortranVersion -> Parse Fixed.AlexInput Fixed.Token a -> String -> a -parseWith fv p = parseUnsafe (makeParserFixed p fv) . B.pack +parseWith fv p = parseUnsafe (makeParserFixed p (VanillaVersion fv)) . B.pack pParser :: String -> ProgramFile () pParser = parseWith Fortran77 F77.programParser @@ -28,7 +28,7 @@ sParser = parseWith Fortran77 F77.statementParser eParser :: String -> Expression () eParser = parseUnsafe p . B.pack - where p = makeParser initParseStateFixedExpr F77.expressionParser Fortran77 + where p = makeParser initParseStateFixedExpr F77.expressionParser (VanillaVersion Fortran77) plParser :: String -> ProgramFile () plParser = parseWith Fortran77Legacy F77.programParser diff --git a/test/Language/Fortran/Parser/Fixed/LexerSpec.hs b/test/Language/Fortran/Parser/Fixed/LexerSpec.hs index fee83413..20298711 100644 --- a/test/Language/Fortran/Parser/Fixed/LexerSpec.hs +++ b/test/Language/Fortran/Parser/Fixed/LexerSpec.hs @@ -13,30 +13,30 @@ import Language.Fortran.Version import Data.List (isPrefixOf) import qualified Data.ByteString.Char8 as B -initState :: FortranVersion -> B.ByteString -> ParseState AlexInput +initState :: QualifiedFortranVersion -> B.ByteString -> ParseState AlexInput initState = initParseStateFixed "" -collectFixedTokens :: FortranVersion -> B.ByteString -> [Token] -collectFixedTokens fv bs = - collectTokens lexer' $ initState fv bs +collectFixedTokens :: QualifiedFortranVersion -> B.ByteString -> [Token] +collectFixedTokens qfv bs = + collectTokens lexer' $ initState qfv bs collectFixedTokens' :: FortranVersion -> String -> [Token] -collectFixedTokens' v = collectFixedTokens v . B.pack +collectFixedTokens' v = collectFixedTokens (VanillaVersion v) . B.pack -collectFixedTokensSafe :: FortranVersion -> B.ByteString -> Maybe [Token] +collectFixedTokensSafe :: QualifiedFortranVersion -> B.ByteString -> Maybe [Token] collectFixedTokensSafe fv bs = collectTokensSafe lexer' $ initState fv bs lex66 :: String -> Maybe Token -lex66 = collectToLex Fortran66 +lex66 = collectToLex (VanillaVersion Fortran66) safeLex66 :: String -> Maybe Token -safeLex66 = collectToLexSafe Fortran66 +safeLex66 = collectToLexSafe (VanillaVersion Fortran66) lex77 :: String -> Maybe Token -lex77 = collectToLex Fortran77 +lex77 = collectToLex (VanillaVersion Fortran77) -collectToLex :: FortranVersion -> String -> Maybe Token +collectToLex :: QualifiedFortranVersion -> String -> Maybe Token collectToLex version srcInput = dropUntil2 $ collectFixedTokens version (B.pack srcInput) where dropUntil2 [] = Nothing @@ -44,7 +44,7 @@ collectToLex version srcInput = dropUntil2 $ collectFixedTokens version (B.pack dropUntil2 [a,_] = Just a dropUntil2 (_:xs) = dropUntil2 xs -collectToLexSafe :: FortranVersion -> String -> Maybe Token +collectToLexSafe :: QualifiedFortranVersion -> String -> Maybe Token collectToLexSafe version srcInput = dropUntil2 $ collectFixedTokensSafe version (B.pack srcInput) where dropUntil2 (Just [a,_]) = Just a @@ -142,7 +142,7 @@ spec = describe "lexN" $ it "`lexN 5` parses lexes next five characters" $ - (lexemeMatch . aiLexeme) (evalParse (lexN 5 >> getAlex) (initState Fortran66 (B.pack "helloWorld"))) `shouldBe` reverse "hello" + (lexemeMatch . aiLexeme) (evalParse (lexN 5 >> getAlex) (initState (VanillaVersion Fortran66) (B.pack "helloWorld"))) `shouldBe` reverse "hello" describe "lexHollerith" $ do it "lexes Hollerith '7hmistral'" $ diff --git a/test/Language/Fortran/Parser/Free/Fortran2003Spec.hs b/test/Language/Fortran/Parser/Free/Fortran2003Spec.hs index ac382332..f6780dc9 100644 --- a/test/Language/Fortran/Parser/Free/Fortran2003Spec.hs +++ b/test/Language/Fortran/Parser/Free/Fortran2003Spec.hs @@ -16,11 +16,11 @@ import qualified Language.Fortran.Parser.Free.Lexer as Free import qualified Data.ByteString.Char8 as B parseWith :: Parse Free.AlexInput Free.Token a -> String -> a -parseWith p = parseUnsafe (makeParserFree p Fortran2003) . B.pack +parseWith p = parseUnsafe (makeParserFree p $ VanillaVersion Fortran2003) . B.pack eParser :: String -> Expression () eParser = parseUnsafe p . B.pack - where p = makeParser initParseStateFreeExpr F2003.expressionParser Fortran2003 + where p = makeParser initParseStateFreeExpr F2003.expressionParser $ VanillaVersion Fortran2003 sParser :: String -> Statement () sParser = parseWith F2003.statementParser diff --git a/test/Language/Fortran/Parser/Free/Fortran90Spec.hs b/test/Language/Fortran/Parser/Free/Fortran90Spec.hs index f6dddd5e..62211326 100644 --- a/test/Language/Fortran/Parser/Free/Fortran90Spec.hs +++ b/test/Language/Fortran/Parser/Free/Fortran90Spec.hs @@ -18,11 +18,11 @@ import qualified Language.Fortran.Parser.Free.Lexer as Free import qualified Data.ByteString.Char8 as B parseWith :: Parse Free.AlexInput Free.Token a -> String -> a -parseWith p = parseUnsafe (makeParserFree p Fortran90) . B.pack +parseWith p = parseUnsafe (makeParserFree p $ VanillaVersion Fortran90) . B.pack eParser :: String -> Expression () eParser = parseUnsafe p . B.pack - where p = makeParser initParseStateFreeExpr F90.expressionParser Fortran90 + where p = makeParser initParseStateFreeExpr F90.expressionParser $ VanillaVersion Fortran90 sParser :: String -> Statement () sParser = parseWith F90.statementParser diff --git a/test/Language/Fortran/Parser/Free/Fortran95Spec.hs b/test/Language/Fortran/Parser/Free/Fortran95Spec.hs index d317b2e6..0b3dde06 100644 --- a/test/Language/Fortran/Parser/Free/Fortran95Spec.hs +++ b/test/Language/Fortran/Parser/Free/Fortran95Spec.hs @@ -20,11 +20,11 @@ import qualified Data.ByteString.Char8 as B import Control.Exception (evaluate) parseWith :: Parse Free.AlexInput Free.Token a -> String -> a -parseWith p = parseUnsafe (makeParserFree p Fortran95) . B.pack +parseWith p = parseUnsafe (makeParserFree p $ VanillaVersion Fortran95) . B.pack eParser :: String -> Expression () eParser = parseUnsafe p . B.pack - where p = makeParser initParseStateFreeExpr F95.expressionParser Fortran95 + where p = makeParser initParseStateFreeExpr F95.expressionParser $ VanillaVersion Fortran95 sParser :: String -> Statement () sParser = parseWith F95.statementParser diff --git a/test/Language/Fortran/Parser/Free/LexerSpec.hs b/test/Language/Fortran/Parser/Free/LexerSpec.hs index db80b2f4..01444e51 100644 --- a/test/Language/Fortran/Parser/Free/LexerSpec.hs +++ b/test/Language/Fortran/Parser/Free/LexerSpec.hs @@ -14,7 +14,7 @@ import qualified Data.ByteString.Char8 as B collectFreeTokens :: FortranVersion -> B.ByteString -> [Token] collectFreeTokens fv bs = - collectTokens lexer' $ initParseStateFree "" fv bs + collectTokens lexer' $ initParseStateFree "" (VanillaVersion fv) bs collectF90 :: String -> [Token] collectF90 = collectFreeTokens Fortran90 . B.pack diff --git a/test/Language/Fortran/Parser/MonadSpec.hs b/test/Language/Fortran/Parser/MonadSpec.hs index 172e53d5..517570e9 100644 --- a/test/Language/Fortran/Parser/MonadSpec.hs +++ b/test/Language/Fortran/Parser/MonadSpec.hs @@ -11,7 +11,7 @@ import Language.Fortran.Util.Position vanillaParseState :: ParseState String vanillaParseState = ParseState { psAlexInput = "" - , psVersion = Fortran66 + , psVersion = VanillaVersion Fortran66 , psFilename = "" , psParanthesesCount = ParanthesesCount 0 False , psContext = [ ConStart ] @@ -40,7 +40,7 @@ instance LastToken SomeInput String where vanillaSomeInput :: ParseState SomeInput vanillaSomeInput = ParseState { psAlexInput = initSomeInput - , psVersion = Fortran66 + , psVersion = VanillaVersion Fortran66 , psFilename = "some.f" , psParanthesesCount = ParanthesesCount 0 False , psContext = [ ConStart ] @@ -51,7 +51,7 @@ spec = describe "ParserMonad" $ do describe "Parse" $ do it "should give out correct version" $ - evalParse getVersion vanillaParseState `shouldBe` Fortran66 + evalParse getVersion vanillaParseState `shouldBe` VanillaVersion Fortran66 it "satisfies read after write equals to what is written" $ let ai = evalParse (putAlex "l'enfer" >> getAlex) vanillaParseState in diff --git a/test/Language/Fortran/Transformation/GroupingSpec.hs b/test/Language/Fortran/Transformation/GroupingSpec.hs index 53f70e8a..df486732 100644 --- a/test/Language/Fortran/Transformation/GroupingSpec.hs +++ b/test/Language/Fortran/Transformation/GroupingSpec.hs @@ -139,15 +139,15 @@ getSingleParsedBlock p c = -- TODO Runs internal transformations, which means we aren't explicitly asking -- for a grouping transformation. Bit weird. getSingleParsedBlock95 :: String -> Block A0 -getSingleParsedBlock95 = getSingleParsedBlock Parser.f95 +getSingleParsedBlock95 = getSingleParsedBlock $ Parser.f95 [] -- TODO Runs internal transformations, which means we aren't explicitly asking -- for a grouping transformation. Bit weird. getSingleParsedBlock77 :: String -> Block A0 -getSingleParsedBlock77 = getSingleParsedBlock Parser.f77 +getSingleParsedBlock77 = getSingleParsedBlock $ Parser.f77 [] getSingleParsedBlock77Legacy :: String -> Block A0 -getSingleParsedBlock77Legacy = getSingleParsedBlock Parser.f77lNoTransform +getSingleParsedBlock77Legacy = getSingleParsedBlock $ Parser.f77lNoTransform [] type SimpleSpan = (Int, Int, Int, Int)