module Network.Google.OAuth2.JWT where
import Codec.Crypto.RSA.Pure
import qualified Data.ByteString as B
import Data.ByteString.Base64.URL (encode)
import Data.ByteString.Lazy (fromStrict, toStrict)
import Data.Maybe (fromMaybe, fromJust)
import Data.Monoid ((<>))
import qualified Data.Text as T
import Data.Text.Encoding
import Data.UnixTime (getUnixTime, utSeconds)
import Foreign.C.Types
import OpenSSL.EVP.PKey (toKeyPair)
import OpenSSL.PEM (PemPasswordSupply (PwNone),
readPrivateKey)
import OpenSSL.RSA
type Scope = T.Text
type Email = T.Text
fromPEMFile :: FilePath -> IO PrivateKey
fromPEMFile f = readFile f >>= fromPEMString
fromPEMString :: String -> IO PrivateKey
fromPEMString s =
fromJust . toKeyPair <$> readPrivateKey s PwNone
>>= \k -> return PrivateKey
{ private_pub =
PublicKey { public_size = rsaSize k
, public_n = rsaN k
, public_e = rsaE k
}
, private_d = rsaD k
, private_p = rsaP k
, private_q = rsaQ k
, private_dP = 0
, private_dQ = 0
, private_qinv = 0
}
getSignedJWT :: Email
-> Maybe Email
-> [Scope]
-> Maybe Int
-> PrivateKey
-> IO (Either String B.ByteString)
getSignedJWT iss msub scopes mexp privateKey = do
let expt = fromIntegral $ fromMaybe 3600 mexp
cs <- jwtClaimsSet
(maybe T.empty (\s -> "\"sub\":\"" <> s <> "\",") msub) expt
let i = jwtHeader <> "." <> cs
return $
if expt > 0 && expt <= 3600 then
case rsassa_pkcs1_v1_5_sign hashSHA256 privateKey (fromStrict i) of
Right s -> Right $ i <> "." <> encode (toStrict s)
Left _ -> Left "RSAError"
else Left "Bad expiration time"
where
jwtHeader = toJWT "{\"alg\":\"RS256\",\"typ\":\"JWT\"}"
jwtClaimsSet s e = do
(exp',iat') <-
getUnixTime >>= \t ->
return ( toText $ utSeconds t + CTime e
, toText $ utSeconds t
)
return $ toJWT $
"{\"iss\":\"" <> iss <> "\"," <> s <> "\"scope\":\""
<> T.intercalate " " scopes <> "\",\"aud\":\"https://ww\
\w.googleapis.com/oauth2/v4/token\",\"exp\":" <> exp'
<> ",\"iat\":" <> iat' <> "}"
toText = T.pack . show
toJWT = encode . encodeUtf8