Skip to content

Commit 093f2e6

Browse files
committed
ES: API changes of Megaparsec and QC
1 parent 50f02e0 commit 093f2e6

File tree

6 files changed

+13
-16
lines changed

6 files changed

+13
-16
lines changed

grin/src/Grin/ExtendedSyntax/Parse.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -14,5 +14,5 @@ import Grin.ExtendedSyntax.TypeEnvDefs
1414
import Grin.ExtendedSyntax.Parse.AST
1515
import Grin.ExtendedSyntax.Parse.TypeEnv
1616

17-
parseGrinWithTypes :: String -> Text -> Either (ParseError Char Void) (TypeEnv, Exp)
17+
parseGrinWithTypes :: String -> Text -> Either (ParseErrorBundle Text Void) (TypeEnv, Exp)
1818
parseGrinWithTypes filename content = (,) <$> parseMarkedTypeEnv filename content <*> parseGrin filename content

grin/src/Grin/ExtendedSyntax/Parse/AST.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -78,7 +78,7 @@ literal = (try $ LFloat . realToFrac <$> signedFloat) <|>
7878
(try $ LInt64 . fromIntegral <$> signedInteger) <|>
7979
(try $ LBool <$> (True <$ kw "#True" <|> False <$ kw "#False")) <|>
8080
(try $ LString <$> lexeme (C.char '#' *> quotedString)) <|>
81-
(try $ LChar <$> lexeme (C.string "#'" *> (escaped <|> anyChar) <* C.char '\''))
81+
(try $ LChar <$> lexeme (C.string "#'" *> (escaped <|> anySingle) <* C.char '\''))
8282

8383
satisfyM :: (a -> Bool) -> Parser a -> Parser a
8484
satisfyM pred parser = do
@@ -122,17 +122,17 @@ tyP =
122122
grinModule :: Parser Exp
123123
grinModule = Program <$> (concat <$> many (try externalBlock)) <*> many def <* sc <* eof
124124

125-
parseGrin :: String -> Text -> Either (ParseError Char Void) Exp
125+
parseGrin :: String -> Text -> Either (ParseErrorBundle Text Void) Exp
126126
parseGrin filename content = runParser grinModule filename (withoutTypeAnnots content)
127127

128128
parseProg :: Text -> Exp
129-
parseProg src = either (error . parseErrorPretty' src) id . parseGrin "" $ withoutTypeAnnots src
129+
parseProg src = either (error . errorBundlePretty) id . parseGrin "" $ withoutTypeAnnots src
130130

131131
parseDef :: Text -> Exp
132-
parseDef src = either (error . parseErrorPretty' src) id . runParser (def <* sc <* eof) "" $ withoutTypeAnnots src
132+
parseDef src = either (error . errorBundlePretty) id . runParser (def <* sc <* eof) "" $ withoutTypeAnnots src
133133

134134
parseExpr :: Text -> Exp
135-
parseExpr src = either (error . parseErrorPretty' src) id . runParser (expr pos1 <* sc <* eof) "" $ withoutTypeAnnots src
135+
parseExpr src = either (error . errorBundlePretty) id . runParser (expr pos1 <* sc <* eof) "" $ withoutTypeAnnots src
136136

137137

138138
withoutTypeAnnots :: Text -> Text

grin/src/Grin/ExtendedSyntax/Parse/Basic.hs

Lines changed: 2 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -95,9 +95,6 @@ set p = Set.fromList <$> bracedList p
9595
set1 :: Ord a => Parser a -> Parser (Set a)
9696
set1 p = Set.fromList <$> bracedList p
9797

98-
anySingle :: MonadParsec e s m => m (Token s)
99-
anySingle = satisfy (const True)
100-
10198
anySingleBut :: MonadParsec e s m => Token s -> m (Token s)
10299
anySingleBut t = satisfy (/= t)
103100

@@ -108,7 +105,7 @@ escaped :: Parser Char
108105
escaped = string "\\\"" >> pure '"'
109106

110107
quotedVar :: Parser Name
111-
quotedVar = packName <$ char '"' <*> someTill (escaped <|> anyChar) (char '"')
108+
quotedVar = packName <$ char '"' <*> someTill (escaped <|> anySingle) (char '"')
112109

113110
escapedStringChar :: Parser Char
114111
escapedStringChar =
@@ -123,7 +120,7 @@ escapedStringChar =
123120
(string "\\v" >> pure '\v')
124121

125122
quotedString :: Parser Text
126-
quotedString = fromString <$> (char '"' *> manyTill (escapedStringChar <|> anyChar) (char '"'))
123+
quotedString = fromString <$> (char '"' *> manyTill (escapedStringChar <|> anySingle) (char '"'))
127124

128125
simpleVar :: Parser Name
129126
simpleVar = (\c s -> packName $ c : s) <$> oneOf allowedInitial <*> many (alphaNumChar <|> oneOf allowedSpecial)

grin/src/Grin/ExtendedSyntax/Parse/TypeEnv.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -113,15 +113,15 @@ entriesToTypeEnv xs = flip execState emptyTypeEnv $ do
113113

114114
-- parses a type environment (without code)
115115
parseTypeEnv :: Text -> TypeEnv
116-
parseTypeEnv src = either (error . parseErrorPretty' src) id
116+
parseTypeEnv src = either (error . errorBundlePretty) id
117117
. runParser typeEnv ""
118118
$ src
119119

120120
-- parses type marked type annotations (even interleaved with code)
121121
parseMarkedTypeEnv' :: Text -> TypeEnv
122-
parseMarkedTypeEnv' src = either (error . parseErrorPretty' src) id $ parseMarkedTypeEnv "" src
122+
parseMarkedTypeEnv' src = either (error . errorBundlePretty) id $ parseMarkedTypeEnv "" src
123123

124-
parseMarkedTypeEnv :: String -> Text -> Either (ParseError Char Void) TypeEnv
124+
parseMarkedTypeEnv :: String -> Text -> Either (ParseErrorBundle Text Void) TypeEnv
125125
parseMarkedTypeEnv filename src = runParser markedTypeEnv filename (withoutCodeLines src)
126126

127127
withoutCodeLines :: Text -> Text

grin/src/Grin/ExtendedSyntax/TH.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -51,7 +51,7 @@ progConst = QuasiQuoter
5151
{ quoteExp = \input -> do
5252
let src = T.pack $ normalizeQQInput input
5353
case P.parseGrin "" src of
54-
Left e -> fail $ parseErrorPretty' src e
54+
Left e -> fail $ errorBundlePretty e
5555
Right p -> liftDataWithText p
5656
, quotePat = undefined
5757
, quoteType = undefined

grin/src/Test/ExtendedSyntax/Old/Test.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -941,7 +941,7 @@ instance Solve G.Prog where
941941
_ -> mzero
942942

943943
changed :: (Testable prop) => Exp -> Exp -> prop -> Property
944-
changed old new = cover (old /= new) 1 "Transformation has effect"
944+
changed old new = cover 1 (old /= new) "Transformation has effect"
945945

946946

947947
newtype SemanticallyCorrectProgram = SC { correctProg :: Exp }

0 commit comments

Comments
 (0)