summaryrefslogtreecommitdiff
path: root/compiler/GHC/Hs
diff options
context:
space:
mode:
authorVladislav Zavialov <vlad.z.4096@gmail.com>2022-06-23 11:50:37 +0300
committerVladislav Zavialov <vlad.z.4096@gmail.com>2022-10-23 00:11:50 +0300
commit11fe42d89d37539bd90f31ca47547922b3fc84ae (patch)
tree52aaeb001808eeeafb4b7bad6d19d7d5e658581c /compiler/GHC/Hs
parent1937016b7834338eef12be19caefc8e37a90cd29 (diff)
downloadhaskell-11fe42d89d37539bd90f31ca47547922b3fc84ae.tar.gz
Class layout info (#19623)
Updates the haddock submodule.
Diffstat (limited to 'compiler/GHC/Hs')
-rw-r--r--compiler/GHC/Hs/Decls.hs3
-rw-r--r--compiler/GHC/Hs/Extension.hs4
2 files changed, 6 insertions, 1 deletions
diff --git a/compiler/GHC/Hs/Decls.hs b/compiler/GHC/Hs/Decls.hs
index e1e368a76b..d296f2b0a6 100644
--- a/compiler/GHC/Hs/Decls.hs
+++ b/compiler/GHC/Hs/Decls.hs
@@ -353,7 +353,8 @@ data DataDeclRn = DataDeclRn
, tcdFVs :: NameSet }
deriving Data
-type instance XClassDecl GhcPs = (EpAnn [AddEpAnn], AnnSortKey, LayoutInfo) -- See Note [Class LayoutInfo]
+type instance XClassDecl GhcPs = (EpAnn [AddEpAnn], AnnSortKey)
+
-- TODO:AZ:tidy up AnnSortKey above
type instance XClassDecl GhcRn = NameSet -- FVs
type instance XClassDecl GhcTc = NameSet -- FVs
diff --git a/compiler/GHC/Hs/Extension.hs b/compiler/GHC/Hs/Extension.hs
index 922288650f..8e73f60b85 100644
--- a/compiler/GHC/Hs/Extension.hs
+++ b/compiler/GHC/Hs/Extension.hs
@@ -11,6 +11,7 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilyDependencies #-}
+{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE UndecidableSuperClasses #-} -- for IsPass; see Note [NoGhcTc]
{-# LANGUAGE UndecidableInstances #-} -- Wrinkle in Note [Trees That Grow]
-- in module Language.Haskell.Syntax.Extension
@@ -27,6 +28,7 @@ import GHC.Prelude
import GHC.TypeLits (KnownSymbol, symbolVal)
import Data.Data hiding ( Fixity )
+import Language.Haskell.Syntax.Concrete
import Language.Haskell.Syntax.Extension
import GHC.Types.Name
import GHC.Types.Name.Reader
@@ -258,3 +260,5 @@ instance KnownSymbol tok => Outputable (HsToken tok) where
instance (KnownSymbol tok, KnownSymbol utok) => Outputable (HsUniToken tok utok) where
ppr HsNormalTok = text (symbolVal (Proxy :: Proxy tok))
ppr HsUnicodeTok = text (symbolVal (Proxy :: Proxy utok))
+
+deriving instance Typeable p => Data (LayoutInfo (GhcPass p))