module Camfort.Analysis.Annotations where
import Data.Data
import Data.Generics.Uniplate.Operations
import Data.Maybe (isJust)
import Data.Map.Lazy hiding (map)
import Debug.Trace
import Camfort.Specification.Units.Environment
import qualified Camfort.Specification.Units.Parser as P
import Camfort.Analysis.CommentAnnotator
import qualified Camfort.Specification.Stencils.Syntax as StencilSpec
import qualified Camfort.Specification.Stencils.Grammar as StencilComment
import qualified Language.Fortran.AST as F
import qualified Language.Fortran.Analysis as FA
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
(Either StencilComment.Specification
(Either StencilSpec.RegionEnv StencilSpec.SpecDecls))
, stencilBlock :: Maybe (F.Block (FA.Analysis Annotation))
} deriving (Eq, Show, Typeable, Data)
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
onPrev :: (a -> a) -> FA.Analysis a -> FA.Analysis a
onPrev f ann = ann { FA.prevAnnotation = f (FA.prevAnnotation ann) }
modifyAnnotation :: F.Annotated f => (a -> a) -> f a -> f a
modifyAnnotation f x = F.setAnnotation (f (F.getAnnotation x)) x