successfully split Annex and AnnexState out of TypeInternals

This commit is contained in:
Joey Hess 2011-01-25 21:49:04 -04:00
parent 109a719b03
commit 082b022f9a
12 changed files with 72 additions and 77 deletions

View file

@ -6,18 +6,20 @@
-} -}
module Annex ( module Annex (
Annex,
AnnexState(..),
getState,
new, new,
run, run,
eval, eval,
gitRepo, gitRepo,
gitRepoChange, gitRepoChange,
backends,
backendsChange, backendsChange,
supportedBackends, FlagName,
Flag(..),
flagIsSet, flagIsSet,
flagChange, flagChange,
flagGet, flagGet,
Flag(..),
queue, queue,
queueGet, queueGet,
queueRun, queueRun,
@ -29,19 +31,38 @@ import qualified Data.Map as M
import qualified GitRepo as Git import qualified GitRepo as Git
import qualified GitQueue import qualified GitQueue
import Types import qualified TypeInternals
import qualified TypeInternals as Internals
-- git-annex's monad
type Annex = StateT AnnexState IO
-- internal state storage
data AnnexState = AnnexState {
repo :: Git.Repo,
backends :: [TypeInternals.Backend Annex],
supportedBackends :: [TypeInternals.Backend Annex],
flags :: M.Map FlagName Flag,
repoqueue :: GitQueue.Queue,
quiet :: Bool
} deriving (Show)
-- command-line flags
type FlagName = String
data Flag =
FlagBool Bool |
FlagString String
deriving (Eq, Read, Show)
{- Create and returns an Annex state object for the specified git repo. -} {- Create and returns an Annex state object for the specified git repo. -}
new :: Git.Repo -> [Backend Annex] -> IO AnnexState new :: Git.Repo -> [TypeInternals.Backend Annex] -> IO AnnexState
new gitrepo allbackends = do new gitrepo allbackends = do
let s = Internals.AnnexState { let s = AnnexState {
Internals.repo = gitrepo, repo = gitrepo,
Internals.backends = [], backends = [],
Internals.supportedBackends = allbackends, supportedBackends = allbackends,
Internals.flags = M.empty, flags = M.empty,
Internals.repoqueue = GitQueue.empty, repoqueue = GitQueue.empty,
Internals.quiet = False quiet = False
} }
(_,s') <- Annex.run s prep (_,s') <- Annex.run s prep
return s' return s'
@ -57,41 +78,33 @@ run state action = runStateT action state
eval :: AnnexState -> Annex a -> IO a eval :: AnnexState -> Annex a -> IO a
eval state action = evalStateT action state eval state action = evalStateT action state
{- gets a value from the internal Annex state -}
getState :: (AnnexState -> a) -> Annex a
getState a = do
state <- get
return (a state)
{- Returns the git repository being acted on -} {- Returns the git repository being acted on -}
gitRepo :: Annex Git.Repo gitRepo :: Annex Git.Repo
gitRepo = do gitRepo = getState repo
state <- get
return (Internals.repo state)
{- Changes the git repository being acted on. -} {- Changes the git repository being acted on. -}
gitRepoChange :: Git.Repo -> Annex () gitRepoChange :: Git.Repo -> Annex ()
gitRepoChange r = do gitRepoChange r = do
state <- get state <- get
put state { Internals.repo = r } put state { repo = r }
{- Returns the backends being used. -}
backends :: Annex [Backend Annex]
backends = do
state <- get
return (Internals.backends state)
{- Sets the backends to use. -} {- Sets the backends to use. -}
backendsChange :: [Backend Annex] -> Annex () backendsChange :: [TypeInternals.Backend Annex] -> Annex ()
backendsChange b = do backendsChange b = do
state <- get state <- get
put state { Internals.backends = b } put state { backends = b }
{- Returns the full list of supported backends. -}
supportedBackends :: Annex [Backend Annex]
supportedBackends = do
state <- get
return (Internals.supportedBackends state)
{- Return True if a Bool flag is set. -} {- Return True if a Bool flag is set. -}
flagIsSet :: FlagName -> Annex Bool flagIsSet :: FlagName -> Annex Bool
flagIsSet name = do flagIsSet name = do
state <- get state <- get
case (M.lookup name $ Internals.flags state) of case (M.lookup name $ flags state) of
Just (FlagBool True) -> return True Just (FlagBool True) -> return True
_ -> return False _ -> return False
@ -99,13 +112,13 @@ flagIsSet name = do
flagChange :: FlagName -> Flag -> Annex () flagChange :: FlagName -> Flag -> Annex ()
flagChange name val = do flagChange name val = do
state <- get state <- get
put state { Internals.flags = M.insert name val $ Internals.flags state } put state { flags = M.insert name val $ flags state }
{- Gets the value of a String flag (or "" if there is no such String flag) -} {- Gets the value of a String flag (or "" if there is no such String flag) -}
flagGet :: FlagName -> Annex String flagGet :: FlagName -> Annex String
flagGet name = do flagGet name = do
state <- get state <- get
case (M.lookup name $ Internals.flags state) of case (M.lookup name $ flags state) of
Just (FlagString s) -> return s Just (FlagString s) -> return s
_ -> return "" _ -> return ""
@ -113,23 +126,23 @@ flagGet name = do
queue :: String -> [String] -> FilePath -> Annex () queue :: String -> [String] -> FilePath -> Annex ()
queue command params file = do queue command params file = do
state <- get state <- get
let q = Internals.repoqueue state let q = repoqueue state
put state { Internals.repoqueue = GitQueue.add q command params file } put state { repoqueue = GitQueue.add q command params file }
{- Returns the queue. -} {- Returns the queue. -}
queueGet :: Annex GitQueue.Queue queueGet :: Annex GitQueue.Queue
queueGet = do queueGet = do
state <- get state <- get
return (Internals.repoqueue state) return (repoqueue state)
{- Runs (and empties) the queue. -} {- Runs (and empties) the queue. -}
queueRun :: Annex () queueRun :: Annex ()
queueRun = do queueRun = do
state <- get state <- get
let q = Internals.repoqueue state let q = repoqueue state
g <- gitRepo g <- gitRepo
liftIO $ GitQueue.run g q liftIO $ GitQueue.run g q
put state { Internals.repoqueue = GitQueue.empty } put state { repoqueue = GitQueue.empty }
{- Changes a git config setting in both internal state and .git/config -} {- Changes a git config setting in both internal state and .git/config -}
setConfig :: String -> String -> Annex () setConfig :: String -> String -> Annex ()

View file

@ -44,11 +44,11 @@ import Messages
{- List of backends in the order to try them when storing a new key. -} {- List of backends in the order to try them when storing a new key. -}
list :: Annex [Backend Annex] list :: Annex [Backend Annex]
list = do list = do
l <- Annex.backends -- list is cached here l <- Annex.getState Annex.backends -- list is cached here
if not $ null l if not $ null l
then return l then return l
else do else do
bs <- Annex.supportedBackends bs <- Annex.getState Annex.supportedBackends
g <- Annex.gitRepo g <- Annex.gitRepo
let defaults = parseBackendList bs $ Git.configGet g "annex.backends" "" let defaults = parseBackendList bs $ Git.configGet g "annex.backends" ""
backendflag <- Annex.flagGet "backend" backendflag <- Annex.flagGet "backend"
@ -121,7 +121,7 @@ fsckKey backend key numcopies = (Internals.fsckKey backend) key numcopies
- by examining what the file symlinks to. -} - by examining what the file symlinks to. -}
lookupFile :: FilePath -> Annex (Maybe (Key, Backend Annex)) lookupFile :: FilePath -> Annex (Maybe (Key, Backend Annex))
lookupFile file = do lookupFile file = do
bs <- Annex.supportedBackends bs <- Annex.getState Annex.supportedBackends
tl <- liftIO $ try getsymlink tl <- liftIO $ try getsymlink
case tl of case tl of
Left _ -> return Nothing Left _ -> return Nothing
@ -150,12 +150,12 @@ lookupFile file = do
chooseBackends :: [FilePath] -> Annex [(FilePath, Maybe (Backend Annex))] chooseBackends :: [FilePath] -> Annex [(FilePath, Maybe (Backend Annex))]
chooseBackends fs = do chooseBackends fs = do
g <- Annex.gitRepo g <- Annex.gitRepo
bs <- Annex.supportedBackends bs <- Annex.getState Annex.supportedBackends
pairs <- liftIO $ Git.checkAttr g "annex.backend" fs pairs <- liftIO $ Git.checkAttr g "annex.backend" fs
return $ map (\(f,b) -> (f, maybeLookupBackendName bs b)) pairs return $ map (\(f,b) -> (f, maybeLookupBackendName bs b)) pairs
{- Returns the backend to use for a key. -} {- Returns the backend to use for a key. -}
keyBackend :: Key -> Annex (Backend Annex) keyBackend :: Key -> Annex (Backend Annex)
keyBackend key = do keyBackend key = do
bs <- Annex.supportedBackends bs <- Annex.getState Annex.supportedBackends
return $ lookupBackendName bs $ backendName key return $ lookupBackendName bs $ backendName key

View file

@ -24,6 +24,7 @@ import qualified Remotes
import qualified GitRepo as Git import qualified GitRepo as Git
import Content import Content
import qualified Annex import qualified Annex
import Types
import UUID import UUID
import Messages import Messages

View file

@ -19,6 +19,7 @@ import Messages
import qualified Annex import qualified Annex
import Locations import Locations
import Content import Content
import Types
backend :: Backend Annex backend :: Backend Annex
backend = Backend.File.backend { backend = Backend.File.backend {

View file

@ -10,6 +10,7 @@ module Backend.URL (backend) where
import Control.Monad.State (liftIO) import Control.Monad.State (liftIO)
import Data.String.Utils import Data.String.Utils
import Types
import TypeInternals import TypeInternals
import Utility import Utility
import Messages import Messages

View file

@ -20,6 +20,7 @@ import Locations
import qualified Annex import qualified Annex
import Content import Content
import Messages import Messages
import Types
backend :: Backend Annex backend :: Backend Annex
backend = Backend.File.backend { backend = Backend.File.backend {

View file

@ -78,9 +78,9 @@ usage header cmds options =
- (but explicitly thrown errors terminate the whole command). - (but explicitly thrown errors terminate the whole command).
- Runs shutdown and propigates an overall error status at the end. - Runs shutdown and propigates an overall error status at the end.
-} -}
tryRun :: AnnexState -> [Annex Bool] -> IO () tryRun :: Annex.AnnexState -> [Annex Bool] -> IO ()
tryRun state actions = tryRun' state 0 actions tryRun state actions = tryRun' state 0 actions
tryRun' :: AnnexState -> Integer -> [Annex Bool] -> IO () tryRun' :: Annex.AnnexState -> Integer -> [Annex Bool] -> IO ()
tryRun' state errnum (a:as) = do tryRun' state errnum (a:as) = do
result <- try $ Annex.run state a result <- try $ Annex.run state a
case result of case result of

View file

@ -18,10 +18,10 @@ import Command
-} -}
type Option = OptDescr (Annex ()) type Option = OptDescr (Annex ())
storeOptBool :: FlagName -> Bool -> Annex () storeOptBool :: Annex.FlagName -> Bool -> Annex ()
storeOptBool name val = Annex.flagChange name $ FlagBool val storeOptBool name val = Annex.flagChange name $ Annex.FlagBool val
storeOptString :: FlagName -> String -> Annex () storeOptString :: Annex.FlagName -> String -> Annex ()
storeOptString name val = Annex.flagChange name $ FlagString val storeOptString name val = Annex.flagChange name $ Annex.FlagString val
commonOptions :: [Option] commonOptions :: [Option]
commonOptions = commonOptions =

View file

@ -105,7 +105,7 @@ readConfigs = do
let todo = cheap ++ doexpensive let todo = cheap ++ doexpensive
unless (null todo) $ do unless (null todo) $ do
_ <- mapM tryGitConfigRead todo _ <- mapM tryGitConfigRead todo
Annex.flagChange "remotesread" $ FlagBool True Annex.flagChange "remotesread" $ Annex.FlagBool True
where where
cachedUUID r = do cachedUUID r = do
u <- getUUID r u <- getUUID r

View file

@ -17,27 +17,6 @@ import Test.QuickCheck
import qualified GitRepo as Git import qualified GitRepo as Git
import qualified GitQueue import qualified GitQueue
-- command-line flags
type FlagName = String
data Flag =
FlagBool Bool |
FlagString String
deriving (Eq, Read, Show)
-- git-annex's runtime state type doesn't really belong here,
-- but it uses Backend, so has to be here to avoid a depends loop.
data AnnexState = AnnexState {
repo :: Git.Repo,
backends :: [Backend Annex],
supportedBackends :: [Backend Annex],
flags :: M.Map FlagName Flag,
repoqueue :: GitQueue.Queue,
quiet :: Bool
} deriving (Show)
-- git-annex's monad
type Annex = StateT AnnexState IO
-- annexed filenames are mapped through a backend into keys -- annexed filenames are mapped through a backend into keys
type KeyName = String type KeyName = String
type BackendName = String type BackendName = String

View file

@ -7,14 +7,12 @@
module Types ( module Types (
Annex, Annex,
AnnexState,
Backend, Backend,
Key, Key,
genKey, genKey,
backendName, backendName,
keyName, keyName
FlagName,
Flag(..)
) where ) where
import TypeInternals import TypeInternals
import Annex

View file

@ -28,6 +28,7 @@ import qualified GitRepo as Git
import qualified Locations import qualified Locations
import qualified Utility import qualified Utility
import qualified TypeInternals import qualified TypeInternals
import qualified Types
import qualified GitAnnex import qualified GitAnnex
import qualified LocationLog import qualified LocationLog
import qualified UUID import qualified UUID
@ -416,7 +417,7 @@ git_annex command params = do
-- Runs an action in the current annex. Note that shutdown actions -- Runs an action in the current annex. Note that shutdown actions
-- are not run; this should only be used for actions that query state. -- are not run; this should only be used for actions that query state.
annexeval :: TypeInternals.Annex a -> IO a annexeval :: Types.Annex a -> IO a
annexeval a = do annexeval a = do
g <- Git.repoFromCwd g <- Git.repoFromCwd
g' <- Git.configRead g g' <- Git.configRead g