Script 'mail_helper' called by obssrc Hello community, here is the log from the commit of package ghc-commonmark for openSUSE:Factory checked in at 2022-08-01 21:28:36 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ Comparing /work/SRC/openSUSE:Factory/ghc-commonmark (Old) and /work/SRC/openSUSE:Factory/.ghc-commonmark.new.1533 (New) ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ Package is "ghc-commonmark" Mon Aug 1 21:28:36 2022 rev:11 rq:985805 version:0.2.2 Changes: -------- --- /work/SRC/openSUSE:Factory/ghc-commonmark/ghc-commonmark.changes 2021-11-11 21:36:28.604891047 +0100 +++ /work/SRC/openSUSE:Factory/.ghc-commonmark.new.1533/ghc-commonmark.changes 2022-08-01 21:28:37.905352267 +0200 @@ -1,0 +2,21 @@ +Sat Apr 2 21:25:44 UTC 2022 - Peter Simons <psimons@suse.com> + +- Update commonmark to version 0.2.2. + ## 0.2.2 + + * Blocks: export `getParentListType` [API change]. + * Require unicode-data >= 0.3. + * Change `mkFormattingSpecMap` so it integrates different + FormattingSpecs that use the same character (#87). Otherwise + we have problems if you have one formatting spec that + reacts to single delimiters and another that reacts to + pairs; if the first fails to match, the fallback behavior + is produced and the second never matches. + * Use unicode-data's faster versions of Data.Char functions. + This speeds up benchmarks for tokenize considerably; little difference + in other benchmarks. unicode-data is already a transitive dependency, + via unicode-transforms. + * Increase strictness in tokenize/go. + * Remove legacy cpp needed to support ghc < 8.4. + +------------------------------------------------------------------- Old: ---- commonmark-0.2.1.1.tar.gz New: ---- commonmark-0.2.2.tar.gz ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ Other differences: ------------------ ++++++ ghc-commonmark.spec ++++++ --- /var/tmp/diff_new_pack.3NfyqK/_old 2022-08-01 21:28:38.381353632 +0200 +++ /var/tmp/diff_new_pack.3NfyqK/_new 2022-08-01 21:28:38.385353644 +0200 @@ -1,7 +1,7 @@ # # spec file for package ghc-commonmark # -# Copyright (c) 2021 SUSE LLC +# Copyright (c) 2022 SUSE LLC # # All modifications and additions to the file contributed by third parties # remain the property of their copyright owners, unless otherwise agreed @@ -19,7 +19,7 @@ %global pkg_name commonmark %bcond_with tests Name: ghc-%{pkg_name} -Version: 0.2.1.1 +Version: 0.2.2 Release: 0 Summary: Pure Haskell commonmark parser License: BSD-3-Clause @@ -32,6 +32,7 @@ BuildRequires: ghc-rpm-macros BuildRequires: ghc-text-devel BuildRequires: ghc-transformers-devel +BuildRequires: ghc-unicode-data-devel BuildRequires: ghc-unicode-transforms-devel ExcludeArch: %{ix86} %if %{with tests} ++++++ commonmark-0.2.1.1.tar.gz -> commonmark-0.2.2.tar.gz ++++++ diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/commonmark-0.2.1.1/benchmark/benchmark.hs new/commonmark-0.2.2/benchmark/benchmark.hs --- old/commonmark-0.2.1.1/benchmark/benchmark.hs 2021-07-21 20:44:47.000000000 +0200 +++ new/commonmark-0.2.2/benchmark/benchmark.hs 2022-01-12 04:38:14.000000000 +0100 @@ -7,9 +7,6 @@ import Commonmark import qualified Data.Text as T import qualified Data.Text.IO as TIO -#if !MIN_VERSION_base(4,11,0) -import Data.Monoid -#endif main :: IO () main = do diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/commonmark-0.2.1.1/changelog.md new/commonmark-0.2.2/changelog.md --- old/commonmark-0.2.1.1/changelog.md 2021-10-23 02:01:08.000000000 +0200 +++ new/commonmark-0.2.2/changelog.md 2022-04-02 22:50:29.000000000 +0200 @@ -1,5 +1,23 @@ # Changelog for commonmark +## 0.2.2 + + * Blocks: export `getParentListType` [API change]. + * Require unicode-data >= 0.3. + * Change `mkFormattingSpecMap` so it integrates different + FormattingSpecs that use the same character (#87). Otherwise + we have problems if you have one formatting spec that + reacts to single delimiters and another that reacts to + pairs; if the first fails to match, the fallback behavior + is produced and the second never matches. + * Use unicode-data's faster versions of Data.Char functions. + This speeds up benchmarks for tokenize considerably; little difference + in other benchmarks. unicode-data is already a transitive dependency, + via unicode-transforms. + * Increase strictness in tokenize/go. + * Remove legacy cpp needed to support ghc < 8.4. + + ## 0.2.1.1 * Fix bug in `prettyShow` for `SourceRange` (#80). diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/commonmark-0.2.1.1/commonmark.cabal new/commonmark-0.2.2/commonmark.cabal --- old/commonmark-0.2.1.1/commonmark.cabal 2021-10-23 02:01:15.000000000 +0200 +++ new/commonmark-0.2.2/commonmark.cabal 2022-04-02 22:50:38.000000000 +0200 @@ -1,6 +1,6 @@ cabal-version: 2.2 name: commonmark -version: 0.2.1.1 +version: 0.2.2 synopsis: Pure Haskell commonmark parser. description: This library provides the core data types and functions @@ -61,6 +61,7 @@ , transformers , parsec , unicode-transforms + , unicode-data >= 0.3 exposed-modules: Commonmark Commonmark.Parser diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/commonmark-0.2.1.1/src/Commonmark/Blocks.hs new/commonmark-0.2.2/src/Commonmark/Blocks.hs --- old/commonmark-0.2.1.1/src/Commonmark/Blocks.hs 2021-10-13 01:35:36.000000000 +0200 +++ new/commonmark-0.2.2/src/Commonmark/Blocks.hs 2022-02-28 06:37:07.000000000 +0100 @@ -1,4 +1,3 @@ -{-# LANGUAGE CPP #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE FlexibleInstances #-} @@ -31,6 +30,7 @@ , linkReferenceDef , renderChildren , reverseSubforests + , getParentListType -- * BlockSpecs , docSpec , indentedCodeSpec @@ -61,10 +61,8 @@ when) import Control.Monad.Trans.Class (lift) import Data.Foldable (foldrM) -#if !MIN_VERSION_base(4,11,0) -import Data.Monoid -#endif -import Data.Char (isAsciiUpper, isDigit, isSpace) +import Unicode.Char (isAsciiUpper, isDigit) +import Unicode.Char.General.Compat (isSpace) import Data.Dynamic import Data.Text (Text) import qualified Data.Map.Strict as M @@ -380,6 +378,18 @@ , listItemBlanksAtEnd :: !Bool } deriving (Show, Eq) +-- | Get type of the enclosing List block. If the parent isn't +-- a List block, return Nothing. +getParentListType :: Monad m => BlockParser m il bl (Maybe ListType) +getParentListType = do + (cur:_) <- nodeStack <$> getState + if blockType (bspec cur) == "List" + then do + let ListData lt _ = fromDyn (blockData (rootLabel cur)) + (ListData (BulletList '*') TightList) + return $ Just lt + else return Nothing + runInlineParser :: Monad m => [Tok] -> BlockParser m il bl il @@ -811,9 +821,23 @@ notFollowedBy blankLine let curdata = fromDyn (blockData (rootLabel cur)) (ListData (BulletList '*') TightList) + let isSingleRomanDigit n = n == 1 || n == 5 || n == 10 || + n == 50 || n == 100 || n == 500 || + n == 1000 + let matchesOrderedListStyle + (OrderedList _s1 e1 d1) (OrderedList s2 e2 d2) = + d1 == d2 && -- roman can match alphabetic if single-digit: + case (e1, e2) of + (LowerAlpha, LowerRoman) -> isSingleRomanDigit s2 + (UpperAlpha, UpperRoman) -> isSingleRomanDigit s2 + (LowerRoman, LowerAlpha) -> isSingleRomanDigit s2 + (UpperRoman, UpperAlpha) -> isSingleRomanDigit s2 + _ -> e1 == e2 + matchesOrderedListStyle _ _ = False + let matchesList (BulletList c) (BulletList d) = c == d - matchesList (OrderedList _ e1 d1) - (OrderedList _ e2 d2) = e1 == e2 && d1 == d2 + matchesList x@OrderedList{} + y@OrderedList{} = matchesOrderedListStyle x y matchesList _ _ = False case blockType (bspec cur) of "List" | listType curdata `matchesList` diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/commonmark-0.2.1.1/src/Commonmark/Entity.hs new/commonmark-0.2.2/src/Commonmark/Entity.hs --- old/commonmark-0.2.1.1/src/Commonmark/Entity.hs 2020-03-29 20:21:58.000000000 +0200 +++ new/commonmark-0.2.2/src/Commonmark/Entity.hs 2022-02-28 06:37:07.000000000 +0100 @@ -1,4 +1,3 @@ -{-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} -- This code for lookupEntity is modified from Text.HTML.TagSoup.Entity -- (C) 2006--2018 Neil Mitchell, released under the BSD-3 license @@ -20,11 +19,8 @@ import Data.Text (Text) import qualified Data.Text.Read as TR import Control.Monad (guard, mzero) -import Data.Char (isDigit, isHexDigit, chr) +import Unicode.Char (chr, isDigit, isHexDigit) import Data.Maybe (isJust) -#if !MIN_VERSION_base(4,11,0) -import Data.Semigroup (Semigroup(..)) -#endif -- | Lookup an entity, using 'lookupNumericEntity' if it starts with -- @#@ and 'lookupNamedEntity' otherwise diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/commonmark-0.2.1.1/src/Commonmark/Html.hs new/commonmark-0.2.2/src/Commonmark/Html.hs --- old/commonmark-0.2.1.1/src/Commonmark/Html.hs 2021-07-21 20:44:47.000000000 +0200 +++ new/commonmark-0.2.2/src/Commonmark/Html.hs 2022-04-01 03:59:54.000000000 +0200 @@ -1,4 +1,3 @@ -{-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances #-} @@ -28,11 +27,9 @@ import qualified Data.ByteString.Char8 as B import qualified Data.Set as Set import Text.Printf (printf) -import Data.Char (ord, isAlphaNum, isAscii, isSpace) +import Unicode.Char (ord, isAlphaNum, isAscii) +import Unicode.Char.General.Compat (isSpace) import Data.Maybe (fromMaybe) -#if !MIN_VERSION_base(4,11,0) -import Data.Semigroup -#endif data ElementType = InlineElement diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/commonmark-0.2.1.1/src/Commonmark/Inlines.hs new/commonmark-0.2.2/src/Commonmark/Inlines.hs --- old/commonmark-0.2.1.1/src/Commonmark/Inlines.hs 2021-07-21 20:44:47.000000000 +0200 +++ new/commonmark-0.2.2/src/Commonmark/Inlines.hs 2022-04-01 03:59:54.000000000 +0200 @@ -1,5 +1,4 @@ {-# LANGUAGE RankNTypes #-} -{-# LANGUAGE CPP #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE BangPatterns #-} {-# LANGUAGE OverloadedStrings #-} @@ -35,20 +34,27 @@ import Commonmark.Tag (htmlTag, Enders, defaultEnders) import Commonmark.Tokens -import Commonmark.TokParsers +import Commonmark.TokParsers + ( lineEnd, + noneOfToks, + whitespace, + oneOfToks, + satisfyWord, + withRaw, + symbol, + satisfyTok, + anyTok, + hasType ) import Commonmark.ReferenceMap import Commonmark.Types -import Control.Monad (guard, mzero) +import Control.Monad (guard, mzero, mplus) import Control.Monad.Trans.State.Strict import Data.List (foldl') -import Data.Char (isAscii, isLetter) +import Unicode.Char (isAscii, isAlpha) import qualified Data.IntMap.Strict as IntMap import qualified Data.Map.Strict as M import Data.Maybe (isJust, mapMaybe, listToMaybe) import qualified Data.Set as Set -#if !MIN_VERSION_base(4,11,0) -import Data.Monoid ((<>)) -#endif import Data.Text (Text) import qualified Data.Text as T import Commonmark.Entity (unEntity, charEntity, numEntity) @@ -242,7 +248,19 @@ ] mkFormattingSpecMap :: [FormattingSpec il] -> FormattingSpecMap il -mkFormattingSpecMap fs = M.fromList [(formattingDelimChar s, s) | s <- fs] +mkFormattingSpecMap fs = + foldr go mempty fs + where + go s = + M.alter (\case -- combine FormattingSpecs with same character (see #87) + Nothing -> Just s + Just s' -> Just + s' { formattingSingleMatch = + formattingSingleMatch s' `mplus` formattingSingleMatch s + , formattingDoubleMatch = + formattingDoubleMatch s' `mplus` formattingDoubleMatch s + }) + (formattingDelimChar s) --- Bracketed specs: @@ -493,7 +511,7 @@ pScheme = do t <- satisfyWord (\t -> case T.uncons t of Nothing -> False - Just (c,rest) -> isAscii c && isLetter c && + Just (c,rest) -> isAscii c && isAlpha c && T.all isAscii rest) ts <- many $ oneOfToks [WordChars, Symbol '+', Symbol '.', Symbol '-'] let s = untokenize (t:ts) diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/commonmark-0.2.1.1/src/Commonmark/SourceMap.hs new/commonmark-0.2.2/src/Commonmark/SourceMap.hs --- old/commonmark-0.2.1.1/src/Commonmark/SourceMap.hs 2020-03-29 20:21:58.000000000 +0200 +++ new/commonmark-0.2.2/src/Commonmark/SourceMap.hs 2022-01-12 04:38:14.000000000 +0100 @@ -1,4 +1,3 @@ -{-# LANGUAGE CPP #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE OverloadedStrings #-} @@ -19,9 +18,6 @@ import qualified Data.Sequence as Seq import Commonmark.Types import Control.Monad.Trans.State -#if !MIN_VERSION_base(4,11,0) -import Data.Semigroup (Semigroup, (<>)) -#endif -- | A map from source positions to a pair of sequences: -- first, elements that start at that position; then, elements diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/commonmark-0.2.1.1/src/Commonmark/Syntax.hs new/commonmark-0.2.2/src/Commonmark/Syntax.hs --- old/commonmark-0.2.1.1/src/Commonmark/Syntax.hs 2020-03-29 20:21:58.000000000 +0200 +++ new/commonmark-0.2.2/src/Commonmark/Syntax.hs 2022-01-12 04:38:14.000000000 +0100 @@ -1,4 +1,3 @@ -{-# LANGUAGE CPP #-} {-# LANGUAGE RankNTypes #-} module Commonmark.Syntax ( SyntaxSpec(..) @@ -11,9 +10,6 @@ import Commonmark.Types import Commonmark.Blocks import Commonmark.Inlines -#if !MIN_VERSION_base(4,11,0) -import Data.Semigroup -#endif -- | A 'SyntaxSpec' defines a basic collection of syntax -- elements or an extension. 'SyntaxSpec's can be composed diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/commonmark-0.2.1.1/src/Commonmark/Tag.hs new/commonmark-0.2.2/src/Commonmark/Tag.hs --- old/commonmark-0.2.1.1/src/Commonmark/Tag.hs 2020-03-29 20:21:58.000000000 +0200 +++ new/commonmark-0.2.2/src/Commonmark/Tag.hs 2022-02-28 06:37:07.000000000 +0100 @@ -14,7 +14,7 @@ import Control.Monad (liftM2, guard) import Control.Monad.Trans.State.Strict import Control.Monad.Trans.Class (lift) -import Data.Char (isAscii, isLetter) +import Unicode.Char (isAscii, isAlpha) import qualified Data.Text as T import Text.Parsec hiding (State) @@ -38,7 +38,7 @@ htmlTagName :: Monad m => ParsecT [Tok] s m [Tok] htmlTagName = try $ do let isTagText = T.all isAscii - let startsWithLetter t' = not (T.null t') && isLetter (T.head t') + let startsWithLetter t' = not (T.null t') && isAlpha (T.head t') t <- satisfyWord (isTagText .&&. startsWithLetter) rest <- many (symbol '-' <|> satisfyWord isTagText) return (t:rest) @@ -49,7 +49,7 @@ htmlAttributeName :: Monad m => ParsecT [Tok] s m [Tok] htmlAttributeName = try $ do let isTagText t' = T.all isAscii t' - let startsWithLetter t' = not (T.null t') && isLetter (T.head t') + let startsWithLetter t' = not (T.null t') && isAlpha (T.head t') t <- satisfyWord (startsWithLetter .&&. isTagText) <|> symbol '_' <|> symbol ':' @@ -184,7 +184,7 @@ op <- symbol '!' alreadyScanned <- lift $ gets scannedForDeclaration guard $ not alreadyScanned - let isDeclName t = not (T.null t) && T.all (isAscii .&&. isLetter) t + let isDeclName t = not (T.null t) && T.all (isAscii .&&. isAlpha) t name <- satisfyWord isDeclName ws <- whitespace contents <- many (satisfyTok (not . hasType (Symbol '>'))) diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/commonmark-0.2.1.1/src/Commonmark/Tokens.hs new/commonmark-0.2.2/src/Commonmark/Tokens.hs --- old/commonmark-0.2.1.1/src/Commonmark/Tokens.hs 2021-07-21 20:44:47.000000000 +0200 +++ new/commonmark-0.2.2/src/Commonmark/Tokens.hs 2022-02-28 06:37:07.000000000 +0100 @@ -10,7 +10,8 @@ , untokenize ) where -import Data.Char (isAlphaNum, isSpace) +import Unicode.Char (isAlphaNum) +import Unicode.Char.General.Compat (isSpace) import Data.Text (Text) import qualified Data.Text as T import Data.Data (Data, Typeable) @@ -43,8 +44,8 @@ f ' ' ' ' = True f x y = isAlphaNum x && isAlphaNum y - go _pos [] = [] - go !pos (t:ts) = -- note that t:ts are guaranteed to be nonempty + go !_pos [] = [] + go !pos (!t:ts) = -- note that t:ts are guaranteed to be nonempty case T.head t of ' ' -> Tok Spaces pos t : go (incSourceColumn pos (T.length t)) ts diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/commonmark-0.2.1.1/src/Commonmark/Types.hs new/commonmark-0.2.2/src/Commonmark/Types.hs --- old/commonmark-0.2.1.1/src/Commonmark/Types.hs 2021-10-13 01:26:18.000000000 +0200 +++ new/commonmark-0.2.2/src/Commonmark/Types.hs 2022-01-12 04:38:14.000000000 +0100 @@ -1,4 +1,3 @@ -{-# LANGUAGE CPP #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE OverloadedStrings #-} @@ -27,9 +26,6 @@ import Data.Typeable (Typeable) import Text.Parsec.Pos (SourcePos, sourceColumn, sourceLine, sourceName) -#if !MIN_VERSION_base(4,11,0) -import Data.Semigroup (Semigroup, (<>)) -#endif newtype Format = Format Text deriving (Show, Data, Typeable) diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/commonmark-0.2.1.1/test/test-commonmark.hs new/commonmark-0.2.2/test/test-commonmark.hs --- old/commonmark-0.2.1.1/test/test-commonmark.hs 2021-07-21 20:44:47.000000000 +0200 +++ new/commonmark-0.2.2/test/test-commonmark.hs 2022-01-12 04:38:14.000000000 +0100 @@ -18,9 +18,6 @@ import Test.Tasty.QuickCheck import Text.Parsec import Text.Parsec.Pos -#if !MIN_VERSION_base(4,11,0) -import Data.Semigroup -#endif readTextFile :: FilePath -> IO Text readTextFile fp = do