How to increment a variable in functional programming?
Asked Answered
U

4

27

How do you increment a variable in a functional programming language?

For example, I want to do:

main :: IO ()
main = do
    let i = 0
    i = i + 1
    print i

Expected output:

1
Ultramicroscopic answered 12/8, 2012 at 12:24 Comment(11)
Why would you want to do something like this in functional programming? All you need to do is generate a list of numbers [1..] and do what you want with as many of them as you want.Poem
I gave a +1 because this is sort of a valid question. But something I found when I learned Haskell was that it taught you to think about solving problems is a different way. The kind of way where you don't need to use for loops.Poem
I don't think this deserves downvotes. Its a legitamate question and is doable (you need to use MVar, IORef, or even STRef. In addition, it serves as a way to tell people "don't do this. ever"Mammillary
Well that's nonsense! 0 is not equal to itself plus one! How in the sweet heavens does that make any mathematical sense? I'm beeing cheeky, but in Haskell = means equals, like in math. You're looking for some other operator that modifies the contents of a mutable variable. As probie indicated, that operator is modifyIORef or something similar.Mintamintage
It depends on what you are really trying to do. You could just say "main = print 1". But I suspect that is not the answer you are looking for.Endocardium
Pasting what I really want to do will get me -10 :)Ultramicroscopic
You are getting down-voted because it is (more or less) obvious you have not made an effort to read the most basic introductory material available on Haskell (or functional programming in general). Your questions sound like "I just bought a plane - does anybody know how I can get on the freeway?". Why would you get on the freeway if you have a plane? Try going through learnyouahaskell.com or book.realworldhaskell.org.Stackhouse
For crap sake it was a FAQ, see below to help other people. I answered my own question. Do you really think noobs like me do not try to do i=i+1?Ultramicroscopic
You don't necessarily find the answer to this in a book, because the book teaches you how to use the language, not how to not use the language. Also, he obviously knew the answer because he answered the question himself...Mammillary
Similar questions are asked occasionally:Counters are initialized every time?, Keep track of the program variables in Haskell like imperative programs, How do I deal with this Haskell difficulty? and more. So there is definitely a need for this type of question to be answered.Monti
Life/Jacket! :) :)Rhodia
R
27

Simple way is to introduce shadowing of a variable name:

main :: IO ()                  -- another way, simpler, specific to monads:
main = do                         main = do
    let i = 0                         let i = 0
    let j = i                         i <- return (i+1)
    let i = j+1                       print i
    print i                    -- because monadic bind is non-recursive

Prints 1.

Just writing let i = i+1 doesn't work because let in Haskell makes recursive definitions — it is actually Scheme's letrec. The i in the right-hand side of let i = i+1 refers to the i in its left hand side — not to the upper level i as might be intended. So we break that equation up by introducing another variable, j.

Another, simpler way is to use monadic bind, <- in the do-notation. This is possible because monadic bind is not recursive.

In both cases we introduce new variable under the same name, thus "shadowing" the old entity, i.e. making it no longer accessible.

How to "think functional"

One thing to understand here is that functional programming with pure — immutable — values (like we have in Haskell) forces us to make time explicit in our code.

In imperative setting time is implicit. We "change" our vars — but any change is sequential. We can never change what that var was a moment ago — only what it will be from now on.

In pure functional programming this is just made explicit. One of the simplest forms this can take is with using lists of values as records of sequential change in imperative programming. Even simpler is to use different variables altogether to represent different values of an entity at different points in time (cf. single assignment and static single assignment form, or SSA).

So instead of "changing" something that can't really be changed anyway, we make an augmented copy of it, and pass that around, using it in place of the old thing.

Rhodia answered 12/8, 2012 at 15:57 Comment(3)
I want a {-# shadow #-} pragma to suppress the name shadowing warning for a binding, because sometimes I really want to shadow.Taylor
@Taylor right. if I shadow a var it is (hopefully) always intentional. in list comprehensions as well. I even did it in my recent answer, powerList' (x:xs) = [ s | s <- powerList' xs, s <- [s, x:s]], "add a subset as is, and also with x prepended". I mean the do bindings though, not let. enabling let binding is too big of a breaking change to the language. you probably didn't mean that.Rhodia
Either in do/pattern guard binding or in case patterns. Things like case f s of (# s, a #) -> case g a s of (# s, b #) -> (# s, Just b #) are totally reasonable. Dunno where you'd stick a pragma though :-/.Taylor
H
9

As a general rule, you don't (and you don't need to). However, in the interests of completeness.

import Data.IORef
main = do
    i <- newIORef 0       -- new IORef i
    modifyIORef i (+1)    -- increase it by 1
    readIORef i >>= print -- print it

However, any answer that says you need to use something like MVar, IORef, STRef etc. is wrong. There is a purely functional way to do this, which in this small rapidly written example doesn't really look very nice.

import Control.Monad.State
type Lens a b = ((a -> b -> a), (a -> b))
setL = fst
getL = snd
modifyL :: Lens a b -> a -> (b -> b) -> a
modifyL lens x f = setL lens x (f (getL lens x))
lensComp :: Lens b c -> Lens a b -> Lens a c
lensComp (set1, get1) (set2, get2) =         -- Compose two lenses
    (\s x -> set2 s (set1 (get2 s) x)        -- Not needed here
     , get1 . get2)                          -- But added for completeness

(+=) :: (Num b) => Lens a b -> Lens a b -> State a ()
x += y = do
    s <- get
    put (modifyL x s (+ (getL y s)))

swap :: Lens a b -> Lens a b -> State a ()
swap x y = do
    s <- get
    let x' = getL x s
    let y' = getL y s
    put (setL y (setL x s y') x')

nFibs :: Int -> Int
nFibs n = evalState (nFibs_ n) (0,1)

nFibs_ :: Int -> State (Int,Int) Int
nFibs_ 0 = fmap snd get -- The second Int is our result
nFibs_ n = do
    x += y       -- Add y to x
    swap x y     -- Swap them
    nFibs_ (n-1) -- Repeat
  where x = ((\(x,y) x' -> (x', y)), fst)
        y = ((\(x,y) y' -> (x, y')), snd)
Habitue answered 12/8, 2012 at 16:53 Comment(4)
isn't it just another way to write nFibs n = snd.head $ iterate g [(0,1)] !! n where g (s:_) = let { s1=addIn s ; s2=swap s1 } in [s2,s1] ; addIn(a,b)=(a+b,b) ; swap(a,b)=(b,a) ? (small oversight - it's the first Int that's the result here).Rhodia
and this is why I shouldn't write things at 3am :p But if you want a simple fib function nFibs n = let fibs = iterate (\(x,y) -> (y, x+y)) (0,1) in (snd . (!! n)) fibs However, the idea has nothing to do with a fibonacci function. The idea was to give an example of functional lenses.Habitue
I wasn't questioning your writing, at all. :) I don't understand why try so hard to be able to write in imperative style, in the first place. Same as calling monadic inject a "return", for some peculiar salesmanship reasons. Why not "sell" functional style better, striving for better compiler support for it (case in point - https://mcmap.net/q/534546/-in-haskell-how-would-you-go-about-generating-a-list-of-all-prime-numbers-upto-a-number-say-x where destructive array update should/could have been used automagically by a compiler, IMHO, although many smart people disagree).Rhodia
Because the question was asked for how to do i=i+1 in a functional programming language. Simply saying you can't or shouldn't is unhelpful.Habitue
U
4

There are several solutions to translate imperative i=i+1 programming to functional programming. Recursive function solution is the recommended way in functional programming, creating a state is almost never what you want to do.

After a while you will learn that you can use [1..] if you need a index for example, but it takes a lot of time and practice to think functionally instead of imperatively.

Here's a other way to do something similar as i=i+1 not identical because there aren't any destructive updates. Note that the State monad example is just for illustration, you probably want [1..] instead:

module Count where
import Control.Monad.State

count :: Int -> Int
count c = c+1

count' :: State Int Int
count' = do
    c <- get
    put (c+1)
    return (c+1)

main :: IO ()
main = do
            -- purely functional, value-modifying (state-passing) way:
    print $ count . count . count . count . count . count $ 0
            -- purely functional, State Monad way
    print $ (`evalState` 0) $ do { 
            count' ; count' ; count' ; count' ; count' ; count' } 
Ultramicroscopic answered 12/8, 2012 at 12:24 Comment(6)
Yeah, except, don't do that. State monad is not something you sprinkle your code with just to make it act imperative. In fact, don't write imperative code in Haskell unless it's needed.Amarillo
I don't think this is a good answer. The use case in which you imperatively would use i=i+1 is almost never translated to "Use State!" in Haskell. A "don't do this!" or "If you really, really need this, use MVar" seems much more sane.Bergstein
Deceptive question' so -1. If you already knew how to model state, why lie about it?Cornstarch
PLEAS READ! blog.stackoverflow.com/2011/07/…Ultramicroscopic
@RichardHuxton It is pretty instinctive to think it is wrong to answer ones own question. I think this is because when points are involved there is a instinctive competitiveness and answering ones own question seems an attempt to monopolize those points. Stackoverflow is about optimizing for questions and answers that are the most useful or help the most people. So the question is did this Q/A do that or not.Monti
My answer is in wiki form, you don't get any points for a wiki answer. Also I did accept the best answer which was not my own.Ultramicroscopic
C
1

Note: This is not an ideal answer but hey, sometimes it might be a little good to give anything at all.

A simple function to increase the variable would suffice.

For example:

incVal :: Integer -> Integer
incVal x = x + 1

main::IO()
main = do
   let i  = 1
   print (incVal i)

Or even an anonymous function to do it.

Cirro answered 29/5, 2020 at 1:16 Comment(0)

© 2022 - 2024 — McMap. All rights reserved.