summaryrefslogtreecommitdiff
path: root/compiler/GHC/Types
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/GHC/Types')
-rw-r--r--compiler/GHC/Types/Error/Codes.hs29
-rw-r--r--compiler/GHC/Types/Hint.hs6
-rw-r--r--compiler/GHC/Types/Hint/Ppr.hs4
-rw-r--r--compiler/GHC/Types/Name/Occurrence.hs21
-rw-r--r--compiler/GHC/Types/SourceFile.hs104
-rw-r--r--compiler/GHC/Types/TyThing/Ppr.hs2
-rw-r--r--compiler/GHC/Types/TyThing/Ppr.hs-boot11
7 files changed, 127 insertions, 50 deletions
diff --git a/compiler/GHC/Types/Error/Codes.hs b/compiler/GHC/Types/Error/Codes.hs
index 5025ff022f..7bcafbe32e 100644
--- a/compiler/GHC/Types/Error/Codes.hs
+++ b/compiler/GHC/Types/Error/Codes.hs
@@ -24,6 +24,8 @@ import GHC.Types.Error ( DiagnosticCode(..), UnknownDiagnostic (..), diagnostic
import GHC.Hs.Extension ( GhcRn )
+import GHC.Core.InstEnv (LookupInstanceErrReason)
+import GHC.Iface.Errors.Types
import GHC.Driver.Errors.Types ( DriverMessage )
import GHC.Parser.Errors.Types ( PsMessage, PsHeaderMessage )
import GHC.HsToCore.Errors.Types ( DsMessage )
@@ -37,8 +39,7 @@ import GHC.Exts ( proxy# )
import GHC.Generics
import GHC.TypeLits ( Symbol, TypeError, ErrorMessage(..) )
import GHC.TypeNats ( Nat, KnownNat, natVal' )
-import GHC.Core.InstEnv (LookupInstanceErrReason)
-import GHC.Iface.Errors.Types
+
{- Note [Diagnostic codes]
~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -359,7 +360,7 @@ type family GhcDiagnosticCode c = n | n -> c where
GhcDiagnosticCode "TcRnTagToEnumResTyNotAnEnum" = 49356
GhcDiagnosticCode "TcRnTagToEnumResTyTypeData" = 96189
GhcDiagnosticCode "TcRnArrowIfThenElsePredDependsOnResultTy" = 55868
- GhcDiagnosticCode "TcRnIllegalHsBootFileDecl" = 58195
+ GhcDiagnosticCode "TcRnIllegalHsBootOrSigDecl" = 58195
GhcDiagnosticCode "TcRnRecursivePatternSynonym" = 72489
GhcDiagnosticCode "TcRnPartialTypeSigTyVarMismatch" = 88793
GhcDiagnosticCode "TcRnPartialTypeSigBadQuantifier" = 94185
@@ -507,7 +508,6 @@ type family GhcDiagnosticCode c = n | n -> c where
GhcDiagnosticCode "TcRnInterfaceLookupError" = 52243
GhcDiagnosticCode "TcRnUnsatisfiedMinimalDef" = 06201
GhcDiagnosticCode "TcRnMisplacedInstSig" = 06202
- GhcDiagnosticCode "TcRnBadBootFamInstDecl" = 06203
GhcDiagnosticCode "TcRnIllegalFamilyInstance" = 06204
GhcDiagnosticCode "TcRnMissingClassAssoc" = 06205
GhcDiagnosticCode "TcRnNotOpenFamily" = 06207
@@ -522,7 +522,6 @@ type family GhcDiagnosticCode c = n | n -> c where
GhcDiagnosticCode "TcRnDuplicateSigDecl" = 31744
GhcDiagnosticCode "TcRnMisplacedSigDecl" = 87866
GhcDiagnosticCode "TcRnUnexpectedDefaultSig" = 40700
- GhcDiagnosticCode "TcRnBindInBootFile" = 11247
GhcDiagnosticCode "TcRnDuplicateMinimalSig" = 85346
GhcDiagnosticCode "TcRnLoopySuperclassSolve" = 36038
GhcDiagnosticCode "TcRnIllegalInstanceHeadDecl" = 12222
@@ -600,6 +599,11 @@ type family GhcDiagnosticCode c = n | n -> c where
GhcDiagnosticCode "TcRnBindingNameConflict" = 10498
GhcDiagnosticCode "NonCanonicalMonoid" = 50928
GhcDiagnosticCode "NonCanonicalMonad" = 22705
+ GhcDiagnosticCode "TcRnUnexpectedDeclarationSplice" = 17599
+ GhcDiagnosticCode "TcRnImplicitImportOfPrelude" = 20540
+ GhcDiagnosticCode "TcRnMissingMain" = 67120
+ GhcDiagnosticCode "TcRnGhciUnliftedBind" = 17999
+ GhcDiagnosticCode "TcRnGhciMonadLookupFail" = 44990
-- PatSynInvalidRhsReason
GhcDiagnosticCode "PatSynNotInvertible" = 69317
@@ -773,6 +777,14 @@ type family GhcDiagnosticCode c = n | n -> c where
GhcDiagnosticCode "EmptyStmtsGroupInDoNotation" = 82311
GhcDiagnosticCode "EmptyStmtsGroupInArrowNotation" = 19442
+ -- HsBoot and Hsig errors
+ GhcDiagnosticCode "MissingBootDefinition" = 63610
+ GhcDiagnosticCode "MissingBootExport" = 91999
+ GhcDiagnosticCode "MissingBootInstance" = 79857
+ GhcDiagnosticCode "BadReexportedBootThing" = 12424
+ GhcDiagnosticCode "BootMismatchedIdTypes" = 11890
+ GhcDiagnosticCode "BootMismatchedTyCons" = 15843
+
-- To generate new random numbers:
-- https://www.random.org/integers/?num=10&min=1&max=99999&col=1&base=10&format=plain
--
@@ -784,6 +796,8 @@ type family GhcDiagnosticCode c = n | n -> c where
GhcDiagnosticCode "TcRnNameByTemplateHaskellQuote" = 40027
GhcDiagnosticCode "TcRnIllegalBindingOfBuiltIn" = 69639
GhcDiagnosticCode "TcRnMixedSelectors" = 40887
+ GhcDiagnosticCode "TcRnBadBootFamInstDecl" = 06203
+ GhcDiagnosticCode "TcRnBindInBootFile" = 11247
{- *********************************************************************
* *
@@ -872,6 +886,11 @@ type family ConRecursInto con where
ConRecursInto "TcRnInterfaceError" = 'Just IfaceMessage
ConRecursInto "Can'tFindInterface" = 'Just MissingInterfaceError
+ -- HsBoot and Hsig errors
+ ConRecursInto "TcRnBootMismatch" = 'Just BootMismatch
+ ConRecursInto "MissingBootThing" = 'Just MissingBootThing
+ ConRecursInto "BootMismatch" = 'Just BootMismatchWhat
+
------------------
-- FFI errors
diff --git a/compiler/GHC/Types/Hint.hs b/compiler/GHC/Types/Hint.hs
index 7057925dea..69f98ba1da 100644
--- a/compiler/GHC/Types/Hint.hs
+++ b/compiler/GHC/Types/Hint.hs
@@ -27,11 +27,12 @@ import qualified Data.List.NonEmpty as NE
import GHC.Utils.Outputable
import qualified GHC.LanguageExtensions as LangExt
-import Data.Typeable
+import Data.Typeable (Typeable)
import GHC.Unit.Module (ModuleName, Module)
import GHC.Hs.Extension (GhcTc, GhcRn)
import GHC.Core.Coercion
import GHC.Core.FamInstEnv (FamFlavor)
+import GHC.Core.TyCon (TyCon)
import GHC.Core.Type (PredType)
import GHC.Types.Fixity (LexicalFixity(..))
import GHC.Types.Name (Name, NameSpace, OccName (occNameFS), isSymOcc, nameOccName)
@@ -453,6 +454,9 @@ data GhcHint
Name -- ^ method with non-canonical implementation
Name -- ^ possible other method to use as the RHS instead
String -- ^ Documentation URL
+ {-| Suggest eta-reducing a type synonym used in the implementation
+ of abstract data. -}
+ | SuggestEtaReduceAbsDataTySyn TyCon
-- | An 'InstantiationSuggestion' for a '.hsig' file. This is generated
-- by GHC in case of a 'DriverUnexpectedSignature' and suggests a way
diff --git a/compiler/GHC/Types/Hint/Ppr.hs b/compiler/GHC/Types/Hint/Ppr.hs
index 4454d872cd..f6b995babc 100644
--- a/compiler/GHC/Types/Hint/Ppr.hs
+++ b/compiler/GHC/Types/Hint/Ppr.hs
@@ -13,6 +13,7 @@ import GHC.Parser.Errors.Basic
import GHC.Types.Hint
import GHC.Core.FamInstEnv (FamFlavor(..))
+import GHC.Core.TyCon
import GHC.Hs.Expr () -- instance Outputable
import {-# SOURCE #-} GHC.Tc.Types.Origin ( ClsInstOrQC(..) )
import GHC.Types.Id
@@ -245,6 +246,9 @@ instance Outputable GhcHint where
text "or define as" <+>
quotes (pprPrefixUnqual lhs <+> text "=" <+> pprPrefixUnqual rhs) $$
text "See also:" <+> text refURL
+ SuggestEtaReduceAbsDataTySyn tc
+ -> text "If possible, eta-reduce the type synonym" <+> ppr_tc <+> text "so that it is nullary."
+ where ppr_tc = quotes (ppr $ tyConName tc)
perhapsAsPat :: SDoc
perhapsAsPat = text "Perhaps you meant an as-pattern, which must not be surrounded by whitespace"
diff --git a/compiler/GHC/Types/Name/Occurrence.hs b/compiler/GHC/Types/Name/Occurrence.hs
index 964c313abd..316b3e911f 100644
--- a/compiler/GHC/Types/Name/Occurrence.hs
+++ b/compiler/GHC/Types/Name/Occurrence.hs
@@ -104,6 +104,9 @@ module GHC.Types.Name.Occurrence (
unionOccSets, unionManyOccSets, elemOccSet,
isEmptyOccSet,
+ -- * Dealing with main
+ mainOcc, ppMainFn,
+
-- * Tidying up
TidyOccEnv, emptyTidyOccEnv, initTidyOccEnv,
tidyOccName, avoidClashesOccEnv, delTidyOccEnvList,
@@ -1253,6 +1256,24 @@ tidyOccName env occ@(OccName occ_sp fs)
{-
************************************************************************
* *
+ Utilies for "main"
+* *
+************************************************************************
+-}
+
+mainOcc :: OccName
+mainOcc = mkVarOccFS (fsLit "main")
+
+ppMainFn :: OccName -> SDoc
+ppMainFn main_occ
+ | main_occ == mainOcc
+ = text "IO action" <+> quotes (ppr main_occ)
+ | otherwise
+ = text "main IO action" <+> quotes (ppr main_occ)
+
+{-
+************************************************************************
+* *
Binary instance
Here rather than in GHC.Iface.Binary because OccName is abstract
* *
diff --git a/compiler/GHC/Types/SourceFile.hs b/compiler/GHC/Types/SourceFile.hs
index 7a1898a51e..0d04a194de 100644
--- a/compiler/GHC/Types/SourceFile.hs
+++ b/compiler/GHC/Types/SourceFile.hs
@@ -1,8 +1,11 @@
+{-# LANGUAGE PatternSynonyms #-}
+
module GHC.Types.SourceFile
- ( HscSource(..)
+ ( HscSource(HsBootFile, HsigFile, ..)
+ , HsBootOrSig(..)
, hscSourceToIsBoot
, isHsBootOrSig
- , isHsigFile
+ , isHsBootFile, isHsigFile
, hscSourceString
)
where
@@ -11,45 +14,57 @@ import GHC.Prelude
import GHC.Utils.Binary
import GHC.Unit.Types
--- Note [HscSource types]
--- ~~~~~~~~~~~~~~~~~~~~~~
--- There are three types of source file for Haskell code:
---
--- * HsSrcFile is an ordinary hs file which contains code,
---
--- * HsBootFile is an hs-boot file, which is used to break
--- recursive module imports (there will always be an
--- HsSrcFile associated with it), and
---
--- * HsigFile is an hsig file, which contains only type
--- signatures and is used to specify signatures for
--- modules.
---
--- Syntactically, hs-boot files and hsig files are quite similar: they
--- only include type signatures and must be associated with an
--- actual HsSrcFile. isHsBootOrSig allows us to abstract over code
--- which is indifferent to which. However, there are some important
--- differences, mostly owing to the fact that hsigs are proper
--- modules (you `import Sig` directly) whereas HsBootFiles are
--- temporary placeholders (you `import {-# SOURCE #-} Mod).
--- When we finish compiling the true implementation of an hs-boot,
--- we replace the HomeModInfo with the real HsSrcFile. An HsigFile, on the
--- other hand, is never replaced (in particular, we *cannot* use the
--- HomeModInfo of the original HsSrcFile backing the signature, since it
--- will export too many symbols.)
---
--- Additionally, while HsSrcFile is the only Haskell file
--- which has *code*, we do generate .o files for HsigFile, because
--- this is how the recompilation checker figures out if a file
--- needs to be recompiled. These are fake object files which
--- should NOT be linked against.
+{- Note [HscSource types]
+~~~~~~~~~~~~~~~~~~~~~~~~~
+There are three types of source file for Haskell code:
+
+ * HsSrcFile is an ordinary hs file which contains code,
+
+ * HsBootFile is an hs-boot file, which is used to break
+ recursive module imports (there will always be an
+ HsSrcFile associated with it), and
+
+ * HsigFile is an hsig file, which contains only type
+ signatures and is used to specify signatures for
+ modules.
+
+Syntactically, hs-boot files and hsig files are quite similar: they
+only include type signatures and must be associated with an
+actual HsSrcFile. isHsBootOrSig allows us to abstract over code
+which is indifferent to which. However, there are some important
+differences, mostly owing to the fact that hsigs are proper
+modules (you `import Sig` directly) whereas HsBootFiles are
+temporary placeholders (you `import {-# SOURCE #-} Mod).
+When we finish compiling the true implementation of an hs-boot,
+we replace the HomeModInfo with the real HsSrcFile. An HsigFile, on the
+other hand, is never replaced (in particular, we *cannot* use the
+HomeModInfo of the original HsSrcFile backing the signature, since it
+will export too many symbols.)
+
+Additionally, while HsSrcFile is the only Haskell file
+which has *code*, we do generate .o files for HsigFile, because
+this is how the recompilation checker figures out if a file
+needs to be recompiled. These are fake object files which
+should NOT be linked against.
+-}
+
+data HsBootOrSig
+ = HsBoot -- ^ .hs-boot file
+ | Hsig -- ^ .hsig file
+ deriving (Eq, Ord, Show)
data HscSource
- = HsSrcFile -- ^ .hs file
- | HsBootFile -- ^ .hs-boot file
- | HsigFile -- ^ .hsig file
+ -- | .hs file
+ = HsSrcFile
+ -- | .hs-boot or .hsig file
+ | HsBootOrSig !HsBootOrSig
deriving (Eq, Ord, Show)
+{-# COMPLETE HsSrcFile, HsBootFile, HsigFile #-}
+pattern HsBootFile, HsigFile :: HscSource
+pattern HsBootFile = HsBootOrSig HsBoot
+pattern HsigFile = HsBootOrSig Hsig
+
-- | Tests if an 'HscSource' is a boot file, primarily for constructing elements
-- of 'BuildModule'. We conflate signatures and modules because they are bound
-- in the same namespace; only boot interfaces can be disambiguated with
@@ -70,15 +85,18 @@ instance Binary HscSource where
_ -> return HsigFile
hscSourceString :: HscSource -> String
-hscSourceString HsSrcFile = ""
-hscSourceString HsBootFile = "[boot]"
-hscSourceString HsigFile = "[sig]"
+hscSourceString HsSrcFile = ""
+hscSourceString HsBootFile = "[boot]"
+hscSourceString HsigFile = "[sig]"
-- See Note [HscSource types]
isHsBootOrSig :: HscSource -> Bool
-isHsBootOrSig HsBootFile = True
-isHsBootOrSig HsigFile = True
-isHsBootOrSig _ = False
+isHsBootOrSig (HsBootOrSig _) = True
+isHsBootOrSig HsSrcFile = False
+
+isHsBootFile :: HscSource -> Bool
+isHsBootFile HsBootFile = True
+isHsBootFile _ = False
isHsigFile :: HscSource -> Bool
isHsigFile HsigFile = True
diff --git a/compiler/GHC/Types/TyThing/Ppr.hs b/compiler/GHC/Types/TyThing/Ppr.hs
index 2982635815..3f0505e492 100644
--- a/compiler/GHC/Types/TyThing/Ppr.hs
+++ b/compiler/GHC/Types/TyThing/Ppr.hs
@@ -28,7 +28,7 @@ import GHC.Core.TyCo.Ppr ( pprUserForAll, pprTypeApp )
import GHC.Iface.Decl ( tyThingToIfaceDecl )
import GHC.Iface.Syntax ( ShowSub(..), ShowHowMuch(..), AltPpr(..)
- , showToHeader, pprIfaceDecl )
+ , showToHeader, pprIfaceDecl )
import GHC.Utils.Outputable
diff --git a/compiler/GHC/Types/TyThing/Ppr.hs-boot b/compiler/GHC/Types/TyThing/Ppr.hs-boot
new file mode 100644
index 0000000000..388a21305c
--- /dev/null
+++ b/compiler/GHC/Types/TyThing/Ppr.hs-boot
@@ -0,0 +1,11 @@
+module GHC.Types.TyThing.Ppr (
+ pprTyThing,
+ pprTyThingInContext
+ ) where
+
+import {-# SOURCE #-} GHC.Iface.Type ( ShowSub )
+import GHC.Types.TyThing ( TyThing )
+import GHC.Utils.Outputable ( SDoc )
+
+pprTyThing :: ShowSub -> TyThing -> SDoc
+pprTyThingInContext :: ShowSub -> TyThing -> SDoc