]> gitweb.michael.orlitzky.com - mailbox-count.git/blob - src/Report.hs
Align the mailbox counts in the summary report to the same column.
[mailbox-count.git] / src / Report.hs
1 {-# LANGUAGE PatternGuards #-}
2
3 module Report (
4 report,
5 report_tests )
6 where
7
8 import Data.List ( foldl', maximumBy )
9 import qualified Data.Map as Map ( Map, alter, empty, foldl, mapWithKey )
10 import Data.Maybe ( catMaybes )
11 import Data.String.Utils ( join )
12 import Database.HDBC (
13 IConnection,
14 SqlValue,
15 safeFromSql,
16 quickQuery )
17 import Database.HDBC.Sqlite3 ( connectSqlite3 )
18 import Test.Tasty ( TestTree, testGroup )
19 import Test.Tasty.HUnit ( (@?=), testCase )
20
21
22 -- Type synonyms to make the signatures below a little more clear.
23 type Domain = String
24 type Username = String
25 type Count = Int
26
27
28 -- | A wrapper around a (domain, count) pair to keep things type-safe.
29 data DomainCount =
30 DomainCount Domain Count
31 deriving (Show)
32
33 -- | A wrapper around a (domain, user) pair to keep things type-safe.
34 data DomainUser =
35 DomainUser Domain Username
36 deriving (Show)
37
38
39 -- | In the detailed report, we store the usernames as a map from a
40 -- domain name to a list of usernames. This type synonym is the type
41 -- of that map.
42 type DomainUserMap = Map.Map Domain [Username]
43
44
45 -- | Convert a list of [SqlByteString, SqlInt32] to 'DomainCount's. If
46 -- the conversion doesn't work for some reason (bad data, not enough
47 -- columns, etc.), we return 'Nothing'.
48 --
49 -- Examples:
50 --
51 -- >>> import Database.HDBC ( iToSql, toSql )
52 --
53 -- >>> list_to_domain_count [toSql "example.com", iToSql 100]
54 -- Just (DomainCount "example.com" 100)
55 --
56 -- >>> list_to_domain_count [toSql "example.com"]
57 -- Nothing
58 --
59 -- >>> list_to_domain_count [toSql "example.com", toSql "example.com"]
60 -- Nothing
61 --
62 list_to_domain_count :: [SqlValue] -> Maybe DomainCount
63 list_to_domain_count (domain:count:_)
64 | Right d <- safeFromSql domain,
65 Right c <- safeFromSql count = Just $ DomainCount d c
66 list_to_domain_count _ =
67 Nothing
68
69
70 -- | Convert a list of [SqlByteString, SqlByteString] to 'DomainUser's. If
71 -- the conversion doesn't work for some reason (bad data, not enough
72 -- columns, etc.), we return 'Nothing'.
73 --
74 -- Examples:
75 --
76 -- >>> import Database.HDBC ( toSql )
77 -- >>>
78 -- >>> list_to_domain_user [toSql "example.com", toSql "user1"]
79 -- Just (DomainUser "example.com" "user1")
80 --
81 -- >>> list_to_domain_user [toSql "example.com"]
82 -- Nothing
83 --
84 list_to_domain_user :: [SqlValue] -> Maybe DomainUser
85 list_to_domain_user (domain:user:_)
86 | Right d <- safeFromSql domain,
87 Right u <- safeFromSql user = Just $ DomainUser d u
88 list_to_domain_user _ =
89 Nothing
90
91
92 -- | Pad each count on the left with spaces so that they start on the
93 -- same column. The 'Int' argument is the length of the longest
94 -- domain name with which this one will be aligned, so when you take
95 -- into consideration the colon and subsequent space, the count will
96 -- be placed in column @longest_length + 3@.
97 --
98 -- Examples:
99 --
100 -- >>> let dc = DomainCount "example.com" 20
101 -- >>> format_domain_count 20 dc
102 -- "example.com: 20"
103 --
104 format_domain_count :: Int -> DomainCount -> String
105 format_domain_count longest_length (DomainCount d c) =
106 d ++ ": " ++ (replicate num_spaces ' ') ++ (show c)
107 where
108 num_spaces = longest_length - length d
109
110 summary_header :: String
111 summary_header = "Summary (number of mailboxes per domain)\n" ++
112 "----------------------------------------"
113
114 report_summary :: IConnection a => a -> IO String
115 report_summary conn = do
116 list_rows <- quickQuery conn query []
117 let maybe_domain_counts = map list_to_domain_count list_rows
118 let domain_counts = catMaybes maybe_domain_counts
119 let n = longest_dc_length domain_counts
120 let formatted_domain_counts = map (format_domain_count n) domain_counts
121 let report_lines = summary_header : formatted_domain_counts
122 return $ join "\n" report_lines
123 where
124 -- | Compare two 'DomainCount's by the length of their domain. The
125 -- one with the longest domain is \"bigger\".
126 compare_dcs_by_length :: DomainCount -> DomainCount -> Ordering
127 compare_dcs_by_length (DomainCount x _) (DomainCount y _) =
128 compare (length x) (length y)
129
130 -- | Find the length of the 'DomainCount' in the list that has the
131 -- longest domain. We need to know this in order to pad the
132 -- counts on the left by the correct number of spaces.
133 longest_dc_length :: [DomainCount] -> Int
134 longest_dc_length dcs =
135 let (DomainCount d _) = longest in length d
136 where
137 longest = maximumBy compare_dcs_by_length dcs
138
139 query = "SELECT domain,COUNT(username) " ++
140 "FROM mailbox " ++
141 "GROUP BY domain "++
142 "ORDER BY domain;"
143
144
145 -- | Construct a Domain -> [Username] (a DomainUserMap) map from a
146 -- list of 'DomainUser's. We do this with a fold over the list of
147 -- 'DomainUser's, appending each new user to the list associated
148 -- with the domain that the user is paired with.
149 --
150 -- The [Username] lists (the values stored in the map) are kept in
151 -- the same order as they are given.
152 --
153 -- Examples:
154 --
155 -- >>> let du1 = DomainUser "example.com" "user1"
156 -- >>> let du2 = DomainUser "example.com" "user2"
157 -- >>> let du3 = DomainUser "example.net" "user3"
158 -- >>> construct_domain_user_map [du1,du2,du3]
159 -- fromList [("example.com",["user1","user2"]),("example.net",["user3"])]
160 --
161 -- >>> construct_domain_user_map [du2,du1,du3]
162 -- fromList [("example.com",["user2","user1"]),("example.net",["user3"])]
163 --
164 construct_domain_user_map :: [DomainUser] -> DomainUserMap
165 construct_domain_user_map dus =
166 foldl' append_this_du Map.empty dus
167 where
168 append_func :: Username -> (Maybe [Username]) -> (Maybe [Username])
169 append_func user maybe_userlist =
170 case maybe_userlist of
171 Just userlist -> Just (userlist ++ [user])
172 Nothing -> Just [user]
173
174 append_this_du :: DomainUserMap -> DomainUser -> DomainUserMap
175 append_this_du du_map (DomainUser domain user) =
176 Map.alter (append_func user) domain du_map
177
178
179 detail_header :: String
180 detail_header = "Detail (list of all mailboxes by domain)\n" ++
181 "----------------------------------------"
182
183 report_detail :: IConnection a => a -> IO String
184 report_detail conn = do
185 list_rows <- quickQuery conn query []
186 let maybe_domain_users = map list_to_domain_user list_rows
187 let domain_users = catMaybes maybe_domain_users
188 let domain_users_map = construct_domain_user_map domain_users
189
190 -- This maps domains to a string listing their users
191 let domain_report_map = Map.mapWithKey format_domain domain_users_map
192 let report_body = Map.foldl (++) "" domain_report_map
193 return $ detail_header ++ report_body
194 where
195 query = "SELECT domain,username " ++
196 "FROM mailbox " ++
197 "ORDER BY domain;"
198
199 format_domain :: Domain -> [Username] -> String
200 format_domain domain users =
201 (join "\n" (domain_header : indented_users)) ++ "\n"
202 where
203 count = length users
204 domain_header = "\n" ++ domain ++ " (" ++ (show count) ++ ")" ++ ":"
205 indented_users = map (" " ++) users
206
207
208 report :: IConnection a => a -> Bool -> IO String
209 report conn do_detail =
210 if do_detail
211 then report_detail conn
212 else report_summary conn
213
214
215
216 -- * Tests
217
218 report_tests :: TestTree
219 report_tests =
220 testGroup "Report Tests" [ test_summary_report, test_detail_report ]
221
222
223 test_summary_report :: TestTree
224 test_summary_report =
225 testCase desc $ do
226 conn <- connectSqlite3 "test/fixtures/postfixadmin.sqlite3"
227 actual <- report_summary conn
228 actual @?= expected
229 where
230 desc = "Summary report looks like it should"
231 expected = summary_header ++
232 "\n" ++
233 "example.com: 3\n" ++
234 "example.invalid: 1\n" ++
235 "example.net: 2\n" ++
236 "example.org: 1"
237
238
239 test_detail_report :: TestTree
240 test_detail_report =
241 testCase desc $ do
242 conn <- connectSqlite3 "test/fixtures/postfixadmin.sqlite3"
243 actual <- report_detail conn
244 actual @?= expected
245 where
246 desc = "Detail report looks like it should"
247 expected = detail_header ++
248 "\n" ++
249 "example.com (3):\n" ++
250 " user1\n" ++
251 " user3\n" ++
252 " user5\n" ++
253 "\n" ++
254 "example.invalid (1):\n" ++
255 " user7\n" ++
256 "\n" ++
257 "example.net (2):\n" ++
258 " user2\n" ++
259 " user4\n" ++
260 "\n" ++
261 "example.org (1):\n" ++
262 " user6\n"