fortran-src-0.2.0.0: Parser and anlyses for Fortran standards 66, 77, 90.

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.

One typical usage might look like:

let modFile1 = genModFile programFile
let modFile2 = alterModFileData (const (Just ...)) "mydata" modFile1
let bytes    = encodeModFile modFile1
...
case decodeModFile bytes of
  Left error -> print error
  Right modFile3 -> ...
    where
      moduleMap = combinedModuleMap (modFile3:otherModuleFiles)
      myData    = lookupModFileData "mydata" modFile3
      renamedPF = analyseRenamesWithModuleMap moduleMap programFile

Synopsis

Documentation

modFileSuffix :: String #

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

data ModFile #

The data stored in the "mod files"

Instances

Eq ModFile # 

Methods

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

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

Data 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 :: (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 # 
Show ModFile # 
Generic ModFile # 

Associated Types

type Rep ModFile :: * -> * #

Methods

from :: ModFile -> Rep ModFile x #

to :: Rep ModFile x -> ModFile #

Binary ModFile # 

Methods

put :: ModFile -> Put #

get :: Get ModFile #

putList :: [ModFile] -> Put #

type Rep ModFile # 

type ModFiles = [ModFile] #

A set of decoded mod files.

emptyModFile :: ModFile #

Starting point.

emptyModFiles :: ModFiles #

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

lookupModFileData :: String -> ModFile -> Maybe ByteString #

Looks up the raw "other data" that may be stored in a ModFile by applications that make use of fortran-src.

getLabelsModFileData :: ModFile -> [String] #

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 #

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 #

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 #

Extracts the module map, declaration map and type analysis from an analysed and renamed ProgramFile, then inserts it into the ModFile.

encodeModFile :: ModFile -> ByteString #

Convert ModFile to a strict ByteString for writing to file.

decodeModFile :: Binary a => ByteString -> Either String a #

Convert a strict ByteString to a ModFile, if possible

type DeclMap = Map Name (DeclContext, SrcSpan) #

Map of unique variable name to the unique name of the program unit where it was defined, and the corresponding SrcSpan.

data DeclContext #

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

Instances

Eq DeclContext # 
Data DeclContext # 

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 :: (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 # 
Show DeclContext # 
Generic DeclContext # 

Associated Types

type Rep DeclContext :: * -> * #

Binary DeclContext # 
type Rep DeclContext # 

extractModuleMap :: forall a. Data a => ProgramFile (Analysis a) -> ModuleMap #

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 #

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

moduleFilename :: ModFile -> String #

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

combinedDeclMap :: ModFiles -> DeclMap #

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 #

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 #

Extract the combined module map from a set of ModFiles. Useful for parsing a Fortran file in a large context of other modules.

genUniqNameToFilenameMap :: ModFiles -> Map Name String #

Create a map that links all unique variable/function names in the ModFiles to their corresponding filename.