[Haskell-cafe] Re: implementing recursive let

2009-11-28 Thread Ben Franksen
Hi Ryan,

first, to get this out of the way, you wrote:

> Also, your definition of "Function" seems to have problems with
> scoping; unless you intended to make a dynamically scoped language,

No, absolutely not! In fact, the whole exercise has been born out of
frustration with certain ad-hoc extensions to an already evil
domain-specific (macro substitution) language -- the extension being to add
dynamically scoped local variables; and the basic evilness to allow
substitution to occur in variable names (similar to make) as a poor man's
substitute for functional abstraction. This makes for extremely cryptic
programs whose result is very hard to predict. My aim is to show that there
is a better way.

> (Value -> Eval Value) seems very likely to get evaluated in the
> context it is called in.

Fortunately, this is not the case, as I explicitly capture the evironment at
the definition site, ignoring the one at the call site:

eval (Lam parm body) = do
  env <- ask
  return $ Function (\val -> local (\_ -> M.insert parm val env) (eval
body))

Now to the interesting part:

> Now the question is, what do you want to happen when given a malformed
> let expression?  I am pretty sure that you need more complicated
> flow-control here in order to get the result.  I believe you are on
> the right track with continuations.

My problem is that I have never really become comfortable with
continuations; just couldn't wrap my head around all the nested lambdas
involved. Is there a nice tutorial (preferably one of those functional
perls, I love them) that explains how CPS actually works to produce those
wonderful effects, like jumping around, fixing evaluation order and
whatnot? I tried to follow the recent explanations by Jacques Carette and
Oleg Kiselyov on this list but I must admit that I understood nought.

> Here is a question; what should these expressions do?
>> let y = x; x = 1 in y
>> let y = x x; x = 1 in x
>> let x = x in x
> 
> The last one is quite telling; I can see three possible behaviors here:
> 
> 1) Loop
> 2) return some simple undefined value
> 3) Give an error "blackhole"
> 
> I will note that behavior (1) seems very difficult to achieve with
> your current monad stack; eval (Var x) terminates simply by looking up
> the value in the environment.
> 
> I think you need to think hard about evaluation order and decide what
> you really want to happen.  The simplest answer, if you want to stay
> with strict evaluation, is probably to only allow recursive *function*
> definitions.  This way you can delay fully initializing the
> environment until after you've finished evaluating the functions
> themselves.

Thanks, Ryan. This got me thinking about the right questions. I found out
that what I really want is a mixture of lazy and strict evaluation: I want
variable definitions in a let expression to be lazy, but application of
functions to be strict. (I don't know whether this kind of mixture has been
used before.) Thus

>> let y = x; x = 1 in y

should evaluate to  1 . I want the meaning of declarations on the same level
to be independent of their relative order. This is a purely functional
language, after all, so why should it matter in which order things are
defined?

>> let y = x x; x = 1 in x

Here  y  is never used, so again this evaluates to  1 .

>> let x = x in x

This should loop (or maybe better detected as a failure i.e. backhole), but
only if and when x is used, either in an application or as the final result
of the program. (In the former case it doesn't make a difference whether  x 
is used in function or in argument position.)

  ***

Thinking about how to make it _explicit_ in my code that application is
strict, whereas variables are lazy, I saw that this needs a change in the
type of environments. It used to be a map from variable names to _values_,
i.e. evaluated expressions. If I change this to a map from variable names
to either thunks (i.e. unevaluated expressions) or (evaluated) values, then
everything else falls smoothly into place; no need for mdo/mfix anymore,
thus no need for fiddling with ErrorT internals to convince it that
variable lookup always succeeds, and last not least all my examples behave
as I expect them to do (see attached code).

So, in a way I /have/ (finally) given up ;-) because variables are now
(internally) mutable cells: when a variable is demanded (e.g. by an
application) it gets mutated from thunk to value. Could as well revert to a
Reader monad and use STRefs for efficiency. (Or maybe I will finally try to
understand how to use continuations for stuff like this.)

I have learned (at least) this: The problem with using the host language's
lazyness for implementing lazyness in the defined language is that the
former is not directly observable. Thus it works fine as long as you buy
the whole package, i.e. either make sure that there can't be a failure, or
else use not only the built-in evaluation order but also the built-in
failure mode: error, pattern mat

Re: [Haskell-cafe] Re: implementing recursive let

2009-11-26 Thread Derek Elkins
On Wed, Nov 25, 2009 at 3:48 PM, Ben Franksen  wrote:
> Derek Elkins wrote:
>> The following code works fine for me, so it seems you are missing some
>> details that may help.
>> [...snip code...]
>
> Thank you! Indeed I did simplify the code when writing the message --
> because I thought that those other bits could not possibly be at
> fault... ;-)
>
> *trying out many changes to my own code and yours*
>
> Ok, I finally found it. What actually made the difference was the case for
> variables:
>
> Your version is
>
>> eval (Var x)   = gets (fromJust . M.lookup x)
>
> which is suitably lazy, whereas mine was (more or less)
>
>> eval e@(Var name) = do
>>   env <- ask
>>   case M.lookup name env of
>>     Nothing  -> do
>>       -- undefined variable reference
>>       warning ("reference to undefined variable " ++ show name)
>>       let val = Data ""
>>       modify (M.insert name val)
>>       return val
>>     Just val -> return val
>
> Note that whatever I do in the 'Nothing' case is irrelevant, your code with
> the Var case replaced by
>
>> eval e@(Var name) = do
>>   env <- ask
>>   case M.lookup name env of
>>     Just val -> return val
>
> loops as well.
>
> My problem is that I still don't understand why this is so! I know of course
> that pattern matching is strict, but I thought this should be ok here,
> since I evaluate the declarations _before_ the body, so when evaluation of
> the body demands the variable, it will be defined.
>
> What am I missing?

The problem is the liftM2 in the Let branch of eval.  You are
executing the body while making the bindings, so you are trying to
look up x while you are still trying to bind it.  One solution is to
move the execution of the body after the binding as in:

eval (Let decls body) = mdo
 let (names,exprs) = unzip decls
 updateEnv env = foldr (uncurry M.insert) env $ zip names values
 values <- local updateEnv $ mapM eval exprs
 local updateEnv $ eval body
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: implementing recursive let

2009-11-26 Thread Ben Franksen
Ben Franksen wrote:
> My problem is that I still don't understand why this is so! I know of
> course that pattern matching is strict, but I thought this should be ok
> here, since I evaluate the declarations _before_ the body, so when
> evaluation of the body demands the variable, it will be defined.

Another data point: It /has/ something to do with ErrorT. If I remove the
ErrorT from the monad stack it works, even with the pattern matching in the
variable lookup:

newtype Eval a = Eval {
unEval :: {- ErrorT String -} (StateT Env (Writer [String])) a
  } deriving (
Monad,
MonadFix,
MonadWriter [String], -- for warnings & other messages
MonadState Env{- ,
MonadError String -}
  )

runEval :: Eval Value -> {- Either String -} Value
runEval = fst . runWriter . flip evalStateT M.empty . {- runErrorT . -}
unEval

*Main> evaluate example 
1

I am still lost as to how to make this work with ErrorT.

Cheers
Ben

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


[Haskell-cafe] Re: implementing recursive let

2009-11-25 Thread Ben Franksen
Derek Elkins wrote:
> The following code works fine for me, so it seems you are missing some
> details that may help.
> [...snip code...]

Thank you! Indeed I did simplify the code when writing the message --
because I thought that those other bits could not possibly be at
fault... ;-)

*trying out many changes to my own code and yours*

Ok, I finally found it. What actually made the difference was the case for
variables:

Your version is

> eval (Var x)   = gets (fromJust . M.lookup x)

which is suitably lazy, whereas mine was (more or less)

> eval e@(Var name) = do
>   env <- ask
>   case M.lookup name env of
> Nothing  -> do
>   -- undefined variable reference
>   warning ("reference to undefined variable " ++ show name)
>   let val = Data ""
>   modify (M.insert name val)
>   return val
> Just val -> return val

Note that whatever I do in the 'Nothing' case is irrelevant, your code with
the Var case replaced by

> eval e@(Var name) = do
>   env <- ask
>   case M.lookup name env of
> Just val -> return val

loops as well.

My problem is that I still don't understand why this is so! I know of course
that pattern matching is strict, but I thought this should be ok here,
since I evaluate the declarations _before_ the body, so when evaluation of
the body demands the variable, it will be defined.

What am I missing?

Cheers
Ben

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