[Haskell-cafe] :i and :t give different types

Don Stewart dons at galois.com
Thu Feb 7 14:47:18 EST 2008


chad.scherrer:
> Hello haskell-cafe,
> 
> In ghci, I tried to get info for Data.Stream.Stream:
> 
> $ ghci
> GHCi, version 6.8.2: http://www.haskell.org/ghc/  :? for help
> Loading package base ... linking ... done.
> Prelude> :m Data.Stream
> Prelude Data.Stream> :i Stream
> data Stream a where
>   Stream :: forall a s.
>             (Data.Stream.Unlifted s) =>
>             !s -> Step a s -> !s -> Stream a
>         -- Defined in Data.Stream

That's fine, and is the correct type.

    data Stream a = forall s. Unlifted s =>
                              Stream !(s -> Step a s)  -- ^ a stepper function
                                     !s                -- ^ an initial state

> instance Functor Stream -- Defined in Data.Stream
> 
> This didn't seem right to me, so I asked tried this:
> 
> Prelude Data.Stream> :t Stream
> Stream :: (Data.Stream.Unlifted s) => (s -> Step a s) -> s -> Stream a

So that's the type of the Stream constructor, which introduces
a new existentially typed Stream (the 'a').

> What's going on here?
> 
> forall a s. (Data.Stream.Unlifted s) => !s -> Step a s -> !s -> Stream a
>  and
> (Data.Stream.Unlifted s) => (s -> Step a s) -> s -> Stream a

One is the type, one is the constructor for the type.

> are completely different, right? And really, neither one makes much
> sense to me. I would have expected
> 
> forall s. (Data.Stream.Unlifted s) => (s -> Step a s) -> s -> Stream a

For the constructor?

This all looks right, as far as I can tell:

    $ ghci -fglasgow-exts
    Prelude> :m + Data.Stream

Info about the data type:

    Prelude Data.Stream> :info Stream
    data Stream a where
      Stream :: forall a s.
                (Data.Stream.Unlifted s) =>
                !s -> Step a s -> !s -> Stream a
        -- Defined in Data.Stream
    instance Functor Stream -- Defined in Data.Stream

The type of the constructor

    Prelude Data.Stream> :t Stream   
    Stream :: forall s a.
              (Data.Stream.Unlifted s) =>
              (s -> Step a s) -> s -> Stream a

The kind of the type:

    Prelude Data.Stream> :k Stream
    Stream :: * -> *

-- Don


More information about the Haskell-Cafe mailing list