module Database.Persist.Audit.Types where
import Control.Applicative (empty)
import Control.Monad (mzero)
import Data.Aeson
import Data.Hashable
import qualified Data.HashMap.Lazy as HML
import Data.Text (Text)
import Database.Persist.TH
import GHC.Generics
type PersistModelFile = [PersistModelFilePiece]
data PersistModelFilePiece = PersistModelFileEntity Entity |
PersistModelFileComment Comment |
PersistModelFileWhiteSpace WhiteSpace
deriving (Eq,Show,Read)
data Entity = Entity {
_getEntityName :: Text
, _isEntityDeriveJson :: Bool
, _getEntitySqlTable :: Maybe Text
, _getEntityChildren :: [EntityChild]
} deriving (Eq,Show,Read)
data EntityChild = EntityChildEntityField EntityField |
EntityChildEntityUnique EntityUnique |
EntityChildEntityDerive EntityDerive |
EntityChildEntityPrimary EntityPrimary |
EntityChildEntityForeign EntityForeign |
EntityChildComment Comment |
EntityChildWhiteSpace WhiteSpace
deriving (Eq,Show,Read)
data EntityField = EntityField {
_getEntityFieldName :: Text
, _getEntityFieldType :: EntityFieldType
, _isEntityFieldMigrationOnly :: Bool
, _isEntityFieldSafeToRemove :: Bool
, _getEntityFieldDefault :: Maybe Text
, _getEntityFieldSqlRow :: Maybe Text
, _getEntityFieldSqlType :: Maybe Text
, _getEntityFieldMaxLen :: Maybe Int
} deriving (Eq,Show,Read)
data Strictness
= Strict
| ExplicitStrict
| Lazy
deriving (Eq,Show,Read)
data EntityFieldType = EntityFieldType {
_getEntityFieldTypeText :: Text
, _getEntityFieldStrictness :: Strictness
, _isEntityFieldTypeList :: Bool
, _isEntityFieldTypeMaybe :: Bool
} deriving (Eq,Show,Read)
data EntityUnique = EntityUnique {
_getEntityUniqueName :: Text
, _getEntityUniqueEntityFieldName :: [Text]
} deriving (Eq,Show,Read)
data EntityDerive = EntityDerive {
_getEntityDeriveTypes :: [Text]
} deriving (Eq,Show,Read)
data EntityPrimary = EntityPrimary {
_getEntityPrimeType :: [Text]
} deriving (Eq,Show,Read)
data EntityForeign = EntityForeign {
_getEntityForeignTable :: Text
, _getEntityForeignTypes :: [Text]
} deriving (Eq,Show,Read)
data WhiteSpace = WhiteSpace {
_getWhiteSpace :: Text
} deriving (Eq,Show,Read)
data Comment = Comment {
_getComment :: Text
} deriving (Eq,Show,Read)
data AuditAction = Create | Delete | Update
deriving (Show, Read, Eq, Ord, Generic)
derivePersistField "AuditAction"
instance Hashable AuditAction
instance FromJSON AuditAction where
parseJSON (Object o) = getAuditAction
where
getAuditAction
| HML.member "Create" o = pure Database.Persist.Audit.Types.Create
| HML.member "Delete" o = pure Database.Persist.Audit.Types.Delete
| HML.member "Update" o = pure Database.Persist.Audit.Types.Update
| True = empty
parseJSON _ = mzero
instance ToJSON AuditAction where
toJSON (Database.Persist.Audit.Types.Create) = object ["Create" .= ([] :: [Int])]
toJSON (Database.Persist.Audit.Types.Delete) = object ["Delete" .= ([] :: [Int])]
toJSON (Database.Persist.Audit.Types.Update) = object ["Update" .= ([] :: [Int])]