camfort-1.0.1: CamFort - Cambridge Fortran infrastructure
Copyright(c) 2017 Dominic Orchard Andrew Rice Mistral Contrastin Matthew Danish
LicenseApache-2.0
Maintainerdom.orchard@gmail.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Camfort.Analysis.ModFile

Description

 
Synopsis

Getting mod files

type MFCompiler r m = r -> ModFiles -> ProgramFile A -> m ModFile Source #

Compiler for ModFile information, parameterised over an underlying monad and the input to the compiler.

genModFiles :: MonadIO m => Maybe FortranVersion -> ModFiles -> MFCompiler r m -> r -> FilePath -> [Filename] -> m ModFiles Source #

Generate mod files based on the given mod file compiler

genModFilesP :: forall m r. MonadIO m => Maybe FortranVersion -> ModFiles -> MFCompiler r m -> r -> [FilePath] -> Producer' ModFile m () Source #

Generate mod files based on the given mod file compiler (Pipes version)

getModFiles :: FilePath -> IO ModFiles Source #

Generate mod files based on the given mod file compiler (Pipes version) (testing 'bi-directional' pipes) genModFilesP' :: forall x' x m r. (MonadIO m) => Maybe FortranVersion -> FM.ModFiles -> MFCompiler r m -> r -> [FilePath] -> [FilePath] -> Proxy x' x () FM.ModFile m () genModFilesP' mv mfs mfc opts files incDirs = parse //> compile where compile :: F.ProgramFile A -> Proxy x' x () FM.ModFile m FM.ModFile compile pf = do mod <- liftIO undefined -- (genCModFile mfc opts mfs pf) yield mod -- request mod pure mod

Generate mod files based on the given mod file compiler (PipesIO version) Accumulates mods as it goes. (testing) genModFilesIO :: Maybe FortranVersion -> FM.ModFiles -> MFCompiler r IO -> r -> [FilePath] -> IO FM.ModFiles genModFilesIO mv mfs mfc opts files = fst $ P.foldM' f (pure mfs) pure (each files) where f :: FM.ModFiles -> Filename -> IO [FM.ModFile] f mods file = do mProgSrc <- readParseSrcFile mv mods file case mProgSrc of Just (pf, _) -> do mod <- genCModFile mfc opts mods pf -- yield mod pure $ mod:mods Nothing -> pure mods

Retrieve the ModFiles under a given path.

readParseSrcDir :: Maybe FortranVersion -> ModFiles -> FileOrDir -> [Filename] -> IO [(ProgramFile A, SourceText)] Source #

readParseSrcDirP :: MonadIO m => Maybe FortranVersion -> ModFiles -> FileOrDir -> [Filename] -> Producer' (ProgramFile A, SourceText) m () Source #

readParseSrcFile :: Maybe FortranVersion -> ModFiles -> Filename -> IO (Maybe (ProgramFile A, SourceText)) Source #

simpleCompiler :: Monad m => MFCompiler () m Source #

Compile the Modfile with only basic information.

Using mod files

withCombinedModuleMap :: Data a => ModFiles -> ProgramFile (Analysis a) -> (ProgramFile (Analysis a), ModuleMap) Source #

Normalize the ProgramFile to include module map information from the ModFiles. Also return the module map, which links source names to unique names within each program unit.

withCombinedEnvironment :: Data a => ModFiles -> ProgramFile a -> (ProgramFile (Analysis a), ModuleMap, TypeEnv) Source #

Normalize the ProgramFile to include environment information from the ModFiles. Also return the module map and type environment.

lookupUniqueName :: ProgramUnitName -> Name -> ModuleMap -> Maybe (Name, NameType) Source #

From a module map, look up the unique name associated with a given source name in the given program unit. Also returns the name type, which tells you whether the name belongs to a subprogram, variable or intrinsic.