Singletons/T209.hs:(0,0)-(0,0): Splicing declarations singletons [d| m :: a -> b -> Bool -> Bool m _ _ x = x class C a b data Hm = Hm deriving anyclass (C Bool) deriving anyclass instance C a a => C a (Maybe a) |] ======> class C a b m :: a -> b -> Bool -> Bool m _ _ x = x data Hm = Hm deriving anyclass (C Bool) deriving anyclass instance C a a => C a (Maybe a) type HmSym0 = Hm type MSym3 (a0123456789876543210 :: a0123456789876543210) (a0123456789876543210 :: b0123456789876543210) (a0123456789876543210 :: Bool) = M a0123456789876543210 a0123456789876543210 a0123456789876543210 instance SuppressUnusedWarnings (MSym2 a0123456789876543210 a0123456789876543210) where suppressUnusedWarnings = snd (((,) MSym2KindInference) ()) data MSym2 (a0123456789876543210 :: a0123456789876543210) (a0123456789876543210 :: b0123456789876543210) :: (~>) Bool Bool where MSym2KindInference :: forall a0123456789876543210 a0123456789876543210 a0123456789876543210 arg. SameKind (Apply (MSym2 a0123456789876543210 a0123456789876543210) arg) (MSym3 a0123456789876543210 a0123456789876543210 arg) => MSym2 a0123456789876543210 a0123456789876543210 a0123456789876543210 type instance Apply (MSym2 a0123456789876543210 a0123456789876543210) a0123456789876543210 = M a0123456789876543210 a0123456789876543210 a0123456789876543210 instance SuppressUnusedWarnings (MSym1 a0123456789876543210) where suppressUnusedWarnings = snd (((,) MSym1KindInference) ()) data MSym1 (a0123456789876543210 :: a0123456789876543210) :: forall b0123456789876543210. (~>) b0123456789876543210 ((~>) Bool Bool) where MSym1KindInference :: forall a0123456789876543210 a0123456789876543210 arg. SameKind (Apply (MSym1 a0123456789876543210) arg) (MSym2 a0123456789876543210 arg) => MSym1 a0123456789876543210 a0123456789876543210 type instance Apply (MSym1 a0123456789876543210) a0123456789876543210 = MSym2 a0123456789876543210 a0123456789876543210 instance SuppressUnusedWarnings MSym0 where suppressUnusedWarnings = snd (((,) MSym0KindInference) ()) data MSym0 :: forall a0123456789876543210 b0123456789876543210. (~>) a0123456789876543210 ((~>) b0123456789876543210 ((~>) Bool Bool)) where MSym0KindInference :: forall a0123456789876543210 arg. SameKind (Apply MSym0 arg) (MSym1 arg) => MSym0 a0123456789876543210 type instance Apply MSym0 a0123456789876543210 = MSym1 a0123456789876543210 type family M (a :: a) (a :: b) (a :: Bool) :: Bool where M _ _ x = x class PC (a :: GHC.Types.Type) (b :: GHC.Types.Type) instance PC Bool Hm instance PC a (Maybe a) sM :: forall a b (t :: a) (t :: b) (t :: Bool). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MSym0 t) t) t :: Bool) sM _ _ (sX :: Sing x) = sX instance SingI (MSym0 :: (~>) a ((~>) b ((~>) Bool Bool))) where sing = (singFun3 @MSym0) sM instance SingI d => SingI (MSym1 (d :: a) :: (~>) b ((~>) Bool Bool)) where sing = (singFun2 @(MSym1 (d :: a))) (sM (sing @d)) instance (SingI d, SingI d) => SingI (MSym2 (d :: a) (d :: b) :: (~>) Bool Bool) where sing = (singFun1 @(MSym2 (d :: a) (d :: b))) ((sM (sing @d)) (sing @d)) data instance Sing :: Hm -> GHC.Types.Type where SHm :: Sing Hm type SHm = (Sing :: Hm -> GHC.Types.Type) instance SingKind Hm where type Demote Hm = Hm fromSing SHm = Hm toSing Hm = SomeSing SHm class SC a b instance SC Bool Hm instance SC a a => SC a (Maybe a) instance SingI Hm where sing = SHm