wai-enforce-https-0.0.2.1: Enforce HTTPS in Wai server app safely.

Copyright(c) Marek Fajkus
LicenseBSD3
Maintainermarek.faj@gmail.com
Safe HaskellNone
LanguageHaskell2010

Network.Wai.Middleware.EnforceHTTPS

Contents

Description

Wai Middleware for enforcing encrypted HTTPS connection safely.

This module is intended to be imported qualified

import qualified Network.Wai.Middleware.EnforceHTTPS as EnforceHTTPS

Example Usage

Following is the most typical config. That is GCP, AWS and Heroku compatible setting using x-forwarded-proto header check and default configuration.

{-# LANGUAGE OverloadedStrings #-}

module Main where

import           Network.HTTP.Types                  (status200)
import           Network.Wai                         (Application, responseLBS)
import           Network.Wai.Handler.Warp            (runEnv)

import qualified Network.Wai.Middleware.EnforceHTTPS as EnforceHTTPS

handler :: Application
handler _ respond = respond $
    responseLBS status200 [] "Hello from behind proxy"

app :: Application
app = EnforceHTTPS.withResolver EnforceHTTPS.xForwardedProto handler

main :: IO ()
main = runEnv 8080 app
Synopsis

Configuration and Initialization

data EnforceHTTPSConfig Source #

Configuration

EnforceHTTPSConfig does export constructor which should not collide with any other functions and therefore can be exposed in import

import Network.Wai.Middleware.EnforceHTTPS (EnforceHTTPSConfig(..))

Default configuration is recommended but you're free to override any default value if you need to.

Configuration of httpsIsSecure can be set using withResolver function which is preferred way for overwriting default Resolver.

defaultConfig :: EnforceHTTPSConfig Source #

Default Configuration Default resolver is proxy to isSecure function

  • uses request Host header information to resolve hostname
  • standard HTTPS port 443
  • redirect includes path and url params
  • uses permanent redirect (301)
  • doesn't include port in Location header id port is 443
  • redirects GET and HEAD methods
  • all other methods are resolved with 405 (Method not Allowed) and with appropriate Allowed header

def :: Middleware Source #

Middleware with default configuration. See defaultConfig for more details.

withResolver :: HTTPSResolver -> Middleware Source #

Construct middleware with provided Resolver See `Provided Resolvers` section for more information.

Provided Resolvers

This module provides most common implementation of rrsolvers used by various cloud providers and reverse proxy implemetations.

type HTTPSResolver = Request -> Bool Source #

Resolvers are function used for testing if Request is made over secure HTTPS protocol.

if True is returned from a Resolver function, request is considered to be secure. In case of False value, redirect logic is called.

xForwardedProto :: HTTPSResolver Source #

Resolver checking value of x-forwarded-proto HTTP header. This header is for instance used by Heroku or GCP Ingress among many others.

Request is secure if value of header is https otherwise request is considered not being secure.

azure :: HTTPSResolver Source #

Azure is proxying with additional `x-arr-ssl` header if original protocol is HTTPS. This resolver checks for the presence of this header.

forwarded :: HTTPSResolver Source #

Forwarded HTTP header is relatively new standard which should replaced all x-* adhoc headers by standardized one. This resolver is using proto=foo part of the header and check for equality with https value.

More information can be found on MDN Complete implementation of Forwarded is located in Network.HTTP.Forwarded module

customProtoHeader :: ByteString -> HTTPSResolver Source #

Some reverse proxies (Kong) are using values similar to x-forwarded-proto but are using different headers. This resolver allows you to specify name of header which should be used for the check. Like xForwardedProto, request is considered as being secure if value of header is https.