{- 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.HoverOptions 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 Language.LSP.Protocol.Types.Common

{-|
Hover options.
-}
data HoverOptions = HoverOptions 
  { {-|

  -}
  HoverOptions -> Maybe Bool
_workDoneProgress :: (Maybe Bool)
  }
  deriving stock (Int -> HoverOptions -> ShowS
[HoverOptions] -> ShowS
HoverOptions -> String
(Int -> HoverOptions -> ShowS)
-> (HoverOptions -> String)
-> ([HoverOptions] -> ShowS)
-> Show HoverOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HoverOptions -> ShowS
showsPrec :: Int -> HoverOptions -> ShowS
$cshow :: HoverOptions -> String
show :: HoverOptions -> String
$cshowList :: [HoverOptions] -> ShowS
showList :: [HoverOptions] -> ShowS
Show, HoverOptions -> HoverOptions -> Bool
(HoverOptions -> HoverOptions -> Bool)
-> (HoverOptions -> HoverOptions -> Bool) -> Eq HoverOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HoverOptions -> HoverOptions -> Bool
== :: HoverOptions -> HoverOptions -> Bool
$c/= :: HoverOptions -> HoverOptions -> Bool
/= :: HoverOptions -> HoverOptions -> Bool
Eq, Eq HoverOptions
Eq HoverOptions =>
(HoverOptions -> HoverOptions -> Ordering)
-> (HoverOptions -> HoverOptions -> Bool)
-> (HoverOptions -> HoverOptions -> Bool)
-> (HoverOptions -> HoverOptions -> Bool)
-> (HoverOptions -> HoverOptions -> Bool)
-> (HoverOptions -> HoverOptions -> HoverOptions)
-> (HoverOptions -> HoverOptions -> HoverOptions)
-> Ord HoverOptions
HoverOptions -> HoverOptions -> Bool
HoverOptions -> HoverOptions -> Ordering
HoverOptions -> HoverOptions -> HoverOptions
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 :: HoverOptions -> HoverOptions -> Ordering
compare :: HoverOptions -> HoverOptions -> Ordering
$c< :: HoverOptions -> HoverOptions -> Bool
< :: HoverOptions -> HoverOptions -> Bool
$c<= :: HoverOptions -> HoverOptions -> Bool
<= :: HoverOptions -> HoverOptions -> Bool
$c> :: HoverOptions -> HoverOptions -> Bool
> :: HoverOptions -> HoverOptions -> Bool
$c>= :: HoverOptions -> HoverOptions -> Bool
>= :: HoverOptions -> HoverOptions -> Bool
$cmax :: HoverOptions -> HoverOptions -> HoverOptions
max :: HoverOptions -> HoverOptions -> HoverOptions
$cmin :: HoverOptions -> HoverOptions -> HoverOptions
min :: HoverOptions -> HoverOptions -> HoverOptions
Ord, (forall x. HoverOptions -> Rep HoverOptions x)
-> (forall x. Rep HoverOptions x -> HoverOptions)
-> Generic HoverOptions
forall x. Rep HoverOptions x -> HoverOptions
forall x. HoverOptions -> Rep HoverOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. HoverOptions -> Rep HoverOptions x
from :: forall x. HoverOptions -> Rep HoverOptions x
$cto :: forall x. Rep HoverOptions x -> HoverOptions
to :: forall x. Rep HoverOptions x -> HoverOptions
Generic)
  deriving anyclass (HoverOptions -> ()
(HoverOptions -> ()) -> NFData HoverOptions
forall a. (a -> ()) -> NFData a
$crnf :: HoverOptions -> ()
rnf :: HoverOptions -> ()
NFData, Eq HoverOptions
Eq HoverOptions =>
(Int -> HoverOptions -> Int)
-> (HoverOptions -> Int) -> Hashable HoverOptions
Int -> HoverOptions -> Int
HoverOptions -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> HoverOptions -> Int
hashWithSalt :: Int -> HoverOptions -> Int
$chash :: HoverOptions -> Int
hash :: HoverOptions -> Int
Hashable)
  deriving (forall ann. HoverOptions -> Doc ann)
-> (forall ann. [HoverOptions] -> Doc ann) -> Pretty HoverOptions
forall ann. [HoverOptions] -> Doc ann
forall ann. HoverOptions -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
$cpretty :: forall ann. HoverOptions -> Doc ann
pretty :: forall ann. HoverOptions -> Doc ann
$cprettyList :: forall ann. [HoverOptions] -> Doc ann
prettyList :: forall ann. [HoverOptions] -> Doc ann
Pretty via (ViaJSON HoverOptions)

instance Aeson.ToJSON HoverOptions where
  toJSON :: HoverOptions -> Value
toJSON (HoverOptions Maybe Bool
arg0) = [Pair] -> Value
Aeson.object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ [[Pair]] -> [Pair]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Pair]] -> [Pair]) -> [[Pair]] -> [Pair]
forall a b. (a -> b) -> a -> b
$  [String
"workDoneProgress" String -> Maybe Bool -> [Pair]
forall e kv v.
(KeyValue e kv, ToJSON v) =>
String -> Maybe v -> [kv]
Language.LSP.Protocol.Types.Common..=? Maybe Bool
arg0]

instance Aeson.FromJSON HoverOptions where
  parseJSON :: Value -> Parser HoverOptions
parseJSON = String
-> (Object -> Parser HoverOptions) -> Value -> Parser HoverOptions
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"HoverOptions" ((Object -> Parser HoverOptions) -> Value -> Parser HoverOptions)
-> (Object -> Parser HoverOptions) -> Value -> Parser HoverOptions
forall a b. (a -> b) -> a -> b
$ \Object
arg -> Maybe Bool -> HoverOptions
HoverOptions (Maybe Bool -> HoverOptions)
-> Parser (Maybe Bool) -> Parser HoverOptions
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
arg Object -> Key -> Parser (Maybe Bool)
forall v. FromJSON v => Object -> Key -> Parser (Maybe v)
Language.LSP.Protocol.Types.Common..:!? Key
"workDoneProgress"