diff options
Diffstat (limited to 'ghc/compiler/utils')
-rw-r--r-- | ghc/compiler/utils/Bag.lhs | 16 | ||||
-rw-r--r-- | ghc/compiler/utils/FiniteMap.lhs | 4 | ||||
-rw-r--r-- | ghc/compiler/utils/ListSetOps.lhs | 4 | ||||
-rw-r--r-- | ghc/compiler/utils/Maybes.lhs | 9 | ||||
-rw-r--r-- | ghc/compiler/utils/Pretty.lhs | 6 | ||||
-rw-r--r-- | ghc/compiler/utils/Util.lhs | 29 |
6 files changed, 52 insertions, 16 deletions
diff --git a/ghc/compiler/utils/Bag.lhs b/ghc/compiler/utils/Bag.lhs index 36fe3148ad..15678cfbe8 100644 --- a/ghc/compiler/utils/Bag.lhs +++ b/ghc/compiler/utils/Bag.lhs @@ -4,13 +4,18 @@ \section[Bags]{@Bag@: an unordered collection with duplicates} \begin{code} +#ifdef COMPILING_GHC #include "HsVersions.h" +#endif module Bag ( Bag, -- abstract type emptyBag, unitBag, unionBags, unionManyBags, - mapBag, -- UNUSED: elemBag, + mapBag, +#ifndef COMPILING_GHC + elemBag, +#endif filterBag, partitionBag, concatBag, foldBag, isEmptyBag, consBag, snocBag, listToBag, bagToList @@ -22,6 +27,8 @@ IMPORT_1_3(List(partition)) import Outputable ( interpp'SP ) import Pretty +#else +import List(partition) #endif data Bag a @@ -35,7 +42,7 @@ data Bag a emptyBag = EmptyBag unitBag = UnitBag -{- UNUSED: +#ifndef COMPILING_GHC elemBag :: Eq a => a -> Bag a -> Bool elemBag x EmptyBag = False @@ -43,7 +50,7 @@ elemBag x (UnitBag y) = x==y elemBag x (TwoBags b1 b2) = x `elemBag` b1 || x `elemBag` b2 elemBag x (ListBag ys) = any (x ==) ys elemBag x (ListOfBags bs) = any (x `elemBag`) bs --} +#endif unionManyBags [] = EmptyBag unionManyBags xs = ListOfBags xs @@ -55,8 +62,9 @@ unionBags b EmptyBag = b unionBags b1 b2 = TwoBags b1 b2 consBag :: a -> Bag a -> Bag a -consBag elt bag = (unitBag elt) `unionBags` bag snocBag :: Bag a -> a -> Bag a + +consBag elt bag = (unitBag elt) `unionBags` bag snocBag bag elt = bag `unionBags` (unitBag elt) isEmptyBag EmptyBag = True diff --git a/ghc/compiler/utils/FiniteMap.lhs b/ghc/compiler/utils/FiniteMap.lhs index c95f0b4626..d8c59893f5 100644 --- a/ghc/compiler/utils/FiniteMap.lhs +++ b/ghc/compiler/utils/FiniteMap.lhs @@ -25,6 +25,10 @@ near the end (only \tr{#ifdef COMPILING_GHC}). #define ASSERT(e) {--} #define IF_NOT_GHC(a) a #define COMMA , +#define _tagCmp compare +#define _LT LT +#define _GT GT +#define _EQ EQ #endif #if defined(COMPILING_GHC) && defined(DEBUG_FINITEMAPS)/* NB NB NB */ diff --git a/ghc/compiler/utils/ListSetOps.lhs b/ghc/compiler/utils/ListSetOps.lhs index 5a46b2391b..39172473d9 100644 --- a/ghc/compiler/utils/ListSetOps.lhs +++ b/ghc/compiler/utils/ListSetOps.lhs @@ -4,13 +4,15 @@ \section[ListSetOps]{Set-like operations on lists} \begin{code} +#ifdef COMPILING_GHC #include "HsVersions.h" +#endif module ListSetOps ( unionLists, intersectLists, minusList -#if ! defined(COMPILING_GHC) +#ifndef COMPILING_GHC , disjointLists, intersectingLists #endif ) where diff --git a/ghc/compiler/utils/Maybes.lhs b/ghc/compiler/utils/Maybes.lhs index 5ed4ac316f..1f17679019 100644 --- a/ghc/compiler/utils/Maybes.lhs +++ b/ghc/compiler/utils/Maybes.lhs @@ -13,7 +13,6 @@ module Maybes ( MaybeErr(..), allMaybes, - catMaybes, firstJust, expectJust, maybeToBool, @@ -28,7 +27,9 @@ module Maybes ( returnMaybe, thenMaB -#if ! defined(COMPILING_GHC) +#if defined(COMPILING_GHC) + , catMaybes +#else , findJust , foldlMaybeErrs , listMaybeErrs @@ -41,6 +42,8 @@ CHK_Ubiq() -- debugging consistency check import Unique (Unique) -- only for specialising +#else +import Maybe -- renamer will tell us if there are any conflicts #endif \end{code} @@ -63,10 +66,12 @@ a list of @Justs@ into a single @Just@, returning @Nothing@ if there are any @Nothings@. \begin{code} +#ifdef COMPILING_GHC catMaybes :: [Maybe a] -> [a] catMaybes [] = [] catMaybes (Nothing : xs) = catMaybes xs catMaybes (Just x : xs) = (x : catMaybes xs) +#endif allMaybes :: [Maybe a] -> Maybe [a] allMaybes [] = Just [] diff --git a/ghc/compiler/utils/Pretty.lhs b/ghc/compiler/utils/Pretty.lhs index 985666d013..ad2a76fb9d 100644 --- a/ghc/compiler/utils/Pretty.lhs +++ b/ghc/compiler/utils/Pretty.lhs @@ -12,10 +12,12 @@ #endif module Pretty ( - SYN_IE(Pretty), #if defined(COMPILING_GHC) + SYN_IE(Pretty), prettyToUn, +#else + Pretty, #endif ppNil, ppStr, ppPStr, ppChar, ppInt, ppInteger, ppFloat, ppDouble, @@ -46,6 +48,8 @@ IMPORT_1_3(Ratio) IMPORT_1_3(IO) import Unpretty ( SYN_IE(Unpretty) ) +#else +import Ratio #endif import CharSeq diff --git a/ghc/compiler/utils/Util.lhs b/ghc/compiler/utils/Util.lhs index adc6e65ba9..6d51f3aaf2 100644 --- a/ghc/compiler/utils/Util.lhs +++ b/ghc/compiler/utils/Util.lhs @@ -9,12 +9,16 @@ # define IF_NOT_GHC(a) {--} #else # define panic error -# define TAG_ _CMP_TAG -# define LT_ _LT -# define EQ_ _EQ -# define GT_ _GT +# define TAG_ Ordering +# define LT_ LT +# define EQ_ EQ +# define GT_ GT +# define _LT LT +# define _EQ EQ +# define _GT GT # define GT__ _ -# define tagCmp_ _tagCmp +# define tagCmp_ compare +# define _tagCmp compare # define FAST_STRING String # define ASSERT(x) {-nothing-} # define IF_NOT_GHC(a) a @@ -41,8 +45,8 @@ module Util ( zipLazy, mapAndUnzip, mapAndUnzip3, nOfThem, lengthExceeds, isSingleton, - startsWith, endsWith, #if defined(COMPILING_GHC) + startsWith, endsWith, isIn, isn'tIn, #endif @@ -65,9 +69,12 @@ module Util ( mapAccumL, mapAccumR, mapAccumB, -- comparisons +#if defined(COMPILING_GHC) Ord3(..), thenCmp, cmpList, - IF_NOT_GHC(cmpString COMMA) cmpPString, +#else + cmpString, +#endif -- pairs IF_NOT_GHC(cfst COMMA applyToPair COMMA applyToFst COMMA) @@ -88,6 +95,8 @@ CHK_Ubiq() -- debugging consistency check IMPORT_1_3(List(zipWith4)) import Pretty +#else +import List(zipWith4) #endif infixr 9 `thenCmp` @@ -212,7 +221,7 @@ startsWith, endsWith :: String -> String -> Maybe String startsWith [] str = Just str startsWith (c:cs) (s:ss) = if c /= s then Nothing else startsWith cs ss -startWith _ [] = Nothing +startsWith _ [] = Nothing endsWith cs ss = case (startsWith (reverse cs) (reverse ss)) of @@ -715,7 +724,11 @@ cmpString (x:xs) (y:ys) = if x == y then cmpString xs ys cmpString [] ys = LT_ cmpString xs [] = GT_ +#ifdef COMPILING_GHC cmpString _ _ = panic# "cmpString" +#else +cmpString _ _ = error "cmpString" +#endif \end{code} \begin{code} |