fix/improve scaffolding
This commit is contained in:
parent
a0a7291616
commit
7fd7ba59ca
@ -46,10 +46,10 @@ with~sitearg~ conf f = do
|
||||
|
||||
with~sitearg~LoadConfig :: Settings.AppEnvironment -> (Application -> IO a) -> IO a
|
||||
with~sitearg~LoadConfig env f = do
|
||||
conf <- Settings.loadConfig Settings.Development
|
||||
conf <- Settings.loadConfig env
|
||||
withFoobar conf f
|
||||
|
||||
|
||||
-- for yesod devel
|
||||
withDevelApp :: Dynamic
|
||||
withDevelApp = do
|
||||
toDyn ((with~sitearg~LoadConfig Settings.Development):: (Application -> IO ()) -> IO ())
|
||||
|
||||
@ -2,6 +2,7 @@
|
||||
module Handler.Root where
|
||||
|
||||
import ~sitearg~
|
||||
import Data.Text
|
||||
|
||||
-- This is a handler function for the GET request method on the RootR
|
||||
-- resource pattern. All of your resource patterns are defined in
|
||||
@ -17,4 +18,3 @@ getRootR = do
|
||||
h2id <- lift newIdent
|
||||
setTitle "~project~ homepage"
|
||||
addWidget $(widgetFile "homepage")
|
||||
|
||||
|
||||
@ -31,7 +31,8 @@ import Language.Haskell.TH.Syntax
|
||||
import Yesod (liftIO, MonadControlIO, addWidget, addCassius, addJulius, addLucius)
|
||||
import Data.Monoid (mempty, mappend)
|
||||
import System.Directory (doesFileExist)
|
||||
import Data.Text (Text)
|
||||
import Prelude hiding (concat)
|
||||
import Data.Text (Text, snoc, append, pack, concat)
|
||||
import Data.Object
|
||||
import qualified Data.Object.Yaml as YAML
|
||||
import Control.Monad (join)
|
||||
|
||||
@ -5,4 +5,3 @@
|
||||
/robots.txt RobotsR GET
|
||||
|
||||
/ RootR GET
|
||||
|
||||
|
||||
@ -34,13 +34,19 @@ getRobotsR = return $ RepPlain $ toContent ("User-agent: *" :: ByteString)
|
||||
-- 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.
|
||||
with~sitearg~ :: AppEnvironment -> (Application -> IO a) -> IO a
|
||||
with~sitearg~ appEnv f = do
|
||||
let h = ~sitearg~ appEnv s
|
||||
with~sitearg~ :: AppConfig -> (Application -> IO a) -> IO a
|
||||
with~sitearg~ conf f = do
|
||||
let h = ~sitearg~ conf s
|
||||
toWaiApp h >>= f
|
||||
where
|
||||
s = static Settings.staticdir
|
||||
s = static Settings.staticDir
|
||||
|
||||
with~sitearg~LoadConfig :: Settings.AppEnvironment -> (Application -> IO a) -> IO a
|
||||
with~sitearg~LoadConfig env f = do
|
||||
conf <- Settings.loadConfig env
|
||||
withFoobar conf f
|
||||
|
||||
withDevelApp :: Dynamic
|
||||
withDevelApp = toDyn (with~sitearg~ Development :: (Application -> IO ()) -> IO ())
|
||||
withDevelApp = do
|
||||
toDyn ((with~sitearg~LoadConfig Settings.Development):: (Application -> IO ()) -> IO ())
|
||||
|
||||
|
||||
@ -5,7 +5,7 @@ import ~sitearg~
|
||||
|
||||
-- This is a handler function for the GET request method on the RootR
|
||||
-- resource pattern. All of your resource patterns are defined in
|
||||
-- ~sitearg~.hs; look for the line beginning with mkYesodData.
|
||||
-- config/routes
|
||||
--
|
||||
-- The majority of the code you will write in Yesod lives in these handler
|
||||
-- functions. You can spread them across multiple files if you are so
|
||||
|
||||
@ -60,5 +60,8 @@ executable ~project~
|
||||
, wai
|
||||
, warp
|
||||
, blaze-builder
|
||||
, cmdargs
|
||||
, data-object
|
||||
, data-object-yaml
|
||||
ghc-options: -Wall -threaded
|
||||
|
||||
|
||||
@ -12,9 +12,11 @@ module Settings
|
||||
, juliusFile
|
||||
, luciusFile
|
||||
, widgetFile
|
||||
, approot
|
||||
, staticroot
|
||||
, staticdir
|
||||
, staticRoot
|
||||
, staticDir
|
||||
, loadConfig
|
||||
, AppEnvironment(..)
|
||||
, AppConfig(..)
|
||||
) where
|
||||
|
||||
import qualified Text.Hamlet as H
|
||||
@ -26,25 +28,55 @@ import Yesod.Widget (addWidget, addCassius, addJulius, addLucius)
|
||||
import Data.Monoid (mempty, mappend)
|
||||
import System.Directory (doesFileExist)
|
||||
import Data.Text (Text)
|
||||
import Data.Object
|
||||
import qualified Data.Object.Yaml as YAML
|
||||
import Control.Monad (join)
|
||||
|
||||
-- | The base URL for your application. This will usually be different for
|
||||
-- development and production. Yesod automatically constructs URLs for you,
|
||||
-- so this value must be accurate to create valid links.
|
||||
approot :: Text
|
||||
#ifdef PRODUCTION
|
||||
-- You probably want to change this. If your domain name was "yesod.com",
|
||||
-- you would probably want it to be:
|
||||
-- > approot = "http://www.yesod.com"
|
||||
-- Please note that there is no trailing slash.
|
||||
approot = "http://localhost:3000"
|
||||
#else
|
||||
approot = "http://localhost:3000"
|
||||
#endif
|
||||
data AppEnvironment = Test
|
||||
| Development
|
||||
| Staging
|
||||
| Production
|
||||
deriving (Eq, Show, Read, Enum, Bounded)
|
||||
|
||||
-- | Dynamic per-environment configuration loaded from the YAML file Settings.yaml.
|
||||
-- Use dynamic settings to avoid the need to re-compile the application (between staging and production environments).
|
||||
--
|
||||
-- By convention these settings should be overwritten by any command line arguments.
|
||||
-- See config/~sitearg~.hs for command line arguments
|
||||
-- Command line arguments provide some convenience but are also required for hosting situations where a setting is read from the environment (appPort on Heroku).
|
||||
--
|
||||
data AppConfig = AppConfig {
|
||||
appEnv :: AppEnvironment
|
||||
|
||||
, appPort :: Int
|
||||
|
||||
-- | The base URL for your application. This will usually be different for
|
||||
-- development and production. Yesod automatically constructs URLs for you,
|
||||
-- so this value must be accurate to create valid links.
|
||||
-- Please note that there is no trailing slash.
|
||||
--
|
||||
-- You probably want to change this! If your domain name was "yesod.com",
|
||||
-- you would probably want it to be:
|
||||
-- > "http://yesod.com"
|
||||
, appRoot :: Text
|
||||
} deriving (Show)
|
||||
|
||||
loadConfig :: AppEnvironment -> IO AppConfig
|
||||
loadConfig env = do
|
||||
allSettings <- (join $ YAML.decodeFile ("config/settings.yml" :: String)) >>= fromMapping
|
||||
settings <- lookupMapping (show env) allSettings
|
||||
appPortS <- lookupScalar "appPort" settings
|
||||
appRootS <- lookupScalar "appRoot" settings
|
||||
return $ AppConfig {
|
||||
appEnv = env
|
||||
, appPort = read $ appPortS
|
||||
, appRoot = read $ (show appRootS)
|
||||
}
|
||||
|
||||
-- | The location of static files on your system. This is a file system
|
||||
-- path. The default value works properly with your scaffolded site.
|
||||
staticdir :: FilePath
|
||||
staticdir = "static"
|
||||
staticDir :: FilePath
|
||||
staticDir = "static"
|
||||
|
||||
-- | The base URL for your static files. As you can see by the default
|
||||
-- value, this can simply be "static" appended to your application root.
|
||||
@ -59,8 +91,8 @@ staticdir = "static"
|
||||
-- have to make a corresponding change here.
|
||||
--
|
||||
-- To see how this value is used, see urlRenderOverride in ~project~.hs
|
||||
staticroot :: Text
|
||||
staticroot = approot `mappend` "/static"
|
||||
staticRoot :: AppConfig -> Text
|
||||
staticRoot conf = (appRoot conf) `mappend` "/static"
|
||||
|
||||
-- The rest of this file contains settings which rarely need changing by a
|
||||
-- user.
|
||||
|
||||
@ -30,7 +30,7 @@ import qualified Data.Text as T
|
||||
-- starts running, such as database connections. Every handler will have
|
||||
-- access to the data present here.
|
||||
data ~sitearg~ = ~sitearg~
|
||||
{ appEnv :: Settings.AppEnvironment
|
||||
{ settings :: Settings.AppConfig
|
||||
, getStatic :: Static -- ^ Settings for static file serving.
|
||||
}
|
||||
|
||||
@ -66,7 +66,7 @@ mkYesodData "~sitearg~" $(parseRoutesFile "config/routes")
|
||||
-- Please see the documentation for the Yesod typeclass. There are a number
|
||||
-- of settings which can be configured by overriding methods here.
|
||||
instance Yesod ~sitearg~ where
|
||||
approot _ = Settings.approot
|
||||
approot = Settings.appRoot . settings
|
||||
|
||||
defaultLayout widget = do
|
||||
mmsg <- getMessage
|
||||
@ -77,8 +77,8 @@ instance Yesod ~sitearg~ where
|
||||
|
||||
-- This is done to provide an optimization for serving static files from
|
||||
-- a separate domain. Please see the staticroot setting in Settings.hs
|
||||
urlRenderOverride a (StaticR s) =
|
||||
Just $ uncurry (joinPath a Settings.staticroot) $ renderRoute s
|
||||
urlRenderOverride y (StaticR s) =
|
||||
Just $ uncurry (joinPath y (Settings.staticRoot $ settings y)) $ renderRoute s
|
||||
urlRenderOverride _ _ = Nothing
|
||||
|
||||
-- This function creates static content files in the static folder
|
||||
@ -87,7 +87,7 @@ instance Yesod ~sitearg~ where
|
||||
-- users receiving stale content.
|
||||
addStaticContent ext' _ content = do
|
||||
let fn = base64md5 content ++ '.' : T.unpack ext'
|
||||
let statictmp = Settings.staticdir ++ "/tmp/"
|
||||
let statictmp = Settings.staticDir ++ "/tmp/"
|
||||
liftIO $ createDirectoryIfMissing True statictmp
|
||||
let fn' = statictmp ++ fn
|
||||
exists <- liftIO $ doesFileExist fn'
|
||||
|
||||
@ -1,5 +1,5 @@
|
||||
user <- lookupScalar "user"
|
||||
password <- lookupScalar "user"
|
||||
host <- lookupScalar "host"
|
||||
port <- lookupScalar "port"
|
||||
return $ "user=" ++ user ++ "password=" ++ password ++ "host=" ++ host ++ "port=" ++ port ++ "dbname= ++ database"
|
||||
connPart <- fmap concat $ (flip mapM) ["user", "password", "host", "port"] $ \key -> do
|
||||
value <- lookupScalar key settings
|
||||
return $ append (snoc (pack key) '=') (snoc value ' ')
|
||||
return $ append connPart (append " dbname= " database)
|
||||
|
||||
|
||||
@ -7,24 +7,20 @@ import System.Console.CmdArgs
|
||||
import Data.Char (toUpper, toLower)
|
||||
|
||||
#if PRODUCTION
|
||||
main :: IO ()
|
||||
main = do
|
||||
args <- cmdArgs argConfig
|
||||
appEnv <- getAppEnv args
|
||||
config <- Settings.loadConfig appEnv
|
||||
let c = if (port args) /= 0 then config {appPort = (port args) } else config
|
||||
with~sitearg~ c $ run (appPort c)
|
||||
|
||||
#else
|
||||
|
||||
import System.IO (hPutStrLn, stderr)
|
||||
import Network.Wai.Middleware.Debug (debug)
|
||||
#endif
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
args <- cmdArgs argConfig
|
||||
appEnv <- getAppEnv args
|
||||
config <- Settings.loadConfig appEnv
|
||||
let c = if (port args) /= 0 then config {appPort = (port args) } else config
|
||||
#if PRODUCTION
|
||||
with~sitearg~ c $ run (appPort c)
|
||||
#else
|
||||
hPutStrLn stderr $ (show appEnv) ++ " application launched, listening on port " ++ show (appPort c)
|
||||
with~sitearg~ c $ run (appPort c) . debug
|
||||
#endif
|
||||
|
||||
4
tests/mini-input.txt
Normal file
4
tests/mini-input.txt
Normal file
@ -0,0 +1,4 @@
|
||||
Michael
|
||||
foobar
|
||||
Foobar
|
||||
m
|
||||
4
tests/postgresql-input.txt
Normal file
4
tests/postgresql-input.txt
Normal file
@ -0,0 +1,4 @@
|
||||
Michael
|
||||
foobar
|
||||
Foobar
|
||||
p
|
||||
@ -1,4 +1,3 @@
|
||||
#!/bin/sh
|
||||
#!/bin/bash -x
|
||||
|
||||
cabal clean && cabal install &&
|
||||
rm -rf foobar && runghc scaffold.hs init < tests/sample-input.txt && cd foobar && cabal install && cabal install -fdevel && cd ..
|
||||
rm -rf foobar && runghc scaffold.hs init && cd foobar && cabal install && cabal install -fdevel && cd ..
|
||||
|
||||
Loading…
Reference in New Issue
Block a user