Skip to content

Commit

Permalink
s/Operator/Name (#919)
Browse files Browse the repository at this point in the history
"Operator" was too specific and did not accurately represent non-operator
identifiers such as function and variable names. "Name" is more
versatile and appropriately covers both operators and identifiers.
  • Loading branch information
toku-sa-n authored Jun 23, 2024
1 parent e78fc84 commit 22ea944
Show file tree
Hide file tree
Showing 10 changed files with 86 additions and 89 deletions.
4 changes: 2 additions & 2 deletions hindent.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -103,9 +103,9 @@ library
HIndent.Ast.Module.Export.Entry
HIndent.Ast.Module.Name
HIndent.Ast.Module.Warning
HIndent.Ast.Name.Infix
HIndent.Ast.Name.Prefix
HIndent.Ast.NodeComments
HIndent.Ast.Operator.Infix
HIndent.Ast.Operator.Prefix
HIndent.Ast.Role
HIndent.Ast.Type
HIndent.Ast.Type.Variable
Expand Down
4 changes: 2 additions & 2 deletions src/HIndent/Ast/Declaration/Bind.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,8 +6,8 @@ module HIndent.Ast.Declaration.Bind
, mkBind
) where

import HIndent.Ast.Name.Infix
import HIndent.Ast.NodeComments
import HIndent.Ast.Operator.Infix
import qualified HIndent.GhcLibParserWrapper.GHC.Hs as GHC
import {-# SOURCE #-} HIndent.Pretty
import HIndent.Pretty.Combinators
Expand Down Expand Up @@ -46,7 +46,7 @@ instance Pretty Bind where
string "pattern "
case parameters of
GHC.InfixCon l r ->
spaced [pretty l, pretty $ fmap mkInfixOperator name, pretty r]
spaced [pretty l, pretty $ fmap mkInfixName name, pretty r]
GHC.PrefixCon _ [] -> pretty name
_ -> spaced [pretty name, pretty parameters]
spacePrefixed [pretty direction, pretty $ fmap PatInsidePatDecl definition]
Expand Down
5 changes: 2 additions & 3 deletions src/HIndent/Ast/Declaration/Class/NameAndTypeVariables.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,8 +6,8 @@ module HIndent.Ast.Declaration.Class.NameAndTypeVariables
) where

import qualified GHC.Types.Fixity as GHC
import HIndent.Ast.Name.Infix
import HIndent.Ast.NodeComments
import HIndent.Ast.Operator.Infix
import HIndent.Ast.Type.Variable
import HIndent.Ast.WithComments
import qualified HIndent.GhcLibParserWrapper.GHC.Hs as GHC
Expand All @@ -34,8 +34,7 @@ instance CommentExtraction NameAndTypeVariables where
instance Pretty NameAndTypeVariables where
pretty' Prefix {..} = spaced $ pretty name : fmap pretty typeVariables
pretty' Infix {..} = do
parens
$ spaced [pretty left, pretty $ fmap mkInfixOperator name, pretty right]
parens $ spaced [pretty left, pretty $ fmap mkInfixName name, pretty right]
spacePrefixed $ fmap pretty remains

mkNameAndTypeVariables :: GHC.TyClDecl GHC.GhcPs -> Maybe NameAndTypeVariables
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -7,8 +7,8 @@ module HIndent.Ast.Declaration.Data.Haskell98.Constructor.Body
) where

import HIndent.Ast.Declaration.Data.Record.Field
import HIndent.Ast.Name.Infix
import HIndent.Ast.NodeComments
import HIndent.Ast.Operator.Infix
import HIndent.Ast.WithComments
import qualified HIndent.GhcLibParserWrapper.GHC.Hs as GHC
import {-# SOURCE #-} HIndent.Pretty
Expand Down Expand Up @@ -37,7 +37,7 @@ instance CommentExtraction Haskell98ConstructorBody where

instance Pretty Haskell98ConstructorBody where
pretty' Infix {..} =
spaced [pretty left, pretty $ fmap mkInfixOperator name, pretty right]
spaced [pretty left, pretty $ fmap mkInfixName name, pretty right]
pretty' Prefix {..} = pretty name >> hor <-|> ver
where
hor = spacePrefixed $ fmap pretty types
Expand Down
5 changes: 2 additions & 3 deletions src/HIndent/Ast/Declaration/Signature.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,8 +13,8 @@ import HIndent.Ast.Declaration.Signature.BooleanFormula
import HIndent.Ast.Declaration.Signature.Fixity
import HIndent.Ast.Declaration.Signature.Inline.Phase
import HIndent.Ast.Declaration.Signature.Inline.Spec
import HIndent.Ast.Name.Infix
import HIndent.Ast.NodeComments
import HIndent.Ast.Operator.Infix
import HIndent.Ast.WithComments
import qualified HIndent.GhcLibParserWrapper.GHC.Hs as GHC
import {-# SOURCE #-} HIndent.Pretty
Expand Down Expand Up @@ -122,8 +122,7 @@ instance Pretty Signature where
$ indentedWithSpace 3
$ printCommentsAnd signature (pretty . HsSigTypeInsideDeclSig)
pretty' Fixity {..} =
spaced
[pretty fixity, hCommaSep $ fmap (pretty . fmap mkInfixOperator) names]
spaced [pretty fixity, hCommaSep $ fmap (pretty . fmap mkInfixName) names]
pretty' Inline {..} = do
string "{-# "
pretty spec
Expand Down
4 changes: 2 additions & 2 deletions src/HIndent/Ast/Declaration/TypeSynonym/Lhs.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,8 +6,8 @@ module HIndent.Ast.Declaration.TypeSynonym.Lhs
) where

import qualified GHC.Types.Fixity as GHC
import HIndent.Ast.Name.Infix
import HIndent.Ast.NodeComments
import HIndent.Ast.Operator.Infix
import HIndent.Ast.Type.Variable
import HIndent.Ast.WithComments
import qualified HIndent.GhcLibParserWrapper.GHC.Hs as GHC
Expand All @@ -33,7 +33,7 @@ instance CommentExtraction TypeSynonymLhs where
instance Pretty TypeSynonymLhs where
pretty' Prefix {..} = spaced $ pretty name : fmap pretty typeVariables
pretty' Infix {..} =
spaced [pretty left, pretty $ fmap mkInfixOperator name, pretty right]
spaced [pretty left, pretty $ fmap mkInfixName name, pretty right]

mkTypeSynonymLhs :: GHC.TyClDecl GHC.GhcPs -> TypeSynonymLhs
mkTypeSynonymLhs GHC.SynDecl {tcdFixity = GHC.Prefix, ..} =
Expand Down
31 changes: 15 additions & 16 deletions src/HIndent/Ast/Operator/Infix.hs → src/HIndent/Ast/Name/Infix.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
{-# LANGUAGE RecordWildCards #-}

module HIndent.Ast.Operator.Infix
( InfixOperator
, mkInfixOperator
module HIndent.Ast.Name.Infix
( InfixName
, mkInfixName
) where

import Data.Maybe
Expand All @@ -14,33 +14,32 @@ import {-# SOURCE #-} HIndent.Pretty
import HIndent.Pretty.Combinators
import HIndent.Pretty.NodeComments

data InfixOperator = InfixOperator
data InfixName = InfixName
{ name :: GHC.OccName
, moduleName :: Maybe GHC.ModuleName
, backtick :: Bool
}

instance CommentExtraction InfixOperator where
nodeComments InfixOperator {} = NodeComments [] [] []
instance CommentExtraction InfixName where
nodeComments InfixName {} = NodeComments [] [] []

instance Pretty InfixOperator where
pretty' InfixOperator {..} =
instance Pretty InfixName where
pretty' InfixName {..} =
wrap $ hDotSep $ catMaybes [pretty <$> moduleName, Just $ pretty name]
where
wrap =
if backtick
then backticks
else id

mkInfixOperator :: GHC.RdrName -> InfixOperator
mkInfixOperator (GHC.Unqual name) =
InfixOperator name Nothing (backticksNeeded name)
mkInfixOperator (GHC.Qual modName name) =
InfixOperator name (Just modName) (backticksNeeded name)
mkInfixOperator (GHC.Orig {}) =
mkInfixName :: GHC.RdrName -> InfixName
mkInfixName (GHC.Unqual name) = InfixName name Nothing (backticksNeeded name)
mkInfixName (GHC.Qual modName name) =
InfixName name (Just modName) (backticksNeeded name)
mkInfixName (GHC.Orig {}) =
error "This AST node should not appear in the parser output."
mkInfixOperator (GHC.Exact name) =
InfixOperator (GHC.occName name) Nothing (backticksNeeded $ GHC.occName name)
mkInfixName (GHC.Exact name) =
InfixName (GHC.occName name) Nothing (backticksNeeded $ GHC.occName name)

backticksNeeded :: GHC.OccName -> Bool
backticksNeeded = not . GHC.isSymOcc
46 changes: 46 additions & 0 deletions src/HIndent/Ast/Name/Prefix.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,46 @@
{-# LANGUAGE RecordWildCards #-}

module HIndent.Ast.Name.Prefix
( PrefixName
, mkPrefixName
) where

import Data.Maybe
import qualified GHC.Types.Name as GHC
import qualified GHC.Types.Name.Reader as GHC
import qualified GHC.Unit.Module as GHC
import HIndent.Ast.NodeComments
import {-# SOURCE #-} HIndent.Pretty
import HIndent.Pretty.Combinators
import HIndent.Pretty.NodeComments

data PrefixName = PrefixName
{ name :: String
, moduleName :: Maybe GHC.ModuleName
, parentheses :: Bool
}

instance CommentExtraction PrefixName where
nodeComments PrefixName {} = NodeComments [] [] []

instance Pretty PrefixName where
pretty' PrefixName {..} =
wrap $ hDotSep $ catMaybes [pretty <$> moduleName, Just $ string name]
where
wrap =
if parentheses
then parens
else id

mkPrefixName :: GHC.RdrName -> PrefixName
mkPrefixName (GHC.Unqual name) =
PrefixName (showOutputable name) Nothing (parensNeeded name)
mkPrefixName (GHC.Qual modName name) =
PrefixName (showOutputable name) (Just modName) (parensNeeded name)
mkPrefixName (GHC.Orig {}) =
error "This AST node should not appear in the parser output."
mkPrefixName (GHC.Exact name) =
PrefixName (showOutputable name) Nothing (parensNeeded $ GHC.occName name)

parensNeeded :: GHC.OccName -> Bool
parensNeeded = GHC.isSymOcc
46 changes: 0 additions & 46 deletions src/HIndent/Ast/Operator/Prefix.hs

This file was deleted.

26 changes: 13 additions & 13 deletions src/HIndent/Pretty.hs
Original file line number Diff line number Diff line change
Expand Up @@ -42,9 +42,9 @@ import HIndent.Ast.Declaration.Family.Type
import HIndent.Ast.Declaration.Signature
import HIndent.Ast.Expression.Bracket
import HIndent.Ast.Expression.Splice
import HIndent.Ast.Name.Infix
import HIndent.Ast.Name.Prefix
import HIndent.Ast.NodeComments
import HIndent.Ast.Operator.Infix
import HIndent.Ast.Operator.Prefix
import HIndent.Ast.Type.Variable
import HIndent.Ast.WithComments
import HIndent.Config
Expand Down Expand Up @@ -152,7 +152,7 @@ instance Pretty (GHC.HsExpr GHC.GhcPs) where
pretty' = prettyHsExpr

prettyHsExpr :: GHC.HsExpr GHC.GhcPs -> Printer ()
prettyHsExpr (GHC.HsVar _ bind) = pretty $ fmap mkPrefixOperator bind
prettyHsExpr (GHC.HsVar _ bind) = pretty $ fmap mkPrefixName bind
prettyHsExpr (GHC.HsUnboundVar _ x) = pretty x
#if MIN_VERSION_ghc_lib_parser(9,6,1)
prettyHsExpr (GHC.HsOverLabel _ _ l) = string "#" >> string (GHC.unpackFS l)
Expand Down Expand Up @@ -551,7 +551,7 @@ prettyMatchExpr GHC.Match {..} =
case (m_pats, m_ctxt) of
(l:r:xs, GHC.FunRhs {..}) -> do
spaced
$ [pretty l, pretty $ fmap mkInfixOperator mc_fun, pretty r]
$ [pretty l, pretty $ fmap mkInfixName mc_fun, pretty r]
++ fmap pretty xs
pretty m_grhss
_ -> error "Not enough parameters are passed."
Expand Down Expand Up @@ -732,21 +732,21 @@ prettyHsType (GHC.HsOpTy _ _ l op r) = do
then do
pretty l
newline
pretty $ fmap mkInfixOperator op
pretty $ fmap mkInfixName op
space
pretty r
else spaced [pretty l, pretty $ fmap mkInfixOperator op, pretty r]
else spaced [pretty l, pretty $ fmap mkInfixName op, pretty r]
#else
prettyHsType (GHC.HsOpTy _ l op r) = do
lineBreak <- gets (configLineBreaks . psConfig)
if showOutputable op `elem` lineBreak
then do
pretty l
newline
pretty $ fmap mkInfixOperator op
pretty $ fmap mkInfixName op
space
pretty r
else spaced [pretty l, pretty $ fmap mkInfixOperator op, pretty r]
else spaced [pretty l, pretty $ fmap mkInfixName op, pretty r]
#endif
prettyHsType (GHC.HsParTy _ inside) = parens $ pretty inside
prettyHsType (GHC.HsIParamTy _ x ty) =
Expand Down Expand Up @@ -831,7 +831,7 @@ instance Pretty ParStmtBlockInsideVerticalList where
vCommaSep $ fmap pretty xs

instance Pretty GHC.RdrName where
pretty' = pretty . mkPrefixOperator
pretty' = pretty . mkPrefixName

instance Pretty
(GHC.GRHS
Expand Down Expand Up @@ -928,7 +928,7 @@ instance Pretty (GHC.Pat GHC.GhcPs) where

instance Pretty PatInsidePatDecl where
pretty' (PatInsidePatDecl (GHC.ConPat {pat_args = (GHC.InfixCon l r), ..})) =
spaced [pretty l, pretty $ fmap mkInfixOperator pat_con, pretty r]
spaced [pretty l, pretty $ fmap mkInfixName pat_con, pretty r]
pretty' (PatInsidePatDecl x) = pretty x

prettyPat :: GHC.Pat GHC.GhcPs -> Printer ()
Expand Down Expand Up @@ -960,13 +960,13 @@ prettyPat (GHC.SumPat _ x position numElem) = do
prettyPat GHC.ConPat {..} =
case pat_args of
GHC.PrefixCon _ as -> do
pretty $ fmap mkPrefixOperator pat_con
pretty $ fmap mkPrefixName pat_con
spacePrefixed $ fmap pretty as
GHC.RecCon rec -> (pretty pat_con >> space) |=> pretty (RecConPat rec)
GHC.InfixCon a b -> do
pretty a
unlessSpecialOp (GHC.unLoc pat_con) space
pretty $ fmap mkInfixOperator pat_con
pretty $ fmap mkInfixName pat_con
unlessSpecialOp (GHC.unLoc pat_con) space
pretty b
prettyPat (GHC.ViewPat _ l r) = spaced [pretty l, string "->", pretty r]
Expand Down Expand Up @@ -1088,7 +1088,7 @@ instance Pretty a => Pretty (GHC.HsScaled GHC.GhcPs a) where

instance Pretty InfixExpr where
pretty' (InfixExpr (GHC.L _ (GHC.HsVar _ bind))) =
pretty $ fmap mkInfixOperator bind
pretty $ fmap mkInfixName bind
pretty' (InfixExpr x) = pretty' x

instance Pretty InfixApp where
Expand Down

0 comments on commit 22ea944

Please sign in to comment.