module Camfort.Specification.Units (synthesiseUnits) where
import Camfort.Analysis.Annotations
import Camfort.Specification.Units.Analysis
(UnitAnalysis, runInference)
import Camfort.Specification.Units.Analysis.Consistent
(ConsistencyError)
import Camfort.Specification.Units.Analysis.Infer
(InferenceReport, InferenceResult(..), getInferred, inferUnits)
import qualified Camfort.Specification.Units.Annotation as UA
import Camfort.Specification.Units.InferenceBackend (chooseImplicitNames)
import Camfort.Specification.Units.Monad
import Camfort.Specification.Units.Synthesis (runSynthesis)
import qualified Language.Fortran.AST as F
import qualified Language.Fortran.Analysis as FA
synthesiseUnits
:: Char -> UnitAnalysis (Either ConsistencyError (InferenceReport, F.ProgramFile Annotation))
synthesiseUnits :: Char
-> UnitAnalysis
(Either ConsistencyError (InferenceReport, ProgramFile Annotation))
synthesiseUnits Char
marker = do
InferenceResult
infRes <- UnitAnalysis InferenceResult
inferUnits
case InferenceResult
infRes of
InfInconsistent ConsistencyError
err -> Either ConsistencyError (InferenceReport, ProgramFile Annotation)
-> UnitAnalysis
(Either ConsistencyError (InferenceReport, ProgramFile Annotation))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either ConsistencyError (InferenceReport, ProgramFile Annotation)
-> UnitAnalysis
(Either
ConsistencyError (InferenceReport, ProgramFile Annotation)))
-> Either
ConsistencyError (InferenceReport, ProgramFile Annotation)
-> UnitAnalysis
(Either ConsistencyError (InferenceReport, ProgramFile Annotation))
forall a b. (a -> b) -> a -> b
$ ConsistencyError
-> Either
ConsistencyError (InferenceReport, ProgramFile Annotation)
forall a b. a -> Either a b
Left ConsistencyError
err
Inferred InferenceReport
report -> do
([(VV, UnitInfo)]
_, UnitState
state) <- UnitSolver [(VV, UnitInfo)]
-> UnitAnalysis ([(VV, UnitInfo)], UnitState)
forall a. UnitSolver a -> UnitAnalysis (a, UnitState)
runInference
(Char -> [(VV, UnitInfo)] -> UnitSolver [(VV, UnitInfo)]
runSynthesis Char
marker ([(VV, UnitInfo)] -> UnitSolver [(VV, UnitInfo)])
-> (InferenceReport -> [(VV, UnitInfo)])
-> InferenceReport
-> UnitSolver [(VV, UnitInfo)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(VV, UnitInfo)] -> [(VV, UnitInfo)]
chooseImplicitNames ([(VV, UnitInfo)] -> [(VV, UnitInfo)])
-> (InferenceReport -> [(VV, UnitInfo)])
-> InferenceReport
-> [(VV, UnitInfo)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InferenceReport -> [(VV, UnitInfo)]
getInferred (InferenceReport -> UnitSolver [(VV, UnitInfo)])
-> InferenceReport -> UnitSolver [(VV, UnitInfo)]
forall a b. (a -> b) -> a -> b
$ InferenceReport
report)
let pfUA :: ProgramFile UA
pfUA = UnitState -> ProgramFile UA
usProgramFile UnitState
state
pfFinal :: ProgramFile Annotation
pfFinal = (UA -> Annotation) -> ProgramFile UA -> ProgramFile Annotation
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (UnitAnnotation Annotation -> Annotation
forall a. UnitAnnotation a -> a
UA.prevAnnotation (UnitAnnotation Annotation -> Annotation)
-> (UA -> UnitAnnotation Annotation) -> UA -> Annotation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UA -> UnitAnnotation Annotation
forall a. Analysis a -> a
FA.prevAnnotation) ProgramFile UA
pfUA
Either ConsistencyError (InferenceReport, ProgramFile Annotation)
-> UnitAnalysis
(Either ConsistencyError (InferenceReport, ProgramFile Annotation))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either ConsistencyError (InferenceReport, ProgramFile Annotation)
-> UnitAnalysis
(Either
ConsistencyError (InferenceReport, ProgramFile Annotation)))
-> ((InferenceReport, ProgramFile Annotation)
-> Either
ConsistencyError (InferenceReport, ProgramFile Annotation))
-> (InferenceReport, ProgramFile Annotation)
-> UnitAnalysis
(Either ConsistencyError (InferenceReport, ProgramFile Annotation))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (InferenceReport, ProgramFile Annotation)
-> Either
ConsistencyError (InferenceReport, ProgramFile Annotation)
forall a b. b -> Either a b
Right ((InferenceReport, ProgramFile Annotation)
-> UnitAnalysis
(Either
ConsistencyError (InferenceReport, ProgramFile Annotation)))
-> (InferenceReport, ProgramFile Annotation)
-> UnitAnalysis
(Either ConsistencyError (InferenceReport, ProgramFile Annotation))
forall a b. (a -> b) -> a -> b
$ (InferenceReport
report, ProgramFile Annotation
pfFinal)