{-# 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.Configurator import Data.Monoid data AppSettings = AppSettings { bindPort :: Int , bindUrl :: String , urlTable :: FilePath } 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" createEmptyIfMissing urls let base = "http://" <> host url = if port == 80 then base else base <> ":" <> show port return AppSettings { bindPort = port , bindUrl = url <> "/" , urlTable = urls }