[commit: ghc] master: Use a less confusing type variable in a few types (9969863)
git at git.haskell.org
git at git.haskell.org
Tue May 29 20:57:47 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/9969863adbd8f467d029254b5520c3340dacd980/ghc
>---------------------------------------------------------------
commit 9969863adbd8f467d029254b5520c3340dacd980
Author: Simon Jakobi <simon.jakobi at gmail.com>
Date: Mon May 21 20:04:07 2018 +0200
Use a less confusing type variable in a few types
>---------------------------------------------------------------
9969863adbd8f467d029254b5520c3340dacd980
compiler/hsSyn/HsImpExp.hs | 4 ++--
compiler/hsSyn/HsSyn.hs | 8 ++++----
2 files changed, 6 insertions(+), 6 deletions(-)
diff --git a/compiler/hsSyn/HsImpExp.hs b/compiler/hsSyn/HsImpExp.hs
index 6f38ba3..39bd9b7 100644
--- a/compiler/hsSyn/HsImpExp.hs
+++ b/compiler/hsSyn/HsImpExp.hs
@@ -41,7 +41,7 @@ One per \tr{import} declaration in a module.
-}
-- | Located Import Declaration
-type LImportDecl name = Located (ImportDecl name)
+type LImportDecl pass = Located (ImportDecl pass)
-- ^ When in a list this may have
--
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnSemi'
@@ -166,7 +166,7 @@ type LIEWrappedName name = Located (IEWrappedName name)
-- | Located Import or Export
-type LIE name = Located (IE name)
+type LIE pass = Located (IE pass)
-- ^ When in a list this may have
--
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnComma'
diff --git a/compiler/hsSyn/HsSyn.hs b/compiler/hsSyn/HsSyn.hs
index b9abcf2..e04abbf 100644
--- a/compiler/hsSyn/HsSyn.hs
+++ b/compiler/hsSyn/HsSyn.hs
@@ -63,12 +63,12 @@ import Data.Data hiding ( Fixity )
-- | Haskell Module
--
-- All we actually declare here is the top-level structure for a module.
-data HsModule name
+data HsModule pass
= HsModule {
hsmodName :: Maybe (Located ModuleName),
-- ^ @Nothing@: \"module X where\" is omitted (in which case the next
-- field is Nothing too)
- hsmodExports :: Maybe (Located [LIE name]),
+ hsmodExports :: Maybe (Located [LIE pass]),
-- ^ Export list
--
-- - @Nothing@: export list omitted, so export everything
@@ -82,11 +82,11 @@ data HsModule name
-- ,'ApiAnnotation.AnnClose'
-- For details on above see note [Api annotations] in ApiAnnotation
- hsmodImports :: [LImportDecl name],
+ hsmodImports :: [LImportDecl pass],
-- ^ We snaffle interesting stuff out of the imported interfaces early
-- on, adding that info to TyDecls/etc; so this list is often empty,
-- downstream.
- hsmodDecls :: [LHsDecl name],
+ hsmodDecls :: [LHsDecl pass],
-- ^ Type, class, value, and interface signature decls
hsmodDeprecMessage :: Maybe (Located WarningTxt),
-- ^ reason\/explanation for warning/deprecation of this module
More information about the ghc-commits
mailing list