-- | An 'EntityDef' represents metadata about a type that @persistent@ uses to
-- store the type in the database, as well as generate Haskell code from it.
--
-- @since 2.13.0.0
module Database.Persist.EntityDef
    ( -- * The 'EntityDef' type
      EntityDef
      -- * Construction
      -- * Accessors
    , getEntityHaskellName
    , getEntityDBName
    , getEntityFields
    , getEntityFieldsDatabase
    , getEntityForeignDefs
    , getEntityUniques
    , getEntityId
    , getEntityIdField
    , getEntityKeyFields
    , getEntityComments
    , getEntityExtra
    , isEntitySum
    , entityPrimary
    , entitiesPrimary
    , keyAndEntityFields
     -- * Setters
    , setEntityId
    , setEntityIdDef
    , setEntityDBName
    , overEntityFields
      -- * Related Types
    , EntityIdDef(..)
    ) where

import Data.Text (Text)
import Data.Map (Map)
import Data.List.NonEmpty (NonEmpty)

import Database.Persist.EntityDef.Internal
import Database.Persist.FieldDef

import Database.Persist.Types.Base
    ( UniqueDef
    , ForeignDef
    , entityKeyFields
    )
import Database.Persist.Names

-- | Retrieve the list of 'UniqueDef' from an 'EntityDef'. This currently does
-- not include a @Primary@ key, if one is defined. A future version of
-- @persistent@ will include a @Primary@ key among the 'Unique' constructors for
-- the 'Entity'.
--
-- @since 2.13.0.0
getEntityUniques
    :: EntityDef
    -> [UniqueDef]
getEntityUniques :: EntityDef -> [UniqueDef]
getEntityUniques = EntityDef -> [UniqueDef]
entityUniques

-- | Retrieve the Haskell name of the given entity.
--
-- @since 2.13.0.0
getEntityHaskellName
    :: EntityDef
    -> EntityNameHS
getEntityHaskellName :: EntityDef -> EntityNameHS
getEntityHaskellName = EntityDef -> EntityNameHS
entityHaskell

-- | Return the database name for the given entity.
--
-- @since 2.13.0.0
getEntityDBName
    :: EntityDef
    -> EntityNameDB
getEntityDBName :: EntityDef -> EntityNameDB
getEntityDBName = EntityDef -> EntityNameDB
entityDB

getEntityExtra :: EntityDef -> Map Text [[Text]]
getEntityExtra :: EntityDef -> Map Text [[Text]]
getEntityExtra = EntityDef -> Map Text [[Text]]
entityExtra

-- |
--
-- @since 2.13.0.0
setEntityDBName :: EntityNameDB -> EntityDef -> EntityDef
setEntityDBName :: EntityNameDB -> EntityDef -> EntityDef
setEntityDBName EntityNameDB
db EntityDef
ed = EntityDef
ed { entityDB :: EntityNameDB
entityDB = EntityNameDB
db }

getEntityComments :: EntityDef -> Maybe Text
getEntityComments :: EntityDef -> Maybe Text
getEntityComments = EntityDef -> Maybe Text
entityComments

-- |
--
-- @since 2.13.0.0
getEntityForeignDefs
    :: EntityDef
    -> [ForeignDef]
getEntityForeignDefs :: EntityDef -> [ForeignDef]
getEntityForeignDefs = EntityDef -> [ForeignDef]
entityForeigns

-- | Retrieve the list of 'FieldDef' that makes up the fields of the entity.
--
-- This does not return the fields for an @Id@ column or an implicit @id@. It
-- will return the key columns if you used the @Primary@ syntax for defining the
-- primary key.
--
-- This does not return fields that are marked 'SafeToRemove' or 'MigrationOnly'
-- - so it only returns fields that are represented in the Haskell type. If you
-- need those fields, use 'getEntityFieldsDatabase'.
--
-- @since 2.13.0.0
getEntityFields
    :: EntityDef
    -> [FieldDef]
getEntityFields :: EntityDef -> [FieldDef]
getEntityFields = (FieldDef -> Bool) -> [FieldDef] -> [FieldDef]
forall a. (a -> Bool) -> [a] -> [a]
filter FieldDef -> Bool
isHaskellField ([FieldDef] -> [FieldDef])
-> (EntityDef -> [FieldDef]) -> EntityDef -> [FieldDef]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntityDef -> [FieldDef]
entityFields

-- | This returns all of the 'FieldDef' defined for the 'EntityDef', including
-- those fields that are marked as 'MigrationOnly' (and therefore only present
-- in the database) or 'SafeToRemove' (and a migration will drop the column if
-- it exists in the database).
--
-- For all the fields that are present on the Haskell-type, see
-- 'getEntityFields'.
--
-- @since 2.13.0.0
getEntityFieldsDatabase
    :: EntityDef
    -> [FieldDef]
getEntityFieldsDatabase :: EntityDef -> [FieldDef]
getEntityFieldsDatabase = EntityDef -> [FieldDef]
entityFields

-- |
--
-- @since 2.13.0.0
isEntitySum
    :: EntityDef
    -> Bool
isEntitySum :: EntityDef -> Bool
isEntitySum = EntityDef -> Bool
entitySum

-- |
--
-- @since 2.13.0.0
getEntityId
    :: EntityDef
    -> EntityIdDef
getEntityId :: EntityDef -> EntityIdDef
getEntityId = EntityDef -> EntityIdDef
entityId

-- |
--
-- @since 2.13.0.0
getEntityIdField :: EntityDef -> Maybe FieldDef
getEntityIdField :: EntityDef -> Maybe FieldDef
getEntityIdField EntityDef
ed =
    case EntityDef -> EntityIdDef
getEntityId EntityDef
ed of
        EntityIdField FieldDef
fd ->
            FieldDef -> Maybe FieldDef
forall (f :: * -> *) a. Applicative f => a -> f a
pure FieldDef
fd
        EntityIdDef
_ ->
            Maybe FieldDef
forall a. Maybe a
Nothing

-- | Set an 'entityId' to be the given 'FieldDef'.
--
-- @since 2.13.0.0
setEntityId
    :: FieldDef
    -> EntityDef
    -> EntityDef
setEntityId :: FieldDef -> EntityDef -> EntityDef
setEntityId FieldDef
fd = EntityIdDef -> EntityDef -> EntityDef
setEntityIdDef (FieldDef -> EntityIdDef
EntityIdField FieldDef
fd)

-- |
--
-- @since 2.13.0.0
setEntityIdDef
    :: EntityIdDef
    -> EntityDef
    -> EntityDef
setEntityIdDef :: EntityIdDef -> EntityDef -> EntityDef
setEntityIdDef EntityIdDef
i EntityDef
ed = EntityDef
ed { entityId :: EntityIdDef
entityId = EntityIdDef
i }

-- |
--
-- @since 2.13.0.0
getEntityKeyFields
    :: EntityDef
    -> NonEmpty FieldDef
getEntityKeyFields :: EntityDef -> NonEmpty FieldDef
getEntityKeyFields = EntityDef -> NonEmpty FieldDef
entityKeyFields

-- | TODO
--
-- @since 2.13.0.0
setEntityFields :: [FieldDef] -> EntityDef -> EntityDef
setEntityFields :: [FieldDef] -> EntityDef -> EntityDef
setEntityFields [FieldDef]
fd EntityDef
ed = EntityDef
ed { entityFields :: [FieldDef]
entityFields = [FieldDef]
fd }

-- | Perform a mapping function over all of the entity fields, as determined by
-- 'getEntityFieldsDatabase'.
--
-- @since 2.13.0.0
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