{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE TypeFamilies, TypeOperators, FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances, MultiParamTypeClasses, OverloadedStrings #-}
{-# LANGUAGE FlexibleContexts, ScopedTypeVariables, ConstraintKinds #-}
{-# LANGUAGE GADTs, CPP, DeriveGeneric, DataKinds, MagicHash #-}
#if MIN_VERSION_base(4, 10, 0)
{-# LANGUAGE TypeApplications #-}
#endif
module Database.Selda.Table
( SelectorLike, Group (..), Attr (..), Table (..), Attribute
, ColInfo (..), AutoIncType (..), ColAttr (..), IndexMethod (..)
, ForeignKey (..)
, table, tableFieldMod
, primary, autoPrimary, weakAutoPrimary
, untypedAutoPrimary, weakUntypedAutoPrimary
, unique
, index, indexUsing
, tableExpr
, isAutoPrimary, isPrimary, isUnique
) where
import Data.Text (Text)
#if MIN_VERSION_base(4, 10, 0)
import Data.Typeable
#else
import Data.Proxy
import GHC.Prim
#endif
import Database.Selda.Types
import Database.Selda.Selectors
import Database.Selda.SqlType
import Database.Selda.Column (Row (..))
import Database.Selda.Generic
import Database.Selda.Table.Type
import Database.Selda.Table.Validation (snub)
import GHC.OverloadedLabels
instance forall x t a. IsLabel x (Selector t a) => IsLabel x (Group t a) where
#if MIN_VERSION_base(4, 10, 0)
fromLabel = Single (fromLabel @x)
#else
fromLabel _ = Single (fromLabel (proxy# :: Proxy# x))
#endif
data Group t a where
(:+) :: Selector t a -> Group t b -> Group t (a :*: b)
Single :: Selector t a -> Group t a
infixr 1 :+
data Attr a where
(:-) :: SelectorLike g => g t a -> Attribute g t a -> Attr t
infixl 0 :-
table :: forall a. Relational a
=> TableName
-> [Attr a]
-> Table a
table tn attrs = tableFieldMod tn attrs id
tableFieldMod :: forall a. Relational a
=> TableName
-> [Attr a]
-> (Text -> Text)
-> Table a
tableFieldMod tn attrs fieldMod = Table
{ tableName = tn
, tableCols = map tidy cols
, tableHasAutoPK = apk
, tableAttrs = concat [combinedAttrs, pkAttrs]
}
where
combinedAttrs =
[ (ixs, a)
| sel :- Attribute [a] <- attrs
, let ixs = indices sel
, case ixs of
(_:_:_) -> True
[_] | a == Unique -> True
[_] | Indexed _ <- a -> True
_ -> False
]
pkAttrs = concat
[ [(ixs, Primary), (ixs, Required)]
| sel :- Attribute [Primary,Required] <- attrs
, let ixs = indices sel
]
cols = zipWith addAttrs [0..] (tblCols (Proxy :: Proxy a) fieldMod)
apk = or [any isAutoPrimary as | _ :- Attribute as <- attrs]
addAttrs n ci = ci
{ colAttrs = colAttrs ci ++ concat
[ as
| sel :- Attribute as <- attrs
, case indices sel of
[colIx] -> colIx == n
_ -> False
]
, colFKs = colFKs ci ++
[ thefk
| sel :- ForeignKey thefk <- attrs
, case indices sel of
[colIx] -> colIx == n
_ -> False
]
}
class SelectorLike g where
indices :: g t a -> [Int]
instance SelectorLike Selector where
indices s = [selectorIndex s]
instance SelectorLike Group where
indices (s :+ ss) = selectorIndex s : indices ss
indices (Single s) = [selectorIndex s]
tidy :: ColInfo -> ColInfo
tidy ci = ci {colAttrs = snub $ colAttrs ci}
data Attribute (g :: * -> * -> *) t c
= Attribute [ColAttr]
| ForeignKey (Table (), ColName)
primary :: Attribute Group t a
primary = Attribute [Primary, Required]
index :: Attribute Group t c
index = Attribute [Indexed Nothing]
indexUsing :: IndexMethod -> Attribute Group t c
indexUsing m = Attribute [Indexed (Just m)]
autoPrimary :: Attribute Selector t (ID t)
autoPrimary = Attribute [AutoPrimary Strong, Required]
weakAutoPrimary :: Attribute Selector t (ID t)
weakAutoPrimary = Attribute [AutoPrimary Weak, Required]
untypedAutoPrimary :: Attribute Selector t RowID
untypedAutoPrimary = Attribute [AutoPrimary Strong, Required]
weakUntypedAutoPrimary :: Attribute Selector t RowID
weakUntypedAutoPrimary = Attribute [AutoPrimary Weak, Required]
unique :: Attribute Group t a
unique = Attribute [Unique]
mkFK :: Table t -> Selector a b -> Attribute Selector c d
mkFK (Table tn tcs tapk tas) sel =
ForeignKey (Table tn tcs tapk tas, colName (tcs !! selectorIndex sel))
class ForeignKey a b where
foreignKey :: Table t -> Selector t a -> Attribute Selector self b
instance ForeignKey a a where
foreignKey = mkFK
instance ForeignKey (Maybe a) a where
foreignKey = mkFK
instance ForeignKey a (Maybe a) where
foreignKey = mkFK
tableExpr :: Table a -> Row s a
tableExpr = Many . map colExpr . tableCols