2016-12-02 13:50:56 -04:00
|
|
|
{- P2P protocol, Annex implementation
|
|
|
|
-
|
2018-03-12 13:43:19 -04:00
|
|
|
- Copyright 2016-2018 Joey Hess <id@joeyh.name>
|
2016-12-02 13:50:56 -04:00
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
2018-03-06 15:14:53 -04:00
|
|
|
{-# LANGUAGE RankNTypes, FlexibleContexts #-}
|
2016-12-02 13:50:56 -04:00
|
|
|
|
|
|
|
module P2P.Annex
|
2018-03-12 13:43:19 -04:00
|
|
|
( RunState(..)
|
|
|
|
, mkRunState
|
2016-12-06 15:40:31 -04:00
|
|
|
, P2PConnection(..)
|
2016-12-02 13:50:56 -04:00
|
|
|
, runFullProto
|
|
|
|
) where
|
|
|
|
|
|
|
|
import Annex.Common
|
|
|
|
import Annex.Content
|
2016-12-02 16:39:01 -04:00
|
|
|
import Annex.Transfer
|
2016-12-09 14:52:38 -04:00
|
|
|
import Annex.ChangedRefs
|
2016-12-02 13:50:56 -04:00
|
|
|
import P2P.Protocol
|
|
|
|
import P2P.IO
|
2016-12-02 14:49:22 -04:00
|
|
|
import Logs.Location
|
|
|
|
import Types.NumCopies
|
2016-12-08 19:56:02 -04:00
|
|
|
import Utility.Metered
|
2016-12-02 13:50:56 -04:00
|
|
|
|
|
|
|
import Control.Monad.Free
|
2016-12-02 15:34:15 -04:00
|
|
|
|
2016-12-02 13:50:56 -04:00
|
|
|
-- Full interpreter for Proto, that can receive and send objects.
|
2018-03-12 13:43:19 -04:00
|
|
|
runFullProto :: RunState -> P2PConnection -> Proto a -> Annex (Either String a)
|
|
|
|
runFullProto runst conn = go
|
2016-12-02 13:50:56 -04:00
|
|
|
where
|
|
|
|
go :: RunProto Annex
|
2016-12-10 11:12:18 -04:00
|
|
|
go (Pure v) = return (Right v)
|
2018-03-12 15:19:40 -04:00
|
|
|
go (Free (Net n)) = runNet runst conn go n
|
2018-03-12 13:43:19 -04:00
|
|
|
go (Free (Local l)) = runLocal runst go l
|
2016-12-02 13:50:56 -04:00
|
|
|
|
2018-03-12 13:43:19 -04:00
|
|
|
runLocal :: RunState -> RunProto Annex -> LocalF (Proto a) -> Annex (Either String a)
|
|
|
|
runLocal runst runner a = case a of
|
2016-12-02 13:50:56 -04:00
|
|
|
TmpContentSize k next -> do
|
|
|
|
tmp <- fromRepo $ gitAnnexTmpObjectLocation k
|
|
|
|
size <- liftIO $ catchDefaultIO 0 $ getFileSize tmp
|
|
|
|
runner (next (Len size))
|
2016-12-06 15:05:44 -04:00
|
|
|
FileSize f next -> do
|
|
|
|
size <- liftIO $ catchDefaultIO 0 $ getFileSize f
|
|
|
|
runner (next (Len size))
|
2016-12-02 14:49:22 -04:00
|
|
|
ContentSize k next -> do
|
|
|
|
let getsize = liftIO . catchMaybeIO . getFileSize
|
|
|
|
size <- inAnnex' isJust Nothing getsize k
|
|
|
|
runner (next (Len <$> size))
|
2016-12-08 19:56:02 -04:00
|
|
|
ReadContent k af o sender next -> do
|
2016-12-02 14:49:22 -04:00
|
|
|
v <- tryNonAsync $ prepSendAnnex k
|
|
|
|
case v of
|
2018-03-13 14:18:30 -04:00
|
|
|
Right (Just (f, checkchanged)) -> do
|
2016-12-08 19:56:02 -04:00
|
|
|
v' <- tryNonAsync $
|
|
|
|
transfer upload k af $
|
2018-03-13 14:18:30 -04:00
|
|
|
sinkfile f o checkchanged sender
|
2016-12-02 14:49:22 -04:00
|
|
|
case v' of
|
2016-12-08 15:47:49 -04:00
|
|
|
Left e -> return (Left (show e))
|
2016-12-08 19:56:02 -04:00
|
|
|
Right (Left e) -> return (Left (show e))
|
|
|
|
Right (Right ok) -> runner (next ok)
|
|
|
|
-- content not available
|
|
|
|
Right Nothing -> runner (next False)
|
2016-12-08 15:47:49 -04:00
|
|
|
Left e -> return (Left (show e))
|
2018-03-13 14:18:30 -04:00
|
|
|
StoreContent k af o l getb validitycheck next -> do
|
2016-12-02 14:49:22 -04:00
|
|
|
ok <- flip catchNonAsync (const $ return False) $
|
2016-12-08 19:56:02 -04:00
|
|
|
transfer download k af $ \p ->
|
2018-03-13 14:18:30 -04:00
|
|
|
getViaTmp DefaultVerify k $ \tmp -> do
|
|
|
|
storefile tmp o l getb validitycheck p
|
2016-12-02 14:49:22 -04:00
|
|
|
runner (next ok)
|
2018-03-13 14:18:30 -04:00
|
|
|
StoreContentTo dest o l getb validitycheck next -> do
|
|
|
|
res <- flip catchNonAsync (const $ return (False, UnVerified)) $
|
|
|
|
storefile dest o l getb validitycheck nullMeterUpdate
|
|
|
|
runner (next res)
|
2016-12-02 14:49:22 -04:00
|
|
|
SetPresent k u next -> do
|
|
|
|
v <- tryNonAsync $ logChange k u InfoPresent
|
|
|
|
case v of
|
2016-12-08 15:47:49 -04:00
|
|
|
Left e -> return (Left (show e))
|
2016-12-02 14:49:22 -04:00
|
|
|
Right () -> runner next
|
|
|
|
CheckContentPresent k next -> do
|
|
|
|
v <- tryNonAsync $ inAnnex k
|
|
|
|
case v of
|
2016-12-08 15:47:49 -04:00
|
|
|
Left e -> return (Left (show e))
|
2016-12-02 14:49:22 -04:00
|
|
|
Right result -> runner (next result)
|
|
|
|
RemoveContent k next -> do
|
2016-12-09 12:47:57 -04:00
|
|
|
v <- tryNonAsync $
|
2016-12-09 12:54:12 -04:00
|
|
|
ifM (Annex.Content.inAnnex k)
|
2016-12-09 12:47:57 -04:00
|
|
|
( lockContentForRemoval k $ \contentlock -> do
|
|
|
|
removeAnnex contentlock
|
|
|
|
logStatus k InfoMissing
|
|
|
|
return True
|
|
|
|
, return True
|
|
|
|
)
|
2016-12-02 14:49:22 -04:00
|
|
|
case v of
|
2016-12-08 15:47:49 -04:00
|
|
|
Left e -> return (Left (show e))
|
2016-12-02 14:49:22 -04:00
|
|
|
Right result -> runner (next result)
|
|
|
|
TryLockContent k protoaction next -> do
|
|
|
|
v <- tryNonAsync $ lockContentShared k $ \verifiedcopy ->
|
|
|
|
case verifiedcopy of
|
|
|
|
LockedCopy _ -> runner (protoaction True)
|
|
|
|
_ -> runner (protoaction False)
|
|
|
|
-- If locking fails, lockContentShared throws an exception.
|
|
|
|
-- Let the peer know it failed.
|
|
|
|
case v of
|
|
|
|
Left _ -> runner $ do
|
|
|
|
protoaction False
|
|
|
|
next
|
|
|
|
Right _ -> runner next
|
2018-03-12 13:43:19 -04:00
|
|
|
WaitRefChange next -> case runst of
|
|
|
|
Serving _ (Just h) _ -> do
|
2016-12-09 15:08:54 -04:00
|
|
|
v <- tryNonAsync $ liftIO $ waitChangedRefs h
|
|
|
|
case v of
|
|
|
|
Left e -> return (Left (show e))
|
|
|
|
Right changedrefs -> runner (next changedrefs)
|
2016-12-09 16:27:20 -04:00
|
|
|
_ -> return $ Left "change notification not available"
|
2018-03-12 21:46:58 -04:00
|
|
|
UpdateMeterTotalSize m sz next -> do
|
|
|
|
liftIO $ setMeterTotalSize m sz
|
|
|
|
runner next
|
2018-03-13 14:18:30 -04:00
|
|
|
RunValidityCheck check next -> runner . next =<< check
|
2016-12-02 16:39:01 -04:00
|
|
|
where
|
2018-03-12 13:43:19 -04:00
|
|
|
transfer mk k af ta = case runst of
|
2016-12-02 16:39:01 -04:00
|
|
|
-- Update transfer logs when serving.
|
2018-03-29 13:04:07 -04:00
|
|
|
-- Using noRetry because we're the sender.
|
2018-03-12 13:43:19 -04:00
|
|
|
Serving theiruuid _ _ ->
|
2016-12-08 19:56:02 -04:00
|
|
|
mk theiruuid k af noRetry ta noNotification
|
2016-12-02 16:39:01 -04:00
|
|
|
-- Transfer logs are updated higher in the stack when
|
|
|
|
-- a client.
|
2018-03-12 13:43:19 -04:00
|
|
|
Client _ -> ta nullMeterUpdate
|
2016-12-08 19:56:02 -04:00
|
|
|
|
2018-03-13 14:18:30 -04:00
|
|
|
storefile dest (Offset o) (Len l) getb validitycheck p = do
|
2016-12-08 19:56:02 -04:00
|
|
|
let p' = offsetMeterUpdate p (toBytesProcessed o)
|
2016-12-08 18:26:03 -04:00
|
|
|
v <- runner getb
|
|
|
|
case v of
|
2018-03-13 14:18:30 -04:00
|
|
|
Right b -> do
|
|
|
|
liftIO $ withBinaryFile dest ReadWriteMode $ \h -> do
|
2016-12-08 18:26:03 -04:00
|
|
|
when (o /= 0) $
|
|
|
|
hSeek h AbsoluteSeek o
|
2016-12-08 19:56:02 -04:00
|
|
|
meteredWrite p' h b
|
2018-03-13 14:18:30 -04:00
|
|
|
rightsize <- do
|
|
|
|
sz <- liftIO $ getFileSize dest
|
|
|
|
return (toInteger sz == l + o)
|
|
|
|
|
|
|
|
runner validitycheck >>= \case
|
|
|
|
Right (Just Valid) ->
|
|
|
|
return (rightsize, UnVerified)
|
|
|
|
_ -> do
|
|
|
|
-- Invalid, or old protocol
|
|
|
|
-- version. Validity is not
|
|
|
|
-- known. Force content
|
|
|
|
-- verification.
|
|
|
|
return (rightsize, MustVerify)
|
2016-12-08 18:26:03 -04:00
|
|
|
Left e -> error e
|
2016-12-08 19:56:02 -04:00
|
|
|
|
2018-03-13 14:18:30 -04:00
|
|
|
sinkfile f (Offset o) checkchanged sender p = bracket setup cleanup go
|
2016-12-08 19:56:02 -04:00
|
|
|
where
|
|
|
|
setup = liftIO $ openBinaryFile f ReadMode
|
|
|
|
cleanup = liftIO . hClose
|
|
|
|
go h = do
|
|
|
|
let p' = offsetMeterUpdate p (toBytesProcessed o)
|
|
|
|
when (o /= 0) $
|
|
|
|
liftIO $ hSeek h AbsoluteSeek o
|
|
|
|
b <- liftIO $ hGetContentsMetered h p'
|
2018-03-13 14:18:30 -04:00
|
|
|
let validitycheck = local $ runValidityCheck $
|
|
|
|
checkchanged >>= return . \case
|
|
|
|
False -> Invalid
|
|
|
|
True -> Valid
|
|
|
|
runner (sender b validitycheck)
|