-- 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.TextDocumentFilter 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 as Row
import qualified Data.Row.Aeson as Aeson
import qualified Data.Row.Hashable as Hashable
import qualified Data.Text
import qualified Language.LSP.Protocol.Types.Common

{-|
A document filter denotes a document by different properties like
the `TextDocument.languageId` of
its resource, or a glob-pattern that is applied to the `TextDocument.fileName`.

Glob patterns can have the following syntax:
- `*` to match one or more characters in a path segment
- `?` to match on one character in a path segment
- `**` to match any number of path segments, including none
- `{}` to group sub patterns into an OR expression. (e.g. `**​/*.{ts,js}` matches all TypeScript and JavaScript files)
- `[]` to declare a range of characters to match in a path segment (e.g., `example.[0-9]` to match on `example.0`, `example.1`, …)
- `[!...]` to negate a range of characters to match in a path segment (e.g., `example.[!0-9]` to match on `example.a`, `example.b`, but not `example.0`)

@sample A language filter that applies to typescript files on disk: `{ language: 'typescript', scheme: 'file' }`
@sample A language filter that applies to all package.json paths: `{ language: 'json', pattern: '**package.json' }`

@since 3.17.0
-}
newtype TextDocumentFilter = TextDocumentFilter ((Row.Rec ("language" Row..== Data.Text.Text Row..+ ("scheme" Row..== (Maybe Data.Text.Text) Row..+ ("pattern" Row..== (Maybe Data.Text.Text) Row..+ Row.Empty)))) Language.LSP.Protocol.Types.Common.|? ((Row.Rec ("language" Row..== (Maybe Data.Text.Text) Row..+ ("scheme" Row..== Data.Text.Text Row..+ ("pattern" Row..== (Maybe Data.Text.Text) Row..+ Row.Empty)))) Language.LSP.Protocol.Types.Common.|? (Row.Rec ("language" Row..== (Maybe Data.Text.Text) Row..+ ("scheme" Row..== (Maybe Data.Text.Text) Row..+ ("pattern" Row..== Data.Text.Text Row..+ Row.Empty))))))
  deriving newtype ([TextDocumentFilter] -> Encoding
[TextDocumentFilter] -> Value
TextDocumentFilter -> Encoding
TextDocumentFilter -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TextDocumentFilter] -> Encoding
$ctoEncodingList :: [TextDocumentFilter] -> Encoding
toJSONList :: [TextDocumentFilter] -> Value
$ctoJSONList :: [TextDocumentFilter] -> Value
toEncoding :: TextDocumentFilter -> Encoding
$ctoEncoding :: TextDocumentFilter -> Encoding
toJSON :: TextDocumentFilter -> Value
$ctoJSON :: TextDocumentFilter -> Value
Aeson.ToJSON, Value -> Parser [TextDocumentFilter]
Value -> Parser TextDocumentFilter
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TextDocumentFilter]
$cparseJSONList :: Value -> Parser [TextDocumentFilter]
parseJSON :: Value -> Parser TextDocumentFilter
$cparseJSON :: Value -> Parser TextDocumentFilter
Aeson.FromJSON)
  deriving stock (Int -> TextDocumentFilter -> ShowS
[TextDocumentFilter] -> ShowS
TextDocumentFilter -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextDocumentFilter] -> ShowS
$cshowList :: [TextDocumentFilter] -> ShowS
show :: TextDocumentFilter -> String
$cshow :: TextDocumentFilter -> String
showsPrec :: Int -> TextDocumentFilter -> ShowS
$cshowsPrec :: Int -> TextDocumentFilter -> ShowS
Show, TextDocumentFilter -> TextDocumentFilter -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextDocumentFilter -> TextDocumentFilter -> Bool
$c/= :: TextDocumentFilter -> TextDocumentFilter -> Bool
== :: TextDocumentFilter -> TextDocumentFilter -> Bool
$c== :: TextDocumentFilter -> TextDocumentFilter -> Bool
Eq, Eq TextDocumentFilter
TextDocumentFilter -> TextDocumentFilter -> Bool
TextDocumentFilter -> TextDocumentFilter -> Ordering
TextDocumentFilter -> TextDocumentFilter -> TextDocumentFilter
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 :: TextDocumentFilter -> TextDocumentFilter -> TextDocumentFilter
$cmin :: TextDocumentFilter -> TextDocumentFilter -> TextDocumentFilter
max :: TextDocumentFilter -> TextDocumentFilter -> TextDocumentFilter
$cmax :: TextDocumentFilter -> TextDocumentFilter -> TextDocumentFilter
>= :: TextDocumentFilter -> TextDocumentFilter -> Bool
$c>= :: TextDocumentFilter -> TextDocumentFilter -> Bool
> :: TextDocumentFilter -> TextDocumentFilter -> Bool
$c> :: TextDocumentFilter -> TextDocumentFilter -> Bool
<= :: TextDocumentFilter -> TextDocumentFilter -> Bool
$c<= :: TextDocumentFilter -> TextDocumentFilter -> Bool
< :: TextDocumentFilter -> TextDocumentFilter -> Bool
$c< :: TextDocumentFilter -> TextDocumentFilter -> Bool
compare :: TextDocumentFilter -> TextDocumentFilter -> Ordering
$ccompare :: TextDocumentFilter -> TextDocumentFilter -> Ordering
Ord, forall x. Rep TextDocumentFilter x -> TextDocumentFilter
forall x. TextDocumentFilter -> Rep TextDocumentFilter x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TextDocumentFilter x -> TextDocumentFilter
$cfrom :: forall x. TextDocumentFilter -> Rep TextDocumentFilter x
Generic)
  deriving anyclass (TextDocumentFilter -> ()
forall a. (a -> ()) -> NFData a
rnf :: TextDocumentFilter -> ()
$crnf :: TextDocumentFilter -> ()
NFData, Eq TextDocumentFilter
Int -> TextDocumentFilter -> Int
TextDocumentFilter -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: TextDocumentFilter -> Int
$chash :: TextDocumentFilter -> Int
hashWithSalt :: Int -> TextDocumentFilter -> Int
$chashWithSalt :: Int -> TextDocumentFilter -> Int
Hashable)
  deriving forall ann. [TextDocumentFilter] -> Doc ann
forall ann. TextDocumentFilter -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
prettyList :: forall ann. [TextDocumentFilter] -> Doc ann
$cprettyList :: forall ann. [TextDocumentFilter] -> Doc ann
pretty :: forall ann. TextDocumentFilter -> Doc ann
$cpretty :: forall ann. TextDocumentFilter -> Doc ann
Pretty via (ViaJSON TextDocumentFilter)