{-# OPTIONS_GHC -Wno-unused-imports #-}
{-# OPTIONS_GHC -Wno-unused-matches #-}
{-# OPTIONS_GHC -Wno-deprecations #-}
module Language.LSP.Protocol.Internal.Types.Moniker where
import Control.DeepSeq
import Data.Hashable
import GHC.Generics
import Language.LSP.Protocol.Utils.Misc
import Prettyprinter
import qualified Data.Aeson as Aeson
import qualified Data.Row.Aeson as Aeson
import qualified Data.Row.Hashable as Hashable
import qualified Data.Text
import qualified Language.LSP.Protocol.Internal.Types.MonikerKind
import qualified Language.LSP.Protocol.Internal.Types.UniquenessLevel
import qualified Language.LSP.Protocol.Types.Common
data Moniker = Moniker
{
Moniker -> Text
_scheme :: Data.Text.Text
,
Moniker -> Text
_identifier :: Data.Text.Text
,
Moniker -> UniquenessLevel
_unique :: Language.LSP.Protocol.Internal.Types.UniquenessLevel.UniquenessLevel
,
Moniker -> Maybe MonikerKind
_kind :: (Maybe Language.LSP.Protocol.Internal.Types.MonikerKind.MonikerKind)
}
deriving stock (Int -> Moniker -> ShowS
[Moniker] -> ShowS
Moniker -> String
(Int -> Moniker -> ShowS)
-> (Moniker -> String) -> ([Moniker] -> ShowS) -> Show Moniker
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Moniker -> ShowS
showsPrec :: Int -> Moniker -> ShowS
$cshow :: Moniker -> String
show :: Moniker -> String
$cshowList :: [Moniker] -> ShowS
showList :: [Moniker] -> ShowS
Show, Moniker -> Moniker -> Bool
(Moniker -> Moniker -> Bool)
-> (Moniker -> Moniker -> Bool) -> Eq Moniker
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Moniker -> Moniker -> Bool
== :: Moniker -> Moniker -> Bool
$c/= :: Moniker -> Moniker -> Bool
/= :: Moniker -> Moniker -> Bool
Eq, Eq Moniker
Eq Moniker =>
(Moniker -> Moniker -> Ordering)
-> (Moniker -> Moniker -> Bool)
-> (Moniker -> Moniker -> Bool)
-> (Moniker -> Moniker -> Bool)
-> (Moniker -> Moniker -> Bool)
-> (Moniker -> Moniker -> Moniker)
-> (Moniker -> Moniker -> Moniker)
-> Ord Moniker
Moniker -> Moniker -> Bool
Moniker -> Moniker -> Ordering
Moniker -> Moniker -> Moniker
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
$ccompare :: Moniker -> Moniker -> Ordering
compare :: Moniker -> Moniker -> Ordering
$c< :: Moniker -> Moniker -> Bool
< :: Moniker -> Moniker -> Bool
$c<= :: Moniker -> Moniker -> Bool
<= :: Moniker -> Moniker -> Bool
$c> :: Moniker -> Moniker -> Bool
> :: Moniker -> Moniker -> Bool
$c>= :: Moniker -> Moniker -> Bool
>= :: Moniker -> Moniker -> Bool
$cmax :: Moniker -> Moniker -> Moniker
max :: Moniker -> Moniker -> Moniker
$cmin :: Moniker -> Moniker -> Moniker
min :: Moniker -> Moniker -> Moniker
Ord, (forall x. Moniker -> Rep Moniker x)
-> (forall x. Rep Moniker x -> Moniker) -> Generic Moniker
forall x. Rep Moniker x -> Moniker
forall x. Moniker -> Rep Moniker x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Moniker -> Rep Moniker x
from :: forall x. Moniker -> Rep Moniker x
$cto :: forall x. Rep Moniker x -> Moniker
to :: forall x. Rep Moniker x -> Moniker
Generic)
deriving anyclass (Moniker -> ()
(Moniker -> ()) -> NFData Moniker
forall a. (a -> ()) -> NFData a
$crnf :: Moniker -> ()
rnf :: Moniker -> ()
NFData, Eq Moniker
Eq Moniker =>
(Int -> Moniker -> Int) -> (Moniker -> Int) -> Hashable Moniker
Int -> Moniker -> Int
Moniker -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> Moniker -> Int
hashWithSalt :: Int -> Moniker -> Int
$chash :: Moniker -> Int
hash :: Moniker -> Int
Hashable)
deriving (forall ann. Moniker -> Doc ann)
-> (forall ann. [Moniker] -> Doc ann) -> Pretty Moniker
forall ann. [Moniker] -> Doc ann
forall ann. Moniker -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
$cpretty :: forall ann. Moniker -> Doc ann
pretty :: forall ann. Moniker -> Doc ann
$cprettyList :: forall ann. [Moniker] -> Doc ann
prettyList :: forall ann. [Moniker] -> Doc ann
Pretty via (ViaJSON Moniker)
instance Aeson.ToJSON Moniker where
toJSON :: Moniker -> Value
toJSON (Moniker Text
arg0 Text
arg1 UniquenessLevel
arg2 Maybe MonikerKind
arg3) = [Pair] -> Value
Aeson.object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ [[Pair]] -> [Pair]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Pair]] -> [Pair]) -> [[Pair]] -> [Pair]
forall a b. (a -> b) -> a -> b
$ [[Key
"scheme" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
Aeson..= Text
arg0]
,[Key
"identifier" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
Aeson..= Text
arg1]
,[Key
"unique" Key -> UniquenessLevel -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
Aeson..= UniquenessLevel
arg2]
,String
"kind" String -> Maybe MonikerKind -> [Pair]
forall e kv v.
(KeyValue e kv, ToJSON v) =>
String -> Maybe v -> [kv]
Language.LSP.Protocol.Types.Common..=? Maybe MonikerKind
arg3]
instance Aeson.FromJSON Moniker where
parseJSON :: Value -> Parser Moniker
parseJSON = String -> (Object -> Parser Moniker) -> Value -> Parser Moniker
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"Moniker" ((Object -> Parser Moniker) -> Value -> Parser Moniker)
-> (Object -> Parser Moniker) -> Value -> Parser Moniker
forall a b. (a -> b) -> a -> b
$ \Object
arg -> Text -> Text -> UniquenessLevel -> Maybe MonikerKind -> Moniker
Moniker (Text -> Text -> UniquenessLevel -> Maybe MonikerKind -> Moniker)
-> Parser Text
-> Parser (Text -> UniquenessLevel -> Maybe MonikerKind -> Moniker)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
arg Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
Aeson..: Key
"scheme" Parser (Text -> UniquenessLevel -> Maybe MonikerKind -> Moniker)
-> Parser Text
-> Parser (UniquenessLevel -> Maybe MonikerKind -> Moniker)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
arg Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
Aeson..: Key
"identifier" Parser (UniquenessLevel -> Maybe MonikerKind -> Moniker)
-> Parser UniquenessLevel -> Parser (Maybe MonikerKind -> Moniker)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
arg Object -> Key -> Parser UniquenessLevel
forall a. FromJSON a => Object -> Key -> Parser a
Aeson..: Key
"unique" Parser (Maybe MonikerKind -> Moniker)
-> Parser (Maybe MonikerKind) -> Parser Moniker
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
arg Object -> Key -> Parser (Maybe MonikerKind)
forall v. FromJSON v => Object -> Key -> Parser (Maybe v)
Language.LSP.Protocol.Types.Common..:!? Key
"kind"