[Git][ghc/ghc][wip/no-typeable-proxy] 2 commits: Remove ghc-linters from needs

Krzysztof Gogolewski gitlab at gitlab.haskell.org
Sat Oct 10 15:58:10 UTC 2020



Krzysztof Gogolewski pushed to branch wip/no-typeable-proxy at Glasgow Haskell Compiler / GHC


Commits:
e9a43b2e by Krzysztof Gogolewski at 2020-10-10T17:57:16+02:00
Remove ghc-linters from needs

- - - - -
1da081eb by Krzysztof Gogolewski at 2020-10-10T17:57:43+02:00
Remove Proxy# argument in Data.Typeable.Internal

Not neccessary. This was from the times TypeRep was not indexed.

- - - - -


5 changed files:

- .gitlab-ci.yml
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/Tc/Instance/Class.hs
- libraries/base/Data/Typeable/Internal.hs
- libraries/base/GHC/Exception.hs-boot


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -248,7 +248,7 @@ validate-x86_64-linux-deb9-unreg-hadrian:
 
 hadrian-ghc-in-ghci:
   stage: quick-build
-  needs: [ghc-linters, lint-linters, lint-submods]
+  needs: [lint-linters, lint-submods]
   image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb9:$DOCKER_REV"
   before_script:
     # workaround for docker permissions
@@ -282,7 +282,7 @@ hadrian-ghc-in-ghci:
 
 .lint-params:
   stage: lint
-  needs: [ghc-linters, lint-submods]
+  needs: [lint-submods]
   tags:
     - lint
   image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb9:$DOCKER_REV"


=====================================
compiler/GHC/HsToCore/Binds.hs
=====================================
@@ -56,7 +56,6 @@ import GHC.Core.Coercion
 import GHC.Core.Multiplicity
 import GHC.Builtin.Types ( typeNatKind, typeSymbolKind )
 import GHC.Types.Id
-import GHC.Types.Id.Make(proxyHashId)
 import GHC.Types.Name
 import GHC.Types.Var.Set
 import GHC.Core.Rules
@@ -1220,7 +1219,7 @@ dsEvTerm (EvFun { et_tvs = tvs, et_given = given
 dsEvTypeable :: Type -> EvTypeable -> DsM CoreExpr
 -- Return a CoreExpr :: Typeable ty
 -- This code is tightly coupled to the representation
--- of TypeRep, in base library Data.Typeable.Internals
+-- of TypeRep, in base library Data.Typeable.Internal
 dsEvTypeable ty ev
   = do { tyCl <- dsLookupTyCon typeableClassName    -- Typeable
        ; let kind = typeKind ty
@@ -1299,14 +1298,13 @@ ds_ev_typeable ty (EvTypeableTyLit ev)
   = -- See Note [Typeable for Nat and Symbol] in GHC.Tc.Solver.Interact
     do { fun  <- dsLookupGlobalId tr_fun
        ; dict <- dsEvTerm ev       -- Of type KnownNat/KnownSymbol
-       ; let proxy = mkTyApps (Var proxyHashId) [ty_kind, ty]
-       ; return (mkApps (mkTyApps (Var fun) [ty]) [ dict, proxy ]) }
+       ; return (mkApps (mkTyApps (Var fun) [ty]) [ dict ]) }
   where
     ty_kind = typeKind ty
 
     -- tr_fun is the Name of
-    --       typeNatTypeRep    :: KnownNat    a => Proxy# a -> TypeRep a
-    -- of    typeSymbolTypeRep :: KnownSymbol a => Proxy# a -> TypeRep a
+    --       typeNatTypeRep    :: KnownNat    a => TypeRep a
+    -- of    typeSymbolTypeRep :: KnownSymbol a => TypeRep a
     tr_fun | ty_kind `eqType` typeNatKind    = typeNatTypeRepName
            | ty_kind `eqType` typeSymbolKind = typeSymbolTypeRepName
            | otherwise = panic "dsEvTypeable: unknown type lit kind"


=====================================
compiler/GHC/Tc/Instance/Class.hs
=====================================
@@ -548,7 +548,7 @@ have this instance, implemented here by doTyLit:
       instance KnownNat n => Typeable (n :: Nat) where
          typeRep = typeNatTypeRep @n
 where
-   Data.Typeable.Internals.typeNatTypeRep :: KnownNat a => TypeRep a
+   Data.Typeable.Internal.typeNatTypeRep :: KnownNat a => TypeRep a
 
 Ultimately typeNatTypeRep uses 'natSing' from KnownNat to get a
 runtime value 'n'; it turns it into a string with 'show' and uses


=====================================
libraries/base/Data/Typeable/Internal.hs
=====================================
@@ -979,12 +979,12 @@ mkTypeLitTyCon name kind_tycon
   where kind = KindRepTyConApp kind_tycon []
 
 -- | Used to make `'Typeable' instance for things of kind Nat
-typeNatTypeRep :: KnownNat a => Proxy# a -> TypeRep a
-typeNatTypeRep p = typeLitTypeRep (show (natVal' p)) tcNat
+typeNatTypeRep :: forall a. KnownNat a => TypeRep a
+typeNatTypeRep = typeLitTypeRep (show (natVal' (proxy# @a))) tcNat
 
 -- | Used to make `'Typeable' instance for things of kind Symbol
-typeSymbolTypeRep :: KnownSymbol a => Proxy# a -> TypeRep a
-typeSymbolTypeRep p = typeLitTypeRep (show (symbolVal' p)) tcSymbol
+typeSymbolTypeRep :: forall a. KnownSymbol a => TypeRep a
+typeSymbolTypeRep = typeLitTypeRep (show (symbolVal' (proxy# @a))) tcSymbol
 
 mkTypeLitFromString :: TypeLitSort -> String -> SomeTypeRep
 mkTypeLitFromString TypeLitSymbol s =


=====================================
libraries/base/GHC/Exception.hs-boot
=====================================
@@ -14,7 +14,7 @@ More dramatically
 
          GHC.Exception
 imports  Data.Typeable
-imports  Data.Typeable.Internals
+imports  Data.Typeable.Internal
 imports  GHC.Arr (fingerprint representation etc)
 imports  GHC.Real
 imports  {-# SOURCE #-} GHC.Exception



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/aefbbb8b08516ba7127a03daa31845b89dd2a5c9...1da081eb2bdb00798357de2a963111c71cfd9895

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/aefbbb8b08516ba7127a03daa31845b89dd2a5c9...1da081eb2bdb00798357de2a963111c71cfd9895
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/20201010/33cffb32/attachment-0001.html>


More information about the ghc-commits mailing list