summaryrefslogtreecommitdiff
path: root/utils/check-exact
diff options
context:
space:
mode:
Diffstat (limited to 'utils/check-exact')
-rw-r--r--utils/check-exact/ExactPrint.hs4
-rw-r--r--utils/check-exact/Transform.hs56
-rw-r--r--utils/check-exact/Types.hs2
-rw-r--r--utils/check-exact/Utils.hs24
4 files changed, 43 insertions, 43 deletions
diff --git a/utils/check-exact/ExactPrint.hs b/utils/check-exact/ExactPrint.hs
index 30f71bdbc8..f65deb456b 100644
--- a/utils/check-exact/ExactPrint.hs
+++ b/utils/check-exact/ExactPrint.hs
@@ -275,7 +275,7 @@ enterAnn (Entry anchor' cs) a = do
-- ---------------------------------------------------------------------
-addCommentsA :: [LAnnotationComment] -> EPP ()
+addCommentsA :: [LEpaComment] -> EPP ()
addCommentsA csNew = addComments (map tokComment csNew)
-- cs <- getUnallocatedComments
-- -- AZ:TODO: sortedlist?
@@ -412,7 +412,7 @@ data AnnotatedList a = AnnotatedList (Maybe Anchor) a
deriving (Eq,Show)
instance (ExactPrint a) => ExactPrint (AnnotatedList a) where
- getAnnotationEntry (AnnotatedList (Just anc) _) = Entry anc (AnnComments [])
+ getAnnotationEntry (AnnotatedList (Just anc) _) = Entry anc (EpaComments [])
getAnnotationEntry (AnnotatedList Nothing _) = NoEntryVal
exact (AnnotatedList an ls) = do
diff --git a/utils/check-exact/Transform.hs b/utils/check-exact/Transform.hs
index fc675e6c77..ec89a5e4be 100644
--- a/utils/check-exact/Transform.hs
+++ b/utils/check-exact/Transform.hs
@@ -470,9 +470,9 @@ setEntryDP' (L (SrcSpanAnn EpAnnNotUsed l) a) dp
= L (SrcSpanAnn
(EpAnn (Anchor (realSrcSpan l) (MovedAnchor dp)) mempty noCom)
l) a
-setEntryDP' (L (SrcSpanAnn (EpAnn (Anchor r _) an (AnnComments [])) l) a) dp
+setEntryDP' (L (SrcSpanAnn (EpAnn (Anchor r _) an (EpaComments [])) l) a) dp
= L (SrcSpanAnn
- (EpAnn (Anchor r (MovedAnchor dp)) an (AnnComments []))
+ (EpAnn (Anchor r (MovedAnchor dp)) an (EpaComments []))
l) a
setEntryDP' (L (SrcSpanAnn (EpAnn (Anchor r _) an cs) l) a) dp
= case sort (priorComments cs) of
@@ -671,22 +671,22 @@ balanceCommentsMatch (L l (Match am mctxt pats (GRHSs xg grhss binds))) = do
stay = map snd stay'
(l'', grhss', binds', logInfo)
= case reverse grhss of
- [] -> (l, [], binds, (AnnComments [], SrcSpanAnn EpAnnNotUsed noSrcSpan))
- (L lg g@(GRHS EpAnnNotUsed _grs _rhs):gs) -> (l, reverse (L lg g:gs), binds, (AnnComments [], SrcSpanAnn EpAnnNotUsed noSrcSpan))
+ [] -> (l, [], binds, (EpaComments [], SrcSpanAnn EpAnnNotUsed noSrcSpan))
+ (L lg g@(GRHS EpAnnNotUsed _grs _rhs):gs) -> (l, reverse (L lg g:gs), binds, (EpaComments [], SrcSpanAnn EpAnnNotUsed noSrcSpan))
(L lg (GRHS ag grs rhs):gs) ->
let
anc1' = setFollowingComments anc1 stay
an1' = setCommentsSrcAnn l anc1'
-- ---------------------------------
- (moved,bindsm) = pushTrailingComments WithWhere (AnnCommentsBalanced [] move) binds
+ (moved,bindsm) = pushTrailingComments WithWhere (EpaCommentsBalanced [] move) binds
-- ---------------------------------
(EpAnn anc an lgc) = ag
lgc' = splitComments (realSrcSpan lg) $ addCommentOrigDeltas lgc
ag' = if moved
then EpAnn anc an lgc'
- else EpAnn anc an (lgc' <> (AnnCommentsBalanced [] move))
+ else EpAnn anc an (lgc' <> (EpaCommentsBalanced [] move))
-- ag' = EpAnn anc an lgc'
in (an1', (reverse $ (L lg (GRHS ag' grs rhs):gs)), bindsm, (anc1',an1'))
@@ -753,8 +753,8 @@ balanceComments' la1 la2 = do
la2' = L an2' s
-- | Like commentsDeltas, but calculates the delta from the end of the anchor, not the start
-trailingCommentsDeltas :: RealSrcSpan -> [LAnnotationComment]
- -> [(Int, LAnnotationComment)]
+trailingCommentsDeltas :: RealSrcSpan -> [LEpaComment]
+ -> [(Int, LEpaComment)]
trailingCommentsDeltas _ [] = []
trailingCommentsDeltas anc (la@(L l _):las)
= deltaComment anc la : trailingCommentsDeltas (anchor l) las
@@ -765,15 +765,15 @@ trailingCommentsDeltas anc (la@(L l _):las)
(ll,_) = ss2pos (anchor loc)
-- AZ:TODO: this is identical to commentsDeltas
-priorCommentsDeltas :: RealSrcSpan -> [LAnnotationComment]
- -> [(Int, LAnnotationComment)]
+priorCommentsDeltas :: RealSrcSpan -> [LEpaComment]
+ -> [(Int, LEpaComment)]
priorCommentsDeltas anc cs = go anc (reverse $ sort cs)
where
- go :: RealSrcSpan -> [LAnnotationComment] -> [(Int, LAnnotationComment)]
+ go :: RealSrcSpan -> [LEpaComment] -> [(Int, LEpaComment)]
go _ [] = []
go anc' (la@(L l _):las) = deltaComment anc' la : go (anchor l) las
- deltaComment :: RealSrcSpan -> LAnnotationComment -> (Int, LAnnotationComment)
+ deltaComment :: RealSrcSpan -> LEpaComment -> (Int, LEpaComment)
deltaComment anc' (L loc c) = (abs(ll - al), L loc c)
where
(al,_) = ss2pos anc'
@@ -783,14 +783,14 @@ priorCommentsDeltas anc cs = go anc (reverse $ sort cs)
-- | Split comments into ones occuring before the end of the reference
-- span, and those after it.
splitComments :: RealSrcSpan -> EpAnnComments -> EpAnnComments
-splitComments p (AnnComments cs) = cs'
+splitComments p (EpaComments cs) = cs'
where
cmp (L (Anchor l _) _) = ss2pos l < ss2posEnd p
(before, after) = break cmp cs
cs' = case after of
- [] -> AnnComments cs
- _ -> AnnCommentsBalanced before after
-splitComments p (AnnCommentsBalanced cs ts) = AnnCommentsBalanced cs' ts'
+ [] -> EpaComments cs
+ _ -> EpaCommentsBalanced before after
+splitComments p (EpaCommentsBalanced cs ts) = EpaCommentsBalanced cs' ts'
where
cmp (L (Anchor l _) _) = ss2pos l < ss2posEnd p
(before, after) = break cmp cs
@@ -801,30 +801,30 @@ splitComments p (AnnCommentsBalanced cs ts) = AnnCommentsBalanced cs' ts'
-- token. Takes an original list of comments, and converts the
-- 'Anchor's to have a have a `MovedAnchor` operation based on the
-- original locations.
-commentOrigDeltas :: [LAnnotationComment] -> [LAnnotationComment]
+commentOrigDeltas :: [LEpaComment] -> [LEpaComment]
commentOrigDeltas [] = []
-commentOrigDeltas lcs@(L _ (GHC.AnnComment _ pt):_) = go pt lcs
+commentOrigDeltas lcs@(L _ (GHC.EpaComment _ pt):_) = go pt lcs
-- TODO:AZ: we now have deltas wrt *all* tokens, not just preceding
-- non-comment. Simplify this.
where
- go :: RealSrcSpan -> [LAnnotationComment] -> [LAnnotationComment]
+ go :: RealSrcSpan -> [LEpaComment] -> [LEpaComment]
go _ [] = []
- go p (L (Anchor la _) (GHC.AnnComment t pp):ls)
- = L (Anchor la op) (GHC.AnnComment t pp) : go p' ls
+ go p (L (Anchor la _) (GHC.EpaComment t pp):ls)
+ = L (Anchor la op) (GHC.EpaComment t pp) : go p' ls
where
p' = p
(r,c) = ss2posEnd pp
op' = if r == 0
then MovedAnchor (ss2delta (r,c+1) la)
else MovedAnchor (ss2delta (r,c) la)
- op = if t == AnnEofComment && op' == MovedAnchor (DP 0 0)
+ op = if t == EpaEofComment && op' == MovedAnchor (DP 0 0)
then MovedAnchor (DP 1 0)
else op'
addCommentOrigDeltas :: EpAnnComments -> EpAnnComments
-addCommentOrigDeltas (AnnComments cs) = AnnComments (commentOrigDeltas cs)
-addCommentOrigDeltas (AnnCommentsBalanced pcs fcs)
- = AnnCommentsBalanced (commentOrigDeltas pcs) (commentOrigDeltas fcs)
+addCommentOrigDeltas (EpaComments cs) = EpaComments (commentOrigDeltas cs)
+addCommentOrigDeltas (EpaCommentsBalanced pcs fcs)
+ = EpaCommentsBalanced (commentOrigDeltas pcs) (commentOrigDeltas fcs)
addCommentOrigDeltasAnn :: (EpAnn' a) -> (EpAnn' a)
addCommentOrigDeltasAnn EpAnnNotUsed = EpAnnNotUsed
@@ -857,12 +857,12 @@ balanceSameLineComments (L la (Match anm mctxt pats (GRHSs x grhss lb))) = do
anc1 = addCommentOrigDeltas $ epAnnComments an1
(EpAnn anc an _) = ga :: EpAnn' GrhsAnn
(csp,csf) = case anc1 of
- AnnComments cs -> ([],cs)
- AnnCommentsBalanced p f -> (p,f)
+ EpaComments cs -> ([],cs)
+ EpaCommentsBalanced p f -> (p,f)
(move',stay') = break (simpleBreak 0) (trailingCommentsDeltas (anchor anc) csf)
move = map snd move'
stay = map snd stay'
- cs1 = AnnCommentsBalanced csp stay
+ cs1 = EpaCommentsBalanced csp stay
gac = addCommentOrigDeltas $ epAnnComments ga
gfc = getFollowingComments gac
diff --git a/utils/check-exact/Types.hs b/utils/check-exact/Types.hs
index 6bae34631a..6717e45698 100644
--- a/utils/check-exact/Types.hs
+++ b/utils/check-exact/Types.hs
@@ -11,7 +11,7 @@
module Types
where
-import GHC hiding (AnnComment)
+import GHC hiding (EpaComment)
import GHC.Utils.Outputable hiding ( (<>) )
import GHC.Driver.Ppr
import Data.Data (Data, toConstr,cast)
diff --git a/utils/check-exact/Utils.hs b/utils/check-exact/Utils.hs
index 9d17106657..63eb17c55d 100644
--- a/utils/check-exact/Utils.hs
+++ b/utils/check-exact/Utils.hs
@@ -24,7 +24,7 @@ import Data.Ord (comparing)
import GHC.Hs.Dump
import Lookup
-import GHC hiding (AnnComment)
+import GHC hiding (EpaComment)
import qualified GHC
import GHC.Types.Name
import GHC.Types.Name.Reader
@@ -260,17 +260,17 @@ isExactName = False `mkQ` isExact
-- ---------------------------------------------------------------------
-ghcCommentText :: LAnnotationComment -> String
-ghcCommentText (L _ (GHC.AnnComment (AnnDocCommentNext s) _)) = s
-ghcCommentText (L _ (GHC.AnnComment (AnnDocCommentPrev s) _)) = s
-ghcCommentText (L _ (GHC.AnnComment (AnnDocCommentNamed s) _)) = s
-ghcCommentText (L _ (GHC.AnnComment (AnnDocSection _ s) _)) = s
-ghcCommentText (L _ (GHC.AnnComment (AnnDocOptions s) _)) = s
-ghcCommentText (L _ (GHC.AnnComment (AnnLineComment s) _)) = s
-ghcCommentText (L _ (GHC.AnnComment (AnnBlockComment s) _)) = s
-ghcCommentText (L _ (GHC.AnnComment (AnnEofComment) _)) = ""
-
-tokComment :: LAnnotationComment -> Comment
+ghcCommentText :: LEpaComment -> String
+ghcCommentText (L _ (GHC.EpaComment (EpaDocCommentNext s) _)) = s
+ghcCommentText (L _ (GHC.EpaComment (EpaDocCommentPrev s) _)) = s
+ghcCommentText (L _ (GHC.EpaComment (EpaDocCommentNamed s) _)) = s
+ghcCommentText (L _ (GHC.EpaComment (EpaDocSection _ s) _)) = s
+ghcCommentText (L _ (GHC.EpaComment (EpaDocOptions s) _)) = s
+ghcCommentText (L _ (GHC.EpaComment (EpaLineComment s) _)) = s
+ghcCommentText (L _ (GHC.EpaComment (EpaBlockComment s) _)) = s
+ghcCommentText (L _ (GHC.EpaComment (EpaEofComment) _)) = ""
+
+tokComment :: LEpaComment -> Comment
tokComment t@(L lt _) = mkComment (normaliseCommentText $ ghcCommentText t) lt
mkComment :: String -> Anchor -> Comment