module Camfort.Specification.Units.Synthesis
(runSynthesis)
where
import Data.Maybe
import qualified Data.Set as S
import Data.Generics.Uniplate.Operations
import Control.Monad.State.Strict hiding (gets)
import qualified Language.Fortran.AST as F
import qualified Language.Fortran.Analysis as FA
import qualified Language.Fortran.Util.Position as FU
import Camfort.Analysis.Annotations hiding (Unitless)
import Camfort.Specification.Units.Environment
import Camfort.Specification.Units.Monad
import Camfort.Specification.Units.InferenceFrontend (puName, puSrcName)
runSynthesis :: Char -> [(VV, UnitInfo)] -> UnitSolver [(VV, UnitInfo)]
runSynthesis marker vars = do
modifyProgramFileM $ descendBiM (synthProgramUnits marker vars) <=< descendBiM (synthBlocks marker vars)
return vars
synthBlocks :: Char -> [(VV, UnitInfo)] -> [F.Block UA] -> UnitSolver [F.Block UA]
synthBlocks marker vars = fmap reverse . foldM (synthBlock marker vars) []
synthBlock :: Char -> [(VV, UnitInfo)] -> [F.Block UA] -> F.Block UA -> UnitSolver [F.Block UA]
synthBlock marker vars bs b@(F.BlStatement a (FU.SrcSpan lp _) _ (F.StDeclaration _ _ _ _ decls)) = do
pf <- usProgramFile `fmap` get
gvSet <- usGivenVarSet `fmap` get
newBs <- fmap catMaybes . forM (universeBi decls) $ \ e -> case e of
e@(F.ExpValue _ _ (F.ValVariable _))
| vname `S.notMember` gvSet
, Just u <- lookup (vname, sname) vars -> do
let newA = a { FA.prevAnnotation = (FA.prevAnnotation a) {
prevAnnotation = (prevAnnotation (FA.prevAnnotation a)) {
refactored = Just lp } } }
newSS = FU.SrcSpan (lp {FU.posColumn = 0}) (lp {FU.posColumn = 0})
txt = marker:" " ++ showUnitDecl (FA.srcName e, u)
space = FU.posColumn lp 1
(F.ProgramFile mi _) = pf
newB = F.BlComment newA newSS . F.Comment $ buildCommentText mi space txt
return $ Just newB
where
vname = FA.varName e
sname = FA.srcName e
(_ :: F.Expression UA) -> return Nothing
return (b:reverse newBs ++ bs)
synthBlock _ _ bs b = return (b:bs)
synthProgramUnits :: Char -> [(VV, UnitInfo)] -> [F.ProgramUnit UA] -> UnitSolver [F.ProgramUnit UA]
synthProgramUnits marker vars pus = do
fmap reverse . foldM (synthProgramUnit marker vars) [] $ pus
synthProgramUnit :: Char -> [(VV, UnitInfo)] -> [F.ProgramUnit UA] -> F.ProgramUnit UA -> UnitSolver [F.ProgramUnit UA]
synthProgramUnit marker vars pus pu@(F.PUFunction a (FU.SrcSpan lp _) _ _ _ _ mret _ _) = do
pf <- usProgramFile `fmap` get
gvSet <- usGivenVarSet `fmap` get
let (vname, sname) = case mret of Just e -> (FA.varName e, FA.srcName e)
Nothing -> (puName pu, puSrcName pu)
case lookup (vname, sname) vars of
Just u | vname `S.notMember` gvSet -> do
let newA = a { FA.prevAnnotation = (FA.prevAnnotation a) {
prevAnnotation = (prevAnnotation (FA.prevAnnotation a)) {
refactored = Just lp } } }
let newSS = FU.SrcSpan (lp {FU.posColumn = 0}) (lp {FU.posColumn = 0})
txt = marker:" " ++ showUnitDecl (sname, u)
space = FU.posColumn lp 1
(F.ProgramFile mi _) = pf
newPU = F.PUComment newA newSS . F.Comment $ buildCommentText mi space txt
fmap (:newPU:pus) $ descendBiM (synthProgramUnits marker vars) pu
_ -> fmap (:pus) $ descendBiM (synthProgramUnits marker vars) pu
synthProgramUnit marker vars pus pu = fmap (:pus) $ descendBiM (synthProgramUnits marker vars) pu
showUnitDecl (sname, u) = "unit(" ++ show u ++ ") :: " ++ sname