retrie-1.2.3: A powerful, easy-to-use codemodding tool for Haskell.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Retrie.ExactPrint

Description

Provides consistent interface with ghc-exactprint.

Synopsis

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

parseDecl :: LibDir -> String -> IO AnnotatedHsDecl Source #

Parse a top-level HsDecl.

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.

Primitive Transformations

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 #

Utils

debug :: c -> String -> c Source #

Annotated AST

ghc-exactprint re-exports

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.

data Comment #

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

Instances details
Data Comment 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

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 :: 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 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

Outputable Comment 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

Methods

ppr :: Comment -> SDoc #

Eq Comment 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

Methods

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

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

Ord Comment 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

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.

Methods

getAnnotationEntry :: a -> Entry #

setAnnotationAnchor :: a -> Anchor -> EpAnnComments -> a #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => a -> EP w m a #

Instances

Instances details
ExactPrint Void 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: Void -> Entry #

setAnnotationAnchor :: Void -> Anchor -> EpAnnComments -> Void #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => Void -> EP w m Void #

ExactPrint FastString 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint HsDocString 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint HsDocStringChunk 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint CCallConv 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: CCallConv -> Entry #

setAnnotationAnchor :: CCallConv -> Anchor -> EpAnnComments -> CCallConv #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => CCallConv -> EP w m CCallConv #

ExactPrint CExportSpec 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint Safety 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: Safety -> Entry #

setAnnotationAnchor :: Safety -> Anchor -> EpAnnComments -> Safety #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => Safety -> EP w m Safety #

ExactPrint StringLiteral 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint Role 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: Role -> Entry #

setAnnotationAnchor :: Role -> Anchor -> EpAnnComments -> Role #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => Role -> EP w m Role #

ExactPrint ModuleName 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint HsIPName 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsIPName -> Entry #

setAnnotationAnchor :: HsIPName -> Anchor -> EpAnnComments -> HsIPName #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsIPName -> EP w m HsIPName #

ExactPrint DataFamInstDeclWithContext 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: DataFamInstDeclWithContext -> Entry #

setAnnotationAnchor :: DataFamInstDeclWithContext -> Anchor -> EpAnnComments -> DataFamInstDeclWithContext #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => DataFamInstDeclWithContext -> EP w m DataFamInstDeclWithContext #

ExactPrint (BooleanFormula (LocatedN RdrName)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint a => ExactPrint (LocatedA a) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: LocatedA a -> Entry #

setAnnotationAnchor :: LocatedA a -> Anchor -> EpAnnComments -> LocatedA a #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => LocatedA a -> EP w m (LocatedA a) #

ExactPrint a => ExactPrint (LocatedC a) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: LocatedC a -> Entry #

setAnnotationAnchor :: LocatedC a -> Anchor -> EpAnnComments -> LocatedC a #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => LocatedC a -> EP w m (LocatedC a) #

ExactPrint (LocatedL (BooleanFormula (LocatedN RdrName))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (Match GhcPs (LocatedA body)) => ExactPrint (LocatedL [LocatedA (Match GhcPs (LocatedA body))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)))]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (IE GhcPs)]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedL [LocatedA (ConDeclField GhcPs)]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedN RdrName) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedP OverlapMode) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedP CType) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedP (WarningTxt GhcPs)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint a => ExactPrint (Located a)

Bare Located elements are simply stripped off without further processing.

Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: Located a -> Entry #

setAnnotationAnchor :: Located a -> Anchor -> EpAnnComments -> Located a #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => Located a -> EP w m (Located a) #

ExactPrint (HsModule GhcPs)

'Located (HsModule GhcPs)' corresponds to ParsedSource

Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (HsBind GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsBind GhcPs -> Entry #

setAnnotationAnchor :: HsBind GhcPs -> Anchor -> EpAnnComments -> HsBind GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsBind GhcPs -> EP w m (HsBind GhcPs) #

ExactPrint (HsIPBinds GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (HsLocalBinds GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (IPBind GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: IPBind GhcPs -> Entry #

setAnnotationAnchor :: IPBind GhcPs -> Anchor -> EpAnnComments -> IPBind GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => IPBind GhcPs -> EP w m (IPBind GhcPs) #

ExactPrint (RecordPatSynField GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (Sig GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: Sig GhcPs -> Entry #

setAnnotationAnchor :: Sig GhcPs -> Anchor -> EpAnnComments -> Sig GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => Sig GhcPs -> EP w m (Sig GhcPs) #

ExactPrint (AnnDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (ClsInstDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (ConDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (DefaultDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (DerivClauseTys GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (DerivDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (DerivStrategy GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (DocDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (FamilyDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (ForeignDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (ForeignExport GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (ForeignImport GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (FunDep GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: FunDep GhcPs -> Entry #

setAnnotationAnchor :: FunDep GhcPs -> Anchor -> EpAnnComments -> FunDep GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => FunDep GhcPs -> EP w m (FunDep GhcPs) #

ExactPrint (HsDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsDecl GhcPs -> Entry #

setAnnotationAnchor :: HsDecl GhcPs -> Anchor -> EpAnnComments -> HsDecl GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsDecl GhcPs -> EP w m (HsDecl GhcPs) #

ExactPrint (HsDerivingClause GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (InjectivityAnn GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (InstDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (RoleAnnotDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (RuleBndr GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (RuleDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (RuleDecls GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (SpliceDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (StandaloneKindSig GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (TyClDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (TyFamInstDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (WarnDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (WarnDecls GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (DotFieldOcc GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (FieldLabelStrings GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (HsCmd GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsCmd GhcPs -> Entry #

setAnnotationAnchor :: HsCmd GhcPs -> Anchor -> EpAnnComments -> HsCmd GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsCmd GhcPs -> EP w m (HsCmd GhcPs) #

ExactPrint (HsCmdTop GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (HsExpr GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsExpr GhcPs -> Entry #

setAnnotationAnchor :: HsExpr GhcPs -> Anchor -> EpAnnComments -> HsExpr GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsExpr GhcPs -> EP w m (HsExpr GhcPs) #

ExactPrint (HsPragE GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (HsTupArg GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (HsUntypedSplice GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (IE GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: IE GhcPs -> Entry #

setAnnotationAnchor :: IE GhcPs -> Anchor -> EpAnnComments -> IE GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => IE GhcPs -> EP w m (IE GhcPs) #

ExactPrint (IEWrappedName GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (ImportDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (HsOverLit GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (HsConPatTyArg GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (Pat GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: Pat GhcPs -> Entry #

setAnnotationAnchor :: Pat GhcPs -> Anchor -> EpAnnComments -> Pat GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => Pat GhcPs -> EP w m (Pat GhcPs) #

ExactPrint (AmbiguousFieldOcc GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (ConDeclField GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (FieldOcc GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (HsForAllTelescope GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (HsPatSigType GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (HsSigType GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (HsType GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsType GhcPs -> Entry #

setAnnotationAnchor :: HsType GhcPs -> Anchor -> EpAnnComments -> HsType GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsType GhcPs -> EP w m (HsType GhcPs) #

ExactPrint a => ExactPrint (Maybe a) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: Maybe a -> Entry #

setAnnotationAnchor :: Maybe a -> Anchor -> EpAnnComments -> Maybe a #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => Maybe a -> EP w m (Maybe a) #

ExactPrint a => ExactPrint [a] 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: [a] -> Entry #

setAnnotationAnchor :: [a] -> Anchor -> EpAnnComments -> [a] #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => [a] -> EP w m [a] #

(ExactPrint (HsFieldBind (LocatedAn NoEpAnns (a GhcPs)) body), ExactPrint (HsFieldBind (LocatedAn NoEpAnns (b GhcPs)) body)) => ExactPrint (Either [LocatedA (HsFieldBind (LocatedAn NoEpAnns (a GhcPs)) body)] [LocatedA (HsFieldBind (LocatedAn NoEpAnns (b GhcPs)) body)]) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint a => ExactPrint (WithHsDocIdentifiers a GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint a => ExactPrint (LocatedAn NoEpAnns a) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (HsValBindsLR GhcPs GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (PatSynBind GhcPs GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint body => ExactPrint (FamEqn GhcPs body) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: FamEqn GhcPs body -> Entry #

setAnnotationAnchor :: FamEqn GhcPs body -> Anchor -> EpAnnComments -> FamEqn GhcPs body #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => FamEqn GhcPs body -> EP w m (FamEqn GhcPs body) #

ExactPrint (GRHS GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (GRHS GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (Match GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (Match GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (ParStmtBlock GhcPs GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint body => ExactPrint (HsFieldBind (LocatedAn NoEpAnns (FieldLabelStrings GhcPs)) body) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (LocatedA body) => ExactPrint (HsFieldBind (LocatedAn NoEpAnns (AmbiguousFieldOcc GhcPs)) (LocatedA body)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint body => ExactPrint (HsFieldBind (LocatedAn NoEpAnns (FieldOcc GhcPs)) body) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint body => ExactPrint (HsRecFields GhcPs body) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsRecFields GhcPs body -> Entry #

setAnnotationAnchor :: HsRecFields GhcPs body -> Anchor -> EpAnnComments -> HsRecFields GhcPs body #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsRecFields GhcPs body -> EP w m (HsRecFields GhcPs body) #

(ExactPrint tm, ExactPrint ty, Outputable tm, Outputable ty) => ExactPrint (HsArg tm ty) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsArg tm ty -> Entry #

setAnnotationAnchor :: HsArg tm ty -> Anchor -> EpAnnComments -> HsArg tm ty #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsArg tm ty -> EP w m (HsArg tm ty) #

ExactPrintTVFlag flag => ExactPrint (HsOuterTyVarBndrs flag GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint a => ExactPrint (HsScaled GhcPs a) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsScaled GhcPs a -> Entry #

setAnnotationAnchor :: HsScaled GhcPs a -> Anchor -> EpAnnComments -> HsScaled GhcPs a #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsScaled GhcPs a -> EP w m (HsScaled GhcPs a) #

ExactPrintTVFlag flag => ExactPrint (HsTyVarBndr flag GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: HsTyVarBndr flag GhcPs -> Entry #

setAnnotationAnchor :: HsTyVarBndr flag GhcPs -> Anchor -> EpAnnComments -> HsTyVarBndr flag GhcPs #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => HsTyVarBndr flag GhcPs -> EP w m (HsTyVarBndr flag GhcPs) #

ExactPrint body => ExactPrint (HsWildCardBndrs GhcPs body) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

ExactPrint (SourceText, RuleName) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

(ExactPrint (LocatedA (body GhcPs)), Anno (StmtLR GhcPs GhcPs (LocatedA (body GhcPs))) ~ SrcSpanAnnA, Anno [GenLocated SrcSpanAnnA (StmtLR GhcPs GhcPs (LocatedA (body GhcPs)))] ~ SrcSpanAnnL, ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (body GhcPs)))])) => ExactPrint (StmtLR GhcPs GhcPs (LocatedA (body GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

Methods

getAnnotationEntry :: StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) -> Entry #

setAnnotationAnchor :: StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) -> Anchor -> EpAnnComments -> StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) #

exact :: forall (m :: Type -> Type) w. (Monad m, Monoid w) => StmtLR GhcPs GhcPs (LocatedA (body GhcPs)) -> EP w m (StmtLR GhcPs GhcPs (LocatedA (body GhcPs))) #

class Monad m => HasTransform (m :: Type -> Type) where #

Used to integrate a Transform into other Monad stacks

Methods

liftT :: Transform a -> m a #

Instances

Instances details
Monad m => HasTransform (TransformT m) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

liftT :: Transform a -> TransformT m a #

data WithWhere #

Constructors

WithWhere 
WithoutWhere 

Instances

Instances details
Show WithWhere 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Eq WithWhere 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

class Data t => HasDecls t where #

Provide a means to get and process the immediate child declartions of a given AST element.

Methods

hsDecls :: forall (m :: Type -> Type). Monad m => t -> TransformT m [LHsDecl GhcPs] #

Return the HsDecls 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

Instances details
HasDecls ParsedSource 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

hsDecls :: forall (m :: Type -> Type). Monad m => ParsedSource -> TransformT m [LHsDecl GhcPs] #

replaceDecls :: forall (m :: Type -> Type). Monad m => ParsedSource -> [LHsDecl GhcPs] -> TransformT m ParsedSource #

HasDecls (LocatedA (HsExpr GhcPs)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

hsDecls :: forall (m :: Type -> Type). Monad m => LocatedA (HsExpr GhcPs) -> TransformT m [LHsDecl GhcPs] #

replaceDecls :: forall (m :: Type -> Type). Monad m => LocatedA (HsExpr GhcPs) -> [LHsDecl GhcPs] -> TransformT m (LocatedA (HsExpr GhcPs)) #

HasDecls (LocatedA (Match GhcPs (LocatedA (HsExpr GhcPs)))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

HasDecls (LocatedA (Stmt GhcPs (LocatedA (HsExpr GhcPs)))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

newtype TransformT (m :: Type -> Type) a #

Monad transformer version of Transform monad

Constructors

TransformT 

Fields

Instances

Instances details
MonadTrans TransformT 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

lift :: Monad m => m a -> TransformT m a #

Monad m => MonadReader () (TransformT m) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

ask :: TransformT m () #

local :: (() -> ()) -> TransformT m a -> TransformT m a #

reader :: (() -> a) -> TransformT m a #

Monad m => MonadState Int (TransformT m) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

get :: TransformT m Int #

put :: Int -> TransformT m () #

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

MonadFail m => MonadFail (TransformT m) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

fail :: String -> TransformT m a #

Monad m => Applicative (TransformT m) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

pure :: a -> TransformT m a #

(<*>) :: TransformT m (a -> b) -> TransformT m a -> TransformT m b #

liftA2 :: (a -> b -> c) -> TransformT m a -> TransformT m b -> TransformT m c #

(*>) :: TransformT m a -> TransformT m b -> TransformT m b #

(<*) :: TransformT m a -> TransformT m b -> TransformT m a #

Functor m => Functor (TransformT m) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

fmap :: (a -> b) -> TransformT m a -> TransformT m b #

(<$) :: a -> TransformT m b -> TransformT m a #

Monad m => Monad (TransformT m) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

(>>=) :: TransformT m a -> (a -> TransformT m b) -> TransformT m b #

(>>) :: TransformT m a -> TransformT m b -> TransformT m b #

return :: a -> TransformT m a #

Monad m => HasTransform (TransformT m) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

liftT :: Transform a -> TransformT m a #

Monad m => MonadWriter [String] (TransformT m) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

writer :: (a, [String]) -> TransformT m a #

tell :: [String] -> TransformT m () #

listen :: TransformT m a -> TransformT m (a, [String]) #

pass :: TransformT m (a, [String] -> [String]) -> TransformT m a #

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.

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

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)

showAst :: Data a => a -> String #

exactPrint :: ExactPrint ast => ast -> String #

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.

runTransform :: Transform a -> (a, Int, [String]) #

Run a transformation in the Transform monad, returning the updated annotations and any logging generated via logTr

runTransformT :: TransformT m a -> m (a, Int, [String]) #

runTransformFrom :: Int -> Transform a -> (a, Int, [String]) #

Run a transformation in the Transform monad, returning the updated annotations and any logging generated via logTr, allocating any new SrcSpans from the provided initial value.

runTransformFromT :: Int -> TransformT m a -> m (a, Int, [String]) #

Run a monad transformer stack for the TransformT monad transformer

hoistTransform :: (forall x. m x -> n x) -> TransformT m a -> TransformT n a #

Change inner monad of TransformT.

logTr :: forall (m :: Type -> Type). Monad m => String -> TransformT m () #

Log a string to the output of the Monad

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

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.

isUniqueSrcSpan :: SrcSpan -> Bool #

Test whether a given SrcSpan was generated by uniqueSrcSpanT

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.

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

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

wrapSig :: LSig GhcPs -> LHsDecl GhcPs #

Convert a LSig into a LHsDecl

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

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) a. Monad m => [LocatedA a] -> TransformT m [LocatedA a] #

noAnnSrcSpanDP :: Monoid ann => SrcSpan -> DeltaPos -> SrcSpanAnn' (EpAnn ann) #

Create a SrcSpanAnn with a MovedAnchor operation using the given DeltaPos.

insertAtStart :: HasDecls ast => ast -> LHsDecl GhcPs -> Transform ast #

Insert a declaration at the beginning or end of 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

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

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

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.

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.

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.

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.

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.

modifyValD :: HasTransform m => SrcSpan -> Decl -> (PMatch -> [Decl] -> m ([Decl], Maybe t)) -> m (Decl, Maybe t) #

Modify a LHsBind wrapped in a ValD. For a PatBind the declarations are extracted and returned after modification. For a FunBind the supplied SrcSpan is used to identify the specific Match to be transformed, for when there are multiple of them.

modifyDeclsT :: (HasDecls t, HasTransform m) => ([LHsDecl GhcPs] -> m [LHsDecl GhcPs]) -> t -> m t #

Apply a transformation to the decls contained in t

showGhc :: Outputable a => a -> String #

debugEnabledFlag :: Bool #

Global switch to enable debug tracing in ghc-exactprint Delta / Print

debugM :: Monad m => String -> m () #

warn :: c -> String -> c #

isGoodDelta :: DeltaPos -> Bool #

A good delta has no negative values.

ss2delta :: Pos -> RealSrcSpan -> DeltaPos #

Create a delta from the current position to the start of the given RealSrcSpan.

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

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

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

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

isPointSrcSpan :: RealSrcSpan -> Bool #

Checks whether a SrcSpan has zero length.

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.

needsWhere :: forall (p :: Pass). DataDefnCons (LConDecl (GhcPass p)) -> Bool #

cmpComments :: Comment -> Comment -> Ordering #

Must compare 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

sortEpaComments :: [LEpaComment] -> [LEpaComment] #

Sort, comparing without span filenames, for CPP injected comments with fake filename

mkKWComment :: AnnKeywordId -> EpaLocation -> Comment #

Makes a comment which originates from a specific keyword.

isKWComment :: Comment -> Bool #

Detects a comment which originates from a specific keyword.

dpFromString :: String -> DeltaPos #

Calculates the distance from the start of a string to the end of a string.

moveAnchor :: Monoid b => SrcAnn a -> SrcAnn b #

Version of l2l that preserves the anchor, immportant if it has an updated AnchorOperation