28

Mind the pure function below, in an imperative language:

def foo(x,y):
    x = f(x) if a(x)
    if c(x): 
        x = g(x)
    else:
        x = h(x)
    x = f(x)
    y = f(y) if a(y)
    x = g(x) if b(y)
    return [x,y]

That function represents a style where you have to incrementally update variables. It can be avoided in most cases, but there are situations where that pattern is unavoidable - for example, writing a cooking procedure for a robot, which inherently requires a series of steps and decisions. Now, imagine we were trying to represent foo in Haskell.

foo x0 y0 =
    let x1 = if a x0 then f x0 else x0 in
    let x2 = if c x1 then g x1 else h x1 in
    let x3 = f x2 in
    let y1 = if a y0 then f y0 else y0 in
    let x4 = if b y1 then g x3 else x3 in
    [x4,y1]

That code works, but it is too complicated and error prone due to the need for manually managing the numeric tags. Notice that, after x1 is set, x0's value should never be used again, but it still can. If you accidentally use it, that will be an undetected error.

I've managed to solve this problem using the State monad:

fooSt x y = execState (do
    (x,y) <- get
    when (a x) (put (f x, y))
    (x,y) <- get
    if c x 
        then put (g x, y) 
        else put (h x, y)
    (x,y) <- get
    put (f x, y)
    (x,y) <- get
    when (a y) (put (x, f y))
    (x,y) <- get
    when (b y) (put (g x, x))) (x,y)

This way, need for tag-tracking goes away, as well as the risk of accidentally using an outdated variable. But now the code is verbose and much harder to understand, mainly due to the repetition of (x,y) <- get.

So: what is a more readable, elegant and safe way to express this pattern?

Full code for testing.

MaiaVictor
  • 51,090
  • 44
  • 144
  • 286
  • Well, first of all, you need just one `let` at the start and one `in` at the end. Also, stateful computations can be expressed with the state monad, although I'm not sure if that's that much of an improvement in this case; In the first place, it's not actually longer than your imperative example. – Cubic Aug 03 '14 at 17:31
  • @Cubic that is true, thank you. The problem is more about the numeric tagging, though, as it is confusing, error prone. For example, after `x1` is set, `x0` shouldn't be used again, but if you commit a mistake and do, this will be an undetected error. I was trying to find an answer via the State monad, but the code got much more bloated (albeit more correct). I guess I will update the question soon. – MaiaVictor Aug 03 '14 at 17:37
  • 6
    I would suggest you to stop thinking imperatively and rather think in a functional way. I agree that it will take some time to getting used to the new pattern, but try to translate imperative ideas to functional languages isn't a great approach. I can help in solving your problem in a more elegant way, if I know what you are trying to achieve. Unfortunately, your `foo` function doesn't give me much idea. – Sibi Aug 03 '14 at 17:45
  • I am, but this **is** an imperative case. Specifically, it is a decision algorithm for how an AI should use his cards in a TCG game. Just like cooking, it naturally involves a series of steps and decisions - there isn't really much you I do about that. – MaiaVictor Aug 03 '14 at 17:51
  • 1
    You could definitely clean this up by using the modify function for the state monad. – bheklilr Aug 03 '14 at 18:14
  • I think part of the problem here is just the naming of things. There are different values of `x` in the imperative solution, but they actually mean something different. If they had different names things would be alot clearer. – WW. Aug 04 '14 at 07:18

6 Answers6

29

Your goals

While the direct transformation of imperative code would usually lead to the ST monad and STRef, lets think about what you actually want to do:

  1. You want to manipulate values conditionally.
  2. You want to return that value.
  3. You want to sequence the steps of your manipulation.

Requirements

Now this indeed looks first like the ST monad. However, if we follow the simple monad laws, together with do notation, we see that

do 
   x <- return $ if somePredicate x then g x
                                    else h x
   x <- return $ if someOtherPredicate x then a x
                                         else b x

is exactly what you want. Since you need only the most basic functions of a monad (return and >>=), you can use the simplest:

The Identity monad

foo x y = runIdentity $ do
    x <- return $ if a x then f x
                         else x
    x <- return $ if c x then g x
                         else h x
    x <- return $ f x 
    y <- return $ if a x then f y
                         else y
    x <- return $ if b y then g x
                         else y
    return (x,y)

Note that you cannot use let x = if a x then f x else x, because in this case the x would be the same on both sides, whereas

x <- return $ if a x then f x 
                     else x

is the same as

(return $ if a x then (f x) else x) >>= \x -> ...

and the x in the if expression is clearly not the same as the resulting one, which is going to be used in the lambda on the right hand side.

Helpers

In order to make this more clear, you can add helpers like

condM :: Monad m => Bool -> a -> a -> m a
condM p a b = return $ if p then a else b

to get an even more concise version:

foo x y = runIdentity $ do
    x <- condM (a x) (f x) x
    x <- fmap f $ condM (c x) (g x) (h x)    
    y <- condM (a y) (f y) y
    x <- condM (b y) (g x) x
    return (x , y)

Ternary craziness

And while we're up to it, lets crank up the craziness and introduce a ternary operator:

(?) :: Bool -> (a, a) -> a
b ? ie = if b then fst ie else snd ie

(??) :: Monad m => Bool -> (a, a) -> m a
(??) p = return . (?) p

(#) :: a -> a -> (a, a)
(#) = (,)

infixr 2 ??
infixr 2 #
infixr 2 ?

foo x y = runIdentity $ do
    x <- a x ?? f x # x
    x <- fmap f $ c x ?? g x # h x
    y <- a y ?? f y # y
    x <- b y ?? g x # x
    return (x , y)

But the bottomline is, that the Identity monad has everything you need for this task.

Imperative or non-imperative

One might argue whether this style is imperative. It's definitely a sequence of actions. But there's no state, unless you count the bound variables. However, then a pack of let … in … declarations also gives an implicit sequence: you expect the first let to bind first.

Using Identity is purely functional

Either way, the code above doesn't introduce mutability. x doesn't get modified, instead you have a new x or y shadowing the last one. This gets clear if you desugar the do expression as noted above:

foo x y = runIdentity $
      a x ?? f x # x   >>= \x ->
      c x ?? g x # h x >>= \x ->
      return (f x)     >>= \x ->
      a y ?? f y # y   >>= \y ->
      b y ?? g x # x   >>= \x ->
      return (x , y)

Getting rid of the simplest monad

However, if we would use (?) on the left hand side and remove the returns, we could replace (>>=) :: m a -> (a -> m b) -> m b) by something with type a -> (a -> b) -> b. This just happens to be flip ($). We end up with:

($>) :: a -> (a -> b) -> b
($>) = flip ($)     
infixr 0 $> -- same infix as ($)

foo x y = a x ? f x # x   $> \x ->
          c x ? g x # h x $> \x ->
          f x             $> \x ->
          a y ? f y # y   $> \y ->
          b y ? g x # x   $> \x ->
          (x, y)

This is very similar to the desugared do expression above. Note that any usage of Identity can be transformed into this style, and vice-versa.

Zeta
  • 103,620
  • 13
  • 194
  • 236
  • 1
    Accepting your answer as it is obviously spot-in in providing exactly what I asked for. Now, wether this is a good style is open to debate. Once, we did everything imperatively. Then Haskell came and showed us there are better alternatives for most of that. Most, but not everything. In my opinion, there **are** problems that are inherently imperative and, for those, this is a great solution. – MaiaVictor Aug 04 '14 at 02:38
  • I would like to thank everyone else, I've investigated every single answer here and learned a lot from that. It is interesting to see how many creative approaches can be applied to the problem. I hope this thread becomes a good reference for future readers. – MaiaVictor Aug 04 '14 at 02:39
  • 1
    About imperative programming: there's a meme that explicitly advertise Haskell as the best imperative language :) http://stackoverflow.com/questions/6622524/why-is-haskell-sometimes-referred-to-as-best-imperative-language (I agree that the Identity monad seems the most straightforward solution in this case) – berdario Aug 04 '14 at 04:20
  • I just want to add that this is not an imperative solution as people may think. This is essentially just a bunch of lambdas composed together :) – is7s Aug 04 '14 at 08:19
  • @is7s: Indeed. The last two examples should make this clear now :D. – Zeta Aug 04 '14 at 08:55
18

The problem you state looks like a nice application for arrows:

import Control.Arrow

if' :: (a -> Bool) -> (a -> a) -> (a -> a) -> a -> a
if' p f g x = if p x then f x else g x

foo2 :: (Int,Int) -> (Int,Int)
foo2 = first (if' c g h . if' a f id) >>>
       first f >>>
       second (if' a f id) >>>
       (\(x,y) -> (if b y then g x else x , y))

in particular, first lifts a function a -> b to (a,c) -> (b,c), which is more idiomatic.

Edit: if' allows a lift

import Control.Applicative (liftA3)

-- a functional if for lifting
if'' b x y = if b then x else y

if' :: (a -> Bool) -> (a -> a) -> (a -> a) -> a -> a
if' = liftA3 if''
Franky
  • 2,339
  • 2
  • 18
  • 27
11

I'd probably do something like this:

foo x y = ( x', y' )
  where x' = bgf y' . cgh . af $ x
        y' = af y

af z    = (if a z then f else id) z
cgh z   = (if c z then g else h) z
bg y x  = (if b y then g else id) x

For something more complicated, you may want to consider using lens:

whenM :: Monad m => m Bool -> m () -> m ()
whenM c a = c >>= \res -> when res a

ifM :: Monad m => m Bool -> m a -> m a -> m a
ifM mb ml mr = mb >>= \b -> if b then ml else mr

foo :: Int -> Int -> (Int, Int)
foo = curry . execState $ do
  whenM (uses _1 a) $ 
    _1 %= f

  ifM (uses _1 c)
    (_1 %= g)
    (_1 %= h)

  _1 %= f

  whenM (uses _2 a) $ 
    _2 %= f

  whenM (uses _2 b) $ do
    _1 %= g

And there's nothing stopping you from using more descriptive variable names:

foo :: Int -> Int -> (Int, Int)
foo = curry . execState $ do
  let x :: Lens (a, c) (b, c) a b
      x = _1
      y :: Lens (c, a) (c, b) a b
      y = _2

  whenM (uses x a) $ 
    x %= f

  ifM (uses x c)
    (x %= g)
    (x %= h)

  x %= f

  whenM (uses y a) $ 
    y %= f

  whenM (uses y b) $ do
    x %= g
rampion
  • 87,131
  • 49
  • 199
  • 315
  • I am upvoting you as you put an effort and managed to find a quite pretty and elegant version of my function! But that was exactly the kind of answer I was trying to avoid when I wrote such a complicated function. What you did will not be useful on the actual use cases of this pattern, such as the "robot cooking procedure" case I mentioned. – MaiaVictor Aug 03 '14 at 17:59
9

This is a job for the ST (state transformer) library.

ST provides:

  • Stateful computations in the form of the ST type. These look like ST s a for a computation that results in a value of type a, and may be run with runST to obtain a pure a value.
  • First-class mutable references in the form of the STRef type. The newSTRef a action creates a new STRef s a reference with an initial value of a, and which can be read with readSTRef ref and written with writeSTRef ref a. A single ST computation can use any number of STRef references internally.

Together, these let you express the same mutable variable functionality as in your imperative example.

To use ST and STRef, we need to import:

{-# LANGUAGE NoMonomorphismRestriction #-}
import Control.Monad.ST.Safe
import Data.STRef

Instead of using the low-level readSTRef and writeSTRef all over the place, we can define the following helpers to match the imperative operations that the Python-style foo example uses:

-- STRef assignment.
(=:) :: STRef s a -> ST s a -> ST s ()
ref =: x  =  writeSTRef ref =<< x

-- STRef function application.
($:) :: (a -> b) -> STRef s a -> ST s b
f $: ref  =  f `fmap` readSTRef ref

-- Postfix guard syntax.
if_ :: Monad m => m () -> m Bool -> m ()
action `if_` guard  =  act' =<< guard
    where act' b = if b then action
                        else return ()

This lets us write:

  • ref =: x to assign the value of ST computation x to the STRef ref.
  • (f $: ref) to apply a pure function f to the STRef ref.
  • action `if_` guard to execute action only if guard results in True.

With these helpers in place, we can faithfully translate the original imperative definition of foo into Haskell:

a = (< 10)
b = even
c = odd
f x = x + 3
g x = x * 2
h x = x - 1
f3 x = x + 2

-- A stateful computation that takes two integer STRefs and result in a final [x,y].
fooST :: Integral n => STRef s n -> STRef s n -> ST s [n]
fooST x y = do
    x =: (f $: x) `if_` (a $: x)

    x' <- readSTRef x
    if c x' then
        x =: (g $: x)
    else
        x =: (h $: x)

    x =: (f $: x)
    y =: (f $: y) `if_` (a $: y)
    x =: (g $: x) `if_` (b $: y)

    sequence [readSTRef x, readSTRef y]

-- Pure wrapper: simply call fooST with two fresh references, and run it.
foo :: Integral n => n -> n -> [n]
foo x y = runST $ do
    x' <- newSTRef x
    y' <- newSTRef y
    fooST x' y'

-- This will print "[9,3]".
main = print (foo 0 0)

Points to note:

  • Although we first had to define some syntactical helpers (=:, $:, if_) before translating foo, this demonstrates how you can use ST and STRef as a foundation to grow your own little imperative language that's directly suited to the problem at hand.
  • Syntax aside, this matches the structure of the original imperative definition exactly, without any error-prone restructuring. Any minor changes to the original example can be mirrored directly to Haskell. (The addition of the temporary x' <- readSTRef x binding in the Haskell code is only in order to use it with the native if/else syntax: if desired, this can be replaced with an appropriate ST-based if/else construct.)
  • The above code demonstrates giving both pure and stateful interfaces to the same computation: pure callers can use foo without knowing that it uses mutable state internally, while ST callers can directly use fooST (and for example provide it with existing STRefs to modify).
Community
  • 1
  • 1
Pi Delport
  • 10,356
  • 3
  • 36
  • 50
6

@Sibi said it best in his comment:

I would suggest you to stop thinking imperatively and rather think in a functional way. I agree that it will take some time to getting used to the new pattern, but try to translate imperative ideas to functional languages isn't a great approach.

Practically speaking, your chain of let can be a good starting point:

foo x0 y0 =
    let x1 = if a x0 then f x0 else x0 in
    let x2 = if c x1 then g x1 else h x1 in
    let x3 = f x2 in
    let y1 = if a y0 then f y0 else y0 in
    let x4 = if b y1 then g x3 else x3 in
    [x4,y1]

But I would suggest using a single let and giving descriptive names to the intermediate stages.

In this example unfortunately I don't have a clue what the various x's and y's do, so I cannot suggest meaningful names. In real code you would use names such as x_normalized, x_translated, or such, instead of x1 and x2, to describe what those values really are.

In fact, in a let or where you don't really have variables: they're just shorthand names you give to intermediate results, to make it easy to compose the final expression (the one after in or before the where.)

This is the spirit behind the x_bar and x_baz below. Try to come up with names that are reasonably descriptive, given the context of your code.

foo x y =
    let x_bar   = if a x then f x else x
        x_baz   = f if c x_bar then g x_bar else h x_bar
        y_bar   = if a y then f y else y
        x_there = if b y_bar then g x_baz else x_baz
    in  [x_there, y_bar]

Then you can start recognizing patterns that were hidden in the imperative code. For example, x_bar and y_bar are basically the same transformation, applied respectively to x and y: that's why they have the same suffix "_bar" in this nonsensical example; then your x2 probably doesn't need an intermediate name , since you can just apply f to the result of the entire "if c then g else h".

Going on with the pattern recognition, you should factor out the transformations that you are applying to variables into sub-lambdas (or whatever you call the auxiliary functions defined in a where clause.)

Again, I don't have a clue what the original code did, so I cannot suggest meaningful names for the auxiliary functions. In a real application, f_if_a would be called normalize_if_needed or thaw_if_frozen or mow_if_overgrown... you get the idea:

foo x y =
    let x_bar   = f_if_a x
        y_bar   = f_if_a y
        x_baz   = f (g_if_c_else_h x_bar)
        x_there = g_if_b x_baz y_bar
    in  [x_there, y_bar]
where
    f_if_a x
        | a x       = f x
        | otherwise = x
    g_if_c_else_h x
        | c x       = g x
        | otherwise = h x
    g_if_b x y
        | b y       = g x
        | otherwise = x

Don't disregard this naming business.

The whole point of Haskell and other pure functional languages is to express algorithms without the assignment operator, meaning the tool that can modify the value of an existing variable.

The names you give to things inside a function definition, whether introduced as arguments, let, or where, can only refer to one value (or auxiliary function) throughout the entire definition, so that your code can be more easily reasoned about and proven correct.

If you don't give them meaningful names (and conversely giving your code a meaningful structure) then you're missing out on the entire purpose of Haskell.

(IMHO the other answers so far, citing monads and other shenanigans, are barking up the wrong tree.)

Tobia
  • 17,856
  • 6
  • 74
  • 93
  • 2
    But I guess you don't understand the point. Imagine that "x" represents a kitchen and the functions represent a robot using that kitchen. So, you get something like that: `kitchen = move_spoons_to_table(kitchen); if (there_are_eggs_on_fridge(kitchen)) put_sugar_on_table(kitchen);` and so on. In that case, there isn't really any meaningful name for the intermediate steps. It is just the kitchen! And if you really use a descriptive a name for every snapshot of the process, you will get some really weird code with abominations such as `kitchenStateAfterBakingCakeButUsingAlternativeSweetener`. – MaiaVictor Aug 04 '14 at 02:20
  • 2
    So, the point is: the algorithm is inherently imperative. It **does describe an imperative action**. The deal with Haskell is that most languages use an imperative style to express everything, even when most of our programs aren't inherently imperative. But there **are** things that are inherently imperative and those need to be representable too! Said that, I really appreciate your answer and thoughts and would love to see your reply for those concerns. Considering what I said, do you think that, for example, Zeta's answer is a great approach - or you still maintain your position? Thank you! – MaiaVictor Aug 04 '14 at 02:23
  • Also, sorry for such a long reply to your answer. Hope I'm not being a help vampire here! – MaiaVictor Aug 04 '14 at 02:25
  • @Viclib Yes, Zeta's answer is a good way to represent a series of imperative steps in Haskell. `do` and `<-` work by enclosing each `<-` and all the lines after that in a new lambda, so that each new `x` is actually a new function argument, that "shadows" the preceding (outer) ones of the same name. You could achieve the same thing by nesting lambdas yourself, without using monads, except that `do` gives you a nicer syntax. I don't know if there is a good syntax for nested lambdas without introducing a monad. – Tobia Aug 04 '14 at 06:14
  • @Viclib I still maintain that for most purposes where you might want to use it, it would be best to rewrite the algorithm in a functional way. If x and y are coordinates, for example, it's much better to give names to the points they represent. Generally speaking, when you can reason about the "space of all states" (domain) of your variable, you can give names to specific points too. When you can't or won't reason about the entire domain, then you can use imperative steps. – Tobia Aug 04 '14 at 06:19
  • @Tobia: Giving sensible names to variables/values isn't really exclusive to functional programming. If I called all widgets in a C++ program `widget_1`, `widget_2`, …, `widget_n`, I would go mad. Instead, I call them `fileSaveDialog`, `nameField`, `panicButton` and so on. That being said, added a lambda-only non-monadic example to my answer, inspired by your comment. – Zeta Aug 04 '14 at 08:53
3

I always prefer layering state transformers to using a single state over a tuple: it definitely declutters things by letting you "focus" on a specific layer (representations of the x and y variables in our case):

import Control.Monad.Trans.Class
import Control.Monad.Trans.State

foo :: x -> y -> (x, y)
foo x y = 
  (flip runState) y $ (flip execStateT) x $ do
    get >>= \v -> when (a v) (put (f v))
    get >>= \v -> put ((if c v then g else h) v)
    modify f
    lift $ get >>= \v -> when (a v) (put (f v))
    lift get >>= \v -> when (b v) (modify g)

The lift function allows us to focus on the inner state layer, which is y.

is7s
  • 3,500
  • 1
  • 20
  • 41
Nikita Volkov
  • 42,792
  • 11
  • 94
  • 169
  • Wouldn't quite agree with that. Transformers are great, but the more you add the more tangled everything becomes... for _focusing_ the obvious thing to use is _[lens](http://hackage.haskell.org/package/lens)es_ as demonstrated by rampion, in a single state entity. – leftaroundabout Aug 03 '14 at 21:36