-- | Functions associated with signing the JSON records module Data.QRCodes.Signature where import Jose.Jws import qualified Data.ByteString.Char8 as BS import Jose.Jwt (unJwt, JwtError) import Crypto.PubKey.RSA as Cr import Control.Lens import System.Directory import Jose.Jwa (JwsAlg (RS256)) import Data.QRCodes.Utils -- | Verify a signed token with a key from a given filepath checkSig :: BS.ByteString -> FilePath -> IO (Either JwtError BS.ByteString) checkSig tok filepath = do key <- read <$> readFile filepath :: IO (Cr.PublicKey, Cr.PrivateKey) let jws = rsaDecode (view _1 key) tok return $ fmap (view _2) jws -- | Sign a token (note that we must pass in a processed token since there is no uppercase/lowercase here) with a key from a given filepath mkSig :: BS.ByteString -> FilePath -> IO BS.ByteString mkSig string filepath = do switch <- doesFileExist filepath if not switch then do putStrLn "generating key..." key <- Cr.generate 256 0x10001 writeFile filepath (show key) else return () key' <- read <$> readFile filepath :: IO (Cr.PublicKey, Cr.PrivateKey) signedToken <- rsaEncode RS256 (view _2 key') string let signed = fmap unJwt signedToken liftEither id (return <$> signed)