module Database.MySQL.Simple
(
Base.ConnectInfo(..)
, Connection
, Query
, In(..)
, Only(..)
, FormatError(fmtMessage, fmtQuery, fmtParams)
, QueryError(qeMessage, qeQuery)
, ResultError(errSQLType, errHaskellType, errMessage)
, Base.connect
, Base.defaultConnectInfo
, Base.close
, query
, query_
, execute
, execute_
, executeMany
, Base.insertID
, withTransaction
, Base.autocommit
, Base.commit
, Base.rollback
, formatMany
, formatQuery
) where
import Blaze.ByteString.Builder (Builder, fromByteString, toByteString)
import Blaze.ByteString.Builder.Char8 (fromChar)
import Control.Applicative ((<$>), pure)
import Control.Exception (Exception, onException, throw)
import Control.Monad.Fix (fix)
import Data.ByteString (ByteString)
import Data.Int (Int64)
import Data.List (intersperse)
import Data.Monoid (mappend, mconcat)
import Data.Typeable (Typeable)
import Database.MySQL.Base (Connection)
import Database.MySQL.Simple.Param (Action(..), inQuotes)
import Database.MySQL.Simple.QueryParams (QueryParams(..))
import Database.MySQL.Simple.QueryResults (QueryResults(..))
import Database.MySQL.Simple.Result (ResultError(..))
import Database.MySQL.Simple.Types (In(..), Only(..), Query(..))
import Text.Regex.PCRE.Light (compile, caseless, match)
import qualified Data.ByteString.Char8 as B
import qualified Database.MySQL.Base as Base
data FormatError = FormatError {
fmtMessage :: String
, fmtQuery :: Query
, fmtParams :: [ByteString]
} deriving (Eq, Show, Typeable)
instance Exception FormatError
data QueryError = QueryError {
qeMessage :: String
, qeQuery :: Query
} deriving (Eq, Show, Typeable)
instance Exception QueryError
formatQuery :: QueryParams q => Connection -> Query -> q -> IO ByteString
formatQuery conn q@(Query template) qs
| null xs && '?' `B.notElem` template = return template
| otherwise = toByteString <$> buildQuery conn q template xs
where xs = renderParams qs
formatMany :: (QueryParams q) => Connection -> Query -> [q] -> IO ByteString
formatMany _ q [] = fmtError "no rows supplied" q []
formatMany conn q@(Query template) qs = do
case match re template [] of
Just [_,before,qbits,after] -> do
bs <- mapM (buildQuery conn q qbits . renderParams) qs
return . toByteString . mconcat $ fromByteString before :
intersperse (fromChar ',') bs ++
[fromByteString after]
_ -> error "foo"
where
re = compile "^([^?]+\\bvalues\\s*)(\\(\\s*[?](?:\\s*,\\s*[?])*\\s*\\))(.*)$"
[caseless]
buildQuery :: Connection -> Query -> ByteString -> [Action] -> IO Builder
buildQuery conn q template xs = zipParams (split template) <$> mapM sub xs
where sub (Plain b) = pure b
sub (Escape s) = (inQuotes . fromByteString) <$> Base.escape conn s
sub (Many ys) = mconcat <$> mapM sub ys
split s = fromByteString h : if B.null t then [] else split (B.tail t)
where (h,t) = B.break (=='?') s
zipParams (t:ts) (p:ps) = t `mappend` p `mappend` zipParams ts ps
zipParams [t] [] = t
zipParams _ _ = fmtError (show (B.count '?' template) ++
" '?' characters, but " ++
show (length xs) ++ " parameters") q xs
execute :: (QueryParams q) => Connection -> Query -> q -> IO Int64
execute conn template qs = do
Base.query conn =<< formatQuery conn template qs
finishExecute template conn
execute_ :: Connection -> Query -> IO Int64
execute_ conn q@(Query stmt) = do
Base.query conn stmt
finishExecute q conn
executeMany :: (QueryParams q) => Connection -> Query -> [q] -> IO Int64
executeMany _ _ [] = return 0
executeMany conn q qs = do
Base.query conn =<< formatMany conn q qs
finishExecute q conn
finishExecute :: Query -> Connection -> IO Int64
finishExecute q conn = do
ncols <- Base.fieldCount (Left conn)
if ncols /= 0
then throw $ QueryError ("execute resulted in " ++ show ncols ++
"-column result") q
else Base.affectedRows conn
query :: (QueryParams q, QueryResults r)
=> Connection -> Query -> q -> IO [r]
query conn template qs = do
Base.query conn =<< formatQuery conn template qs
finishQuery template conn
query_ :: (QueryResults r) => Connection -> Query -> IO [r]
query_ conn q@(Query que) = do
Base.query conn que
finishQuery q conn
finishQuery :: (QueryResults r) => Query -> Connection -> IO [r]
finishQuery q conn = do
r <- Base.storeResult conn
ncols <- Base.fieldCount (Right r)
if ncols == 0
then throw $ QueryError "query resulted in zero-column result" q
else do
fs <- Base.fetchFields r
flip fix [] $ \loop acc -> do
row <- Base.fetchRow r
case row of
[] -> return (reverse acc)
_ -> let !c = convertResults fs row
in loop (c:acc)
withTransaction :: Connection -> IO a -> IO a
withTransaction conn act = do
r <- act `onException` Base.rollback conn
Base.commit conn
return r
fmtError :: String -> Query -> [Action] -> a
fmtError msg q xs = throw FormatError {
fmtMessage = msg
, fmtQuery = q
, fmtParams = map twiddle xs
}
where twiddle (Plain b) = toByteString b
twiddle (Escape s) = s
twiddle (Many ys) = B.concat (map twiddle ys)