Script 'mail_helper' called by obssrc Hello community, here is the log from the commit of package ghc-megaparsec for openSUSE:Factory checked in at 2025-07-31 17:45:35 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ Comparing /work/SRC/openSUSE:Factory/ghc-megaparsec (Old) and /work/SRC/openSUSE:Factory/.ghc-megaparsec.new.1944 (New) ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Package is "ghc-megaparsec" Thu Jul 31 17:45:35 2025 rev:22 rq:1296441 version:9.7.0 Changes: -------- --- /work/SRC/openSUSE:Factory/ghc-megaparsec/ghc-megaparsec.changes 2024-03-20 21:16:12.874133214 +0100 +++ /work/SRC/openSUSE:Factory/.ghc-megaparsec.new.1944/ghc-megaparsec.changes 2025-07-31 17:46:30.724930922 +0200 @@ -1,0 +2,17 @@ +Tue Nov 19 16:16:28 UTC 2024 - Peter Simons <psim...@suse.com> + +- Update megaparsec to version 9.7.0. + ## Megaparsec 9.7.0 + + * Implemented correct handling of wide Unicode characters in error messages. + To that end, a new module `Text.Megaparsec.Unicode` was introduced. [Issue + 370](https://github.com/mrkkrp/megaparsec/issues/370). + * Inlined `Applicative` operators `(<*)` and `(*>)`. [PR + 566](https://github.com/mrkkrp/megaparsec/pull/566). + * `many` and `some` of the `Alternative` instance of `ParsecT` are now more + efficient, since they use the monadic implementations under the hood. + [Issue 567](https://github.com/mrkkrp/megaparsec/issues/567). + * Added `Text.Megaparsec.Error.errorBundlePrettyForGhcPreProcessors`. [PR + 573](https://github.com/mrkkrp/megaparsec/pull/573). + +------------------------------------------------------------------- Old: ---- megaparsec-9.6.1.tar.gz New: ---- megaparsec-9.7.0.tar.gz ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ Other differences: ------------------ ++++++ ghc-megaparsec.spec ++++++ --- /var/tmp/diff_new_pack.UpoolG/_old 2025-07-31 17:46:31.368957689 +0200 +++ /var/tmp/diff_new_pack.UpoolG/_new 2025-07-31 17:46:31.368957689 +0200 @@ -1,7 +1,7 @@ # # spec file for package ghc-megaparsec # -# Copyright (c) 2023 SUSE LLC +# Copyright (c) 2024 SUSE LLC # # All modifications and additions to the file contributed by third parties # remain the property of their copyright owners, unless otherwise agreed @@ -19,13 +19,15 @@ %global pkg_name megaparsec %global pkgver %{pkg_name}-%{version} Name: ghc-%{pkg_name} -Version: 9.6.1 +Version: 9.7.0 Release: 0 Summary: Monadic parser combinators License: BSD-2-Clause URL: https://hackage.haskell.org/package/%{pkg_name} Source0: https://hackage.haskell.org/package/%{pkg_name}-%{version}/%{pkg_name}-%{version}.tar.gz BuildRequires: ghc-Cabal-devel +BuildRequires: ghc-array-devel +BuildRequires: ghc-array-prof BuildRequires: ghc-base-devel BuildRequires: ghc-base-prof BuildRequires: ghc-bytestring-devel ++++++ megaparsec-9.6.1.tar.gz -> megaparsec-9.7.0.tar.gz ++++++ diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/megaparsec-9.6.1/CHANGELOG.md new/megaparsec-9.7.0/CHANGELOG.md --- old/megaparsec-9.6.1/CHANGELOG.md 2001-09-09 03:46:40.000000000 +0200 +++ new/megaparsec-9.7.0/CHANGELOG.md 2001-09-09 03:46:40.000000000 +0200 @@ -1,5 +1,18 @@ *Megaparsec follows [SemVer](https://semver.org/).* +## Megaparsec 9.7.0 + +* Implemented correct handling of wide Unicode characters in error messages. + To that end, a new module `Text.Megaparsec.Unicode` was introduced. [Issue + 370](https://github.com/mrkkrp/megaparsec/issues/370). +* Inlined `Applicative` operators `(<*)` and `(*>)`. [PR + 566](https://github.com/mrkkrp/megaparsec/pull/566). +* `many` and `some` of the `Alternative` instance of `ParsecT` are now more + efficient, since they use the monadic implementations under the hood. + [Issue 567](https://github.com/mrkkrp/megaparsec/issues/567). +* Added `Text.Megaparsec.Error.errorBundlePrettyForGhcPreProcessors`. [PR + 573](https://github.com/mrkkrp/megaparsec/pull/573). + ## Megaparsec 9.6.1 * Exposed `Text.Megaparsec.State`, so that the new functions (`initialState` diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/megaparsec-9.6.1/Text/Megaparsec/Error.hs new/megaparsec-9.7.0/Text/Megaparsec/Error.hs --- old/megaparsec-9.6.1/Text/Megaparsec/Error.hs 2001-09-09 03:46:40.000000000 +0200 +++ new/megaparsec-9.7.0/Text/Megaparsec/Error.hs 2001-09-09 03:46:40.000000000 +0200 @@ -41,12 +41,15 @@ -- * Pretty-printing ShowErrorComponent (..), errorBundlePretty, + errorBundlePrettyForGhcPreProcessors, + errorBundlePrettyWith, parseErrorPretty, parseErrorTextPretty, showErrorItem, ) where +import Control.Arrow ((>>>)) import Control.DeepSeq import Control.Exception import Control.Monad.State.Strict @@ -64,6 +67,7 @@ import Text.Megaparsec.Pos import Text.Megaparsec.State import Text.Megaparsec.Stream +import qualified Text.Megaparsec.Unicode as Unicode ---------------------------------------------------------------------------- -- Parse error type @@ -348,24 +352,24 @@ showErrorComponent = absurd -- | Pretty-print a 'ParseErrorBundle'. All 'ParseError's in the bundle will --- be pretty-printed in order together with the corresponding offending --- lines by doing a single pass over the input stream. The rendered 'String' --- always ends with a newline. +-- be pretty-printed in order, by applying a provided format function, with +-- a single pass over the input stream. -- --- @since 7.0.0 -errorBundlePretty :: +-- @since 9.7.0 +errorBundlePrettyWith :: forall s e. ( VisualStream s, - TraversableStream s, - ShowErrorComponent e + TraversableStream s ) => + -- | Format function for a single 'ParseError' + (Maybe String -> SourcePos -> ParseError s e -> String) -> -- | Parse error bundle to display ParseErrorBundle s e -> -- | Textual rendition of the bundle String -errorBundlePretty ParseErrorBundle {..} = +errorBundlePrettyWith format ParseErrorBundle {..} = let (r, _) = foldl f (id, bundlePosState) bundleErrors - in drop 1 (r "") + in r "" where f :: (ShowS, PosState s) -> @@ -375,6 +379,33 @@ where (msline, pst') = reachOffset (errorOffset e) pst epos = pstateSourcePos pst' + outChunk = format msline epos e + +-- | Pretty-print a 'ParseErrorBundle'. All 'ParseError's in the bundle will +-- be pretty-printed in order together with the corresponding offending +-- lines by doing a single pass over the input stream. The rendered 'String' +-- always ends with a newline. +-- +-- @since 7.0.0 +errorBundlePretty :: + forall s e. + ( VisualStream s, + TraversableStream s, + ShowErrorComponent e + ) => + -- | Parse error bundle to display + ParseErrorBundle s e -> + -- | Textual rendition of the bundle + String +errorBundlePretty = drop 1 . errorBundlePrettyWith format + where + format :: + Maybe String -> + SourcePos -> + ParseError s e -> + String + format msline epos e = outChunk + where outChunk = "\n" <> sourcePosPretty epos @@ -397,7 +428,7 @@ lineNumber = (show . unPos . sourceLine) epos padding = replicate (length lineNumber + 1) ' ' rpshift = unPos (sourceColumn epos) - 1 - slineLen = length sline + slineLen = Unicode.stringLength sline in padding <> "|\n" <> lineNumber @@ -417,6 +448,41 @@ FancyError _ xs -> E.foldl' (\a b -> max a (errorFancyLength b)) 1 xs +-- | Pretty-print a 'ParseErrorBundle'. All 'ParseError's in the bundle will +-- be pretty-printed in order by doing a single pass over the input stream. +-- +-- The rendered format is suitable for custom GHC pre-processors (as can be +-- specified with -F -pgmF). +-- +-- @since 9.7.0 +errorBundlePrettyForGhcPreProcessors :: + forall s e. + ( VisualStream s, + TraversableStream s, + ShowErrorComponent e + ) => + -- | Parse error bundle to display + ParseErrorBundle s e -> + -- | Textual rendition of the bundle + String +errorBundlePrettyForGhcPreProcessors = errorBundlePrettyWith format + where + format :: + Maybe String -> + SourcePos -> + ParseError s e -> + String + format _msline epos e = + sourcePosPretty epos + <> ":" + <> indent (parseErrorTextPretty e) + + indent :: String -> String + indent = + lines >>> \case + [err] -> err + err -> intercalate "\n" $ map (" " <>) err + -- | Pretty-print a 'ParseError'. The rendered 'String' always ends with a -- newline. -- diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/megaparsec-9.6.1/Text/Megaparsec/Internal.hs new/megaparsec-9.7.0/Text/Megaparsec/Internal.hs --- old/megaparsec-9.6.1/Text/Megaparsec/Internal.hs 2001-09-09 03:46:40.000000000 +0200 +++ new/megaparsec-9.7.0/Text/Megaparsec/Internal.hs 2001-09-09 03:46:40.000000000 +0200 @@ -46,6 +46,7 @@ import Control.Applicative import Control.Monad +import qualified Control.Monad.Combinators import Control.Monad.Cont.Class import Control.Monad.Error.Class import qualified Control.Monad.Fail as Fail @@ -174,7 +175,9 @@ pure = pPure (<*>) = pAp p1 *> p2 = p1 `pBind` const p2 + {-# INLINE (*>) #-} p1 <* p2 = do x1 <- p1; void p2; return x1 + {-# INLINE (<*) #-} pPure :: (Stream s) => a -> ParsecT e s m a pPure x = ParsecT $ \s _ _ eok _ -> eok x s mempty @@ -209,6 +212,8 @@ instance (Ord e, Stream s) => Alternative (ParsecT e s m) where empty = mzero (<|>) = mplus + many = Control.Monad.Combinators.many + some = Control.Monad.Combinators.some -- | 'return' returns a parser that __succeeds__ without consuming input. instance (Stream s) => Monad (ParsecT e s m) where @@ -329,7 +334,7 @@ -- __Note__: strictly speaking, this instance is unlawful. The right -- identity law does not hold, e.g. in general this is not true: -- --- > v >> mzero = mero +-- > v >> mzero = mzero -- -- However the following holds: -- diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/megaparsec-9.6.1/Text/Megaparsec/Stream.hs new/megaparsec-9.7.0/Text/Megaparsec/Stream.hs --- old/megaparsec-9.6.1/Text/Megaparsec/Stream.hs 2001-09-09 03:46:40.000000000 +0200 +++ new/megaparsec-9.7.0/Text/Megaparsec/Stream.hs 2001-09-09 03:46:40.000000000 +0200 @@ -52,6 +52,7 @@ import Data.Word (Word8) import Text.Megaparsec.Pos import Text.Megaparsec.State +import qualified Text.Megaparsec.Unicode as Unicode -- | Type class for inputs that can be consumed by the library. -- @@ -426,6 +427,7 @@ instance VisualStream String where showTokens Proxy = stringPretty + tokensLength Proxy = Unicode.stringLength instance VisualStream B.ByteString where showTokens Proxy = stringPretty . fmap (chr . fromIntegral) @@ -435,9 +437,11 @@ instance VisualStream T.Text where showTokens Proxy = stringPretty + tokensLength Proxy = Unicode.stringLength instance VisualStream TL.Text where showTokens Proxy = stringPretty + tokensLength Proxy = Unicode.stringLength -- | Type class for inputs that can also be used for error reporting. -- @@ -510,37 +514,37 @@ instance TraversableStream String where -- NOTE Do not eta-reduce these (breaks inlining) reachOffset o pst = - reachOffset' splitAt foldl' id id ('\n', '\t') o pst + reachOffset' splitAt foldl' id id ('\n', '\t') charInc o pst reachOffsetNoLine o pst = - reachOffsetNoLine' splitAt foldl' ('\n', '\t') o pst + reachOffsetNoLine' splitAt foldl' ('\n', '\t') charInc o pst instance TraversableStream B.ByteString where -- NOTE Do not eta-reduce these (breaks inlining) reachOffset o pst = - reachOffset' B.splitAt B.foldl' B8.unpack (chr . fromIntegral) (10, 9) o pst + reachOffset' B.splitAt B.foldl' B8.unpack (chr . fromIntegral) (10, 9) byteInc o pst reachOffsetNoLine o pst = - reachOffsetNoLine' B.splitAt B.foldl' (10, 9) o pst + reachOffsetNoLine' B.splitAt B.foldl' (10, 9) byteInc o pst instance TraversableStream BL.ByteString where -- NOTE Do not eta-reduce these (breaks inlining) reachOffset o pst = - reachOffset' splitAtBL BL.foldl' BL8.unpack (chr . fromIntegral) (10, 9) o pst + reachOffset' splitAtBL BL.foldl' BL8.unpack (chr . fromIntegral) (10, 9) byteInc o pst reachOffsetNoLine o pst = - reachOffsetNoLine' splitAtBL BL.foldl' (10, 9) o pst + reachOffsetNoLine' splitAtBL BL.foldl' (10, 9) byteInc o pst instance TraversableStream T.Text where -- NOTE Do not eta-reduce (breaks inlining of reachOffset'). reachOffset o pst = - reachOffset' T.splitAt T.foldl' T.unpack id ('\n', '\t') o pst + reachOffset' T.splitAt T.foldl' T.unpack id ('\n', '\t') charInc o pst reachOffsetNoLine o pst = - reachOffsetNoLine' T.splitAt T.foldl' ('\n', '\t') o pst + reachOffsetNoLine' T.splitAt T.foldl' ('\n', '\t') charInc o pst instance TraversableStream TL.Text where -- NOTE Do not eta-reduce (breaks inlining of reachOffset'). reachOffset o pst = - reachOffset' splitAtTL TL.foldl' TL.unpack id ('\n', '\t') o pst + reachOffset' splitAtTL TL.foldl' TL.unpack id ('\n', '\t') charInc o pst reachOffsetNoLine o pst = - reachOffsetNoLine' splitAtTL TL.foldl' ('\n', '\t') o pst + reachOffsetNoLine' splitAtTL TL.foldl' ('\n', '\t') charInc o pst ---------------------------------------------------------------------------- -- Helpers @@ -564,6 +568,8 @@ (Token s -> Char) -> -- | Newline token and tab token (Token s, Token s) -> + -- | Increment in column position for a token + (Token s -> Pos) -> -- | Offset to reach Int -> -- | Initial 'PosState' to use @@ -576,6 +582,7 @@ fromToks fromTok (newlineTok, tabTok) + columnIncrement o PosState {..} = ( Just $ case expandTab pstateTabWidth @@ -624,7 +631,7 @@ (g . (fromTok ch :)) | otherwise -> St - (SourcePos n l (c <> pos1)) + (SourcePos n l (c <> columnIncrement ch)) (g . (fromTok ch :)) {-# INLINE reachOffset' #-} @@ -639,6 +646,8 @@ -- | Newline token and tab token (Token s, Token s) -> -- | Offset to reach + -- | Increment in column position for a token + (Token s -> Pos) -> Int -> -- | Initial 'PosState' to use PosState s -> @@ -648,6 +657,7 @@ splitAt' foldl'' (newlineTok, tabTok) + columnIncrement o PosState {..} = ( PosState @@ -670,7 +680,7 @@ | ch == tabTok -> SourcePos n l (mkPos $ c' + w - ((c' - 1) `rem` w)) | otherwise -> - SourcePos n l (c <> pos1) + SourcePos n l (c <> columnIncrement ch) {-# INLINE reachOffsetNoLine' #-} -- | Like 'BL.splitAt' but accepts the index as an 'Int'. @@ -753,3 +763,13 @@ go !i 0 (x : xs) = x : go (i + 1) 0 xs go !i n xs = ' ' : go (i + 1) (n - 1) xs w = unPos w' + +-- | Return increment in column position that corresponds to the given +-- 'Char'. +charInc :: Char -> Pos +charInc ch = if Unicode.isWideChar ch then pos1 <> pos1 else pos1 + +-- | Return increment in column position that corresponds to the given +-- 'Word8'. +byteInc :: Word8 -> Pos +byteInc _ = pos1 diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/megaparsec-9.6.1/Text/Megaparsec/Unicode.hs new/megaparsec-9.7.0/Text/Megaparsec/Unicode.hs --- old/megaparsec-9.6.1/Text/Megaparsec/Unicode.hs 1970-01-01 01:00:00.000000000 +0100 +++ new/megaparsec-9.7.0/Text/Megaparsec/Unicode.hs 2001-09-09 03:46:40.000000000 +0200 @@ -0,0 +1,180 @@ +{-# LANGUAGE Safe #-} + +-- | +-- Module : Text.Megaparsec.Unicode +-- Copyright : © 2024–present Megaparsec contributors +-- License : FreeBSD +-- +-- Maintainer : Mark Karpov <markkarpo...@gmail.com> +-- Stability : experimental +-- Portability : portable +-- +-- Utility functions for working with Unicode. +-- +-- @since 9.7.0 +module Text.Megaparsec.Unicode + ( stringLength, + charLength, + isWideChar, + ) +where + +import Data.Array (Array, bounds, listArray, (!)) +import Data.Char (ord) + +-- | Calculate length of a string taking into account the fact that certain +-- 'Char's may span more than 1 column. +-- +-- @since 9.7.0 +stringLength :: (Traversable t) => t Char -> Int +stringLength = sum . fmap charLength + +-- | Return length of an individual 'Char'. +-- +-- @since 9.7.0 +charLength :: Char -> Int +charLength ch = if isWideChar ch then 2 else 1 + +-- | Determine whether the given 'Char' is “wide”, that is, whether it spans +-- 2 columns instead of one. +-- +-- @since 9.7.0 +isWideChar :: Char -> Bool +isWideChar c = go (bounds wideCharRanges) + where + go (lo, hi) + | hi < lo = False + | a <= n && n <= b = True + | n < a = go (lo, pred mid) + | otherwise = go (succ mid, hi) + where + mid = (lo + hi) `div` 2 + (a, b) = wideCharRanges ! mid + n = ord c + +-- | Wide character ranges. +wideCharRanges :: Array Int (Int, Int) +wideCharRanges = + listArray + (0, 118) + [ (0x001100, 0x00115f), + (0x00231a, 0x00231b), + (0x002329, 0x00232a), + (0x0023e9, 0x0023ec), + (0x0023f0, 0x0023f0), + (0x0023f3, 0x0023f3), + (0x0025fd, 0x0025fe), + (0x002614, 0x002615), + (0x002648, 0x002653), + (0x00267f, 0x00267f), + (0x002693, 0x002693), + (0x0026a1, 0x0026a1), + (0x0026aa, 0x0026ab), + (0x0026bd, 0x0026be), + (0x0026c4, 0x0026c5), + (0x0026ce, 0x0026ce), + (0x0026d4, 0x0026d4), + (0x0026ea, 0x0026ea), + (0x0026f2, 0x0026f3), + (0x0026f5, 0x0026f5), + (0x0026fa, 0x0026fa), + (0x0026fd, 0x0026fd), + (0x002705, 0x002705), + (0x00270a, 0x00270b), + (0x002728, 0x002728), + (0x00274c, 0x00274c), + (0x00274e, 0x00274e), + (0x002753, 0x002755), + (0x002757, 0x002757), + (0x002795, 0x002797), + (0x0027b0, 0x0027b0), + (0x0027bf, 0x0027bf), + (0x002b1b, 0x002b1c), + (0x002b50, 0x002b50), + (0x002b55, 0x002b55), + (0x002e80, 0x002e99), + (0x002e9b, 0x002ef3), + (0x002f00, 0x002fd5), + (0x002ff0, 0x002ffb), + (0x003000, 0x00303e), + (0x003041, 0x003096), + (0x003099, 0x0030ff), + (0x003105, 0x00312f), + (0x003131, 0x00318e), + (0x003190, 0x0031ba), + (0x0031c0, 0x0031e3), + (0x0031f0, 0x00321e), + (0x003220, 0x003247), + (0x003250, 0x004db5), + (0x004e00, 0x009fef), + (0x00a000, 0x00a48c), + (0x00a490, 0x00a4c6), + (0x00a960, 0x00a97c), + (0x00ac00, 0x00d7a3), + (0x00f900, 0x00fa6d), + (0x00fa70, 0x00fad9), + (0x00fe10, 0x00fe19), + (0x00fe30, 0x00fe52), + (0x00fe54, 0x00fe66), + (0x00fe68, 0x00fe6b), + (0x00ff01, 0x00ff60), + (0x00ffe0, 0x00ffe6), + (0x016fe0, 0x016fe3), + (0x017000, 0x0187f7), + (0x018800, 0x018af2), + (0x01b000, 0x01b11e), + (0x01b150, 0x01b152), + (0x01b164, 0x01b167), + (0x01b170, 0x01b2fb), + (0x01f004, 0x01f004), + (0x01f0cf, 0x01f0cf), + (0x01f18e, 0x01f18e), + (0x01f191, 0x01f19a), + (0x01f200, 0x01f202), + (0x01f210, 0x01f23b), + (0x01f240, 0x01f248), + (0x01f250, 0x01f251), + (0x01f260, 0x01f265), + (0x01f300, 0x01f320), + (0x01f32d, 0x01f335), + (0x01f337, 0x01f37c), + (0x01f37e, 0x01f393), + (0x01f3a0, 0x01f3ca), + (0x01f3cf, 0x01f3d3), + (0x01f3e0, 0x01f3f0), + (0x01f3f4, 0x01f3f4), + (0x01f3f8, 0x01f43e), + (0x01f440, 0x01f440), + (0x01f442, 0x01f4fc), + (0x01f4ff, 0x01f53d), + (0x01f54b, 0x01f54e), + (0x01f550, 0x01f567), + (0x01f57a, 0x01f57a), + (0x01f595, 0x01f596), + (0x01f5a4, 0x01f5a4), + (0x01f5fb, 0x01f64f), + (0x01f680, 0x01f6c5), + (0x01f6cc, 0x01f6cc), + (0x01f6d0, 0x01f6d2), + (0x01f6d5, 0x01f6d5), + (0x01f6eb, 0x01f6ec), + (0x01f6f4, 0x01f6fa), + (0x01f7e0, 0x01f7eb), + (0x01f90d, 0x01f971), + (0x01f973, 0x01f976), + (0x01f97a, 0x01f9a2), + (0x01f9a5, 0x01f9aa), + (0x01f9ae, 0x01f9ca), + (0x01f9cd, 0x01f9ff), + (0x01fa70, 0x01fa73), + (0x01fa78, 0x01fa7a), + (0x01fa80, 0x01fa82), + (0x01fa90, 0x01fa95), + (0x020000, 0x02a6d6), + (0x02a700, 0x02b734), + (0x02b740, 0x02b81d), + (0x02b820, 0x02cea1), + (0x02ceb0, 0x02ebe0), + (0x02f800, 0x02fa1d) + ] +{-# NOINLINE wideCharRanges #-} diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/megaparsec-9.6.1/Text/Megaparsec.hs new/megaparsec-9.7.0/Text/Megaparsec.hs --- old/megaparsec-9.6.1/Text/Megaparsec.hs 2001-09-09 03:46:40.000000000 +0200 +++ new/megaparsec-9.7.0/Text/Megaparsec.hs 2001-09-09 03:46:40.000000000 +0200 @@ -130,12 +130,16 @@ -- -- Note that we re-export monadic combinators from -- "Control.Monad.Combinators" because these are more efficient than --- 'Applicative'-based ones. Thus 'many' and 'some' may clash with the +-- 'Applicative'-based ones (†). Thus 'many' and 'some' may clash with the -- functions from "Control.Applicative". You need to hide the functions like -- this: -- -- > import Control.Applicative hiding (many, some) -- +-- † As of Megaparsec 9.7.0 'Control.Applicative.many' and +-- 'Control.Applicative.some' are as efficient as their monadic +-- counterparts. +-- -- Also note that you can import "Control.Monad.Combinators.NonEmpty" if you -- wish that combinators like 'some' return 'NonEmpty' lists. The module -- lives in the @parser-combinators@ package (you need at least version @@ -516,7 +520,7 @@ -- | Collection of matching tokens f (Token s) -> m (Token s) -oneOf cs = satisfy (`elem` cs) +oneOf cs = satisfy (\x -> elem x cs) {-# INLINE oneOf #-} -- | As the dual of 'oneOf', @'noneOf' ts@ succeeds if the current token @@ -538,7 +542,7 @@ -- | Collection of taken we should not match f (Token s) -> m (Token s) -noneOf cs = satisfy (`notElem` cs) +noneOf cs = satisfy (\x -> notElem x cs) {-# INLINE noneOf #-} -- | @'chunk' chk@ only matches the chunk @chk@. diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/megaparsec-9.6.1/megaparsec.cabal new/megaparsec-9.7.0/megaparsec.cabal --- old/megaparsec-9.6.1/megaparsec.cabal 2001-09-09 03:46:40.000000000 +0200 +++ new/megaparsec-9.7.0/megaparsec.cabal 2001-09-09 03:46:40.000000000 +0200 @@ -1,6 +1,6 @@ cabal-version: 2.4 name: megaparsec -version: 9.6.1 +version: 9.7.0 license: BSD-2-Clause license-file: LICENSE.md maintainer: Mark Karpov <markkarpo...@gmail.com> @@ -9,7 +9,7 @@ Paolo Martini <pa...@nemail.it>, Daan Leijen <d...@microsoft.com> -tested-with: ghc ==9.4.7 ghc ==9.6.3 ghc ==9.8.1 +tested-with: ghc ==9.6.3 ghc ==9.8.2 ghc ==9.10.1 homepage: https://github.com/mrkkrp/megaparsec bug-reports: https://github.com/mrkkrp/megaparsec/issues synopsis: Monadic parser combinators @@ -48,6 +48,7 @@ Text.Megaparsec.Pos Text.Megaparsec.State Text.Megaparsec.Stream + Text.Megaparsec.Unicode other-modules: Text.Megaparsec.Class @@ -56,6 +57,7 @@ default-language: Haskell2010 build-depends: + array >=0.5.3 && <0.6, base >=4.15 && <5, bytestring >=0.2 && <0.13, case-insensitive >=1.2 && <1.3, @@ -70,7 +72,7 @@ if flag(dev) ghc-options: -Wall -Werror -Wredundant-constraints -Wpartial-fields - -Wunused-packages + -Wunused-packages -Wno-unused-imports else ghc-options: -O2 -Wall