]> gitweb.michael.orlitzky.com - dead/halcyon.git/blob - src/OptionalConfiguration.hs
Clean up a bunch of code and comments.
[dead/halcyon.git] / src / OptionalConfiguration.hs
1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE FlexibleInstances #-}
3 {-# LANGUAGE OverloadedStrings #-}
4
5 -- | The program will parse ~/.halcyonrc for any available configuration
6 -- directives, resulting in an OptionalCfg. The command-line
7 -- arguments will be used to create another OptionalCfg, and the two
8 -- will be merged. Finally, a default_config will be updated from
9 -- the merged OptionalCfgs.
10 --
11
12 module OptionalConfiguration (
13 OptionalCfg(..),
14 from_rc )
15 where
16
17 import qualified Data.Configurator as DC (
18 Worth (Optional),
19 load,
20 lookup )
21
22 import Data.Data ( Data )
23 import Data.Maybe ( fromMaybe )
24 import Data.Monoid ( Monoid(..) )
25 import Data.Typeable ( Typeable )
26 import Paths_halcyon ( getSysconfDir )
27 import System.Directory ( getHomeDirectory )
28 import System.FilePath ( (</>) )
29 import System.IO ( hPutStrLn, stderr )
30 import System.IO.Error ( catchIOError )
31
32 import Usernames ( Usernames(..) )
33
34
35 -- | The same as Cfg, except everything is optional. It's easy to
36 -- merge two of these by simply dropping the Nothings in favor of
37 -- the Justs. The 'usernames' are left un-maybed so that cmdargs
38 -- can parse more than one of them.
39 --
40 data OptionalCfg =
41 OptionalCfg { consumer_key :: Maybe String,
42 consumer_secret :: Maybe String,
43 access_token :: Maybe String,
44 access_secret :: Maybe String,
45 heartbeat :: Maybe Int,
46 ignore_replies :: Maybe Bool,
47 ignore_retweets :: Maybe Bool,
48 sendmail_path :: Maybe String,
49 from_address :: Maybe String,
50 to_address :: Maybe String,
51 verbose :: Maybe Bool,
52 usernames :: Usernames }
53 deriving (Show, Data, Typeable)
54
55 instance Monoid OptionalCfg where
56 mempty = OptionalCfg
57 Nothing
58 Nothing
59 Nothing
60 Nothing
61 Nothing
62 Nothing
63 Nothing
64 Nothing
65 Nothing
66 Nothing
67 Nothing
68 (Usernames [])
69
70 cfg1 `mappend` cfg2 =
71 OptionalCfg
72 (merge (consumer_key cfg1) (consumer_key cfg2))
73 (merge (consumer_secret cfg1) (consumer_secret cfg2))
74 (merge (access_token cfg1) (access_token cfg2))
75 (merge (access_secret cfg1) (access_secret cfg2))
76 (merge (heartbeat cfg1) (heartbeat cfg2))
77 (merge (ignore_replies cfg1) (ignore_replies cfg2))
78 (merge (ignore_retweets cfg1) (ignore_retweets cfg2))
79 (merge (sendmail_path cfg1) (sendmail_path cfg2))
80 (merge (from_address cfg1) (from_address cfg2))
81 (merge (to_address cfg1) (to_address cfg2))
82 (merge (verbose cfg1) (verbose cfg2))
83 all_usernames
84 where
85 merge :: (Maybe a) -> (Maybe a) -> (Maybe a)
86 merge Nothing Nothing = Nothing
87 merge (Just x) Nothing = Just x
88 merge Nothing (Just x) = Just x
89 merge (Just _) (Just y) = Just y
90
91 -- Use only the latter usernames if there are any.
92 all_usernames =
93 usernames $ if (null (get_usernames (usernames cfg2)))
94 then cfg1
95 else cfg2
96
97
98 -- | Obtain an 'OptionalCfg' from halcyonrc in either the global
99 -- configuration directory or the user's home directory. The one in
100 -- $HOME is prefixed by a dot so that it is hidden.
101 --
102 -- We make an attempt at cross-platform compatibility; we will try
103 -- to find the correct directory even on Windows. But if the calls
104 -- to getHomeDirectory/getSysconfDir fail for whatever reason, we
105 -- fall back to using the Unix-specific /etc and $HOME.
106 --
107 from_rc :: IO OptionalCfg
108 from_rc = do
109 etc <- catchIOError getSysconfDir (\e -> do
110 hPutStrLn stderr (show e)
111 return "/etc")
112 home <- catchIOError getHomeDirectory (\e -> do
113 hPutStrLn stderr (show e)
114 return "$(HOME)")
115 let global_config_path = etc </> "halcyonrc"
116 let user_config_path = home </> ".halcyonrc"
117 cfg <- DC.load [ DC.Optional global_config_path,
118 DC.Optional user_config_path ]
119
120 cfg_consumer_key <- DC.lookup cfg "consumer-key"
121 cfg_consumer_secret <- DC.lookup cfg "consumer-secret"
122 cfg_access_token <- DC.lookup cfg "access-token"
123 cfg_access_secret <- DC.lookup cfg "access-secret"
124 cfg_heartbeat <- DC.lookup cfg "heartbeat"
125 cfg_ignore_replies <- DC.lookup cfg "ignore-replies"
126 cfg_ignore_retweets <- DC.lookup cfg "ignore-retweets"
127 cfg_sendmail_path <- DC.lookup cfg "sendmail-path"
128 cfg_from_address <- DC.lookup cfg "from"
129 cfg_to_address <- DC.lookup cfg "to"
130 cfg_verbose <- DC.lookup cfg "verbose"
131 cfg_usernames <- DC.lookup cfg "usernames"
132
133 return $ OptionalCfg
134 cfg_consumer_key
135 cfg_consumer_secret
136 cfg_access_token
137 cfg_access_secret
138 cfg_heartbeat
139 cfg_ignore_replies
140 cfg_ignore_retweets
141 cfg_sendmail_path
142 cfg_from_address
143 cfg_to_address
144 cfg_verbose
145 (fromMaybe (Usernames []) cfg_usernames)