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 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 (writeAST parse) pf
    return $ transformBi linkBlocks pf'
  where
    writeAST :: (Data a, ASTEmbeddable a ast)
             => AnnotationParser ast -> Block a -> Logger (Block a)
    writeAST parse b@(BlComment a srcSpan 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
    writeAST _ b = return b
    
    linkBlocks :: (Data a, Linkable a) => [ Block a ] -> [ Block a ]
    linkBlocks [ ] = [ ]
    linkBlocks [ x ] = [ x ]
    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 = b : linkBlocks bs
      where
        isComment BlComment{} = True
        isComment _ = False
class ASTEmbeddable a ast where
  annotateWithAST :: a -> ast -> a
class Linkable a where
  link :: a -> Block a -> a
  
  
  
  
  
  linkMultiple :: [Block a] -> [Block a] -> ([Block a], [Block a])
  linkMultiple comments blocks =
     (map (fmap $ flip link (head blocks)) comments, blocks)
parserWarn :: SrcSpan -> String -> Logger ()
parserWarn srcSpan err = tell [ "Error " ++ show srcSpan ++ ": " ++ err ]