[GHC] #15043: Expand type synonym

GHC ghc-devs at haskell.org
Wed Apr 18 13:11:48 UTC 2018


#15043: Expand type synonym
-------------------------------------+-------------------------------------
        Reporter:  domenkozar        |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:  8.6.1
       Component:  Compiler (Type    |              Version:  8.2.2
  checker)                           |
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------
Changes (by RyanGlScott):

 * cc: osa1 (added)


Comment:

 OK, I believe I can reproduce the essence of this with the following,
 smaller example:

 {{{#!hs
 module Bug where

 type Foo = Int

 f :: Maybe Foo
 f = ['a']
 }}}
 {{{
 $ ghci Bug.hs -fprint-expanded-synonyms
 GHCi, version 8.4.1: http://www.haskell.org/ghc/  :? for help
 Loaded GHCi configuration from /home/rgscott/.ghci
 [1 of 1] Compiling Bug              ( Bug.hs, interpreted )

 Bug.hs:6:5: error:
     • Couldn't match expected type ‘Maybe Foo’
                   with actual type ‘[Char]’
     • In the expression: ['a']
       In an equation for ‘f’: f = ['a']
   |
 6 | f = ['a']
   |     ^^^^^
 }}}

 Note that this error message does not expand `Foo`.

 That being said, the GHC commentary would suggest that this is
 intentional. See
 [http://git.haskell.org/ghc.git/blob/5d76846405240c051b00cddcda9d8d02c880968e:/compiler/typecheck/TcErrors.hs#l2431
 this Note]:

 {{{#!hs
 {-
 Note [Expanding type synonyms to make types similar]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

 In type error messages, if -fprint-expanded-types is used, we want to
 expand
 type synonyms to make expected and found types as similar as possible, but
 we
 shouldn't expand types too much to make type messages even more verbose
 and
 harder to understand. The whole point here is to make the difference in
 expected
 and found types clearer.

 `expandSynonymsToMatch` does this, it takes two types, and expands type
 synonyms
 only as much as necessary. Given two types t1 and t2:

   * If they're already same, it just returns the types.

   * If they're in form `C1 t1_1 .. t1_n` and `C2 t2_1 .. t2_m` (C1 and C2
 are
     type constructors), it expands C1 and C2 if they're different type
 synonyms.
     Then it recursively does the same thing on expanded types. If C1 and
 C2 are
     same, then it applies the same procedure to arguments of C1 and
 arguments of
     C2 to make them as similar as possible.

     Most important thing here is to keep number of synonym expansions at
     minimum. For example, if t1 is `T (T3, T5, Int)` and t2 is `T (T5, T3,
     Bool)` where T5 = T4, T4 = T3, ..., T1 = X, it returns `T (T3, T3,
 Int)` and
     `T (T3, T3, Bool)`.

   * Otherwise types don't have same shapes and so the difference is
 clearly
     visible. It doesn't do any expansions and show these types.

 Note that we only expand top-layer type synonyms. Only when top-layer
 constructors are the same we start expanding inner type synonyms.
 -}
 }}}

 Since the "top-level constructors" in this example, `Maybe` and `[]`, are
 different, it avoids expanding the type synonyms in their arguments.

 The same reason applies to your example, since the "top-level
 constructors" are `(:-)` and `Handler`, which are different.

 osa1, you implemented `-fprint-expanded-synonyms` in
 ae96c751c869813ab95e712f8daac8516bb4795f. Do you agree with this analysis?

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


More information about the ghc-tickets mailing list