Skip to content
Snippets Groups Projects
Commit 580a1e57 authored by sof's avatar sof
Browse files

[project @ 1997-08-25 22:25:50 by sof]

Removed use of COMPILING_GHC
parent b6595910
No related branches found
No related tags found
No related merge requests found
......@@ -4,32 +4,24 @@
\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,
#ifndef COMPILING_GHC
elemBag,
#endif
filterBag, partitionBag, concatBag, foldBag, foldrBag,
isEmptyBag, consBag, snocBag,
listToBag, bagToList
) where
#ifdef COMPILING_GHC
IMP_Ubiq(){-uitous-}
IMPORT_1_3(List(partition))
import Outputable --( interpp'SP )
import Pretty
#else
import List(partition)
#endif
data Bag a
= EmptyBag
......@@ -42,7 +34,6 @@ data Bag a
emptyBag = EmptyBag
unitBag = UnitBag
#ifndef COMPILING_GHC
elemBag :: Eq a => a -> Bag a -> Bool
elemBag x EmptyBag = False
......@@ -50,7 +41,6 @@ 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
......@@ -158,8 +148,6 @@ bagToList b = foldrBag (:) [] b
\end{code}
\begin{code}
#ifdef COMPILING_GHC
instance (Outputable a) => Outputable (Bag a) where
ppr sty EmptyBag = ptext SLIT("emptyBag")
ppr sty (UnitBag a) = ppr sty a
......@@ -167,5 +155,4 @@ instance (Outputable a) => Outputable (Bag a) where
ppr sty (ListBag as) = interpp'SP sty as
ppr sty (ListOfBags bs) = brackets (interpp'SP sty bs)
#endif {- COMPILING_GHC -}
\end{code}
......@@ -20,9 +20,6 @@ module BitSet (
BitSet, -- abstract type
mkBS, listBS, emptyBS, unitBS,
unionBS, minusBS
#if ! defined(COMPILING_GHC)
, elementBS, intersectBS, isEmptyBS
#endif
) where
#ifdef __GLASGOW_HASKELL__
......@@ -60,7 +57,7 @@ unionBS (MkBS x#) (MkBS y#) = MkBS (x# `or#` y#)
minusBS :: BitSet -> BitSet -> BitSet
minusBS (MkBS x#) (MkBS y#) = MkBS (x# `and#` (not# y#))
#if ! defined(COMPILING_GHC)
#if 0
-- not used in GHC
isEmptyBS :: BitSet -> Bool
isEmptyBS (MkBS s#)
......@@ -106,7 +103,7 @@ unitBS x = MkBS (1 `ashInt` x)
unionBS :: BitSet -> BitSet -> BitSet
unionBS (MkBS x) (MkBS y) = MkBS (x `logiorInt` y)
#if ! defined(COMPILING_GHC)
#if 0
-- not used in GHC
isEmptyBS :: BitSet -> Bool
isEmptyBS (MkBS s)
......@@ -155,7 +152,7 @@ unitBS x = MkBS (1 `bitLsh` x)
unionBS :: BitSet -> BitSet -> BitSet
unionBS (MkBS x) (MkBS y) = MkBS (x `bitOr` y)
#if ! defined(COMPILING_GHC)
#if 0
-- not used in GHC
isEmptyBS :: BitSet -> Bool
isEmptyBS (MkBS s)
......
\begin{code}
#if defined(COMPILING_GHC)
# include "HsVersions.h"
#endif
module Digraph(
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment