{- 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.DidChangeTextDocumentParams 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 Language.LSP.Protocol.Internal.Types.TextDocumentContentChangeEvent
import qualified Language.LSP.Protocol.Internal.Types.VersionedTextDocumentIdentifier
import qualified Language.LSP.Protocol.Types.Common

{-|
The change text document notification's parameters.
-}
data DidChangeTextDocumentParams = DidChangeTextDocumentParams 
  { {-|
  The document that did change. The version number points
  to the version after all provided content changes have
  been applied.
  -}
  DidChangeTextDocumentParams -> VersionedTextDocumentIdentifier
_textDocument :: Language.LSP.Protocol.Internal.Types.VersionedTextDocumentIdentifier.VersionedTextDocumentIdentifier
  , {-|
  The actual content changes. The content changes describe single state changes
  to the document. So if there are two content changes c1 (at array index 0) and
  c2 (at array index 1) for a document in state S then c1 moves the document from
  S to S' and c2 from S' to S''. So c1 is computed on the state S and c2 is computed
  on the state S'.

  To mirror the content of a document using change events use the following approach:
  - start with the same initial content
  - apply the 'textDocument/didChange' notifications in the order you receive them.
  - apply the `TextDocumentContentChangeEvent`s in a single notification in the order
    you receive them.
  -}
  DidChangeTextDocumentParams -> [TextDocumentContentChangeEvent]
_contentChanges :: [Language.LSP.Protocol.Internal.Types.TextDocumentContentChangeEvent.TextDocumentContentChangeEvent]
  }
  deriving stock (Int -> DidChangeTextDocumentParams -> ShowS
[DidChangeTextDocumentParams] -> ShowS
DidChangeTextDocumentParams -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DidChangeTextDocumentParams] -> ShowS
$cshowList :: [DidChangeTextDocumentParams] -> ShowS
show :: DidChangeTextDocumentParams -> String
$cshow :: DidChangeTextDocumentParams -> String
showsPrec :: Int -> DidChangeTextDocumentParams -> ShowS
$cshowsPrec :: Int -> DidChangeTextDocumentParams -> ShowS
Show, DidChangeTextDocumentParams -> DidChangeTextDocumentParams -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DidChangeTextDocumentParams -> DidChangeTextDocumentParams -> Bool
$c/= :: DidChangeTextDocumentParams -> DidChangeTextDocumentParams -> Bool
== :: DidChangeTextDocumentParams -> DidChangeTextDocumentParams -> Bool
$c== :: DidChangeTextDocumentParams -> DidChangeTextDocumentParams -> Bool
Eq, Eq DidChangeTextDocumentParams
DidChangeTextDocumentParams -> DidChangeTextDocumentParams -> Bool
DidChangeTextDocumentParams
-> DidChangeTextDocumentParams -> Ordering
DidChangeTextDocumentParams
-> DidChangeTextDocumentParams -> DidChangeTextDocumentParams
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 :: DidChangeTextDocumentParams
-> DidChangeTextDocumentParams -> DidChangeTextDocumentParams
$cmin :: DidChangeTextDocumentParams
-> DidChangeTextDocumentParams -> DidChangeTextDocumentParams
max :: DidChangeTextDocumentParams
-> DidChangeTextDocumentParams -> DidChangeTextDocumentParams
$cmax :: DidChangeTextDocumentParams
-> DidChangeTextDocumentParams -> DidChangeTextDocumentParams
>= :: DidChangeTextDocumentParams -> DidChangeTextDocumentParams -> Bool
$c>= :: DidChangeTextDocumentParams -> DidChangeTextDocumentParams -> Bool
> :: DidChangeTextDocumentParams -> DidChangeTextDocumentParams -> Bool
$c> :: DidChangeTextDocumentParams -> DidChangeTextDocumentParams -> Bool
<= :: DidChangeTextDocumentParams -> DidChangeTextDocumentParams -> Bool
$c<= :: DidChangeTextDocumentParams -> DidChangeTextDocumentParams -> Bool
< :: DidChangeTextDocumentParams -> DidChangeTextDocumentParams -> Bool
$c< :: DidChangeTextDocumentParams -> DidChangeTextDocumentParams -> Bool
compare :: DidChangeTextDocumentParams
-> DidChangeTextDocumentParams -> Ordering
$ccompare :: DidChangeTextDocumentParams
-> DidChangeTextDocumentParams -> Ordering
Ord, forall x.
Rep DidChangeTextDocumentParams x -> DidChangeTextDocumentParams
forall x.
DidChangeTextDocumentParams -> Rep DidChangeTextDocumentParams x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DidChangeTextDocumentParams x -> DidChangeTextDocumentParams
$cfrom :: forall x.
DidChangeTextDocumentParams -> Rep DidChangeTextDocumentParams x
Generic)
  deriving anyclass (DidChangeTextDocumentParams -> ()
forall a. (a -> ()) -> NFData a
rnf :: DidChangeTextDocumentParams -> ()
$crnf :: DidChangeTextDocumentParams -> ()
NFData, Eq DidChangeTextDocumentParams
Int -> DidChangeTextDocumentParams -> Int
DidChangeTextDocumentParams -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: DidChangeTextDocumentParams -> Int
$chash :: DidChangeTextDocumentParams -> Int
hashWithSalt :: Int -> DidChangeTextDocumentParams -> Int
$chashWithSalt :: Int -> DidChangeTextDocumentParams -> Int
Hashable)
  deriving forall ann. [DidChangeTextDocumentParams] -> Doc ann
forall ann. DidChangeTextDocumentParams -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
prettyList :: forall ann. [DidChangeTextDocumentParams] -> Doc ann
$cprettyList :: forall ann. [DidChangeTextDocumentParams] -> Doc ann
pretty :: forall ann. DidChangeTextDocumentParams -> Doc ann
$cpretty :: forall ann. DidChangeTextDocumentParams -> Doc ann
Pretty via (ViaJSON DidChangeTextDocumentParams)

instance Aeson.ToJSON DidChangeTextDocumentParams where
  toJSON :: DidChangeTextDocumentParams -> Value
toJSON (DidChangeTextDocumentParams VersionedTextDocumentIdentifier
arg0 [TextDocumentContentChangeEvent]
arg1) = [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
"textDocument" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Aeson..= VersionedTextDocumentIdentifier
arg0]
    ,[Key
"contentChanges" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Aeson..= [TextDocumentContentChangeEvent]
arg1]]

instance Aeson.FromJSON DidChangeTextDocumentParams where
  parseJSON :: Value -> Parser DidChangeTextDocumentParams
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"DidChangeTextDocumentParams" forall a b. (a -> b) -> a -> b
$ \Object
arg -> VersionedTextDocumentIdentifier
-> [TextDocumentContentChangeEvent] -> DidChangeTextDocumentParams
DidChangeTextDocumentParams forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
arg forall a. FromJSON a => Object -> Key -> Parser a
Aeson..: Key
"textDocument" 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
"contentChanges"