Teo Camarasu pushed to branch wip/teo/move-out-bits-of-th-from-ghc-internal at Glasgow Haskell Compiler / GHC

Commits:

6 changed files:

Changes:

  • libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs
    ... ... @@ -555,20 +555,6 @@ pragInlD name inline rm phases
    555 555
     pragOpaqueD :: Quote m => Name -> m Dec
    
    556 556
     pragOpaqueD name = pure $ PragmaD $ OpaqueP name
    
    557 557
     
    
    558
    -{-# DEPRECATED pragSpecD "Please use 'pragSpecED' instead. 'pragSpecD' will be removed in GHC 9.18." #-}
    
    559
    -pragSpecD :: Quote m => Name -> m Type -> Phases -> m Dec
    
    560
    -pragSpecD n ty phases
    
    561
    -  = do
    
    562
    -      ty1    <- ty
    
    563
    -      pure $ PragmaD $ SpecialiseP n ty1 Nothing phases
    
    564
    -
    
    565
    -{-# DEPRECATED pragSpecInlD "Please use 'pragSpecInlED' instead. 'pragSpecInlD' will be removed in GHC 9.18." #-}
    
    566
    -pragSpecInlD :: Quote m => Name -> m Type -> Inline -> Phases -> m Dec
    
    567
    -pragSpecInlD n ty inline phases
    
    568
    -  = do
    
    569
    -      ty1    <- ty
    
    570
    -      pure $ PragmaD $ SpecialiseP n ty1 (Just inline) phases
    
    571
    -
    
    572 558
     pragSpecED :: Quote m
    
    573 559
                => Maybe [m (TyVarBndr ())] -> [m RuleBndr]
    
    574 560
                -> m Exp
    
    ... ... @@ -868,22 +854,6 @@ implicitParamT n t
    868 854
           t' <- t
    
    869 855
           pure $ ImplicitParamT n t'
    
    870 856
     
    
    871
    -{-# DEPRECATED classP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please use 'conT' and 'appT'." #-}
    
    872
    -classP :: Quote m => Name -> [m Type] -> m Pred
    
    873
    -classP cla tys
    
    874
    -  = do
    
    875
    -      tysl <- sequenceA tys
    
    876
    -      pure (foldl AppT (ConT cla) tysl)
    
    877
    -
    
    878
    -{-# DEPRECATED equalP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please see 'equalityT'." #-}
    
    879
    -equalP :: Quote m => m Type -> m Type -> m Pred
    
    880
    -equalP tleft tright
    
    881
    -  = do
    
    882
    -      tleft1  <- tleft
    
    883
    -      tright1 <- tright
    
    884
    -      eqT <- equalityT
    
    885
    -      pure (foldl AppT eqT [tleft1, tright1])
    
    886
    -
    
    887 857
     promotedT :: Quote m => Name -> m Type
    
    888 858
     promotedT = pure . PromotedT
    
    889 859
     
    
    ... ... @@ -906,20 +876,6 @@ noSourceStrictness = pure NoSourceStrictness
    906 876
     sourceLazy         = pure SourceLazy
    
    907 877
     sourceStrict       = pure SourceStrict
    
    908 878
     
    
    909
    -{-# DEPRECATED isStrict
    
    910
    -    ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
    
    911
    -     "Example usage: 'bang noSourceUnpackedness sourceStrict'"] #-}
    
    912
    -{-# DEPRECATED notStrict
    
    913
    -    ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
    
    914
    -     "Example usage: 'bang noSourceUnpackedness noSourceStrictness'"] #-}
    
    915
    -{-# DEPRECATED unpacked
    
    916
    -    ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
    
    917
    -     "Example usage: 'bang sourceUnpack sourceStrict'"] #-}
    
    918
    -isStrict, notStrict, unpacked :: Quote m => m Strict
    
    919
    -isStrict = bang noSourceUnpackedness sourceStrict
    
    920
    -notStrict = bang noSourceUnpackedness noSourceStrictness
    
    921
    -unpacked = bang sourceUnpack sourceStrict
    
    922
    -
    
    923 879
     bang :: Quote m => m SourceUnpackedness -> m SourceStrictness -> m Bang
    
    924 880
     bang u s = do u' <- u
    
    925 881
                   s' <- s
    
    ... ... @@ -931,16 +887,6 @@ bangType = liftA2 (,)
    931 887
     varBangType :: Quote m => Name -> m BangType -> m VarBangType
    
    932 888
     varBangType v bt = (\(b, t) -> (v, b, t)) <$> bt
    
    933 889
     
    
    934
    -{-# DEPRECATED strictType
    
    935
    -               "As of @template-haskell-2.11.0.0@, 'StrictType' has been replaced by 'BangType'. Please use 'bangType' instead." #-}
    
    936
    -strictType :: Quote m => m Strict -> m Type -> m StrictType
    
    937
    -strictType = bangType
    
    938
    -
    
    939
    -{-# DEPRECATED varStrictType
    
    940
    -               "As of @template-haskell-2.11.0.0@, 'VarStrictType' has been replaced by 'VarBangType'. Please use 'varBangType' instead." #-}
    
    941
    -varStrictType :: Quote m => Name -> m StrictType -> m VarStrictType
    
    942
    -varStrictType = varBangType
    
    943
    -
    
    944 890
     -- * Type Literals
    
    945 891
     
    
    946 892
     -- 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
    33 33
     import qualified GHC.Internal.TH.Lib as Lib (litE)  -- See wrinkle (W4) of Note [Tracking dependencies on primitives]
    
    34 34
     
    
    35 35
     import GHC.Internal.Data.Either
    
    36
    -import GHC.Internal.Type.Reflection
    
    37 36
     import GHC.Internal.Data.Bool
    
    38 37
     import GHC.Internal.Base hiding (NonEmpty(..), Type, Module, inline)
    
    39 38
     import GHC.Internal.Data.Foldable
    

  • libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
    ... ... @@ -844,12 +844,6 @@ addTempFile suffix = Q (qAddTempFile suffix)
    844 844
     addTopDecls :: [Dec] -> Q ()
    
    845 845
     addTopDecls ds = Q (qAddTopDecls ds)
    
    846 846
     
    
    847
    --- |
    
    848
    -addForeignFile :: ForeignSrcLang -> String -> Q ()
    
    849
    -addForeignFile = addForeignSource
    
    850
    -{-# DEPRECATED addForeignFile
    
    851
    -               "Use 'Language.Haskell.TH.Syntax.addForeignSource' instead"
    
    852
    -  #-} -- deprecated in 8.6
    
    853 847
     
    
    854 848
     -- | Emit a foreign file which will be compiled and linked to the object for
    
    855 849
     -- 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
    395 395
     
    
    396 396
     conP :: Quote m => Name -> [m Pat] -> m Pat
    
    397 397
     conP n xs = Internal.conP n [] xs
    
    398
    +
    
    399
    +
    
    400
    +--------------------------------------------------------------------------------
    
    401
    +-- * Constraint predicates (deprecated)
    
    402
    +
    
    403
    +{-# DEPRECATED classP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please use 'conT' and 'appT'." #-}
    
    404
    +classP :: Quote m => Name -> [m Type] -> m Pred
    
    405
    +classP cla tys
    
    406
    +  = do
    
    407
    +      tysl <- sequenceA tys
    
    408
    +      pure (foldl AppT (ConT cla) tysl)
    
    409
    +
    
    410
    +{-# DEPRECATED equalP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please see 'equalityT'." #-}
    
    411
    +equalP :: Quote m => m Type -> m Type -> m Pred
    
    412
    +equalP tleft tright
    
    413
    +  = do
    
    414
    +      tleft1  <- tleft
    
    415
    +      tright1 <- tright
    
    416
    +      eqT <- equalityT
    
    417
    +      pure (foldl AppT eqT [tleft1, tright1])
    
    418
    +
    
    419
    +--------------------------------------------------------------------------------
    
    420
    +-- * Strictness queries (deprecated)
    
    421
    +{-# DEPRECATED isStrict
    
    422
    +    ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
    
    423
    +     "Example usage: 'bang noSourceUnpackedness sourceStrict'"] #-}
    
    424
    +{-# DEPRECATED notStrict
    
    425
    +    ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
    
    426
    +     "Example usage: 'bang noSourceUnpackedness noSourceStrictness'"] #-}
    
    427
    +{-# DEPRECATED unpacked
    
    428
    +    ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
    
    429
    +     "Example usage: 'bang sourceUnpack sourceStrict'"] #-}
    
    430
    +isStrict, notStrict, unpacked :: Quote m => m Strict
    
    431
    +isStrict = bang noSourceUnpackedness sourceStrict
    
    432
    +notStrict = bang noSourceUnpackedness noSourceStrictness
    
    433
    +unpacked = bang sourceUnpack sourceStrict
    
    434
    +
    
    435
    +{-# DEPRECATED strictType
    
    436
    +               "As of @template-haskell-2.11.0.0@, 'StrictType' has been replaced by 'BangType'. Please use 'bangType' instead." #-}
    
    437
    +strictType :: Quote m => m Strict -> m Type -> m StrictType
    
    438
    +strictType = bangType
    
    439
    +
    
    440
    +{-# DEPRECATED varStrictType
    
    441
    +               "As of @template-haskell-2.11.0.0@, 'VarStrictType' has been replaced by 'VarBangType'. Please use 'varBangType' instead." #-}
    
    442
    +varStrictType :: Quote m => Name -> m StrictType -> m VarStrictType
    
    443
    +varStrictType = varBangType
    
    444
    +
    
    445
    +--------------------------------------------------------------------------------
    
    446
    +-- * Specialisation pragmas (deprecated)
    
    447
    +
    
    448
    +{-# DEPRECATED pragSpecD "Please use 'pragSpecED' instead. 'pragSpecD' will be removed in GHC 9.18." #-}
    
    449
    +pragSpecD :: Quote m => Name -> m Type -> Phases -> m Dec
    
    450
    +pragSpecD n ty phases
    
    451
    +  = do
    
    452
    +      ty1    <- ty
    
    453
    +      pure $ PragmaD $ SpecialiseP n ty1 Nothing phases
    
    454
    +
    
    455
    +{-# DEPRECATED pragSpecInlD "Please use 'pragSpecInlED' instead. 'pragSpecInlD' will be removed in GHC 9.18." #-}
    
    456
    +pragSpecInlD :: Quote m => Name -> m Type -> Inline -> Phases -> m Dec
    
    457
    +pragSpecInlD n ty inline phases
    
    458
    +  = do
    
    459
    +      ty1    <- ty
    
    460
    +      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 )
    208 208
     -- This module completely re-exports 'GHC.Boot.TH.Syntax',
    
    209 209
     -- and exports additionally functions that depend on filepath.
    
    210 210
     
    
    211
    +-- |
    
    212
    +addForeignFile :: ForeignSrcLang -> String -> Q ()
    
    213
    +addForeignFile = addForeignSource
    
    214
    +{-# DEPRECATED addForeignFile
    
    215
    +               "Use 'Language.Haskell.TH.Syntax.addForeignSource' instead"
    
    216
    +  #-} -- deprecated in 8.6
    
    217
    +
    
    211 218
     -- | The input is a filepath, which if relative is offset by the package root.
    
    212 219
     makeRelativeToProject :: FilePath -> Q FilePath
    
    213 220
     makeRelativeToProject fp | isRelative fp = do
    

  • rts/Messages.c
    ... ... @@ -187,6 +187,10 @@ uint32_t messageBlackHole(Capability *cap, MessageBlackHole *msg)
    187 187
             return 0;
    
    188 188
         }
    
    189 189
     
    
    190
    +    if(bh_info == &stg_WHITEHOLE_info){
    
    191
    +      fprintf(stderr, "\noh nooo %xll\n", ((StgInd*)bh)->indirectee);
    
    192
    +    }
    
    193
    +
    
    190 194
         // The blackhole must indirect to a TSO, a BLOCKING_QUEUE, an IND,
    
    191 195
         // or a value.
    
    192 196
         StgClosure *p;