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 <=> (====) :: a -> a -> a (====) a _ = a infix 4 ==== type (:====$$$) (t :: a0123456789876543210) (t :: a0123456789876543210) = (:====) t t instance SuppressUnusedWarnings (:====$$) where suppressUnusedWarnings _ = snd ((GHC.Tuple.(,) (:====$$###)) GHC.Tuple.()) data (:====$$) (l :: a0123456789876543210) (l :: TyFun a0123456789876543210 a0123456789876543210) = forall arg. SameKind (Apply ((:====$$) l) arg) ((:====$$$) l arg) => (:====$$###) type instance Apply ((:====$$) l) l = (:====) l l instance SuppressUnusedWarnings (:====$) where suppressUnusedWarnings _ = snd ((GHC.Tuple.(,) (:====$###)) GHC.Tuple.()) data (:====$) (l :: TyFun a0123456789876543210 (TyFun a0123456789876543210 a0123456789876543210 -> GHC.Types.Type)) = forall arg. SameKind (Apply (:====$) arg) ((:====$$) arg) => (:====$###) type instance Apply (:====$) l = (:====$$) l type family (:====) (a :: a) (a :: a) :: a where (:====) a _z_0123456789876543210 = a infix 4 :==== infix 4 :<=> type (:<=>$$$) (t :: a0123456789876543210) (t :: a0123456789876543210) = (:<=>) t t instance SuppressUnusedWarnings (:<=>$$) where suppressUnusedWarnings _ = snd ((GHC.Tuple.(,) (:<=>$$###)) GHC.Tuple.()) data (:<=>$$) (l :: a0123456789876543210) (l :: TyFun a0123456789876543210 Ordering) = forall arg. SameKind (Apply ((:<=>$$) l) arg) ((:<=>$$$) l arg) => (:<=>$$###) type instance Apply ((:<=>$$) l) l = (:<=>) l l instance SuppressUnusedWarnings (:<=>$) where suppressUnusedWarnings _ = snd ((GHC.Tuple.(,) (:<=>$###)) GHC.Tuple.()) data (:<=>$) (l :: TyFun a0123456789876543210 (TyFun a0123456789876543210 Ordering -> GHC.Types.Type)) = forall arg. SameKind (Apply (:<=>$) arg) ((:<=>$$) arg) => (:<=>$###) type instance Apply (:<=>$) l = (:<=>$$) l class PMyOrd (a :: GHC.Types.Type) 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 :: Sing a) _ = sA class SMyOrd a where (%:<=>) :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply (:<=>$) t) t :: Ordering)