Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 0 additions & 2 deletions lsp-types/lsp-types.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -90,8 +90,6 @@ library
, rope-utf16-splay >= 0.3.1.0
, scientific
, some
, dependent-sum-template >= 0.1.0.0
-- transitive dependency of the previous one, which does not have the correct lower bound
, dependent-sum >= 0.7.1.0
, text
, template-haskell
Expand Down
23 changes: 20 additions & 3 deletions lsp-types/src/Language/LSP/Types/Method.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE FlexibleInstances #-}
Expand All @@ -16,7 +17,10 @@ import Data.Text (Text)
import Language.LSP.Types.Utils
import Data.Function (on)
import Control.Applicative
import Data.GADT.Compare.TH
import Data.GADT.Compare
import Data.Type.Equality
import GHC.Exts (Int(..), dataToTag#)
import Unsafe.Coerce

-- ---------------------------------------------------------------------

Expand Down Expand Up @@ -184,8 +188,21 @@ data SMethod (m :: Method f t) where
SCancelRequest :: SMethod CancelRequest
SCustomMethod :: Text -> SMethod CustomMethod

deriveGEq ''SMethod
deriveGCompare ''SMethod
instance GEq SMethod where
geq x y = case gcompare x y of
GLT -> Nothing
GEQ -> Just Refl
GGT -> Nothing

instance GCompare SMethod where
gcompare (SCustomMethod x) (SCustomMethod y) = case x `compare` y of
LT -> GLT
EQ -> GEQ
GT -> GGT
gcompare x y = case I# (dataToTag# x) `compare` I# (dataToTag# y) of
LT -> GLT
EQ -> unsafeCoerce GEQ
GT -> GGT

deriving instance Eq (SMethod m)
deriving instance Ord (SMethod m)
Expand Down