-- |
--
-- @since 2.13.0.0
module Database.Persist.FieldDef
    ( -- * The 'FieldDef' type
      FieldDef
      -- ** Setters
    , setFieldAttrs
    , overFieldAttrs
    , addFieldAttr
      -- ** Helpers
    , isFieldNullable
    , isFieldMaybe
    , isFieldNotGenerated
    , isHaskellField
      -- * 'FieldCascade'
    , FieldCascade(..)
    , renderFieldCascade
    , renderCascadeAction
    , noCascade
    , CascadeAction(..)
    ) where

import Database.Persist.FieldDef.Internal

import Database.Persist.Types.Base
       ( FieldAttr(..)
       , FieldType(..)
       , IsNullable(..)
       , fieldAttrsContainsNullable
       , isHaskellField
       )

-- | Replace the 'FieldDef' 'FieldAttr' with the new list.
--
-- @since 2.13.0.0
setFieldAttrs :: [FieldAttr] -> FieldDef -> FieldDef
setFieldAttrs :: [FieldAttr] -> FieldDef -> FieldDef
setFieldAttrs [FieldAttr]
fas FieldDef
fd = FieldDef
fd { fieldAttrs :: [FieldAttr]
fieldAttrs = [FieldAttr]
fas }

-- | Modify the list of field attributes.
--
-- @since 2.13.0.0
overFieldAttrs :: ([FieldAttr] -> [FieldAttr]) -> FieldDef -> FieldDef
overFieldAttrs :: ([FieldAttr] -> [FieldAttr]) -> FieldDef -> FieldDef
overFieldAttrs [FieldAttr] -> [FieldAttr]
k FieldDef
fd = FieldDef
fd { fieldAttrs :: [FieldAttr]
fieldAttrs = [FieldAttr] -> [FieldAttr]
k (FieldDef -> [FieldAttr]
fieldAttrs FieldDef
fd) }

-- | Add an attribute to the list of field attributes.
--
-- @since 2.13.0.0
addFieldAttr :: FieldAttr -> FieldDef -> FieldDef
addFieldAttr :: FieldAttr -> FieldDef -> FieldDef
addFieldAttr FieldAttr
fa = ([FieldAttr] -> [FieldAttr]) -> FieldDef -> FieldDef
overFieldAttrs (FieldAttr
fa FieldAttr -> [FieldAttr] -> [FieldAttr]
forall a. a -> [a] -> [a]
:)

-- | Check if the field definition is nullable
--
-- @since 2.13.0.0
isFieldNullable :: FieldDef -> IsNullable
isFieldNullable :: FieldDef -> IsNullable
isFieldNullable =
    [FieldAttr] -> IsNullable
fieldAttrsContainsNullable ([FieldAttr] -> IsNullable)
-> (FieldDef -> [FieldAttr]) -> FieldDef -> IsNullable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldDef -> [FieldAttr]
fieldAttrs

-- | Check if the field is `Maybe a`
--
-- @since 2.13.0.0
isFieldMaybe :: FieldDef -> Bool
isFieldMaybe :: FieldDef -> Bool
isFieldMaybe FieldDef
field =
    case FieldDef -> FieldType
fieldType FieldDef
field of
        FTApp (FTTypeCon Maybe Text
_ Text
"Maybe") FieldType
_ ->
            Bool
True
        FieldType
_ ->
            Bool
False