{-# OPTIONS_GHC -Wno-unused-imports #-}
{-# OPTIONS_GHC -Wno-unused-matches #-}
{-# OPTIONS_GHC -Wno-deprecations #-}
module Language.LSP.Protocol.Internal.Types.WorkspaceEdit 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.Map
import qualified Data.Row.Aeson as Aeson
import qualified Data.Row.Hashable as Hashable
import qualified Language.LSP.Protocol.Internal.Types.ChangeAnnotation
import qualified Language.LSP.Protocol.Internal.Types.ChangeAnnotationIdentifier
import qualified Language.LSP.Protocol.Internal.Types.CreateFile
import qualified Language.LSP.Protocol.Internal.Types.DeleteFile
import qualified Language.LSP.Protocol.Internal.Types.RenameFile
import qualified Language.LSP.Protocol.Internal.Types.TextDocumentEdit
import qualified Language.LSP.Protocol.Internal.Types.TextEdit
import qualified Language.LSP.Protocol.Types.Common
import qualified Language.LSP.Protocol.Types.Uri
data WorkspaceEdit = WorkspaceEdit
{
WorkspaceEdit -> Maybe (Map Uri [TextEdit])
_changes :: (Maybe (Data.Map.Map Language.LSP.Protocol.Types.Uri.Uri [Language.LSP.Protocol.Internal.Types.TextEdit.TextEdit]))
,
WorkspaceEdit
-> Maybe
[TextDocumentEdit |? (CreateFile |? (RenameFile |? DeleteFile))]
_documentChanges :: (Maybe [(Language.LSP.Protocol.Internal.Types.TextDocumentEdit.TextDocumentEdit Language.LSP.Protocol.Types.Common.|? (Language.LSP.Protocol.Internal.Types.CreateFile.CreateFile Language.LSP.Protocol.Types.Common.|? (Language.LSP.Protocol.Internal.Types.RenameFile.RenameFile Language.LSP.Protocol.Types.Common.|? Language.LSP.Protocol.Internal.Types.DeleteFile.DeleteFile)))])
,
WorkspaceEdit
-> Maybe (Map ChangeAnnotationIdentifier ChangeAnnotation)
_changeAnnotations :: (Maybe (Data.Map.Map Language.LSP.Protocol.Internal.Types.ChangeAnnotationIdentifier.ChangeAnnotationIdentifier Language.LSP.Protocol.Internal.Types.ChangeAnnotation.ChangeAnnotation))
}
deriving stock (Int -> WorkspaceEdit -> ShowS
[WorkspaceEdit] -> ShowS
WorkspaceEdit -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WorkspaceEdit] -> ShowS
$cshowList :: [WorkspaceEdit] -> ShowS
show :: WorkspaceEdit -> String
$cshow :: WorkspaceEdit -> String
showsPrec :: Int -> WorkspaceEdit -> ShowS
$cshowsPrec :: Int -> WorkspaceEdit -> ShowS
Show, WorkspaceEdit -> WorkspaceEdit -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WorkspaceEdit -> WorkspaceEdit -> Bool
$c/= :: WorkspaceEdit -> WorkspaceEdit -> Bool
== :: WorkspaceEdit -> WorkspaceEdit -> Bool
$c== :: WorkspaceEdit -> WorkspaceEdit -> Bool
Eq, Eq WorkspaceEdit
WorkspaceEdit -> WorkspaceEdit -> Bool
WorkspaceEdit -> WorkspaceEdit -> Ordering
WorkspaceEdit -> WorkspaceEdit -> WorkspaceEdit
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 :: WorkspaceEdit -> WorkspaceEdit -> WorkspaceEdit
$cmin :: WorkspaceEdit -> WorkspaceEdit -> WorkspaceEdit
max :: WorkspaceEdit -> WorkspaceEdit -> WorkspaceEdit
$cmax :: WorkspaceEdit -> WorkspaceEdit -> WorkspaceEdit
>= :: WorkspaceEdit -> WorkspaceEdit -> Bool
$c>= :: WorkspaceEdit -> WorkspaceEdit -> Bool
> :: WorkspaceEdit -> WorkspaceEdit -> Bool
$c> :: WorkspaceEdit -> WorkspaceEdit -> Bool
<= :: WorkspaceEdit -> WorkspaceEdit -> Bool
$c<= :: WorkspaceEdit -> WorkspaceEdit -> Bool
< :: WorkspaceEdit -> WorkspaceEdit -> Bool
$c< :: WorkspaceEdit -> WorkspaceEdit -> Bool
compare :: WorkspaceEdit -> WorkspaceEdit -> Ordering
$ccompare :: WorkspaceEdit -> WorkspaceEdit -> Ordering
Ord, forall x. Rep WorkspaceEdit x -> WorkspaceEdit
forall x. WorkspaceEdit -> Rep WorkspaceEdit x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WorkspaceEdit x -> WorkspaceEdit
$cfrom :: forall x. WorkspaceEdit -> Rep WorkspaceEdit x
Generic)
deriving anyclass (WorkspaceEdit -> ()
forall a. (a -> ()) -> NFData a
rnf :: WorkspaceEdit -> ()
$crnf :: WorkspaceEdit -> ()
NFData, Eq WorkspaceEdit
Int -> WorkspaceEdit -> Int
WorkspaceEdit -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: WorkspaceEdit -> Int
$chash :: WorkspaceEdit -> Int
hashWithSalt :: Int -> WorkspaceEdit -> Int
$chashWithSalt :: Int -> WorkspaceEdit -> Int
Hashable)
deriving forall ann. [WorkspaceEdit] -> Doc ann
forall ann. WorkspaceEdit -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
prettyList :: forall ann. [WorkspaceEdit] -> Doc ann
$cprettyList :: forall ann. [WorkspaceEdit] -> Doc ann
pretty :: forall ann. WorkspaceEdit -> Doc ann
$cpretty :: forall ann. WorkspaceEdit -> Doc ann
Pretty via (ViaJSON WorkspaceEdit)
instance Aeson.ToJSON WorkspaceEdit where
toJSON :: WorkspaceEdit -> Value
toJSON (WorkspaceEdit Maybe (Map Uri [TextEdit])
arg0 Maybe
[TextDocumentEdit |? (CreateFile |? (RenameFile |? DeleteFile))]
arg1 Maybe (Map ChangeAnnotationIdentifier ChangeAnnotation)
arg2) = [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
"changes" forall kv v. (KeyValue kv, ToJSON v) => String -> Maybe v -> [kv]
Language.LSP.Protocol.Types.Common..=? Maybe (Map Uri [TextEdit])
arg0
,String
"documentChanges" forall kv v. (KeyValue kv, ToJSON v) => String -> Maybe v -> [kv]
Language.LSP.Protocol.Types.Common..=? Maybe
[TextDocumentEdit |? (CreateFile |? (RenameFile |? DeleteFile))]
arg1
,String
"changeAnnotations" forall kv v. (KeyValue kv, ToJSON v) => String -> Maybe v -> [kv]
Language.LSP.Protocol.Types.Common..=? Maybe (Map ChangeAnnotationIdentifier ChangeAnnotation)
arg2]
instance Aeson.FromJSON WorkspaceEdit where
parseJSON :: Value -> Parser WorkspaceEdit
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"WorkspaceEdit" forall a b. (a -> b) -> a -> b
$ \Object
arg -> Maybe (Map Uri [TextEdit])
-> Maybe
[TextDocumentEdit |? (CreateFile |? (RenameFile |? DeleteFile))]
-> Maybe (Map ChangeAnnotationIdentifier ChangeAnnotation)
-> WorkspaceEdit
WorkspaceEdit 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
"changes" 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
"documentChanges" 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
"changeAnnotations"