{-# LANGUAGE OverloadedStrings #-}
module Database.Selda.SQL.Print.Config (PPConfig (..), defPPConfig) where
import Data.Text (Text)
import qualified Data.Text as T
import Database.Selda.SqlType
import Database.Selda.Table
data PPConfig = PPConfig
{
ppType :: SqlTypeRep -> Text
, ppTypeHook :: SqlTypeRep -> [ColAttr] -> (SqlTypeRep -> Text) -> Text
, ppTypePK :: SqlTypeRep -> Text
, ppPlaceholder :: Int -> Text
, ppColAttrs :: [ColAttr] -> Text
, ppColAttrsHook :: SqlTypeRep -> [ColAttr] -> ([ColAttr] -> Text) -> Text
, ppAutoIncInsert :: Text
, ppMaxInsertParams :: Maybe Int
, ppIndexMethodHook :: IndexMethod -> Text
}
defPPConfig :: PPConfig
defPPConfig = PPConfig
{ ppType = defType
, ppTypeHook = \ty _ _ -> defType ty
, ppTypePK = defType
, ppPlaceholder = T.cons '$' . T.pack . show
, ppColAttrs = T.unwords . map defColAttr
, ppColAttrsHook = \_ ats _ -> T.unwords $ map defColAttr ats
, ppAutoIncInsert = "NULL"
, ppMaxInsertParams = Nothing
, ppIndexMethodHook = const ""
}
defType :: SqlTypeRep -> Text
defType TText = "TEXT"
defType TRowID = "INTEGER"
defType TInt = "INT"
defType TFloat = "DOUBLE"
defType TBool = "BOOLEAN"
defType TDateTime = "DATETIME"
defType TDate = "DATE"
defType TTime = "TIME"
defType TBlob = "BLOB"
defType TUUID = "BLOB"
defType TJSON = "BLOB"
defColAttr :: ColAttr -> Text
defColAttr Primary = ""
defColAttr (AutoPrimary Strong) = "PRIMARY KEY AUTOINCREMENT"
defColAttr (AutoPrimary Weak) = "PRIMARY KEY"
defColAttr Required = "NOT NULL"
defColAttr Optional = "NULL"
defColAttr Unique = "UNIQUE"
defColAttr (Indexed _) = ""