git-annex/Annex.hs

148 lines
3.6 KiB
Haskell
Raw Normal View History

2010-10-27 20:53:54 +00:00
{- git-annex monad
-
2011-11-09 05:15:51 +00:00
- Copyright 2010-2011 Joey Hess <joey@kitenet.net>
2010-10-27 20:53:54 +00:00
-
- Licensed under the GNU GPL version 3 or higher.
-}
2010-10-10 19:04:07 +00:00
{-# LANGUAGE GeneralizedNewtypeDeriving, TypeFamilies, MultiParamTypeClasses #-}
2010-10-11 21:52:46 +00:00
module Annex (
Annex,
AnnexState(..),
OutputType(..),
2010-10-14 07:18:11 +00:00
new,
newState,
2010-10-14 07:18:11 +00:00
run,
2010-11-01 03:24:16 +00:00
eval,
getState,
changeState,
gitRepo,
inRepo,
fromRepo,
2010-10-11 21:52:46 +00:00
) where
2010-10-10 19:04:07 +00:00
import Control.Monad.State
import Control.Monad.Trans.Control (StM, MonadBaseControl, liftBaseWith, restoreM)
import Control.Monad.Base (liftBase, MonadBase)
2010-10-16 20:20:49 +00:00
import Common
import qualified Git
import qualified Git.Config
import Git.CatFile
2011-12-20 18:37:53 +00:00
import qualified 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
import qualified Utility.Format
import qualified Data.Map as M
-- git-annex's monad
newtype Annex a = Annex { runAnnex :: StateT AnnexState IO a }
deriving (
Monad,
MonadIO,
MonadState AnnexState,
Functor,
Applicative
)
instance MonadBase IO Annex where
liftBase = Annex . liftBase
instance MonadBaseControl IO Annex where
newtype StM Annex a = StAnnex (StM (StateT AnnexState IO) a)
liftBaseWith f = Annex $ liftBaseWith $ \runInIO ->
f $ liftM StAnnex . runInIO . runAnnex
restoreM = Annex . restoreM . unStAnnex
where
unStAnnex (StAnnex st) = st
2011-11-09 05:15:51 +00:00
data OutputType = NormalOutput | QuietOutput | JSONOutput
2011-12-31 08:19:10 +00:00
type Matcher a = Either [Utility.Matcher.Token a] (Utility.Matcher.Matcher a)
-- internal state storage
data AnnexState = AnnexState
{ repo :: Git.Repo
2011-12-31 08:11:39 +00:00
, backends :: [BackendA Annex]
, remotes :: [Types.Remote.RemoteA Annex]
2011-12-20 18:37:53 +00:00
, repoqueue :: Git.Queue.Queue
, output :: OutputType
, force :: Bool
, fast :: Bool
, auto :: Bool
, format :: Maybe Utility.Format.Format
, branchstate :: BranchState
, catfilehandle :: Maybe CatFileHandle
, forcebackend :: Maybe String
2011-06-01 20:49:17 +00:00
, forcenumcopies :: Maybe Int
, toremote :: Maybe String
, fromremote :: Maybe String
2011-12-31 08:19:10 +00:00
, limit :: Matcher (FilePath -> Annex Bool)
, forcetrust :: [(UUID, TrustLevel)]
, trustmap :: Maybe TrustMap
, ciphers :: M.Map EncryptedCipher Cipher
2011-04-16 20:41:46 +00:00
}
newState :: Git.Repo -> AnnexState
newState gitrepo = AnnexState
{ repo = gitrepo
, backends = []
, remotes = []
2011-12-20 18:37:53 +00:00
, repoqueue = Git.Queue.new
, output = NormalOutput
, force = False
, fast = False
, auto = False
, format = Nothing
, branchstate = startBranchState
, catfilehandle = Nothing
, forcebackend = Nothing
2011-06-01 20:49:17 +00:00
, forcenumcopies = Nothing
, toremote = Nothing
, fromremote = Nothing
, limit = Left []
, forcetrust = []
, trustmap = Nothing
, ciphers = M.empty
}
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.Config.read 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-12-20 20:03:09 +00:00
- Example: changeState $ \s -> s { output = QuietOutput }
-}
changeState :: (AnnexState -> AnnexState) -> Annex ()
2011-06-16 22:27:01 +00:00
changeState = modify
{- Returns the annex's git repository. -}
2010-10-14 07:18:11 +00:00
gitRepo :: Annex Git.Repo
gitRepo = getState repo
{- Runs an IO action in the annex's git repository. -}
inRepo :: (Git.Repo -> IO a) -> Annex a
2011-11-12 18:24:07 +00:00
inRepo a = liftIO . a =<< gitRepo
{- Extracts a value from the annex's git repisitory. -}
fromRepo :: (Git.Repo -> a) -> Annex a
fromRepo a = a <$> gitRepo