[GHC] #16068: Unsaturated type synonyms as arguments work in 8.6.3 but not HEAD

GHC ghc-devs at haskell.org
Wed Dec 19 11:57:42 UTC 2018


#16068: Unsaturated type synonyms as arguments work in 8.6.3 but not HEAD
-------------------------------------+-------------------------------------
           Reporter:                 |             Owner:  (none)
  quasicomputational                 |
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.7
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 Input, derived from code seen in the wild in hpack 0.31.1:

 {{{
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE FlexibleContexts #-}
 module Main where

 type WithCommonOptions cSources cxxSources jsSources a = a

 data Traverse m cSources cSources_ cxxSources cxxSources_ jsSources
 jsSources_ = Traverse {
   traverseCSources :: cSources -> m cSources_
 , traverseCxxSources :: cxxSources -> m cxxSources_
 , traverseJsSources :: jsSources -> m jsSources_
 }

 type Traversal_ t = forall m cSources cSources_ cxxSources cxxSources_
 jsSources jsSources_ a. Monad m
   => Traverse m cSources cSources_ cxxSources cxxSources_ jsSources
 jsSources_
   -> t cSources cxxSources jsSources a
   -> m (t cSources_ cxxSources_ jsSources_ a)

 traverseWithCommonOptions :: Traversal_ WithCommonOptions
 traverseWithCommonOptions = undefined

 main = return ()
 }}}

 Using a GHC compiled from revision
 074eae255793de6a94e8172015e7022c80a5cd15, I get this error:

 {{{
 Main.hs:19:30: error:
     • The type synonym ‘WithCommonOptions’ should have 4 arguments, but
 has been given none
     • In the type signature:
         traverseWithCommonOptions :: Traversal_ WithCommonOptions
    |
 19 | traverseWithCommonOptions :: Traversal_ WithCommonOptions
    |
 }}}

 GHC 8.6.3 accepts the module without complaint.

 I'm actually surprised that the previous code worked and I wouldn't
 complain if this is closed as working as intended. However, there's no
 mention of this change in the migration guide for 8.8 yet, so I'm not
 certain it's intentional.

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


More information about the ghc-tickets mailing list