[GHC] #4175: GHCi support for type/data families should match that of related features
GHC
cvs-ghc at haskell.org
Thu Mar 7 19:32:25 CET 2013
#4175: GHCi support for type/data families should match that of related features
---------------------------------+------------------------------------------
Reporter: claus | Owner:
Type: bug | Status: patch
Priority: low | Milestone: 7.6.2
Component: GHCi | Version: 6.12.3
Keywords: FD TF | Os: Unknown/Multiple
Architecture: Unknown/Multiple | Failure: None/Unknown
Difficulty: | Testcase:
Blockedby: | Blocking:
Related: |
---------------------------------+------------------------------------------
Changes (by parcs):
* status: new => patch
Comment:
I've attached a patch that implements support for showing type family
instances through `:info`.
Examples:
{{{
{-# LANGUAGE TypeFamilies #-}
type family A a b
type instance A Int Int = ()
type instance A (Maybe a) a = a
data family B a
data instance B () = MkB
class C a where
type D a b
instance C Int where
type D Int () = String
instance C () where
type D () () = Bool
type family E a
type instance where
E () = Bool
E Int = String
}}}
{{{
Main> :i A
type family A a b :: * -- Defined at tf.hs:3:13
type instance A (Maybe a) a -- Defined at tf.hs:5:15
type instance A Int Int -- Defined at tf.hs:4:15
}}}
{{{
*Main> :i B
data family B a -- Defined at tf.hs:7:13
data instance B () -- Defined at tf.hs:8:15
}}}
{{{
*Main> :i D
class C a where
type family D a b :: *
-- Defined at tf.hs:11:10
type D () () -- Defined at tf.hs:17:10
type D Int () -- Defined at tf.hs:14:10
}}}
{{{
Main> :i E
type family E a :: * -- Defined at tf.hs:23:13
type instance where
E () -- Defined at tf.hs:26:5
E Int -- Defined at tf.hs:27:5
}}}
{{{
*Main> :i ()
data () = () -- Defined in ‛GHC.Tuple’
instance C () -- Defined at tf.hs:16:10
...
data instance B () -- Defined at tf.hs:8:15
type D () () -- Defined at tf.hs:17:10
type D Int () -- Defined at tf.hs:14:10
type instance where
E () -- Defined at tf.hs:26:5
E Int -- Defined at tf.hs:27:5
}}}
{{{
*Main> :i Maybe
data Maybe a = Nothing | Just a -- Defined in ‛Data.Maybe’
...
type instance A (Maybe a) a -- Defined at tf.hs:5:15
}}}
{{{
*Main> :i Int
data Int = GHC.Types.I# GHC.Prim.Int# -- Defined in ‛GHC.Types’
instance C Int -- Defined at tf.hs:13:10
...
type instance A Int Int -- Defined at tf.hs:4:15
type D Int () -- Defined at tf.hs:14:10
type instance where
E () -- Defined at tf.hs:26:5
E Int -- Defined at tf.hs:27:5
}}}
The patch causes a trivial testsuite failure:
{{{
Unexpected failures:
ghci/scripts T5417 [bad stdout] (ghci)
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4175#comment:6>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list