split out Types.Import and some changes to the types in it
This commit is contained in:
parent
936aee6a60
commit
fd304dce60
6 changed files with 50 additions and 24 deletions
|
@ -29,7 +29,7 @@ import qualified Database.Queue as H
|
|||
import Database.Init
|
||||
import Annex.Locations
|
||||
import Annex.Common hiding (delete)
|
||||
import Types.Remote (ContentIdentifier(..))
|
||||
import Types.Import
|
||||
|
||||
import Database.Persist.Sql hiding (Key)
|
||||
import Database.Persist.TH
|
||||
|
|
|
@ -23,7 +23,7 @@ import Key
|
|||
import Utility.InodeCache
|
||||
import Git.Types (Ref(..))
|
||||
import Types.UUID
|
||||
import Types.Remote (ContentIdentifier(..))
|
||||
import Types.Import
|
||||
|
||||
-- A serialized Key
|
||||
newtype SKey = SKey String
|
||||
|
|
|
@ -52,7 +52,7 @@ instance HasImportUnsupported (RemoteConfig -> RemoteGitConfig -> Annex Bool) wh
|
|||
|
||||
instance HasImportUnsupported (ImportActions Annex) where
|
||||
importUnsupported = ImportActions
|
||||
{ listContents = return Nothing
|
||||
{ listImportableContents = return Nothing
|
||||
, retrieveExportWithContentIdentifier = \_ _ _ _ -> return Nothing
|
||||
, storeExportWithContentIdentifier = \_ _ _ _ _ -> return Nothing
|
||||
}
|
||||
|
|
43
Types/Import.hs
Normal file
43
Types/Import.hs
Normal file
|
@ -0,0 +1,43 @@
|
|||
{- git-annex import types
|
||||
-
|
||||
- Copyright 2019 Joey Hess <id@joeyh.name>
|
||||
-
|
||||
- Licensed under the GNU GPL version 3 or higher.
|
||||
-}
|
||||
|
||||
module Types.Import where
|
||||
|
||||
import qualified Data.ByteString as S
|
||||
import Data.Char
|
||||
|
||||
import Types.Export
|
||||
import Utility.QuickCheck
|
||||
import Utility.FileSystemEncoding
|
||||
|
||||
{- Location of content on a remote that can be imported.
|
||||
- This is just an alias to ExportLocation, because both are referring to a
|
||||
- location on the remote. -}
|
||||
type ImportLocation = ExportLocation
|
||||
|
||||
{- An identifier for content stored on a remote that has been imported into
|
||||
- the repository. It should be reasonably short since it is stored in the
|
||||
- git-annex branch. -}
|
||||
newtype ContentIdentifier = ContentIdentifier S.ByteString
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
instance Arbitrary ContentIdentifier where
|
||||
-- Avoid non-ascii ContentIdentifiers because fully arbitrary
|
||||
-- strings may not be encoded using the filesystem
|
||||
-- encoding, which is normally applied to all input.
|
||||
arbitrary = ContentIdentifier . encodeBS
|
||||
<$> arbitrary `suchThat` all isAscii
|
||||
|
||||
{- List of files that can be imported from a remote. -}
|
||||
data ImportableContents = ImportableContents
|
||||
{ importableContents :: [(ImportLocation, ContentIdentifier)]
|
||||
, importableHistory :: [ImportableContents]
|
||||
-- ^ Used by remotes that support importing historical versions of
|
||||
-- files that are stored in them. This is equivilant to a git
|
||||
-- commit history.
|
||||
}
|
||||
deriving (Show)
|
|
@ -21,14 +21,11 @@ module Types.Remote
|
|||
, RetrievalSecurityPolicy(..)
|
||||
, isExportSupported
|
||||
, ExportActions(..)
|
||||
, ContentIdentifier(..)
|
||||
, ContentHistory(..)
|
||||
, ImportActions(..)
|
||||
)
|
||||
where
|
||||
|
||||
import qualified Data.Map as M
|
||||
import qualified Data.ByteString as S
|
||||
import Data.Ord
|
||||
|
||||
import qualified Git
|
||||
|
@ -40,12 +37,12 @@ import Types.Creds
|
|||
import Types.UrlContents
|
||||
import Types.NumCopies
|
||||
import Types.Export
|
||||
import Types.Import
|
||||
import Config.Cost
|
||||
import Utility.Metered
|
||||
import Git.Types (RemoteName)
|
||||
import Utility.SafeCommand
|
||||
import Utility.Url
|
||||
import Utility.QuickCheck
|
||||
|
||||
type RemoteConfigKey = String
|
||||
|
||||
|
@ -244,28 +241,13 @@ data ExportActions a = ExportActions
|
|||
, renameExport :: Key -> ExportLocation -> ExportLocation -> a Bool
|
||||
}
|
||||
|
||||
{- An identifier for content stored on a remote. It should be reasonably
|
||||
- short since it is stored in the git-annex branch. -}
|
||||
newtype ContentIdentifier = ContentIdentifier S.ByteString
|
||||
deriving (Eq, Ord, Show, Arbitrary)
|
||||
|
||||
{- Some remotes may support importing a history of versions of content that
|
||||
- is stored in them. This is equivilant to a git commit history. -}
|
||||
data ContentHistory t
|
||||
= ContentHistoryNode t
|
||||
| ContentHistory
|
||||
{ contentHistoryCurrent :: t
|
||||
, contentHistoryPrev :: [ContentHistory t]
|
||||
}
|
||||
deriving (Show)
|
||||
|
||||
data ImportActions a = ImportActions
|
||||
-- Finds the current set of files that are stored in the remote,
|
||||
-- along with their content identifiers.
|
||||
--
|
||||
-- May also find old versions of files that are still stored in the
|
||||
-- remote, and return a ContentHistory with multiple nodes.
|
||||
{ listContents :: a (Maybe (ContentHistory [(ExportLocation, ContentIdentifier)]))
|
||||
-- remote.
|
||||
{ listImportableContents :: a (Maybe ImportableContents)
|
||||
-- Retrieves a file from the remote. Ensures that the file
|
||||
-- it retrieves has the requested ContentIdentifier.
|
||||
--
|
||||
|
|
|
@ -976,6 +976,7 @@ Executable git-annex
|
|||
Types.FileMatcher
|
||||
Types.GitConfig
|
||||
Types.Group
|
||||
Types.Import
|
||||
Types.Key
|
||||
Types.KeySource
|
||||
Types.LockCache
|
||||
|
|
Loading…
Add table
Reference in a new issue