git-annex/Types/Key.hs
Joey Hess 521d4ede1e
fix build with cryptonite-0.20
Some blake hash varieties were not yet available in that version.
Rather than tracking exact details of what cryptonite supported when,
disable blake unless using a current cryptonite.
2018-03-15 11:16:00 -04:00

158 lines
6.5 KiB
Haskell

{- git-annex Key data type
-
- Copyright 2011-2017 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU GPL version 3 or higher.
-}
{-# LANGUAGE CPP #-}
module Types.Key where
import Utility.PartialPrelude
import System.Posix.Types
{- A Key has a unique name, which is derived from a particular backend,
- and may contain other optional metadata. -}
data Key = Key
{ keyName :: String
, keyVariety :: KeyVariety
, keySize :: Maybe Integer
, keyMtime :: Maybe EpochTime
, keyChunkSize :: Maybe Integer
, keyChunkNum :: Maybe Integer
} deriving (Eq, Ord, Read, Show)
{- A filename may be associated with a Key. -}
newtype AssociatedFile = AssociatedFile (Maybe FilePath)
deriving (Show, Eq, Ord)
{- There are several different varieties of keys. -}
data KeyVariety
= SHA2Key HashSize HasExt
| SHA3Key HashSize HasExt
| SKEINKey HashSize HasExt
| Blake2bKey HashSize HasExt
| Blake2sKey HashSize HasExt
| Blake2spKey HashSize HasExt
| SHA1Key HasExt
| MD5Key HasExt
| WORMKey
| URLKey
-- Some repositories may contain keys of other varieties,
-- which can still be processed to some extent.
| OtherKey String
deriving (Eq, Ord, Read, Show)
{- Some varieties of keys may contain an extension at the end of the
- keyName -}
newtype HasExt = HasExt Bool
deriving (Eq, Ord, Read, Show)
newtype HashSize = HashSize Int
deriving (Eq, Ord, Read, Show)
hasExt :: KeyVariety -> Bool
hasExt (SHA2Key _ (HasExt b)) = b
hasExt (SHA3Key _ (HasExt b)) = b
hasExt (SKEINKey _ (HasExt b)) = b
hasExt (Blake2bKey _ (HasExt b)) = b
hasExt (Blake2sKey _ (HasExt b)) = b
hasExt (Blake2spKey _ (HasExt b)) = b
hasExt (SHA1Key (HasExt b)) = b
hasExt (MD5Key (HasExt b)) = b
hasExt WORMKey = False
hasExt URLKey = False
hasExt (OtherKey s) = end s == "E"
sameExceptExt :: KeyVariety -> KeyVariety -> Bool
sameExceptExt (SHA2Key sz1 _) (SHA2Key sz2 _) = sz1 == sz2
sameExceptExt (SHA3Key sz1 _) (SHA3Key sz2 _) = sz1 == sz2
sameExceptExt (SKEINKey sz1 _) (SKEINKey sz2 _) = sz1 == sz2
sameExceptExt (Blake2bKey sz1 _) (Blake2bKey sz2 _) = sz1 == sz2
sameExceptExt (Blake2sKey sz1 _) (Blake2sKey sz2 _) = sz1 == sz2
sameExceptExt (Blake2spKey sz1 _) (Blake2spKey sz2 _) = sz1 == sz2
sameExceptExt (SHA1Key _) (SHA1Key _) = True
sameExceptExt (MD5Key _) (MD5Key _) = True
sameExceptExt _ _ = False
{- Is the Key variety cryptographically secure, such that no two differing
- file contents can be mapped to the same Key? -}
cryptographicallySecure :: KeyVariety -> Bool
cryptographicallySecure (SHA2Key _ _) = True
cryptographicallySecure (SHA3Key _ _) = True
cryptographicallySecure (SKEINKey _ _) = True
cryptographicallySecure (Blake2bKey _ _) = True
cryptographicallySecure (Blake2sKey _ _) = True
cryptographicallySecure (Blake2spKey _ _) = True
cryptographicallySecure _ = False
formatKeyVariety :: KeyVariety -> String
formatKeyVariety v = case v of
SHA2Key sz e -> adde e (addsz sz "SHA")
SHA3Key sz e -> adde e (addsz sz "SHA3_")
SKEINKey sz e -> adde e (addsz sz "SKEIN")
Blake2bKey sz e -> adde e (addsz sz "BLAKE2B")
Blake2sKey sz e -> adde e (addsz sz "BLAKE2S")
Blake2spKey sz e -> adde e (addsz sz "BLAKE2SP")
SHA1Key e -> adde e "SHA1"
MD5Key e -> adde e "MD5"
WORMKey -> "WORM"
URLKey -> "URL"
OtherKey s -> s
where
adde (HasExt False) s = s
adde (HasExt True) s = s ++ "E"
addsz (HashSize n) s = s ++ show n
parseKeyVariety :: String -> KeyVariety
parseKeyVariety "SHA256" = SHA2Key (HashSize 256) (HasExt False)
parseKeyVariety "SHA256E" = SHA2Key (HashSize 256) (HasExt True)
parseKeyVariety "SHA512" = SHA2Key (HashSize 512) (HasExt False)
parseKeyVariety "SHA512E" = SHA2Key (HashSize 512) (HasExt True)
parseKeyVariety "SHA224" = SHA2Key (HashSize 224) (HasExt False)
parseKeyVariety "SHA224E" = SHA2Key (HashSize 224) (HasExt True)
parseKeyVariety "SHA384" = SHA2Key (HashSize 384) (HasExt False)
parseKeyVariety "SHA384E" = SHA2Key (HashSize 384) (HasExt True)
parseKeyVariety "SHA3_512" = SHA3Key (HashSize 512) (HasExt False)
parseKeyVariety "SHA3_512E" = SHA3Key (HashSize 512) (HasExt True)
parseKeyVariety "SHA3_384" = SHA3Key (HashSize 384) (HasExt False)
parseKeyVariety "SHA3_384E" = SHA3Key (HashSize 384) (HasExt True)
parseKeyVariety "SHA3_256" = SHA3Key (HashSize 256) (HasExt False)
parseKeyVariety "SHA3_256E" = SHA3Key (HashSize 256) (HasExt True)
parseKeyVariety "SHA3_224" = SHA3Key (HashSize 224) (HasExt False)
parseKeyVariety "SHA3_224E" = SHA3Key (HashSize 224) (HasExt True)
parseKeyVariety "SKEIN512" = SKEINKey (HashSize 512) (HasExt False)
parseKeyVariety "SKEIN512E" = SKEINKey (HashSize 512) (HasExt True)
parseKeyVariety "SKEIN256" = SKEINKey (HashSize 256) (HasExt False)
parseKeyVariety "SKEIN256E" = SKEINKey (HashSize 256) (HasExt True)
#if MIN_VERSION_cryptonite(0,23,0)
parseKeyVariety "BLAKE2B160" = Blake2bKey (HashSize 160) (HasExt False)
parseKeyVariety "BLAKE2B160E" = Blake2bKey (HashSize 160) (HasExt True)
parseKeyVariety "BLAKE2B224" = Blake2bKey (HashSize 224) (HasExt False)
parseKeyVariety "BLAKE2B224E" = Blake2bKey (HashSize 224) (HasExt True)
parseKeyVariety "BLAKE2B256" = Blake2bKey (HashSize 256) (HasExt False)
parseKeyVariety "BLAKE2B256E" = Blake2bKey (HashSize 256) (HasExt True)
parseKeyVariety "BLAKE2B384" = Blake2bKey (HashSize 384) (HasExt False)
parseKeyVariety "BLAKE2B384E" = Blake2bKey (HashSize 384) (HasExt True)
parseKeyVariety "BLAKE2B512" = Blake2bKey (HashSize 512) (HasExt False)
parseKeyVariety "BLAKE2B512E" = Blake2bKey (HashSize 512) (HasExt True)
parseKeyVariety "BLAKE2S160" = Blake2sKey (HashSize 160) (HasExt False)
parseKeyVariety "BLAKE2S160E" = Blake2sKey (HashSize 160) (HasExt True)
parseKeyVariety "BLAKE2S224" = Blake2sKey (HashSize 224) (HasExt False)
parseKeyVariety "BLAKE2S224E" = Blake2sKey (HashSize 224) (HasExt True)
parseKeyVariety "BLAKE2S256" = Blake2sKey (HashSize 256) (HasExt False)
parseKeyVariety "BLAKE2S256E" = Blake2sKey (HashSize 256) (HasExt True)
parseKeyVariety "BLAKE2SP224" = Blake2spKey (HashSize 224) (HasExt False)
parseKeyVariety "BLAKE2SP224E" = Blake2spKey (HashSize 224) (HasExt True)
parseKeyVariety "BLAKE2SP256" = Blake2spKey (HashSize 256) (HasExt False)
parseKeyVariety "BLAKE2SP256E" = Blake2spKey (HashSize 256) (HasExt True)
#endif
parseKeyVariety "SHA1" = SHA1Key (HasExt False)
parseKeyVariety "SHA1E" = SHA1Key (HasExt True)
parseKeyVariety "MD5" = MD5Key (HasExt False)
parseKeyVariety "MD5E" = MD5Key (HasExt True)
parseKeyVariety "WORM" = WORMKey
parseKeyVariety "URL" = URLKey
parseKeyVariety s = OtherKey s