{- 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.UInitializeParams where

import Control.DeepSeq
import Data.Hashable
import GHC.Generics
import Language.LSP.Protocol.Utils.Misc
import Prettyprinter
import qualified Data.Aeson
import qualified Data.Aeson as Aeson
import qualified Data.Row as Row
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.ClientCapabilities
import qualified Language.LSP.Protocol.Internal.Types.ProgressToken
import qualified Language.LSP.Protocol.Internal.Types.TraceValues
import qualified Language.LSP.Protocol.Types.Common
import qualified Language.LSP.Protocol.Types.Uri

{-|
The initialize parameters
-}
data UInitializeParams = UInitializeParams 
  { {-|
  An optional token that a server can use to report work done progress.
  -}
  UInitializeParams -> Maybe ProgressToken
_workDoneToken :: (Maybe Language.LSP.Protocol.Internal.Types.ProgressToken.ProgressToken)
  , {-|
  The process Id of the parent process that started
  the server.

  Is `null` if the process has not been started by another process.
  If the parent process is not alive then the server should exit.
  -}
  UInitializeParams -> Int32 |? Null
_processId :: (Language.LSP.Protocol.Types.Common.Int32 Language.LSP.Protocol.Types.Common.|? Language.LSP.Protocol.Types.Common.Null)
  , {-|
  Information about the client

  @since 3.15.0
  -}
  UInitializeParams
-> Maybe
     (Rec
        (("name" .== Text)
         .+ (Extend "version" (Maybe Text) ('R '[]) .+ 'R '[])))
_clientInfo :: (Maybe (Row.Rec ("name" Row..== Data.Text.Text Row..+ ("version" Row..== (Maybe Data.Text.Text) Row..+ Row.Empty))))
  , {-|
  The locale the client is currently showing the user interface
  in. This must not necessarily be the locale of the operating
  system.

  Uses IETF language tags as the value's syntax
  (See https://en.wikipedia.org/wiki/IETF_language_tag)

  @since 3.16.0
  -}
  UInitializeParams -> Maybe Text
_locale :: (Maybe Data.Text.Text)
  , {-|
  The rootPath of the workspace. Is null
  if no folder is open.

  @deprecated in favour of rootUri.
  -}
  UInitializeParams -> Maybe (Text |? Null)
_rootPath :: (Maybe (Data.Text.Text Language.LSP.Protocol.Types.Common.|? Language.LSP.Protocol.Types.Common.Null))
  , {-|
  The rootUri of the workspace. Is null if no
  folder is open. If both `rootPath` and `rootUri` are set
  `rootUri` wins.

  @deprecated in favour of workspaceFolders.
  -}
  UInitializeParams -> Uri |? Null
_rootUri :: (Language.LSP.Protocol.Types.Uri.Uri Language.LSP.Protocol.Types.Common.|? Language.LSP.Protocol.Types.Common.Null)
  , {-|
  The capabilities provided by the client (editor or tool)
  -}
  UInitializeParams -> ClientCapabilities
_capabilities :: Language.LSP.Protocol.Internal.Types.ClientCapabilities.ClientCapabilities
  , {-|
  User provided initialization options.
  -}
  UInitializeParams -> Maybe Value
_initializationOptions :: (Maybe Data.Aeson.Value)
  , {-|
  The initial trace setting. If omitted trace is disabled ('off').
  -}
  UInitializeParams -> Maybe TraceValues
_trace :: (Maybe Language.LSP.Protocol.Internal.Types.TraceValues.TraceValues)
  }
  deriving stock (Int -> UInitializeParams -> ShowS
[UInitializeParams] -> ShowS
UInitializeParams -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UInitializeParams] -> ShowS
$cshowList :: [UInitializeParams] -> ShowS
show :: UInitializeParams -> String
$cshow :: UInitializeParams -> String
showsPrec :: Int -> UInitializeParams -> ShowS
$cshowsPrec :: Int -> UInitializeParams -> ShowS
Show, UInitializeParams -> UInitializeParams -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UInitializeParams -> UInitializeParams -> Bool
$c/= :: UInitializeParams -> UInitializeParams -> Bool
== :: UInitializeParams -> UInitializeParams -> Bool
$c== :: UInitializeParams -> UInitializeParams -> Bool
Eq, Eq UInitializeParams
UInitializeParams -> UInitializeParams -> Bool
UInitializeParams -> UInitializeParams -> Ordering
UInitializeParams -> UInitializeParams -> UInitializeParams
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 :: UInitializeParams -> UInitializeParams -> UInitializeParams
$cmin :: UInitializeParams -> UInitializeParams -> UInitializeParams
max :: UInitializeParams -> UInitializeParams -> UInitializeParams
$cmax :: UInitializeParams -> UInitializeParams -> UInitializeParams
>= :: UInitializeParams -> UInitializeParams -> Bool
$c>= :: UInitializeParams -> UInitializeParams -> Bool
> :: UInitializeParams -> UInitializeParams -> Bool
$c> :: UInitializeParams -> UInitializeParams -> Bool
<= :: UInitializeParams -> UInitializeParams -> Bool
$c<= :: UInitializeParams -> UInitializeParams -> Bool
< :: UInitializeParams -> UInitializeParams -> Bool
$c< :: UInitializeParams -> UInitializeParams -> Bool
compare :: UInitializeParams -> UInitializeParams -> Ordering
$ccompare :: UInitializeParams -> UInitializeParams -> Ordering
Ord, forall x. Rep UInitializeParams x -> UInitializeParams
forall x. UInitializeParams -> Rep UInitializeParams x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UInitializeParams x -> UInitializeParams
$cfrom :: forall x. UInitializeParams -> Rep UInitializeParams x
Generic)
  deriving anyclass (UInitializeParams -> ()
forall a. (a -> ()) -> NFData a
rnf :: UInitializeParams -> ()
$crnf :: UInitializeParams -> ()
NFData, Eq UInitializeParams
Int -> UInitializeParams -> Int
UInitializeParams -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: UInitializeParams -> Int
$chash :: UInitializeParams -> Int
hashWithSalt :: Int -> UInitializeParams -> Int
$chashWithSalt :: Int -> UInitializeParams -> Int
Hashable)
  deriving forall ann. [UInitializeParams] -> Doc ann
forall ann. UInitializeParams -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
prettyList :: forall ann. [UInitializeParams] -> Doc ann
$cprettyList :: forall ann. [UInitializeParams] -> Doc ann
pretty :: forall ann. UInitializeParams -> Doc ann
$cpretty :: forall ann. UInitializeParams -> Doc ann
Pretty via (ViaJSON UInitializeParams)

instance Aeson.ToJSON UInitializeParams where
  toJSON :: UInitializeParams -> Value
toJSON (UInitializeParams Maybe ProgressToken
arg0 Int32 |? Null
arg1 Maybe
  (Rec
     (("name" .== Text)
      .+ (Extend "version" (Maybe Text) ('R '[]) .+ 'R '[])))
arg2 Maybe Text
arg3 Maybe (Text |? Null)
arg4 Uri |? Null
arg5 ClientCapabilities
arg6 Maybe Value
arg7 Maybe TraceValues
arg8) = [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
$  [String
"workDoneToken" forall kv v. (KeyValue kv, ToJSON v) => String -> Maybe v -> [kv]
Language.LSP.Protocol.Types.Common..=? Maybe ProgressToken
arg0
    ,[Key
"processId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Aeson..= Int32 |? Null
arg1]
    ,String
"clientInfo" forall kv v. (KeyValue kv, ToJSON v) => String -> Maybe v -> [kv]
Language.LSP.Protocol.Types.Common..=? Maybe
  (Rec
     (("name" .== Text)
      .+ (Extend "version" (Maybe Text) ('R '[]) .+ 'R '[])))
arg2
    ,String
"locale" forall kv v. (KeyValue kv, ToJSON v) => String -> Maybe v -> [kv]
Language.LSP.Protocol.Types.Common..=? Maybe Text
arg3
    ,String
"rootPath" forall kv v. (KeyValue kv, ToJSON v) => String -> Maybe v -> [kv]
Language.LSP.Protocol.Types.Common..=? Maybe (Text |? Null)
arg4
    ,[Key
"rootUri" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Aeson..= Uri |? Null
arg5]
    ,[Key
"capabilities" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Aeson..= ClientCapabilities
arg6]
    ,String
"initializationOptions" forall kv v. (KeyValue kv, ToJSON v) => String -> Maybe v -> [kv]
Language.LSP.Protocol.Types.Common..=? Maybe Value
arg7
    ,String
"trace" forall kv v. (KeyValue kv, ToJSON v) => String -> Maybe v -> [kv]
Language.LSP.Protocol.Types.Common..=? Maybe TraceValues
arg8]

instance Aeson.FromJSON UInitializeParams where
  parseJSON :: Value -> Parser UInitializeParams
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"_InitializeParams" forall a b. (a -> b) -> a -> b
$ \Object
arg -> Maybe ProgressToken
-> (Int32 |? Null)
-> Maybe
     (Rec
        (("name" .== Text)
         .+ (Extend "version" (Maybe Text) ('R '[]) .+ 'R '[])))
-> Maybe Text
-> Maybe (Text |? Null)
-> (Uri |? Null)
-> ClientCapabilities
-> Maybe Value
-> Maybe TraceValues
-> UInitializeParams
UInitializeParams forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
arg forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Aeson..:! Key
"workDoneToken" forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
arg forall a. FromJSON a => Object -> Key -> Parser a
Aeson..: Key
"processId" 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
"clientInfo" 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
"locale" 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
"rootPath" forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
arg forall a. FromJSON a => Object -> Key -> Parser a
Aeson..: Key
"rootUri" forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
arg forall a. FromJSON a => Object -> Key -> Parser a
Aeson..: Key
"capabilities" 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
"initializationOptions" 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
"trace"