module Language.Haskell.Refact.Utils.ExactPrint
(
replace
, replaceAnnKey
, copyAnn
, setAnnKeywordDP
, clearPriorComments
, balanceAllComments
) where
import qualified GHC as GHC
import qualified Data.Generics as SYB
import Control.Monad
import Language.Haskell.GHC.ExactPrint.Transform
import Language.Haskell.GHC.ExactPrint.Types
import Language.Haskell.Refact.Utils.GhcUtils
import qualified Data.Map as Map
replaceAnnKey :: (SYB.Data old,SYB.Data new)
=> GHC.Located old -> GHC.Located new -> Anns -> Anns
replaceAnnKey old new ans =
case Map.lookup (mkAnnKey old) ans of
Nothing -> ans
Just v -> anns'
where
anns1 = Map.delete (mkAnnKey old) ans
anns' = Map.insert (mkAnnKey new) v anns1
copyAnn :: (SYB.Data old,SYB.Data new)
=> GHC.Located old -> GHC.Located new -> Anns -> Anns
copyAnn old new ans =
case Map.lookup (mkAnnKey old) ans of
Nothing -> ans
Just v -> Map.insert (mkAnnKey new) v ans
replace :: AnnKey -> AnnKey -> Anns -> Maybe Anns
replace old new ans = do
let as = ans
oldan <- Map.lookup old as
newan <- Map.lookup new as
let newan' = Ann
{ annEntryDelta = annEntryDelta oldan
, annPriorComments = annPriorComments oldan
, annFollowingComments = annFollowingComments oldan
, annsDP = moveAnns (annsDP oldan) (annsDP newan)
, annSortKey = annSortKey oldan
, annCapturedSpan = annCapturedSpan oldan
}
return ((\anns -> Map.delete old . Map.insert new newan' $ anns) ans)
moveAnns :: [(KeywordId, DeltaPos)] -> [(KeywordId, DeltaPos)] -> [(KeywordId, DeltaPos)]
moveAnns [] xs = xs
moveAnns ((_, dp): _) ((kw, _):xs) = (kw,dp) : xs
moveAnns _ [] = []
setAnnKeywordDP :: (SYB.Data a) => GHC.Located a -> KeywordId -> DeltaPos -> Transform ()
setAnnKeywordDP la kw dp = modifyAnnsT changer
where
changer ans = case Map.lookup (mkAnnKey la) ans of
Nothing -> ans
Just an -> Map.insert (mkAnnKey la) (an {annsDP = map update (annsDP an)}) ans
update (kw',dp')
| kw == kw' = (kw',dp)
| otherwise = (kw',dp')
clearPriorComments :: (SYB.Data a) => GHC.Located a -> Transform ()
clearPriorComments la = do
edp <- getEntryDPT la
modifyAnnsT $ \ans ->
case Map.lookup (mkAnnKey la) ans of
Nothing -> ans
Just an -> Map.insert (mkAnnKey la) (an {annPriorComments = [] }) ans
setEntryDPT la edp
balanceAllComments :: SYB.Data a => GHC.Located a -> Transform (GHC.Located a)
balanceAllComments la
= everywhereM' (SYB.mkM inMod
`SYB.extM` inExpr
`SYB.extM` inMatch
`SYB.extM` inStmt
) la
where
inMod :: GHC.ParsedSource -> Transform (GHC.ParsedSource)
inMod m = doBalance m
inExpr :: GHC.LHsExpr GHC.RdrName -> Transform (GHC.LHsExpr GHC.RdrName)
inExpr e = doBalance e
inMatch :: (GHC.LMatch GHC.RdrName (GHC.LHsExpr GHC.RdrName)) -> Transform (GHC.LMatch GHC.RdrName (GHC.LHsExpr GHC.RdrName))
inMatch m = doBalance m
inStmt :: GHC.LStmt GHC.RdrName (GHC.LHsExpr GHC.RdrName) -> Transform (GHC.LStmt GHC.RdrName (GHC.LHsExpr GHC.RdrName))
inStmt s = doBalance s
doBalance t = do
decls <- hsDecls t
let
go [] = return []
go [x] = return [x]
go (x1:x2:xs) = do
balanceComments x1 x2
go (x2:xs)
_ <- go decls
unless (null decls) $ moveTrailingComments t (last decls)
return t