Skip to content

Commit

Permalink
Merge remote-tracking branch 'origin/master'
Browse files Browse the repository at this point in the history
Conflicts:
	yesod-test/yesod-test.cabal
  • Loading branch information
snoyberg committed Mar 29, 2012
2 parents 690b017 + 4545b2a commit 37ad3c0
Show file tree
Hide file tree
Showing 25 changed files with 115 additions and 97 deletions.
1 change: 1 addition & 0 deletions .gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -7,3 +7,4 @@ client_session_key.aes
cabal-dev/
yesod/foobar/
yesod-platform/yesod-platform.cabal
.virthualenv
1 change: 1 addition & 0 deletions sources.txt
Original file line number Diff line number Diff line change
Expand Up @@ -17,3 +17,4 @@
./yesod-default
./yesod-test
./yesod
./yesod-test
2 changes: 1 addition & 1 deletion yesod-core/Yesod/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,13 +28,13 @@ module Yesod.Core
, logError
, logOther
-- * Sessions
, Session
, SessionBackend (..)
, defaultClientSessionBackend
, clientSessionBackend
, saveClientSession
, loadClientSession
, Header(..)
, BackendSession
-- * JS loaders
, loadJsYepnope
, ScriptLoadPosition (..)
Expand Down
24 changes: 5 additions & 19 deletions yesod-core/Yesod/Internal/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,12 +26,12 @@ module Yesod.Internal.Core
, fileLocationToString
, messageLoggerHandler
-- * Sessions
, Session
, SessionBackend (..)
, defaultClientSessionBackend
, clientSessionBackend
, saveClientSession
, loadClientSession
, BackendSession
-- * jsLoader
, ScriptLoadPosition (..)
, BottomOfHeadAsync
Expand Down Expand Up @@ -324,20 +324,6 @@ $doctype 5
key <- CS.getKey CS.defaultKeyFile
return $ Just $ clientSessionBackend key 120

type Session = [(Text, S8.ByteString)]

data SessionBackend master = SessionBackend
{ sbSaveSession :: master
-> W.Request
-> UTCTime -- ^ The current time
-> Session -- ^ The old session (before running handler)
-> Session -- ^ The final session
-> IO [Header]
, sbLoadSession :: master
-> W.Request
-> UTCTime -- ^ The current time
-> IO Session
}

messageLoggerHandler :: Yesod m
=> Loc -> LogLevel -> Text -> GHandler s m ()
Expand Down Expand Up @@ -725,7 +711,7 @@ loadClientSession :: Yesod master
-> master
-> W.Request
-> UTCTime
-> IO Session
-> IO BackendSession
loadClientSession key _ req now = return . fromMaybe [] $ do
raw <- lookup "Cookie" $ W.requestHeaders req
val <- lookup sessionName $ parseCookies raw
Expand All @@ -738,12 +724,12 @@ saveClientSession :: Yesod master
-> master
-> W.Request
-> UTCTime
-> Session
-> Session
-> BackendSession
-> BackendSession
-> IO [Header]
saveClientSession key timeout master _ now _ sess = do
-- fixme should we be caching this?
iv <- liftIO $ CS.randomIV
iv <- liftIO CS.randomIV
return [AddCookie def
{ setCookieName = sessionName
, setCookieValue = sessionVal iv
Expand Down
21 changes: 21 additions & 0 deletions yesod-core/Yesod/Internal/Session.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,11 @@
module Yesod.Internal.Session
( encodeClientSession
, decodeClientSession
, BackendSession
, SessionBackend(..)
) where

import Yesod.Internal (Header(..))
import qualified Web.ClientSession as CS
import Data.Serialize
import Data.Time
Expand All @@ -12,6 +15,24 @@ import Data.Text (Text, pack, unpack)
import Control.Arrow (first)
import Control.Applicative ((<$>))

import qualified Data.ByteString.Char8 as S8
import qualified Network.Wai as W

type BackendSession = [(Text, S8.ByteString)]

data SessionBackend master = SessionBackend
{ sbSaveSession :: master
-> W.Request
-> UTCTime -- ^ The current time
-> BackendSession -- ^ The old session (before running handler)
-> BackendSession -- ^ The final session
-> IO [Header]
, sbLoadSession :: master
-> W.Request
-> UTCTime -- ^ The current time
-> IO BackendSession
}

encodeClientSession :: CS.Key
-> CS.IV
-> UTCTime -- ^ expire time
Expand Down
2 changes: 1 addition & 1 deletion yesod-core/test/YesodCoreTest/Cache.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ import Test.Hspec.HUnit()
import Network.Wai
import Network.Wai.Test

import Yesod.Core hiding (Session)
import Yesod.Core

data C = C

Expand Down
2 changes: 1 addition & 1 deletion yesod-core/test/YesodCoreTest/CleanPath.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ module YesodCoreTest.CleanPath (cleanPathTest, Widget) where
import Test.Hspec
import Test.Hspec.HUnit()

import Yesod.Core hiding (Request, Session)
import Yesod.Core hiding (Request)

import Network.Wai
import Network.Wai.Test
Expand Down
2 changes: 1 addition & 1 deletion yesod-core/test/YesodCoreTest/ErrorHandling.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ module YesodCoreTest.ErrorHandling
( errorHandlingTest
, Widget
) where
import Yesod.Core hiding (Session)
import Yesod.Core
import Test.Hspec
import Test.Hspec.HUnit()
import Network.Wai
Expand Down
2 changes: 1 addition & 1 deletion yesod-core/test/YesodCoreTest/Exceptions.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ module YesodCoreTest.Exceptions (exceptionsTest, Widget) where
import Test.Hspec
import Test.Hspec.HUnit ()

import Yesod.Core hiding (Request, Session)
import Yesod.Core hiding (Request)
import Network.Wai
import Network.Wai.Test
import Network.HTTP.Types (status301)
Expand Down
2 changes: 1 addition & 1 deletion yesod-core/test/YesodCoreTest/JsLoader.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ import YesodCoreTest.JsLoaderSites.Bottom (B(..))
import Test.Hspec
import Test.Hspec.HUnit ()

import Yesod.Core hiding (Request, Session)
import Yesod.Core hiding (Request)
import Network.Wai.Test

data H = H
Expand Down
2 changes: 1 addition & 1 deletion yesod-core/test/YesodCoreTest/Links.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ module YesodCoreTest.Links (linksTest, Widget) where
import Test.Hspec
import Test.Hspec.HUnit ()

import Yesod.Core hiding (Request, Session)
import Yesod.Core hiding (Request)
import Text.Hamlet
import Network.Wai.Test

Expand Down
2 changes: 1 addition & 1 deletion yesod-core/test/YesodCoreTest/Media.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ module YesodCoreTest.Media (mediaTest, Widget) where

import Test.Hspec
import Test.Hspec.HUnit ()
import Yesod.Core hiding (Request, Session)
import Yesod.Core hiding (Request)
import Network.Wai
import Network.Wai.Test
import Text.Lucius
Expand Down
2 changes: 1 addition & 1 deletion yesod-core/test/YesodCoreTest/NoOverloadedStrings.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@ module YesodCoreTest.NoOverloadedStrings (noOverloadedTest, Widget) where
import Test.Hspec
import Test.Hspec.HUnit ()

import Yesod.Core hiding (Request, Session)
import Yesod.Core hiding (Request)
import Network.Wai.Test
import Data.Monoid (mempty)

Expand Down
2 changes: 1 addition & 1 deletion yesod-core/test/YesodCoreTest/WaiSubsite.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@
module YesodCoreTest.WaiSubsite (specs, Widget) where

import YesodCoreTest.YesodTest
import Yesod.Core hiding (Session)
import Yesod.Core
import qualified Network.HTTP.Types as H

myApp :: Application
Expand Down
2 changes: 1 addition & 1 deletion yesod-core/test/YesodCoreTest/Widget.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ module YesodCoreTest.Widget (widgetTest) where
import Test.Hspec
import Test.Hspec.HUnit ()

import Yesod.Core hiding (Request, Session)
import Yesod.Core hiding (Request)
import Text.Julius
import Text.Lucius
import Text.Hamlet
Expand Down
2 changes: 1 addition & 1 deletion yesod-core/test/YesodCoreTest/YesodTest.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ module YesodCoreTest.YesodTest
, module Test.Hspec
) where

import Yesod.Core hiding (Session, Request)
import Yesod.Core hiding (Request)
import Network.Wai.Test
import Network.Wai
import Test.Hspec
Expand Down
30 changes: 15 additions & 15 deletions yesod/Scaffolding/Scaffolder.hs
Original file line number Diff line number Diff line change
Expand Up @@ -109,10 +109,10 @@ scaffold = do
putStrLn "That's it! I'm creating your files now..."

let withConnectionPool = case backend of
Sqlite -> $(codegen $ "sqliteConnPool")
Postgresql -> $(codegen $ "postgresqlConnPool")
Sqlite -> $(codegen "sqliteConnPool")
Postgresql -> $(codegen "postgresqlConnPool")
Mysql -> ""
MongoDB -> $(codegen $ "mongoDBConnPool")
MongoDB -> $(codegen "mongoDBConnPool")
Tiny -> ""

packages =
Expand Down Expand Up @@ -144,29 +144,29 @@ scaffold = do
mkDir "Settings"
mkDir "messages"

writeFile' ("deploy/Procfile") $(codegen "deploy/Procfile")
writeFile' "deploy/Procfile" $(codegen "deploy/Procfile")

case backend of
Sqlite -> writeFile' ("config/" ++ backendLower ++ ".yml") $(codegen ("config/sqlite.yml"))
Postgresql -> writeFile' ("config/" ++ backendLower ++ ".yml") $(codegen ("config/postgresql.yml"))
MongoDB -> writeFile' ("config/" ++ backendLower ++ ".yml") $(codegen ("config/mongoDB.yml"))
Mysql -> writeFile' ("config/" ++ backendLower ++ ".yml") $(codegen ("config/mysql.yml"))
Sqlite -> writeFile' ("config/" ++ backendLower ++ ".yml") $(codegen "config/sqlite.yml")
Postgresql -> writeFile' ("config/" ++ backendLower ++ ".yml") $(codegen "config/postgresql.yml")
MongoDB -> writeFile' ("config/" ++ backendLower ++ ".yml") $(codegen "config/mongoDB.yml")
Mysql -> writeFile' ("config/" ++ backendLower ++ ".yml") $(codegen "config/mysql.yml")
Tiny -> return ()

let isTiny = backend == Tiny
ifTiny a b = if isTiny then a else b

writeFile' ("config/settings.yml") $(codegen "config/settings.yml")
writeFile' ("main.hs") $(codegen "main.hs")
writeFile' ("devel.hs") $(codegen "devel.hs")
writeFile' "config/settings.yml" $(codegen "config/settings.yml")
writeFile' "main.hs" $(codegen "main.hs")
writeFile' "devel.hs" $(codegen "devel.hs")
writeFile' (project ++ ".cabal") $ ifTiny $(codegen "tiny/project.cabal") $(codegen "project.cabal")
when useTests $ do
when useTests $
appendFile' (project ++ ".cabal") $(codegen "cabal_test_suite")

writeFile' ".ghci" $(codegen ".ghci")
writeFile' "LICENSE" $(codegen "LICENSE")
writeFile' ("Foundation.hs") $ ifTiny $(codegen "tiny/Foundation.hs") $(codegen "Foundation.hs")
writeFile' ("Import.hs") $ ifTiny $(codegen "tiny/Import.hs") $(codegen "Import.hs")
writeFile' "Foundation.hs" $ ifTiny $(codegen "tiny/Foundation.hs") $(codegen "Foundation.hs")
writeFile' "Import.hs" $ ifTiny $(codegen "tiny/Import.hs") $(codegen "Import.hs")
writeFile' "Application.hs" $ ifTiny $(codegen "tiny/Application.hs") $(codegen "Application.hs")
writeFile' "Handler/Home.hs" $(codegen "Handler/Home.hs")
unless isTiny $ writeFile' "Model.hs" $(codegen "Model.hs")
Expand Down Expand Up @@ -200,7 +200,7 @@ scaffold = do
return $ pack `AppE` LitE (StringL $ S.unpack bs))

S.writeFile (dir ++ "/config/robots.txt")
$(runIO (S.readFile "scaffold/config/robots.txt.cg") >>= \bs -> do
$(runIO (S.readFile "scaffold/config/robots.txt.cg") >>= \bs ->
[|S.pack $(return $ LitE $ StringL $ S.unpack bs)|])

putStr $(codegenDir "input" "done")
26 changes: 15 additions & 11 deletions yesod/scaffold/Application.hs.cg
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Application
( getApplication
( makeApplication
, getApplicationDev
) where

Expand Down Expand Up @@ -32,15 +32,9 @@ mkYesodDispatch "~sitearg~" resources~sitearg~
-- performs initialization and creates a WAI application. This is also the
-- place to put your migrate statements to have automatic database
-- migrations handled by Yesod.
getApplication :: AppConfig DefaultEnv Extra -> Logger -> IO Application
getApplication conf logger = do
manager <- newManager def
s <- staticSite
dbconf <- withYamlEnvironment "config/~dbConfigFile~.yml" (appEnv conf)
Database.Persist.Store.loadConfig >>=
Database.Persist.Store.applyEnv
p <- Database.Persist.Store.createPoolConfig (dbconf :: Settings.PersistConfig)~runMigration~
let foundation = ~sitearg~ conf setLogger s p manager dbconf
makeApplication :: AppConfig DefaultEnv Extra -> Logger -> IO Application
makeApplication conf logger = do
foundation <- makeFoundation conf logger
app <- toWaiAppPlain foundation
return $ logWare app
where
Expand All @@ -52,10 +46,20 @@ getApplication conf logger = do
logWare = logCallback (logBS setLogger)
#endif

makeFoundation :: AppConfig DefaultEnv Extra -> Logger -> IO ~sitearg~
makeFoundation conf _ = do
manager <- newManager def
s <- staticSite
dbconf <- withYamlEnvironment "config/~dbConfigFile~.yml" (appEnv conf)
Database.Persist.Store.loadConfig >>=
Database.Persist.Store.applyEnv
p <- Database.Persist.Store.createPoolConfig (dbconf :: Settings.PersistConfig)~runMigration~
return $ ~sitearg~ conf setLogger s p manager dbconf

-- for yesod devel
getApplicationDev :: IO (Int, Application)
getApplicationDev =
defaultDevelApp loader getApplication
defaultDevelApp loader makeApplication
where
loader = loadConfig (configSettings Development)
{ csParseExtra = parseExtra
Expand Down
4 changes: 2 additions & 2 deletions yesod/scaffold/deploy/Procfile.cg
Original file line number Diff line number Diff line change
Expand Up @@ -25,8 +25,8 @@
# #endif
#
#
# getApplication :: AppConfig DefaultEnv Extra -> Logger -> IO Application
# getApplication conf logger = do
# makeApplication :: AppConfig DefaultEnv Extra -> Logger -> IO Application
# makeApplication conf logger = do
# manager <- newManager def
# s <- staticSite
# hconfig <- loadHerokuConfig
Expand Down
4 changes: 2 additions & 2 deletions yesod/scaffold/main.hs.cg
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@ import Prelude (IO)
import Yesod.Default.Config (fromArgs)
import Yesod.Default.Main (defaultMain)
import Settings (parseExtra)
import Application (getApplication)
import Application (makeApplication)

main :: IO ()
main = defaultMain (fromArgs parseExtra) getApplication
main = defaultMain (fromArgs parseExtra) makeApplication
22 changes: 22 additions & 0 deletions yesod/scaffold/tests/HomeTest.hs.cg
Original file line number Diff line number Diff line change
@@ -0,0 +1,22 @@
module TestHome (homeSpecs) where

import Import
import Yesod.Test

homeSpecs :: Specs
homeSpecs =
describe "These are some example tests" $
it "loads the index and checks it looks right" $ do
get_ "/"
statusIs 200
htmlAllContain "h1" "Hello"

post "/" $ do
addNonce
fileByLabel "Choose a file" "tests/main.hs" "text/plain" -- talk about self-reference
byLabel "What's on the file?" "Some Content"

statusIs 200
htmlCount ".message" 1
htmlAllContain ".message" "Some Content"
htmlAllContain ".message" "text/plain"
Loading

0 comments on commit 37ad3c0

Please sign in to comment.