[GHC] #13775: Type family expansion is too lazy, allows accepting of ill-typed terms
GHC
ghc-devs at haskell.org
Mon Jul 16 20:08:30 UTC 2018
#13775: Type family expansion is too lazy, allows accepting of ill-typed terms
-------------------------------------+-------------------------------------
Reporter: fizruk | Owner: diatchki
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 8.0.2
checker) | Keywords:
Resolution: | CustomTypeErrors
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC accepts | Unknown/Multiple
invalid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by tom-bop):
Are we sure this has to do with `TypeError`s? I see the same problem
without them:
{{{#!haskell
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
import GHC.TypeLits
import Data.Proxy
type family Head xs where
-- As written, this compiles, and it also compiles if you uncomment
either
-- of these lines:
-- Head '[] = 'True ~ 'False
-- Head '[] = TypeError ('Text "empty list")
Head (x ': xs) = x
main = print $ show (Proxy::Proxy (Head '[]))
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13775#comment:9>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list