Merge branch 'update-persistent' of https://github.com/DanBurton/yesod

This commit is contained in:
Michael Snoyman 2018-10-14 10:47:23 +03:00
commit aed169b43f
No known key found for this signature in database
GPG Key ID: A048E8C057E86876
12 changed files with 32 additions and 11 deletions

View File

@ -1,3 +1,7 @@
## 1.6.0.1
* Compile with GHC 8.6 [#1561](https://github.com/yesodweb/yesod/pull/1561)
## 1.6.0
* Upgrade to yesod-core 1.6.0

View File

@ -1,5 +1,6 @@
{-# LANGUAGE DeriveDataTypeable, OverloadedStrings, QuasiQuotes #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
@ -69,7 +70,9 @@ authOAuth oauth mkCreds = AuthPlugin name dispatch login
setSession oauthSessionName $ lookupTokenSecret tok
redirect $ authorizeUrl oauth' tok
dispatch "GET" [] = do
Just tokSec <- lookupSession oauthSessionName
tokSec <- lookupSession oauthSessionName >>= \case
Just t -> return t
Nothing -> liftIO $ fail "lookupSession could not find session"
deleteSession oauthSessionName
reqTok <-
if oauthVersion oauth == OAuth10

View File

@ -1,5 +1,5 @@
name: yesod-auth-oauth
version: 1.6.0
version: 1.6.0.1
license: BSD3
license-file: LICENSE
author: Hiromi Ishii

View File

@ -2,7 +2,7 @@
## 1.6.5
* Add support for persistent 2.9 [#1516](https://github.com/yesodweb/yesod/pull/1516)
* Add support for persistent 2.9 [#1516](https://github.com/yesodweb/yesod/pull/1516), [#1561](https://github.com/yesodweb/yesod/pull/1561)
## 1.6.4.1

View File

@ -1,6 +1,6 @@
## 1.6.1
## 1.6.0.1
* Add support for persistent 2.9 [#1516](https://github.com/yesodweb/yesod/pull/1516)
* Add support for persistent 2.9 [#1516](https://github.com/yesodweb/yesod/pull/1516), [#1561](https://github.com/yesodweb/yesod/pull/1561)
## 1.6.0

View File

@ -1,5 +1,5 @@
name: yesod-persistent
version: 1.6.1
version: 1.6.0.1
license: MIT
license-file: LICENSE
author: Michael Snoyman <michael@snoyman.com>

View File

@ -1,3 +1,7 @@
## 1.6.0.1
* Make test suite build with GHC 8.6 [#1561](https://github.com/yesodweb/yesod/pull/1561)
## 1.6.0
* Upgrade to yesod-core 1.6.0

View File

@ -1,4 +1,5 @@
{-# LANGUAGE TemplateHaskell, QuasiQuotes, TypeFamilies, OverloadedStrings #-}
{-# LANGUAGE LambdaCase #-}
module EmbedProductionTest where
-- Tests the production mode of the embedded static subsite by
@ -108,7 +109,9 @@ embedProductionSpecs = yesodSpec (MyApp eProduction) $ do
yit "Embedded Javascript" $ do
get HomeR
statusIs 200
[script] <- htmlQuery "script"
script <- htmlQuery "script" >>= \case
[s] -> return s
_ -> liftIO $ fail "Expected singleton list of script"
let src = BL.takeWhile (/= 34) $ BL.drop 1 $ BL.dropWhile (/= 34) script -- 34 is "
get $ TL.toStrict $ TL.decodeUtf8 src

View File

@ -1,5 +1,5 @@
name: yesod-static
version: 1.6.0
version: 1.6.0.1
license: MIT
license-file: LICENSE
author: Michael Snoyman <michael@snoyman.com>

View File

@ -1,3 +1,7 @@
## 1.6.5.1
* Make test suite build with GHC 8.6 [#1561](https://github.com/yesodweb/yesod/pull/1561)
## 1.6.5
bodyEquals prints out actual body in addition to expected body in failure msg
[#1525](https://github.com/yesodweb/yesod/pull/1525)

View File

@ -5,6 +5,7 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TypeFamilies #-}
@ -482,8 +483,10 @@ postHomeR = defaultLayout
postResourcesR :: Handler ()
postResourcesR = do
([("foo", t)], _) <- runRequestBody
sendResponseCreated $ ResourceR t
t <- runRequestBody >>= \case
([("foo", t)], _) -> return t
_ -> liftIO $ fail "postResourcesR pattern match failure"
sendResponseCreated $ ResourceR t
getResourceR :: Text -> Handler Html
getResourceR i = defaultLayout

View File

@ -1,5 +1,5 @@
name: yesod-test
version: 1.6.5
version: 1.6.5.1
license: MIT
license-file: LICENSE
author: Nubis <nubis@woobiz.com.ar>