Do lazy imperative programming languages exist? If not, why not? - lazy-evaluation

If I'm not mistaken, the concept of a "lazy imperative programming language" makes perfect sense.
For example, I envision that the following code should cause the program to print "7"
a <- 1
b <- a+5
a <- 2
print([b])
while the following code should cause the program to print "6"
a <- 1
b <- [a+5]
a <- 2
print(b)
and the following code should cause the program to print the string "a+5"
a <- 1
b <- a+5
a <- 2
print(b)
The idea is that [..] flattens an expression by performing an evaluation, using the current values of each variable.
Question. Do lazy imperative programming languages exist, and if not, why not? Is there any particular reason why they cannot ever exist?

Related

F#: how to calculate a subset using filtering predicate?

E.g.
For integer numbers between 1 and 10, select 3 numbers that:
1. Sum of these 3 numbers equals to 24
2. These 3 numbers could build a right triangle.
How to use F# to get these 3 numbers?
I know for Haskell this is very simple:
Prelude> let rightTriangle=[(a,b,c)|c<-[1..10],a<-[1..c],b<-[1..a],a^2+b^2==c^2,a+b+c==24]
Prelude> rightTriangle
The solution is
[(8,6,10)]
I'm not sure if
F# could help to generate a Cartesian product conveniently?
F# could add different filter conditions inside one expression?
So, how to implement it with F# conveniently?
Thanks.
The direct equivalent of the Haskell version in F# would be to use list comprehensions:
let rightTriangle=
[for c in 1 .. 10 do
for a in 1 .. c do
for b in 1 .. a do
if pown a 2 + pown b 2 = pown c 2 && a + b + c = 24 then
yield a, b, c ]
Generally speaking, F# comprehensions are closer to "normal F# language" rather than being a special language feature (if you drop the [ .. ] around it, it looks almost like imperative iteration using loops).
The for construct corresponds to a <- 1 .. 10, but you need to nest multiple fors if you want to bind multiple variables
The if construct corresponds to the filtering using the == bit in Haskell
The yield specifies what values should be returned from the list comprehension

transferring an imperative for-loop into idiomatic haskell

I have some difficulties to transfer imperative algorithms into a functional style. The main concept that I cannot wrap my head around is how to fill sequences with values according to their position in the sequence. How would an idiomatic solution for the following algorithm look in Haskell?
A = unsigned char[256]
idx <- 1
for(i = 0 to 255)
if (some_condition(i))
A[i] <- idx
idx++
else
A[i] = 0;
The algorithm basically creates a lookup table for the mapping function of a histogram.
Do you know any resources which would help me to understand this kind of problem better?
One of the core ideas in functional programming is to express algorithms as data transformations. In a lazy language like Haskell, we can even go a step further and think of lazy data structures as reified computations. In a very real sense, Haskell's lists are more like loops than normal linked lists: they can be calculated incrementally and don't have to exist in memory all at once. At the same time, we still get many of the advantages of having a data type like that ability to pass it around and inspect it with pattern matching.
With this in mind, the "trick" for expressing a for-loop with an index is to create a list of all the values it can take. Your example is probably the simplest case: i takes all the values from 0 to 255, so we can use Haskell's built-in notation for ranges:
[0..255]
At a high level, this is Haskell's equivalent of for (i = 0 to 255); we can then execute the actual logic in the loop by traversing this list either by a recursive function or a higher-order function from the standard library. (The second option is highly preferred.)
This particular logic is a good fit for a fold. A fold lets us take in a list item by item and build up a result of some sort. At each step, we get a list item and the value of our built-up result so far. In this particular case, we want to process the list from left to right while incrementing an index, so we can use foldl; the one tricky part is that it will produce the list backwards.
Here's the type of foldl:
foldl :: (b -> a -> b) -> b -> [a] -> b
So our function takes in our intermediate value and a list element and produces an updated intermediate value. Since we're constructing a list and keeping track of an index, our intermediate value will be a pair that contains both. Then, once we have the final result, we can ignore the idx value and reverse the final list we get:
a = let (result, _) = foldl step ([], 1) [0..255] in reverse result
where step (a, idx) i
| someCondition i = (idx:a, idx + 1)
| otherwise = (0:a, idx)
In fact, the pattern of transforming a list while keeping track of some intermediate state (idx in this case) is common enough so that it has a function of its own in terms of the State type. The core abstraction is a bit more involved (read through ["You Could Have Invented Monads"][you] for a great introduction), but the resulting code is actually quite pleasant to read (except for the imports, I guess :P):
import Control.Applicative
import Control.Monad
import Control.Monad.State
a = evalState (mapM step [0..255]) 1
where step i
| someCondition i = get <* modify (+ 1)
| otherwise = return 0
The idea is that we map over [0..255] while keeping track of some state (the value of idx) in the background. evalState is how we put all the plumbing together and just get our final result. The step function is applied to each input list element and can also access or modify the state.
The first case of the step function is interesting. The <* operator tells it to do the thing on the left first, the thing on the right second but return the value on the left. This lets us get the current state, increment it but still return the value we got before it was incremented. The fact that our notion of state is a first-class entity and we can have library functions like <* is very powerful—I've found this particular idiom really useful for traversing trees, and other similar idioms have been quite useful for other code.
There are several ways to approach this problem depending on what data structure you want to use. The simplest one would probably be with lists and the basic functions available in Prelude:
a = go 1 [] [0..255]
where
go idx out [] = out
go idx out (i:is) =
if condition i
then go (idx + 1) (out ++ [idx]) is
else go idx (out ++ [0]) is
This uses the worker pattern with two accumulators, idx and out, and it traverses down the last parameter until no more elements are left, then returns out. This could certainly be converted into a fold of some sort, but in any case it won't be very efficient, appending items to a list with ++ is very inefficient. You could make it better by using idx : out and 0 : out, then using reverse on the output of go, but it still isn't an ideal solution.
Another solution might be to use the State monad:
a = flip runState 1 $ forM [0..255] $ \i -> do
idx <- get
if condition i
then do
put $ idx + 1 -- idx++
return idx -- A[i] = idx
else return 0
Which certainly looks a lot more imperative. The 1 in flip runState 1 is indicating that your initial state is idx = 1, then you use forM (which looks like a for loop but really isn't) over [0..255], the loop variable is i, and then it's just a matter of implementing the rest of the logic.
If you want to go a lot more advanced you could use the StateT and ST monads to have an actual mutable array with a state at the same time. The explanation of how this works is far beyond the scope of this answer, though:
import Control.Monad.State
import Control.Monad.ST
import qualified Data.Vector as V
import qualified Data.Vector.Mutable as MV
a :: V.Vector Int
a = runST $ (V.freeze =<<) $ flip evalStateT (1 :: Int) $ do
a' <- lift $ MV.new 256
lift $ MV.set a' 0
forM_ [0..255] $ \i -> do
when (condition i) $ do
idx <- get
lift $ MV.write a' i idx
put $ idx + 1
return a'
I simplified it a bit so that each element is set to 0 from the start, we begin with an initial state of idx = 1, loop over [0..255], if the current index i meets the condition then get the current idx, write it to the current index, then increment idx. Run this as a stateful operation, then freeze the vector, and finally run the ST monad side of things. This allows for an actual mutable vector hidden safely within the ST monad so that the outside world doesn't know that to calculate a you have to do some rather strange things.
Explicit recursion:
a = go 0 1
where go 256 _ = []
go i idx | someCondition i = idx : go (i+1) (idx+1)
| otherwise = 0 : go (i+1) idx
Unfolding: (variant of the explicit recursion above)
a = unfoldr f (0,1)
where f (256,_) = Nothing
f (i,idx) | someCondition i = Just (idx,(i+1,idx+1))
| otherwise = Just (0 ,(i+1,idx ))
Loops can usually be expressed using different fold functions. Here is a solution which uses foldl(you can switch to foldl' if you run into a stackoverflow error):
f :: (Num a) => (b -> Bool) -> a -> [b] -> [a]
f pred startVal = reverse . fst . foldl step ([], startVal)
where
step (xs, curVal) x
| pred x = (curVal:xs, curVal + 1)
| otherwise = (0:xs, curVal)
How to use it? This function takes a predicate (someCondition in your code), the initial value of an index and a list of element to iterate over. That is, you can call f someCondition 1 [0..255] to obtain the result for the example from your question.

Matching a char in a matrix on Ocaml

I am making a game solver and while using a matrix in OCaml, I need to check whenever it's complete, with A's or V's, to do so I attempeted to see if there is a '.' in at least one of the cells because that symbolizes an empty cell. Here goes the code:
let is_solved m n =
for i=0 to n do
for j=0 to n do
if(m.(i).(j)='.') then false
done
done;;
So my is_solved function has to return false when it finds a '.' at any position or true if it doesn't. But OCaml is giving me a:
Error: The variant type unit has no constructor false
I am new to OCaml but can someone tell me what I need to fix or even why is it giving me that error message?
First, note that the value of any OCaml construct of the form for ... done is (), the single value of type unit. You can't give a value to the loop as you seem to be trying to do.
Your immediate problem is that when you use if without else in OCaml, the value of the expression has to be of type unit. This is necessary because the type has to be the same in both cases. However, it's not really worth fixing this due to the above problem.
If you want to use for loops to solve your problem, you'll need to use an imperative approach. That is, you'll need to keep a mutable value to hold what you want to return at the end.
(Since you're new to OCaml it might be useful to try coding this function in a more functional style just to see how it looks.)
You can write this function in a recursive way as Jeffrey has suggested, just to give you a starting kick, I will provide a general template letting you to fill the gaps:
let todo = failwith
(* [is_solved field m n] true if exists '.' in the [field], where
[field] is a matrix of size [m] x [n] *)
let is_solved field m n =
let rec outer = function
| 0 -> todo "outer loop ends"
| m -> inner m n
and inner m = function
| 0 -> todo "inner loop ends"
| n -> todo "inner loop workload" in
outer m

Evaluation functions and expressions in Boolean expressions

I am aware how we can evaluate an expression after converting into Polish Notations. However I would like to know how I can evaluate something like this:
If a < b Then a + b Else a - b
a + b happens in case condition a < b is True, otherwise, if False a - b is computed.
The grammar is not an issue here. Since I only need the algorithm to solve this problem. I am able evaluate boolean and algebraic expressions. But how can I go about solving the above problem?
Do you need to assign a+b or a-b to something?
You can do this:
int c = a < b ? a+b : a-b;
Or
int sign = a < b ? 1 : -1;
int c = a + (sign * b);
Refer to LISP language for S-express:
e.g
(if (> a b) ; if-part
(+ a b) ; then-part
(- a b)) ; else-part
Actually if you want evaluate just this simple if statement, toknize it and evaluate it, but if you want to evaluate somehow more complicated things, like nested if then else, if with experssions, multiple else, variable assignments, types, ... you need to use some parser, like LR parsers. You can use e.g Lex&Yacc to write a good parser for your own language. They support somehow complicated grammars. But if you want to know how does LR parser (or so) works, you should read into them, and see how they use their table to read tokens and parse them. e.g take a look at wiki page and see how does LR parser table works (it's something more than simple stack and is not easy to describe it here).
If your problem is just really parsing if statement, you can cheat from parser techniques, you can add empty thing after a < b, which means some action, and empty thing after else, which also means an action. When you parsed the condition, depending on correctness or wrongness you will run one of actions. By the way if you want to parse expressions inside if statement you need conditional stack, means something like SLR table.
Basically, you need to build in support for a ternary operator. IE, where currently you pop an operator, and then wait for 2 sequential values before resolving it, you need to wait for 3 if your current operation is IF, and 2 for the other operations.
To handle the if statement, you can consider the if statement in terms of C++'s ternary operator. Which formats you want your grammar to support is up to you.
a < b ? a + b : a - b
You should be able to evaluate boolean operators on your stack the way you currently evaluate arithmetic operations, so a < b should be pushed as
< a b
The if can be represented by its own symbol on the stack, we can stick with '?'.
? < a b
and the 2 possible conditions to evaluate need to separated by another operator, might as well use ':'
? < a b : + a b - a b
So now when you pop '?', you see it is the operator that needs 3 values, so put it aside as you normally would, and continue to evaluate the stack until you have 3 values. The ':' operator should be a binary operator, that simply pushes both of its values back onto the stack.
Once you have 3 values on the stack, you evaluate ? as:
If the first value is 1, push the 2nd value, throw away the third.
If the first value is 0, throw away the 2nd and push the 3rd.

Haskell: partially drop lazy evaluated results

I have a very large decision tree. It is used as follows:
-- once per application start
t :: Tree
t = buildDecisionTree
-- done several times
makeDecision :: Something -> Decision
makeDecision something = search t something
This decision tree is way too large to fit in memory. But, thanks to lazy evaluation, it is only partially evaluated.
The problem is, that there are scenarios where all possible decisions are tried causing the whole tree to be evaluated. This is not going to terminate, but should not cause a memory overflow either. Further, if this process is aborted, the memory usage does not decrease, as a huge subtree is still evaluated already.
A solution would be to reevaluate the tree every time makeDecision is called, but this would loose the benefits of caching decisions and significantly slow down makeDecision.
I would like to go a middle course. In particular it is very common in my application to do successive decisions with common path prefix in the tree. So I would like to cache the last used path but drop the others, causing them to reevaluate the next time they are used. How can I do this in Haskell?
It is not possible in pure haskell, see question Can a thunk be duplicated to improve memory performance? (as pointed out by #shang). You can, however, do this with IO.
We start with the module heade and list only the type and the functions that should make this module (which will use unsafePerformIO) safe. It is also possible to do this without unsafePerformIO, but that would mean that the user has to keep more of his code in IO.
{-# LANGUAGE ExistentialQuantification #-}
module ReEval (ReEval, newReEval, readReEval, resetReEval) where
import Data.IORef
import System.IO.Unsafe
We start by defining a data type that stores a value in a way that prevents all sharing, by keeping the function and the argument away from each other, and only apply the function when we want the value. Note that the value returned by unsharedValue can be shared, but not with the return value of other invocations (assuming the function is doing something non-trivial):
data Unshared a = forall b. Unshared (b -> a) b
unsharedValue :: Unshared a -> a
unsharedValue (Unshared f x) = f x
Now we define our data type of resettable computations. We need to store the computation and the current value. The latter is stored in an IORef, as we want to be able to reset it.
data ReEval a = ReEval {
calculation :: Unshared a,
currentValue :: IORef a
}
To wrap a value in a ReEval box, we need to have a function and an argument. Why not just a -> ReEval a? Because then there would be no way to prevent the parameter to be shared.
newReEval :: (b -> a) -> b -> ReEval a
newReEval f x = unsafePerformIO $ do
let c = Unshared f x
ref <- newIORef (unsharedValue c)
return $ ReEval c ref
Reading is simple: Just get the value from the IORef. This use of unsafePerformIO is safe becuase we will always get the value of unsharedValue c, although a different “copy” of it.
readReEval :: ReEval a -> a
readReEval r = unsafePerformIO $ readIORef (currentValue r)
And finally the resetting. I left it in the IO monad, not because it would be any less safe than the other function to be wrapped in unsafePerformIO, but because this is the easiest way to give the user control over when the resetting actually happens. You don’t want to risk that all your calls to resetReEval are lazily delayed until your memory has run out or even optimized away because there is no return value to use.
resetReEval :: ReEval a -> IO ()
resetReEval r = writeIORef (currentValue r) (unsharedValue (calculation r))
This is the end of the module. Here is example code:
import Debug.Trace
import ReEval
main = do
let func a = trace ("func " ++ show a) negate a
let l = [ newReEval func n | n <- [1..5] ]
print (map readReEval l)
print (map readReEval l)
mapM_ resetReEval l
print (map readReEval l)
And here you can see that it does what expected:
$ runhaskell test.hs
func 1
func 2
func 3
func 4
func 5
[-1,-2,-3,-4,-5]
[-1,-2,-3,-4,-5]
func 1
func 2
func 3
func 4
func 5
[-1,-2,-3,-4,-5]

Resources