{-# LANGUAGE
    CPP
  , OverloadedStrings
  , UnicodeSyntax
  #-}
-- |Configurations for the Lucu httpd.
module Network.HTTP.Lucu.Config
    ( Config(..)
#if defined(HAVE_SSL)
    , SSLConfig(..)
#endif
    )
    where
import Data.Ascii (Ascii)
import Data.CaseInsensitive (CI)
import qualified Data.CaseInsensitive as CI
import Data.Convertible.Base
import Data.Convertible.Instances.Text ()
import Data.Default
import Data.Text (Text)
import Network
import Network.BSD
import Network.HTTP.Lucu.MIMEType.Guess
import Network.HTTP.Lucu.MIMEType.DefaultExtensionMap
#if defined(HAVE_SSL)
import OpenSSL.Session
#endif
import Prelude.Unicode
import System.IO.Unsafe

-- |Configuration record for to run the httpd.
data Config = Config {

    -- |A banner string to be sent to clients with \"Server\" response
    -- header field.
      cnfServerSoftware  !Ascii

    -- |The host name of the server. This value will be used in
    -- built-in pages like \"404 Not Found\".
    , cnfServerHost  !(CI Text)

    -- |A port number (or a service name) to listen to HTTP clients.
    , cnfServerPort  !ServiceName

    -- |Local IPv4 address to listen to both HTTP and HTTPS
    -- clients. Set this to @('Just' "0.0.0.0")@ if you want to accept
    -- any IPv4 connections. Set this to 'Nothing' to disable IPv4.
    , cnfServerV4Addr  !(Maybe HostName)

    -- |Local IPv6 address to listen to both HTTP and HTTPS
    -- clients. Set this to @('Just' "::")@ if you want to accept any
    -- IPv6 connections. Set this to 'Nothing' to disable IPv6. Note
    -- that there is currently no ways to assign separate ports to
    -- IPv4 and IPv6 server sockets (but I don't think that will be a
    -- problem.)
    , cnfServerV6Addr  !(Maybe HostName)

#if defined(HAVE_SSL)
    -- |Configuration for HTTPS connections. Set this 'Nothing' to
    -- disable HTTPS.
    , cnfSSLConfig  !(Maybe SSLConfig)
#endif

    -- |The maximum number of requests to simultaneously accept in one
    -- connection. If a client exceeds this limitation, its last
    -- request won't be processed until a response for its earliest
    -- pending request is sent back to the client.
    , cnfMaxPipelineDepth  !Int

    -- |The maximum length of request entity to accept in octets. Note
    -- that this is nothing but a default value used by
    -- 'Network.HTTP.Lucu.Resource.getForm' and such when they are
    -- applied to 'Nothing', so there is no guarantee that this value
    -- always constrains all the requests.
    , cnfMaxEntityLength  !Int

    -- |Whether to dump too late abortions to the stderr or not. See
    -- 'Network.HTTP.Lucu.Abortion.abort'.
    , cnfDumpTooLateAbortionToStderr  !Bool

    -- |A mapping table from file extensions to MIME Types. This value
    -- is used by 'Network.HTTP.Lucu.StaticFile.staticFile' to guess
    -- the MIME Type of static files. Note that MIME Types are
    -- currently guessed only by file name.
    -- 
    -- Guessing by file magic might be a good idea but that's not
    -- implemented (yet).
    , cnfExtToMIMEType  !ExtMap
    }

#if defined(HAVE_SSL)
-- |Configuration record for HTTPS connections.
data SSLConfig
    = SSLConfig {
        -- |A port number (or a service name) to listen to HTTPS
        -- clients. Local addresses (both for IPv4 and IPv6) will be
        -- derived from the parent 'Config'.
        sslServerPort  !ServiceName

        -- |An SSL context for accepting connections. You must set it
        -- up yourself with at least a server certification.
      , sslContext  !SSLContext
      }
#endif

-- |The default configuration. Generally you can use this value as-is,
-- or possibly you just want to replace the 'cnfServerSoftware' and
-- 'cnfServerPort'. SSL connections are disabled by default.
instance Default Config where
    def = Config {
            cnfServerSoftware              = "Lucu/1.0"
          , cnfServerHost                  = CI.mk  cs $ unsafePerformIO getHostName
          , cnfServerPort                  = "http"
          , cnfServerV4Addr                = Just "0.0.0.0"
          , cnfServerV6Addr                = Just "::"
#if defined(HAVE_SSL)
          , cnfSSLConfig                   = Nothing
#endif
          , cnfMaxPipelineDepth            = 100
          , cnfMaxEntityLength             = 16 * 1024 * 1024 -- 16 MiB
          , cnfDumpTooLateAbortionToStderr = True
          , cnfExtToMIMEType               = defaultExtensionMap
          }