at the moment I'm writing a small program which runs a couple SQLServer queries. To make the queries type-save I created a module "SQLQuery" which lets you design queries in a save way.
To execute the queries they have to be of type Query thus I did the following...
toSql $
T.pack (show (SELECT [Column "name"] (FROM (Table "kundenDBs")) (WHERE [AND (condition "activeProdData" Eq "'true'")]) NothingGB (ORDERBY [Column "name"] ASC)))
My Main.hs code is...
{-# LANGUAGE OverloadedStrings #-}
import Database.ODBC.SQLServer
import Data.ByteString
import qualified Data.Text as T
import SQLQuery (AND (..), Column (..), Direction (..), FROM (..),
GROUPBY (..), ORDERBY (..), Operand (..),
Operator (..), SELECT (..), Table (..), WHERE (..),
condition)
main :: IO ()
main = do
conn <- connectToDB
selectGipscommDB conn
clients <- queryClients conn
selectClientDB conn
orders <- queryOrders conn
print clients
print orders
-- Produces valid sql string (tested!)
print $ show (SELECT [Column "name"] (FROM (Table "kundenDBs")) (WHERE [AND (condition "activeProdData" Eq "'true'")]) NothingGB (ORDERBY [Column "name"] ASC))
close conn
connectToDB :: IO Connection
connectToDB =
connect
"DRIVER={ODBC Driver 13 for SQL Server};SERVER=xxx;Uid=yyy;Pwd=zzz"
selectGipscommDB :: Connection -> IO ()
selectGipscommDB =
flip exec gipscommDB
gipscommDB :: Query
gipscommDB =
"USE abc"
type Client = ByteString
queryClients :: Connection -> IO [Client]
queryClients =
flip query clientsSql
clientsSql :: Query
clientsSql =
toSql $ T.pack (show (SELECT [Column "name"] (FROM (Table "kundenDBs")) (WHERE [AND (condition "activeProdData" Eq "'true'")]) NothingGB (ORDERBY [Column "name"] ASC)))
-- "SELECT name FROM kundenDBs WHERE activeProdData = 'true' ORDER BY name"
type Product = ByteString
type Order = ByteString
queryOrders :: Connection -> IO [(Product, Order)]
queryOrders = flip query ordersSql
ordersSql :: Query
ordersSql =
"SELECT artikelnummer, auftrag FROM ProdData_ WHERE artikelnummer <> '' AND auftrag <> '' GROUP BY auftrag, artikelnummer ORDER BY artikelnummer"
selectClientDB :: Connection -> IO ()
selectClientDB =
flip exec clientDB
clientDB :: Query
clientDB =
"USE xyz"
My SQLQuery module code is...
{-# LANGUAGE OverloadedStrings #-}
module SQLQuery where
import Data.List (intercalate)
import Data.Maybe (fromMaybe)
import Data.String (IsString (fromString))
import qualified Data.Text as T
import Database.ODBC.SQLServer
-- SELECT
--
data SELECT
= SELECT [Column] FROM WHERE GROUPBY ORDERBY
instance Show SELECT where
show (SELECT cols from where' groupBy orderBy) =
"SELECT " ++ join ", " cols ++ " " ++ show from ++ " " ++ show where' ++ " " ++ show groupBy ++ " " ++ show orderBy
-- FROM
--
newtype FROM = FROM Table
instance Show FROM where
show (FROM tbl) = "FROM " ++ show tbl
-- WHERE
--
data WHERE
= WHERE [AND]
| NothingW
instance Show WHERE where
show (WHERE ands) = "WHERE " ++ join " AND " ands
show NothingW = ""
-- AND
--
newtype AND = AND Condition
instance Show AND where
show (AND cond) = show cond
--GROUPBY
--
data GROUPBY
= GROUPBY [Column]
| NothingGB
instance Show GROUPBY where
show (GROUPBY cols) = "GROUP BY " ++ join ", " cols
show NothingGB = ""
-- ORDERBY
--
newtype ORDERBY = ORDERBY [Column]
instance Show ORDERBY where
show (ORDERBY cols) = "ORDER BY " ++ join ", " cols
-- Table
--
newtype Table = Table String
instance Show Table where
show (Table tbl) = tbl
-- Column
--
data Column = Column String Direction
instance Show Column where
show (Column col dir) = col ++ " " ++ show dir
-- Condition
--
data Condition
= Condition Operand Operator Operand
instance Show Condition where
show (Condition operand1 operator operand2) = show operand1 <> show operator <> show operand2
condition :: String -> Operator -> String -> Condition
condition operand1 operator operand2 =
Condition (Operand operand1) operator (Operand operand2)
-- Operand
--
newtype Operand = Operand String
instance Show Operand where
show (Operand operand) = operand
-- Operator
--
data Operator
= Eq
| Ueq
| Gt
| Lt
instance Show Operator where
show Eq = " = "
show Ueq = " <> "
show Gt = " > "
show Lt = " < "
-- Direction
--
data Direction
= ASC
| DESC
instance Show Direction where
show ASC = "ASC"
show DESC = "DESC"
-- Functions
--
join :: Show a => String -> [a] -> String
join str = intercalate str . map show
which type check but lead to an error at runtime...
UpdateProdData-exe.EXE: UnsuccessfulReturnCode "odbc_SQLExecDirectW" (-1) "[Microsoft][ODBC
Driver 13 for SQL Server][SQL Server]In EXECUTE <procname>, procname can only be a literal or
variable of type char, varchar, nchar, or nvarchar.[Microsoft][ODBC Driver 13 for SQL Server][SQL Server]In EXECUTE <procname>, procname can only be a literal or variable of type char,
varchar, nchar, or nvarchar."
Well, I have no clue how to resolve this issue so I would be thankful if someone could help me. :)
The Haskell ODBC library is designed to do string escaping. What seems to be happening is that toSql "String"
wraps up the contents of the string as an escaped SQL string, not an unescaped query.
If you use fromString myQuery
instead of toSQL $ T.pack myQuery
it should work.