[GHC] #8357: Pretty printing of kind-involving inferred types

GHC ghc-devs at haskell.org
Wed Sep 25 11:53:41 CEST 2013


#8357: Pretty printing of kind-involving inferred types
------------------------------------+-------------------------------------
       Reporter:  ksf               |             Owner:
           Type:  bug               |            Status:  new
       Priority:  normal            |         Milestone:
      Component:  Compiler          |           Version:  7.7
       Keywords:                    |  Operating System:  Unknown/Multiple
   Architecture:  Unknown/Multiple  |   Type of failure:  None/Unknown
     Difficulty:  Unknown           |         Test Case:
     Blocked By:                    |          Blocking:
Related Tickets:                    |
------------------------------------+-------------------------------------
 An example of inferred types (foo, bar, both), for brevity's sake omitting
 value-level details:

 {{{

 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE DataKinds #-}
 {-# LANGUAGE KindSignatures #-}
 {-# LANGUAGE TypeOperators #-}
 import GHC.TypeLits

 data (:::) (sy :: Symbol) ty
 data Key (sy :: Symbol)
 data Rec (rs :: [*])

 (*=) :: Key sy -> ty -> Rec '[sy ::: ty]
 (*=) = undefined

 (.*.) :: (Union xs ys ~ rs) => Rec xs -> Rec ys -> Rec rs
 (.*.) = undefined

 type family Union (xs :: [*]) (ys :: [*]) :: [*]  where
     Union ((sy ::: t) ': xs) ys = (sy ::: t) ': Union xs ys
     Union '[] ys = ys


 fFoo :: Key "foo"
 fFoo = undefined

 fBar :: Key "bar"
 fBar = undefined


 foo ::  Rec ((':) * ("foo" ::: [Char]) ('[] *))
 foo = fFoo *= "foo"

 bar ::  Rec ((':) * ("bar" ::: [Char]) ('[] *))
 bar = fBar *= "bar"

 both :: Rec ((':) * ("foo" ::: [Char]) ((':) * ("bar" ::: [Char]) ('[]
 *)))
 both = foo .*. bar
 }}}

 There's actually two issues, here: First, the most serious one, GHC prints
 kind annotations (*) that it can't even parse back, and then [*] types are
 pretty printed with ': constructors instead of nicely with [,] syntax.

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8357>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler



More information about the ghc-tickets mailing list