1{- git SHA stuff
2 -
3 - Copyright 2011,2020 Joey Hess <id@joeyh.name>
4 -
5 - Licensed under the GNU AGPL version 3 or higher.
6 -}
7
8{-# LANGUAGE OverloadedStrings #-}
9
10module Git.Sha where
11
12import Common
13import Git.Types
14
15import qualified Data.ByteString as S
16import Data.Char
17
18{- Runs an action that causes a git subcommand to emit a Sha, and strips
19 - any trailing newline, returning the sha. -}
20getSha :: String -> IO S.ByteString -> IO Sha
21getSha subcommand a = maybe bad return =<< extractSha <$> a
22  where
23	bad = error $ "failed to read sha from git " ++ subcommand
24
25{- Extracts the Sha from a ByteString.
26 -
27 - There can be a trailing newline after it, but nothing else.
28 -}
29extractSha :: S.ByteString -> Maybe Sha
30extractSha s
31	| len `elem` shaSizes = val s
32	| len - 1 `elem` shaSizes && S.length s' == len - 1 = val s'
33	| otherwise = Nothing
34  where
35	len = S.length s
36	s' = firstLine' s
37	val v
38		| S.all validinsha v = Just $ Ref v
39		| otherwise = Nothing
40	validinsha w = or
41		[ w >= 48 && w <= 57 -- 0-9
42		, w >= 97 && w <= 102 -- a-f
43		, w >= 65 && w <= 70 -- A-F
44		]
45
46{- Sizes of git shas. -}
47shaSizes :: [Int]
48shaSizes =
49	[ 40 -- sha1 (must come first)
50	, 64 -- sha256
51	]
52
53{- Git plumbing often uses a all 0 sha to represent things like a
54 - deleted file. -}
55nullShas :: [Sha]
56nullShas = map (\n -> Ref (S.replicate n zero)) shaSizes
57  where
58	zero = fromIntegral (ord '0')
59
60{- Sha to provide to git plumbing when deleting a file.
61 -
62 - It's ok to provide a sha1; git versions that use sha256 will map the
63 - sha1 to the sha256, or probably just treat all null sha1 specially
64 - the same as all null sha256. -}
65deleteSha :: Sha
66deleteSha = Prelude.head nullShas
67
68{- Git's magic empty tree.
69 -
70 - It's ok to provide the sha1 of this to git to refer to an empty tree;
71 - git versions that use sha256 will map the sha1 to the sha256.
72 -}
73emptyTree :: Ref
74emptyTree = Ref "4b825dc642cb6eb9a060e54bf8d69288fbee4904"
75