[commit: ghc] ghc-8.6: TTG typo: XFieldOcc should be XCFieldOcc (10fa804)
git at git.haskell.org
git at git.haskell.org
Mon Jul 30 22:26:14 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : ghc-8.6
Link : http://ghc.haskell.org/trac/ghc/changeset/10fa80418286fb5ec9a1b78edc872ccd004d4499/ghc
>---------------------------------------------------------------
commit 10fa80418286fb5ec9a1b78edc872ccd004d4499
Author: Alan Zimmerman <alan.zimm at gmail.com>
Date: Sun Jul 15 19:35:51 2018 +0200
TTG typo: XFieldOcc should be XCFieldOcc
In the following
data FieldOcc pass = FieldOcc { extFieldOcc :: XFieldOcc pass
, rdrNameFieldOcc :: Located RdrName
-- ^ See Note [Located RdrNames] in HsExpr
}
| XFieldOcc
(XXFieldOcc pass)
we are using XFieldOcc for both the extFieldOcc type and the extra constructor.
The first one should be XCFieldOcc
Updates haddock submodule
closes #15386
(cherry picked from commit 926954196f9ffd7b89cba53061b39ef996e1650c)
>---------------------------------------------------------------
10fa80418286fb5ec9a1b78edc872ccd004d4499
compiler/hsSyn/HsExtension.hs | 4 ++--
compiler/hsSyn/HsPat.hs | 4 ++--
compiler/hsSyn/HsTypes.hs | 12 ++++++------
utils/haddock | 2 +-
4 files changed, 11 insertions(+), 11 deletions(-)
diff --git a/compiler/hsSyn/HsExtension.hs b/compiler/hsSyn/HsExtension.hs
index a23b973..a7c467d 100644
--- a/compiler/hsSyn/HsExtension.hs
+++ b/compiler/hsSyn/HsExtension.hs
@@ -973,11 +973,11 @@ type ForallXConDeclField (c :: * -> Constraint) (x :: *) =
-- ---------------------------------------------------------------------
-type family XFieldOcc x
+type family XCFieldOcc x
type family XXFieldOcc x
type ForallXFieldOcc (c :: * -> Constraint) (x :: *) =
- ( c (XFieldOcc x)
+ ( c (XCFieldOcc x)
, c (XXFieldOcc x)
)
diff --git a/compiler/hsSyn/HsPat.hs b/compiler/hsSyn/HsPat.hs
index 866b0e2..faefb84 100644
--- a/compiler/hsSyn/HsPat.hs
+++ b/compiler/hsSyn/HsPat.hs
@@ -444,14 +444,14 @@ data HsRecField' id arg = HsRecField {
--
-- See also Note [Disambiguating record fields] in TcExpr.
-hsRecFields :: HsRecFields p arg -> [XFieldOcc p]
+hsRecFields :: HsRecFields p arg -> [XCFieldOcc p]
hsRecFields rbinds = map (unLoc . hsRecFieldSel . unLoc) (rec_flds rbinds)
-- Probably won't typecheck at once, things have changed :/
hsRecFieldsArgs :: HsRecFields p arg -> [arg]
hsRecFieldsArgs rbinds = map (hsRecFieldArg . unLoc) (rec_flds rbinds)
-hsRecFieldSel :: HsRecField pass arg -> Located (XFieldOcc pass)
+hsRecFieldSel :: HsRecField pass arg -> Located (XCFieldOcc pass)
hsRecFieldSel = fmap extFieldOcc . hsRecFieldLbl
hsRecFieldId :: HsRecField GhcTc arg -> Located Id
diff --git a/compiler/hsSyn/HsTypes.hs b/compiler/hsSyn/HsTypes.hs
index cbaa9fb..3512bf7 100644
--- a/compiler/hsSyn/HsTypes.hs
+++ b/compiler/hsSyn/HsTypes.hs
@@ -1136,19 +1136,19 @@ type LFieldOcc pass = Located (FieldOcc pass)
-- Represents an *occurrence* of an unambiguous field. We store
-- both the 'RdrName' the user originally wrote, and after the
-- renamer, the selector function.
-data FieldOcc pass = FieldOcc { extFieldOcc :: XFieldOcc pass
+data FieldOcc pass = FieldOcc { extFieldOcc :: XCFieldOcc pass
, rdrNameFieldOcc :: Located RdrName
-- ^ See Note [Located RdrNames] in HsExpr
}
| XFieldOcc
(XXFieldOcc pass)
-deriving instance (p ~ GhcPass pass, Eq (XFieldOcc p)) => Eq (FieldOcc p)
-deriving instance (p ~ GhcPass pass, Ord (XFieldOcc p)) => Ord (FieldOcc p)
+deriving instance (p ~ GhcPass pass, Eq (XCFieldOcc p)) => Eq (FieldOcc p)
+deriving instance (p ~ GhcPass pass, Ord (XCFieldOcc p)) => Ord (FieldOcc p)
-type instance XFieldOcc GhcPs = NoExt
-type instance XFieldOcc GhcRn = Name
-type instance XFieldOcc GhcTc = Id
+type instance XCFieldOcc GhcPs = NoExt
+type instance XCFieldOcc GhcRn = Name
+type instance XCFieldOcc GhcTc = Id
type instance XXFieldOcc (GhcPass _) = NoExt
diff --git a/utils/haddock b/utils/haddock
index 679f612..9765c10 160000
--- a/utils/haddock
+++ b/utils/haddock
@@ -1 +1 @@
-Subproject commit 679f61210b18acd6299687fca66c81196ca358a5
+Subproject commit 9765c10a27013b5c9168ee507d1f3b34cb4be26f
More information about the ghc-commits
mailing list