module Data.Generics.Strafunski.StrategyLib.RefactoringTheme where
import Data.Generics.Strafunski.StrategyLib.StrategyPrelude
import Control.Monad.Identity hiding (fail)
import Data.Generics.Strafunski.StrategyLib.KeyholeTheme
import Data.Generics.Strafunski.StrategyLib.NameTheme
class (
Term abstr,
Eq name,
Term [abstr],
Term apply
)
=> Abstraction abstr name tpe apply
| abstr -> name,
abstr -> tpe,
abstr -> apply,
apply -> name,
apply -> abstr
where
getAbstrName :: abstr -> Maybe name
getAbstrParas :: abstr -> Maybe [(name,tpe)]
getAbstrBody :: abstr -> Maybe apply
getApplyName :: apply -> Maybe name
getApplyParas :: apply -> Maybe [(name,tpe)]
constrAbstr :: name -> [(name,tpe)] -> apply -> Maybe abstr
constrApply :: name -> [(name,tpe)] -> Maybe apply
eliminate :: (Term prog, Abstraction abstr name tpe apply)
=> TU [(name,tpe)] Identity
-> TU [name] Identity
-> (abstr -> Maybe abstr)
-> prog
-> Maybe prog
eliminate declared referenced unwrap prog
= do { abstr <- selectFocus unwrap prog;
name <- getAbstrName abstr;
() <- unusedAbstr name;
deleteFocus unwrap prog
}
where
unusedAbstr name = maybe (notIsFree prog) notIsFree selectScope
where
argtype :: Monad m => (x -> y) -> x -> m x
argtype _ = return
selectScope = selectHost unwrap (argtype unwrap) prog
notIsFree scope
= do
scope' <- deleteFocus unwrap scope
names <- return (freeNames declared referenced scope')
guard (not (elem name names))
introduce :: (Term prog, Abstraction abstr name tpe apply)
=> TU [(name,tpe)] Identity
-> TU [name] Identity
-> ([abstr] -> Maybe [abstr])
-> abstr
-> prog
-> Maybe prog
introduce declared referenced unwrap abstr =
replaceFocus (\abstrlist ->
do
abstrlist' <- unwrap abstrlist
name <- getAbstrName abstr
free <- return $ freeNames declared referenced abstrlist'
def <- mapM getAbstrName abstrlist'
guard (and [not (elem name free), not (elem name def)])
return (abstr:abstrlist') )
extract :: (Term prog, Abstraction abstr name tpe apply)
=> TU [(name,tpe)] Identity
-> TU [name] Identity
-> (apply -> Maybe apply)
-> ([abstr] -> [abstr])
-> ([abstr] -> Maybe [abstr])
-> ([(name,tpe)] -> apply -> Bool)
-> name
-> prog
-> Maybe prog
extract declared referenced unwrap wrap unwrap' check name prog
= do
(bound,focus) <- boundTypedNames declared unwrap prog
free <- return $ freeTypedNames declared referenced bound focus
guard (check bound focus)
abstr <- constrAbstr name free focus
prog' <- markHost (maybe False (const True) . unwrap) wrap prog
prog'' <- introduce declared referenced unwrap' abstr prog'
apply <- constrApply name free
replaceFocus (maybe Nothing (const (Just apply)) . unwrap) prog''