fast-tags-2.0.1: Fast incremental vi and emacs tags.
Safe HaskellNone
LanguageHaskell2010

FastTags.Token

Documentation

data Pos a Source #

Constructors

Pos 

Fields

Instances

Instances details
Eq a => Eq (Pos a) Source # 
Instance details

Defined in FastTags.Token

Methods

(==) :: Pos a -> Pos a -> Bool #

(/=) :: Pos a -> Pos a -> Bool #

Ord a => Ord (Pos a) Source # 
Instance details

Defined in FastTags.Token

Methods

compare :: Pos a -> Pos a -> Ordering #

(<) :: Pos a -> Pos a -> Bool #

(<=) :: Pos a -> Pos a -> Bool #

(>) :: Pos a -> Pos a -> Bool #

(>=) :: Pos a -> Pos a -> Bool #

max :: Pos a -> Pos a -> Pos a #

min :: Pos a -> Pos a -> Pos a #

Show a => Show (Pos a) Source # 
Instance details

Defined in FastTags.Token

Methods

showsPrec :: Int -> Pos a -> ShowS #

show :: Pos a -> String #

showList :: [Pos a] -> ShowS #

NFData a => NFData (Pos a) Source # 
Instance details

Defined in FastTags.Token

Methods

rnf :: Pos a -> () #

newtype Line Source #

Constructors

Line 

Fields

Instances

Instances details
Eq Line Source # 
Instance details

Defined in FastTags.Token

Methods

(==) :: Line -> Line -> Bool #

(/=) :: Line -> Line -> Bool #

Num Line Source # 
Instance details

Defined in FastTags.Token

Methods

(+) :: Line -> Line -> Line #

(-) :: Line -> Line -> Line #

(*) :: Line -> Line -> Line #

negate :: Line -> Line #

abs :: Line -> Line #

signum :: Line -> Line #

fromInteger :: Integer -> Line #

Ord Line Source # 
Instance details

Defined in FastTags.Token

Methods

compare :: Line -> Line -> Ordering #

(<) :: Line -> Line -> Bool #

(<=) :: Line -> Line -> Bool #

(>) :: Line -> Line -> Bool #

(>=) :: Line -> Line -> Bool #

max :: Line -> Line -> Line #

min :: Line -> Line -> Line #

Show Line Source # 
Instance details

Defined in FastTags.Token

Methods

showsPrec :: Int -> Line -> ShowS #

show :: Line -> String #

showList :: [Line] -> ShowS #

NFData Line Source # 
Instance details

Defined in FastTags.Token

Methods

rnf :: Line -> () #

newtype Offset Source #

Constructors

Offset 

Fields

Instances

Instances details
Eq Offset Source # 
Instance details

Defined in FastTags.Token

Methods

(==) :: Offset -> Offset -> Bool #

(/=) :: Offset -> Offset -> Bool #

Num Offset Source # 
Instance details

Defined in FastTags.Token

Ord Offset Source # 
Instance details

Defined in FastTags.Token

Show Offset Source # 
Instance details

Defined in FastTags.Token

NFData Offset Source # 
Instance details

Defined in FastTags.Token

Methods

rnf :: Offset -> () #

data SrcPos Source #

Constructors

SrcPos 

Fields

Instances

Instances details
Eq SrcPos Source # 
Instance details

Defined in FastTags.Token

Methods

(==) :: SrcPos -> SrcPos -> Bool #

(/=) :: SrcPos -> SrcPos -> Bool #

Ord SrcPos Source # 
Instance details

Defined in FastTags.Token

Show SrcPos Source # 
Instance details

Defined in FastTags.Token

NFData SrcPos Source # 
Instance details

Defined in FastTags.Token

Methods

rnf :: SrcPos -> () #

data TokenVal Source #

Constructors

KWCase 
KWClass 
KWData 
KWDefault 
KWDeriving 
KWDo 
KWElse 
KWFamily 
KWForeign 
KWIf 
KWImport 
KWIn 
KWInfix 
KWInfixl 
KWInfixr 
KWInstance 
KWLet 
KWModule 
KWNewtype 
KWOf 
KWThen 
KWType 
KWWhere 
Arrow 
At 
Backtick 
Comma 
Dot 
DoubleColon 
Equals 
ExclamationMark 
Implies 
LBrace 
LBracket 
LParen 
Pipe 
RBrace 
RBracket 
RParen 
Tilde 
Semicolon 
T !Text 
Newline !Int

Special token, not part of Haskell spec. Stores indentation.

String

String contents is not tracked since it's irrelevant.

Character

Actual character not tracked since it's irrelevant.

Number

Actual value not tracked since it's irrelevant.

QuasiquoterStart 
QuasiquoterEnd 
SpliceStart 
ToplevelSplice 
LambdaBackslash 
CppDefine !Text 
HSCEnum 
HSCDirective 
HSCDirectiveBraced

e.g. {ndefine foo...nbar}, ends with RBrace

LBanana 
RBanana 
Error Text 
DQuote 
EOF 

Instances

Instances details
Eq TokenVal Source # 
Instance details

Defined in FastTags.Token

Ord TokenVal Source # 
Instance details

Defined in FastTags.Token

Show TokenVal Source # 
Instance details

Defined in FastTags.Token

Generic TokenVal Source # 
Instance details

Defined in FastTags.Token

Associated Types

type Rep TokenVal :: Type -> Type #

Methods

from :: TokenVal -> Rep TokenVal x #

to :: Rep TokenVal x -> TokenVal #

NFData TokenVal Source # 
Instance details

Defined in FastTags.Token

Methods

rnf :: TokenVal -> () #

type Rep TokenVal Source # 
Instance details

Defined in FastTags.Token

type Rep TokenVal = D1 ('MetaData "TokenVal" "FastTags.Token" "fast-tags-2.0.1-GA3xJbsvAK4I5Nvjy5MNAy" 'False) (((((C1 ('MetaCons "KWCase" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KWClass" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KWData" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "KWDefault" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KWDeriving" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "KWDo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KWElse" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "KWFamily" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KWForeign" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "KWIf" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KWImport" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "KWIn" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KWInfix" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "KWInfixl" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KWInfixr" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "KWInstance" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KWLet" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KWModule" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "KWNewtype" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KWOf" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "KWThen" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KWType" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "KWWhere" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Arrow" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "At" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Backtick" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Comma" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Dot" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DoubleColon" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Equals" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "ExclamationMark" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Implies" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LBrace" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "LBracket" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LParen" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Pipe" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RBrace" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "RBracket" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RParen" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Tilde" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Semicolon" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "T" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "Newline" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int))) :+: (C1 ('MetaCons "String" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Character" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Number" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "QuasiquoterStart" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "QuasiquoterEnd" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "SpliceStart" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ToplevelSplice" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LambdaBackslash" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CppDefine" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Text))))) :+: (((C1 ('MetaCons "HSCEnum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HSCDirective" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HSCDirectiveBraced" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LBanana" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "RBanana" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Error" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) :+: (C1 ('MetaCons "DQuote" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EOF" 'PrefixI 'False) (U1 :: Type -> Type)))))))