Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data AppView' arg = Application Expr [NamedArg arg]
- type AppView = AppView' Expr
- appView :: Expr -> AppView
- appView' :: Expr -> AppView' (AppInfo, Expr)
- maybeProjTurnPostfix :: Expr -> Maybe Expr
- unAppView :: AppView -> Expr
- data LamView = LamView [LamBinding] Expr
- lamView :: Expr -> LamView
- asView :: Pattern -> ([Name], Pattern)
- isSet :: Expr -> Bool
- unScope :: Expr -> Expr
- deepUnscope :: ExprLike a => a -> a
- deepUnscopeDecls :: [Declaration] -> [Declaration]
- deepUnscopeDecl :: Declaration -> [Declaration]
- class ExprLike a where
- recurseExpr :: Applicative m => (Expr -> m Expr -> m Expr) -> a -> m a
- foldExpr :: Monoid m => (Expr -> m) -> a -> m
- traverseExpr :: (Applicative m, Monad m) => (Expr -> m Expr) -> a -> m a
- mapExpr :: (Expr -> Expr) -> a -> a
Documentation
Application Expr [NamedArg arg] |
appView :: Expr -> AppView Source #
Gather applications to expose head and spine.
Note: everything is an application, possibly of itself to 0 arguments
asView :: Pattern -> ([Name], Pattern) Source #
Gather top-level AsP
atterns to expose underlying pattern.
deepUnscope :: ExprLike a => a -> a Source #
Remove ScopedExpr
wrappers everywhere.
NB: Unless the implementation of ExprLike
for clauses
has been finished, this does not work for clauses yet.
deepUnscopeDecls :: [Declaration] -> [Declaration] Source #
deepUnscopeDecl :: Declaration -> [Declaration] Source #
Traversal
class ExprLike a where Source #
Apply an expression rewriting to every subexpression, inside-out. See Agda.Syntax.Internal.Generic.
Nothing
recurseExpr :: Applicative m => (Expr -> m Expr -> m Expr) -> a -> m a Source #
The first expression is pre-traversal, the second one post-traversal.
default recurseExpr :: (Traversable f, ExprLike a', a ~ f a', Applicative m) => (Expr -> m Expr -> m Expr) -> a -> m a Source #
foldExpr :: Monoid m => (Expr -> m) -> a -> m Source #
traverseExpr :: (Applicative m, Monad m) => (Expr -> m Expr) -> a -> m a Source #