git-annex/Annex.hs

118 lines
2.7 KiB
Haskell
Raw Normal View History

2010-10-27 20:53:54 +00:00
{- git-annex monad
-
- Copyright 2010 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
2010-10-10 19:04:07 +00:00
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
2010-10-11 21:52:46 +00:00
module Annex (
Annex,
AnnexState(..),
OutputType(..),
2010-10-14 07:18:11 +00:00
new,
run,
2010-11-01 03:24:16 +00:00
eval,
getState,
changeState,
gitRepo
2010-10-11 21:52:46 +00:00
) where
2010-10-10 19:04:07 +00:00
import Control.Monad.State
import Control.Monad.IO.Control
import Control.Applicative hiding (empty)
2010-10-16 20:20:49 +00:00
import qualified Git
2011-06-30 17:25:37 +00:00
import Git.Queue
import Types.Backend
import qualified Types.Remote
import Types.Crypto
import Types.BranchState
import Types.TrustLevel
import Types.UUID
import qualified Utility.Matcher
-- git-annex's monad
newtype Annex a = Annex { runAnnex :: StateT AnnexState IO a }
deriving (
Monad,
MonadIO,
MonadControlIO,
MonadState AnnexState,
Functor,
Applicative
)
-- internal state storage
data AnnexState = AnnexState
{ repo :: Git.Repo
, backends :: [Backend Annex]
, remotes :: [Types.Remote.Remote Annex]
, repoqueue :: Queue
, output :: OutputType
, force :: Bool
, fast :: Bool
, auto :: Bool
, branchstate :: BranchState
, forcebackend :: Maybe String
2011-06-01 20:49:17 +00:00
, forcenumcopies :: Maybe Int
, defaultkey :: Maybe String
, toremote :: Maybe String
, fromremote :: Maybe String
, limit :: Either [Utility.Matcher.Token (FilePath -> Annex Bool)] (Utility.Matcher.Matcher (FilePath -> Annex Bool))
, forcetrust :: [(UUID, TrustLevel)]
, trustmap :: Maybe TrustMap
, cipher :: Maybe Cipher
2011-04-16 20:41:46 +00:00
}
data OutputType = NormalOutput | QuietOutput | JSONOutput
newState :: Git.Repo -> AnnexState
newState gitrepo = AnnexState
{ repo = gitrepo
, backends = []
, remotes = []
, repoqueue = empty
, output = NormalOutput
, force = False
, fast = False
, auto = False
, branchstate = startBranchState
, forcebackend = Nothing
2011-06-01 20:49:17 +00:00
, forcenumcopies = Nothing
, defaultkey = Nothing
, toremote = Nothing
, fromremote = Nothing
, limit = Left []
, forcetrust = []
, trustmap = Nothing
2011-04-16 20:41:46 +00:00
, cipher = Nothing
}
2010-10-14 07:18:11 +00:00
{- Create and returns an Annex state object for the specified git repo. -}
new :: Git.Repo -> IO AnnexState
new gitrepo = newState <$> Git.configRead gitrepo
2010-10-14 07:18:11 +00:00
{- performs an action in the Annex monad -}
2011-01-11 22:13:26 +00:00
run :: AnnexState -> Annex a -> IO (a, AnnexState)
run s a = runStateT (runAnnex a) s
2011-01-11 22:13:26 +00:00
eval :: AnnexState -> Annex a -> IO a
eval s a = evalStateT (runAnnex a) s
2010-10-14 07:18:11 +00:00
{- Gets a value from the internal state, selected by the passed value
- constructor. -}
getState :: (AnnexState -> a) -> Annex a
2011-06-16 22:27:01 +00:00
getState = gets
{- Applies a state mutation function to change the internal state.
-
2011-06-16 22:27:01 +00:00
- Example: changeState $ \s -> s { quiet = True }
-}
changeState :: (AnnexState -> AnnexState) -> Annex ()
2011-06-16 22:27:01 +00:00
changeState = modify
{- Returns the git repository being acted on -}
2010-10-14 07:18:11 +00:00
gitRepo :: Annex Git.Repo
gitRepo = getState repo