Singletons/Maybe.hs:(0,0)-(0,0): Splicing declarations singletons [d| data Maybe a = Nothing | Just a deriving (Eq, Show) |] ======> data Maybe a = Nothing | Just a deriving (Eq, Show) type NothingSym0 = Nothing type JustSym1 (t :: a0123456789876543210) = Just t instance SuppressUnusedWarnings JustSym0 where suppressUnusedWarnings = snd ((GHC.Tuple.(,) JustSym0KindInference) GHC.Tuple.()) data JustSym0 (l :: TyFun a0123456789876543210 (Maybe a0123456789876543210)) = forall arg. SameKind (Apply JustSym0 arg) (JustSym1 arg) => JustSym0KindInference type instance Apply JustSym0 l = Just l type family ShowsPrec_0123456789876543210 (a :: GHC.Types.Nat) (a :: Maybe a) (a :: GHC.Types.Symbol) :: GHC.Types.Symbol where ShowsPrec_0123456789876543210 _ Nothing a_0123456789876543210 = Apply (Apply ShowStringSym0 "Nothing") a_0123456789876543210 ShowsPrec_0123456789876543210 p_0123456789876543210 (Just arg_0123456789876543210) a_0123456789876543210 = Apply (Apply (Apply ShowParenSym0 (Apply (Apply (>@#@$) p_0123456789876543210) (Data.Singletons.Prelude.Num.FromInteger 10))) (Apply (Apply (.@#@$) (Apply ShowStringSym0 "Just ")) (Apply (Apply ShowsPrecSym0 (Data.Singletons.Prelude.Num.FromInteger 11)) arg_0123456789876543210))) a_0123456789876543210 type ShowsPrec_0123456789876543210Sym3 (t :: GHC.Types.Nat) (t :: Maybe a0123456789876543210) (t :: GHC.Types.Symbol) = ShowsPrec_0123456789876543210 t t t instance SuppressUnusedWarnings ShowsPrec_0123456789876543210Sym2 where suppressUnusedWarnings = snd ((GHC.Tuple.(,) ShowsPrec_0123456789876543210Sym2KindInference) GHC.Tuple.()) data ShowsPrec_0123456789876543210Sym2 (l :: GHC.Types.Nat) (l :: Maybe a0123456789876543210) (l :: TyFun GHC.Types.Symbol GHC.Types.Symbol) = forall arg. SameKind (Apply (ShowsPrec_0123456789876543210Sym2 l l) arg) (ShowsPrec_0123456789876543210Sym3 l l arg) => ShowsPrec_0123456789876543210Sym2KindInference type instance Apply (ShowsPrec_0123456789876543210Sym2 l l) l = ShowsPrec_0123456789876543210 l l l instance SuppressUnusedWarnings ShowsPrec_0123456789876543210Sym1 where suppressUnusedWarnings = snd ((GHC.Tuple.(,) ShowsPrec_0123456789876543210Sym1KindInference) GHC.Tuple.()) data ShowsPrec_0123456789876543210Sym1 (l :: GHC.Types.Nat) (l :: TyFun (Maybe a0123456789876543210) (TyFun GHC.Types.Symbol GHC.Types.Symbol -> GHC.Types.Type)) = forall arg. SameKind (Apply (ShowsPrec_0123456789876543210Sym1 l) arg) (ShowsPrec_0123456789876543210Sym2 l arg) => ShowsPrec_0123456789876543210Sym1KindInference type instance Apply (ShowsPrec_0123456789876543210Sym1 l) l = ShowsPrec_0123456789876543210Sym2 l l instance SuppressUnusedWarnings ShowsPrec_0123456789876543210Sym0 where suppressUnusedWarnings = snd ((GHC.Tuple.(,) ShowsPrec_0123456789876543210Sym0KindInference) GHC.Tuple.()) data ShowsPrec_0123456789876543210Sym0 (l :: TyFun GHC.Types.Nat (TyFun (Maybe a0123456789876543210) (TyFun GHC.Types.Symbol GHC.Types.Symbol -> GHC.Types.Type) -> GHC.Types.Type)) = forall arg. SameKind (Apply ShowsPrec_0123456789876543210Sym0 arg) (ShowsPrec_0123456789876543210Sym1 arg) => ShowsPrec_0123456789876543210Sym0KindInference type instance Apply ShowsPrec_0123456789876543210Sym0 l = ShowsPrec_0123456789876543210Sym1 l instance PShow (Maybe a) where type ShowsPrec a a a = Apply (Apply (Apply ShowsPrec_0123456789876543210Sym0 a) a) a type family Equals_0123456789876543210 (a :: Maybe a) (b :: Maybe a) :: Bool where Equals_0123456789876543210 Nothing Nothing = TrueSym0 Equals_0123456789876543210 (Just a) (Just b) = (==) a b Equals_0123456789876543210 (_ :: Maybe a) (_ :: Maybe a) = FalseSym0 instance PEq (Maybe a) where type (==) a b = Equals_0123456789876543210 a b data instance Sing (z :: Maybe a) where SNothing :: Sing Nothing SJust :: forall (n :: a). (Sing (n :: a)) -> Sing (Just n) type SMaybe = (Sing :: Maybe a -> GHC.Types.Type) instance SingKind a => SingKind (Maybe a) where type Demote (Maybe a) = Maybe (Demote a) fromSing SNothing = Nothing fromSing (SJust b) = Just (fromSing b) toSing Nothing = SomeSing SNothing toSing (Just (b :: Demote a)) = case toSing b :: SomeSing a of { SomeSing c -> SomeSing (SJust c) } instance SShow a => SShow (Maybe a) where sShowsPrec :: forall (t1 :: GHC.Types.Nat) (t2 :: Maybe a) (t3 :: GHC.Types.Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun GHC.Types.Nat (TyFun (Maybe a) (TyFun GHC.Types.Symbol GHC.Types.Symbol -> GHC.Types.Type) -> GHC.Types.Type) -> GHC.Types.Type) t1) t2) t3) sShowsPrec _ SNothing (sA_0123456789876543210 :: Sing a_0123456789876543210) = (applySing ((applySing ((singFun2 @ShowStringSym0) sShowString)) (sing :: Sing "Nothing"))) sA_0123456789876543210 sShowsPrec (sP_0123456789876543210 :: Sing p_0123456789876543210) (SJust (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 "Just ")))) ((applySing ((applySing ((singFun3 @ShowsPrecSym0) sShowsPrec)) (Data.Singletons.Prelude.Num.sFromInteger (sing :: Sing 11)))) sArg_0123456789876543210)))) sA_0123456789876543210 instance SEq a => SEq (Maybe a) where (%==) SNothing SNothing = STrue (%==) SNothing (SJust _) = SFalse (%==) (SJust _) SNothing = SFalse (%==) (SJust a) (SJust b) = ((%==) a) b instance SDecide a => SDecide (Maybe a) where (%~) SNothing SNothing = Proved Refl (%~) SNothing (SJust _) = Disproved (\ x -> case x of) (%~) (SJust _) SNothing = Disproved (\ x -> case x of) (%~) (SJust a) (SJust b) = case ((%~) a) b of Proved Refl -> Proved Refl Disproved contra -> Disproved (\ refl -> case refl of { Refl -> contra Refl }) instance Data.Singletons.ShowSing.ShowSing a => Data.Singletons.ShowSing.ShowSing (Maybe a) where Data.Singletons.ShowSing.showsSingPrec _ SNothing = showString "SNothing" Data.Singletons.ShowSing.showsSingPrec p_0123456789876543210 (SJust arg_0123456789876543210) = (showParen (((>) p_0123456789876543210) 10)) (((.) (showString "SJust ")) ((Data.Singletons.ShowSing.showsSingPrec 11) arg_0123456789876543210)) instance Data.Singletons.ShowSing.ShowSing a => Show (Sing (z :: Maybe a)) where showsPrec = Data.Singletons.ShowSing.showsSingPrec instance SingI Nothing where sing = SNothing instance SingI n => SingI (Just (n :: a)) where sing = SJust sing