Skip to content

Commit

Permalink
Don't use deprecated packages in examples, fix examples for more rece…
Browse files Browse the repository at this point in the history
…nt stack lts
  • Loading branch information
jhrcek committed Sep 24, 2024
1 parent 43b6c4a commit 25c8b92
Show file tree
Hide file tree
Showing 3 changed files with 22 additions and 18 deletions.
31 changes: 15 additions & 16 deletions examples/scotty/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,8 +8,7 @@ module Main where
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Reader (ReaderT, ask, lift,
runReaderT)
import Crypto.Random.AESCtr (AESRNG, makeSystem)
import Crypto.Random.API (cprgGenBytes)
import Crypto.Random (SystemDRG, getSystemDRG, randomBytesGenerate)
import Data.Aeson (FromJSON)
import Data.ByteString (ByteString)
import Data.ByteString.Base64.URL (encode)
Expand Down Expand Up @@ -49,7 +48,7 @@ type SessionStateMap = Map T.Text (O.State, O.Nonce)

data AuthServerEnv = AuthServerEnv
{ oidc :: O.OIDC
, cprg :: IORef AESRNG
, sdrg :: IORef SystemDRG
, ssm :: IORef SessionStateMap
, mgr :: Manager
}
Expand All @@ -73,13 +72,13 @@ main = do
let port = getPort baseUrl
redirectUri = baseUrl <> "/login/cb"

cprg <- makeSystem >>= newIORef
sdrg <- getSystemDRG >>= newIORef
ssm <- newIORef M.empty
mgr <- newManager tlsManagerSettings
prov <- O.discover "https://accounts.google.com" mgr
let oidc = O.setCredentials clientId clientSecret redirectUri $ O.newOIDC prov

run port oidc cprg ssm mgr
run port oidc sdrg ssm mgr

getPort :: ByteString -> Int
getPort bs = fromMaybe 3000 port
Expand All @@ -90,10 +89,10 @@ getPort bs = fromMaybe 3000 port
xs -> let p = (!! 0) . L.reverse $ xs
in fst <$> B.readInt p

run :: Int -> O.OIDC -> IORef AESRNG -> IORef SessionStateMap -> Manager -> IO ()
run port oidc cprg ssm mgr = scottyT port runReader run'
run :: Int -> O.OIDC -> IORef SystemDRG -> IORef SessionStateMap -> Manager -> IO ()
run port oidc sdrg ssm mgr = scottyT port runReader run'
where
runReader a = runReaderT a (AuthServerEnv oidc cprg ssm mgr)
runReader a = runReaderT a (AuthServerEnv oidc sdrg ssm mgr)

run' :: AuthServer ()
run' = do
Expand All @@ -105,8 +104,8 @@ run' = do
post "/login" $ do
AuthServerEnv{..} <- lift ask

sid <- genSessionId cprg
let store = sessionStoreFromSession cprg ssm sid
sid <- genSessionId sdrg
let store = sessionStoreFromSession sdrg ssm sid
loc <- liftIO $ O.prepareAuthenticationRequestUrl store oidc [O.email, O.profile] []
setSimpleCookie cookieName sid
redirect . TL.pack . show $ loc
Expand All @@ -129,7 +128,7 @@ run' = do
case cookie of
Just sid -> do
AuthServerEnv{..} <- lift ask
let store = sessionStoreFromSession cprg ssm sid
let store = sessionStoreFromSession sdrg ssm sid
state <- param "state"
code <- param "code"
tokens <- liftIO $ O.getValidTokens store oidc mgr state code
Expand All @@ -150,9 +149,9 @@ run' = do
H.toHtml (email profile)
H.p $ H.img ! (A.src $ H.textValue $ picture profile)

gen cprg = encode <$> atomicModifyIORef' cprg (swap . cprgGenBytes 64)
genSessionId cprg = liftIO $ decodeUtf8 <$> gen cprg
genBytes cprg = liftIO $ gen cprg
gen sdrg = encode <$> atomicModifyIORef' sdrg (swap . randomBytesGenerate 64)
genSessionId sdrg = liftIO $ decodeUtf8 <$> gen sdrg
genBytes sdrg = liftIO $ gen sdrg
saveState ssm sid st nonce = liftIO $ atomicModifyIORef' ssm $ \m -> (M.insert sid (st, nonce) m, ())
getStateBy ssm sid _st = liftIO $ do
m <- M.lookup sid <$> readIORef ssm
Expand All @@ -161,9 +160,9 @@ run' = do
_ -> Nothing
deleteState ssm sid = liftIO $ atomicModifyIORef' ssm $ \m -> (M.delete sid m, ())

sessionStoreFromSession cprg ssm sid =
sessionStoreFromSession sdrg ssm sid =
O.SessionStore
{ sessionStoreGenerate = genBytes cprg
{ sessionStoreGenerate = genBytes sdrg
, sessionStoreSave = saveState ssm sid
, sessionStoreGet = getStateBy ssm sid
, sessionStoreDelete = const $ deleteState ssm sid
Expand Down
4 changes: 2 additions & 2 deletions oidc-client.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -115,11 +115,11 @@ executable scotty-example
, containers
, mtl
, wai-extra
-- scotty-cookie not compatible with scotty 0.20+
, scotty < 0.20
, scotty-cookie
, blaze-html
, cprng-aes
, crypto-random
, crypton ^>= 0.34
, base64-bytestring
, http-types
, http-client
Expand Down
5 changes: 5 additions & 0 deletions stack.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@ packages:
# Dependency packages to be pulled from upstream that are not in the resolver
extra-deps:
- jose-jwt-0.10.0@sha256:6ed175a01c721e317ceea15eb251a81de145c03711a977517935633a5cdec1d4,3546
- scotty-0.12.1@sha256:15c06ece267187c4324645e54f2104a63fe3eb8ce6eb5698e4093735daba1f1a,5437
- scotty-cookie-0.1.0.3@sha256:3ff1df13a5acba8ba170a5ac22b3ac6a2c227791292536ce1ebfc41038f58fc9,1204
- crypton-0.34@sha256:9e4b50d79d1fba681befa08151db7223d2b4bb72564853e8530e614105d53a1a,14577

Expand All @@ -15,6 +16,10 @@ flags: {}
# Extra package databases containing global packages
extra-package-dbs: []

allow-newer: true
allow-newer-deps:
- scotty

nix:
packages:
- ghc
Expand Down

0 comments on commit 25c8b92

Please sign in to comment.