What is the story behind the type of undefined?

David Feuer david.feuer at gmail.com
Sun Feb 1 19:38:00 UTC 2015


Yes it does. Thanks. For the sake of consistency, I'd rather even have
separate functions with funny-looking types than hidden magic. That
is, we could hypothetically have

undefined# :: forall (a :: #) . a
error# :: forall (a :: #) . String -> a

There's no mechanism in Haskell to create things with such types, but
at least that would make the strange types explicit. Of course, if
someone can do something better, well, better is better.

On Sun, Feb 1, 2015 at 2:07 PM, Adam Gundry <adam at well-typed.com> wrote:
> Hi David,
>
> See Note [Error and friends have an "open-tyvar" forall] in MkCore. The
> short answer is that error and undefined are treated magically by GHC:
> the actual type of undefined is
>
>     forall (a :: OpenKind) . a
>
> and both * and # are subkinds of OpenKind.
>
> (There is a plan to get rid of this subkinding in favour of normal
> polymorphism, but it hasn't been implemented yet. See
> https://ghc.haskell.org/trac/ghc/wiki/NoSubKinds for more details.)
>
> Hope this helps,
>
> Adam
>
>
> On 01/02/15 18:54, David Feuer wrote:
>> If I define
>>
>> {-# LANGUAGE MagicHash #-}
>>
>> g :: Int# -> Int
>> g 3# = 3
>>
>> myUndefined = undefined
>>
>> then this gives a sensible type error about a kind mismatch:
>>
>> usual :: Int
>> usual = g myUndefined
>>
>> but this, oddly enough, compiles:
>>
>> peculiar :: Int
>> peculiar = g undefined
>>
>> GHCi and the definition in GHC.Error agree that
>>
>> undefined :: a
>>
>> So why am I allowed to use it as a type of kind #?
>
>
>
> --
> Adam Gundry, Haskell Consultant
> Well-Typed LLP, http://www.well-typed.com/


More information about the ghc-devs mailing list