[Git][ghc/ghc][wip/expand-do] some fixes after rebasing and doc changes
Apoorv Ingle (@ani)
gitlab at gitlab.haskell.org
Tue Jul 25 17:33:58 UTC 2023
Apoorv Ingle pushed to branch wip/expand-do at Glasgow Haskell Compiler / GHC
Commits:
edfcfc2b by Apoorv Ingle at 2023-07-25T12:33:45-05:00
some fixes after rebasing and doc changes
- - - - -
3 changed files:
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Tc/Gen/Pat.hs
Changes:
=====================================
compiler/GHC/Hs/Expr.hs
=====================================
@@ -462,9 +462,11 @@ type instance XXExpr GhcTc = XXExprGhcTc
data XXExprGhcRn
= ExpandedExpr
- {-# UNPACK #-} !(HsExpansion (HsExpr GhcRn) (HsExpr GhcRn))
+ {-# UNPACK #-} !(HsExpansion (HsExpr GhcRn) -- Original source expression
+ (HsExpr GhcRn)) -- Expanded expression
| ExpandedStmt
- {-# UNPACK #-} !(HsExpansion (ExprLStmt GhcRn) (HsExpr GhcRn))
+ {-# UNPACK #-} !(HsExpansion (ExprLStmt GhcRn) -- Original source do statement with location
+ (HsExpr GhcRn)) -- Expanded expression
| PopErrCtxt
{-# UNPACK #-} !(LHsExpr GhcRn)
-- Placeholder for identifying generated source locations in GhcRn phase
@@ -479,15 +481,15 @@ mkPopErrCtxtExpr a = XExpr (PopErrCtxt a)
-- and the two components of the expansion: original and
-- desugared expressions.
mkExpandedExpr
- :: HsExpr GhcRn -- ^ source expression
- -> HsExpr GhcRn -- ^ expanded expression
- -> HsExpr GhcRn -- ^ suitably wrapped 'HsExpansion'
+ :: HsExpr GhcRn -- ^ source expression
+ -> HsExpr GhcRn -- ^ expanded expression
+ -> HsExpr GhcRn -- ^ suitably wrapped 'HsExpansion'
mkExpandedExpr a b = XExpr (ExpandedExpr (HsExpanded a b))
mkExpandedStmt
- :: ExprLStmt GhcRn -- ^ source statement
+ :: ExprLStmt GhcRn -- ^ source statement
-> HsExpr GhcRn -- ^ expanded expression
- -> HsExpr GhcRn -- ^ suitably wrapped 'HsExpansion'
+ -> HsExpr GhcRn -- ^ suitably wrapped 'HsExpansion'
mkExpandedStmt a b = XExpr (ExpandedStmt (HsExpanded a b))
data XXExprGhcTc
@@ -495,10 +497,12 @@ data XXExprGhcTc
{-# UNPACK #-} !(HsWrap HsExpr)
| ExpansionExpr -- See Note [Rebindable syntax and HsExpansion] below
- {-# UNPACK #-} !(HsExpansion (HsExpr GhcRn) (HsExpr GhcTc))
+ {-# UNPACK #-} !(HsExpansion (HsExpr GhcRn) -- Original source expression
+ (HsExpr GhcTc)) -- Expanded expression typechecked
- | ExpansionStmt -- See Note [Rebindable syntax and HsExpansion] below
- {-# UNPACK #-} !(HsExpansion (ExprLStmt GhcRn) (HsExpr GhcTc))
+ | ExpansionStmt -- See Note [Expanding HsDo with HsExpansion] below
+ {-# UNPACK #-} !(HsExpansion (ExprLStmt GhcRn) -- Original source do statement with location
+ (HsExpr GhcTc)) -- Expanded expression typechecked
| ConLikeTc -- Result of typechecking a data-con
-- See Note [Typechecking data constructors] in
=====================================
compiler/GHC/Hs/Pat.hs
=====================================
@@ -618,7 +618,7 @@ isSimplePat p = case unLoc p of
_ -> Nothing
-- | Is this pattern boring from the perspective of pattern-match checking,
--- i.e. introduces no new pieces of long-dinstance information
+-- i.e. introduces no new pieces of long-distance information
-- which could influence pattern-match checking?
--
-- See Note [Boring patterns].
=====================================
compiler/GHC/Tc/Gen/Pat.hs
=====================================
@@ -1655,7 +1655,7 @@ checkGADT conlike ex_tvs arg_tys = \case
has_existentials = any (`elemVarSet` tyCoVarsOfTypes arg_tys) ex_tvs
-- | Very similar to GHC.Tc.Pat.isIrrefutableHsPat, but doesn't depend on type checking
--- does depend on the type environment however
+-- It does depend on the type environment however as we need to check ConPat case in more detail
isIrrefutableHsPatRn' :: TcGblEnv -> Bool -> LPat GhcRn -> TcM Bool
isIrrefutableHsPatRn' tc_env is_strict pat = goL pat
where
@@ -1707,5 +1707,9 @@ isIrrefutableHsPatRn' tc_env is_strict pat = goL pat
-- since we cannot know until the splice is evaluated.
go (SplicePat {}) = return False
+ -- The behavior of this case is unimportant, as GHC will throw an error shortly
+ -- after reaching this case for other reasons (see TcRnIllegalTypePattern).
+ go (EmbTyPat {}) = return True
+
go (XPat ext) = case ext of
HsPatExpanded _ pat -> go pat
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/edfcfc2b8f952f4c5ef6dd13eac8ca299bedc8be
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/edfcfc2b8f952f4c5ef6dd13eac8ca299bedc8be
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230725/8b4c0cff/attachment-0001.html>
More information about the ghc-commits
mailing list