Hi Jose and fellow haskellers
[From: Jose Emilio Labra Gayo <[EMAIL PROTECTED]>]
[Subject: insert sort with foldr]
[Date: Sat, 10 Jan 1998 20:28:10 +0100 (MET)]
|
| I am trying to define common functions with recursive combinators
| avoiding recursive definitions.
I'm interested in the same problem. I've tried out several recursive
combinators to see how useful they are. I'll call these combinators
"folds" below.
First to your problem with `insert' (and thus with `isort'). As
you've noted there's sometimes a problem of inefficiency (or
termination in the case of infinite lists) of definitions made with
`foldr'. Your first definition of `insert' always walks over all of
its list argument, but it should only walk as far as is needed, like
the standard recursive definition.
You mention `unfold':
> -- as Bird and Wadler, p. 173, but with `not p'
> unfold :: (a -> b) -> (a -> Bool) -> (a -> a) -> a -> [b]
> unfold f p g x
> | p x = []
> | otherwise = (f x):(unfold f p g (g x))
A slight generalisation of `unfold' can be used to define `insert':
> gunfold :: (a -> b) -> (a -> Bool) -> (a -> a) -> (a -> [b]) -> a -> [b]
> gunfold f p g h x
> | p x = h x
> | otherwise = (f x):(gunfold f p g h (g x))
>
> insert :: Ord a => a -> [a] -> [a]
> insert x xs
> = gunfold head p tail (x:) xs
> where p xs = null xs || head xs > x
Using `gunfold' one can define `List.delete', `merge', and `take'.
Pairing up arguments to form a new recursion argument to a fold is a
handy trick:
> tk :: Int -> [a] -> [a]
> tk n xs
> = gunfold (head.snd) p (cross (pred,tail)) (const []) (n,xs)
> where p (n,xs) = n == 0 || null xs
>
> cross :: (a -> b,c -> d) -> (a,c) -> (b,d)
> cross (f,g) (x,y) = (f x, g y)
But we don't really need `gunfold' to do write `take'. With another
trick -- returning functions -- `foldr' can be used (Meijer & Jeuring,
_Merging monads and folds for FP_, Advanced FP, LNCS 925):
> tk2 :: Int -> [a] -> [a]
> tk2 n xs
> = foldr f (const []) xs n -- note flip'ed args
> where f a h = (\n -> case n of 0 -> []; n+1 -> a:h n)
The same trick can be used to define `foldl' in terms of `foldr' (or
vice versa) so maybe we only need `foldr'? However, using the other
folds is more intuitive for many functions... (There is also one
unfold function in the Haskell library: Maybe.unfoldr.)
One can generalise `gunfold' and `foldr' into a single quite useful
fold:
> genFold :: (a -> b -> b) -> (a -> Bool) -> (a -> a) -> (a -> b) -> a -> b
> genFold f p g h x
> | p x = h x
> | otherwise = f x (genFold f p g h (g x))
>
> fac :: Int -> Int
> fac n
> = genFold (*) p pred id n
> where p n = n == 0 || n == 1
>
> sorted :: Ord a => [a] -> Bool
> sorted xs
> = genFold f atom tail (const True) xs
> where f (x':x:xs) b = x' <= x && b
>
> atom :: [a] -> Bool
> atom xs = null xs || null (tail xs)
By the way I can't define `foldr1' using `foldr', but with `genFold'
it is easy. Did I miss something obvious, or is `genFold' really
needed?
The question of what what constitutes a "fundamental" or minimal set
of folds that can be used to define all other recursive functions
seems to depend upon several issues:
- are infinite structures present?
- what tricks do we use?
- what other constructs and (non-recursive) definitions must also be
available (un/curry, ...)?
I'd appreciate any insights on this question. For the moment I'm
interested in list and integer datatypes though there is work on
folding over other types including user-defined types (see
e.g. Jansson & Jeuring's POPL 97 paper on polytypism).
I think the answers lie in category theory, but it is not a very
accessible subject. (Though I recommend a look at a new book: Bird &
de Moor, Algebra of programming, Prentice Hall, 1997.)
Related questions are:
- do we need other folds if we don't want to compromise (time)
efficiency?
- can we invent natural/useful folds also for super-linear functions
like `isort', `List.nub' etc. instead of defining them using two or
more `foldr'-s?
All comments and pointers are most welcome.
Cheers,
Bjarte
--
Bjarte M. ?stvold [EMAIL PROTECTED]
Dept. of Computer and Information Science +47 73 59 44 83 (tel)
Norwegian Univ. of Science and Technology +47 73 59 44 66 (fax)
Gl?shaugen, N-7034 Trondheim, Norway