Update scaffolding with new load connection functions

Yesod.Settings provides load functions which were previously scaffolded.
They load the ConsStrs for SQL and ConnParams for Mongo.

This prevents the need for a lot of the imports in the scaffolding
settings and simplifies the existing Text import.
This commit is contained in:
patrick brisbin 2011-09-11 14:57:06 -04:00
parent 256245cd2b
commit fa3fabcfba
6 changed files with 6 additions and 45 deletions

View File

@ -94,10 +94,6 @@ scaffold = do
MongoDB -> $(codegen $ "mongoDBConnPool")
Tiny -> ""
settingsTextImport = case backend of
Postgresql -> "import Data.Text (Text, concat)\nimport Prelude hiding (concat)"
_ -> "import Data.Text (Text)"
packages =
if backend == MongoDB
then " , persistent-mongoDB >= 0.6.1 && < 0.7\n , mongoDB >= 1.1\n , bson >= 0.1.5\n"

View File

@ -32,10 +32,7 @@ import Yesod (liftIO, MonadControlIO, addWidget, addCassius, addJulius, addLuciu
import Yesod.Settings
import Data.Monoid (mempty)
import System.Directory (doesFileExist)
~settingsTextImport~
import Data.Object
import qualified Data.Object.Yaml as YAML
import Control.Monad (join)
import Data.Text (Text)
-- Static setting below. Changing these requires a recompile

View File

@ -3,14 +3,6 @@ runConnectionPool = runMongoDBConn (ConfirmWrites [u"j" =: True])
withConnectionPool :: (MonadControlIO m, Applicative m) => AppConfig -> (ConnectionPool -> m b) -> m b
withConnectionPool conf f = do
(database,host) <- liftIO $ loadConnParams (appEnv conf)
(database,host) <- liftIO $ loadMongoConnParams (appEnv conf)
withMongoDBPool (u database) host (connectionPoolSize conf) f
where
-- | The database connection parameters.
-- loadConnParams :: AppEnvironment -> IO (Database, HostName)
loadConnParams env = do
allSettings <- (join $ YAML.decodeFile ("config/mongoDB.yml" :: String)) >>= fromMapping
settings <- lookupMapping (show env) allSettings
database <- lookupScalar "database" settings
host <- lookupScalar "host" settings
return (database, host)

View File

@ -3,21 +3,8 @@ runConnectionPool = runSqlPool
withConnectionPool :: MonadControlIO m => AppConfig -> (ConnectionPool -> m a) -> m a
withConnectionPool conf f = do
cs <- liftIO $ loadConnStr (appEnv conf)
cs <- liftIO $ load~upper~ConnStr (appEnv conf)
with~upper~Pool cs (connectionPoolSize conf) f
where
-- | The database connection string. The meaning of this string is backend-
-- specific.
loadConnStr :: AppEnvironment -> IO Text
loadConnStr env = do
allSettings <- (join $ YAML.decodeFile ("config/~backendLower~.yml" :: String)) >>= fromMapping
settings <- lookupMapping (show env) allSettings
database <- lookupScalar "database" settings :: IO Text
connPart <- fmap concat $ (flip mapM) ["user", "password", "host", "port"] $ \key -> do
value <- lookupScalar key settings
return $ [st| #{key}=#{value} |]
return $ [st|#{connPart} dbname=#{database}|]
-- Example of making a dynamic configuration static
-- use /return $(mkConnStr Production)/ instead of loadConnStr

View File

@ -3,16 +3,8 @@ runConnectionPool = runSqlPool
withConnectionPool :: MonadControlIO m => AppConfig -> (ConnectionPool -> m a) -> m a
withConnectionPool conf f = do
cs <- liftIO $ loadConnStr (appEnv conf)
cs <- liftIO $ load~upper~ConnStr (appEnv conf)
with~upper~Pool cs (connectionPoolSize conf) f
where
-- | The database connection string. The meaning of this string is backend-
-- specific.
loadConnStr :: AppEnvironment -> IO Text
loadConnStr env = do
allSettings <- (join $ YAML.decodeFile ("config/~backendLower~.yml" :: String)) >>= fromMapping
settings <- lookupMapping (show env) allSettings
lookupScalar "database" settings
-- Example of making a dynamic configuration static
-- use /return $(mkConnStr Production)/ instead of loadConnStr

View File

@ -27,10 +27,7 @@ import Yesod.Widget (addWidget, addCassius, addJulius, addLucius, whamletFile)
import Yesod.Settings
import Data.Monoid (mempty)
import System.Directory (doesFileExist)
~settingsTextImport~
import Data.Object
import qualified Data.Object.Yaml as YAML
import Control.Monad (join)
import Data.Text (Text)
-- | The location of static files on your system. This is a file system
-- path. The default value works properly with your scaffolded site.