If the local variable can be changed ...

In FP the variable can not be changed once created. Yes, it has much advantage . However, i feel it is too strict. As we know, the local variable is allocated on stack which is thread safe. So if the local variable can be changed, then we can use loop, etc. same as imperative languages. For example, for (i=0; i<100; i++) where `i` is a local variable in function. Any suggestion is appreciated! ----- fac n = let { f = foldr (*) 1 [1..n] } in f -- View this message in context: http://old.nabble.com/If-the-local-variable-can-be-changed-...-tp27844016p27... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On 10 March 2010 11:25, zaxis
So if the local variable can be changed, then we can use loop, etc. same as imperative languages. For example, for (i=0; i<100; i++) where `i` is a local variable in function.
But why would we want to? That's what folds, etc. are for! -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

If your code performs a common task (such as conversion, accumulation,
testing), then you should use higher-level constructs than a for loop.
Using map, filter, foldr, and foldl will make it easier to write
correct code.
If you'd like to imitate a for loop exactly -- that is, to perform
some action multiple times -- it's very easy to create a pure
function. We do not have to stoop to mutable variables.
-------------------------------------------------
for :: Monad m => a -> (a -> Bool) -> (a -> a) -> (a -> m ()) -> m ()
for start test step body = loop start where
loop x = if test x
then body x >> loop (step x)
else return ()
main = for 0 (< 100) (+ 1) $ \i -> do
-- do something with i
print i
-------------------------------------------------
On Tue, Mar 9, 2010 at 16:25, zaxis
In FP the variable can not be changed once created. Yes, it has much advantage . However, i feel it is too strict. As we know, the local variable is allocated on stack which is thread safe.
So if the local variable can be changed, then we can use loop, etc. same as imperative languages. For example, for (i=0; i<100; i++) where `i` is a local variable in function.
Any suggestion is appreciated!
----- fac n = let { f = foldr (*) 1 [1..n] } in f -- View this message in context: http://old.nabble.com/If-the-local-variable-can-be-changed-...-tp27844016p27... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Yes, we can imitate all of it (such as `when`, `until` and `for`) because haskell is a good DSL language. However, i feel it will be more convenient if the language itself supports all these fundations. jmillikin wrote:
If your code performs a common task (such as conversion, accumulation, testing), then you should use higher-level constructs than a for loop. Using map, filter, foldr, and foldl will make it easier to write correct code.
If you'd like to imitate a for loop exactly -- that is, to perform some action multiple times -- it's very easy to create a pure function. We do not have to stoop to mutable variables.
------------------------------------------------- for :: Monad m => a -> (a -> Bool) -> (a -> a) -> (a -> m ()) -> m () for start test step body = loop start where loop x = if test x then body x >> loop (step x) else return ()
main = for 0 (< 100) (+ 1) $ \i -> do -- do something with i print i -------------------------------------------------
On Tue, Mar 9, 2010 at 16:25, zaxis
wrote: In FP the variable can not be changed once created. Yes, it has much advantage . However, i feel it is too strict. As we know, the local variable is allocated on stack which is thread safe.
So if the local variable can be changed, then we can use loop, etc. same as imperative languages. For example, for (i=0; i<100; i++) where `i` is a local variable in function.
Any suggestion is appreciated!
----- fac n = let { f = foldr (*) 1 [1..n] } in f -- View this message in context: http://old.nabble.com/If-the-local-variable-can-be-changed-...-tp27844016p27... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
----- fac n = let { f = foldr (*) 1 [1..n] } in f -- View this message in context: http://old.nabble.com/If-the-local-variable-can-be-changed-...-tp27844016p27... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On 10 March 2010 16:45, zaxis
Yes, we can imitate all of it (such as `when`, `until` and `for`) because haskell is a good DSL language. However, i feel it will be more convenient if the language itself supports all these fundations.
You seem to be missing the point of referential transparency [1] and purity [2], something which most of us quite _like_ about Haskell. If you absolutely _need_ mutation within Haskell, see IORefs and the like. [1]: http://en.wikipedia.org/wiki/Referential_transparency_(computer_science) [2]: http://en.wikipedia.org/wiki/Purely_functional -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

zaxis wrote:
Yes, we can imitate all of it (such as `when`, `until` and `for`) because haskell is a good DSL language. However, i feel it will be more convenient if the language itself supports all these fundations.
There is such a language, its called Disciple and its compiler is DDC: http://www.haskell.org/haskellwiki/DDC However, the compiler is an experimental compiler, is still incomplete and has bugs. Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/

So if the local variable can be changed, then we can use loop, etc. same as imperative languages. For example, for (i=0; i<100; i++) where `i` is a local variable in function.
It is true that a pure language could support such things (some pure languages do, e.g. Sisal). The experience of people using SML and Haskell seems to indicate that this is not very important in those languages: it's easy for the programmer to turn his variable-assignments into something pure (using new variables instead), and it's reasonably easy as well for the compiler to recognize loops and handle them just as efficiently as if they were while/for loops in an imperative language. OTOH, allowing modification of variables makes the whole language impure, because of variables caught in closures, e.g.: let count = 0 in \() -> count := count + 1; count so it has very far reaching consequences. Stefan

zaxis
As we know, the local variable is allocated on stack which is thread safe.
It's not. http://en.wikipedia.org/wiki/Funarg_problem#Example -- Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig masha'allah insha'allah
participants (6)
-
Chung-chieh Shan
-
Erik de Castro Lopo
-
Ivan Miljenovic
-
John Millikin
-
Stefan Monnier
-
zaxis