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