Skip to content

Commit

Permalink
Removes a smattering of, apparent, dead code.
Browse files Browse the repository at this point in the history
Using weeder to find unused definitions. There are a great many more,
but this was an attempt to be relatively conservative in the removal.
  • Loading branch information
telser committed Jan 2, 2025
1 parent 62073c9 commit 68153bb
Show file tree
Hide file tree
Showing 5 changed files with 2 additions and 84 deletions.
1 change: 0 additions & 1 deletion Cabal-described/src/Distribution/Described.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,6 @@ module Distribution.Described (
reMunch1CS,
-- * Variables
reVar0,
reVar1,
-- * Special expressions
reDot,
reComma,
Expand Down
50 changes: 2 additions & 48 deletions Cabal-described/src/Distribution/Utils/CharSet.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,12 +17,9 @@ module Distribution.Utils.CharSet (
difference,
-- * Query
size,
null,
member,
-- * Conversions
fromList,
toList,
fromIntervalList,
toIntervalList,
-- * Special lists
alpha,
Expand All @@ -31,12 +28,12 @@ module Distribution.Utils.CharSet (
) where

import Data.Char (chr, isAlpha, isAlphaNum, isUpper, ord)
import Data.List (foldl', sortBy)
import Data.List (foldl')
import Data.Monoid (Monoid (..))
import Data.String (IsString (..))
import Distribution.Compat.Semigroup (Semigroup (..))
import Prelude
(Bool (..), Bounded (..), Char, Enum (..), Eq (..), Int, Maybe (..), Num (..), Ord (..), Show (..), String, concatMap, flip, fst, otherwise, showParen,
(Bounded (..), Char, Enum (..), Eq (..), Int, Num (..), Ord (..), Show (..), String, concatMap, flip, otherwise, showParen,
showString, uncurry, ($), (.))

#if MIN_VERSION_containers(0,5,0)
Expand Down Expand Up @@ -78,40 +75,15 @@ empty = CS IM.empty
universe :: CharSet
universe = CS $ IM.singleton 0 0x10ffff

-- | Check whether 'CharSet' is 'empty'.
null :: CharSet -> Bool
null (CS cs) = IM.null cs

-- | Size of 'CharSet'
--
-- >>> size $ fromIntervalList [('a','f'), ('0','9')]
-- 16
--
-- >>> length $ toList $ fromIntervalList [('a','f'), ('0','9')]
-- 16
--
size :: CharSet -> Int
size (CS m) = foldl' (\ !acc (lo, hi) -> acc + (hi - lo) + 1) 0 (IM.toList m)

-- | Singleton character set.
singleton :: Char -> CharSet
singleton c = CS (IM.singleton (ord c) (ord c))

-- | Test whether character is in the set.
member :: Char -> CharSet -> Bool
#if MIN_VERSION_containers(0,5,0)
member c (CS m) = case IM.lookupLE i m of
Nothing -> False
Just (_, hi) -> i <= hi
where
#else
member c (CS m) = go (IM.toList m)
where
go [] = False
go ((x,y):zs) = (x <= i && i <= y) || go zs
#endif
i = ord c

-- | Insert 'Char' into 'CharSet'.
insert :: Char -> CharSet -> CharSet
insert c (CS m) = normalise (IM.insert (ord c) (ord c) m)
Expand Down Expand Up @@ -179,24 +151,6 @@ toList = concatMap (uncurry enumFromTo) . toIntervalList
toIntervalList :: CharSet -> [(Char, Char)]
toIntervalList (CS m) = [ (chr lo, chr hi) | (lo, hi) <- IM.toList m ]

-- | Convert from interval pairs.
--
-- >>> fromIntervalList []
-- ""
--
-- >>> fromIntervalList [('a','f'), ('0','9')]
-- "0123456789abcdef"
--
-- >>> fromIntervalList [('Z','A')]
-- ""
--
fromIntervalList :: [(Char,Char)] -> CharSet
fromIntervalList xs = normalise' $ sortBy (\a b -> compare (fst a) (fst b))
[ (ord lo, ord hi)
| (lo, hi) <- xs
, lo <= hi
]

-------------------------------------------------------------------------------
-- Normalisation
-------------------------------------------------------------------------------
Expand Down
1 change: 0 additions & 1 deletion Cabal-tests/Cabal-tests.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,6 @@ test-suite unit-tests
hs-source-dirs: tests
other-modules:
Test.Laws
Test.QuickCheck.Utils
UnitTests.Distribution.CabalSpecVersion
UnitTests.Distribution.Compat.Graph
UnitTests.Distribution.Compat.Time
Expand Down
29 changes: 0 additions & 29 deletions Cabal-tests/tests/Test/QuickCheck/Utils.hs

This file was deleted.

5 changes: 0 additions & 5 deletions cabal-benchmarks/bench/CabalBenchmarks.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,6 @@ import Distribution.Version

import qualified Data.ByteString as BS

import qualified Distribution.Types.VersionInterval.Legacy as Old
import qualified Distribution.Types.VersionInterval as New

-------------------------------------------------------------------------------
Expand Down Expand Up @@ -38,7 +37,6 @@ main = defaultMain
, env bigVersionRangeA $ \vr -> bench "pat4" $ nf f vr
]
in [ suite "def" normaliseVersionRange
, suite "old" oldNormaliseVersionRange
, suite "new" newNormaliseVersionRange
]
]
Expand All @@ -47,9 +45,6 @@ main = defaultMain
-- VersionRanges normalisation
-------------------------------------------------------------------------------

oldNormaliseVersionRange :: VersionRange -> VersionRange
oldNormaliseVersionRange = Old.fromVersionIntervals . Old.toVersionIntervals

newNormaliseVersionRange :: VersionRange -> VersionRange
newNormaliseVersionRange = New.normaliseVersionRange2

Expand Down

0 comments on commit 68153bb

Please sign in to comment.