module Botan.Hash.Keccak
( Keccak1600(..)
, Keccak1600Digest(..)
, keccak1600
, keccak1600Lazy
) where

import GHC.TypeLits

import Data.Maybe
import Data.Proxy

import Data.Type.Bool
import Data.Type.Equality

import qualified Data.ByteString as ByteString
import qualified Data.ByteString.Lazy as Lazy
import qualified Data.Text as Text

import qualified Botan.Hash as Botan
import qualified Botan.Utility as Botan

import Botan.Hash.Class
import Botan.Prelude

-- Keccak1600 type

data Keccak1600 (n :: Nat)

type Keccak1600Size (n :: Nat) = (KnownNat n, (n == 224 || n == 256 || n == 384 || n == 512) ~ True)

type Keccak1600Digest n = Digest (Keccak1600 n)

newtype instance Digest (Keccak1600 n) = Keccak1600Digest
    { forall (n :: Nat). Digest (Keccak1600 n) -> ByteString
getKeccak1600ByteString :: ByteString {- ByteVector n -} }
    deriving newtype (Digest (Keccak1600 n) -> Digest (Keccak1600 n) -> Bool
(Digest (Keccak1600 n) -> Digest (Keccak1600 n) -> Bool)
-> (Digest (Keccak1600 n) -> Digest (Keccak1600 n) -> Bool)
-> Eq (Digest (Keccak1600 n))
forall (n :: Nat).
Digest (Keccak1600 n) -> Digest (Keccak1600 n) -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall (n :: Nat).
Digest (Keccak1600 n) -> Digest (Keccak1600 n) -> Bool
== :: Digest (Keccak1600 n) -> Digest (Keccak1600 n) -> Bool
$c/= :: forall (n :: Nat).
Digest (Keccak1600 n) -> Digest (Keccak1600 n) -> Bool
/= :: Digest (Keccak1600 n) -> Digest (Keccak1600 n) -> Bool
Eq, Eq (Digest (Keccak1600 n))
Eq (Digest (Keccak1600 n)) =>
(Digest (Keccak1600 n) -> Digest (Keccak1600 n) -> Ordering)
-> (Digest (Keccak1600 n) -> Digest (Keccak1600 n) -> Bool)
-> (Digest (Keccak1600 n) -> Digest (Keccak1600 n) -> Bool)
-> (Digest (Keccak1600 n) -> Digest (Keccak1600 n) -> Bool)
-> (Digest (Keccak1600 n) -> Digest (Keccak1600 n) -> Bool)
-> (Digest (Keccak1600 n)
    -> Digest (Keccak1600 n) -> Digest (Keccak1600 n))
-> (Digest (Keccak1600 n)
    -> Digest (Keccak1600 n) -> Digest (Keccak1600 n))
-> Ord (Digest (Keccak1600 n))
Digest (Keccak1600 n) -> Digest (Keccak1600 n) -> Bool
Digest (Keccak1600 n) -> Digest (Keccak1600 n) -> Ordering
Digest (Keccak1600 n)
-> Digest (Keccak1600 n) -> Digest (Keccak1600 n)
forall (n :: Nat). Eq (Digest (Keccak1600 n))
forall (n :: Nat).
Digest (Keccak1600 n) -> Digest (Keccak1600 n) -> Bool
forall (n :: Nat).
Digest (Keccak1600 n) -> Digest (Keccak1600 n) -> Ordering
forall (n :: Nat).
Digest (Keccak1600 n)
-> Digest (Keccak1600 n) -> Digest (Keccak1600 n)
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: forall (n :: Nat).
Digest (Keccak1600 n) -> Digest (Keccak1600 n) -> Ordering
compare :: Digest (Keccak1600 n) -> Digest (Keccak1600 n) -> Ordering
$c< :: forall (n :: Nat).
Digest (Keccak1600 n) -> Digest (Keccak1600 n) -> Bool
< :: Digest (Keccak1600 n) -> Digest (Keccak1600 n) -> Bool
$c<= :: forall (n :: Nat).
Digest (Keccak1600 n) -> Digest (Keccak1600 n) -> Bool
<= :: Digest (Keccak1600 n) -> Digest (Keccak1600 n) -> Bool
$c> :: forall (n :: Nat).
Digest (Keccak1600 n) -> Digest (Keccak1600 n) -> Bool
> :: Digest (Keccak1600 n) -> Digest (Keccak1600 n) -> Bool
$c>= :: forall (n :: Nat).
Digest (Keccak1600 n) -> Digest (Keccak1600 n) -> Bool
>= :: Digest (Keccak1600 n) -> Digest (Keccak1600 n) -> Bool
$cmax :: forall (n :: Nat).
Digest (Keccak1600 n)
-> Digest (Keccak1600 n) -> Digest (Keccak1600 n)
max :: Digest (Keccak1600 n)
-> Digest (Keccak1600 n) -> Digest (Keccak1600 n)
$cmin :: forall (n :: Nat).
Digest (Keccak1600 n)
-> Digest (Keccak1600 n) -> Digest (Keccak1600 n)
min :: Digest (Keccak1600 n)
-> Digest (Keccak1600 n) -> Digest (Keccak1600 n)
Ord)

instance Show (Digest (Keccak1600 n)) where
    show :: Digest (Keccak1600 n) -> String
    show :: Digest (Keccak1600 n) -> String
show (Keccak1600Digest ByteString
bytes) = Text -> String
Text.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ ByteString -> HexCase -> Text
Botan.hexEncode ByteString
bytes HexCase
Botan.Lower

instance (Keccak1600Size n) => Hash (Keccak1600 n) where
    hash :: ByteString -> Digest (Keccak1600 n)
    hash :: ByteString -> Digest (Keccak1600 n)
hash = ByteString -> Digest (Keccak1600 n)
forall (n :: Nat). ByteString -> Digest (Keccak1600 n)
Keccak1600Digest (ByteString -> Digest (Keccak1600 n))
-> (ByteString -> ByteString)
-> ByteString
-> Digest (Keccak1600 n)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash -> ByteString -> ByteString
Botan.hash Hash
h where
        n :: Int
n = Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Integer -> Int) -> Integer -> Int
forall a b. (a -> b) -> a -> b
$ Proxy n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy n -> Integer) -> Proxy n -> Integer
forall a b. (a -> b) -> a -> b
$ forall (t :: Nat). Proxy t
forall {k} (t :: k). Proxy t
Proxy @n
        h :: Hash
h = Maybe Hash -> Hash
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe Hash -> Hash) -> Maybe Hash -> Hash
forall a b. (a -> b) -> a -> b
$ Int -> Maybe Hash
Botan.keccak1600 Int
n
instance (Keccak1600Size n) => IncrementalHash (Keccak1600 n) where
    hashLazy :: Lazy.ByteString -> Digest (Keccak1600 n)
    hashLazy :: ByteString -> Digest (Keccak1600 n)
hashLazy = ByteString -> Digest (Keccak1600 n)
forall (n :: Nat). ByteString -> Digest (Keccak1600 n)
Keccak1600Digest (ByteString -> Digest (Keccak1600 n))
-> (ByteString -> ByteString)
-> ByteString
-> Digest (Keccak1600 n)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash -> ByteString -> ByteString
Botan.hashLazy Hash
h where
        n :: Int
n = Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Integer -> Int) -> Integer -> Int
forall a b. (a -> b) -> a -> b
$ Proxy n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy n -> Integer) -> Proxy n -> Integer
forall a b. (a -> b) -> a -> b
$ forall (t :: Nat). Proxy t
forall {k} (t :: k). Proxy t
Proxy @n
        h :: Hash
h = Maybe Hash -> Hash
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe Hash -> Hash) -> Maybe Hash -> Hash
forall a b. (a -> b) -> a -> b
$ Int -> Maybe Hash
Botan.keccak1600 Int
n

-- Keccak1600 hash

keccak1600 :: (Keccak1600Size n) => ByteString -> Keccak1600Digest n
keccak1600 :: forall (n :: Nat).
Keccak1600Size n =>
ByteString -> Digest (Keccak1600 n)
keccak1600 = ByteString -> Digest (Keccak1600 n)
forall hash. Hash hash => ByteString -> Digest hash
hash

keccak1600Lazy :: (Keccak1600Size n) => Lazy.ByteString -> Keccak1600Digest n
keccak1600Lazy :: forall (n :: Nat).
Keccak1600Size n =>
ByteString -> Digest (Keccak1600 n)
keccak1600Lazy = ByteString -> Digest (Keccak1600 n)
forall hash. IncrementalHash hash => ByteString -> Digest hash
hashLazy