[commit: ghc] wip/ttypeable: Things (10f40d5)
git at git.haskell.org
git at git.haskell.org
Sun Jan 29 20:20:14 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/ttypeable
Link : http://ghc.haskell.org/trac/ghc/changeset/10f40d51a1b09dd956e2ab7994bcd5524a251dcb/ghc
>---------------------------------------------------------------
commit 10f40d51a1b09dd956e2ab7994bcd5524a251dcb
Author: Ben Gamari <ben at smart-cactus.org>
Date: Sun Oct 23 14:26:15 2016 -0400
Things
>---------------------------------------------------------------
10f40d51a1b09dd956e2ab7994bcd5524a251dcb
compiler/coreSyn/CoreLint.hs | 2 +-
libraries/base/Data/Dynamic.hs | 8 ++++++--
libraries/base/Type/Reflection.hs | 1 -
3 files changed, 7 insertions(+), 4 deletions(-)
diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs
index c86b6b2..3ca3785 100644
--- a/compiler/coreSyn/CoreLint.hs
+++ b/compiler/coreSyn/CoreLint.hs
@@ -1174,7 +1174,7 @@ lintArrow :: SDoc -> LintedKind -> LintedKind -> LintM LintedKind
-- See Note [GHC Formalism]
lintArrow what k1 k2 -- Eg lintArrow "type or kind `blah'" k1 k2
-- or lintarrow "coercion `blah'" k1 k2
- = do { unless (okArrowArgKind k1) (addErrL (msg (text "argument") k1))
+ = do { --unless (okArrowArgKind k1) (addErrL (msg (text "argument") k1))
; unless (okArrowResultKind k2) (addErrL (msg (text "result") k2))
; return liftedTypeKind }
where
diff --git a/libraries/base/Data/Dynamic.hs b/libraries/base/Data/Dynamic.hs
index dd6a5f2..a147605 100644
--- a/libraries/base/Data/Dynamic.hs
+++ b/libraries/base/Data/Dynamic.hs
@@ -4,6 +4,7 @@
{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TypeApplications #-}
-----------------------------------------------------------------------------
-- |
@@ -135,8 +136,11 @@ fromDynamic (Dynamic t v)
-- (f::(a->b)) `dynApply` (x::a) = (f a)::b
dynApply :: Dynamic -> Dynamic -> Maybe Dynamic
dynApply (Dynamic (TRFun ta tr) f) (Dynamic ta' x)
- | Just HRefl <- ta `eqTypeRep` ta' = Just (Dynamic tr (f x))
-dynApply _ _ = Nothing
+ | Just HRefl <- ta `eqTypeRep` ta'
+ , Just HRefl <- typeRepKind tr `eqTypeRep` typeRep @Type
+ = Just (Dynamic tr (f x))
+dynApply _ _
+ = Nothing
dynApp :: Dynamic -> Dynamic -> Dynamic
dynApp f x = case dynApply f x of
diff --git a/libraries/base/Type/Reflection.hs b/libraries/base/Type/Reflection.hs
index 8057a2e..94d3d91 100644
--- a/libraries/base/Type/Reflection.hs
+++ b/libraries/base/Type/Reflection.hs
@@ -17,7 +17,6 @@ module Type.Reflection
, I.TypeRep
, I.typeOf
, pattern I.TRApp, pattern I.TRCon, pattern I.TRFun
- , I.decomposeFun
, I.typeRepFingerprint
, I.typeRepTyCon
, I.typeRepKind
More information about the ghc-commits
mailing list