Safe Haskell | None |
---|
- type SimpPos = (Int, Int)
- unmodified :: Bool
- modified :: Bool
- simpPos0 :: (Int, Int)
- nullSrcSpan :: SrcSpan
- showToks :: [PosToken] -> String
- whiteSpaceTokens :: (Int, Int) -> Int -> [PosToken]
- realSrcLocFromTok :: PosToken -> RealSrcLoc
- isWhite :: PosToken -> Bool
- notWhite :: PosToken -> Bool
- isWhiteSpace :: PosToken -> Bool
- isWhiteSpaceOrIgnored :: PosToken -> Bool
- isIgnored :: PosToken -> Bool
- isIgnoredNonComment :: PosToken -> Bool
- isComment :: PosToken -> Bool
- isMultiLineComment :: PosToken -> Bool
- isOpenSquareBracket :: PosToken -> Bool
- isCloseSquareBracket :: PosToken -> Bool
- isIn :: PosToken -> Bool
- isComma :: PosToken -> Bool
- isBar :: PosToken -> Bool
- endsWithNewLn :: PosToken -> Bool
- startsWithNewLn :: PosToken -> Bool
- hasNewLn :: PosToken -> Bool
- compressPreNewLns :: [PosToken] -> [PosToken]
- compressEndNewLns :: [PosToken] -> [PosToken]
- lengthOfLastLine :: [PosToken] -> Int
- getToks :: (SimpPos, SimpPos) -> [PosToken] -> [PosToken]
- replaceTokNoReAlign :: [PosToken] -> SimpPos -> PosToken -> [PosToken]
- deleteToks :: [PosToken] -> SimpPos -> SimpPos -> [PosToken]
- doRmWhites :: Int -> [PosToken] -> [PosToken]
- srcLocs :: Data t => t -> [SimpPos]
- getSrcSpan :: Data t => t -> Maybe SrcSpan
- getAllSrcLocs :: Data t => t -> [(SimpPos, SimpPos)]
- getBiggestStartEndLoc :: Data t => t -> (SimpPos, SimpPos)
- extendForwards :: [PosToken] -> (SimpPos, SimpPos) -> (PosToken -> Bool) -> (SimpPos, SimpPos)
- extendBackwards :: [PosToken] -> (SimpPos, SimpPos) -> (PosToken -> Bool) -> (SimpPos, SimpPos)
- startEndLocIncFowComment :: Data t => [PosToken] -> t -> (SimpPos, SimpPos)
- startEndLocIncComments :: Data t => [PosToken] -> t -> (SimpPos, SimpPos)
- startEndLocIncComments' :: [PosToken] -> (SimpPos, SimpPos) -> (SimpPos, SimpPos)
- tokenise :: RealSrcLoc -> Int -> Bool -> String -> IO [PosToken]
- basicTokenise :: String -> IO [PosToken]
- lexStringToRichTokens :: RealSrcLoc -> String -> IO [PosToken]
- prettyprint :: Outputable a => a -> String
- prettyprintPatList :: (t -> String) -> Bool -> [t] -> String
- groupTokensByLine :: [PosToken] -> [[PosToken]]
- toksOnSameLine :: PosToken -> PosToken -> Bool
- addLocInfo :: (LHsBind Name, [PosToken]) -> RefactGhc (LHsBind Name, [PosToken])
- getLineOffset :: [PosToken] -> SimpPos -> Int
- tokenCol :: PosToken -> Int
- tokenColEnd :: PosToken -> Int
- tokenRow :: PosToken -> Int
- tokenPos :: (GenLocated SrcSpan t1, t) -> SimpPos
- tokenPosEnd :: (GenLocated SrcSpan t1, t) -> SimpPos
- tokenSrcSpan :: (Located t1, t) -> SrcSpan
- tokenCon :: PosToken -> String
- increaseSrcSpan :: SimpPos -> PosToken -> PosToken
- getGhcLoc :: SrcSpan -> (Int, Int)
- getGhcLocEnd :: SrcSpan -> (Int, Int)
- getLocatedStart :: GenLocated SrcSpan t -> (Int, Int)
- getLocatedEnd :: GenLocated SrcSpan t -> (Int, Int)
- getStartEndLoc :: Data t => t -> (SimpPos, SimpPos)
- startEndLocGhc :: Located b -> (SimpPos, SimpPos)
- realSrcLocEndTok :: PosToken -> RealSrcLoc
- fileNameFromTok :: PosToken -> FastString
- splitToks :: (SimpPos, SimpPos) -> [PosToken] -> ([PosToken], [PosToken], [PosToken])
- emptyList :: [t] -> Bool
- nonEmptyList :: [t] -> Bool
- divideComments :: Int -> Int -> [PosToken] -> ([PosToken], [PosToken])
- notWhiteSpace :: PosToken -> Bool
- isDoubleColon :: PosToken -> Bool
- isEmpty :: PosToken -> Bool
- isWhereOrLet :: PosToken -> Bool
- isWhere :: PosToken -> Bool
- isLet :: PosToken -> Bool
- isElse :: PosToken -> Bool
- isThen :: PosToken -> Bool
- isOf :: PosToken -> Bool
- isDo :: PosToken -> Bool
- getIndentOffset :: [PosToken] -> SimpPos -> Int
- splitOnNewLn :: [PosToken] -> ([PosToken], [PosToken])
- tokenLen :: PosToken -> Int
- newLnToken :: PosToken -> PosToken
- newLinesToken :: Int -> PosToken -> PosToken
- monotonicLineToks :: [PosToken] -> [PosToken]
- reSequenceToks :: [PosToken] -> [PosToken]
- mkToken :: Token -> SimpPos -> String -> PosToken
- mkZeroToken :: PosToken
- markToken :: PosToken -> PosToken
- isMarked :: PosToken -> Bool
- addOffsetToToks :: SimpPos -> [PosToken] -> [PosToken]
- matchTokenPos :: PosToken -> PosToken -> PosToken
Documentation
isWhiteSpace :: PosToken -> BoolSource
isIgnoredNonComment :: PosToken -> BoolSource
Tokens that are ignored when determining the first non-comment token in a span
endsWithNewLn :: PosToken -> BoolSource
Returns True if the token ends with '\n' ++AZ++: is this meaningful?
startsWithNewLn :: PosToken -> BoolSource
Returns True if the token starts with `\n`. ++AZ++: is this meaningful?
compressPreNewLns :: [PosToken] -> [PosToken]Source
Remove the extra preceding empty lines.
compressEndNewLns :: [PosToken] -> [PosToken]Source
Remove the following extra empty lines.
lengthOfLastLine :: [PosToken] -> IntSource
Given a token stream covering multi-lines, calculate the length of the last line AZ: should be the last token start col, plus length of token.
getToks :: (SimpPos, SimpPos) -> [PosToken] -> [PosToken]Source
get a token stream specified by the start and end position.
replaceTokNoReAlign :: [PosToken] -> SimpPos -> PosToken -> [PosToken]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
deleteToks :: [PosToken] -> SimpPos -> SimpPos -> [PosToken]Source
Delete a sequence of tokens specified by the start position and end position from the token stream, then adjust the remaining token stream to preserve layout
doRmWhites :: Int -> [PosToken] -> [PosToken]Source
remove at most n white space tokens from the beginning of ts
srcLocs :: Data t => t -> [SimpPos]Source
get all the source locations (use locations) in an AST phrase t according the the occurrence order of identifiers.
getSrcSpan :: Data t => t -> Maybe SrcSpanSource
Get the first SrcSpan found, in top down traversal
getAllSrcLocs :: Data t => t -> [(SimpPos, SimpPos)]Source
Get all the source locations in a given syntax fragment
getBiggestStartEndLoc :: Data t => t -> (SimpPos, SimpPos)Source
extendForwards :: [PosToken] -> (SimpPos, SimpPos) -> (PosToken -> Bool) -> (SimpPos, SimpPos)Source
Extend the given position forwards to the end of the file while the supplied condition holds
extendBackwards :: [PosToken] -> (SimpPos, SimpPos) -> (PosToken -> Bool) -> (SimpPos, SimpPos)Source
Extend the given position backwards to the front of the file while the supplied condition holds
startEndLocIncFowComment :: Data t => [PosToken] -> t -> (SimpPos, SimpPos)Source
Get the start&end location of syntax phrase t, then extend the end location to cover the comment/white spaces or new line which starts in the same line as the end location TODO: deprecate this in favour of startEndLocIncComments
startEndLocIncComments :: Data t => [PosToken] -> t -> (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.
In this routine, 'then','else','do' and 'in' are treated as comments.
tokenise :: RealSrcLoc -> Int -> Bool -> String -> IO [PosToken]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++
basicTokenise :: String -> IO [PosToken]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
lexStringToRichTokens :: RealSrcLoc -> String -> IO [PosToken]Source
prettyprint :: Outputable a => a -> StringSource
prettyprintPatList :: (t -> String) -> Bool -> [t] -> StringSource
groupTokensByLine :: [PosToken] -> [[PosToken]]Source
toksOnSameLine :: PosToken -> PosToken -> BoolSource
getLineOffset :: [PosToken] -> SimpPos -> IntSource
Get the start of the line before the pos,
tokenColEnd :: PosToken -> IntSource
tokenPos :: (GenLocated SrcSpan t1, t) -> SimpPosSource
tokenPosEnd :: (GenLocated SrcSpan t1, t) -> SimpPosSource
tokenSrcSpan :: (Located t1, t) -> SrcSpanSource
increaseSrcSpan :: SimpPos -> PosToken -> PosTokenSource
getGhcLocEnd :: SrcSpan -> (Int, Int)Source
getLocatedStart :: GenLocated SrcSpan t -> (Int, Int)Source
getLocatedEnd :: GenLocated SrcSpan t -> (Int, Int)Source
getStartEndLoc :: Data t => t -> (SimpPos, SimpPos)Source
startEndLocGhc :: Located b -> (SimpPos, SimpPos)Source
splitToks :: (SimpPos, SimpPos) -> [PosToken] -> ([PosToken], [PosToken], [PosToken])Source
Split the token stream into three parts: the tokens before the startPos, the tokens between startPos and endPos, and the tokens after endPos. Note: The startPos and endPos refer to the startPos of a token only. So a single token will have the same startPos and endPos NO^^^^
nonEmptyList :: [t] -> BoolSource
divideComments :: Int -> Int -> [PosToken] -> ([PosToken], [PosToken])Source
Split a set of comment tokens into the ones that belong with the startLine and those that belong with the endLine
notWhiteSpace :: PosToken -> BoolSource
isDoubleColon :: PosToken -> BoolSource
isWhereOrLet :: PosToken -> BoolSource
getIndentOffset :: [PosToken] -> SimpPos -> IntSource
Get the indent of the line before, taking into account in-line 'where', 'let', 'in' and 'do' tokens
splitOnNewLn :: [PosToken] -> ([PosToken], [PosToken])Source
newLnToken :: PosToken -> PosTokenSource
newLinesToken :: Int -> PosToken -> PosTokenSource
monotonicLineToks :: [PosToken] -> [PosToken]Source
sort out line numbering so that they are always monotonically increasing.
reSequenceToks :: [PosToken] -> [PosToken]Source
Adjust token stream to cater for changes in token length due to token renaming
mkToken :: Token -> SimpPos -> String -> PosTokenSource
Compose a new token using the given arguments.
markToken :: PosToken -> PosTokenSource
Mark a token so that it can be use to trigger layout checking later when the toks are retrieved
addOffsetToToks :: SimpPos -> [PosToken] -> [PosToken]Source
Add a constant line and column offset to a span of tokens
matchTokenPos :: PosToken -> PosToken -> PosTokenSource
Transfer the location information from the first param to the second