How to do this in FP way?

Hello, I am getting familiar with FP now, and I have a "program design" kind of question. Say I have something like this in C: static int old; int diff (int now) { /* this would be called once a second */ int ret = now - old; old = now; return ret; } Because there is no "variable" in Haskell. So how to do this in a FP way? Thanks.

Magicloud Magiclouds wrote:
Say I have something like this in C: static int old; int diff (int now) { /* this would be called once a second */ int ret = now - old; old = now; return ret; } Because there is no "variable" in Haskell. So how to do this in a FP way?
So you have a global time count that is updated every second - I presume for the rest of the process to use, avoiding syscalls due to expense. Am I getting this right? You can use mutable variables in Haskell, though some people will frown, but it might fit your need. See MVar, STM, or IO Refs. At any rate, if what you are doing needs to check the clock time then this code isn't going to be pure. Perhaps you just want something in particular to be triggered every second then use control-timeout, event-list, or control-event. Tom

I can think of 2 ways.
> module Main where
>
> import Control.Monad.State
First, normal way:
> diff (now, old) = (now - old, now)
diff takes now and old and returns result (now - old) and modified old (now).
For example,
diff (diff (1,0))
==> diff (1 - 0, 1)
==> diff (1, 1)
==> (1 - 1, 1)
==> (0, 1)
I think people use the word "threaded" to describe what diff is doing:
the variable "old" is threaded through many calls to diff.
> testDiff = diff . diff . diff . diff . diff . diff $ (2, 1)
testDiff returns (2,1)
Second way is using monads:
> diff' now = do
> old <- get
> put now
> return (now - old)
diff' uses State monad.
If you're not familiar with monads, State monad does similar to what
diff function does (it threads the variable "old").
But, being a monadic action, diff' looks like imperative version
syntactically. It gives illusion of having global variable (old).
> testDiff' = do
> result <- diff' 2
> result <- diff' result
> result <- diff' result
> result <- diff' result
> result <- diff' result
> result <- diff' result
> return result
>
> runTestDiff' = runState testDiff' 1
runTestDiff' also returns (2,1)
2008/6/15 Magicloud Magiclouds
Hello, I am getting familiar with FP now, and I have a "program design" kind of question. Say I have something like this in C: static int old; int diff (int now) { /* this would be called once a second */ int ret = now - old; old = now; return ret; } Because there is no "variable" in Haskell. So how to do this in a FP way?
Thanks.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

"Magicloud Magiclouds"
static int old; int diff (int now) { /* this would be called once a second */ int ret = now - old; old = now; return ret; }
You do it with variables, of course. This is out of some GLUT code, using IORef's: idle :: State -> IdleCallback idle state = do t0 <- get $ t state t1 <- get elapsedTime t state $= t1 let td = fromIntegral t1 - fromIntegral t0 fps state $= 1/td * 1000 angle' state $~! (+2) (bpx, bpy) <- get $ ballPos state (bvx, bvy) <- get $ ballVel state ballPos state $= (bpx + bvx*td, bpy + bvy*td) postRedisplay Nothing One half of all Haskell coders will tell you that mutable state isn't a good starting point to learn Haskell, the other half will tell you the same because they want to be cool kids, too. -- (c) this sig last receiving data processing entity. Inspect headers for past copyright information. All rights reserved. Unauthorised copying, hiring, renting, public performance and/or broadcasting of this signature prohibited.

One half of all Haskell coders will tell you that mutable state isn't a good starting point to learn Haskell, the other half will tell you the same because they want to be cool kids, too.
And the one left over will point out that he asked how to do this the FP way, not the imperative way? If it was me btw, I'd take a stab at the problem being that each time we do something a time gets updated and we want to know how much time has passed since we last did "something". I'd approach this by generating a lazy list of times at which we started doing "something", and then generating a lazy list of time differences. Bob

Thomas Davie
One half of all Haskell coders will tell you that mutable state isn't a good starting point to learn Haskell, the other half will tell you the same because they want to be cool kids, too.
And the one left over will point out that he asked how to do this the FP way, not the imperative way?
There's no difference, as you can't do time-accounting non-strict and still expect it to give meaningful results: I'm merely trying to be helpful. None of the other solutions allow for the IO Monad. -- (c) this sig last receiving data processing entity. Inspect headers for past copyright information. All rights reserved. Unauthorised copying, hiring, renting, public performance and/or broadcasting of this signature prohibited.

On 16 Jun 2008, at 18:28, Achim Schneider wrote:
Thomas Davie
wrote: One half of all Haskell coders will tell you that mutable state isn't a good starting point to learn Haskell, the other half will tell you the same because they want to be cool kids, too.
And the one left over will point out that he asked how to do this the FP way, not the imperative way?
There's no difference, as you can't do time-accounting non-strict and still expect it to give meaningful results: I'm merely trying to be helpful. None of the other solutions allow for the IO Monad.
Firstly, I'd phrase that differently -- the IO Monad doesn't allow for the other solutions -- the other solutions are the truly functional ones. Secondly, I'm curious as to why you think that the two are incompatible, are you saying that for any meaningful kind of computation we need to resort to IORefs? I'd strongly contest that idea. Bob

Thomas Davie
On 16 Jun 2008, at 18:28, Achim Schneider wrote:
Thomas Davie
wrote: One half of all Haskell coders will tell you that mutable state isn't a good starting point to learn Haskell, the other half will tell you the same because they want to be cool kids, too.
And the one left over will point out that he asked how to do this the FP way, not the imperative way?
There's no difference, as you can't do time-accounting non-strict and still expect it to give meaningful results: I'm merely trying to be helpful. None of the other solutions allow for the IO Monad.
Firstly, I'd phrase that differently -- the IO Monad doesn't allow for the other solutions -- the other solutions are the truly functional ones. Secondly, I'm curious as to why you think that the two are incompatible, are you saying that for any meaningful kind of computation we need to resort to IORefs? I'd strongly contest that idea.
We have to resort to IO actions to get the time, and to IORefs because we need to chain up different calls to getCurrentTime using the IO Monad. The rest of the program can work with whatever you like best. -- (c) this sig last receiving data processing entity. Inspect headers for past copyright information. All rights reserved. Unauthorised copying, hiring, renting, public performance and/or broadcasting of this signature prohibited.

On Mon, 16 Jun 2008, Achim Schneider wrote:
We have to resort to IO actions to get the time, and to IORefs because we need to chain up different calls to getCurrentTime using the IO Monad. The rest of the program can work with whatever you like best.
Isn't (StateT s IO a) the cleaner alternative to IORef?

Henning Thielemann
On Mon, 16 Jun 2008, Achim Schneider wrote:
We have to resort to IO actions to get the time, and to IORefs because we need to chain up different calls to getCurrentTime using the IO Monad. The rest of the program can work with whatever you like best.
Isn't (StateT s IO a) the cleaner alternative to IORef?
Yes. But then using one IORef in one place won't make your program harder to understand, using Monad transformers quite certainly will. Admittedly, I'm becoming dodgy. -- (c) this sig last receiving data processing entity. Inspect headers for past copyright information. All rights reserved. Unauthorised copying, hiring, renting, public performance and/or broadcasting of this signature prohibited.

Yes, that's it, State.
Thanks.
-----邮件原件-----
发件人: haskell-cafe-bounces@haskell.org
[mailto:haskell-cafe-bounces@haskell.org] 代表 Achim Schneider
发送时间: 2008年6月16日 12:01
收件人: haskell-cafe@haskell.org
主题: [Haskell-cafe] Re: How to do this in FP way?
"Magicloud Magiclouds"
static int old; int diff (int now) { /* this would be called once a second */ int ret = now - old; old = now; return ret; }
You do it with variables, of course. This is out of some GLUT code, using IORef's: idle :: State -> IdleCallback idle state = do t0 <- get $ t state t1 <- get elapsedTime t state $= t1 let td = fromIntegral t1 - fromIntegral t0 fps state $= 1/td * 1000 angle' state $~! (+2) (bpx, bpy) <- get $ ballPos state (bvx, bvy) <- get $ ballVel state ballPos state $= (bpx + bvx*td, bpy + bvy*td) postRedisplay Nothing One half of all Haskell coders will tell you that mutable state isn't a good starting point to learn Haskell, the other half will tell you the same because they want to be cool kids, too. -- (c) this sig last receiving data processing entity. Inspect headers for past copyright information. All rights reserved. Unauthorised copying, hiring, renting, public performance and/or broadcasting of this signature prohibited. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I think if I do not use a state, and the function would be called for many
times, it would waste memory, if using something like loop, right?
-----邮件原件-----
发件人: haskell-cafe-bounces@haskell.org
[mailto:haskell-cafe-bounces@haskell.org] 代表 Achim Schneider
发送时间: 2008年6月16日 12:01
收件人: haskell-cafe@haskell.org
主题: [Haskell-cafe] Re: How to do this in FP way?
"Magicloud Magiclouds"
static int old; int diff (int now) { /* this would be called once a second */ int ret = now - old; old = now; return ret; }
You do it with variables, of course. This is out of some GLUT code, using IORef's: idle :: State -> IdleCallback idle state = do t0 <- get $ t state t1 <- get elapsedTime t state $= t1 let td = fromIntegral t1 - fromIntegral t0 fps state $= 1/td * 1000 angle' state $~! (+2) (bpx, bpy) <- get $ ballPos state (bvx, bvy) <- get $ ballVel state ballPos state $= (bpx + bvx*td, bpy + bvy*td) postRedisplay Nothing One half of all Haskell coders will tell you that mutable state isn't a good starting point to learn Haskell, the other half will tell you the same because they want to be cool kids, too. -- (c) this sig last receiving data processing entity. Inspect headers for past copyright information. All rights reserved. Unauthorised copying, hiring, renting, public performance and/or broadcasting of this signature prohibited. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

"Magicloud"
I think if I do not use a state, and the function would be called for many times, it would waste memory, if using something like loop, right?
nope, at least not in general. update :: MyState -> Int -> MyState draw :: MyState -> IO () mainLoop :: MyState -> Int -> IO () mainLoop st old = do now <- getTimeOfDay let td = now - old st' = update st td draw st' mainLoop st' now runs in constant space. Look up "tail recursion" in wikipedia.
-----邮件原件----- 发件人: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] 代表 Achim Schneider 发送时间: 2008年6月16日 12:01 收件人: haskell-cafe@haskell.org 主题: [Haskell-cafe] Re: How to do this in FP way?
"Magicloud Magiclouds"
wrote: static int old; int diff (int now) { /* this would be called once a second */ int ret = now - old; old = now; return ret; }
You do it with variables, of course. This is out of some GLUT code, using IORef's:
idle :: State -> IdleCallback idle state = do t0 <- get $ t state t1 <- get elapsedTime t state $= t1 let td = fromIntegral t1 - fromIntegral t0 fps state $= 1/td * 1000
angle' state $~! (+2)
(bpx, bpy) <- get $ ballPos state (bvx, bvy) <- get $ ballVel state
ballPos state $= (bpx + bvx*td, bpy + bvy*td) postRedisplay Nothing
One half of all Haskell coders will tell you that mutable state isn't a good starting point to learn Haskell, the other half will tell you the same because they want to be cool kids, too.
-- (c) this sig last receiving data processing entity. Inspect headers for past copyright information. All rights reserved. Unauthorised copying, hiring, renting, public performance and/or broadcasting of this signature prohibited.

But if there are some beautiful arithmetics that do not use something like
state, I won't say no to them.
-----邮件原件-----
发件人: haskell-cafe-bounces@haskell.org
[mailto:haskell-cafe-bounces@haskell.org] 代表 Achim Schneider
发送时间: 2008年6月16日 12:01
收件人: haskell-cafe@haskell.org
主题: [Haskell-cafe] Re: How to do this in FP way?
"Magicloud Magiclouds"
static int old; int diff (int now) { /* this would be called once a second */ int ret = now - old; old = now; return ret; }
You do it with variables, of course. This is out of some GLUT code, using IORef's: idle :: State -> IdleCallback idle state = do t0 <- get $ t state t1 <- get elapsedTime t state $= t1 let td = fromIntegral t1 - fromIntegral t0 fps state $= 1/td * 1000 angle' state $~! (+2) (bpx, bpy) <- get $ ballPos state (bvx, bvy) <- get $ ballVel state ballPos state $= (bpx + bvx*td, bpy + bvy*td) postRedisplay Nothing One half of all Haskell coders will tell you that mutable state isn't a good starting point to learn Haskell, the other half will tell you the same because they want to be cool kids, too. -- (c) this sig last receiving data processing entity. Inspect headers for past copyright information. All rights reserved. Unauthorised copying, hiring, renting, public performance and/or broadcasting of this signature prohibited. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

"Magicloud Magiclouds"
static int old; int diff (int now) { /* this would be called once a second */ int ret = now - old; old = now; return ret; }
Because there is no "variable" in Haskell. So how to do this in a FP way?
I would claim the FP way is like this: -- | Repeatedly subtract values from a baseline, returning a list -- containing each intermediate result diff :: Int -> [Int] -> [Int] diff = scanl (-) Prelude> diff 100 [1..10] [100,99,97,94,90,85,79,72,64,55,45] -k -- If I haven't seen further, it is by standing in the footprints of giants

On Mon, 2008-06-16 at 10:19 +0200, Ketil Malde wrote:
"Magicloud Magiclouds"
writes: static int old; int diff (int now) { /* this would be called once a second */ int ret = now - old; old = now; return ret; }
Because there is no "variable" in Haskell. So how to do this in a FP way?
I would claim the FP way is like this:
-- | Repeatedly subtract values from a baseline, returning a list -- containing each intermediate result diff :: Int -> [Int] -> [Int] diff = scanl (-)
Prelude> diff 100 [1..10] [100,99,97,94,90,85,79,72,64,55,45]
Better yet, you could create a recursive type that reflects what you are actually doing: newtype Step a = Step (a -> (a, Step a)) diff' :: Int -> Step Int diff' x = Step (\a -> let r = a - x in (r, diff' r)) This way it will be easier to resume previous diff computations. Best, Michał

2008/6/15 Magicloud Magiclouds
Hello, I am getting familiar with FP now, and I have a "program design" kind of question. Say I have something like this in C: static int old; int diff (int now) { /* this would be called once a second */ int ret = now - old; old = now; return ret; } Because there is no "variable" in Haskell. So how to do this in a FP way?
A better question would be to think about what you are trying to accomplish, and then ask how to achieve that through functional programming. David

David Roundy wrote:
A better question would be to think about what you are trying to accomplish, and then ask how to achieve that through functional programming.
Amen! I was waiting for somebody to say that... There are a dozen situations in an imperative language where you'd write a loop. But in Haskell, you might well do something entirely different for each situation. So it really pays to focus on what the end result you're after is, rather than how to translate imperative code line-for-line into Haskell.

OK. Here it is.
I want to make a monitor tool for linux. It runs for a long time, and give
out a certain process's io stat per second. The way I get io stat is to read
from /proc/pid/io. But the data in this file is a total, I need to read it
first, then next second, read it again, and shows the difference, and go on.
So, what is your idea?
-----邮件原件-----
发件人: David Roundy [mailto:daveroundy@gmail.com]
发送时间: 2008年6月17日 1:17
收件人: Magicloud Magiclouds
抄送: haskell-cafe@haskell.org
主题: Re: [Haskell-cafe] How to do this in FP way?
2008/6/15 Magicloud Magiclouds
Hello, I am getting familiar with FP now, and I have a "program design" kind of question. Say I have something like this in C: static int old; int diff (int now) { /* this would be called once a second */ int ret = now - old; old = now; return ret; } Because there is no "variable" in Haskell. So how to do this in a FP way?
A better question would be to think about what you are trying to accomplish, and then ask how to achieve that through functional programming. David

magicloud.magiclouds:
OK. Here it is. I want to make a monitor tool for linux. It runs for a long time, and give out a certain process's io stat per second. The way I get io stat is to read from /proc/pid/io. But the data in this file is a total, I need to read it first, then next second, read it again, and shows the difference, and go on. So, what is your idea?
Easy, import Control.Concurrent import Control.Monad main = go 0 where go st = forever $ do n <- read `fmap` readFile "/proc/pid/io" print (n - st) -- display difference threadDelay (10^6) -- Don

dons:
magicloud.magiclouds:
OK. Here it is. I want to make a monitor tool for linux. It runs for a long time, and give out a certain process's io stat per second. The way I get io stat is to read from /proc/pid/io. But the data in this file is a total, I need to read it first, then next second, read it again, and shows the difference, and go on. So, what is your idea?
Easy,
import Control.Concurrent import Control.Monad
main = go 0 where go st = forever $ do n <- read `fmap` readFile "/proc/pid/io" print (n - st) -- display difference threadDelay (10^6)
Oops, not 'forever' :) go st = do ... go n

On Tue, Jun 17, 2008 at 08:56:31AM -0700, Don Stewart wrote:
dons:
magicloud.magiclouds:
OK. Here it is. I want to make a monitor tool for linux. It runs for a long time, and give out a certain process's io stat per second. The way I get io stat is to read from /proc/pid/io. But the data in this file is a total, I need to read it first, then next second, read it again, and shows the difference, and go on. So, what is your idea?
Easy,
import Control.Concurrent import Control.Monad
main = go 0 where go st = forever $ do n <- read `fmap` readFile "/proc/pid/io" print (n - st) -- display difference threadDelay (10^6)
Oops, not 'forever' :)
go st = do ... go n
or doEverySecond :: (a -> IO a) -> a -> IO () doEverySecond job n = do n' <- job n threadDelay (10^6) doEverySecond job n' showChange :: Int -> IO Int showChange n = do n' <- read `fmap` readFile "/proc/pid/io" print (n' - n) -- display difference return n' main = doEverySecond showChange 0 -- note: prints bogus value first time This demonstrates how you can abstract the ideas in Don's solution just a bit, so that you could reuse these functions for somewhat different purposes. For such a simple function you'd probably be better with Don's solution, but if your monitor tool is starting to look more complicated than this, perhaps you're better off breaking it into different functions. David

On Mon, Jun 16, 2008 at 10:31:22AM +0800, Magicloud Magiclouds wrote:
Hello, I am getting familiar with FP now, and I have a "program design" kind of question. Say I have something like this in C: static int old; int diff (int now) { /* this would be called once a second */ int ret = now - old; old = now; return ret; } Because there is no "variable" in Haskell. So how to do this in a FP way?
Thanks.
I think that "called once a second" suggests that you perhaps should not do that in a FP way. A state-changing function called frequently suggests that you are perhaps doing something with a notion of time, maybe a game? Then FRP is your FP approach. Or I would recommend you to explain your problem, because FP approach could lie on much more higher level than one can figure out looking at your short snippet.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- pierre

On 6/16/08, Magicloud Magiclouds
Hello, I am getting familiar with FP now, and I have a "program design" kind of question. Say I have something like this in C: static int old; int diff (int now) { /* this would be called once a second */ int ret = now - old; old = now; return ret; } Because there is no "variable" in Haskell. So how to do this in a FP way?
The short answer is that your question amounts to "How do I do imperative programming in an FP way", to which the answer is "you really should try to avoid it". Longer answer: I think you'll be bette served if you describe your problem on a much higher level than this. Chances are that if you write your program in an FP way, you wouldn't need a function like your diff. That said, Haskell do have variables (in this case an IORef would do what you want), but again, you probably don't want that, so if you post what problem you're trying to solve using "diff", then it will be easier to help you design it in an FP way. Doing things in an FP way tend to impact your program a lot more than just some minor changes to the functions at the "bottom", it will change the whole design. -- Sebastian Sylvan +44(0)7857-300802 UIN: 44640862
participants (15)
-
Achim Schneider
-
Andrew Coppin
-
David Roundy
-
David Roundy
-
Don Stewart
-
Henning Thielemann
-
Ketil Malde
-
Magicloud
-
Magicloud Magiclouds
-
Michał Pałka
-
pierre
-
sam lee
-
Sebastian Sylvan
-
Thomas Davie
-
Thomas M. DuBuisson