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 checkSig :: BS.ByteString -> IO (Either JwtError BS.ByteString) checkSig tok = do key <- read <$> readFile ".key.hk" :: IO (Cr.PublicKey, Cr.PrivateKey) let jws = rsaDecode (view _1 key) tok return $ fmap (view _2) jws -- | Sign a token (note that we map the string to all lowercase before signing since QR codes do not distinguish case once read) mkSig :: BS.ByteString -> IO BS.ByteString mkSig string = do switch <- doesFileExist ".key.hk" if not switch then do putStrLn "generating key..." key <- Cr.generate 256 0x10001 writeFile ".key.hk" (show key) else return () key' <- read <$> readFile ".key.hk" :: IO (Cr.PublicKey, Cr.PrivateKey) signedToken <- rsaEncode RS256 (view _2 key') string let signed = fmap unJwt signedToken liftEither id (return <$> signed)