module Database.Relational.Query.SQL (
QuerySuffix, showsQuerySuffix,
updatePrefixSQL,
updateSQL',
updateOtherThanKeySQL', updateOtherThanKeySQL,
insertPrefixSQL, insertSQL, insertSizedChunkSQL,
deletePrefixSQL', deletePrefixSQL
) where
import Data.Array (listArray, (!))
import Data.Monoid (mconcat, (<>))
import Language.SQL.Keyword (Keyword(..), (.=.), (|*|))
import qualified Language.SQL.Keyword as SQL
import Database.Record.ToSql (untypedUpdateValuesIndex)
import Database.Relational.Query.Internal.SQL (StringSQL, stringSQL, showStringSQL, rowConsStringSQL)
import Database.Relational.Query.Pi (Pi)
import qualified Database.Relational.Query.Pi.Unsafe as UnsafePi
import Database.Relational.Query.Component (ColumnSQL, showsColumnSQL, showsColumnSQL)
import Database.Relational.Query.Table (Table, name, columns)
import qualified Database.Relational.Query.Projection as Projection
type QuerySuffix = [Keyword]
showsQuerySuffix :: QuerySuffix -> StringSQL
showsQuerySuffix = mconcat
updatePrefixSQL :: Table r -> StringSQL
updatePrefixSQL table = UPDATE <> stringSQL (name table)
updateSQL' :: String
-> [ColumnSQL]
-> [ColumnSQL]
-> String
updateSQL' table cols key =
showStringSQL $ mconcat
[UPDATE, stringSQL table, SET, SQL.fold (|*|) updAssigns,
WHERE, SQL.fold SQL.and keyAssigns]
where
assigns cs = [ showsColumnSQL c .=. "?" | c <- cs ]
updAssigns = assigns cols
keyAssigns = assigns key
updateOtherThanKeySQL' :: String
-> [ColumnSQL]
-> [Int]
-> String
updateOtherThanKeySQL' table cols ixs =
updateSQL' table updColumns keyColumns
where
width' = length cols
cols' = listArray (0, width' 1) cols
otherThanKey = untypedUpdateValuesIndex ixs width'
columns' is = [ cols' ! i | i <- is ]
updColumns = columns' otherThanKey
keyColumns = columns' ixs
updateOtherThanKeySQL :: Table r
-> Pi r p
-> String
updateOtherThanKeySQL tbl key =
updateOtherThanKeySQL' (name tbl) (columns tbl) (UnsafePi.unsafeExpandIndexes key)
insertPrefixSQL :: Pi r r' -> Table r -> StringSQL
insertPrefixSQL pi' table =
INSERT <> INTO <> stringSQL (name table) <> rowConsStringSQL [showsColumnSQL c | c <- cols] where
cols = Projection.columns . Projection.pi (Projection.unsafeFromTable table) $ pi'
insertChunkSQL :: Int
-> Pi r r'
-> Table r
-> String
insertChunkSQL n0 pi' tbl = showStringSQL $ insertPrefixSQL pi' tbl <> VALUES <> vs where
n | n0 >= 1 = n0
| otherwise = error $ "Invalid chunk count value: " ++ show n0
w = UnsafePi.width pi'
vs = SQL.fold (|*|) . replicate n $ rowConsStringSQL (replicate w "?")
insertSizedChunkSQL :: Pi r r'
-> Table r
-> Int
-> (String, Int)
insertSizedChunkSQL pi' tbl th = (insertChunkSQL n pi' tbl, n) where
w = UnsafePi.width pi'
n = th `quot` w + 1
insertSQL :: Pi r r'
-> Table r
-> String
insertSQL = insertChunkSQL 1
deletePrefixSQL' :: String -> StringSQL
deletePrefixSQL' table = DELETE <> FROM <> stringSQL table
deletePrefixSQL :: Table r
-> StringSQL
deletePrefixSQL = deletePrefixSQL' . name