{-# LANGUAGE ScopedTypeVariables, OverloadedStrings, ViewPatterns, RecordWildCards, DeriveFunctor #-}
module General.Web(
Input(..),
Output(..), readInput, server
) where
import Network.Wai.Handler.Warp hiding (Port, Handle)
import Network.Wai.Handler.WarpTLS
import Action.CmdLine
import Network.Wai.Logger
import Network.Wai
import Control.DeepSeq
import Network.HTTP.Types (parseQuery, decodePathSegments)
import Network.HTTP.Types.Status
import qualified Data.Text as Text
import qualified Data.ByteString.Char8 as BS
import qualified Data.ByteString.Lazy.Char8 as LBS
import Data.List.Extra
import Data.Aeson.Encoding
import Data.Char
import Data.String
import Data.Tuple.Extra
import Data.Maybe
import Data.Monoid
import System.FilePath
import Control.Exception.Extra
import System.Time.Extra
import General.Log
import Prelude
import qualified Data.ByteString.UTF8 as UTF8
data Input = Input
{inputURL :: [String]
,inputArgs :: [(String, String)]
} deriving Show
readInput :: String -> Maybe Input
readInput (breakOn "?" -> (a,b)) =
if (badPath path || badArgs args) then Nothing else Just $ Input path args
where
path = parsePath a
parsePath = map Text.unpack
. decodePathSegments
. BS.pack
badPath = any (all (== '.')) . filter (/= "")
args = parseArgs b
parseArgs = map (UTF8.toString *** maybe "" UTF8.toString)
. parseQuery
. UTF8.fromString
badArgs = not . all (all isLower . fst)
data Output
= OutputText LBS.ByteString
| OutputHTML LBS.ByteString
| OutputJavascript LBS.ByteString
| OutputJSON Encoding
| OutputFail LBS.ByteString
| OutputFile FilePath
deriving Show
forceBS :: Output -> LBS.ByteString
forceBS (OutputText x) = force x
forceBS (OutputJSON x) = force $ encodingToLazyByteString x
forceBS (OutputHTML x) = force x
forceBS (OutputJavascript x) = force x
forceBS (OutputFail x) = force x
forceBS (OutputFile x) = rnf x `seq` LBS.empty
instance NFData Output where
rnf x = forceBS x `seq` ()
server :: Log -> CmdLine -> (Input -> IO Output) -> IO ()
server log Server{..} act = do
let
host' = fromString $
if host == "" then
if local then
"127.0.0.1"
else
"*"
else
host
set = setOnExceptionResponse exceptionResponseForDebug
. setHost host'
. setPort port $
defaultSettings
runServer :: Application -> IO ()
runServer = if https then runTLS (tlsSettings cert key) set
else runSettings set
secH = if no_security_headers then []
else [
("Content-Security-Policy",
"default-src 'self';"
<> " script-src 'self' https://code.jquery.com/ https://rawcdn.githack.com;"
<> " style-src 'self' 'unsafe-inline' https://rawcdn.githack.com;"
<> " img-src 'self' https://rawcdn.githack.com;"
<> " frame-ancestors 'self';"
<> " form-action 'self';"
<> " upgrade-insecure-requests;"
<> " block-all-mixed-content"),
("X-Frame-Options", "sameorigin"),
("X-Content-Type-Options", "nosniff"),
("X-XSS-Protection", "1; mode=block"),
("Referrer-Policy", "no-referrer-when-downgrade"),
("Strict-Transport-Security", "max-age=31536000; includeSubDomains")]
logAddMessage log $ "Server starting on port " ++ show port ++ " and host/IP " ++ show host'
runServer $ \req reply -> do
let pq = BS.unpack $ rawPathInfo req <> rawQueryString req
putStrLn pq
(time, res) <- duration $ case readInput pq of
Nothing -> pure $ Right (OutputFail "", LBS.pack $ "Bad URL: " ++ pq)
Just pay ->
handle_ (fmap Left . showException) $ do
s <- act pay; bs <- evaluate $ forceBS s; pure $ Right (s, bs)
logAddEntry log (showSockAddr $ remoteHost req) pq time (either Just (const Nothing) res)
case res of
Left s -> reply $ responseLBS status500 [] $ LBS.pack s
Right (v, bs) -> reply $ case v of
OutputFile file -> responseFile status200
([("content-type",c) | Just c <- [lookup (takeExtension file) contentType]] ++ secH) file Nothing
OutputText{} -> responseLBS status200 (("content-type","text/plain") : secH) bs
OutputJSON{} -> responseLBS status200 (("content-type","application/json") : ("access-control-allow-origin","*") : secH) bs
OutputFail{} -> responseLBS status400 (("content-type","text/plain") : secH) bs
OutputHTML{} -> responseLBS status200 (("content-type","text/html") : secH) bs
OutputJavascript{} -> responseLBS status200 (("content-type","text/javascript") : secH) bs
contentType = [(".html","text/html"),(".css","text/css"),(".js","text/javascript")]