-- BlockCipher.hs: OpenPGP (RFC4880) block cipher stuff
-- Copyright © 2013-2016  Clint Adams
-- This software is released under the terms of the Expat license.
-- (See the LICENSE file).

{-# LANGUAGE RankNTypes #-}

module Codec.Encryption.OpenPGP.BlockCipher (
    keySize
  , withSymmetricCipher
) where

import Codec.Encryption.OpenPGP.Internal.CryptoCipherTypes (HOWrappedOldCCT(..))
import Codec.Encryption.OpenPGP.Internal.Cryptonite (HOWrappedCCT(..))
import Codec.Encryption.OpenPGP.Internal.HOBlockCipher
import Codec.Encryption.OpenPGP.Types

import qualified Crypto.Cipher.Blowfish as Blowfish
import qualified Crypto.Cipher.TripleDES as TripleDES
import qualified Crypto.Cipher.AES as AES
import qualified Crypto.Cipher.Camellia as Camellia
import qualified Crypto.Nettle.Ciphers as CNC
import qualified Data.ByteString as B

type HOCipher a = forall cipher. HOBlockCipher cipher => cipher -> Either String a

withSymmetricCipher :: SymmetricAlgorithm -> B.ByteString -> HOCipher a -> Either String a
withSymmetricCipher Plaintext _ _ = Left "this shouldn't have happened" -- FIXME: orphan instance?
withSymmetricCipher IDEA _ _ = Left "IDEA not yet implemented" -- FIXME: IDEA
withSymmetricCipher ReservedSAFER _ _ = Left "SAFER not implemented" -- FIXME: or not?
withSymmetricCipher ReservedDES _ _ = Left "DES not implemented" -- FIXME: or not?
withSymmetricCipher (OtherSA _) _ _ = Left "Unknown, unimplemented symmetric algorithm"
withSymmetricCipher CAST5 key f = (cipherInit key :: Either String (HOWrappedOldCCT CNC.CAST128)) >>= f
withSymmetricCipher Twofish key f = (cipherInit key :: Either String (HOWrappedOldCCT CNC.TWOFISH)) >>= f
withSymmetricCipher TripleDES key f = (cipherInit key :: Either String (HOWrappedCCT TripleDES.DES_EDE3)) >>= f
withSymmetricCipher Blowfish key f = (cipherInit key :: Either String (HOWrappedCCT Blowfish.Blowfish128)) >>= f
withSymmetricCipher AES128 key f = (cipherInit key :: Either String (HOWrappedCCT AES.AES128)) >>= f
withSymmetricCipher AES192 key f = (cipherInit key :: Either String (HOWrappedCCT AES.AES192)) >>= f
withSymmetricCipher AES256 key f = (cipherInit key :: Either String (HOWrappedCCT AES.AES256)) >>= f
withSymmetricCipher Camellia128 key f = (cipherInit key :: Either String (HOWrappedCCT Camellia.Camellia128)) >>= f
withSymmetricCipher Camellia192 key f = (cipherInit key :: Either String (HOWrappedOldCCT CNC.Camellia192)) >>= f
withSymmetricCipher Camellia256 key f = (cipherInit key :: Either String (HOWrappedOldCCT CNC.Camellia256)) >>= f

-- in octets; FIXME: co-opt Cipher's cipherKeySize or not?
keySize :: SymmetricAlgorithm -> Int
keySize Plaintext = 0
keySize IDEA = 16 -- according to https://en.wikipedia.org/wiki/International_Data_Encryption_Algorithm
keySize TripleDES = 24 -- RFC 4880 says 168 bits (derived from 192 bits) but we don't know who does the derivation
keySize CAST5 = 16
keySize Blowfish = 16
keySize ReservedSAFER = undefined
keySize ReservedDES = undefined
keySize AES128 = 16
keySize AES192 = 24
keySize AES256 = 32
keySize Twofish = 32
keySize Camellia128 = 16
keySize Camellia192 = 24
keySize Camellia256 = 32
keySize (OtherSA _) = undefined