Upgrade/hack Module

mxxun/ghc-9.2
mrkun 2022-01-30 23:39:37 +03:00
parent 1fa45be586
commit 4b4629289a
3 changed files with 21 additions and 18 deletions

View File

@ -624,7 +624,7 @@ docNodeAnnKW ast kw bdm =
docNodeMoveToKWDP docNodeMoveToKWDP
:: Data.Data.Data ast :: Data.Data.Data ast
=> Located ast => LocatedAn an ast
-> AnnKeywordId -> AnnKeywordId
-> Bool -> Bool
-> ToBriDocM BriDocNumbered -> ToBriDocM BriDocNumbered

View File

@ -23,16 +23,16 @@ import Language.Haskell.GHC.ExactPrint.Types
import Language.Haskell.Brittany.Internal.EPCompat (Annotation) import Language.Haskell.Brittany.Internal.EPCompat (Annotation)
layoutModule :: ToBriDoc' HsModule layoutModule :: ToBriDoc' an HsModule
layoutModule lmod@(L _ mod') = case mod' of layoutModule lmod@(L _ mod') = case mod' of
-- Implicit module Main -- Implicit module Main
HsModule _ Nothing _ imports _ _ _ -> do HsModule _ _ Nothing _ imports _ _ _ -> do
commentedImports <- transformToCommentedImport imports commentedImports <- transformToCommentedImport imports
-- groupify commentedImports `forM_` tellDebugMessShow -- groupify commentedImports `forM_` tellDebugMessShow
docLines (commentedImportsToDoc <$> sortCommentedImports commentedImports) docLines (commentedImportsToDoc <$> sortCommentedImports commentedImports)
-- sortedImports <- sortImports imports -- sortedImports <- sortImports imports
-- docLines $ [layoutImport y i | (y, i) <- sortedImports] -- docLines $ [layoutImport y i | (y, i) <- sortedImports]
HsModule _ (Just n) les imports _ _ _ -> do HsModule _ _ (Just n) les imports _ _ _ -> do
commentedImports <- transformToCommentedImport imports commentedImports <- transformToCommentedImport imports
-- groupify commentedImports `forM_` tellDebugMessShow -- groupify commentedImports `forM_` tellDebugMessShow
-- sortedImports <- sortImports imports -- sortedImports <- sortImports imports
@ -100,11 +100,12 @@ transformToCommentedImport
:: [LImportDecl GhcPs] -> ToBriDocM [CommentedImport] :: [LImportDecl GhcPs] -> ToBriDocM [CommentedImport]
transformToCommentedImport is = do transformToCommentedImport is = do
nodeWithAnnotations <- is `forM` \i@(L _ rawImport) -> do nodeWithAnnotations <- is `forM` \i@(L _ rawImport) -> do
annotionMay <- astAnn i annotionMay <- undefined -- astAnn i
pure (annotionMay, rawImport) pure (annotionMay, rawImport)
let let
convertComment (c, DP (y, x)) = convertComment (c, _ {-DP (y, x)-}) =
replicate (y - 1) EmptyLine ++ [IndependentComment (c, DP (1, x))] undefined
-- replicate (y - 1) EmptyLine ++ [IndependentComment (c, DP (1, x))]
accumF accumF
:: [(Comment, DeltaPos)] :: [(Comment, DeltaPos)]
-> (Maybe Annotation, ImportDecl GhcPs) -> (Maybe Annotation, ImportDecl GhcPs)
@ -121,21 +122,22 @@ transformToCommentedImport is = do
) )
Just ann -> Just ann ->
let let
blanksBeforeImportDecl = deltaRow (annEntryDelta ann) - 1 blanksBeforeImportDecl = undefined -- deltaRow (annEntryDelta ann) - 1
(newAccumulator, priorComments') = (newAccumulator, priorComments') =
List.span ((== 0) . deltaRow . snd) (annPriorComments ann) List.span ((== 0) . {-deltaRow-} undefined . snd) ({-annPriorComments-} undefined ann)
go go
:: [(Comment, DeltaPos)] :: [(Comment, DeltaPos)]
-> [(Comment, DeltaPos)] -> [(Comment, DeltaPos)]
-> ([CommentedImport], [(Comment, DeltaPos)], Int) -> ([CommentedImport], [(Comment, DeltaPos)], Int)
go acc [] = ([], acc, 0) go acc [] = ([], acc, 0)
go acc [c1@(_, DP (y, _))] = ([], c1 : acc, y - 1) go acc _ = undefined
go acc (c1@(_, DP (1, _)) : xs) = go (c1 : acc) xs -- go acc [c1@(_, {DP (y, _)})] = ([], c1 : acc, y - 1)
go acc ((c1, DP (y, x)) : xs) = -- go acc (c1@(_, DP (1, _)) : xs) = go (c1 : acc) xs
( (convertComment =<< xs) ++ replicate (y - 1) EmptyLine -- go acc ((c1, DP (y, x)) : xs) =
, (c1, DP (1, x)) : acc -- ( (convertComment =<< xs) ++ replicate (y - 1) EmptyLine
, 0 -- , (c1, DP (1, x)) : acc
) -- , 0
-- )
(convertedIndependentComments, beforeComments, initialBlanks) = (convertedIndependentComments, beforeComments, initialBlanks) =
if blanksBeforeImportDecl /= 0 if blanksBeforeImportDecl /= 0
then (convertComment =<< priorComments', [], 0) then (convertComment =<< priorComments', [], 0)
@ -195,4 +197,5 @@ commentedImportsToDoc = \case
ImportStatement r -> docSeq ImportStatement r -> docSeq
(layoutImport (importStatement r) : map commentToDoc (commentsAfter r)) (layoutImport (importStatement r) : map commentToDoc (commentsAfter r))
where where
commentToDoc (c, DP (_y, x)) = docLitS (replicate x ' ' ++ commentContents c) commentToDoc (c, _ {-DP (_y, x)-}) = undefined
-- docLitS (replicate x ' ' ++ commentContents c)

View File

@ -220,7 +220,7 @@ type ToBriDocM = MultiRWSS.MultiRWS
'[NodeAllocIndex] -- state '[NodeAllocIndex] -- state
type ToBriDoc an (sym :: Kind.Type -> Kind.Type) = LocatedAn an (sym GhcPs) -> ToBriDocM BriDocNumbered type ToBriDoc an (sym :: Kind.Type -> Kind.Type) = LocatedAn an (sym GhcPs) -> ToBriDocM BriDocNumbered
type ToBriDoc' sym = Located sym -> ToBriDocM BriDocNumbered type ToBriDoc' an sym = LocatedAn an sym -> ToBriDocM BriDocNumbered
type ToBriDocC sym c = Located sym -> ToBriDocM c type ToBriDocC sym c = Located sym -> ToBriDocM c
data DocMultiLine data DocMultiLine