{- ORMOLU_DISABLE -}
{- HLINT ignore -}
-- THIS IS A GENERATED FILE, DO NOT EDIT

{-# OPTIONS_GHC -Wno-unused-imports #-}
{-# OPTIONS_GHC -Wno-unused-matches #-}
{-# OPTIONS_GHC -Wno-deprecations #-}
module Language.LSP.Protocol.Internal.Types.InlayHintLabelPart 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.Command
import qualified Language.LSP.Protocol.Internal.Types.Location
import qualified Language.LSP.Protocol.Internal.Types.MarkupContent
import qualified Language.LSP.Protocol.Types.Common

{-|
An inlay hint label part allows for interactive and composite labels
of inlay hints.

@since 3.17.0
-}
data InlayHintLabelPart = InlayHintLabelPart 
  { {-|
  The value of this label part.
  -}
  InlayHintLabelPart -> Text
_value :: Data.Text.Text
  , {-|
  The tooltip text when you hover over this label part. Depending on
  the client capability `inlayHint.resolveSupport` clients might resolve
  this property late using the resolve request.
  -}
  InlayHintLabelPart -> Maybe (Text |? MarkupContent)
_tooltip :: (Maybe (Data.Text.Text Language.LSP.Protocol.Types.Common.|? Language.LSP.Protocol.Internal.Types.MarkupContent.MarkupContent))
  , {-|
  An optional source code location that represents this
  label part.

  The editor will use this location for the hover and for code navigation
  features: This part will become a clickable link that resolves to the
  definition of the symbol at the given location (not necessarily the
  location itself), it shows the hover that shows at the given location,
  and it shows a context menu with further code navigation commands.

  Depending on the client capability `inlayHint.resolveSupport` clients
  might resolve this property late using the resolve request.
  -}
  InlayHintLabelPart -> Maybe Location
_location :: (Maybe Language.LSP.Protocol.Internal.Types.Location.Location)
  , {-|
  An optional command for this label part.

  Depending on the client capability `inlayHint.resolveSupport` clients
  might resolve this property late using the resolve request.
  -}
  InlayHintLabelPart -> Maybe Command
_command :: (Maybe Language.LSP.Protocol.Internal.Types.Command.Command)
  }
  deriving stock (Int -> InlayHintLabelPart -> ShowS
[InlayHintLabelPart] -> ShowS
InlayHintLabelPart -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InlayHintLabelPart] -> ShowS
$cshowList :: [InlayHintLabelPart] -> ShowS
show :: InlayHintLabelPart -> String
$cshow :: InlayHintLabelPart -> String
showsPrec :: Int -> InlayHintLabelPart -> ShowS
$cshowsPrec :: Int -> InlayHintLabelPart -> ShowS
Show, InlayHintLabelPart -> InlayHintLabelPart -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InlayHintLabelPart -> InlayHintLabelPart -> Bool
$c/= :: InlayHintLabelPart -> InlayHintLabelPart -> Bool
== :: InlayHintLabelPart -> InlayHintLabelPart -> Bool
$c== :: InlayHintLabelPart -> InlayHintLabelPart -> Bool
Eq, Eq InlayHintLabelPart
InlayHintLabelPart -> InlayHintLabelPart -> Bool
InlayHintLabelPart -> InlayHintLabelPart -> Ordering
InlayHintLabelPart -> InlayHintLabelPart -> InlayHintLabelPart
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
min :: InlayHintLabelPart -> InlayHintLabelPart -> InlayHintLabelPart
$cmin :: InlayHintLabelPart -> InlayHintLabelPart -> InlayHintLabelPart
max :: InlayHintLabelPart -> InlayHintLabelPart -> InlayHintLabelPart
$cmax :: InlayHintLabelPart -> InlayHintLabelPart -> InlayHintLabelPart
>= :: InlayHintLabelPart -> InlayHintLabelPart -> Bool
$c>= :: InlayHintLabelPart -> InlayHintLabelPart -> Bool
> :: InlayHintLabelPart -> InlayHintLabelPart -> Bool
$c> :: InlayHintLabelPart -> InlayHintLabelPart -> Bool
<= :: InlayHintLabelPart -> InlayHintLabelPart -> Bool
$c<= :: InlayHintLabelPart -> InlayHintLabelPart -> Bool
< :: InlayHintLabelPart -> InlayHintLabelPart -> Bool
$c< :: InlayHintLabelPart -> InlayHintLabelPart -> Bool
compare :: InlayHintLabelPart -> InlayHintLabelPart -> Ordering
$ccompare :: InlayHintLabelPart -> InlayHintLabelPart -> Ordering
Ord, forall x. Rep InlayHintLabelPart x -> InlayHintLabelPart
forall x. InlayHintLabelPart -> Rep InlayHintLabelPart x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InlayHintLabelPart x -> InlayHintLabelPart
$cfrom :: forall x. InlayHintLabelPart -> Rep InlayHintLabelPart x
Generic)
  deriving anyclass (InlayHintLabelPart -> ()
forall a. (a -> ()) -> NFData a
rnf :: InlayHintLabelPart -> ()
$crnf :: InlayHintLabelPart -> ()
NFData, Eq InlayHintLabelPart
Int -> InlayHintLabelPart -> Int
InlayHintLabelPart -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: InlayHintLabelPart -> Int
$chash :: InlayHintLabelPart -> Int
hashWithSalt :: Int -> InlayHintLabelPart -> Int
$chashWithSalt :: Int -> InlayHintLabelPart -> Int
Hashable)
  deriving forall ann. [InlayHintLabelPart] -> Doc ann
forall ann. InlayHintLabelPart -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
prettyList :: forall ann. [InlayHintLabelPart] -> Doc ann
$cprettyList :: forall ann. [InlayHintLabelPart] -> Doc ann
pretty :: forall ann. InlayHintLabelPart -> Doc ann
$cpretty :: forall ann. InlayHintLabelPart -> Doc ann
Pretty via (ViaJSON InlayHintLabelPart)

instance Aeson.ToJSON InlayHintLabelPart where
  toJSON :: InlayHintLabelPart -> Value
toJSON (InlayHintLabelPart Text
arg0 Maybe (Text |? MarkupContent)
arg1 Maybe Location
arg2 Maybe Command
arg3) = [Pair] -> Value
Aeson.object forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall a b. (a -> b) -> a -> b
$  [[Key
"value" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Aeson..= Text
arg0]
    ,String
"tooltip" forall kv v. (KeyValue kv, ToJSON v) => String -> Maybe v -> [kv]
Language.LSP.Protocol.Types.Common..=? Maybe (Text |? MarkupContent)
arg1
    ,String
"location" forall kv v. (KeyValue kv, ToJSON v) => String -> Maybe v -> [kv]
Language.LSP.Protocol.Types.Common..=? Maybe Location
arg2
    ,String
"command" forall kv v. (KeyValue kv, ToJSON v) => String -> Maybe v -> [kv]
Language.LSP.Protocol.Types.Common..=? Maybe Command
arg3]

instance Aeson.FromJSON InlayHintLabelPart where
  parseJSON :: Value -> Parser InlayHintLabelPart
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"InlayHintLabelPart" forall a b. (a -> b) -> a -> b
$ \Object
arg -> Text
-> Maybe (Text |? MarkupContent)
-> Maybe Location
-> Maybe Command
-> InlayHintLabelPart
InlayHintLabelPart forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
arg forall a. FromJSON a => Object -> Key -> Parser a
Aeson..: Key
"value" forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
arg forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Aeson..:! Key
"tooltip" forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
arg forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Aeson..:! Key
"location" forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
arg forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Aeson..:! Key
"command"