module Network.PinPon.Notification
(
Notification(..)
, headline
, message
, sound
, defaultNotification
) where
import Protolude
import Control.Lens ((&), (?~), mapped, makeLenses)
import Control.Monad (void)
import Data.Aeson.Types
(FromJSON(..), ToJSON(..), genericParseJSON, genericToEncoding,
genericToJSON)
import Data.Text (Text)
import Data.Swagger
(ToSchema(..), description, example, genericDeclareNamedSchema,
schema)
import Lucid
(ToHtml(..), HtmlT, doctypehtml_, head_, title_, body_)
import Network.PinPon.Util
(recordTypeJSONOptions, recordTypeSwaggerOptions)
data Notification = Notification
{ _headline :: !Text
, _message :: !Text
, _sound :: !Text
} deriving (Show, Generic)
makeLenses ''Notification
defaultNotification :: Notification
defaultNotification = Notification "Ring! Ring!" "Someone is ringing the doorbell!" "default"
instance ToJSON Notification where
toJSON = genericToJSON recordTypeJSONOptions
toEncoding = genericToEncoding recordTypeJSONOptions
instance FromJSON Notification where
parseJSON = genericParseJSON recordTypeJSONOptions
instance ToSchema Notification where
declareNamedSchema proxy =
genericDeclareNamedSchema recordTypeSwaggerOptions proxy
& mapped.schema.description ?~ "A doorbell notification"
& mapped.schema.example ?~ toJSON defaultNotification
notificationResultDocument :: (Monad m) => HtmlT m a -> HtmlT m a -> HtmlT m a
notificationResultDocument hl msg =
doctypehtml_ $ do
void $ head_ $ title_ hl
body_ msg
instance ToHtml Notification where
toHtml (Notification hl msg _) = notificationResultDocument (toHtml hl) (toHtml msg)
toHtmlRaw = toHtml