stackage-server/Foundation.hs

166 lines
6.4 KiB
Haskell
Raw Permalink 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
2015-10-06 10:03:31 +00:00
import Data.Slug (HasGenIO (getGenIO))
2014-12-09 12:01:38 +00:00
import Data.WebsiteContent
import Settings (widgetFile, Extra (..))
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 Types
import Yesod.Core.Types (Logger)
2014-06-03 13:10:35 +00:00
import Yesod.Default.Config
2015-10-11 11:16:10 +00:00
import Yesod.AtomFeed
2014-12-09 12:01:38 +00:00
import Yesod.GitRepo
2015-05-11 17:23:09 +00:00
import Stackage.Database
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.
, httpManager :: Manager
, appLogger :: Logger
, genIO :: MWC.GenIO
2014-12-09 12:01:38 +00:00
, websiteContent :: GitRepo WebsiteContent
, stackageDatabase :: IO StackageDatabase
, latestStackMatcher :: IO (Text -> Maybe Text)
-- ^ Give a pattern, get a URL
2016-05-08 08:39:19 +00:00
, appHoogleLock :: MVar ()
-- ^ Avoid concurrent Hoogle queries, see
-- https://github.com/fpco/stackage-server/issues/172
2014-04-09 07:52:04 +00:00
}
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
-- 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")
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
-- 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
]))
2015-10-11 11:16:10 +00:00
atomLink FeedR "Recent Stackage snapshots"
$(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.
2015-03-26 12:28:14 +00:00
urlRenderOverride y route@StaticR{} =
Just $ uncurry (joinPath y "") $ renderRoute route
urlRenderOverride _ _ = Nothing
{- 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 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"
_ -> ""
2014-12-14 19:18:40 +00:00
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
2015-05-11 17:23:09 +00:00
2015-05-12 08:42:19 +00:00
instance GetStackageDatabase Handler where
getStackageDatabase = getYesod >>= liftIO . stackageDatabase
2015-05-12 08:42:19 +00:00
instance GetStackageDatabase (WidgetT App IO) where
getStackageDatabase = getYesod >>= liftIO . stackageDatabase