Skip to content

Commit f009c2e

Browse files
committed
Removes a smattering of, apparent, dead code.
Using weeder to find unused definitions. There are a great many more, but this was an attempt to be relatively conservative in the removal.
1 parent dda541c commit f009c2e

File tree

51 files changed

+20
-1185
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

51 files changed

+20
-1185
lines changed

Diff for: Cabal-described/src/Distribution/Described.hs

-1
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,6 @@ module Distribution.Described (
1313
reMunch1CS,
1414
-- * Variables
1515
reVar0,
16-
reVar1,
1716
-- * Special expressions
1817
reDot,
1918
reComma,

Diff for: Cabal-described/src/Distribution/Utils/CharSet.hs

+2-27
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,6 @@ module Distribution.Utils.CharSet (
2222
-- * Conversions
2323
fromList,
2424
toList,
25-
fromIntervalList,
2625
toIntervalList,
2726
-- * Special lists
2827
alpha,
@@ -31,12 +30,12 @@ module Distribution.Utils.CharSet (
3130
) where
3231

3332
import Data.Char (chr, isAlpha, isAlphaNum, isUpper, ord)
34-
import Data.List (foldl', sortBy)
33+
import Data.List (foldl')
3534
import Data.Monoid (Monoid (..))
3635
import Data.String (IsString (..))
3736
import Distribution.Compat.Semigroup (Semigroup (..))
3837
import Prelude
39-
(Bool (..), Bounded (..), Char, Enum (..), Eq (..), Int, Maybe (..), Num (..), Ord (..), Show (..), String, concatMap, flip, fst, otherwise, showParen,
38+
(Bool (..), Bounded (..), Char, Enum (..), Eq (..), Int, Maybe (..), Num (..), Ord (..), Show (..), String, concatMap, flip, otherwise, showParen,
4039
showString, uncurry, ($), (.))
4140

4241
#if MIN_VERSION_containers(0,5,0)
@@ -84,12 +83,6 @@ null (CS cs) = IM.null cs
8483

8584
-- | Size of 'CharSet'
8685
--
87-
-- >>> size $ fromIntervalList [('a','f'), ('0','9')]
88-
-- 16
89-
--
90-
-- >>> length $ toList $ fromIntervalList [('a','f'), ('0','9')]
91-
-- 16
92-
--
9386
size :: CharSet -> Int
9487
size (CS m) = foldl' (\ !acc (lo, hi) -> acc + (hi - lo) + 1) 0 (IM.toList m)
9588

@@ -179,24 +172,6 @@ toList = concatMap (uncurry enumFromTo) . toIntervalList
179172
toIntervalList :: CharSet -> [(Char, Char)]
180173
toIntervalList (CS m) = [ (chr lo, chr hi) | (lo, hi) <- IM.toList m ]
181174

182-
-- | Convert from interval pairs.
183-
--
184-
-- >>> fromIntervalList []
185-
-- ""
186-
--
187-
-- >>> fromIntervalList [('a','f'), ('0','9')]
188-
-- "0123456789abcdef"
189-
--
190-
-- >>> fromIntervalList [('Z','A')]
191-
-- ""
192-
--
193-
fromIntervalList :: [(Char,Char)] -> CharSet
194-
fromIntervalList xs = normalise' $ sortBy (\a b -> compare (fst a) (fst b))
195-
[ (ord lo, ord hi)
196-
| (lo, hi) <- xs
197-
, lo <= hi
198-
]
199-
200175
-------------------------------------------------------------------------------
201176
-- Normalisation
202177
-------------------------------------------------------------------------------

Diff for: Cabal-syntax/src/Distribution/Compat/CharParsing.hs

-54
Original file line numberDiff line numberDiff line change
@@ -22,18 +22,10 @@
2222
module Distribution.Compat.CharParsing
2323
( -- * Combinators
2424
oneOf -- :: CharParsing m => [Char] -> m Char
25-
, noneOf -- :: CharParsing m => [Char] -> m Char
2625
, spaces -- :: CharParsing m => m ()
2726
, space -- :: CharParsing m => m Char
28-
, newline -- :: CharParsing m => m Char
29-
, tab -- :: CharParsing m => m Char
3027
, upper -- :: CharParsing m => m Char
31-
, lower -- :: CharParsing m => m Char
32-
, alphaNum -- :: CharParsing m => m Char
33-
, letter -- :: CharParsing m => m Char
34-
, digit -- :: CharParsing m => m Char
3528
, hexDigit -- :: CharParsing m => m Char
36-
, octDigit -- :: CharParsing m => m Char
3729
, satisfyRange -- :: CharParsing m => Char -> Char -> m Char
3830

3931
-- * Class
@@ -76,15 +68,6 @@ oneOf :: CharParsing m => [Char] -> m Char
7668
oneOf xs = satisfy (\c -> c `elem` xs)
7769
{-# INLINE oneOf #-}
7870

79-
-- | As the dual of 'oneOf', @noneOf cs@ succeeds if the current
80-
-- character is /not/ in the supplied list of characters @cs@. Returns the
81-
-- parsed character.
82-
--
83-
-- > consonant = noneOf "aeiou"
84-
noneOf :: CharParsing m => [Char] -> m Char
85-
noneOf xs = satisfy (\c -> c `notElem` xs)
86-
{-# INLINE noneOf #-}
87-
8871
-- | Skips /zero/ or more white space characters. See also 'skipMany'.
8972
spaces :: CharParsing m => m ()
9073
spaces = skipMany space <?> "white space"
@@ -96,54 +79,17 @@ space :: CharParsing m => m Char
9679
space = satisfy isSpace <?> "space"
9780
{-# INLINE space #-}
9881

99-
-- | Parses a newline character (\'\\n\'). Returns a newline character.
100-
newline :: CharParsing m => m Char
101-
newline = char '\n' <?> "new-line"
102-
{-# INLINE newline #-}
103-
104-
-- | Parses a tab character (\'\\t\'). Returns a tab character.
105-
tab :: CharParsing m => m Char
106-
tab = char '\t' <?> "tab"
107-
{-# INLINE tab #-}
108-
10982
-- | Parses an upper case letter. Returns the parsed character.
11083
upper :: CharParsing m => m Char
11184
upper = satisfy isUpper <?> "uppercase letter"
11285
{-# INLINE upper #-}
11386

114-
-- | Parses a lower case character. Returns the parsed character.
115-
lower :: CharParsing m => m Char
116-
lower = satisfy isLower <?> "lowercase letter"
117-
{-# INLINE lower #-}
118-
119-
-- | Parses a letter or digit. Returns the parsed character.
120-
alphaNum :: CharParsing m => m Char
121-
alphaNum = satisfy isAlphaNum <?> "letter or digit"
122-
{-# INLINE alphaNum #-}
123-
124-
-- | Parses a letter (an upper case or lower case character). Returns the
125-
-- parsed character.
126-
letter :: CharParsing m => m Char
127-
letter = satisfy isAlpha <?> "letter"
128-
{-# INLINE letter #-}
129-
130-
-- | Parses a digit. Returns the parsed character.
131-
digit :: CharParsing m => m Char
132-
digit = satisfy isDigit <?> "digit"
133-
{-# INLINE digit #-}
134-
13587
-- | Parses a hexadecimal digit (a digit or a letter between \'a\' and
13688
-- \'f\' or \'A\' and \'F\'). Returns the parsed character.
13789
hexDigit :: CharParsing m => m Char
13890
hexDigit = satisfy isHexDigit <?> "hexadecimal digit"
13991
{-# INLINE hexDigit #-}
14092

141-
-- | Parses an octal digit (a character between \'0\' and \'7\'). Returns
142-
-- the parsed character.
143-
octDigit :: CharParsing m => m Char
144-
octDigit = satisfy isOctDigit <?> "octal digit"
145-
{-# INLINE octDigit #-}
146-
14793
satisfyRange :: CharParsing m => Char -> Char -> m Char
14894
satisfyRange a z = satisfy (\c -> c >= a && c <= z)
14995
{-# INLINE satisfyRange #-}

Diff for: Cabal-syntax/src/Distribution/Compat/Graph.hs

-35
Original file line numberDiff line numberDiff line change
@@ -49,18 +49,14 @@ module Distribution.Compat.Graph
4949

5050
-- * Query
5151
, null
52-
, size
5352
, member
5453
, lookup
5554

5655
-- * Construction
5756
, empty
5857
, insert
59-
, deleteKey
60-
, deleteLookup
6158

6259
-- * Combine
63-
, unionLeft
6460
, unionRight
6561

6662
-- * Graph algorithms
@@ -72,7 +68,6 @@ module Distribution.Compat.Graph
7268
, revNeighbors
7369
, closure
7470
, revClosure
75-
, topSort
7671
, revTopSort
7772

7873
-- * Conversions
@@ -93,7 +88,6 @@ module Distribution.Compat.Graph
9388

9489
-- * Node type
9590
, Node (..)
96-
, nodeValue
9791
) where
9892

9993
import Distribution.Compat.Prelude hiding (empty, lookup, null, toList)
@@ -200,10 +194,6 @@ instance (IsNode a, IsNode b, Key a ~ Key b) => IsNode (Either a b) where
200194
data Node k a = N a k [k]
201195
deriving (Show, Eq)
202196

203-
-- | Get the value from a 'Node'.
204-
nodeValue :: Node k a -> a
205-
nodeValue (N a _ _) = a
206-
207197
instance Functor (Node k) where
208198
fmap f (N a k ks) = N (f a) k ks
209199

@@ -222,10 +212,6 @@ instance Ord k => IsNode (Node k a) where
222212
null :: Graph a -> Bool
223213
null = Map.null . toMap
224214

225-
-- | /O(1)/. The number of nodes in the graph.
226-
size :: Graph a -> Int
227-
size = Map.size . toMap
228-
229215
-- | /O(log V)/. Check if the key is in the graph.
230216
member :: IsNode a => Key a -> Graph a -> Bool
231217
member k g = Map.member k (toMap g)
@@ -244,17 +230,6 @@ empty = fromMap Map.empty
244230
insert :: IsNode a => a -> Graph a -> Graph a
245231
insert !n g = fromMap (Map.insert (nodeKey n) n (toMap g))
246232

247-
-- | /O(log V)/. Delete the node at a key from the graph.
248-
deleteKey :: IsNode a => Key a -> Graph a -> Graph a
249-
deleteKey k g = fromMap (Map.delete k (toMap g))
250-
251-
-- | /O(log V)/. Lookup and delete. This function returns the deleted
252-
-- value if it existed.
253-
deleteLookup :: IsNode a => Key a -> Graph a -> (Maybe a, Graph a)
254-
deleteLookup k g =
255-
let (r, m') = Map.updateLookupWithKey (\_ _ -> Nothing) k (toMap g)
256-
in (r, fromMap m')
257-
258233
-- Combining
259234

260235
-- | /O(V + V')/. Right-biased union, preferring entries
@@ -263,11 +238,6 @@ deleteLookup k g =
263238
unionRight :: IsNode a => Graph a -> Graph a -> Graph a
264239
unionRight g g' = fromMap (Map.union (toMap g') (toMap g))
265240

266-
-- | /O(V + V')/. Left-biased union, preferring entries from
267-
-- the first map when conflicts occur.
268-
unionLeft :: IsNode a => Graph a -> Graph a -> Graph a
269-
unionLeft = flip unionRight
270-
271241
-- Graph-like operations
272242

273243
-- | /Ω(V + E)/. Compute the strongly connected components of a graph.
@@ -336,11 +306,6 @@ flattenForest = concatMap Tree.flatten
336306
decodeVertexForest :: Graph a -> Tree.Forest G.Vertex -> [a]
337307
decodeVertexForest g = map (graphVertexToNode g) . flattenForest
338308

339-
-- | Topologically sort the nodes of a graph.
340-
-- Requires amortized construction of graph.
341-
topSort :: Graph a -> [a]
342-
topSort g = map (graphVertexToNode g) $ G.topSort (graphForward g)
343-
344309
-- | Reverse topologically sort the nodes of a graph.
345310
-- Requires amortized construction of graph.
346311
revTopSort :: Graph a -> [a]

Diff for: Cabal-syntax/src/Distribution/Compat/Lens.hs

+1-12
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,6 @@ module Distribution.Compat.Lens
1717

1818
-- ** rank-1 types
1919
, Getting
20-
, AGetter
2120
, ASetter
2221
, ALens
2322
, ALens'
@@ -55,7 +54,6 @@ module Distribution.Compat.Lens
5554
, (%=)
5655
, (^#)
5756
, (#~)
58-
, (#%~)
5957

6058
-- * Internal Comonads
6159
, Pretext (..)
@@ -87,7 +85,6 @@ type Traversal' s a = Traversal s s a a
8785

8886
type Getting r s a = LensLike (Const r) s s a a
8987

90-
type AGetter s a = LensLike (Const a) s s a a -- this doesn't exist in 'lens'
9188
type ASetter s t a b = LensLike Identity s t a b
9289
type ALens s t a b = LensLike (Pretext a b) s t a b
9390

@@ -172,7 +169,7 @@ infixl 1 &
172169

173170
infixl 8 ^., ^#
174171
infixr 4 .~, %~, ?~
175-
infixr 4 #~, #%~
172+
infixr 4 #~
176173
infixr 4 .=, %=, ?=
177174

178175
(^.) :: s -> Getting a s a -> a
@@ -210,18 +207,10 @@ s ^# l = aview l s
210207
(#~) l b s = pretextPeek b (l pretextSell s)
211208
{-# INLINE (#~) #-}
212209

213-
(#%~) :: ALens s t a b -> (a -> b) -> s -> t
214-
(#%~) l f s = pretextPeeks f (l pretextSell s)
215-
{-# INLINE (#%~) #-}
216-
217210
pretextSell :: a -> Pretext a b b
218211
pretextSell a = Pretext (\afb -> afb a)
219212
{-# INLINE pretextSell #-}
220213

221-
pretextPeeks :: (a -> b) -> Pretext a b t -> t
222-
pretextPeeks f (Pretext m) = runIdentity $ m (\x -> Identity (f x))
223-
{-# INLINE pretextPeeks #-}
224-
225214
pretextPeek :: b -> Pretext a b t -> t
226215
pretextPeek b (Pretext m) = runIdentity $ m (\_ -> Identity b)
227216
{-# INLINE pretextPeek #-}

Diff for: Cabal-syntax/src/Distribution/Compat/Newtype.hs

+1-25
Original file line numberDiff line numberDiff line change
@@ -4,12 +4,9 @@
44
{-# LANGUAGE FunctionalDependencies #-}
55

66
-- | Per Conor McBride, the 'Newtype' typeclass represents the packing and
7-
-- unpacking of a newtype, and allows you to operate under that newtype with
8-
-- functions such as 'ala'.
7+
-- unpacking of a newtype.
98
module Distribution.Compat.Newtype
109
( Newtype (..)
11-
, ala
12-
, alaf
1310
, pack'
1411
, unpack'
1512
) where
@@ -63,27 +60,6 @@ instance Newtype a (Sum a)
6360
instance Newtype a (Product a)
6461
instance Newtype (a -> a) (Endo a)
6562

66-
-- |
67-
--
68-
-- >>> ala Sum foldMap [1, 2, 3, 4 :: Int]
69-
-- 10
70-
--
71-
-- /Note:/ the user supplied function for the newtype is /ignored/.
72-
--
73-
-- >>> ala (Sum . (+1)) foldMap [1, 2, 3, 4 :: Int]
74-
-- 10
75-
ala :: (Newtype o n, Newtype o' n') => (o -> n) -> ((o -> n) -> b -> n') -> (b -> o')
76-
ala pa hof = alaf pa hof id
77-
78-
-- |
79-
--
80-
-- >>> alaf Sum foldMap length ["cabal", "install"]
81-
-- 12
82-
--
83-
-- /Note:/ as with 'ala', the user supplied function for the newtype is /ignored/.
84-
alaf :: (Newtype o n, Newtype o' n') => (o -> n) -> ((a -> n) -> b -> n') -> (a -> o) -> (b -> o')
85-
alaf _ hof f = unpack . hof (pack . f)
86-
8763
-- | Variant of 'pack', which takes a phantom type.
8864
pack' :: Newtype o n => (o -> n) -> o -> n
8965
pack' _ = pack

0 commit comments

Comments
 (0)