By | fr33domlover |
At | 2016-04-29 |
Title | Make the Pack module build and export it |
Description |
Edit file hit-harder.cabal 0 → 0
+ 28 , Data.Git.Harder.Pack
+ 33 , binary
+ 34 , bytestring
- 35 --, fgl
+ 38 , cryptonite
+ 41 , memory
+ 42 , monad-hash
- 41 --, unordered-containers
+ 46 , unordered-containers
+ 47 , zlib
… … … … Edit file src/Data/Git/Harder/Pack.hs 0 → 0
+ 16 {-# LANGUAGE OverloadedStrings #-}
+ 17 + 27 import Codec.Compression.Zlib (compress)
+ 28 import Control.Monad.IO.Class (liftIO)
+ 29 import Control.Monad.Trans.Hash
+ 30 import Crypto.Hash.Algorithms (SHA1)
- 31 - 32 putPackHeader :: Int -> Put
+ 37 import Data.ByteArray (convert)
+ 38 import Data.Foldable (foldlM)
+ 39 --import Data.Git.Ref (Ref, toBinary)
+ 40 import Data.Git.Repository (resolveTreeish)
+ 41 --import Data.Git.Revision (Revision (..))
+ 42 import Data.Git.Storage (Git, getObjectRaw)
+ 43 import Data.Git.Storage.Object (ObjectInfo (..))
+ 44 import Data.Git.Types (ObjectType (..), Commit (..))
+ 45 import Data.HashSet (HashSet)
+ 46 import Data.Maybe (fromMaybe)
+ 47 import Data.Word (Word8, Word32, Word64)
+ 48 + 49 import qualified Data.ByteString.Lazy as BL (ByteString, toChunks)
+ 50 import qualified Data.HashSet as S
+ 51 + 52 import Data.Git.Harder
+ 53 + 54 putPackHeader :: Word32 -> Put
… … … … - 50 putByteString "PACK" -- Signature
- 51 putWord32be 2 -- Version number
- 52 putInt32be numOfObjects -- Number of objects contained in the pack
+ 72 putByteString "PACK" -- Signature
+ 73 putWord32be 2 -- Version number
+ 74 putWord32be numOfObjects -- Number of objects contained in the pack
+ 75 + 76 putPackHeader' :: Int -> Put
+ 77 putPackHeader' n =
+ 78 case toIntegralSized n of
+ 79 Nothing -> error "Invalid number of objects to pack"
+ 80 Just w -> putPackHeader w
… … … … - 67 treeIds = map (commitTreeish git) commits
+ 95 treeIds = map (ObjId . commitTreeish) commits
- 71 visit s oid _ _ _ = S.insert oid s
+ 99 visit s oid _ _ = return (S.insert oid s, TAContinue)
- 74 let initial = S.fromList commitsIds `S.union` S.fromList treeIds
+ 102 let initial = S.fromList commitIds `S.union` S.fromList treeIds
… … … … - 93 low7bits :: Bits a => a -> Word8
+ 121 low7bits :: (Integral a, Bits a) => a -> Word8
- 95 let mw = fromIntegralSized $ n .&. 0x7f
+ 123 let mw = toIntegralSized $ n .&. 0x7f
… … … … - 113 putExtensibleWord :: Bits a => a -> Put
+ 141 putExtensibleWord :: (Integral a, Bits a) => a -> Put
… … … … - 127 :: Bits a
+ 155 :: (Integral a, Bits a)
- 136 if rest == zeroBits
- 137 then putWord8 $ stops first
- 138 else do
- 139 putWord8 $ continues first
- 140 let first' = low7bits rest
- 141 rest' = unsafeShiftR rest 7
- 142 putExtensibleWord' first' rest'
+ 164 in if rest == zeroBits
+ 165 then putWord8 $ stops first
+ 166 else do
+ 167 putWord8 $ continues first
+ 168 let first' = low7bits rest
+ 169 rest' = unsafeShiftR rest 7
+ 170 putExtensibleWord' first' rest'
… … … … - 163 compressObect (ObjectInfo (t, s, _mp) odata _ochains) = CompressedObject
+ 191 compressObject (ObjectInfo (t, s, _mp) odata _ochains) = CompressedObject
… … … … - 182 updateHashMulti $ toChunks lbs
+ 210 updateHashMulti $ BL.toChunks lbs
- 188 header <- writeHashed $ putPackHeader $ S.size oidset
+ 216 header <- writeHashed $ putPackHeader' $ S.size oidset
… … … … Edit file stack.yaml 0 → 0
- 14 extra-deps: []
+ 14 extra-deps:
+ 15 - monad-hash-0.1
… … … …