Safe Haskell | None |
---|
- fetchToksFinal :: RefactGhc [PosToken]
- fetchLinesFinal :: RefactGhc [Line]
- fetchOrigToks :: RefactGhc [PosToken]
- fetchToks :: RefactGhc [PosToken]
- getTypecheckedModule :: RefactGhc TypecheckedModule
- getRefactStreamModified :: RefactGhc Bool
- getRefactInscopes :: RefactGhc InScopes
- getRefactRenamed :: RefactGhc RenamedSource
- putRefactRenamed :: RenamedSource -> RefactGhc ()
- getRefactParsed :: RefactGhc ParsedSource
- putParsedModule :: TypecheckedModule -> [PosToken] -> RefactGhc ()
- clearParsedModule :: RefactGhc ()
- getRefactFileName :: RefactGhc (Maybe FilePath)
- replaceToken :: SrcSpan -> PosToken -> RefactGhc ()
- putToksForSpan :: SrcSpan -> [PosToken] -> RefactGhc SrcSpan
- getToksForSpan :: SrcSpan -> RefactGhc [PosToken]
- getToksForSpanNoInv :: SrcSpan -> RefactGhc [PosToken]
- getToksForSpanWithIntros :: SrcSpan -> RefactGhc [PosToken]
- getToksBeforeSpan :: SrcSpan -> RefactGhc ReversedToks
- putToksForPos :: (SimpPos, SimpPos) -> [PosToken] -> RefactGhc SrcSpan
- putToksAfterSpan :: SrcSpan -> Positioning -> [PosToken] -> RefactGhc SrcSpan
- putToksAfterPos :: (SimpPos, SimpPos) -> Positioning -> [PosToken] -> RefactGhc SrcSpan
- putDeclToksAfterSpan :: Data t => SrcSpan -> Located t -> Positioning -> [PosToken] -> RefactGhc (Located t)
- removeToksForSpan :: SrcSpan -> RefactGhc ()
- removeToksForPos :: (SimpPos, SimpPos) -> RefactGhc ()
- syncDeclToLatestStash :: Data t => Located t -> RefactGhc (Located t)
- indentDeclAndToks :: Data t => Located t -> Int -> RefactGhc (Located t)
- drawTokenTree :: String -> RefactGhc ()
- drawTokenTreeDetailed :: String -> RefactGhc ()
- getTokenTree :: RefactGhc (Tree Entry)
- showLinesDebug :: String -> RefactGhc ()
- getRefactDone :: RefactGhc Bool
- setRefactDone :: RefactGhc ()
- clearRefactDone :: RefactGhc ()
- setStateStorage :: StateStorage -> RefactGhc ()
- getStateStorage :: RefactGhc StateStorage
- updateToks :: Data t => Located t -> Located t -> (Located t -> [Char]) -> Bool -> RefactGhc ()
- updateToksWithPos :: Data t => (SimpPos, SimpPos) -> t -> (t -> [Char]) -> Bool -> RefactGhc ()
- initRefactModule :: TypecheckedModule -> [PosToken] -> Maybe RefactModule
Conveniences for state access
fetchToksFinal :: RefactGhc [PosToken]Source
fetch the final tokens
fetchLinesFinal :: RefactGhc [Line]Source
fetch the final tokens in Ppr format
fetchOrigToks :: RefactGhc [PosToken]Source
fetch the pristine token stream
putRefactRenamed :: RenamedSource -> RefactGhc ()Source
putParsedModule :: TypecheckedModule -> [PosToken] -> RefactGhc ()Source
TokenUtils API
replaceToken :: SrcSpan -> PosToken -> RefactGhc ()Source
Replace a token occurring in a given GHC.SrcSpan
putToksForSpan :: SrcSpan -> [PosToken] -> RefactGhc SrcSpanSource
Replace the tokens for a given GHC.SrcSpan, return new GHC.SrcSpan delimiting new tokens
getToksForSpan :: SrcSpan -> RefactGhc [PosToken]Source
Get the current tokens for a given GHC.SrcSpan.
getToksForSpanNoInv :: SrcSpan -> RefactGhc [PosToken]Source
Get the current tokens for a given GHC.SrcSpan, without checking the invariant. TODO: this should not be necessary
getToksForSpanWithIntros :: SrcSpan -> RefactGhc [PosToken]Source
Get the current tokens for a given GHC.SrcSpan, leaving out any leading 'then', 'else', 'of', 'do' or 'in' tokens
getToksBeforeSpan :: SrcSpan -> RefactGhc ReversedToksSource
Get the current tokens preceding a given GHC.SrcSpan.
putToksForPos :: (SimpPos, SimpPos) -> [PosToken] -> RefactGhc SrcSpanSource
Replace the tokens for a given GHC.SrcSpan, return GHC.SrcSpan they are placed in
putToksAfterSpan :: SrcSpan -> Positioning -> [PosToken] -> RefactGhc SrcSpanSource
Add tokens after a designated GHC.SrcSpan
putToksAfterPos :: (SimpPos, SimpPos) -> Positioning -> [PosToken] -> RefactGhc SrcSpanSource
Add tokens after a designated position
putDeclToksAfterSpan :: Data t => SrcSpan -> Located t -> Positioning -> [PosToken] -> RefactGhc (Located t)Source
Add tokens after a designated GHC.SrcSpan, and update the AST fragment to reflect it
removeToksForSpan :: SrcSpan -> RefactGhc ()Source
Remove a GHC.SrcSpan and its associated tokens
removeToksForPos :: (SimpPos, SimpPos) -> RefactGhc ()Source
Remove a GHC.SrcSpan and its associated tokens
indentDeclAndToks :: Data t => Located t -> Int -> RefactGhc (Located t)Source
Indent an AST fragment and its associated tokens by a set amount
LayoutUtils API
For debugging
drawTokenTree :: String -> RefactGhc ()Source
Print the Token Tree for debug purposes
drawTokenTreeDetailed :: String -> RefactGhc ()Source
Print detailed Token Tree for debug purposes
getTokenTree :: RefactGhc (Tree Entry)Source
Get the Token Tree for debug purposes
showLinesDebug :: String -> RefactGhc ()Source
State flags for managing generic traversals
setRefactDone :: RefactGhc ()Source
setStateStorage :: StateStorage -> RefactGhc ()Source