No that's correct.  I have to say the multiplate code is incredibly
hard to decipher.

On 25 February 2012 19:47, Sjoerd Visscher <sjo...@w3future.com> wrote:
> I don't understand what you mean.
>
>>>> ($[]) . foldFor expr freeVariablesPlate $ Add (Let ("x" := Con 1) (Add 
>>>> (EVar "x") (EVar "y"))) (EVar "x")
> (["y","x"],[])
>
> I.e. free variables y and x, no bound variables. Is that not correct?
>
> Sjoerd
>
> On Feb 25, 2012, at 7:15 PM, Thomas Schilling wrote:
>
>> That will give you the wrong answer for an expression like:
>>
>>  (let x = 1 in x + y) + x
>>
>> Unless you do a renaming pass first, you will end up both with a bound
>> "x" and a free "x".
>>
>> On 25 February 2012 16:29, Sjoerd Visscher <sjo...@w3future.com> wrote:
>>>
>>> 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
>>>
>>>
>>>
>>>
>>>
>>> _______________________________________________
>>> Haskell-Cafe mailing list
>>> Haskell-Cafe@haskell.org
>>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>>
>>
>> --
>> Push the envelope. Watch it bend.
>>
>
> --
> Sjoerd Visscher
> https://github.com/sjoerdvisscher/blog
>
>
>
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



-- 
Push the envelope. Watch it bend.

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to