{-# LANGUAGE DataKinds                  #-}
{-# LANGUAGE StandaloneDeriving         #-}
{-# LANGUAGE GADTs                      #-}
{-# LANGUAGE TypeFamilies               #-}
{-# LANGUAGE TypeInType                 #-}
{-# OPTIONS_GHC -Wno-unticked-promoted-constructors #-}
module Language.LSP.Types.LspId where

import qualified Data.Aeson                                 as A
import           Data.Text                                  (Text)
import           Data.IxMap
import Language.LSP.Types.Method

-- | Id used for a request, Can be either a String or an Int
data LspId (m :: Method f Request) = IdInt !Int | IdString !Text
  deriving (Int -> LspId m -> ShowS
[LspId m] -> ShowS
LspId m -> String
(Int -> LspId m -> ShowS)
-> (LspId m -> String) -> ([LspId m] -> ShowS) -> Show (LspId m)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (f :: From) (m :: Method f 'Request).
Int -> LspId m -> ShowS
forall (f :: From) (m :: Method f 'Request). [LspId m] -> ShowS
forall (f :: From) (m :: Method f 'Request). LspId m -> String
showList :: [LspId m] -> ShowS
$cshowList :: forall (f :: From) (m :: Method f 'Request). [LspId m] -> ShowS
show :: LspId m -> String
$cshow :: forall (f :: From) (m :: Method f 'Request). LspId m -> String
showsPrec :: Int -> LspId m -> ShowS
$cshowsPrec :: forall (f :: From) (m :: Method f 'Request).
Int -> LspId m -> ShowS
Show,ReadPrec [LspId m]
ReadPrec (LspId m)
Int -> ReadS (LspId m)
ReadS [LspId m]
(Int -> ReadS (LspId m))
-> ReadS [LspId m]
-> ReadPrec (LspId m)
-> ReadPrec [LspId m]
-> Read (LspId m)
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall (f :: From) (m :: Method f 'Request). ReadPrec [LspId m]
forall (f :: From) (m :: Method f 'Request). ReadPrec (LspId m)
forall (f :: From) (m :: Method f 'Request). Int -> ReadS (LspId m)
forall (f :: From) (m :: Method f 'Request). ReadS [LspId m]
readListPrec :: ReadPrec [LspId m]
$creadListPrec :: forall (f :: From) (m :: Method f 'Request). ReadPrec [LspId m]
readPrec :: ReadPrec (LspId m)
$creadPrec :: forall (f :: From) (m :: Method f 'Request). ReadPrec (LspId m)
readList :: ReadS [LspId m]
$creadList :: forall (f :: From) (m :: Method f 'Request). ReadS [LspId m]
readsPrec :: Int -> ReadS (LspId m)
$creadsPrec :: forall (f :: From) (m :: Method f 'Request). Int -> ReadS (LspId m)
Read,LspId m -> LspId m -> Bool
(LspId m -> LspId m -> Bool)
-> (LspId m -> LspId m -> Bool) -> Eq (LspId m)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (f :: From) (m :: Method f 'Request).
LspId m -> LspId m -> Bool
/= :: LspId m -> LspId m -> Bool
$c/= :: forall (f :: From) (m :: Method f 'Request).
LspId m -> LspId m -> Bool
== :: LspId m -> LspId m -> Bool
$c== :: forall (f :: From) (m :: Method f 'Request).
LspId m -> LspId m -> Bool
Eq,Eq (LspId m)
Eq (LspId m)
-> (LspId m -> LspId m -> Ordering)
-> (LspId m -> LspId m -> Bool)
-> (LspId m -> LspId m -> Bool)
-> (LspId m -> LspId m -> Bool)
-> (LspId m -> LspId m -> Bool)
-> (LspId m -> LspId m -> LspId m)
-> (LspId m -> LspId m -> LspId m)
-> Ord (LspId m)
LspId m -> LspId m -> Bool
LspId m -> LspId m -> Ordering
LspId m -> LspId m -> LspId m
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall (f :: From) (m :: Method f 'Request). Eq (LspId m)
forall (f :: From) (m :: Method f 'Request).
LspId m -> LspId m -> Bool
forall (f :: From) (m :: Method f 'Request).
LspId m -> LspId m -> Ordering
forall (f :: From) (m :: Method f 'Request).
LspId m -> LspId m -> LspId m
min :: LspId m -> LspId m -> LspId m
$cmin :: forall (f :: From) (m :: Method f 'Request).
LspId m -> LspId m -> LspId m
max :: LspId m -> LspId m -> LspId m
$cmax :: forall (f :: From) (m :: Method f 'Request).
LspId m -> LspId m -> LspId m
>= :: LspId m -> LspId m -> Bool
$c>= :: forall (f :: From) (m :: Method f 'Request).
LspId m -> LspId m -> Bool
> :: LspId m -> LspId m -> Bool
$c> :: forall (f :: From) (m :: Method f 'Request).
LspId m -> LspId m -> Bool
<= :: LspId m -> LspId m -> Bool
$c<= :: forall (f :: From) (m :: Method f 'Request).
LspId m -> LspId m -> Bool
< :: LspId m -> LspId m -> Bool
$c< :: forall (f :: From) (m :: Method f 'Request).
LspId m -> LspId m -> Bool
compare :: LspId m -> LspId m -> Ordering
$ccompare :: forall (f :: From) (m :: Method f 'Request).
LspId m -> LspId m -> Ordering
$cp1Ord :: forall (f :: From) (m :: Method f 'Request). Eq (LspId m)
Ord)

instance A.ToJSON (LspId m) where
  toJSON :: LspId m -> Value
toJSON (IdInt Int
i)    = Int -> Value
forall a. ToJSON a => a -> Value
A.toJSON Int
i
  toJSON (IdString Text
s) = Text -> Value
forall a. ToJSON a => a -> Value
A.toJSON Text
s

instance A.FromJSON (LspId m) where
  parseJSON :: Value -> Parser (LspId m)
parseJSON v :: Value
v@(A.Number Scientific
_) = Int -> LspId m
forall (f :: From) (m :: Method f 'Request). Int -> LspId m
IdInt (Int -> LspId m) -> Parser Int -> Parser (LspId m)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Int
forall a. FromJSON a => Value -> Parser a
A.parseJSON Value
v
  parseJSON  (A.String  Text
s) = LspId m -> Parser (LspId m)
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> LspId m
forall (f :: From) (m :: Method f 'Request). Text -> LspId m
IdString Text
s)
  parseJSON Value
_              = Parser (LspId m)
forall a. Monoid a => a
mempty

instance IxOrd LspId where
  type Base LspId = SomeLspId
  toBase :: LspId a -> Base LspId
toBase = LspId a -> Base LspId
forall (f :: From) (m :: Method f 'Request). LspId m -> SomeLspId
SomeLspId

data SomeLspId where
  SomeLspId :: !(LspId m) -> SomeLspId

deriving instance Show SomeLspId
instance Eq SomeLspId where
  SomeLspId (IdInt Int
a) == :: SomeLspId -> SomeLspId -> Bool
== SomeLspId (IdInt Int
b) = Int
a Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
b
  SomeLspId (IdString Text
a) == SomeLspId (IdString Text
b) = Text
a Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
b
  SomeLspId
_ == SomeLspId
_ = Bool
False
instance Ord SomeLspId where
  compare :: SomeLspId -> SomeLspId -> Ordering
compare (SomeLspId LspId m
x) (SomeLspId LspId m
y) = LspId m -> LspId m -> Ordering
forall (f :: From) (f :: From) (m :: Method f 'Request)
       (m :: Method f 'Request).
LspId m -> LspId m -> Ordering
go LspId m
x LspId m
y
    where
      go :: LspId m -> LspId m -> Ordering
go (IdInt    Int
a) (IdInt    Int
b) = Int
a Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` Int
b
      go (IdString Text
a) (IdString Text
b) = Text
a Text -> Text -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` Text
b
      go (IdInt    Int
_) (IdString Text
_) = Ordering
LT
      go (IdString Text
_) (IdInt    Int
_) = Ordering
GT