{-# OPTIONS_GHC -Wno-unused-imports #-}
{-# OPTIONS_GHC -Wno-unused-matches #-}
{-# OPTIONS_GHC -Wno-deprecations #-}
module Language.LSP.Protocol.Internal.Types.CompletionList 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.CompletionItem
import qualified Language.LSP.Protocol.Internal.Types.InsertTextFormat
import qualified Language.LSP.Protocol.Internal.Types.InsertTextMode
import qualified Language.LSP.Protocol.Internal.Types.Range
import qualified Language.LSP.Protocol.Types.Common
data CompletionList = CompletionList
{
CompletionList -> Bool
_isIncomplete :: Bool
,
CompletionList
-> Maybe
(Rec
(("commitCharacters" .== Maybe [Text])
.+ (("editRange"
.== Maybe
(Range
|? Rec
(("insert" .== Range)
.+ (Extend "replace" Range ('R '[]) .+ 'R '[]))))
.+ (("insertTextFormat" .== Maybe InsertTextFormat)
.+ (Extend "insertTextMode" (Maybe InsertTextMode) ('R '[])
.+ (("data" .== Maybe Value) .+ 'R '[]))))))
_itemDefaults :: (Maybe (Row.Rec ("commitCharacters" Row..== (Maybe [Data.Text.Text]) Row..+ ("editRange" Row..== (Maybe (Language.LSP.Protocol.Internal.Types.Range.Range Language.LSP.Protocol.Types.Common.|? (Row.Rec ("insert" Row..== Language.LSP.Protocol.Internal.Types.Range.Range Row..+ ("replace" Row..== Language.LSP.Protocol.Internal.Types.Range.Range Row..+ Row.Empty))))) Row..+ ("insertTextFormat" Row..== (Maybe Language.LSP.Protocol.Internal.Types.InsertTextFormat.InsertTextFormat) Row..+ ("insertTextMode" Row..== (Maybe Language.LSP.Protocol.Internal.Types.InsertTextMode.InsertTextMode) Row..+ ("data" Row..== (Maybe Data.Aeson.Value) Row..+ Row.Empty)))))))
,
CompletionList -> [CompletionItem]
_items :: [Language.LSP.Protocol.Internal.Types.CompletionItem.CompletionItem]
}
deriving stock (Int -> CompletionList -> ShowS
[CompletionList] -> ShowS
CompletionList -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CompletionList] -> ShowS
$cshowList :: [CompletionList] -> ShowS
show :: CompletionList -> String
$cshow :: CompletionList -> String
showsPrec :: Int -> CompletionList -> ShowS
$cshowsPrec :: Int -> CompletionList -> ShowS
Show, CompletionList -> CompletionList -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CompletionList -> CompletionList -> Bool
$c/= :: CompletionList -> CompletionList -> Bool
== :: CompletionList -> CompletionList -> Bool
$c== :: CompletionList -> CompletionList -> Bool
Eq, Eq CompletionList
CompletionList -> CompletionList -> Bool
CompletionList -> CompletionList -> Ordering
CompletionList -> CompletionList -> CompletionList
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 :: CompletionList -> CompletionList -> CompletionList
$cmin :: CompletionList -> CompletionList -> CompletionList
max :: CompletionList -> CompletionList -> CompletionList
$cmax :: CompletionList -> CompletionList -> CompletionList
>= :: CompletionList -> CompletionList -> Bool
$c>= :: CompletionList -> CompletionList -> Bool
> :: CompletionList -> CompletionList -> Bool
$c> :: CompletionList -> CompletionList -> Bool
<= :: CompletionList -> CompletionList -> Bool
$c<= :: CompletionList -> CompletionList -> Bool
< :: CompletionList -> CompletionList -> Bool
$c< :: CompletionList -> CompletionList -> Bool
compare :: CompletionList -> CompletionList -> Ordering
$ccompare :: CompletionList -> CompletionList -> Ordering
Ord, forall x. Rep CompletionList x -> CompletionList
forall x. CompletionList -> Rep CompletionList x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CompletionList x -> CompletionList
$cfrom :: forall x. CompletionList -> Rep CompletionList x
Generic)
deriving anyclass (CompletionList -> ()
forall a. (a -> ()) -> NFData a
rnf :: CompletionList -> ()
$crnf :: CompletionList -> ()
NFData, Eq CompletionList
Int -> CompletionList -> Int
CompletionList -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: CompletionList -> Int
$chash :: CompletionList -> Int
hashWithSalt :: Int -> CompletionList -> Int
$chashWithSalt :: Int -> CompletionList -> Int
Hashable)
deriving forall ann. [CompletionList] -> Doc ann
forall ann. CompletionList -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
prettyList :: forall ann. [CompletionList] -> Doc ann
$cprettyList :: forall ann. [CompletionList] -> Doc ann
pretty :: forall ann. CompletionList -> Doc ann
$cpretty :: forall ann. CompletionList -> Doc ann
Pretty via (ViaJSON CompletionList)
instance Aeson.ToJSON CompletionList where
toJSON :: CompletionList -> Value
toJSON (CompletionList Bool
arg0 Maybe
(Rec
(("commitCharacters" .== Maybe [Text])
.+ (("editRange"
.== Maybe
(Range
|? Rec
(("insert" .== Range)
.+ (Extend "replace" Range ('R '[]) .+ 'R '[]))))
.+ (("insertTextFormat" .== Maybe InsertTextFormat)
.+ (Extend "insertTextMode" (Maybe InsertTextMode) ('R '[])
.+ (("data" .== Maybe Value) .+ 'R '[]))))))
arg1 [CompletionItem]
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
$ [[Key
"isIncomplete" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Aeson..= Bool
arg0]
,String
"itemDefaults" forall kv v. (KeyValue kv, ToJSON v) => String -> Maybe v -> [kv]
Language.LSP.Protocol.Types.Common..=? Maybe
(Rec
(("commitCharacters" .== Maybe [Text])
.+ (("editRange"
.== Maybe
(Range
|? Rec
(("insert" .== Range)
.+ (Extend "replace" Range ('R '[]) .+ 'R '[]))))
.+ (("insertTextFormat" .== Maybe InsertTextFormat)
.+ (Extend "insertTextMode" (Maybe InsertTextMode) ('R '[])
.+ (("data" .== Maybe Value) .+ 'R '[]))))))
arg1
,[Key
"items" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Aeson..= [CompletionItem]
arg2]]
instance Aeson.FromJSON CompletionList where
parseJSON :: Value -> Parser CompletionList
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"CompletionList" forall a b. (a -> b) -> a -> b
$ \Object
arg -> Bool
-> Maybe
(Rec
(("commitCharacters" .== Maybe [Text])
.+ (("editRange"
.== Maybe
(Range
|? Rec
(("insert" .== Range)
.+ (Extend "replace" Range ('R '[]) .+ 'R '[]))))
.+ (("insertTextFormat" .== Maybe InsertTextFormat)
.+ (Extend "insertTextMode" (Maybe InsertTextMode) ('R '[])
.+ (("data" .== Maybe Value) .+ 'R '[]))))))
-> [CompletionItem]
-> CompletionList
CompletionList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
arg forall a. FromJSON a => Object -> Key -> Parser a
Aeson..: Key
"isIncomplete" 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
"itemDefaults" 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
"items"