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

FastTags.Tag

Synopsis

types

data TagVal Source #

Constructors

TagVal 

Fields

Instances

Instances details
Eq TagVal Source # 
Instance details

Defined in FastTags.Tag

Methods

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

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

Ord TagVal Source # 
Instance details

Defined in FastTags.Tag

Show TagVal Source # 
Instance details

Defined in FastTags.Tag

NFData TagVal Source # 
Instance details

Defined in FastTags.Tag

Methods

rnf :: TagVal -> () #

data Type Source #

The Ord instance is used to sort tags with the same name. Given multiple matches, vim will visit them in order, so this should be in the order of interest.

We rely that Type < Constructor. TODO how and where? For sorting tags?

Constructors

Function 
Type 
Constructor 
Class 
Module 
Operator 
Pattern 
Family 
Define

Preprocessor #define

Instances

Instances details
Eq Type Source # 
Instance details

Defined in FastTags.Tag

Methods

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

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

Ord Type Source # 
Instance details

Defined in FastTags.Tag

Methods

compare :: Type -> Type -> Ordering #

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

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

(>) :: Type -> Type -> Bool #

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

max :: Type -> Type -> Type #

min :: Type -> Type -> Type #

Show Type Source # 
Instance details

Defined in FastTags.Tag

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

NFData Type Source # 
Instance details

Defined in FastTags.Tag

Methods

rnf :: Type -> () #

data Tag Source #

Constructors

Tag !(Pos TagVal) 
RepeatableTag !(Pos TagVal)

Just like Tag, except these should be deduplicated by their TagVal, where the one with the lowest line number will be preferred. The idea seems to be that functions will emit a tag for both the signature and definition. TODO seems like a hack, why not just deduplicate all tags? And I think I do that now with dropAdjacent.

Warning !(Pos String) 

Instances

Instances details
Eq Tag Source # 
Instance details

Defined in FastTags.Tag

Methods

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

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

Ord Tag Source # 
Instance details

Defined in FastTags.Tag

Methods

compare :: Tag -> Tag -> Ordering #

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

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

(>) :: Tag -> Tag -> Bool #

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

max :: Tag -> Tag -> Tag #

min :: Tag -> Tag -> Tag #

Show Tag Source # 
Instance details

Defined in FastTags.Tag

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

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 -> () #

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 -> () #

newtype UnstrippedTokens Source #

Newlines have to remain in the tokens because breakBlocks relies on them. But they make pattern matching on the tokens unreliable because newlines might be anywhere. A newtype makes sure that the tokens only get stripped once and that I don't do any pattern matching on unstripped tokens.

Constructors

UnstrippedTokens [Token] 

process

processFile :: FilePath -> Bool -> IO ([Pos TagVal], [String]) Source #

Read tags from one file.

qualify :: Bool -> Maybe Text -> Pos TagVal -> Pos TagVal Source #

Each tag is split into a one qualified with its module name and one without.

TODO I could mark it static, to put in a file: mark, which would make vim prioritize it for same-file tags, but I think it already does that, so maybe this isn't necessary?

process :: FilePath -> Bool -> ByteString -> ([Pos TagVal], [String]) Source #

Process one file's worth of tags.

util

isHsFile :: FilePath -> Bool Source #

Crude predicate for Haskell files

data ProcessMode Source #

Constructors

ProcessVanilla

LitVanilla Haskell file - everything can produce tags

ProcessAlexHappy

Alex/Happy, only first and last braced blocks may produce tags

stripNewlines :: UnstrippedTokens -> [Token] Source #

It's easier to scan for tokens without pesky newlines popping up everywhere. But I need to keep the newlines in in case I hit a where and need to call breakBlocks again.

breakBlocks :: ProcessMode -> UnstrippedTokens -> [UnstrippedTokens] Source #

Break the input up into blocks based on indentation.

whereBlock :: UnstrippedTokens -> [UnstrippedTokens] Source #

Skip to the where and split the indented block below it.