Skip to content

Commit

Permalink
Define alias macros
Browse files Browse the repository at this point in the history
  • Loading branch information
toku-sa-n committed Apr 15, 2023
1 parent c929528 commit 7752091
Show file tree
Hide file tree
Showing 12 changed files with 127 additions and 120 deletions.
4 changes: 2 additions & 2 deletions src/HIndent.hs
Original file line number Diff line number Diff line change
Expand Up @@ -124,7 +124,7 @@ reformat config mexts mfilepath =
(f x)
| otherwise = f x
-- | Generate an AST from the given module for debugging.
#if MIN_VERSION_ghc_lib_parser(9,6,1)
#if GLP961
testAst :: ByteString -> Either String (HsModule GhcPs)
#else
testAst :: ByteString -> Either String HsModule
Expand All @@ -145,7 +145,7 @@ testAst x =
hasTrailingLine :: ByteString -> Bool
hasTrailingLine xs = not (S8.null xs) && S8.last xs == '\n'
-- | Print the module.
#if MIN_VERSION_ghc_lib_parser(9,6,1)
#if GLP961
prettyPrint :: Config -> (HsModule GhcPs) -> Builder
#else
prettyPrint :: Config -> HsModule -> Builder
Expand Down
26 changes: 13 additions & 13 deletions src/HIndent/ModulePreprocessing.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ import Type.Reflection
--
-- Pretty-printing a module without calling this function for it before may
-- raise an error or not print it correctly.
#if MIN_VERSION_ghc_lib_parser(9,6,1)
#if GLP961
modifyASTForPrettyPrinting :: (HsModule GhcPs) -> (HsModule GhcPs)
#else
modifyASTForPrettyPrinting :: HsModule -> HsModule
Expand All @@ -46,7 +46,7 @@ modifyASTForPrettyPrinting m = relocateComments (beforeRelocation m) allComments
isEofComment _ = False
-- | This function modifies the given module AST to apply fixities of infix
-- operators defined in the 'base' package.
#if MIN_VERSION_ghc_lib_parser(9,6,1)
#if GLP961
fixFixities :: (HsModule GhcPs) -> (HsModule GhcPs)
#else
fixFixities :: HsModule -> HsModule
Expand All @@ -59,7 +59,7 @@ fixFixities = applyFixities baseFixities
-- locates comments in the wrong position in the process of comment
-- relocation. This function prevents it by fixing the 'L?GRHS''s source
-- span.
#if MIN_VERSION_ghc_lib_parser(9,6,1)
#if GLP961
resetLGRHSEndPositionInModule :: (HsModule GhcPs) -> (HsModule GhcPs)
#else
resetLGRHSEndPositionInModule :: HsModule -> HsModule
Expand All @@ -70,7 +70,7 @@ resetLGRHSEndPositionInModule = everywhere (mkT resetLGRHSEndPosition)
-- For example, the last element of 'HsDo' of 'HsExpr' is the element
-- before a bar, and the elements are not sorted by their locations. This
-- function fixes the orderings.
#if MIN_VERSION_ghc_lib_parser(9,6,1)
#if GLP961
sortExprLStmt :: (HsModule GhcPs) -> (HsModule GhcPs)
#else
sortExprLStmt :: HsModule -> HsModule
Expand All @@ -82,15 +82,15 @@ sortExprLStmt m@HsModule {hsmodDecls = xs} = m {hsmodDecls = sorted}
sortByLoc = sortBy (compare `on` srcSpanToRealSrcSpan . locA . getLoc)
-- | This function removes all comments from the given module not to
-- duplicate them on comment relocation.
#if MIN_VERSION_ghc_lib_parser(9,6,1)
#if GLP961
removeComments :: (HsModule GhcPs) -> (HsModule GhcPs)
#else
removeComments :: HsModule -> HsModule
#endif
removeComments = everywhere (mkT $ const emptyComments)
-- | This function replaces all 'EpAnnNotUsed's in 'SrcSpanAnn''s with
-- 'EpAnn's to make it possible to locate comments on them.
#if MIN_VERSION_ghc_lib_parser(9,6,1)
#if GLP961
replaceAllNotUsedAnns :: (HsModule GhcPs) -> (HsModule GhcPs)
#else
replaceAllNotUsedAnns :: HsModule -> HsModule
Expand Down Expand Up @@ -123,7 +123,7 @@ replaceAllNotUsedAnns = everywhere app
emptyEpaLocation = EpaDelta (SameLine 0) []
-- | This function sets the start column of 'hsmodName' of the given
-- 'HsModule' to 1 to correctly locate comments above the module name.
#if MIN_VERSION_ghc_lib_parser(9,6,1)
#if GLP961
resetModuleNameColumn :: (HsModule GhcPs) -> (HsModule GhcPs)
#else
resetModuleNameColumn :: HsModule -> HsModule
Expand All @@ -144,7 +144,7 @@ resetModuleNameColumn m = m
-- The 'fun_id' contains the function's name. However, 'FunRhs' of 'Match'
-- also contains the name, and we use the latter one. This function
-- prevents comments from being located in 'fun_id'.
#if MIN_VERSION_ghc_lib_parser(9,6,1)
#if GLP961
closeEpAnnOfFunBindFunId :: (HsModule GhcPs) -> (HsModule GhcPs)
#else
closeEpAnnOfFunBindFunId :: HsModule -> HsModule
Expand All @@ -161,7 +161,7 @@ closeEpAnnOfFunBindFunId = everywhere (mkT closeEpAnn)
-- The field contains the annotation of the match LHS. However, the same
-- information is also stored inside the 'Match'. This function removes the
-- duplication not to locate comments on a wrong point.
#if MIN_VERSION_ghc_lib_parser(9,6,1)
#if GLP961
closeEpAnnOfMatchMExt :: (HsModule GhcPs) -> (HsModule GhcPs)
#else
closeEpAnnOfMatchMExt :: HsModule -> HsModule
Expand All @@ -182,7 +182,7 @@ closeEpAnnOfMatchMExt = everywhere closeEpAnn
--
-- 'HsFunTy' should not have any comments. Instead, its LHS and RHS should
-- have them.
#if MIN_VERSION_ghc_lib_parser(9,6,1)
#if GLP961
closeEpAnnOfHsFunTy :: (HsModule GhcPs) -> (HsModule GhcPs)
#else
closeEpAnnOfHsFunTy :: HsModule -> HsModule
Expand All @@ -195,7 +195,7 @@ closeEpAnnOfHsFunTy = everywhere (mkT closeEpAnn)
-- | This function replaces all 'EpAnn's that contain placeholder anchors
-- to locate comments correctly. A placeholder anchor is an anchor pointing
-- on (-1, -1).
#if MIN_VERSION_ghc_lib_parser(9,6,1)
#if GLP961
closePlaceHolderEpAnns :: (HsModule GhcPs) -> (HsModule GhcPs)
#else
closePlaceHolderEpAnns :: HsModule -> HsModule
Expand All @@ -215,7 +215,7 @@ closePlaceHolderEpAnns = everywhere closeEpAnn
-- | This function removes all 'DocD's from the given module. They have
-- haddocks, but the same information is stored in 'EpaCommentTok's. Thus,
-- we need to remove the duplication.
#if MIN_VERSION_ghc_lib_parser(9,6,1)
#if GLP961
removeAllDocDs :: (HsModule GhcPs) -> (HsModule GhcPs)
#else
removeAllDocDs :: HsModule -> HsModule
Expand All @@ -232,7 +232,7 @@ removeAllDocDs x@HsModule {hsmodDecls = decls} =
-- See the documentation of 'resetLGRHSEndPositionInModule' for the reason.
resetLGRHSEndPosition ::
LGRHS GhcPs (LHsExpr GhcPs) -> LGRHS GhcPs (LHsExpr GhcPs)
#if MIN_VERSION_ghc_lib_parser(9,4,1)
#if GLP941
resetLGRHSEndPosition (L (SrcSpanAnn locAnn@EpAnn {} sp) (GRHS ext@EpAnn {..} stmt body)) =
let lastPosition =
maximum $ realSrcSpanEnd . anchor <$> listify collectAnchor body
Expand Down
16 changes: 8 additions & 8 deletions src/HIndent/ModulePreprocessing/CommentRelocation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -63,7 +63,7 @@ data Wrapper =
type WithComments = State [LEpaComment]
-- | This function collects all comments from the passed 'HsModule', and
-- modifies all 'EpAnn's so that all 'EpAnn's have 'EpaCommentsBalanced's.
#if MIN_VERSION_ghc_lib_parser(9,6,1)
#if GLP961
relocateComments :: HsModule GhcPs -> [LEpaComment] -> HsModule GhcPs
#else
relocateComments :: HsModule -> [LEpaComment] -> HsModule
Expand All @@ -82,7 +82,7 @@ relocateComments = evalState . relocate
cs <- get
assert (null cs) (pure x)
-- | This function locates pragmas to the module's EPA.
#if MIN_VERSION_ghc_lib_parser(9,6,1)
#if GLP961
relocatePragmas :: HsModule GhcPs -> WithComments (HsModule GhcPs)
relocatePragmas m@HsModule {hsmodExt = xmod@XModulePs {hsmodAnn = epa@EpAnn {}}} = do
newAnn <- insertComments (isPragma . ac_tok . unLoc) insertPriorComments epa
Expand All @@ -96,7 +96,7 @@ relocatePragmas m@HsModule {hsmodAnn = epa@EpAnn {}} = do
relocatePragmas m = pure m
-- | This function locates comments that are located before pragmas to the
-- module's EPA.
#if MIN_VERSION_ghc_lib_parser(9,6,1)
#if GLP961
relocateCommentsBeforePragmas :: HsModule GhcPs -> WithComments (HsModule GhcPs)
relocateCommentsBeforePragmas m@HsModule {hsmodExt = xmod@XModulePs {hsmodAnn = ann}}
| pragmaExists m = do
Expand All @@ -118,7 +118,7 @@ relocateCommentsBeforePragmas m@HsModule {hsmodAnn = ann}

-- | This function locates comments that are located before each element of
-- an export list.
#if MIN_VERSION_ghc_lib_parser(9,6,1)
#if GLP961
relocateCommentsInExportList :: HsModule GhcPs -> WithComments (HsModule GhcPs)
#else
relocateCommentsInExportList :: HsModule -> WithComments HsModule
Expand All @@ -140,7 +140,7 @@ relocateCommentsInExportList m@HsModule {hsmodExports = Just (L listSp@SrcSpanAn
realSrcSpanStart (anchor listAnn) < realSrcSpanStart comAnc
relocateCommentsInExportList x = pure x
-- | This function locates comments located before top-level declarations.
#if MIN_VERSION_ghc_lib_parser(9,6,1)
#if GLP961
relocateCommentsBeforeTopLevelDecls ::
HsModule GhcPs -> WithComments (HsModule GhcPs)
#else
Expand All @@ -158,7 +158,7 @@ relocateCommentsBeforeTopLevelDecls = everywhereM (applyM f)
-- | This function scans the given AST from bottom to top and locates
-- comments that are on the same line as the node. Comments are stored in
-- the 'followingComments' of 'EpaCommentsBalanced'.
#if MIN_VERSION_ghc_lib_parser(9,6,1)
#if GLP961
relocateCommentsSameLine :: HsModule GhcPs -> WithComments (HsModule GhcPs)
#else
relocateCommentsSameLine :: HsModule -> WithComments HsModule
Expand All @@ -176,7 +176,7 @@ relocateCommentsSameLine = everywhereMEpAnnsBackwards f
srcSpanStartLine comAnc == srcSpanEndLine anc
-- | This function locates comments above the top-level declarations in
-- a 'where' clause in the topmost declaration.
#if MIN_VERSION_ghc_lib_parser(9,6,1)
#if GLP961
relocateCommentsTopLevelWhereClause ::
HsModule GhcPs -> WithComments (HsModule GhcPs)
#else
Expand Down Expand Up @@ -226,7 +226,7 @@ relocateCommentsTopLevelWhereClause m@HsModule {..} = do
srcSpanEndLine comAnc + 1 == srcSpanStartLine anc
-- | This function scans the given AST from bottom to top and locates
-- comments in the comment pool after each node on it.
#if MIN_VERSION_ghc_lib_parser(9,6,1)
#if GLP961
relocateCommentsAfter :: HsModule GhcPs -> WithComments (HsModule GhcPs)
#else
relocateCommentsAfter :: HsModule -> WithComments HsModule
Expand Down
6 changes: 3 additions & 3 deletions src/HIndent/Parse.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,13 +16,13 @@ import qualified GHC.Parser as GLP
import GHC.Parser.Lexer hiding (buffer)
import GHC.Stack
import GHC.Types.SrcLoc
#if MIN_VERSION_ghc_lib_parser(9,4,1)
#if GLP941
import GHC.Utils.Error
import GHC.Utils.Outputable hiding ((<>), empty, text)
#endif
-- | This function parses the given Haskell source code with the given file
-- path (if any) and parse options.
#if MIN_VERSION_ghc_lib_parser(9,6,1)
#if GLP961
parseModule ::
Maybe FilePath -> [GLP.Extension] -> String -> ParseResult (HsModule GhcPs)
#else
Expand Down Expand Up @@ -54,7 +54,7 @@ lexCode code
-- The 'StarIsType' extension is always enabled to compile a code using
-- kinds like '* -> *'.
parserOptsFromExtensions :: [GLP.Extension] -> ParserOpts
#if MIN_VERSION_ghc_lib_parser(9,4,1)
#if GLP941
parserOptsFromExtensions opts =
mkParserOpts
opts'
Expand Down
Loading

0 comments on commit 7752091

Please sign in to comment.