]> gitweb.michael.orlitzky.com - list-remote-forwards.git/commitdiff
Fix hlint suggestions.
authorMichael Orlitzky <michael@orlitzky.com>
Fri, 28 Nov 2014 05:11:02 +0000 (00:11 -0500)
committerMichael Orlitzky <michael@orlitzky.com>
Fri, 28 Nov 2014 05:11:02 +0000 (00:11 -0500)
src/Forward.hs
src/Main.hs
src/Report.hs

index 7de53b858375287049f4e1c692f56316e28b18c6..3e9ad88fba5c0275443e1934034685ce5423739c 100644 (file)
@@ -214,8 +214,8 @@ address_domain (Forward (Address addr) _) = domain_part addr
 domain_part :: String -> Maybe Domain
 domain_part address =
   case parts of
 domain_part :: String -> Maybe Domain
 domain_part address =
   case parts of
-    (_:domain:[]) -> Just domain
-    _             -> Nothing
+    [_,domain] -> Just domain
+    _          -> Nothing
   where
     parts = split "@" address
 
   where
     parts = split "@" address
 
index ab4d05590458d819413da4dccab941d61a3c28cc..66d02a084449102dace81985744afdf25e4da8f6 100644 (file)
@@ -79,4 +79,4 @@ main = do
   where
     show_sql_error :: SqlError -> IO ()
     show_sql_error se = hPutStrLn stderr $
   where
     show_sql_error :: SqlError -> IO ()
     show_sql_error se = hPutStrLn stderr $
-      "SQL Error (" ++ (show $ seNativeError se) ++ "): " ++ (seErrorMsg se)
+      "SQL Error (" ++ show (seNativeError se) ++ "): " ++ (seErrorMsg se)
index 5b3853350efc3a07c581ad20b354741c3d127cc5..dd3ce4e9ae5d698c7d9985c2e32f7e937a10f2dd 100644 (file)
@@ -1,5 +1,3 @@
-{-# LANGUAGE PatternGuards #-}
-
 module Report (
   report,
   report_tests )
 module Report (
   report,
   report_tests )
@@ -13,6 +11,7 @@ import qualified Data.Set as Set ( map )
 import Data.String.Utils ( join )
 import Database.HDBC (
   IConnection,
 import Data.String.Utils ( join )
 import Database.HDBC (
   IConnection,
+  Statement,
   execute,
   prepare,
   sFetchAllRows')
   execute,
   prepare,
   sFetchAllRows')
@@ -35,6 +34,17 @@ import MxList ( MxList(..) )
 --   WARNING: Also defined in the "Forward" module.
 type Domain = String
 
 --   WARNING: Also defined in the "Forward" module.
 type Domain = String
 
+
+-- | We really want executeRaw here, but there's a bug: it will tell
+--   us we can't fetch rows from the statement since it hasn't been
+--   executed yet!
+--
+my_executeRaw :: Statement -> IO [[Maybe String]]
+my_executeRaw stmt = do
+  _ <- execute stmt []
+  sFetchAllRows' stmt
+
+
 -- | Given a connection @conn@ and a @query@, return a list of domains
 --   found by executing @query@ on @conn. The @query@ is assumed to
 --   return only one column, containing domains.
 -- | Given a connection @conn@ and a @query@, return a list of domains
 --   found by executing @query@ on @conn. The @query@ is assumed to
 --   return only one column, containing domains.
@@ -45,14 +55,7 @@ get_domain_list :: IConnection a
                 -> IO [Domain] -- ^ The list of domains returned from @query@
 get_domain_list conn query = do
   stmt <- prepare conn query
                 -> IO [Domain] -- ^ The list of domains returned from @query@
 get_domain_list conn query = do
   stmt <- prepare conn query
-
-  -- We really want executeRaw here, but there's a bug: it will tell
-  -- us we can't fetch rows from the statement since it hasn't been
-  -- executed yet!
-  _ <- execute stmt []
-
-  -- rows :: [[Maybe String]]
-  rows <- sFetchAllRows' stmt
+  rows <- my_executeRaw stmt
 
   -- rows' :: [Maybe String]
   let rows' = map (listToMaybe . catMaybes) rows
 
   -- rows' :: [Maybe String]
   let rows' = map (listToMaybe . catMaybes) rows
@@ -77,14 +80,7 @@ get_forward_list :: IConnection a
                  -> IO [Forward]  -- ^ A list of forwards returned from @query@
 get_forward_list conn query = do
   stmt <- prepare conn query
                  -> IO [Forward]  -- ^ A list of forwards returned from @query@
 get_forward_list conn query = do
   stmt <- prepare conn query
-
-  -- We really want executeRaw here, but there's a bug: it will tell
-  -- us we can't fetch rows from the statement since it hasn't been
-  -- executed yet!
-  _ <- execute stmt []
-
-  -- rows :: [[Maybe String]]
-  rows <- sFetchAllRows' stmt
+  rows <- my_executeRaw stmt
 
   -- forwards :: [Forward]
   let forwards = concatMap (strings_to_forwards . catMaybes) rows
 
   -- forwards :: [Forward]
   let forwards = concatMap (strings_to_forwards . catMaybes) rows