{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 710
{-# LANGUAGE StaticPointers #-}
#endif
module Hackage.Security.Client (
checkForUpdates
, HasUpdates(..)
, downloadPackage
, downloadPackage'
, Directory(..)
, DirectoryEntry(..)
, getDirectory
, IndexFile(..)
, IndexEntry(..)
, IndexCallbacks(..)
, withIndex
, requiresBootstrap
, bootstrap
, module Hackage.Security.TUF
, module Hackage.Security.Key
, trusted
, Repository
, DownloadedFile(..)
, SomeRemoteError(..)
, LogMessage(..)
, uncheckClientErrors
, VerificationError(..)
, VerificationHistory
, RootUpdated(..)
, InvalidPackageException(..)
, InvalidFileInIndex(..)
, LocalFileCorrupted(..)
) where
import Prelude hiding (log)
import Control.Arrow (first)
import Control.Exception
import Control.Monad
import Control.Monad.IO.Class
import Data.List (sortBy)
import Data.Maybe (isNothing)
import Data.Ord (comparing)
import Data.Time
import Data.Traversable (for)
import Data.Typeable (Typeable)
import qualified Codec.Archive.Tar as Tar
import qualified Codec.Archive.Tar.Entry as Tar
import qualified Codec.Archive.Tar.Index as Tar
import qualified Data.ByteString.Lazy as BS.L
import qualified Data.ByteString.Lazy.Char8 as BS.L.C8
import Distribution.Package (PackageIdentifier)
import Distribution.Text (display)
import Hackage.Security.Client.Formats
import Hackage.Security.Client.Repository
import Hackage.Security.Client.Verify
import Hackage.Security.JSON
import Hackage.Security.Key
import Hackage.Security.Key.Env (KeyEnv)
import Hackage.Security.Trusted
import Hackage.Security.Trusted.TCB
import Hackage.Security.TUF
import Hackage.Security.Util.Checked
import Hackage.Security.Util.Path
import Hackage.Security.Util.Pretty
import Hackage.Security.Util.Some
import Hackage.Security.Util.Stack
import qualified Hackage.Security.Key.Env as KeyEnv
data HasUpdates = HasUpdates | NoUpdates
deriving (Show, Eq, Ord)
checkForUpdates :: (Throws VerificationError, Throws SomeRemoteError)
=> Repository down
-> Maybe UTCTime
-> IO HasUpdates
checkForUpdates rep@Repository{..} mNow =
withMirror rep $ limitIterations []
where
maxNumIterations :: Int
maxNumIterations = 5
limitIterations :: VerificationHistory -> IO HasUpdates
limitIterations history | length history >= maxNumIterations =
throwChecked $ VerificationErrorLoop (reverse history)
limitIterations history = do
cachedInfo <- getCachedInfo rep
mHasUpdates <- tryChecked
$ tryChecked
$ runVerify repLockCache
$ go attemptNr cachedInfo
case mHasUpdates of
Left ex -> do
log rep $ LogVerificationError ex
let history' = Right ex : history
attemptNr' = attemptNr + 1
updateRoot rep mNow attemptNr' cachedInfo (Left ex)
limitIterations history'
Right (Left RootUpdated) -> do
log rep $ LogRootUpdated
let history' = Left RootUpdated : history
limitIterations history'
Right (Right hasUpdates) ->
return hasUpdates
where
attemptNr :: AttemptNr
attemptNr = fromIntegral $ length history
go :: Throws RootUpdated => AttemptNr -> CachedInfo -> Verify HasUpdates
go attemptNr cachedInfo@CachedInfo{..} = do
newTS <- getRemoteFile' RemoteTimestamp
let newInfoSS = static timestampInfoSnapshot <$$> newTS
if not (fileChanged cachedInfoSnapshot newInfoSS)
then return NoUpdates
else do
newSS <- getRemoteFile' (RemoteSnapshot newInfoSS)
let newInfoRoot = static snapshotInfoRoot <$$> newSS
newInfoMirrors = static snapshotInfoMirrors <$$> newSS
newInfoTarGz = static snapshotInfoTarGz <$$> newSS
mNewInfoTar = trustElems (static snapshotInfoTar <$$> newSS)
when (rootChanged cachedInfoRoot newInfoRoot) $ liftIO $ do
updateRoot rep mNow attemptNr cachedInfo (Right newInfoRoot)
throwChecked RootUpdated
when (fileChanged cachedInfoMirrors newInfoMirrors) $
newMirrors =<< getRemoteFile' (RemoteMirrors newInfoMirrors)
when (fileChanged cachedInfoTarGz newInfoTarGz) $
updateIndex newInfoTarGz mNewInfoTar
return HasUpdates
where
getRemoteFile' :: ( VerifyRole a
, FromJSON ReadJSON_Keys_Layout (Signed a)
)
=> RemoteFile (f :- ()) Metadata -> Verify (Trusted a)
getRemoteFile' = liftM fst . getRemoteFile rep cachedInfo attemptNr mNow
updateIndex :: Trusted FileInfo
-> Maybe (Trusted FileInfo)
-> Verify ()
updateIndex newInfoTarGz Nothing = do
(targetPath, tempPath) <- getRemote' rep attemptNr $
RemoteIndex (HFZ FGz) (FsGz newInfoTarGz)
verifyFileInfo' (Just newInfoTarGz) targetPath tempPath
updateIndex newInfoTarGz (Just newInfoTar) = do
(format, targetPath, tempPath) <- getRemote rep attemptNr $
RemoteIndex (HFS (HFZ FGz)) (FsUnGz newInfoTar newInfoTarGz)
case format of
Some FGz -> verifyFileInfo' (Just newInfoTarGz) targetPath tempPath
Some FUn -> verifyFileInfo' (Just newInfoTar) targetPath tempPath
rootChanged :: Maybe (Trusted FileInfo) -> Trusted FileInfo -> Bool
rootChanged Nothing _ = False
rootChanged (Just old) new = not (trustedFileInfoEqual old new)
fileChanged :: Maybe (Trusted FileInfo) -> Trusted FileInfo -> Bool
fileChanged Nothing _ = True
fileChanged (Just old) new = not (trustedFileInfoEqual old new)
newMirrors :: Trusted Mirrors -> Verify ()
newMirrors _ = return ()
updateRoot :: (Throws VerificationError, Throws SomeRemoteError)
=> Repository down
-> Maybe UTCTime
-> AttemptNr
-> CachedInfo
-> Either VerificationError (Trusted FileInfo)
-> IO ()
updateRoot rep@Repository{..} mNow isRetry cachedInfo eFileInfo = do
rootReallyChanged <- runVerify repLockCache $ do
(_newRoot :: Trusted Root, rootTempFile) <- getRemoteFile
rep
cachedInfo
isRetry
mNow
(RemoteRoot (eitherToMaybe eFileInfo))
case eFileInfo of
Right _ ->
return True
Left _e -> liftIO $ do
oldRootFile <- repGetCachedRoot
oldRootInfo <- DeclareTrusted <$> computeFileInfo oldRootFile
not <$> downloadedVerify rootTempFile oldRootInfo
when rootReallyChanged $ clearCache rep
data CachedInfo = CachedInfo {
cachedRoot :: Trusted Root
, cachedKeyEnv :: KeyEnv
, cachedTimestamp :: Maybe (Trusted Timestamp)
, cachedSnapshot :: Maybe (Trusted Snapshot)
, cachedMirrors :: Maybe (Trusted Mirrors)
, cachedInfoSnapshot :: Maybe (Trusted FileInfo)
, cachedInfoRoot :: Maybe (Trusted FileInfo)
, cachedInfoMirrors :: Maybe (Trusted FileInfo)
, cachedInfoTarGz :: Maybe (Trusted FileInfo)
}
cachedVersion :: CachedInfo -> RemoteFile fs typ -> Maybe FileVersion
cachedVersion CachedInfo{..} remoteFile =
case mustCache remoteFile of
CacheAs CachedTimestamp -> timestampVersion . trusted <$> cachedTimestamp
CacheAs CachedSnapshot -> snapshotVersion . trusted <$> cachedSnapshot
CacheAs CachedMirrors -> mirrorsVersion . trusted <$> cachedMirrors
CacheAs CachedRoot -> Just . rootVersion . trusted $ cachedRoot
CacheIndex -> Nothing
DontCache -> Nothing
getCachedInfo ::
#if __GLASGOW_HASKELL__ < 800
(Applicative m, MonadIO m)
#else
MonadIO m
#endif
=> Repository down -> m CachedInfo
getCachedInfo rep = do
(cachedRoot, cachedKeyEnv) <- readLocalRoot rep
cachedTimestamp <- readLocalFile rep cachedKeyEnv CachedTimestamp
cachedSnapshot <- readLocalFile rep cachedKeyEnv CachedSnapshot
cachedMirrors <- readLocalFile rep cachedKeyEnv CachedMirrors
let cachedInfoSnapshot = fmap (static timestampInfoSnapshot <$$>) cachedTimestamp
cachedInfoRoot = fmap (static snapshotInfoRoot <$$>) cachedSnapshot
cachedInfoMirrors = fmap (static snapshotInfoMirrors <$$>) cachedSnapshot
cachedInfoTarGz = fmap (static snapshotInfoTarGz <$$>) cachedSnapshot
return CachedInfo{..}
readLocalRoot :: MonadIO m => Repository down -> m (Trusted Root, KeyEnv)
readLocalRoot rep = do
cachedPath <- liftIO $ repGetCachedRoot rep
signedRoot <- throwErrorsUnchecked LocalFileCorrupted =<<
readCachedJSON rep KeyEnv.empty cachedPath
return (trustLocalFile signedRoot, rootKeys (signed signedRoot))
readLocalFile :: ( FromJSON ReadJSON_Keys_Layout (Signed a), MonadIO m
#if __GLASGOW_HASKELL__ < 800
, Applicative m
#endif
)
=> Repository down -> KeyEnv -> CachedFile -> m (Maybe (Trusted a))
readLocalFile rep cachedKeyEnv file = do
mCachedPath <- liftIO $ repGetCached rep file
for mCachedPath $ \cachedPath -> do
signed <- throwErrorsUnchecked LocalFileCorrupted =<<
readCachedJSON rep cachedKeyEnv cachedPath
return $ trustLocalFile signed
getRemoteFile :: ( Throws VerificationError
, Throws SomeRemoteError
, VerifyRole a
, FromJSON ReadJSON_Keys_Layout (Signed a)
)
=> Repository down
-> CachedInfo
-> AttemptNr
-> Maybe UTCTime
-> RemoteFile (f :- ()) Metadata
-> Verify (Trusted a, down Metadata)
getRemoteFile rep@Repository{..} cachedInfo@CachedInfo{..} isRetry mNow file = do
(targetPath, tempPath) <- getRemote' rep isRetry file
verifyFileInfo' (remoteFileDefaultInfo file) targetPath tempPath
signed <- throwErrorsChecked (VerificationErrorDeserialization targetPath) =<<
readDownloadedJSON rep cachedKeyEnv tempPath
verified <- throwErrorsChecked id $ verifyRole
cachedRoot
targetPath
(cachedVersion cachedInfo file)
mNow
signed
return (trustVerified verified, tempPath)
downloadPackage :: ( Throws SomeRemoteError
, Throws VerificationError
, Throws InvalidPackageException
)
=> Repository down
-> PackageIdentifier
-> Path Absolute
-> IO ()
downloadPackage rep@Repository{..} pkgId dest =
withMirror rep $
withIndex rep $ \IndexCallbacks{..} -> runVerify repLockCache $ do
targetFileInfo <- liftIO $ indexLookupFileInfo pkgId
tarGz <- do
(targetPath, downloaded) <- getRemote' rep (AttemptNr 0) $
RemotePkgTarGz pkgId targetFileInfo
verifyFileInfo' (Just targetFileInfo) targetPath downloaded
return downloaded
liftIO $ downloadedCopyTo tarGz dest
downloadPackage' :: ( Throws SomeRemoteError
, Throws VerificationError
, Throws InvalidPackageException
)
=> Repository down
-> PackageIdentifier
-> FilePath
-> IO ()
downloadPackage' rep pkgId dest =
downloadPackage rep pkgId =<< makeAbsolute (fromFilePath dest)
data Directory = Directory {
directoryFirst :: DirectoryEntry
, directoryNext :: DirectoryEntry
, directoryLookup :: forall dec. IndexFile dec -> Maybe DirectoryEntry
, directoryEntries :: [(DirectoryEntry, IndexPath, Maybe (Some IndexFile))]
}
newtype DirectoryEntry = DirectoryEntry {
directoryEntryBlockNo :: Tar.TarEntryOffset
}
deriving (Eq, Ord)
instance Show DirectoryEntry where
show = show . directoryEntryBlockNo
instance Read DirectoryEntry where
readsPrec p = map (first DirectoryEntry) . readsPrec p
getDirectory :: Repository down -> IO Directory
getDirectory Repository{..} = mkDirectory <$> repGetIndexIdx
where
mkDirectory :: Tar.TarIndex -> Directory
mkDirectory idx = Directory {
directoryFirst = DirectoryEntry 0
, directoryNext = DirectoryEntry $ Tar.indexEndEntryOffset idx
, directoryLookup = liftM dirEntry . Tar.lookup idx . filePath
, directoryEntries = map mkEntry $ sortBy (comparing snd) (Tar.toList idx)
}
mkEntry :: (FilePath, Tar.TarEntryOffset)
-> (DirectoryEntry, IndexPath, Maybe (Some IndexFile))
mkEntry (fp, off) = (DirectoryEntry off, path, indexFile path)
where
path = indexPath fp
dirEntry :: Tar.TarIndexEntry -> DirectoryEntry
dirEntry (Tar.TarFileEntry offset) = DirectoryEntry offset
dirEntry (Tar.TarDir _) = error "directoryLookup: unexpected directory"
indexFile :: IndexPath -> Maybe (Some IndexFile)
indexFile = indexFileFromPath repIndexLayout
indexPath :: FilePath -> IndexPath
indexPath = rootPath . fromUnrootedFilePath
filePath :: IndexFile dec -> FilePath
filePath = toUnrootedFilePath . unrootPath . indexFileToPath repIndexLayout
data IndexEntry dec = IndexEntry {
indexEntryPath :: IndexPath
, indexEntryPathParsed :: Maybe (IndexFile dec)
, indexEntryContent :: BS.L.ByteString
, indexEntryContentParsed :: Either SomeException dec
, indexEntryTime :: Tar.EpochTime
}
data IndexCallbacks = IndexCallbacks {
indexLookupEntry :: DirectoryEntry
-> IO (Some IndexEntry, Maybe DirectoryEntry)
, indexLookupFile :: forall dec.
IndexFile dec
-> IO (Maybe (IndexEntry dec))
, indexLookupFileEntry :: forall dec.
DirectoryEntry
-> IndexFile dec
-> IO (IndexEntry dec)
, indexLookupCabal :: Throws InvalidPackageException
=> PackageIdentifier
-> IO (Trusted BS.L.ByteString)
, indexLookupMetadata :: Throws InvalidPackageException
=> PackageIdentifier
-> IO (Trusted Targets)
, indexLookupFileInfo :: ( Throws InvalidPackageException
, Throws VerificationError
)
=> PackageIdentifier
-> IO (Trusted FileInfo)
, indexLookupHash :: ( Throws InvalidPackageException
, Throws VerificationError
)
=> PackageIdentifier
-> IO (Trusted Hash)
, indexDirectory :: Directory
}
withIndex :: Repository down -> (IndexCallbacks -> IO a) -> IO a
withIndex rep@Repository{..} callback = do
(_cachedRoot, keyEnv) <- readLocalRoot rep
dir@Directory{..} <- getDirectory rep
repWithIndex $ \h -> do
let getEntry :: DirectoryEntry
-> IO (Some IndexEntry, Maybe DirectoryEntry)
getEntry entry = do
(tarEntry, content, next) <- getTarEntry entry
let path = indexPath tarEntry
case indexFile path of
Nothing ->
return (Some (mkEntry tarEntry content Nothing), next)
Just (Some file) ->
return (Some (mkEntry tarEntry content (Just file)), next)
getFile :: IndexFile dec -> IO (Maybe (IndexEntry dec))
getFile file =
case directoryLookup file of
Nothing -> return Nothing
Just dirEntry -> Just <$> getFileEntry dirEntry file
getFileEntry :: DirectoryEntry
-> IndexFile dec
-> IO (IndexEntry dec)
getFileEntry dirEntry file = do
(tarEntry, content, _next) <- getTarEntry dirEntry
return $ mkEntry tarEntry content (Just file)
mkEntry :: Tar.Entry
-> BS.L.ByteString
-> Maybe (IndexFile dec)
-> IndexEntry dec
mkEntry tarEntry content mFile = IndexEntry {
indexEntryPath = indexPath tarEntry
, indexEntryPathParsed = mFile
, indexEntryContent = content
, indexEntryContentParsed = parseContent mFile content
, indexEntryTime = Tar.entryTime tarEntry
}
parseContent :: Maybe (IndexFile dec)
-> BS.L.ByteString -> Either SomeException dec
parseContent Nothing _ = Left pathNotRecognized
parseContent (Just file) raw = case file of
IndexPkgPrefs _ ->
Right ()
IndexPkgCabal _ ->
Right ()
IndexPkgMetadata _ ->
let mkEx = either
(Left . SomeException . InvalidFileInIndex file raw)
Right
in mkEx $ parseJSON_Keys_NoLayout keyEnv raw
getTarEntry :: DirectoryEntry
-> IO (Tar.Entry, BS.L.ByteString, Maybe DirectoryEntry)
getTarEntry (DirectoryEntry offset) = do
entry <- Tar.hReadEntry h offset
content <- case Tar.entryContent entry of
Tar.NormalFile content _sz -> return content
_ -> throwIO $ userError "withIndex: unexpected entry"
let next = DirectoryEntry $ Tar.nextEntryOffset entry offset
mNext = guard (next < directoryNext) >> return next
return (entry, content, mNext)
getCabal :: Throws InvalidPackageException
=> PackageIdentifier -> IO (Trusted BS.L.ByteString)
getCabal pkgId = do
mCabal <- getFile $ IndexPkgCabal pkgId
case mCabal of
Nothing ->
throwChecked $ InvalidPackageException pkgId
Just IndexEntry{..} ->
return $ DeclareTrusted indexEntryContent
getMetadata :: Throws InvalidPackageException
=> PackageIdentifier -> IO (Trusted Targets)
getMetadata pkgId = do
mEntry <- getFile $ IndexPkgMetadata pkgId
case mEntry of
Nothing ->
throwChecked $ InvalidPackageException pkgId
Just IndexEntry{indexEntryContentParsed = Left ex} ->
throwUnchecked $ ex
Just IndexEntry{indexEntryContentParsed = Right signed} ->
return $ trustLocalFile signed
getFileInfo :: ( Throws InvalidPackageException
, Throws VerificationError
)
=> PackageIdentifier -> IO (Trusted FileInfo)
getFileInfo pkgId = do
targets <- getMetadata pkgId
let mTargetMetadata :: Maybe (Trusted FileInfo)
mTargetMetadata = trustElems
$ trustStatic (static targetsLookup)
`trustApply` DeclareTrusted (targetPath pkgId)
`trustApply` targets
case mTargetMetadata of
Nothing ->
throwChecked $ VerificationErrorUnknownTarget (targetPath pkgId)
Just info ->
return info
getHash :: ( Throws InvalidPackageException
, Throws VerificationError
)
=> PackageIdentifier -> IO (Trusted Hash)
getHash pkgId = do
info <- getFileInfo pkgId
let mTrustedHash :: Maybe (Trusted Hash)
mTrustedHash = trustElems
$ trustStatic (static fileInfoSHA256)
`trustApply` info
case mTrustedHash of
Nothing ->
throwChecked $ VerificationErrorMissingSHA256 (targetPath pkgId)
Just hash ->
return hash
callback IndexCallbacks{
indexLookupEntry = getEntry
, indexLookupFile = getFile
, indexLookupFileEntry = getFileEntry
, indexDirectory = dir
, indexLookupCabal = getCabal
, indexLookupMetadata = getMetadata
, indexLookupFileInfo = getFileInfo
, indexLookupHash = getHash
}
where
indexPath :: Tar.Entry -> IndexPath
indexPath = rootPath . fromUnrootedFilePath
. Tar.fromTarPathToPosixPath
. Tar.entryTarPath
indexFile :: IndexPath -> Maybe (Some IndexFile)
indexFile = indexFileFromPath repIndexLayout
targetPath :: PackageIdentifier -> TargetPath
targetPath = TargetPathRepo . repoLayoutPkgTarGz repLayout
pathNotRecognized :: SomeException
pathNotRecognized = SomeException (userError "Path not recognized")
requiresBootstrap :: Repository down -> IO Bool
requiresBootstrap rep = isNothing <$> repGetCached rep CachedRoot
bootstrap :: (Throws SomeRemoteError, Throws VerificationError)
=> Repository down -> [KeyId] -> KeyThreshold -> IO ()
bootstrap rep@Repository{..} trustedRootKeys keyThreshold = withMirror rep $ runVerify repLockCache $ do
_newRoot :: Trusted Root <- do
(targetPath, tempPath) <- getRemote' rep (AttemptNr 0) (RemoteRoot Nothing)
signed <- throwErrorsChecked (VerificationErrorDeserialization targetPath) =<<
readDownloadedJSON rep KeyEnv.empty tempPath
verified <- throwErrorsChecked id $ verifyFingerprints
trustedRootKeys
keyThreshold
targetPath
signed
return $ trustVerified verified
clearCache rep
getRemote :: forall fs down typ. Throws SomeRemoteError
=> Repository down
-> AttemptNr
-> RemoteFile fs typ
-> Verify (Some Format, TargetPath, down typ)
getRemote r attemptNr file = do
(Some format, downloaded) <- repGetRemote r attemptNr file
let targetPath = TargetPathRepo $ remoteRepoPath' (repLayout r) file format
return (Some (hasFormatGet format), targetPath, downloaded)
getRemote' :: forall f down typ. Throws SomeRemoteError
=> Repository down
-> AttemptNr
-> RemoteFile (f :- ()) typ
-> Verify (TargetPath, down typ)
getRemote' r isRetry file = ignoreFormat <$> getRemote r isRetry file
where
ignoreFormat (_format, targetPath, tempPath) = (targetPath, tempPath)
clearCache :: MonadIO m => Repository down -> m ()
clearCache r = liftIO $ repClearCache r
log :: MonadIO m => Repository down -> LogMessage -> m ()
log r msg = liftIO $ repLog r msg
withMirror :: Repository down -> IO a -> IO a
withMirror rep callback = do
mMirrors <- repGetCached rep CachedMirrors
mirrors <- case mMirrors of
Nothing -> return Nothing
Just fp -> filterMirrors <$>
(throwErrorsUnchecked LocalFileCorrupted =<<
readJSON_NoKeys_NoLayout fp)
repWithMirror rep mirrors $ callback
where
filterMirrors :: UninterpretedSignatures Mirrors -> Maybe [Mirror]
filterMirrors = Just
. filter (canUseMirror . mirrorContent)
. mirrorsMirrors
. uninterpretedSigned
canUseMirror :: MirrorContent -> Bool
canUseMirror MirrorFull = True
uncheckClientErrors :: ( ( Throws VerificationError
, Throws SomeRemoteError
, Throws InvalidPackageException
) => IO a )
-> IO a
uncheckClientErrors act = handleChecked rethrowVerificationError
$ handleChecked rethrowSomeRemoteError
$ handleChecked rethrowInvalidPackageException
$ act
where
rethrowVerificationError :: VerificationError -> IO a
rethrowVerificationError = throwIO
rethrowSomeRemoteError :: SomeRemoteError -> IO a
rethrowSomeRemoteError = throwIO
rethrowInvalidPackageException :: InvalidPackageException -> IO a
rethrowInvalidPackageException = throwIO
data InvalidPackageException = InvalidPackageException PackageIdentifier
deriving (Typeable)
data LocalFileCorrupted = LocalFileCorrupted DeserializationError
deriving (Typeable)
data InvalidFileInIndex = forall dec. InvalidFileInIndex {
invalidFileInIndex :: IndexFile dec
, invalidFileInIndexRaw :: BS.L.ByteString
, invalidFileInIndexError :: DeserializationError
}
deriving (Typeable)
#if MIN_VERSION_base(4,8,0)
deriving instance Show InvalidPackageException
deriving instance Show LocalFileCorrupted
deriving instance Show InvalidFileInIndex
instance Exception InvalidPackageException where displayException = pretty
instance Exception LocalFileCorrupted where displayException = pretty
instance Exception InvalidFileInIndex where displayException = pretty
#else
instance Show InvalidPackageException where show = pretty
instance Show LocalFileCorrupted where show = pretty
instance Show InvalidFileInIndex where show = pretty
instance Exception InvalidPackageException
instance Exception LocalFileCorrupted
instance Exception InvalidFileInIndex
#endif
instance Pretty InvalidPackageException where
pretty (InvalidPackageException pkgId) = "Invalid package " ++ display pkgId
instance Pretty LocalFileCorrupted where
pretty (LocalFileCorrupted err) = "Local file corrupted: " ++ pretty err
instance Pretty InvalidFileInIndex where
pretty (InvalidFileInIndex file raw err) = unlines [
"Invalid file in index: " ++ pretty file
, "Error: " ++ pretty err
, "Unparsed file: " ++ BS.L.C8.unpack raw
]
trustLocalFile :: Signed a -> Trusted a
trustLocalFile Signed{..} = DeclareTrusted signed
verifyFileInfo' :: (MonadIO m, DownloadedFile down)
=> Maybe (Trusted FileInfo)
-> TargetPath
-> down typ
-> m ()
verifyFileInfo' Nothing _ _ = return ()
verifyFileInfo' (Just info) targetPath tempPath = liftIO $ do
verified <- downloadedVerify tempPath info
unless verified $ throw $ VerificationErrorFileInfo targetPath
readCachedJSON :: (MonadIO m, FromJSON ReadJSON_Keys_Layout a)
=> Repository down -> KeyEnv -> Path Absolute
-> m (Either DeserializationError a)
readCachedJSON Repository{..} keyEnv fp = liftIO $ do
bs <- readLazyByteString fp
evaluate $ parseJSON_Keys_Layout keyEnv repLayout bs
readDownloadedJSON :: (MonadIO m, FromJSON ReadJSON_Keys_Layout a)
=> Repository down -> KeyEnv -> down Metadata
-> m (Either DeserializationError a)
readDownloadedJSON Repository{..} keyEnv fp = liftIO $ do
bs <- downloadedRead fp
evaluate $ parseJSON_Keys_Layout keyEnv repLayout bs
throwErrorsUnchecked :: ( MonadIO m
, Exception e'
)
=> (e -> e') -> Either e a -> m a
throwErrorsUnchecked f (Left err) = liftIO $ throwUnchecked (f err)
throwErrorsUnchecked _ (Right a) = return a
throwErrorsChecked :: ( Throws e'
, MonadIO m
, Exception e'
)
=> (e -> e') -> Either e a -> m a
throwErrorsChecked f (Left err) = liftIO $ throwChecked (f err)
throwErrorsChecked _ (Right a) = return a
eitherToMaybe :: Either a b -> Maybe b
eitherToMaybe (Left _) = Nothing
eitherToMaybe (Right b) = Just b