{-# OPTIONS_GHC -Wno-unused-imports #-}
{-# OPTIONS_GHC -Wno-unused-matches #-}
{-# OPTIONS_GHC -Wno-deprecations #-}
module Language.LSP.Protocol.Internal.Types.Pattern 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.Text
newtype Pattern = Pattern Data.Text.Text
  deriving newtype ( [Pattern] -> Value
[Pattern] -> Encoding
Pattern -> Bool
Pattern -> Value
Pattern -> Encoding
(Pattern -> Value)
-> (Pattern -> Encoding)
-> ([Pattern] -> Value)
-> ([Pattern] -> Encoding)
-> (Pattern -> Bool)
-> ToJSON Pattern
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Pattern -> Value
toJSON :: Pattern -> Value
$ctoEncoding :: Pattern -> Encoding
toEncoding :: Pattern -> Encoding
$ctoJSONList :: [Pattern] -> Value
toJSONList :: [Pattern] -> Value
$ctoEncodingList :: [Pattern] -> Encoding
toEncodingList :: [Pattern] -> Encoding
$comitField :: Pattern -> Bool
omitField :: Pattern -> Bool
Aeson.ToJSON
  , Maybe Pattern
Value -> Parser [Pattern]
Value -> Parser Pattern
(Value -> Parser Pattern)
-> (Value -> Parser [Pattern]) -> Maybe Pattern -> FromJSON Pattern
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Pattern
parseJSON :: Value -> Parser Pattern
$cparseJSONList :: Value -> Parser [Pattern]
parseJSONList :: Value -> Parser [Pattern]
$comittedField :: Maybe Pattern
omittedField :: Maybe Pattern
Aeson.FromJSON
  , ToJSONKeyFunction [Pattern]
ToJSONKeyFunction Pattern
ToJSONKeyFunction Pattern
-> ToJSONKeyFunction [Pattern] -> ToJSONKey Pattern
forall a.
ToJSONKeyFunction a -> ToJSONKeyFunction [a] -> ToJSONKey a
$ctoJSONKey :: ToJSONKeyFunction Pattern
toJSONKey :: ToJSONKeyFunction Pattern
$ctoJSONKeyList :: ToJSONKeyFunction [Pattern]
toJSONKeyList :: ToJSONKeyFunction [Pattern]
Aeson.ToJSONKey
  , FromJSONKeyFunction [Pattern]
FromJSONKeyFunction Pattern
FromJSONKeyFunction Pattern
-> FromJSONKeyFunction [Pattern] -> FromJSONKey Pattern
forall a.
FromJSONKeyFunction a -> FromJSONKeyFunction [a] -> FromJSONKey a
$cfromJSONKey :: FromJSONKeyFunction Pattern
fromJSONKey :: FromJSONKeyFunction Pattern
$cfromJSONKeyList :: FromJSONKeyFunction [Pattern]
fromJSONKeyList :: FromJSONKeyFunction [Pattern]
Aeson.FromJSONKey )
  deriving stock (Int -> Pattern -> ShowS
[Pattern] -> ShowS
Pattern -> String
(Int -> Pattern -> ShowS)
-> (Pattern -> String) -> ([Pattern] -> ShowS) -> Show Pattern
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Pattern -> ShowS
showsPrec :: Int -> Pattern -> ShowS
$cshow :: Pattern -> String
show :: Pattern -> String
$cshowList :: [Pattern] -> ShowS
showList :: [Pattern] -> ShowS
Show, Pattern -> Pattern -> Bool
(Pattern -> Pattern -> Bool)
-> (Pattern -> Pattern -> Bool) -> Eq Pattern
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Pattern -> Pattern -> Bool
== :: Pattern -> Pattern -> Bool
$c/= :: Pattern -> Pattern -> Bool
/= :: Pattern -> Pattern -> Bool
Eq, Eq Pattern
Eq Pattern =>
(Pattern -> Pattern -> Ordering)
-> (Pattern -> Pattern -> Bool)
-> (Pattern -> Pattern -> Bool)
-> (Pattern -> Pattern -> Bool)
-> (Pattern -> Pattern -> Bool)
-> (Pattern -> Pattern -> Pattern)
-> (Pattern -> Pattern -> Pattern)
-> Ord Pattern
Pattern -> Pattern -> Bool
Pattern -> Pattern -> Ordering
Pattern -> Pattern -> Pattern
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 :: Pattern -> Pattern -> Ordering
compare :: Pattern -> Pattern -> Ordering
$c< :: Pattern -> Pattern -> Bool
< :: Pattern -> Pattern -> Bool
$c<= :: Pattern -> Pattern -> Bool
<= :: Pattern -> Pattern -> Bool
$c> :: Pattern -> Pattern -> Bool
> :: Pattern -> Pattern -> Bool
$c>= :: Pattern -> Pattern -> Bool
>= :: Pattern -> Pattern -> Bool
$cmax :: Pattern -> Pattern -> Pattern
max :: Pattern -> Pattern -> Pattern
$cmin :: Pattern -> Pattern -> Pattern
min :: Pattern -> Pattern -> Pattern
Ord, (forall x. Pattern -> Rep Pattern x)
-> (forall x. Rep Pattern x -> Pattern) -> Generic Pattern
forall x. Rep Pattern x -> Pattern
forall x. Pattern -> Rep Pattern x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Pattern -> Rep Pattern x
from :: forall x. Pattern -> Rep Pattern x
$cto :: forall x. Rep Pattern x -> Pattern
to :: forall x. Rep Pattern x -> Pattern
Generic)
  deriving anyclass (Pattern -> ()
(Pattern -> ()) -> NFData Pattern
forall a. (a -> ()) -> NFData a
$crnf :: Pattern -> ()
rnf :: Pattern -> ()
NFData, Eq Pattern
Eq Pattern =>
(Int -> Pattern -> Int) -> (Pattern -> Int) -> Hashable Pattern
Int -> Pattern -> Int
Pattern -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> Pattern -> Int
hashWithSalt :: Int -> Pattern -> Int
$chash :: Pattern -> Int
hash :: Pattern -> Int
Hashable)
  deriving (forall ann. Pattern -> Doc ann)
-> (forall ann. [Pattern] -> Doc ann) -> Pretty Pattern
forall ann. [Pattern] -> Doc ann
forall ann. Pattern -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
$cpretty :: forall ann. Pattern -> Doc ann
pretty :: forall ann. Pattern -> Doc ann
$cprettyList :: forall ann. [Pattern] -> Doc ann
prettyList :: forall ann. [Pattern] -> Doc ann
Pretty via (ViaJSON Pattern)