22{-# LANGUAGE TemplateHaskell #-}
33{-# LANGUAGE DataKinds #-}
44{-# LANGUAGE GADTs #-}
5+ {-# LANGUAGE MagicHash #-}
56{-# LANGUAGE TypeFamilies #-}
67{-# LANGUAGE TypeInType #-}
78{-# LANGUAGE FlexibleInstances #-}
@@ -16,7 +17,10 @@ import Data.Text (Text)
1617import Language.LSP.Types.Utils
1718import Data.Function (on )
1819import Control.Applicative
19- import Data.GADT.Compare.TH
20+ import Data.GADT.Compare
21+ import Data.Type.Equality
22+ import GHC.Exts (Int (.. ), dataToTag #)
23+ import Unsafe.Coerce
2024
2125-- ---------------------------------------------------------------------
2226
@@ -184,8 +188,21 @@ data SMethod (m :: Method f t) where
184188 SCancelRequest :: SMethod CancelRequest
185189 SCustomMethod :: Text -> SMethod CustomMethod
186190
187- deriveGEq ''SMethod
188- deriveGCompare ''SMethod
191+ instance GEq SMethod where
192+ geq x y = case gcompare x y of
193+ GLT -> Nothing
194+ GEQ -> Just Refl
195+ GGT -> Nothing
196+
197+ instance GCompare SMethod where
198+ gcompare (SCustomMethod x) (SCustomMethod y) = case x `compare` y of
199+ LT -> GLT
200+ EQ -> GEQ
201+ GT -> GGT
202+ gcompare x y = case I # (dataToTag# x) `compare` I # (dataToTag# y) of
203+ LT -> GLT
204+ EQ -> unsafeCoerce GEQ
205+ GT -> GGT
189206
190207deriving instance Eq (SMethod m )
191208deriving instance Ord (SMethod m )
0 commit comments