module Camfort.Analysis.CommentAnnotator
( annotateComments
, isComment
, ASTEmbeddable(..)
, Linkable(..)
) where
import Data.Data (Data)
import Data.Generics.Uniplate.Operations
import Language.Fortran.AST
import Language.Fortran.Util.Position
import Camfort.Specification.Parser ( looksLikeASpec
, runParser
, SpecParseError
, SpecParser)
annotateComments :: forall m e a ast .
(Monad m, Data a, Linkable a, ASTEmbeddable a ast)
=> SpecParser e ast
-> (SrcSpan -> SpecParseError e -> m ())
-> ProgramFile a
-> m (ProgramFile a)
annotateComments parser handleErr pf = do
pf' <- transformBiM writeASTProgramUnits =<< transformBiM writeASTBlocks pf
return . descendBi linkProgramUnits $ descendBi linkBlocks pf'
where
writeAST a d srcSpan comment =
if looksLikeASpec parser comment
then case runParser parser comment of
Left err -> handleErr srcSpan err >> pure d
Right ast -> pure $ setAnnotation (annotateWithAST a ast) d
else pure d
writeASTProgramUnits :: ProgramUnit a -> m (ProgramUnit a)
writeASTProgramUnits pu@(PUComment a srcSpan (Comment comment)) =
writeAST a pu srcSpan comment
writeASTProgramUnits pu = pure pu
writeASTBlocks :: Block a -> m (Block a)
writeASTBlocks b@(BlComment a srcSpan (Comment comment)) =
writeAST a b srcSpan comment
writeASTBlocks b = pure b
joinComments [ ] = [ ]
joinComments dss@(d:ds)
| isComment d =
let (comments, rest) = span isComment dss
linkMulti = (map (fmap $ flip linker (head rest)) comments, rest)
in if null rest
then comments
else let (procs, unprocs) = linkMulti
in procs ++ joinComments unprocs
| otherwise = descendBi joinComments d
: joinComments ds
linkBlocks :: (Data a, Linkable a) => [ Block a ] -> [ Block a ]
linkBlocks = joinComments
linkProgramUnits :: (Data a, Linkable a) => [ ProgramUnit a ] -> [ ProgramUnit a ]
linkProgramUnits = joinComments
class ASTEmbeddable a ast where
annotateWithAST :: a -> ast -> a
class Linkable a where
link :: a -> Block a -> a
linkPU :: a -> ProgramUnit a -> a
class Linked a where
linker :: (Linkable b) => b -> a b -> b
instance Linked Block where
linker = link
instance Linked ProgramUnit where
linker = linkPU
class HasComment a where
isComment :: a -> Bool
instance HasComment (Block a) where
isComment BlComment{} = True
isComment _ = False
instance HasComment (ProgramUnit a) where
isComment PUComment{} = True
isComment _ = False