aboutsummaryrefslogtreecommitdiff
path: root/src/Config.hs
blob: 12fc09d8c0109b31a541bc8a62133a0fc3dc3467 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
{-# LANGUAGE OverloadedStrings, LambdaCase, TemplateHaskell #-}

module Config (
    Config(..),
    getConfig,
    makeOpenSearch,
    sendEmail
) where

import Prelude hiding (lookup)

import Control.Applicative ((<|>))
import Control.Monad.IO.Class (MonadIO, liftIO)
import Control.Monad.Logger (MonadLogger, logInfo, logWarn, logError)
import Data.Aeson.KeyMap (empty, lookup)
import Data.Functor ((<&>))
import Data.Maybe (fromMaybe)
import Data.String (fromString, IsString)
import Data.Text (Text, pack)
import Data.Yaml
import Network.Wai.Handler.Warp (HostPreference)
import System.Environment (lookupEnv)
import System.Exit (ExitCode(..))
import System.Process (proc, createProcess, waitForProcess)

data Config = Config {
    confPort :: Int,
    confHost :: HostPreference,
    confBaseUrl :: Text,
    confFavicon :: Text,
    confDbPath :: Text,
    confUser :: Text,
    confPwHash :: Text,
    confEmailCmd :: Maybe FilePath,
    confAdminEmail :: String
} deriving (Show, Eq)

getConfig :: IO Config
getConfig = do
    confFile <- decodeFileEither "fastbangs.yaml" <&> \case
        Right ob -> ob
        Left _ -> empty

    Config
        <$> (read <$> resolveVal (lookup "port" confFile) "PORT" "20546")
        <*> resolveVal (lookup "bind-addr"     confFile) "BIND_ADDR"     "*6"
        <*> resolveVal (lookup "base-url"      confFile) "BASE_URL"      "http://localhost:20546"
        <*> resolveVal (lookup "favicon-url"   confFile) "FAVICON_URL"   ""
        <*> resolveVal (lookup "db-path"       confFile) "DB_PATH"       "banger.db"
        <*> resolveVal (lookup "admin-user"    confFile) "ADMIN_USER"    "bleb"
        <*> resolveVal (lookup "admin-pw-hash" confFile) "ADMIN_PW_HASH" "" -- prevent login without manual pw
        <*> fmap (<|> lookup "email-command" confFile) (lookupEnv "EMAIL_CMD")
        <*> resolveVal (lookup "admin-email" confFile) "ADMIN_EMAIL" ""

  where resolveVal :: IsString s => Maybe String -> String -> String -> IO s
        resolveVal mayConf q def = do
            mayEnv <- lookupEnv q
            return $ fromString $ fromMaybe def $ mayEnv <|> mayConf

makeOpenSearch :: Config -> Maybe Text -> Text
makeOpenSearch cfg defBang =
       "<OpenSearchDescription xmlns=\"http://a9.com/-/spec/opensearch/1.1/\"\n"
    <> "                       xmlns:moz=\"http://www.mozilla.org/2006/browser/search/\">\n"
    <> "    <ShortName>" <> name <> "</ShortName>\n"
    <> "    <Description>Handles search bangs (mostly) locally.</Description>\n"
    <> "    <InputEncoding>UTF-8</InputEncoding>\n"
    <> "    <Image width=\"16\" height=\"16\" type=\"image/x-icon\">" <> confFavicon cfg <> "</Image>\n"
    <> "    <Url type=\"text/html\" template=\"" <> searchUrl <> "\"/>\n"
    <> "</OpenSearchDescription>\n"

  where (searchUrl, name) = case defBang of
            Nothing -> (confBaseUrl cfg <> "/#{searchTerms}", "FastBangs")
            Just b  -> (confBaseUrl cfg <> "/#" <> b <> "#{searchTerms}", "FastBangs (" <> b <> ")")

sendEmail :: (MonadLogger m, MonadIO m) => Config -> String -> String -> String -> m ()
sendEmail cfg to subject body = case confEmailCmd cfg of
    Nothing -> do
        $(logWarn) $ "Would've send email to " <> pack (show to) <> ", but no command was configured"
    Just cmd -> do
        (_, _, _, ph) <- liftIO $ createProcess $ proc cmd [to, subject, body]
        exitCode <- liftIO $ waitForProcess ph
        case exitCode of
            ExitSuccess -> $(logInfo)  $ "Sent email to " <> pack (show to)
            ExitFailure i -> $(logError) $ "Sending email returned " <> pack (show i)