module Camfort.Analysis.Annotations
(
Annotation(..)
, A
, UA
, unitAnnotation
, pRefactored
, onPrev
, getAstSpec
, getParseSpec
, getRegionSpec
, giveAstSpec
, giveParseSpec
, giveRegionSpec
, Report
, buildCommentText
) where
import Data.Data
import Data.Maybe (isJust)
import Camfort.Specification.Units.Environment
import qualified Camfort.Specification.Units.Parser.Types as P
import Camfort.Analysis.CommentAnnotator
import qualified Camfort.Specification.Stencils.Syntax as StencilSpec
import qualified Camfort.Specification.Stencils.Parser.Types as StencilComment
import qualified Language.Fortran.AST as F
import qualified Language.Fortran.Analysis as FA
import Language.Fortran.ParserMonad (FortranVersion(Fortran90))
import qualified Language.Fortran.Util.Position as FU
type Report = String
type A = Annotation
data Annotation =
A { unitVar :: Int
, number :: Int
, refactored :: Maybe FU.Position
, newNode :: Bool
, deleteNode :: Bool
, stencilSpec :: Maybe SpecAnnotation
, stencilBlock :: Maybe (F.Block (FA.Analysis Annotation))
} deriving (Eq, Show, Typeable, Data)
data SpecAnnotation
= ParserSpec StencilComment.Specification
| RegionDecl StencilSpec.RegionDecl
| ASTSpec StencilSpec.SpecDecls
deriving (Eq, Show, Data)
giveParseSpec :: StencilComment.Specification -> Annotation -> Annotation
giveParseSpec spec ann = ann { stencilSpec = Just $ ParserSpec spec }
giveRegionSpec :: StencilSpec.RegionDecl -> Annotation -> Annotation
giveRegionSpec spec ann = ann { stencilSpec = Just $ RegionDecl spec }
giveAstSpec :: StencilSpec.SpecDecls -> Annotation -> Annotation
giveAstSpec spec ann = ann { stencilSpec = Just $ ASTSpec spec }
getParseSpec :: Annotation -> Maybe StencilComment.Specification
getParseSpec s = case stencilSpec s of
(Just (ParserSpec spec)) -> Just spec
_ -> Nothing
getRegionSpec :: Annotation -> Maybe StencilSpec.RegionDecl
getRegionSpec s = case stencilSpec s of
(Just (RegionDecl renv)) -> Just renv
_ -> Nothing
getAstSpec :: Annotation -> Maybe StencilSpec.SpecDecls
getAstSpec s = case stencilSpec s of
(Just (ASTSpec ast)) -> Just ast
_ -> Nothing
pRefactored :: Annotation -> Bool
pRefactored = isJust . refactored
unitAnnotation = A
{ unitVar = 0
, number = 0
, refactored = Nothing
, newNode = False
, deleteNode = False
, stencilSpec = Nothing
, stencilBlock = Nothing
}
type UA = FA.Analysis (UnitAnnotation A)
instance ASTEmbeddable UA P.UnitStatement where
annotateWithAST ann ast =
onPrev (\ ann -> ann { unitSpec = Just ast }) ann
instance Linkable UA where
link ann (b@(F.BlStatement _ _ _ F.StDeclaration {})) =
onPrev (\ ann -> ann { unitBlock = Just b }) ann
link ann b = ann
linkPU ann (pu@(F.PUFunction {})) =
onPrev (\ ann -> ann { unitPU = Just pu }) ann
linkPU ann (pu@(F.PUSubroutine {})) =
onPrev (\ ann -> ann { unitPU = Just pu }) ann
linkPU ann b = ann
onPrev :: (a -> a) -> FA.Analysis a -> FA.Analysis a
onPrev f ann = ann { FA.prevAnnotation = f (FA.prevAnnotation ann) }
buildCommentText :: F.MetaInfo -> Int -> String -> String
buildCommentText mi col text | isModernFortran = replicate col ' ' ++ "!" ++ text
| otherwise = "c" ++ text
where isModernFortran = F.miVersion mi >= Fortran90