{-# OPTIONS_GHC -Wno-unused-imports #-}
{-# OPTIONS_GHC -Wno-unused-matches #-}
{-# OPTIONS_GHC -Wno-deprecations #-}
module Language.LSP.Protocol.Internal.Types.SymbolInformation 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.Location
import qualified Language.LSP.Protocol.Internal.Types.SymbolKind
import qualified Language.LSP.Protocol.Internal.Types.SymbolTag
import qualified Language.LSP.Protocol.Types.Common
data SymbolInformation = SymbolInformation
{
SymbolInformation -> Text
_name :: Data.Text.Text
,
SymbolInformation -> SymbolKind
_kind :: Language.LSP.Protocol.Internal.Types.SymbolKind.SymbolKind
,
SymbolInformation -> Maybe [SymbolTag]
_tags :: (Maybe [Language.LSP.Protocol.Internal.Types.SymbolTag.SymbolTag])
,
SymbolInformation -> Maybe Text
_containerName :: (Maybe Data.Text.Text)
,
SymbolInformation -> Maybe Bool
_deprecated :: (Maybe Bool)
,
SymbolInformation -> Location
_location :: Language.LSP.Protocol.Internal.Types.Location.Location
}
deriving stock (Int -> SymbolInformation -> ShowS
[SymbolInformation] -> ShowS
SymbolInformation -> String
(Int -> SymbolInformation -> ShowS)
-> (SymbolInformation -> String)
-> ([SymbolInformation] -> ShowS)
-> Show SymbolInformation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SymbolInformation -> ShowS
showsPrec :: Int -> SymbolInformation -> ShowS
$cshow :: SymbolInformation -> String
show :: SymbolInformation -> String
$cshowList :: [SymbolInformation] -> ShowS
showList :: [SymbolInformation] -> ShowS
Show, SymbolInformation -> SymbolInformation -> Bool
(SymbolInformation -> SymbolInformation -> Bool)
-> (SymbolInformation -> SymbolInformation -> Bool)
-> Eq SymbolInformation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SymbolInformation -> SymbolInformation -> Bool
== :: SymbolInformation -> SymbolInformation -> Bool
$c/= :: SymbolInformation -> SymbolInformation -> Bool
/= :: SymbolInformation -> SymbolInformation -> Bool
Eq, Eq SymbolInformation
Eq SymbolInformation =>
(SymbolInformation -> SymbolInformation -> Ordering)
-> (SymbolInformation -> SymbolInformation -> Bool)
-> (SymbolInformation -> SymbolInformation -> Bool)
-> (SymbolInformation -> SymbolInformation -> Bool)
-> (SymbolInformation -> SymbolInformation -> Bool)
-> (SymbolInformation -> SymbolInformation -> SymbolInformation)
-> (SymbolInformation -> SymbolInformation -> SymbolInformation)
-> Ord SymbolInformation
SymbolInformation -> SymbolInformation -> Bool
SymbolInformation -> SymbolInformation -> Ordering
SymbolInformation -> SymbolInformation -> SymbolInformation
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 :: SymbolInformation -> SymbolInformation -> Ordering
compare :: SymbolInformation -> SymbolInformation -> Ordering
$c< :: SymbolInformation -> SymbolInformation -> Bool
< :: SymbolInformation -> SymbolInformation -> Bool
$c<= :: SymbolInformation -> SymbolInformation -> Bool
<= :: SymbolInformation -> SymbolInformation -> Bool
$c> :: SymbolInformation -> SymbolInformation -> Bool
> :: SymbolInformation -> SymbolInformation -> Bool
$c>= :: SymbolInformation -> SymbolInformation -> Bool
>= :: SymbolInformation -> SymbolInformation -> Bool
$cmax :: SymbolInformation -> SymbolInformation -> SymbolInformation
max :: SymbolInformation -> SymbolInformation -> SymbolInformation
$cmin :: SymbolInformation -> SymbolInformation -> SymbolInformation
min :: SymbolInformation -> SymbolInformation -> SymbolInformation
Ord, (forall x. SymbolInformation -> Rep SymbolInformation x)
-> (forall x. Rep SymbolInformation x -> SymbolInformation)
-> Generic SymbolInformation
forall x. Rep SymbolInformation x -> SymbolInformation
forall x. SymbolInformation -> Rep SymbolInformation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SymbolInformation -> Rep SymbolInformation x
from :: forall x. SymbolInformation -> Rep SymbolInformation x
$cto :: forall x. Rep SymbolInformation x -> SymbolInformation
to :: forall x. Rep SymbolInformation x -> SymbolInformation
Generic)
deriving anyclass (SymbolInformation -> ()
(SymbolInformation -> ()) -> NFData SymbolInformation
forall a. (a -> ()) -> NFData a
$crnf :: SymbolInformation -> ()
rnf :: SymbolInformation -> ()
NFData, Eq SymbolInformation
Eq SymbolInformation =>
(Int -> SymbolInformation -> Int)
-> (SymbolInformation -> Int) -> Hashable SymbolInformation
Int -> SymbolInformation -> Int
SymbolInformation -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> SymbolInformation -> Int
hashWithSalt :: Int -> SymbolInformation -> Int
$chash :: SymbolInformation -> Int
hash :: SymbolInformation -> Int
Hashable)
deriving (forall ann. SymbolInformation -> Doc ann)
-> (forall ann. [SymbolInformation] -> Doc ann)
-> Pretty SymbolInformation
forall ann. [SymbolInformation] -> Doc ann
forall ann. SymbolInformation -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
$cpretty :: forall ann. SymbolInformation -> Doc ann
pretty :: forall ann. SymbolInformation -> Doc ann
$cprettyList :: forall ann. [SymbolInformation] -> Doc ann
prettyList :: forall ann. [SymbolInformation] -> Doc ann
Pretty via (ViaJSON SymbolInformation)
instance Aeson.ToJSON SymbolInformation where
toJSON :: SymbolInformation -> Value
toJSON (SymbolInformation Text
arg0 SymbolKind
arg1 Maybe [SymbolTag]
arg2 Maybe Text
arg3 Maybe Bool
arg4 Location
arg5) = [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
"name" 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
"kind" Key -> SymbolKind -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
Aeson..= SymbolKind
arg1]
,String
"tags" String -> Maybe [SymbolTag] -> [Pair]
forall e kv v.
(KeyValue e kv, ToJSON v) =>
String -> Maybe v -> [kv]
Language.LSP.Protocol.Types.Common..=? Maybe [SymbolTag]
arg2
,String
"containerName" String -> Maybe Text -> [Pair]
forall e kv v.
(KeyValue e kv, ToJSON v) =>
String -> Maybe v -> [kv]
Language.LSP.Protocol.Types.Common..=? Maybe Text
arg3
,String
"deprecated" String -> Maybe Bool -> [Pair]
forall e kv v.
(KeyValue e kv, ToJSON v) =>
String -> Maybe v -> [kv]
Language.LSP.Protocol.Types.Common..=? Maybe Bool
arg4
,[Key
"location" Key -> Location -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
Aeson..= Location
arg5]]
instance Aeson.FromJSON SymbolInformation where
parseJSON :: Value -> Parser SymbolInformation
parseJSON = String
-> (Object -> Parser SymbolInformation)
-> Value
-> Parser SymbolInformation
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"SymbolInformation" ((Object -> Parser SymbolInformation)
-> Value -> Parser SymbolInformation)
-> (Object -> Parser SymbolInformation)
-> Value
-> Parser SymbolInformation
forall a b. (a -> b) -> a -> b
$ \Object
arg -> Text
-> SymbolKind
-> Maybe [SymbolTag]
-> Maybe Text
-> Maybe Bool
-> Location
-> SymbolInformation
SymbolInformation (Text
-> SymbolKind
-> Maybe [SymbolTag]
-> Maybe Text
-> Maybe Bool
-> Location
-> SymbolInformation)
-> Parser Text
-> Parser
(SymbolKind
-> Maybe [SymbolTag]
-> Maybe Text
-> Maybe Bool
-> Location
-> SymbolInformation)
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
"name" Parser
(SymbolKind
-> Maybe [SymbolTag]
-> Maybe Text
-> Maybe Bool
-> Location
-> SymbolInformation)
-> Parser SymbolKind
-> Parser
(Maybe [SymbolTag]
-> Maybe Text -> Maybe Bool -> Location -> SymbolInformation)
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 SymbolKind
forall a. FromJSON a => Object -> Key -> Parser a
Aeson..: Key
"kind" Parser
(Maybe [SymbolTag]
-> Maybe Text -> Maybe Bool -> Location -> SymbolInformation)
-> Parser (Maybe [SymbolTag])
-> Parser
(Maybe Text -> Maybe Bool -> Location -> SymbolInformation)
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 [SymbolTag])
forall v. FromJSON v => Object -> Key -> Parser (Maybe v)
Language.LSP.Protocol.Types.Common..:!? Key
"tags" Parser (Maybe Text -> Maybe Bool -> Location -> SymbolInformation)
-> Parser (Maybe Text)
-> Parser (Maybe Bool -> Location -> SymbolInformation)
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 Text)
forall v. FromJSON v => Object -> Key -> Parser (Maybe v)
Language.LSP.Protocol.Types.Common..:!? Key
"containerName" Parser (Maybe Bool -> Location -> SymbolInformation)
-> Parser (Maybe Bool) -> Parser (Location -> SymbolInformation)
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 Bool)
forall v. FromJSON v => Object -> Key -> Parser (Maybe v)
Language.LSP.Protocol.Types.Common..:!? Key
"deprecated" Parser (Location -> SymbolInformation)
-> Parser Location -> Parser SymbolInformation
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 Location
forall a. FromJSON a => Object -> Key -> Parser a
Aeson..: Key
"location"