[Haskell-cafe] Using multiplate to get free variables from a syntax tree

Sjoerd Visscher sjoerd at w3future.com
Sat Feb 25 17:29:46 CET 2012


On Feb 24, 2012, at 10:09 PM, Stephen Tetley wrote:

> I'm not familiar with Multiplate either, but presumably you can
> descend into the decl - collect the bound vars, then descend into the
> body expr. 

> Naturally you would need a monadic traversal
> rather than an applicative one...


It turns out the traversal is still applicative. What we want to collect are the free and the declared variables, given the bound variables. ('Let' will turn the declared variables into bound variables.) So the type is [Var] -> ([Var], [Var]). Note that this is a Monoid, thanks to the instances for ((->) r), (,) and []. So we can use the code from preorderFold, but add an exception for the 'Let' case.

freeVariablesPlate :: Plate (Constant ([Var] -> ([Var], [Var])))
freeVariablesPlate = handleLet (varPlate `appendPlate` multiplate freeVariablesPlate)
  where 
    varPlate = Plate {
      expr = \x -> Constant $ \bounded -> ([ v | EVar v <- [x], v `notElem` bounded], []),
      decl = \x -> Constant $ const ([], [ v | v := _ <- [x]])
    }
    handleLet plate = plate { expr = exprLet }
      where
        exprLet (Let d e) = Constant $ \bounded -> 
          let
            (freeD, declD) = foldFor decl plate d bounded
            (freeE, _)     = foldFor expr plate e (declD ++ bounded)
          in
            (freeD ++ freeE, [])
        exprLet x = expr plate x

freeVars :: Expr -> [Var]
freeVars = fst . ($ []) . foldFor expr freeVariablesPlate

>>> freeVars $ Let ("x" := Con 42) (Add (EVar "x") (EVar "y"))
["y"]

--
Sjoerd Visscher
https://github.com/sjoerdvisscher/blog







More information about the Haskell-Cafe mailing list