|
2 | 2 | {-# LANGUAGE DataKinds #-}
|
3 | 3 | {-# LANGUAGE DoAndIfThenElse #-}
|
4 | 4 | {-# LANGUAGE FlexibleContexts #-}
|
5 |
| -{-# LANGUAGE LambdaCase #-} |
6 | 5 | {-# LANGUAGE MultiWayIf #-}
|
7 | 6 | {-# LANGUAGE NamedFieldPuns #-}
|
8 | 7 | {-# LANGUAGE RecordWildCards #-}
|
@@ -38,7 +37,7 @@ import Language.Haskell.Stylish.Printer
|
38 | 37 | import Language.Haskell.Stylish.Step
|
39 | 38 | import Language.Haskell.Stylish.Util
|
40 | 39 |
|
41 |
| - |
| 40 | +import Debug.Trace |
42 | 41 | --------------------------------------------------------------------------------
|
43 | 42 | data Indent
|
44 | 43 | = SameLine
|
@@ -93,19 +92,17 @@ step cfg = makeStep "Data" \ls m -> Editor.apply (changes m) ls
|
93 | 92 | changes :: Module -> Editor.Edits
|
94 | 93 | changes = foldMap (formatDataDecl cfg) . dataDecls
|
95 | 94 |
|
96 |
| - getComments :: GHC.AddEpAnn -> [GHC.LEpaComment] |
97 |
| - getComments (GHC.AddEpAnn _ epaLoc) = case epaLoc of |
98 |
| - GHC.EpaDelta _ comments -> comments |
99 |
| - GHC.EpaSpan _ -> [] |
| 95 | + getComments :: GHC.SrcSpanAnnA -> [GHC.LEpaComment] |
| 96 | + getComments (GHC.EpAnn _ _ c)= GHC.priorComments c |
100 | 97 |
|
101 | 98 | dataDecls :: Module -> [DataDecl]
|
102 | 99 | dataDecls m = do
|
103 |
| - ldecl <- GHC.hsmodDecls $ GHC.unLoc m |
104 |
| - GHC.TyClD _ tycld <- pure $ GHC.unLoc ldecl |
| 100 | + ldecl <- GHC.hsmodDecls . GHC.unLoc $ m |
| 101 | + (GHC.TyClD _ tycld, annos) <- pure $ (\(GHC.L anno ty) -> (ty, anno)) ldecl |
105 | 102 | loc <- maybeToList $ GHC.srcSpanToRealSrcSpan $ GHC.getLocA ldecl
|
106 | 103 | case tycld of
|
107 | 104 | GHC.DataDecl {..} -> pure $ MkDataDecl
|
108 |
| - { dataComments = foldMap getComments tcdDExt |
| 105 | + { dataComments = getComments annos |
109 | 106 | , dataLoc = loc
|
110 | 107 | , dataDeclName = tcdLName
|
111 | 108 | , dataTypeVars = tcdTyVars
|
@@ -150,7 +147,7 @@ putDataDecl cfg@Config {..} decl = do
|
150 | 147 |
|
151 | 148 | onelineEnum =
|
152 | 149 | isEnum decl && not cBreakEnums &&
|
153 |
| - all (not . commentGroupHasComments) constructorComments |
| 150 | + (not . any commentGroupHasComments) constructorComments |
154 | 151 |
|
155 | 152 | putText $ newOrData decl
|
156 | 153 | space
|
@@ -179,9 +176,14 @@ putDataDecl cfg@Config {..} decl = do
|
179 | 176 | forM_ (GHC.dd_cons defn) $ putNewtypeConstructor cfg
|
180 | 177 | | not . null $ GHC.dd_cons defn -> do
|
181 | 178 | forM_ (flagEnds constructorComments) $ \(CommentGroup {..}, firstGroup, lastGroup) -> do
|
182 |
| - forM_ cgPrior $ \lc -> do |
183 |
| - putComment $ GHC.unLoc lc |
184 |
| - consIndent lineLengthAfterEq |
| 179 | + forM_ cgPrior $ \(GHC.L l c) -> do |
| 180 | + -- ugly workaround to make sure we don't reprint a haddock |
| 181 | + -- comment before a data declaration after a data |
| 182 | + -- declaration… |
| 183 | + let GHC.EpaSpan (GHC.RealSrcSpan comLoc _) = l |
| 184 | + when (GHC.srcSpanStartLine comLoc >= GHC.srcSpanStartLine (dataLoc decl)) $ do |
| 185 | + putComment c |
| 186 | + consIndent lineLengthAfterEq |
185 | 187 |
|
186 | 188 | forM_ (flagEnds cgItems) $ \((lcon, mbInlineComment), firstItem, lastItem) -> do
|
187 | 189 | unless (isGADT decl) $ do
|
@@ -335,7 +337,7 @@ putConstructor cfg consIndent lcons = case GHC.unLoc lcons of
|
335 | 337 | GHC.ConDeclGADT {..} -> do
|
336 | 338 | -- Put argument to constructor first:
|
337 | 339 | case con_g_args of
|
338 |
| - GHC.PrefixConGADT _ _ -> sep (comma >> space) $ fmap putRdrName $ toList con_names |
| 340 | + GHC.PrefixConGADT _ _ -> sep (comma >> space) (putRdrName <$> toList con_names) |
339 | 341 | GHC.RecConGADT _ _ -> error . mconcat $
|
340 | 342 | [ "Language.Haskell.Stylish.Step.Data.putConstructor: "
|
341 | 343 | , "encountered a GADT with record constructors, not supported yet"
|
|
0 commit comments