Hello community,

here is the log from the commit of package ghc-yesod-core for openSUSE:Factory 
checked in at 2016-10-22 13:21:23
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/ghc-yesod-core (Old)
 and      /work/SRC/openSUSE:Factory/.ghc-yesod-core.new (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Package is "ghc-yesod-core"

Changes:
--------
--- /work/SRC/openSUSE:Factory/ghc-yesod-core/ghc-yesod-core.changes    
2016-08-26 23:17:29.000000000 +0200
+++ /work/SRC/openSUSE:Factory/.ghc-yesod-core.new/ghc-yesod-core.changes       
2016-10-22 13:21:24.000000000 +0200
@@ -1,0 +2,10 @@
+Sat Oct  1 17:18:12 UTC 2016 - psim...@suse.com
+
+- Update to version 1.4.25 with cabal2obs.
+
+-------------------------------------------------------------------
+Thu Sep 15 06:53:57 UTC 2016 - psim...@suse.com
+
+- Update to version 1.4.24 revision 0 with cabal2obs.
+
+-------------------------------------------------------------------

Old:
----
  yesod-core-1.4.23.tar.gz

New:
----
  yesod-core-1.4.25.tar.gz

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

Other differences:
------------------
++++++ ghc-yesod-core.spec ++++++
--- /var/tmp/diff_new_pack.XfM06V/_old  2016-10-22 13:21:25.000000000 +0200
+++ /var/tmp/diff_new_pack.XfM06V/_new  2016-10-22 13:21:25.000000000 +0200
@@ -19,7 +19,7 @@
 %global pkg_name yesod-core
 %bcond_with tests
 Name:           ghc-%{pkg_name}
-Version:        1.4.23
+Version:        1.4.25
 Release:        0
 Summary:        Creation of type-safe, RESTful web applications
 License:        MIT

++++++ yesod-core-1.4.23.tar.gz -> yesod-core-1.4.25.tar.gz ++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/yesod-core-1.4.23/ChangeLog.md 
new/yesod-core-1.4.25/ChangeLog.md
--- old/yesod-core-1.4.23/ChangeLog.md  2016-08-10 14:21:43.000000000 +0200
+++ new/yesod-core-1.4.25/ChangeLog.md  2016-09-26 06:19:15.000000000 +0200
@@ -1,3 +1,16 @@
+## 1.4.25
+
+* Add instance of MonadHandler and MonadWidget for ExceptT 
[#1278](https://github.com/yesodweb/yesod/pull/1278)
+
+## 1.4.24
+
+* cached and cachedBy will not overwrite global state changes 
[#1268](https://github.com/yesodweb/yesod/pull/1268)
+
+## 1.4.23.1
+
+* Don't allow sending multiple cookies with the same name to the client, in 
accordance with [RFC 6265](https://tools.ietf.org/html/rfc6265). This fixes an 
issue where multiple CSRF tokens were sent to the client. 
[#1258](https://github.com/yesodweb/yesod/pull/1258)
+* Default CSRF tokens to the root path "/", fixing an issue where multiple 
tokens were stored in cookies, and using the wrong one led to CSRF errors 
[#1248](https://github.com/yesodweb/yesod/pull/1248)
+
 ## 1.4.23
 
 * urlParamRenderOverride method for Yesod class 
[#1257](https://github.com/yesodweb/yesod/pull/1257)
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/yesod-core-1.4.23/Yesod/Core/Class/Handler.hs 
new/yesod-core-1.4.25/Yesod/Core/Class/Handler.hs
--- old/yesod-core-1.4.23/Yesod/Core/Class/Handler.hs   2016-08-10 
14:21:43.000000000 +0200
+++ new/yesod-core-1.4.25/Yesod/Core/Class/Handler.hs   2016-09-26 
06:19:15.000000000 +0200
@@ -24,6 +24,9 @@
 import Control.Monad.Trans.List     ( ListT    )
 import Control.Monad.Trans.Maybe    ( MaybeT   )
 import Control.Monad.Trans.Error    ( ErrorT, Error)
+#if MIN_VERSION_transformers(0,4,0)
+import Control.Monad.Trans.Except   ( ExceptT  )
+#endif
 import Control.Monad.Trans.Reader   ( ReaderT  )
 import Control.Monad.Trans.State    ( StateT   )
 import Control.Monad.Trans.Writer   ( WriterT  )
@@ -55,6 +58,9 @@
 GO(ListT)
 GO(MaybeT)
 GOX(Error e, ErrorT e)
+#if MIN_VERSION_transformers(0,4,0)
+GO(ExceptT e)
+#endif
 GO(ReaderT r)
 GO(StateT s)
 GOX(Monoid w, WriterT w)
@@ -78,6 +84,9 @@
 GO(ListT)
 GO(MaybeT)
 GOX(Error e, ErrorT e)
+#if MIN_VERSION_transformers(0,4,0)
+GO(ExceptT e)
+#endif
 GO(ReaderT r)
 GO(StateT s)
 GOX(Monoid w, WriterT w)
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/yesod-core-1.4.23/Yesod/Core/Class/Yesod.hs 
new/yesod-core-1.4.25/Yesod/Core/Class/Yesod.hs
--- old/yesod-core-1.4.23/Yesod/Core/Class/Yesod.hs     2016-08-10 
14:21:43.000000000 +0200
+++ new/yesod-core-1.4.25/Yesod/Core/Class/Yesod.hs     2016-09-26 
06:19:15.000000000 +0200
@@ -419,9 +419,9 @@
 -- all responses so that browsers will rewrite all http links to https
 -- until the timeout expires. For security, the max-age of the STS header
 -- should always equal or exceed the client sessions timeout. This defends
--- against hijacking attacks on the sessions of users who attempt to access
--- the site using an http url. This middleware makes a site functionally
--- inaccessible over vanilla http in all standard browsers.
+-- against SSL-stripping man-in-the-middle attacks. It is only effective if
+-- a secure connection has already been made; Strict-Transport-Security
+-- headers are ignored over HTTP.
 --
 -- Since 1.4.7
 sslOnlyMiddleware :: Yesod site
@@ -491,14 +491,18 @@
 
 -- | Calls 'csrfSetCookieMiddleware' with the 'defaultCsrfCookieName'.
 --
+-- The cookie's path is set to @/@, making it valid for your whole website.
+--
 -- Since 1.4.14
 defaultCsrfSetCookieMiddleware :: Yesod site => HandlerT site IO res -> 
HandlerT site IO res
-defaultCsrfSetCookieMiddleware handler = csrfSetCookieMiddleware handler (def 
{ setCookieName = defaultCsrfCookieName })
+defaultCsrfSetCookieMiddleware handler = setCsrfCookie >> handler
 
 -- | Takes a 'SetCookie' and overrides its value with a CSRF token, then sets 
the cookie. See 'setCsrfCookieWithCookie'.
 --
 -- For details, see the "AJAX CSRF protection" section of "Yesod.Core.Handler".
 --
+-- Make sure to set the 'setCookiePath' to the root path of your application, 
otherwise you'll generate a new CSRF token for every path of your app. If your 
app is run from from e.g. www.example.com\/app1, use @app1@. The vast majority 
of sites will just use @/@.
+--
 -- Since 1.4.14
 csrfSetCookieMiddleware :: Yesod site => HandlerT site IO res -> SetCookie -> 
HandlerT site IO res
 csrfSetCookieMiddleware handler cookie = setCsrfCookieWithCookie cookie >> 
handler
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/yesod-core-1.4.23/Yesod/Core/Handler.hs 
new/yesod-core-1.4.25/Yesod/Core/Handler.hs
--- old/yesod-core-1.4.23/Yesod/Core/Handler.hs 2016-08-10 14:21:43.000000000 
+0200
+++ new/yesod-core-1.4.25/Yesod/Core/Handler.hs 2016-09-26 06:19:15.000000000 
+0200
@@ -214,6 +214,7 @@
 import qualified Data.ByteString               as S
 import qualified Data.ByteString.Lazy          as L
 import qualified Data.Map                      as Map
+import qualified Data.HashMap.Strict           as HM
 
 import           Data.Byteable                 (constEqBytes)
 
@@ -615,10 +616,14 @@
 
 -- | Bypass remaining handler code and output the given JSON with the given
 -- status code.
--- 
+--
 -- Since 1.4.18
 sendStatusJSON :: (MonadHandler m, ToJSON c) => H.Status -> c -> m a
+#if MIN_VERSION_aeson(0, 11, 0)
+sendStatusJSON s v = sendResponseStatus s (toEncoding v)
+#else
 sendStatusJSON s v = sendResponseStatus s (toJSON v)
+#endif
 
 -- | Send a 201 "Created" response with the given route as the Location
 -- response header.
@@ -724,7 +729,11 @@
 -- | Set the cookie on the client.
 
 setCookie :: MonadHandler m => SetCookie -> m ()
-setCookie = addHeaderInternal . AddCookie
+setCookie sc = do
+  addHeaderInternal (DeleteCookie name path)
+  addHeaderInternal (AddCookie sc)
+  where name = setCookieName sc
+        path = maybe "/" id (setCookiePath sc)
 
 -- | Helper function for setCookieExpires value
 getExpires :: MonadIO m
@@ -994,12 +1003,14 @@
        => m a
        -> m a
 cached action = do
-    gs <- get
-    eres <- Cache.cached (ghsCache gs) action
+    cache <- ghsCache <$> get
+    eres <- Cache.cached cache action
     case eres of
       Right res -> return res
       Left (newCache, res) -> do
-          put $ gs { ghsCache = newCache }
+          gs <- get
+          let merged = newCache `HM.union` ghsCache gs
+          put $ gs { ghsCache = merged }
           return res
 
 -- | a per-request cache. just like 'cached'.
@@ -1014,12 +1025,14 @@
 -- Since 1.4.0
 cachedBy :: (MonadHandler m, Typeable a) => S.ByteString -> m a -> m a
 cachedBy k action = do
-    gs <- get
-    eres <- Cache.cachedBy (ghsCacheBy gs) k action
+    cache <- ghsCacheBy <$> get
+    eres <- Cache.cachedBy cache k action
     case eres of
       Right res -> return res
       Left (newCache, res) -> do
-          put $ gs { ghsCacheBy = newCache }
+          gs <- get
+          let merged = newCache `HM.union` ghsCacheBy gs
+          put $ gs { ghsCacheBy = merged }
           return res
 
 -- | Get the list of supported languages supplied by the user.
@@ -1354,7 +1367,7 @@
 --
 -- The form-based approach has the advantage of working for users with 
Javascript disabled, while adding the token to the headers with Javascript 
allows things like submitting JSON or binary data in AJAX requests. Yesod 
supports checking for a CSRF token in either the POST parameters of the form 
('checkCsrfParamNamed'), the headers ('checkCsrfHeaderNamed'), or both options 
('checkCsrfHeaderOrParam').
 --
--- The easiest way to check both sources is to add the 'defaultCsrfMiddleware' 
to your Yesod Middleware.
+-- The easiest way to check both sources is to add the 
'Yesod.Core.defaultCsrfMiddleware' to your Yesod Middleware.
 
 -- | The default cookie name for the CSRF token ("XSRF-TOKEN").
 --
@@ -1364,12 +1377,16 @@
 
 -- | Sets a cookie with a CSRF token, using 'defaultCsrfCookieName' for the 
cookie name.
 --
+-- The cookie's path is set to @/@, making it valid for your whole website.
+--
 -- Since 1.4.14
 setCsrfCookie :: MonadHandler m => m ()
-setCsrfCookie = setCsrfCookieWithCookie def { setCookieName = 
defaultCsrfCookieName }
+setCsrfCookie = setCsrfCookieWithCookie def { setCookieName = 
defaultCsrfCookieName, setCookiePath = Just "/" }
 
 -- | Takes a 'SetCookie' and overrides its value with a CSRF token, then sets 
the cookie.
 --
+-- Make sure to set the 'setCookiePath' to the root path of your application, 
otherwise you'll generate a new CSRF token for every path of your app. If your 
app is run from from e.g. www.example.com\/app1, use @app1@. The vast majority 
of sites will just use @/@.
+--
 -- Since 1.4.14
 setCsrfCookieWithCookie :: MonadHandler m => SetCookie -> m ()
 setCsrfCookieWithCookie cookie  = do
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/yesod-core-1.4.23/Yesod/Core/Types.hs 
new/yesod-core-1.4.25/Yesod/Core/Types.hs
--- old/yesod-core-1.4.23/Yesod/Core/Types.hs   2016-08-10 14:21:43.000000000 
+0200
+++ new/yesod-core-1.4.25/Yesod/Core/Types.hs   2016-09-26 06:19:15.000000000 
+0200
@@ -323,7 +323,7 @@
 ----- header stuff
 -- | Headers to be added to a 'Result'.
 data Header =
-    AddCookie SetCookie
+      AddCookie SetCookie
     | DeleteCookie ByteString ByteString
     | Header ByteString ByteString
     deriving (Eq, Show)
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/yesod-core-1.4.23/test/YesodCoreTest/Cache.hs 
new/yesod-core-1.4.25/test/YesodCoreTest/Cache.hs
--- old/yesod-core-1.4.23/test/YesodCoreTest/Cache.hs   2016-08-10 
14:21:43.000000000 +0200
+++ new/yesod-core-1.4.25/test/YesodCoreTest/Cache.hs   2016-09-26 
06:19:15.000000000 +0200
@@ -2,6 +2,7 @@
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE Rank2Types #-}
 module YesodCoreTest.Cache (cacheTest, Widget) where
 
 import Test.Hspec
@@ -25,6 +26,8 @@
 mkYesod "C" [parseRoutes|
 /    RootR GET
 /key KeyR GET
+/nested NestedR GET
+/nested-key NestedKeyR GET
 |]
 
 instance Yesod C where
@@ -55,6 +58,24 @@
 
     return $ RepPlain $ toContent $ show [v1a, v1b, v2a, v2b, v3a, v3b]
 
+getNestedR :: Handler RepPlain
+getNestedR = getNested cached
+
+getNestedKeyR :: Handler RepPlain
+getNestedKeyR = getNested $ cachedBy "3"
+
+-- | Issue #1266
+getNested ::  (forall a. Typeable a => (Handler a -> Handler a)) -> Handler 
RepPlain
+getNested cacheMethod = do
+    ref <- newIORef 0
+    let getV2 = atomicModifyIORef ref $ \i -> (i + 1, V2 $ i + 1)
+    V1 _ <- cacheMethod $ do
+      V2 val <- cacheMethod $ getV2
+      return $ V1 val
+    V2 v2 <- cacheMethod $ getV2
+
+    return $ RepPlain $ toContent $ show v2
+
 cacheTest :: Spec
 cacheTest =
   describe "Test.Cache" $ do
@@ -68,5 +89,15 @@
       assertStatus 200 res
       assertBody (L8.pack $ show [1, 1, 2, 2, 3, 3 :: Int]) res
 
+    it "nested cached" $ runner $ do
+      res <- request defaultRequest { pathInfo = ["nested"] }
+      assertStatus 200 res
+      assertBody (L8.pack $ show (1 :: Int)) res
+
+    it "nested cachedBy" $ runner $ do
+      res <- request defaultRequest { pathInfo = ["nested-key"] }
+      assertStatus 200 res
+      assertBody (L8.pack $ show (1 :: Int)) res
+
 runner :: Session () -> IO ()
 runner f = toWaiApp C >>= runSession f
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/yesod-core-1.4.23/test/YesodCoreTest/Csrf.hs 
new/yesod-core-1.4.25/test/YesodCoreTest/Csrf.hs
--- old/yesod-core-1.4.23/test/YesodCoreTest/Csrf.hs    2016-08-10 
14:21:43.000000000 +0200
+++ new/yesod-core-1.4.25/test/YesodCoreTest/Csrf.hs    2016-09-26 
06:19:15.000000000 +0200
@@ -45,6 +45,12 @@
         assertStatus 200 res
         assertClientCookieExists "Should have an XSRF-TOKEN cookie" 
defaultCsrfCookieName
 
+    it "uses / as the path of the cookie" $ runner $ do -- 
https://github.com/yesodweb/yesod/issues/1247
+        res <- request defaultRequest
+        assertStatus 200 res
+        cookiePath <- fmap setCookiePath requireCsrfCookie
+        liftIO $ cookiePath `shouldBe` Just "/"
+
     it "200s write requests with the correct CSRF header, but no param" $ 
runner $ do
         getRes <- request defaultRequest
         assertStatus 200 getRes
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/yesod-core-1.4.23/yesod-core.cabal 
new/yesod-core-1.4.25/yesod-core.cabal
--- old/yesod-core-1.4.23/yesod-core.cabal      2016-08-10 14:21:43.000000000 
+0200
+++ new/yesod-core-1.4.25/yesod-core.cabal      2016-09-26 06:19:15.000000000 
+0200
@@ -1,5 +1,5 @@
 name:            yesod-core
-version:         1.4.23
+version:         1.4.25
 license:         MIT
 license-file:    LICENSE
 author:          Michael Snoyman <mich...@snoyman.com>


Reply via email to