Safe Haskell | None |
---|
This module contains an API to manage a token stream.
This API is used internally by MonadFunctions and the other utility modules, it should probably never be used directly in a refactoring.
- initTokenCache :: [PosToken] -> TokenCache
- mkTreeFromTokens :: [PosToken] -> Tree Entry
- mkTreeFromSpanTokens :: ForestSpan -> [PosToken] -> Tree Entry
- putToksInCache :: TokenCache -> SrcSpan -> [PosToken] -> (TokenCache, SrcSpan)
- replaceTokenInCache :: TokenCache -> SrcSpan -> PosToken -> TokenCache
- removeToksFromCache :: TokenCache -> SrcSpan -> TokenCache
- getTreeFromCache :: SrcSpan -> TokenCache -> Tree Entry
- replaceTreeInCache :: SrcSpan -> Tree Entry -> TokenCache -> TokenCache
- syncAstToLatestCache :: Data t => TokenCache -> Located t -> Located t
- getTokensFor :: Bool -> Tree Entry -> SrcSpan -> (Tree Entry, [PosToken])
- getTokensForNoIntros :: Bool -> Tree Entry -> SrcSpan -> (Tree Entry, [PosToken])
- getTokensBefore :: Tree Entry -> SrcSpan -> (Tree Entry, ReversedToks)
- replaceTokenForSrcSpan :: Tree Entry -> SrcSpan -> PosToken -> Tree Entry
- updateTokensForSrcSpan :: Tree Entry -> SrcSpan -> [PosToken] -> (Tree Entry, SrcSpan, Tree Entry)
- insertSrcSpan :: Tree Entry -> ForestSpan -> Tree Entry
- removeSrcSpan :: Tree Entry -> ForestSpan -> (Tree Entry, Tree Entry)
- getSrcSpanFor :: Tree Entry -> ForestSpan -> (Tree Entry, Tree Entry)
- addNewSrcSpanAndToksAfter :: Tree Entry -> SrcSpan -> SrcSpan -> Positioning -> [PosToken] -> (Tree Entry, SrcSpan)
- addToksAfterSrcSpan :: Tree Entry -> SrcSpan -> Positioning -> [PosToken] -> (Tree Entry, SrcSpan)
- addDeclToksAfterSrcSpan :: Data t => Tree Entry -> SrcSpan -> Positioning -> [PosToken] -> Located t -> (Tree Entry, SrcSpan, Located t)
- syncAST :: Data t => Located t -> SrcSpan -> Tree Entry -> (Located t, Tree Entry)
- indentDeclToks :: Data t => Located t -> Tree Entry -> Int -> (Located t, Tree Entry)
- data Positioning
- = PlaceAdjacent
- | PlaceAbsolute !Int !Int
- | PlaceAbsCol !Int !Int !Int
- | PlaceOffset !Int !Int !Int
- | PlaceIndent !Int !Int !Int
- retrieveTokensFinal :: Tree Entry -> [PosToken]
- retrieveTokensInterim :: Tree Entry -> [PosToken]
- retrieveTokens' :: Tree Entry -> [Entry]
- treeIdFromForestSpan :: ForestSpan -> TreeId
- reAlignMarked :: [PosToken] -> [PosToken]
- posToSrcSpan :: Tree Entry -> (SimpPos, SimpPos) -> SrcSpan
- posToSrcSpanTok :: PosToken -> (SimpPos, SimpPos) -> SrcSpan
- fileNameFromTok :: PosToken -> FastString
- treeStartEnd :: Tree Entry -> ForestSpan
- spanStartEnd :: SrcSpan -> ForestSpan
- data ReversedToks = RT [PosToken]
- reverseToks :: [PosToken] -> ReversedToks
- unReverseToks :: ReversedToks -> [PosToken]
- reversedToks :: ReversedToks -> [PosToken]
- placeToksForSpan :: Tree Entry -> SrcSpan -> Tree Entry -> Positioning -> [PosToken] -> [PosToken]
- limitPrevToks :: ReversedToks -> SrcSpan -> ReversedToks
- reIndentToks :: Positioning -> [PosToken] -> [PosToken] -> [PosToken]
- reAlignOneLine :: [PosToken] -> [PosToken]
- reAlignToks :: [PosToken] -> [PosToken]
- splitForestOnSpan :: Forest Entry -> ForestSpan -> ([Tree Entry], [Tree Entry], [Tree Entry])
- spanContains :: ForestSpan -> ForestSpan -> Bool
- containsStart :: ForestSpan -> ForestSpan -> Bool
- containsMiddle :: ForestSpan -> ForestSpan -> Bool
- containsEnd :: ForestSpan -> ForestSpan -> Bool
- doSplitTree :: Tree Entry -> ForestSpan -> ([Tree Entry], [Tree Entry], [Tree Entry])
- splitSubtree :: Tree Entry -> ForestSpan -> ([Tree Entry], [Tree Entry], [Tree Entry])
- splitSubToks :: Tree Entry -> (ForestPos, ForestPos) -> ([Tree Entry], [Tree Entry], [Tree Entry])
- nonCommentSpan :: [PosToken] -> (SimpPos, SimpPos)
- invariantOk :: Tree Entry -> Bool
- invariant :: Tree Entry -> [String]
- showForest :: [Tree Entry] -> [String]
- showTree :: Tree Entry -> String
- showSrcSpan :: SrcSpan -> String
- showSrcSpanF :: SrcSpan -> String
- ghcSpanStartEnd :: SrcSpan -> ((Int, Int), (Int, Int))
- insertNodeAfter :: Tree Entry -> Tree Entry -> Tree Entry -> Tree Entry
- retrievePrevLineToks :: TreePos Full Entry -> ReversedToks
- openZipperToNode :: Tree Entry -> TreePos Full Entry -> TreePos Full Entry
- openZipperToSpan :: ForestSpan -> TreePos Full Entry -> TreePos Full Entry
- forestSpanToSimpPos :: ForestSpan -> (SimpPos, SimpPos)
- forestSpanToGhcPos :: ForestSpan -> (SimpPos, SimpPos)
- ghcLineToForestLine :: Int -> ForestLine
- forestLineToGhcLine :: ForestLine -> Int
- forestSpanToSrcSpan :: ForestSpan -> SrcSpan
- forestPosVersionSet :: ForestPos -> Bool
- forestPosVersionNotSet :: ForestPos -> Bool
- forestSpanLenChanged :: ForestSpan -> Bool
- forestSpanVersions :: ForestSpan -> (Int, Int)
- forestSpanVersionSet :: ForestSpan -> Bool
- forestSpanVersionNotSet :: ForestSpan -> Bool
- insertForestLineInSrcSpan :: ForestLine -> SrcSpan -> SrcSpan
- insertLenChangedInSrcSpan :: Bool -> Bool -> SrcSpan -> SrcSpan
- insertVersionsInSrcSpan :: Int -> Int -> SrcSpan -> SrcSpan
- srcSpanToForestSpan :: SrcSpan -> ForestSpan
- nullSpan :: ForestSpan
- nullPos :: ForestPos
- simpPosToForestSpan :: (SimpPos, SimpPos) -> ForestSpan
- srcPosToSimpPos :: (Int, Int) -> (Int, Int)
- showForestSpan :: ForestSpan -> String
- deleteGapsToks :: [Entry] -> [PosToken]
- deleteGapsToks' :: [Entry] -> [(SimpPos, String, ForestSpan, [PosToken])]
- calcEndGap :: Tree Entry -> ForestSpan -> SimpPos
- stripForestLines :: [PosToken] -> [PosToken]
- drawTreeEntry :: Tree Entry -> String
- drawTokenCache :: TokenCache -> String
- drawTokenCacheDetailed :: TokenCache -> String
- drawForestEntry :: Forest Entry -> String
- drawEntry :: Tree Entry -> [String]
Creating
initTokenCache :: [PosToken] -> TokenCacheSource
mkTreeFromTokens :: [PosToken] -> Tree EntrySource
Make a tree representing a particular set of tokens
mkTreeFromSpanTokens :: ForestSpan -> [PosToken] -> Tree EntrySource
Make a tree representing a particular set of tokens
Operations at TokenCache
level
putToksInCache :: TokenCache -> SrcSpan -> [PosToken] -> (TokenCache, SrcSpan)Source
replaceTokenInCache :: TokenCache -> SrcSpan -> PosToken -> TokenCacheSource
getTreeFromCache :: SrcSpan -> TokenCache -> Tree EntrySource
replaceTreeInCache :: SrcSpan -> Tree Entry -> TokenCache -> TokenCacheSource
syncAstToLatestCache :: Data t => TokenCache -> Located t -> Located tSource
Assuming most recent operation has stashed the old tokens, sync the given AST to the most recent stash entry
Operations at Tree
Entry
level
getTokensFor :: Bool -> Tree Entry -> SrcSpan -> (Tree Entry, [PosToken])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.
getTokensForNoIntros :: Bool -> Tree Entry -> SrcSpan -> (Tree Entry, [PosToken])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 :: Tree Entry -> SrcSpan -> (Tree Entry, ReversedToks)Source
Get the tokens preceding a given SrcSpan
replaceTokenForSrcSpan :: Tree Entry -> SrcSpan -> PosToken -> Tree EntrySource
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
updateTokensForSrcSpan :: Tree Entry -> SrcSpan -> [PosToken] -> (Tree Entry, SrcSpan, Tree Entry)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?
insertSrcSpan :: Tree Entry -> ForestSpan -> Tree EntrySource
Insert a ForestSpan into the forest, if it is not there already. Assumes the forest was populated with the tokens containing the ForestSpan already
Removes a ForestSpan and its tokens from the forest.
getSrcSpanFor :: Tree Entry -> ForestSpan -> (Tree Entry, Tree Entry)Source
Retrieve a path to the tree containing a ForestSpan from the forest, inserting it if not already present
addNewSrcSpanAndToksAfterSource
:: Tree Entry | The forest to update |
-> SrcSpan | The new span comes after this one |
-> SrcSpan | Existing span for the tokens |
-> Positioning | |
-> [PosToken] | The new tokens belonging to the new SrcSpan |
-> (Tree Entry, SrcSpan) | 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.
:: Tree Entry | TokenTree to be modified |
-> SrcSpan | Preceding location for new tokens |
-> Positioning | |
-> [PosToken] | New tokens to be added |
-> (Tree Entry, SrcSpan) | 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
:: Data t | |
=> Tree Entry | TokenTree to be modified |
-> SrcSpan | Preceding location for new tokens |
-> Positioning | |
-> [PosToken] | New tokens to be added |
-> Located t | Declaration the tokens belong to, to be synced |
-> (Tree Entry, SrcSpan, Located t) | updated TokenTree ,SrcSpan location for -> (Tree Entry, GHC.SrcSpan,t) -- ^ updated TokenTree ,SrcSpan location for the new tokens in the TokenTree, and updated AST element |
Add new tokens belonging to an AST fragment after a given SrcSpan, and re-sync the AST fragment to match the new location
:: Data t | |
=> Located t | The AST (or fragment) |
-> SrcSpan | The SrcSpan created in the Tree Entry |
-> Tree Entry | Existing token tree |
-> (Located t, Tree Entry) | Updated AST and tokens |
Synchronise a located AST fragment to use a newly created SrcSpan in the token tree. TODO: Should this indent the tokens as well?
:: Data t | |
=> Located t | The AST (or fragment) |
-> Tree Entry | Existing token tree |
-> Int | (signed) number of columns to indent/dedent |
-> (Located t, Tree Entry) | Updated AST and tokens |
indent the tree and tokens by the given offset, and sync the AST to the tree too.
data Positioning Source
How new SrcSpans should be inserted in the Token tree, relative to the prior span
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 |
Retrieving tokens
retrieveTokensFinal :: Tree Entry -> [PosToken]Source
Retrieve all the tokens at the leaves of the tree, in order. Marked tokens are re-aligned, and gaps are closed.
retrieveTokensInterim :: Tree Entry -> [PosToken]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
retrieveTokens' :: Tree Entry -> [Entry]Source
Token Tree Selection
Token marking and re-alignment
reAlignMarked :: [PosToken] -> [PosToken]Source
Utility
posToSrcSpan :: Tree Entry -> (SimpPos, SimpPos) -> SrcSpanSource
Convert a simple (start,end) position to a SrcSpan belonging to the file in the tree
posToSrcSpanTok :: PosToken -> (SimpPos, SimpPos) -> SrcSpanSource
Convert a simple (start,end) position to a SrcSpan belonging to the file in the given token
treeStartEnd :: Tree Entry -> ForestSpanSource
Get the start and end position of a Tree treeStartEnd :: Tree Entry -> (SimpPos,SimpPos) treeStartEnd (Node (Entry sspan _) _) = (getGhcLoc sspan,getGhcLocEnd sspan)
spanStartEnd :: SrcSpan -> ForestSpanSource
Get the start and end position of a SrcSpan spanStartEnd :: GHC.SrcSpan -> (SimpPos,SimpPos) spanStartEnd sspan = (getGhcLoc sspan,getGhcLocEnd sspan)
A token stream with last tokens first, and functions to manipulate it
data ReversedToks Source
Keep track of when tokens are reversed, to avoid confusion
reverseToks :: [PosToken] -> ReversedToksSource
unReverseToks :: ReversedToks -> [PosToken]Source
reversedToks :: ReversedToks -> [PosToken]Source
Internal, for testing
placeToksForSpan :: Tree Entry -> SrcSpan -> Tree Entry -> Positioning -> [PosToken] -> [PosToken]Source
reIndentToks :: Positioning -> [PosToken] -> [PosToken] -> [PosToken]Source
reAlignOneLine :: [PosToken] -> [PosToken]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.
reAlignToks :: [PosToken] -> [PosToken]Source
splitForestOnSpan :: Forest Entry -> ForestSpan -> ([Tree Entry], [Tree Entry], [Tree Entry])Source
Split a forest of trees into a (begin,middle,end) according to a ForestSpan, such that no tokens are included in begin or end belonging to the ForestSpan, and all of middle has some part of the ForestSpan
spanContains :: ForestSpan -> ForestSpan -> BoolSource
Does the first span contain the second? Takes cognisance of the various flags a ForestSpan can have. NOTE: This function relies on the Eq instance for ForestLine
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 :: Tree Entry -> ForestSpan -> ([Tree Entry], [Tree Entry], [Tree Entry])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.
splitSubToks :: Tree Entry -> (ForestPos, ForestPos) -> ([Tree Entry], [Tree Entry], [Tree Entry])Source
nonCommentSpan :: [PosToken] -> (SimpPos, SimpPos)Source
Extract the start and end position of a span, without any leading or trailing comments
invariantOk :: Tree Entry -> BoolSource
Utility function to either return True or throw an error to report the problem
invariant :: Tree Entry -> [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 nullSpan 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
showForest :: [Tree Entry] -> [String]Source
showSrcSpan :: SrcSpan -> StringSource
showSrcSpanF :: SrcSpan -> StringSource
insertNodeAfter :: Tree Entry -> Tree Entry -> Tree Entry -> Tree EntrySource
Insert a new node after the designated one in the tree
retrievePrevLineToks :: TreePos Full Entry -> ReversedToksSource
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.
openZipperToNode :: Tree Entry -> TreePos Full Entry -> TreePos Full EntrySource
Open a zipper so that its focus is the given node NOTE: the node must already be in the tree
openZipperToSpan :: ForestSpan -> TreePos Full Entry -> TreePos Full EntrySource
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
forestSpanToSimpPos :: ForestSpan -> (SimpPos, SimpPos)Source
Strip out the version markers
forestSpanToGhcPos :: ForestSpan -> (SimpPos, SimpPos)Source
Strip out the version markers
ghcLineToForestLine :: Int -> ForestLineSource
Extract an encoded ForestLine from a GHC line
forestPosVersionSet :: ForestPos -> BoolSource
Checks if the version is non-zero
forestPosVersionNotSet :: ForestPos -> BoolSource
Checks if the version is zero
forestSpanVersions :: ForestSpan -> (Int, Int)Source
Gets the version numbers
forestSpanVersionSet :: ForestSpan -> BoolSource
Checks if the version is non-zero in either position
forestSpanVersionNotSet :: ForestSpan -> BoolSource
Checks if the version is zero in both positions
insertForestLineInSrcSpan :: ForestLine -> SrcSpan -> SrcSpanSource
Replace any ForestLine flags already in a SrcSpan with the given ones
deleteGapsToks :: [Entry] -> [PosToken]Source
Process the leaf nodes of a tree to remove all deleted spans
deleteGapsToks' :: [Entry] -> [(SimpPos, String, ForestSpan, [PosToken])]Source
Process the leaf nodes of a tree to remove all deleted spans
calcEndGap :: Tree Entry -> 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.
stripForestLines :: [PosToken] -> [PosToken]Source
Based on Data.Tree
drawTreeEntry :: Tree Entry -> StringSource
Neat 2-dimensional drawing of a tree.
drawTokenCache :: TokenCache -> StringSource
Call drawTreeEntry on the entire token cache
drawTokenCacheDetailed :: TokenCache -> StringSource
Call drawTreeEntry on the entire token cache
drawForestEntry :: Forest Entry -> StringSource
Neat 2-dimensional drawing of a forest.