rename modules for data types into Types/ directory
This commit is contained in:
parent
971ab27e78
commit
703c437bd9
32 changed files with 61 additions and 59 deletions
41
Types/Backend.hs
Normal file
41
Types/Backend.hs
Normal file
|
@ -0,0 +1,41 @@
|
|||
{- git-annex key/value backend data type
|
||||
-
|
||||
- Most things should not need this, using Types instead
|
||||
-
|
||||
- Copyright 2010 Joey Hess <joey@kitenet.net>
|
||||
-
|
||||
- Licensed under the GNU GPL version 3 or higher.
|
||||
-}
|
||||
|
||||
module Types.Backend where
|
||||
|
||||
import Types.Key
|
||||
|
||||
data Backend a = Backend {
|
||||
-- name of this backend
|
||||
name :: String,
|
||||
-- converts a filename to a key
|
||||
getKey :: FilePath -> a (Maybe Key),
|
||||
-- stores a file's contents to a key
|
||||
storeFileKey :: FilePath -> Key -> a Bool,
|
||||
-- retrieves a key's contents to a file
|
||||
retrieveKeyFile :: Key -> FilePath -> a Bool,
|
||||
-- removes a key, optionally checking that enough copies are stored
|
||||
-- elsewhere
|
||||
removeKey :: Key -> Maybe Int -> a Bool,
|
||||
-- checks if a backend is storing the content of a key
|
||||
hasKey :: Key -> a Bool,
|
||||
-- called during fsck to check a key
|
||||
-- (second parameter may be the filename associated with it)
|
||||
-- (third parameter may be the number of copies that there should
|
||||
-- be of the key)
|
||||
fsckKey :: Key -> Maybe FilePath -> Maybe Int -> a Bool,
|
||||
-- Is a newer repesentation possible for a key?
|
||||
upgradableKey :: Key -> a Bool
|
||||
}
|
||||
|
||||
instance Show (Backend a) where
|
||||
show backend = "Backend { name =\"" ++ name backend ++ "\" }"
|
||||
|
||||
instance Eq (Backend a) where
|
||||
a == b = name a == name b
|
23
Types/Crypto.hs
Normal file
23
Types/Crypto.hs
Normal file
|
@ -0,0 +1,23 @@
|
|||
{- git-annex crypto types
|
||||
-
|
||||
- Copyright 2011 Joey Hess <joey@kitenet.net>
|
||||
-
|
||||
- Licensed under the GNU GPL version 3 or higher.
|
||||
-}
|
||||
|
||||
module Types.Crypto where
|
||||
|
||||
import Data.String.Utils
|
||||
|
||||
-- XXX ideally, this would be a locked memory region
|
||||
newtype Cipher = Cipher String
|
||||
|
||||
data EncryptedCipher = EncryptedCipher String KeyIds
|
||||
|
||||
newtype KeyIds = KeyIds [String]
|
||||
|
||||
instance Show KeyIds where
|
||||
show (KeyIds ks) = join "," ks
|
||||
|
||||
instance Read KeyIds where
|
||||
readsPrec _ s = [(KeyIds (split "," s), "")]
|
76
Types/Key.hs
Normal file
76
Types/Key.hs
Normal file
|
@ -0,0 +1,76 @@
|
|||
{- git-annex Key data type
|
||||
-
|
||||
- Most things should not need this, using Types instead
|
||||
-
|
||||
- Copyright 2011 Joey Hess <joey@kitenet.net>
|
||||
-
|
||||
- Licensed under the GNU GPL version 3 or higher.
|
||||
-}
|
||||
|
||||
module Types.Key (
|
||||
Key(..),
|
||||
stubKey,
|
||||
readKey,
|
||||
|
||||
prop_idempotent_key_read_show
|
||||
) where
|
||||
|
||||
import Utility
|
||||
import System.Posix.Types
|
||||
|
||||
{- A Key has a unique name, is associated with a key/value backend,
|
||||
- and may contain other optional metadata. -}
|
||||
data Key = Key {
|
||||
keyName :: String,
|
||||
keyBackendName :: String,
|
||||
keySize :: Maybe Integer,
|
||||
keyMtime :: Maybe EpochTime
|
||||
} deriving (Eq, Ord)
|
||||
|
||||
stubKey :: Key
|
||||
stubKey = Key {
|
||||
keyName = "",
|
||||
keyBackendName = "",
|
||||
keySize = Nothing,
|
||||
keyMtime = Nothing
|
||||
}
|
||||
|
||||
fieldSep :: Char
|
||||
fieldSep = '-'
|
||||
|
||||
{- Keys show as strings that are suitable for use as filenames.
|
||||
- The name field is always shown last, separated by doubled fieldSeps,
|
||||
- and is the only field allowed to contain the fieldSep. -}
|
||||
instance Show Key where
|
||||
show Key { keyBackendName = b, keySize = s, keyMtime = m, keyName = n } =
|
||||
b +++ ('s' ?: s) +++ ('m' ?: m) +++ (fieldSep : n)
|
||||
where
|
||||
"" +++ y = y
|
||||
x +++ "" = x
|
||||
x +++ y = x ++ fieldSep:y
|
||||
c ?: (Just v) = c:(show v)
|
||||
_ ?: _ = ""
|
||||
|
||||
readKey :: String -> Maybe Key
|
||||
readKey s = if key == Just stubKey then Nothing else key
|
||||
where
|
||||
key = startbackend stubKey s
|
||||
|
||||
startbackend k v = sepfield k v addbackend
|
||||
|
||||
sepfield k v a = case span (/= fieldSep) v of
|
||||
(v', _:r) -> findfields r $ a k v'
|
||||
_ -> Nothing
|
||||
|
||||
findfields (c:v) (Just k)
|
||||
| c == fieldSep = Just $ k { keyName = v }
|
||||
| otherwise = sepfield k v $ addfield c
|
||||
findfields _ v = v
|
||||
|
||||
addbackend k v = Just k { keyBackendName = v }
|
||||
addfield 's' k v = Just k { keySize = readMaybe v }
|
||||
addfield 'm' k v = Just k { keyMtime = readMaybe v }
|
||||
addfield _ _ _ = Nothing
|
||||
|
||||
prop_idempotent_key_read_show :: Key -> Bool
|
||||
prop_idempotent_key_read_show k = Just k == (readKey $ show k)
|
65
Types/Remote.hs
Normal file
65
Types/Remote.hs
Normal file
|
@ -0,0 +1,65 @@
|
|||
{- git-annex remotes types
|
||||
-
|
||||
- Most things should not need this, using Remote instead
|
||||
-
|
||||
- Copyright 2011 Joey Hess <joey@kitenet.net>
|
||||
-
|
||||
- Licensed under the GNU GPL version 3 or higher.
|
||||
-}
|
||||
|
||||
module Types.Remote where
|
||||
|
||||
import Control.Exception
|
||||
import Data.Map as M
|
||||
|
||||
import qualified GitRepo as Git
|
||||
import Types.Key
|
||||
|
||||
type RemoteConfig = M.Map String String
|
||||
|
||||
{- There are different types of remotes. -}
|
||||
data RemoteType a = RemoteType {
|
||||
-- human visible type name
|
||||
typename :: String,
|
||||
-- enumerates remotes of this type
|
||||
enumerate :: a [Git.Repo],
|
||||
-- generates a remote of this type
|
||||
generate :: Git.Repo -> String -> Maybe RemoteConfig -> a (Remote a),
|
||||
-- initializes or changes a remote
|
||||
setup :: String -> RemoteConfig -> a RemoteConfig
|
||||
}
|
||||
|
||||
{- An individual remote. -}
|
||||
data Remote a = Remote {
|
||||
-- each Remote has a unique uuid
|
||||
uuid :: String,
|
||||
-- each Remote has a human visible name
|
||||
name :: String,
|
||||
-- Remotes have a use cost; higher is more expensive
|
||||
cost :: Int,
|
||||
-- Transfers a key to the remote.
|
||||
storeKey :: Key -> a Bool,
|
||||
-- retrieves a key's contents to a file
|
||||
retrieveKeyFile :: Key -> FilePath -> a Bool,
|
||||
-- removes a key's contents
|
||||
removeKey :: Key -> a Bool,
|
||||
-- Checks if a key is present in the remote; if the remote
|
||||
-- cannot be accessed returns a Left error.
|
||||
hasKey :: Key -> a (Either IOException Bool),
|
||||
-- Some remotes can check hasKey without an expensive network
|
||||
-- operation.
|
||||
hasKeyCheap :: Bool,
|
||||
-- a Remote can have a persistent configuration store
|
||||
config :: Maybe RemoteConfig
|
||||
}
|
||||
|
||||
instance Show (Remote a) where
|
||||
show remote = "Remote { name =\"" ++ name remote ++ "\" }"
|
||||
|
||||
-- two remotes are the same if they have the same uuid
|
||||
instance Eq (Remote a) where
|
||||
x == y = uuid x == uuid y
|
||||
|
||||
-- order remotes by cost
|
||||
instance Ord (Remote a) where
|
||||
compare x y = compare (cost x) (cost y)
|
11
Types/UUID.hs
Normal file
11
Types/UUID.hs
Normal file
|
@ -0,0 +1,11 @@
|
|||
{- git-annex UUID type
|
||||
-
|
||||
- Copyright 2011 Joey Hess <joey@kitenet.net>
|
||||
-
|
||||
- Licensed under the GNU GPL version 3 or higher.
|
||||
-}
|
||||
|
||||
module Types.UUID where
|
||||
|
||||
-- might be nice to have a newtype, but lots of stuff treats uuids as strings
|
||||
type UUID = String
|
Loading…
Add table
Add a link
Reference in a new issue