{-# LANGUAGE AllowAmbiguousTypes #-}

module Database.GP.SqlGenerator
  ( insertStmtFor,
    updateStmtFor,
    selectFromStmt,
    deleteStmtFor,
    createTableStmtFor,
    dropTableStmtFor,
    WhereClauseExpr,
    Field,
    field,
    whereClauseValues,
    (&&.),
    (||.),
    (=.),
    (>.),
    (<.),
    (>=.),
    (<=.),
    (<>.),
    like,
    contains,
    between,
    in',
    isNull,
    not',
    sqlFun,
    allEntries,
    byId,
  )
where

import           Data.List          (intercalate)
import Database.GP.Entity
import Database.GP.Query

-- |
--  This module defines some basic SQL statements for Record Data Types that are instances of 'Entity'.
--  The SQL statements are generated using Haskell generics to provide compile time reflection capabilities.

-- | A function that returns an SQL insert statement for an entity. Type 'a' must be an instance of Data.
-- The function will use the field names of the data type to generate the column names in the insert statement.
-- The values of the fields will be used as the values in the insert statement.
-- Output example: INSERT INTO Person (id, name, age, address) VALUES (123456, "Alice", 25, "123 Main St");
insertStmtFor :: forall a. Entity a => String
insertStmtFor :: forall a. Entity a => String
insertStmtFor =
  String
"INSERT INTO "
    forall a. [a] -> [a] -> [a]
++ forall a. Entity a => String
tableName @a
    forall a. [a] -> [a] -> [a]
++ String
" ("
    forall a. [a] -> [a] -> [a]
++ forall a. [a] -> [[a]] -> [a]
intercalate String
", " [String]
columns
    forall a. [a] -> [a] -> [a]
++ String
") VALUES ("
    forall a. [a] -> [a] -> [a]
++ forall a. [a] -> [[a]] -> [a]
intercalate String
", " (Int -> [String]
params (forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
columns))
    forall a. [a] -> [a] -> [a]
++ String
");"
  where
    columns :: [String]
columns = forall a. Entity a => [String]
columnNamesFor @a

columnNamesFor :: forall a. Entity a => [String]
columnNamesFor :: forall a. Entity a => [String]
columnNamesFor = forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd [(String, String)]
fieldColumnPairs
  where
    fieldColumnPairs :: [(String, String)]
fieldColumnPairs = forall a. Entity a => [(String, String)]
fieldsToColumns @a

-- | A function that returns an SQL update statement for an entity. Type 'a' must be an instance of Entity.
updateStmtFor :: forall a. (Entity a) => String
updateStmtFor :: forall a. Entity a => String
updateStmtFor =
  String
"UPDATE "
    forall a. [a] -> [a] -> [a]
++ forall a. Entity a => String
tableName @a
    forall a. [a] -> [a] -> [a]
++ String
" SET "
    forall a. [a] -> [a] -> [a]
++ forall a. [a] -> [[a]] -> [a]
intercalate String
", " [String]
updatePairs
    forall a. [a] -> [a] -> [a]
++ String
" WHERE "
    forall a. [a] -> [a] -> [a]
++ forall a. Entity a => String
idColumn @a
    forall a. [a] -> [a] -> [a]
++ String
" = ?"
    forall a. [a] -> [a] -> [a]
++ String
";"
  where
    updatePairs :: [String]
updatePairs = forall a b. (a -> b) -> [a] -> [b]
map (forall a. [a] -> [a] -> [a]
++ String
" = ?") (forall a. Entity a => [String]
columnNamesFor @a)

-- | A function that returns an SQL select statement for an entity. Type 'a' must be an instance of Entity.
--   The function takes a where clause expression as parameter. This expression is used to filter the result set.
selectFromStmt :: forall a. (Entity a) => WhereClauseExpr -> String
selectFromStmt :: forall a. Entity a => WhereClauseExpr -> String
selectFromStmt WhereClauseExpr
whereClauseExpr =
  String
"SELECT "
    forall a. [a] -> [a] -> [a]
++ forall a. [a] -> [[a]] -> [a]
intercalate String
", " (forall a. Entity a => [String]
columnNamesFor @a)
    forall a. [a] -> [a] -> [a]
++ String
" FROM "
    forall a. [a] -> [a] -> [a]
++ forall a. Entity a => String
tableName @a
    forall a. [a] -> [a] -> [a]
++ String
" WHERE "
    forall a. [a] -> [a] -> [a]
++ forall a. Entity a => WhereClauseExpr -> String
whereClauseExprToSql @a WhereClauseExpr
whereClauseExpr
    forall a. [a] -> [a] -> [a]
++ String
";"

deleteStmtFor :: forall a. (Entity a) => String
deleteStmtFor :: forall a. Entity a => String
deleteStmtFor =
  String
"DELETE FROM "
    forall a. [a] -> [a] -> [a]
++ forall a. Entity a => String
tableName @a
    forall a. [a] -> [a] -> [a]
++ String
" WHERE "
    forall a. [a] -> [a] -> [a]
++ forall a. Entity a => String
idColumn @a
    forall a. [a] -> [a] -> [a]
++ String
" = ?;"

createTableStmtFor :: forall a. (Entity a) => Database -> String
createTableStmtFor :: forall a. Entity a => Database -> String
createTableStmtFor Database
dbServer =
  String
"CREATE TABLE "
    forall a. [a] -> [a] -> [a]
++ forall a. Entity a => String
tableName @a
    forall a. [a] -> [a] -> [a]
++ String
" ("
    forall a. [a] -> [a] -> [a]
++ forall a. [a] -> [[a]] -> [a]
intercalate String
", " (forall a b. (a -> b) -> [a] -> [b]
map (\(String
f, String
c) -> String
c forall a. [a] -> [a] -> [a]
++ String
" " forall a. [a] -> [a] -> [a]
++ forall a. Entity a => Database -> String -> String
columnTypeFor @a Database
dbServer String
f forall a. [a] -> [a] -> [a]
++ String -> String
optionalPK String
f) (forall a. Entity a => [(String, String)]
fieldsToColumns @a))
    forall a. [a] -> [a] -> [a]
++ String
");"
  where
    isIdField :: String -> Bool
isIdField String
f = String
f forall a. Eq a => a -> a -> Bool
== forall a. Entity a => String
idField @a
    optionalPK :: String -> String
optionalPK String
f = if String -> Bool
isIdField String
f then String
" PRIMARY KEY" else String
""

-- | A function that returns the column type for a field of an entity.
-- TODO: Support other databases than just SQLite.
columnTypeFor :: forall a. (Entity a) => Database -> String -> String
columnTypeFor :: forall a. Entity a => Database -> String -> String
columnTypeFor Database
SQLite String
fieldName =
  case String
fType of
    String
"Int"    -> String
"INTEGER"
    String
"String" -> String
"TEXT"
    String
"Double" -> String
"REAL"
    String
"Float"  -> String
"REAL"
    String
"Bool"   -> String
"INT"
    String
_        -> String
"TEXT"
  where
    maybeFType :: Maybe TypeRep
maybeFType = forall a. Entity a => String -> Maybe TypeRep
maybeFieldTypeFor @a String
fieldName
    fType :: String
fType = forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"OTHER" forall a. Show a => a -> String
show Maybe TypeRep
maybeFType
columnTypeFor Database
other String
_ = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"Schema creation for " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Database
other forall a. [a] -> [a] -> [a]
++ String
" not implemented yet"

dropTableStmtFor :: forall a. (Entity a) => String
dropTableStmtFor :: forall a. Entity a => String
dropTableStmtFor =
  String
"DROP TABLE IF EXISTS "
    forall a. [a] -> [a] -> [a]
++ forall a. Entity a => String
tableName @a
    forall a. [a] -> [a] -> [a]
++ String
";"