{-# LANGUAGE DeriveGeneric #-}
module Snap.AtlassianConnect.Tenant
   ( TenantWithUser
   , Tenant(..)
   , TenantKey
   ) where

import           Data.Aeson.Types
import qualified Data.Text                            as T
import           GHC.Generics
import qualified Snap.AtlassianConnect.AtlassianTypes as CA
import           Snap.AtlassianConnect.Instances

-- | When we get a tenant from Atlassian Connect we can also optionally reciever the user key that made the request.
-- This structure reflects that possibility.
type TenantWithUser = (Tenant, Maybe CA.UserKey)

instance FromJSON Tenant

-- | Represents a tenant key. The unique identifier for each Atlassian Connect tenant.
type TenantKey = T.Text

-- | Represents an Atlassian Cloud tenant. Your Atlassian Connect add-on can be installed into multiple Atlassian
-- Cloud tenants.
data Tenant = Tenant
   { tenantId      :: Integer       -- ^ Your identifier for this tenant.
   , key           :: TenantKey     -- ^ The unique identifier for this tenant accross Atlassian Connect.
   , publicKey     :: T.Text        -- ^ The public key for this atlassian connect application.
   , oauthClientId :: Maybe T.Text  -- ^ The OAuth Client Id for this tenant. If this add-on does not support user impersonation then this may not be present.
   , sharedSecret  :: T.Text        -- ^ The shared secret for this atlassian connect application. Used for JWT token generation.
   , baseUrl       :: ConnectURI    -- ^ The base url of the Atlassian Cloud host application (product).
   , productType   :: T.Text        -- ^ The type of product you have connected to in the Atlassian Cloud. (E.g. JIRA, Confluence)
   } deriving (Eq, Show, Generic)