stackage-server/Foundation.hs

300 lines
12 KiB
Haskell
Raw Normal View History

2014-04-09 07:52:04 +00:00
module Foundation where
2014-06-03 13:10:35 +00:00
import ClassyPrelude.Yesod
import Data.BlobStore
import Data.Slug (safeMakeSlug, HasGenIO (getGenIO), randomSlug, Slug, SnapSlug)
2014-12-09 12:01:38 +00:00
import Data.WebsiteContent
2014-04-09 07:52:04 +00:00
import qualified Database.Persist
import Database.Persist.Sql (PersistentSqlException (Couldn'tGetSQLConnection))
2014-06-03 13:10:35 +00:00
import Model
import qualified Settings
2014-11-27 12:08:18 +00:00
import Settings (widgetFile, Extra (..), GoogleAuth (..))
2014-06-03 13:10:35 +00:00
import Settings.Development (development)
import Settings.StaticFiles
2014-04-09 11:38:54 +00:00
import qualified System.Random.MWC as MWC
2014-12-14 19:18:40 +00:00
import Text.Blaze
2014-06-03 13:10:35 +00:00
import Text.Hamlet (hamletFile)
import Text.Jasmine (minifym)
import Types
import Yesod.Auth
import Yesod.Auth.BrowserId
2014-11-27 12:08:18 +00:00
import Yesod.Auth.GoogleEmail2
2014-10-23 04:33:39 +00:00
import Yesod.Core.Types (Logger, GWData)
2014-06-03 13:10:35 +00:00
import Yesod.Default.Config
import Yesod.Default.Util (addStaticContentExternal)
2014-12-09 12:01:38 +00:00
import Yesod.GitRepo
2015-03-22 14:16:28 +00:00
import Stackage.Types
2014-04-09 07:52:04 +00:00
-- | The site argument for your application. This can be a good place to
-- keep settings and values requiring initialization before your application
-- starts running, such as database connections. Every handler will have
-- access to the data present here.
data App = App
{ settings :: AppConfig DefaultEnv Extra
, getStatic :: Static -- ^ Settings for static file serving.
, connPool :: Database.Persist.PersistConfigPool Settings.PersistConf -- ^ Database connection pool.
, httpManager :: Manager
, persistConfig :: Settings.PersistConf
, appLogger :: Logger
, genIO :: MWC.GenIO
, blobStore :: BlobStore StoreKey
, haddockRootDir :: FilePath
2015-01-04 14:43:11 +00:00
, appDocUnpacker :: DocUnpacker
2014-10-20 11:46:57 +00:00
-- ^ We have a dedicated thread so that (1) we don't try to unpack too many
-- things at once, (2) we never unpack the same thing twice at the same
-- time, and (3) so that even if the client connection dies, we finish the
-- unpack job.
, widgetCache :: IORef (HashMap Text (UTCTime, GWData (Route App)))
2014-12-09 12:01:38 +00:00
, websiteContent :: GitRepo WebsiteContent
2014-04-09 07:52:04 +00:00
}
2015-01-04 14:43:11 +00:00
data DocUnpacker = DocUnpacker
{ duRequestDocs :: Entity Stackage -> IO UnpackStatus
, duGetStatus :: IO Text
, duForceReload :: Entity Stackage -> IO ()
}
2014-04-17 17:30:52 +00:00
data Progress = ProgressWorking !Text
| ProgressDone !Text !(Route App)
instance HasBlobStore App StoreKey where
getBlobStore = blobStore
2014-04-09 11:38:54 +00:00
instance HasGenIO App where
getGenIO = genIO
2014-04-09 07:52:04 +00:00
instance HasHttpManager App where
getHttpManager = httpManager
instance HasHackageRoot App where
getHackageRoot = hackageRoot . appExtra . settings
2014-04-09 07:52:04 +00:00
-- This is where we define all of the routes in our application. For a full
-- explanation of the syntax, please see:
-- http://www.yesodweb.com/book/routing-and-handlers
--
-- Note that this is really half the story; in Application.hs, mkYesodDispatch
-- generates the rest of the code. Please see the linked documentation for an
-- explanation for this split.
mkYesodData "App" $(parseRoutesFile "config/routes")
2014-04-17 17:30:52 +00:00
deriving instance Show Progress
2014-04-09 07:52:04 +00:00
type Form x = Html -> MForm (HandlerT App IO) (FormResult x, Widget)
defaultLayoutNoContainer :: Widget -> Handler Html
defaultLayoutNoContainer = defaultLayoutWithContainer False
defaultLayoutWithContainer :: Bool -> Widget -> Handler Html
defaultLayoutWithContainer insideContainer widget = do
mmsg <- getMessage
muser <- catch maybeAuth $ \e -> case e of
Couldn'tGetSQLConnection -> return Nothing
_ -> throwM e
-- We break up the default layout into two components:
-- default-layout is the contents of the body tag, and
-- default-layout-wrapper is the entire page. Since the final
-- value passed to hamletToRepHtml cannot be a widget, this allows
-- you to use normal widget features in default-layout.
cur <- getCurrentRoute
pc <- widgetToPageContent $ do
$(combineStylesheets 'StaticR
[ css_normalize_css
, css_bootstrap_css
, css_bootstrap_responsive_css
])
$((combineScripts 'StaticR
[ js_jquery_js
, js_bootstrap_js
]))
$(widgetFile "default-layout")
mcurr <- getCurrentRoute
let notHome = mcurr /= Just HomeR
withUrlRenderer $(hamletFile "templates/default-layout-wrapper.hamlet")
2014-04-09 07:52:04 +00:00
-- Please see the documentation for the Yesod typeclass. There are a number
-- of settings which can be configured by overriding methods here.
instance Yesod App where
approot = ApprootMaster $ appRoot . settings
-- Store session data on the client in encrypted cookies,
-- default session idle timeout is 120 minutes
makeSessionBackend _ = fmap Just $ defaultClientSessionBackend
(120 * 60) -- 120 minutes
"config/client_session_key.aes"
defaultLayout = defaultLayoutWithContainer True
2014-04-09 07:52:04 +00:00
-- Ideally we would just have an approot that always includes https, and
-- redirect users from non-SSL to SSL connections. However, cabal-install
-- is broken, and does not support TLS. Therefore, we *don't* force the
-- redirect.
--
-- Nonetheless, we want to keep generated links as https:// links. The
-- problem is that sometimes CORS kicks in and breaks a static resource
-- when loading from a non-secure page. So we have this ugly hack: whenever
-- the destination is a static file, don't include the scheme or hostname.
urlRenderOverride y (StaticR s) =
Just $ uncurry (joinPath y "") $ renderRoute s
urlRenderOverride _ _ = Nothing
2014-04-09 07:52:04 +00:00
-- The page to be redirected to when authentication is required.
authRoute _ = Just $ AuthR LoginR
{- Temporarily disable to allow for horizontal scaling
2014-04-09 07:52:04 +00:00
-- This function creates static content files in the static folder
-- and names them based on a hash of their content. This allows
-- expiration dates to be set far in the future without worry of
-- users receiving stale content.
addStaticContent =
addStaticContentExternal minifym genFileName Settings.staticDir (StaticR . flip StaticRoute [])
where
-- Generate a unique filename based on the content itself
genFileName lbs
| development = "autogen-" ++ base64md5 lbs
| otherwise = base64md5 lbs
-}
2014-04-09 07:52:04 +00:00
-- Place Javascript at bottom of the body tag so the rest of the page loads first
jsLoader _ = BottomOfBody
-- What messages should be logged. The following includes all messages when
-- in development, and warnings and errors in production.
2014-10-23 18:19:22 +00:00
shouldLog _ "CLEANUP" _ = False
2014-05-14 05:46:02 +00:00
shouldLog _ source level =
development || level == LevelWarn || level == LevelError || source == "CLEANUP"
2014-04-09 07:52:04 +00:00
makeLogger = return . appLogger
2014-04-17 09:09:44 +00:00
maximumContentLength _ (Just UploadStackageR) = Just 50000000
2014-10-20 12:43:23 +00:00
maximumContentLength _ (Just UploadHaddockR{}) = Just 100000000
2015-03-16 09:40:44 +00:00
maximumContentLength _ (Just UploadV2R) = Just 100000000
2014-04-17 09:09:44 +00:00
maximumContentLength _ _ = Just 2000000
2014-12-14 19:18:40 +00:00
instance ToMarkup (Route App) where
2014-12-15 13:44:12 +00:00
toMarkup c =
case c of
AllSnapshotsR{} -> "Snapshots"
UploadStackageR{} -> "Upload"
AuthR (LoginR{}) -> "Login"
_ -> ""
2014-12-14 19:18:40 +00:00
2014-04-09 07:52:04 +00:00
-- How to run database actions.
instance YesodPersist App where
2014-11-18 16:09:25 +00:00
type YesodPersistBackend App = SqlBackend
2014-04-09 07:52:04 +00:00
runDB = defaultRunDB persistConfig connPool
instance YesodPersistRunner App where
getDBRunner = defaultGetDBRunner connPool
instance YesodAuth App where
type AuthId App = UserId
-- Where to send a user after successful login
loginDest _ = HomeR
-- Where to send a user after logout
logoutDest _ = HomeR
2014-11-11 16:50:09 +00:00
redirectToReferer _ = True
2014-04-09 11:38:54 +00:00
getAuthId creds = do
muid <- maybeAuthId
join $ runDB $ case muid of
2014-04-09 07:52:04 +00:00
Nothing -> do
2014-04-09 11:38:54 +00:00
x <- getBy $ UniqueEmail $ credsIdent creds
case x of
Just (Entity _ email) -> return $ return $ Just $ emailUser email
Nothing -> do
handle' <- getHandle (0 :: Int)
token <- getToken
userid <- insert User
{ userHandle = handle'
, userDisplay = credsIdent creds
, userToken = token
}
void $ insert Email
{ emailEmail = credsIdent creds
, emailUser = userid
}
return $ return $ Just userid
Just uid -> do
memail <- getBy $ UniqueEmail $ credsIdent creds
case memail of
Nothing -> do
void $ insert Email
{ emailEmail = credsIdent creds
, emailUser = uid
}
return $ do
setMessage $ toHtml $ concat
[ "Email address "
, credsIdent creds
, " added to your account."
]
redirect ProfileR
2014-12-15 13:17:10 +00:00
Just (Entity _ email)
| emailUser email == uid -> return $ do
setMessage $ toHtml $ concat
[ "The email address "
, credsIdent creds
, " is already part of your account"
]
redirect ProfileR
| otherwise -> invalidArgs $ return $ concat
[ "The email address "
, credsIdent creds
, " is already associated with a different account."
]
2014-04-09 11:38:54 +00:00
where
handleBase = takeWhile (/= '@') (credsIdent creds)
getHandle cnt | cnt > 50 = error "Could not get a unique slug"
getHandle cnt = do
slug <- lift $ safeMakeSlug handleBase (cnt > 0)
muser <- getBy $ UniqueHandle slug
case muser of
Nothing -> return slug
Just _ -> getHandle (cnt + 1)
2014-04-09 07:52:04 +00:00
-- You can add other plugins like BrowserID, email or OAuth here
2014-11-27 12:08:18 +00:00
authPlugins app =
authBrowserId def : google
where
google =
case googleAuth $ appExtra $ settings app of
Nothing -> []
Just GoogleAuth {..} -> [authGoogleEmail gaClientId gaClientSecret]
2014-04-09 07:52:04 +00:00
authHttpManager = httpManager
2014-11-18 16:09:25 +00:00
instance YesodAuthPersist App
2014-04-09 07:52:04 +00:00
2014-04-09 11:38:54 +00:00
getToken :: YesodDB App Slug
getToken =
go (0 :: Int)
where
go cnt | cnt > 50 = error "Could not get a unique token"
go cnt = do
slug <- lift $ randomSlug 25
muser <- getBy $ UniqueToken slug
case muser of
Nothing -> return slug
Just _ -> go (cnt + 1)
2014-04-09 07:52:04 +00:00
-- This instance is required to use forms. You can modify renderMessage to
-- achieve customized and internationalized form validation messages.
instance RenderMessage App FormMessage where
renderMessage _ _ = defaultFormMessage
-- | Get the 'Extra' value, used to hold data from the settings.yml file.
getExtra :: Handler Extra
getExtra = fmap (appExtra . settings) getYesod
-- Note: previous versions of the scaffolding included a deliver function to
-- send emails. Unfortunately, there are too many different options for us to
-- give a reasonable default. Instead, the information is available on the
-- wiki:
--
-- https://github.com/yesodweb/yesod/wiki/Sending-email