{-# LANGUAGE DeriveGeneric     #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications  #-}
module Imm.Callback where
import           Imm.Feed
import qualified Data.Map                  as Map
import           Data.MessagePack.Object
import           Data.Text.Prettyprint.Doc
import           Dhall                     hiding (maybe)
data Callback = Callback
  { _executable :: FilePath
  , _arguments  :: [Text]
  } deriving (Eq, Generic, Ord, Read, Show)
instance FromDhall Callback
instance Pretty Callback where
  pretty (Callback executable arguments) = pretty executable <+> sep (pretty <$> arguments)
data Message = Message Feed FeedElement deriving(Eq, Generic, Ord, Show)
instance MessagePack Message where
  toObject (Message feed element) = toObject @(Map Text Text)
    $ Map.insert "feed" (renderFeed feed)
    $ Map.insert "element" (renderFeedElement element) mempty
  fromObject object = fromObject object >>= \m -> Message
    <$> (lookup @(Map Text Text) "feed" m >>= eitherToMaybe . parseFeed)
    <*> (lookup @(Map Text Text) "element" m >>= eitherToMaybe . parseFeedElement)
    where eitherToMaybe (Right a) = Just a
          eitherToMaybe _         = Nothing