{-# 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 :: Maybe FilePath -> IO AppSettings settings path = do configPath <- case path of Just path -> return path Nothing -> getUserConfigFile "breve" "" urlsPath <- getUserDataFile "breve" "" config <- load [Required configPath] host <- lookupDefault "localhost" config "hostname" portnum <- 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" let port = if portnum == 443 then "" else ":" <> pack (show portnum) url = "https://" <> host <> port <> "/" baseURL <- lookupDefault url config "baseurl" createEmptyIfMissing urls return AppSettings { bindHost = host , bindPort = portnum , bindUrl = baseURL , urlTable = urls , tlsSettings = (tlsSettingsChain cert chain key) { tlsAllowedVersions = [TLS12, TLS11] , tlsCiphers = ciphersuite_strong } }