ghc-exactprint-0.5.3.0: ExactPrint for GHC

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.GHC.ExactPrint.Types

Contents

Synopsis

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

  • annEntryDelta :: !DeltaPos

    Offset used to get to the start of the SrcSpan, from whatever the prior output was, including all annPriorComments (field below).

  • annPriorComments :: ![(Comment, DeltaPos)]

    Comments coming after the last non-comment output of the preceding element but before the SrcSpan being annotated by this Annotation. If these are changed then annEntryDelta (field above) must also change to match.

  • annFollowingComments :: ![(Comment, DeltaPos)]

    Comments coming after the last output for the element subject to this Annotation. These will only be added by AST transformations, and care must be taken not to disturb layout of following elements.

  • annsDP :: ![(KeywordId, DeltaPos)]

    Annotations associated with this element.

  • annSortKey :: !(Maybe [SrcSpan])

    Captures the sort order of sub elements. This is needed when the sub-elements have been split (as in a HsLocalBind which holds separate binds and sigs) or for infix patterns where the order has been re-arranged. It is captured explicitly so that after the Delta phase a SrcSpan is used purely as an index into the annotations, allowing transformations of the AST including the introduction of new Located items or re-arranging existing ones.

  • annCapturedSpan :: !(Maybe AnnKey)

    Occasionally we must calculate a SrcSpan for an unlocated list of elements which we must remember for the Print phase. e.g. the statements in a HsLet or HsDo. These must be managed as a group because they all need eo be vertically aligned for the Haskell layout rules, and this guarantees this property in the presence of AST edits.

data KeywordId 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.

Instances

Eq KeywordId Source # 
Data KeywordId Source # 

Methods

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

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

toConstr :: KeywordId -> Constr #

dataTypeOf :: KeywordId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord KeywordId Source # 
Show KeywordId Source # 
Outputable KeywordId Source # 

data Comment Source #

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

Instances

Eq Comment Source # 

Methods

(==) :: Comment -> Comment -> Bool #

(/=) :: Comment -> Comment -> Bool #

Data Comment Source # 

Methods

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 :: (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 #

Ord Comment Source # 
Show Comment Source # 
Outputable Comment Source # 

Methods

ppr :: Comment -> SDoc #

pprPrec :: Rational -> Comment -> SDoc #

Positions

type Pos = (Int, Int) Source #

newtype DeltaPos Source #

A relative positions, row then column

Constructors

DP (Int, Int) 

Instances

Eq DeltaPos Source # 
Data DeltaPos Source # 

Methods

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

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

toConstr :: DeltaPos -> Constr #

dataTypeOf :: DeltaPos -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DeltaPos Source # 
Show DeltaPos Source # 
Outputable DeltaPos Source # 

AnnKey

data AnnKey Source #

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 

Instances

Eq AnnKey Source # 

Methods

(==) :: AnnKey -> AnnKey -> Bool #

(/=) :: AnnKey -> AnnKey -> Bool #

Data AnnKey Source # 

Methods

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

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

toConstr :: AnnKey -> Constr #

dataTypeOf :: AnnKey -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AnnKey Source # 
Show AnnKey Source # 
Outputable AnnKey Source # 

Methods

ppr :: AnnKey -> SDoc #

pprPrec :: Rational -> AnnKey -> SDoc #

Monad m => MonadState (Anns, Int) (TransformT m) # 

Methods

get :: TransformT m (Anns, Int) #

put :: (Anns, Int) -> TransformT m () #

state :: ((Anns, Int) -> (a, (Anns, Int))) -> TransformT m a #

mkAnnKey :: Data a => Located a -> AnnKey Source #

Make an unwrapped AnnKey for the LHsDecl case, a normal one otherwise.

data AnnConName Source #

Constructors

CN 

Fields

Instances

Eq AnnConName Source # 
Data AnnConName Source # 

Methods

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

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

toConstr :: AnnConName -> Constr #

dataTypeOf :: AnnConName -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AnnConName Source # 
Show AnnConName Source # 
Outputable AnnConName Source # 

Other

data ACS' a Source #

Constructors

ACS 

Fields

  • acs :: !(Map a Int)

    how many levels each AstContext should propagate down the AST. Removed when it hits zero

Internal Types

declFun :: (forall a. Data a => Located a -> b) -> LHsDecl RdrName -> b Source #