aboutsummaryrefslogtreecommitdiff
path: root/Types
diff options
context:
space:
mode:
authorGravatar Joey Hess <joeyh@joeyh.name>2017-09-15 16:34:45 -0400
committerGravatar Joey Hess <joeyh@joeyh.name>2017-09-15 16:46:03 -0400
commit15d757049d764410e3d71bbb68640549f86fc543 (patch)
tree8bdff79aa30eb197142899ef82f03cc577f61862 /Types
parent2d3f18876550ee2e37a60aea1c0faaa369606ae0 (diff)
split out Types.Export
Diffstat (limited to 'Types')
-rw-r--r--Types/Export.hs31
-rw-r--r--Types/Remote.hs26
2 files changed, 32 insertions, 25 deletions
diff --git a/Types/Export.hs b/Types/Export.hs
new file mode 100644
index 000000000..cc1b8debf
--- /dev/null
+++ b/Types/Export.hs
@@ -0,0 +1,31 @@
+{- git-annex export types
+ -
+ - Copyright 2017 Joey Hess <id@joeyh.name>
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+module Types.Export where
+
+import qualified System.FilePath.Posix as Posix
+
+-- A location on a remote that a key can be exported to.
+-- The FilePath will be relative to the top of the export,
+-- and may contain unix-style path separators.
+newtype ExportLocation = ExportLocation FilePath
+ deriving (Show, Eq)
+
+newtype ExportDirectory = ExportDirectory FilePath
+ deriving (Show, Eq)
+
+-- | All subdirectories down to the ExportLocation, with the deepest ones
+-- last. Does not include the top of the export.
+exportDirectories :: ExportLocation -> [ExportDirectory]
+exportDirectories (ExportLocation f) =
+ map (ExportDirectory . Posix.joinPath . reverse) (subs [] dirs)
+ where
+ subs _ [] = []
+ subs ps (d:ds) = (d:ps) : subs (d:ps) ds
+
+ dirs = map Posix.dropTrailingPathSeparator $
+ reverse $ drop 1 $ reverse $ Posix.splitPath f
diff --git a/Types/Remote.hs b/Types/Remote.hs
index adec32973..a734be979 100644
--- a/Types/Remote.hs
+++ b/Types/Remote.hs
@@ -18,16 +18,12 @@ module Types.Remote
, Availability(..)
, Verification(..)
, unVerified
- , ExportLocation(..)
- , ExportDirectory(..)
, isExportSupported
, ExportActions(..)
- , exportedDirectories
)
where
import qualified Data.Map as M
-import qualified System.FilePath.Posix as Posix
import Data.Ord
import qualified Git
@@ -38,6 +34,7 @@ import Types.Availability
import Types.Creds
import Types.UrlContents
import Types.NumCopies
+import Types.Export
import Config.Cost
import Utility.Metered
import Git.Types (RemoteName)
@@ -161,15 +158,6 @@ unVerified a = do
ok <- a
return (ok, UnVerified)
--- A location on a remote that a key can be exported to.
--- The FilePath will be relative, and may contain unix-style path
--- separators.
-newtype ExportLocation = ExportLocation FilePath
- deriving (Show, Eq)
-
-newtype ExportDirectory = ExportDirectory FilePath
- deriving (Show, Eq)
-
isExportSupported :: RemoteA a -> a Bool
isExportSupported r = exportSupported (remotetype r) (config r) (gitconfig r)
@@ -200,15 +188,3 @@ data ExportActions a = ExportActions
-- support renames.
, renameExport :: Key -> ExportLocation -> ExportLocation -> a Bool
}
-
--- | All subdirectories down to the ExportLocation, with the deepest ones
--- last. Does not include the top of the export.
-exportedDirectories :: ExportLocation -> [ExportDirectory]
-exportedDirectories (ExportLocation f) =
- map (ExportDirectory . Posix.joinPath . reverse) (subs [] dirs)
- where
- subs _ [] = []
- subs ps (d:ds) = (d:ps) : subs (d:ps) ds
-
- dirs = map Posix.dropTrailingPathSeparator $
- reverse $ drop 1 $ reverse $ Posix.splitPath f