| License | BSD-3-Clause |
|---|---|
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Swarm.Language.Syntax.Util
Contents
Description
Helper functions for working with Terms and Syntax
Synopsis
- mkOp :: Const -> Syntax -> Syntax -> Syntax
- mkOp' :: Const -> Term -> Term -> Term
- unfoldApps :: Syntax' ty -> NonEmpty (Syntax' ty)
- mkTuple :: [Syntax] -> Syntax
- unTuple :: Syntax' ty -> [Syntax' ty]
- erase :: Functor t => t ty -> t ()
- eraseS :: Syntax' ty -> Term
- freeVarsS :: forall ty. Traversal' (Syntax' ty) (Syntax' ty)
- freeVarsT :: forall ty. Traversal' (Syntax' ty) (Term' ty)
- freeVarsV :: Traversal' (Syntax' ty) Var
- mapFreeS :: Var -> (Syntax' ty -> Syntax' ty) -> Syntax' ty -> Syntax' ty
- locVarToSyntax' :: LocVar -> ty -> Syntax' ty
- asTree :: Data a => Syntax' a -> Tree (Syntax' a)
- measureAstSize :: Data a => Syntax' a -> Int
Documentation
mkOp :: Const -> Syntax -> Syntax -> Syntax Source #
Make an infix operation (e.g. 2 + 3) a curried function
application (e.g. ((+) 2) 3).
mkOp' :: Const -> Term -> Term -> Term Source #
Make an infix operation, discarding any location information
unfoldApps :: Syntax' ty -> NonEmpty (Syntax' ty) Source #
Turn function application chain into a list.
>>>syntaxWrap f = fmap (^. sTerm) . f . Syntax NoLoc>>>syntaxWrap unfoldApps (mkOp' Mul (TInt 1) (TInt 2)) -- 1 * 2TConst Mul :| [TInt 1,TInt 2]
Erasure
Term traversal
freeVarsS :: forall ty. Traversal' (Syntax' ty) (Syntax' ty) Source #
Traversal over those subterms of a term which represent free
variables. The S suffix indicates that it is a Traversal over
the Syntax nodes (which contain type and source location info)
containing free variables inside a larger Syntax value. Note
that if you want to get the list of all Syntax nodes
representing free variables, you can do so via .toListOf
freeVarsS
mapFreeS :: Var -> (Syntax' ty -> Syntax' ty) -> Syntax' ty -> Syntax' ty Source #
Apply a function to all free occurrences of a particular variable.
locVarToSyntax' :: LocVar -> ty -> Syntax' ty Source #