Skip to content

Commit bd817eb

Browse files
committed
Resolve #6728: TotalIndexState cannot be empty string
1 parent b89a1c6 commit bd817eb

File tree

6 files changed

+41
-4
lines changed

6 files changed

+41
-4
lines changed

Cabal/Distribution/FieldGrammar/Described.hs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -22,6 +22,7 @@ module Distribution.FieldGrammar.Described (
2222
-- * Lists
2323
reSpacedList,
2424
reCommaList,
25+
reCommaNonEmpty,
2526
reOptCommaList,
2627
-- * Character Sets
2728
csChar,
@@ -72,6 +73,9 @@ reSpacedList = REMunch RESpaces1
7273
reCommaList :: GrammarRegex a -> GrammarRegex a
7374
reCommaList = RECommaList
7475

76+
reCommaNonEmpty :: GrammarRegex a -> GrammarRegex a
77+
reCommaNonEmpty = RECommaNonEmpty
78+
7579
reOptCommaList :: GrammarRegex a -> GrammarRegex a
7680
reOptCommaList = REOptCommaList
7781

Cabal/Distribution/Parsec.hs

Lines changed: 14 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -40,6 +40,7 @@ module Distribution.Parsec (
4040
parsecMaybeQuoted,
4141
parsecCommaList,
4242
parsecLeadingCommaList,
43+
parsecLeadingCommaNonEmpty,
4344
parsecOptCommaList,
4445
parsecLeadingOptCommaList,
4546
parsecStandard,
@@ -309,6 +310,19 @@ parsecLeadingCommaList p = do
309310
lp = p <* P.spaces
310311
comma = P.char ',' *> P.spaces P.<?> "comma"
311312

313+
-- |
314+
--
315+
-- @since 3.4.0.0
316+
parsecLeadingCommaNonEmpty :: CabalParsing m => m a -> m (NonEmpty a)
317+
parsecLeadingCommaNonEmpty p = do
318+
c <- P.optional comma
319+
case c of
320+
Nothing -> P.sepEndByNonEmpty lp comma
321+
Just _ -> P.sepByNonEmpty lp comma
322+
where
323+
lp = p <* P.spaces
324+
comma = P.char ',' *> P.spaces P.<?> "comma"
325+
312326
parsecOptCommaList :: CabalParsing m => m a -> m [a]
313327
parsecOptCommaList p = P.sepBy (p <* P.spaces) (P.optional comma)
314328
where

Cabal/Distribution/Utils/GrammarRegex.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -50,6 +50,7 @@ data GrammarRegex a
5050
| RESpaces -- ^ zero-or-more spaces
5151
| RESpaces1 -- ^ one-or-more spaces
5252
| RECommaList (GrammarRegex a) -- ^ comma list (note, leading or trailing commas)
53+
| RECommaNonEmpty (GrammarRegex a) -- ^ comma non-empty list
5354
| REOptCommaList (GrammarRegex a) -- ^ opt comma list
5455

5556
| RETodo -- ^ unspecified
@@ -146,6 +147,8 @@ regexDoc = go 0 . vacuous where
146147

147148
go _ (RECommaList r) =
148149
"\\mathrm{commalist}" <<>> go 4 r
150+
go _ (RECommaNonEmpty r) =
151+
"\\mathrm{commanonempty}" <<>> go 4 r
149152
go _ (REOptCommaList r) =
150153
"\\mathrm{optcommalist}" <<>> go 4 r
151154

Cabal/tests/UnitTests/Distribution/Described.hs

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -136,13 +136,21 @@ convert = go id . vacuous where
136136
go _ RESpaces1 = RE.ch_ ' ' RE.\/ " " RE.\/ "\n"
137137

138138
go f (RECommaList r) = go f (expandedCommaList r)
139+
go f (RECommaNonEmpty r)= go f (expandedCommaNonEmpty r)
139140
go f (REOptCommaList r) = go f (expandedOptCommaList r)
140141

141142
go _ RETodo = RE.Null
142143

143144
expandedCommaList :: GrammarRegex a -> GrammarRegex a
144145
expandedCommaList = REUnion . expandedCommaList'
145146

147+
expandedCommaNonEmpty :: GrammarRegex a -> GrammarRegex a
148+
expandedCommaNonEmpty r = REUnion
149+
[ REMunch1 reSpacedComma r
150+
, reComma <> RESpaces <> REMunch1 reSpacedComma r
151+
, REMunch1 reSpacedComma r <> RESpaces <> reComma
152+
]
153+
146154
expandedCommaList' :: GrammarRegex a -> [GrammarRegex a]
147155
expandedCommaList' r =
148156
[ REMunch reSpacedComma r

cabal-install/Distribution/Client/IndexUtils/IndexState.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,7 @@ import Distribution.Client.IndexUtils.Timestamp (Timestamp)
2222
import Distribution.Client.Types.RepoName (RepoName (..))
2323

2424
import Distribution.FieldGrammar.Described
25-
import Distribution.Parsec (Parsec (..), parsecLeadingCommaList)
25+
import Distribution.Parsec (Parsec (..), parsecLeadingCommaNonEmpty)
2626
import Distribution.Pretty (Pretty (..))
2727

2828
import qualified Data.Map.Strict as Map
@@ -60,7 +60,7 @@ instance Pretty TotalIndexState where
6060
-- Just (TIS IndexStateHead (fromList []))
6161
--
6262
-- >>> simpleParsec "" :: Maybe TotalIndexState
63-
-- Just (TIS IndexStateHead (fromList []))
63+
-- Nothing
6464
--
6565
-- >>> simpleParsec "hackage.haskell.org HEAD" :: Maybe TotalIndexState
6666
-- Just (TIS IndexStateHead (fromList []))
@@ -72,7 +72,7 @@ instance Pretty TotalIndexState where
7272
-- Just (TIS IndexStateHead (fromList [(RepoName "hackage.haskell.org",IndexStateTime (TS 1580819696))]))
7373
--
7474
instance Parsec TotalIndexState where
75-
parsec = normalise . foldl' add headTotalIndexState <$> parsecLeadingCommaList single0 where
75+
parsec = normalise . foldl' add headTotalIndexState <$> parsecLeadingCommaNonEmpty single0 where
7676
single0 = startsWithRepoName <|> TokTimestamp <$> parsec
7777
startsWithRepoName = do
7878
reponame <- parsec
@@ -89,7 +89,7 @@ instance Parsec TotalIndexState where
8989
add (TIS def m) (TokRepo rn idx) = TIS def (Map.insert rn idx m)
9090

9191
instance Described TotalIndexState where
92-
describe _ = reCommaList $ REUnion
92+
describe _ = reCommaNonEmpty $ REUnion
9393
[ describe (Proxy :: Proxy RepoName) <> RESpaces1 <> ris
9494
, ris
9595
]

cabal-install/tests/UnitTests/Distribution/Client/Described.hs

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -132,13 +132,21 @@ convert = go id . vacuous where
132132
go _ RESpaces1 = RE.ch_ ' ' RE.\/ " " RE.\/ "\n"
133133

134134
go f (RECommaList r) = go f (expandedCommaList r)
135+
go f (RECommaNonEmpty r)= go f (expandedCommaNonEmpty r)
135136
go f (REOptCommaList r) = go f (expandedOptCommaList r)
136137

137138
go _ RETodo = RE.Null
138139

139140
expandedCommaList :: GrammarRegex a -> GrammarRegex a
140141
expandedCommaList = REUnion . expandedCommaList'
141142

143+
expandedCommaNonEmpty :: GrammarRegex a -> GrammarRegex a
144+
expandedCommaNonEmpty r = REUnion
145+
[ REMunch1 reSpacedComma r
146+
, reComma <> RESpaces <> REMunch1 reSpacedComma r
147+
, REMunch1 reSpacedComma r <> RESpaces <> reComma
148+
]
149+
142150
expandedCommaList' :: GrammarRegex a -> [GrammarRegex a]
143151
expandedCommaList' r =
144152
[ REMunch reSpacedComma r

0 commit comments

Comments
 (0)