2
2
{-# LANGUAGE TemplateHaskell #-}
3
3
{-# LANGUAGE DataKinds #-}
4
4
{-# LANGUAGE GADTs #-}
5
+ {-# LANGUAGE MagicHash #-}
5
6
{-# LANGUAGE TypeFamilies #-}
6
7
{-# LANGUAGE TypeInType #-}
7
8
{-# LANGUAGE FlexibleInstances #-}
@@ -16,7 +17,10 @@ import Data.Text (Text)
16
17
import Language.LSP.Types.Utils
17
18
import Data.Function (on )
18
19
import 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
20
24
21
25
-- ---------------------------------------------------------------------
22
26
@@ -184,8 +188,21 @@ data SMethod (m :: Method f t) where
184
188
SCancelRequest :: SMethod CancelRequest
185
189
SCustomMethod :: Text -> SMethod CustomMethod
186
190
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
189
206
190
207
deriving instance Eq (SMethod m )
191
208
deriving instance Ord (SMethod m )
0 commit comments