module Crypto.Classes
	( 
	
	  Hash(..)
	, hash
	, hash'
	, hashFunc
	, hashFunc'
	
	, BlockCipher(..)
	, blockSizeBytes
	, buildKeyIO
	, StreamCipher(..)
	, buildStreamKeyIO
	, AsymCipher(..)
	, buildKeyPairIO
	, Signing(..)
	, buildSigningKeyPairIO
	
	, for
	, (.::.)
	) where
import Data.Serialize
import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString as B
import qualified Data.ByteString.Internal as I
import Data.List (foldl')
import Data.Word (Word64)
import Data.Tagged
import Crypto.Types
import Crypto.Random
import System.Entropy
class (Serialize d, Eq d, Ord d)
    => Hash ctx d | d -> ctx, ctx -> d where
  outputLength	:: Tagged d BitLength	      
  blockLength	:: Tagged d BitLength	      
  initialCtx	:: ctx			      
  updateCtx	:: ctx -> B.ByteString -> ctx 
                                              
  finalize	:: ctx -> B.ByteString -> d   
hash :: (Hash ctx d) => L.ByteString -> d
hash msg = res
  where
  res = finalize ctx end
  ctx = foldl' updateCtx initialCtx blks
  (blks,end) = makeBlocks msg blockLen
  blockLen = (blockLength .::. res) `div` 8
hash' :: (Hash ctx d) => B.ByteString -> d
hash' msg = res
  where
  res = finalize (updateCtx initialCtx top) end
  (top, end) = B.splitAt remlen msg
  remlen = B.length msg  (B.length msg `rem` bLen)
  bLen = blockLength `for` res `div` 8
hashFunc :: Hash c d => d -> (L.ByteString -> d)
hashFunc d = f
  where
  f = hash
  a = f undefined `asTypeOf` d
hashFunc' :: Hash c d => d -> (B.ByteString -> d)
hashFunc' d = f
  where
  f = hash'
  a = f undefined `asTypeOf` d
makeBlocks :: L.ByteString -> ByteLength -> ([B.ByteString], B.ByteString)
makeBlocks msg len = go (L.toChunks msg)
  where
  go [] = ([],B.empty)
  go (x:xs)
    | B.length x >= len =
	let l = B.length x  B.length x `rem` len
	    (top,end) = B.splitAt l x
	    (rest,trueEnd) = go (end:xs)
	in (top:rest, trueEnd)
    | otherwise =
	case xs of
		[] -> ([], x)
		(a:as) -> go (B.append x a : as)
for :: Tagged a b -> a -> b
for t _ = unTagged t
(.::.) :: Tagged a b -> a -> b
(.::.) = for
class ( Serialize k) => BlockCipher k where
  blockSize	:: Tagged k BitLength			
  encryptBlock	:: k -> B.ByteString -> B.ByteString	
  decryptBlock	:: k -> B.ByteString -> B.ByteString	
  buildKey	:: B.ByteString -> Maybe k		
  keyLength	:: Tagged k BitLength			
blockSizeBytes :: (BlockCipher k) => Tagged k ByteLength
blockSizeBytes = fmap (`div` 8) blockSize
buildKeyIO :: (BlockCipher k) => IO k
buildKeyIO = go 0
  where
  go 1000 = error "Tried 1000 times to generate a key from the system entropy.\
                  \  No keys were returned! Perhaps the system entropy is broken\
                  \ or perhaps the BlockCipher instance being used has a non-flat\
                  \ keyspace."
  go i = do
	let bs = keyLength
	kd <- getEntropy ((7 + untag bs) `div` 8)
	case buildKey kd of
		Nothing -> go (i+1)
		Just k  -> return $ k `asTaggedTypeOf` bs
class (Serialize p, Serialize v) => AsymCipher p v where
  buildKeyPair :: CryptoRandomGen g => g -> BitLength -> Either GenError ((p,v),g) 
  encryptAsym      :: (CryptoRandomGen g) => g -> p -> B.ByteString -> Either GenError (B.ByteString,g)	
  decryptAsym      :: v -> B.ByteString -> Maybe B.ByteString  
  publicKeyLength  :: p -> BitLength
  privateKeyLength :: v -> BitLength
buildKeyPairIO :: AsymCipher p v => BitLength -> IO (Either GenError (p,v))
buildKeyPairIO bl = do
	g <- newGenIO :: IO SystemRandom
	case buildKeyPair g bl of
		Left err -> return (Left err)
		Right (k,_) -> return (Right k)
class (Serialize k) => StreamCipher k iv | k -> iv where
  buildStreamKey	:: B.ByteString -> Maybe k
  encryptStream		:: k -> iv -> B.ByteString -> (B.ByteString, iv)
  decryptStream 	:: k -> iv -> B.ByteString -> (B.ByteString, iv)
  streamKeyLength	:: Tagged k BitLength
buildStreamKeyIO :: StreamCipher k iv => IO k
buildStreamKeyIO = go 0
  where
  go 1000 = error "Tried 1000 times to generate a stream key from the system entropy.\
                  \  No keys were returned! Perhaps the system entropy is broken\
                  \ or perhaps the BlockCipher instance being used has a non-flat\
                  \ keyspace."
  go i = do
	let k = streamKeyLength
	kd <- getEntropy ((untag k + 7) `div` 8)
	case buildStreamKey kd of
		Nothing -> go (i+1)
		Just k' -> return $ k' `asTaggedTypeOf` k
class (Serialize p, Serialize v) => Signing p v | p -> v, v -> p  where
  sign	 :: CryptoRandomGen g => g -> v -> L.ByteString -> Either GenError (B.ByteString, g)
  verify :: p -> L.ByteString -> B.ByteString -> Bool
  buildSigningPair :: CryptoRandomGen g => g -> BitLength -> Either GenError ((p, v), g)
  signingKeyLength :: v -> BitLength
  verifyingKeyLength :: p -> BitLength
buildSigningKeyPairIO :: (Signing p v) => BitLength -> IO (Either GenError (p,v))
buildSigningKeyPairIO bl = do
	g <- newGenIO :: IO SystemRandom
	case buildSigningPair g bl of
		Left err -> return $ Left err
		Right (k,_) -> return $ Right k