{-# LANGUAGE CPP #-}
module Hackage.Security.Client.Repository.Remote (
withRepository
, RepoOpts(..)
, defaultRepoOpts
, RemoteTemp
, FileSize(..)
, fileSizeWithinBounds
) where
import Control.Concurrent
import Control.Exception
import Control.Monad.Cont
import Data.List (nub, intercalate)
import Data.Typeable
import Network.URI hiding (uriPath, path)
import System.IO ()
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BS.L
import Hackage.Security.Client.Formats
import Hackage.Security.Client.Repository
import Hackage.Security.Client.Repository.Cache (Cache)
import Hackage.Security.Client.Repository.HttpLib
import Hackage.Security.Client.Verify
import Hackage.Security.Trusted
import Hackage.Security.TUF
import Hackage.Security.Util.Checked
import Hackage.Security.Util.IO
import Hackage.Security.Util.Path
import Hackage.Security.Util.Pretty
import Hackage.Security.Util.Some
import Hackage.Security.Util.Exit
import qualified Hackage.Security.Client.Repository.Cache as Cache
newtype ServerCapabilities = SC (MVar ServerCapabilities_)
data ServerCapabilities_ = ServerCapabilities {
serverAcceptRangesBytes :: Bool
}
newServerCapabilities :: IO ServerCapabilities
newServerCapabilities = SC <$> newMVar ServerCapabilities {
serverAcceptRangesBytes = False
}
updateServerCapabilities :: ServerCapabilities -> [HttpResponseHeader] -> IO ()
updateServerCapabilities (SC mv) responseHeaders = modifyMVar_ mv $ \caps ->
return $ caps {
serverAcceptRangesBytes = serverAcceptRangesBytes caps
|| HttpResponseAcceptRangesBytes `elem` responseHeaders
}
checkServerCapability :: MonadIO m
=> ServerCapabilities -> (ServerCapabilities_ -> a) -> m a
checkServerCapability (SC mv) f = liftIO $ withMVar mv $ return . f
data FileSize =
FileSizeExact Int54
| FileSizeBound Int54
deriving Show
fileSizeWithinBounds :: Int54 -> FileSize -> Bool
fileSizeWithinBounds sz (FileSizeExact sz') = sz <= sz'
fileSizeWithinBounds sz (FileSizeBound sz') = sz <= sz'
data RepoOpts = RepoOpts {
repoAllowAdditionalMirrors :: Bool
}
defaultRepoOpts :: RepoOpts
defaultRepoOpts = RepoOpts {
repoAllowAdditionalMirrors = True
}
withRepository
:: HttpLib
-> [URI]
-> RepoOpts
-> Cache
-> RepoLayout
-> IndexLayout
-> (LogMessage -> IO ())
-> (Repository RemoteTemp -> IO a)
-> IO a
withRepository httpLib
outOfBandMirrors
repoOpts
cache
repLayout
repIndexLayout
logger
callback
= do
selectedMirror <- newMVar Nothing
caps <- newServerCapabilities
let remoteConfig mirror = RemoteConfig {
cfgLayout = repLayout
, cfgHttpLib = httpLib
, cfgBase = mirror
, cfgCache = cache
, cfgCaps = caps
, cfgLogger = liftIO . logger
, cfgOpts = repoOpts
}
callback Repository {
repGetRemote = getRemote remoteConfig selectedMirror
, repGetCached = Cache.getCached cache
, repGetCachedRoot = Cache.getCachedRoot cache
, repClearCache = Cache.clearCache cache
, repWithIndex = Cache.withIndex cache
, repGetIndexIdx = Cache.getIndexIdx cache
, repLockCache = Cache.lockCacheWithLogger logger cache
, repWithMirror = withMirror httpLib
selectedMirror
logger
outOfBandMirrors
repoOpts
, repLog = logger
, repLayout = repLayout
, repIndexLayout = repIndexLayout
, repDescription = "Remote repository at " ++ show outOfBandMirrors
}
type SelectedMirror = MVar (Maybe URI)
getSelectedMirror :: SelectedMirror -> IO URI
getSelectedMirror selectedMirror = do
mBaseURI <- readMVar selectedMirror
case mBaseURI of
Nothing -> internalError "Internal error: no mirror selected"
Just baseURI -> return baseURI
getRemote :: Throws SomeRemoteError
=> (URI -> RemoteConfig)
-> SelectedMirror
-> AttemptNr
-> RemoteFile fs typ
-> Verify (Some (HasFormat fs), RemoteTemp typ)
getRemote remoteConfig selectedMirror attemptNr remoteFile = do
baseURI <- liftIO $ getSelectedMirror selectedMirror
let cfg = remoteConfig baseURI
downloadMethod <- liftIO $ pickDownloadMethod cfg attemptNr remoteFile
getFile cfg attemptNr remoteFile downloadMethod
httpRequestHeaders :: RemoteConfig -> AttemptNr -> [HttpRequestHeader]
httpRequestHeaders RemoteConfig{..} attemptNr =
if attemptNr == 0 then defaultHeaders
else HttpRequestMaxAge0 : defaultHeaders
where
defaultHeaders :: [HttpRequestHeader]
defaultHeaders = [HttpRequestNoTransform]
withMirror :: forall a.
HttpLib
-> SelectedMirror
-> (LogMessage -> IO ())
-> [URI]
-> RepoOpts
-> Maybe [Mirror]
-> IO a
-> IO a
withMirror HttpLib{..}
selectedMirror
logger
oobMirrors
repoOpts
tufMirrors
callback
=
go orderedMirrors
where
go :: [URI] -> IO a
go [] = internalError "No mirrors configured"
go [m] = do
logger $ LogSelectedMirror (show m)
select m $ callback
go (m:ms) = do
logger $ LogSelectedMirror (show m)
catchChecked (select m callback) $ \ex -> do
logger $ LogMirrorFailed (show m) ex
go ms
orderedMirrors :: [URI]
orderedMirrors = nub $ concat [
oobMirrors
, if repoAllowAdditionalMirrors repoOpts
then maybe [] (map mirrorUrlBase) tufMirrors
else []
]
select :: URI -> IO a -> IO a
select uri =
bracket_ (modifyMVar_ selectedMirror $ \_ -> return $ Just uri)
(modifyMVar_ selectedMirror $ \_ -> return Nothing)
data DownloadMethod :: * -> * -> * where
NeverUpdated :: {
neverUpdatedFormat :: HasFormat fs f
} -> DownloadMethod fs typ
CannotUpdate :: {
cannotUpdateFormat :: HasFormat fs f
, cannotUpdateReason :: UpdateFailure
} -> DownloadMethod fs Binary
Update :: {
updateFormat :: HasFormat fs f
, updateInfo :: Trusted FileInfo
, updateLocal :: Path Absolute
, updateTail :: Int54
} -> DownloadMethod fs Binary
pickDownloadMethod :: forall fs typ. RemoteConfig
-> AttemptNr
-> RemoteFile fs typ
-> IO (DownloadMethod fs typ)
pickDownloadMethod RemoteConfig{..} attemptNr remoteFile =
case remoteFile of
RemoteTimestamp -> return $ NeverUpdated (HFZ FUn)
(RemoteRoot _) -> return $ NeverUpdated (HFZ FUn)
(RemoteSnapshot _) -> return $ NeverUpdated (HFZ FUn)
(RemoteMirrors _) -> return $ NeverUpdated (HFZ FUn)
(RemotePkgTarGz _ _) -> return $ NeverUpdated (HFZ FGz)
(RemoteIndex hasGz formats) -> multipleExitPoints $ do
rangeSupport <- checkServerCapability cfgCaps serverAcceptRangesBytes
unless rangeSupport $ exit $ CannotUpdate hasGz UpdateImpossibleUnsupported
mCachedIndex <- lift $ Cache.getCachedIndex cfgCache (hasFormatGet hasGz)
cachedIndex <- case mCachedIndex of
Nothing -> exit $ CannotUpdate hasGz UpdateImpossibleNoLocalCopy
Just fp -> return fp
when (attemptNr >= 2) $ exit $ CannotUpdate hasGz UpdateFailedTwice
return Update {
updateFormat = hasGz
, updateInfo = formatsLookup hasGz formats
, updateLocal = cachedIndex
, updateTail = 65536
}
getFile :: forall fs typ. Throws SomeRemoteError
=> RemoteConfig
-> AttemptNr
-> RemoteFile fs typ
-> DownloadMethod fs typ
-> Verify (Some (HasFormat fs), RemoteTemp typ)
getFile cfg@RemoteConfig{..} attemptNr remoteFile method =
go method
where
go :: DownloadMethod fs typ -> Verify (Some (HasFormat fs), RemoteTemp typ)
go NeverUpdated{..} = do
cfgLogger $ LogDownloading remoteFile
download neverUpdatedFormat
go CannotUpdate{..} = do
cfgLogger $ LogCannotUpdate remoteFile cannotUpdateReason
cfgLogger $ LogDownloading remoteFile
download cannotUpdateFormat
go Update{..} = do
cfgLogger $ LogUpdating remoteFile
update updateFormat updateInfo updateLocal updateTail
headers :: [HttpRequestHeader]
headers = httpRequestHeaders cfg attemptNr
download :: HasFormat fs f -> Verify (Some (HasFormat fs), RemoteTemp typ)
download format = do
(tempPath, h) <- openTempFile (Cache.cacheRoot cfgCache) (uriTemplate uri)
liftIO $ do
httpGet headers uri $ \responseHeaders bodyReader -> do
updateServerCapabilities cfgCaps responseHeaders
execBodyReader targetPath sz h bodyReader
hClose h
cacheIfVerified format $ DownloadedWhole tempPath
where
targetPath = TargetPathRepo $ remoteRepoPath' cfgLayout remoteFile format
uri = formatsLookup format $ remoteFileURI cfgLayout cfgBase remoteFile
sz = formatsLookup format $ remoteFileSize remoteFile
update :: (typ ~ Binary)
=> HasFormat fs f
-> Trusted FileInfo
-> Path Absolute
-> Int54
-> Verify (Some (HasFormat fs), RemoteTemp typ)
update format info cachedFile fileTail = do
currentSz <- liftIO $ getFileSize cachedFile
let fileSz = fileLength' info
range = (0 `max` (currentSz - fileTail), fileSz)
range' = (fromIntegral (fst range), fromIntegral (snd range))
cacheRoot = Cache.cacheRoot cfgCache
(tempPath, h) <- openTempFile cacheRoot (uriTemplate uri)
statusCode <- liftIO $
httpGetRange headers uri range' $ \statusCode responseHeaders bodyReader -> do
updateServerCapabilities cfgCaps responseHeaders
let expectedSize =
case statusCode of
HttpStatus206PartialContent ->
FileSizeExact (snd range - fst range)
HttpStatus200OK ->
FileSizeExact fileSz
execBodyReader targetPath expectedSize h bodyReader
hClose h
return statusCode
let downloaded =
case statusCode of
HttpStatus206PartialContent ->
DownloadedDelta {
deltaTemp = tempPath
, deltaExisting = cachedFile
, deltaSeek = fst range
}
HttpStatus200OK ->
DownloadedWhole tempPath
cacheIfVerified format downloaded
where
targetPath = TargetPathRepo repoPath
uri = modifyUriPath cfgBase (`anchorRepoPathRemotely` repoPath)
repoPath = remoteRepoPath' cfgLayout remoteFile format
cacheIfVerified :: HasFormat fs f -> RemoteTemp typ
-> Verify (Some (HasFormat fs), RemoteTemp typ)
cacheIfVerified format remoteTemp = do
ifVerified $
Cache.cacheRemoteFile cfgCache
remoteTemp
(hasFormatGet format)
(mustCache remoteFile)
return (Some format, remoteTemp)
httpGetRange :: forall a. Throws SomeRemoteError
=> [HttpRequestHeader]
-> URI
-> (Int, Int)
-> (HttpStatus -> [HttpResponseHeader] -> BodyReader -> IO a)
-> IO a
HttpLib{..} = cfgHttpLib
execBodyReader :: Throws SomeRemoteError
=> TargetPath
-> FileSize
-> Handle
-> BodyReader
-> IO ()
execBodyReader file mlen h br = go 0
where
go :: Int54 -> IO ()
go sz = do
unless (sz `fileSizeWithinBounds` mlen) $
throwChecked $ SomeRemoteError $ FileTooLarge file mlen
bs <- br
if BS.null bs
then return ()
else BS.hPut h bs >> go (sz + fromIntegral (BS.length bs))
data FileTooLarge = FileTooLarge {
fileTooLargePath :: TargetPath
, fileTooLargeExpected :: FileSize
}
deriving (Typeable)
instance Pretty FileTooLarge where
pretty FileTooLarge{..} = concat [
"file returned by server too large: "
, pretty fileTooLargePath
, " (expected " ++ expected fileTooLargeExpected ++ " bytes)"
]
where
expected :: FileSize -> String
expected (FileSizeExact n) = "exactly " ++ show n
expected (FileSizeBound n) = "at most " ++ show n
#if MIN_VERSION_base(4,8,0)
deriving instance Show FileTooLarge
instance Exception FileTooLarge where displayException = pretty
#else
instance Exception FileTooLarge
instance Show FileTooLarge where show = pretty
#endif
remoteFileURI :: RepoLayout -> URI -> RemoteFile fs typ -> Formats fs URI
remoteFileURI repoLayout baseURI = fmap aux . remoteRepoPath repoLayout
where
aux :: RepoPath -> URI
aux repoPath = modifyUriPath baseURI (`anchorRepoPathRemotely` repoPath)
remoteFileSize :: RemoteFile fs typ -> Formats fs FileSize
remoteFileSize (RemoteTimestamp) =
FsUn $ FileSizeBound fileSizeBoundTimestamp
remoteFileSize (RemoteRoot mLen) =
FsUn $ maybe (FileSizeBound fileSizeBoundRoot)
(FileSizeExact . fileLength')
mLen
remoteFileSize (RemoteSnapshot len) =
FsUn $ FileSizeExact (fileLength' len)
remoteFileSize (RemoteMirrors len) =
FsUn $ FileSizeExact (fileLength' len)
remoteFileSize (RemoteIndex _ lens) =
fmap (FileSizeExact . fileLength') lens
remoteFileSize (RemotePkgTarGz _pkgId len) =
FsGz $ FileSizeExact (fileLength' len)
fileSizeBoundTimestamp :: Int54
fileSizeBoundTimestamp = 4096
fileSizeBoundRoot :: Int54
fileSizeBoundRoot = 2 * 1024 * 2014
data RemoteConfig = RemoteConfig {
cfgLayout :: RepoLayout
, cfgHttpLib :: HttpLib
, cfgBase :: URI
, cfgCache :: Cache
, cfgCaps :: ServerCapabilities
, cfgLogger :: forall m. MonadIO m => LogMessage -> m ()
, cfgOpts :: RepoOpts
}
uriTemplate :: URI -> String
uriTemplate = takeFileName . uriPath
fileLength' :: Trusted FileInfo -> Int54
fileLength' = fileLength . fileInfoLength . trusted
data RemoteTemp :: * -> * where
DownloadedWhole :: {
wholeTemp :: Path Absolute
} -> RemoteTemp a
DownloadedDelta :: {
deltaTemp :: Path Absolute
, deltaExisting :: Path Absolute
, deltaSeek :: Int54
} -> RemoteTemp Binary
instance Pretty (RemoteTemp typ) where
pretty DownloadedWhole{..} = intercalate " " $ [
"DownloadedWhole"
, pretty wholeTemp
]
pretty DownloadedDelta{..} = intercalate " " $ [
"DownloadedDelta"
, pretty deltaTemp
, pretty deltaExisting
, show deltaSeek
]
instance DownloadedFile RemoteTemp where
downloadedVerify = verifyRemoteFile
downloadedRead = readLazyByteString . wholeTemp
downloadedCopyTo = \f dest ->
case f of
DownloadedWhole{..} ->
renameFile wholeTemp dest
DownloadedDelta{..} -> do
unless (deltaExisting == dest) $
throwIO $ userError "Assertion failure: deltaExisting /= dest"
withFile deltaExisting ReadWriteMode $ \h -> do
hSeek h AbsoluteSeek (fromIntegral deltaSeek)
BS.L.hPut h =<< readLazyByteString deltaTemp
verifyRemoteFile :: RemoteTemp typ -> Trusted FileInfo -> IO Bool
verifyRemoteFile remoteTemp trustedInfo = do
sz <- FileLength <$> remoteSize remoteTemp
if sz /= fileInfoLength (trusted trustedInfo)
then return False
else withRemoteBS remoteTemp $
compareTrustedFileInfo (trusted trustedInfo) . fileInfo
where
remoteSize :: RemoteTemp typ -> IO Int54
remoteSize DownloadedWhole{..} = getFileSize wholeTemp
remoteSize DownloadedDelta{..} = do
deltaSize <- getFileSize deltaTemp
return $ deltaSeek + deltaSize
withRemoteBS :: RemoteTemp typ -> (BS.L.ByteString -> Bool) -> IO Bool
withRemoteBS DownloadedWhole{..} callback = do
withFile wholeTemp ReadMode $ \h -> do
bs <- BS.L.hGetContents h
evaluate $ callback bs
withRemoteBS DownloadedDelta{..} callback =
withFile deltaExisting ReadMode $ \hExisting ->
withFile deltaTemp ReadMode $ \hTemp -> do
existing <- BS.L.hGetContents hExisting
temp <- BS.L.hGetContents hTemp
evaluate $ callback $ BS.L.concat [
BS.L.take (fromIntegral deltaSeek) existing
, temp
]