Singletons/LambdaCase.hs:(0,0)-(0,0): Splicing declarations singletons [d| foo1 :: a -> Maybe a -> a foo1 d x = (\case Just y -> y Nothing -> d) x foo2 :: a -> Maybe a -> a foo2 d _ = (\case Just y -> y Nothing -> d) (Just d) foo3 :: a -> b -> a foo3 a b = (\case (p, _) -> p) (a, b) |] ======> foo1 :: a -> Maybe a -> a foo1 d x = (\case Just y -> y Nothing -> d) x foo2 :: a -> Maybe a -> a foo2 d _ = (\case Just y -> y Nothing -> d) (Just d) foo3 :: a -> b -> a foo3 a b = (\case (p, _) -> p) (a, b) type family Case_0123456789876543210 a b x_0123456789876543210 t where Case_0123456789876543210 a b x_0123456789876543210 '(p, _) = p type family Lambda_0123456789876543210 a b t where Lambda_0123456789876543210 a b x_0123456789876543210 = Case_0123456789876543210 a b x_0123456789876543210 x_0123456789876543210 type Lambda_0123456789876543210Sym3 a0123456789876543210 b0123456789876543210 t0123456789876543210 = Lambda_0123456789876543210 a0123456789876543210 b0123456789876543210 t0123456789876543210 instance SuppressUnusedWarnings (Lambda_0123456789876543210Sym2 b0123456789876543210 a0123456789876543210) where suppressUnusedWarnings = snd (((,) Lambda_0123456789876543210Sym2KindInference) ()) data Lambda_0123456789876543210Sym2 a0123456789876543210 b0123456789876543210 t0123456789876543210 where Lambda_0123456789876543210Sym2KindInference :: forall a0123456789876543210 b0123456789876543210 t0123456789876543210 arg. SameKind (Apply (Lambda_0123456789876543210Sym2 a0123456789876543210 b0123456789876543210) arg) (Lambda_0123456789876543210Sym3 a0123456789876543210 b0123456789876543210 arg) => Lambda_0123456789876543210Sym2 a0123456789876543210 b0123456789876543210 t0123456789876543210 type instance Apply (Lambda_0123456789876543210Sym2 b0123456789876543210 a0123456789876543210) t0123456789876543210 = Lambda_0123456789876543210 b0123456789876543210 a0123456789876543210 t0123456789876543210 instance SuppressUnusedWarnings (Lambda_0123456789876543210Sym1 a0123456789876543210) where suppressUnusedWarnings = snd (((,) Lambda_0123456789876543210Sym1KindInference) ()) data Lambda_0123456789876543210Sym1 a0123456789876543210 b0123456789876543210 where Lambda_0123456789876543210Sym1KindInference :: forall a0123456789876543210 b0123456789876543210 arg. SameKind (Apply (Lambda_0123456789876543210Sym1 a0123456789876543210) arg) (Lambda_0123456789876543210Sym2 a0123456789876543210 arg) => Lambda_0123456789876543210Sym1 a0123456789876543210 b0123456789876543210 type instance Apply (Lambda_0123456789876543210Sym1 a0123456789876543210) b0123456789876543210 = Lambda_0123456789876543210Sym2 a0123456789876543210 b0123456789876543210 instance SuppressUnusedWarnings Lambda_0123456789876543210Sym0 where suppressUnusedWarnings = snd (((,) Lambda_0123456789876543210Sym0KindInference) ()) data Lambda_0123456789876543210Sym0 a0123456789876543210 where Lambda_0123456789876543210Sym0KindInference :: forall a0123456789876543210 arg. SameKind (Apply Lambda_0123456789876543210Sym0 arg) (Lambda_0123456789876543210Sym1 arg) => Lambda_0123456789876543210Sym0 a0123456789876543210 type instance Apply Lambda_0123456789876543210Sym0 a0123456789876543210 = Lambda_0123456789876543210Sym1 a0123456789876543210 type family Case_0123456789876543210 d x_0123456789876543210 t where Case_0123456789876543210 d x_0123456789876543210 ( 'Just y) = y Case_0123456789876543210 d x_0123456789876543210 'Nothing = d type family Lambda_0123456789876543210 d t where Lambda_0123456789876543210 d x_0123456789876543210 = Case_0123456789876543210 d x_0123456789876543210 x_0123456789876543210 type Lambda_0123456789876543210Sym2 d0123456789876543210 t0123456789876543210 = Lambda_0123456789876543210 d0123456789876543210 t0123456789876543210 instance SuppressUnusedWarnings (Lambda_0123456789876543210Sym1 d0123456789876543210) where suppressUnusedWarnings = snd (((,) Lambda_0123456789876543210Sym1KindInference) ()) data Lambda_0123456789876543210Sym1 d0123456789876543210 t0123456789876543210 where Lambda_0123456789876543210Sym1KindInference :: forall d0123456789876543210 t0123456789876543210 arg. SameKind (Apply (Lambda_0123456789876543210Sym1 d0123456789876543210) arg) (Lambda_0123456789876543210Sym2 d0123456789876543210 arg) => Lambda_0123456789876543210Sym1 d0123456789876543210 t0123456789876543210 type instance Apply (Lambda_0123456789876543210Sym1 d0123456789876543210) t0123456789876543210 = Lambda_0123456789876543210 d0123456789876543210 t0123456789876543210 instance SuppressUnusedWarnings Lambda_0123456789876543210Sym0 where suppressUnusedWarnings = snd (((,) Lambda_0123456789876543210Sym0KindInference) ()) data Lambda_0123456789876543210Sym0 d0123456789876543210 where Lambda_0123456789876543210Sym0KindInference :: forall d0123456789876543210 arg. SameKind (Apply Lambda_0123456789876543210Sym0 arg) (Lambda_0123456789876543210Sym1 arg) => Lambda_0123456789876543210Sym0 d0123456789876543210 type instance Apply Lambda_0123456789876543210Sym0 d0123456789876543210 = Lambda_0123456789876543210Sym1 d0123456789876543210 type family Case_0123456789876543210 d x x_0123456789876543210 t where Case_0123456789876543210 d x x_0123456789876543210 ( 'Just y) = y Case_0123456789876543210 d x x_0123456789876543210 'Nothing = d type family Lambda_0123456789876543210 d x t where Lambda_0123456789876543210 d x x_0123456789876543210 = Case_0123456789876543210 d x x_0123456789876543210 x_0123456789876543210 type Lambda_0123456789876543210Sym3 d0123456789876543210 x0123456789876543210 t0123456789876543210 = Lambda_0123456789876543210 d0123456789876543210 x0123456789876543210 t0123456789876543210 instance SuppressUnusedWarnings (Lambda_0123456789876543210Sym2 x0123456789876543210 d0123456789876543210) where suppressUnusedWarnings = snd (((,) Lambda_0123456789876543210Sym2KindInference) ()) data Lambda_0123456789876543210Sym2 d0123456789876543210 x0123456789876543210 t0123456789876543210 where Lambda_0123456789876543210Sym2KindInference :: forall d0123456789876543210 x0123456789876543210 t0123456789876543210 arg. SameKind (Apply (Lambda_0123456789876543210Sym2 d0123456789876543210 x0123456789876543210) arg) (Lambda_0123456789876543210Sym3 d0123456789876543210 x0123456789876543210 arg) => Lambda_0123456789876543210Sym2 d0123456789876543210 x0123456789876543210 t0123456789876543210 type instance Apply (Lambda_0123456789876543210Sym2 x0123456789876543210 d0123456789876543210) t0123456789876543210 = Lambda_0123456789876543210 x0123456789876543210 d0123456789876543210 t0123456789876543210 instance SuppressUnusedWarnings (Lambda_0123456789876543210Sym1 d0123456789876543210) where suppressUnusedWarnings = snd (((,) Lambda_0123456789876543210Sym1KindInference) ()) data Lambda_0123456789876543210Sym1 d0123456789876543210 x0123456789876543210 where Lambda_0123456789876543210Sym1KindInference :: forall d0123456789876543210 x0123456789876543210 arg. SameKind (Apply (Lambda_0123456789876543210Sym1 d0123456789876543210) arg) (Lambda_0123456789876543210Sym2 d0123456789876543210 arg) => Lambda_0123456789876543210Sym1 d0123456789876543210 x0123456789876543210 type instance Apply (Lambda_0123456789876543210Sym1 d0123456789876543210) x0123456789876543210 = Lambda_0123456789876543210Sym2 d0123456789876543210 x0123456789876543210 instance SuppressUnusedWarnings Lambda_0123456789876543210Sym0 where suppressUnusedWarnings = snd (((,) Lambda_0123456789876543210Sym0KindInference) ()) data Lambda_0123456789876543210Sym0 d0123456789876543210 where Lambda_0123456789876543210Sym0KindInference :: forall d0123456789876543210 arg. SameKind (Apply Lambda_0123456789876543210Sym0 arg) (Lambda_0123456789876543210Sym1 arg) => Lambda_0123456789876543210Sym0 d0123456789876543210 type instance Apply Lambda_0123456789876543210Sym0 d0123456789876543210 = Lambda_0123456789876543210Sym1 d0123456789876543210 type Foo3Sym2 (a0123456789876543210 :: a0123456789876543210) (a0123456789876543210 :: b0123456789876543210) = Foo3 a0123456789876543210 a0123456789876543210 instance SuppressUnusedWarnings (Foo3Sym1 a0123456789876543210) where suppressUnusedWarnings = snd (((,) Foo3Sym1KindInference) ()) data Foo3Sym1 (a0123456789876543210 :: a0123456789876543210) :: forall b0123456789876543210. (~>) b0123456789876543210 a0123456789876543210 where Foo3Sym1KindInference :: forall a0123456789876543210 a0123456789876543210 arg. SameKind (Apply (Foo3Sym1 a0123456789876543210) arg) (Foo3Sym2 a0123456789876543210 arg) => Foo3Sym1 a0123456789876543210 a0123456789876543210 type instance Apply (Foo3Sym1 a0123456789876543210) a0123456789876543210 = Foo3 a0123456789876543210 a0123456789876543210 instance SuppressUnusedWarnings Foo3Sym0 where suppressUnusedWarnings = snd (((,) Foo3Sym0KindInference) ()) data Foo3Sym0 :: forall a0123456789876543210 b0123456789876543210. (~>) a0123456789876543210 ((~>) b0123456789876543210 a0123456789876543210) where Foo3Sym0KindInference :: forall a0123456789876543210 arg. SameKind (Apply Foo3Sym0 arg) (Foo3Sym1 arg) => Foo3Sym0 a0123456789876543210 type instance Apply Foo3Sym0 a0123456789876543210 = Foo3Sym1 a0123456789876543210 type Foo2Sym2 (a0123456789876543210 :: a0123456789876543210) (a0123456789876543210 :: Maybe a0123456789876543210) = Foo2 a0123456789876543210 a0123456789876543210 instance SuppressUnusedWarnings (Foo2Sym1 a0123456789876543210) where suppressUnusedWarnings = snd (((,) Foo2Sym1KindInference) ()) data Foo2Sym1 (a0123456789876543210 :: a0123456789876543210) :: (~>) (Maybe a0123456789876543210) a0123456789876543210 where Foo2Sym1KindInference :: forall a0123456789876543210 a0123456789876543210 arg. SameKind (Apply (Foo2Sym1 a0123456789876543210) arg) (Foo2Sym2 a0123456789876543210 arg) => Foo2Sym1 a0123456789876543210 a0123456789876543210 type instance Apply (Foo2Sym1 a0123456789876543210) a0123456789876543210 = Foo2 a0123456789876543210 a0123456789876543210 instance SuppressUnusedWarnings Foo2Sym0 where suppressUnusedWarnings = snd (((,) Foo2Sym0KindInference) ()) data Foo2Sym0 :: forall a0123456789876543210. (~>) a0123456789876543210 ((~>) (Maybe a0123456789876543210) a0123456789876543210) where Foo2Sym0KindInference :: forall a0123456789876543210 arg. SameKind (Apply Foo2Sym0 arg) (Foo2Sym1 arg) => Foo2Sym0 a0123456789876543210 type instance Apply Foo2Sym0 a0123456789876543210 = Foo2Sym1 a0123456789876543210 type Foo1Sym2 (a0123456789876543210 :: a0123456789876543210) (a0123456789876543210 :: Maybe a0123456789876543210) = Foo1 a0123456789876543210 a0123456789876543210 instance SuppressUnusedWarnings (Foo1Sym1 a0123456789876543210) where suppressUnusedWarnings = snd (((,) Foo1Sym1KindInference) ()) data Foo1Sym1 (a0123456789876543210 :: a0123456789876543210) :: (~>) (Maybe a0123456789876543210) a0123456789876543210 where Foo1Sym1KindInference :: forall a0123456789876543210 a0123456789876543210 arg. SameKind (Apply (Foo1Sym1 a0123456789876543210) arg) (Foo1Sym2 a0123456789876543210 arg) => Foo1Sym1 a0123456789876543210 a0123456789876543210 type instance Apply (Foo1Sym1 a0123456789876543210) a0123456789876543210 = Foo1 a0123456789876543210 a0123456789876543210 instance SuppressUnusedWarnings Foo1Sym0 where suppressUnusedWarnings = snd (((,) Foo1Sym0KindInference) ()) data Foo1Sym0 :: forall a0123456789876543210. (~>) a0123456789876543210 ((~>) (Maybe a0123456789876543210) a0123456789876543210) where Foo1Sym0KindInference :: forall a0123456789876543210 arg. SameKind (Apply Foo1Sym0 arg) (Foo1Sym1 arg) => Foo1Sym0 a0123456789876543210 type instance Apply Foo1Sym0 a0123456789876543210 = Foo1Sym1 a0123456789876543210 type family Foo3 (a :: a) (a :: b) :: a where Foo3 a b = Apply (Apply (Apply Lambda_0123456789876543210Sym0 a) b) (Apply (Apply Tuple2Sym0 a) b) type family Foo2 (a :: a) (a :: Maybe a) :: a where Foo2 d _ = Apply (Apply Lambda_0123456789876543210Sym0 d) (Apply JustSym0 d) type family Foo1 (a :: a) (a :: Maybe a) :: a where Foo1 d x = Apply (Apply (Apply Lambda_0123456789876543210Sym0 d) x) x sFoo3 :: forall a b (t :: a) (t :: b). Sing t -> Sing t -> Sing (Apply (Apply Foo3Sym0 t) t :: a) sFoo2 :: forall a (t :: a) (t :: Maybe a). Sing t -> Sing t -> Sing (Apply (Apply Foo2Sym0 t) t :: a) sFoo1 :: forall a (t :: a) (t :: Maybe a). Sing t -> Sing t -> Sing (Apply (Apply Foo1Sym0 t) t :: a) sFoo3 (sA :: Sing a) (sB :: Sing b) = (applySing ((singFun1 @(Apply (Apply Lambda_0123456789876543210Sym0 a) b)) (\ sX_0123456789876543210 -> case sX_0123456789876543210 of { (_ :: Sing x_0123456789876543210) -> (case sX_0123456789876543210 of { STuple2 (sP :: Sing p) _ -> sP }) :: Sing (Case_0123456789876543210 a b x_0123456789876543210 x_0123456789876543210) }))) ((applySing ((applySing ((singFun2 @Tuple2Sym0) STuple2)) sA)) sB) sFoo2 (sD :: Sing d) _ = (applySing ((singFun1 @(Apply Lambda_0123456789876543210Sym0 d)) (\ sX_0123456789876543210 -> case sX_0123456789876543210 of { (_ :: Sing x_0123456789876543210) -> (case sX_0123456789876543210 of SJust (sY :: Sing y) -> sY SNothing -> sD) :: Sing (Case_0123456789876543210 d x_0123456789876543210 x_0123456789876543210) }))) ((applySing ((singFun1 @JustSym0) SJust)) sD) sFoo1 (sD :: Sing d) (sX :: Sing x) = (applySing ((singFun1 @(Apply (Apply Lambda_0123456789876543210Sym0 d) x)) (\ sX_0123456789876543210 -> case sX_0123456789876543210 of { (_ :: Sing x_0123456789876543210) -> (case sX_0123456789876543210 of SJust (sY :: Sing y) -> sY SNothing -> sD) :: Sing (Case_0123456789876543210 d x x_0123456789876543210 x_0123456789876543210) }))) sX instance SingI (Foo3Sym0 :: (~>) a ((~>) b a)) where sing = (singFun2 @Foo3Sym0) sFoo3 instance SingI d => SingI (Foo3Sym1 (d :: a) :: (~>) b a) where sing = (singFun1 @(Foo3Sym1 (d :: a))) (sFoo3 (sing @d)) instance SingI (Foo2Sym0 :: (~>) a ((~>) (Maybe a) a)) where sing = (singFun2 @Foo2Sym0) sFoo2 instance SingI d => SingI (Foo2Sym1 (d :: a) :: (~>) (Maybe a) a) where sing = (singFun1 @(Foo2Sym1 (d :: a))) (sFoo2 (sing @d)) instance SingI (Foo1Sym0 :: (~>) a ((~>) (Maybe a) a)) where sing = (singFun2 @Foo1Sym0) sFoo1 instance SingI d => SingI (Foo1Sym1 (d :: a) :: (~>) (Maybe a) a) where sing = (singFun1 @(Foo1Sym1 (d :: a))) (sFoo1 (sing @d))