]> gitweb.michael.orlitzky.com - dead/halcyon.git/blob - src/OptionalConfiguration.hs
607659ea811ce200577ed1a04a645b86ae2a602b
[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
27 import Usernames ( Usernames(..) )
28
29
30 -- | The same as Cfg, except everything is optional. It's easy to
31 -- merge two of these by simply dropping the Nothings in favor of
32 -- the Justs. The 'usernames' are left un-maybed so that cmdargs
33 -- can parse more than one of them.
34 --
35 data OptionalCfg =
36 OptionalCfg { consumer_key :: Maybe String,
37 consumer_secret :: Maybe String,
38 access_token :: Maybe String,
39 access_secret :: Maybe String,
40 heartbeat :: Maybe Int,
41 ignore_replies :: Maybe Bool,
42 ignore_retweets :: Maybe Bool,
43 sendmail_path :: Maybe String,
44 from_address :: Maybe String,
45 to_address :: Maybe String,
46 verbose :: Maybe Bool,
47 usernames :: Usernames }
48 deriving (Show, Data, Typeable)
49
50 instance Monoid OptionalCfg where
51 mempty = OptionalCfg
52 Nothing
53 Nothing
54 Nothing
55 Nothing
56 Nothing
57 Nothing
58 Nothing
59 Nothing
60 Nothing
61 Nothing
62 Nothing
63 (Usernames [])
64
65 cfg1 `mappend` cfg2 =
66 OptionalCfg
67 (merge (consumer_key cfg1) (consumer_key cfg2))
68 (merge (consumer_secret cfg1) (consumer_secret cfg2))
69 (merge (access_token cfg1) (access_token cfg2))
70 (merge (access_secret cfg1) (access_secret cfg2))
71 (merge (heartbeat cfg1) (heartbeat cfg2))
72 (merge (ignore_replies cfg1) (ignore_replies cfg2))
73 (merge (ignore_retweets cfg1) (ignore_retweets cfg2))
74 (merge (sendmail_path cfg1) (sendmail_path cfg2))
75 (merge (from_address cfg1) (from_address cfg2))
76 (merge (to_address cfg1) (to_address cfg2))
77 (merge (verbose cfg1) (verbose cfg2))
78 all_usernames
79 where
80 merge :: (Maybe a) -> (Maybe a) -> (Maybe a)
81 merge Nothing Nothing = Nothing
82 merge (Just x) Nothing = Just x
83 merge Nothing (Just x) = Just x
84 merge (Just _) (Just y) = Just y
85
86 -- Use only the latter usernames if there are any.
87 all_usernames =
88 usernames $ if (null (get_usernames (usernames cfg2)))
89 then cfg1
90 else cfg2
91
92 from_rc :: IO OptionalCfg
93 from_rc = do
94 cfg <- DC.load [ DC.Optional "$(HOME)/.halcyonrc" ]
95 cfg_consumer_key <- DC.lookup cfg "consumer-key"
96 cfg_consumer_secret <- DC.lookup cfg "consumer-secret"
97 cfg_access_token <- DC.lookup cfg "access-token"
98 cfg_access_secret <- DC.lookup cfg "access-secret"
99 cfg_heartbeat <- DC.lookup cfg "heartbeat"
100 cfg_ignore_replies <- DC.lookup cfg "ignore-replies"
101 cfg_ignore_retweets <- DC.lookup cfg "ignore-retweets"
102 cfg_sendmail_path <- DC.lookup cfg "sendmail-path"
103 cfg_from_address <- DC.lookup cfg "from"
104 cfg_to_address <- DC.lookup cfg "to"
105 cfg_verbose <- DC.lookup cfg "verbose"
106 cfg_usernames <- DC.lookup cfg "usernames"
107
108 return $ OptionalCfg
109 cfg_consumer_key
110 cfg_consumer_secret
111 cfg_access_token
112 cfg_access_secret
113 cfg_heartbeat
114 cfg_ignore_replies
115 cfg_ignore_retweets
116 cfg_sendmail_path
117 cfg_from_address
118 cfg_to_address
119 cfg_verbose
120 (fromMaybe (Usernames []) cfg_usernames)