haskell-tools-prettyprint-1.1.0.2: Pretty printing of Haskell-Tools AST

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Tools.PrettyPrint.Prepare

Description

A module for preparing the representation of the AST for pretty printing.

Synopsis

Documentation

prepareAST :: StringBuffer -> Ann UModule dom RangeStage -> Ann UModule dom SrcTemplateStage Source #

Prepares the AST for pretty printing

placeComments :: RangeInfo stage => Map ApiAnnKey [SrcSpan] -> Map SrcSpan [Located AnnotationComment] -> Ann UModule dom stage -> Ann UModule dom stage Source #

Puts comments in the nodes they should be attached to. Watches for lexical tokens that may divide the comment and the supposed element. Leaves the AST in a state where parent nodes does not contain all of their children.

after :: AfterBefore i => String -> i -> i Source #

Put the given string before the element if it is not empty

followedBy :: AfterBefore i => String -> i -> i Source #

The given string should follow the element if it is not empty

relativeIndented :: RelativeIndent i => Int -> i -> i Source #

The element should be indented relatively to its parent

minimumIndented :: MinimumIndent i => Int -> i -> i Source #

The elements should be indented at least to the given number of spaces

separatedBy :: String -> ListInfo SrcTemplateStage -> ListInfo SrcTemplateStage Source #

The elements of the list should be separated by the given string by default (might be overridden)

indented :: ListInfo SrcTemplateStage -> ListInfo SrcTemplateStage Source #

The elements of the list should be indented on the same column

data SourceTemplateElem Source #

An element of a source template for a singleton AST node.

Constructors

TextElem

Source text belonging to the current node

ChildElem

Placeholder for the next children of the node

Instances
Eq SourceTemplateElem Source # 
Instance details

Defined in Language.Haskell.Tools.PrettyPrint.Prepare.SourceTemplate

Data SourceTemplateElem Source # 
Instance details

Defined in Language.Haskell.Tools.PrettyPrint.Prepare.SourceTemplate

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SourceTemplateElem -> c SourceTemplateElem #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SourceTemplateElem #

toConstr :: SourceTemplateElem -> Constr #

dataTypeOf :: SourceTemplateElem -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SourceTemplateElem) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourceTemplateElem) #

gmapT :: (forall b. Data b => b -> b) -> SourceTemplateElem -> SourceTemplateElem #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SourceTemplateElem -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SourceTemplateElem -> r #

gmapQ :: (forall d. Data d => d -> u) -> SourceTemplateElem -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SourceTemplateElem -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SourceTemplateElem -> m SourceTemplateElem #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceTemplateElem -> m SourceTemplateElem #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceTemplateElem -> m SourceTemplateElem #

Ord SourceTemplateElem Source # 
Instance details

Defined in Language.Haskell.Tools.PrettyPrint.Prepare.SourceTemplate

Show SourceTemplateElem Source # 
Instance details

Defined in Language.Haskell.Tools.PrettyPrint.Prepare.SourceTemplate

data SourceTemplateTextElem Source #

Instances
Eq SourceTemplateTextElem Source # 
Instance details

Defined in Language.Haskell.Tools.PrettyPrint.Prepare.SourceTemplate

Data SourceTemplateTextElem Source # 
Instance details

Defined in Language.Haskell.Tools.PrettyPrint.Prepare.SourceTemplate

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SourceTemplateTextElem -> c SourceTemplateTextElem #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SourceTemplateTextElem #

toConstr :: SourceTemplateTextElem -> Constr #

dataTypeOf :: SourceTemplateTextElem -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SourceTemplateTextElem) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourceTemplateTextElem) #

gmapT :: (forall b. Data b => b -> b) -> SourceTemplateTextElem -> SourceTemplateTextElem #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SourceTemplateTextElem -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SourceTemplateTextElem -> r #

gmapQ :: (forall d. Data d => d -> u) -> SourceTemplateTextElem -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SourceTemplateTextElem -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SourceTemplateTextElem -> m SourceTemplateTextElem #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceTemplateTextElem -> m SourceTemplateTextElem #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceTemplateTextElem -> m SourceTemplateTextElem #

Ord SourceTemplateTextElem Source # 
Instance details

Defined in Language.Haskell.Tools.PrettyPrint.Prepare.SourceTemplate

Show SourceTemplateTextElem Source # 
Instance details

Defined in Language.Haskell.Tools.PrettyPrint.Prepare.SourceTemplate

fixRanges :: SourceInfoTraversal node => Ann node dom RangeStage -> Ann node dom NormRangeStage Source #

Modifies ranges to contain their children

cutUpRanges :: forall node dom. SourceInfoTraversal node => Ann node dom NormRangeStage -> Ann node dom RngTemplateStage Source #

Creates a source template from the ranges and the input file. All source ranges must be good ranges.

getLocIndices :: SourceInfoTraversal e => Ann e dom RngTemplateStage -> Set (RealSrcLoc, Int) Source #

Assigns an index (in the order they are used) for each range

mapLocIndices :: Ord k => StringBuffer -> Set (RealSrcLoc, k) -> Map k String Source #

Partitions the source file in the order where the parts are used in the AST

extractStayingElems :: SourceInfoTraversal node => Ann node dom SrcTemplateStage -> Ann node dom SrcTemplateStage Source #

Marks template elements in the AST that should always be present in the source code, regardless of their containing elements being deleted. Currently it recognizes CPP pragmas (lines starting with #) This function should only be applied to an AST if CPP is enabled.