[GHC] #9897: Couldn't match type `Id (Id Char)' with `Char'
GHC
ghc-devs at haskell.org
Thu Dec 18 04:55:46 UTC 2014
#9897: Couldn't match type `Id (Id Char)' with `Char'
-------------------------------------+-------------------------------------
Reporter: erisco | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 7.8.3
checker) | Operating System: Windows
Keywords: | Type of failure: GHC
Architecture: x86_64 (amd64) | rejects valid program
Difficulty: Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions:
-------------------------------------+-------------------------------------
'foo' is expected to type check given that 'bar' and 'qux' type check.
{{{
ghc_bug.hs:21:7:
Couldn't match type `Id (Id Char)' with `Char'
Expected type: (:.:) Id Id Char
Actual type: Char
In the expression: 'x'
In an equation for `foo': foo = 'x'
}}}
{{{#!hs
{-# LANGUAGE TypeOperators, TypeFamilies #-}
module Main where
type family (:.:) g f a where
(:.:) g f a = g (f a)
--
type family Id x where
Id x = x
--
-- Type checks
bar :: Id (Id Char)
bar = 'x'
-- Type checks
qux = 'x' :: (Id :.: Id) Char
-- Couldn't match type `Id (Id Char)' with `Char'
foo :: (Id :.: Id) Char
foo = 'x'
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9897>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list