Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- debugEnabledFlag :: Bool
- debug :: c -> String -> c
- debugM :: Monad m => String -> m ()
- warn :: c -> String -> c
- captureOrderBinds :: [LHsDecl GhcPs] -> AnnSortKey BindTag
- notDocDecl :: LHsDecl GhcPs -> Bool
- notIEDoc :: LIE GhcPs -> Bool
- isGoodDelta :: DeltaPos -> Bool
- ss2delta :: Pos -> RealSrcSpan -> DeltaPos
- ss2deltaEnd :: RealSrcSpan -> RealSrcSpan -> DeltaPos
- ss2deltaStart :: RealSrcSpan -> RealSrcSpan -> DeltaPos
- pos2delta :: Pos -> Pos -> DeltaPos
- undelta :: Pos -> DeltaPos -> LayoutStartCol -> Pos
- 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
- eloc2str :: EpaLocation -> String
- isPointSrcSpan :: RealSrcSpan -> Bool
- commentOrigDelta :: LEpaComment -> LEpaComment
- origDelta :: RealSrcSpan -> RealSrcSpan -> DeltaPos
- needsWhere :: forall (p :: Pass). DataDefnCons (LConDecl (GhcPass p)) -> Bool
- insertCppComments :: ParsedSource -> [LEpaComment] -> ParsedSource
- workInComments :: EpAnnComments -> [LEpaComment] -> EpAnnComments
- insertTopLevelCppComments :: HsModule GhcPs -> [LEpaComment] -> (HsModule GhcPs, [LEpaComment])
- annListBracketsLocs :: AnnListBrackets -> (EpaLocation, EpaLocation)
- data SplitWhere
- splitOnWhere :: SplitWhere -> EpToken "where" -> [LEpaComment] -> ([LEpaComment], [LEpaComment])
- balanceFirstLocatedAComments :: [LocatedA a] -> ([LocatedA a], [LEpaComment])
- priorCommentsDeltas' :: RealSrcSpan -> [LEpaComment] -> [(Int, LEpaComment)]
- allocatePriorComments :: Pos -> [LEpaComment] -> ([LEpaComment], [LEpaComment])
- insertRemainingCppComments :: ParsedSource -> [LEpaComment] -> ParsedSource
- ghcCommentText :: LEpaComment -> String
- tokComment :: LEpaComment -> [Comment]
- hsDocStringComments :: EpaLocation -> RealSrcSpan -> HsDocString -> [Comment]
- dedentDocChunk :: LHsDocStringChunk -> LHsDocStringChunk
- dedentDocChunkBy :: Int -> LHsDocStringChunk -> LHsDocStringChunk
- epaCommentsBalanced :: [LEpaComment] -> [LEpaComment] -> EpAnnComments
- mkEpaComments :: [Comment] -> [Comment] -> EpAnnComments
- comment2LEpaComment :: Comment -> LEpaComment
- mkLEpaComment :: String -> NoCommentsLocation -> RealSrcSpan -> LEpaComment
- mkComment :: String -> NoCommentsLocation -> RealSrcSpan -> Comment
- normaliseCommentText :: String -> String
- cmpComments :: Comment -> Comment -> Ordering
- sortComments :: [Comment] -> [Comment]
- sortEpaComments :: [LEpaComment] -> [LEpaComment]
- mkKWComment :: String -> NoCommentsLocation -> Comment
- sortAnchorLocated :: [GenLocated EpaLocation a] -> [GenLocated EpaLocation a]
- dpFromString :: String -> DeltaPos
- isSymbolRdrName :: RdrName -> Bool
- rdrName2String :: RdrName -> String
- name2String :: Name -> String
- type DeclsByTag a = Map DeclTag [(RealSrcSpan, a)]
- orderedDecls :: AnnSortKey DeclTag -> DeclsByTag a -> [(RealSrcSpan, a)]
- hsDeclsClassDecl :: TyClDecl GhcPs -> [LHsDecl GhcPs]
- replaceDeclsClassDecl :: TyClDecl GhcPs -> [LHsDecl GhcPs] -> TyClDecl GhcPs
- partitionWithSortKey :: [LHsDecl GhcPs] -> ([DeclTag], LHsBinds GhcPs, [LSig GhcPs], [LFamilyDecl GhcPs], [LTyFamInstDecl GhcPs], [LDataFamInstDecl GhcPs], [LDocDecl GhcPs])
- orderedDeclsBinds :: AnnSortKey BindTag -> [LHsDecl GhcPs] -> [LHsDecl GhcPs] -> [LHsDecl GhcPs]
- hsDeclsLocalBinds :: HsLocalBinds GhcPs -> [LHsDecl GhcPs]
- hsDeclsValBinds :: HsValBindsLR GhcPs GhcPs -> [LHsDecl GhcPs]
- decl2Bind :: LHsDecl GhcPs -> [LHsBind GhcPs]
- decl2Sig :: LHsDecl GhcPs -> [LSig GhcPs]
- wrapSig :: LSig GhcPs -> LHsDecl GhcPs
- wrapDecl :: LHsBind GhcPs -> LHsDecl GhcPs
- showAst :: Data a => a -> String
Documentation
debugEnabledFlag :: Bool Source #
Global switch to enable debug tracing in ghc-exactprint Delta / Print
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.
captureOrderBinds :: [LHsDecl GhcPs] -> AnnSortKey BindTag Source #
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
ss2pos :: RealSrcSpan -> Pos Source #
ss2posEnd :: RealSrcSpan -> Pos Source #
rs :: SrcSpan -> RealSrcSpan Source #
spanLength :: RealSrcSpan -> Int Source #
eloc2str :: EpaLocation -> String Source #
Useful for debug dumps
isPointSrcSpan :: RealSrcSpan -> Bool Source #
Checks whether a SrcSpan has zero length.
commentOrigDelta :: LEpaComment -> LEpaComment Source #
A GHC comment includes the span of the preceding token. Take an
original comment, and convert the 'Anchor to have a have a
MovedAnchor
operation based on the original location, only if it
does not already have one.
origDelta :: RealSrcSpan -> RealSrcSpan -> DeltaPos Source #
needsWhere :: forall (p :: Pass). DataDefnCons (LConDecl (GhcPass p)) -> Bool Source #
insertCppComments :: ParsedSource -> [LEpaComment] -> ParsedSource Source #
Insert the comments at the appropriate places in the AST
workInComments :: EpAnnComments -> [LEpaComment] -> EpAnnComments Source #
insertTopLevelCppComments :: HsModule GhcPs -> [LEpaComment] -> (HsModule GhcPs, [LEpaComment]) Source #
data SplitWhere Source #
splitOnWhere :: SplitWhere -> EpToken "where" -> [LEpaComment] -> ([LEpaComment], [LEpaComment]) Source #
balanceFirstLocatedAComments :: [LocatedA a] -> ([LocatedA a], [LEpaComment]) Source #
priorCommentsDeltas' :: RealSrcSpan -> [LEpaComment] -> [(Int, LEpaComment)] Source #
allocatePriorComments :: Pos -> [LEpaComment] -> ([LEpaComment], [LEpaComment]) Source #
ghcCommentText :: LEpaComment -> String Source #
tokComment :: LEpaComment -> [Comment] Source #
hsDocStringComments :: EpaLocation -> RealSrcSpan -> HsDocString -> [Comment] Source #
epaCommentsBalanced :: [LEpaComment] -> [LEpaComment] -> EpAnnComments Source #
mkEpaComments :: [Comment] -> [Comment] -> EpAnnComments Source #
mkLEpaComment :: String -> NoCommentsLocation -> RealSrcSpan -> LEpaComment Source #
mkComment :: String -> NoCommentsLocation -> RealSrcSpan -> Comment 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 :: String -> NoCommentsLocation -> Comment Source #
Makes a comment which originates from a specific keyword.
sortAnchorLocated :: [GenLocated EpaLocation a] -> [GenLocated EpaLocation a] Source #
dpFromString :: String -> DeltaPos Source #
Calculates the distance from the start of a string to the end of a string.
isSymbolRdrName :: RdrName -> Bool Source #
rdrName2String :: RdrName -> String Source #
name2String :: Name -> String Source #
type DeclsByTag a = Map DeclTag [(RealSrcSpan, a)] Source #
orderedDecls :: AnnSortKey DeclTag -> DeclsByTag a -> [(RealSrcSpan, a)] Source #
partitionWithSortKey :: [LHsDecl GhcPs] -> ([DeclTag], LHsBinds GhcPs, [LSig GhcPs], [LFamilyDecl GhcPs], [LTyFamInstDecl GhcPs], [LDataFamInstDecl GhcPs], [LDocDecl GhcPs]) Source #
orderedDeclsBinds :: AnnSortKey BindTag -> [LHsDecl GhcPs] -> [LHsDecl GhcPs] -> [LHsDecl GhcPs] Source #
hsDeclsLocalBinds :: HsLocalBinds GhcPs -> [LHsDecl GhcPs] Source #
hsDeclsValBinds :: HsValBindsLR GhcPs GhcPs -> [LHsDecl GhcPs] Source #