File tree Expand file tree Collapse file tree 1 file changed +6
-3
lines changed Expand file tree Collapse file tree 1 file changed +6
-3
lines changed Original file line number Diff line number Diff line change @@ -93,7 +93,7 @@ import qualified Data.List as List
9393
9494-- | A bit set with unspecified container type.
9595data GBitSet c a = (Enum a , Bits c , Num c ) => BitSet
96- { _n :: {-# UNPACK #-} ! Int -- ^ Number of elements in the bit set.
96+ { _n :: Int -- ^ Number of elements in the bit set.
9797# if defined (__GLASGOW_HASKELL__ ) && (__GLASGOW_HASKELL__ >= 708 )
9898 , _bits :: {-# UNPACK #-} ! c -- ^ Bit container.
9999# else
@@ -263,13 +263,16 @@ filter f = fromList . List.filter f . toList
263263-- | /O(d * n)/. Convert this bit set set to a list of elements.
264264toList :: Num c => GBitSet c a -> [a ]
265265toList bs = build (\ k z -> foldr k z bs)
266- {-# INLINE toList #-}
266+ {-# INLINE [0] toList #-}
267267
268268-- | /O(d * n)/. Make a bit set from a list of elements.
269269fromList :: (Enum a , Bits c , Num c ) => [a ] -> GBitSet c a
270270fromList xs = BitSet { _n = popCount b, _bits = b } where
271271 b = List. foldl' (\ i x -> i `setBit` fromEnum x) 0 xs
272- {-# INLINE fromList #-}
272+ {-# INLINE [0] fromList #-}
273+ {-# RULES
274+ "fromList/toList" forall bs. fromList (toList bs) = bs
275+ #-}
273276
274277-- | /O(1)/. Internal function, which extracts the underlying container
275278-- from the bit set.
You can’t perform that action at this time.
0 commit comments