问题
>>>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!"
回答1:
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.
回答2:
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"
来源:https://stackoverflow.com/questions/15523093/haskell-flip-fix-fix