| Safe Haskell | None |
|---|---|
| Language | GHC2021 |
Web.Hyperbole.Effect.OAuth2
Synopsis
- data OAuth2 (a :: Type -> Type) b where
- authUrl :: forall (es :: [Effect]). OAuth2 :> es => URI -> Scopes -> Eff es URI
- validateCode :: forall (es :: [Effect]). OAuth2 :> es => Eff es (Token Code)
- exchangeAuth :: forall (es :: [Effect]). OAuth2 :> es => Token Code -> Eff es Authenticated
- exchangeRefresh :: forall (es :: [Effect]). OAuth2 :> es => Token Refresh -> Eff es Authenticated
- runOAuth2 :: forall (es :: [Effect]) a. (GenRandom :> es, IOE :> es, Hyperbole :> es) => Config -> Manager -> Eff (OAuth2 ': es) a -> Eff es a
- getConfigEnv :: forall (es :: [Effect]). Environment :> es => Eff es Config
- newtype Scopes = Scopes [Text]
- data AuthFlow = AuthFlow {}
- data Config = Config {}
- data TokenType = Bearer
- data Authenticated = Authenticated {}
- newtype Token (a :: k) = Token {}
- data ClientId
- data ClientSecret
- data Code
- data Access
- data Refresh
- data State
- data Auth
- data OAuth2Error
Documentation
data OAuth2 (a :: Type -> Type) b where Source #
Constructors
| AuthUrl :: forall (a :: Type -> Type). URI -> Scopes -> OAuth2 a URI | |
| ValidateCode :: forall (a :: Type -> Type). OAuth2 a (Token Code) | |
| ExchangeAuth :: forall (a :: Type -> Type). Token Code -> OAuth2 a Authenticated | |
| ExchangeRefresh :: forall (a :: Type -> Type). Token Refresh -> OAuth2 a Authenticated |
Instances
| type DispatchOf OAuth2 Source # | |
Defined in Web.Hyperbole.Effect.OAuth2 | |
exchangeAuth :: forall (es :: [Effect]). OAuth2 :> es => Token Code -> Eff es Authenticated Source #
exchangeRefresh :: forall (es :: [Effect]). OAuth2 :> es => Token Refresh -> Eff es Authenticated Source #
runOAuth2 :: forall (es :: [Effect]) a. (GenRandom :> es, IOE :> es, Hyperbole :> es) => Config -> Manager -> Eff (OAuth2 ': es) a -> Eff es a Source #
getConfigEnv :: forall (es :: [Effect]). 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
| FromJSON Scopes Source # | |||||
Defined in Web.Hyperbole.Effect.OAuth2 | |||||
| ToJSON Scopes Source # | |||||
| IsString Scopes Source # | |||||
Defined in Web.Hyperbole.Effect.OAuth2 Methods fromString :: String -> Scopes # | |||||
| Generic Scopes Source # | |||||
Defined in Web.Hyperbole.Effect.OAuth2 Associated Types
| |||||
| 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 # | |||||
| type Rep Scopes Source # | |||||
Defined in Web.Hyperbole.Effect.OAuth2 | |||||
Instances
Constructors
| Bearer |
Instances
| FromJSON TokenType Source # | |
Defined in Web.Hyperbole.Effect.OAuth2 | |
| ToJSON TokenType Source # | |
| Generic TokenType Source # | |
Defined in Web.Hyperbole.Effect.OAuth2 | |
| 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 # | |
| type Rep TokenType Source # | |
data Authenticated Source #
Constructors
| Authenticated | |
Instances
| FromJSON Authenticated Source # | |||||
Defined in Web.Hyperbole.Effect.OAuth2 Methods parseJSON :: Value -> Parser Authenticated # parseJSONList :: Value -> Parser [Authenticated] # | |||||
| ToJSON Authenticated Source # | |||||
Defined in Web.Hyperbole.Effect.OAuth2 Methods toJSON :: Authenticated -> Value # toEncoding :: Authenticated -> Encoding # toJSONList :: [Authenticated] -> Value # toEncodingList :: [Authenticated] -> Encoding # omitField :: Authenticated -> Bool # | |||||
| Generic Authenticated Source # | |||||
Defined in Web.Hyperbole.Effect.OAuth2 Associated Types
| |||||
| Show Authenticated Source # | |||||
Defined in Web.Hyperbole.Effect.OAuth2 Methods showsPrec :: Int -> Authenticated -> ShowS # show :: Authenticated -> String # showList :: [Authenticated] -> ShowS # | |||||
| FromEncoded Authenticated Source # | |||||
Defined in Web.Hyperbole.Effect.OAuth2 Methods parseEncoded :: Encoded -> Either String Authenticated Source # | |||||
| ToEncoded Authenticated Source # | |||||
Defined in Web.Hyperbole.Effect.OAuth2 Methods toEncoded :: Authenticated -> Encoded Source # | |||||
| FromParam Authenticated Source # | |||||
Defined in Web.Hyperbole.Effect.OAuth2 Methods parseParam :: ParamValue -> Either String Authenticated Source # decodeFormValue :: Maybe Text -> Either String Authenticated Source # | |||||
| ToParam Authenticated Source # | |||||
Defined in Web.Hyperbole.Effect.OAuth2 Methods toParam :: Authenticated -> ParamValue Source # | |||||
| Session Authenticated Source # | |||||
Defined in Web.Hyperbole.Effect.OAuth2 Methods sessionKey :: Key Source # cookiePath :: Maybe Path Source # toCookie :: Authenticated -> CookieValue Source # parseCookie :: CookieValue -> Either String Authenticated Source # | |||||
| type Rep Authenticated Source # | |||||
Defined in Web.Hyperbole.Effect.OAuth2 type Rep Authenticated = D1 ('MetaData "Authenticated" "Web.Hyperbole.Effect.OAuth2" "hyperbole-0.5.0-BYuNJFea9uW7InKipgZBzY" 'False) (C1 ('MetaCons "Authenticated" 'PrefixI 'True) ((S1 ('MetaSel ('Just "tokenType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TokenType) :*: S1 ('MetaSel ('Just "expiresIn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))) :*: (S1 ('MetaSel ('Just "scope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Scopes)) :*: (S1 ('MetaSel ('Just "accessToken") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Token Access)) :*: S1 ('MetaSel ('Just "refreshToken") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Token Refresh))))))) | |||||
newtype Token (a :: k) Source #
Instances
| FromJSON (Token a) Source # | |
Defined in Web.Hyperbole.Effect.GenRandom | |
| ToJSON (Token a) Source # | |
| 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 # | |
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 # | |