summaryrefslogtreecommitdiff
path: root/compiler
diff options
context:
space:
mode:
authorJan Stolarek <jan.stolarek@p.lodz.pl>2014-04-19 06:58:07 +0200
committerJan Stolarek <jan.stolarek@p.lodz.pl>2014-04-19 11:20:51 +0200
commit1d2ffb6ab1ef973c85f893b5ea4a72cfa59ce484 (patch)
tree5f698d69fe2383300f51e71e824e86dad6cc8508 /compiler
parent41f5b7e3e0648302b9c5dc485917a391d21d15a1 (diff)
downloadhaskell-1d2ffb6ab1ef973c85f893b5ea4a72cfa59ce484.tar.gz
Validate inferred theta. Fixes #8883
This checks that all the required extensions are enabled for the inferred type signature. Updates binary and vector submodules.
Diffstat (limited to 'compiler')
-rw-r--r--compiler/llvmGen/LlvmCodeGen.hs1
-rw-r--r--compiler/nativeGen/RegAlloc/Liveness.hs1
-rw-r--r--compiler/nativeGen/X86/Instr.hs1
-rw-r--r--compiler/typecheck/TcBinds.lhs5
-rw-r--r--compiler/typecheck/TcSMonad.lhs1
5 files changed, 9 insertions, 0 deletions
diff --git a/compiler/llvmGen/LlvmCodeGen.hs b/compiler/llvmGen/LlvmCodeGen.hs
index d0f343fa92..61e7e39a49 100644
--- a/compiler/llvmGen/LlvmCodeGen.hs
+++ b/compiler/llvmGen/LlvmCodeGen.hs
@@ -2,6 +2,7 @@
-- | This is the top-level module in the LLVM code generator.
--
+{-# LANGUAGE TypeFamilies #-}
module LlvmCodeGen ( llvmCodeGen, llvmFixupAsm ) where
#include "HsVersions.h"
diff --git a/compiler/nativeGen/RegAlloc/Liveness.hs b/compiler/nativeGen/RegAlloc/Liveness.hs
index 6dd4cec0de..b0e763a6f0 100644
--- a/compiler/nativeGen/RegAlloc/Liveness.hs
+++ b/compiler/nativeGen/RegAlloc/Liveness.hs
@@ -5,6 +5,7 @@
-- (c) The University of Glasgow 2004-2013
--
-----------------------------------------------------------------------------
+{-# LANGUAGE FlexibleContexts, TypeFamilies #-}
module RegAlloc.Liveness (
RegSet,
RegMap, emptyRegMap,
diff --git a/compiler/nativeGen/X86/Instr.hs b/compiler/nativeGen/X86/Instr.hs
index 8284270be1..75e5b9e737 100644
--- a/compiler/nativeGen/X86/Instr.hs
+++ b/compiler/nativeGen/X86/Instr.hs
@@ -9,6 +9,7 @@
#include "HsVersions.h"
#include "nativeGen/NCG.h"
+{-# LANGUAGE TypeFamilies #-}
module X86.Instr (Instr(..), Operand(..), PrefetchVariant(..), JumpDest,
getJumpDestBlockId, canShortcut, shortcutStatics,
shortcutJump, i386_insert_ffrees, allocMoreStack,
diff --git a/compiler/typecheck/TcBinds.lhs b/compiler/typecheck/TcBinds.lhs
index d46e441130..17f124b0d8 100644
--- a/compiler/typecheck/TcBinds.lhs
+++ b/compiler/typecheck/TcBinds.lhs
@@ -54,6 +54,7 @@ import FastString
import Type(mkStrLitTy)
import Class(classTyCon)
import PrelNames(ipClassName)
+import TcValidity (checkValidTheta)
import Control.Monad
@@ -562,6 +563,10 @@ tcPolyInfer rec_tc prag_fn tc_sig_fn mono closed bind_list
simplifyInfer closed mono name_taus wanted
; theta <- zonkTcThetaType (map evVarPred givens)
+ -- We need to check inferred theta for validity. The reason is that we
+ -- might have inferred theta that requires language extension that is
+ -- not turned on. See #8883. Example can be found in the T8883 testcase.
+ ; checkValidTheta (InfSigCtxt (fst . head $ name_taus)) theta
; exports <- checkNoErrs $ mapM (mkExport prag_fn qtvs theta) mono_infos
; loc <- getSrcSpanM
diff --git a/compiler/typecheck/TcSMonad.lhs b/compiler/typecheck/TcSMonad.lhs
index b7faf153ca..51f4945564 100644
--- a/compiler/typecheck/TcSMonad.lhs
+++ b/compiler/typecheck/TcSMonad.lhs
@@ -1,5 +1,6 @@
\begin{code}
-- Type definitions for the constraint solver
+{-# LANGUAGE TypeFamilies #-}
module TcSMonad (
-- Canonical constraints, definition is now in TcRnTypes