Safe Haskell | None |
---|---|
Language | GHC2021 |
Network.Globus.Types
Synopsis
- (/:) :: forall {k} (a :: k). Uri a -> String -> Uri a
- param :: forall {k} (a :: k). Text -> Text -> Uri a -> Uri a
- appendQuery :: Text -> Maybe Text -> String -> String
- renderUri :: forall {k} (a :: k). Uri a -> Text
- newtype State = State Text
- data TokenItem = TokenItem {
- scope :: Scopes
- access_token :: Token 'Access
- expires_in :: Int
- state :: State
- data GlobusError
- type Token (a :: k) = Tagged a Text
- type Id (a :: k) = Tagged a Text
- type Uri (a :: k) = Tagged a URI
- data Token'
- data Id'
- dataLabelsToJSON :: (Generic a, GToJSON' Value Zero (Rep a)) => a -> Value
- dataLabelsFromJSON :: (Generic a, GFromJSON Zero (Rep a)) => Value -> Parser a
- dataLabels :: String -> String
- data DataType (s :: Symbol) = DataType
- data DataKey (s :: Symbol) = DataKey {}
- data Endpoint
- = Redirect
- | Authorization
- | Tokens
- | App
- data Scope
- data ScopeIdentity
- scopeText :: Scope -> Text
- scope :: Text -> Maybe Scope
- newtype Scopes = Scopes (NonEmpty Scope)
Documentation
Opaque secret identifying the user. Validate on redirect
Constructors
TokenItem | |
Fields
|
Instances
data GlobusError Source #
Constructors
InvalidURI String URI | |
Unauthorized Request ByteString | |
ResponseBadStatus Request Status ByteString | |
ResponseBadJSON Request String ByteString | |
MissingScope Scope (NonEmpty TokenItem) |
Instances
Exception GlobusError Source # | |
Defined in Network.Globus.Types Methods toException :: GlobusError -> SomeException # fromException :: SomeException -> Maybe GlobusError # displayException :: GlobusError -> String # backtraceDesired :: GlobusError -> Bool # | |
Show GlobusError Source # | |
Defined in Network.Globus.Types Methods showsPrec :: Int -> GlobusError -> ShowS # show :: GlobusError -> String # showList :: [GlobusError] -> ShowS # |
Constructors
Submission | |
Request | |
Collection |
dataLabels :: String -> String Source #
data DataType (s :: Symbol) Source #
Constructors
DataType |
Instances
FromJSON (DataType s) Source # | |
Defined in Network.Globus.Types | |
KnownSymbol s => ToJSON (DataType s) Source # | |
data DataKey (s :: Symbol) Source #
Instances
Generic (DataKey s) Source # | |||||
Defined in Network.Globus.Types Associated Types
| |||||
FromJSON (DataKey s) Source # | |||||
Defined in Network.Globus.Types | |||||
type Rep (DataKey s) Source # | |||||
Defined in Network.Globus.Types type Rep (DataKey s) = D1 ('MetaData "DataKey" "Network.Globus.Types" "globus-0.2.0-inplace" 'False) (C1 ('MetaCons "DataKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "data_type") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (DataType s)) :*: S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text))) |
Constructors
TransferAll | |
Identity ScopeIdentity |
data ScopeIdentity Source #
Instances
Show ScopeIdentity Source # | |
Defined in Network.Globus.Types Methods showsPrec :: Int -> ScopeIdentity -> ShowS # show :: ScopeIdentity -> String # showList :: [ScopeIdentity] -> ShowS # | |
Eq ScopeIdentity Source # | |
Defined in Network.Globus.Types Methods (==) :: ScopeIdentity -> ScopeIdentity -> Bool # (/=) :: ScopeIdentity -> ScopeIdentity -> Bool # |