Skip to content

Commit

Permalink
Separate modifiers by space in TotalIndexState
Browse files Browse the repository at this point in the history
  • Loading branch information
phadej committed Apr 9, 2020
1 parent 30da456 commit 57729c9
Show file tree
Hide file tree
Showing 4 changed files with 54 additions and 28 deletions.
7 changes: 4 additions & 3 deletions Cabal/Distribution/FieldGrammar/Described.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,3 @@
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Distribution.FieldGrammar.Described (
Expand Down Expand Up @@ -28,6 +25,7 @@ module Distribution.FieldGrammar.Described (
reOptCommaList,
-- * Character Sets
csChar,
csAlpha,
csAlphaNum,
csUpper,
csNotSpace,
Expand Down Expand Up @@ -126,6 +124,9 @@ reSpacedComma = RESpaces <> reComma <> RESpaces
csChar :: Char -> CS.CharSet
csChar = CS.singleton

csAlpha :: CS.CharSet
csAlpha = CS.alpha

csAlphaNum :: CS.CharSet
csAlphaNum = CS.alphanum

Expand Down
52 changes: 31 additions & 21 deletions cabal-install/Distribution/Client/IndexUtils/IndexState.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,13 +22,16 @@ import Distribution.Client.IndexUtils.Timestamp (Timestamp)
import Distribution.Client.Types.RepoName (RepoName (..))

import Distribution.FieldGrammar.Described
import Distribution.Parsec (Parsec (..))
import Distribution.Parsec (Parsec (..), parsecLeadingCommaList)
import Distribution.Pretty (Pretty (..))

import qualified Data.Map.Strict as Map
import qualified Distribution.Compat.CharParsing as P
import qualified Text.PrettyPrint as Disp

-- $setup
-- >>> import Distribution.Parsec

-------------------------------------------------------------------------------
-- Total index state
-------------------------------------------------------------------------------
Expand All @@ -51,34 +54,41 @@ instance Pretty TotalIndexState where
pretty (TIS def m) = foldl' go (pretty def) (Map.toList m) where
go doc (rn, idx) = doc Disp.<+> pretty rn <<>> Disp.colon <<>> pretty idx

-- |
--
-- >>> simpleParsec "HEAD" :: Maybe TotalIndexState
-- Just (TIS IndexStateHead (fromList []))
--
-- >>> simpleParsec "" :: Maybe TotalIndexState
-- Just (TIS IndexStateHead (fromList []))
--
-- >>> simpleParsec "hackage.haskell.org HEAD" :: Maybe TotalIndexState
-- Just (TIS IndexStateHead (fromList []))
--
-- >>> simpleParsec "2020-02-04T12:34:56Z, hackage.haskell.org HEAD" :: Maybe TotalIndexState
-- Just (TIS (IndexStateTime (TS 1580819696)) (fromList [(RepoName "hackage.haskell.org",IndexStateHead)]))
--
-- >>> simpleParsec "hackage.haskell.org 2020-02-04T12:34:56Z" :: Maybe TotalIndexState
-- Just (TIS IndexStateHead (fromList [(RepoName "hackage.haskell.org",IndexStateTime (TS 1580819696))]))
--
instance Parsec TotalIndexState where
parsec = normalise . foldl' add headTotalIndexState <$> some (single0 <* P.spaces) where
-- hard to do without try
-- 2020-03-21T11:22:33Z looks like it begins with
-- repository name 2020-03-21T11
--
-- To make this easy, we could forbid repository names starting with digit
--
single0 = P.try single1 <|> TokTimestamp <$> parsec
single1 = do
token <- P.munch1 (\c -> isAlphaNum c || c == '_' || c == '-' || c == '.')
single2 token <|> single3 token

single2 token = do
_ <- P.char ':'
idx <- parsec
return (TokRepo (RepoName token) idx)

single3 "HEAD" = return TokHead
single3 token = P.unexpected ("Repository " ++ token ++ " without index state (after comma)")
parsec = normalise . foldl' add headTotalIndexState <$> parsecLeadingCommaList single0 where
single0 = startsWithRepoName <|> TokTimestamp <$> parsec
startsWithRepoName = do
reponame <- parsec
if reponame == RepoName "HEAD"
then return TokHead
else do
P.spaces
TokRepo reponame <$> parsec

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

instance Described TotalIndexState where
describe _ = REMunch1 RESpaces1 $ REUnion
describe _ = reCommaList $ REUnion
[ describe (Proxy :: Proxy RepoName) <> reChar ':' <> ris
, ris
]
Expand Down
Empty file.
23 changes: 19 additions & 4 deletions cabal-install/Distribution/Client/Types/RepoName.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,13 +7,16 @@ module Distribution.Client.Types.RepoName (
import Distribution.Client.Compat.Prelude
import Prelude ()

import Distribution.FieldGrammar.Described (Described (..), csAlphaNum, reMunch1CS)
import Distribution.FieldGrammar.Described (Described (..), Regex (..), csAlpha, csAlphaNum, reMunchCS)
import Distribution.Parsec (Parsec (..))
import Distribution.Pretty (Pretty (..))

import qualified Distribution.Compat.CharParsing as P
import qualified Text.PrettyPrint as Disp

-- $setup
-- >>> import Distribution.Parsec

-- | Repository name.
--
-- May be used as path segment.
Expand All @@ -31,9 +34,21 @@ instance NFData RepoName
instance Pretty RepoName where
pretty = Disp.text . unRepoName

-- |
--
-- >>> simpleParsec "hackage.haskell.org" :: Maybe RepoName
-- Just (RepoName "hackage.haskell.org")
--
-- >>> simpleParsec "0123" :: Maybe RepoName
-- Nothing
--
instance Parsec RepoName where
parsec = RepoName <$>
P.munch1 (\c -> isAlphaNum c || c == '_' || c == '-' || c == '.')
parsec = RepoName <$> parser where
parser = (:) <$> lead <*> rest
lead = P.satisfy (\c -> isAlpha c || c == '_' || c == '-' || c == '.')
rest = P.munch1 (\c -> isAlphaNum c || c == '_' || c == '-' || c == '.')

instance Described RepoName where
describe _ = reMunch1CS $ csAlphaNum <> fromString "_-."
describe _ = lead <> rest where
lead = RECharSet $ csAlpha <> fromString "_-."
rest = reMunchCS $ csAlphaNum <> fromString "_-."

0 comments on commit 57729c9

Please sign in to comment.