Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Format of Camfort precompiled files with information about Fortran
modules. The ModuleMap
stores information important to the
renamer. The other data is up to you.
Note that the encoder and decoder work on lists of ModFile so that one fsmod-file may contain information about multiple Fortran files.
One typical usage might look like:
let modFile1 = genModFile programFile let modFile2 = alterModFileData (const (Just ...)) "mydata" modFile1 let bytes = encodeModFile [modFile2] ... case decodeModFile bytes of Left error -> print error Right modFile3:otherModuleFiles -> ... where moduleMap = combinedModuleMap (modFile3:otherModuleFiles) myData = lookupModFileData "mydata" modFile3 renamedPF = analyseRenamesWithModuleMap moduleMap programFile
Synopsis
- data ModFile
- type ModFiles = [ModFile]
- emptyModFile :: ModFile
- emptyModFiles :: ModFiles
- modFileSuffix :: String
- lookupModFileData :: String -> ModFile -> Maybe ByteString
- getLabelsModFileData :: ModFile -> [String]
- alterModFileData :: (Maybe ByteString -> Maybe ByteString) -> String -> ModFile -> ModFile
- alterModFileDataF :: Functor f => (Maybe ByteString -> f (Maybe ByteString)) -> String -> ModFile -> f ModFile
- genModFile :: forall a. Data a => ProgramFile (Analysis a) -> ModFile
- regenModFile :: forall a. Data a => ProgramFile (Analysis a) -> ModFile -> ModFile
- encodeModFile :: [ModFile] -> ByteString
- decodeModFile :: ByteString -> Either String [ModFile]
- decodeModFiles :: [FilePath] -> IO [(FilePath, ModFile)]
- decodeModFiles' :: [FilePath] -> IO ModFiles
- moduleFilename :: ModFile -> String
- type StringMap = Map String String
- extractStringMap :: Data a => a -> (a, StringMap)
- combinedStringMap :: ModFiles -> StringMap
- data DeclContext
- type DeclMap = Map Name (DeclContext, SrcSpan)
- extractDeclMap :: forall a. Data a => ProgramFile (Analysis a) -> DeclMap
- combinedDeclMap :: ModFiles -> DeclMap
- extractModuleMap :: forall a. Data a => ProgramFile (Analysis a) -> ModuleMap
- combinedModuleMap :: ModFiles -> ModuleMap
- combinedTypeEnv :: ModFiles -> TypeEnv
- type ParamVarMap = ParameterVarMap
- extractParamVarMap :: forall a. Data a => ProgramFile (Analysis a) -> ParamVarMap
- combinedParamVarMap :: ModFiles -> ParamVarMap
- genUniqNameToFilenameMap :: ModFiles -> Map Name String
- data TimestampStatus
- checkTimestamps :: FilePath -> IO TimestampStatus
Main defitions
The data stored in the "mod files"
Instances
emptyModFile :: ModFile Source #
Starting point.
emptyModFiles :: ModFiles Source #
Empty set of mod files. (future proof: may not always be a list)
modFileSuffix :: String Source #
Standard ending of fortran-src-format "mod files"
lookupModFileData :: String -> ModFile -> Maybe ByteString Source #
Looks up the raw "other data" that may be stored in a ModFile by applications that make use of fortran-src.
getLabelsModFileData :: ModFile -> [String] Source #
Get a list of the labels present in the "other data" of a ModFile. More of a meta-programming / debugging feature.
alterModFileData :: (Maybe ByteString -> Maybe ByteString) -> String -> ModFile -> ModFile Source #
Allows modificationinsertiondeletion of "other data" that may
be stored in a ModFile by applications that make use of
fortran-src. See alter
for more information about
the interface of this function.
alterModFileDataF :: Functor f => (Maybe ByteString -> f (Maybe ByteString)) -> String -> ModFile -> f ModFile Source #
Creation
genModFile :: forall a. Data a => ProgramFile (Analysis a) -> ModFile Source #
Generate a fresh ModFile from the module map, declaration map and type analysis of a given analysed and renamed ProgramFile.
regenModFile :: forall a. Data a => ProgramFile (Analysis a) -> ModFile -> ModFile Source #
Extracts the module map, declaration map and type analysis from an analysed and renamed ProgramFile, then inserts it into the ModFile.
En/decoding
encodeModFile :: [ModFile] -> ByteString Source #
Convert ModFiles to a strict ByteString for writing to file.
decodeModFile :: ByteString -> Either String [ModFile] Source #
Convert a strict ByteString to ModFiles, if possible. Revert the String aliases according to the StringMap.
Operations
moduleFilename :: ModFile -> String Source #
Get the associated Fortran filename that was used to compile the ModFile.
type StringMap = Map String String Source #
A map of aliases => strings, in order to save space and share structure for repeated strings.
extractStringMap :: Data a => a -> (a, StringMap) Source #
Extract a string map from the given data, leaving behind aliased values in place of strings in the returned version.
combinedStringMap :: ModFiles -> StringMap Source #
Extract the combined string map of ModFiles. Mainly internal use.
data DeclContext Source #
Context of a declaration: the ProgramUnit where it was declared.
DCMain | |
DCBlockData | |
DCModule ProgramUnitName | |
DCFunction (ProgramUnitName, ProgramUnitName) | (uniqName, srcName) |
DCSubroutine (ProgramUnitName, ProgramUnitName) | (uniqName, srcName) |
Instances
type DeclMap = Map Name (DeclContext, SrcSpan) Source #
Map of unique variable name to the unique name of the program unit where it was defined, and the corresponding SrcSpan.
extractDeclMap :: forall a. Data a => ProgramFile (Analysis a) -> DeclMap Source #
Extract map of declared variables with their associated program unit and source span.
combinedDeclMap :: ModFiles -> DeclMap Source #
Extract the combined declaration map from a set of ModFiles. Useful for parsing a Fortran file in a large context of other modules.
extractModuleMap :: forall a. Data a => ProgramFile (Analysis a) -> ModuleMap Source #
Extract all module maps (name -> environment) by collecting all of the stored module maps within the PUModule annotation.
combinedModuleMap :: ModFiles -> ModuleMap Source #
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 -> TypeEnv Source #
Extract the combined module map from a set of ModFiles. Useful for parsing a Fortran file in a large context of other modules.
type ParamVarMap = ParameterVarMap Source #
A map of variables => their constant expression if known
extractParamVarMap :: forall a. Data a => ProgramFile (Analysis a) -> ParamVarMap Source #
Extract a map of variables assigned to constant values.
combinedParamVarMap :: ModFiles -> ParamVarMap Source #
Extract the combined string map of ModFiles. Mainly internal use.
genUniqNameToFilenameMap :: ModFiles -> Map Name String Source #
Create a map that links all unique variable/function names in the ModFiles to their corresponding filename.
data TimestampStatus Source #
Status of mod-file compared to Fortran file.
checkTimestamps :: FilePath -> IO TimestampStatus Source #
Compare the source file timestamp to the fsmod file timestamp, if it exists.