[Haskell-cafe] How to do this in FP way?
sam lee
skynare at gmail.com
Sun Jun 15 23:10:09 EDT 2008
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 <magicloud.magiclouds at gmail.com>:
> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
More information about the Haskell-Cafe
mailing list