[GHC] #16356: Unexpected type application in default declaration
GHC
ghc-devs at haskell.org
Fri Feb 22 23:02:43 UTC 2019
#16356: Unexpected type application in default declaration
-------------------------------------+-------------------------------------
Reporter: int-index | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.6.3
(Type checker) |
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:
-------------------------------------+-------------------------------------
All of these work:
{{{#!hs
{-# LANGUAGE PolyKinds, TypeApplications, TypeFamilies, FlexibleInstances
#-}
import Data.Kind (Type)
data B (a :: k)
type family FClosed :: k -> Type where
FClosed @k = B @k
type family FOpen :: k -> Type
type instance FOpen @k = B @k
class FAssocClass k where
type FAssoc :: k -> Type
instance FAssocClass k where
type FAssoc @k = B @k
}}}
This one doesn't:
{{{#!hs
class FAssocDefaultClass k where
type FAssocDefault :: k -> Type
type FAssocDefault @k = B @k
}}}
{{{
A.hs:21:23: error:
Unexpected type application @k
In the default declaration for ‘FAssocDefault’
|
21 | type FAssocDefault @k = B @k
|
}}}
So, what are the rules of the game? Let's fix this and document in the
User's Guide.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/16356>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list