module Crypto.Cipher.Types.Base
( KeyError(..)
, KeySizeSpecifier(..)
, Key(..)
, IV(..)
, Cipher(..)
, AuthTag(..)
, AEADMode(..)
, DataUnitOffset
) where
import Data.Byteable
import Data.SecureMem
import Data.Word
import Data.ByteString (ByteString)
data KeyError =
KeyErrorTooSmall
| KeyErrorTooBig
| KeyErrorInvalid String
deriving (Show,Eq)
data KeySizeSpecifier =
KeySizeRange Int Int
| KeySizeEnum [Int]
| KeySizeFixed Int
deriving (Show,Eq)
type DataUnitOffset = Word32
newtype Key c = Key SecureMem deriving (Eq)
instance ToSecureMem (Key c) where
toSecureMem (Key sm) = sm
instance Byteable (Key c) where
toBytes (Key sm) = toBytes sm
newtype IV c = IV ByteString deriving (Eq)
instance Byteable (IV c) where
toBytes (IV sm) = sm
newtype AuthTag = AuthTag ByteString
deriving (Show)
instance Eq AuthTag where
(AuthTag a) == (AuthTag b) = constEqBytes a b
instance Byteable AuthTag where
toBytes (AuthTag bs) = bs
data AEADMode =
AEAD_OCB
| AEAD_CCM
| AEAD_EAX
| AEAD_CWC
| AEAD_GCM
deriving (Show,Eq)
class Cipher cipher where
cipherInit :: Key cipher -> cipher
cipherName :: cipher -> String
cipherKeySize :: cipher -> KeySizeSpecifier