summaryrefslogtreecommitdiff
path: root/Types/StoreRetrieve.hs
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2014-07-29 14:53:17 -0400
committerGravatar Joey Hess <joey@kitenet.net>2014-07-29 15:16:12 -0400
commit48674a62c7d1fb9932c2bd234e6f851ec75478ac (patch)
tree42e85e57863731f46373052c3d2f6ba269121491 /Types/StoreRetrieve.hs
parent51a3747830e9c3a966185977b50652a928b3ee84 (diff)
add ContentSource type, for remotes that act on files rather than ByteStrings
Note that currently nothing cleans up a ContentSource's file, when eg, retrieving chunks.
Diffstat (limited to 'Types/StoreRetrieve.hs')
-rw-r--r--Types/StoreRetrieve.hs54
1 files changed, 54 insertions, 0 deletions
diff --git a/Types/StoreRetrieve.hs b/Types/StoreRetrieve.hs
new file mode 100644
index 000000000..2520d6309
--- /dev/null
+++ b/Types/StoreRetrieve.hs
@@ -0,0 +1,54 @@
+{- Types for Storer and Retriever
+ -
+ - Copyright 2014 Joey Hess <joey@kitenet.net>
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+{-# LANGUAGE Rank2Types #-}
+
+module Types.StoreRetrieve where
+
+import Common.Annex
+import Utility.Metered
+import Utility.Tmp
+
+import qualified Data.ByteString.Lazy as L
+
+-- Prepares for and then runs an action that will act on a Key's
+-- content, passing it a helper when the preparation is successful.
+type Preparer helper = forall a. Key -> (Maybe helper -> Annex a) -> Annex a
+
+-- A source of a Key's content.
+data ContentSource
+ = FileContent FilePath
+ | ByteContent L.ByteString
+
+-- Action that stores a Key's content on a remote.
+-- Can throw exceptions.
+type Storer = Key -> ContentSource -> MeterUpdate -> IO Bool
+
+-- Action that retrieves a Key's content from a remote.
+-- Throws exception if key is not present, or remote is not accessible.
+type Retriever = Key -> IO ContentSource
+
+fileStorer :: (Key -> FilePath -> MeterUpdate -> IO Bool) -> Storer
+fileStorer a k (FileContent f) m = a k f m
+fileStorer a k (ByteContent b) m = do
+ withTmpFile "tmpXXXXXX" $ \f h -> do
+ L.hPut h b
+ hClose h
+ a k f m
+
+byteStorer :: (Key -> L.ByteString -> MeterUpdate -> IO Bool) -> Storer
+byteStorer a k c m = withBytes c $ \b -> a k b m
+
+withBytes :: ContentSource -> (L.ByteString -> IO a) -> IO a
+withBytes (ByteContent b) a = a b
+withBytes (FileContent f) a = a =<< L.readFile f
+
+fileRetriever :: (Key -> IO FilePath) -> Retriever
+fileRetriever a k = FileContent <$> a k
+
+byteRetriever :: (Key -> IO L.ByteString) -> Retriever
+byteRetriever a k = ByteContent <$> a k