{-# LANGUAGE OverloadedStrings #-} module Breve.Settings where import Control.Monad (when) import System.Environment (lookupEnv) import System.Environment.XDG.BaseDir import System.Directory (doesFileExist) import Data.Text (Text, pack) import Data.Configurator import Data.Monoid import Network.Wai.Handler.WarpTLS (TLSSettings (..), tlsSettingsChain) import Network.TLS (Version (..)) import Network.TLS.Extra (ciphersuite_strong) data AppSettings = AppSettings { bindHost :: Text , bindPort :: Int , bindUrl :: Text , urlTable :: FilePath , tlsSettings :: TLSSettings } createEmptyIfMissing :: FilePath -> IO () createEmptyIfMissing file = do exists <- doesFileExist file when (not exists) (writeFile file "") settings :: IO AppSettings settings = do urlsPath <- getUserDataFile "breve" "" configPath <- getUserConfigFile "breve" "" config <- load [Required configPath] host <- lookupDefault "localhost" config "hostname" port <- lookupDefault 3000 config "port" urls <- lookupDefault urlsPath config "urltable" cert <- lookupDefault "/usr/share/tls/breve.crt" config "tls.cert" key <- lookupDefault "/usr/share/tls/breve.key" config "tls.key" chain <- lookupDefault [] config "tls.chain" createEmptyIfMissing urls let base = "https://" <> host url = if port == 443 then base else base <> ":" <> pack (show port) tls = (tlsSettingsChain cert chain key) { tlsAllowedVersions = [TLS12, TLS11] , tlsCiphers = ciphersuite_strong } return AppSettings { bindHost = host , bindPort = port , bindUrl = url <> "/" , urlTable = urls , tlsSettings = tls }