haskell-token-utils-0.0.0.2: Utilities to tie up tokens to an AST

Safe HaskellSafe-Inferred

Language.Haskell.TokenUtils.Types

Synopsis

Documentation

data Entry a Source

An entry in the data structure for a particular srcspan.

Constructors

Entry !ForestSpan !Layout ![a]

Entry has * the source span contained in this Node * how the sub-elements nest * the tokens for the SrcSpan if subtree is empty

Deleted !ForestSpan !RowOffset !SimpPos

Deleted has * the source span has been deleted * prior gap in lines * the gap between this span end and the start of the next in the fringe of the tree.

Instances

IsToken a => Eq (Entry a) 
IsToken t => Ord (LayoutTree t) 
Show a => Show (Entry a) 
HasLoc (Entry a) 

data TokenCache a Source

Constructors

TK 

Fields

tkCache :: !(Map TreeId (Tree (Entry a)))
 
tkLastTreeId :: !TreeId
 

data TreeId Source

Constructors

TId !Int 

Instances

mainTid :: TreeIdSource

Identifies the tree carrying the main tokens, not any work in progress or deleted ones

type ForestSpan = (ForestPos, ForestPos)Source

Match a SrcSpan, using a ForestLine as the marker

data ForestLine Source

Constructors

ForestLine 

Fields

flSpanLengthChanged :: !Bool

The length of the span may have changed due to updated tokens.

flTreeSelector :: !Int
 
flInsertVersion :: !Int
 
flLine :: !Int
 

type Row = IntSource

type Col = IntSource

data Layout Source

Constructors

Above EndOffset (Row, Col) (Row, Col) EndOffset

Initial offset from token before the stacked list of items, the (r,c) of the first non-comment token, the (r,c) of the end of the last non-comment token in the stacked list to be able to calculate the (RowOffset,ColOffset) between the last token and the start of the next item.

NoChange 

data Located e Source

Constructors

L Span e 

Instances

Show e => Show (Located e) 

data Span Source

Constructors

Span (Row, Col) (Row, Col) 

forestSpanToSimpPos :: ForestSpan -> (SimpPos, SimpPos)Source

Strip out the version markers

forestSpanVersionSet :: ForestSpan -> BoolSource

Checks if the version is non-zero in either position

treeStartEnd :: Tree (Entry a) -> ForestSpanSource

Get the start and end position of a Tree treeStartEnd :: Tree Entry -> (SimpPos,SimpPos) treeStartEnd (Node (Entry sspan _) _) = (getGhcLoc sspan,getGhcLocEnd sspan)

groupTokensByLine :: IsToken a => [a] -> [[a]]Source

increaseSrcSpan :: IsToken a => SimpPos -> a -> aSource

Shift the whole token by the given offset

addOffsetToToks :: IsToken a => SimpPos -> [a] -> [a]Source

Add a constant line and column offset to a span of tokens

ghcLineToForestLine :: Int -> ForestLineSource

Extract an encoded ForestLine from a GHC line

class Show a => IsToken a whereSource

The IsToken class captures the different token type in use. For GHC it represents the type returned by getRichTokenStream, namely [(GHC.Located GHC.Token, String)] For haskell-src-exts this is the reult of lexTokenStream, namely `[HSE.Loc HSE.Token]`

Methods

getSpan :: a -> SpanSource

putSpan :: a -> Span -> aSource

tokenLen :: a -> IntSource

tokenLen returns the length of the string representation of the token, not just the difference in the location, as the string may have changed without the position being updated, e.g. in a renaming

isComment :: a -> BoolSource

isEmpty :: a -> BoolSource

Zero-length tokens, as appear in GHC as markers

mkZeroToken :: aSource

isDo :: a -> BoolSource

isElse :: a -> BoolSource

isIn :: a -> BoolSource

isLet :: a -> BoolSource

isOf :: a -> BoolSource

isThen :: a -> BoolSource

isWhere :: a -> BoolSource

tokenToString :: a -> StringSource

showTokenStream :: [a] -> StringSource

markToken :: a -> aSource

Mark a token so that it can be use to trigger layout checking later when the toks are retrieved

isMarked :: a -> BoolSource

isIgnoredNonComment :: IsToken a => a -> BoolSource

Tokens that are ignored when determining the first non-comment token in a span

class HasLoc a whereSource

class Allocatable b a whereSource

Methods

allocTokens :: b -> [a] -> LayoutTree aSource

Instances

Allocatable (Module SrcSpanInfo) (Loc TuToken)

This instance is the purpose of this module