{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
module Data.GS1.DWhat
(LabelEPC(..)
, ParentLabel(..)
, InputEPC(..)
, OutputEPC (..)
, ObjectDWhat(..)
, AggregationDWhat(..)
, TransactionDWhat(..)
, TransformationDWhat(..)
, DWhat(..)
, readLabelEPC
, urn2LabelEPC
)
where
import GHC.Generics
import Data.Semigroup
import Data.Aeson
import Data.Aeson.TH
import Data.Swagger
import qualified Data.Text as T
import Data.GS1.EPC
data LabelEPC
= CL
{ _clClassLabelEpc :: ClassLabelEPC
, _clQuantity :: Maybe Quantity
}
| IL
{ _ilInstanceLabelEpc :: InstanceLabelEPC
}
deriving (Show, Read, Eq, Generic)
$(deriveJSON defaultOptions ''LabelEPC)
instance ToSchema LabelEPC
newtype ParentLabel = ParentLabel {unParentLabel :: InstanceLabelEPC}
deriving (Show, Read, Eq, Generic, ToJSON, FromJSON, URI)
newtype InputEPC = InputEPC {unInputEPC :: LabelEPC}
deriving (Show, Read, Eq, Generic, ToJSON, FromJSON)
newtype OutputEPC = OutputEPC {unOutputEPC :: LabelEPC}
deriving (Show, Read, Eq, Generic, ToJSON, FromJSON)
instance ToSchema ParentLabel
instance ToSchema InputEPC
instance ToSchema OutputEPC
readLabelEPC :: Maybe Quantity -> T.Text -> Either ParseFailure LabelEPC
readLabelEPC mQt epcStr =
fmap (`CL` mQt) (readURIClassLabelEPC epcTokens)
<>
fmap IL (readURIInstanceLabelEPC epcTokens)
where
epcTokens = T.splitOn ":" epcStr
urn2LabelEPC :: T.Text -> Either ParseFailure LabelEPC
urn2LabelEPC = readLabelEPC Nothing
data ObjectDWhat =
ObjectDWhat
{
_objAction :: Action
, _objEpcList :: [LabelEPC]
} deriving (Show, Eq, Generic)
data AggregationDWhat =
AggregationDWhat
{
_aggAction :: Action
, _aggParentLabel :: Maybe ParentLabel
, _aggChildEpcList :: [LabelEPC]
} deriving (Show, Eq, Generic)
data TransactionDWhat =
TransactionDWhat
{
_transactionAction :: Action
, _transactionParentLabel :: Maybe ParentLabel
, _transactionBizTransactionList :: [BizTransaction]
, _transactionEpcList :: [LabelEPC]
} deriving (Show, Eq, Generic)
data TransformationDWhat =
TransformationDWhat
{
_transformationId :: Maybe TransformationId
, _transformationInputEpcList :: [InputEPC]
, _transformationOutputEpcList :: [OutputEPC]
} deriving (Show, Eq, Generic)
instance FromJSON ObjectDWhat
instance FromJSON AggregationDWhat
instance FromJSON TransactionDWhat
instance FromJSON TransformationDWhat
instance ToJSON ObjectDWhat
instance ToJSON AggregationDWhat
instance ToJSON TransactionDWhat
instance ToJSON TransformationDWhat
instance ToSchema ObjectDWhat
instance ToSchema AggregationDWhat
instance ToSchema TransactionDWhat
instance ToSchema TransformationDWhat
data DWhat =
ObjWhat ObjectDWhat
| AggWhat AggregationDWhat
| TransactWhat TransactionDWhat
| TransformWhat TransformationDWhat
deriving (Show, Eq, Generic)
$(deriveJSON defaultOptions ''DWhat)
instance ToSchema DWhat