Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Web.Hyperbole.Effect.OAuth2
Synopsis
- data OAuth2 :: Effect where
- AuthUrl :: URI -> Scopes -> OAuth2 m URI
- ValidateCode :: OAuth2 m (Token Code)
- ExchangeAuth :: Token Code -> OAuth2 m Authenticated
- ExchangeRefresh :: Token Refresh -> OAuth2 m Authenticated
- authUrl :: OAuth2 :> es => URI -> Scopes -> Eff es URI
- validateCode :: OAuth2 :> es => Eff es (Token Code)
- exchangeAuth :: OAuth2 :> es => Token Code -> Eff es Authenticated
- exchangeRefresh :: OAuth2 :> es => Token Refresh -> Eff es Authenticated
- runOAuth2 :: (GenRandom :> es, IOE :> es, Hyperbole :> es) => Config -> Manager -> Eff (OAuth2 : es) a -> Eff es a
- getConfigEnv :: Environment :> es => Eff es Config
- newtype Scopes = Scopes [Text]
- data AuthFlow = AuthFlow {}
- data Config = Config {}
- data TokenType = Bearer
- data Authenticated = Authenticated {}
- newtype Token a = Token {}
- data ClientId
- data ClientSecret
- data Code
- data Access
- data Refresh
- data State
- data Auth
- data OAuth2Error
Documentation
data OAuth2 :: Effect where Source #
Constructors
AuthUrl :: URI -> Scopes -> OAuth2 m URI | |
ValidateCode :: OAuth2 m (Token Code) | |
ExchangeAuth :: Token Code -> OAuth2 m Authenticated | |
ExchangeRefresh :: Token Refresh -> OAuth2 m Authenticated |
Instances
type DispatchOf OAuth2 Source # | |
Defined in Web.Hyperbole.Effect.OAuth2 |
exchangeAuth :: OAuth2 :> es => Token Code -> Eff es Authenticated Source #
exchangeRefresh :: OAuth2 :> es => Token Refresh -> Eff es Authenticated Source #
runOAuth2 :: (GenRandom :> es, IOE :> es, Hyperbole :> es) => Config -> Manager -> Eff (OAuth2 : es) a -> Eff es a Source #
getConfigEnv :: Environment :> es => Eff es Config Source #
read oauth config from env. This is not required, you can obtain these secrets another way and configure the app however you please. Just pass the results into runOAuth2 in your app
Instances
IsString Scopes Source # | |
Defined in Web.Hyperbole.Effect.OAuth2 Methods fromString :: String -> Scopes # | |
Generic Scopes Source # | |
Show Scopes Source # | |
FromParam Scopes Source # | |
Defined in Web.Hyperbole.Effect.OAuth2 Methods parseParam :: ParamValue -> Either String Scopes Source # decodeFormValue :: Maybe Text -> Either String Scopes Source # | |
ToParam Scopes Source # | |
Defined in Web.Hyperbole.Effect.OAuth2 Methods toParam :: Scopes -> ParamValue Source # | |
FromJSON Scopes Source # | |
Defined in Web.Hyperbole.Effect.OAuth2 | |
ToJSON Scopes Source # | |
type Rep Scopes Source # | |
Defined in Web.Hyperbole.Effect.OAuth2 |
Instances
Generic AuthFlow Source # | |
Default AuthFlow Source # | |
Defined in Web.Hyperbole.Effect.OAuth2 | |
FromEncoded AuthFlow Source # | |
Defined in Web.Hyperbole.Effect.OAuth2 | |
ToEncoded AuthFlow Source # | |
Session AuthFlow Source # | |
Defined in Web.Hyperbole.Effect.OAuth2 Methods sessionKey :: Key Source # cookiePath :: Maybe Path Source # toCookie :: AuthFlow -> CookieValue Source # parseCookie :: CookieValue -> Either String AuthFlow Source # | |
type Rep AuthFlow Source # | |
Defined in Web.Hyperbole.Effect.OAuth2 type Rep AuthFlow = D1 ('MetaData "AuthFlow" "Web.Hyperbole.Effect.OAuth2" "hyperbole-0.5.0-inplace" 'False) (C1 ('MetaCons "AuthFlow" 'PrefixI 'True) (S1 ('MetaSel ('Just "redirect") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 URI) :*: S1 ('MetaSel ('Just "state") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Token State)))) |
Constructors
Bearer |
Instances
Generic TokenType Source # | |
Read TokenType Source # | |
Show TokenType Source # | |
FromParam TokenType Source # | |
Defined in Web.Hyperbole.Effect.OAuth2 Methods parseParam :: ParamValue -> Either String TokenType Source # decodeFormValue :: Maybe Text -> Either String TokenType Source # | |
ToParam TokenType Source # | |
Defined in Web.Hyperbole.Effect.OAuth2 Methods toParam :: TokenType -> ParamValue Source # | |
FromJSON TokenType Source # | |
Defined in Web.Hyperbole.Effect.OAuth2 | |
ToJSON TokenType Source # | |
type Rep TokenType Source # | |
data Authenticated Source #
Constructors
Authenticated | |
Instances
Instances
Read (Token a) Source # | |
Show (Token a) Source # | |
Eq (Token a) Source # | |
FromParam (Token a) Source # | |
Defined in Web.Hyperbole.Effect.GenRandom Methods parseParam :: ParamValue -> Either String (Token a) Source # decodeFormValue :: Maybe Text -> Either String (Token a) Source # | |
ToParam (Token a) Source # | |
Defined in Web.Hyperbole.Effect.GenRandom Methods toParam :: Token a -> ParamValue Source # | |
FromJSON (Token a) Source # | |
Defined in Web.Hyperbole.Effect.GenRandom | |
ToJSON (Token a) Source # | |
data ClientSecret Source #
data OAuth2Error Source #
Constructors
OAuth2BadResponse String ByteString | |
OAuth2TokenRequest HttpException | |
OAuth2BadEnv String String |
Instances
Exception OAuth2Error Source # | |
Defined in Web.Hyperbole.Effect.OAuth2 Methods toException :: OAuth2Error -> SomeException # fromException :: SomeException -> Maybe OAuth2Error # displayException :: OAuth2Error -> String # | |
Show OAuth2Error Source # | |
Defined in Web.Hyperbole.Effect.OAuth2 Methods showsPrec :: Int -> OAuth2Error -> ShowS # show :: OAuth2Error -> String # showList :: [OAuth2Error] -> ShowS # |