Skip to content

Commit

Permalink
Format
Browse files Browse the repository at this point in the history
  • Loading branch information
freizl committed Aug 16, 2023
1 parent d7abd58 commit 4e54127
Show file tree
Hide file tree
Showing 9 changed files with 21 additions and 14 deletions.
8 changes: 4 additions & 4 deletions hoauth2-demo/src/App.hs
Original file line number Diff line number Diff line change
Expand Up @@ -142,8 +142,8 @@ createAuthorizationUri AppEnv {..} idpName = do
(DemoIdp idp) <- pure (findIdpByName idpName)
authCodeApp <- createAuthorizationCodeApp idp idpName
(authorizationUri, codeVerifier) <-
liftIO
$ if isSupportPkce idpName
liftIO $
if isSupportPkce idpName
then fmap (second Just) (mkPkceAuthorizeRequest authCodeApp)
else pure (mkAuthorizationRequest authCodeApp, Nothing)
insertCodeVerifier sessionStore idpName codeVerifier
Expand Down Expand Up @@ -302,8 +302,8 @@ fetchTokenAndUser AppEnv {..} idpData@(IdpAuthorizationCodeAppSessionData {..})
if isSupportPkce idpName
then do
when (isNothing authorizePkceCodeVerifier) (throwE "Unable to find code verifier")
withExceptT tokenRequestErrorErrorToText
$ conduitPkceTokenRequest
withExceptT tokenRequestErrorErrorToText $
conduitPkceTokenRequest
idpApp
mgr
(exchangeTokenText, fromJust authorizePkceCodeVerifier)
Expand Down
1 change: 0 additions & 1 deletion hoauth2-providers/src/Network/OAuth2/Provider.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,4 +18,3 @@ data IdpName
| Weibo
| ZOHO
deriving (Eq, Ord, Show, Enum, Bounded, Generic)

2 changes: 1 addition & 1 deletion hoauth2-tutorial/src/HOAuth2ExperimentTutorial.hs
Original file line number Diff line number Diff line change
Expand Up @@ -291,7 +291,7 @@ paramValue key params =
hasParam t = (== t) . fst

-- | Lift ExceptT to ActionM which is basically the handler Monad in Scotty.
excepttToActionM :: (Show a) => ExceptT TL.Text IO a -> ActionM a
excepttToActionM :: Show a => ExceptT TL.Text IO a -> ActionM a
excepttToActionM e = do
result <- liftIO $ runExceptT e
either Scotty.raise pure result
Expand Down
2 changes: 2 additions & 0 deletions hoauth2/src/Network/OAuth/OAuth2.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,8 +5,10 @@ module Network.OAuth.OAuth2 (

-- * Authorization Requset
module Network.OAuth.OAuth2.AuthorizationRequest,

-- * Token Request
module Network.OAuth.OAuth2.TokenRequest,

-- * OAuth'ed http client utilities
module Network.OAuth.OAuth2.HttpClient,
) where
Expand Down
10 changes: 9 additions & 1 deletion hoauth2/src/Network/OAuth/OAuth2/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,9 @@ import URI.ByteString.Aeson ()
import URI.ByteString.QQ

-------------------------------------------------------------------------------

-- * OAuth2 Configuration

-------------------------------------------------------------------------------

-- | Query Parameter Representation
Expand All @@ -49,7 +51,9 @@ instance Default OAuth2 where
}

-------------------------------------------------------------------------------

-- * Tokens

-------------------------------------------------------------------------------

newtype AccessToken = AccessToken {atoken :: Text} deriving (Binary, Eq, Show, FromJSON, ToJSON)
Expand All @@ -62,6 +66,7 @@ newtype IdToken = IdToken {idtoken :: Text} deriving (Binary, Eq, Show, FromJSON
newtype ExchangeToken = ExchangeToken {extoken :: Text} deriving (Show, FromJSON, ToJSON)

-- FIXME: rename to TokenResponse and move to that module

-- | https://www.rfc-editor.org/rfc/rfc6749#section-4.1.4
data OAuth2Token = OAuth2Token
{ accessToken :: AccessToken
Expand Down Expand Up @@ -96,7 +101,9 @@ instance ToJSON OAuth2Token where
toEncoding = genericToEncoding defaultOptions {fieldLabelModifier = camelTo2 '_'}

-------------------------------------------------------------------------------

-- * Client Authentication methods

-------------------------------------------------------------------------------

-- | https://www.rfc-editor.org/rfc/rfc6749#section-2.3
Expand All @@ -118,7 +125,9 @@ data ClientAuthenticationMethod
deriving (Eq)

-------------------------------------------------------------------------------

-- * Utilies for Request and URI

-------------------------------------------------------------------------------

-- | Type synonym of post body content
Expand All @@ -127,7 +136,6 @@ type PostBody = [(BS.ByteString, BS.ByteString)]
-- | Type sysnonym of request query params
type QueryParams = [(BS.ByteString, BS.ByteString)]


defaultRequestHeaders :: [(HT.HeaderName, BS.ByteString)]
defaultRequestHeaders =
[ (HT.hUserAgent, "hoauth2-" <> BS8.pack (showVersion version))
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -21,9 +21,9 @@ data AuthorizationRequestParam = AuthorizationRequestParam
, arState :: AuthorizeState
, arClientId :: ClientId
, arRedirectUri :: Maybe RedirectUri
-- | It could be optional there is only one redirect_uri registered.
-- See: https://www.rfc-editor.org/rfc/rfc6749#section-3.1.2.3
, arResponseType :: ResponseType
-- ^ It could be optional there is only one redirect_uri registered.
-- See: https://www.rfc-editor.org/rfc/rfc6749#section-3.1.2.3
, arExtraParams :: Map Text Text
}

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -4,10 +4,10 @@ module Network.OAuth2.Experiment.Flows.RefreshTokenRequest where

import Control.Monad.IO.Class (MonadIO (..))
import Control.Monad.Trans.Except (ExceptT (..))
import Data.Map.Strict qualified as Map
import Data.Text.Lazy (Text)
import Data.Map.Strict (Map)
import Data.Map.Strict qualified as Map
import Data.Set (Set)
import Data.Text.Lazy (Text)
import Network.HTTP.Conduit
import Network.OAuth.OAuth2 hiding (RefreshToken)
import Network.OAuth.OAuth2 qualified as OAuth2
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -52,7 +52,7 @@ instance HasAuthorizeRequest AuthorizationCodeApplication where
}

instance HasPkceAuthorizeRequest AuthorizationCodeApplication where
mkPkceAuthorizeRequestParam :: (MonadIO m) => AuthorizationCodeApplication -> m (AuthorizationRequestParam, CodeVerifier)
mkPkceAuthorizeRequestParam :: MonadIO m => AuthorizationCodeApplication -> m (AuthorizationRequestParam, CodeVerifier)
mkPkceAuthorizeRequestParam app = do
PkceRequestParam {..} <- mkPkceParam
let authReqParam = mkAuthorizationRequestParam app
Expand Down
2 changes: 0 additions & 2 deletions hoauth2/src/Network/OAuth2/Experiment/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,6 @@ import URI.ByteString (URI, serializeURIRef')
-- And it is PolyKinds.
-- Hence whenever `Idp i` or `IdpApplication i a` is used as function parameter,
-- PolyKinds need to be enabled.
--
data Idp (i :: k) = Idp
{ idpUserInfoEndpoint :: URI
-- ^ Userinfo Endpoint
Expand All @@ -54,7 +53,6 @@ data Idp (i :: k) = Idp
-- * `Network.OAuth2.Experiment.ClientCredentialsApplication`
-- * `Network.OAuth2.Experiment.ResourceOwnerPasswordApplication`
-- * `Network.OAuth2.Experiment.JwtBearerApplication`
--
data IdpApplication (i :: k) a = IdpApplication
{ idp :: Idp i
, application :: a
Expand Down

0 comments on commit 4e54127

Please sign in to comment.