[GHC] #12697: Improve output of pattern synonym info

GHC ghc-devs at haskell.org
Thu Oct 13 18:59:56 UTC 2016


#12697: Improve output of pattern synonym info
-------------------------------------+-------------------------------------
           Reporter:  Iceland_jack   |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.0.1
           Keywords:                 |  Operating System:  Unknown/Multiple
  PatternSynonyms                    |
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 {{{#!hs
 import GHC.Prim
 import Data.Kind

 data TypeRep :: forall k. k -> Type where
   TI :: TypeRep Int
   TB :: TypeRep Bool
   TL :: TypeRep []
   TA :: TypeRep f -> TypeRep x -> TypeRep (f x)

 data (a::k1) :~~: (b::k2) where
   HRefl :: a :~~: a
 deriving instance Show (a :~~: b)

 eqTT :: TypeRep (a::k1) -> TypeRep (b::k2) -> Maybe (a :~~: b)
 eqTT TI TI = Just HRefl
 eqTT TB TB = Just HRefl
 eqTT TL TL = Just HRefl

 pattern IsList <- (eqTT TL -> Just HRefl)
   where IsList = TL
 }}}

 What is the type of `IsList`? The result of `:type` is only accurate when
 used as an expression (`IsList :: TypeRep []`) and the result of `:info`
 is uses `~#`

 {{{
 >>> :info IsList
 pattern IsList :: forall k2 (b :: k2). () => ((* -> *) ~# k2,
                                               [] ~# b) => TypeRep b
 }}}

 which won't parse (`parse error on input ‘~#’`).

 {{{#!hs
 -- t9R4.hs:20:67: error: …
 --     • Expected kind ‘* -> *’, but ‘b’ has kind ‘k2’
 --     • In the second argument of ‘~’, namely ‘b’
 -- Compilation failed.
 pattern IsList :: forall k2 (b :: k2). () => ((* -> *) ~ k2, [] ~ b) =>
 TypeRep b
 pattern IsList <- (eqTT TL -> Just HRefl)
   where IsList = TL
 }}}

 The user may try to use `~` but we need
 [https://hackage.haskell.org/package/ghc-prim-0.5.0.0/docs/GHC-
 Types.html#t:-126--126- heterogeneous equality from GHC.Types] (`~~`)

 {{{#!hs
 pattern IsList :: forall k2 (b :: k2). () => ((* -> *) ~ k2, [] ~~ b) =>
 TypeRep b
 }}}

 and in the end, we only need

 {{{#!hs
 pattern List :: () => [] ~~ b => T b
 }}}

 `:info` should show something closer to that! Copy-pasting should work

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


More information about the ghc-tickets mailing list