atlassian-connect-descriptor-0.4.10.0: Code that helps you create a valid Atlassian Connect Descriptor.

Copyright(c) Robert Massioli 2014
LicenseAPACHE-2
Maintainerrmassaioli@atlassian.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Data.Connect.Descriptor

Contents

Description

This module provides the data types to let you write your own typesafe Atlassian Connect descriptor and it comes with Aeson bindings so that you can easily convert into json: the format that the Atlassian Connect framework expects.

Atlassian Connect is a framework for writing Add-on's that can run inside the Atlassian Cloud products. You can find more information from the Atlassian Connect documentation https://developer.atlassian.com/static/connect/docs/guides/introduction.html.

The plugin descriptor is defined by the Plugin class. The end result of using this Haskell Module should be for you to end up with a valid Plugin. To turn your plugin into JSON that the Atlassian marketplace can accept just use the encode function from the Aeson library. For example, here in an example Atlassian Connect Descriptor:

pluginToJsonString :: Plugin -> ByteString
pluginToJsonString = encode

exampleDescriptor :: Plugin
exampleDescriptor = (pluginDescriptor (PluginKey "my-example-connect") baseURL (Authentication Jwt))
    { pluginName = Just . Name $ "My Example Connect Addon"
    , pluginDescription = Just "This is an example connect descriptor."
    , vendor = Just $ Vendor (Name "Awesome Devs") (toURI "http://awesome-devs.com")
    , lifecycle = Just defaultLifecycle
    , modules = Just exampleModules
    , enableLicensing = Just False
    , links = HM.fromList
        [ ("documentation", toURI "http://awesome-devs.com/docs")
        , ("source", toURI "http://bitbucket.org/awesome-devs/connect-addon")
        ]
    , scopes = Just [Read, Admin]
    }

exampleModules :: Modules
exampleModules = Modules exampleJIRAModules emptyConfluenceModules

exampleJIRAModules :: JIRAModules
exampleJIRAModules = emptyJIRAModules
    { jmWebPanels = Just
        [ WebPanel
            { wpKey = "test-web-panel"
            , wpName = simpleText "Test Web Panel"
            , wpTooltip = Just $ simpleText "This is a test web panel..."
            , wpLocation = "some-location-in-jira"
            , wpUrl = "/panel/location/for"
            , wpConditions = [staticJiraCondition UserIsAdminJiraCondition]
            , wpWeight = Nothing
            , wpLayout = Nothing
            , wpParams = noParams
            }
        ]
    , jmGeneralPages = Just
        [ JIRAPage
            { jiraPageKey = "test-general-page"
            , jiraPageName = simpleText "Test General Page"
            , jiraPageLocation = Just "some-other-location-in-jira"
            , jiraPageWeight = Just 1234
            , jiraPageUrl = "/panel/general-page"
            , jiraPageIcon = Just IconDetails
                { iconUrl = "/static/path/to/icon.png"
                , iconWidth = Just 20
                , iconHeight = Just 40
                }
            , jiraPageConditions = [staticJiraCondition UserHasIssueHistoryJiraCondition]
            , jiraPageParams = noParams
            }
        ]
    , jmWebhooks = Just
        [ Webhook
            { webhookEvent = JiraIssueDeleted
            , webhookUrl = "/webhook/handle-deletion"
            }
        ]
    }

You can use this library to make your own. This library will experience change whenever the Atlassian Connect descriptor changes. There are likely to be many breaking changes but we will keep track of them using the standard Haskell version structure.

Synopsis

Atlassian Connect Add-on Descriptor

data Plugin Source #

A Plugin is the end result of an Atlassian Connect descriptor. It is what you should provide to the Atlassian Marketplace in order to register your plugin and it is what your Atlassian Cloud customers will download to install your Add-on via the Atlassian UPM (Universal Plugin Manager). Only a very small number of fields are strictly required to generate a valid Atlassian Connect plugin descriptor. Everything that is optional is marked by a maybe type.

Even though we provide documentation here you shoucd check the Atlassian Connect Descriptor documentation if you want to get accurate information on the contents of a plugin: https://developer.atlassian.com/static/connect/docs/modules/

Constructors

Plugin 

Fields

  • pluginKey :: PluginKey

    Plugin keys are required. The important detail about this key is that it should be unique across the Atlassian Marketplace. For example, a good key might be com.yourcompanyorpersonalname.youraddonname because it would be unique in the marketplace.

  • pluginBaseUrl :: URI

    Every plugin must specify a base url where all other relative URI's in the plugin will call to in production. This is the url that the Atlassian Marketplace will query for your descriptor and the url that your customers will come in on. This is especially important for load balanced applications and will also likely be different in your staging and production environments.

  • authentication :: Authentication

    The authentication type that you plugin requires. See Authentication for more details.

  • pluginName :: Maybe (Name Plugin)

    While your add-on does not require a name it is strongly recommended as this is the human readable name that will appear in the UPM amongst other places.

  • pluginDescription :: Maybe Text

    You should give your add-on a description. This description will appear in multiple locations on the Atlassian Marketplace and UPM and will be used to explain what your add-on does.

  • vendor :: Maybe Vendor

    You are the Vendor. Put your details here!

  • lifecycle :: Maybe Lifecycle

    Atlassian Connect addon's have a lifecycle. Register your handlers for the Lifecycle events here so that you can tell, for example, when your addon is installed or enabled.

  • modules :: Maybe Modules

    The modules that your Atlassian Connect add-on provides to the Cloud application. Look at the Modules documentaiton for more information.

  • apiVersion :: Maybe Text

    Required if you wish to provide new versions of your addon to a subset of beta customers.

  • enableLicensing :: Maybe Bool

    If you are giving away a free add-on then you can set this to false, otherwise set it to true.

  • links :: HashMap Text URI

    A collection of custom links that you wish to publish with your add-on. Like documentation or bug-tracking links.

  • scopes :: Maybe [ProductScope]

    The scopes that your add-on requires. See ProductScope for more information.

  • apiMigrations :: Maybe ApiMigrations

    The Migrations that this app has opted into.

Instances
Show Plugin Source # 
Instance details

Defined in Data.Connect.Descriptor

Generic Plugin Source # 
Instance details

Defined in Data.Connect.Descriptor

Associated Types

type Rep Plugin :: Type -> Type #

Methods

from :: Plugin -> Rep Plugin x #

to :: Rep Plugin x -> Plugin #

ToJSON Plugin Source # 
Instance details

Defined in Data.Connect.Descriptor

ToJSON (Name Plugin) Source # 
Instance details

Defined in Data.Connect.Descriptor

type Rep Plugin Source # 
Instance details

Defined in Data.Connect.Descriptor

type Rep Plugin = D1 (MetaData "Plugin" "Data.Connect.Descriptor" "atlassian-connect-descriptor-0.4.10.0-9IB5n7ayoT45x7ylOmuoxH" False) (C1 (MetaCons "Plugin" PrefixI True) (((S1 (MetaSel (Just "pluginKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PluginKey) :*: (S1 (MetaSel (Just "pluginBaseUrl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 URI) :*: S1 (MetaSel (Just "authentication") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Authentication))) :*: (S1 (MetaSel (Just "pluginName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Name Plugin))) :*: (S1 (MetaSel (Just "pluginDescription") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "vendor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Vendor))))) :*: ((S1 (MetaSel (Just "lifecycle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Lifecycle)) :*: (S1 (MetaSel (Just "modules") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Modules)) :*: S1 (MetaSel (Just "apiVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)))) :*: ((S1 (MetaSel (Just "enableLicensing") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 (MetaSel (Just "links") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text URI))) :*: (S1 (MetaSel (Just "scopes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [ProductScope])) :*: S1 (MetaSel (Just "apiMigrations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ApiMigrations)))))))

pluginDescriptor Source #

Arguments

:: PluginKey

The key for your add-on.

-> URI

The base url for your add-on.

-> Authentication

The authentication that your add-on requires.

-> Plugin

A bare-bones Atlassian Connect descriptor.

A helper method to generate a bare-bones Atlassian Connect add-on by providing only the absolutely required fields. You can then use Haskell record syntax to update the plugin with more details. For example:

(pluginDescriptor (PluginKey . pack $ "com.company.mycoolplugin") (fromJust . parseURI $ "http://mycoolplugin.company.com") (Authentication Jwt))
   { pluginName = Just . Name . pack $ "My Cool Plugin"
   , pluginDescription = Just . pack $ "Chil and be cool, you have a plugin descriptor."
   }

Basic Types

data Key t a Source #

This data type represents a Key for a particular data type.

Constructors

Key t 
Instances
Eq t => Eq (Key t a) Source # 
Instance details

Defined in Data.Connect.BaseTypes

Methods

(==) :: Key t a -> Key t a -> Bool #

(/=) :: Key t a -> Key t a -> Bool #

Show t => Show (Key t a) Source # 
Instance details

Defined in Data.Connect.BaseTypes

Methods

showsPrec :: Int -> Key t a -> ShowS #

show :: Key t a -> String #

showList :: [Key t a] -> ShowS #

Generic (Key t a) Source # 
Instance details

Defined in Data.Connect.BaseTypes

Associated Types

type Rep (Key t a) :: Type -> Type #

Methods

from :: Key t a -> Rep (Key t a) x #

to :: Rep (Key t a) x -> Key t a #

type Rep (Key t a) Source # 
Instance details

Defined in Data.Connect.BaseTypes

type Rep (Key t a) = D1 (MetaData "Key" "Data.Connect.BaseTypes" "atlassian-connect-descriptor-0.4.10.0-9IB5n7ayoT45x7ylOmuoxH" False) (C1 (MetaCons "Key" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 t)))

data PluginKey Source #

This data type represents an Atlassian Connect Add-on key.

Constructors

PluginKey Text 
Instances
Eq PluginKey Source # 
Instance details

Defined in Data.Connect.BaseTypes

Show PluginKey Source # 
Instance details

Defined in Data.Connect.BaseTypes

Generic PluginKey Source # 
Instance details

Defined in Data.Connect.BaseTypes

Associated Types

type Rep PluginKey :: Type -> Type #

ToJSON PluginKey Source # 
Instance details

Defined in Data.Connect.BaseTypes

ToJSON (Name PluginKey) Source # 
Instance details

Defined in Data.Connect.BaseTypes

type Rep PluginKey Source # 
Instance details

Defined in Data.Connect.BaseTypes

type Rep PluginKey = D1 (MetaData "PluginKey" "Data.Connect.BaseTypes" "atlassian-connect-descriptor-0.4.10.0-9IB5n7ayoT45x7ylOmuoxH" False) (C1 (MetaCons "PluginKey" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype Timeout Source #

Represents a timeout in seconds.

Constructors

Timeout Second 
Instances
Enum Timeout Source # 
Instance details

Defined in Data.Connect.BaseTypes

Eq Timeout Source # 
Instance details

Defined in Data.Connect.BaseTypes

Methods

(==) :: Timeout -> Timeout -> Bool #

(/=) :: Timeout -> Timeout -> Bool #

Integral Timeout Source # 
Instance details

Defined in Data.Connect.BaseTypes

Num Timeout Source # 
Instance details

Defined in Data.Connect.BaseTypes

Ord Timeout Source # 
Instance details

Defined in Data.Connect.BaseTypes

Real Timeout Source # 
Instance details

Defined in Data.Connect.BaseTypes

Show Timeout Source # 
Instance details

Defined in Data.Connect.BaseTypes

data Vendor Source #

Represents the Vendor of the add-on; which will be you. Put your details in this structure.

Constructors

Vendor 

Fields

  • vendorName :: Name Vendor

    Your name as a Vendor. Might be your personal name or your business name.

  • vendorUrl :: URI

    A URL to a website that represents you as a vendor.

Instances
Eq Vendor Source # 
Instance details

Defined in Data.Connect.BaseTypes

Methods

(==) :: Vendor -> Vendor -> Bool #

(/=) :: Vendor -> Vendor -> Bool #

Show Vendor Source # 
Instance details

Defined in Data.Connect.BaseTypes

Generic Vendor Source # 
Instance details

Defined in Data.Connect.BaseTypes

Associated Types

type Rep Vendor :: Type -> Type #

Methods

from :: Vendor -> Rep Vendor x #

to :: Rep Vendor x -> Vendor #

ToJSON Vendor Source # 
Instance details

Defined in Data.Connect.BaseTypes

ToJSON (Name Vendor) Source # 
Instance details

Defined in Data.Connect.BaseTypes

type Rep Vendor Source # 
Instance details

Defined in Data.Connect.BaseTypes

type Rep Vendor = D1 (MetaData "Vendor" "Data.Connect.BaseTypes" "atlassian-connect-descriptor-0.4.10.0-9IB5n7ayoT45x7ylOmuoxH" False) (C1 (MetaCons "Vendor" PrefixI True) (S1 (MetaSel (Just "vendorName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Name Vendor)) :*: S1 (MetaSel (Just "vendorUrl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 URI)))

data Authentication Source #

If your Atlassian Connect addon wants to perform any server side communication with the host product then you will need to use authentication. Otherwise you should specify that you don't need authentication.

Constructors

Authentication 

Fields

Instances
Eq Authentication Source # 
Instance details

Defined in Data.Connect.BaseTypes

Show Authentication Source # 
Instance details

Defined in Data.Connect.BaseTypes

Generic Authentication Source # 
Instance details

Defined in Data.Connect.BaseTypes

Associated Types

type Rep Authentication :: Type -> Type #

ToJSON Authentication Source # 
Instance details

Defined in Data.Connect.BaseTypes

type Rep Authentication Source # 
Instance details

Defined in Data.Connect.BaseTypes

type Rep Authentication = D1 (MetaData "Authentication" "Data.Connect.BaseTypes" "atlassian-connect-descriptor-0.4.10.0-9IB5n7ayoT45x7ylOmuoxH" False) (C1 (MetaCons "Authentication" PrefixI True) (S1 (MetaSel (Just "authType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AuthType)))

data AuthType Source #

The authentication type that you wish to use in your Add-on.

Constructors

Jwt

If you need to communicate with the host product then you will want to request JWT authentication.

None

If you do not need to communicate the host product then you should request None for authentication.

Instances
Eq AuthType Source # 
Instance details

Defined in Data.Connect.BaseTypes

Show AuthType Source # 
Instance details

Defined in Data.Connect.BaseTypes

Generic AuthType Source # 
Instance details

Defined in Data.Connect.BaseTypes

Associated Types

type Rep AuthType :: Type -> Type #

Methods

from :: AuthType -> Rep AuthType x #

to :: Rep AuthType x -> AuthType #

ToJSON AuthType Source # 
Instance details

Defined in Data.Connect.BaseTypes

type Rep AuthType Source # 
Instance details

Defined in Data.Connect.BaseTypes

type Rep AuthType = D1 (MetaData "AuthType" "Data.Connect.BaseTypes" "atlassian-connect-descriptor-0.4.10.0-9IB5n7ayoT45x7ylOmuoxH" False) (C1 (MetaCons "Jwt" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "None" PrefixI False) (U1 :: Type -> Type))

data IconDetails Source #

Represents an arbitrary icon. Potentially for an Atlassian Connect module or for the entire add-on itself.

Constructors

IconDetails 

Fields

Instances
Show IconDetails Source # 
Instance details

Defined in Data.Connect.BaseTypes

Generic IconDetails Source # 
Instance details

Defined in Data.Connect.BaseTypes

Associated Types

type Rep IconDetails :: Type -> Type #

ToJSON IconDetails Source # 
Instance details

Defined in Data.Connect.BaseTypes

type Rep IconDetails Source # 
Instance details

Defined in Data.Connect.BaseTypes

type Rep IconDetails = D1 (MetaData "IconDetails" "Data.Connect.BaseTypes" "atlassian-connect-descriptor-0.4.10.0-9IB5n7ayoT45x7ylOmuoxH" False) (C1 (MetaCons "IconDetails" PrefixI True) (S1 (MetaSel (Just "iconUrl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: (S1 (MetaSel (Just "iconWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Integer)) :*: S1 (MetaSel (Just "iconHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Integer)))))

data Name a Source #

Atlassian Connect descriptors contain many names: module names, add-on names, vendor names etc. We want to make sure that these names don't get put in places that they do not belong. Or, if they do get moved around, they get moved around specifically. We are just adding type saefty to names.

Constructors

Name Text 
Instances
Eq (Name a) Source # 
Instance details

Defined in Data.Connect.BaseTypes

Methods

(==) :: Name a -> Name a -> Bool #

(/=) :: Name a -> Name a -> Bool #

Show (Name a) Source # 
Instance details

Defined in Data.Connect.BaseTypes

Methods

showsPrec :: Int -> Name a -> ShowS #

show :: Name a -> String #

showList :: [Name a] -> ShowS #

Generic (Name a) Source # 
Instance details

Defined in Data.Connect.BaseTypes

Associated Types

type Rep (Name a) :: Type -> Type #

Methods

from :: Name a -> Rep (Name a) x #

to :: Rep (Name a) x -> Name a #

ToJSON (Name Vendor) Source # 
Instance details

Defined in Data.Connect.BaseTypes

ToJSON (Name PluginKey) Source # 
Instance details

Defined in Data.Connect.BaseTypes

ToJSON (Name Plugin) Source # 
Instance details

Defined in Data.Connect.Descriptor

type Rep (Name a) Source # 
Instance details

Defined in Data.Connect.BaseTypes

type Rep (Name a) = D1 (MetaData "Name" "Data.Connect.BaseTypes" "atlassian-connect-descriptor-0.4.10.0-9IB5n7ayoT45x7ylOmuoxH" False) (C1 (MetaCons "Name" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data I18nText Source #

Represents a standard text type in the descriptor than may be Internationalised in the future. However, currently there is no I18n support: http://goo.gl/9vJEsW

Constructors

I18nText 

Fields

Instances
Show I18nText Source # 
Instance details

Defined in Data.Connect.BaseTypes

Generic I18nText Source # 
Instance details

Defined in Data.Connect.BaseTypes

Associated Types

type Rep I18nText :: Type -> Type #

Methods

from :: I18nText -> Rep I18nText x #

to :: Rep I18nText x -> I18nText #

ToJSON I18nText Source # 
Instance details

Defined in Data.Connect.BaseTypes

type Rep I18nText Source # 
Instance details

Defined in Data.Connect.BaseTypes

type Rep I18nText = D1 (MetaData "I18nText" "Data.Connect.BaseTypes" "atlassian-connect-descriptor-0.4.10.0-9IB5n7ayoT45x7ylOmuoxH" False) (C1 (MetaCons "I18nText" PrefixI True) (S1 (MetaSel (Just "dValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "dI18n") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

simpleText :: Text -> I18nText Source #

Since there is currently no I18n support (http://goo.gl/9vJEsW) we have this helper method to quickly create an I18nText from a standard Text object.

data URLBean Source #

This represents a URL wrapped as an object instead of as a plain text element.

Constructors

URLBean 

Fields

Instances
Show URLBean Source # 
Instance details

Defined in Data.Connect.BaseTypes

Generic URLBean Source # 
Instance details

Defined in Data.Connect.BaseTypes

Associated Types

type Rep URLBean :: Type -> Type #

Methods

from :: URLBean -> Rep URLBean x #

to :: Rep URLBean x -> URLBean #

ToJSON URLBean Source # 
Instance details

Defined in Data.Connect.BaseTypes

type Rep URLBean Source # 
Instance details

Defined in Data.Connect.BaseTypes

type Rep URLBean = D1 (MetaData "URLBean" "Data.Connect.BaseTypes" "atlassian-connect-descriptor-0.4.10.0-9IB5n7ayoT45x7ylOmuoxH" False) (C1 (MetaCons "URLBean" PrefixI True) (S1 (MetaSel (Just "ubUrl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

toUrl :: Text -> URLBean Source #

Wrap a regular Text based URL inside a URLBean.

data Length Source #

A basic length type for HTML elements. Useful for WebPanels and other modules that may require length specifications.

Constructors

Pixels Integer

Specify a length in pixels

Percentage Integer

Specify a length as a percentage in the range [0-100].

Instances
Show Length Source # 
Instance details

Defined in Data.Connect.BaseTypes

Generic Length Source # 
Instance details

Defined in Data.Connect.BaseTypes

Associated Types

type Rep Length :: Type -> Type #

Methods

from :: Length -> Rep Length x #

to :: Rep Length x -> Length #

ToJSON Length Source # 
Instance details

Defined in Data.Connect.BaseTypes

type Rep Length Source # 
Instance details

Defined in Data.Connect.BaseTypes

type Rep Length = D1 (MetaData "Length" "Data.Connect.BaseTypes" "atlassian-connect-descriptor-0.4.10.0-9IB5n7ayoT45x7ylOmuoxH" False) (C1 (MetaCons "Pixels" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)) :+: C1 (MetaCons "Percentage" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)))

type Weight = Integer Source #

Represents the weight of an element in a menu.

type ModuleParams = HashMap Text Text Source #

The standard representation for module parameters.

noParams :: ModuleParams Source #

No parameters. A useful helper when you don't want to pass any parameters to a module.

Migrations

data ApiMigrations Source #

Constructors

ApiMigrations 

Fields

Instances
Show ApiMigrations Source # 
Instance details

Defined in Data.Connect.Descriptor

Generic ApiMigrations Source # 
Instance details

Defined in Data.Connect.Descriptor

Associated Types

type Rep ApiMigrations :: Type -> Type #

ToJSON ApiMigrations Source # 
Instance details

Defined in Data.Connect.Descriptor

type Rep ApiMigrations Source # 
Instance details

Defined in Data.Connect.Descriptor

type Rep ApiMigrations = D1 (MetaData "ApiMigrations" "Data.Connect.Descriptor" "atlassian-connect-descriptor-0.4.10.0-9IB5n7ayoT45x7ylOmuoxH" False) (C1 (MetaCons "ApiMigrations" PrefixI True) (S1 (MetaSel (Just "migrationGdpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))

Lifecycle

data Lifecycle Source #

Every Atlassian Connect add-on can be installed, uninstalled, enabled and disabled. These are known as Lifecycle events. These events will fire on each and every Cloud instance that your add-on is installed on. You can request in your Atlassian Connect add-on descriptor to be alerted of lifecycle events. When the event fires, if you have requested it, you will be given the details of the event in a JSON blob by the host application.

The lifecycle events are documented fully in the Atlassian Connect documentation: https://developer.atlassian.com/static/connect/docs/modules/lifecycle.html

It is important to note that the installed event is particularily important to any Atlassian Connect add-on that needs to use Jwt auth tokens because the installed handler will come with the shared secret for your add-on on that particular instance.

Constructors

Lifecycle 

Fields

  • installed :: Maybe URI

    Potential relative URI to call every time an add-on is installed on an instance.

  • uninstalled :: Maybe URI

    Potential relative URI to call every time an add-on is uninstalled on an instance.

  • enabled :: Maybe URI

    Potential relative URI to call every time an add-on is enabled on an instance.

  • disabled :: Maybe URI

    Potential relative URI to call every time an add-on is disabled on an instance.

Instances
Show Lifecycle Source # 
Instance details

Defined in Data.Connect.Lifecycle

Generic Lifecycle Source # 
Instance details

Defined in Data.Connect.Lifecycle

Associated Types

type Rep Lifecycle :: Type -> Type #

ToJSON Lifecycle Source # 
Instance details

Defined in Data.Connect.Lifecycle

type Rep Lifecycle Source # 
Instance details

Defined in Data.Connect.Lifecycle

type Rep Lifecycle = D1 (MetaData "Lifecycle" "Data.Connect.Lifecycle" "atlassian-connect-descriptor-0.4.10.0-9IB5n7ayoT45x7ylOmuoxH" False) (C1 (MetaCons "Lifecycle" PrefixI True) ((S1 (MetaSel (Just "installed") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe URI)) :*: S1 (MetaSel (Just "uninstalled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe URI))) :*: (S1 (MetaSel (Just "enabled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe URI)) :*: S1 (MetaSel (Just "disabled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe URI)))))

emptyLifecycle :: Lifecycle Source #

The empty Lifecycle allowing you to specify exactly which events you wish to handle with Haskell record syntax.

defaultLifecycle :: Lifecycle Source #

The default Lifecycle where installed goes to /installed and so on and so forth for every lifecycle event. You can choose to disclude certain events by Nothing them out.

Add-on Modules

data Modules Source #

Modules are perhaps the most important part of your Atlassian Connect descriptor. They specify which parts of the host application you wish to inject content into. They provide your entry point into the host application.

Atlassian Connect provides a large set of pre-defined entry points into the host application. Some of which are common to every application and some of which are unique to the particular application that you are targeting:

Note: One important point about modules: they must all have a key and that key must be unique inside the same Atlassian Connect addon.

Constructors

Modules 

Fields

Instances
Show Modules Source # 
Instance details

Defined in Data.Connect.Modules

Generic Modules Source # 
Instance details

Defined in Data.Connect.Modules

Associated Types

type Rep Modules :: Type -> Type #

Methods

from :: Modules -> Rep Modules x #

to :: Rep Modules x -> Modules #

ToJSON Modules Source # 
Instance details

Defined in Data.Connect.Modules

type Rep Modules Source # 
Instance details

Defined in Data.Connect.Modules

type Rep Modules = D1 (MetaData "Modules" "Data.Connect.Modules" "atlassian-connect-descriptor-0.4.10.0-9IB5n7ayoT45x7ylOmuoxH" False) (C1 (MetaCons "Modules" PrefixI True) (S1 (MetaSel (Just "jiraModules") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JIRAModules) :*: S1 (MetaSel (Just "confluenceModules") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ConfluenceModules)))

data JIRAModules Source #

A collection of all of the JIRA Modules that you can define. For more documentation on which Modules are supported the Atlassian Connect framework please see Modules. You can also find more documentation on each of the modules.

Instances
Show JIRAModules Source # 
Instance details

Defined in Data.Connect.Modules

Generic JIRAModules Source # 
Instance details

Defined in Data.Connect.Modules

Associated Types

type Rep JIRAModules :: Type -> Type #

ToJSON JIRAModules Source # 
Instance details

Defined in Data.Connect.Modules

type Rep JIRAModules Source # 
Instance details

Defined in Data.Connect.Modules

type Rep JIRAModules = D1 (MetaData "JIRAModules" "Data.Connect.Modules" "atlassian-connect-descriptor-0.4.10.0-9IB5n7ayoT45x7ylOmuoxH" False) (C1 (MetaCons "JIRAModules" PrefixI True) ((((S1 (MetaSel (Just "jmWebSections") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [JIRAWebSection])) :*: S1 (MetaSel (Just "jmWebItems") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [WebItem]))) :*: (S1 (MetaSel (Just "jmWebPanels") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [WebPanel])) :*: S1 (MetaSel (Just "jmGeneralPages") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [JIRAPage])))) :*: ((S1 (MetaSel (Just "jmAdminPages") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [JIRAPage])) :*: S1 (MetaSel (Just "jmConfigurePage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe JIRAPage))) :*: (S1 (MetaSel (Just "jmJiraSearchRequestViews") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [JIRASearchRequestView])) :*: (S1 (MetaSel (Just "jmJiraProfileTabPanels") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [JIRAGenericTabPanel])) :*: S1 (MetaSel (Just "jmJiraVersionTabPanels") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [JIRAGenericTabPanel])))))) :*: (((S1 (MetaSel (Just "jmJiraProjectTabPanels") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [JIRAGenericTabPanel])) :*: S1 (MetaSel (Just "jmJiraProjectAdminTabPanels") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [JIRAProjectAdminTabPanel]))) :*: (S1 (MetaSel (Just "jmJiraIssueTabPanels") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [JIRAGenericTabPanel])) :*: (S1 (MetaSel (Just "jmJiraComponentTabPanels") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [JIRAGenericTabPanel])) :*: S1 (MetaSel (Just "jmJiraIssueContents") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [JIRAIssueContent]))))) :*: ((S1 (MetaSel (Just "jmJiraIssueGlances") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [JIRAIssueGlance])) :*: S1 (MetaSel (Just "jmJiraReports") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [JIRAReport]))) :*: (S1 (MetaSel (Just "jmWebhooks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Webhook])) :*: (S1 (MetaSel (Just "jmJiraWorkflowPostFunctions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [JIRAWorkflowPostFunction])) :*: S1 (MetaSel (Just "jmJiraEntityProperties") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [JIRAEntityProperties]))))))))

emptyJIRAModules :: JIRAModules Source #

Empty JIRA Modules; useful when you only want to define a few modules via Haskell record syntax.

data ConfluenceModules Source #

A collection of all of the Confluence Modules that you can define. For more documentation on which Modules are supported the Atlassian Connect framework please see Modules. You can also find more documentation on each of the modules.

Instances
Show ConfluenceModules Source # 
Instance details

Defined in Data.Connect.Modules

Generic ConfluenceModules Source # 
Instance details

Defined in Data.Connect.Modules

Associated Types

type Rep ConfluenceModules :: Type -> Type #

ToJSON ConfluenceModules Source # 
Instance details

Defined in Data.Connect.Modules

type Rep ConfluenceModules Source # 
Instance details

Defined in Data.Connect.Modules

type Rep ConfluenceModules = D1 (MetaData "ConfluenceModules" "Data.Connect.Modules" "atlassian-connect-descriptor-0.4.10.0-9IB5n7ayoT45x7ylOmuoxH" False) (C1 (MetaCons "ConfluenceModules" PrefixI True) (S1 (MetaSel (Just "confluenceWebPanels") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [WebPanel])) :*: S1 (MetaSel (Just "confluenceWebItems") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [WebItem]))))

emptyConfluenceModules :: ConfluenceModules Source #

Empty Confluence Modules; useful when you only want to define a few modules via Haskell record syntax.

Web Sections, Items and Panels

data JIRAWebSection Source #

A JIRAWebSection represents a location in the host application that you can add WebItems to. In this way you can give your add-on sections to inject content into.

For more information read the Atlassian Connect documentation: https://developer.atlassian.com/static/connect/docs/modules/jira/web-section.html

Constructors

JIRAWebSection 

Fields

Instances
Show JIRAWebSection Source # 
Instance details

Defined in Data.Connect.Modules

Generic JIRAWebSection Source # 
Instance details

Defined in Data.Connect.Modules

Associated Types

type Rep JIRAWebSection :: Type -> Type #

ToJSON JIRAWebSection Source # 
Instance details

Defined in Data.Connect.Modules

type Rep JIRAWebSection Source # 
Instance details

Defined in Data.Connect.Modules

data WebItem Source #

A WebItem is a like that can be placed in one of an Atlassian Products many menus. Currently the WebItem has the same structure for both JIRA and Confluence. You can read their documentation here:

Web items are very useful for providing links to your Atlassian Connect pages. See GeneralPage or AdminPage for more information.

Constructors

WebItem 

Fields

Instances
Show WebItem Source # 
Instance details

Defined in Data.Connect.Modules

Generic WebItem Source # 
Instance details

Defined in Data.Connect.Modules

Associated Types

type Rep WebItem :: Type -> Type #

Methods

from :: WebItem -> Rep WebItem x #

to :: Rep WebItem x -> WebItem #

ToJSON WebItem Source # 
Instance details

Defined in Data.Connect.Modules

type Rep WebItem Source # 
Instance details

Defined in Data.Connect.Modules

data WebItemContext Source #

Wether to open the url relative to the current page, the current addon or the current product. This lets you control where Atlassian Connect web items point to.

Instances
Show WebItemContext Source # 
Instance details

Defined in Data.Connect.Modules

Generic WebItemContext Source # 
Instance details

Defined in Data.Connect.Modules

Associated Types

type Rep WebItemContext :: Type -> Type #

ToJSON WebItemContext Source # 
Instance details

Defined in Data.Connect.Modules

type Rep WebItemContext Source # 
Instance details

Defined in Data.Connect.Modules

type Rep WebItemContext = D1 (MetaData "WebItemContext" "Data.Connect.Modules" "atlassian-connect-descriptor-0.4.10.0-9IB5n7ayoT45x7ylOmuoxH" False) (C1 (MetaCons "PageContext" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "AddonContext" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ProductContext" PrefixI False) (U1 :: Type -> Type)))

data WebPanel Source #

A WebPanel is an injectable segment of the host application that you can place content inside. Currently the WebPanel has the same structure for both JIRA and Confluence but, potentially, that could change in the future. You can read their Atlassian Connect documentation here:

Here is what an example Hello World web panel might look like:

helloWorldWebPanel = WebPanel
   { wpKey = "hello-world"
   , wpName = Name "Hello world!"
   , wpUrl = "/panel/show-hello-world"
   , wpLocation = "atl.jira.view.issue.right.context"
   , wpConditions = [staticJiraCondition UserIsLoggedInJiraCondition]
   }
   where
      toURI = fromJust . parseRelativeReference

WebPanels are a great way to inject your add-on's content into the host application.

Constructors

WebPanel 

Fields

Instances
Show WebPanel Source # 
Instance details

Defined in Data.Connect.Modules

Generic WebPanel Source # 
Instance details

Defined in Data.Connect.Modules

Associated Types

type Rep WebPanel :: Type -> Type #

Methods

from :: WebPanel -> Rep WebPanel x #

to :: Rep WebPanel x -> WebPanel #

ToJSON WebPanel Source # 
Instance details

Defined in Data.Connect.Modules

type Rep WebPanel Source # 
Instance details

Defined in Data.Connect.Modules

data WebPanelLayout Source #

A WebPanelLayout allows you to specify the dimensions of your Web Panel if that is required.

Constructors

WebPanelLayout 
Instances
Show WebPanelLayout Source # 
Instance details

Defined in Data.Connect.Modules

Generic WebPanelLayout Source # 
Instance details

Defined in Data.Connect.Modules

Associated Types

type Rep WebPanelLayout :: Type -> Type #

ToJSON WebPanelLayout Source # 
Instance details

Defined in Data.Connect.Modules

type Rep WebPanelLayout Source # 
Instance details

Defined in Data.Connect.Modules

type Rep WebPanelLayout = D1 (MetaData "WebPanelLayout" "Data.Connect.Modules" "atlassian-connect-descriptor-0.4.10.0-9IB5n7ayoT45x7ylOmuoxH" False) (C1 (MetaCons "WebPanelLayout" PrefixI True) (S1 (MetaSel (Just "wplWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Length) :*: S1 (MetaSel (Just "wplHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Length)))

JIRA Pages

data JIRAPage Source #

A JIRAPage is gives you a location in the host product that you addon can present content and behave just like any other host product page. The main types of pages in JIRA are:

  • General pages: for just getting a geniric chunk of realestate to display your content.
  • Admin pages: for getting a page in the admin seciton of JIRA to display your content.
  • Configuration page: Every Atlassian Connect plugin can have a configuration page to configure the plugin when installed.

This is very useful for pages like Configuration screens or Statistics pages where you really want the user to be immersed in working with your add-on inside the host product.

General pages, like Web Panels, are common to JIRA and Confluence and share the same json format. However they have separate documentation:

Even though, at this point in time, the documentation looks identical. You can find the Admin page and Configure page documentation in the official Atlassian Connect documentation too.

Constructors

JIRAPage 

Fields

Instances
Show JIRAPage Source # 
Instance details

Defined in Data.Connect.Modules

Generic JIRAPage Source # 
Instance details

Defined in Data.Connect.Modules

Associated Types

type Rep JIRAPage :: Type -> Type #

Methods

from :: JIRAPage -> Rep JIRAPage x #

to :: Rep JIRAPage x -> JIRAPage #

ToJSON JIRAPage Source # 
Instance details

Defined in Data.Connect.Modules

type Rep JIRAPage Source # 
Instance details

Defined in Data.Connect.Modules

JIRA Tab Panels

data JIRAGenericTabPanel Source #

JIRA has the concept of a TabPanel which is a panel where you can inject content along with a WebItem that is automatically created for you so that you can navigate to the tab panel in question. Tab panels often have a common format and this JIRAGenericTabPanel encapsulates that common format and allows you to apply it to many different scenarios.

Constructors

JIRAGenericTabPanel 

Fields

  • jtpKey :: Text

    The add-on unique key for this module.

  • jtpName :: I18nText

    The user facing name of this panel. Likely to appear as the name of the link to the tab panel.

  • jtpUrl :: Text

    The URL to your addon where you will provide the content for the panel.

  • jtpConditions :: [Condition]

    The conditions under which this tapb panel should be displayed.

  • jtpWeight :: Maybe Weight

    The higher the weight the lower down in the list of tabs the link to this tab panel will be displayed.

  • jtpParams :: ModuleParams

    Optional parameters for the tab panel.

Instances
Show JIRAGenericTabPanel Source # 
Instance details

Defined in Data.Connect.Modules

Generic JIRAGenericTabPanel Source # 
Instance details

Defined in Data.Connect.Modules

Associated Types

type Rep JIRAGenericTabPanel :: Type -> Type #

ToJSON JIRAGenericTabPanel Source # 
Instance details

Defined in Data.Connect.Modules

type Rep JIRAGenericTabPanel Source # 
Instance details

Defined in Data.Connect.Modules

data JIRAProjectAdminTabPanel Source #

A JIRAProjectAdminTabPanel is useful for when you want to add a page to the administration screens of a project. This module will create a web item in the sidebar of every project for you and provide a web panel in the JIRA Project Admin section.

Constructors

JIRAProjectAdminTabPanel 

Fields

  • jpatpKey :: Text

    The add-on unique key for this module.

  • jpatpName :: I18nText

    The user facing name of this panel. Likely to appear as the name of the link to the tab panel.

  • jpatpUrl :: Text

    The URL to your addon where you will provide the content for the panel.

  • jpatpLocation :: Text

    The location in JIRA Admin that you wish the link to this panel to appear.

  • jpatpConditions :: [Condition]

    The conditions under which this panel should be displayed. UserIsAdminCondition is redundant.

  • jpatpWeight :: Maybe Weight

    The higher the weight the lower down in the list of tabs the link to this tab panel will be displayed.

  • jpatpParams :: ModuleParams

    Optional parameters for the tab panel.

Instances
Show JIRAProjectAdminTabPanel Source # 
Instance details

Defined in Data.Connect.Modules

Generic JIRAProjectAdminTabPanel Source # 
Instance details

Defined in Data.Connect.Modules

Associated Types

type Rep JIRAProjectAdminTabPanel :: Type -> Type #

ToJSON JIRAProjectAdminTabPanel Source # 
Instance details

Defined in Data.Connect.Modules

type Rep JIRAProjectAdminTabPanel Source # 
Instance details

Defined in Data.Connect.Modules

JIRA Specific Modules

data JIRASearchRequestView Source #

A Search Request View allows you to render a custom representation of a search result. Rendering a custom XML format is a common example.

For more information read the Atlassian Connect documentation: https://developer.atlassian.com/static/connect/docs/modules/jira/search-request-view.html

Constructors

JIRASearchRequestView 

Fields

Instances
Show JIRASearchRequestView Source # 
Instance details

Defined in Data.Connect.Modules

Generic JIRASearchRequestView Source # 
Instance details

Defined in Data.Connect.Modules

Associated Types

type Rep JIRASearchRequestView :: Type -> Type #

ToJSON JIRASearchRequestView Source # 
Instance details

Defined in Data.Connect.Modules

type Rep JIRASearchRequestView Source # 
Instance details

Defined in Data.Connect.Modules

data JIRAIssueContent Source #

This module adds a content button to the context area of the new Jira issue view. Content can have an icon, tooltip, and target.

Constructors

JIRAIssueContent 

Fields

Instances
Show JIRAIssueContent Source # 
Instance details

Defined in Data.Connect.Modules

Generic JIRAIssueContent Source # 
Instance details

Defined in Data.Connect.Modules

Associated Types

type Rep JIRAIssueContent :: Type -> Type #

ToJSON JIRAIssueContent Source # 
Instance details

Defined in Data.Connect.Modules

type Rep JIRAIssueContent Source # 
Instance details

Defined in Data.Connect.Modules

data JIRAIssueGlance Source #

This module adds a glance to the context area of the new Jira issue view. Glances can have an icon, content, and status.

Constructors

JIRAIssueGlance 

Fields

Instances
Show JIRAIssueGlance Source # 
Instance details

Defined in Data.Connect.Modules

Generic JIRAIssueGlance Source # 
Instance details

Defined in Data.Connect.Modules

Associated Types

type Rep JIRAIssueGlance :: Type -> Type #

ToJSON JIRAIssueGlance Source # 
Instance details

Defined in Data.Connect.Modules

type Rep JIRAIssueGlance Source # 
Instance details

Defined in Data.Connect.Modules

data JIRAReport Source #

A JIRAReport will provide a report on the JIRA issues in the project. It allows you to write custom reporting for JIRA.

For more information read the Atlassian Connect documentation: https://developer.atlassian.com/static/connect/docs/modules/jira/report.html

Constructors

JIRAReport 

Fields

Instances
Show JIRAReport Source # 
Instance details

Defined in Data.Connect.Modules

Generic JIRAReport Source # 
Instance details

Defined in Data.Connect.Modules

Associated Types

type Rep JIRAReport :: Type -> Type #

ToJSON JIRAReport Source # 
Instance details

Defined in Data.Connect.Modules

type Rep JIRAReport Source # 
Instance details

Defined in Data.Connect.Modules

data JIRAReportCategory Source #

The report category for a JIRAReport. Useful in organising the different types of reports.

Constructors

AgileRC

This report is visible to agile customers.

IssueAnalysisRC

This report does issue analysis.

ForecastManagementRC

This report considers future of the project state.

OtherRC

Any report that does not fit into the other categories goes here.

data Target Source #

A Target represents the location that a link will be opened into.

Constructors

TargetPage

Open the link into the current page.

TargetDialog (Maybe DialogOptions)

Open the link into a dialog on the page with the given options.

TargetInlineDialog (Maybe InlineDialogOptions)

Open the link into an inline dialog with the given options.

Instances
Show Target Source # 
Instance details

Defined in Data.Connect.Modules

ToJSON Target Source # 
Instance details

Defined in Data.Connect.Modules

data JIRAWorkflowPostFunction Source #

A JIRAWorkflowPostFunction carries out any additional processing required after a JIRA workflow transition is executed.

For more information read the Atlassian Connect documentation: https://developer.atlassian.com/static/connect/docs/modules/jira/workflow-post-function.html

Or you could read the JIRA documentation on Workflow Post Functions to learn more: https://confluence.atlassian.com/display/Cloud/Advanced+Workflow+Configuration#AdvancedWorkflowConfiguration-postfunctions

Constructors

JIRAWorkflowPostFunction 

Fields

Instances
Show JIRAWorkflowPostFunction Source # 
Instance details

Defined in Data.Connect.Modules

Generic JIRAWorkflowPostFunction Source # 
Instance details

Defined in Data.Connect.Modules

Associated Types

type Rep JIRAWorkflowPostFunction :: Type -> Type #

ToJSON JIRAWorkflowPostFunction Source # 
Instance details

Defined in Data.Connect.Modules

type Rep JIRAWorkflowPostFunction Source # 
Instance details

Defined in Data.Connect.Modules

data DialogOptions Source #

Options for a dialog that a link may be opened into.

Constructors

DialogOptions 

Fields

Instances
Show DialogOptions Source # 
Instance details

Defined in Data.Connect.Modules

Generic DialogOptions Source # 
Instance details

Defined in Data.Connect.Modules

Associated Types

type Rep DialogOptions :: Type -> Type #

ToJSON DialogOptions Source # 
Instance details

Defined in Data.Connect.Modules

type Rep DialogOptions Source # 
Instance details

Defined in Data.Connect.Modules

type Rep DialogOptions = D1 (MetaData "DialogOptions" "Data.Connect.Modules" "atlassian-connect-descriptor-0.4.10.0-9IB5n7ayoT45x7ylOmuoxH" False) (C1 (MetaCons "DialogOptions" PrefixI True) (S1 (MetaSel (Just "doHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Integer)) :*: (S1 (MetaSel (Just "doWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Integer)) :*: S1 (MetaSel (Just "doChrome") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool)))))

data InlineDialogOptions Source #

Options for an inline dialog that a link may be opened into.

Constructors

InlineDialogOptions 

Fields

Instances
Show InlineDialogOptions Source # 
Instance details

Defined in Data.Connect.Modules

Generic InlineDialogOptions Source # 
Instance details

Defined in Data.Connect.Modules

Associated Types

type Rep InlineDialogOptions :: Type -> Type #

ToJSON InlineDialogOptions Source # 
Instance details

Defined in Data.Connect.Modules

type Rep InlineDialogOptions Source # 
Instance details

Defined in Data.Connect.Modules

data JIRAEntityProperties Source #

JIRAEntityProperties are used to set Key / Value pair information on JIRA Issues that can be searched via JQL and are indexed by JIRA. The can also be accessed directly via rest api so they allow you to store data in client-only Atlassian Connect plugins. Very handy!

The data stored as entity properties is in the JSON data format so multiple values can be stored against the one property.

For more information read the JIRA Documentation on the topic: https://developer.atlassian.com/display/JIRADEV/JIRA+Entity+Properties+Overview

Or read the Atlassian Connect documentation on the topic: https://developer.atlassian.com/static/connect/docs/modules/jira/entity-property.html

Constructors

JIRAEntityProperties 

Fields

Instances
Show JIRAEntityProperties Source # 
Instance details

Defined in Data.Connect.Modules

Generic JIRAEntityProperties Source # 
Instance details

Defined in Data.Connect.Modules

Associated Types

type Rep JIRAEntityProperties :: Type -> Type #

ToJSON JIRAEntityProperties Source # 
Instance details

Defined in Data.Connect.Modules

type Rep JIRAEntityProperties Source # 
Instance details

Defined in Data.Connect.Modules

type Rep JIRAEntityProperties = D1 (MetaData "JIRAEntityProperties" "Data.Connect.Modules" "atlassian-connect-descriptor-0.4.10.0-9IB5n7ayoT45x7ylOmuoxH" False) (C1 (MetaCons "JIRAEntityProperties" PrefixI True) ((S1 (MetaSel (Just "jepKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "jepName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 I18nText)) :*: (S1 (MetaSel (Just "jepEntityType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe EntityType)) :*: S1 (MetaSel (Just "jepKeyConfigurations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [KeyConfiguration]))))

data EntityType Source #

An EntityType represents the type of entity that the JIRA Entity Property should be attatched to. By default entity types are attatched to issues.

Constructors

IssueEntityType 

data KeyConfiguration Source #

A KeyConfiguration is the key for this particular property and the JSON flattened paths to the elements that should be extracted from this property. For more information see the Atlassian Connect documentation: https://developer.atlassian.com/static/connect/docs/modules/fragment/index-key-configuration.html

Constructors

KeyConfiguration 

Fields

Instances
Show KeyConfiguration Source # 
Instance details

Defined in Data.Connect.Modules

Generic KeyConfiguration Source # 
Instance details

Defined in Data.Connect.Modules

Associated Types

type Rep KeyConfiguration :: Type -> Type #

ToJSON KeyConfiguration Source # 
Instance details

Defined in Data.Connect.Modules

type Rep KeyConfiguration Source # 
Instance details

Defined in Data.Connect.Modules

type Rep KeyConfiguration = D1 (MetaData "KeyConfiguration" "Data.Connect.Modules" "atlassian-connect-descriptor-0.4.10.0-9IB5n7ayoT45x7ylOmuoxH" False) (C1 (MetaCons "KeyConfiguration" PrefixI True) (S1 (MetaSel (Just "kcPropertyKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "kcExtractions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Extraction])))

data Extraction Source #

An Extraction represents a snippet of data that should be extracted from a KeyConfiguration such that it is Indexed by JIRA and capable of being searched in JQL.

Constructors

Extraction 

Fields

Instances
Show Extraction Source # 
Instance details

Defined in Data.Connect.Modules

Generic Extraction Source # 
Instance details

Defined in Data.Connect.Modules

Associated Types

type Rep Extraction :: Type -> Type #

ToJSON Extraction Source # 
Instance details

Defined in Data.Connect.Modules

type Rep Extraction Source # 
Instance details

Defined in Data.Connect.Modules

type Rep Extraction = D1 (MetaData "Extraction" "Data.Connect.Modules" "atlassian-connect-descriptor-0.4.10.0-9IB5n7ayoT45x7ylOmuoxH" False) (C1 (MetaCons "Extraction" PrefixI True) (S1 (MetaSel (Just "extractionObjectName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: (S1 (MetaSel (Just "extractionType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ExtractionType) :*: S1 (MetaSel (Just "extractionAlias") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)))))

data ExtractionType Source #

The style in which the data should be extracted and indexed. For example, you may want the data to be treated as a Date or as a Number.

Constructors

ExtractionTypeNumber

Index the data as a numeric type.

ExtractionTypeText

Index the data as a text based type, with words.

ExtractionTypeString

Index the data as an exact string.

ExtractionTypeDate

Index the data as a Date.

ExtractionTypeUser

Index the data as Atlassian Account IDs.

Webhooks

data Webhook Source #

When users of the host application perform updates your Atlassian Connect add-on will not be alerted unless it listens to the WebhookEvents coming from that application. Webhooks are the way to close the issue recency loop in the Atlassian products. It is important to note that Webhooks are 'best effort' and that there is no guarantee that the webhook will make it to your Atlassian Connect application.

The Atlassian connect webhook documentation explains this in more detail: https://developer.atlassian.com/static/connect/docs/modules/jira/webhook.html

Constructors

Webhook 

Fields

Instances
Show Webhook Source # 
Instance details

Defined in Data.Connect.Webhooks

Generic Webhook Source # 
Instance details

Defined in Data.Connect.Webhooks

Associated Types

type Rep Webhook :: Type -> Type #

Methods

from :: Webhook -> Rep Webhook x #

to :: Rep Webhook x -> Webhook #

ToJSON Webhook Source # 
Instance details

Defined in Data.Connect.Webhooks

type Rep Webhook Source # 
Instance details

Defined in Data.Connect.Webhooks

type Rep Webhook = D1 (MetaData "Webhook" "Data.Connect.Webhooks" "atlassian-connect-descriptor-0.4.10.0-9IB5n7ayoT45x7ylOmuoxH" False) (C1 (MetaCons "Webhook" PrefixI True) (S1 (MetaSel (Just "webhookEvent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 WebhookEvent) :*: S1 (MetaSel (Just "webhookUrl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data WebhookEvent Source #

The webhook event that you wish to watch from your Atlassian Connect add-on.

Constructors

ConnectAddonDisabled 
ConnectAddonEnabled 
JiraWebhookPostFunction 
JiraIssueCreated 
JiraIssueDeleted 
JiraIssueUpdated 
JiraWorklogUpdated 
JiraVersionCreated 
JiraVersionDeleted 
JiraVersionMerged 
JiraVersionUpdated 
JiraVersionMoved 
JiraVersionReleased 
JiraVersionUnreleased 
JiraProjectCreated 
JiraProjectUpdated 
JiraProjectDeleted 
JiraPluginEnabled 
JiraPluginsUpgraded 
JiraRemoteIssueLinkAggregateClearedEvent 
JiraRemoteWorkflowPostFunction 
JiraUserCreated 
JiraUserDeleted 
JiraUserUpdated 
ConfluenceAttachmentCreated 
ConfluenceAttachmentRemoved 
ConfluenceAttachmentUpdated 
ConfluenceAttachmentViewed 
ConfluenceBlogCreated 
ConfluenceBlogRemoved 
ConfluenceBlogRestored 
ConfluenceBlogTrashed 
ConfluenceBlogUpdated 
ConfluenceBlogViewed 
ConfluenceCacheStatisticsChanged 
ConfluenceCommentCreated 
ConfluenceCommentRemoved 
ConfluenceCommentUpdated 
ConfluenceContentPermissionsUpdated 
ConfluenceLabelAdded 
ConfluenceLabelCreated 
ConfluenceLabelDeleted 
ConfluenceLabelRemoved 
ConfluenceLogin 
ConfluenceLoginFailed 
ConfluenceLogout 
ConfluencePageChildrenReordered 
ConfluencePageCreated 
ConfluencePageMoved 
ConfluencePageRemoved 
ConfluencePageRestored 
ConfluencePageTrashed 
ConfluencePageUpdated 
ConfluencePageViewed 
ConfluenceSearchPerformed 
ConfluenceSpaceCreated 
ConfluenceSpaceLogoUpdated 
ConfluenceSpacePermissionsUpdated 
ConfluenceSpaceRemoved 
ConfluenceSpaceUpdated 
ConfluenceStatusCleared 
ConfluenceStatusCreated 
ConfluenceStatusRemoved 
ConfluenceUserCreated 
ConfluenceUserDeactivated 
ConfluenceUserFollowed 
ConfluenceUserReactivated 
ConfluenceUserRemoved 
ConfluenceGroupCreated 
ConfluenceGroupRemoved 

Module Conditions

data Condition Source #

A Condition can be placed on an Atlassian Connect Module to cause it to display or not based on the result it returns. For example, you can choose not to show a WebPanel if the user viewing the page is not logged in. Conditions are very useful in curating when your modules will appear to your users.

The Atlassian Connect documentation describes conditions fully: https://developer.atlassian.com/static/connect/docs/concepts/conditions.html

Constructors

SingleCondition

A single condition based on a source.

Fields

CompositeCondition

A condition that is the composition of one or more conditions. The ConditionType decides the way in which the conditions are composed

Fields

data ConditionType Source #

Composite Conditions can be joined together to behave as a single condition. The way that you can join them together is decided by the condition type.

Constructors

AndCondition

The boolean intersection of the conditions.

OrCondition

The boolean union of the conditions.

data ConditionSource Source #

Conditions can be specified by the Host application or by the Atlassian Connect add-on itself. This means that the source of the condition needs to be specified and that is what you can use this data type to do.

Constructors

StaticJIRACondition JIRACondition

A static JIRA condition.

StaticConfluenceCondition ConfluenceCondition

A static Confluence condition.

RemoteCondition

A remote condition defined by your Atlassian Connect application.

Fields

  • remoteConditionPath :: String

    The relative URI that you should hit in your Atlassian Connect application to get the condition result. This URI, when hit, should return a JSON response in the format:

    { "shouldDisplay": <true|false> }

remoteCondition :: String -> Condition Source #

Given a URI that defines a remote condition convert it into a regular Condition.

data JIRACondition Source #

The conditions that have been provided by JIRA. Please see the single condition documentation for more details: https://developer.atlassian.com/static/connect/docs/modules/fragment/single-condition.html

Instances
Eq JIRACondition Source # 
Instance details

Defined in Data.Connect.Conditions

Show JIRACondition Source # 
Instance details

Defined in Data.Connect.Conditions

Generic JIRACondition Source # 
Instance details

Defined in Data.Connect.Conditions

Associated Types

type Rep JIRACondition :: Type -> Type #

ToJSON JIRACondition Source # 
Instance details

Defined in Data.Connect.Conditions

type Rep JIRACondition Source # 
Instance details

Defined in Data.Connect.Conditions

type Rep JIRACondition = D1 (MetaData "JIRACondition" "Data.Connect.Conditions" "atlassian-connect-descriptor-0.4.10.0-9IB5n7ayoT45x7ylOmuoxH" False) ((((C1 (MetaCons "CanAttachFileToIssueJiraCondition" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CanManageAttachmentsJiraCondition" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "EntityPropertyEqualToJiraCondition" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "FeatureFlagJiraCondition" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "HasIssuePermissionJiraCondition" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "HasProjectPermissionJiraCondition" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "HasSelectedProjectPermissionJiraCondition" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "HasSubTasksAvaliableJiraCondition" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "HasVotedForIssueJiraCondition" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "IsAdminModeJiraCondition" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "IsIssueAssignedToCurrentUserJiraCondition" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "IsIssueEditableJiraCondition" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "IsIssueReportedByCurrentUserJiraCondition" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "IsIssueUnresolvedJiraCondition" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "IsSubTaskJiraCondition" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "IsWatchingIssueJiraCondition" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "LinkingEnabledJiraCondition" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SubTasksEnabledJiraCondition" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "TimeTrackingEnabledJiraCondition" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "UserHasIssueHistoryJiraCondition" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "UserIsAdminJiraCondition" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "UserIsLoggedInJiraCondition" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "UserIsProjectAdminJiraCondition" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "UserIsSysadminJiraCondition" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "UserIsTheLoggedInUserJiraCondition" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "VotingEnabledJiraCondition" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "WatchingEnabledJiraCondition" PrefixI False) (U1 :: Type -> Type))))))

staticJiraCondition :: JIRACondition -> Condition Source #

Turn a standard JIRA Condition into a regular Condition.

data ConfluenceCondition Source #

The conditions that have been provided by Confluence. Please see the single condition documentation for more details: https://developer.atlassian.com/static/connect/docs/modules/fragment/single-condition.html

Constructors

ActiveThemeConfluenceCondition 
CanEditSpaceStylesConfluenceCondition 
CanSignupConfluenceCondition 
ContentHasAnyPermissionsSetConfluenceCondition 
CreateContentConfluenceCondition 
EmailAddressPublicConfluenceCondition 
FavouritePageConfluenceCondition 
FavouriteSpaceConfluenceCondition 
FeatureFlagConfluenceCondition 
FollowingTargetUserConfluenceCondition 
HasAttachmentConfluenceCondition 
HasBlogPostConfluenceCondition 
HasPageConfluenceCondition 
HasSpaceConfluenceCondition 
HasTemplateConfluenceCondition 
LatestVersionConfluenceCondition 
NotPersonalSpaceConfluenceCondition 
PrintableVersionConfluenceCondition 
ShowingPageAttachmentsConfluenceCondition 
SpaceFunctionPermissionConfluenceCondition 
SpaceSidebarConfluenceCondition 
TargetUserCanSetStatusConfluenceCondition 
TargetUserHasPersonalBlogConfluenceCondition 
TargetUserHasPersonalSpaceConfluenceCondition 
ThreadedCommentsConfluenceCondition 
TinyUrlSupportedConfluenceCondition 
UserCanCreatePersonalSpaceConfluenceCondition 
UserCanUpdateUserStatusConfluenceCondition 
UserCanUseConfluenceConfluenceCondition 
UserFavouritingTargetUserPersonalSpaceConfluenceCondition 
UserHasPersonalBlogConfluenceCondition 
UserHasPersonalSpaceConfluenceCondition 
UserIsAdminConfluenceCondition 
UserIsConfluenceAdministratorConfluenceCondition 
UserIsLoggedInConfluenceCondition 
UserIsSysadminConfluenceCondition 
UserLoggedInEditableConfluenceCondition 
UserWatchingPageConfluenceCondition 
UserWatchingSpaceConfluenceCondition 
UserWatchingSpaceForContentTypeConfluenceCondition 
ViewingContentConfluenceCondition 
ViewingOwnProfileConfluenceCondition 
Instances
Eq ConfluenceCondition Source # 
Instance details

Defined in Data.Connect.Conditions

Show ConfluenceCondition Source # 
Instance details

Defined in Data.Connect.Conditions

Generic ConfluenceCondition Source # 
Instance details

Defined in Data.Connect.Conditions

Associated Types

type Rep ConfluenceCondition :: Type -> Type #

ToJSON ConfluenceCondition Source # 
Instance details

Defined in Data.Connect.Conditions

type Rep ConfluenceCondition Source # 
Instance details

Defined in Data.Connect.Conditions

type Rep ConfluenceCondition = D1 (MetaData "ConfluenceCondition" "Data.Connect.Conditions" "atlassian-connect-descriptor-0.4.10.0-9IB5n7ayoT45x7ylOmuoxH" False) (((((C1 (MetaCons "ActiveThemeConfluenceCondition" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CanEditSpaceStylesConfluenceCondition" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CanSignupConfluenceCondition" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ContentHasAnyPermissionsSetConfluenceCondition" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CreateContentConfluenceCondition" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "EmailAddressPublicConfluenceCondition" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "FavouritePageConfluenceCondition" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "FavouriteSpaceConfluenceCondition" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "FeatureFlagConfluenceCondition" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "FollowingTargetUserConfluenceCondition" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "HasAttachmentConfluenceCondition" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "HasBlogPostConfluenceCondition" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "HasPageConfluenceCondition" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "HasSpaceConfluenceCondition" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "HasTemplateConfluenceCondition" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "LatestVersionConfluenceCondition" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "NotPersonalSpaceConfluenceCondition" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PrintableVersionConfluenceCondition" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "ShowingPageAttachmentsConfluenceCondition" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "SpaceFunctionPermissionConfluenceCondition" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SpaceSidebarConfluenceCondition" PrefixI False) (U1 :: Type -> Type)))))) :+: ((((C1 (MetaCons "TargetUserCanSetStatusConfluenceCondition" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TargetUserHasPersonalBlogConfluenceCondition" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "TargetUserHasPersonalSpaceConfluenceCondition" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ThreadedCommentsConfluenceCondition" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TinyUrlSupportedConfluenceCondition" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "UserCanCreatePersonalSpaceConfluenceCondition" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "UserCanUpdateUserStatusConfluenceCondition" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "UserCanUseConfluenceConfluenceCondition" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "UserFavouritingTargetUserPersonalSpaceConfluenceCondition" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "UserHasPersonalBlogConfluenceCondition" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "UserHasPersonalSpaceConfluenceCondition" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "UserIsAdminConfluenceCondition" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "UserIsConfluenceAdministratorConfluenceCondition" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "UserIsLoggedInConfluenceCondition" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "UserIsSysadminConfluenceCondition" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "UserLoggedInEditableConfluenceCondition" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "UserWatchingPageConfluenceCondition" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "UserWatchingSpaceConfluenceCondition" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "UserWatchingSpaceForContentTypeConfluenceCondition" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ViewingContentConfluenceCondition" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ViewingOwnProfileConfluenceCondition" PrefixI False) (U1 :: Type -> Type)))))))

staticConfluenceCondition :: ConfluenceCondition -> Condition Source #

Turn a standard Confluence Condition into a regular Condition.

invertCondition :: Condition -> Condition Source #

Invert the given condition.

Scopes (Permissions)

data ProductScope Source #

Scopes are an Atlassian Connect concept that declare how much access your addon requires to any give Cloud instance. These scopes can be thought of as permissions are are well documented: https://developer.atlassian.com/static/connect/docs/scopes/scopes.html

It is important to note that these scopes only give you restricted access to certain REST resources. You can not query any REST url as you would with an Atlassian Server plugin. The restricted set of REST resources per application can be found in the Atlassian Connect documentation.

Constructors

Read

The read scope means that you can pull data from the Cloud application.

Write

The write scope gives you the same access as a regular user of the Atlassian connect application.

Delete

The delete scope is required if you want to perform potentially destructive operations on data.

ProjectAdmin

A JIRA specific scope. Lets your add-on administer a project in JIRA.

SpaceAdmin

A Confluence specific scope. Lets your add-on administer a space in Confluence.

Admin

Gives your Atlassian Connect add-on administrative rights to the Cloud instance. (But NOT system administrator permission. Happily you cannot request that level of access.)

ActAsUser

Add-ons with this scope can access resources and perform actions in JIRA and Confluence on behalf of users.

Instances
Eq ProductScope Source # 
Instance details

Defined in Data.Connect.Scopes

Show ProductScope Source # 
Instance details

Defined in Data.Connect.Scopes

Generic ProductScope Source # 
Instance details

Defined in Data.Connect.Scopes

Associated Types

type Rep ProductScope :: Type -> Type #

ToJSON ProductScope Source # 
Instance details

Defined in Data.Connect.Scopes

FromJSON ProductScope Source # 
Instance details

Defined in Data.Connect.Scopes

type Rep ProductScope Source # 
Instance details

Defined in Data.Connect.Scopes

type Rep ProductScope = D1 (MetaData "ProductScope" "Data.Connect.Scopes" "atlassian-connect-descriptor-0.4.10.0-9IB5n7ayoT45x7ylOmuoxH" False) ((C1 (MetaCons "Read" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Write" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Delete" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "ProjectAdmin" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SpaceAdmin" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Admin" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ActAsUser" PrefixI False) (U1 :: Type -> Type))))