5

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.

Ignat Insarov
  • 4,444
  • 13
  • 34
  • `convergeM` cannot be written, but it is not needed. Write a function that combines the effects of `converge` and `last` *efficiently* (i.e. without traversing the list twice), and you should be able to loft it. – n. 'pronouns' m. Jan 20 '18 at 07:19
  • @n.m. Why can't it? – Ignat Insarov Jan 20 '18 at 07:34
  • Because it wants to return `[m a]` but it only allowed to return things that look like `m something`. `m [a]` is OK but then `last` won't work and you need `lastM`. Not that it's hard to do, but it's wasteful. – n. 'pronouns' m. Jan 20 '18 at 07:51
  • @n.m. Wasteful in a sense of lines of code exerted on `lastM`? – Ignat Insarov Jan 20 '18 at 08:10
  • Wasteful in a sense of building a list and then traversing it to find its last element. Why would you do that? – n. 'pronouns' m. Jan 20 '18 at 08:22
  • @n.m. I have sketched a solution according to what you are saying and I will update the question with it shortly, but I believe it will be to the benefit of everyone observing if you yourself compose an answer -- a form both more spacious and more endurant. There are quite a few presuppositions worth unraveling here. – Ignat Insarov Jan 20 '18 at 08:38
  • 1
    @Kindaro: I still do not see why you need the *last* element, why not build and access the list in reverse – Willem Van Onsem Jan 20 '18 at 11:46
  • 1
    @Kindaro I believe it's impossible to write `fixpM` without getting the side effects of the intermediate approximations. Think about it; it doesn't make sense that you can get the approximation out of a computation and check whether it's close to the previous one without actually doing the computation! If you mean, e.g. `State s` altering the `s` as the approximations are calculated, well, *too bad*. You can alter the argument to `fixpM` to restore the state as well as possible, but a) `fixpM` can't do that itself and b) good luck doing that to `IO` or the like. – HTNW Jan 20 '18 at 20:37

0 Answers0