[GHC] #12853: Unpromoted tuples in TH in correctly accepted by tthe type checker
GHC
ghc-devs at haskell.org
Sat Nov 19 04:19:09 UTC 2016
#12853: Unpromoted tuples in TH in correctly accepted by tthe type checker
-------------------------------------+-------------------------------------
Reporter: erikd | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 8.2.1
Component: Compiler | Version: 8.1
(Type checker) |
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: Other
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
This issue was discovered when writing tests for #11629.
Test case:
{{{#!hs
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE FlexibleInstances #-}
module T11629 where
import Control.Monad
import Language.Haskell.TH
class C (a :: Bool)
class D (a :: (Bool, Bool))
class E (a :: [Bool])
instance C True
instance C 'False
instance D '(True, False)
instance D '(False, True)
instance E '[True, False]
instance E '[False, True]
do
let getType (InstanceD _ _ ty _) = ty
getType _ = error "getType: only defined for
InstanceD"
failMsg a ty1 ty2 = fail $ "example " ++ a
++ ": ty1 /= ty2, where\n ty1 = "
++ show ty1 ++ "\n ty2 = " ++ show ty2
withoutSig (ForallT tvs cxt ty) = ForallT tvs cxt (withoutSig ty)
withoutSig (AppT ty1 ty2) = AppT (withoutSig ty1) (withoutSig
ty2)
withoutSig (SigT ty ki) = withoutSig ty
withoutSig ty = ty
-- test #2: type quotations and reified types should agree wrt
-- promoted tuples.
ty1 <- [t| D '(True, False) |]
ty2 <- [t| D (False, True) |]
ClassI _ insts <- reify ''D
let [ty1', ty2'] = map (withoutSig . getType) insts
when (ty1 /= ty1') $ failMsg "C" ty1 ty1'
when (ty2 /= ty2') $ failMsg "D" ty2 ty2'
return []
}}}
According to @RyanlGlScott in https://phabricator.haskell.org/D2188#79228
the code `D (True, False)` in regular Haskell code would be rejected as a
Kind error, whereas when its in Oxford brackets like `[t| D (True, False)
|]`, it manages to sneak through the type checker.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12853>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list