-{-# LANGUAGE PatternGuards #-}
-
module Report (
report,
report_tests )
import Data.String.Utils ( join )
import Database.HDBC (
IConnection,
+ Statement,
execute,
prepare,
sFetchAllRows')
-- 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.
-> 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
-> 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