Skip to content

Commit

Permalink
Define ModuleWarning in replacement for WarningTxt (#823)
Browse files Browse the repository at this point in the history
* Create `Warning.hs`

* `WithComments`

* Do not depend on GHC AST

* Remove an unused instance

* Remove an unused type

* pretty kind

* `prettyMsgs`

* Separation

* Fix

* Format

* Fix

* Fix
  • Loading branch information
toku-sa-n authored Mar 4, 2024
1 parent b4b9103 commit 8006820
Show file tree
Hide file tree
Showing 7 changed files with 85 additions and 40 deletions.
2 changes: 2 additions & 0 deletions hindent.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,8 @@ library
HIndent.Ast.Module
HIndent.Ast.Module.Declaration
HIndent.Ast.Module.Name
HIndent.Ast.Module.Warning
HIndent.Ast.Module.Warning.Kind
HIndent.Ast.NodeComments
HIndent.Ast.WithComments
HIndent.ByteString
Expand Down
9 changes: 4 additions & 5 deletions src/HIndent/Ast/Module/Declaration.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,18 +7,17 @@ module HIndent.Ast.Module.Declaration

import HIndent.Applicative
import HIndent.Ast.Module.Name
import HIndent.Ast.Module.Warning
import HIndent.Ast.NodeComments
import HIndent.Ast.WithComments
import qualified HIndent.GhcLibParserWrapper.GHC.Hs as GHC
import qualified HIndent.GhcLibParserWrapper.GHC.Unit.Module.Warnings as GHC
import HIndent.Pretty
import HIndent.Pretty.Combinators
import HIndent.Pretty.NodeComments
import HIndent.Pretty.Types

data ModuleDeclaration = ModuleDeclaration
{ name :: WithComments ModuleName
, warning :: Maybe (GHC.LocatedP GHC.WarningTxt')
, warning :: Maybe (WithComments ModuleWarning)
, exports :: Maybe (GHC.LocatedL [GHC.LIE GHC.GhcPs])
}

Expand All @@ -30,7 +29,7 @@ instance Pretty ModuleDeclaration where
pretty name
whenJust warning $ \x -> do
space
pretty $ fmap ModuleDeprecatedPragma x
pretty x
whenJust exports $ \xs -> do
newline
indentedBlock $ do
Expand All @@ -43,5 +42,5 @@ mkModuleDeclaration m =
Nothing -> Nothing
Just name' -> Just ModuleDeclaration {..}
where name = mkModuleName <$> fromGenLocated name'
warning = GHC.getDeprecMessage m
warning = mkModuleWarning m
exports = GHC.hsmodExports m
58 changes: 58 additions & 0 deletions src/HIndent/Ast/Module/Warning.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,58 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE RecordWildCards #-}

module HIndent.Ast.Module.Warning
( ModuleWarning
, mkModuleWarning
) where

import HIndent.Ast.Module.Warning.Kind
import HIndent.Ast.NodeComments
import HIndent.Ast.WithComments
import qualified HIndent.GhcLibParserWrapper.GHC.Hs as GHC
import qualified HIndent.GhcLibParserWrapper.GHC.Unit.Module.Warnings as GHC
import HIndent.Pretty
import HIndent.Pretty.Combinators
import HIndent.Pretty.NodeComments

data ModuleWarning = ModuleWarning
{ messages :: [String]
, kind :: Kind
}

instance CommentExtraction ModuleWarning where
nodeComments _ = NodeComments [] [] []

instance Pretty ModuleWarning where
pretty' ModuleWarning {..} = do
string "{-# "
pretty kind
space
prettyMsgs
string " #-}"
where
prettyMsgs =
case messages of
[x] -> string x
xs -> hList $ fmap string xs

mkModuleWarning :: GHC.HsModule' -> Maybe (WithComments ModuleWarning)
mkModuleWarning =
fmap (fromGenLocated . fmap fromWarningTxt) . GHC.getDeprecMessage

fromWarningTxt :: GHC.WarningTxt' -> ModuleWarning
#if MIN_VERSION_ghc_lib_parser(9, 8, 1)
fromWarningTxt (GHC.WarningTxt _ _ s) = ModuleWarning {..}
where
messages = fmap showOutputable s
kind = Warning
#else
fromWarningTxt (GHC.WarningTxt _ s) = ModuleWarning {..}
where
messages = fmap showOutputable s
kind = Warning
#endif
fromWarningTxt (GHC.DeprecatedTxt _ s) = ModuleWarning {..}
where
messages = fmap showOutputable s
kind = Deprecated
19 changes: 19 additions & 0 deletions src/HIndent/Ast/Module/Warning/Kind.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
module HIndent.Ast.Module.Warning.Kind
( Kind(..)
) where

import HIndent.Ast.NodeComments
import HIndent.Pretty
import HIndent.Pretty.Combinators
import HIndent.Pretty.NodeComments

data Kind
= Warning
| Deprecated

instance CommentExtraction Kind where
nodeComments _ = NodeComments [] [] []

instance Pretty Kind where
pretty' Warning = string "WARNING"
pretty' Deprecated = string "DEPRECATED"
22 changes: 1 addition & 21 deletions src/HIndent/Pretty.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2493,27 +2493,7 @@ instance Pretty CCallConv where
pretty' StdCallConv = string "stdcall"
pretty' PrimCallConv = string "prim"
pretty' JavaScriptCallConv = string "javascript"
#if MIN_VERSION_ghc_lib_parser(9, 8, 1)
instance Pretty ModuleDeprecatedPragma where
pretty' (ModuleDeprecatedPragma (WarningTxt _ _ [msg])) =
spaced [string "{-# WARNING", pretty msg, string "#-}"]
pretty' (ModuleDeprecatedPragma (WarningTxt _ _ msgs)) =
spaced [string "{-# WARNING", hList $ fmap pretty msgs, string "#-}"]
pretty' (ModuleDeprecatedPragma (DeprecatedTxt _ [msg])) =
spaced [string "{-# DEPRECATED", pretty msg, string "#-}"]
pretty' (ModuleDeprecatedPragma (DeprecatedTxt _ msgs)) =
spaced [string "{-# DEPRECATED", hList $ fmap pretty msgs, string "#-}"]
#else
instance Pretty ModuleDeprecatedPragma where
pretty' (ModuleDeprecatedPragma (WarningTxt _ [msg])) =
spaced [string "{-# WARNING", pretty msg, string "#-}"]
pretty' (ModuleDeprecatedPragma (WarningTxt _ msgs)) =
spaced [string "{-# WARNING", hList $ fmap pretty msgs, string "#-}"]
pretty' (ModuleDeprecatedPragma (DeprecatedTxt _ [msg])) =
spaced [string "{-# DEPRECATED", pretty msg, string "#-}"]
pretty' (ModuleDeprecatedPragma (DeprecatedTxt _ msgs)) =
spaced [string "{-# DEPRECATED", hList $ fmap pretty msgs, string "#-}"]
#endif

instance Pretty HsSrcBang where
pretty' (HsSrcBang _ unpack strictness) = do
pretty unpack
Expand Down
3 changes: 0 additions & 3 deletions src/HIndent/Pretty/NodeComments.hs
Original file line number Diff line number Diff line change
Expand Up @@ -961,9 +961,6 @@ instance CommentExtraction (RuleBndr GhcPs) where
instance CommentExtraction CCallConv where
nodeComments = const emptyNodeComments

instance CommentExtraction ModuleDeprecatedPragma where
nodeComments ModuleDeprecatedPragma {} = emptyNodeComments

instance CommentExtraction HsSrcBang where
nodeComments HsSrcBang {} = emptyNodeComments

Expand Down
12 changes: 1 addition & 11 deletions src/HIndent/Pretty/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,7 +40,6 @@ module HIndent.Pretty.Types
, ModuleNameWithPrefix(..)
, PatInsidePatDecl(..)
, LambdaCase(..)
, ModuleDeprecatedPragma(..)
, ListComprehension(..)
, DoExpression(..)
, DoOrMdo(..)
Expand All @@ -56,7 +55,6 @@ module HIndent.Pretty.Types

import GHC.Hs
import GHC.Types.Name.Reader
import GHC.Unit.Module.Warnings
#if !MIN_VERSION_ghc_lib_parser(9,6,1)
import GHC.Unit
#endif
Expand Down Expand Up @@ -254,15 +252,7 @@ data LambdaCase = LambdaCase
{ lamCaseGroup :: MatchGroup GhcPs (LHsExpr GhcPs)
, caseOrCases :: CaseOrCases
}
#if MIN_VERSION_ghc_lib_parser(9,4,1)
-- | A deprecation pragma for a module.
newtype ModuleDeprecatedPragma =
ModuleDeprecatedPragma (WarningTxt GhcPs)
#else
-- | A deprecation pragma for a module.
newtype ModuleDeprecatedPragma =
ModuleDeprecatedPragma WarningTxt
#endif

-- | Use this type to pretty-print a list comprehension.
data ListComprehension = ListComprehension
{ listCompLhs :: ExprLStmt GhcPs -- ^ @f x@ of @[f x| x <- xs]@.
Expand Down

0 comments on commit 8006820

Please sign in to comment.