Add defaultRunner (not scaffold not updated)

This commit is contained in:
patrick brisbin 2011-09-22 22:38:51 -04:00
parent 70b54929bf
commit 33e0f37400
2 changed files with 44 additions and 0 deletions

View File

@ -1,16 +1,25 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Yesod.Default.Main
( defaultMain
, defaultRunner
, defaultDevelApp
, defaultDevelAppWith
) where
import Yesod.Core
import Yesod.Default.Config
import Yesod.Logger (Logger, makeLogger, logString, logLazyText, flushLogger)
import Network.Wai (Application)
import Network.Wai.Handler.Warp (run)
import Network.Wai.Middleware.Debug (debugHandle)
#ifndef WINDOWS
import qualified System.Posix.Signals as Signal
import Control.Concurrent (forkIO, killThread)
import Control.Concurrent.MVar (newEmptyMVar, putMVar, takeMVar)
#endif
-- | Run your app, taking environment and port settings from the
-- commandline.
--
@ -31,6 +40,35 @@ defaultMain load withSite = do
logger <- makeLogger
withSite config logger $ run (appPort config)
-- | Run your application continously, listening for SIGINT and exiting
-- when recieved
--
-- > withYourSite :: AppConfig DefaultEnv -> Logger -> (Application -> IO a) -> IO ()
-- > withYourSite conf logger f = do
-- > Settings.withConnectionPool conf $ \p -> do
-- > runConnectionPool (runMigration yourMigration) p
-- > defaultRunner f $ YourSite conf logger p
--
-- TODO: ifdef WINDOWS
--
defaultRunner :: (YesodDispatch y y, Yesod y)
=> (Application -> IO a)
-> y -- ^ your foundation type
-> IO ()
defaultRunner f h =
#ifdef WINDOWS
toWaiApp h >>= f >> return ()
#else
do
tid <- forkIO $ toWaiApp h >>= f >> return ()
flag <- newEmptyMVar
_ <- Signal.installHandler Signal.sigINT (Signal.CatchOnce $ do
putStrLn "Caught an interrupt"
killThread tid
putMVar flag ()) Nothing
takeMVar flag
#endif
-- | Run your development app using the provided @'DefaultEnv'@ type
--
-- > withDevelAppPort :: Dynamic

View File

@ -14,6 +14,9 @@ description: Convenient wrappers for your the configuration and
execution of your yesod application
library
if os(windows)
cpp-options: -DWINDOWS
build-depends: base >= 4 && < 5
, yesod-core >= 0.9 && < 0.10
, cmdargs >= 0.8 && < 0.9
@ -25,6 +28,9 @@ library
, text >= 0.9 && < 1.0
, directory >= 1.0 && < 1.2
if !os(windows)
build-depends: unix
exposed-modules: Yesod.Default.Config
, Yesod.Default.Main
, Yesod.Default.Util