| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Retrie.ExactPrint.Annotated
Synopsis
- data Annotated ast
- astA :: Annotated ast -> ast
- seedA :: Annotated ast -> Int
- type AnnotatedHsDecl = Annotated (LHsDecl GhcPs)
- type AnnotatedHsExpr = Annotated (LHsExpr GhcPs)
- type AnnotatedHsType = Annotated (LHsType GhcPs)
- type AnnotatedImport = Annotated (LImportDecl GhcPs)
- type AnnotatedImports = Annotated [LImportDecl GhcPs]
- type AnnotatedModule = Annotated (Located (HsModule GhcPs))
- type AnnotatedPat = Annotated (LPat GhcPs)
- type AnnotatedStmt = Annotated (LStmt GhcPs (LHsExpr GhcPs))
- pruneA :: (Data ast, Monad m) => ast -> TransformT m (Annotated ast)
- graftA :: (Data ast, Monad m) => Annotated ast -> TransformT m ast
- transformA :: Monad m => Annotated ast1 -> (ast1 -> TransformT m ast2) -> m (Annotated ast2)
- trimA :: Data ast => Annotated ast -> Annotated ast
- setEntryDPA :: Default an => Annotated (LocatedAn an ast) -> DeltaPos -> Annotated (LocatedAn an ast)
- printA :: (Data ast, ExactPrint ast) => Annotated ast -> String
- printA' :: (Data ast, ExactPrint ast) => Annotated ast -> String
- showAstA :: (Data ast, ExactPrint ast) => Annotated ast -> String
- unsafeMkA :: ast -> Int -> Annotated ast
Annotated
Annotated packages an AST fragment with the annotations necessary to
 exactPrint or transform that AST.
Instances
| Foldable Annotated Source # | |
| Defined in Retrie.ExactPrint.Annotated Methods fold :: Monoid m => Annotated m -> m # foldMap :: Monoid m => (a -> m) -> Annotated a -> m # foldMap' :: Monoid m => (a -> m) -> Annotated a -> m # foldr :: (a -> b -> b) -> b -> Annotated a -> b # foldr' :: (a -> b -> b) -> b -> Annotated a -> b # foldl :: (b -> a -> b) -> b -> Annotated a -> b # foldl' :: (b -> a -> b) -> b -> Annotated a -> b # foldr1 :: (a -> a -> a) -> Annotated a -> a # foldl1 :: (a -> a -> a) -> Annotated a -> a # toList :: Annotated a -> [a] # length :: Annotated a -> Int # elem :: Eq a => a -> Annotated a -> Bool # maximum :: Ord a => Annotated a -> a # minimum :: Ord a => Annotated a -> a # | |
| Traversable Annotated Source # | |
| Defined in Retrie.ExactPrint.Annotated | |
| Functor Annotated Source # | |
| Data ast => Data (Annotated ast) Source # | |
| Defined in Retrie.ExactPrint.Annotated Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Annotated ast -> c (Annotated ast) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Annotated ast) # toConstr :: Annotated ast -> Constr # dataTypeOf :: Annotated ast -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Annotated ast)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Annotated ast)) # gmapT :: (forall b. Data b => b -> b) -> Annotated ast -> Annotated ast # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Annotated ast -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Annotated ast -> r # gmapQ :: (forall d. Data d => d -> u) -> Annotated ast -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Annotated ast -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Annotated ast -> m (Annotated ast) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Annotated ast -> m (Annotated ast) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Annotated ast -> m (Annotated ast) # | |
| (Data ast, Monoid ast) => Monoid (Annotated ast) Source # | |
| (Data ast, Monoid ast) => Semigroup (Annotated ast) Source # | |
| Default ast => Default (Annotated ast) Source # | |
| Defined in Retrie.ExactPrint.Annotated | |
seedA :: Annotated ast -> Int Source #
Name supply used by ghc-exactprint to generate unique locations.
Synonyms
type AnnotatedImport = Annotated (LImportDecl GhcPs) Source #
type AnnotatedImports = Annotated [LImportDecl GhcPs] Source #
Operations
pruneA :: (Data ast, Monad m) => ast -> TransformT m (Annotated ast) Source #
Encapsulate something in the current transformation into an Annotated
 thing. This is the inverse of graftT. For example:
splitHead :: Monad m => Annotated [a] -> m (Annotated a, Annotated [a]) splitHead l = fmap astA $ transformA l $ \(x:xs) -> do y <- pruneA x ys <- pruneA xs return (y, ys)
graftA :: (Data ast, Monad m) => Annotated ast -> TransformT m ast Source #
Graft an Annotated thing into the current transformation.
 The resulting AST will have proper annotations within the TransformT
 computation. For example:
mkDeclList :: IO (Annotated [LHsDecl GhcPs])
mkDeclList = do
  ad1 <- parseDecl "myId :: a -> a"
  ad2 <- parseDecl "myId x = x"
  transformA ad1 $ \ d1 -> do
    d2 <- graftA ad2
    return [d1, d2]transformA :: Monad m => Annotated ast1 -> (ast1 -> TransformT m ast2) -> m (Annotated ast2) Source #
Transform an Annotated thing.
trimA :: Data ast => Annotated ast -> Annotated ast Source #
Trim the annotation data to only include annotations for ast.
 (Usually, the annotation data is a superset of what is necessary.)
 Also freshens all source locations, so filename information
 in annotation keys is discarded.
Note: not commonly needed, but useful if you want to inspect the annotation data directly and don't want to wade through a mountain of output.
setEntryDPA :: Default an => Annotated (LocatedAn an ast) -> DeltaPos -> Annotated (LocatedAn an ast) Source #
printA :: (Data ast, ExactPrint ast) => Annotated ast -> String Source #
Exactprint an Annotated thing.
showAstA :: (Data ast, ExactPrint ast) => Annotated ast -> String Source #
showAst an Annotated thing.