{-# LANGUAGE MultiParamTypeClasses, OverloadedStrings #-} module Breve.Common where import Paths_breve (getDataFileName) import Control.Monad.IO.Class (liftIO) import Control.Monad (when) import Text.Printf (printf) import System.Environment (lookupEnv) import System.Environment.XDG.BaseDir import System.Directory (doesFileExist) import Data.Configurator import Web.Simple.Templates import Network.Wai.Handler.Warp data ServerSettings = ServerSettings { bindHostname :: String , bindPort :: Int , bindUrl :: String , urlTable :: FilePath , warpSettings :: Settings } data AppSettings = AppSettings {} instance HasTemplates IO AppSettings where defaultLayout = do main <- liftIO (getDataFileName "static/main.html") Just <$> getTemplate main createEmptyIfMissing :: FilePath -> IO () createEmptyIfMissing file = do exists <- doesFileExist file when (not exists) (writeFile file "") newAppSettings :: IO AppSettings newAppSettings = return AppSettings newServerSettings :: IO ServerSettings newServerSettings = 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 return ServerSettings { bindHostname = host , bindPort = port , bindUrl = if port == 80 then printf "http://%s/" host else printf "http://%s:%d/" host port , urlTable = urls , warpSettings = setPort port defaultSettings }