Re: [Haskell-cafe] Evaluating type expressions in GHCi

From: Sean Leather
I would like to ask GHCi for the type that a type expression will evaluate to, once all definitions of type synonyms and (when possible) type families have been inlined.
It appears that I can do some part of this for type T by using ":t undefined :: T": ... undefined :: F (Int, Bool) :: (Bool, Int)
I also get what I expect here:
ghci> :t undefined :: F (a, Bool) undefined :: F (a, Bool) :: (F a, Int)
Of course, this doesn't work on types of kinds other than *.
In the absence of interpreter support, you can work around that by making appropriate type constructors. {-# LANGUAGE TypeFamilies, KindSignatures, EmptyDataDecls #-} type family G a :: * -> * type instance G Int = Maybe type instance G Bool = [] data Wrap1 (t :: * -> *) ghci> :t undefined :: Wrap1 (G Int) undefined :: Wrap1 (G Int) :: Wrap1 Maybe The development version of ghci seems to support type declarations, which would make this easier. https://github.com/ghc/ghc/commit/3db757241ce7fb99c096c30481aefa86bb9855a1 Brandon
participants (1)
-
Brandon Moore