module Database.Persist.EntityDef
(
EntityDef
, getEntityHaskellName
, getEntityDBName
, getEntityFields
, getEntityFieldsDatabase
, getEntityForeignDefs
, getEntityUniques
, getEntityUniquesNoPrimaryKey
, getEntityId
, getEntityIdField
, getEntityKeyFields
, getEntityComments
, getEntityExtra
, isEntitySum
, entityPrimary
, entitiesPrimary
, keyAndEntityFields
, setEntityId
, setEntityIdDef
, setEntityDBName
, overEntityFields
, EntityIdDef(..)
) where
import Data.List.NonEmpty (NonEmpty)
import Data.Map (Map)
import Data.Text (Text)
import Database.Persist.EntityDef.Internal
import Database.Persist.FieldDef
import Database.Persist.Names
import Database.Persist.Types.Base (ForeignDef, UniqueDef(..), entityKeyFields)
getEntityUniquesNoPrimaryKey
:: EntityDef
-> [UniqueDef]
getEntityUniquesNoPrimaryKey :: EntityDef -> [UniqueDef]
getEntityUniquesNoPrimaryKey EntityDef
ed =
forall a. (a -> Bool) -> [a] -> [a]
filter UniqueDef -> Bool
isNotPrimaryKey forall a b. (a -> b) -> a -> b
$ EntityDef -> [UniqueDef]
entityUniques EntityDef
ed
where
isNotPrimaryKey :: UniqueDef -> Bool
isNotPrimaryKey UniqueDef
ud =
let
constraintName :: Text
constraintName = ConstraintNameHS -> Text
unConstraintNameHS forall a b. (a -> b) -> a -> b
$ UniqueDef -> ConstraintNameHS
uniqueHaskell UniqueDef
ud
in
Text
constraintName forall a. Eq a => a -> a -> Bool
/= EntityNameHS -> Text
unEntityNameHS (EntityDef -> EntityNameHS
getEntityHaskellName EntityDef
ed) forall a. Semigroup a => a -> a -> a
<> Text
"PrimaryKey"
getEntityUniques
:: EntityDef
-> [UniqueDef]
getEntityUniques :: EntityDef -> [UniqueDef]
getEntityUniques =
EntityDef -> [UniqueDef]
entityUniques
getEntityHaskellName
:: EntityDef
-> EntityNameHS
getEntityHaskellName :: EntityDef -> EntityNameHS
getEntityHaskellName = EntityDef -> EntityNameHS
entityHaskell
getEntityDBName
:: EntityDef
-> EntityNameDB
getEntityDBName :: EntityDef -> EntityNameDB
getEntityDBName = EntityDef -> EntityNameDB
entityDB
getEntityExtra :: EntityDef -> Map Text [[Text]]
= EntityDef -> Map Text [[Text]]
entityExtra
setEntityDBName :: EntityNameDB -> EntityDef -> EntityDef
setEntityDBName :: EntityNameDB -> EntityDef -> EntityDef
setEntityDBName EntityNameDB
db EntityDef
ed = EntityDef
ed { entityDB :: EntityNameDB
entityDB = EntityNameDB
db }
getEntityComments :: EntityDef -> Maybe Text
= EntityDef -> Maybe Text
entityComments
getEntityForeignDefs
:: EntityDef
-> [ForeignDef]
getEntityForeignDefs :: EntityDef -> [ForeignDef]
getEntityForeignDefs = EntityDef -> [ForeignDef]
entityForeigns
getEntityFields
:: EntityDef
-> [FieldDef]
getEntityFields :: EntityDef -> [FieldDef]
getEntityFields = forall a. (a -> Bool) -> [a] -> [a]
filter FieldDef -> Bool
isHaskellField forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntityDef -> [FieldDef]
entityFields
getEntityFieldsDatabase
:: EntityDef
-> [FieldDef]
getEntityFieldsDatabase :: EntityDef -> [FieldDef]
getEntityFieldsDatabase = EntityDef -> [FieldDef]
entityFields
isEntitySum
:: EntityDef
-> Bool
isEntitySum :: EntityDef -> Bool
isEntitySum = EntityDef -> Bool
entitySum
getEntityId
:: EntityDef
-> EntityIdDef
getEntityId :: EntityDef -> EntityIdDef
getEntityId = EntityDef -> EntityIdDef
entityId
getEntityIdField :: EntityDef -> Maybe FieldDef
getEntityIdField :: EntityDef -> Maybe FieldDef
getEntityIdField EntityDef
ed =
case EntityDef -> EntityIdDef
getEntityId EntityDef
ed of
EntityIdField FieldDef
fd ->
forall (f :: * -> *) a. Applicative f => a -> f a
pure FieldDef
fd
EntityIdDef
_ ->
forall a. Maybe a
Nothing
setEntityId
:: FieldDef
-> EntityDef
-> EntityDef
setEntityId :: FieldDef -> EntityDef -> EntityDef
setEntityId FieldDef
fd = EntityIdDef -> EntityDef -> EntityDef
setEntityIdDef (FieldDef -> EntityIdDef
EntityIdField FieldDef
fd)
setEntityIdDef
:: EntityIdDef
-> EntityDef
-> EntityDef
setEntityIdDef :: EntityIdDef -> EntityDef -> EntityDef
setEntityIdDef EntityIdDef
i EntityDef
ed = EntityDef
ed { entityId :: EntityIdDef
entityId = EntityIdDef
i }
getEntityKeyFields
:: EntityDef
-> NonEmpty FieldDef
getEntityKeyFields :: EntityDef -> NonEmpty FieldDef
getEntityKeyFields = EntityDef -> NonEmpty FieldDef
entityKeyFields
setEntityFields :: [FieldDef] -> EntityDef -> EntityDef
setEntityFields :: [FieldDef] -> EntityDef -> EntityDef
setEntityFields [FieldDef]
fd EntityDef
ed = EntityDef
ed { entityFields :: [FieldDef]
entityFields = [FieldDef]
fd }
overEntityFields
:: ([FieldDef] -> [FieldDef])
-> EntityDef
-> EntityDef
overEntityFields :: ([FieldDef] -> [FieldDef]) -> EntityDef -> EntityDef
overEntityFields [FieldDef] -> [FieldDef]
f EntityDef
ed =
[FieldDef] -> EntityDef -> EntityDef
setEntityFields ([FieldDef] -> [FieldDef]
f (EntityDef -> [FieldDef]
getEntityFieldsDatabase EntityDef
ed)) EntityDef
ed