10
>>>flip fix (0 :: Int) (\a b -> putStrLn "abc")
Output: "abc"

This is a simplified version of using flip fix.
I saw this way of using it in some youtube video which are probably from google tech talk or some other talks.

Can somebody give me some pointers(not some memory address, thanks!) that what exactly fix is. I know the general definition from documentation on the official site. And I have scanned through lots of stuff on the internet, just couldn't find an answer that is comprehensive and simple to understand.

And flip fix just looks like a mystery to me. What actually happened in that particular function call?

BTW, I only picked Haskell up like 2 months ago. And I'm not very good at Math :(


This is the complete code, shared by the person who did that presentation, if anyone is interested:

(Oh, and here's the wiki link explaining the game mastermind Click)

module Mastermind where

import Control.Monad
import Data.Function
import Data.List
import System.Random

data Score = Score
  { scoreRightPos :: Int
  , scoreWrongPos :: Int
  }
  deriving (Eq, Show)

instance Read Score where
  readsPrec _ r = [ (Score rp wp, t)
                  | (rp, s) <- readsPrec 11 r
                  , (wp, t) <- readsPrec 11 s
                  ]

calcScore :: (Eq a) => [a] -> [a] -> Score
calcScore secret guess = Score rightPos wrongPos
  where
    rightPos    = length [() | (a, b) <- zip secret guess, a == b]
    wrongPos    = length secret - length wrongTokens - rightPos
    wrongTokens = guess \\ secret

pool :: String
pool = "rgbywo"

universe :: [String]
universe = perms 4 pool

perms :: Int -> [a] -> [[a]]
perms n p = [s' | s <- subsequences p, length s == n, s' <- permutations s]

chooseSecret :: IO String
chooseSecret = do
  i <- randomRIO (0, length universe - 1)
  return $ universe !! i

guessSecret :: [Score] -> [String]-> [String]
guessSecret _      []    = []
guessSecret ~(s:h) (g:u) = g : guessSecret h [g' | g' <- u, calcScore g' g == s]

playSecreter :: IO ()
playSecreter = do
  secret <- chooseSecret
  flip fix (0 :: Int) $ \loop numGuesses -> do
    putStr "Guess: "
    guess <- getLine
    let
      score       = calcScore secret guess
      numGuesses' = numGuesses + 1
    print score
    case scoreRightPos score of
      4 -> putStrLn $ "Well done, you guessed in " ++ show numGuesses'
      _ -> loop numGuesses'

playBoth :: IO ()
playBoth = do
  secret <- chooseSecret
  let
    guesses     = guessSecret scores universe
    scores      = map (calcScore secret) guesses
    history     = zip guesses scores
  forM_ history $ \(guess, score) -> do
    putStr "Guess: "
    putStrLn guess
    print score
  putStrLn $ "Well done, you guessed in " ++ show (length history)

playGuesser :: IO ()
playGuesser = do
  input <- getContents
  let
    guesses     = guessSecret scores universe
    scores      = map read $ lines input
    history     = zip guesses scores
  forM_ guesses $ \guess -> do
    putStrLn guess
    putStr "Score: "
  case snd $ last history of
    Score 4 0 -> putStrLn $ "Well done me, I guessed in " ++ show (length history)
    _         -> putStrLn "Cheat!"
duplode
  • 31,361
  • 7
  • 69
  • 130
pochen
  • 855
  • 10
  • 21
  • FYI, the talk was about implementing the game Mastermind, given by Peter Marks at the London Haskell Users' Group. – Tom Ellis Nov 15 '13 at 15:17

2 Answers2

15

fix is the fixed-point operator. As you probably know from it's definition, it computes the fixed point of a function. This means, for a given function f, it searches for a value x such that f x == x.

How to find such a value for an arbitrary function?

We can view x as the result of infinite term f (f (f ... ) ...)). Obviously, since it is infinite, adding f in front of it doesn't change it, so f x will be the same as x. Of course, we cannot express an infinite term, but we can define fix as fix f = f (fix f), which expresses the idea.

Does it makes sense?

Will it ever terminate? Yes, it will, but only because Haskell is a lazy language. If f doesn't need its argument, it will not evaluate it, so the computation will terminate, it won't loop forever. If we call fix on a function that always uses its argument (it is strict), it will never terminate. So some functions have a fixed point, some don't. And Haskell's lazy evaluation ensures that we compute it, if it exists.

Why is fix useful?

It expresses recursion. Any recursive function can be expressed using fix, without any additional recursion. So fix is a very powerful tool! Let's say we have

fact :: Int -> Int
fact 0 = 1
fact n = n * fact (n - 1)

we can eliminate recursion using fix as follows:

fact :: Int -> Int
fact = fix fact'
  where
    fact' :: (Int -> Int) -> Int -> Int
    fact' _ 0 = 1
    fact' r n = n * r (n - 1)

Here, fact' isn't recursive. The recursion has been moved into fix. The idea is that fact' accepts as its first argument a function that it will use for a recursive call, if it needs to. If you expand fix fact' using the definition of fix, you'll see that it does the same as the original fact.

So you could have a language that only has a primitive fix operator and otherwise doesn't permit any recursive definitions, and you could express everything you can with recursive definitions.

Back to your example

Let's view flip fix (0 :: Int) (\a b -> putStrLn "abc"), it is just fix (\a b -> putStrLn "abc") (0 :: Int). Now let's evaluate:

fix (\a b -> putStrLn "abc") =
(\a b -> putStrLn "abc") (fix (\a b -> putStrLn "abc")) =
\b -> putStrLn "abc"

So the whole expression evaluates to (\b -> putStrLn "abc") (0 :: Int) which is just putStrLn "abc". Because function \a b -> putStrLn "abc" ignores its first argument, fix never recurses. It's actually used here only to obfuscate the code.

Petr
  • 60,177
  • 8
  • 136
  • 295
  • 1
    How wonderful! I just happen to be watching another video about laziness when I see your explanation, the speaker is Simon Peyton Jones! Laziness for the win. I didn't know that `fix` could terminate only because it's Haskell! – pochen Mar 20 '13 at 12:46
  • So `fact'` is the first argument for itself, and the `Int` argument (**0** in the first pattern matching, **n** in the second pattern matching) is just the same as the only (omitted) argument for `fact`. Is that right? @Petr Pudlák – pochen Mar 20 '13 at 12:58
  • 1
    @prM The first argument to `fact'` is actually `fix fact'`. We say to `fact'` something like "compute one level of the computation and we give you the recursive version of yourself, if you need". Function `fact'` is of type `(Int -> Int) -> (Int -> Int)`, and when we use `fix` on it, we compute its fixed point of type `(Int -> Int)`. So the fixed point result is a function! This is why we have just `fix fact'` there. And you're right, the second `Int` argument for `fact'` correspond to the only argument of `fact`. – Petr Mar 20 '13 at 14:07
  • @prM Wikipedia article [Fixed-point combinator](https://en.wikipedia.org/wiki/Fixed-point_combinator) also provides valuable information. If you're also studying the lambda calculus, you might be interested in [Clear, intuitive derivation of the fixed-point combinator (Y combinator)?](http://cs.stackexchange.com/q/9604/2448). `Y` combinator is basically the same thing as `fix`, only expressed in the untyped lambda calculus. (In Haskell, we define `fix` as a recursive function, but in the untyped lambda calculus, we can define this operator as a lambda term, without any recursion.) – Petr Mar 20 '13 at 14:11
  • I've written `flip fix` in production code before. It has a couple uses. `flip fix arg0 $ \loop arg -> do { ... something that uses loop conditionally, passing in a new value for arg ...}`, in particular. Fewest parens and extra definitions when you're creating recursive functions inside a do block that depend on names already bound in the scope of the do block. – Carl Mar 20 '13 at 17:47
  • 3
    Excellent answer. I'd emphasize two things, however: (a) it's worth explicitly pointing out that the first equation for `fact'`, `fact' _ 0 = 1`, doesn't use its first argument, which is how the `fact' (fact' (...))` infinite stack is "exited" in this case; (b) while the `fix f = f (fix f)` definition is the easier one to understand, the more practical alternative is `fix f = let r = f r in r`, which is more performance-friendly; the easy one tends to compile to code that allocates a new thunk at each step, while the `let` version leads to circular reference graphs that reuse the same thunks. – Luis Casillas Mar 20 '13 at 18:18
  • Thank you @PetrPudlák ! Impressive answers! One last thing I don't understand, how does the type of `fix fact'` fit into `fact'`? – pochen Mar 21 '13 at 06:06
  • Thank you @sacundim ! Always good to know more about performance :) – pochen Mar 21 '13 at 06:06
  • @prM Consider what `fix f` does - it searches for `x` such that `f x = x`. This means that `f` must be a function from some type `a` to `a`, in other words `f :: a -> a`. And its fixed point is of course of the same type as the argument and result of `f` - `fix f :: a`. So `fix` alone has type `fix :: (a -> a) -> a`. In the case of `fact'`, our `a` is `Int -> Int`. So `fact' :: (Int -> Int) -> (Int -> Int)` and `fix fact' :: Int -> Int`. – Petr Mar 21 '13 at 07:02
4

This is just a funny way to write a recursive lambda, I can think of two possibilities why this is done:

  • The programmer wanted to confuse newbies.
  • He comes from a language that is more restrictive with recursion (like some LISP, or ML maybe?)

You could rewrite the code much clearer like:

    loop secret 0
where
    loop secret numGuesses = do
         putStr "Guess: "
         guess <- getLine
         let
             score       = calcScore secret guess
             numGuesses' = numGuesses + 1
         print score
         case scoreRightPos score of
           4 -> putStrLn $ "Well done, you guessed in " ++ show numGuesses'
           _ -> loop secret numGuesses'

The difference being that you must pass the secret manually, which is avoided by the recursive lambda (and this might be another reason to write it with fix)

For a deeper understanding of fix, goog for "y-combinator"

Ingo
  • 34,949
  • 5
  • 49
  • 97