fix build with xmpp and w/o webapp

This commit is contained in:
Joey Hess 2013-03-24 18:55:19 -04:00
parent cfd3b16fe1
commit 3ef6b6a200
3 changed files with 27 additions and 37 deletions

View file

@ -20,6 +20,7 @@ import qualified Remote
import Utility.ThreadScheduler import Utility.ThreadScheduler
import Assistant.WebApp (UrlRenderer, renderUrl) import Assistant.WebApp (UrlRenderer, renderUrl)
import Assistant.WebApp.Types hiding (liftAssistant) import Assistant.WebApp.Types hiding (liftAssistant)
import Assistant.WebApp.Configurators.XMPP (checkCloudRepos)
import Assistant.Alert import Assistant.Alert
import Assistant.Pairing import Assistant.Pairing
import Assistant.XMPP.Git import Assistant.XMPP.Git
@ -106,8 +107,9 @@ xmppClient urlrenderer d creds =
maybe noop (inAssistant . pairMsgReceived urlrenderer stage u selfjid) (parseJID c) maybe noop (inAssistant . pairMsgReceived urlrenderer stage u selfjid) (parseJID c)
handle _ (GotNetMessage m@(Pushing _ pushstage)) handle _ (GotNetMessage m@(Pushing _ pushstage))
| isPushInitiation pushstage = inAssistant $ | isPushInitiation pushstage = inAssistant $
unlessM (queueNetPushMessage m) $ unlessM (queueNetPushMessage m) $ do
void $ forkIO <~> handlePushInitiation urlrenderer m let checker = checkCloudRepos urlrenderer
void $ forkIO <~> handlePushInitiation checker m
| otherwise = void $ inAssistant $ queueNetPushMessage m | otherwise = void $ inAssistant $ queueNetPushMessage m
handle _ (Ignorable _) = noop handle _ (Ignorable _) = noop
handle _ (Unknown _) = noop handle _ (Unknown _) = noop

View file

@ -50,21 +50,23 @@ xmppNeeded = whenM (isNothing <$> liftAnnex getXMPPCreds) $ do
xmppNeeded = return () xmppNeeded = return ()
#endif #endif
{- Displays an alert suggesting to configure a cloud repo {- When appropriate, displays an alert suggesting to configure a cloud repo
- to suppliment an XMPP remote. -} - to suppliment an XMPP remote. -}
cloudRepoNeeded :: UrlRenderer -> UUID -> Assistant () checkCloudRepos :: UrlRenderer -> Remote -> Assistant ()
#ifdef WITH_XMPP #ifdef WITH_XMPP
cloudRepoNeeded urlrenderer for = do checkCloudRepos urlrenderer r =
buddyname <- getBuddyName for unlessM (syncingToCloudRemote <$> getDaemonStatus) $ do
url <- liftIO $ renderUrl urlrenderer (NeedCloudRepoR for) [] buddyname <- getBuddyName $ Remote.uuid r
close <- asIO1 removeAlert url <- liftIO $
void $ addAlert $ cloudRepoNeededAlert buddyname $ AlertButton renderUrl urlrenderer (NeedCloudRepoR $ Remote.uuid r) []
{ buttonLabel = "Add a cloud repository" close <- asIO1 removeAlert
, buttonUrl = url void $ addAlert $ cloudRepoNeededAlert buddyname $ AlertButton
, buttonAction = Just close { buttonLabel = "Add a cloud repository"
} , buttonUrl = url
, buttonAction = Just close
}
#else #else
cloudRepoNeeded = return () checkCloudRepos _ _ = noop
#endif #endif
{- Returns the name of the friend corresponding to a {- Returns the name of the friend corresponding to a
@ -88,7 +90,7 @@ getNeedCloudRepoR for = page "Cloud repository needed" (Just Configuration) $ do
buddyname <- liftAssistant $ getBuddyName for buddyname <- liftAssistant $ getBuddyName for
$(widgetFile "configurators/xmpp/needcloudrepo") $(widgetFile "configurators/xmpp/needcloudrepo")
#else #else
needCloudRepoR = xmppPage $ getNeedCloudRepoR = xmppPage $
$(widgetFile "configurators/xmpp/disabled") $(widgetFile "configurators/xmpp/disabled")
#endif #endif

View file

@ -31,10 +31,6 @@ import qualified Remote as Remote
import Remote.List import Remote.List
import Utility.FileMode import Utility.FileMode
import Utility.Shell import Utility.Shell
#ifdef WITH_WEBAPP
import Assistant.WebApp (UrlRenderer)
import Assistant.WebApp.Configurators.XMPP
#endif
import Network.Protocol.XMPP import Network.Protocol.XMPP
import qualified Data.Text as T import qualified Data.Text as T
@ -256,11 +252,11 @@ xmppRemotes cid = case baseJID <$> parseJID cid of
where where
matching loc r = repoIsUrl r && repoLocation r == loc matching loc r = repoIsUrl r && repoLocation r == loc
handlePushInitiation :: UrlRenderer -> NetMessage -> Assistant () handlePushInitiation :: (Remote -> Assistant ()) -> NetMessage -> Assistant ()
handlePushInitiation _ (Pushing cid CanPush) = handlePushInitiation _ (Pushing cid CanPush) =
unlessM (null <$> xmppRemotes cid) $ unlessM (null <$> xmppRemotes cid) $
sendNetMessage $ Pushing cid PushRequest sendNetMessage $ Pushing cid PushRequest
handlePushInitiation urlrenderer (Pushing cid PushRequest) = handlePushInitiation checkcloudrepos (Pushing cid PushRequest) =
go =<< liftAnnex (inRepo Git.Branch.current) go =<< liftAnnex (inRepo Git.Branch.current)
where where
go Nothing = noop go Nothing = noop
@ -276,29 +272,19 @@ handlePushInitiation urlrenderer (Pushing cid PushRequest) =
void $ alertWhile (syncAlert [r]) $ void $ alertWhile (syncAlert [r]) $
xmppPush cid xmppPush cid
(taggedPush u selfjid branch r) (taggedPush u selfjid branch r)
(handleDeferred urlrenderer) (handleDeferred checkcloudrepos)
checkCloudRepos urlrenderer r checkcloudrepos r
handlePushInitiation urlrenderer (Pushing cid StartingPush) = do handlePushInitiation checkcloudrepos (Pushing cid StartingPush) = do
rs <- xmppRemotes cid rs <- xmppRemotes cid
unless (null rs) $ do unless (null rs) $ do
void $ alertWhile (syncAlert rs) $ void $ alertWhile (syncAlert rs) $
xmppReceivePack cid (handleDeferred urlrenderer) xmppReceivePack cid (handleDeferred checkcloudrepos)
mapM_ (checkCloudRepos urlrenderer) rs mapM_ checkcloudrepos rs
handlePushInitiation _ _ = noop handlePushInitiation _ _ = noop
handleDeferred :: UrlRenderer -> NetMessage -> Assistant () handleDeferred :: (Remote -> Assistant ()) -> NetMessage -> Assistant ()
handleDeferred = handlePushInitiation handleDeferred = handlePushInitiation
checkCloudRepos :: UrlRenderer -> Remote -> Assistant ()
-- TODO only display if needed
checkCloudRepos urlrenderer r =
#ifdef WITH_WEBAPP
unlessM (syncingToCloudRemote <$> getDaemonStatus) $
cloudRepoNeeded urlrenderer (Remote.uuid r)
#else
noop
#endif
writeChunk :: Handle -> B.ByteString -> IO () writeChunk :: Handle -> B.ByteString -> IO ()
writeChunk h b = do writeChunk h b = do
B.hPut h b B.hPut h b