2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
4 \section[Util]{Highly random utility functions}
7 -- IF_NOT_GHC is meant to make this module useful outside the context of GHC
13 Eager, thenEager, returnEager, mapEager, appEager, runEager,
16 -- general list processing
17 zipEqual, zipWithEqual, zipWith3Equal, zipWith4Equal,
18 zipLazy, stretchZipWith,
19 mapAndUnzip, mapAndUnzip3,
20 nOfThem, lengthExceeds, isSingleton, only,
31 IF_NOT_GHC(quicksort COMMA stableSortLt COMMA mergesort COMMA)
33 IF_NOT_GHC(mergeSort COMMA) naturalMergeSortLe, -- from Carsten
34 IF_NOT_GHC(naturalMergeSort COMMA mergeSortLe COMMA)
36 -- transitive closures
40 mapAccumL, mapAccumR, mapAccumB, foldl2, count,
43 thenCmp, cmpList, prefixMatch, suffixMatch,
49 IF_NOT_GHC(cfst COMMA applyToPair COMMA applyToFst COMMA)
50 IF_NOT_GHC(applyToSnd COMMA foldPair COMMA)
54 #if __GLASGOW_HASKELL__ < 402
61 #if __GLASGOW_HASKELL__ <= 408
69 #include "../includes/config.h"
70 #include "HsVersions.h"
72 import List ( zipWith4 )
73 import Maybe ( Maybe(..) )
74 import Panic ( panic )
75 import IOExts ( IORef, newIORef, unsafePerformIO )
77 #if __GLASGOW_HASKELL__ <= 408
78 import Exception ( catchIO, justIoErrors, raiseInThread )
80 #ifndef mingw32_TARGET_OS
86 %************************************************************************
88 \subsection{The Eager monad}
90 %************************************************************************
92 The @Eager@ monad is just an encoding of continuation-passing style,
93 used to allow you to express "do this and then that", mainly to avoid
94 space leaks. It's done with a type synonym to save bureaucracy.
99 type Eager ans a = (a -> ans) -> ans
101 runEager :: Eager a a -> a
102 runEager m = m (\x -> x)
104 appEager :: Eager ans a -> (a -> ans) -> ans
105 appEager m cont = m cont
107 thenEager :: Eager ans a -> (a -> Eager ans b) -> Eager ans b
108 thenEager m k cont = m (\r -> k r cont)
110 returnEager :: a -> Eager ans a
111 returnEager v cont = cont v
113 mapEager :: (a -> Eager ans b) -> [a] -> Eager ans [b]
114 mapEager f [] = returnEager []
115 mapEager f (x:xs) = f x `thenEager` \ y ->
116 mapEager f xs `thenEager` \ ys ->
121 %************************************************************************
123 \subsection{A for loop}
125 %************************************************************************
128 -- Compose a function with itself n times. (nth rather than twice)
129 nTimes :: Int -> (a -> a) -> (a -> a)
132 nTimes n f = f . nTimes (n-1) f
135 %************************************************************************
137 \subsection{Maybe-ery}
139 %************************************************************************
142 unJust :: String -> Maybe a -> a
143 unJust who (Just x) = x
144 unJust who Nothing = panic ("unJust of Nothing, called by " ++ who)
147 %************************************************************************
149 \subsection[Utils-lists]{General list processing}
151 %************************************************************************
153 A paranoid @zip@ (and some @zipWith@ friends) that checks the lists
154 are of equal length. Alastair Reid thinks this should only happen if
155 DEBUGging on; hey, why not?
158 zipEqual :: String -> [a] -> [b] -> [(a,b)]
159 zipWithEqual :: String -> (a->b->c) -> [a]->[b]->[c]
160 zipWith3Equal :: String -> (a->b->c->d) -> [a]->[b]->[c]->[d]
161 zipWith4Equal :: String -> (a->b->c->d->e) -> [a]->[b]->[c]->[d]->[e]
165 zipWithEqual _ = zipWith
166 zipWith3Equal _ = zipWith3
167 zipWith4Equal _ = zipWith4
169 zipEqual msg [] [] = []
170 zipEqual msg (a:as) (b:bs) = (a,b) : zipEqual msg as bs
171 zipEqual msg as bs = panic ("zipEqual: unequal lists:"++msg)
173 zipWithEqual msg z (a:as) (b:bs)= z a b : zipWithEqual msg z as bs
174 zipWithEqual msg _ [] [] = []
175 zipWithEqual msg _ _ _ = panic ("zipWithEqual: unequal lists:"++msg)
177 zipWith3Equal msg z (a:as) (b:bs) (c:cs)
178 = z a b c : zipWith3Equal msg z as bs cs
179 zipWith3Equal msg _ [] [] [] = []
180 zipWith3Equal msg _ _ _ _ = panic ("zipWith3Equal: unequal lists:"++msg)
182 zipWith4Equal msg z (a:as) (b:bs) (c:cs) (d:ds)
183 = z a b c d : zipWith4Equal msg z as bs cs ds
184 zipWith4Equal msg _ [] [] [] [] = []
185 zipWith4Equal msg _ _ _ _ _ = panic ("zipWith4Equal: unequal lists:"++msg)
190 -- zipLazy is lazy in the second list (observe the ~)
192 zipLazy :: [a] -> [b] -> [(a,b)]
194 zipLazy (x:xs) ~(y:ys) = (x,y) : zipLazy xs ys
199 stretchZipWith :: (a -> Bool) -> b -> (a->b->c) -> [a] -> [b] -> [c]
200 -- (stretchZipWith p z f xs ys) stretches ys by inserting z in
201 -- the places where p returns *True*
203 stretchZipWith p z f [] ys = []
204 stretchZipWith p z f (x:xs) ys
205 | p x = f x z : stretchZipWith p z f xs ys
206 | otherwise = case ys of
208 (y:ys) -> f x y : stretchZipWith p z f xs ys
213 mapAndUnzip :: (a -> (b, c)) -> [a] -> ([b], [c])
215 mapAndUnzip f [] = ([],[])
219 (rs1, rs2) = mapAndUnzip f xs
223 mapAndUnzip3 :: (a -> (b, c, d)) -> [a] -> ([b], [c], [d])
225 mapAndUnzip3 f [] = ([],[],[])
226 mapAndUnzip3 f (x:xs)
229 (rs1, rs2, rs3) = mapAndUnzip3 f xs
231 (r1:rs1, r2:rs2, r3:rs3)
235 nOfThem :: Int -> a -> [a]
236 nOfThem n thing = replicate n thing
238 lengthExceeds :: [a] -> Int -> Bool
239 -- (lengthExceeds xs n) is True if length xs > n
240 (x:xs) `lengthExceeds` n = n < 1 || xs `lengthExceeds` (n - 1)
241 [] `lengthExceeds` n = n < 0
243 isSingleton :: [a] -> Bool
244 isSingleton [x] = True
245 isSingleton _ = False
256 snocView :: [a] -> ([a], a) -- Split off the last element
257 snocView xs = go xs []
259 go [x] acc = (reverse acc, x)
260 go (x:xs) acc = go xs (x:acc)
263 Debugging/specialising versions of \tr{elem} and \tr{notElem}
266 isIn, isn'tIn :: (Eq a) => String -> a -> [a] -> Bool
269 isIn msg x ys = elem__ x ys
270 isn'tIn msg x ys = notElem__ x ys
272 --these are here to be SPECIALIZEd (automagically)
274 elem__ x (y:ys) = x==y || elem__ x ys
276 notElem__ x [] = True
277 notElem__ x (y:ys) = x /= y && notElem__ x ys
281 = elem (_ILIT 0) x ys
285 | i ># _ILIT 100 = panic ("Over-long elem in: " ++ msg)
286 | otherwise = x == y || elem (i +# _ILIT(1)) x ys
289 = notElem (_ILIT 0) x ys
291 notElem i x [] = True
293 | i ># _ILIT 100 = panic ("Over-long notElem in: " ++ msg)
294 | otherwise = x /= y && notElem (i +# _ILIT(1)) x ys
300 %************************************************************************
302 \subsection[Utils-sorting]{Sorting}
304 %************************************************************************
306 %************************************************************************
308 \subsubsection[Utils-quicksorting]{Quicksorts}
310 %************************************************************************
315 -- tail-recursive, etc., "quicker sort" [as per Meira thesis]
316 quicksort :: (a -> a -> Bool) -- Less-than predicate
318 -> [a] -- Result list in increasing order
321 quicksort lt [x] = [x]
322 quicksort lt (x:xs) = split x [] [] xs
324 split x lo hi [] = quicksort lt lo ++ (x : quicksort lt hi)
325 split x lo hi (y:ys) | y `lt` x = split x (y:lo) hi ys
326 | True = split x lo (y:hi) ys
330 Quicksort variant from Lennart's Haskell-library contribution. This
331 is a {\em stable} sort.
334 stableSortLt = sortLt -- synonym; when we want to highlight stable-ness
336 sortLt :: (a -> a -> Bool) -- Less-than predicate
338 -> [a] -- Result list
340 sortLt lt l = qsort lt l []
342 -- qsort is stable and does not concatenate.
343 qsort :: (a -> a -> Bool) -- Less-than predicate
344 -> [a] -- xs, Input list
345 -> [a] -- r, Concatenate this list to the sorted input list
346 -> [a] -- Result = sort xs ++ r
350 qsort lt (x:xs) r = qpart lt x xs [] [] r
352 -- qpart partitions and sorts the sublists
353 -- rlt contains things less than x,
354 -- rge contains the ones greater than or equal to x.
355 -- Both have equal elements reversed with respect to the original list.
357 qpart lt x [] rlt rge r =
358 -- rlt and rge are in reverse order and must be sorted with an
359 -- anti-stable sorting
360 rqsort lt rlt (x : rqsort lt rge r)
362 qpart lt x (y:ys) rlt rge r =
365 qpart lt x ys (y:rlt) rge r
368 qpart lt x ys rlt (y:rge) r
370 -- rqsort is as qsort but anti-stable, i.e. reverses equal elements
372 rqsort lt [x] r = x:r
373 rqsort lt (x:xs) r = rqpart lt x xs [] [] r
375 rqpart lt x [] rle rgt r =
376 qsort lt rle (x : qsort lt rgt r)
378 rqpart lt x (y:ys) rle rgt r =
381 rqpart lt x ys rle (y:rgt) r
384 rqpart lt x ys (y:rle) rgt r
387 %************************************************************************
389 \subsubsection[Utils-dull-mergesort]{A rather dull mergesort}
391 %************************************************************************
395 mergesort :: (a -> a -> Ordering) -> [a] -> [a]
397 mergesort cmp xs = merge_lists (split_into_runs [] xs)
399 a `le` b = case cmp a b of { LT -> True; EQ -> True; GT -> False }
400 a `ge` b = case cmp a b of { LT -> False; EQ -> True; GT -> True }
402 split_into_runs [] [] = []
403 split_into_runs run [] = [run]
404 split_into_runs [] (x:xs) = split_into_runs [x] xs
405 split_into_runs [r] (x:xs) | x `ge` r = split_into_runs [r,x] xs
406 split_into_runs rl@(r:rs) (x:xs) | x `le` r = split_into_runs (x:rl) xs
407 | True = rl : (split_into_runs [x] xs)
410 merge_lists (x:xs) = merge x (merge_lists xs)
414 merge xl@(x:xs) yl@(y:ys)
416 EQ -> x : y : (merge xs ys)
417 LT -> x : (merge xs yl)
418 GT -> y : (merge xl ys)
422 %************************************************************************
424 \subsubsection[Utils-Carsten-mergesort]{A mergesort from Carsten}
426 %************************************************************************
429 Date: Mon, 3 May 93 20:45:23 +0200
430 From: Carsten Kehler Holst <kehler@cs.chalmers.se>
431 To: partain@dcs.gla.ac.uk
432 Subject: natural merge sort beats quick sort [ and it is prettier ]
434 Here is a piece of Haskell code that I'm rather fond of. See it as an
435 attempt to get rid of the ridiculous quick-sort routine. group is
436 quite useful by itself I think it was John's idea originally though I
437 believe the lazy version is due to me [surprisingly complicated].
438 gamma [used to be called] is called gamma because I got inspired by
439 the Gamma calculus. It is not very close to the calculus but does
440 behave less sequentially than both foldr and foldl. One could imagine
441 a version of gamma that took a unit element as well thereby avoiding
442 the problem with empty lists.
444 I've tried this code against
446 1) insertion sort - as provided by haskell
447 2) the normal implementation of quick sort
448 3) a deforested version of quick sort due to Jan Sparud
449 4) a super-optimized-quick-sort of Lennart's
451 If the list is partially sorted both merge sort and in particular
452 natural merge sort wins. If the list is random [ average length of
453 rising subsequences = approx 2 ] mergesort still wins and natural
454 merge sort is marginally beaten by Lennart's soqs. The space
455 consumption of merge sort is a bit worse than Lennart's quick sort
456 approx a factor of 2. And a lot worse if Sparud's bug-fix [see his
457 fpca article ] isn't used because of group.
464 group :: (a -> a -> Bool) -> [a] -> [[a]]
467 Date: Mon, 12 Feb 1996 15:09:41 +0000
468 From: Andy Gill <andy@dcs.gla.ac.uk>
470 Here is a `better' definition of group.
473 group p (x:xs) = group' xs x x (x :)
475 group' [] _ _ s = [s []]
476 group' (x:xs) x_min x_max s
477 | not (x `p` x_max) = group' xs x_min x (s . (x :))
478 | x `p` x_min = group' xs x x_max ((x :) . s)
479 | otherwise = s [] : group' xs x x (x :)
481 -- This one works forwards *and* backwards, as well as also being
482 -- faster that the one in Util.lhs.
487 let ((h1:t1):tt1) = group p xs
488 (t,tt) = if null xs then ([],[]) else
489 if x `p` h1 then (h1:t1,tt1) else
494 generalMerge :: (a -> a -> Bool) -> [a] -> [a] -> [a]
495 generalMerge p xs [] = xs
496 generalMerge p [] ys = ys
497 generalMerge p (x:xs) (y:ys) | x `p` y = x : generalMerge p xs (y:ys)
498 | otherwise = y : generalMerge p (x:xs) ys
500 -- gamma is now called balancedFold
502 balancedFold :: (a -> a -> a) -> [a] -> a
503 balancedFold f [] = error "can't reduce an empty list using balancedFold"
504 balancedFold f [x] = x
505 balancedFold f l = balancedFold f (balancedFold' f l)
507 balancedFold' :: (a -> a -> a) -> [a] -> [a]
508 balancedFold' f (x:y:xs) = f x y : balancedFold' f xs
509 balancedFold' f xs = xs
511 generalMergeSort p [] = []
512 generalMergeSort p xs = (balancedFold (generalMerge p) . map (: [])) xs
514 generalNaturalMergeSort p [] = []
515 generalNaturalMergeSort p xs = (balancedFold (generalMerge p) . group p) xs
517 mergeSort, naturalMergeSort :: Ord a => [a] -> [a]
519 mergeSort = generalMergeSort (<=)
520 naturalMergeSort = generalNaturalMergeSort (<=)
522 mergeSortLe le = generalMergeSort le
523 naturalMergeSortLe le = generalNaturalMergeSort le
526 %************************************************************************
528 \subsection[Utils-transitive-closure]{Transitive closure}
530 %************************************************************************
532 This algorithm for transitive closure is straightforward, albeit quadratic.
535 transitiveClosure :: (a -> [a]) -- Successor function
536 -> (a -> a -> Bool) -- Equality predicate
538 -> [a] -- The transitive closure
540 transitiveClosure succ eq xs
544 go done (x:xs) | x `is_in` done = go done xs
545 | otherwise = go (x:done) (succ x ++ xs)
548 x `is_in` (y:ys) | eq x y = True
549 | otherwise = x `is_in` ys
552 %************************************************************************
554 \subsection[Utils-accum]{Accumulating}
556 %************************************************************************
558 @mapAccumL@ behaves like a combination
559 of @map@ and @foldl@;
560 it applies a function to each element of a list, passing an accumulating
561 parameter from left to right, and returning a final value of this
562 accumulator together with the new list.
565 mapAccumL :: (acc -> x -> (acc, y)) -- Function of elt of input list
566 -- and accumulator, returning new
567 -- accumulator and elt of result list
568 -> acc -- Initial accumulator
570 -> (acc, [y]) -- Final accumulator and result list
572 mapAccumL f b [] = (b, [])
573 mapAccumL f b (x:xs) = (b'', x':xs') where
575 (b'', xs') = mapAccumL f b' xs
578 @mapAccumR@ does the same, but working from right to left instead. Its type is
579 the same as @mapAccumL@, though.
582 mapAccumR :: (acc -> x -> (acc, y)) -- Function of elt of input list
583 -- and accumulator, returning new
584 -- accumulator and elt of result list
585 -> acc -- Initial accumulator
587 -> (acc, [y]) -- Final accumulator and result list
589 mapAccumR f b [] = (b, [])
590 mapAccumR f b (x:xs) = (b'', x':xs') where
592 (b', xs') = mapAccumR f b xs
595 Here is the bi-directional version, that works from both left and right.
598 mapAccumB :: (accl -> accr -> x -> (accl, accr,y))
599 -- Function of elt of input list
600 -- and accumulator, returning new
601 -- accumulator and elt of result list
602 -> accl -- Initial accumulator from left
603 -> accr -- Initial accumulator from right
605 -> (accl, accr, [y]) -- Final accumulators and result list
607 mapAccumB f a b [] = (a,b,[])
608 mapAccumB f a b (x:xs) = (a'',b'',y:ys)
610 (a',b'',y) = f a b' x
611 (a'',b',ys) = mapAccumB f a' b xs
614 A combination of foldl with zip. It works with equal length lists.
617 foldl2 :: (acc -> a -> b -> acc) -> acc -> [a] -> [b] -> acc
619 foldl2 k z (a:as) (b:bs) = foldl2 k (k z a b) as bs
622 Count the number of times a predicate is true
625 count :: (a -> Bool) -> [a] -> Int
627 count p (x:xs) | p x = 1 + count p xs
628 | otherwise = count p xs
632 %************************************************************************
634 \subsection[Utils-comparison]{Comparisons}
636 %************************************************************************
639 thenCmp :: Ordering -> Ordering -> Ordering
640 {-# INLINE thenCmp #-}
642 thenCmp other any = other
644 cmpList :: (a -> a -> Ordering) -> [a] -> [a] -> Ordering
645 -- `cmpList' uses a user-specified comparer
647 cmpList cmp [] [] = EQ
648 cmpList cmp [] _ = LT
649 cmpList cmp _ [] = GT
650 cmpList cmp (a:as) (b:bs)
651 = case cmp a b of { EQ -> cmpList cmp as bs; xxx -> xxx }
655 prefixMatch :: Eq a => [a] -> [a] -> Bool
656 prefixMatch [] _str = True
657 prefixMatch _pat [] = False
658 prefixMatch (p:ps) (s:ss) | p == s = prefixMatch ps ss
661 suffixMatch :: Eq a => [a] -> [a] -> Bool
662 suffixMatch pat str = prefixMatch (reverse pat) (reverse str)
665 %************************************************************************
667 \subsection[Utils-pairs]{Pairs}
669 %************************************************************************
671 The following are curried versions of @fst@ and @snd@.
674 cfst :: a -> b -> a -- stranal-sem only (Note)
678 The following provide us higher order functions that, when applied
679 to a function, operate on pairs.
682 applyToPair :: ((a -> c),(b -> d)) -> (a,b) -> (c,d)
683 applyToPair (f,g) (x,y) = (f x, g y)
685 applyToFst :: (a -> c) -> (a,b)-> (c,b)
686 applyToFst f (x,y) = (f x,y)
688 applyToSnd :: (b -> d) -> (a,b) -> (a,d)
689 applyToSnd f (x,y) = (x,f y)
691 foldPair :: (a->a->a,b->b->b) -> (a,b) -> [(a,b)] -> (a,b)
692 foldPair fg ab [] = ab
693 foldPair fg@(f,g) ab ((a,b):abs) = (f a u,g b v)
694 where (u,v) = foldPair fg ab abs
698 unzipWith :: (a -> b -> c) -> [(a, b)] -> [c]
699 unzipWith f pairs = map ( \ (a, b) -> f a b ) pairs
704 seqList :: [a] -> b -> b
706 seqList :: (Eval a) => [a] -> b -> b
709 seqList (x:xs) b = x `seq` seqList xs b
711 #if __HASKELL1__ <= 4
712 ($!) :: (Eval a) => (a -> b) -> a -> b
718 #if __GLASGOW_HASKELL__ < 402
719 bracket :: IO a -> (a -> IO b) -> (a -> IO c) -> IO c
720 bracket before after thing = do
722 r <- (thing a) `catch` (\err -> after a >> fail err)
731 global :: a -> IORef a
732 global a = unsafePerformIO (newIORef a)
738 #if __GLASGOW_HASKELL__ <= 408
740 ioErrors = justIoErrors
741 throwTo = raiseInThread
744 #ifdef mingw32_TARGET_OS
745 foreign import "_getpid" myGetProcessID :: IO Int
747 myGetProcessID :: IO Int
748 myGetProcessID = Posix.getProcessID