Script 'mail_helper' called by obssrc
Hello community,

here is the log from the commit of package ghc-lucid for openSUSE:Factory 
checked in at 2021-11-11 21:37:39
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/ghc-lucid (Old)
 and      /work/SRC/openSUSE:Factory/.ghc-lucid.new.1890 (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Package is "ghc-lucid"

Thu Nov 11 21:37:39 2021 rev:6 rq:930440 version:2.10.0

Changes:
--------
--- /work/SRC/openSUSE:Factory/ghc-lucid/ghc-lucid.changes      2021-03-10 
08:58:07.154942489 +0100
+++ /work/SRC/openSUSE:Factory/.ghc-lucid.new.1890/ghc-lucid.changes    
2021-11-11 21:38:28.688978627 +0100
@@ -1,0 +2,12 @@
+Tue Oct 19 07:21:39 UTC 2021 - [email protected]
+
+- Update lucid to version 2.10.0.
+  ## 2.9.13
+
+  * Change internal attributes representation from HashMap to Map. This
+    introduces stable ordering, at a negligible performance cost for
+    realistic element sizes. This may affect some test suites.
+  * doctype no longer accepts attributes. You can use `with` with
+    `doctypeHtml` now, if needed.
+
+-------------------------------------------------------------------

Old:
----
  lucid-2.9.12.1.tar.gz

New:
----
  lucid-2.10.0.tar.gz

++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Other differences:
------------------
++++++ ghc-lucid.spec ++++++
--- /var/tmp/diff_new_pack.k2dn2u/_old  2021-11-11 21:38:29.056978896 +0100
+++ /var/tmp/diff_new_pack.k2dn2u/_new  2021-11-11 21:38:29.056978896 +0100
@@ -19,7 +19,7 @@
 %global pkg_name lucid
 %bcond_with tests
 Name:           ghc-%{pkg_name}
-Version:        2.9.12.1
+Version:        2.10.0
 Release:        0
 Summary:        Clear to write, read and edit DSL for HTML
 License:        BSD-3-Clause

++++++ lucid-2.9.12.1.tar.gz -> lucid-2.10.0.tar.gz ++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/lucid-2.9.12.1/CHANGELOG.md 
new/lucid-2.10.0/CHANGELOG.md
--- old/lucid-2.9.12.1/CHANGELOG.md     2001-09-09 03:46:40.000000000 +0200
+++ new/lucid-2.10.0/CHANGELOG.md       2021-10-17 16:14:14.000000000 +0200
@@ -1,6 +1,14 @@
+## 2.9.13
+
+* Change internal attributes representation from HashMap to Map. This
+  introduces stable ordering, at a negligible performance cost for
+  realistic element sizes. This may affect some test suites.
+* doctype no longer accepts attributes. You can use `with` with
+  `doctypeHtml` now, if needed.
+
 ## 2.9.12.1
 
-* Allow different orderings of attributes in test-suite 
+* Allow different orderings of attributes in test-suite
 
 ## 2.9.12
 
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/lucid-2.9.12.1/benchmarks/HtmlBenchmarks.hs 
new/lucid-2.10.0/benchmarks/HtmlBenchmarks.hs
--- old/lucid-2.9.12.1/benchmarks/HtmlBenchmarks.hs     2001-09-09 
03:46:40.000000000 +0200
+++ new/lucid-2.10.0/benchmarks/HtmlBenchmarks.hs       2021-10-17 
16:11:19.000000000 +0200
@@ -7,12 +7,12 @@
 module HtmlBenchmarks where
 
 import           Data.Monoid (Monoid,mappend,mempty)
+import           Data.Text (Text)
 import qualified Data.Text as T
 -- import qualified Data.Text.Lazy.Builder as B
 
 import qualified Prelude as P
 import           Prelude hiding (div, id)
-import           Data.String
 
 -- import BenchmarkUtils
 import           Lucid
@@ -22,10 +22,10 @@
 -- | Description of an HTML benchmark
 --
 data HtmlBenchmark = forall a. HtmlBenchmark
-    String       -- ^ Name.
+    String          -- ^ Name.
     (a -> Html ())  -- ^ Rendering function.
-    a            -- ^ Data.
-    (Html ())         -- ^ Longer description.
+    a               -- ^ Data.
+    (Html ())       -- ^ Longer description.
 
 -- | List containing all benchmarks.
 --
@@ -40,15 +40,19 @@
     , HtmlBenchmark "wideTree" wideTree wideTreeData $
         "A very wide tree (" >> toHtml (show (length wideTreeData)) >> " 
elements)"
     , HtmlBenchmark "wideTreeEscaping" wideTree wideTreeEscapingData $ do
-        "A very wide tree (" >> toHtml (show (length wideTreeData)) >> " 
elements)"
+        "A very wide tree (" >> toHtml (show (length wideTreeEscapingData)) >> 
" elements)"
         " with lots of escaping"
     , HtmlBenchmark "deepTree" deepTree deepTreeData $ do
         "A really deep tree (" >> toHtml (show deepTreeData) >> " nested 
templates)"
     , HtmlBenchmark "manyAttributes" manyAttributes manyAttributesData $ do
         "A single element with " >> toHtml (show (length manyAttributesData))
-        " attributes."
+        "  distinct attributes."
+    , HtmlBenchmark "duplicateAttributes" duplicateAttributes 
duplicateAttributesData $ do
+        "A single element with a single attribute and " >> toHtml (show 
(length duplicateAttributesData))
+        " values."
     , HtmlBenchmark "customAttribute" customAttributes customAttributesData $
-        "Creating custom attributes"
+        "Creating custom attributes (middle ground between manyAttributes and 
duplicateAttributes)"
+
     ]
 
 rows :: Int
@@ -58,20 +62,20 @@
 bigTableData = replicate rows [1..10]
 {-# NOINLINE bigTableData #-}
 
-basicData :: (String, String, [String])
+basicData :: (Text, Text, [Text])
 basicData = ("Just a test", "joe", items)
 {-# NOINLINE basicData #-}
 
-items :: [String]
-items = map (("Number " `mappend`) . show) [1 :: Int .. 14]
+items :: [Text]
+items = map (("Number " `mappend`) . T.pack . show) [1 :: Int .. 14]
 {-# NOINLINE items #-}
 
-wideTreeData :: [String]
+wideTreeData :: [Text]
 wideTreeData = take 5000 $
     cycle ["??f.(??x.fxx)(??x.fxx)", "These old days", "Foobar", "lol", "x ??? 
A"]
 {-# NOINLINE wideTreeData #-}
 
-wideTreeEscapingData :: [String]
+wideTreeEscapingData :: [Text]
 wideTreeEscapingData = take 1000 $
     cycle ["<><>", "\"lol\"", "<&>", "'>>'"]
 {-# NOINLINE wideTreeEscapingData #-}
@@ -80,10 +84,15 @@
 deepTreeData = 1000
 {-# NOINLINE deepTreeData #-}
 
-manyAttributesData :: [String]
-manyAttributesData = wideTreeData
+manyAttributesData :: [(T.Text, T.Text)]
+manyAttributesData = zipWith mk [0 ..] wideTreeData where
+    mk :: Int -> T.Text -> (T.Text, T.Text)
+    mk i val = (T.pack ("attr" ++ show i), val)
+
+duplicateAttributesData :: [Text]
+duplicateAttributesData = wideTreeData
 
-customAttributesData :: [(String, String)]
+customAttributesData :: [(Text, Text)]
 customAttributesData = zip wideTreeData wideTreeData
 
 -- | Render the argument matrix as an HTML table.
@@ -97,7 +106,7 @@
 
 -- | Render a simple HTML page with some data.
 --
-basic :: (String, String, [String])  -- ^ (Title, User, Items)
+basic :: (Text, Text, [Text])  -- ^ (Title, User, Items)
       -> Html ()                        -- ^ Result.
 basic (title', user, items') = html_ $ do
     head_ $ title_ $ toHtml title'
@@ -112,7 +121,7 @@
 
 -- | A benchmark producing a very wide but very shallow tree.
 --
-wideTree :: [String]  -- ^ Text to create a tree from.
+wideTree :: [Text]  -- ^ Text to create a tree from.
          -> Html ()      -- ^ Result.
 wideTree = div_ . mapM_ ((with p_ [id_ "foo"]) . toHtml)
 
@@ -125,11 +134,15 @@
 
 -- | Create an element with many attributes.
 --
-manyAttributes :: [String]  -- ^ List of attribute values.
+manyAttributes :: [(T.Text, T.Text)]  -- ^ List of attribute values.
+               -> Html ()      -- ^ Result.
+manyAttributes as = img_ (map (\(key, val) -> makeAttribute key val) as)
+
+duplicateAttributes :: [Text]  -- ^ List of attribute values.
                -> Html ()      -- ^ Result.
-manyAttributes as = img_ (map (id_ . T.pack) as)
+duplicateAttributes as = img_ (map id_ as)
 
-customAttributes :: [(String, String)]  -- ^ List of attribute name, value 
pairs
+customAttributes :: [(Text, Text)]  -- ^ List of attribute name, value pairs
                  -> Html ()                -- ^ Result
 customAttributes xs =
-  img_ (map (\(key,val) -> makeAttribute (fromString key) (T.pack val)) xs)
+  img_ (map (\(key,val) -> makeAttribute key val) xs)
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/lucid-2.9.12.1/lucid.cabal 
new/lucid-2.10.0/lucid.cabal
--- old/lucid-2.9.12.1/lucid.cabal      2001-09-09 03:46:40.000000000 +0200
+++ new/lucid-2.10.0/lucid.cabal        2021-10-18 10:30:56.000000000 +0200
@@ -1,5 +1,5 @@
 name:                lucid
-version:             2.9.12.1
+version:             2.10.0
 synopsis:            Clear to write, read and edit DSL for HTML
 description:
   Clear to write, read and edit DSL for HTML.
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/lucid-2.9.12.1/src/Lucid/Base.hs 
new/lucid-2.10.0/src/Lucid/Base.hs
--- old/lucid-2.9.12.1/src/Lucid/Base.hs        2001-09-09 03:46:40.000000000 
+0200
+++ new/lucid-2.10.0/src/Lucid/Base.hs  2021-10-17 16:11:19.000000000 +0200
@@ -53,8 +53,8 @@
 import qualified Data.ByteString.Lazy as L
 import qualified Data.ByteString as S
 import           Data.Functor.Identity
-import           Data.HashMap.Strict (HashMap)
-import qualified Data.HashMap.Strict as M
+import           Data.Map.Strict (Map)
+import qualified Data.Map.Strict as M
 import           Data.Hashable (Hashable(..))
 import           Data.Semigroup (Semigroup (..))
 import           Data.Monoid (Monoid (..))
@@ -86,7 +86,7 @@
 -- | A monad transformer that generates HTML. Use the simpler 'Html'
 -- type if you don't want to transform over some other monad.
 newtype HtmlT m a =
-  HtmlT {runHtmlT :: m (HashMap Text Text -> Builder,a)
+  HtmlT {runHtmlT :: m (Map Text Text -> Builder,a)
          -- ^ This is the low-level way to run the HTML transformer,
          -- finally returning an element builder and a value. You can
          -- pass 'mempty' for this argument for a top-level call. See
@@ -355,7 +355,7 @@
       toPair (Attribute x y) = (x,y)
 
 -- | Union two sets of arguments and append duplicate keys.
-unionArgs :: HashMap Text Text -> HashMap Text Text -> HashMap Text Text
+unionArgs :: Map Text Text -> Map Text Text -> Map Text Text
 unionArgs = M.unionWith (<>)
 
 
--------------------------------------------------------------------------------
@@ -529,7 +529,7 @@
      else s "=\"" <> Blaze.fromHtmlEscapedText val <> s "\""
 
 -- | Folding and monoidally appending attributes.
-foldlMapWithKey :: Monoid m => (k -> v -> m) -> HashMap k v -> m
+foldlMapWithKey :: Monoid m => (k -> v -> m) -> Map k v -> m
 foldlMapWithKey f = M.foldlWithKey' (\m k v -> m `mappend` f k v) mempty
 
 -- | Convenience function for constructing builders.
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/lucid-2.9.12.1/src/Lucid/Html5.hs 
new/lucid-2.10.0/src/Lucid/Html5.hs
--- old/lucid-2.9.12.1/src/Lucid/Html5.hs       2001-09-09 03:46:40.000000000 
+0200
+++ new/lucid-2.10.0/src/Lucid/Html5.hs 2021-10-12 11:55:15.000000000 +0200
@@ -15,8 +15,12 @@
 -- Elements
 
 -- | @DOCTYPE@ element
+--
+-- This is implemented as "raw output", because the doctype doesn't
+-- accept attributes, such as those inserted via 'with'.
+--
 doctype_ :: Applicative m => HtmlT m ()
-doctype_ = makeElementNoEnd "!DOCTYPE HTML"
+doctype_ = HtmlT (pure (const "<!DOCTYPE HTML>", ()))
 
 -- | @DOCTYPE@ element + @html@ element
 doctypehtml_ :: Applicative m => HtmlT m a -> HtmlT m a
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/lucid-2.9.12.1/test/Main.hs 
new/lucid-2.10.0/test/Main.hs
--- old/lucid-2.9.12.1/test/Main.hs     2001-09-09 03:46:40.000000000 +0200
+++ new/lucid-2.10.0/test/Main.hs       2021-05-19 23:27:44.000000000 +0200
@@ -166,7 +166,7 @@
                  [class_ "foo",style_ "attrib"]
                  (style_ "")) ==?*
         [ "<p style=\"attrib\" class=\"foo\"><style></style></p>"
-        , "<pclass=\"foo\" style=\"attrib\"><style></style></p>"
+        , "<p class=\"foo\" style=\"attrib\"><style></style></p>"
         ]
      it "no closing" $
         renderText (with p_ [class_ "foo"] (with (input_ [type_ "text"]) 
[class_ "zot"])) ==?*

Reply via email to