Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- 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
- type AnnSpan = SrcSpan
- data AnnKey = AnnKey AnnSpan AnnConName
- mkAnnKey :: Constraints a => 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
- | InTypeApp
- | CtxOnly
- | CtxFirst
- | CtxMiddle
- | CtxLast
- | CtxPos Int
- | FollowingLine
- type AstContextSet = ACS' AstContext
- defaultACS :: AstContextSet
- data ACS' a = ACS {}
- data ListContexts = LC {}
- type Constraints a = (Data a, Data (SrcSpanLess a), HasSrcSpan a)
- type GhcPs = GhcPs
- type GhcRn = GhcRn
- type GhcTc = GhcTc
- noExt :: NoExtField
- newtype LayoutStartCol = LayoutStartCol {}
- declFun :: (forall a. Data a => Located a -> b) -> LHsDecl GhcPs -> b
Core Types
type Anns = Map AnnKey Annotation Source #
This structure holds a complete set of annotations for an AST
data Annotation Source #
Ann | |
|
Instances
Eq Annotation Source # | |
Defined in Language.Haskell.GHC.ExactPrint.Types (==) :: Annotation -> Annotation -> Bool # (/=) :: Annotation -> Annotation -> Bool # | |
Show Annotation Source # | |
Defined in Language.Haskell.GHC.ExactPrint.Types showsPrec :: Int -> Annotation -> ShowS # show :: Annotation -> String # showList :: [Annotation] -> ShowS # | |
Outputable Annotation Source # | |
Defined in Language.Haskell.GHC.ExactPrint.Types ppr :: Annotation -> SDoc # pprPrec :: Rational -> Annotation -> SDoc # | |
Monad m => MonadState (Anns, Int) (TransformT m) Source # | |
Defined in Language.Haskell.GHC.ExactPrint.Transform |
annNone :: Annotation Source #
The different syntactic elements which are not represented in the AST.
G AnnKeywordId | A normal keyword |
AnnSemiSep | A separating comma |
AnnTypeApp | Visible type application annotation |
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 # | |
Defined in Language.Haskell.GHC.ExactPrint.Types 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 :: forall r r'. (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 # | |
Defined in Language.Haskell.GHC.ExactPrint.Types | |
Show KeywordId Source # | |
Outputable KeywordId 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
Comment | |
|
Instances
Eq Comment Source # | |
Data Comment Source # | |
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 # | |
Ord Comment Source # | |
Defined in Language.Haskell.GHC.ExactPrint.Types | |
Show Comment Source # | |
Outputable Comment Source # | |
Positions
A relative positions, row then column
Instances
Eq DeltaPos Source # | |
Data DeltaPos Source # | |
Defined in Language.Haskell.GHC.ExactPrint.Types 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 :: forall r r'. (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 # | |
Defined in Language.Haskell.GHC.ExactPrint.Types | |
Show DeltaPos Source # | |
Outputable DeltaPos Source # | |
deltaColumn :: DeltaPos -> Int Source #
AnnKey
type AnnSpan = SrcSpan Source #
From GHC 9.0 the ParsedSource uses RealSrcSpan instead of SrcSpan. Compatibility type
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
Instances
Eq AnnKey Source # | |
Data AnnKey Source # | |
Defined in Language.Haskell.GHC.ExactPrint.Types 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 :: forall r r'. (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 # | |
Monad m => MonadState (Anns, Int) (TransformT m) Source # | |
Defined in Language.Haskell.GHC.ExactPrint.Transform |
mkAnnKey :: Constraints a => 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
data AstContext Source #
Instances
type AstContextSet = ACS' AstContext Source #
Instances
Show a => Show (ACS' a) Source # | |
Semigroup (ACS' AstContext) Source # | |
Defined in Language.Haskell.GHC.ExactPrint.Types (<>) :: ACS' AstContext -> ACS' AstContext -> ACS' AstContext # sconcat :: NonEmpty (ACS' AstContext) -> ACS' AstContext # stimes :: Integral b => b -> ACS' AstContext -> ACS' AstContext # | |
Monoid (ACS' AstContext) Source # | |
Defined in Language.Haskell.GHC.ExactPrint.Types mempty :: ACS' AstContext # mappend :: ACS' AstContext -> ACS' AstContext -> ACS' AstContext # mconcat :: [ACS' AstContext] -> ACS' AstContext # | |
Show a => Outputable (ACS' a) Source # | |
data ListContexts Source #
Instances
Eq ListContexts Source # | |
Defined in Language.Haskell.GHC.ExactPrint.Types (==) :: ListContexts -> ListContexts -> Bool # (/=) :: ListContexts -> ListContexts -> Bool # | |
Show ListContexts Source # | |
Defined in Language.Haskell.GHC.ExactPrint.Types showsPrec :: Int -> ListContexts -> ShowS # show :: ListContexts -> String # showList :: [ListContexts] -> ShowS # |
For managing compatibility
type Constraints a = (Data a, Data (SrcSpanLess a), HasSrcSpan a) Source #
GHC version compatibility
noExt :: NoExtField Source #
Internal Types
newtype LayoutStartCol Source #
Marks the start column of a layout block.
Instances
Eq LayoutStartCol Source # | |
Defined in Language.Haskell.GHC.ExactPrint.Types (==) :: LayoutStartCol -> LayoutStartCol -> Bool # (/=) :: LayoutStartCol -> LayoutStartCol -> Bool # | |
Num LayoutStartCol Source # | |
Defined in Language.Haskell.GHC.ExactPrint.Types (+) :: LayoutStartCol -> LayoutStartCol -> LayoutStartCol # (-) :: LayoutStartCol -> LayoutStartCol -> LayoutStartCol # (*) :: LayoutStartCol -> LayoutStartCol -> LayoutStartCol # negate :: LayoutStartCol -> LayoutStartCol # abs :: LayoutStartCol -> LayoutStartCol # signum :: LayoutStartCol -> LayoutStartCol # fromInteger :: Integer -> LayoutStartCol # | |
Show LayoutStartCol Source # | |
Defined in Language.Haskell.GHC.ExactPrint.Types showsPrec :: Int -> LayoutStartCol -> ShowS # show :: LayoutStartCol -> String # showList :: [LayoutStartCol] -> ShowS # |