Singletons/Fixity.hs:(0,0)-(0,0): Splicing declarations singletons [d| infix 4 ==== infix 4 <=> (====) :: a -> a -> a a ==== _ = a class MyOrd a where (<=>) :: a -> a -> Ordering infix 4 <=> |] ======> class MyOrd a where (<=>) :: a -> a -> Ordering infix 4 <=> (====) :: forall a. a -> a -> a (====) a _ = a infix 4 ==== type (:====$$$) (t :: a0123456789) (t :: a0123456789) = (:====) t t instance SuppressUnusedWarnings (:====$$) where suppressUnusedWarnings _ = snd (GHC.Tuple.(,) (:====$$###) GHC.Tuple.()) data (:====$$) (l :: a0123456789) (l :: TyFun a0123456789 a0123456789) = forall arg. KindOf (Apply ((:====$$) l) arg) ~ KindOf ((:====$$$) l arg) => (:====$$###) type instance Apply ((:====$$) l) l = (:====$$$) l l instance SuppressUnusedWarnings (:====$) where suppressUnusedWarnings _ = snd (GHC.Tuple.(,) (:====$###) GHC.Tuple.()) data (:====$) (l :: TyFun a0123456789 (TyFun a0123456789 a0123456789 -> GHC.Types.Type)) = forall arg. KindOf (Apply (:====$) arg) ~ KindOf ((:====$$) arg) => (:====$###) type instance Apply (:====$) l = (:====$$) l type family (:====) (a :: a) (a :: a) :: a where (:====) a _z_0123456789 = a infix 4 :==== infix 4 :<=> type (:<=>$$$) (t :: a0123456789) (t :: a0123456789) = (:<=>) t t instance SuppressUnusedWarnings (:<=>$$) where suppressUnusedWarnings _ = snd (GHC.Tuple.(,) (:<=>$$###) GHC.Tuple.()) data (:<=>$$) (l :: a0123456789) (l :: TyFun a0123456789 Ordering) = forall arg. KindOf (Apply ((:<=>$$) l) arg) ~ KindOf ((:<=>$$$) l arg) => (:<=>$$###) type instance Apply ((:<=>$$) l) l = (:<=>$$$) l l instance SuppressUnusedWarnings (:<=>$) where suppressUnusedWarnings _ = snd (GHC.Tuple.(,) (:<=>$###) GHC.Tuple.()) data (:<=>$) (l :: TyFun a0123456789 (TyFun a0123456789 Ordering -> GHC.Types.Type)) = forall arg. KindOf (Apply (:<=>$) arg) ~ KindOf ((:<=>$$) arg) => (:<=>$###) type instance Apply (:<=>$) l = (:<=>$$) l class kproxy ~ Proxy => PMyOrd (kproxy :: Proxy a) where type (:<=>) (arg :: a) (arg :: a) :: Ordering infix 4 %:==== infix 4 %:<=> (%:====) :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply (:====$) t) t :: a) (%:====) sA _s_z_0123456789 = let lambda :: forall a _z_0123456789. (t ~ a, t ~ _z_0123456789) => Sing a -> Sing _z_0123456789 -> Sing (Apply (Apply (:====$) t) t :: a) lambda a _z_0123456789 = a in lambda sA _s_z_0123456789 class SMyOrd a where (%:<=>) :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply (:<=>$) t) t :: Ordering)