module Camfort.Analysis.CommentAnnotator ( annotateComments
, Logger
, ASTEmbeddable(..)
, Linkable(..)
, AnnotationParseError(..)
, AnnotationParser
, failWith
) where
import Control.Monad.Writer.Strict (Writer(..), tell)
import Data.Generics.Uniplate.Operations
import Data.Data (Data)
import Debug.Trace
import Language.Fortran.AST
import Language.Fortran.Util.Position
type Logger = Writer [ String ]
type AnnotationParser ast = String -> Either AnnotationParseError ast
data AnnotationParseError =
NotAnnotation
| ProbablyAnnotation String
deriving (Eq, Show)
failWith :: AnnotationParser ast
failWith = Left . ProbablyAnnotation
annotateComments :: forall a ast . (Data a, Linkable a, ASTEmbeddable a ast)
=> AnnotationParser ast
-> ProgramFile a
-> Logger (ProgramFile a)
annotateComments parse pf = do
pf' <- transformBiM (writeASTProgramUnits parse) =<< transformBiM (writeASTBlocks parse) pf
return . descendBi linkProgramUnits $ descendBi linkBlocks pf'
where
writeASTBlocks :: (Data a, ASTEmbeddable a ast) => AnnotationParser ast -> Block a -> Logger (Block a)
writeASTBlocks parse b@(BlComment a srcSpan (Comment comment)) =
case parse comment of
Right ast -> return $ setAnnotation (annotateWithAST a ast) b
Left NotAnnotation -> return b
Left (ProbablyAnnotation err) -> parserWarn srcSpan err >> return b
writeASTBlocks _ b = return b
writeASTProgramUnits :: (Data a, ASTEmbeddable a ast) => AnnotationParser ast -> ProgramUnit a -> Logger (ProgramUnit a)
writeASTProgramUnits parse pu@(PUComment a srcSpan (Comment comment)) =
case parse comment of
Right ast -> return $ setAnnotation (annotateWithAST a ast) pu
Left NotAnnotation -> return pu
Left (ProbablyAnnotation err) -> parserWarn srcSpan err >> return pu
writeASTProgramUnits _ pu = return pu
linkBlocks :: (Data a, Linkable a) => [ Block a ] -> [ Block a ]
linkBlocks [ ] = [ ]
linkBlocks blocks@(b:bs)
| BlComment{} <- b =
let (comments, rest) = span isComment blocks
in if null rest
then comments
else let (bs, bs') = linkMultiple comments rest
in bs ++ linkBlocks bs'
| otherwise = (descendBi linkBlocks b) : linkBlocks bs
where
isComment BlComment{} = True
isComment _ = False
linkProgramUnits :: (Data a, Linkable a) => [ ProgramUnit a ] -> [ ProgramUnit a ]
linkProgramUnits [ ] = [ ]
linkProgramUnits programUnits@(pu:pus)
| PUComment{} <- pu =
let (comments, rest) = span isComment programUnits
in if null rest
then comments
else let (procPUs, unprocPUs) = linkMultiplePUs comments rest
in procPUs ++ linkProgramUnits unprocPUs
| otherwise = (descendBi linkProgramUnits pu) : linkProgramUnits pus
where
isComment PUComment{} = True
isComment _ = False
class ASTEmbeddable a ast where
annotateWithAST :: a -> ast -> a
class Linkable a where
link :: a -> Block a -> a
linkPU :: a -> ProgramUnit a -> a
linkMultiple :: [Block a] -> [Block a] -> ([Block a], [Block a])
linkMultiple comments blocks =
(map (fmap $ flip link (head blocks)) comments, blocks)
linkMultiplePUs :: [ProgramUnit a] -> [ProgramUnit a] -> ([ProgramUnit a], [ProgramUnit a])
linkMultiplePUs comments pus =
(map (fmap $ flip linkPU (head pus)) comments, pus)
parserWarn :: SrcSpan -> String -> Logger ()
parserWarn srcSpan err = tell [ "Error " ++ show srcSpan ++ ": " ++ err ]