Skip to content

Commit f14a077

Browse files
authored
Merge pull request #383 from Bodigrim/master
Eliminate dependent-sum-template dependency
2 parents 4a8f16f + c70ecc6 commit f14a077

File tree

2 files changed

+20
-5
lines changed

2 files changed

+20
-5
lines changed

lsp-types/lsp-types.cabal

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -90,8 +90,6 @@ library
9090
, rope-utf16-splay >= 0.3.1.0
9191
, scientific
9292
, some
93-
, dependent-sum-template >= 0.1.0.0
94-
-- transitive dependency of the previous one, which does not have the correct lower bound
9593
, dependent-sum >= 0.7.1.0
9694
, text
9795
, template-haskell

lsp-types/src/Language/LSP/Types/Method.hs

Lines changed: 20 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
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)
1617
import Language.LSP.Types.Utils
1718
import Data.Function (on)
1819
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
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

190207
deriving instance Eq (SMethod m)
191208
deriving instance Ord (SMethod m)

0 commit comments

Comments
 (0)