summaryrefslogtreecommitdiff
path: root/Logs
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2014-07-24 16:23:36 -0400
committerGravatar Joey Hess <joey@kitenet.net>2014-07-24 16:23:36 -0400
commit2b414feaf2d20452794d0cdd608c6dd91feb1ec1 (patch)
tree16f4caafc5158227eda6b36462b93a9c3f35173f /Logs
parent35b31b00e4efbf84bcfb814acc477bbb89b50107 (diff)
implement chunk logs
Slightly tricky as they are not normal UUIDBased logs, but are instead maps from (uuid, chunksize) to chunkcount. This commit was sponsored by Frank Thomas.
Diffstat (limited to 'Logs')
-rw-r--r--Logs/Chunk.hs44
-rw-r--r--Logs/Chunk/Pure.hs32
-rw-r--r--Logs/UUIDBased.hs2
3 files changed, 77 insertions, 1 deletions
diff --git a/Logs/Chunk.hs b/Logs/Chunk.hs
new file mode 100644
index 000000000..76da50947
--- /dev/null
+++ b/Logs/Chunk.hs
@@ -0,0 +1,44 @@
+{- Chunk logs.
+ -
+ - An object can be stored in chunked for on a remote; these logs keep
+ - track of the chunk size used, and the number of chunks.
+ -
+ - It's possible for a single object to be stored multiple times on the
+ - same remote using different chunk sizes. So, while this is a MapLog, it
+ - is not a normal UUIDBased log. Intead, it's a map from UUID and chunk
+ - size to number of chunks.
+ -
+ - Format: "timestamp uuid:chunksize chunkcount"
+ -
+ - Copyright 2014 Joey Hess <joey@kitenet.net>
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+module Logs.Chunk where
+
+import Common.Annex
+import Logs
+import Logs.MapLog
+import qualified Annex.Branch
+import Logs.Chunk.Pure
+
+import qualified Data.Map as M
+import Data.Time.Clock.POSIX
+
+chunksStored :: UUID -> Key -> ChunkSize -> ChunkCount -> Annex ()
+chunksStored u k chunksize chunkcount = do
+ ts <- liftIO getPOSIXTime
+ Annex.Branch.change (chunkLogFile k) $
+ showLog . changeMapLog ts (u, chunksize) chunkcount . parseLog
+
+chunksRemoved :: UUID -> Key -> ChunkSize -> Annex ()
+chunksRemoved u k chunksize = chunksStored u k chunksize 0
+
+getCurrentChunks :: UUID -> Key -> Annex [(ChunkSize, ChunkCount)]
+getCurrentChunks u k = select . parseLog <$> Annex.Branch.get (chunkLogFile k)
+ where
+ select = filter (\(_sz, ct) -> ct > 0)
+ . map (\((_ku, sz), l) -> (sz, value l))
+ . M.toList
+ . M.filterWithKey (\(ku, _sz) _ -> ku == u)
diff --git a/Logs/Chunk/Pure.hs b/Logs/Chunk/Pure.hs
new file mode 100644
index 000000000..09e871c38
--- /dev/null
+++ b/Logs/Chunk/Pure.hs
@@ -0,0 +1,32 @@
+{- Chunk logs, pure operations.
+ -
+ - Copyright 2014 Joey Hess <joey@kitenet.net>
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+module Logs.Chunk.Pure where
+
+import Common.Annex
+import Logs.MapLog
+import Data.Int
+
+type ChunkSize = Int64
+
+type ChunkCount = Integer
+
+type ChunkLog = MapLog (UUID, ChunkSize) ChunkCount
+
+parseLog :: String -> ChunkLog
+parseLog = parseMapLog fieldparser valueparser
+ where
+ fieldparser s =
+ let (u,sz) = separate (== ':') s
+ in (,) <$> pure (toUUID u) <*> readish sz
+ valueparser = readish
+
+showLog :: ChunkLog -> String
+showLog = showMapLog fieldshower valueshower
+ where
+ fieldshower (u, sz) = fromUUID u ++ ':' : show sz
+ valueshower = show
diff --git a/Logs/UUIDBased.hs b/Logs/UUIDBased.hs
index b403b6253..fe1c9e012 100644
--- a/Logs/UUIDBased.hs
+++ b/Logs/UUIDBased.hs
@@ -1,6 +1,6 @@
{- git-annex uuid-based logs
-
- - This is used to store information about a UUID in a way that can
+ - This is used to store information about UUIDs in a way that can
- be union merged.
-
- A line of the log will look like: "UUID[ INFO[ timestamp=foo]]"