[Git][ghc/ghc][wip/teo/move-out-bits-of-th-from-ghc-internal] 2 commits: template-haskell: move deprecated parts of interface out of ghc-internal

Teo Camarasu pushed to branch wip/teo/move-out-bits-of-th-from-ghc-internal at Glasgow Haskell Compiler / GHC Commits: 19ea95f7 by Teo Camarasu at 2025-08-01T11:15:29+01:00 template-haskell: move deprecated parts of interface out of ghc-internal Since these are deprecated we know that they won't be used in GHC code. The only one we keep is `report`, which is used to implement the non-deprecated versions. - - - - - e734fb21 by Teo Camarasu at 2025-08-01T15:22:56+01:00 fixup! template-haskell: move some identifiers from ghc-internal to template-haskell - - - - - 6 changed files: - libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs - libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - rts/Messages.c Changes: ===================================== libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs ===================================== @@ -555,20 +555,6 @@ pragInlD name inline rm phases pragOpaqueD :: Quote m => Name -> m Dec pragOpaqueD name = pure $ PragmaD $ OpaqueP name -{-# DEPRECATED pragSpecD "Please use 'pragSpecED' instead. 'pragSpecD' will be removed in GHC 9.18." #-} -pragSpecD :: Quote m => Name -> m Type -> Phases -> m Dec -pragSpecD n ty phases - = do - ty1 <- ty - pure $ PragmaD $ SpecialiseP n ty1 Nothing phases - -{-# DEPRECATED pragSpecInlD "Please use 'pragSpecInlED' instead. 'pragSpecInlD' will be removed in GHC 9.18." #-} -pragSpecInlD :: Quote m => Name -> m Type -> Inline -> Phases -> m Dec -pragSpecInlD n ty inline phases - = do - ty1 <- ty - pure $ PragmaD $ SpecialiseP n ty1 (Just inline) phases - pragSpecED :: Quote m => Maybe [m (TyVarBndr ())] -> [m RuleBndr] -> m Exp @@ -868,22 +854,6 @@ implicitParamT n t t' <- t pure $ ImplicitParamT n t' -{-# DEPRECATED classP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please use 'conT' and 'appT'." #-} -classP :: Quote m => Name -> [m Type] -> m Pred -classP cla tys - = do - tysl <- sequenceA tys - pure (foldl AppT (ConT cla) tysl) - -{-# DEPRECATED equalP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please see 'equalityT'." #-} -equalP :: Quote m => m Type -> m Type -> m Pred -equalP tleft tright - = do - tleft1 <- tleft - tright1 <- tright - eqT <- equalityT - pure (foldl AppT eqT [tleft1, tright1]) - promotedT :: Quote m => Name -> m Type promotedT = pure . PromotedT @@ -906,20 +876,6 @@ noSourceStrictness = pure NoSourceStrictness sourceLazy = pure SourceLazy sourceStrict = pure SourceStrict -{-# DEPRECATED isStrict - ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ", - "Example usage: 'bang noSourceUnpackedness sourceStrict'"] #-} -{-# DEPRECATED notStrict - ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ", - "Example usage: 'bang noSourceUnpackedness noSourceStrictness'"] #-} -{-# DEPRECATED unpacked - ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ", - "Example usage: 'bang sourceUnpack sourceStrict'"] #-} -isStrict, notStrict, unpacked :: Quote m => m Strict -isStrict = bang noSourceUnpackedness sourceStrict -notStrict = bang noSourceUnpackedness noSourceStrictness -unpacked = bang sourceUnpack sourceStrict - bang :: Quote m => m SourceUnpackedness -> m SourceStrictness -> m Bang bang u s = do u' <- u s' <- s @@ -931,16 +887,6 @@ bangType = liftA2 (,) varBangType :: Quote m => Name -> m BangType -> m VarBangType varBangType v bt = (\(b, t) -> (v, b, t)) <$> bt -{-# DEPRECATED strictType - "As of @template-haskell-2.11.0.0@, 'StrictType' has been replaced by 'BangType'. Please use 'bangType' instead." #-} -strictType :: Quote m => m Strict -> m Type -> m StrictType -strictType = bangType - -{-# DEPRECATED varStrictType - "As of @template-haskell-2.11.0.0@, 'VarStrictType' has been replaced by 'VarBangType'. Please use 'varBangType' instead." #-} -varStrictType :: Quote m => Name -> m StrictType -> m VarStrictType -varStrictType = varBangType - -- * Type Literals -- MonadFail here complicates things (a lot) because it would mean we would ===================================== libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs ===================================== @@ -33,7 +33,6 @@ import GHC.Internal.TH.Syntax import qualified GHC.Internal.TH.Lib as Lib (litE) -- See wrinkle (W4) of Note [Tracking dependencies on primitives] import GHC.Internal.Data.Either -import GHC.Internal.Type.Reflection import GHC.Internal.Data.Bool import GHC.Internal.Base hiding (NonEmpty(..), Type, Module, inline) import GHC.Internal.Data.Foldable ===================================== libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs ===================================== @@ -844,12 +844,6 @@ addTempFile suffix = Q (qAddTempFile suffix) addTopDecls :: [Dec] -> Q () addTopDecls ds = Q (qAddTopDecls ds) --- | -addForeignFile :: ForeignSrcLang -> String -> Q () -addForeignFile = addForeignSource -{-# DEPRECATED addForeignFile - "Use 'Language.Haskell.TH.Syntax.addForeignSource' instead" - #-} -- deprecated in 8.6 -- | Emit a foreign file which will be compiled and linked to the object for -- the current module. Currently only languages that can be compiled with ===================================== libraries/template-haskell/Language/Haskell/TH/Lib.hs ===================================== @@ -395,3 +395,66 @@ mdoE = Internal.mdoE Nothing conP :: Quote m => Name -> [m Pat] -> m Pat conP n xs = Internal.conP n [] xs + + +-------------------------------------------------------------------------------- +-- * Constraint predicates (deprecated) + +{-# DEPRECATED classP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please use 'conT' and 'appT'." #-} +classP :: Quote m => Name -> [m Type] -> m Pred +classP cla tys + = do + tysl <- sequenceA tys + pure (foldl AppT (ConT cla) tysl) + +{-# DEPRECATED equalP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please see 'equalityT'." #-} +equalP :: Quote m => m Type -> m Type -> m Pred +equalP tleft tright + = do + tleft1 <- tleft + tright1 <- tright + eqT <- equalityT + pure (foldl AppT eqT [tleft1, tright1]) + +-------------------------------------------------------------------------------- +-- * Strictness queries (deprecated) +{-# DEPRECATED isStrict + ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ", + "Example usage: 'bang noSourceUnpackedness sourceStrict'"] #-} +{-# DEPRECATED notStrict + ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ", + "Example usage: 'bang noSourceUnpackedness noSourceStrictness'"] #-} +{-# DEPRECATED unpacked + ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ", + "Example usage: 'bang sourceUnpack sourceStrict'"] #-} +isStrict, notStrict, unpacked :: Quote m => m Strict +isStrict = bang noSourceUnpackedness sourceStrict +notStrict = bang noSourceUnpackedness noSourceStrictness +unpacked = bang sourceUnpack sourceStrict + +{-# DEPRECATED strictType + "As of @template-haskell-2.11.0.0@, 'StrictType' has been replaced by 'BangType'. Please use 'bangType' instead." #-} +strictType :: Quote m => m Strict -> m Type -> m StrictType +strictType = bangType + +{-# DEPRECATED varStrictType + "As of @template-haskell-2.11.0.0@, 'VarStrictType' has been replaced by 'VarBangType'. Please use 'varBangType' instead." #-} +varStrictType :: Quote m => Name -> m StrictType -> m VarStrictType +varStrictType = varBangType + +-------------------------------------------------------------------------------- +-- * Specialisation pragmas (deprecated) + +{-# DEPRECATED pragSpecD "Please use 'pragSpecED' instead. 'pragSpecD' will be removed in GHC 9.18." #-} +pragSpecD :: Quote m => Name -> m Type -> Phases -> m Dec +pragSpecD n ty phases + = do + ty1 <- ty + pure $ PragmaD $ SpecialiseP n ty1 Nothing phases + +{-# DEPRECATED pragSpecInlD "Please use 'pragSpecInlED' instead. 'pragSpecInlD' will be removed in GHC 9.18." #-} +pragSpecInlD :: Quote m => Name -> m Type -> Inline -> Phases -> m Dec +pragSpecInlD n ty inline phases + = do + ty1 <- ty + pure $ PragmaD $ SpecialiseP n ty1 (Just inline) phases ===================================== libraries/template-haskell/Language/Haskell/TH/Syntax.hs ===================================== @@ -208,6 +208,13 @@ import GHC.Lexeme ( startsVarSym, startsVarId ) -- This module completely re-exports 'GHC.Boot.TH.Syntax', -- and exports additionally functions that depend on filepath. +-- | +addForeignFile :: ForeignSrcLang -> String -> Q () +addForeignFile = addForeignSource +{-# DEPRECATED addForeignFile + "Use 'Language.Haskell.TH.Syntax.addForeignSource' instead" + #-} -- deprecated in 8.6 + -- | The input is a filepath, which if relative is offset by the package root. makeRelativeToProject :: FilePath -> Q FilePath makeRelativeToProject fp | isRelative fp = do ===================================== rts/Messages.c ===================================== @@ -187,6 +187,10 @@ uint32_t messageBlackHole(Capability *cap, MessageBlackHole *msg) return 0; } + if(bh_info == &stg_WHITEHOLE_info){ + fprintf(stderr, "\noh nooo %xll\n", ((StgInd*)bh)->indirectee); + } + // The blackhole must indirect to a TSO, a BLOCKING_QUEUE, an IND, // or a value. StgClosure *p; View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c6c7dd648615b74d4854948e9453e71... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c6c7dd648615b74d4854948e9453e71... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Teo Camarasu (@teo)