Transforming a function that computes a fixed point - haskell

I have a function which computes a fixed point in terms of iterate:
equivalenceClosure :: (Ord a) => Relation a -> Relation a
equivalenceClosure = fst . List.head -- "guaranteed" to exist
. List.dropWhile (uncurry (/=)) -- removes pairs that are not equal
. U.List.pairwise (,) -- applies (,) to adjacent list elements
. iterate ( reflexivity
. symmetry
. transitivity
)
Notice that we can abstract from this to:
findFixedPoint :: (a -> a) -> a -> a
findFixedPoint f = fst . List.head
. List.dropWhile (uncurry (/=)) -- dropWhile we have not reached the fixed point
. U.List.pairwise (,) -- applies (,) to adjacent list elements
. iterate
$ f
Can this function be written in terms of fix? It seems like there should be a transformation from this scheme to something with fix in it, but I don't see it.

There's quite a bit going on here, from the mechanics of lazy evaluation, to the definition of a fixed point to the method of finding a fixed point. In short, I believe you may be incorrectly interchanging the fixed point of function application in the lambda calculus with your needs.
It may be helpful to note that your implementation of finding the fixed-point (utilizing iterate) requires a starting value for the sequence of function application. Contrast this to the fix function, which requires no such starting value (As a heads up, the types give this away already: findFixedPoint is of type (a -> a) -> a -> a, whereas fix has type (a -> a) -> a). This is inherently because the two functions do subtly different things.
Let's dig into this a little deeper. First, I should say that you may need to give a little bit more information (your implementation of pairwise, for example), but with a naive first-try, and my (possibly flawed) implementation of what I believe you want out of pairwise, your findFixedPoint function is equivalent in result to fix, for a certain class of functions only
Let's take a look at some code:
{-# LANGUAGE RankNTypes #-}
import Control.Monad.Fix
import qualified Data.List as List
findFixedPoint :: forall a. Eq a => (a -> a) -> a -> a
findFixedPoint f = fst . List.head
. List.dropWhile (uncurry (/=)) -- dropWhile we have not reached the fixed point
. pairwise (,) -- applies (,) to adjacent list elements
. iterate f
pairwise :: (a -> a -> b) -> [a] -> [b]
pairwise f [] = []
pairwise f (x:[]) = []
pairwise f (x:(xs:xss)) = f x xs:pairwise f xss
contrast this to the definition of fix:
fix :: (a -> a) -> a
fix f = let x = f x in x
and you'll notice that we're finding a very different kind of fixed-point (i.e. we abuse lazy evaluation to generate a fixed point for function application in the mathematical sense, where we only stop evaluation iff* the resulting function, applied to itself, evaluates to the same function).
For illustration, let's define a few functions:
lambdaA = const 3
lambdaB = (*)3
and let's see the difference between fix and findFixedPoint:
*Main> fix lambdaA -- evaluates to const 3 (const 3) = const 3
-- fixed point after one iteration
3
*Main> findFixedPoint lambdaA 0 -- evaluates to [const 3 0, const 3 (const 3 0), ... thunks]
-- followed by grabbing the head.
3
*Main> fix lambdaB -- does not stop evaluating
^CInterrupted.
*Main> findFixedPoint lambdaB 0 -- evaluates to [0, 0, ...thunks]
-- followed by grabbing the head
0
now if we can't specify the starting value, what is fix used for? It turns out that by adding fix to the lambda calculus, we gain the ability to specify the evaluation of recursive functions. Consider fact' = \rec n -> if n == 0 then 1 else n * rec (n-1), we can compute the fixed point of fact' as:
*Main> (fix fact') 5
120
where in evaluating (fix fact') repeatedly applies fact' itself until we reach the same function, which we then call with the value 5. We can see this in:
fix fact'
= fact' (fix fact')
= (\rec n -> if n == 0 then 1 else n * rec (n-1)) (fix fact')
= \n -> if n == 0 then 1 else n * fix fact' (n-1)
= \n -> if n == 0 then 1 else n * fact' (fix fact') (n-1)
= \n -> if n == 0 then 1
else n * (\rec n' -> if n' == 0 then 1 else n' * rec (n'-1)) (fix fact') (n-1)
= \n -> if n == 0 then 1
else n * (if n-1 == 0 then 1 else (n-1) * fix fact' (n-2))
= \n -> if n == 0 then 1
else n * (if n-1 == 0 then 1
else (n-1) * (if n-2 == 0 then 1
else (n-2) * fix fact' (n-3)))
= ...
So what does all this mean? depending on the function you're dealing with, you won't necessarily be able to use fix to compute the kind of fixed point you want. This is, to my knowledge, dependent on the function(s) in question. Not all functions have the kind of fixed point computed by fix!
*I've avoided talking about domain theory, as I believe it would only confuse an already subtle topic. If you're curious, fix finds a certain kind of fixed point, namely the least available fixed point of the poset the function is specified over.

Just for the record, it is possible to define the function findFixedPoint using fix.
As Raeez has pointed out, recursive functions can be defined in terms of fix.
The function that you are interested in can be recursively defined as:
findFixedPoint :: Eq a => (a -> a) -> a -> a
findFixedPoint f x =
case (f x) == x of
True -> x
False -> findFixedPoint f (f x)
This means that we can define it as fix ffp where ffp is:
ffp :: Eq a => ((a -> a) -> a -> a) -> (a -> a) -> a -> a
ffp g f x =
case (f x) == x of
True -> x
False -> g f (f x)
For a concrete example, let us assume that f is defined as
f = drop 1
It is easy to see that for every finite list l we have findFixedPoint f l == [].
Here is how fix ffp would work when the "value argument" is []:
(fix ffp) f []
= { definition of fix }
ffp (fix ffp) f []
= { f [] = [] and definition of ffp }
[]
On the other hand, if the "value argument" is [42], we would have:
fix ffp f [42]
= { definition of fix }
ffp (fix ffp) f [42]
= { f [42] =/= [42] and definition of ffp }
(fix ffp) f (f [42])
= { f [42] = [] }
(fix ffp) f []
= { see above }
[]

Related

Fold that's both constant-space and short-circuiting

I'm trying to build a Haskell function that does basically the same thing as Prelude's product. Unlike that function, however, it should have these two properties:
It should operate in constant space (ignoring the fact that some numeric types like Integer aren't). For example, I want myProduct (replicate 100000000 1) to eventually return 1, unlike Prelude's product which uses up all of my RAM and then gives *** Exception: stack overflow.
It should short-circuit when it encounters a 0. For example, I want myProduct (0:undefined) to return 0, unlike Prelude's product which gives *** Exception: Prelude.undefined.
Here's what I've come up with so far:
myProduct :: (Eq n, Num n) => [n] -> n
myProduct = go 1
where go acc (x:xs) = if x == 0 then 0 else acc `seq` go (acc * x) xs
go acc [] = acc
That works exactly how I want it to for lists, but I'd like to generalize it to have type (Foldable t, Eq n, Num n) => t n -> n. Is it possible to do this with any of the folds? If I just use foldr, then it will short-circuit but won't be constant-space, and if I just use foldl', then it will be constant-space but won't short-circuit.
If you spell your function slightly differently, it's more obvious how to turn it into a foldr. Namely:
myProduct :: (Eq n, Num n) => [n] -> n
myProduct = flip go 1 where
go (x:xs) = if x == 0 then \acc -> 0 else \acc -> acc `seq` go xs (acc * x)
go [] = \acc -> acc
Now go has got that foldr flavor, and we can just fill in the holes.
myProduct :: (Foldable t, Eq n, Num n) => t n -> n
myProduct = flip go 1 where
go = foldr
(\x f -> if x == 0 then \acc -> 0 else \acc -> acc `seq` f (acc * x))
(\acc -> acc)
Hopefully you can see where each of those pieces came from in the previous explicit-recursion style and how mechanical the transformation is. Then I'd make a few aesthetic tweaks:
myProduct :: (Foldable t, Eq n, Num n) => t n -> n
myProduct xs = foldr step id xs 1 where
step 0 f acc = 0
step x f acc = f $! acc * x
And we're all done! A bit of quick testing in ghci reveals that it still short-circuits on 0 as required and uses constant space when specialized to lists.
You might be looking for foldM. Instantiate it with m = Either b and you get short circuiting behavior (or Maybe, depends if you have many possible early exit values, or one known in advance).
foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b
I recall discussions whether there should be foldM', but IIRC GHC does the right thing most of the time.
import Control.Monad
import Data.Maybe
myProduct :: (Foldable t, Eq n, Num n) => t n -> n
myProduct = fromMaybe 0 . foldM go 1
where go acc x = if x == 0 then Nothing else Just $! acc * x

Is there a way to capture a tuple of higher-order functions in Haskell?

I understand that it's impossible to pattern match functions in Haskell, and I fully understand why. However, I have two closely related questions. First, in cases where you'd like to partially apply functions for use later, is there a way of defining and capturing the return if it's a tuple? Or am I wrong, and this is still trying to pattern match functions under my nose?
For example, suppose I'm trying to get the quotient and remainder of a value with various multiples of ten. Then, how would I write something like this?
q, r :: Integral a => a -> a
(q, r) = (12345 `quotRem`)
I realize here, there are separate functions that exist, so I could do this instead:
q, r :: Integral a => a -> a
q = (12345 `quot`)
r = (12345 `rem`)
However, that's a very specific case, and there are unlimited other examples of functions that return tuples that would be nice to generalize. For example, a function that returns the number of evens and odds in a list.
evens, odds :: Integral a => [a] -> Int
(evens, odds) = (length . (filter even), length . (filter odd))
This leads me to my second question. The above works just fine in GHCi.
Prelude> let (evens, odds) = (length . (filter even), length . (filter odd))
Prelude> :t evens
evens :: Integral a => [a] -> Int
Prelude> evens [1..10]
5
What's even more confusing is it even works by "pattern-matching" in the same way that I was playing with (q, r) in the beginning:
Prelude> let evensOdds = (length . (filter even), length . (filter odd))
Prelude> :t evensOdds
evensOdds :: (Integral a1, Integral a) => ([a1] -> Int, [a] -> Int)
Prelude> let (ev,od) = evensOdds
Prelude> :t ev
ev :: Integral a1 => [a1] -> Int
Prelude> ev [1..10]
5
It also works just fine in an actual file loaded into GHCi, even though (evens, odds) doesn't. Why are these two different, and why does the second one work in GHCi at all if it doesn't work normally? Can what's different here be leveraged in some way?
You never pattern matched on a function. You always pattern matched on the pair-constructor (,). Your (even, odds) example
(evens, odds) = (length . (filter even), length . (filter odd))
just works like
(first, second) = (x, y)
It doesn't matter what type x and y have at that point.
Your (q, r) example doesn't work due to quotRem's type. Let's recall it and compare it with (q, r)'s type:
quotRem :: Integral n => n -> n -> (n , n)
quotRem 12345 :: Integral n => n -> (n , n)
(q, r) :: Integral n => (n -> n, n -> n)
As you can see, the pair (q, r)'type differs from quotRem's one. Still, it's possible to write your function:
pairify :: (a -> (b, c)) -> (a -> b, a -> c)
pairify f = (fst . f, snd . f)
(q,r) = pairify (quotRem 12345)
But as you can see we don't gain too much from pairify. By the way, partition from Data.List provides your (even, odds) functionality:
(even, odds) = pairify (partition even)
Look at the type of (12345 `quotRem`):
Integral a => a -> (a, a)
It’s a single function that returns a tuple. If you want to make this into a tuple of functions, you can compose it with fst and snd:
(q, r) = (fst . f, snd . f)
where f = (12345 `quotRem`)
If you want to do this in a point-free way, one way is to use the &&& combinator from Control.Arrow. Its fully general type is:
Arrow a => a b c -> a b d -> a b (c, d)
Specialised to the -> arrow, that’s:
(b -> c) -> (b -> d) -> b -> (c, d)
So it takes two functions, each taking a value of type b, and returns both their results (of types c and d) in a tuple. So here you can do something like this:
split = (fst .) &&& (snd .)
(q, r) = split (12345 `quotRem`)
Whereas if you look at the type of (length . filter even, length . filter odd), it’s a tuple already,
(Integral a, Integral b) => ([a] -> Int, [b] -> Int)
Which is why of course you can destructure this tuple to bind evens and odds.

Project Euler 3 - Haskell

I'm working my way through the Project Euler problems in Haskell. I have got a solution for Problem 3 below, I have tested it on small numbers and it works, however due to the brute force implementation by deriving all the primes numbers first it is exponentially slow for larger numbers.
-- Project Euler 3
module Main
where
import System.IO
import Data.List
main = do
hSetBuffering stdin LineBuffering
putStrLn "This program returns the prime factors of a given integer"
putStrLn "Please enter a number"
nums <- getPrimes
putStrLn "The prime factors are: "
print (sort nums)
getPrimes = do
userNum <- getLine
let n = read userNum :: Int
let xs = [2..n]
return $ getFactors n (primeGen xs)
--primeGen :: (Integral a) => [a] -> [a]
primeGen [] = []
primeGen (x:xs) =
if x >= 2
then x:primeGen (filter (\n->n`mod` x/=0) xs)
else 1:[2]
--getFactors
getFactors :: (Integral a) => a -> [a] -> [a]
getFactors n xs = [ x | x <- xs, n `mod` x == 0]
I have looked at the solution here and can see how it is optimised by the first guard in factor. What I dont understand is this:
primes = 2 : filter ((==1) . length . primeFactors) [3,5..]
Specifically the first argument of filter.
((==1) . length . primeFactors)
As primeFactors is itself a function I don't understand how it is used in this context. Could somebody explain what is happening here please?
If you were to open ghci on the command line and type
Prelude> :t filter
You would get an output of
filter :: (a -> Bool) -> [a] -> [a]
What this means is that filter takes 2 arguments.
(a -> Bool) is a function that takes a single input, and returns a Bool.
[a] is a list of any type, as longs as it is the same type from the first argument.
filter will loop over every element in the list of its second argument, and apply it to the function that is its first argument. If the first argument returns True, it is added to the resulting list.
Again, in ghci, if you were to type
Prelude> :t (((==1) . length . primeFactors))
You should get
(((==1) . length . primeFactors)) :: a -> Bool
(==1) is a partially applied function.
Prelude> :t (==)
(==) :: Eq a => a -> a -> Bool
Prelude> :t (==1)
(==1) :: (Eq a, Num a) => a -> Bool
It only needs to take a single argument instead of two.
Meaning that together, it will take a single argument, and return a Boolean.
The way it works is as follows.
primeFactors will take a single argument, and calculate the results, which is a [Int].
length will take this list, and calculate the length of the list, and return an Int
(==1) will
look to see if the values returned by length is equal to 1.
If the length of the list is 1, that means it is a prime number.
(.) :: (b -> c) -> (a -> b) -> a -> c is the composition function, so
f . g = \x -> f (g x)
We can chain more than two functions together with this operator
f . g . h === \x -> f (g (h x))
This is what is happening in the expression ((==1) . length . primeFactors).
The expression
filter ((==1) . length . primeFactors) [3,5..]
is filtering the list [3, 5..] using the function (==1) . length . primeFactors. This notation is usually called point free, not because it doesn't have . points, but because it doesn't have any explicit arguments (called "points" in some mathematical contexts).
The . is actually a function, and in particular it performs function composition. If you have two functions f and g, then f . g = \x -> f (g x), that's all there is to it! The precedence of this operator lets you chain together many functions quite smoothly, so if you have f . g . h, this is the same as \x -> f (g (h x)). When you have many functions to chain together, the composition operator is very useful.
So in this case, you have the functions (==1), length, and primeFactors being compose together. (==1) is a function through what is called operator sections, meaning that you provide an argument to one side of an operator, and it results in a function that takes one argument and applies it to the other side. Other examples and their equivalent lambda forms are
(+1) => \x -> x + 1
(==1) => \x -> x == 1
(++"world") => \x -> x ++ "world"
("hello"++) => \x -> "hello" ++ x
If you wanted, you could re-write this expression using a lambda:
(==1) . length . primeFactors => (\x0 -> x0 == 1) . length . primeFactors
=> (\x1 -> (\x0 -> x0 == 1) (length (primeFactors x1)))
Or a bit cleaner using the $ operator:
(\x1 -> (\x0 -> x0 == 1) $ length $ primeFactors x1)
But this is still a lot more "wordy" than simply
(==1) . length . primeFactors
One thing to keep in mind is the type signature for .:
(.) :: (b -> c) -> (a -> b) -> a -> c
But I think it looks better with some extra parentheses:
(.) :: (b -> c) -> (a -> b) -> (a -> c)
This makes it more clear that this function takes two other functions and returns a third one. Pay close attention the the order of the type variables in this function. The first argument to . is a function (b -> c), and the second is a function (a -> b). You can think of it as going right to left, rather than the left to right behavior that we're used to in most OOP languages (something like myObj.someProperty.getSomeList().length()). We can get this functionality by defining a new operator that has the reverse order of arguments. If we use the F# convention, our operator is called |>:
(|>) :: (a -> b) -> (b -> c) -> (a -> c)
(|>) = flip (.)
Then we could have written this as
filter (primeFactors |> length |> (==1)) [3, 5..]
And you can think of |> as an arrow "feeding" the result of one function into the next.
This simply means, keep only the odd numbers that have only one prime factor.
In other pseodo-code: filter(x -> length(primeFactors(x)) == 1) for any x in [3,5,..]

What else can `loeb` function be used for?

I am trying to understand "Löb and möb: strange loops in Haskell", but right now the meaning is sleaping away from me, I just don't see why it could be useful. Just to recall function loeb is defined as
loeb :: Functor f => f (f a -> a) -> f a
loeb x = go where go = fmap ($ go) x
or equivalently:
loeb x = go
where go = fmap (\z -> z go) x
In the article there is an example with [] functor and spreadsheets implementation, but it is bit foreign for me just as spreadsheets themselves (never used them).
While I'm understanding that spreadsheet thing, I think it would help a lot for me and others to have more examples, despite lists. Is there any application for loeb for Maybe or other functors?
The primary source (I think) for loeb is Dan Piponi's blog, A Neighborhood of Infinity. There he explains the whole concept in greater detail. I'll replicate a little bit of that as an answer and add some examples.
loeb implements a strange kind of lazy recursion
loeb :: Functor a => a (a x -> x) -> a x
loeb x = fmap (\a -> a (loeb x)) x
Let's imagine we have a type a, where Functor a, and an a-algebra (a function of type a x -> x). You might think of this as a way of computing a value from a structure of values. For instance, here are a few []-algebras:
length :: [Int] -> Int
(!! 3) :: [a] -> a
const 3 :: Num a => [a] -> a
\l -> l !! 2 + l !! 3 :: Num a => [a] -> a
We can see that these a-algebras can use both values stored in the Functor and the structure of the Functor itself.
Another way to think of d :: a x -> x is as a value of x which requires some context–a whole Functorized value a x–in order to be computed. Perhaps this interpretation is more clearly written as Reader (a x) x, emphasizing that this is just a value of x which is delayed, awaiting the a x context to be produced.
type Delay q x = q -> x
Using these ideas we can describe loeb as follows. We're given a f-structure containing some Delayed values, where f is a Functor
Functor f, f (Delay q x)
Naturally, if we were given a q then we could convert this into a not delayed form. In fact, there's only one (non-cheating) function that does this polymorphically:
force :: Functor f => f (Delay q x) -> q -> f x
force f q = fmap ($ q) f
What loeb does is handle the extra tricky case where q is actually force f q, the very result of this function. If you're familiar with fix, this is exactly how we can produce this result.
loeb :: Functor a => a (Delay (a x) x) -> a x
loeb f = fix (force f)
So to make an example, we simply must build a structure containing Delayed values. One natural example of this is to use the list examples from before
> loeb [ length :: [Int] -> Int
, const 3 :: [Int] -> Int
, const 5 :: [Int] -> Int
, (!! 2) :: [Int] -> Int
, (\l -> l !! 2 + l !! 3) :: [Int] -> Int
]
[5, 3, 5, 5, 10]
Here we can see that the list is full of values delayed waiting on the result of evaluating the list. This computation can proceed exactly because there are no loops in data dependency, so the whole thing can just be determined lazily. For instance, const 3 and const 5 are both immediately available as values. length requires that we know the length of the list but none of the values contained so it also proceeds immediately on our fixed-length list. The interesting ones are the values delayed waiting on other values from inside our result list, but since (!! 2) only ends up depending on the third value of the result list, which is determined by const 5 and thus can be immediately available, the computation moves forward. The same idea happens with (\l -> l !! 2 + l !! 3).
So there you have it: loeb completes this strange kind of delayed value recursion. We can use it on any kind of Functor, though. All we need to do is to think of some useful Delayed values.
Chris Kuklewicz's comment notes that there's not a lot you could do interestingly with Maybe as your functor. That's because all of the delayed values over Maybe take the form
maybe (default :: a) (f :: a -> a) :: Maybe a -> a
and all of the interesting values of Maybe (Delay (Maybe a) a) ought to be Just (maybe default f) since loeb Nothing = Nothing. So at the end of the day, the default value never even gets used---we always just have that
loeb (Just (maybe default f)) == fix f
so we may as well write that directly.
You can use it for dynamic programming. The example that comes to mind is the Smith-Waterman algorithm.
import Data.Array
import Data.List
import Control.Monad
data Base = T | C | A | G deriving (Eq,Show)
data Diff = Sub Base Base | Id Base | Del Base | Ins Base deriving (Eq,Show)
loeb x = let go = fmap ($ go) x in go
s a b = if a == b then 1 else 0
smithWaterman a' b' = let
[al,bl] = map length [a',b']
[a,b] = zipWith (\l s -> array (1,s) $ zip [1..] l) [a',b'] [al,bl]
h = loeb $ array ((0,0),(al,bl)) $
[((x,0),const 0) | x <- [0 .. al]] ++
[((0,y),const 0) | y <- [1 .. bl]] ++
[((x,y),\h' -> maximum [
0,
(h' ! (x - 1,y - 1)) + s (a ! x) (b ! y),
(h' ! (x - 1, y)) + 1,
(h' ! (x, y - 1)) + 1
]
) | x <- [1 .. al], y <- [1 .. bl]]
ml l (0,0) = l
ml l (x,0) = ml (Del (a ! x): l) (x - 1, 0)
ml l (0,y) = ml (Ins (b ! y): l) (0, y - 1)
ml l (x,y) = let
(p,e) = maximumBy ((`ap` snd) . (. fst) . (const .) . (. (h !)) . compare . (h !) . fst) [
((x - 1,y),Del (a ! x)),
((y, x - 1),Ins (b ! y)),
((y - 1, x - 1),if a ! x == b ! y then Id (a ! x) else Sub (a ! x) (b ! y))
]
in ml (e : l) p
in ml [] (al,bl)
Here is a live example where it is used for: Map String Float
http://tryplayg.herokuapp.com/try/spreadsheet.hs/edit
with loop detection and loop resolution.
This program calculates speed, time and space. Each one depends on the other two. Each cell has two values: his current entered value and the expression as a function of the other cell values/expressions. circularity is permitted.
The Cell recalculation code uses the famous loeb expression by Dan Piponi in the 2006. Until now by my knowledge there haven't been any materialization of this formula on a real working spreadsheet. this one is close to it. Since loeb enters in a infinite loop when circular expressions are used, the program counts the loops and reduces complexity by progressively substituting formulas by cell values until the expression has no loops
This program is configured for immediate recalculation on cell change, but that can be adapted to allow the modification of more than one cell before recalculation by triggering it by means of a button.
This is blog pos:
http://haskell-web.blogspot.com.es/2014/09/spreadsheet-like-program-in-browser.html

There is a function that searches for an attractive fixed point through iteration. Can we generalize it to monadic functions?

Intro
Fixed points are such arguments to a function that it would return unchanged: f x == x. An example would be (\x -> x^2) 1 == 1 -- here the fixed point is 1.
Attractive fixed points are those fixed points that can be found by iteration from some starting point. For example, (\x -> x^2) 0.5 would converge to 0, thus 0 is an attractive fixed point of this function.
Attractive fixed points can be, with luck, approached (and, in some cases, even reached in that many steps) from a suitable non-fixed point by iterating the function from that point. Other times, the iteration will diverge, so there should first be a proof in place that a fixed point will attract the iterating process. For some functions, the proof is common knowledge.
The code
I have tidied up some prior art that accomplishes the task neatly. I then set out to extend the same idea to monadic functions, but to no luck. This is the code I have by now:
module Fix where
-- | Take elements from a list until met two equal adjacent elements. Of those,
-- take only the first one, then be done with it.
--
-- This function is intended to operate on infinite lists, but it will still
-- work on finite ones.
converge :: Eq a => [a] -> [a]
converge = convergeBy (==)
-- \ r a = \x -> (x + a / x) / 2
-- \ -- ^ A method of computing square roots due to Isaac Newton.
-- \ take 8 $ iterate (r 2) 1
-- [1.0,1.5,1.4166666666666665,1.4142156862745097,1.4142135623746899,
-- 1.414213562373095,1.414213562373095,1.414213562373095]
-- \ converge $ iterate (r 2) 1
-- [1.0,1.5,1.4166666666666665,1.4142156862745097,1.4142135623746899,1.414213562373095]
-- | Find a fixed point of a function. May present a non-terminating function
-- if applied carelessly!
fixp :: Eq a => (a -> a) -> a -> a
fixp f = last . converge . iterate f
-- \ fixp (r 2) 1
-- 1.414213562373095
-- | Non-overloaded counterpart to `converge`.
convergeBy :: (a -> a -> Bool) -> [a] -> [a]
convergeBy _ [ ] = [ ]
convergeBy _ [x] = [x]
convergeBy eq (x: xs#(y: _))
| x `eq` y = [x]
| otherwise = x : convergeBy eq xs
-- \ convergeBy (\x y -> abs (x - y) < 0.001) $ iterate (r 2) 1
-- [1.0,1.5,1.4166666666666665,1.4142156862745097]
-- | Non-overloaded counterpart to `fixp`.
fixpBy :: (a -> a -> Bool) -> (a -> a) -> a -> a
fixpBy eq f = last . convergeBy eq . iterate f
-- \ fixpBy (\x y -> abs (x - y) < 0.001) (r 2) 1
-- 1.4142156862745097
-- | Find a fixed point of a monadic function. May present a non-terminating
-- function if applied carelessly!
-- TODO
fixpM :: (Eq a, Monad m) => (m a -> m a) -> m a -> m a
fixpM f = last . _ . iterate f
(It may be loaded in repl. There are examples to be run in the comments, for illustration.)
The problem
There is an _ in the definition of fixpM above. It is a function of type [m a] -> [m a] that should do, in principle, the same as the function converge above, but kinda lifted. I have come to suspect it can't be written.
I do have composed another, specialized code for fixpM:
fixpM :: (Eq a, Monad m) => (a -> m a) -> a -> m a
fixpM f x = do
y <- f x
if x == y
then return x
else fixpM f y
-- \ fixpM (\x -> (".", x^2)) 0.5
-- ("............",0.0)
(An example run is, again, found in a comment.)
-- But it is a whole different algorithm, not an extension / generalization of the pure function we started with. In particular, we do not pass the stage where a list of inits up to the first repetition is made available.
Can we not extend the pure algorithm to work on monadic functions?
And why so?
I would admire a hint towards a piece of theory that explains how to either prove impossibility or construct a solution in a routine fashion, but perhaps this is just a triviality I'm missing while busy typing idle questions, in which case a straightforward counterexample would defeat me.
P.S. I understand this is a somewhat trivial exercise. Still, I want to have become done with it once and forever.
P.S. 2 A better approximation to the pure variant, as suggested by #n-m (retaining iterate), would look like this:
fixpM :: (Eq a, Monad m) => (m a -> m a) -> m a -> m a
fixpM f = collapse . iterate f
where
collapse (mx: mxs #(my: _)) = do
x <- mx
y <- my
if x == y
then return x
else collapse mxs
Through the use of iterate, its behaviour with regard to the monad is different in that the effects are retained between consecutive approximations. Performance-wise, these functions are of the same complexity.
P.S. 3 A more complete rendition of the ideas offered by #n-m encodes the algorithm, as far as I can see, one to one with the pure variant:
fixpM :: (Eq a, Monad m) => (m a -> m a) -> m a -> m a
fixpM f = lastM . convergeM . iterate (f >>= \x -> return x )
convergeM :: (Monad m, Eq a) => [m a] -> m [a]
convergeM = convergeByM (==)
convergeByM :: (Monad m, Eq a) => (a -> a -> Bool) -> [m a] -> m [a]
convergeByM _ [ ] = return [ ]
convergeByM _ [mx] = mx >>= \x -> return [x]
convergeByM eq xs = do
case xs of
[ ] -> return [ ]
[mx] -> mx >>= \x -> return [x]
(mx: mxs #(my: _)) -> do
x <- mx
y <- my
if x `eq` y
then return [x]
else do
xs <- convergeM mxs
return (x:xs)
lastM :: Monad m => m [a] -> m a
lastM mxs = mxs >>= \xs -> case xs of
[] -> error "Fix.lastM: No last element!"
xs -> return . head . reverse $ xs
Unfortunately, it happens to be rather lengthy. More substantially, both these solutions have the same somewhat undesirable behaviour with regard to the effects of the monad: all the effects are retained between consecutive approximations.

Resources