[commit: ghc] master: Have addModFinalizer expose the local type environment. (c1ed955)

git at git.haskell.org git at git.haskell.org
Fri Jan 6 18:19:21 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/c1ed9557ad4e40caa72b27693527e02887ddd896/ghc

>---------------------------------------------------------------

commit c1ed9557ad4e40caa72b27693527e02887ddd896
Author: Facundo Domínguez <facundo.dominguez at tweag.io>
Date:   Tue Dec 20 08:39:10 2016 -0300

    Have addModFinalizer expose the local type environment.
    
    Kind inference in ghci was interfered when renaming of type splices
    introduced the HsSpliced data constructor. This patch has kind
    inference skip over it.
    
    Test Plan: ./validate
    
    Reviewers: simonpj, rrnewton, bgamari, goldfire, austin
    
    Subscribers: thomie, mboes
    
    Differential Revision: https://phabricator.haskell.org/D2886
    
    GHC Trac Issues: #12985


>---------------------------------------------------------------

c1ed9557ad4e40caa72b27693527e02887ddd896
 compiler/typecheck/TcHsType.hs                | 8 ++++++++
 testsuite/tests/ghci/scripts/GhciKinds.script | 7 +++++++
 testsuite/tests/ghci/scripts/GhciKinds.stdout | 2 ++
 3 files changed, 17 insertions(+)

diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs
index d96e74e..3fa6077 100644
--- a/compiler/typecheck/TcHsType.hs
+++ b/compiler/typecheck/TcHsType.hs
@@ -446,6 +446,14 @@ tc_infer_hs_type mode (HsKindSig ty sig)
   = do { sig' <- tc_lhs_kind (kindLevel mode) sig
        ; ty' <- tc_lhs_type mode ty sig'
        ; return (ty', sig') }
+-- HsSpliced is an annotation produced by 'RnSplice.rnSpliceType' to communicate
+-- the splice location to the typechecker. Here we skip over it in order to have
+-- the same kind inferred for a given expression whether it was produced from
+-- splices or not.
+--
+-- See Note [Delaying modFinalizers in untyped splices].
+tc_infer_hs_type mode (HsSpliceTy (HsSpliced _ (HsSplicedTy ty)) _)
+  = tc_infer_hs_type mode ty
 tc_infer_hs_type mode (HsDocTy ty _) = tc_infer_lhs_type mode ty
 tc_infer_hs_type _    (HsCoreTy ty)  = return (ty, typeKind ty)
 tc_infer_hs_type mode other_ty
diff --git a/testsuite/tests/ghci/scripts/GhciKinds.script b/testsuite/tests/ghci/scripts/GhciKinds.script
index fa94015..a7220fe 100644
--- a/testsuite/tests/ghci/scripts/GhciKinds.script
+++ b/testsuite/tests/ghci/scripts/GhciKinds.script
@@ -8,3 +8,10 @@
 
 :seti -XRankNTypes
 :kind! forall a. F (Maybe a)
+
+:set -XUnboxedTuples -XTemplateHaskell -XMagicHash
+:set -fprint-explicit-runtime-reps -fprint-explicit-kinds
+:set -fprint-explicit-foralls
+:m + GHC.Exts Language.Haskell.TH Language.Haskell.TH.Lib
+:m + Language.Haskell.TH.Syntax
+:k $(unboxedTupleT 2)
diff --git a/testsuite/tests/ghci/scripts/GhciKinds.stdout b/testsuite/tests/ghci/scripts/GhciKinds.stdout
index e34b84a..3556e62 100644
--- a/testsuite/tests/ghci/scripts/GhciKinds.stdout
+++ b/testsuite/tests/ghci/scripts/GhciKinds.stdout
@@ -9,3 +9,5 @@ F (Maybe Bool) :: *
 = Char
 forall a. F (Maybe a) :: *
 = Char
+$(unboxedTupleT 2) :: forall (k0 :: RuntimeRep) (k1 :: RuntimeRep).
+                      TYPE k0 -> TYPE k1 -> TYPE 'UnboxedTupleRep



More information about the ghc-commits mailing list