module Passbook.Types(
PassValue(..)
, PassField(..)
, PassType(..)
, PassContent(..)
, Pass(..)
, RelevantDate(..)
, Location(..)
, RGBColor
, BarcodeFormat(..)
, Barcode(..)
, Alignment(..)
, DateTimeStyle(..)
, NumberStyle(..)
, TransitType(..)
, WebService(..)
, Manifest(..)
, rgb
, mkBarcode
, mkSimpleField
) where
import Control.Applicative (pure, (<$>), (<*>))
import Control.Monad (mzero)
import Data.Aeson
import Data.Aeson.TH
import Data.Aeson.Types hiding (Parser)
import Data.Attoparsec.Number
import Data.Attoparsec.Text
import qualified Data.HashMap.Strict as HM
import Data.Text (Text, pack, unpack)
import qualified Data.Text.Lazy as LT
import Data.Time
import Data.Typeable
import System.Locale
import Text.Shakespeare.Text
data PassValue = PassInt Integer
| PassDouble Double
| PassDate UTCTime
| PassText Text
deriving (Eq, Ord, Show, Read, Typeable)
newtype RelevantDate = RelevantDate UTCTime deriving (Eq, Ord, Show, Read, Typeable)
data Location = Location {
latitude :: Double
, longitude :: Double
, altitude :: Maybe Double
, relevantText :: Maybe Text
} deriving (Eq, Ord, Show, Read, Typeable)
data RGBColor = RGB Int Int Int
deriving (Eq, Ord, Show, Read, Typeable)
data BarcodeFormat = QRCode
| PDF417
| Aztec
deriving (Eq, Ord, Show, Read, Typeable)
data Barcode = Barcode {
altText :: Maybe Text
, format :: BarcodeFormat
, message :: Text
, messageEncoding :: Text
} deriving (Eq, Ord, Show, Read, Typeable)
data Alignment = LeftAlign
| Center
| RightAlign
| Natural
deriving (Eq, Ord, Show, Read, Typeable)
data DateTimeStyle = None
| Short
| Medium
| Long
| Full
deriving (Eq, Ord, Show, Read, Typeable)
data NumberStyle = Decimal
| Percent
| Scientific
| SpellOut
deriving (Eq, Ord, Show, Read, Typeable)
data PassField = PassField {
changeMessage :: Maybe Text
, key :: Text
, label :: Maybe Text
, textAlignment :: Maybe Alignment
, value :: PassValue
, dateStyle :: Maybe DateTimeStyle
, timeStyle :: Maybe DateTimeStyle
, isRelative :: Maybe Bool
, currencyCode :: Maybe Text
, numberStyle :: Maybe NumberStyle
} deriving (Eq, Ord, Show, Read, Typeable)
data TransitType = Air
| Boat
| Bus
| Train
| GenericTransit
deriving (Eq, Ord, Show, Read, Typeable)
data PassType = BoardingPass TransitType PassContent
| Coupon PassContent
| Event PassContent
| GenericPass PassContent
| StoreCard PassContent
deriving (Eq, Ord, Show, Read, Typeable)
data WebService = WebService {
authenticationToken :: Text
, webServiceURL :: Text
} deriving (Eq, Ord, Show, Read, Typeable)
data PassContent = PassContent {
headerFields :: [PassField]
, primaryFields :: [PassField]
, secondaryFields :: [PassField]
, auxiliaryFields :: [PassField]
, backFields :: [PassField]
} deriving (Eq, Ord, Show, Read, Typeable)
data Pass = Pass {
description :: Text
, organizationName :: Text
, passTypeIdentifier :: Text
, serialNumber :: Text
, teamIdentifier :: Text
, associatedStoreIdentifiers :: [Text]
, locations :: [Location]
, relevantDate :: Maybe RelevantDate
, barcode :: Maybe Barcode
, backgroundColor :: Maybe RGBColor
, foregroundColor :: Maybe RGBColor
, labelColor :: Maybe Text
, logoText :: Maybe Text
, suppressStripShine :: Maybe Bool
, webService :: Maybe WebService
, passContent :: PassType
} deriving (Eq, Ord, Show, Read, Typeable)
data Manifest = Manifest [(LT.Text, LT.Text)]
instance ToJSON Manifest where
toJSON (Manifest files) =
let pairs = map (\(f, h) -> LT.toStrict f .= h) files
in object pairs
(-:) :: ToJSON a => Text -> Maybe a -> [Pair] -> [Pair]
(-:) _ Nothing = id
(-:) key (Just value) = ((key .= value) :)
$(deriveToJSON id ''PassContent)
instance ToJSON Location where
toJSON Location{..} =
let pairs = ("altitude" -: altitude)
$ ("relevantText" -: relevantText)
$ ["latitude" .= latitude
,"longitude" .= longitude]
in object pairs
instance ToJSON Barcode where
toJSON Barcode{..} =
let pairs = ("altText" -: altText)
$ [ "format" .= format
, "message" .= message
, "messageEncoding" .= messageEncoding ]
in object pairs
instance ToJSON PassField where
toJSON PassField{..} =
let pairs = ("changeMessage" -: changeMessage)
$ ("label" -: label)
$ ("textAlignment" -: textAlignment)
$ ("dateStyle" -: dateStyle)
$ ("timeStyle" -: timeStyle)
$ ("isRelative" -: isRelative)
$ ("currencyCode" -: currencyCode)
$ ("numberStyle" -: numberStyle)
$ ["key" .= key, "value" .= value]
in object pairs
instance ToJSON Pass where
toJSON Pass{..} =
let pairs = ("relevantDate" -: relevantDate)
$ ("barcode" -: barcode)
$ ("backgroundColor" -: backgroundColor)
$ ("foregroundColor" -: foregroundColor)
$ ("labelColor" -: labelColor)
$ ("logoText" -: logoText)
$ ("suppressStripShine" -: suppressStripShine)
$ ("authenticationToken" -: fmap authenticationToken webService)
$ ("webServiceURL" -: fmap webServiceURL webService)
$ [ "description" .= description
, "formatVersion" .= (1 :: Int)
, "organizationName" .= organizationName
, "passTypeIdentifier" .= passTypeIdentifier
, "serialNumber" .= serialNumber
, "teamIdentifier" .= teamIdentifier
, "associatedStoreIdentifiers" .= associatedStoreIdentifiers
, "locations" .= locations
, passTypeName passContent .= passContent]
in object pairs
getPassContent :: PassType -> PassContent
getPassContent pc = case pc of
BoardingPass _ pc -> pc
Coupon pc -> pc
Event pc -> pc
GenericPass pc -> pc
StoreCard pc -> pc
instance ToJSON PassType where
toJSON (BoardingPass tt PassContent{..}) = object [
"transitType" .= tt
, "headerFields" .= headerFields
, "primaryFields" .= primaryFields
, "secondaryFields" .= secondaryFields
, "auxiliaryFields" .= auxiliaryFields
, "backFields" .= backFields ]
toJSON pt = toJSON $ getPassContent pt
renderRGB :: RGBColor -> Text
renderRGB (RGB r g b) = [st|rgb(#{show r},#{show g},#{show b})|]
instance ToJSON RGBColor where
toJSON = toJSON . renderRGB
passTypeName :: PassType -> Text
passTypeName (BoardingPass _ _) = "boardingPass"
passTypeName (Coupon _) = "coupon"
passTypeName (Event _) = "eventTicket"
passTypeName (GenericPass _) = "generic"
passTypeName (StoreCard _) = "storeCard"
instance ToJSON BarcodeFormat where
toJSON QRCode = toJSON ("PKBarcodeFormatQR" :: Text)
toJSON PDF417 = toJSON ("PKBarcodeFormatPDF417" :: Text)
toJSON Aztec = toJSON ("PKBarcodeFormatAztec" :: Text)
instance ToJSON Alignment where
toJSON LeftAlign = toJSON ("PKTextAlignmentLeft" :: Text)
toJSON Center = toJSON ("PKTextAlignmentCenter" :: Text)
toJSON RightAlign = toJSON ("PKTextAlignmentRight" :: Text)
toJSON Natural = toJSON ("PKTextAlignment" :: Text)
instance ToJSON DateTimeStyle where
toJSON None = toJSON ("NSDateFormatterNoStyle" :: Text)
toJSON Short = toJSON ("NSDateFormatterShortStyle" :: Text)
toJSON Medium = toJSON ("NSDateFormatterMediumStyle" :: Text)
toJSON Long = toJSON ("NSDateFormatterLongStyle" :: Text)
toJSON Full = toJSON ("NSDateFormatterFullStyle" :: Text)
instance ToJSON NumberStyle where
toJSON Decimal = toJSON ("PKNumberStyleDecimal" :: Text)
toJSON Percent = toJSON ("PKNumberStylePercent" :: Text)
toJSON Scientific = toJSON ("PKNumberStyleScientific" :: Text)
toJSON SpellOut = toJSON ("PKNumberStyleSpellOut" :: Text)
instance ToJSON TransitType where
toJSON Air = toJSON ("PKTransitTypeAir" :: Text)
toJSON Boat = toJSON ("PKTransitTypeBoat" :: Text)
toJSON Bus = toJSON ("PKTransitTypeBus" :: Text)
toJSON Train = toJSON ("PKTransitTypeTrain" :: Text)
toJSON GenericTransit = toJSON ("PKTransitTypeGeneric" :: Text)
instance ToJSON PassValue where
toJSON (PassInt i) = toJSON i
toJSON (PassDouble d) = toJSON d
toJSON (PassText t) = toJSON t
toJSON (PassDate d) = jsonPassdate d
instance ToJSON RelevantDate where
toJSON (RelevantDate d) = jsonPassdate d
timeFormat = iso8601DateFormat $ Just $ timeFmt defaultTimeLocale
jsonPassdate = toJSON . formatTime defaultTimeLocale timeFormat
parseJsonDate :: Text -> Maybe UTCTime
parseJsonDate = parseTime defaultTimeLocale timeFormat . unpack
instance FromJSON Alignment where
parseJSON (String t) = case t of
"PKTextAlignmentLeft" -> pure LeftAlign
"PKTextAlignmentCenter" -> pure Center
"PKTextAlignmentRight" -> pure RightAlign
"PKTextAlignment" -> pure Natural
_ -> fail "Could not parse text alignment style"
parseJSON _ = mzero
instance FromJSON DateTimeStyle where
parseJSON (String t) = case t of
"NSDateFormatterNoStyle" -> pure None
"NSDateFormatterShortStyle" -> pure Short
"NSDateFormatterMediumStyle" -> pure Medium
"NSDateFormatterLongStyle" -> pure Long
"NSDateFormatterFullStyle" -> pure Full
_ -> fail "Could not parse date formatting style"
parseJSON _ = mzero
instance FromJSON NumberStyle where
parseJSON (String t) = case t of
"PKNumberStyleDecimal" -> pure Decimal
"PKNumberStylePercent" -> pure Percent
"PKNumberStyleScientific" -> pure Scientific
"PKNumberStyleSpellOut" -> pure SpellOut
_ -> fail "Could not parse number formatting style"
parseJSON _ = mzero
instance FromJSON BarcodeFormat where
parseJSON (String t) = case t of
"PKBarcodeFormatQR" -> pure QRCode
"PKBarcodeFormatAztec" -> pure Aztec
"PKBarcodeFormatPDF417" -> pure PDF417
_ -> fail "Could not parse barcode format"
parseJSON _ = mzero
instance FromJSON TransitType where
parseJSON (String t) = case t of
"PKTransitTypeAir" -> pure Air
"PKTransitTypeBoat" -> pure Boat
"PKTransitTypeBus" -> pure Bus
"PKTransitTypeTrain" -> pure Train
"PKTransitTypeGeneric" -> pure GenericTransit
_ -> fail "Could not parse transit type"
parseJSON _ = mzero
instance FromJSON Location where
parseJSON (Object v) = Location <$>
v .: "latitude" <*>
v .: "longitude" <*>
v .:? "altitude" <*>
v .:? "relevantText"
parseJSON _ = mzero
instance FromJSON Barcode where
parseJSON (Object v) = Barcode <$>
v .:? "altText" <*>
v .: "format" <*>
v .: "message" <*>
v .: "messageEncoding"
parseJSON _ = mzero
instance FromJSON PassValue where
parseJSON (Number (I i)) = pure $ PassInt i
parseJSON (Number (D d)) = pure $ PassDouble d
parseJSON (String t) = case parseJsonDate t of
Just d -> pure $ PassDate d
Nothing -> pure $ PassText t
parseJSON _ = fail "Could not parse pass field value"
instance FromJSON PassField where
parseJSON (Object v) =
PassField <$>
v .:? "changeMessage" <*>
v .: "key" <*>
v .:? "label" <*>
v .:? "textAlignment" <*>
v .: "value" <*>
v .:? "dateStyle" <*>
v .:? "timeStyle" <*>
v .:? "isRelative" <*>
v .:? "currencyCode" <*>
v .:? "numberStyle"
parseJSON _ = mzero
instance FromJSON RelevantDate where
parseJSON (String t) = case parseJsonDate t of
(Just d) -> pure $ RelevantDate d
Nothing -> fail "Could not parse relevant date"
parseJSON _ = mzero
$(deriveFromJSON id ''PassContent)
parseWebService :: Maybe Text -> Maybe Text -> Maybe WebService
parseWebService Nothing _ = Nothing
parseWebService _ Nothing = Nothing
parseWebService (Just token) (Just url) = Just $ WebService token url
parseRGB :: Parser RGBColor
parseRGB = RGB <$> ("rgb(" .*> decimal)
<*> ("," .*> decimal)
<*> ("," .*> decimal)
instance FromJSON RGBColor where
parseJSON (String t) = case parseOnly parseRGB t of
Left f -> fail f
Right r -> pure r
parseJSON _ = mzero
instance FromJSON PassType where
parseJSON (Object v)
|HM.member "boardingPass" v =
withValue "boardingPass" $ \val -> case val of
Object o -> BoardingPass <$> o .: "transitType"
<*> parseJSON val
_ -> fail "Could not parse Boarding Pass"
| HM.member "coupon" v =
withValue "coupon" $ \o -> Coupon <$> parseJSON o
| HM.member "eventTicket" v =
withValue "eventTicket" $ \o -> Event <$> parseJSON o
| HM.member "storeCard" v =
withValue "storeCard" $ \o -> StoreCard <$> parseJSON o
| HM.member "generic" v =
withValue "generic" $ \o -> GenericPass <$> parseJSON o
where
withValue k f = f $ v HM.! k
instance FromJSON Pass where
parseJSON o@(Object v) =
Pass <$>
v .: "description" <*>
v .: "organizationName" <*>
v .: "passTypeIdentifier" <*>
v .: "serialNumber" <*>
v .: "teamIdentifier" <*>
v .: "associatedStoreIdentifiers" <*>
v .: "locations" <*>
v .:? "relevantDate" <*>
v .:? "barcode" <*>
v .:? "backgroundColor" <*>
v .:? "foregroundColor" <*>
v .:? "labelColor" <*>
v .:? "logoText" <*>
v .:? "suppressStripShine" <*>
wbs <*>
parseJSON o
where
wbs = parseWebService <$> v .:? "authenticationToken"
<*> v .:? "webServiceURL"
mkBarcode :: Text -> BarcodeFormat -> Barcode
mkBarcode m f = Barcode (Just m) f m "iso-8859-1"
rgb :: (Int, Int, Int) -> Maybe RGBColor
rgb (r, g, b) | isInRange r && isInRange b && isInRange b = Just $ RGB r g b
| otherwise = Nothing
where
isInRange x = 0 <= x && x <= 255
mkSimpleField :: Text
-> PassValue
-> Maybe Text
-> PassField
mkSimpleField k v l = PassField Nothing k l Nothing v Nothing Nothing
Nothing Nothing Nothing