Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Provides consistent interface with ghc-exactprint.
Synopsis
- fix :: (Data ast, MonadIO m) => FixityEnv -> ast -> TransformT m ast
- type LibDir = FilePath
- parseContent :: LibDir -> FixityEnv -> FilePath -> String -> IO AnnotatedModule
- parseContentNoFixity :: LibDir -> FilePath -> String -> IO AnnotatedModule
- parseDecl :: LibDir -> String -> IO AnnotatedHsDecl
- parseExpr :: LibDir -> String -> IO AnnotatedHsExpr
- parseImports :: LibDir -> [String] -> IO AnnotatedImports
- parsePattern :: LibDir -> String -> IO AnnotatedPat
- parseStmt :: LibDir -> String -> IO AnnotatedStmt
- parseType :: LibDir -> String -> IO AnnotatedHsType
- addAllAnnsT :: (HasCallStack, Monoid an, Data a, Data b, MonadIO m, Typeable an) => LocatedAn an a -> LocatedAn an b -> TransformT m (LocatedAn an b)
- swapEntryDPT :: (Data a, Data b, Monad m, Monoid a1, Monoid a2, Typeable a1, Typeable a2) => LocatedAn a1 a -> LocatedAn a2 b -> TransformT m (LocatedAn a1 a, LocatedAn a2 b)
- transferAnnsT :: (Data a, Data b, Monad m) => (TrailingAnn -> Bool) -> LocatedA a -> LocatedA b -> TransformT m (LocatedA b)
- transferEntryAnnsT :: (HasCallStack, Data a, Data b, Monad m) => (TrailingAnn -> Bool) -> LocatedA a -> LocatedA b -> TransformT m (LocatedA b)
- transferEntryDPT :: (HasCallStack, Data a, Data b, Monad m) => Located a -> Located b -> TransformT m ()
- transferAnchor :: LocatedA a -> LocatedA b -> LocatedA b
- debugDump :: (Data a, ExactPrint a) => Annotated a -> IO ()
- debugParse :: LibDir -> FixityEnv -> String -> IO ()
- debug :: c -> String -> c
- hasComments :: LocatedAn an a -> Bool
- isComma :: TrailingAnn -> Bool
- module Retrie.ExactPrint.Annotated
- makeDeltaAst' :: Data a => a -> a
- modifyDeclsT :: (HasDecls t, HasTransform m) => ([LHsDecl GhcPs] -> m [LHsDecl GhcPs]) -> t -> m t
- modifyValD :: HasTransform m => SrcSpan -> Decl -> (PMatch -> [Decl] -> m ([Decl], Maybe t)) -> m (Decl, Maybe t)
- replaceDeclsValbinds :: forall (m :: Type -> Type). Monad m => WithWhere -> HsLocalBinds GhcPs -> [LHsDecl GhcPs] -> TransformT m (HsLocalBinds GhcPs)
- hsDeclsValBinds :: forall (m :: Type -> Type). Monad m => HsLocalBinds GhcPs -> TransformT m [LHsDecl GhcPs]
- replaceDeclsPatBind :: forall (m :: Type -> Type). Monad m => LHsBind GhcPs -> [LHsDecl GhcPs] -> TransformT m (LHsBind GhcPs)
- replaceDeclsPatBindD :: forall (m :: Type -> Type). Monad m => LHsDecl GhcPs -> [LHsDecl GhcPs] -> TransformT m (LHsDecl GhcPs)
- hsDeclsPatBind :: forall (m :: Type -> Type). Monad m => LHsBind GhcPs -> TransformT m [LHsDecl GhcPs]
- hsDeclsPatBindD :: forall (m :: Type -> Type). Monad m => LHsDecl GhcPs -> TransformT m [LHsDecl GhcPs]
- insertBefore :: HasDecls (LocatedA ast) => LocatedA old -> LocatedA ast -> LHsDecl GhcPs -> Transform (LocatedA ast)
- insertAfter :: HasDecls (LocatedA ast) => LocatedA old -> LocatedA ast -> LHsDecl GhcPs -> Transform (LocatedA ast)
- insertAtEnd :: HasDecls ast => ast -> LHsDecl GhcPs -> Transform ast
- insertAtStart :: HasDecls ast => ast -> LHsDecl GhcPs -> Transform ast
- insertAt :: HasDecls ast => (LHsDecl GhcPs -> [LHsDecl GhcPs] -> [LHsDecl GhcPs]) -> ast -> LHsDecl GhcPs -> Transform ast
- addComma :: SrcSpanAnnA -> SrcSpanAnnA
- mn :: Int -> AnchorOperation
- m1 :: AnchorOperation
- m0 :: AnchorOperation
- dn :: Int -> EpaLocation
- d1 :: EpaLocation
- d0 :: EpaLocation
- noAnnSrcSpanDPn :: Monoid ann => SrcSpan -> Int -> SrcSpanAnn' (EpAnn ann)
- noAnnSrcSpanDP1 :: Monoid ann => SrcSpan -> SrcSpanAnn' (EpAnn ann)
- noAnnSrcSpanDP0 :: Monoid ann => SrcSpan -> SrcSpanAnn' (EpAnn ann)
- noAnnSrcSpanDP :: Monoid ann => SrcSpan -> DeltaPos -> SrcSpanAnn' (EpAnn ann)
- anchorEof :: ParsedSource -> ParsedSource
- balanceCommentsList' :: forall (m :: Type -> Type) a. Monad m => [LocatedA a] -> TransformT m [LocatedA a]
- balanceComments :: forall (m :: Type -> Type). Monad m => LHsDecl GhcPs -> LHsDecl GhcPs -> TransformT m (LHsDecl GhcPs, LHsDecl GhcPs)
- balanceCommentsList :: forall (m :: Type -> Type). Monad m => [LHsDecl GhcPs] -> TransformT m [LHsDecl GhcPs]
- transferEntryDP' :: forall (m :: Type -> Type). Monad m => LHsDecl GhcPs -> LHsDecl GhcPs -> TransformT m (LHsDecl GhcPs)
- getEntryDP :: LocatedAn t a -> DeltaPos
- wrapDecl :: LHsBind GhcPs -> LHsDecl GhcPs
- wrapSig :: LSig GhcPs -> LHsDecl GhcPs
- decl2Sig :: LHsDecl GhcPs -> [LSig GhcPs]
- decl2Bind :: LHsDecl GhcPs -> [LHsBind GhcPs]
- captureTypeSigSpacing :: LHsDecl GhcPs -> LHsDecl GhcPs
- captureLineSpacing :: Default t => [LocatedAn t e] -> [LocatedAn t e]
- captureMatchLineSpacing :: LHsDecl GhcPs -> LHsDecl GhcPs
- captureOrder :: [LocatedA b] -> AnnSortKey
- isUniqueSrcSpan :: SrcSpan -> Bool
- uniqueSrcSpanT :: forall (m :: Type -> Type). Monad m => TransformT m SrcSpan
- logDataWithAnnsTr :: forall (m :: Type -> Type) a. (Monad m, Data a) => String -> a -> TransformT m ()
- logTr :: forall (m :: Type -> Type). Monad m => String -> TransformT m ()
- hoistTransform :: (forall x. m x -> n x) -> TransformT m a -> TransformT n a
- runTransformFromT :: Int -> TransformT m a -> m (a, Int, [String])
- runTransformFrom :: Int -> Transform a -> (a, Int, [String])
- runTransformT :: TransformT m a -> m (a, Int, [String])
- runTransform :: Transform a -> (a, Int, [String])
- type Transform = TransformT Identity
- newtype TransformT (m :: Type -> Type) a = TransformT {
- unTransformT :: RWST () [String] Int m a
- class Data t => HasDecls t where
- hsDecls :: forall (m :: Type -> Type). Monad m => t -> TransformT m [LHsDecl GhcPs]
- replaceDecls :: forall (m :: Type -> Type). Monad m => t -> [LHsDecl GhcPs] -> TransformT m t
- data WithWhere
- class Monad m => HasTransform (m :: Type -> Type) where
- makeDeltaAst :: ExactPrint ast => ast -> ast
- exactPrint :: ExactPrint ast => ast -> String
- showAst :: Data a => a -> String
- class Typeable a => ExactPrint a where
- getAnnotationEntry :: a -> Entry
- setAnnotationAnchor :: a -> Anchor -> EpAnnComments -> a
- exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => a -> EP w m a
- showAstData :: Data a => BlankSrcSpan -> BlankEpAnnotations -> a -> SDoc
- data BlankSrcSpan
- data BlankEpAnnotations
- parseModule :: LibDir -> FilePath -> IO (ParseResult ParsedSource)
- data Comment
- showGhc :: Outputable a => a -> String
- hackAnchorToSrcSpan :: Anchor -> SrcSpan
- hackSrcSpanToAnchor :: SrcSpan -> Anchor
- anchorToEpaLocation :: Anchor -> EpaLocation
- addEpAnnLoc :: AddEpAnn -> EpaLocation
- setTrailingAnnLoc :: TrailingAnn -> EpaLocation -> TrailingAnn
- trailingAnnLoc :: TrailingAnn -> EpaLocation
- trailingAnnToAddEpAnn :: TrailingAnn -> AddEpAnn
- moveAnchor :: Monoid b => SrcAnn a -> SrcAnn b
- setAnchorHsModule :: HsModule -> Anchor -> EpAnnComments -> HsModule
- setAnchorEpaL :: EpAnn AnnList -> Anchor -> EpAnnComments -> EpAnn AnnList
- setAnchorEpa :: Default an => EpAnn an -> Anchor -> EpAnnComments -> EpAnn an
- setAnchorAn :: Default an => LocatedAn an a -> Anchor -> EpAnnComments -> LocatedAn an a
- locatedAnAnchor :: LocatedAn a t -> RealSrcSpan
- name2String :: Name -> String
- rdrName2String :: RdrName -> String
- dpFromString :: String -> DeltaPos
- sortAnchorLocated :: [GenLocated Anchor a] -> [GenLocated Anchor a]
- noKWComments :: [Comment] -> [Comment]
- isKWComment :: Comment -> Bool
- mkKWComment :: AnnKeywordId -> EpaLocation -> Comment
- sortEpaComments :: [LEpaComment] -> [LEpaComment]
- sortComments :: [Comment] -> [Comment]
- cmpComments :: Comment -> Comment -> Ordering
- normaliseCommentText :: String -> String
- mkComment :: String -> Anchor -> RealSrcSpan -> Comment
- mkLEpaComment :: String -> Anchor -> RealSrcSpan -> LEpaComment
- comment2LEpaComment :: Comment -> LEpaComment
- mkEpaComments :: [Comment] -> [Comment] -> EpAnnComments
- tokComment :: LEpaComment -> Comment
- ghcCommentText :: LEpaComment -> String
- insertCppComments :: ParsedSource -> [LEpaComment] -> ParsedSource
- isGadt :: forall (p :: Pass). [LConDecl (GhcPass p)] -> Bool
- orderByKey :: [(RealSrcSpan, a)] -> [RealSrcSpan] -> [(RealSrcSpan, a)]
- isPointSrcSpan :: RealSrcSpan -> Bool
- spanLength :: RealSrcSpan -> Int
- badRealSrcSpan :: RealSrcSpan
- range2rs :: (Pos, Pos) -> RealSrcSpan
- rs :: SrcSpan -> RealSrcSpan
- rs2range :: RealSrcSpan -> (Pos, Pos)
- ss2range :: SrcSpan -> (Pos, Pos)
- ss2posEnd :: RealSrcSpan -> Pos
- ss2pos :: RealSrcSpan -> Pos
- adjustDeltaForOffset :: LayoutStartCol -> DeltaPos -> DeltaPos
- undeltaSpan :: RealSrcSpan -> AnnKeywordId -> DeltaPos -> AddEpAnn
- undelta :: Pos -> DeltaPos -> LayoutStartCol -> Pos
- pos2delta :: Pos -> Pos -> DeltaPos
- ss2deltaStart :: RealSrcSpan -> RealSrcSpan -> DeltaPos
- ss2deltaEnd :: RealSrcSpan -> RealSrcSpan -> DeltaPos
- ss2delta :: Pos -> RealSrcSpan -> DeltaPos
- isGoodDelta :: DeltaPos -> Bool
- warn :: c -> String -> c
- debugM :: Monad m => String -> m ()
- debugP :: String -> c -> c
- debugPEnabledFlag :: Bool
- debugEnabledFlag :: Bool
- module Language.Haskell.GHC.ExactPrint.Transform
Fixity re-association
fix :: (Data ast, MonadIO m) => FixityEnv -> ast -> TransformT m ast Source #
Re-associate AST using given FixityEnv
. (The GHC parser has no knowledge
of operator fixity, because that requires running the renamer, so it parses
all operators as left-associated.)
Parsers
parseContent :: LibDir -> FixityEnv -> FilePath -> String -> IO AnnotatedModule Source #
parseContentNoFixity :: LibDir -> FilePath -> String -> IO AnnotatedModule Source #
parseImports :: LibDir -> [String] -> IO AnnotatedImports Source #
Parse import statements. Each string must be a full import statement, including the keyword 'import'. Supports full import syntax.
parsePattern :: LibDir -> String -> IO AnnotatedPat Source #
Parse a Pat
.
Primitive Transformations
addAllAnnsT :: (HasCallStack, Monoid an, Data a, Data b, MonadIO m, Typeable an) => LocatedAn an a -> LocatedAn an b -> TransformT m (LocatedAn an b) Source #
swapEntryDPT :: (Data a, Data b, Monad m, Monoid a1, Monoid a2, Typeable a1, Typeable a2) => LocatedAn a1 a -> LocatedAn a2 b -> TransformT m (LocatedAn a1 a, LocatedAn a2 b) Source #
transferAnnsT :: (Data a, Data b, Monad m) => (TrailingAnn -> Bool) -> LocatedA a -> LocatedA b -> TransformT m (LocatedA b) Source #
transferEntryAnnsT :: (HasCallStack, Data a, Data b, Monad m) => (TrailingAnn -> Bool) -> LocatedA a -> LocatedA b -> TransformT m (LocatedA b) Source #
transferEntryDPT :: (HasCallStack, Data a, Data b, Monad m) => Located a -> Located b -> TransformT m () Source #
Transform
monad version of transferEntryDP
Utils
hasComments :: LocatedAn an a -> Bool Source #
isComma :: TrailingAnn -> Bool Source #
Annotated AST
module Retrie.ExactPrint.Annotated
ghc-exactprint re-exports
makeDeltaAst' :: Data a => a -> a #
Generic top-down traversal through the given AST fragment, converting all ExactPrint Anchor's into ones with an equivalent MovedAnchor operation. Initially ignores comments
modifyDeclsT :: (HasDecls t, HasTransform m) => ([LHsDecl GhcPs] -> m [LHsDecl GhcPs]) -> t -> m t #
Apply a transformation to the decls contained in t
modifyValD :: HasTransform m => SrcSpan -> Decl -> (PMatch -> [Decl] -> m ([Decl], Maybe t)) -> m (Decl, Maybe t) #
replaceDeclsValbinds :: forall (m :: Type -> Type). Monad m => WithWhere -> HsLocalBinds GhcPs -> [LHsDecl GhcPs] -> TransformT m (HsLocalBinds GhcPs) #
Utility function for returning decls to HsLocalBinds
. Use with
care, as this does not manage the declaration order, the
ordering should be done by the calling function from the HsLocalBinds
context in the AST.
hsDeclsValBinds :: forall (m :: Type -> Type). Monad m => HsLocalBinds GhcPs -> TransformT m [LHsDecl GhcPs] #
replaceDeclsPatBind :: forall (m :: Type -> Type). Monad m => LHsBind GhcPs -> [LHsDecl GhcPs] -> TransformT m (LHsBind GhcPs) #
Replace the immediate declarations for a PatBind
. This
cannot be a member of HasDecls
because a FunBind
is not idempotent
for hsDecls
/ replaceDecls
. hsDeclsPatBind
/ replaceDeclsPatBind
is
idempotent.
replaceDeclsPatBindD :: forall (m :: Type -> Type). Monad m => LHsDecl GhcPs -> [LHsDecl GhcPs] -> TransformT m (LHsDecl GhcPs) #
Replace the immediate declarations for a PatBind
wrapped in a ValD
. This
cannot be a member of HasDecls
because a FunBind
is not idempotent
for hsDecls
/ replaceDecls
. hsDeclsPatBindD
/ replaceDeclsPatBindD
is
idempotent.
hsDeclsPatBind :: forall (m :: Type -> Type). Monad m => LHsBind GhcPs -> TransformT m [LHsDecl GhcPs] #
Extract the immediate declarations for a PatBind
. This
cannot be a member of HasDecls
because a FunBind
is not idempotent
for hsDecls
/ replaceDecls
. hsDeclsPatBind
/ replaceDeclsPatBind
is
idempotent.
hsDeclsPatBindD :: forall (m :: Type -> Type). Monad m => LHsDecl GhcPs -> TransformT m [LHsDecl GhcPs] #
Extract the immediate declarations for a PatBind
wrapped in a ValD
. This
cannot be a member of HasDecls
because a FunBind
is not idempotent
for hsDecls
/ replaceDecls
. hsDeclsPatBindD
/ replaceDeclsPatBindD
is
idempotent.
insertBefore :: HasDecls (LocatedA ast) => LocatedA old -> LocatedA ast -> LHsDecl GhcPs -> Transform (LocatedA ast) #
Insert a declaration at a specific location in the subdecls of the given AST item
insertAfter :: HasDecls (LocatedA ast) => LocatedA old -> LocatedA ast -> LHsDecl GhcPs -> Transform (LocatedA ast) #
Insert a declaration at a specific location in the subdecls of the given AST item
insertAtEnd :: HasDecls ast => ast -> LHsDecl GhcPs -> Transform ast #
Insert a declaration at the beginning or end of the subdecls of the given AST item
insertAtStart :: HasDecls ast => ast -> LHsDecl GhcPs -> Transform ast #
Insert a declaration at the beginning or end of the subdecls of the given AST item
insertAt :: HasDecls ast => (LHsDecl GhcPs -> [LHsDecl GhcPs] -> [LHsDecl GhcPs]) -> ast -> LHsDecl GhcPs -> Transform ast #
Insert a declaration into an AST element having sub-declarations
(HasDecls
) according to the given location function.
addComma :: SrcSpanAnnA -> SrcSpanAnnA #
mn :: Int -> AnchorOperation #
m1 :: AnchorOperation #
m0 :: AnchorOperation #
dn :: Int -> EpaLocation #
d1 :: EpaLocation #
d0 :: EpaLocation #
noAnnSrcSpanDPn :: Monoid ann => SrcSpan -> Int -> SrcSpanAnn' (EpAnn ann) #
noAnnSrcSpanDP1 :: Monoid ann => SrcSpan -> SrcSpanAnn' (EpAnn ann) #
noAnnSrcSpanDP0 :: Monoid ann => SrcSpan -> SrcSpanAnn' (EpAnn ann) #
noAnnSrcSpanDP :: Monoid ann => SrcSpan -> DeltaPos -> SrcSpanAnn' (EpAnn ann) #
Create a SrcSpanAnn
with a MovedAnchor
operation using the
given DeltaPos
.
anchorEof :: ParsedSource -> ParsedSource #
balanceCommentsList' :: forall (m :: Type -> Type) a. Monad m => [LocatedA a] -> TransformT m [LocatedA a] #
balanceComments :: forall (m :: Type -> Type). Monad m => LHsDecl GhcPs -> LHsDecl GhcPs -> TransformT m (LHsDecl GhcPs, LHsDecl GhcPs) #
The GHC parser puts all comments appearing between the end of one AST
item and the beginning of the next as annPriorComments
for the second one.
This function takes two adjacent AST items and moves any annPriorComments
from the second one to the annFollowingComments
of the first if they belong
to it instead. This is typically required before deleting or duplicating
either of the AST elements.
balanceCommentsList :: forall (m :: Type -> Type). Monad m => [LHsDecl GhcPs] -> TransformT m [LHsDecl GhcPs] #
transferEntryDP' :: forall (m :: Type -> Type). Monad m => LHsDecl GhcPs -> LHsDecl GhcPs -> TransformT m (LHsDecl GhcPs) #
Take the annEntryDelta associated with the first item and associate it with the second. Also transfer any comments occuring before it. TODO: call transferEntryDP, and use pushDeclDP
getEntryDP :: LocatedAn t a -> DeltaPos #
decl2Sig :: LHsDecl GhcPs -> [LSig GhcPs] #
Pure function to convert a LSig
to a LHsBind
. This does
nothing to any annotations that may be attached to either of the elements.
It is used as a utility function in replaceDecls
decl2Bind :: LHsDecl GhcPs -> [LHsBind GhcPs] #
Pure function to convert a LHsDecl
to a LHsBind
. This does
nothing to any annotations that may be attached to either of the elements.
It is used as a utility function in replaceDecls
captureLineSpacing :: Default t => [LocatedAn t e] -> [LocatedAn t e] #
captureOrder :: [LocatedA b] -> AnnSortKey #
If a list has been re-ordered or had items added, capture the new order in
the appropriate AnnSortKey
attached to the Annotation
for the list.
isUniqueSrcSpan :: SrcSpan -> Bool #
Test whether a given SrcSpan
was generated by uniqueSrcSpanT
uniqueSrcSpanT :: forall (m :: Type -> Type). Monad m => TransformT m SrcSpan #
If we need to add new elements to the AST, they need their own
SrcSpan
for this.
logDataWithAnnsTr :: forall (m :: Type -> Type) a. (Monad m, Data a) => String -> a -> TransformT m () #
Log a representation of the given AST with annotations to the output of the Monad
logTr :: forall (m :: Type -> Type). Monad m => String -> TransformT m () #
Log a string to the output of the Monad
hoistTransform :: (forall x. m x -> n x) -> TransformT m a -> TransformT n a #
Change inner monad of TransformT
.
runTransformFromT :: Int -> TransformT m a -> m (a, Int, [String]) #
Run a monad transformer stack for the TransformT
monad transformer
runTransformT :: TransformT m a -> m (a, Int, [String]) #
runTransform :: Transform a -> (a, Int, [String]) #
type Transform = TransformT Identity #
Monad type for updating the AST and managing the annotations at the same time. The W state is used to generate logging information if required.
newtype TransformT (m :: Type -> Type) a #
Monad transformer version of Transform
monad
TransformT | |
|
Instances
class Data t => HasDecls t where #
Provide a means to get and process the immediate child declartions of a given AST element.
hsDecls :: forall (m :: Type -> Type). Monad m => t -> TransformT m [LHsDecl GhcPs] #
Return the HsDecl
s that are directly enclosed in the
given syntax phrase. They are always returned in the wrapped HsDecl
form, even if orginating in local decls. This is safe, as annotations
never attach to the wrapper, only to the wrapped item.
replaceDecls :: forall (m :: Type -> Type). Monad m => t -> [LHsDecl GhcPs] -> TransformT m t #
Replace the directly enclosed decl list by the given
decl list. Runs in the Transform
monad to be able to update list order
annotations, and rebalance comments and other layout changes as needed.
For example, a call on replaceDecls for a wrapped FunBind
having no
where clause will convert
-- |This is a function foo = x -- comment1
in to
-- |This is a function foo = x -- comment1 where nn = 2
Instances
class Monad m => HasTransform (m :: Type -> Type) where #
Used to integrate a Transform
into other Monad stacks
Instances
Monad m => HasTransform (TransformT m) | |
Defined in Language.Haskell.GHC.ExactPrint.Transform liftT :: Transform a -> TransformT m a # |
makeDeltaAst :: ExactPrint ast => ast -> ast #
Transform concrete annotations into relative annotations which
are more useful when transforming an AST. This corresponds to the
earlier relativiseApiAnns
.
exactPrint :: ExactPrint ast => ast -> String #
class Typeable a => ExactPrint a where #
An AST fragment with an annotation must be able to return the
requirements for nesting another one, captured in an Entry
, and
to be able to use the rest of the exactprint machinery to print the
element. In the analogy to Outputable, exact
plays the role of
ppr
.
getAnnotationEntry :: a -> Entry #
setAnnotationAnchor :: a -> Anchor -> EpAnnComments -> a #
exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => a -> EP w m a #
Instances
showAstData :: Data a => BlankSrcSpan -> BlankEpAnnotations -> a -> SDoc #
Show a GHC syntax tree. This parameterised because it is also used for comparing ASTs in ppr roundtripping tests, where the SrcSpan's are blanked out, to avoid comparing locations, only structure
data BlankSrcSpan #
Instances
Show BlankSrcSpan | |
Defined in Language.Haskell.GHC.ExactPrint.Dump showsPrec :: Int -> BlankSrcSpan -> ShowS # show :: BlankSrcSpan -> String # showList :: [BlankSrcSpan] -> ShowS # | |
Eq BlankSrcSpan | |
Defined in Language.Haskell.GHC.ExactPrint.Dump (==) :: BlankSrcSpan -> BlankSrcSpan -> Bool # (/=) :: BlankSrcSpan -> BlankSrcSpan -> Bool # |
data BlankEpAnnotations #
Instances
Show BlankEpAnnotations | |
Defined in Language.Haskell.GHC.ExactPrint.Dump showsPrec :: Int -> BlankEpAnnotations -> ShowS # show :: BlankEpAnnotations -> String # showList :: [BlankEpAnnotations] -> ShowS # | |
Eq BlankEpAnnotations | |
Defined in Language.Haskell.GHC.ExactPrint.Dump (==) :: BlankEpAnnotations -> BlankEpAnnotations -> Bool # (/=) :: BlankEpAnnotations -> BlankEpAnnotations -> Bool # |
parseModule :: LibDir -> FilePath -> IO (ParseResult ParsedSource) #
This entry point will also work out which language extensions are required and perform CPP processing if necessary.
parseModule = parseModuleWithCpp defaultCppOptions
Note: ParsedSource
is a synonym for Located
(HsModule
GhcPs
)
A Haskell comment. The AnnKeywordId
is present if it has been converted
from an AnnKeywordId
because the annotation must be interleaved into the
stream and does not have a well-defined position
Instances
Data Comment | |
Defined in Language.Haskell.GHC.ExactPrint.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Comment -> c Comment # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Comment # toConstr :: Comment -> Constr # dataTypeOf :: Comment -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Comment) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Comment) # gmapT :: (forall b. Data b => b -> b) -> Comment -> Comment # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Comment -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Comment -> r # gmapQ :: (forall d. Data d => d -> u) -> Comment -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Comment -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Comment -> m Comment # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Comment -> m Comment # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Comment -> m Comment # | |
Show Comment | |
Outputable Comment | |
Defined in Language.Haskell.GHC.ExactPrint.Types | |
Eq Comment | |
Ord Comment | |
Defined in Language.Haskell.GHC.ExactPrint.Types |
showGhc :: Outputable a => a -> String #
hackAnchorToSrcSpan :: Anchor -> SrcSpan #
hackSrcSpanToAnchor :: SrcSpan -> Anchor #
addEpAnnLoc :: AddEpAnn -> EpaLocation #
setTrailingAnnLoc :: TrailingAnn -> EpaLocation -> TrailingAnn #
moveAnchor :: Monoid b => SrcAnn a -> SrcAnn b #
Version of l2l that preserves the anchor, immportant if it has an updated AnchorOperation
setAnchorHsModule :: HsModule -> Anchor -> EpAnnComments -> HsModule #
setAnchorEpaL :: EpAnn AnnList -> Anchor -> EpAnnComments -> EpAnn AnnList #
setAnchorEpa :: Default an => EpAnn an -> Anchor -> EpAnnComments -> EpAnn an #
setAnchorAn :: Default an => LocatedAn an a -> Anchor -> EpAnnComments -> LocatedAn an a #
locatedAnAnchor :: LocatedAn a t -> RealSrcSpan #
name2String :: Name -> String #
rdrName2String :: RdrName -> String #
dpFromString :: String -> DeltaPos #
Calculates the distance from the start of a string to the end of a string.
sortAnchorLocated :: [GenLocated Anchor a] -> [GenLocated Anchor a] #
noKWComments :: [Comment] -> [Comment] #
isKWComment :: Comment -> Bool #
Detects a comment which originates from a specific keyword.
mkKWComment :: AnnKeywordId -> EpaLocation -> Comment #
Makes a comment which originates from a specific keyword.
sortEpaComments :: [LEpaComment] -> [LEpaComment] #
Sort, comparing without span filenames, for CPP injected comments with fake filename
sortComments :: [Comment] -> [Comment] #
Sort, comparing without span filenames, for CPP injected comments with fake filename
cmpComments :: Comment -> Comment -> Ordering #
Must compare without span filenames, for CPP injected comments with fake filename
normaliseCommentText :: String -> String #
mkLEpaComment :: String -> Anchor -> RealSrcSpan -> LEpaComment #
mkEpaComments :: [Comment] -> [Comment] -> EpAnnComments #
tokComment :: LEpaComment -> Comment #
ghcCommentText :: LEpaComment -> String #
insertCppComments :: ParsedSource -> [LEpaComment] -> ParsedSource #
orderByKey :: [(RealSrcSpan, a)] -> [RealSrcSpan] -> [(RealSrcSpan, a)] #
Given a list of items and a list of keys, returns a list of items ordered by their position in the list of keys.
isPointSrcSpan :: RealSrcSpan -> Bool #
Checks whether a SrcSpan has zero length.
spanLength :: RealSrcSpan -> Int #
range2rs :: (Pos, Pos) -> RealSrcSpan #
rs :: SrcSpan -> RealSrcSpan #
rs2range :: RealSrcSpan -> (Pos, Pos) #
ss2posEnd :: RealSrcSpan -> Pos #
ss2pos :: RealSrcSpan -> Pos #
adjustDeltaForOffset :: LayoutStartCol -> DeltaPos -> DeltaPos #
undeltaSpan :: RealSrcSpan -> AnnKeywordId -> DeltaPos -> AddEpAnn #
undelta :: Pos -> DeltaPos -> LayoutStartCol -> Pos #
Apply the delta to the current position, taking into account the current column offset if advancing to a new line
pos2delta :: Pos -> Pos -> DeltaPos #
Convert the start of the second Pos
to be an offset from the
first. The assumption is the reference starts before the second Pos
ss2deltaStart :: RealSrcSpan -> RealSrcSpan -> DeltaPos #
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
ss2deltaEnd :: RealSrcSpan -> RealSrcSpan -> DeltaPos #
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
ss2delta :: Pos -> RealSrcSpan -> DeltaPos #
Create a delta from the current position to the start of the given
RealSrcSpan
.
isGoodDelta :: DeltaPos -> Bool #
A good delta has no negative values.
Global switch to enable debug tracing in ghc-exactprint Pretty
Global switch to enable debug tracing in ghc-exactprint Delta / Print