hs-boot files don't support boring classes
Summary
A class declaration in an hs-boot
file with no constraints and no methods is considered to be abstract, and modules importing the class with a {-# SOURCE #-}
import cannot instantiate it. Unfortunately, this heuristic isn't quite right: it's sometimes useful to have an actual class with no constraints or methods, especially with FunctionalDependencies
. The obvious work-around is to give the class an explicitly empty constraint in the hs-boot
file, but this fails in a somewhat surprising fashion.
Steps to reproduce
-- Fish.hs
{-# language FunctionalDependencies #-}
module Fish where
import Shark
class Guppy a b | a -> b
-- Fish.hs-boot
{-# language FunctionalDependencies #-}
module Fish where
class () => Guppy a b | a -> b
-- Coral.hs
{-# language MultiParamTypeClasses #-}
module Coral where
import {-# SOURCE #-} Fish
import Data.Proxy
data Hoop
instance Guppy Hoop Char
yeah :: Guppy a b => proxy a -> Proxy b
yeah _ = Proxy
-- Shark.hs
module Shark where
import {-# SOURCE #-} Fish
import Coral
import Data.Proxy
goom :: Proxy Hoop -> Proxy Char
goom = yeah
Expected behavior
I expected to get an error about the constraints in the hs-boot
file not matching the one in the hs
file (since one has no constraints and the other has an empty constraint tuple). I hoped that GHC would understand the hs-boot
declaration to mean that the class itself actually has no constraints (and therefore no methods). What I actually got is just silly:
Coral.hs:8:10: error:
• Cannot define instance for abstract class ‘Guppy’
• In the instance declaration for ‘Guppy Hoop Char’
|
8 | instance Guppy Hoop Char
So when GHC sees the Guppy
declaration in Fish.hs-boot
, it simply erases the () =>
before even deciding whether the declaration is abstract. This really makes no sense! Either () =>
is the same as not having constraints (in which case the declaration in the hs-boot
file should be considered complete) or it is not the same (in which case I should get a complaint about mismatched declarations). I guess a third possibility is that they currently are the same, but that the GHC devs don't commit to them remaining so. If that's the case, I would also expect a mismatch error, but I would be a bit annoyed.
Environment
- GHC version used:
Optional:
- Operating System:
- System Architecture: