Remove defaultRunner, @snoyberg already has it in Utils
This commit is contained in:
parent
b8f1ee151d
commit
22ca2af421
@ -2,24 +2,16 @@
|
||||
{-# 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.
|
||||
--
|
||||
@ -40,35 +32,6 @@ 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
|
||||
|
||||
Loading…
Reference in New Issue
Block a user