{-# LANGUAGE DeriveGeneric #-}
module Snap.AtlassianConnect.LifecycleResponse
   ( LifecycleResponse(..)
   , ClientKey
   , getLifecycleResponse
   ) where

import           Control.Applicative             ((<$>))
import qualified Data.Aeson                      as A
import           Data.Aeson.Types
import           Data.AesonHelpers
import qualified Data.Text                       as T
import           GHC.Generics
import           Snap.AtlassianConnect.Instances
import qualified Snap.Core                       as SC
import qualified Snap.Snaplet                    as SS

-- | Represents the 'client key' from the Atlassian Connect framework in the host product.
type ClientKey = T.Text

-- | When an Atlassian Connect plugin is installed or uninstalled this is the lifecycle response that your add-on
-- will be sent (in JSON). Use this data structure to handle lifecycle event data from the host application.
data LifecycleResponse = LifecycleResponseInstalled
  { lrKey            :: T.Text
  , lrClientKey      :: ClientKey
  , lrPublicKey      :: T.Text
  , lrSharedSecret   :: Maybe T.Text
  , lrServerVersion  :: Maybe T.Text
  , lrPluginsVersion :: Maybe T.Text
  , lrBaseUrl        :: ConnectURI
  , lrProductType    :: Maybe T.Text
  , lrDescription    :: Maybe T.Text
  , lrEventType      :: Maybe T.Text
  } deriving (Eq, Show, Generic)

instance FromJSON LifecycleResponse where
    parseJSON = genericParseJSON baseOptions
      { fieldLabelModifier = stripFieldNamePrefix "lr"
      }

-- |  A convenience method to get a Lifecycle Response from the response body.
getLifecycleResponse :: SS.Handler b a (Maybe LifecycleResponse)
getLifecycleResponse = A.decode <$> SC.readRequestBody (1024 * 10)