module Database.Selda.Table.Type where
import Database.Selda.SqlType (SqlTypeRep)
import Database.Selda.SQL (SQL)
import Database.Selda.Types
import Database.Selda.Exp
data Table a = Table
{
tableName :: TableName
, tableCols :: [ColInfo]
, tableHasAutoPK :: Bool
, tableAttrs :: [([Int], ColAttr)]
}
indexedCols :: Table a -> [(ColName, Maybe IndexMethod)]
indexedCols t =
[ (colName col, mmethod)
| col <- tableCols t
, Indexed mmethod <- colAttrs col
]
data ColInfo = ColInfo
{ colName :: ColName
, colType :: SqlTypeRep
, colAttrs :: [ColAttr]
, colFKs :: [(Table (), ColName)]
, colExpr :: UntypedCol SQL
}
data AutoIncType = Weak | Strong
deriving (Show, Eq, Ord)
data ColAttr
= Primary
| AutoPrimary AutoIncType
| Required
| Optional
| Unique
| Indexed (Maybe IndexMethod)
deriving (Show, Eq, Ord)
isAutoPrimary :: ColAttr -> Bool
isAutoPrimary (AutoPrimary _) = True
isAutoPrimary _ = False
isPrimary :: ColAttr -> Bool
isPrimary Primary = True
isPrimary attr = isAutoPrimary attr
isUnique :: ColAttr -> Bool
isUnique Unique = True
isUnique (Indexed _) = True
isUnique attr = isPrimary attr
data IndexMethod
= BTreeIndex
| HashIndex
deriving (Show, Eq, Ord)