{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE FlexibleContexts #-}
module Language.LSP.Types.Lens where
import Language.LSP.Types.Cancellation
import Language.LSP.Types.ClientCapabilities
import Language.LSP.Types.CodeAction
import Language.LSP.Types.CodeLens
import Language.LSP.Types.DocumentColor
import Language.LSP.Types.Command
import Language.LSP.Types.Completion
import Language.LSP.Types.Configuration
import Language.LSP.Types.Declaration
import Language.LSP.Types.Definition
import Language.LSP.Types.Diagnostic
import Language.LSP.Types.DocumentFilter
import Language.LSP.Types.DocumentHighlight
import Language.LSP.Types.DocumentLink
import Language.LSP.Types.FoldingRange
import Language.LSP.Types.Formatting
import Language.LSP.Types.Hover
import Language.LSP.Types.Implementation
import Language.LSP.Types.Initialize
import Language.LSP.Types.Location
import Language.LSP.Types.Progress
import Language.LSP.Types.Registration
import Language.LSP.Types.References
import Language.LSP.Types.Rename
import Language.LSP.Types.SignatureHelp
import Language.LSP.Types.SelectionRange
import Language.LSP.Types.ServerCapabilities
import Language.LSP.Types.DocumentSymbol
import Language.LSP.Types.TextDocument
import Language.LSP.Types.TypeDefinition
import Language.LSP.Types.Window
import Language.LSP.Types.WatchedFiles
import Language.LSP.Types.WorkspaceEdit
import Language.LSP.Types.WorkspaceFolders
import Language.LSP.Types.WorkspaceSymbol
import Language.LSP.Types.Message
import Control.Lens.TH
makeFieldsNoPrefix ''WorkspaceEditClientCapabilities
makeFieldsNoPrefix ''DidChangeConfigurationClientCapabilities
makeFieldsNoPrefix ''ExecuteCommandClientCapabilities
makeFieldsNoPrefix ''WorkspaceClientCapabilities
makeFieldsNoPrefix ''TextDocumentSyncClientCapabilities
makeFieldsNoPrefix ''CompletionItemTagsClientCapabilities
makeFieldsNoPrefix ''CompletionItemKindClientCapabilities
makeFieldsNoPrefix ''CompletionClientCapabilities
makeFieldsNoPrefix ''HoverClientCapabilities
makeFieldsNoPrefix ''SignatureHelpSignatureInformation
makeFieldsNoPrefix ''SignatureHelpParameterInformation
makeFieldsNoPrefix ''SignatureHelpClientCapabilities
makeFieldsNoPrefix ''ReferencesClientCapabilities
makeFieldsNoPrefix ''DefinitionClientCapabilities
makeFieldsNoPrefix ''TypeDefinitionClientCapabilities
makeFieldsNoPrefix ''ImplementationClientCapabilities
makeFieldsNoPrefix ''PublishDiagnosticsClientCapabilities
makeFieldsNoPrefix ''PublishDiagnosticsTagsClientCapabilities
makeFieldsNoPrefix ''TextDocumentClientCapabilities
makeFieldsNoPrefix ''ClientCapabilities
makeFieldsNoPrefix ''CompletionOptions
makeFieldsNoPrefix ''SignatureHelpOptions
makeFieldsNoPrefix ''ExecuteCommandOptions
makeFieldsNoPrefix ''SaveOptions
makeFieldsNoPrefix ''TextDocumentSyncOptions
makeFieldsNoPrefix ''WorkspaceServerCapabilities
makeFieldsNoPrefix ''WorkspaceFoldersServerCapabilities
makeFieldsNoPrefix ''ServerCapabilities
makeFieldsNoPrefix ''Registration
makeFieldsNoPrefix ''RegistrationParams
makeFieldsNoPrefix ''TextDocumentRegistrationOptions
makeFieldsNoPrefix ''Unregistration
makeFieldsNoPrefix ''UnregistrationParams
makeFieldsNoPrefix ''DidChangeConfigurationParams
makeFieldsNoPrefix ''ConfigurationItem
makeFieldsNoPrefix ''ConfigurationParams
makeFieldsNoPrefix ''DidOpenTextDocumentParams
makeFieldsNoPrefix ''TextDocumentContentChangeEvent
makeFieldsNoPrefix ''DidChangeTextDocumentParams
makeFieldsNoPrefix ''TextDocumentChangeRegistrationOptions
makeFieldsNoPrefix ''WillSaveTextDocumentParams
makeFieldsNoPrefix ''DidSaveTextDocumentParams
makeFieldsNoPrefix ''TextDocumentSaveRegistrationOptions
makeFieldsNoPrefix ''DidCloseTextDocumentParams
makeFieldsNoPrefix ''PublishDiagnosticsParams
makeFieldsNoPrefix ''LanguageString
makeFieldsNoPrefix ''ParameterInformation
makeFieldsNoPrefix ''SignatureInformation
makeFieldsNoPrefix ''SignatureHelp
makeFieldsNoPrefix ''SignatureHelpRegistrationOptions
makeFieldsNoPrefix ''ReferenceContext
makeFieldsNoPrefix ''ReferenceParams
makeFieldsNoPrefix ''ExecuteCommandParams
makeFieldsNoPrefix ''ExecuteCommandRegistrationOptions
makeFieldsNoPrefix ''ApplyWorkspaceEditParams
makeFieldsNoPrefix ''ApplyWorkspaceEditResponseBody
makeFieldsNoPrefix ''InitializeParams
makeFieldsNoPrefix ''InitializeError
makeFieldsNoPrefix ''InitializeResult
makeFieldsNoPrefix ''ClientInfo
makeFieldsNoPrefix ''ServerInfo
makeFieldsNoPrefix ''InitializedParams
makeFieldsNoPrefix ''DidChangeWatchedFilesClientCapabilities
makeFieldsNoPrefix ''DidChangeWatchedFilesRegistrationOptions
makeFieldsNoPrefix ''FileSystemWatcher
makeFieldsNoPrefix ''WatchKind
makeFieldsNoPrefix ''FileEvent
makeFieldsNoPrefix ''DidChangeWatchedFilesParams
makeFieldsNoPrefix ''WorkspaceSymbolKindClientCapabilities
makeFieldsNoPrefix ''WorkspaceSymbolClientCapabilities
makeFieldsNoPrefix ''WorkspaceSymbolOptions
makeFieldsNoPrefix ''WorkspaceSymbolRegistrationOptions
makeFieldsNoPrefix ''WorkspaceSymbolParams
makeFieldsNoPrefix ''Position
makeFieldsNoPrefix ''Range
makeFieldsNoPrefix ''Location
makeFieldsNoPrefix ''CompletionItem
makeFieldsNoPrefix ''CompletionContext
makeFieldsNoPrefix ''CompletionList
makeFieldsNoPrefix ''CompletionParams
makeFieldsNoPrefix ''CompletionRegistrationOptions
makeFieldsNoPrefix ''DeclarationClientCapabilities
makeFieldsNoPrefix ''DeclarationOptions
makeFieldsNoPrefix ''DeclarationRegistrationOptions
makeFieldsNoPrefix ''DeclarationParams
makeFieldsNoPrefix ''CodeActionKindClientCapabilities
makeFieldsNoPrefix ''CodeActionLiteralSupport
makeFieldsNoPrefix ''CodeActionClientCapabilities
makeFieldsNoPrefix ''CodeActionOptions
makeFieldsNoPrefix ''CodeActionRegistrationOptions
makeFieldsNoPrefix ''CodeActionContext
makeFieldsNoPrefix ''CodeActionParams
makeFieldsNoPrefix ''CodeAction
makeFieldsNoPrefix ''CodeLensClientCapabilities
makeFieldsNoPrefix ''CodeLensOptions
makeFieldsNoPrefix ''CodeLensRegistrationOptions
makeFieldsNoPrefix ''CodeLensParams
makeFieldsNoPrefix ''CodeLens
makeFieldsNoPrefix ''DocumentLinkClientCapabilities
makeFieldsNoPrefix ''DocumentLinkOptions
makeFieldsNoPrefix ''DocumentLinkRegistrationOptions
makeFieldsNoPrefix ''DocumentLinkParams
makeFieldsNoPrefix ''DocumentLink
makeFieldsNoPrefix ''DocumentColorClientCapabilities
makeFieldsNoPrefix ''DocumentColorOptions
makeFieldsNoPrefix ''DocumentColorRegistrationOptions
makeFieldsNoPrefix ''DocumentColorParams
makeFieldsNoPrefix ''Color
makeFieldsNoPrefix ''ColorInformation
makeFieldsNoPrefix ''ColorPresentationParams
makeFieldsNoPrefix ''ColorPresentation
makeFieldsNoPrefix ''DocumentFormattingClientCapabilities
makeFieldsNoPrefix ''DocumentFormattingOptions
makeFieldsNoPrefix ''DocumentFormattingRegistrationOptions
makeFieldsNoPrefix ''FormattingOptions
makeFieldsNoPrefix ''DocumentFormattingParams
makeFieldsNoPrefix ''DocumentRangeFormattingClientCapabilities
makeFieldsNoPrefix ''DocumentRangeFormattingOptions
makeFieldsNoPrefix ''DocumentRangeFormattingRegistrationOptions
makeFieldsNoPrefix ''DocumentRangeFormattingParams
makeFieldsNoPrefix ''DocumentOnTypeFormattingClientCapabilities
makeFieldsNoPrefix ''DocumentOnTypeFormattingOptions
makeFieldsNoPrefix ''DocumentOnTypeFormattingRegistrationOptions
makeFieldsNoPrefix ''DocumentOnTypeFormattingParams
makeFieldsNoPrefix ''RenameClientCapabilities
makeFieldsNoPrefix ''RenameOptions
makeFieldsNoPrefix ''RenameRegistrationOptions
makeFieldsNoPrefix ''RenameParams
makeFieldsNoPrefix ''PrepareRenameParams
makeFieldsNoPrefix ''RangeWithPlaceholder
makeFieldsNoPrefix ''FoldingRangeClientCapabilities
makeFieldsNoPrefix ''FoldingRangeOptions
makeFieldsNoPrefix ''FoldingRangeRegistrationOptions
makeFieldsNoPrefix ''FoldingRangeParams
makeFieldsNoPrefix ''FoldingRange
makeFieldsNoPrefix ''SelectionRangeClientCapabilities
makeFieldsNoPrefix ''SelectionRangeOptions
makeFieldsNoPrefix ''SelectionRangeRegistrationOptions
makeFieldsNoPrefix ''SelectionRangeParams
makeFieldsNoPrefix ''SelectionRange
makeFieldsNoPrefix ''DocumentHighlightClientCapabilities
makeFieldsNoPrefix ''DocumentHighlightOptions
makeFieldsNoPrefix ''DocumentHighlightRegistrationOptions
makeFieldsNoPrefix ''DocumentHighlightParams
makeFieldsNoPrefix ''DocumentHighlight
makeFieldsNoPrefix ''DocumentSymbolKindClientCapabilities
makeFieldsNoPrefix ''DocumentSymbolClientCapabilities
makeFieldsNoPrefix ''DocumentSymbolOptions
makeFieldsNoPrefix ''DocumentSymbolRegistrationOptions
makeFieldsNoPrefix ''DocumentSymbolParams
makeFieldsNoPrefix ''DocumentSymbol
makeFieldsNoPrefix ''SymbolInformation
makeFieldsNoPrefix ''DocumentFilter
makeFieldsNoPrefix ''TextEdit
makeFieldsNoPrefix ''VersionedTextDocumentIdentifier
makeFieldsNoPrefix ''TextDocumentEdit
makeFieldsNoPrefix ''WorkspaceEdit
makeFieldsNoPrefix ''WorkspaceFolder
makeFieldsNoPrefix ''WorkspaceFoldersChangeEvent
makeFieldsNoPrefix ''DidChangeWorkspaceFoldersParams
makeFieldsNoPrefix ''RequestMessage
makeFieldsNoPrefix ''ResponseError
makeFieldsNoPrefix ''ResponseMessage
makeFieldsNoPrefix ''NotificationMessage
makeFieldsNoPrefix ''CancelParams
makeFieldsNoPrefix ''TextDocumentItem
makeFieldsNoPrefix ''TextDocumentIdentifier
makeFieldsNoPrefix ''TextDocumentPositionParams
makeFieldsNoPrefix ''Command
makeFieldsNoPrefix ''Diagnostic
makeFieldsNoPrefix ''DiagnosticRelatedInformation
makeFieldsNoPrefix ''Hover
makeFieldsNoPrefix ''HoverRegistrationOptions
makeFieldsNoPrefix ''ShowMessageParams
makeFieldsNoPrefix ''MessageActionItem
makeFieldsNoPrefix ''ShowMessageRequestParams
makeFieldsNoPrefix ''LogMessageParams
makeFieldsNoPrefix ''ProgressParams
makeFieldsNoPrefix ''WorkDoneProgressBeginParams
makeFieldsNoPrefix ''WorkDoneProgressReportParams
makeFieldsNoPrefix ''WorkDoneProgressEndParams
makeFieldsNoPrefix ''WorkDoneProgressCancelParams
makeFieldsNoPrefix ''WorkDoneProgressCreateParams