]> gitweb.michael.orlitzky.com - list-remote-forwards.git/blob - src/Main.hs
list-remote-forwards.cabal: delete the redundant description
[list-remote-forwards.git] / src / Main.hs
1 {-# LANGUAGE DoAndIfThenElse #-}
2 {-# LANGUAGE NoMonomorphismRestriction #-}
3 module Main (main)
4 where
5
6 import Data.Maybe ( fromMaybe )
7 import Data.String.Utils ( join )
8 import Database.HDBC (
9 SqlError(seNativeError, seErrorMsg),
10 handleSql )
11 import Database.HDBC.PostgreSQL ( connectPostgreSQL )
12 import Database.HDBC.Sqlite3 ( connectSqlite3 )
13 import System.Console.CmdArgs ( def )
14 import System.Directory ( doesFileExist )
15 import System.IO ( hPutStrLn, stderr )
16
17 import CommandLine ( get_args )
18 import Configuration (
19 Configuration(database, host, password, port, username),
20 merge_optional )
21 import qualified OptionalConfiguration as OC ( from_rc )
22 import Report ( report )
23 import String ( trim )
24
25
26 -- | Construct a connection string (postgres-only, for now) from a
27 -- 'Configuration'. All of these are optional, at least for
28 -- Postgres, and so we want to avoid appending e.g. \"host=\" to the
29 -- connection string if @(host cfg)@ is 'Nothing'.
30 --
31 -- ==== __Examples__
32 --
33 -- >>> let default_cfg = def :: Configuration
34 -- >>> let cfg = default_cfg { host = Just "localhost" }
35 -- >>> connection_string cfg
36 -- "host=localhost"
37 -- >>> let cfg2 = cfg { username = Just "postgres" }
38 -- >>> connection_string cfg2
39 -- "host=localhost user=postgres"
40 --
41 connection_string :: Configuration -> String
42 connection_string cfg =
43 trim $ join " " [host_part, port_part, user_part, pw_part, db_part]
44 where
45 host_part = let h = fmap ("host=" ++) (host cfg) in fromMaybe "" h
46 port_part = let p = fmap (("port=" ++) . show) (port cfg) in fromMaybe "" p
47 user_part = let u = fmap ("user=" ++) (username cfg) in fromMaybe "" u
48 pw_part = let pw = fmap ("password=" ++) (password cfg) in fromMaybe "" pw
49 db_part = let db = fmap ("dbname=" ++) (database cfg) in fromMaybe "" db
50
51
52 main :: IO ()
53 main = do
54 rc_cfg <- OC.from_rc
55 cmd_cfg <- get_args
56
57 -- Merge the config file options with the command-line ones,
58 -- prefering the command-line ones.
59 let opt_config = rc_cfg <> cmd_cfg
60
61 -- Update a default config with any options that have been set in
62 -- either the config file or on the command-line. We initialize
63 -- logging before the missing parameter checks below so that we can
64 -- log the errors.
65 let cfg = (def :: Configuration) `merge_optional` opt_config
66
67 -- If a database name was specified, and that name exists as a file
68 -- on the system, assume that the user wanted to use SQLite.
69 handleSql show_sql_error $ do
70 r <- case (database cfg) of
71 Nothing -> connectPostgreSQL (connection_string cfg) >>= report cfg
72
73 Just dbname -> do
74 exists <- doesFileExist dbname
75 if exists
76 then connectSqlite3 dbname >>= report cfg
77 else connectPostgreSQL (connection_string cfg) >>= report cfg
78
79 -- The DB connection is implicitly closed when it gets garbage collected.
80 putStr r
81
82 where
83 show_sql_error :: SqlError -> IO ()
84 show_sql_error se = hPutStrLn stderr $
85 "SQL Error (" ++ show (seNativeError se) ++ "): " ++ (seErrorMsg se)