sampu/src/Core/HTTP.hs

47 lines
1.5 KiB
Haskell

module Core.HTTP where
import qualified Core.Configuration as Conf
import qualified Core.Handlers as Handle
import Control.Monad ( mapM_ )
import Data.String ( fromString )
import Network.Wai.Handler.Warp ( Port, run )
import Network.Wai.Middleware.RequestLogger ( logStdout, logStdoutDev )
import Network.Wai.Middleware.Static ( staticPolicy, noDots, addBase, (>->) )
import System.FilePath ( takeFileName )
import Web.Twain
-- Get the port to listen on from the ENV and start the webserver.
main :: IO ()
main = do
port <- Conf.port
let app = preProcessors
++ routes
++ postProcessors
run (read port) $
foldr ($) (notFound Handle.missing) app
-- These Middlewares are executed before any routes are reached.
preProcessors :: [Middleware]
preProcessors = [ logStdoutDev
, staticPolicy (noDots >-> addBase "data/assets/public")
]
-- These Middlewares are executed after all other routes are exhausted
postProcessors :: [Middleware]
postProcessors = []
-- Core routes expressed as a list of WAI Middlewares.
routes :: [Middleware]
routes =
[ get "/" Handle.index
, get "/style.css" Handle.theme
, get "/posts" Handle.postsIndex
, get "/posts/:name" Handle.posts
, get "/contact" Handle.contact
, get "/atom.xml" Handle.feed
, get "/feed" Handle.feed
]