{- 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.Declaration 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.Internal.Types.Location
import qualified Language.LSP.Protocol.Types.Common

{-|
The declaration of a symbol representation as one or many `Location`.
-}
newtype Declaration = Declaration (Language.LSP.Protocol.Internal.Types.Location.Location Language.LSP.Protocol.Types.Common.|? [Language.LSP.Protocol.Internal.Types.Location.Location])
  deriving newtype ([Declaration] -> Encoding
[Declaration] -> Value
Declaration -> Encoding
Declaration -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Declaration] -> Encoding
$ctoEncodingList :: [Declaration] -> Encoding
toJSONList :: [Declaration] -> Value
$ctoJSONList :: [Declaration] -> Value
toEncoding :: Declaration -> Encoding
$ctoEncoding :: Declaration -> Encoding
toJSON :: Declaration -> Value
$ctoJSON :: Declaration -> Value
Aeson.ToJSON, Value -> Parser [Declaration]
Value -> Parser Declaration
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Declaration]
$cparseJSONList :: Value -> Parser [Declaration]
parseJSON :: Value -> Parser Declaration
$cparseJSON :: Value -> Parser Declaration
Aeson.FromJSON)
  deriving stock (Int -> Declaration -> ShowS
[Declaration] -> ShowS
Declaration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Declaration] -> ShowS
$cshowList :: [Declaration] -> ShowS
show :: Declaration -> String
$cshow :: Declaration -> String
showsPrec :: Int -> Declaration -> ShowS
$cshowsPrec :: Int -> Declaration -> ShowS
Show, Declaration -> Declaration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Declaration -> Declaration -> Bool
$c/= :: Declaration -> Declaration -> Bool
== :: Declaration -> Declaration -> Bool
$c== :: Declaration -> Declaration -> Bool
Eq, Eq Declaration
Declaration -> Declaration -> Bool
Declaration -> Declaration -> Ordering
Declaration -> Declaration -> Declaration
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 :: Declaration -> Declaration -> Declaration
$cmin :: Declaration -> Declaration -> Declaration
max :: Declaration -> Declaration -> Declaration
$cmax :: Declaration -> Declaration -> Declaration
>= :: Declaration -> Declaration -> Bool
$c>= :: Declaration -> Declaration -> Bool
> :: Declaration -> Declaration -> Bool
$c> :: Declaration -> Declaration -> Bool
<= :: Declaration -> Declaration -> Bool
$c<= :: Declaration -> Declaration -> Bool
< :: Declaration -> Declaration -> Bool
$c< :: Declaration -> Declaration -> Bool
compare :: Declaration -> Declaration -> Ordering
$ccompare :: Declaration -> Declaration -> Ordering
Ord, forall x. Rep Declaration x -> Declaration
forall x. Declaration -> Rep Declaration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Declaration x -> Declaration
$cfrom :: forall x. Declaration -> Rep Declaration x
Generic)
  deriving anyclass (Declaration -> ()
forall a. (a -> ()) -> NFData a
rnf :: Declaration -> ()
$crnf :: Declaration -> ()
NFData, Eq Declaration
Int -> Declaration -> Int
Declaration -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: Declaration -> Int
$chash :: Declaration -> Int
hashWithSalt :: Int -> Declaration -> Int
$chashWithSalt :: Int -> Declaration -> Int
Hashable)
  deriving forall ann. [Declaration] -> Doc ann
forall ann. Declaration -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
prettyList :: forall ann. [Declaration] -> Doc ann
$cprettyList :: forall ann. [Declaration] -> Doc ann
pretty :: forall ann. Declaration -> Doc ann
$cpretty :: forall ann. Declaration -> Doc ann
Pretty via (ViaJSON Declaration)