Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- ss2pos :: SrcSpan -> Pos
- ss2posEnd :: SrcSpan -> Pos
- ss2range :: SrcSpan -> (Pos, Pos)
- undelta :: Pos -> DeltaPos -> LayoutStartCol -> Pos
- isPointSrcSpan :: AnnSpan -> Bool
- pos2delta :: Pos -> Pos -> DeltaPos
- ss2delta :: Pos -> SrcSpan -> DeltaPos
- addDP :: DeltaPos -> DeltaPos -> DeltaPos
- spanLength :: SrcSpan -> Int
- isGoodDelta :: DeltaPos -> Bool
- rs :: SrcSpan -> AnnSpan
- sr :: SrcSpan -> SrcSpan
- mkComment :: String -> SrcSpan -> Comment
- mkKWComment :: AnnKeywordId -> SrcSpan -> Comment
- dpFromString :: String -> DeltaPos
- comment2dp :: (Comment, DeltaPos) -> (KeywordId, DeltaPos)
- extractComments :: ApiAnns -> [Comment]
- srcSpanStartLine :: SrcSpan -> Int
- srcSpanEndLine :: SrcSpan -> Int
- srcSpanStartColumn :: SrcSpan -> Int
- srcSpanEndColumn :: SrcSpan -> Int
- rdrName2String :: RdrName -> String
- isSymbolRdrName :: RdrName -> Bool
- tokComment :: Located AnnotationComment -> Comment
- isListComp :: HsStmtContext name -> Bool
- isGadt :: [LConDecl name] -> Bool
- isExactName :: Data name => name -> Bool
- getAnnotationEP :: (Data a, Data (SrcSpanLess a), HasSrcSpan a) => a -> Anns -> Maybe Annotation
- annTrueEntryDelta :: Annotation -> DeltaPos
- annCommentEntryDelta :: Annotation -> DeltaPos -> DeltaPos
- annLeadingCommentEntryDelta :: Annotation -> DeltaPos
- orderByKey :: Eq o => [(o, a)] -> [o] -> [(o, a)]
- setAcs :: Set AstContext -> AstContextSet -> AstContextSet
- setAcsWithLevel :: Ord a => Set a -> Int -> ACS' a -> ACS' a
- unsetAcs :: Ord a => a -> ACS' a -> ACS' a
- inAcs :: Ord a => Set a -> ACS' a -> Bool
- pushAcs :: ACS' a -> ACS' a
- bumpAcs :: ACS' a -> ACS' a
- debug :: c -> String -> c
- debugP :: String -> c -> c
- debugM :: Monad m => String -> m ()
- warn :: c -> String -> c
- showGhc :: Outputable a => a -> String
- showAnnData :: Data a => Anns -> Int -> a -> String
- occAttributes :: OccName -> String
- showSDoc_ :: SDoc -> String
- showSDocDebug_ :: SDoc -> String
- ghead :: String -> [a] -> a
- glast :: String -> [a] -> a
- gtail :: String -> [a] -> [a]
- gfromJust :: String -> Maybe a -> a
Manipulating Positons
undelta :: Pos -> DeltaPos -> LayoutStartCol -> Pos Source #
Apply the delta to the current position, taking into account the current column offset if advancing to a new line
isPointSrcSpan :: AnnSpan -> Bool Source #
Checks whether a SrcSpan has zero length.
pos2delta :: Pos -> Pos -> DeltaPos Source #
Convert the start of the second Pos
to be an offset from the
first. The assumption is the reference starts before the second Pos
ss2delta :: Pos -> SrcSpan -> DeltaPos Source #
Create a delta from the current position to the start of the given
SrcSpan
.
addDP :: DeltaPos -> DeltaPos -> DeltaPos Source #
Add together two DeltaPos
taking into account newlines
DP (0, 1) `addDP` DP (0, 2) == DP (0, 3) DP (0, 9) `addDP` DP (1, 5) == DP (1, 5) DP (1, 4) `addDP` DP (1, 3) == DP (2, 3)
spanLength :: SrcSpan -> Int Source #
isGoodDelta :: DeltaPos -> Bool Source #
A good delta has no negative values.
Manipulating Comments
mkKWComment :: AnnKeywordId -> SrcSpan -> Comment Source #
Makes a comment which originates from a specific keyword.
dpFromString :: String -> DeltaPos Source #
Calculates the distance from the start of a string to the end of a string.
extractComments :: ApiAnns -> [Comment] Source #
GHC Functions
srcSpanStartLine :: SrcSpan -> Int Source #
srcSpanEndLine :: SrcSpan -> Int Source #
srcSpanStartColumn :: SrcSpan -> Int Source #
srcSpanEndColumn :: SrcSpan -> Int Source #
rdrName2String :: RdrName -> String Source #
isSymbolRdrName :: RdrName -> Bool Source #
isListComp :: HsStmtContext name -> Bool Source #
isExactName :: Data name => name -> Bool Source #
Manipulating Annotations
getAnnotationEP :: (Data a, Data (SrcSpanLess a), HasSrcSpan a) => a -> Anns -> Maybe Annotation Source #
annTrueEntryDelta :: Annotation -> DeltaPos Source #
The "true entry" is the distance from the last concrete element to the start of the current element.
annCommentEntryDelta :: Annotation -> DeltaPos -> DeltaPos Source #
Take an annotation and a required "true entry" and calculate an equivalent one relative to the last comment in the annPriorComments.
annLeadingCommentEntryDelta :: Annotation -> DeltaPos Source #
Return the DP of the first item that generates output, either a comment or the entry DP
General Utility
orderByKey :: Eq o => [(o, a)] -> [o] -> [(o, a)] Source #
Given a list of items and a list of keys, returns a list of items ordered by their position in the list of keys.
AST Context management
setAcs :: Set AstContext -> AstContextSet -> AstContextSet Source #
Put the provided context elements into the existing set with fresh level counts
setAcsWithLevel :: Ord a => Set a -> Int -> ACS' a -> ACS' a Source #
Put the provided context elements into the existing set with given level counts setAcsWithLevel :: Set.Set AstContext -> Int -> AstContextSet -> AstContextSet setAcsWithLevel ctxt level (ACS a) = ACS a' where upd s (k,v) = Map.insert k v s a' = foldl' upd a $ zip (Set.toList ctxt) (repeat level)
unsetAcs :: Ord a => a -> ACS' a -> ACS' a Source #
Remove the provided context element from the existing set unsetAcs :: AstContext -> AstContextSet -> AstContextSet
inAcs :: Ord a => Set a -> ACS' a -> Bool Source #
Are any of the contexts currently active? inAcs :: Set.Set AstContext -> AstContextSet -> Bool
pushAcs :: ACS' a -> ACS' a Source #
propagate the ACS down a level, dropping all values which hit zero pushAcs :: AstContextSet -> AstContextSet
bumpAcs :: ACS' a -> ACS' a Source #
Sometimes we have to pass the context down unchanged. Bump each count up by
one so that it is unchanged after a pushAcs
call.
bumpAcs :: AstContextSet -> AstContextSet
For tests
debug :: c -> String -> c Source #
Provide a version of trace that comes at the end of the line, so it can easily be commented out when debugging different things.
showGhc :: Outputable a => a -> String Source #
Show a GHC.Outputable structure
showAnnData :: Data a => Anns -> Int -> a -> String Source #
Show a GHC AST with interleaved Annotation information.
occAttributes :: OccName -> String Source #
showSDocDebug_ :: SDoc -> String Source #