| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Language.Haskell.GHC.ExactPrint.Types
- type Anns = Map AnnKey Annotation
 - emptyAnns :: Anns
 - data Annotation = Ann {
- annEntryDelta :: !DeltaPos
 - annPriorComments :: ![(Comment, DeltaPos)]
 - annFollowingComments :: ![(Comment, DeltaPos)]
 - annsDP :: ![(KeywordId, DeltaPos)]
 - annSortKey :: !(Maybe [SrcSpan])
 - annCapturedSpan :: !(Maybe AnnKey)
 
 - annNone :: Annotation
 - data KeywordId
 - data Comment = Comment {}
 - type Pos = (Int, Int)
 - newtype DeltaPos = DP (Int, Int)
 - deltaRow :: DeltaPos -> Int
 - deltaColumn :: DeltaPos -> Int
 - data AnnKey = AnnKey SrcSpan AnnConName
 - mkAnnKey :: Data a => Located a -> AnnKey
 - data AnnConName = CN {}
 - annGetConstr :: Data a => a -> AnnConName
 - data Rigidity
 - data AstContext
- = LambdaExpr
 - | CaseAlt
 - | NoPrecedingSpace
 - | HasHiding
 - | AdvanceLine
 - | NoAdvanceLine
 - | Intercalate
 - | InIE
 - | PrefixOp
 - | PrefixOpDollar
 - | InfixOp
 - | ListStart
 - | ListItem
 - | TopLevel
 - | NoDarrow
 - | AddVbar
 - | Deriving
 - | Parens
 - | ExplicitNeverActive
 - | InGadt
 - | InRecCon
 - | InClassDecl
 - | InSpliceDecl
 - | LeftMost
 - | CtxOnly
 - | CtxFirst
 - | CtxMiddle
 - | CtxLast
 - | CtxPos Int
 - | FollowingLine
 
 - type AstContextSet = ACS' AstContext
 - defaultACS :: AstContextSet
 - data ACS' a = ACS {}
 - data ListContexts = LC {}
 - newtype LayoutStartCol = LayoutStartCol {}
 - declFun :: (forall a. Data a => Located a -> b) -> LHsDecl RdrName -> b
 
Core Types
type Anns = Map AnnKey Annotation Source #
This structure holds a complete set of annotations for an AST
data Annotation Source #
Constructors
| Ann | |
Fields 
  | |
Instances
| Eq Annotation Source # | |
| Show Annotation Source # | |
| Outputable Annotation Source # | |
| Monad m => MonadState (Anns, Int) (TransformT m) # | |
annNone :: Annotation Source #
The different syntactic elements which are not represented in the AST.
Constructors
| G AnnKeywordId | A normal keyword  | 
| AnnSemiSep | A seperating comma  | 
| AnnComment Comment | |
| AnnString String | Used to pass information from Delta to Print when we have to work out details from the original SrcSpan.  | 
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
Constructors
| Comment | |
Fields 
  | |
Positions
A relative positions, row then column
deltaColumn :: DeltaPos -> Int Source #
AnnKey
For every Located a, use the SrcSpan and constructor name of
 a as the key, to store the standard annotation.
 These are used to maintain context in the AP and EP monads
Constructors
| AnnKey SrcSpan AnnConName | 
mkAnnKey :: Data a => Located a -> AnnKey Source #
Make an unwrapped AnnKey for the LHsDecl case, a normal one otherwise.
data AnnConName Source #
Instances
annGetConstr :: Data a => a -> AnnConName Source #
Other
Constructors
| NormalLayout | |
| RigidLayout | 
data AstContext Source #
Constructors
Instances
type AstContextSet = ACS' AstContext Source #
Constructors
| ACS | |
data ListContexts Source #
Instances
Internal Types
newtype LayoutStartCol Source #
Marks the start column of a layout block.
Constructors
| LayoutStartCol | |
Fields  | |
Instances