{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-}
module Data.GS1.Event
(EventType(..)
, Event(..)
, allEventTypes
, getEventType
, mkEventType
, stringify
)
where
import Data.Aeson
import Data.Aeson.TH
import Data.GS1.DWhat
import Data.GS1.DWhen
import Data.GS1.DWhere
import Data.GS1.DWhy
import Data.GS1.EventId
import Data.GS1.Utils
import Data.String (IsString)
import Data.Swagger
import qualified Data.Text as T
import GHC.Generics
data EventType
= ObjectEventT
| AggregationEventT
| TransactionEventT
| TransformationEventT
deriving (Show, Eq, Generic, Enum, Read)
$(deriveJSON defaultOptions ''EventType)
instance ToSchema EventType
stringify :: IsString a => EventType -> a
stringify ObjectEventT = "ObjectEvent"
stringify AggregationEventT = "AggregationEvent"
stringify TransactionEventT = "TransactionEvent"
stringify TransformationEventT = "TransformationEvent"
getEventType :: DWhat -> EventType
getEventType ObjWhat{} = ObjectEventT
getEventType AggWhat{} = AggregationEventT
getEventType TransactWhat{} = TransactionEventT
getEventType TransformWhat{} = TransformationEventT
mkEventType :: T.Text -> Maybe EventType
mkEventType = mkByName
allEventTypes :: [EventType]
allEventTypes = [ObjectEventT ..]
data Event = Event
{
_etype :: EventType
, _eid :: Maybe EventId
, _what :: DWhat
, _when :: DWhen
, _why :: DWhy
, _where :: DWhere
}
deriving (Show, Eq, Generic)
$(deriveJSON defaultOptions ''Event)
instance ToSchema Event