[GHC] #15827: Explicit foralls in type family equations are pretty-printed inconsistently (and strangely, at times)

GHC ghc-devs at haskell.org
Mon Oct 29 12:55:01 UTC 2018


#15827: Explicit foralls in type family equations are pretty-printed inconsistently
(and strangely, at times)
-------------------------------------+-------------------------------------
           Reporter:  RyanGlScott    |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.7
           Keywords:  TypeFamilies   |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 Load the following code into GHCi HEAD (8.7+):

 {{{#!hs
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE TypeFamilies #-}
 module Bug where

 import Data.Kind

 type family F1 a
 type instance forall a. F1 a = Maybe a

 type family F2 a where
   forall a. F2 a = Maybe a

 data family D a
 data instance forall a. D a = MkD (Maybe a)
 }}}

 And make sure you have the `-fprint-explicit-foralls` flag enabled. Now
 let's see what happens when we look up the `:info` for each of these type
 families:

 {{{
 $ ~/Software/ghc2/inplace/bin/ghc-stage2 --interactive Bug.hs -fprint-
 explicit-foralls
 GHCi, version 8.7.20181029: http://www.haskell.org/ghc/  :? for help
 Loaded GHCi configuration from /home/rgscott/.ghci
 [1 of 1] Compiling Bug              ( Bug.hs, interpreted )
 Ok, one module loaded.
 λ> :i F1
 type family F1 a :: *   -- Defined at Bug.hs:7:1
 type instance F1 a = Maybe a    -- Defined at Bug.hs:8:25
 λ> :i F2
 type family F2 a :: *
   where [a] F2 a = Maybe a
         -- Defined at Bug.hs:10:1
 λ> :i D
 data family D a         -- Defined at Bug.hs:13:1
 data instance D a = MkD (Maybe a)       -- Defined at Bug.hs:14:25
 }}}

 There are two strange things of note here:

 * The equations for `F1` and `D` do not have any explicit `forall`s
 displayed at all, despite the fact that `-fprint-explicit-foralls` is
 enabled.
 * The equation for `F2` //does// have an explicit `forall` displayed, but
 in a rather bizarre fashion:

 {{{
 λ> :i F2
 type family F2 a :: *
   where [a] F2 a = Maybe a
         -- Defined at Bug.hs:10:1
 }}}

    I certainly wasn't expecting to see the type variables in square
 brackets. I would have hoped to see something like this instead:

 {{{
 λ> :i F2
 type family F2 a :: *
   where forall a. F2 a = Maybe a
         -- Defined at Bug.hs:10:1
 }}}

 Now that the "more explicit `forall`s" proposal is implemented, my hope is
 that it will be somewhat simple to change the way that this is pretty-
 printed (we already store the explicit `forall` information within the
 AST, after all).

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


More information about the ghc-tickets mailing list