module Database.PostgreSQL.Store.Table (
Table (..),
TableEntity (..),
genTableName,
genTableColumns,
genTableColumnsOn,
GenericTable,
describeGenericTable,
KColumns (..),
KTable (..),
GColumns (..),
GTable (..),
AnalyzeRecordRep,
AnalyzeTableRep,
AnalyzeTable
) where
import GHC.Generics
import GHC.TypeLits
import qualified Data.ByteString as B
import Data.Kind
import Data.Proxy
import Data.Tagged
import Database.PostgreSQL.Store.Entity
import Database.PostgreSQL.Store.Query.Builder
import Database.PostgreSQL.Store.Utilities
data KColumns
= TCombine KColumns KColumns
| TSelector Symbol Type
class GColumns (rec :: KColumns) where
gDescribeColumns :: Tagged rec [B.ByteString]
instance (KnownSymbol name) => GColumns ('TSelector name typ) where
gDescribeColumns =
Tagged [buildByteString (symbolVal @name Proxy)]
instance (GColumns lhs, GColumns rhs) => GColumns ('TCombine lhs rhs) where
gDescribeColumns =
Tagged (untag (gDescribeColumns @lhs) ++ untag (gDescribeColumns @rhs))
type family AnalyzeRecordRep org (rec :: * -> *) :: KColumns where
AnalyzeRecordRep org (S1 ('MetaSel ('Just name) m1 m2 m3) (Rec0 typ)) =
'TSelector name typ
AnalyzeRecordRep org (S1 ('MetaSel 'Nothing m1 m2 m3) a) =
TypeError ('Text "Given type "
':<>: 'ShowType org
':<>: 'Text " must have a single record constructor")
AnalyzeRecordRep org (lhs :*: rhs) =
'TCombine (AnalyzeRecordRep org lhs) (AnalyzeRecordRep org rhs)
AnalyzeRecordRep org U1 =
TypeError ('Text "Given type "
':<>: 'ShowType org
':<>: 'Text " has one constructor, therefore that constructor must have \
\at least one field")
AnalyzeRecordRep org other =
TypeError ('Text "Given type "
':<>: 'ShowType org
':<>: 'Text " has a constructor with an invalid selector"
':$$: 'ShowType other)
data KTable = TTable Symbol KColumns
data Table = Table {
tableName :: B.ByteString,
tableCols :: [B.ByteString]
} deriving (Show, Eq, Ord)
class GTable (tbl :: KTable) where
gDescribeTable :: Tagged tbl Table
instance (KnownSymbol name, GColumns cols) => GTable ('TTable name cols) where
gDescribeTable =
Tagged (Table (buildByteString (symbolVal @name Proxy))
(untag (gDescribeColumns @cols)))
type family AnalyzeTableRep org (dat :: * -> *) :: KTable where
AnalyzeTableRep org (D1 meta1 (C1 ('MetaCons name f 'True) sel)) =
'TTable name (AnalyzeRecordRep org sel)
AnalyzeTableRep org (D1 meta other) =
TypeError ('Text "Given type "
':<>: 'ShowType org
':<>: 'Text " must have a single record constructor")
AnalyzeTableRep org other =
TypeError ('Text "Given type "
':<>: 'ShowType org
':<>: 'Text " is not a valid data type"
':$$: 'ShowType other)
type AnalyzeTable a = AnalyzeTableRep a (Rep a)
type GenericTable a = (Generic a, GTable (AnalyzeTable a))
describeGenericTable :: forall a. (GenericTable a) => Tagged a Table
describeGenericTable =
retag (gDescribeTable @(AnalyzeTable a))
class (Entity a) => TableEntity a where
describeTableType :: Tagged a Table
default describeTableType :: (GenericTable a) => Tagged a Table
describeTableType = describeGenericTable
genTableName :: Table -> QueryGenerator a
genTableName (Table name _) =
genIdentifier name
genTableColumns :: Table -> QueryGenerator a
genTableColumns (Table name columns) =
joinGens (B.singleton 44) (map (genNestedIdentifier name) columns)
genTableColumnsOn :: Table -> B.ByteString -> QueryGenerator a
genTableColumnsOn (Table _ columns) name =
joinGens (B.singleton 44) (map (genNestedIdentifier name) columns)