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