Skip to content

Commit b983469

Browse files
Remove CabalParsing class, specialize to ParsecParser
1 parent dda541c commit b983469

File tree

26 files changed

+128
-123
lines changed

26 files changed

+128
-123
lines changed

Cabal-syntax/src/Distribution/Backpack.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -228,7 +228,7 @@ dispOpenModuleSubstEntry (k, v) = pretty k <<>> Disp.char '=' <<>> pretty v
228228
-- | Inverse to 'dispModSubst'.
229229
--
230230
-- @since 2.2
231-
parsecOpenModuleSubst :: CabalParsing m => m OpenModuleSubst
231+
parsecOpenModuleSubst :: ParsecParser OpenModuleSubst
232232
parsecOpenModuleSubst =
233233
fmap Map.fromList
234234
. flip P.sepBy (P.char ',')
@@ -237,7 +237,7 @@ parsecOpenModuleSubst =
237237
-- | Inverse to 'dispModSubstEntry'.
238238
--
239239
-- @since 2.2
240-
parsecOpenModuleSubstEntry :: CabalParsing m => m (ModuleName, OpenModule)
240+
parsecOpenModuleSubstEntry :: ParsecParser (ModuleName, OpenModule)
241241
parsecOpenModuleSubstEntry =
242242
do
243243
k <- parsec

Cabal-syntax/src/Distribution/FieldGrammar/FieldDescrs.hs

Lines changed: 6 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,7 @@ import qualified Text.PrettyPrint as Disp
2929
-- strict pair
3030
data SP s = SP
3131
{ pPretty :: !(s -> Disp.Doc)
32-
, pParse :: !(forall m. P.CabalParsing m => s -> m s)
32+
, pParse :: !(s -> P.ParsecParser s)
3333
}
3434

3535
-- | A collection of field parsers and pretty-printers.
@@ -40,21 +40,20 @@ instance Applicative (FieldDescrs s) where
4040
pure _ = F mempty
4141
f <*> x = F (mappend (runF f) (runF x))
4242

43-
singletonF :: P.FieldName -> (s -> Disp.Doc) -> (forall m. P.CabalParsing m => s -> m s) -> FieldDescrs s a
43+
singletonF :: P.FieldName -> (s -> Disp.Doc) -> (s -> P.ParsecParser s) -> FieldDescrs s a
4444
singletonF fn f g = F $ Map.singleton fn (SP f g)
4545

4646
-- | Lookup a field value pretty-printer.
4747
fieldDescrPretty :: FieldDescrs s a -> P.FieldName -> Maybe (s -> Disp.Doc)
4848
fieldDescrPretty (F m) fn = pPretty <$> Map.lookup fn m
4949

5050
-- | Lookup a field value parser.
51-
fieldDescrParse :: P.CabalParsing m => FieldDescrs s a -> P.FieldName -> Maybe (s -> m s)
51+
fieldDescrParse :: FieldDescrs s a -> P.FieldName -> Maybe (s -> P.ParsecParser s)
5252
fieldDescrParse (F m) fn = (\f -> pParse f) <$> Map.lookup fn m
5353

5454
fieldDescrsToList
55-
:: P.CabalParsing m
56-
=> FieldDescrs s a
57-
-> [(P.FieldName, s -> Disp.Doc, s -> m s)]
55+
:: FieldDescrs s a
56+
-> [(P.FieldName, s -> Disp.Doc, s -> P.ParsecParser s)]
5857
fieldDescrsToList = map mk . Map.toList . runF
5958
where
6059
mk (name, SP ppr parse) = (name, ppr, parse)
@@ -111,7 +110,7 @@ instance FieldGrammar ParsecPretty FieldDescrs where
111110
availableSince _ _ = id
112111
hiddenField _ = F mempty
113112

114-
parsecFreeText :: P.CabalParsing m => m String
113+
parsecFreeText :: P.ParsecParser String
115114
parsecFreeText = dropDotLines <$ C.spaces <*> many C.anyChar
116115
where
117116
-- Example package with dot lines

Cabal-syntax/src/Distribution/FieldGrammar/Newtypes.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -96,8 +96,8 @@ data NoCommaFSep = NoCommaFSep
9696
class Sep sep where
9797
prettySep :: Proxy sep -> [Doc] -> Doc
9898

99-
parseSep :: CabalParsing m => Proxy sep -> m a -> m [a]
100-
parseSepNE :: CabalParsing m => Proxy sep -> m a -> m (NonEmpty a)
99+
parseSep :: Proxy sep -> ParsecParser a -> ParsecParser [a]
100+
parseSepNE :: Proxy sep -> ParsecParser a -> ParsecParser (NonEmpty a)
101101

102102
instance Sep CommaVCat where
103103
prettySep _ = vcat . punctuate comma
@@ -449,7 +449,7 @@ instance Pretty TestedWith where
449449
pretty x = case unpack x of
450450
(compiler, vr) -> pretty compiler <+> pretty vr
451451

452-
parsecTestedWith :: CabalParsing m => m (CompilerFlavor, VersionRange)
452+
parsecTestedWith :: ParsecParser (CompilerFlavor, VersionRange)
453453
parsecTestedWith = do
454454
name <- lexemeParsec
455455
ver <- parsec <|> pure anyVersion

Cabal-syntax/src/Distribution/ModuleName.hs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -57,27 +57,27 @@ instance Pretty ModuleName where
5757
instance Parsec ModuleName where
5858
parsec = parsecModuleName
5959

60-
parsecModuleName :: forall m. CabalParsing m => m ModuleName
60+
parsecModuleName :: ParsecParser ModuleName
6161
parsecModuleName = state0 DList.empty
6262
where
63-
upper :: m Char
63+
upper :: ParsecParser Char
6464
!upper = P.satisfy isUpper
6565

66-
ch :: m Char
66+
ch :: ParsecParser Char
6767
!ch = P.satisfy (\c -> validModuleChar c || c == '.')
6868

69-
alt :: m ModuleName -> m ModuleName -> m ModuleName
69+
alt :: ParsecParser ModuleName -> ParsecParser ModuleName -> ParsecParser ModuleName
7070
!alt = (<|>)
7171

72-
state0 :: DList.DList Char -> m ModuleName
72+
state0 :: DList.DList Char -> ParsecParser ModuleName
7373
state0 acc = do
7474
c <- upper
7575
state1 (DList.snoc acc c)
7676

77-
state1 :: DList.DList Char -> m ModuleName
77+
state1 :: DList.DList Char -> ParsecParser ModuleName
7878
state1 acc = state1' acc `alt` return (fromString (DList.toList acc))
7979

80-
state1' :: DList.DList Char -> m ModuleName
80+
state1' :: DList.DList Char -> ParsecParser ModuleName
8181
state1' acc = do
8282
c <- ch
8383
case c of

Cabal-syntax/src/Distribution/PackageDescription/Configuration.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -108,7 +108,7 @@ simplifyWithSysParams os arch cinfo cond = (cond', flags)
108108
--
109109

110110
-- | Parse a configuration condition from a string.
111-
parseCondition :: CabalParsing m => m (Condition ConfVar)
111+
parseCondition :: ParsecParser (Condition ConfVar)
112112
parseCondition = condOr
113113
where
114114
condOr = sepByNonEmpty condAnd (oper "||") >>= return . foldl1 COr

0 commit comments

Comments
 (0)