aboutsummaryrefslogtreecommitdiff
path: root/Types
diff options
context:
space:
mode:
authorGravatar Joey Hess <joeyh@joeyh.name>2016-08-03 12:37:12 -0400
committerGravatar Joey Hess <joeyh@joeyh.name>2016-08-03 12:37:12 -0400
commit508517de485e77196a8d8e33558f4185c50dea96 (patch)
tree319fc6e63da144e40dd124a07f4bb6c0ad25c5ee /Types
parent019733f00d01301d71acc46245d2dc130934d951 (diff)
get, move, copy, mirror: Added --failed switch which retries failed copies/moves
Note that get --from foo --failed will get things that a previous get --from bar tried and failed to get, etc. I considered making --failed only retry transfers from the same remote, but it was easier, and seems more useful, to not have the same remote requirement. Noisy due to some refactoring into Types/
Diffstat (limited to 'Types')
-rw-r--r--Types/ActionItem.hs54
-rw-r--r--Types/Transfer.hs47
2 files changed, 101 insertions, 0 deletions
diff --git a/Types/ActionItem.hs b/Types/ActionItem.hs
new file mode 100644
index 000000000..a0097e45a
--- /dev/null
+++ b/Types/ActionItem.hs
@@ -0,0 +1,54 @@
+{- items that a command can act on
+ -
+ - Copyright 2016 Joey Hess <id@joeyh.name>
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-}
+
+module Types.ActionItem where
+
+import Types.Key
+import Types.Transfer
+import Git.FilePath
+
+import Data.Maybe
+
+data ActionItem
+ = ActionItemAssociatedFile AssociatedFile
+ | ActionItemKey
+ | ActionItemBranchFilePath BranchFilePath
+ | ActionItemFailedTransfer Transfer TransferInfo
+
+class MkActionItem t where
+ mkActionItem :: t -> ActionItem
+
+instance MkActionItem AssociatedFile where
+ mkActionItem = ActionItemAssociatedFile
+
+instance MkActionItem Key where
+ mkActionItem _ = ActionItemKey
+
+instance MkActionItem BranchFilePath where
+ mkActionItem = ActionItemBranchFilePath
+
+instance MkActionItem (Transfer, TransferInfo) where
+ mkActionItem = uncurry ActionItemFailedTransfer
+
+actionItemDesc :: ActionItem -> Key -> String
+actionItemDesc (ActionItemAssociatedFile (Just f)) _ = f
+actionItemDesc (ActionItemAssociatedFile Nothing) k = key2file k
+actionItemDesc ActionItemKey k = key2file k
+actionItemDesc (ActionItemBranchFilePath bfp) _ = descBranchFilePath bfp
+actionItemDesc (ActionItemFailedTransfer _ i) k =
+ fromMaybe (key2file k) (associatedFile i)
+
+actionItemWorkTreeFile :: ActionItem -> Maybe FilePath
+actionItemWorkTreeFile (ActionItemAssociatedFile af) = af
+actionItemWorkTreeFile _ = Nothing
+
+actionItemTransferDirection :: ActionItem -> Maybe Direction
+actionItemTransferDirection (ActionItemFailedTransfer t _) = Just $
+ transferDirection t
+actionItemTransferDirection _ = Nothing
diff --git a/Types/Transfer.hs b/Types/Transfer.hs
new file mode 100644
index 000000000..528d1d5cb
--- /dev/null
+++ b/Types/Transfer.hs
@@ -0,0 +1,47 @@
+{- git-annex transfer types
+ -
+ - Copyright 2012 Joey Hess <id@joeyh.name>
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+module Types.Transfer where
+
+import Types
+import Utility.PID
+
+import Data.Time.Clock.POSIX
+import Control.Concurrent
+
+{- Enough information to uniquely identify a transfer, used as the filename
+ - of the transfer information file. -}
+data Transfer = Transfer
+ { transferDirection :: Direction
+ , transferUUID :: UUID
+ , transferKey :: Key
+ }
+ deriving (Eq, Ord, Read, Show)
+
+{- Information about a Transfer, stored in the transfer information file.
+ -
+ - Note that the associatedFile may not correspond to a file in the local
+ - git repository. It's some file, possibly relative to some directory,
+ - of some repository, that was acted on to initiate the transfer.
+ -}
+data TransferInfo = TransferInfo
+ { startedTime :: Maybe POSIXTime
+ , transferPid :: Maybe PID
+ , transferTid :: Maybe ThreadId
+ , transferRemote :: Maybe Remote
+ , bytesComplete :: Maybe Integer
+ , associatedFile :: Maybe FilePath
+ , transferPaused :: Bool
+ }
+ deriving (Show, Eq, Ord)
+
+stubTransferInfo :: TransferInfo
+stubTransferInfo = TransferInfo Nothing Nothing Nothing Nothing Nothing Nothing False
+
+data Direction = Upload | Download
+ deriving (Eq, Ord, Read, Show)
+