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

Safe HaskellSafe-Inferred

Language.Haskell.TokenUtils.TokenUtils

Contents

Synopsis

Creating

initTokenCacheLayout :: IsToken a => Tree (Entry a) -> TokenCache aSource

The primary data structure is the TokenCache. This holds the evolving forest of modified LayoutTrees. Each concrete implementation should provide a function to generate a LayoutTree from its specific AST and tokens.

mkTreeFromTokens :: IsToken a => [a] -> Tree (Entry a)Source

Make a tree representing a particular set of tokens

mkTreeFromSpanTokens :: IsToken a => ForestSpan -> [a] -> Tree (Entry a)Source

Make a tree representing a particular set of tokens

Module type

data Positioning Source

How new SrcSpans should be inserted in the Token tree, relative to the prior span

Constructors

PlaceAdjacent

Only a single space between the end of the prior span and the new one

PlaceAbsolute !Int !Int

Start at the specified line and col

PlaceAbsCol !Int !Int !Int

Line offset and absolute Col. Mainly for forcing start at left margin, number of lines to add at the end

PlaceOffset !Int !Int !Int

Line and Col offset for start, num lines to add at the end relative to the indent level of the prior span

PlaceIndent !Int !Int !Int

Line and Col offset for start, num lines to add at the end relative to the indent level of the prior line

Instances

data ReversedToks a Source

Keep track of when tokens are reversed, to avoid confusion

Constructors

RT [a] 

Instances

Show a => Show (ReversedToks a) 

High level functions for use by clients, at TokenCache level

addTokensAfterSpanInCacheSource

Arguments

:: IsToken a 
=> TokenCache a 
-> SimpSpan

Preceding location for new tokens

-> Positioning 
-> [a]

New tokens to be added

-> (TokenCache a, SimpSpan)

updated TokenCache and SrcSpan location for the new tokens in the TokenTree

High level functions for use by clients, at LayoutTree level

Operations at LayoutTree level

updateTokensForSrcSpan :: IsToken a => Tree (Entry a) -> SimpSpan -> [a] -> (Tree (Entry a), SimpSpan, Tree (Entry a))Source

Replace the tokens for a given SrcSpan with new ones. The SrcSpan will be inserted into the tree if it is not already there. If the SrcSpan changes size, replace the SrcSpan with a new one (marked), and return it, as well as the old one TODO: What about trailing comments? Preserve or replace?

replaceTokenForSrcSpan :: IsToken a => Tree (Entry a) -> SimpSpan -> a -> Tree (Entry a)Source

Replace a single token in a token tree, without changing the structure of the tree NOTE: the GHC.SrcSpan may have been used to select the appropriate forest in the first place, and is required to select the correct span in the tree, due to the ForestLine annotations that may be present

getSrcSpanFor :: IsToken a => Tree (Entry a) -> ForestSpan -> (Tree (Entry a), Tree (Entry a))Source

Retrieve a path to the tree containing a ForestSpan from the forest, inserting it if not already present

indentDeclToksSource

Arguments

:: (IsToken a, HasLoc t) 
=> (t -> ForestSpan -> t) 
-> t

The AST (or fragment)

-> Tree (Entry a)

Existing token tree

-> Int

(signed) number of columns to indent/dedent

-> (t, Tree (Entry a))

Updated AST and tokens

indent the tree and tokens by the given offset, and sync the AST to the tree too.

addToksAfterSrcSpanSource

Arguments

:: IsToken a 
=> Tree (Entry a)

TokenTree to be modified

-> SimpSpan

Preceding location for new tokens

-> Positioning 
-> [a]

New tokens to be added

-> (Tree (Entry a), SimpSpan)

updated TokenTree and SrcSpan location for the new tokens in the TokenTree

Add new tokens after the given SrcSpan, constructing a new SrcSpan in the process

reIndentToks :: IsToken a => Positioning -> [a] -> [a] -> [a]Source

Place the new tokens so that they are positioned correctly relative to the previous tokens

Working with tokens

basicTokenise :: IsToken a => String -> [a]Source

Convert a string into a set of Haskell tokens. It has default position and offset, since it will be stitched into place in TokenUtils

tokenise :: IsToken a => SimpSpan -> Int -> Bool -> String -> [a]Source

Convert a string into a set of Haskell tokens, following the given position, with each line indented by a given column offset if required TODO: replace 'colOffset withFirstLineIndent' with a Maybe Int ++AZ++

invariant :: IsToken a => Tree (Entry a) -> [String]Source

Check the invariant for the token cache. Returns list of any errors found. Invariants: 1. For each tree, either the rootLabel has a SrcSpan only, or the subForest /= []. 2a. The trees making up the subForest of a given node fully include the parent SrcSpan. i.e. the leaves contain all the tokens for a given SrcSpan. 2b. The subForest is in SrcSpan order 3. A given SrcSpan can only appear (or be included) in a single tree of the forest. 4. The parent link for all sub-trees does exist, and actually points to the parent. 5. There are no nullForestSpan entries in the tree NOTE: the tokens may extend before or after the SrcSpan, due to comments only NOTE2: this will have to be revisited when edits to the tokens are made

retrieveTokensInterim :: IsToken a => Tree (Entry a) -> [a]Source

Retrieve all the tokens at the leaves of the tree, in order. No adjustments are made to address gaps or re-alignment of the tokens

getTokensForNoIntros :: IsToken a => Bool -> Tree (Entry a) -> SimpSpan -> (Tree (Entry a), [a])Source

Get the (possible cached) tokens for a given source span, and cache their being fetched. NOTE: The SrcSpan may be one introduced by HaRe, rather than GHC.

getTokensFor :: IsToken a => Bool -> Tree (Entry a) -> SimpSpan -> (Tree (Entry a), [a])Source

Get the (possible cached) tokens for a given source span, and cache their being fetched. NOTE: The SrcSpan may be one introduced by HaRe, rather than GHC.

getTokensBefore :: IsToken a => Tree (Entry a) -> SimpSpan -> (Tree (Entry a), ReversedToks a)Source

Get the tokens preceding a given SrcSpan

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

splitOnNewLn :: IsToken a => [a] -> ([a], [a])Source

getIndentOffset :: IsToken a => [a] -> SimpPos -> IntSource

Get the indent of the line before, taking into account in-line 'where', 'let', 'in' and 'do' tokens

newLnToken :: IsToken a => a -> aSource

startEndLocIncComments' :: IsToken a => [a] -> (SimpPos, SimpPos) -> (SimpPos, SimpPos)Source

Get the start&end location of t in the token stream, then extend the start and end location to cover the preceding and following comments.

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

Strip out the version markers

should be in utils

showTree :: IsToken a => Tree (Entry a) -> StringSource

showToks :: IsToken a => [a] -> StringSource

Exposed for testing only

addNewSrcSpanAndToksAfterSource

Arguments

:: IsToken a 
=> Tree (Entry a)

The forest to update

-> SimpSpan

The new span comes after this one

-> SimpSpan

Existing span for the tokens

-> Positioning 
-> [a]

The new tokens belonging to the new SrcSpan

-> (Tree (Entry a), SimpSpan)

Unique SrcSpan allocated in the forest to identify this span in its position

Add a new SrcSpan and Tokens after a given one in the token stream and forest. This will be given a unique SrcSpan in return, which specifically indexes into the forest.

openZipperToSpan :: IsToken a => ForestSpan -> TreePos Full (Entry a) -> TreePos Full (Entry a)Source

Open a zipper so that its focus has the given SrcSpan in its subtree, or the location where the SrcSpan should go, if it is not in the tree

openZipperToSpanAdded :: IsToken a => ForestSpan -> TreePos Full (Entry a) -> TreePos Full (Entry a)Source

Open a zipper to a SrcSpan that has been added in the tree, and thus does not necessarily fall in the logical hierarchy of the tree

retrievePrevLineToks :: IsToken a => TreePos Full (Entry a) -> ReversedToks aSource

Starting from a point in the zipper, retrieve all tokens backwards until the line changes for a non-comment/non-empty token or beginning of file.

insertSrcSpan :: IsToken a => Tree (Entry a) -> ForestSpan -> Tree (Entry a)Source

Insert a ForestSpan into the forest, if it is not there already. Assumes the forest was populated with the tokens containing the ForestSpan already

removeSrcSpanSource

Arguments

:: IsToken a 
=> Tree (Entry a) 
-> ForestSpan 
-> (Tree (Entry a), Tree (Entry a))

Updated forest, removed span

Removes a ForestSpan and its tokens from the forest.

containsStart :: ForestSpan -> ForestSpan -> BoolSource

True if the start of the second param lies in the span of the first

containsMiddle :: ForestSpan -> ForestSpan -> BoolSource

True if the start of the second param lies before the first, and ends after or on the second

containsEnd :: ForestSpan -> ForestSpan -> BoolSource

True if the end of the second param lies in the span of the first

splitSubtree :: IsToken a => Tree (Entry a) -> ForestSpan -> ([Tree (Entry a)], [Tree (Entry a)], [Tree (Entry a)])Source

Split a given tree into a possibly empty part that lies before the srcspan, the part that is wholly included in the srcspan and the part the lies outside of it at the end.

insertNodeAfter :: IsToken a => Tree (Entry a) -> Tree (Entry a) -> Tree (Entry a) -> Tree (Entry a)Source

Insert a new node after the designated one in the tree

splitSubToks :: IsToken a => Tree (Entry a) -> (ForestPos, ForestPos) -> ([Tree (Entry a)], [Tree (Entry a)], [Tree (Entry a)])Source

placeToksForSpan :: IsToken a => Tree (Entry a) -> SimpSpan -> Tree (Entry a) -> Positioning -> [a] -> [a]Source

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

Some tokens are marked if they belong to identifiers which have been renamed. When the renaming takes place, no layout adjustment is done. This function adjusts the spacing for the rest of the line to match as far as possible the original spacing, except for the name change.

calcEndGap :: IsToken a => Tree (Entry a) -> ForestSpan -> SimpPosSource

For a span about to be deleted, calculate the gap between the end of the span being deleted and the start of the next one, at a token level.

getTreeSpansAsList :: IsToken a => Tree (Entry a) -> [(Int, ForestSpan)]Source

openZipperToSpanOrig :: IsToken a => ForestSpan -> TreePos Full (Entry a) -> TreePos Full (Entry a)Source

Open a zipper so that its focus has the given SrcSpan in its subtree, or the location where the SrcSpan should go, if it is not in the tree

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

Replace a single token in the token stream by a new token, without adjusting the layout. Note1: does not re-align, else other later replacements may fail. Note2: must keep original end col, to know what the inter-token gap was when re-aligning

exported for historical tests only

initTokenCache :: IsToken a => [a] -> TokenCache aSource

Deprecated: residual from tests

Initialise a TokenCache from tokens only. Does not generate a layout-aware tree due to missing AST

matchTokenPos :: IsToken a => a -> a -> aSource

Transfer the location information from the first param to the second