On 11 September 2018 at 21:50, Rodrigo Stevaux <roehst@gmail.com> wrote:
It is easy to read an environment in applicative style, ie:

type Env = [(String, Int)]
data Term = Add Term Term | Number Int | Var String deriving Show
eval :: Term -> Env -> Int
eval (Add a b) = (+) <$> eval a <*> eval b
eval (Var name) = fetch name
eval (Number i) = pure i

fetch :: String -> Env -> Int
fetch name = fromJust . lookup name

But can the eval function change the Env being passed, as to implement
a "let" operation, without using monads? I tried I lot but ultimately
I resorted to (>>=) in the function monad:

bind f k = \r -> k (f r) r

I think what you mean is something like: can we extend Term with a let binding expression and implement eval using applicative interface without (>>=)?

I think we can, and it's a bit awkward, but possible, because of the Reader monad.

A trivial way of introducing let that does not manifest the issues you point out is

data Term = Add Term Term | Number Int | Var String | Let String Int Term

You can then implement the case for eval with

eval (Let s v t) = eval t . update s v

where the function update simply updates a value in the associative list. A simple implementation is:

update :: Ord a => a -> b -> [(a, b)] -> [(a, b)]
update s v = nubBy eqFst . insertBy cmpFst (s, v)
  where
    eqFst  x y = (==)    (fst x) (fst y)
    cmpFst x y = compare (fst x) (fst y)

Of course, this does not need the monad interface, but it does not really need the applicative interface to evaluate the term either (except indirectly in eval t).

Perhaps a more interesting alternative is:

data Term = ... | LetT String Term Term

where the other cases in Term remain the same. Now you need to eval the first term to change the environment, which is, I guess, what you wanted?

You can do this combining composition with applicative:

eval (LetT s t1 t2) = eval t2 . (update' <*> pure s <*> eval t1)
  where
    update' :: Env -> String -> Int -> Env
    update' e s v = update s v e

And a test (which is equivalent to let b = a + 8 in b + 1):

*Main> eval (LetT "b" (Add (Number 8) (Var "a")) (Add (Number 1) (Var "b"))) [("a", 7)]
16

 

I do not think so, because in applicative style each operand can have
an effect (reading the environment) but can not affect other operands
(including the next ones), i.e., there is no notion of sequencing in
applicatives
Is this reasoning right?

As Tom pointed out, not 100%, not generally, I think. This seems to be specific to the reader monad.

All the best,

Ivan