@@ -3,15 +3,11 @@ Description : Cryptographic hashing interface for hnix-store, on top
33 of the cryptohash family of libraries.
44-}
55{-# LANGUAGE AllowAmbiguousTypes #-}
6- {-# LANGUAGE DataKinds #-}
76{-# LANGUAGE GeneralizedNewtypeDeriving #-}
8- {-# LANGUAGE PolyKinds #-}
9- {-# LANGUAGE RankNTypes #-}
107{-# LANGUAGE TypeFamilies #-}
11- {-# LANGUAGE KindSignatures #-}
128{-# LANGUAGE ScopedTypeVariables #-}
139{-# LANGUAGE TypeApplications #-}
14- {-# LANGUAGE TypeInType #-}
10+ {-# LANGUAGE DataKinds #-}
1511{-# LANGUAGE OverloadedStrings #-}
1612
1713module System.Nix.Internal.Hash where
@@ -21,21 +17,16 @@ import qualified Crypto.Hash.SHA1 as SHA1
2117import qualified Crypto.Hash.SHA256 as SHA256
2218import qualified Data.ByteString as BS
2319import qualified Data.ByteString.Base16 as Base16
24- import qualified Data.ByteString.Char8 as BSC
2520import Data.Bits (xor )
26- import qualified Data.ByteString as BS
2721import qualified Data.ByteString.Lazy as BSL
2822import qualified Data.Hashable as DataHashable
29- import Data.Kind (Type )
3023import Data.List (foldl' )
31- import Data.Monoid
3224import Data.Proxy (Proxy (Proxy ))
3325import Data.Text (Text )
3426import qualified Data.Text as T
3527import qualified Data.Text.Encoding as T
36- import qualified Data.Vector as V
3728import Data.Word (Word8 )
38- import GHC.TypeLits
29+ import GHC.TypeLits ( Nat , KnownNat , natVal )
3930import qualified System.Nix.Base32 as Base32
4031
4132-- | The universe of supported hash algorithms.
@@ -58,7 +49,7 @@ newtype Digest (a :: HashAlgorithm) =
5849-- 'HashAlgorithm'. Every 'HashAlgorithm' should have an instance.
5950class ValidAlgo (a :: HashAlgorithm ) where
6051 -- | The incremental state for constructing a hash.
61- type AlgoCtx a :: Type
52+ type AlgoCtx a
6253
6354 -- | Start building a new hash.
6455 initialize :: AlgoCtx a
@@ -69,7 +60,7 @@ class ValidAlgo (a :: HashAlgorithm) where
6960
7061-- | An algorithm with a canonical name, for serialization purposes
7162-- (e.g. SRI hashes)
72- class NamedAlgo a where
63+ class NamedAlgo ( a :: HashAlgorithm ) where
7364 algoName :: Text
7465
7566instance NamedAlgo 'MD5 where
0 commit comments