module Camfort.Specification.Stencils.CheckFrontend where
import Data.Generics.Uniplate.Operations
import Control.Arrow
import Control.Monad.State.Strict
import Control.Monad.Writer.Strict hiding (Product)
import qualified Camfort.Helpers.Vec as V
import Camfort.Specification.Stencils.CheckBackend
import qualified Camfort.Specification.Stencils.Consistency as C
import qualified Camfort.Specification.Stencils.Grammar as Gram
import Camfort.Specification.Stencils.Model
import Camfort.Specification.Stencils.InferenceFrontend hiding (LogLine)
import Camfort.Specification.Stencils.Syntax
import Camfort.Analysis.Annotations
import Camfort.Analysis.CommentAnnotator
import qualified Language.Fortran.AST as F
import qualified Language.Fortran.Analysis as FA
import qualified Language.Fortran.Analysis.Renaming as FAR
import qualified Language.Fortran.Analysis.BBlocks as FAB
import qualified Language.Fortran.Analysis.DataFlow as FAD
import qualified Language.Fortran.Util.Position as FU
import qualified Data.Map as M
import Data.Maybe
import Algebra.Lattice (joins1)
import Data.Int
import qualified Data.Set as S
stencilChecking :: FAR.NameMap -> F.ProgramFile (FA.Analysis A) -> [String]
stencilChecking nameMap pf = snd . runWriter $
do
pf' <- annotateComments Gram.specParser pf
let bm = FAD.genBlockMap pf'
let bbm = FAB.genBBlockMap pf'
let sgr = FAB.genSuperBBGr bbm
let gr = FAB.superBBGrGraph sgr
let dm = FAD.genDefMap bm
let pprint = map (\(span, spec) -> show span ++ " " ++ spec)
let rd = FAD.reachingDefinitions dm gr
let flTo = FAD.genFlowsToGraph bm dm gr rd
let beMap = FAD.genBackEdgeMap (FAD.dominators gr) gr
let ivmap = FAD.genInductionVarMapByASTBlock beMap gr
let results = let ?flowsGraph = flTo in
let ?nameMap = nameMap
in descendBiM perProgramUnitCheck pf'
let (_, output) = evalState (runWriterT results) (([], Nothing), ivmap)
tell $ pprint output
type LogLine = (FU.SrcSpan, String)
type Checker a =
WriterT [LogLine]
(State ((RegionEnv, Maybe F.ProgramUnitName), FAD.InductionVarMapByASTBlock)) a
parseCommentToAST :: FA.Analysis A -> FU.SrcSpan -> Checker (FA.Analysis A)
parseCommentToAST ann span =
case stencilSpec (FA.prevAnnotation ann) of
Just (Left stencilComment) -> do
((regionEnv, _), _) <- get
let ?renv = regionEnv
in case synToAst stencilComment of
Left err -> error $ show span ++ ": " ++ err
Right ast -> return $ onPrev
(\ann -> ann {stencilSpec = Just (Right ast)}) ann
_ -> return ann
updateRegionEnv :: FA.Analysis A -> Checker ()
updateRegionEnv ann =
case stencilSpec (FA.prevAnnotation ann) of
Just (Right (Left regionEnv)) -> modify $ first (first (regionEnv ++))
_ -> return ()
checkOffsetsAgainstSpec :: [(Variable, Multiplicity [[Int]])]
-> [(Variable, Specification)]
-> Bool
checkOffsetsAgainstSpec offsetMaps specMaps =
flip all specToVecList $
\case
(spec, Once (V.VL vs)) -> spec `C.consistent` (Once . toUNF) vs == C.Consistent
(spec, Mult (V.VL vs)) -> spec `C.consistent` (Mult . toUNF) vs == C.Consistent
where
toUNF :: [ V.Vec n Int64 ] -> UnionNF n Offsets
toUNF = joins1 . map (return . fmap intToSubscript)
intToSubscript :: Int64 -> Offsets
intToSubscript i
| fromIntegral i == absoluteRep = SetOfIntegers
| otherwise = Offsets . S.singleton $ i
specToVecList :: [ (Specification, Multiplicity (V.VecList Int64)) ]
specToVecList = map (second (fmap V.fromLists)) specToIxs
specToIxs :: [ (Specification, Multiplicity [ [ Int64 ] ]) ]
specToIxs = pairWithFst specMaps (map (second toInt64) offsetMaps)
toInt64 :: Multiplicity [ [ Int ] ] -> Multiplicity [ [ Int64 ] ]
toInt64 = fmap (map (map fromIntegral))
pairWithFst :: Eq a => [ (a, b) ] -> [ (a, c) ] -> [ (b, c) ]
pairWithFst [] _ = []
pairWithFst ((key, val):xs) ys =
map ((val,) . snd) (filter ((key ==) . fst) ys) ++ pairWithFst xs ys
perProgramUnitCheck :: (?nameMap :: FAR.NameMap, ?flowsGraph :: FAD.FlowsGraph A)
=> F.ProgramUnit (FA.Analysis A) -> Checker (F.ProgramUnit (FA.Analysis A))
perProgramUnitCheck p@F.PUModule{} = do
modify $ first (second (const (Just $ FA.puName p)))
descendBiM perBlockCheck p
perProgramUnitCheck p = descendBiM perBlockCheck p
perBlockCheck :: (?nameMap :: FAR.NameMap, ?flowsGraph :: FAD.FlowsGraph A)
=> F.Block (FA.Analysis A) -> Checker (F.Block (FA.Analysis A))
perBlockCheck b@(F.BlComment ann span _) = do
ann' <- parseCommentToAST ann span
updateRegionEnv ann'
let b' = F.setAnnotation ann' b
case (stencilSpec $ FA.prevAnnotation ann', stencilBlock $ FA.prevAnnotation ann') of
(Just (Right (Right specDecls)), Just block) ->
case block of
s@(F.BlStatement _ span' _ (F.StExpressionAssign _ _ lhs _)) ->
case isArraySubscript lhs of
Just subs -> do
ivmap <- snd <$> get
let realName v = v `fromMaybe` (v `M.lookup` ?nameMap)
let lhsN = fromMaybe [] (neighbourIndex ivmap subs)
let correctNames = map (first realName)
let relOffsets = correctNames . fst . runWriter $ genOffsets ivmap lhsN [s]
let multOffsets = map (\relOffset ->
case relOffset of
(var, (True, offsets)) -> (var, Mult offsets)
(var, (False, offsets)) -> (var, Once offsets)) relOffsets
let expandedDecls =
concatMap (\(vars,spec) -> map (flip (,) spec) vars) specDecls
if checkOffsetsAgainstSpec multOffsets expandedDecls
then tell [ (span, "Correct.") ]
else do
let correctNames2 = map (first (map realName))
let inferred = correctNames2 . fst . fst . runWriter $ genSpecifications ivmap lhsN [s]
let sp = replicate 8 ' '
tell [ (span,
"Not well specified.\n"
++ sp ++ "Specification is:\n"
++ sp ++ sp ++ pprintSpecDecls specDecls ++ "\n"
++ sp ++ "but at " ++ show span' ++ " the code behaves as\n"
++ sp ++ sp ++ pprintSpecDecls inferred) ]
return b'
Nothing -> return b'
F.BlDo{} -> return b'
_ -> return b'
_ -> return b'
perBlockCheck b@(F.BlDo _ _ _ _ _ _ body _) = do
mapM_ (descendBiM perBlockCheck) body
return b
perBlockCheck b = do
updateRegionEnv . F.getAnnotation $ b
mapM_ (descendBiM perBlockCheck) $ children b
return b