module Data.Blob ( Blob (..)
, BlobId
, BlobStore
, WriteContext
, ReadContext
, openBlobStore
, newBlob
, writePartial
, endWrite
, createBlob
, startRead
, readPartial
, skipBytes
, endRead
, readBlob
, deleteBlob
) where
import qualified Crypto.Hash.SHA512 as SHA512
import qualified Data.Blob.FileOperations as F
import Data.Blob.GC (markAsAccessible)
import Data.Blob.Types
openBlobStore :: FilePath -> IO BlobStore
openBlobStore dir = do
F.createTempIfMissing dir
F.createCurrIfMissing dir
return $ BlobStore dir
newBlob :: BlobStore -> IO WriteContext
newBlob (BlobStore dir) = do
filename <- F.createUniqueFile dir
let temploc = TempLocation dir filename
h <- F.openFileForWrite $ F.getTempPath temploc
return $ WriteContext temploc h SHA512.init
writePartial :: WriteContext -> Blob -> IO WriteContext
writePartial (WriteContext l h ctx) (Blob b) = do
F.writeToHandle h b
let newctx = SHA512.update ctx b
return $ WriteContext l h newctx
endWrite :: WriteContext -> IO BlobId
endWrite (WriteContext l h ctx) = do
F.syncAndClose h
markAsAccessible blobId
F.moveFile (F.getTempPath l) (baseDir l) newfilename
return blobId
where
newfilename = "sha512-" ++ F.toFileName (SHA512.finalize ctx)
blobId = BlobId (baseDir l) newfilename
createBlob :: BlobStore -> Blob -> IO BlobId
createBlob blobstore blob = newBlob blobstore
>>= \wc -> writePartial wc blob
>>= endWrite
startRead :: BlobId -> IO ReadContext
startRead loc = fmap ReadContext $ F.openFileForRead (F.getCurrPath loc)
readPartial :: ReadContext -> Int -> IO Blob
readPartial (ReadContext h) sz = fmap Blob $ F.readFromHandle h sz
skipBytes :: ReadContext -> Integer -> IO ()
skipBytes (ReadContext h) = F.seekHandle h
endRead :: ReadContext -> IO ()
endRead (ReadContext h) = F.closeHandle h
readBlob :: BlobId -> IO Blob
readBlob blobid = fmap Blob $ F.readFile (F.getCurrPath blobid)
deleteBlob :: BlobId -> IO ()
deleteBlob = F.deleteFile . F.getCurrPath