Singletons/T371.hs:(0,0)-(0,0): Splicing declarations singletons [d| data Y (a :: Type) = Y1 | Y2 (X a) deriving Show data X (a :: Type) = X1 | X2 (Y a) deriving Show |] ======> data X (a :: Type) = X1 | X2 (Y a) deriving Show data Y (a :: Type) = Y1 | Y2 (X a) deriving Show type X1Sym0 = X1 :: X (a :: Type) type X2Sym0 :: forall (a :: Type). (~>) (Y a) (X (a :: Type)) data X2Sym0 a0123456789876543210 where X2Sym0KindInference :: SameKind (Apply X2Sym0 arg) (X2Sym1 arg) => X2Sym0 a0123456789876543210 type instance Apply X2Sym0 a0123456789876543210 = X2Sym1 a0123456789876543210 instance SuppressUnusedWarnings X2Sym0 where suppressUnusedWarnings = snd (((,) X2Sym0KindInference) ()) type X2Sym1 (a0123456789876543210 :: Y a) = X2 a0123456789876543210 :: X (a :: Type) type Y1Sym0 = Y1 :: Y (a :: Type) type Y2Sym0 :: forall (a :: Type). (~>) (X a) (Y (a :: Type)) data Y2Sym0 a0123456789876543210 where Y2Sym0KindInference :: SameKind (Apply Y2Sym0 arg) (Y2Sym1 arg) => Y2Sym0 a0123456789876543210 type instance Apply Y2Sym0 a0123456789876543210 = Y2Sym1 a0123456789876543210 instance SuppressUnusedWarnings Y2Sym0 where suppressUnusedWarnings = snd (((,) Y2Sym0KindInference) ()) type Y2Sym1 (a0123456789876543210 :: X a) = Y2 a0123456789876543210 :: Y (a :: Type) type ShowsPrec_0123456789876543210 :: GHC.Types.Nat -> X a -> GHC.Types.Symbol -> GHC.Types.Symbol type family ShowsPrec_0123456789876543210 a a a where ShowsPrec_0123456789876543210 _ X1 a_0123456789876543210 = Apply (Apply ShowStringSym0 "X1") a_0123456789876543210 ShowsPrec_0123456789876543210 p_0123456789876543210 (X2 arg_0123456789876543210) a_0123456789876543210 = Apply (Apply (Apply ShowParenSym0 (Apply (Apply (>@#@$) p_0123456789876543210) (Data.Singletons.Prelude.Num.FromInteger 10))) (Apply (Apply (.@#@$) (Apply ShowStringSym0 "X2 ")) (Apply (Apply ShowsPrecSym0 (Data.Singletons.Prelude.Num.FromInteger 11)) arg_0123456789876543210))) a_0123456789876543210 type ShowsPrec_0123456789876543210Sym0 :: (~>) GHC.Types.Nat ((~>) (X a) ((~>) GHC.Types.Symbol GHC.Types.Symbol)) data ShowsPrec_0123456789876543210Sym0 a0123456789876543210 where ShowsPrec_0123456789876543210Sym0KindInference :: SameKind (Apply ShowsPrec_0123456789876543210Sym0 arg) (ShowsPrec_0123456789876543210Sym1 arg) => ShowsPrec_0123456789876543210Sym0 a0123456789876543210 type instance Apply ShowsPrec_0123456789876543210Sym0 a0123456789876543210 = ShowsPrec_0123456789876543210Sym1 a0123456789876543210 instance SuppressUnusedWarnings ShowsPrec_0123456789876543210Sym0 where suppressUnusedWarnings = snd (((,) ShowsPrec_0123456789876543210Sym0KindInference) ()) type ShowsPrec_0123456789876543210Sym1 :: GHC.Types.Nat -> (~>) (X a) ((~>) GHC.Types.Symbol GHC.Types.Symbol) data ShowsPrec_0123456789876543210Sym1 a0123456789876543210 a0123456789876543210 where ShowsPrec_0123456789876543210Sym1KindInference :: SameKind (Apply (ShowsPrec_0123456789876543210Sym1 a0123456789876543210) arg) (ShowsPrec_0123456789876543210Sym2 a0123456789876543210 arg) => ShowsPrec_0123456789876543210Sym1 a0123456789876543210 a0123456789876543210 type instance Apply (ShowsPrec_0123456789876543210Sym1 a0123456789876543210) a0123456789876543210 = ShowsPrec_0123456789876543210Sym2 a0123456789876543210 a0123456789876543210 instance SuppressUnusedWarnings (ShowsPrec_0123456789876543210Sym1 a0123456789876543210) where suppressUnusedWarnings = snd (((,) ShowsPrec_0123456789876543210Sym1KindInference) ()) type ShowsPrec_0123456789876543210Sym2 :: GHC.Types.Nat -> X a -> (~>) GHC.Types.Symbol GHC.Types.Symbol data ShowsPrec_0123456789876543210Sym2 a0123456789876543210 a0123456789876543210 a0123456789876543210 where ShowsPrec_0123456789876543210Sym2KindInference :: SameKind (Apply (ShowsPrec_0123456789876543210Sym2 a0123456789876543210 a0123456789876543210) arg) (ShowsPrec_0123456789876543210Sym3 a0123456789876543210 a0123456789876543210 arg) => ShowsPrec_0123456789876543210Sym2 a0123456789876543210 a0123456789876543210 a0123456789876543210 type instance Apply (ShowsPrec_0123456789876543210Sym2 a0123456789876543210 a0123456789876543210) a0123456789876543210 = ShowsPrec_0123456789876543210Sym3 a0123456789876543210 a0123456789876543210 a0123456789876543210 instance SuppressUnusedWarnings (ShowsPrec_0123456789876543210Sym2 a0123456789876543210 a0123456789876543210) where suppressUnusedWarnings = snd (((,) ShowsPrec_0123456789876543210Sym2KindInference) ()) type ShowsPrec_0123456789876543210Sym3 (a0123456789876543210 :: GHC.Types.Nat) (a0123456789876543210 :: X a) (a0123456789876543210 :: GHC.Types.Symbol) = ShowsPrec_0123456789876543210 a0123456789876543210 a0123456789876543210 a0123456789876543210 :: GHC.Types.Symbol instance PShow (X a) where type ShowsPrec a a a = Apply (Apply (Apply ShowsPrec_0123456789876543210Sym0 a) a) a type ShowsPrec_0123456789876543210 :: GHC.Types.Nat -> Y a -> GHC.Types.Symbol -> GHC.Types.Symbol type family ShowsPrec_0123456789876543210 a a a where ShowsPrec_0123456789876543210 _ Y1 a_0123456789876543210 = Apply (Apply ShowStringSym0 "Y1") a_0123456789876543210 ShowsPrec_0123456789876543210 p_0123456789876543210 (Y2 arg_0123456789876543210) a_0123456789876543210 = Apply (Apply (Apply ShowParenSym0 (Apply (Apply (>@#@$) p_0123456789876543210) (Data.Singletons.Prelude.Num.FromInteger 10))) (Apply (Apply (.@#@$) (Apply ShowStringSym0 "Y2 ")) (Apply (Apply ShowsPrecSym0 (Data.Singletons.Prelude.Num.FromInteger 11)) arg_0123456789876543210))) a_0123456789876543210 type ShowsPrec_0123456789876543210Sym0 :: (~>) GHC.Types.Nat ((~>) (Y a) ((~>) GHC.Types.Symbol GHC.Types.Symbol)) data ShowsPrec_0123456789876543210Sym0 a0123456789876543210 where ShowsPrec_0123456789876543210Sym0KindInference :: SameKind (Apply ShowsPrec_0123456789876543210Sym0 arg) (ShowsPrec_0123456789876543210Sym1 arg) => ShowsPrec_0123456789876543210Sym0 a0123456789876543210 type instance Apply ShowsPrec_0123456789876543210Sym0 a0123456789876543210 = ShowsPrec_0123456789876543210Sym1 a0123456789876543210 instance SuppressUnusedWarnings ShowsPrec_0123456789876543210Sym0 where suppressUnusedWarnings = snd (((,) ShowsPrec_0123456789876543210Sym0KindInference) ()) type ShowsPrec_0123456789876543210Sym1 :: GHC.Types.Nat -> (~>) (Y a) ((~>) GHC.Types.Symbol GHC.Types.Symbol) data ShowsPrec_0123456789876543210Sym1 a0123456789876543210 a0123456789876543210 where ShowsPrec_0123456789876543210Sym1KindInference :: SameKind (Apply (ShowsPrec_0123456789876543210Sym1 a0123456789876543210) arg) (ShowsPrec_0123456789876543210Sym2 a0123456789876543210 arg) => ShowsPrec_0123456789876543210Sym1 a0123456789876543210 a0123456789876543210 type instance Apply (ShowsPrec_0123456789876543210Sym1 a0123456789876543210) a0123456789876543210 = ShowsPrec_0123456789876543210Sym2 a0123456789876543210 a0123456789876543210 instance SuppressUnusedWarnings (ShowsPrec_0123456789876543210Sym1 a0123456789876543210) where suppressUnusedWarnings = snd (((,) ShowsPrec_0123456789876543210Sym1KindInference) ()) type ShowsPrec_0123456789876543210Sym2 :: GHC.Types.Nat -> Y a -> (~>) GHC.Types.Symbol GHC.Types.Symbol data ShowsPrec_0123456789876543210Sym2 a0123456789876543210 a0123456789876543210 a0123456789876543210 where ShowsPrec_0123456789876543210Sym2KindInference :: SameKind (Apply (ShowsPrec_0123456789876543210Sym2 a0123456789876543210 a0123456789876543210) arg) (ShowsPrec_0123456789876543210Sym3 a0123456789876543210 a0123456789876543210 arg) => ShowsPrec_0123456789876543210Sym2 a0123456789876543210 a0123456789876543210 a0123456789876543210 type instance Apply (ShowsPrec_0123456789876543210Sym2 a0123456789876543210 a0123456789876543210) a0123456789876543210 = ShowsPrec_0123456789876543210Sym3 a0123456789876543210 a0123456789876543210 a0123456789876543210 instance SuppressUnusedWarnings (ShowsPrec_0123456789876543210Sym2 a0123456789876543210 a0123456789876543210) where suppressUnusedWarnings = snd (((,) ShowsPrec_0123456789876543210Sym2KindInference) ()) type ShowsPrec_0123456789876543210Sym3 (a0123456789876543210 :: GHC.Types.Nat) (a0123456789876543210 :: Y a) (a0123456789876543210 :: GHC.Types.Symbol) = ShowsPrec_0123456789876543210 a0123456789876543210 a0123456789876543210 a0123456789876543210 :: GHC.Types.Symbol instance PShow (Y a) where type ShowsPrec a a a = Apply (Apply (Apply ShowsPrec_0123456789876543210Sym0 a) a) a data SX :: forall a. X (a :: Type) -> Type where SX1 :: forall (a :: Type). SX (X1 :: X (a :: Type)) SX2 :: forall (a :: Type) (n :: Y a). (Sing n) -> SX (X2 n :: X (a :: Type)) type instance Sing @(X a) = SX instance SingKind a => SingKind (X a) where type Demote (X a) = X (Demote a) fromSing SX1 = X1 fromSing (SX2 b) = X2 (fromSing b) toSing X1 = SomeSing SX1 toSing (X2 (b :: Demote (Y a))) = case toSing b :: SomeSing (Y a) of { SomeSing c -> SomeSing (SX2 c) } data SY :: forall a. Y (a :: Type) -> Type where SY1 :: forall (a :: Type). SY (Y1 :: Y (a :: Type)) SY2 :: forall (a :: Type) (n :: X a). (Sing n) -> SY (Y2 n :: Y (a :: Type)) type instance Sing @(Y a) = SY instance SingKind a => SingKind (Y a) where type Demote (Y a) = Y (Demote a) fromSing SY1 = Y1 fromSing (SY2 b) = Y2 (fromSing b) toSing Y1 = SomeSing SY1 toSing (Y2 (b :: Demote (X a))) = case toSing b :: SomeSing (X a) of { SomeSing c -> SomeSing (SY2 c) } instance SShow (Y a) => SShow (X a) where sShowsPrec :: forall (t1 :: GHC.Types.Nat) (t2 :: X a) (t3 :: GHC.Types.Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun GHC.Types.Nat ((~>) (X a) ((~>) GHC.Types.Symbol GHC.Types.Symbol)) -> Type) t1) t2) t3) sShowsPrec _ SX1 (sA_0123456789876543210 :: Sing a_0123456789876543210) = (applySing ((applySing ((singFun2 @ShowStringSym0) sShowString)) (sing :: Sing "X1"))) sA_0123456789876543210 sShowsPrec (sP_0123456789876543210 :: Sing p_0123456789876543210) (SX2 (sArg_0123456789876543210 :: Sing arg_0123456789876543210)) (sA_0123456789876543210 :: Sing a_0123456789876543210) = (applySing ((applySing ((applySing ((singFun3 @ShowParenSym0) sShowParen)) ((applySing ((applySing ((singFun2 @(>@#@$)) (%>))) sP_0123456789876543210)) (Data.Singletons.Prelude.Num.sFromInteger (sing :: Sing 10))))) ((applySing ((applySing ((singFun3 @(.@#@$)) (%.))) ((applySing ((singFun2 @ShowStringSym0) sShowString)) (sing :: Sing "X2 ")))) ((applySing ((applySing ((singFun3 @ShowsPrecSym0) sShowsPrec)) (Data.Singletons.Prelude.Num.sFromInteger (sing :: Sing 11)))) sArg_0123456789876543210)))) sA_0123456789876543210 instance SShow (X a) => SShow (Y a) where sShowsPrec :: forall (t1 :: GHC.Types.Nat) (t2 :: Y a) (t3 :: GHC.Types.Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun GHC.Types.Nat ((~>) (Y a) ((~>) GHC.Types.Symbol GHC.Types.Symbol)) -> Type) t1) t2) t3) sShowsPrec _ SY1 (sA_0123456789876543210 :: Sing a_0123456789876543210) = (applySing ((applySing ((singFun2 @ShowStringSym0) sShowString)) (sing :: Sing "Y1"))) sA_0123456789876543210 sShowsPrec (sP_0123456789876543210 :: Sing p_0123456789876543210) (SY2 (sArg_0123456789876543210 :: Sing arg_0123456789876543210)) (sA_0123456789876543210 :: Sing a_0123456789876543210) = (applySing ((applySing ((applySing ((singFun3 @ShowParenSym0) sShowParen)) ((applySing ((applySing ((singFun2 @(>@#@$)) (%>))) sP_0123456789876543210)) (Data.Singletons.Prelude.Num.sFromInteger (sing :: Sing 10))))) ((applySing ((applySing ((singFun3 @(.@#@$)) (%.))) ((applySing ((singFun2 @ShowStringSym0) sShowString)) (sing :: Sing "Y2 ")))) ((applySing ((applySing ((singFun3 @ShowsPrecSym0) sShowsPrec)) (Data.Singletons.Prelude.Num.sFromInteger (sing :: Sing 11)))) sArg_0123456789876543210)))) sA_0123456789876543210 instance Data.Singletons.ShowSing.ShowSing (Y a) => Show (SX (z :: X a)) where showsPrec _ SX1 = showString "SX1" showsPrec p_0123456789876543210 (SX2 (arg_0123456789876543210 :: Sing argTy_0123456789876543210)) = (showParen (((>) p_0123456789876543210) 10)) (((.) (showString "SX2 ")) ((showsPrec 11) arg_0123456789876543210)) :: Data.Singletons.ShowSing.ShowSing' argTy_0123456789876543210 => ShowS instance Data.Singletons.ShowSing.ShowSing (X a) => Show (SY (z :: Y a)) where showsPrec _ SY1 = showString "SY1" showsPrec p_0123456789876543210 (SY2 (arg_0123456789876543210 :: Sing argTy_0123456789876543210)) = (showParen (((>) p_0123456789876543210) 10)) (((.) (showString "SY2 ")) ((showsPrec 11) arg_0123456789876543210)) :: Data.Singletons.ShowSing.ShowSing' argTy_0123456789876543210 => ShowS instance SingI X1 where sing = SX1 instance SingI n => SingI (X2 (n :: Y a)) where sing = SX2 sing instance SingI (X2Sym0 :: (~>) (Y a) (X (a :: Type))) where sing = (singFun1 @X2Sym0) SX2 instance SingI Y1 where sing = SY1 instance SingI n => SingI (Y2 (n :: X a)) where sing = SY2 sing instance SingI (Y2Sym0 :: (~>) (X a) (Y (a :: Type))) where sing = (singFun1 @Y2Sym0) SY2