fortran-src-0.4.3: Parsers and analyses for Fortran standards 66, 77, 90 and 95.
Safe HaskellNone
LanguageHaskell2010

Language.Fortran.Util.ModFile

Description

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

Documentation

modFileSuffix :: String Source #

Standard ending of fortran-src-format "mod files"

data ModFile Source #

The data stored in the "mod files"

Instances

Instances details
Eq ModFile Source # 
Instance details

Defined in Language.Fortran.Util.ModFile

Methods

(==) :: ModFile -> ModFile -> Bool #

(/=) :: ModFile -> ModFile -> Bool #

Data ModFile Source # 
Instance details

Defined in Language.Fortran.Util.ModFile

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModFile -> c ModFile #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModFile #

toConstr :: ModFile -> Constr #

dataTypeOf :: ModFile -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ModFile) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModFile) #

gmapT :: (forall b. Data b => b -> b) -> ModFile -> ModFile #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModFile -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModFile -> r #

gmapQ :: (forall d. Data d => d -> u) -> ModFile -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ModFile -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModFile -> m ModFile #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModFile -> m ModFile #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModFile -> m ModFile #

Ord ModFile Source # 
Instance details

Defined in Language.Fortran.Util.ModFile

Show ModFile Source # 
Instance details

Defined in Language.Fortran.Util.ModFile

Generic ModFile Source # 
Instance details

Defined in Language.Fortran.Util.ModFile

Associated Types

type Rep ModFile :: Type -> Type #

Methods

from :: ModFile -> Rep ModFile x #

to :: Rep ModFile x -> ModFile #

Binary ModFile Source # 
Instance details

Defined in Language.Fortran.Util.ModFile

Methods

put :: ModFile -> Put #

get :: Get ModFile #

putList :: [ModFile] -> Put #

type Rep ModFile Source # 
Instance details

Defined in Language.Fortran.Util.ModFile

type ModFiles = [ModFile] Source #

A set of decoded mod files.

emptyModFile :: ModFile Source #

Starting point.

emptyModFiles :: ModFiles Source #

Empty set of mod files. (future proof: may not always be a list)

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.

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.

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.

type StringMap = Map String String Source #

A map of aliases => strings, in order to save space and share structure for repeated strings.

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.

type ParamVarMap = ParameterVarMap Source #

A map of variables => their constant expression if known

data DeclContext Source #

Context of a declaration: the ProgramUnit where it was declared.

Instances

Instances details
Eq DeclContext Source # 
Instance details

Defined in Language.Fortran.Util.ModFile

Data DeclContext Source # 
Instance details

Defined in Language.Fortran.Util.ModFile

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeclContext -> c DeclContext #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeclContext #

toConstr :: DeclContext -> Constr #

dataTypeOf :: DeclContext -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DeclContext) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeclContext) #

gmapT :: (forall b. Data b => b -> b) -> DeclContext -> DeclContext #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeclContext -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeclContext -> r #

gmapQ :: (forall d. Data d => d -> u) -> DeclContext -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DeclContext -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeclContext -> m DeclContext #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeclContext -> m DeclContext #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeclContext -> m DeclContext #

Ord DeclContext Source # 
Instance details

Defined in Language.Fortran.Util.ModFile

Show DeclContext Source # 
Instance details

Defined in Language.Fortran.Util.ModFile

Generic DeclContext Source # 
Instance details

Defined in Language.Fortran.Util.ModFile

Associated Types

type Rep DeclContext :: Type -> Type #

Binary DeclContext Source # 
Instance details

Defined in Language.Fortran.Util.ModFile

type Rep DeclContext Source # 
Instance details

Defined in Language.Fortran.Util.ModFile

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.

extractDeclMap :: forall a. Data a => ProgramFile (Analysis a) -> DeclMap Source #

Extract map of declared variables with their associated program unit and source span.

moduleFilename :: ModFile -> String Source #

Get the associated Fortran filename that was used to compile the ModFile.

combinedStringMap :: ModFiles -> StringMap Source #

Extract the combined string map of ModFiles. Mainly internal use.

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.

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.

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.