module Language.Fortran.Parser.Any where
import Language.Fortran.AST
import Language.Fortran.Util.ModFile
import Language.Fortran.Version (FortranVersion(..), deduceFortranVersion)
import Language.Fortran.ParserMonad (ParseErrorSimple(..), fromParseResult)
import Language.Fortran.Parser.Fortran66 ( fortran66Parser, fortran66ParserWithModFiles )
import Language.Fortran.Parser.Fortran77 ( fortran77Parser, fortran77ParserWithModFiles
, extended77Parser, extended77ParserWithModFiles
, legacy77Parser, legacy77ParserWithModFiles )
import Language.Fortran.Parser.Fortran90 ( fortran90Parser, fortran90ParserWithModFiles )
import Language.Fortran.Parser.Fortran95 ( fortran95Parser, fortran95ParserWithModFiles )
import Language.Fortran.Parser.Fortran2003 ( fortran2003Parser, fortran2003ParserWithModFiles )
import qualified Data.ByteString.Char8 as B
type Parser = B.ByteString -> String -> Either ParseErrorSimple (ProgramFile A0)
parserVersions :: [(FortranVersion, Parser)]
parserVersions :: [(FortranVersion, Parser)]
parserVersions =
[ (FortranVersion
Fortran66, ParseResult AlexInput Token (ProgramFile A0)
-> Either ParseErrorSimple (ProgramFile A0)
forall c b a.
Show c =>
ParseResult b c a -> Either ParseErrorSimple a
fromParseResult (ParseResult AlexInput Token (ProgramFile A0)
-> Either ParseErrorSimple (ProgramFile A0))
-> (ByteString
-> String -> ParseResult AlexInput Token (ProgramFile A0))
-> Parser
forall b c t a. (b -> c) -> (t -> a -> b) -> t -> a -> c
`after` ByteString
-> String -> ParseResult AlexInput Token (ProgramFile A0)
fortran66Parser)
, (FortranVersion
Fortran77, ParseResult AlexInput Token (ProgramFile A0)
-> Either ParseErrorSimple (ProgramFile A0)
forall c b a.
Show c =>
ParseResult b c a -> Either ParseErrorSimple a
fromParseResult (ParseResult AlexInput Token (ProgramFile A0)
-> Either ParseErrorSimple (ProgramFile A0))
-> (ByteString
-> String -> ParseResult AlexInput Token (ProgramFile A0))
-> Parser
forall b c t a. (b -> c) -> (t -> a -> b) -> t -> a -> c
`after` ByteString
-> String -> ParseResult AlexInput Token (ProgramFile A0)
fortran77Parser)
, (FortranVersion
Fortran77Extended, ParseResult AlexInput Token (ProgramFile A0)
-> Either ParseErrorSimple (ProgramFile A0)
forall c b a.
Show c =>
ParseResult b c a -> Either ParseErrorSimple a
fromParseResult (ParseResult AlexInput Token (ProgramFile A0)
-> Either ParseErrorSimple (ProgramFile A0))
-> (ByteString
-> String -> ParseResult AlexInput Token (ProgramFile A0))
-> Parser
forall b c t a. (b -> c) -> (t -> a -> b) -> t -> a -> c
`after` ByteString
-> String -> ParseResult AlexInput Token (ProgramFile A0)
extended77Parser)
, (FortranVersion
Fortran77Legacy, ParseResult AlexInput Token (ProgramFile A0)
-> Either ParseErrorSimple (ProgramFile A0)
forall c b a.
Show c =>
ParseResult b c a -> Either ParseErrorSimple a
fromParseResult (ParseResult AlexInput Token (ProgramFile A0)
-> Either ParseErrorSimple (ProgramFile A0))
-> (ByteString
-> String -> ParseResult AlexInput Token (ProgramFile A0))
-> Parser
forall b c t a. (b -> c) -> (t -> a -> b) -> t -> a -> c
`after` ByteString
-> String -> ParseResult AlexInput Token (ProgramFile A0)
legacy77Parser)
, (FortranVersion
Fortran90, ParseResult AlexInput Token (ProgramFile A0)
-> Either ParseErrorSimple (ProgramFile A0)
forall c b a.
Show c =>
ParseResult b c a -> Either ParseErrorSimple a
fromParseResult (ParseResult AlexInput Token (ProgramFile A0)
-> Either ParseErrorSimple (ProgramFile A0))
-> (ByteString
-> String -> ParseResult AlexInput Token (ProgramFile A0))
-> Parser
forall b c t a. (b -> c) -> (t -> a -> b) -> t -> a -> c
`after` ByteString
-> String -> ParseResult AlexInput Token (ProgramFile A0)
fortran90Parser)
, (FortranVersion
Fortran95, ParseResult AlexInput Token (ProgramFile A0)
-> Either ParseErrorSimple (ProgramFile A0)
forall c b a.
Show c =>
ParseResult b c a -> Either ParseErrorSimple a
fromParseResult (ParseResult AlexInput Token (ProgramFile A0)
-> Either ParseErrorSimple (ProgramFile A0))
-> (ByteString
-> String -> ParseResult AlexInput Token (ProgramFile A0))
-> Parser
forall b c t a. (b -> c) -> (t -> a -> b) -> t -> a -> c
`after` ByteString
-> String -> ParseResult AlexInput Token (ProgramFile A0)
fortran95Parser)
, (FortranVersion
Fortran2003, ParseResult AlexInput Token (ProgramFile A0)
-> Either ParseErrorSimple (ProgramFile A0)
forall c b a.
Show c =>
ParseResult b c a -> Either ParseErrorSimple a
fromParseResult (ParseResult AlexInput Token (ProgramFile A0)
-> Either ParseErrorSimple (ProgramFile A0))
-> (ByteString
-> String -> ParseResult AlexInput Token (ProgramFile A0))
-> Parser
forall b c t a. (b -> c) -> (t -> a -> b) -> t -> a -> c
`after` ByteString
-> String -> ParseResult AlexInput Token (ProgramFile A0)
fortran2003Parser) ]
type ParserWithModFiles = ModFiles -> B.ByteString -> String -> Either ParseErrorSimple (ProgramFile A0)
parserWithModFilesVersions :: [(FortranVersion, ParserWithModFiles)]
parserWithModFilesVersions :: [(FortranVersion, ParserWithModFiles)]
parserWithModFilesVersions =
[ (FortranVersion
Fortran66, \ModFiles
m ByteString
s -> ParseResult AlexInput Token (ProgramFile A0)
-> Either ParseErrorSimple (ProgramFile A0)
forall c b a.
Show c =>
ParseResult b c a -> Either ParseErrorSimple a
fromParseResult (ParseResult AlexInput Token (ProgramFile A0)
-> Either ParseErrorSimple (ProgramFile A0))
-> (String -> ParseResult AlexInput Token (ProgramFile A0))
-> String
-> Either ParseErrorSimple (ProgramFile A0)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModFiles
-> ByteString
-> String
-> ParseResult AlexInput Token (ProgramFile A0)
fortran66ParserWithModFiles ModFiles
m ByteString
s)
, (FortranVersion
Fortran77, \ModFiles
m ByteString
s -> ParseResult AlexInput Token (ProgramFile A0)
-> Either ParseErrorSimple (ProgramFile A0)
forall c b a.
Show c =>
ParseResult b c a -> Either ParseErrorSimple a
fromParseResult (ParseResult AlexInput Token (ProgramFile A0)
-> Either ParseErrorSimple (ProgramFile A0))
-> (String -> ParseResult AlexInput Token (ProgramFile A0))
-> String
-> Either ParseErrorSimple (ProgramFile A0)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModFiles
-> ByteString
-> String
-> ParseResult AlexInput Token (ProgramFile A0)
fortran77ParserWithModFiles ModFiles
m ByteString
s)
, (FortranVersion
Fortran77Extended, \ModFiles
m ByteString
s -> ParseResult AlexInput Token (ProgramFile A0)
-> Either ParseErrorSimple (ProgramFile A0)
forall c b a.
Show c =>
ParseResult b c a -> Either ParseErrorSimple a
fromParseResult (ParseResult AlexInput Token (ProgramFile A0)
-> Either ParseErrorSimple (ProgramFile A0))
-> (String -> ParseResult AlexInput Token (ProgramFile A0))
-> String
-> Either ParseErrorSimple (ProgramFile A0)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModFiles
-> ByteString
-> String
-> ParseResult AlexInput Token (ProgramFile A0)
extended77ParserWithModFiles ModFiles
m ByteString
s)
, (FortranVersion
Fortran77Legacy, \ModFiles
m ByteString
s -> ParseResult AlexInput Token (ProgramFile A0)
-> Either ParseErrorSimple (ProgramFile A0)
forall c b a.
Show c =>
ParseResult b c a -> Either ParseErrorSimple a
fromParseResult (ParseResult AlexInput Token (ProgramFile A0)
-> Either ParseErrorSimple (ProgramFile A0))
-> (String -> ParseResult AlexInput Token (ProgramFile A0))
-> String
-> Either ParseErrorSimple (ProgramFile A0)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModFiles
-> ByteString
-> String
-> ParseResult AlexInput Token (ProgramFile A0)
legacy77ParserWithModFiles ModFiles
m ByteString
s)
, (FortranVersion
Fortran90, \ModFiles
m ByteString
s -> ParseResult AlexInput Token (ProgramFile A0)
-> Either ParseErrorSimple (ProgramFile A0)
forall c b a.
Show c =>
ParseResult b c a -> Either ParseErrorSimple a
fromParseResult (ParseResult AlexInput Token (ProgramFile A0)
-> Either ParseErrorSimple (ProgramFile A0))
-> (String -> ParseResult AlexInput Token (ProgramFile A0))
-> String
-> Either ParseErrorSimple (ProgramFile A0)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModFiles
-> ByteString
-> String
-> ParseResult AlexInput Token (ProgramFile A0)
fortran90ParserWithModFiles ModFiles
m ByteString
s)
, (FortranVersion
Fortran95, \ModFiles
m ByteString
s -> ParseResult AlexInput Token (ProgramFile A0)
-> Either ParseErrorSimple (ProgramFile A0)
forall c b a.
Show c =>
ParseResult b c a -> Either ParseErrorSimple a
fromParseResult (ParseResult AlexInput Token (ProgramFile A0)
-> Either ParseErrorSimple (ProgramFile A0))
-> (String -> ParseResult AlexInput Token (ProgramFile A0))
-> String
-> Either ParseErrorSimple (ProgramFile A0)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModFiles
-> ByteString
-> String
-> ParseResult AlexInput Token (ProgramFile A0)
fortran95ParserWithModFiles ModFiles
m ByteString
s)
, (FortranVersion
Fortran2003, \ModFiles
m ByteString
s -> ParseResult AlexInput Token (ProgramFile A0)
-> Either ParseErrorSimple (ProgramFile A0)
forall c b a.
Show c =>
ParseResult b c a -> Either ParseErrorSimple a
fromParseResult (ParseResult AlexInput Token (ProgramFile A0)
-> Either ParseErrorSimple (ProgramFile A0))
-> (String -> ParseResult AlexInput Token (ProgramFile A0))
-> String
-> Either ParseErrorSimple (ProgramFile A0)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModFiles
-> ByteString
-> String
-> ParseResult AlexInput Token (ProgramFile A0)
fortran2003ParserWithModFiles ModFiles
m ByteString
s) ]
after :: (b -> c) -> (t -> a -> b) -> t -> a -> c
after :: (b -> c) -> (t -> a -> b) -> t -> a -> c
after b -> c
g t -> a -> b
f t
x = b -> c
g (b -> c) -> (a -> b) -> a -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. t -> a -> b
f t
x
fortranParser :: Parser
fortranParser :: Parser
fortranParser ByteString
contents String
filename = do
let Just Parser
parserF = FortranVersion -> [(FortranVersion, Parser)] -> Maybe Parser
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup (String -> FortranVersion
deduceFortranVersion String
filename) [(FortranVersion, Parser)]
parserVersions
Parser
parserF ByteString
contents String
filename
fortranParserWithModFiles :: ParserWithModFiles
fortranParserWithModFiles :: ParserWithModFiles
fortranParserWithModFiles ModFiles
mods ByteString
contents String
filename = do
let Just ParserWithModFiles
parserF = FortranVersion
-> [(FortranVersion, ParserWithModFiles)]
-> Maybe ParserWithModFiles
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup (String -> FortranVersion
deduceFortranVersion String
filename) [(FortranVersion, ParserWithModFiles)]
parserWithModFilesVersions
ParserWithModFiles
parserF ModFiles
mods ByteString
contents String
filename
fortranParserWithVersion :: FortranVersion -> Parser
fortranParserWithVersion :: FortranVersion -> Parser
fortranParserWithVersion FortranVersion
v ByteString
contents String
filename = do
let Just Parser
parserF = FortranVersion -> [(FortranVersion, Parser)] -> Maybe Parser
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup FortranVersion
v [(FortranVersion, Parser)]
parserVersions
Parser
parserF ByteString
contents String
filename
fortranParserWithModFilesAndVersion :: FortranVersion -> ParserWithModFiles
fortranParserWithModFilesAndVersion :: FortranVersion -> ParserWithModFiles
fortranParserWithModFilesAndVersion FortranVersion
v ModFiles
mods ByteString
contents String
filename = do
let Just ParserWithModFiles
parserF = FortranVersion
-> [(FortranVersion, ParserWithModFiles)]
-> Maybe ParserWithModFiles
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup FortranVersion
v [(FortranVersion, ParserWithModFiles)]
parserWithModFilesVersions
ParserWithModFiles
parserF ModFiles
mods ByteString
contents String
filename