[GHC] #13680: Can't use TypeApplications with empty list expression

GHC ghc-devs at haskell.org
Wed May 10 14:30:35 UTC 2017


#13680: Can't use TypeApplications with empty list expression
-------------------------------------+-------------------------------------
           Reporter:  RyanGlScott    |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.0.1
  (Type checker)                     |
           Keywords:                 |  Operating System:  Unknown/Multiple
  TypeApplications                   |
       Architecture:                 |   Type of failure:  GHC rejects
  Unknown/Multiple                   |  valid program
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 Why can't I do this?

 {{{#!hs
 {-# LANGUAGE TypeApplications #-}
 module Bug where

 foo :: [Int]
 foo = [] @Int
 }}}

 Compiling this with GHC 8.0.1, 8.0.2, 8.2.1, or HEAD gives me:

 {{{
 $ /opt/ghc/head/bin/ghci Bug2.hs
 GHCi, version 8.3.20170509: http://www.haskell.org/ghc/  :? for help
 Loaded GHCi configuration from /home/rgscott/.ghci
 [1 of 1] Compiling Bug              ( Bug2.hs, interpreted )

 Bug2.hs:5:7: error:
     • Cannot apply expression of type ‘[a0]’
       to a visible type argument ‘Int’
     • In the expression: [] @Int
       In an equation for ‘foo’: foo = [] @Int
   |
 5 | foo = [] @Int
   |       ^^^^^^^
 }}}

 This seems really strange, since I can use `TypeApplications` with
 expressions like `Nothing @Int` without issues. According to GHCi:

 {{{
 $ /opt/ghc/head/bin/ghci
 GHCi, version 8.3.20170509: http://www.haskell.org/ghc/  :? for help
 Loaded GHCi configuration from /home/rgscott/.ghci
 λ> :set -XTypeApplications -fprint-explicit-foralls
 λ> :type +v []
 [] :: forall {a}. [a]
 λ> :type +v Nothing
 Nothing :: forall a. Maybe a
 }}}

 The type variable for `[]` isn't visible! But I don't see any reason why
 it shouldn't be, especially since, conceptually, the data type declaration
 for lists is:

 {{{#!hs
 data [] a = [] | a : [a]
 }}}

 I suspect that `[]`'s tyvar binder visibility is not wired into GHC
 correctly.

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


More information about the ghc-tickets mailing list