{- 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.LSPErrorCodes 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 LSPErrorCodes = 
    {-|
  A request failed but it was syntactically correct, e.g the
  method name was known and the parameters were valid. The error
  message should contain human readable information about why
  the request failed.

  @since 3.17.0
  -}
  LSPErrorCodes_RequestFailed
  | {-|
  The server cancelled the request. This error code should
  only be used for requests that explicitly support being
  server cancellable.

  @since 3.17.0
  -}
  LSPErrorCodes_ServerCancelled
  | {-|
  The server detected that the content of a document got
  modified outside normal conditions. A server should
  NOT send this error code if it detects a content change
  in it unprocessed messages. The result even computed
  on an older state might still be useful for the client.

  If a client decides that a result is not of any use anymore
  the client should cancel the request.
  -}
  LSPErrorCodes_ContentModified
  | {-|
  The client has canceled a request and a server as detected
  the cancel.
  -}
  LSPErrorCodes_RequestCancelled
  | LSPErrorCodes_Custom Language.LSP.Protocol.Types.Common.Int32
  deriving stock (Int -> LSPErrorCodes -> ShowS
[LSPErrorCodes] -> ShowS
LSPErrorCodes -> String
(Int -> LSPErrorCodes -> ShowS)
-> (LSPErrorCodes -> String)
-> ([LSPErrorCodes] -> ShowS)
-> Show LSPErrorCodes
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LSPErrorCodes -> ShowS
showsPrec :: Int -> LSPErrorCodes -> ShowS
$cshow :: LSPErrorCodes -> String
show :: LSPErrorCodes -> String
$cshowList :: [LSPErrorCodes] -> ShowS
showList :: [LSPErrorCodes] -> ShowS
Show, LSPErrorCodes -> LSPErrorCodes -> Bool
(LSPErrorCodes -> LSPErrorCodes -> Bool)
-> (LSPErrorCodes -> LSPErrorCodes -> Bool) -> Eq LSPErrorCodes
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LSPErrorCodes -> LSPErrorCodes -> Bool
== :: LSPErrorCodes -> LSPErrorCodes -> Bool
$c/= :: LSPErrorCodes -> LSPErrorCodes -> Bool
/= :: LSPErrorCodes -> LSPErrorCodes -> Bool
Eq, Eq LSPErrorCodes
Eq LSPErrorCodes =>
(LSPErrorCodes -> LSPErrorCodes -> Ordering)
-> (LSPErrorCodes -> LSPErrorCodes -> Bool)
-> (LSPErrorCodes -> LSPErrorCodes -> Bool)
-> (LSPErrorCodes -> LSPErrorCodes -> Bool)
-> (LSPErrorCodes -> LSPErrorCodes -> Bool)
-> (LSPErrorCodes -> LSPErrorCodes -> LSPErrorCodes)
-> (LSPErrorCodes -> LSPErrorCodes -> LSPErrorCodes)
-> Ord LSPErrorCodes
LSPErrorCodes -> LSPErrorCodes -> Bool
LSPErrorCodes -> LSPErrorCodes -> Ordering
LSPErrorCodes -> LSPErrorCodes -> LSPErrorCodes
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 :: LSPErrorCodes -> LSPErrorCodes -> Ordering
compare :: LSPErrorCodes -> LSPErrorCodes -> Ordering
$c< :: LSPErrorCodes -> LSPErrorCodes -> Bool
< :: LSPErrorCodes -> LSPErrorCodes -> Bool
$c<= :: LSPErrorCodes -> LSPErrorCodes -> Bool
<= :: LSPErrorCodes -> LSPErrorCodes -> Bool
$c> :: LSPErrorCodes -> LSPErrorCodes -> Bool
> :: LSPErrorCodes -> LSPErrorCodes -> Bool
$c>= :: LSPErrorCodes -> LSPErrorCodes -> Bool
>= :: LSPErrorCodes -> LSPErrorCodes -> Bool
$cmax :: LSPErrorCodes -> LSPErrorCodes -> LSPErrorCodes
max :: LSPErrorCodes -> LSPErrorCodes -> LSPErrorCodes
$cmin :: LSPErrorCodes -> LSPErrorCodes -> LSPErrorCodes
min :: LSPErrorCodes -> LSPErrorCodes -> LSPErrorCodes
Ord, (forall x. LSPErrorCodes -> Rep LSPErrorCodes x)
-> (forall x. Rep LSPErrorCodes x -> LSPErrorCodes)
-> Generic LSPErrorCodes
forall x. Rep LSPErrorCodes x -> LSPErrorCodes
forall x. LSPErrorCodes -> Rep LSPErrorCodes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LSPErrorCodes -> Rep LSPErrorCodes x
from :: forall x. LSPErrorCodes -> Rep LSPErrorCodes x
$cto :: forall x. Rep LSPErrorCodes x -> LSPErrorCodes
to :: forall x. Rep LSPErrorCodes x -> LSPErrorCodes
Generic)
  deriving anyclass (LSPErrorCodes -> ()
(LSPErrorCodes -> ()) -> NFData LSPErrorCodes
forall a. (a -> ()) -> NFData a
$crnf :: LSPErrorCodes -> ()
rnf :: LSPErrorCodes -> ()
NFData, Eq LSPErrorCodes
Eq LSPErrorCodes =>
(Int -> LSPErrorCodes -> Int)
-> (LSPErrorCodes -> Int) -> Hashable LSPErrorCodes
Int -> LSPErrorCodes -> Int
LSPErrorCodes -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> LSPErrorCodes -> Int
hashWithSalt :: Int -> LSPErrorCodes -> Int
$chash :: LSPErrorCodes -> Int
hash :: LSPErrorCodes -> Int
Hashable)
  deriving ( [LSPErrorCodes] -> Value
[LSPErrorCodes] -> Encoding
LSPErrorCodes -> Bool
LSPErrorCodes -> Value
LSPErrorCodes -> Encoding
(LSPErrorCodes -> Value)
-> (LSPErrorCodes -> Encoding)
-> ([LSPErrorCodes] -> Value)
-> ([LSPErrorCodes] -> Encoding)
-> (LSPErrorCodes -> Bool)
-> ToJSON LSPErrorCodes
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: LSPErrorCodes -> Value
toJSON :: LSPErrorCodes -> Value
$ctoEncoding :: LSPErrorCodes -> Encoding
toEncoding :: LSPErrorCodes -> Encoding
$ctoJSONList :: [LSPErrorCodes] -> Value
toJSONList :: [LSPErrorCodes] -> Value
$ctoEncodingList :: [LSPErrorCodes] -> Encoding
toEncodingList :: [LSPErrorCodes] -> Encoding
$comitField :: LSPErrorCodes -> Bool
omitField :: LSPErrorCodes -> Bool
Aeson.ToJSON
  , Maybe LSPErrorCodes
Value -> Parser [LSPErrorCodes]
Value -> Parser LSPErrorCodes
(Value -> Parser LSPErrorCodes)
-> (Value -> Parser [LSPErrorCodes])
-> Maybe LSPErrorCodes
-> FromJSON LSPErrorCodes
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser LSPErrorCodes
parseJSON :: Value -> Parser LSPErrorCodes
$cparseJSONList :: Value -> Parser [LSPErrorCodes]
parseJSONList :: Value -> Parser [LSPErrorCodes]
$comittedField :: Maybe LSPErrorCodes
omittedField :: Maybe LSPErrorCodes
Aeson.FromJSON ) via (Language.LSP.Protocol.Types.LspEnum.AsLspEnum LSPErrorCodes)
  deriving (forall ann. LSPErrorCodes -> Doc ann)
-> (forall ann. [LSPErrorCodes] -> Doc ann) -> Pretty LSPErrorCodes
forall ann. [LSPErrorCodes] -> Doc ann
forall ann. LSPErrorCodes -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
$cpretty :: forall ann. LSPErrorCodes -> Doc ann
pretty :: forall ann. LSPErrorCodes -> Doc ann
$cprettyList :: forall ann. [LSPErrorCodes] -> Doc ann
prettyList :: forall ann. [LSPErrorCodes] -> Doc ann
Pretty via (ViaJSON LSPErrorCodes)

instance Language.LSP.Protocol.Types.LspEnum.LspEnum LSPErrorCodes where
  knownValues :: Set LSPErrorCodes
knownValues = [LSPErrorCodes] -> Set LSPErrorCodes
forall a. Ord a => [a] -> Set a
Data.Set.fromList [LSPErrorCodes
LSPErrorCodes_RequestFailed
    ,LSPErrorCodes
LSPErrorCodes_ServerCancelled
    ,LSPErrorCodes
LSPErrorCodes_ContentModified
    ,LSPErrorCodes
LSPErrorCodes_RequestCancelled]
  type EnumBaseType LSPErrorCodes = Language.LSP.Protocol.Types.Common.Int32
  toEnumBaseType :: LSPErrorCodes -> EnumBaseType LSPErrorCodes
toEnumBaseType LSPErrorCodes
LSPErrorCodes_RequestFailed = Int32
EnumBaseType LSPErrorCodes
-32803
  toEnumBaseType LSPErrorCodes
LSPErrorCodes_ServerCancelled = Int32
EnumBaseType LSPErrorCodes
-32802
  toEnumBaseType LSPErrorCodes
LSPErrorCodes_ContentModified = Int32
EnumBaseType LSPErrorCodes
-32801
  toEnumBaseType LSPErrorCodes
LSPErrorCodes_RequestCancelled = Int32
EnumBaseType LSPErrorCodes
-32800
  toEnumBaseType (LSPErrorCodes_Custom Int32
arg) = Int32
EnumBaseType LSPErrorCodes
arg

instance Language.LSP.Protocol.Types.LspEnum.LspOpenEnum LSPErrorCodes where
  fromOpenEnumBaseType :: EnumBaseType LSPErrorCodes -> LSPErrorCodes
fromOpenEnumBaseType EnumBaseType LSPErrorCodes
-32803 = LSPErrorCodes
LSPErrorCodes_RequestFailed
  fromOpenEnumBaseType EnumBaseType LSPErrorCodes
-32802 = LSPErrorCodes
LSPErrorCodes_ServerCancelled
  fromOpenEnumBaseType EnumBaseType LSPErrorCodes
-32801 = LSPErrorCodes
LSPErrorCodes_ContentModified
  fromOpenEnumBaseType EnumBaseType LSPErrorCodes
-32800 = LSPErrorCodes
LSPErrorCodes_RequestCancelled
  fromOpenEnumBaseType EnumBaseType LSPErrorCodes
arg = Int32 -> LSPErrorCodes
LSPErrorCodes_Custom Int32
EnumBaseType LSPErrorCodes
arg