{-# LANGUAGE OverloadedStrings #-}
module Database.Relational.SimpleSql (
  
  QuerySuffix, showsQuerySuffix,
  
  updatePrefixSQL,
  updateOtherThanKeySQL,
  
  insertPrefixSQL,
  
  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.Internal.String
  (StringSQL, stringSQL, showStringSQL, rowConsStringSQL, )
import Database.Relational.Pi (Pi, expandIndexes')
import Database.Relational.Table (Table, name, columns, recordWidth)
import qualified Database.Relational.Record as Record
type QuerySuffix = [Keyword]
showsQuerySuffix :: QuerySuffix -> StringSQL
showsQuerySuffix =  mconcat
updatePrefixSQL :: Table r -> StringSQL
updatePrefixSQL table = UPDATE <> stringSQL (name table)
updateSQL' :: String      
           -> [StringSQL] 
           -> [StringSQL] 
           -> String      
updateSQL' table cols key =
  showStringSQL $ mconcat
  [UPDATE, stringSQL table, SET, SQL.fold (|*|) updAssigns,
   WHERE, SQL.fold SQL.and keyAssigns]
  where
    assigns cs = [ c .=. "?" | c <- cs ]
    updAssigns = assigns cols
    keyAssigns = assigns key
updateOtherThanKeySQL' :: String      
                       -> [StringSQL] 
                       -> [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) (expandIndexes' (recordWidth tbl) key)
insertPrefixSQL :: Pi r r' -> Table r -> StringSQL
insertPrefixSQL pi' table =
  INSERT <> INTO <> stringSQL (name table) <> rowConsStringSQL cols  where
    cols = Record.columns . Record.wpi (recordWidth table) (Record.unsafeFromTable table) $ pi'
deletePrefixSQL' :: String -> StringSQL
deletePrefixSQL' table = DELETE <> FROM <> stringSQL table
deletePrefixSQL :: Table r   
                -> StringSQL 
deletePrefixSQL = deletePrefixSQL' . name