[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: We can't UNPACK multi-constructor GADTs

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Wed Mar 12 03:11:58 UTC 2025



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
b6d5b091 by Simon Peyton Jones at 2025-03-11T22:39:23-04:00
We can't UNPACK multi-constructor GADTs

This MR fixes #25672

See Note [Unpacking GADTs and existentials] in GHC.Types.Id.Make

- - - - -
8eae151d by Teo Camarasu at 2025-03-11T22:40:00-04:00
template-haskell: Add explicit exports lists to all remaining modules

- - - - -
db621b58 by Teo Camarasu at 2025-03-11T22:40:00-04:00
template-haskell: fix haddocks

It seems that we need a direct dependency on ghc-internal, otherwise
Haddock cannot find our haddocks

The bug seems to be caused by Hadrian because if I rebuild with
cabal-install (without this extra dependency) then I get accurate
Haddocks.

Resolves #25705

- - - - -
59e77cf4 by Ben Gamari at 2025-03-11T23:11:39-04:00
mk-ghcup-metadata: Clean up and add type annotations

Getting this file right has historically been quite painful as it is a
dynamically-typed script running only late in the release pipeline.

- - - - -
df68f43d by Ben Gamari at 2025-03-11T23:11:40-04:00
rts: Drop imports of pthreads functions in cmm sources

These are no longer used. I noticed these while looking for uses of
__PIC__ in Cmm sources.

- - - - -


16 changed files:

- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Types/Id/Make.hs
- libraries/template-haskell/Language/Haskell/TH/Ppr.hs
- libraries/template-haskell/Language/Haskell/TH/PprLib.hs
- libraries/template-haskell/Language/Haskell/TH/Syntax.hs
- libraries/template-haskell/template-haskell.cabal.in
- rts/HeapStackCheck.cmm
- rts/PrimOps.cmm
- + testsuite/tests/simplCore/should_fail/T25672.hs
- + testsuite/tests/simplCore/should_fail/T25672.stderr
- testsuite/tests/simplCore/should_fail/all.T
- utils/haddock/html-test/ref/QuasiExpr.html
- utils/haddock/html-test/ref/TH.html
- utils/haddock/html-test/ref/Threaded_TH.html


Changes:

=====================================
.gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
=====================================
@@ -43,10 +43,9 @@ import json
 import urllib.parse
 import fetch_gitlab
 
-def eprint(*args, **kwargs):
+def eprint(*args, **kwargs) -> None:
     print(*args, file=sys.stderr, **kwargs)
 
-
 gl = gitlab.Gitlab('https://gitlab.haskell.org', per_page=100)
 
 # TODO: Take this file as an argument
@@ -60,6 +59,10 @@ with open(metadata_file, 'r') as f:
 
 eprint(f"Supported platforms: {job_mapping.keys()}")
 
+# Mapping from job name to its corresponding Job
+JobMap = Dict[str, gitlab.Job]
+
+GhcupDist = object
 
 # Artifact precisely specifies a job what the bindist to download is called.
 class Artifact(NamedTuple):
@@ -86,32 +89,32 @@ test_artifact = Artifact('source-tarball'
                         , 'ghc-{version}/testsuite'
                         , 'ghc{version}-testsuite')
 
-def debian(n, arch='x86_64'):
-    return linux_platform(arch, "{arch}-linux-deb{n}".format(arch=arch, n=n))
-
-def darwin(arch):
+def darwin(arch: str) -> PlatformSpec:
     return PlatformSpec ( '{arch}-darwin'.format(arch=arch)
                         , 'ghc-{version}-{arch}-apple-darwin'.format(arch=arch, version="{version}") )
 
 windowsArtifact = PlatformSpec ( 'x86_64-windows'
                                , 'ghc-{version}-x86_64-unknown-mingw32' )
 
-def centos(n, arch='x86_64'):
+def debian(n: int, arch: str='x86_64') -> PlatformSpec:
+    return linux_platform(arch, "{arch}-linux-deb{n}".format(arch=arch, n=n))
+
+def centos(n: int, arch='x86_64') -> PlatformSpec:
     return linux_platform(arch, "{arch}-linux-centos{n}".format(n=n,arch=arch))
 
-def fedora(n, arch='x86_64'):
+def fedora(n: int, arch='x86_64') -> PlatformSpec:
     return linux_platform(arch, "{arch}-linux-fedora{n}".format(n=n,arch=arch))
 
-def alpine(n, arch='x86_64'):
+def alpine(n: str, arch='x86_64') -> PlatformSpec:
     return linux_platform(arch, "{arch}-linux-alpine{n}".format(n=n,arch=arch))
 
-def rocky(n, arch='x86_64'):
+def rocky(n: int, arch='x86_64') -> PlatformSpec:
     return linux_platform(arch, "{arch}-linux-rocky{n}".format(n=n,arch=arch))
 
-def ubuntu(n, arch='x86_64'):
+def ubuntu(n: str, arch='x86_64') -> PlatformSpec:
     return linux_platform(arch, "{arch}-linux-ubuntu{n}".format(n=n,arch=arch))
 
-def linux_platform(arch, opsys):
+def linux_platform(arch: str, opsys: str) -> PlatformSpec:
     return PlatformSpec( opsys, 'ghc-{version}-{arch}-unknown-linux'.format(version="{version}", arch=arch) )
 
 
@@ -135,10 +138,10 @@ def download_and_hash(url):
     hash_cache[url] = digest
     return digest
 
-uri_to_anchor_cache=dict()
+uri_to_anchor_cache = {} # type: Dict[str, str]
 
 # Make the metadata for one platform.
-def mk_one_metadata(release_mode, version, job_map, artifact):
+def mk_one_metadata(release_mode: bool, version: str, job_map: JobMap, artifact: Artifact) -> GhcupDist:
     job_id = job_map[artifact.job_name].id
 
     url = base_url.format(job_id=job_id, artifact_name=urllib.parse.quote_plus(artifact.download_name.format(version=version)))
@@ -181,7 +184,7 @@ def mk_one_metadata(release_mode, version, job_map, artifact):
 
 # Turns a platform into an Artifact respecting pipeline_type
 # Looks up the right job to use from the .gitlab/jobs-metadata.json file
-def mk_from_platform(pipeline_type, platform):
+def mk_from_platform(pipeline_type: str, platform: PlatformSpec) -> Artifact:
     info = job_mapping[platform.name][pipeline_type]
     eprint(f"From {platform.name} / {pipeline_type} selecting {info['name']}")
     return Artifact(info['name']
@@ -192,7 +195,7 @@ def mk_from_platform(pipeline_type, platform):
 
 
 # Generate the new metadata for a specific GHC mode etc
-def mk_new_yaml(release_mode, version, date, pipeline_type, job_map):
+def mk_new_yaml(release_mode: bool, version: str, date: str, pipeline_type, job_map: JobMap) -> object:
     def mk(platform):
         eprint("\n=== " + platform.name + " " + ('=' * (75 - len(platform.name))))
         return mk_one_metadata(release_mode, version, job_map, mk_from_platform(pipeline_type, platform))
@@ -201,7 +204,7 @@ def mk_new_yaml(release_mode, version, date, pipeline_type, job_map):
     ubuntu1804 = mk(ubuntu("18_04"))
     ubuntu2004 = mk(ubuntu("20_04"))
     ubuntu2204 = mk(ubuntu("22_04"))
-    rocky8 = mk(rocky("8"))
+    rocky8 = mk(rocky(8))
     centos7 = mk(centos(7))
     fedora33 = mk(fedora(33))
     darwin_x86 = mk(darwin("x86_64"))
@@ -301,14 +304,14 @@ def mk_new_yaml(release_mode, version, date, pipeline_type, job_map):
         }
 
 
-def setNightlyTags(ghcup_metadata):
+def setNightlyTags(ghcup_metadata: dict) -> None:
     for version in ghcup_metadata['ghcupDownloads']['GHC']:
         if "LatestNightly" in ghcup_metadata['ghcupDownloads']['GHC'][version]["viTags"]:
             ghcup_metadata['ghcupDownloads']['GHC'][version]["viTags"].remove("LatestNightly")
             ghcup_metadata['ghcupDownloads']['GHC'][version]["viTags"].append("Nightly")
 
 
-def mk_dumper(version):
+def mk_dumper(version: str) -> yaml.Dumper:
   class CustomAliasDumper(yaml.Dumper):
       def __init__(self, *args, **kwargs):
           super().__init__(*args, **kwargs)


=====================================
compiler/GHC/Core/DataCon.hs
=====================================
@@ -1018,6 +1018,9 @@ instance Data.Data DataCon where
     gunfold _ _  = error "gunfold"
     dataTypeOf _ = mkNoRepType "DataCon"
 
+instance Outputable HsSrcBang where
+    ppr (HsSrcBang _source_text bang) = ppr bang
+
 instance Outputable HsBang where
     ppr (HsBang prag mark) = ppr prag <+> ppr mark
 


=====================================
compiler/GHC/Tc/TyCl.hs
=====================================
@@ -4817,6 +4817,8 @@ checkValidDataCon dflags existential_ok tc con
         ; traceTc "Done validity of data con" $
           vcat [ ppr con
                , text "Datacon wrapper type:" <+> ppr (dataConWrapperType con)
+               , text "Datacon src bangs:" <+> ppr (dataConSrcBangs con)
+               , text "Datacon impl bangs:" <+> ppr (dataConImplBangs con)
                , text "Datacon rep type:" <+> ppr (dataConRepType con)
                , text "Datacon display type:" <+> ppr data_con_display_type
                , text "Rep typcon binders:" <+> ppr (tyConBinders (dataConTyCon con))


=====================================
compiler/GHC/Types/Id/Make.hs
=====================================
@@ -1540,39 +1540,87 @@ shouldUnpackArgTy bang_opts prag fam_envs arg_ty
 
 
 
--- Given a type already assumed to have been normalized by topNormaliseType,
--- unpackable_type_datacons ty = Just datacons
--- iff ty is of the form
---     T ty1 .. tyn
--- and T is an algebraic data type (not newtype), in which no data
--- constructors have existentials, and datacons is the list of data
--- constructors of T.
 unpackable_type_datacons :: Type -> Maybe [DataCon]
+-- Given a type already assumed to have been normalized by topNormaliseType,
+--    unpackable_type_datacons (T ty1 .. tyn) = Just datacons
+-- iff the type can be unpacked (see Note [Unpacking GADTs and existentials])
+-- and `datacons` are the data constructors of T
 unpackable_type_datacons ty
   | Just (tc, _) <- splitTyConApp_maybe ty
-  , not (isNewTyCon tc)  -- Even though `ty` has been normalised, it could still
-                         -- be a /recursive/ newtype, so we must check for that
+  , not (isNewTyCon tc)
+      -- isNewTyCon: even though `ty` has been normalised, whic includes looking
+      -- through newtypes, it could still be a /recursive/ newtype, so we must
+      -- check for that case
   , Just cons <- tyConDataCons_maybe tc
-  , not (null cons)      -- Don't upack nullary sums; no need.
-                         -- They already take zero bits
-  , all (null . dataConExTyCoVars) cons
-  = Just cons -- See Note [Unpacking GADTs and existentials]
+  , unpackable_cons cons
+  = Just cons
   | otherwise
   = Nothing
+  where
+    unpackable_cons :: [DataCon] -> Bool
+    -- True if we can unpack a value of type (T t1 .. tn),
+    -- where T is an algebraic data type with these constructors
+    -- See Note [Unpacking GADTs and existentials]
+    unpackable_cons []   -- Don't unpack nullary sums; no need.
+      = False            -- They already take zero bits; see (UC0)
+
+    unpackable_cons [con]   -- Exactly one data constructor; see (UC1)
+      = null (dataConExTyCoVars con)
+
+    unpackable_cons cons  -- More than one data constructor; see (UC2)
+      = all isVanillaDataCon cons
 
 {-
 Note [Unpacking GADTs and existentials]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-There is nothing stopping us unpacking a data type with equality
-components, like
-  data Equal a b where
-    Equal :: Equal a a
-
-And it'd be fine to unpack a product type with existential components
-too, but that would require a bit more plumbing, so currently we don't.
+Can we unpack a value of an algebraic data type T? For example
+   data D a = MkD {-# UNPACK #-} (T a)
+Can we unpack that (T a) field?
+
+Three cases to consider in `unpackable_cons`
+
+(UC0) No data constructors; a nullary sum type.  This already takes zero
+      bits so there is no point in unpacking it.
+
+(UC1) Single-constructor types (products).  We can just represent it by
+   its fields. For example, if `T` is defined as:
+      data T a = MkT a a Int
+   then we can unpack it as follows.  The worker for MkD takes three unpacked fields:
+       data D a = MkD a a Int
+       $MkD :: T a -> D a
+       $MkD (MkT a1 a2 i) = MkD a1 a2 i
+
+   We currently /can't/ do this if T has existentially-bound type variables,
+   hence:   null (dataConExTyCoVars con)   in `unpackable_cons`.
+   But see also (UC3) below.
+
+   But we /can/ do it for (some) GADTs, such as:
+      data Equal a b where { Equal :: Equal a a }
+      data Wom a where { Wom1 :: Int -> Wom Bool }
+   We will get a MkD constructor that includes some coercion arguments,
+   but that is fine.   See #14978.  We still can't accommodate existentials,
+   but these particular examples don't use existentials.
+
+(UC2) Multi-constructor types, e.g.
+        data T a = T1 a | T2 Int a
+  Here we unpack the field to an unboxed sum type, thus:
+    data D a = MkD (# a | (# Int, a #) #)
+
+  However, now we can't deal with GADTs at all, because we'd need an
+  unboxed sum whose component was a unboxed tuple, whose component(s)
+  have kind (CONSTRAINT r); and that's not well-kinded.  Hence the
+    all isVanillaDataCon
+  condition in `unpackable_cons`. See #25672.
+
+(UC3)  For single-constructor types, with some more plumbing we could
+   allow existentials. e.g.
+       data T a = forall b. MkT a (b->Int) b
+   could unpack to
+       data D a = forall b. MkD a (b->Int) b
+       $MkD :: T a -> D a
+       $MkD (MkT @b x f y) = MkD @b x f y
+   Eminently possible, but more plumbing needed.
 
-So for now we require: null (dataConExTyCoVars data_con)
-See #14978
 
 Note [Unpack one-wide fields]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~


=====================================
libraries/template-haskell/Language/Haskell/TH/Ppr.hs
=====================================
@@ -1,9 +1,91 @@
 {-# LANGUAGE Safe #-}
 
--- | contains a prettyprinter for the
--- Template Haskell datatypes
-module Language.Haskell.TH.Ppr
-  ( module GHC.Boot.TH.Ppr )
-  where
+{- | contains a prettyprinter for the
+Template Haskell datatypes
+-}
+module Language.Haskell.TH.Ppr (
+    appPrec,
+    bar,
+    bytesToString,
+    commaSep,
+    commaSepApplied,
+    commaSepWith,
+    fromTANormal,
+    funPrec,
+    hashParens,
+    isStarT,
+    isSymOcc,
+    nestDepth,
+    noPrec,
+    opPrec,
+    parensIf,
+    pprBangType,
+    pprBndrVis,
+    pprBody,
+    pprClause,
+    pprCtxWith,
+    pprCxt,
+    pprExp,
+    pprFields,
+    pprFixity,
+    pprForall,
+    pprForall',
+    pprForallVis,
+    pprFunArgType,
+    pprGadtRHS,
+    pprGuarded,
+    pprInfixExp,
+    pprInfixT,
+    pprLit,
+    pprMatchPat,
+    pprMaybeExp,
+    pprNamespaceSpecifier,
+    pprParendType,
+    pprParendTypeArg,
+    pprPat,
+    pprPatSynSig,
+    pprPatSynType,
+    pprPrefixOcc,
+    pprRecFields,
+    pprStrictType,
+    pprString,
+    pprTyApp,
+    pprTyLit,
+    pprType,
+    pprVarBangType,
+    pprVarStrictType,
+    ppr_bndrs,
+    ppr_ctx_preds_with,
+    ppr_cxt_preds,
+    ppr_data,
+    ppr_dec,
+    ppr_deriv_clause,
+    ppr_deriv_strategy,
+    ppr_newtype,
+    ppr_overlap,
+    ppr_sig,
+    ppr_tf_head,
+    ppr_tySyn,
+    ppr_type_data,
+    ppr_typedef,
+    pprint,
+    qualPrec,
+    quoteParens,
+    semiSep,
+    semiSepWith,
+    sepWith,
+    showtextl,
+    sigPrec,
+    split,
+    unboxedSumBars,
+    unopPrec,
+    where_clause,
+    ForallVisFlag (..),
+    Ppr (..),
+    PprFlag (..),
+    Precedence,
+    TypeArg (..),
+)
+where
 
 import GHC.Boot.TH.Ppr


=====================================
libraries/template-haskell/Language/Haskell/TH/PprLib.hs
=====================================
@@ -1,8 +1,56 @@
 {-# LANGUAGE Safe #-}
 
 -- | Monadic front-end to Text.PrettyPrint
-module Language.Haskell.TH.PprLib
-  ( module GHC.Boot.TH.PprLib )
-  where
+module Language.Haskell.TH.PprLib (
+    ($$),
+    ($+$),
+    (<+>),
+    (<>),
+    arrow,
+    braces,
+    brackets,
+    cat,
+    char,
+    colon,
+    comma,
+    dcolon,
+    double,
+    doubleQuotes,
+    empty,
+    equals,
+    fcat,
+    float,
+    fsep,
+    hang,
+    hcat,
+    hsep,
+    int,
+    integer,
+    isEmpty,
+    lbrace,
+    lbrack,
+    lparen,
+    nest,
+    parens,
+    pprName,
+    pprName',
+    ptext,
+    punctuate,
+    quotes,
+    rational,
+    rbrace,
+    rbrack,
+    rparen,
+    semi,
+    sep,
+    space,
+    text,
+    to_HPJ_Doc,
+    vcat,
+    Doc,
+    PprM,
+)
+where
 
+import Prelude hiding ((<>))
 import GHC.Boot.TH.PprLib


=====================================
libraries/template-haskell/Language/Haskell/TH/Syntax.hs
=====================================
@@ -1,22 +1,206 @@
 {-# LANGUAGE MagicHash #-}
-{-# LANGUAGE UnboxedTuples #-}
 {-# LANGUAGE TemplateHaskellQuotes #-}
 {-# LANGUAGE Trustworthy #-}
-module Language.Haskell.TH.Syntax
-  ( module GHC.Boot.TH.Syntax
-  , makeRelativeToProject
-  , module GHC.Boot.TH.Lift
-  , addrToByteArrayName
-  , addrToByteArray
-  )
+{-# LANGUAGE UnboxedTuples #-}
+
+module Language.Haskell.TH.Syntax (
+    Quote (..),
+    Exp (..),
+    Match (..),
+    Clause (..),
+    Q (..),
+    Pat (..),
+    Stmt (..),
+    Con (..),
+    Type (..),
+    Dec (..),
+    BangType,
+    VarBangType,
+    FieldExp,
+    FieldPat,
+    Name (..),
+    FunDep (..),
+    Pred,
+    RuleBndr (..),
+    TySynEqn (..),
+    InjectivityAnn (..),
+    Kind,
+    Overlap (..),
+    DerivClause (..),
+    DerivStrategy (..),
+    Code (..),
+    ModName (..),
+    addCorePlugin,
+    addDependentFile,
+    addForeignFile,
+    addForeignFilePath,
+    addForeignSource,
+    addModFinalizer,
+    addTempFile,
+    addTopDecls,
+    badIO,
+    bindCode,
+    bindCode_,
+    cmpEq,
+    compareBytes,
+    counter,
+    defaultFixity,
+    eqBytes,
+    extsEnabled,
+    getDoc,
+    getPackageRoot,
+    getQ,
+    get_cons_names,
+    hoistCode,
+    isExtEnabled,
+    isInstance,
+    joinCode,
+    liftCode,
+    location,
+    lookupName,
+    lookupTypeName,
+    lookupValueName,
+    manyName,
+    maxPrecedence,
+    memcmp,
+    mkNameG,
+    mkNameU,
+    mkOccName,
+    mkPkgName,
+    mk_tup_name,
+    mkName,
+    mkNameG_v,
+    mkNameG_d,
+    mkNameG_tc,
+    mkNameL,
+    mkNameS,
+    unTypeCode,
+    mkModName,
+    unsafeCodeCoerce,
+    mkNameQ,
+    mkNameG_fld,
+    modString,
+    nameBase,
+    nameModule,
+    namePackage,
+    nameSpace,
+    newDeclarationGroup,
+    newNameIO,
+    occString,
+    oneName,
+    pkgString,
+    putDoc,
+    putQ,
+    recover,
+    reify,
+    reifyAnnotations,
+    reifyConStrictness,
+    reifyFixity,
+    reifyInstances,
+    reifyModule,
+    reifyRoles,
+    reifyType,
+    report,
+    reportError,
+    reportWarning,
+    runIO,
+    sequenceQ,
+    runQ,
+    showName,
+    showName',
+    thenCmp,
+    tupleDataName,
+    tupleTypeName,
+    unTypeQ,
+    unboxedSumDataName,
+    unboxedSumTypeName,
+    unboxedTupleDataName,
+    unboxedTupleTypeName,
+    unsafeTExpCoerce,
+    ForeignSrcLang (..),
+    Extension (..),
+    AnnLookup (..),
+    AnnTarget (..),
+    Arity,
+    Bang (..),
+    BndrVis (..),
+    Body (..),
+    Bytes (..),
+    Callconv (..),
+    CharPos,
+    Cxt,
+    DecidedStrictness (..),
+    DocLoc (..),
+    FamilyResultSig (..),
+    Fixity (..),
+    FixityDirection (..),
+    Foreign (..),
+    Guard (..),
+    Info (..),
+    Inline (..),
+    InstanceDec,
+    Lit (..),
+    Loc (..),
+    Module (..),
+    ModuleInfo (..),
+    NameFlavour (..),
+    NameIs (..),
+    NameSpace (..),
+    NamespaceSpecifier (..),
+    OccName (..),
+    ParentName,
+    PatSynArgs (..),
+    PatSynDir (..),
+    PatSynType,
+    Phases (..),
+    PkgName (..),
+    Pragma (..),
+    Quasi (..),
+    Range (..),
+    Role (..),
+    RuleMatch (..),
+    Safety (..),
+    SourceStrictness (..),
+    SourceUnpackedness (..),
+    Specificity (..),
+    Strict,
+    StrictType,
+    SumAlt,
+    SumArity,
+    TExp (..),
+    TyLit (..),
+    TyVarBndr (..),
+    TypeFamilyHead (..),
+    Uniq,
+    Unlifted,
+    VarStrictType,
+    makeRelativeToProject,
+    liftString,
+    Lift (..),
+    dataToCodeQ,
+    dataToExpQ,
+    dataToPatQ,
+    dataToQa,
+    falseName,
+    justName,
+    leftName,
+    liftData,
+    liftDataTyped,
+    nonemptyName,
+    nothingName,
+    rightName,
+    trueName,
+    addrToByteArrayName,
+    addrToByteArray,
+)
 where
 
-import GHC.Boot.TH.Syntax
-import GHC.Boot.TH.Lift
-import System.FilePath
 import Data.Array.Byte
+import GHC.Boot.TH.Lift
+import GHC.Boot.TH.Syntax
 import GHC.Exts
 import GHC.ST
+import System.FilePath
 
 -- This module completely re-exports 'GHC.Boot.TH.Syntax',
 -- and exports additionally functions that depend on filepath.
@@ -41,4 +225,3 @@ addrToByteArray (I# len) addr = runST $ ST $
     (# s', mb #) -> case copyAddrToByteArray# addr mb 0# len s' of
       s'' -> case unsafeFreezeByteArray# mb s'' of
         (# s''', ret #) -> (# s''', ByteArray ret #)
-


=====================================
libraries/template-haskell/template-haskell.cabal.in
=====================================
@@ -53,6 +53,10 @@ Library
 
     build-depends:
         base        >= 4.11 && < 4.22,
+        -- We don't directly depend on any of the modules from `ghc-internal`
+        -- But we need to depend on it to work around a hadrian bug.
+        -- See: https://gitlab.haskell.org/ghc/ghc/-/issues/25705
+        ghc-internal == @ProjectVersionForLib at .*,
         ghc-boot-th == @ProjectVersionMunged@
 
     other-modules:


=====================================
rts/HeapStackCheck.cmm
=====================================
@@ -14,9 +14,6 @@
 #include "Updates.h"
 #include "SMPClosureOps.h"
 
-#if defined(__PIC__)
-import pthread_mutex_unlock;
-#endif
 import AcquireSRWLockExclusive;
 import ReleaseSRWLockExclusives;
 


=====================================
rts/PrimOps.cmm
=====================================
@@ -25,10 +25,6 @@
 #include "MachDeps.h"
 #include "SMPClosureOps.h"
 
-#if defined(__PIC__)
-import pthread_mutex_lock;
-import pthread_mutex_unlock;
-#endif
 import CLOSURE ghczminternal_GHCziInternalziControlziExceptionziBase_nestedAtomically_closure;
 import CLOSURE ghczminternal_GHCziInternalziIOziException_heapOverflow_closure;
 import CLOSURE ghczminternal_GHCziInternalziIOziException_blockedIndefinitelyOnMVar_closure;


=====================================
testsuite/tests/simplCore/should_fail/T25672.hs
=====================================
@@ -0,0 +1,15 @@
+{-# LANGUAGE KindSignatures #-}
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE GADTs #-}
+
+module T25672 where
+
+data IntOrWord (isInt :: Bool) where
+    Int :: !Int -> IntOrWord True
+    Word :: !Word -> IntOrWord False
+
+data WrapIntOrWord (isInt :: Bool)
+    = WrapIntOrWord {lit :: {-# UNPACK #-} !(IntOrWord isInt)}
+
+boom :: WrapIntOrWord True
+boom = WrapIntOrWord (Int 1)


=====================================
testsuite/tests/simplCore/should_fail/T25672.stderr
=====================================
@@ -0,0 +1,6 @@
+T25672.hs:12:7: warning: [GHC-40091]
+    • Ignoring unusable UNPACK pragma
+        on the first argument of ‘WrapIntOrWord’
+    • In the definition of data constructor ‘WrapIntOrWord’
+      In the data type declaration for ‘WrapIntOrWord’
+


=====================================
testsuite/tests/simplCore/should_fail/all.T
=====================================
@@ -1,3 +1,6 @@
 test('T7411', [expect_broken_for(7411, ['optasm', 'optllvm',
                                         'threaded2', 'dyn']),
                exit_code(1)], compile_and_run, [''])
+
+# This one produces a warning
+test('T25672', normal, compile, ['-O'])


=====================================
utils/haddock/html-test/ref/QuasiExpr.html
=====================================
@@ -335,9 +335,9 @@
 	    >parseExprExp</a
 	    > :: <a href="#" title="Data.String"
 	    >String</a
-	    > -> <a href="#" title="Language.Haskell.TH"
+	    > -> <a href="#" title="Language.Haskell.TH.Syntax"
 	    >Q</a
-	    > <a href="#" title="Language.Haskell.TH"
+	    > <a href="#" title="Language.Haskell.TH.Syntax"
 	    >Exp</a
 	    > <a href="#" class="selflink"
 	    >#</a


=====================================
utils/haddock/html-test/ref/TH.html
=====================================
@@ -55,9 +55,9 @@
 	><p class="src"
 	  ><a id="v:decl" class="def"
 	    >decl</a
-	    > :: <a href="#" title="Language.Haskell.TH"
+	    > :: <a href="#" title="Language.Haskell.TH.Syntax"
 	    >Q</a
-	    > [<a href="#" title="Language.Haskell.TH"
+	    > [<a href="#" title="Language.Haskell.TH.Syntax"
 	    >Dec</a
 	    >] <a href="#" class="selflink"
 	    >#</a


=====================================
utils/haddock/html-test/ref/Threaded_TH.html
=====================================
@@ -67,9 +67,9 @@
 	  ><li class="src short"
 	    ><a href="#"
 	      >forkTH</a
-	      > :: <a href="#" title="Language.Haskell.TH"
+	      > :: <a href="#" title="Language.Haskell.TH.Syntax"
 	      >Q</a
-	      > <a href="#" title="Language.Haskell.TH"
+	      > <a href="#" title="Language.Haskell.TH.Syntax"
 	      >Exp</a
 	      ></li
 	    ></ul
@@ -82,9 +82,9 @@
 	><p class="src"
 	  ><a id="v:forkTH" class="def"
 	    >forkTH</a
-	    > :: <a href="#" title="Language.Haskell.TH"
+	    > :: <a href="#" title="Language.Haskell.TH.Syntax"
 	    >Q</a
-	    > <a href="#" title="Language.Haskell.TH"
+	    > <a href="#" title="Language.Haskell.TH.Syntax"
 	    >Exp</a
 	    > <a href="#" class="selflink"
 	    >#</a



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a1c2a7a98ba3feff2bf81181807d98ead79c776e...df68f43dfa93e97e70f226671588bfec45d891c4

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a1c2a7a98ba3feff2bf81181807d98ead79c776e...df68f43dfa93e97e70f226671588bfec45d891c4
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/20250311/85918894/attachment-0001.html>


More information about the ghc-commits mailing list