-- | This sets up the recommended implementation of Sha1.
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE FlexibleInstances #-}
--
-- The orphan instance declaration separates the implementation and
-- setting the recommended instances. Therefore, we ignore the warning.
--

module Raaz.Hash.Blake2.Recommendation where

import Raaz.Core
import Raaz.Hash.Blake2.Internal
import qualified Raaz.Hash.Blake2.Implementation.CPortable as CPortable


-- | Recommended implementation for blake2b.
instance Recommendation BLAKE2b where
  recommended :: BLAKE2b -> Implementation BLAKE2b
recommended BLAKE2b
_ = Implementation BLAKE2b
CPortable.implementation2b

-- | Recommended implementation for balke2s.
instance Recommendation BLAKE2s where
  recommended :: BLAKE2s -> Implementation BLAKE2s
recommended BLAKE2s
_ = Implementation BLAKE2s
CPortable.implementation2s