|
2 | 2 |
|
3 | 3 | module Main where
|
4 | 4 |
|
5 |
| -import Crypto.Hash (Digest) |
6 |
| -import qualified Crypto.Hash as CH |
7 |
| -import Data.Byteable (toBytes) |
8 |
| -import Data.ByteString (ByteString) |
9 |
| -import Data.ByteString.Lazy (toStrict) |
10 |
| -import Data.Monoid ((<>)) |
11 |
| -import Options.Applicative |
12 |
| - |
13 |
| -import System.IO.Streams (InputStream, stdin, stdout, |
14 |
| - withFileAsInput, write) |
15 |
| -import System.IO.Streams.Crypto (hashInputStream) |
16 |
| - |
17 |
| -import qualified Data.Multihash.Base as MB |
18 |
| -import qualified Data.Multihash.Digest as MH |
19 |
| - |
20 |
| - |
21 |
| -data Termination = Null | Newline deriving (Show, Eq) |
22 |
| -data Config = |
23 |
| - Config |
24 |
| - { cfFile :: Maybe FilePath |
25 |
| - , cfAlgo :: MH.HashAlgorithm |
26 |
| - , cfBase :: MB.BaseEncoding |
27 |
| - , cfHash :: Maybe MH.Digest |
28 |
| - , cfTerm :: Termination |
29 |
| - } deriving Show |
30 |
| - |
| 5 | +import Crypto.Hash (Digest) |
| 6 | +import qualified Crypto.Hash as CH |
| 7 | +import Data.ByteString (ByteString) |
| 8 | +import Data.ByteString.Lazy (toStrict) |
| 9 | +import Data.Byteable (toBytes) |
| 10 | +import Data.Monoid ((<>)) |
| 11 | +import Options.Applicative |
| 12 | + |
| 13 | +import System.IO.Streams (InputStream, stdin, stdout, withFileAsInput, write) |
| 14 | +import System.IO.Streams.Crypto (hashInputStream) |
| 15 | + |
| 16 | +import qualified Data.Multihash.Base as MB |
| 17 | +import qualified Data.Multihash.Digest as MH |
| 18 | + |
| 19 | +data Termination |
| 20 | + = Null |
| 21 | + | Newline |
| 22 | + deriving (Show, Eq) |
| 23 | + |
| 24 | +data Config = Config |
| 25 | + { cfFile :: Maybe FilePath |
| 26 | + , cfAlgo :: MH.HashAlgorithm |
| 27 | + , cfBase :: MB.BaseEncoding |
| 28 | + , cfHash :: Maybe MH.Digest |
| 29 | + , cfTerm :: Termination |
| 30 | + } deriving (Show) |
31 | 31 |
|
32 | 32 | main :: IO ()
|
33 |
| -main = do |
| 33 | +main |
34 | 34 | -- TODO add file checking
|
35 |
| - config <- execParser opts |
36 |
| - digest <- maybe (hashStdin config) (hashFile config) $ cfFile config |
37 |
| - write (multihash config digest) stdout |
| 35 | + = do |
| 36 | + config <- execParser opts |
| 37 | + digest <- maybe (hashStdin config) (hashFile config) $ cfFile config |
| 38 | + write (multihash config digest) stdout |
38 | 39 | where
|
39 | 40 | hashStdin config = hash (cfAlgo config) stdin
|
40 | 41 | hashFile config file = withFileAsInput file . hash $ cfAlgo config
|
41 | 42 | multihash (Config _file algo base _hash term) =
|
42 |
| - Just . toStrict . line term . MB.encode base . MH.encode algo |
43 |
| - |
44 |
| - line Null = (<> "\0") |
| 43 | + Just . toStrict . line term . MB.encode base . MH.encode algo |
| 44 | + line Null = (<> "\0") |
45 | 45 | line Newline = (<> "\n")
|
46 | 46 |
|
47 |
| - |
48 | 47 | -- TODO add BLAKE support
|
49 | 48 | hash :: MH.HashAlgorithm -> InputStream ByteString -> IO MH.Digest
|
50 |
| -hash MH.SHA1 is = toBytes <$> (hashInputStream is :: IO (Digest CH.SHA1)) |
| 49 | +hash MH.SHA1 is = toBytes <$> (hashInputStream is :: IO (Digest CH.SHA1)) |
51 | 50 | hash MH.SHA256 is = toBytes <$> (hashInputStream is :: IO (Digest CH.SHA256))
|
52 | 51 | hash MH.SHA512 is = toBytes <$> (hashInputStream is :: IO (Digest CH.SHA512))
|
53 |
| -hash MH.SHA3 is = toBytes <$> (hashInputStream is :: IO (Digest CH.SHA3_256)) |
| 52 | +hash MH.SHA3 is = toBytes <$> (hashInputStream is :: IO (Digest CH.SHA3_256)) |
54 | 53 | hash MH.BLAKE2B _ = undefined
|
55 | 54 | hash MH.BLAKE2S _ = undefined
|
56 | 55 |
|
57 |
| - |
58 | 56 | opts :: ParserInfo Config
|
59 |
| -opts = info |
60 |
| - (helper <*> (Config |
61 |
| - <$> fileArg |
62 |
| - <*> algoOpt |
63 |
| - <*> baseOpt |
64 |
| - <*> checkOpt |
65 |
| - <*> nullTermFlag |
66 |
| - )) |
67 |
| - (fullDesc |
68 |
| - <> header "Generate a multihash for the given input." |
69 |
| - <> progDesc "Hash from FILE or stdin if not given.") |
70 |
| - |
| 57 | +opts = |
| 58 | + info |
| 59 | + (helper <*> |
| 60 | + (Config <$> fileArg <*> algoOpt <*> baseOpt <*> checkOpt <*> nullTermFlag)) |
| 61 | + (fullDesc <> header "Generate a multihash for the given input." <> |
| 62 | + progDesc "Hash from FILE or stdin if not given.") |
71 | 63 |
|
72 | 64 | algoOpt :: Parser MH.HashAlgorithm
|
73 | 65 | algoOpt =
|
74 |
| - option auto |
75 |
| - $ long "algorithm" |
76 |
| - <> short 'a' |
77 |
| - <> metavar "ALGO" |
78 |
| - <> showDefault <> value MH.SHA256 |
79 |
| - <> help ("Hash algorithm to apply to input, ignored if checking hash " <> show ([minBound..] :: [MH.HashAlgorithm])) |
80 |
| - |
| 66 | + option auto $ |
| 67 | + long "algorithm" <> short 'a' <> metavar "ALGO" <> showDefault <> |
| 68 | + value MH.SHA256 <> |
| 69 | + help |
| 70 | + ("Hash algorithm to apply to input, ignored if checking hash " <> |
| 71 | + show ([minBound ..] :: [MH.HashAlgorithm])) |
81 | 72 |
|
82 | 73 | baseOpt :: Parser MB.BaseEncoding
|
83 | 74 | baseOpt =
|
84 |
| - option auto |
85 |
| - $ long "encoding" |
86 |
| - <> short 'e' |
87 |
| - <> metavar "ENCODING" |
88 |
| - <> showDefault <> value MB.Base58 |
89 |
| - <> help ("Base encoding of output digest, ignored if checking hash " <> show ([minBound..] :: [MB.BaseEncoding])) |
90 |
| - |
| 75 | + option auto $ |
| 76 | + long "encoding" <> short 'e' <> metavar "ENCODING" <> showDefault <> |
| 77 | + value MB.Base58 <> |
| 78 | + help |
| 79 | + ("Base encoding of output digest, ignored if checking hash " <> |
| 80 | + show ([minBound ..] :: [MB.BaseEncoding])) |
91 | 81 |
|
92 | 82 | checkOpt :: Parser (Maybe MH.Digest)
|
93 | 83 | checkOpt =
|
94 |
| - optional . option auto |
95 |
| - $ long "check" |
96 |
| - <> short 'c' |
97 |
| - <> metavar "DIGEST" |
98 |
| - <> help "Check for matching digest" |
99 |
| - |
| 84 | + optional . option auto $ |
| 85 | + long "check" <> short 'c' <> metavar "DIGEST" <> |
| 86 | + help "Check for matching digest" |
100 | 87 |
|
101 | 88 | nullTermFlag :: Parser Termination
|
102 | 89 | nullTermFlag =
|
103 |
| - flag Newline Null |
104 |
| - $ long "print0" |
105 |
| - <> short '0' |
106 |
| - <> help "End filenames with NUL, for use with xargs" |
107 |
| - |
| 90 | + flag Newline Null $ |
| 91 | + long "print0" <> short '0' <> |
| 92 | + help "End filenames with NUL, for use with xargs" |
108 | 93 |
|
109 | 94 | fileArg :: Parser (Maybe FilePath)
|
110 | 95 | fileArg = optional . argument str $ metavar "FILE"
|
0 commit comments