HaRe-0.7.2.4: the Haskell Refactorer.

Safe HaskellNone

Language.Haskell.Refact.Utils.TokenUtils

Contents

Description

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.

Synopsis

Operations at TokenCache level

putToksInCache :: IsToken a => TokenCache a -> Span -> [a] -> (TokenCache a, Span)

syncAstToLatestCache :: Data t => TokenCache PosToken -> 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

addToksAfterSrcSpan

Arguments

:: IsToken a 
=> Tree (Entry a)

TokenTree to be modified

-> Span

Preceding location for new tokens

-> Positioning 
-> [a]

New tokens to be added

-> (Tree (Entry a), Span)

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

addDeclToksAfterSrcSpanSource

Arguments

:: Data t 
=> Tree (Entry PosToken)

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 PosToken), SrcSpan, Located t)

updated TokenTree ,SrcSpan location for -> (Tree (Entry PosToken), 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

syncASTSource

Arguments

:: Data t 
=> Located t

The AST (or fragment)

-> ForestSpan

The SrcSpan created in the Tree (Entry PosToken)

-> Located t

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?

indentDeclToks

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.

data Positioning

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

Retrieving tokens

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

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

Token Tree Selection

Token marking and re-alignment

Utility

posToSrcSpan :: Tree (Entry PosToken) -> (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 a) -> ForestSpan

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

A token stream with last tokens first, and functions to manipulate it

Internal, for testing

nonCommentSpan :: IsToken a => [a] -> (SimpPos, SimpPos)

Extract the start and end position of a span, without any leading or trailing comments

forestSpanToSimpPos :: ForestSpan -> (SimpPos, SimpPos)

Strip out the version markers

forestSpanToGhcPos :: ForestSpan -> (SimpPos, SimpPos)

Strip out the version markers

ghcLineToForestLine :: Int -> ForestLine

Extract an encoded ForestLine from a GHC line

forestSpanVersions :: ForestSpan -> (Int, Int)

Gets the version numbers

forestSpanVersionSet :: ForestSpan -> Bool

Checks if the version is non-zero in either position

insertForestLineInSrcSpan :: ForestLine -> SrcSpan -> SrcSpanSource

Replace any ForestLine flags already in a SrcSpan with the given ones

deleteGapsToks :: [Entry PosToken] -> [PosToken]Source

Process the leaf nodes of a tree to remove all deleted spans

Based on Data.Tree

drawTreeEntry :: Tree (Entry a) -> String

Neat 2-dimensional drawing of a tree.

drawForestEntry :: Forest (Entry a) -> String

Neat 2-dimensional drawing of a forest.