Hi all!
I have the following program tested with ghc 9.2.2, it shows different behavior when using GHC2021 or Haskell2010:
-- GHC version: 9.2.2
{-# OPTIONS_GHC -Wall #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GHC2021 #-}
-- {-# LANGUAGE Haskell2010 #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
import Data.Kind (Type)
import Data.Proxy (Proxy (..))
import Data.Typeable (Typeable)
class Typeable a => Typeable' a where
tag :: Proxy a -> String
class Typeable' a => Typeable'' a where
type T1 a :: Type
type T2 a :: Type
data A a = A
{ val1 :: T1 a
, val2 :: T2 a
}
-- * Does not work in GHC2021, but Haskell2010
instance Typeable'' a => Typeable' (A a) where
-- * Works in GHC2021
-- instance (Typeable'' a, Typeable (A a)) => Typeable' (A a) where
tag _ = "A/" ++ tag (Proxy @a)
data B
instance Typeable' B where
tag _ = "B"
instance Typeable'' B where
type T1 B = String
type T2 B = Int
main :: IO ()
main = do
let a = A "hello" 42 :: A B
putStrLn $ tag (Proxy @(A B)) ++ ": " ++ show(val1 a) ++ show(val2 a)
By using GHC2021, this does not compile where I got:
ghc2021-and-typeable.hs:28:10-40: error: …
• Could not deduce (Typeable k)
arising from the superclasses of an instance declaration
from the context: Typeable'' a
bound by the instance declaration
at /home/hellwolf/Projects/my/haskell-examples/2022-05-28-ghc2021-and-typeable/ghc2021-and-typeable.hs:28:10-40
• In the instance declaration for ‘Typeable' (A a)’
|
Compilation failed.
But if I enable {-# LANGUAGE Haskell2010 #-}
instead, the program compiles and works.
The code that’s the problem is:
instance Typeable'' a => Typeable' (A a) where
Fine, I can change it to more specific constraints instead:
instance (Typeable'' a, Typeable (A a)) => Typeable' (A a) where
Now the same code compiles for both GHC2021 and Haskell2010.
One more note, I cannot isolate a case into this minimal example I wrote, that case in another project I am doing also producing this warning when using the more specific “Typeable” constraint:
It seems making sense, since why on earth should I need to declare something explicitly “Typeable” anyhow?
But I cannot make a minimal example that can demonstrate this warning appearing when fixing the first issue.
Thank your for your time,