git-annex/Assistant/Monad.hs

145 lines
3.8 KiB
Haskell
Raw Normal View History

{- git-annex assistant monad
-
- Copyright 2012 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
{-# LANGUAGE GeneralizedNewtypeDeriving, MultiParamTypeClasses #-}
{-# LANGUAGE PackageImports #-}
module Assistant.Monad (
Assistant,
AssistantData(..),
newAssistantData,
runAssistant,
getAssistant,
LiftAnnex,
liftAnnex,
(<~>),
(<<~),
asIO,
asIO1,
asIO2,
2013-01-26 03:14:32 +00:00
ThreadName,
debug,
) where
import "mtl" Control.Monad.Reader
import qualified Control.Monad.Fail as Fail
import Annex.Common hiding (debug)
2012-10-29 23:07:10 +00:00
import Assistant.Types.ThreadedMonad
2012-10-30 18:11:14 +00:00
import Assistant.Types.DaemonStatus
2012-10-29 23:14:30 +00:00
import Assistant.Types.ScanRemotes
2012-10-30 18:34:48 +00:00
import Assistant.Types.TransferQueue
import Assistant.Types.TransferSlots
2012-10-29 21:52:43 +00:00
import Assistant.Types.Pushes
2012-10-29 23:20:54 +00:00
import Assistant.Types.BranchChange
2012-10-29 23:35:18 +00:00
import Assistant.Types.Commits
2012-10-29 23:30:23 +00:00
import Assistant.Types.Changes
import Assistant.Types.RepoProblem
import Assistant.Types.ThreadName
import Assistant.Types.RemoteControl
import Assistant.Types.CredPairCache
import qualified Utility.Debug as Debug
2013-01-26 03:14:32 +00:00
newtype Assistant a = Assistant { mkAssistant :: ReaderT AssistantData IO a }
deriving (
Monad,
MonadIO,
MonadReader AssistantData,
MonadCatch,
MonadThrow,
MonadMask,
Fail.MonadFail,
Functor,
Applicative
)
data AssistantData = AssistantData
{ threadName :: ThreadName
, threadState :: ThreadState
, daemonStatusHandle :: DaemonStatusHandle
, scanRemoteMap :: ScanRemoteMap
, transferQueue :: TransferQueue
, transferSlots :: TransferSlots
, failedPushMap :: FailedPushMap
, failedExportMap :: FailedPushMap
, commitChan :: CommitChan
, exportCommitChan :: CommitChan
2013-04-24 20:13:22 +00:00
, changePool :: ChangePool
, repoProblemChan :: RepoProblemChan
, branchChangeHandle :: BranchChangeHandle
, remoteControl :: RemoteControl
, credPairCache :: CredPairCache
}
newAssistantData :: ThreadState -> DaemonStatusHandle -> IO AssistantData
newAssistantData st dstatus = AssistantData
<$> pure (ThreadName "main")
<*> pure st
<*> pure dstatus
<*> newScanRemoteMap
<*> newTransferQueue
<*> newTransferSlots
<*> newFailedPushMap
<*> newFailedPushMap
<*> newCommitChan
<*> newCommitChan
2013-04-24 20:13:22 +00:00
<*> newChangePool
<*> newRepoProblemChan
<*> newBranchChangeHandle
<*> newRemoteControl
<*> newCredPairCache
runAssistant :: AssistantData -> Assistant a -> IO a
runAssistant d a = runReaderT (mkAssistant a) d
getAssistant :: (AssistantData -> a) -> Assistant a
getAssistant = reader
{- Using a type class for lifting into the annex monad allows
- easily lifting to it from multiple different monads. -}
class LiftAnnex m where
liftAnnex :: Annex a -> m a
{- Runs an action in the git-annex monad. Note that the same monad state
2013-12-19 09:57:50 +00:00
- is shared among all assistant threads, so only one of these can run at
- a time. Therefore, long-duration actions should be avoided. -}
instance LiftAnnex Assistant where
liftAnnex a = do
st <- reader threadState
liftIO $ runThreadState st a
{- Runs an IO action, passing it an IO action that runs an Assistant action. -}
(<~>) :: (IO a -> IO b) -> Assistant a -> Assistant b
io <~> a = do
d <- reader id
liftIO $ io $ runAssistant d a
{- Creates an IO action that will run an Assistant action when run. -}
asIO :: Assistant a -> Assistant (IO a)
asIO a = do
d <- reader id
return $ runAssistant d a
asIO1 :: (a -> Assistant b) -> Assistant (a -> IO b)
asIO1 a = do
d <- reader id
return $ \v -> runAssistant d $ a v
asIO2 :: (a -> b -> Assistant c) -> Assistant (a -> b -> IO c)
asIO2 a = do
d <- reader id
return $ \v1 v2 -> runAssistant d (a v1 v2)
{- Runs an IO action on a selected field of the AssistantData. -}
(<<~) :: (a -> IO b) -> (AssistantData -> a) -> Assistant b
io <<~ v = reader v >>= liftIO . io
2013-01-26 03:14:32 +00:00
debug :: [String] -> Assistant ()
debug ws = do
ThreadName name <- getAssistant threadName
liftIO $ Debug.debug (Debug.DebugSource (encodeBS name)) (unwords ws)