Skip to content

Commit

Permalink
Allow mtl-2.3, require jose-0.10 (#1627)
Browse files Browse the repository at this point in the history
  • Loading branch information
ysangkok committed Nov 17, 2022
1 parent ad25e98 commit 8f081bd
Show file tree
Hide file tree
Showing 18 changed files with 29 additions and 28 deletions.
2 changes: 1 addition & 1 deletion servant-auth/servant-auth-client/servant-auth-client.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -74,7 +74,7 @@ test-suite spec
, transformers >= 0.4.2.0 && < 0.6
, wai >= 3.2.1.2 && < 3.3
, warp >= 3.2.25 && < 3.4
, jose >= 0.7.0.0 && < 0.10
, jose >= 0.10 && < 0.11
other-modules:
Servant.Auth.ClientSpec
default-language: Haskell2010
4 changes: 2 additions & 2 deletions servant-auth/servant-auth-server/servant-auth-server.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -41,11 +41,11 @@ library
, data-default-class >= 0.1.2.0 && < 0.2
, entropy >= 0.4.1.3 && < 0.5
, http-types >= 0.12.2 && < 0.13
, jose >= 0.7.0.0 && < 0.10
, jose >= 0.10 && < 0.11
, lens >= 4.16.1 && < 5.3
, memory >= 0.14.16 && < 0.19
, monad-time >= 0.3.1.0 && < 0.4
, mtl >= 2.2.2 && < 2.3
, mtl ^>= 2.2.2 || ^>= 2.3.1
, servant >= 0.13 && < 0.20
, servant-auth == 0.4.*
, servant-server >= 0.13 && < 0.20
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@
module Servant.Auth.Server.Internal.Cookie where

import Blaze.ByteString.Builder (toByteString)
import Control.Monad (MonadPlus(..), guard)
import Control.Monad.Except
import Control.Monad.Reader
import qualified Crypto.JOSE as Jose
Expand Down
Original file line number Diff line number Diff line change
@@ -1,18 +1,14 @@
module Servant.Auth.Server.Internal.JWT where

import Control.Lens
import Control.Monad.Except
import Control.Monad (MonadPlus(..), guard)
import Control.Monad.Reader
import qualified Crypto.JOSE as Jose
import qualified Crypto.JWT as Jose
import Data.Aeson (FromJSON, Result (..), ToJSON, fromJSON,
toJSON)
import Data.ByteArray (constEq)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BSL
import qualified Data.HashMap.Strict as HM
import Data.Maybe (fromMaybe)
import qualified Data.Text as T
import Data.Time (UTCTime)
import Network.Wai (requestHeaders)

Expand Down Expand Up @@ -42,7 +38,7 @@ jwtAuthCheck jwtSettings = do
-- token expires.
makeJWT :: ToJWT a
=> a -> JWTSettings -> Maybe UTCTime -> IO (Either Jose.Error BSL.ByteString)
makeJWT v cfg expiry = runExceptT $ do
makeJWT v cfg expiry = Jose.runJOSE $ do
bestAlg <- Jose.bestJWSAlg $ signingKey cfg
let alg = fromMaybe bestAlg $ jwtAlg cfg
ejwt <- Jose.signClaims (signingKey cfg)
Expand All @@ -59,7 +55,7 @@ makeJWT v cfg expiry = runExceptT $ do
verifyJWT :: FromJWT a => JWTSettings -> BS.ByteString -> IO (Maybe a)
verifyJWT jwtCfg input = do
keys <- validationKeys jwtCfg
verifiedJWT <- runExceptT $ do
verifiedJWT <- Jose.runJOSE $ do
unverifiedJWT <- Jose.decodeCompact (BSL.fromStrict input)
Jose.verifyClaims
(jwtSettingsToJwtValidationSettings jwtCfg)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@
module Servant.Auth.Server.Internal.Types where

import Control.Applicative
import Control.Monad (MonadPlus(..), ap)
import Control.Monad.Reader
import Control.Monad.Time
import Data.Monoid (Monoid (..))
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -6,13 +6,12 @@ module Servant.Auth.ServerSpec (spec) where
#endif

import Control.Lens
import Control.Monad.Except (runExceptT)
import Control.Monad.IO.Class (liftIO)
import Crypto.JOSE (Alg (HS256, None), Error,
JWK, JWSHeader,
KeyMaterialGenParam (OctGenParam),
ToCompact, encodeCompact,
genJWK, newJWSHeader)
genJWK, newJWSHeader, runJOSE)
import Crypto.JWT (Audience (..), ClaimsSet,
NumericDate (NumericDate),
SignedJWT,
Expand Down Expand Up @@ -540,7 +539,7 @@ addJwtToHeader jwt = case jwt of
$ defaults & header "Authorization" .~ ["Bearer " <> BSL.toStrict v]

createJWT :: JWK -> JWSHeader () -> ClaimsSet -> IO (Either Error Crypto.JWT.SignedJWT)
createJWT k a b = runExceptT $ signClaims k a b
createJWT k a b = runJOSE $ signClaims k a b

addJwtToCookie :: ToCompact a => CookieSettings -> Either Error a -> IO Options
addJwtToCookie ccfg jwt = case jwt >>= (return . encodeCompact) of
Expand Down
2 changes: 1 addition & 1 deletion servant-auth/servant-auth/servant-auth.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,7 @@ library
base >= 4.10 && < 4.18
, containers >= 0.6 && < 0.7
, aeson >= 1.3.1.1 && < 3
, jose >= 0.7.0.0 && < 0.10
, jose >= 0.10 && < 0.11
, lens >= 4.16.1 && < 5.3
, servant >= 0.15 && < 0.20
, text >= 1.2.3.0 && < 2.1
Expand Down
2 changes: 1 addition & 1 deletion servant-client-core/servant-client-core.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -56,7 +56,7 @@ library
, containers >= 0.5.7.1 && < 0.7
, deepseq >= 1.4.2.0 && < 1.5
, text >= 1.2.3.0 && < 2.1
, transformers >= 0.5.2.0 && < 0.6
, transformers >= 0.5.2.0 && < 0.7
, template-haskell >= 2.11.1.0 && < 2.20

if !impl(ghc >= 8.2)
Expand Down
2 changes: 1 addition & 1 deletion servant-client-ghcjs/servant-client-ghcjs.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,7 @@ library
, http-media >=0.6.2 && <0.9
, http-types >=0.12 && <0.13
, monad-control >=1.0.0.4 && <1.1
, mtl >=2.2.2 && <2.3
, mtl ^>=2.2.2 || ^>=2.3.1
, semigroupoids >=5.3 && <5.4
, string-conversions >=0.3 && <0.5
, transformers >=0.3 && <0.6
Expand Down
4 changes: 2 additions & 2 deletions servant-client/servant-client.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -45,11 +45,11 @@ library
, bytestring >= 0.10.8.1 && < 0.12
, containers >= 0.5.7.1 && < 0.7
, deepseq >= 1.4.2.0 && < 1.5
, mtl >= 2.2.2 && < 2.3
, mtl ^>= 2.2.2 || ^>= 2.3.1
, stm >= 2.4.5.1 && < 2.6
, text >= 1.2.3.0 && < 2.1
, time >= 1.6.0.1 && < 1.13
, transformers >= 0.5.2.0 && < 0.6
, transformers >= 0.5.2.0 && < 0.7

if !impl(ghc >= 8.2)
build-depends:
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,8 @@ import Control.DeepSeq
(NFData, force)
import Control.Exception
(evaluate, throwIO)
import Control.Monad ()
import Control.Monad
(unless)
import Control.Monad.Base
(MonadBase (..))
import Control.Monad.Codensity
Expand Down
2 changes: 1 addition & 1 deletion servant-conduit/servant-conduit.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@ library
base >=4.9 && <5
, bytestring >=0.10.8.1 && <0.12
, conduit >=1.3.1 && <1.4
, mtl >=2.2.2 && <2.3
, mtl ^>=2.2.2 || ^>=2.3.1
, resourcet >=1.2.2 && <1.3
, servant >=0.15 && <0.20
, unliftio-core >=0.1.2.0 && <0.3
Expand Down
4 changes: 2 additions & 2 deletions servant-http-streams/servant-http-streams.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -42,10 +42,10 @@ library
, bytestring >= 0.10.8.1 && < 0.12
, containers >= 0.5.7.1 && < 0.7
, deepseq >= 1.4.2.0 && < 1.5
, mtl >= 2.2.2 && < 2.3
, mtl ^>= 2.2.2 || ^>= 2.3.1
, text >= 1.2.3.0 && < 2.1
, time >= 1.6.0.1 && < 1.13
, transformers >= 0.5.2.0 && < 0.6
, transformers >= 0.5.2.0 && < 0.7

if !impl(ghc >= 8.2)
build-depends:
Expand Down
2 changes: 1 addition & 1 deletion servant-machines/servant-machines.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@ library
base >=4.9 && <5
, bytestring >=0.10.8.1 && <0.12
, machines >=0.6.4 && <0.8
, mtl >=2.2.2 && <2.3
, mtl ^>=2.2.2 || ^>=2.3.1
, servant >=0.15 && <0.20
hs-source-dirs: src
default-language: Haskell2010
Expand Down
2 changes: 1 addition & 1 deletion servant-pipes/servant-pipes.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ library
, bytestring >=0.10.8.1 && <0.12
, pipes >=4.3.9 && <4.4
, pipes-safe >=2.3.1 && <2.4
, mtl >=2.2.2 && <2.3
, mtl ^>=2.2.2 || ^>=2.3.1
, monad-control >=1.0.2.3 && <1.1
, servant >=0.15 && <0.20
hs-source-dirs: src
Expand Down
4 changes: 2 additions & 2 deletions servant-server/servant-server.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -64,9 +64,9 @@ library
, bytestring >= 0.10.8.1 && < 0.12
, constraints >= 0.2 && < 0.14
, containers >= 0.5.7.1 && < 0.7
, mtl >= 2.2.2 && < 2.3
, mtl ^>= 2.2.2 || ^>= 2.3.1
, text >= 1.2.3.0 && < 2.1
, transformers >= 0.5.2.0 && < 0.6
, transformers >= 0.5.2.0 && < 0.7
, filepath >= 1.4.1.1 && < 1.5

-- Servant dependencies
Expand Down
4 changes: 2 additions & 2 deletions servant/servant.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -83,9 +83,9 @@ library
base >= 4.9 && < 4.18
, bytestring >= 0.10.8.1 && < 0.12
, constraints >= 0.2
, mtl >= 2.2.2 && < 2.3
, mtl ^>= 2.2.2 || ^>= 2.3.1
, sop-core >= 0.4.0.0 && < 0.6
, transformers >= 0.5.2.0 && < 0.6
, transformers >= 0.5.2.0 && < 0.7
, text >= 1.2.3.0 && < 2.1


Expand Down
3 changes: 3 additions & 0 deletions servant/src/Servant/Types/SourceT.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
Expand Down Expand Up @@ -154,8 +155,10 @@ instance (Applicative m, Show1 m, Show a) => Show (StepT m a) where
-- | >>> lift [1,2,3] :: StepT [] Int
-- Effect [Yield 1 Stop,Yield 2 Stop,Yield 3 Stop]
--
#if !MIN_VERSION_transformers(0,6,0)
instance MonadTrans StepT where
lift = Effect . fmap (`Yield` Stop)
#endif

instance MFunctor StepT where
hoist f = go where
Expand Down

0 comments on commit 8f081bd

Please sign in to comment.