X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Futils%2FUtil.lhs;h=ed7ee9aca6a27aadcc5d4c32a241b65d3e795506;hb=423d477bfecd490de1449c59325c8776f91d7aac;hp=5b4200b4db27d8328d0c7989a6c4b32541df6f0e;hpb=904f158f9fe208b8154029dff655a6eab4b2828e;p=ghc-hetmet.git diff --git a/ghc/compiler/utils/Util.lhs b/ghc/compiler/utils/Util.lhs index 5b4200b..ed7ee9a 100644 --- a/ghc/compiler/utils/Util.lhs +++ b/ghc/compiler/utils/Util.lhs @@ -1,60 +1,78 @@ % -% (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 +% (c) The University of Glasgow 1992-2002 % \section[Util]{Highly random utility functions} \begin{code} --- IF_NOT_GHC is meant to make this module useful outside the context of GHC -#define IF_NOT_GHC(a) - module Util ( - -- The Eager monad - Eager, thenEager, returnEager, mapEager, appEager, runEager, -- general list processing zipEqual, zipWithEqual, zipWith3Equal, zipWith4Equal, - zipLazy, stretchZipEqual, + zipLazy, stretchZipWith, mapAndUnzip, mapAndUnzip3, - nOfThem, lengthExceeds, isSingleton, only, - snocView, - isIn, isn'tIn, + nOfThem, filterOut, + lengthExceeds, lengthIs, lengthAtLeast, listLengthCmp, atLength, + isSingleton, only, + notNull, snocView, - -- association lists - assoc, assocUsing, assocDefault, assocDefaultUsing, + isIn, isn'tIn, - -- duplicate handling - hasNoDups, equivClasses, runs, removeDups, equivClassesByUniq, + -- for-loop + nTimes, -- sorting - IF_NOT_GHC(quicksort COMMA stableSortLt COMMA mergesort COMMA) - sortLt, - IF_NOT_GHC(mergeSort COMMA) naturalMergeSortLe, -- from Carsten - IF_NOT_GHC(naturalMergeSort COMMA mergeSortLe COMMA) + sortLt, naturalMergeSortLe, -- transitive closures transitiveClosure, -- accumulating - mapAccumL, mapAccumR, mapAccumB, foldl2, count, + mapAccumL, mapAccumR, mapAccumB, + foldl2, count, + + takeList, dropList, splitAtList, -- comparisons - thenCmp, cmpList, + eqListBy, equalLength, compareLength, + thenCmp, cmpList, prefixMatch, suffixMatch, maybePrefixMatch, -- strictness - seqList, ($!), + foldl', seqList, -- pairs - IF_NOT_GHC(cfst COMMA applyToPair COMMA applyToFst COMMA) - IF_NOT_GHC(applyToSnd COMMA foldPair COMMA) - unzipWith + unzipWith, + + global, + + -- module names + looksLikeModuleName, + + toArgs, + + -- Floating point stuff + readRational, ) where +#include "../includes/ghcconfig.h" #include "HsVersions.h" +import Panic ( panic, trace ) +import FastTypes + +#if __GLASGOW_HASKELL__ <= 408 +import EXCEPTION ( catchIO, justIoErrors, raiseInThread ) +#endif +import DATA_IOREF ( IORef, newIORef ) +import UNSAFE_IO ( unsafePerformIO ) + +import qualified List ( elem, notElem ) + +#ifndef DEBUG import List ( zipWith4 ) -import Panic ( panic ) -import Unique ( Unique ) -import UniqFM ( eltsUFM, emptyUFM, addToUFM_C ) +#endif + +import Char ( isUpper, isAlphaNum, isSpace, ord, isDigit ) +import Ratio ( (%) ) infixr 9 `thenCmp` \end{code} @@ -70,6 +88,8 @@ used to allow you to express "do this and then that", mainly to avoid space leaks. It's done with a type synonym to save bureaucracy. \begin{code} +#if NOT_USED + type Eager ans a = (a -> ans) -> ans runEager :: Eager a a -> a @@ -89,6 +109,21 @@ mapEager f [] = returnEager [] mapEager f (x:xs) = f x `thenEager` \ y -> mapEager f xs `thenEager` \ ys -> returnEager (y:ys) +#endif +\end{code} + +%************************************************************************ +%* * +\subsection{A for loop} +%* * +%************************************************************************ + +\begin{code} +-- Compose a function with itself n times. (nth rather than twice) +nTimes :: Int -> (a -> a) -> (a -> a) +nTimes 0 _ = id +nTimes 1 f = f +nTimes n f = f . nTimes (n-1) f \end{code} %************************************************************************ @@ -97,6 +132,14 @@ mapEager f (x:xs) = f x `thenEager` \ y -> %* * %************************************************************************ +\begin{code} +filterOut :: (a->Bool) -> [a] -> [a] +-- Like filter, only reverses the sense of the test +filterOut p [] = [] +filterOut p (x:xs) | p x = filterOut p xs + | otherwise = x : filterOut p xs +\end{code} + A paranoid @zip@ (and some @zipWith@ friends) that checks the lists are of equal length. Alastair Reid thinks this should only happen if DEBUGging on; hey, why not? @@ -143,13 +186,16 @@ zipLazy (x:xs) ~(y:ys) = (x,y) : zipLazy xs ys \begin{code} -stretchZipEqual :: (a -> b -> Maybe a) -> [a] -> [b] -> [a] --- (stretchZipEqual f xs ys) stretches ys to "fit" the places where f returns a Just +stretchZipWith :: (a -> Bool) -> b -> (a->b->c) -> [a] -> [b] -> [c] +-- (stretchZipWith p z f xs ys) stretches ys by inserting z in +-- the places where p returns *True* -stretchZipEqual f [] [] = [] -stretchZipEqual f (x:xs) (y:ys) = case f x y of - Just x' -> x' : stretchZipEqual f xs ys - Nothing -> x : stretchZipEqual f xs (y:ys) +stretchZipWith p z f [] ys = [] +stretchZipWith p z f (x:xs) ys + | p x = f x z : stretchZipWith p z f xs ys + | otherwise = case ys of + [] -> [] + (y:ys) -> f x y : stretchZipWith p z f xs ys \end{code} @@ -179,15 +225,66 @@ mapAndUnzip3 f (x:xs) nOfThem :: Int -> a -> [a] nOfThem n thing = replicate n thing +-- 'atLength atLen atEnd ls n' unravels list 'ls' to position 'n'; +-- specification: +-- +-- atLength atLenPred atEndPred ls n +-- | n < 0 = atLenPred n +-- | length ls < n = atEndPred (n - length ls) +-- | otherwise = atLenPred (drop n ls) +-- +atLength :: ([a] -> b) + -> (Int -> b) + -> [a] + -> Int + -> b +atLength atLenPred atEndPred ls n + | n < 0 = atEndPred n + | otherwise = go n ls + where + go n [] = atEndPred n + go 0 ls = atLenPred ls + go n (_:xs) = go (n-1) xs + +-- special cases. lengthExceeds :: [a] -> Int -> Bool --- (lengthExceeds xs n) is True if length xs > n -(x:xs) `lengthExceeds` n = n < 1 || xs `lengthExceeds` (n - 1) -[] `lengthExceeds` n = n < 0 +-- (lengthExceeds xs n) = (length xs > n) +lengthExceeds = atLength notNull (const False) + +lengthAtLeast :: [a] -> Int -> Bool +lengthAtLeast = atLength notNull (== 0) + +lengthIs :: [a] -> Int -> Bool +lengthIs = atLength null (==0) + +listLengthCmp :: [a] -> Int -> Ordering +listLengthCmp = atLength atLen atEnd + where + atEnd 0 = EQ + atEnd x + | x > 0 = LT -- not yet seen 'n' elts, so list length is < n. + | otherwise = GT + + atLen [] = EQ + atLen _ = GT isSingleton :: [a] -> Bool isSingleton [x] = True isSingleton _ = False +notNull :: [a] -> Bool +notNull [] = False +notNull _ = True + +snocView :: [a] -> Maybe ([a],a) + -- Split off the last element +snocView [] = Nothing +snocView xs = go [] xs + where + -- Invariant: second arg is non-empty + go acc [x] = Just (reverse acc, x) + go acc (x:xs) = go (x:acc) xs + only :: [a] -> a #ifdef DEBUG only [a] = a @@ -196,14 +293,6 @@ only (a:_) = a #endif \end{code} -\begin{code} -snocView :: [a] -> ([a], a) -- Split off the last element -snocView xs = go xs [] - where - go [x] acc = (reverse acc, x) - go (x:xs) acc = go xs (x:acc) -\end{code} - Debugging/specialising versions of \tr{elem} and \tr{notElem} \begin{code} @@ -220,134 +309,25 @@ elem__ x (y:ys) = x==y || elem__ x ys notElem__ x [] = True notElem__ x (y:ys) = x /= y && notElem__ x ys -# else {- DEBUG -} +# else /* DEBUG */ isIn msg x ys - = elem ILIT(0) x ys + = elem (_ILIT 0) x ys where elem i _ [] = False elem i x (y:ys) - | i _GE_ ILIT(100) = panic ("Over-long elem in: " ++ msg) - | otherwise = x == y || elem (i _ADD_ ILIT(1)) x ys + | i ># _ILIT 100 = trace ("Over-long elem in " ++ msg) $ + x `List.elem` (y:ys) + | otherwise = x == y || elem (i +# _ILIT(1)) x ys isn'tIn msg x ys - = notElem ILIT(0) x ys + = notElem (_ILIT 0) x ys where notElem i x [] = True notElem i x (y:ys) - | i _GE_ ILIT(100) = panic ("Over-long notElem in: " ++ msg) - | otherwise = x /= y && notElem (i _ADD_ ILIT(1)) x ys - -# endif {- DEBUG -} - -\end{code} - -%************************************************************************ -%* * -\subsection[Utils-assoc]{Association lists} -%* * -%************************************************************************ - -See also @assocMaybe@ and @mkLookupFun@ in module @Maybes@. - -\begin{code} -assoc :: (Eq a) => String -> [(a, b)] -> a -> b -assocDefault :: (Eq a) => b -> [(a, b)] -> a -> b -assocUsing :: (a -> a -> Bool) -> String -> [(a, b)] -> a -> b -assocDefaultUsing :: (a -> a -> Bool) -> b -> [(a, b)] -> a -> b - -assocDefaultUsing eq deflt ((k,v) : rest) key - | k `eq` key = v - | otherwise = assocDefaultUsing eq deflt rest key - -assocDefaultUsing eq deflt [] key = deflt - -assoc crash_msg list key = assocDefaultUsing (==) (panic ("Failed in assoc: " ++ crash_msg)) list key -assocDefault deflt list key = assocDefaultUsing (==) deflt list key -assocUsing eq crash_msg list key = assocDefaultUsing eq (panic ("Failed in assoc: " ++ crash_msg)) list key -\end{code} - -%************************************************************************ -%* * -\subsection[Utils-dups]{Duplicate-handling} -%* * -%************************************************************************ - -\begin{code} -hasNoDups :: (Eq a) => [a] -> Bool - -hasNoDups xs = f [] xs - where - f seen_so_far [] = True - f seen_so_far (x:xs) = if x `is_elem` seen_so_far then - False - else - f (x:seen_so_far) xs - - is_elem = isIn "hasNoDups" -\end{code} - -\begin{code} -equivClasses :: (a -> a -> Ordering) -- Comparison - -> [a] - -> [[a]] - -equivClasses cmp stuff@[] = [] -equivClasses cmp stuff@[item] = [stuff] -equivClasses cmp items - = runs eq (sortLt lt items) - where - eq a b = case cmp a b of { EQ -> True; _ -> False } - lt a b = case cmp a b of { LT -> True; _ -> False } -\end{code} - -The first cases in @equivClasses@ above are just to cut to the point -more quickly... - -@runs@ groups a list into a list of lists, each sublist being a run of -identical elements of the input list. It is passed a predicate @p@ which -tells when two elements are equal. - -\begin{code} -runs :: (a -> a -> Bool) -- Equality - -> [a] - -> [[a]] - -runs p [] = [] -runs p (x:xs) = case (span (p x) xs) of - (first, rest) -> (x:first) : (runs p rest) -\end{code} - -\begin{code} -removeDups :: (a -> a -> Ordering) -- Comparison function - -> [a] - -> ([a], -- List with no duplicates - [[a]]) -- List of duplicate groups. One representative from - -- each group appears in the first result - -removeDups cmp [] = ([], []) -removeDups cmp [x] = ([x],[]) -removeDups cmp xs - = case (mapAccumR collect_dups [] (equivClasses cmp xs)) of { (dups, xs') -> - (xs', dups) } - where - collect_dups dups_so_far [x] = (dups_so_far, x) - collect_dups dups_so_far dups@(x:xs) = (dups:dups_so_far, x) -\end{code} - - -\begin{code} -equivClassesByUniq :: (a -> Unique) -> [a] -> [[a]] - -- NB: it's *very* important that if we have the input list [a,b,c], - -- where a,b,c all have the same unique, then we get back the list - -- [a,b,c] - -- not - -- [c,b,a] - -- Hence the use of foldr, plus the reversed-args tack_on below -equivClassesByUniq get_uniq xs - = eltsUFM (foldr add emptyUFM xs) - where - add a ufm = addToUFM_C tack_on ufm (get_uniq a) [a] - tack_on old new = new++old + | i ># _ILIT 100 = trace ("Over-long notElem in " ++ msg) $ + x `List.notElem` (y:ys) + | otherwise = x /= y && notElem (i +# _ILIT(1)) x ys +# endif /* DEBUG */ \end{code} %************************************************************************ @@ -363,6 +343,8 @@ equivClassesByUniq get_uniq xs %************************************************************************ \begin{code} +#if NOT_USED + -- tail-recursive, etc., "quicker sort" [as per Meira thesis] quicksort :: (a -> a -> Bool) -- Less-than predicate -> [a] -- Input list @@ -375,14 +357,13 @@ quicksort lt (x:xs) = split x [] [] xs split x lo hi [] = quicksort lt lo ++ (x : quicksort lt hi) split x lo hi (y:ys) | y `lt` x = split x (y:lo) hi ys | True = split x lo (y:hi) ys +#endif \end{code} Quicksort variant from Lennart's Haskell-library contribution. This is a {\em stable} sort. \begin{code} -stableSortLt = sortLt -- synonym; when we want to highlight stable-ness - sortLt :: (a -> a -> Bool) -- Less-than predicate -> [a] -- Input list -> [a] -- Result list @@ -441,6 +422,7 @@ rqpart lt x (y:ys) rle rgt r = %************************************************************************ \begin{code} +#if NOT_USED mergesort :: (a -> a -> Ordering) -> [a] -> [a] mergesort cmp xs = merge_lists (split_into_runs [] xs) @@ -465,6 +447,7 @@ mergesort cmp xs = merge_lists (split_into_runs [] xs) EQ -> x : y : (merge xs ys) LT -> x : (merge xs yl) GT -> y : (merge xl ys) +#endif \end{code} %************************************************************************ @@ -556,18 +539,21 @@ balancedFold' :: (a -> a -> a) -> [a] -> [a] balancedFold' f (x:y:xs) = f x y : balancedFold' f xs balancedFold' f xs = xs -generalMergeSort p [] = [] -generalMergeSort p xs = (balancedFold (generalMerge p) . map (: [])) xs - generalNaturalMergeSort p [] = [] generalNaturalMergeSort p xs = (balancedFold (generalMerge p) . group p) xs +#if NOT_USED +generalMergeSort p [] = [] +generalMergeSort p xs = (balancedFold (generalMerge p) . map (: [])) xs + mergeSort, naturalMergeSort :: Ord a => [a] -> [a] mergeSort = generalMergeSort (<=) naturalMergeSort = generalNaturalMergeSort (<=) mergeSortLe le = generalMergeSort le +#endif + naturalMergeSortLe le = generalNaturalMergeSort le \end{code} @@ -659,6 +645,16 @@ mapAccumB f a b (x:xs) = (a'',b'',y:ys) (a'',b',ys) = mapAccumB f a' b xs \end{code} +A strict version of foldl. + +\begin{code} +foldl' :: (a -> b -> a) -> a -> [b] -> a +foldl' f z xs = lgo z xs + where + lgo z [] = z + lgo z (x:xs) = (lgo $! (f z x)) xs +\end{code} + A combination of foldl with zip. It works with equal length lists. \begin{code} @@ -676,6 +672,32 @@ count p (x:xs) | p x = 1 + count p xs | otherwise = count p xs \end{code} +@splitAt@, @take@, and @drop@ but with length of another +list giving the break-off point: + +\begin{code} +takeList :: [b] -> [a] -> [a] +takeList [] _ = [] +takeList (_:xs) ls = + case ls of + [] -> [] + (y:ys) -> y : takeList xs ys + +dropList :: [b] -> [a] -> [a] +dropList [] xs = xs +dropList _ xs@[] = xs +dropList (_:xs) (_:ys) = dropList xs ys + + +splitAtList :: [b] -> [a] -> ([a], [a]) +splitAtList [] xs = ([], xs) +splitAtList _ xs@[] = (xs, xs) +splitAtList (_:xs) (y:ys) = (y:ys', ys'') + where + (ys', ys'') = splitAtList xs ys + +\end{code} + %************************************************************************ %* * @@ -684,6 +706,22 @@ count p (x:xs) | p x = 1 + count p xs %************************************************************************ \begin{code} +eqListBy :: (a->a->Bool) -> [a] -> [a] -> Bool +eqListBy eq [] [] = True +eqListBy eq (x:xs) (y:ys) = eq x y && eqListBy eq xs ys +eqListBy eq xs ys = False + +equalLength :: [a] -> [b] -> Bool +equalLength [] [] = True +equalLength (_:xs) (_:ys) = equalLength xs ys +equalLength xs ys = False + +compareLength :: [a] -> [b] -> Ordering +compareLength [] [] = EQ +compareLength (_:xs) (_:ys) = compareLength xs ys +compareLength [] _ys = LT +compareLength _xs [] = GT + thenCmp :: Ordering -> Ordering -> Ordering {-# INLINE thenCmp #-} thenCmp EQ any = any @@ -700,16 +738,22 @@ cmpList cmp (a:as) (b:bs) \end{code} \begin{code} -cmpString :: String -> String -> Ordering +prefixMatch :: Eq a => [a] -> [a] -> Bool +prefixMatch [] _str = True +prefixMatch _pat [] = False +prefixMatch (p:ps) (s:ss) | p == s = prefixMatch ps ss + | otherwise = False -cmpString [] [] = EQ -cmpString (x:xs) (y:ys) = if x == y then cmpString xs ys - else if x < y then LT - else GT -cmpString [] ys = LT -cmpString xs [] = GT -\end{code} +maybePrefixMatch :: String -> String -> Maybe String +maybePrefixMatch [] rest = Just rest +maybePrefixMatch (_:_) [] = Nothing +maybePrefixMatch (p:pat) (r:rest) + | p == r = maybePrefixMatch pat rest + | otherwise = Nothing +suffixMatch :: Eq a => [a] -> [a] -> Bool +suffixMatch pat str = prefixMatch (reverse pat) (reverse str) +\end{code} %************************************************************************ %* * @@ -720,14 +764,17 @@ cmpString xs [] = GT The following are curried versions of @fst@ and @snd@. \begin{code} +#if NOT_USED cfst :: a -> b -> a -- stranal-sem only (Note) cfst x y = x +#endif \end{code} The following provide us higher order functions that, when applied to a function, operate on pairs. \begin{code} +#if NOT_USED applyToPair :: ((a -> c),(b -> d)) -> (a,b) -> (c,d) applyToPair (f,g) (x,y) = (f x, g y) @@ -736,11 +783,7 @@ applyToFst f (x,y) = (f x,y) applyToSnd :: (b -> d) -> (a,b) -> (a,d) applyToSnd f (x,y) = (x,f y) - -foldPair :: (a->a->a,b->b->b) -> (a,b) -> [(a,b)] -> (a,b) -foldPair fg ab [] = ab -foldPair fg@(f,g) ab ((a,b):abs) = (f a u,g b v) - where (u,v) = foldPair fg ab abs +#endif \end{code} \begin{code} @@ -749,26 +792,99 @@ unzipWith f pairs = map ( \ (a, b) -> f a b ) pairs \end{code} \begin{code} -#if __HASKELL1__ > 4 seqList :: [a] -> b -> b -#else -seqList :: (Eval a) => [a] -> b -> b -#endif seqList [] b = b seqList (x:xs) b = x `seq` seqList xs b +\end{code} -#if __HASKELL1__ <= 4 -($!) :: (Eval a) => (a -> b) -> a -> b -f $! x = x `seq` f x -#endif +Global variables: + +\begin{code} +global :: a -> IORef a +global a = unsafePerformIO (newIORef a) \end{code} +Module names: + \begin{code} -#if __GLASGOW_HASKELL__ < 402 -bracket :: IO a -> (a -> IO b) -> (a -> IO c) -> IO c -bracket before after thing = do - a <- before - (thing a) `catch` (\err -> after a >>= fail err) - after a -#endif +looksLikeModuleName [] = False +looksLikeModuleName (c:cs) = isUpper c && go cs + where go [] = True + go ('.':cs) = looksLikeModuleName cs + go (c:cs) = (isAlphaNum c || c == '_') && go cs +\end{code} + +Akin to @Prelude.words@, but sensitive to dquoted entities treating +them as single words. + +\begin{code} +toArgs :: String -> [String] +toArgs "" = [] +toArgs s = + case break (\ ch -> isSpace ch || ch == '"') (dropWhile isSpace s) of -- " + (w,aft) -> + (\ ws -> if null w then ws else w : ws) $ + case aft of + [] -> [] + (x:xs) + | x /= '"' -> toArgs xs + | otherwise -> + case lex aft of + ((str,rs):_) -> stripQuotes str : toArgs rs + _ -> [aft] + where + -- strip away dquotes; assume first and last chars contain quotes. + stripQuotes :: String -> String + stripQuotes ('"':xs) = init xs + stripQuotes xs = xs +\end{code} + +-- ----------------------------------------------------------------------------- +-- Floats + +\begin{code} +readRational__ :: ReadS Rational -- NB: doesn't handle leading "-" +readRational__ r = do + (n,d,s) <- readFix r + (k,t) <- readExp s + return ((n%1)*10^^(k-d), t) + where + readFix r = do + (ds,s) <- lexDecDigits r + (ds',t) <- lexDotDigits s + return (read (ds++ds'), length ds', t) + + readExp (e:s) | e `elem` "eE" = readExp' s + readExp s = return (0,s) + + readExp' ('+':s) = readDec s + readExp' ('-':s) = do + (k,t) <- readDec s + return (-k,t) + readExp' s = readDec s + + readDec s = do + (ds,r) <- nonnull isDigit s + return (foldl1 (\n d -> n * 10 + d) [ ord d - ord '0' | d <- ds ], + r) + + lexDecDigits = nonnull isDigit + + lexDotDigits ('.':s) = return (span isDigit s) + lexDotDigits s = return ("",s) + + nonnull p s = do (cs@(_:_),t) <- return (span p s) + return (cs,t) + +readRational :: String -> Rational -- NB: *does* handle a leading "-" +readRational top_s + = case top_s of + '-' : xs -> - (read_me xs) + xs -> read_me xs + where + read_me s + = case (do { (x,"") <- readRational__ s ; return x }) of + [x] -> x + [] -> error ("readRational: no parse:" ++ top_s) + _ -> error ("readRational: ambiguous parse:" ++ top_s) \end{code}