stackage-server/Application.hs

222 lines
9 KiB
Haskell
Raw Normal View History

2014-04-09 07:52:04 +00:00
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Application
( makeApplication
, getApplicationDev
, makeFoundation
) where
import qualified Aws
import Control.Concurrent (forkIO, threadDelay)
import Control.Monad.Logger (runLoggingT, LoggingT)
import Control.Monad.Reader (runReaderT, ReaderT)
import Control.Monad.Reader (MonadReader (..))
import Control.Monad.Trans.Control
import Data.BlobStore (fileStore, storeWrite, cachedS3Store)
import Data.Conduit.Lazy (MonadActive, monadActive)
import Data.Hackage
import Data.Hackage.Views
import Data.Time (diffUTCTime)
import qualified Database.Persist
import Filesystem (getModified, removeTree)
import Import hiding (catch)
import Language.Haskell.TH.Syntax (Loc(..))
import Network.Wai.Logger (clockDateCacher)
import Network.Wai.Middleware.RequestLogger
2014-04-09 07:52:04 +00:00
( mkRequestLogger, outputFormat, OutputFormat (..), IPAddrSource (..), destination
)
import qualified Network.Wai.Middleware.RequestLogger as RequestLogger
import Settings
import System.Log.FastLogger (newStdoutLoggerSet, newFileLoggerSet, defaultBufSize, flushLogStr, fromLogStr)
2014-04-09 11:38:54 +00:00
import qualified System.Random.MWC as MWC
import Yesod.Core.Types (loggerSet, Logger (Logger))
import Yesod.Default.Config
import Yesod.Default.Handlers
import Yesod.Default.Main
import qualified Echo
2014-04-09 07:52:04 +00:00
-- Import all relevant handler modules here.
-- Don't forget to add new modules to your cabal file!
import Handler.Home
2014-06-01 11:35:10 +00:00
import Handler.Snapshots
import Handler.Profile
import Handler.Email
import Handler.ResetToken
import Handler.UploadStackage
import Handler.StackageHome
import Handler.StackageIndex
import Handler.StackageSdist
import Handler.HackageViewIndex
import Handler.HackageViewSdist
import Handler.Aliases
import Handler.Alias
import Handler.Progress
import Handler.System
2014-04-09 07:52:04 +00:00
-- This line actually creates our YesodDispatch instance. It is the second half
-- of the call to mkYesodData which occurs in Foundation.hs. Please see the
-- comments there for more details.
mkYesodDispatch "App" resourcesApp
-- This function allocates resources (such as a database connection pool),
-- 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.
makeApplication :: Bool -- ^ Use Echo.
-> AppConfig DefaultEnv Extra -> IO (Application, LogFunc)
makeApplication echo@True conf = do
foundation <- makeFoundation echo conf
app <- toWaiAppPlain foundation
logWare <- mkRequestLogger def
{ destination = RequestLogger.Callback (const (return ()))
}
Echo.clear
return (logWare (defaultMiddlewaresNoLogging app),logFunc)
where logFunc (Loc filename _pkg _mod (line,_) _) source level str =
Echo.write (filename,line) (show source ++ ": " ++ show level ++ ": " ++ toStr str)
toStr = unpack . decodeUtf8 . fromLogStr
makeApplication echo@False conf = do
foundation <- makeFoundation echo conf
2014-04-09 07:52:04 +00:00
-- Initialize the logging middleware
logWare <- mkRequestLogger def
{ outputFormat =
if development
then Detailed True
else Apache FromSocket
, destination = RequestLogger.Logger $ loggerSet $ appLogger foundation
}
-- Create the WAI application and apply middlewares
app <- toWaiAppPlain foundation
let logFunc = messageLoggerSource foundation (appLogger foundation)
2014-04-10 16:39:09 +00:00
middleware = logWare . defaultMiddlewaresNoLogging
2014-04-09 11:38:54 +00:00
return (middleware app, logFunc)
2014-04-09 07:52:04 +00:00
-- | Loads up any necessary settings, creates your foundation datatype, and
-- performs some initialization.
makeFoundation :: Bool -> AppConfig DefaultEnv Extra -> IO App
makeFoundation useEcho conf = do
2014-04-09 07:52:04 +00:00
manager <- newManager
s <- staticSite
dbconf <- withYamlEnvironment "config/postgresql.yml" (appEnv conf)
Database.Persist.loadConfig >>=
Database.Persist.applyEnv
p <- Database.Persist.createPoolConfig (dbconf :: Settings.PersistConf)
loggerSet' <- if useEcho
then newFileLoggerSet defaultBufSize "/dev/null"
else newStdoutLoggerSet defaultBufSize
2014-04-09 07:52:04 +00:00
(getter, updater) <- clockDateCacher
-- If the Yesod logger (as opposed to the request logger middleware) is
-- used less than once a second on average, you may prefer to omit this
-- thread and use "(updater >> getter)" in place of "getter" below. That
-- would update the cache every time it is used, instead of every second.
let updateLoop = do
threadDelay 1000000
updater
2014-04-10 16:39:09 +00:00
flushLogStr loggerSet'
2014-04-09 07:52:04 +00:00
updateLoop
_ <- forkIO updateLoop
2014-04-09 11:38:54 +00:00
gen <- MWC.createSystemRandom
2014-04-17 17:30:52 +00:00
progressMap' <- newIORef mempty
nextProgressKey' <- newIORef 0
2014-04-09 11:38:54 +00:00
2014-05-20 13:51:21 +00:00
blobStore' <-
case storeConfig $ appExtra conf of
BSCFile root -> return $ fileStore root
BSCAWS root access secret bucket prefix -> do
creds <- Aws.Credentials
<$> pure (encodeUtf8 access)
<*> pure (encodeUtf8 secret)
<*> newIORef []
return $ cachedS3Store root creds bucket prefix manager
2014-04-09 07:52:04 +00:00
let logger = Yesod.Core.Types.Logger loggerSet' getter
2014-04-09 11:38:54 +00:00
foundation = App
{ settings = conf
, getStatic = s
, connPool = p
, httpManager = manager
, persistConfig = dbconf
, appLogger = logger
, genIO = gen
2014-05-20 13:51:21 +00:00
, blobStore = blobStore'
2014-04-17 17:30:52 +00:00
, progressMap = progressMap'
, nextProgressKey = nextProgressKey'
2014-04-09 11:38:54 +00:00
}
2014-04-09 07:52:04 +00:00
-- Perform database migration using our application's logging settings.
runLoggingT
(Database.Persist.runPool dbconf (runMigration migrateAll) p)
(messageLoggerSource foundation logger)
-- Start the cabal file loader
2014-06-01 12:08:10 +00:00
void $ forkIO $ forever $ flip runLoggingT (messageLoggerSource foundation logger) $ do
2014-05-14 05:46:02 +00:00
$logInfoS "CLEANUP" "Cleaning up /tmp"
2014-05-14 05:28:00 +00:00
now <- liftIO getCurrentTime
runResourceT $ sourceDirectory "/tmp" $$ mapM_C (cleanupTemp now)
2014-05-14 05:46:02 +00:00
$logInfoS "CLEANUP" "Cleaning up complete"
2014-05-14 05:28:00 +00:00
2014-04-16 12:29:24 +00:00
--when development $ liftIO $ threadDelay $ 5 * 60 * 1000000
2014-04-13 05:48:58 +00:00
eres <- tryAny $ flip runReaderT foundation $ do
2014-04-16 12:29:24 +00:00
let runDB' :: SqlPersistT (ResourceT (ReaderT App (LoggingT IO))) a
-> ReaderT App (LoggingT IO) a
runDB' = runResourceT . flip (Database.Persist.runPool dbconf) p
uploadHistory0 <- runDB' $ selectSource [] [] $$ sinkUploadHistory
UploadState uploadHistory newUploads <- loadCabalFiles uploadHistory0
runDB' $ mapM_ insert_ newUploads
2014-04-13 05:48:58 +00:00
let views =
2014-04-16 12:29:24 +00:00
[ ("pvp", viewPVP uploadHistory)
2014-04-13 05:48:58 +00:00
, ("no-bounds", viewNoBounds)
, ("unchanged", viewUnchanged)
]
forM_ views $ \(name, func) ->
runResourceT $ flip (Database.Persist.runPool dbconf) p $ createView
name
func
2014-04-16 12:29:24 +00:00
(sourceHistory uploadHistory)
2014-04-13 05:48:58 +00:00
(storeWrite $ HackageViewIndex name)
case eres of
Left e -> $logError $ tshow e
Right () -> return ()
2014-06-01 12:08:10 +00:00
liftIO $ threadDelay $ 30 * 60 * 1000000
2014-04-09 07:52:04 +00:00
return foundation
2014-05-14 05:28:00 +00:00
cleanupTemp :: UTCTime -> FilePath -> ResourceT (LoggingT IO) ()
cleanupTemp now fp
| any (`isPrefixOf` name) prefixes = handleAny ($logError . tshow) $ do
modified <- liftIO $ getModified fp
2014-05-14 05:46:02 +00:00
if (diffUTCTime now modified > 60 * 60)
then do
$logInfoS "CLEANUP" $ "Removing temp directory: " ++ fpToText fp
2014-05-14 05:28:00 +00:00
liftIO $ removeTree fp
2014-05-14 05:46:02 +00:00
$logInfoS "CLEANUP" $ "Temp directory deleted: " ++ fpToText fp
else $logInfoS "CLEANUP" $ "Ignoring recent entry: " ++ fpToText fp
| otherwise = $logInfoS "CLEANUP" $ "Ignoring unmatched path: " ++ fpToText fp
2014-05-14 05:28:00 +00:00
where
name = fpToText $ filename fp
prefixes = asVector $ pack
[ "hackage-index"
, "createview"
, "build00index."
, "newindex"
]
2014-04-13 05:48:58 +00:00
instance MonadActive m => MonadActive (SqlPersistT m) where -- FIXME orphan upstream
monadActive = lift monadActive
instance MonadReader env m => MonadReader env (SqlPersistT m) where
ask = lift ask
local f m =
do stT <- liftWith (\run -> local f (run m))
restoreT (return stT)
2014-04-13 05:48:58 +00:00
2014-04-09 07:52:04 +00:00
-- for yesod devel
getApplicationDev :: Bool -> IO (Int, Application)
getApplicationDev useEcho =
defaultDevelApp loader (fmap fst . makeApplication useEcho)
2014-04-09 07:52:04 +00:00
where
loader = Yesod.Default.Config.loadConfig (configSettings Development)
{ csParseExtra = parseExtra
}