nvim-hs-1.0.0.3: Haskell plugin backend for neovim

Copyright(c) Sebastian Witte
LicenseApache-2.0
Maintainerwoozletoff@gmail.com
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Neovim.Quickfix

Description

 
Synopsis

Documentation

setqflist :: (Monoid strType, NvimObject strType) => [QuickfixListItem strType] -> QuickfixAction -> Neovim env () Source #

This is a wrapper around neovim's setqflist(). strType can be any string that you can append to (hence Monoid) that is also an instance of NvimObject. You can e.g. use the plain old String.

data ColumnNumber Source #

Instances
Eq ColumnNumber Source # 
Instance details

Defined in Neovim.Quickfix

Ord ColumnNumber Source # 
Instance details

Defined in Neovim.Quickfix

Show ColumnNumber Source # 
Instance details

Defined in Neovim.Quickfix

Generic ColumnNumber Source # 
Instance details

Defined in Neovim.Quickfix

Associated Types

type Rep ColumnNumber :: * -> * #

NFData ColumnNumber Source # 
Instance details

Defined in Neovim.Quickfix

Methods

rnf :: ColumnNumber -> () #

type Rep ColumnNumber Source # 
Instance details

Defined in Neovim.Quickfix

type Rep ColumnNumber = D1 (MetaData "ColumnNumber" "Neovim.Quickfix" "nvim-hs-1.0.0.3-6LpgVRGxbdI9yanlUoNJD1" False) (C1 (MetaCons "VisualColumn" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: (C1 (MetaCons "ByteIndexColumn" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: C1 (MetaCons "NoColumn" PrefixI False) (U1 :: * -> *)))

data SignLocation strType Source #

Constructors

LineNumber Int 
SearchPattern strType 
Instances
Eq strType => Eq (SignLocation strType) Source # 
Instance details

Defined in Neovim.Quickfix

Methods

(==) :: SignLocation strType -> SignLocation strType -> Bool #

(/=) :: SignLocation strType -> SignLocation strType -> Bool #

Ord strType => Ord (SignLocation strType) Source # 
Instance details

Defined in Neovim.Quickfix

Methods

compare :: SignLocation strType -> SignLocation strType -> Ordering #

(<) :: SignLocation strType -> SignLocation strType -> Bool #

(<=) :: SignLocation strType -> SignLocation strType -> Bool #

(>) :: SignLocation strType -> SignLocation strType -> Bool #

(>=) :: SignLocation strType -> SignLocation strType -> Bool #

max :: SignLocation strType -> SignLocation strType -> SignLocation strType #

min :: SignLocation strType -> SignLocation strType -> SignLocation strType #

Show strType => Show (SignLocation strType) Source # 
Instance details

Defined in Neovim.Quickfix

Methods

showsPrec :: Int -> SignLocation strType -> ShowS #

show :: SignLocation strType -> String #

showList :: [SignLocation strType] -> ShowS #

Generic (SignLocation strType) Source # 
Instance details

Defined in Neovim.Quickfix

Associated Types

type Rep (SignLocation strType) :: * -> * #

Methods

from :: SignLocation strType -> Rep (SignLocation strType) x #

to :: Rep (SignLocation strType) x -> SignLocation strType #

NFData strType => NFData (SignLocation strType) Source # 
Instance details

Defined in Neovim.Quickfix

Methods

rnf :: SignLocation strType -> () #

type Rep (SignLocation strType) Source # 
Instance details

Defined in Neovim.Quickfix

type Rep (SignLocation strType) = D1 (MetaData "SignLocation" "Neovim.Quickfix" "nvim-hs-1.0.0.3-6LpgVRGxbdI9yanlUoNJD1" False) (C1 (MetaCons "LineNumber" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: C1 (MetaCons "SearchPattern" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 strType)))

data QuickfixListItem strType Source #

Quickfix list item. The parameter names should mostly conform to those in :h setqflist(). Some fields are merged to explicitly state mutually exclusive elements or some other behavior of the fields.

see quickfixListItem for creating a value of this type without typing too much.

Constructors

QFItem 

Fields

  • bufOrFile :: Either Int strType

    Since the filename is only used if no buffer can be specified, this field is a merge of bufnr and filename.

  • lnumOrPattern :: Either Int strType

    Line number or search pattern to locate the error.

  • col :: ColumnNumber

    A tuple of a column number and a boolean indicating which kind of indexing should be used. True means that the visual column should be used. False means to use the byte index.

  • nr :: Maybe Int

    Error number.

  • text :: strType

    Description of the error.

  • errorType :: QuickfixErrorType

    Type of error.

Instances
Eq strType => Eq (QuickfixListItem strType) Source # 
Instance details

Defined in Neovim.Quickfix

Methods

(==) :: QuickfixListItem strType -> QuickfixListItem strType -> Bool #

(/=) :: QuickfixListItem strType -> QuickfixListItem strType -> Bool #

Show strType => Show (QuickfixListItem strType) Source # 
Instance details

Defined in Neovim.Quickfix

Methods

showsPrec :: Int -> QuickfixListItem strType -> ShowS #

show :: QuickfixListItem strType -> String #

showList :: [QuickfixListItem strType] -> ShowS #

Generic (QuickfixListItem strType) Source # 
Instance details

Defined in Neovim.Quickfix

Associated Types

type Rep (QuickfixListItem strType) :: * -> * #

Methods

from :: QuickfixListItem strType -> Rep (QuickfixListItem strType) x #

to :: Rep (QuickfixListItem strType) x -> QuickfixListItem strType #

NFData strType => NFData (QuickfixListItem strType) Source # 
Instance details

Defined in Neovim.Quickfix

Methods

rnf :: QuickfixListItem strType -> () #

(Monoid strType, NvimObject strType) => NvimObject (QuickfixListItem strType) Source # 
Instance details

Defined in Neovim.Quickfix

type Rep (QuickfixListItem strType) Source # 
Instance details

Defined in Neovim.Quickfix

data QuickfixErrorType Source #

Simple error type enum.

Constructors

Warning 
Error 
Instances
Bounded QuickfixErrorType Source # 
Instance details

Defined in Neovim.Quickfix

Enum QuickfixErrorType Source # 
Instance details

Defined in Neovim.Quickfix

Eq QuickfixErrorType Source # 
Instance details

Defined in Neovim.Quickfix

Ord QuickfixErrorType Source # 
Instance details

Defined in Neovim.Quickfix

Read QuickfixErrorType Source # 
Instance details

Defined in Neovim.Quickfix

Show QuickfixErrorType Source # 
Instance details

Defined in Neovim.Quickfix

Generic QuickfixErrorType Source # 
Instance details

Defined in Neovim.Quickfix

Associated Types

type Rep QuickfixErrorType :: * -> * #

NFData QuickfixErrorType Source # 
Instance details

Defined in Neovim.Quickfix

Methods

rnf :: QuickfixErrorType -> () #

NvimObject QuickfixErrorType Source # 
Instance details

Defined in Neovim.Quickfix

type Rep QuickfixErrorType Source # 
Instance details

Defined in Neovim.Quickfix

type Rep QuickfixErrorType = D1 (MetaData "QuickfixErrorType" "Neovim.Quickfix" "nvim-hs-1.0.0.3-6LpgVRGxbdI9yanlUoNJD1" False) (C1 (MetaCons "Warning" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Error" PrefixI False) (U1 :: * -> *))

quickfixListItem Source #

Arguments

:: Monoid strType 
=> Either Int strType

buffer of file name

-> Either Int strType

line number or pattern

-> QuickfixListItem strType 

Create a QuickfixListItem by providing the minimal amount of arguments needed.

data QuickfixAction Source #

Constructors

Append

Add items to the current list (or create a new one if none exists).

Replace

Replace current list (or create a new one if none exists).

New

Create a new list.

Instances
Bounded QuickfixAction Source # 
Instance details

Defined in Neovim.Quickfix

Enum QuickfixAction Source # 
Instance details

Defined in Neovim.Quickfix

Eq QuickfixAction Source # 
Instance details

Defined in Neovim.Quickfix

Ord QuickfixAction Source # 
Instance details

Defined in Neovim.Quickfix

Show QuickfixAction Source # 
Instance details

Defined in Neovim.Quickfix

Generic QuickfixAction Source # 
Instance details

Defined in Neovim.Quickfix

Associated Types

type Rep QuickfixAction :: * -> * #

NFData QuickfixAction Source # 
Instance details

Defined in Neovim.Quickfix

Methods

rnf :: QuickfixAction -> () #

NvimObject QuickfixAction Source # 
Instance details

Defined in Neovim.Quickfix

type Rep QuickfixAction Source # 
Instance details

Defined in Neovim.Quickfix

type Rep QuickfixAction = D1 (MetaData "QuickfixAction" "Neovim.Quickfix" "nvim-hs-1.0.0.3-6LpgVRGxbdI9yanlUoNJD1" False) (C1 (MetaCons "Append" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Replace" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "New" PrefixI False) (U1 :: * -> *)))