{-# OPTIONS_GHC -Wno-unused-imports #-}
{-# OPTIONS_GHC -Wno-unused-matches #-}
{-# OPTIONS_GHC -Wno-deprecations #-}
module Language.LSP.Protocol.Internal.Types.InsertTextFormat 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.Set
import qualified Data.String
import qualified Language.LSP.Protocol.Types.Common
import qualified Language.LSP.Protocol.Types.LspEnum
data InsertTextFormat = 
    
  InsertTextFormat_PlainText
  | 
  InsertTextFormat_Snippet
  deriving stock (Int -> InsertTextFormat -> ShowS
[InsertTextFormat] -> ShowS
InsertTextFormat -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InsertTextFormat] -> ShowS
$cshowList :: [InsertTextFormat] -> ShowS
show :: InsertTextFormat -> String
$cshow :: InsertTextFormat -> String
showsPrec :: Int -> InsertTextFormat -> ShowS
$cshowsPrec :: Int -> InsertTextFormat -> ShowS
Show, InsertTextFormat -> InsertTextFormat -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InsertTextFormat -> InsertTextFormat -> Bool
$c/= :: InsertTextFormat -> InsertTextFormat -> Bool
== :: InsertTextFormat -> InsertTextFormat -> Bool
$c== :: InsertTextFormat -> InsertTextFormat -> Bool
Eq, Eq InsertTextFormat
InsertTextFormat -> InsertTextFormat -> Bool
InsertTextFormat -> InsertTextFormat -> Ordering
InsertTextFormat -> InsertTextFormat -> InsertTextFormat
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 :: InsertTextFormat -> InsertTextFormat -> InsertTextFormat
$cmin :: InsertTextFormat -> InsertTextFormat -> InsertTextFormat
max :: InsertTextFormat -> InsertTextFormat -> InsertTextFormat
$cmax :: InsertTextFormat -> InsertTextFormat -> InsertTextFormat
>= :: InsertTextFormat -> InsertTextFormat -> Bool
$c>= :: InsertTextFormat -> InsertTextFormat -> Bool
> :: InsertTextFormat -> InsertTextFormat -> Bool
$c> :: InsertTextFormat -> InsertTextFormat -> Bool
<= :: InsertTextFormat -> InsertTextFormat -> Bool
$c<= :: InsertTextFormat -> InsertTextFormat -> Bool
< :: InsertTextFormat -> InsertTextFormat -> Bool
$c< :: InsertTextFormat -> InsertTextFormat -> Bool
compare :: InsertTextFormat -> InsertTextFormat -> Ordering
$ccompare :: InsertTextFormat -> InsertTextFormat -> Ordering
Ord, forall x. Rep InsertTextFormat x -> InsertTextFormat
forall x. InsertTextFormat -> Rep InsertTextFormat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InsertTextFormat x -> InsertTextFormat
$cfrom :: forall x. InsertTextFormat -> Rep InsertTextFormat x
Generic)
  deriving anyclass (InsertTextFormat -> ()
forall a. (a -> ()) -> NFData a
rnf :: InsertTextFormat -> ()
$crnf :: InsertTextFormat -> ()
NFData, Eq InsertTextFormat
Int -> InsertTextFormat -> Int
InsertTextFormat -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: InsertTextFormat -> Int
$chash :: InsertTextFormat -> Int
hashWithSalt :: Int -> InsertTextFormat -> Int
$chashWithSalt :: Int -> InsertTextFormat -> Int
Hashable)
  deriving ( [InsertTextFormat] -> Encoding
[InsertTextFormat] -> Value
InsertTextFormat -> Encoding
InsertTextFormat -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [InsertTextFormat] -> Encoding
$ctoEncodingList :: [InsertTextFormat] -> Encoding
toJSONList :: [InsertTextFormat] -> Value
$ctoJSONList :: [InsertTextFormat] -> Value
toEncoding :: InsertTextFormat -> Encoding
$ctoEncoding :: InsertTextFormat -> Encoding
toJSON :: InsertTextFormat -> Value
$ctoJSON :: InsertTextFormat -> Value
Aeson.ToJSON
  , Value -> Parser [InsertTextFormat]
Value -> Parser InsertTextFormat
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [InsertTextFormat]
$cparseJSONList :: Value -> Parser [InsertTextFormat]
parseJSON :: Value -> Parser InsertTextFormat
$cparseJSON :: Value -> Parser InsertTextFormat
Aeson.FromJSON ) via (Language.LSP.Protocol.Types.LspEnum.AsLspEnum InsertTextFormat Language.LSP.Protocol.Types.Common.UInt)
  deriving forall ann. [InsertTextFormat] -> Doc ann
forall ann. InsertTextFormat -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
prettyList :: forall ann. [InsertTextFormat] -> Doc ann
$cprettyList :: forall ann. [InsertTextFormat] -> Doc ann
pretty :: forall ann. InsertTextFormat -> Doc ann
$cpretty :: forall ann. InsertTextFormat -> Doc ann
Pretty via (ViaJSON InsertTextFormat)
instance Language.LSP.Protocol.Types.LspEnum.LspEnum InsertTextFormat where
  knownValues :: Set InsertTextFormat
knownValues = forall a. Ord a => [a] -> Set a
Data.Set.fromList [InsertTextFormat
InsertTextFormat_PlainText
    ,InsertTextFormat
InsertTextFormat_Snippet]
  type EnumBaseType InsertTextFormat = Language.LSP.Protocol.Types.Common.UInt
  toEnumBaseType :: InsertTextFormat -> EnumBaseType InsertTextFormat
toEnumBaseType InsertTextFormat
InsertTextFormat_PlainText = UInt
1
  toEnumBaseType InsertTextFormat
InsertTextFormat_Snippet = UInt
2
  fromEnumBaseType :: EnumBaseType InsertTextFormat -> Maybe InsertTextFormat
fromEnumBaseType EnumBaseType InsertTextFormat
1 = forall (f :: * -> *) a. Applicative f => a -> f a
pure InsertTextFormat
InsertTextFormat_PlainText
  fromEnumBaseType EnumBaseType InsertTextFormat
2 = forall (f :: * -> *) a. Applicative f => a -> f a
pure InsertTextFormat
InsertTextFormat_Snippet
  fromEnumBaseType EnumBaseType InsertTextFormat
_ = forall a. Maybe a
Nothing