[Haskell-cafe] Uses of `fix' combinator

Miguel Mitrofanov miguelimo38 at yandex.ru
Thu Feb 19 09:31:08 EST 2009


Each data type in Haskell contains one element, which is usually  
"invisible". It's called "bottom" and denoted by (_|_).

Naturally (_|_) of type Int and (_|_) of type Char are different;  
however, they are denoted as if they are the same, 'cause there isn't  
much difference between them. Anyway, if you try to calculate  
something which happens to be (_|_) and your program would throw an  
error or loop forever.

Now, since there is (_|_)::Int and (_|_)::Char, there are also ((_|_), 
(_|_)) :: (Int, Char) as well as (1, (_|_)) :: (Int, Char) and ((_|_),  
'a') :: (Int, Char); all of them are different from (_|_) :: (Int,  
Char). If a value contains (_|_) somewhere inside it, we say that it  
is less defined than the value obtained from it by replacing (_|_)s  
with something else. For example, (_|_) is less defined than ((_|_),(_| 
_)), which is less defined than (1, (_|_)) or ((_|_), 'a'); and both  
of them are less defined than (1, 'a').

'fix' is a function which maps a function 'f' to the LEAST defined x  
such that f x = x. Such 'x' always exists; it could be (_|_), but it  
could be something else. For example, (^^2) is a strict function,  
which means that (_|_)^^2 = (_|_); therefore fix (^^2) = (_|_) - which  
you've discovered yourself.

A stupid example: fix (\a -> (1, snd a)) = (1, (_|_)). (_|_) is not  
the right answer: (\a -> (1, snd a)) (_|_) = (1, snd (_|_)) = (1, (_| 
_)) which isn't (_|_).

Another, less stupid example: fix (\a -> (1, fst a)) = (1, 1) - which  
doesn't contain (_|_) anywhere inside it. See, (_|_) is not the right  
answer here: (\a -> (1, fst a)) (_|_) = (1, fst (_|_)) = (1, (_|_)),  
which isn't (_|_). But (1, (_|_)) is not the right answer either: (\a - 
 > (1, fst a)) (1, (_|_)) = (1, fst (1, (_|_))) = (1, 1).

On 19 Feb 2009, at 17:00, Khudyakov Alexey wrote:

> Hello,
>
> While browsing documentation I've found following function
>
>> -- | @'fix' f@ is the least fixed point of the function @f@,
>> -- i.e. the least defined @x@ such that @f x = x at .
>> fix :: (a -> a) -> a
>> fix f = let x = f x in x
>
> I have two questions. How could this function be used? I'm unable to  
> imagine
> any. Naive approach lead to nothing (no surprise):
>
> Prelude Data.Function> fix (^^2)
> <interactive>: out of memory (requested 2097152 bytes)
>
>
> Second question what does word `least' mean?`a' isn't an Ord instance.
>
> --
>  Khudyakov Alexey
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list