{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} module Api ( getProfileActivity ) where import Control.Monad.IO.Class import Crypto.Cipher.AES (AES256) import Crypto.Cipher.Types (BlockCipher (..), Cipher (..), IV, KeySizeSpecifier (..), cipherInit, ctrCombine, makeIV, nullIV) import Crypto.Error (CryptoError, CryptoFailable (..), eitherCryptoError) import Crypto.PubKey.OpenSsh (OpenSshPrivateKey (..), decodePrivate, encodePrivate) import qualified Crypto.PubKey.OpenSsh.Decode as D import qualified Crypto.PubKey.OpenSsh.Types as T import Crypto.PubKey.RSA (PrivateKey (..), PublicKey (..), generate) import Crypto.PubKey.RSA.PKCS15 import qualified Crypto.Random.Types as CRT import qualified Crypto.Simple.CBC as SC import qualified Crypto.Types.PubKey.RSA as CRSA import Data.ByteArray (ByteArray) import qualified Data.ByteString as B import qualified Data.ByteString.Base64 as BBS64 import qualified Data.ByteString.Char8 as BS import Data.Hashable import Data.Maybe import Data.PEM import qualified Data.Text as T import GHC.Generics import System.Directory ---------------------------------------------------------------------------------- endpoint = "https://api.yoti.com/api/v1" authKeyHeader = "X-Yoti-Auth-Key" digestHeader = "X-Yoti-Auth-Digest" sdkHeader = "X-Yoti-SDK" ---------------------------------------------------------------------------------- getProfileActivity :: BS.ByteString -> String -> IO () getProfileActivity token pathToKeyPair = do privKeyE <- readPemRsaKey' pathToKeyPair -- by default: test/keys/test.pem case privKeyE of Left error -> do putStrLn $ " | ERR: " ++ error return $ () Right privKey -> do putStrLn $ show $ privKey let tknE = BBS64.decode token case tknE of Left err -> do putStrLn $ " | ERR: " ++ (err) Right tkn -> do let decryptedMsg = decrypt Nothing privKey tkn case decryptedMsg of Left err -> putStrLn $ " | ERR: " ++ (show $ err) Right msg -> do putStrLn $ show $ msg return $ () -- |Read private RSA Key in PEM format readPemRsaKey' :: MonadIO m => FilePath -- ^file path to read key from; must be PEM -> m (Either String PrivateKey) readPemRsaKey' path = do exists <- liftIO $ doesFileExist path case exists of False -> return $ Left $ "File not found!" True -> do eKey <- liftIO $ D.decodePrivate <$> B.readFile path return $ case eKey of Right (T.OpenSshPrivateKeyRsa k) -> Right k Right other -> Left " | Not RSA" Left err -> Left $ " | " ++ ( show $ err) main :: IO () main = putStrLn "--"