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

Safe HaskellNone
LanguageHaskell2010

Language.Fortran.Analysis

Contents

Description

Common data structures and functions supporting analysis of the AST.

Synopsis

Documentation

initAnalysis :: Functor b => b a -> b (Analysis a) Source #

Create analysis annotations for the program, saving the original annotations.

stripAnalysis :: Functor b => b (Analysis a) -> b a Source #

Remove analysis annotations from the program, restoring the original annotations.

data Analysis a Source #

Constructors

Analysis 

Fields

Instances

Eq a => Eq (Analysis a) Source # 

Methods

(==) :: Analysis a -> Analysis a -> Bool #

(/=) :: Analysis a -> Analysis a -> Bool #

Data a => Data (Analysis a) Source # 

Methods

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

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

toConstr :: Analysis a -> Constr #

dataTypeOf :: Analysis a -> DataType #

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

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

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

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

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

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

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

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

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

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

Show a => Show (Analysis a) Source # 

Methods

showsPrec :: Int -> Analysis a -> ShowS #

show :: Analysis a -> String #

showList :: [Analysis a] -> ShowS #

varName :: Expression (Analysis a) -> String Source #

Obtain either uniqueName or source name from an ExpValue variable.

srcName :: Expression (Analysis a) -> String Source #

Obtain the source name from an ExpValue variable.

genVar :: Analysis a -> SrcSpan -> String -> Expression (Analysis a) Source #

Generate an ExpValue variable with its source name == to its uniqueName.

puName :: ProgramUnit (Analysis a) -> ProgramUnitName Source #

Obtain either ProgramUnit uniqueName or whatever is in the AST.

puSrcName :: ProgramUnit (Analysis a) -> ProgramUnitName Source #

Obtain either ProgramUnit sourceName or whatever is in the AST.

blockRhsExprs :: Data a => Block a -> [Expression a] Source #

Set of expressions used -- not defined -- by an AST-block.

rhsExprs :: (Data a, Data (b a)) => b a -> [Expression a] Source #

Return list of expressions that are not "left-hand-side" of assignment statements.

data NameType Source #

Constructors

NTSubprogram 
NTVariable 

Instances

Eq NameType Source # 
Data NameType Source # 

Methods

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

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

toConstr :: NameType -> Constr #

dataTypeOf :: NameType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord NameType Source # 
Show NameType Source # 

data IDType Source #

Constructors

IDType 

Instances

Eq IDType Source # 

Methods

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

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

Data IDType Source # 

Methods

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

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

toConstr :: IDType -> Constr #

dataTypeOf :: IDType -> DataType #

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

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

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

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

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

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

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

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

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

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

Show IDType Source # 

data ConstructType Source #

Instances

Eq ConstructType Source # 
Data ConstructType Source # 

Methods

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

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

toConstr :: ConstructType -> Constr #

dataTypeOf :: ConstructType -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ConstructType Source # 

data BaseType Source #

Instances

Eq BaseType Source # 
Data BaseType Source # 

Methods

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

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

toConstr :: BaseType -> Constr #

dataTypeOf :: BaseType -> DataType #

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

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

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

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

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

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

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

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

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

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

Show BaseType Source # 
Generic BaseType Source # 

Associated Types

type Rep BaseType :: * -> * #

Methods

from :: BaseType -> Rep BaseType x #

to :: Rep BaseType x -> BaseType #

Out BaseType Source # 

Methods

docPrec :: Int -> BaseType -> Doc #

doc :: BaseType -> Doc #

docList :: [BaseType] -> Doc #

Pretty BaseType Source # 
type Rep BaseType Source # 
type Rep BaseType = D1 (MetaData "BaseType" "Language.Fortran.AST" "fortran-src-0.1.0.3-91DD86MnaFR2VbfFJIGSH6" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "TypeInteger" PrefixI False) U1) (C1 (MetaCons "TypeReal" PrefixI False) U1)) ((:+:) (C1 (MetaCons "TypeDoublePrecision" PrefixI False) U1) (C1 (MetaCons "TypeComplex" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "TypeDoubleComplex" PrefixI False) U1) (C1 (MetaCons "TypeLogical" PrefixI False) U1)) ((:+:) (C1 (MetaCons "TypeCharacter" PrefixI False) U1) (C1 (MetaCons "TypeCustom" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))))

lhsExprs :: (Data a, Data (b a)) => b a -> [Expression a] Source #

Return list of expressions used as the left-hand-side of assignment statements (including for-loops and function-calls by reference).

isLExpr :: Expression a -> Bool Source #

Is this an expression capable of assignment?

allVars :: forall a b. (Data a, Data (b (Analysis a))) => b (Analysis a) -> [Name] Source #

Set of names found in an AST node.

allLhsVars :: (Data a, Data (b (Analysis a))) => b (Analysis a) -> [Name] Source #

Set of names found in the parts of an AST that are the target of an assignment statement.

blockVarUses :: Data a => Block (Analysis a) -> [Name] Source #

Set of names used -- not defined -- by an AST-block.

blockVarDefs :: Data a => Block (Analysis a) -> [Name] Source #

Set of names defined by an AST-block.

type BB a = [Block a] Source #

Basic block

type BBGr a = Gr (BB a) () Source #

Basic block graph.

type TransFunc f g a = (f (Analysis a) -> f (Analysis a)) -> g (Analysis a) -> g (Analysis a) Source #

The type of "transformBi"-family functions

type TransFuncM m f g a = (f (Analysis a) -> m (f (Analysis a))) -> g (Analysis a) -> m (g (Analysis a)) Source #

The type of "transformBiM"-family functions

Orphan instances

(Typeable * a, Typeable * b) => Data (Gr a b) Source # 

Methods

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

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

toConstr :: Gr a b -> Constr #

dataTypeOf :: Gr a b -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Gr a b)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Gr a b)) #

gmapT :: (forall c. Data c => c -> c) -> Gr a b -> Gr a b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Gr a b -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Gr a b -> r #

gmapQ :: (forall d. Data d => d -> u) -> Gr a b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Gr a b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Gr a b -> m (Gr a b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Gr a b -> m (Gr a b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Gr a b -> m (Gr a b) #