Skip to content

Commit efff91c

Browse files
committed
Separate modifiers by space in TotalIndexState
1 parent 30da456 commit efff91c

File tree

5 files changed

+64
-33
lines changed

5 files changed

+64
-33
lines changed

Cabal/Distribution/FieldGrammar/Described.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,3 @@
1-
{-# LANGUAGE DeriveFoldable #-}
2-
{-# LANGUAGE DeriveFunctor #-}
3-
{-# LANGUAGE DeriveTraversable #-}
41
{-# LANGUAGE OverloadedStrings #-}
52
{-# LANGUAGE ScopedTypeVariables #-}
63
module Distribution.FieldGrammar.Described (
@@ -28,6 +25,7 @@ module Distribution.FieldGrammar.Described (
2825
reOptCommaList,
2926
-- * Character Sets
3027
csChar,
28+
csAlpha,
3129
csAlphaNum,
3230
csUpper,
3331
csNotSpace,
@@ -126,6 +124,9 @@ reSpacedComma = RESpaces <> reComma <> RESpaces
126124
csChar :: Char -> CS.CharSet
127125
csChar = CS.singleton
128126

127+
csAlpha :: CS.CharSet
128+
csAlpha = CS.alpha
129+
129130
csAlphaNum :: CS.CharSet
130131
csAlphaNum = CS.alphanum
131132

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

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

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

2828
import qualified Data.Map.Strict as Map
2929
import qualified Distribution.Compat.CharParsing as P
3030
import qualified Text.PrettyPrint as Disp
3131

32+
-- $setup
33+
-- >>> import Distribution.Parsec
34+
3235
-------------------------------------------------------------------------------
3336
-- Total index state
3437
-------------------------------------------------------------------------------
@@ -44,42 +47,50 @@ instance NFData TotalIndexState
4447
instance Pretty TotalIndexState where
4548
pretty (TIS IndexStateHead m)
4649
| not (Map.null m)
47-
= Disp.hsep
48-
[ pretty rn <<>> Disp.colon <<>> pretty idx
50+
= Disp.hsep $ Disp.punctuate Disp.comma
51+
[ pretty rn Disp.<+> pretty idx
4952
| (rn, idx) <- Map.toList m
5053
]
5154
pretty (TIS def m) = foldl' go (pretty def) (Map.toList m) where
52-
go doc (rn, idx) = doc Disp.<+> pretty rn <<>> Disp.colon <<>> pretty idx
55+
go doc (rn, idx) = doc <<>> Disp.comma Disp.<+> pretty rn Disp.<+> pretty idx
5356

57+
-- |
58+
--
59+
-- >>> simpleParsec "HEAD" :: Maybe TotalIndexState
60+
-- Just (TIS IndexStateHead (fromList []))
61+
--
62+
-- >>> simpleParsec "" :: Maybe TotalIndexState
63+
-- Just (TIS IndexStateHead (fromList []))
64+
--
65+
-- >>> simpleParsec "hackage.haskell.org HEAD" :: Maybe TotalIndexState
66+
-- Just (TIS IndexStateHead (fromList []))
67+
--
68+
-- >>> simpleParsec "2020-02-04T12:34:56Z, hackage.haskell.org HEAD" :: Maybe TotalIndexState
69+
-- Just (TIS (IndexStateTime (TS 1580819696)) (fromList [(RepoName "hackage.haskell.org",IndexStateHead)]))
70+
--
71+
-- >>> simpleParsec "hackage.haskell.org 2020-02-04T12:34:56Z" :: Maybe TotalIndexState
72+
-- Just (TIS IndexStateHead (fromList [(RepoName "hackage.haskell.org",IndexStateTime (TS 1580819696))]))
73+
--
5474
instance Parsec TotalIndexState where
55-
parsec = normalise . foldl' add headTotalIndexState <$> some (single0 <* P.spaces) where
56-
-- hard to do without try
57-
-- 2020-03-21T11:22:33Z looks like it begins with
58-
-- repository name 2020-03-21T11
59-
--
60-
-- To make this easy, we could forbid repository names starting with digit
61-
--
62-
single0 = P.try single1 <|> TokTimestamp <$> parsec
63-
single1 = do
64-
token <- P.munch1 (\c -> isAlphaNum c || c == '_' || c == '-' || c == '.')
65-
single2 token <|> single3 token
66-
67-
single2 token = do
68-
_ <- P.char ':'
69-
idx <- parsec
70-
return (TokRepo (RepoName token) idx)
71-
72-
single3 "HEAD" = return TokHead
73-
single3 token = P.unexpected ("Repository " ++ token ++ " without index state (after comma)")
75+
parsec = normalise . foldl' add headTotalIndexState <$> parsecLeadingCommaList single0 where
76+
single0 = startsWithRepoName <|> TokTimestamp <$> parsec
77+
startsWithRepoName = do
78+
reponame <- parsec
79+
-- the "HEAD" is technically a valid reponame...
80+
if reponame == RepoName "HEAD"
81+
then return TokHead
82+
else do
83+
P.spaces
84+
TokRepo reponame <$> parsec
7485

7586
add :: TotalIndexState -> Tok -> TotalIndexState
7687
add _ TokHead = headTotalIndexState
7788
add _ (TokTimestamp ts) = TIS (IndexStateTime ts) Map.empty
7889
add (TIS def m) (TokRepo rn idx) = TIS def (Map.insert rn idx m)
7990

8091
instance Described TotalIndexState where
81-
describe _ = REMunch1 RESpaces1 $ REUnion
82-
[ describe (Proxy :: Proxy RepoName) <> reChar ':' <> ris
92+
describe _ = reCommaList $ REUnion
93+
[ describe (Proxy :: Proxy RepoName) <> RESpaces1 <> ris
8394
, ris
8495
]
8596
where

cabal-install/Distribution/Client/Types/Packages.hs

Whitespace-only changes.

cabal-install/Distribution/Client/Types/RepoName.hs

Lines changed: 19 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -7,13 +7,16 @@ module Distribution.Client.Types.RepoName (
77
import Distribution.Client.Compat.Prelude
88
import Prelude ()
99

10-
import Distribution.FieldGrammar.Described (Described (..), csAlphaNum, reMunch1CS)
10+
import Distribution.FieldGrammar.Described (Described (..), Regex (..), csAlpha, csAlphaNum, reMunchCS)
1111
import Distribution.Parsec (Parsec (..))
1212
import Distribution.Pretty (Pretty (..))
1313

1414
import qualified Distribution.Compat.CharParsing as P
1515
import qualified Text.PrettyPrint as Disp
1616

17+
-- $setup
18+
-- >>> import Distribution.Parsec
19+
1720
-- | Repository name.
1821
--
1922
-- May be used as path segment.
@@ -31,9 +34,21 @@ instance NFData RepoName
3134
instance Pretty RepoName where
3235
pretty = Disp.text . unRepoName
3336

37+
-- |
38+
--
39+
-- >>> simpleParsec "hackage.haskell.org" :: Maybe RepoName
40+
-- Just (RepoName "hackage.haskell.org")
41+
--
42+
-- >>> simpleParsec "0123" :: Maybe RepoName
43+
-- Nothing
44+
--
3445
instance Parsec RepoName where
35-
parsec = RepoName <$>
36-
P.munch1 (\c -> isAlphaNum c || c == '_' || c == '-' || c == '.')
46+
parsec = RepoName <$> parser where
47+
parser = (:) <$> lead <*> rest
48+
lead = P.satisfy (\c -> isAlpha c || c == '_' || c == '-' || c == '.')
49+
rest = P.munch (\c -> isAlphaNum c || c == '_' || c == '-' || c == '.')
3750

3851
instance Described RepoName where
39-
describe _ = reMunch1CS $ csAlphaNum <> fromString "_-."
52+
describe _ = lead <> rest where
53+
lead = RECharSet $ csAlpha <> fromString "_-."
54+
rest = reMunchCS $ csAlphaNum <> fromString "_-."

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

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -152,7 +152,11 @@ arbitraryFlag :: Gen a -> Gen (Flag a)
152152
arbitraryFlag = liftArbitrary
153153

154154
instance Arbitrary RepoName where
155-
arbitrary = RepoName <$> listOf1 (elements
155+
arbitrary = RepoName <$> mk where
156+
mk = (:) <$> lead <*> rest
157+
lead = elements
158+
[ c | c <- [ '\NUL' .. '\255' ], isAlpha c || c `elem` "_-."]
159+
rest = listOf (elements
156160
[ c | c <- [ '\NUL' .. '\255' ], isAlphaNum c || c `elem` "_-."])
157161

158162
instance Arbitrary ReportLevel where

0 commit comments

Comments
 (0)