[Haskell-beginners] Excellent illustration of using the Haskell types -- revising Richard Bird's floor function so that it works properly

Costello, Roger L. costello at mitre.org
Sun Nov 4 10:40:36 CET 2012


Hi Folks,

On page 82 of the book "Introduction to Functional Programming using Haskell" the author Richard Bird provides this sample implementation of the floor function: 

floor x  =  searchFrom 0
                where 	searchFrom  	=  decrease . upper . lower
                            	lower              	=  until (<=x) decrease
                          	upper               	=  until (>x) increase
                          	decrease n  	=  n - 1
                          	increase n  	=  n + 1

The problem with that implementation is that it does not return an Integer value; rather, it returns a decimal (Double) value. Here's an example:

	floor (-3.4) 	-- returns (-4.0)

That is wrong. The specification for floor says that it "maps a value of type Float to a value of type Integer." Clearly it is not producing an Integer result.

I will now explain how to revise floor so that it returns an Integer value. In the process we will see an excellent illustration of the Haskell types.

The heart of the problem is with the until function.

Here is how Richard Bird implements it: 

until 		::  (a -> Bool) -> (a -> a) -> a -> a
until p f y 	=  if p y then y else until p f (f y)

It takes three arguments, p, f, and y. Look at the signature of that function. The type of the third argument, y, dictates the type of the other arguments and the type of the result--whatever type y is, the other arguments must be the same type and the result must be the same type. 

Function until is first invoked by function lower: 

	lower  =  until (<=x) decrease 0

Here are the three arguments provided to function until:

(1)  p is the partial function (<=x), where x is the input to the floor function. Suppose x is this value: x  =  (-3.4)

(2)  f is the function decrease

(3)  y is 0

Now you may argue, "Hey, the third argument, y, is 0 and that's an Integer, so clearly the result of function until will be an Integer." However, that is not correct. The type of 0 is ambiguous, it could be an Integer or it could be a Double. This ambiguity can be seen by checking its type using WinGHCi:

:type 0
0 :: Num a => a

The class Num is high up in Haskell's type hierarchy and it represents any number (Integer, Double, etc.). Thus, we cannot determine the type of function until's result just by examining its third argument. The other arguments will determine whether the 0 is an Integer or a Double.  Let's examine the first argument: 

	p is the partial function (<=x), where x  =  (-3.4)

p compares "some value" against (-3.4). Let's check the type of (-3.4) using WinGHCi:

:type (-3.4)
(-3.4) :: Fractional a => a

The datatype Double falls within the class Fractional. So p compares "some value" against a Double. 

	Fundamental rule of Haskell: you cannot compare an 
	Integer against a Double, you can only compare a 
	Double against a Double.  

Recall that p compares "some value" against (-3.4). What is that "some value"? If we examine the body of function until we see that it is the third argument, y, and we know that y  =  0. Ah, now we know how Haskell will treat 0: since the 0 is being compared against a Double value Haskell will treat the 0 as a Double. Okay, now that we know the type of y we can plug it into the type signature for function until:  

until  ::  (a -> Bool) -> (a -> a) -> Double -> a

All a's must be of the same type, so the other a's must also be Double:

until  ::  (Double -> Bool) -> (Double -> Double) -> Double -> Double

Therefore function until will return a Double value. For example:

	until (<=x) decrease 0		-- returns (0.0)

The output of function until is assigned to function lower:

	lower  =  until (<=x) decrease	

So the result of function lower is a Double value.

The output of lower is then input to upper and the Double datatype propagates through the entire chain of composed functions: 

	decrease . upper . lower

The result of function floor is therefore a Double value.

Okay, so how do we get floor to return an Integer value? The key is to prevent p in function until from casting the type of y to a Double. Recall function lower:

lower  =  until (<=x) decrease 0

Notice that p is this partial function:

	(<=x)

We must modify p to express, "Hey, compare x against an Integer value that has been cast to a Double value." That is implemented using a Lambda (anonymous) function:

	(\a -> (realToFrac a) <= x)

Read that as: For whatever value, a, is provided convert it to a Fractional (Double) value and then compare it to x.

Wow!

So we are telling Haskell that the 0 is not to be treated as a Fractional (Double) value, it is to be treated as a Real (Integer) value. 

At last, we can implement function floor and it will return the desired Integer result:

floor x = searchFrom 0
          	where 	searchFrom  	=  	decrease . upper . lower
                	lower       	=  	until (\a -> (realToFrac a) <= x) decrease
                	upper       	=  	until (\a -> (realToFrac a) > x) increase
                	decrease n  	=  	n - 1
                	increase n  	=  	n + 1

Notice that wherever function until is called (in lower and upper), the first argument, p, is a Lambda (anonymous) function that takes its argument, a, and casts it from a Real (Integer) value to a Fractional (Double) value. Here are a couple examples of using this revised floor function:

	floor (-3.4)	-- returns (-4)
	floor 3.4	-- returns 3

Notice that floor now returns an Integer value, which is what we want.

Here is the signature for floor:

floor :: (Fractional a, Ord a, Real c) => a -> c

Read as: Invoke function floor with a Fractional (Double) value and it will return a Real (Integer) value. 

On page 83 Richard Bird shows a second version of function floor that uses a binary search:

floor x = searchFrom (-1, 1)
          	where 	searchFrom = fst . middle . cross(lower, upper)
                	lower = until (<= x) double
                	upper = until (> x) double
                	middle = until done improve
                	done (m, n) = (m + 1 == n)
                	improve (m, n)  =  if p <= x then (p, n) else (m, p)
                                 		 where p = (m + n) div 2

That has multiple problems. First, it is syntactically not a well-formed Haskell program because the div operator (on the last line) must have back ticks ( ` ) surrounding it:

				where p = (m + n) `div` 2

Second, the functions lower and upper invoke function until. The first argument to until must be a Lambda function as described above:

                	lower = until (\m -> (realToFrac m) <= x) double
                	upper = until (\n -> (realToFrac n) > x) double

Third, the function improve compares p (an Integer) against x (a Double), so p must be cast to a Fractional (Double) value:

                	improve (m, n)  =  if (realToFrac p) <= x then (p, n) else (m, p)
                                 		   where p = (m + n) div 2

With those three changes the function works as desired: 

floor x = searchFrom (-1, 1)
          	where 	searchFrom = fst . middle . cross(lower, upper)
                	lower = until (\m -> (realToFrac m) <= x) double
                	upper = until (\n -> (realToFrac n) > x) double
                	middle = until done improve
                	done (m, n) = (m + 1 == n)
                	improve (m, n)  =  if (realToFrac p) <= x then (p, n) else (m, p)
                                 		   where p = (m + n) `div` 2

Here are a couple examples of using the revised floor function:

	floor (-3.4)	-- returns (-4)
	floor 3.4	-- returns 3

Notice that floor now returns an Integer value, which is what we want.

Here is the signature for floor:

floor :: (Fractional a, Ord a, Real c) => a -> c

Read as: Invoke function floor with a Fractional (Double) value and it will return a Real (Integer) value.

/Roger



More information about the Beginners mailing list