Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- debugEnabledFlag :: Bool
- debugPEnabledFlag :: Bool
- debug :: c -> String -> c
- debugP :: String -> c -> c
- debugM :: Monad m => String -> m ()
- warn :: c -> String -> c
- isGoodDelta :: DeltaPos -> Bool
- ss2delta :: Pos -> RealSrcSpan -> DeltaPos
- ss2deltaEnd :: RealSrcSpan -> RealSrcSpan -> DeltaPos
- ss2deltaStart :: RealSrcSpan -> RealSrcSpan -> DeltaPos
- pos2delta :: Pos -> Pos -> DeltaPos
- undelta :: Pos -> DeltaPos -> LayoutStartCol -> Pos
- undeltaSpan :: RealSrcSpan -> AnnKeywordId -> DeltaPos -> AddEpAnn
- adjustDeltaForOffset :: LayoutStartCol -> DeltaPos -> DeltaPos
- ss2pos :: RealSrcSpan -> Pos
- ss2posEnd :: RealSrcSpan -> Pos
- ss2range :: SrcSpan -> (Pos, Pos)
- rs2range :: RealSrcSpan -> (Pos, Pos)
- rs :: SrcSpan -> RealSrcSpan
- range2rs :: (Pos, Pos) -> RealSrcSpan
- badRealSrcSpan :: RealSrcSpan
- spanLength :: RealSrcSpan -> Int
- isPointSrcSpan :: RealSrcSpan -> Bool
- orderByKey :: [(RealSrcSpan, a)] -> [RealSrcSpan] -> [(RealSrcSpan, a)]
- isGadt :: [LConDecl (GhcPass p)] -> Bool
- insertCppComments :: ParsedSource -> [LEpaComment] -> ParsedSource
- ghcCommentText :: LEpaComment -> String
- tokComment :: LEpaComment -> Comment
- mkEpaComments :: [Comment] -> [Comment] -> EpAnnComments
- comment2LEpaComment :: Comment -> LEpaComment
- mkLEpaComment :: String -> Anchor -> RealSrcSpan -> LEpaComment
- mkComment :: String -> Anchor -> RealSrcSpan -> Comment
- normaliseCommentText :: String -> String
- cmpComments :: Comment -> Comment -> Ordering
- sortComments :: [Comment] -> [Comment]
- sortEpaComments :: [LEpaComment] -> [LEpaComment]
- mkKWComment :: AnnKeywordId -> EpaLocation -> Comment
- isKWComment :: Comment -> Bool
- noKWComments :: [Comment] -> [Comment]
- sortAnchorLocated :: [GenLocated Anchor a] -> [GenLocated Anchor a]
- dpFromString :: String -> DeltaPos
- rdrName2String :: RdrName -> String
- name2String :: Name -> String
- locatedAnAnchor :: LocatedAn a t -> RealSrcSpan
- setAnchorAn :: Default an => LocatedAn an a -> Anchor -> EpAnnComments -> LocatedAn an a
- setAnchorEpa :: Default an => EpAnn an -> Anchor -> EpAnnComments -> EpAnn an
- setAnchorEpaL :: EpAnn AnnList -> Anchor -> EpAnnComments -> EpAnn AnnList
- setAnchorHsModule :: HsModule -> Anchor -> EpAnnComments -> HsModule
- moveAnchor :: Monoid b => SrcAnn a -> SrcAnn b
- trailingAnnToAddEpAnn :: TrailingAnn -> AddEpAnn
- trailingAnnLoc :: TrailingAnn -> EpaLocation
- setTrailingAnnLoc :: TrailingAnn -> EpaLocation -> TrailingAnn
- addEpAnnLoc :: AddEpAnn -> EpaLocation
- anchorToEpaLocation :: Anchor -> EpaLocation
- hackSrcSpanToAnchor :: SrcSpan -> Anchor
- hackAnchorToSrcSpan :: Anchor -> SrcSpan
Documentation
debugEnabledFlag :: Bool Source #
Global switch to enable debug tracing in ghc-exactprint Delta / Print
debugPEnabledFlag :: Bool Source #
Global switch to enable debug tracing in ghc-exactprint Pretty
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.
isGoodDelta :: DeltaPos -> Bool Source #
A good delta has no negative values.
ss2delta :: Pos -> RealSrcSpan -> DeltaPos Source #
Create a delta from the current position to the start of the given
RealSrcSpan
.
ss2deltaEnd :: RealSrcSpan -> RealSrcSpan -> DeltaPos Source #
create a delta from the end of a current span. The +1 is because the stored position ends up one past the span, this is prior to that adjustment
ss2deltaStart :: RealSrcSpan -> RealSrcSpan -> DeltaPos Source #
create a delta from the start of a current span. The +1 is because the stored position ends up one past the span, this is prior to that adjustment
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
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
undeltaSpan :: RealSrcSpan -> AnnKeywordId -> DeltaPos -> AddEpAnn Source #
ss2pos :: RealSrcSpan -> Pos Source #
ss2posEnd :: RealSrcSpan -> Pos Source #
rs :: SrcSpan -> RealSrcSpan Source #
spanLength :: RealSrcSpan -> Int Source #
isPointSrcSpan :: RealSrcSpan -> Bool Source #
Checks whether a SrcSpan has zero length.
orderByKey :: [(RealSrcSpan, a)] -> [RealSrcSpan] -> [(RealSrcSpan, 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.
insertCppComments :: ParsedSource -> [LEpaComment] -> ParsedSource Source #
ghcCommentText :: LEpaComment -> String Source #
tokComment :: LEpaComment -> Comment Source #
mkEpaComments :: [Comment] -> [Comment] -> EpAnnComments Source #
mkLEpaComment :: String -> Anchor -> RealSrcSpan -> LEpaComment Source #
normaliseCommentText :: String -> String Source #
cmpComments :: Comment -> Comment -> Ordering Source #
Must compare without span filenames, for CPP injected comments with fake filename
sortComments :: [Comment] -> [Comment] Source #
Sort, comparing without span filenames, for CPP injected comments with fake filename
sortEpaComments :: [LEpaComment] -> [LEpaComment] Source #
Sort, comparing without span filenames, for CPP injected comments with fake filename
mkKWComment :: AnnKeywordId -> EpaLocation -> Comment Source #
Makes a comment which originates from a specific keyword.
isKWComment :: Comment -> Bool Source #
Detects a comment which originates from a specific keyword.
noKWComments :: [Comment] -> [Comment] Source #
sortAnchorLocated :: [GenLocated Anchor a] -> [GenLocated Anchor a] Source #
dpFromString :: String -> DeltaPos Source #
Calculates the distance from the start of a string to the end of a string.
rdrName2String :: RdrName -> String Source #
name2String :: Name -> String Source #
locatedAnAnchor :: LocatedAn a t -> RealSrcSpan Source #
setAnchorAn :: Default an => LocatedAn an a -> Anchor -> EpAnnComments -> LocatedAn an a Source #
setAnchorEpa :: Default an => EpAnn an -> Anchor -> EpAnnComments -> EpAnn an Source #
setAnchorEpaL :: EpAnn AnnList -> Anchor -> EpAnnComments -> EpAnn AnnList Source #
setAnchorHsModule :: HsModule -> Anchor -> EpAnnComments -> HsModule Source #
moveAnchor :: Monoid b => SrcAnn a -> SrcAnn b Source #
Version of l2l that preserves the anchor, immportant if it has an updated AnchorOperation
addEpAnnLoc :: AddEpAnn -> EpaLocation Source #
hackSrcSpanToAnchor :: SrcSpan -> Anchor Source #
hackAnchorToSrcSpan :: Anchor -> SrcSpan Source #