{-# LANGUAGE CPP #-}
module Hackage.Security.Client.Repository (
Metadata
, Binary
, RemoteFile(..)
, CachedFile(..)
, IndexFile(..)
, remoteFileDefaultFormat
, remoteFileDefaultInfo
, Repository(..)
, AttemptNr(..)
, LogMessage(..)
, UpdateFailure(..)
, SomeRemoteError(..)
, DownloadedFile(..)
, mirrorsUnsupported
, remoteRepoPath
, remoteRepoPath'
, IsCached(..)
, mustCache
) where
import MyPrelude
import Control.Exception
import Data.Typeable (Typeable)
import qualified Codec.Archive.Tar.Index as Tar
import qualified Data.ByteString.Lazy as BS.L
import Distribution.Package
import Distribution.Text
import Hackage.Security.Client.Formats
import Hackage.Security.Client.Verify
import Hackage.Security.Trusted
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
data Metadata
data Binary
data RemoteFile :: * -> * -> * where
RemoteTimestamp :: RemoteFile (FormatUn :- ()) Metadata
RemoteRoot :: Maybe (Trusted FileInfo) -> RemoteFile (FormatUn :- ()) Metadata
RemoteSnapshot :: Trusted FileInfo -> RemoteFile (FormatUn :- ()) Metadata
RemoteMirrors :: Trusted FileInfo -> RemoteFile (FormatUn :- ()) Metadata
RemoteIndex :: HasFormat fs FormatGz
-> Formats fs (Trusted FileInfo)
-> RemoteFile fs Binary
RemotePkgTarGz :: PackageIdentifier
-> Trusted FileInfo
-> RemoteFile (FormatGz :- ()) Binary
deriving instance Show (RemoteFile fs typ)
instance Pretty (RemoteFile fs typ) where
pretty :: RemoteFile fs typ -> String
pretty RemoteFile fs typ
RemoteTimestamp = String
"timestamp"
pretty (RemoteRoot Maybe (Trusted FileInfo)
_) = String
"root"
pretty (RemoteSnapshot Trusted FileInfo
_) = String
"snapshot"
pretty (RemoteMirrors Trusted FileInfo
_) = String
"mirrors"
pretty (RemoteIndex HasFormat fs FormatGz
_ Formats fs (Trusted FileInfo)
_) = String
"index"
pretty (RemotePkgTarGz PackageIdentifier
pkgId Trusted FileInfo
_) = String
"package " String -> ShowS
forall a. [a] -> [a] -> [a]
++ PackageIdentifier -> String
forall a. Pretty a => a -> String
display PackageIdentifier
pkgId
data CachedFile =
CachedTimestamp
| CachedRoot
| CachedSnapshot
| CachedMirrors
deriving (CachedFile -> CachedFile -> Bool
(CachedFile -> CachedFile -> Bool)
-> (CachedFile -> CachedFile -> Bool) -> Eq CachedFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CachedFile -> CachedFile -> Bool
== :: CachedFile -> CachedFile -> Bool
$c/= :: CachedFile -> CachedFile -> Bool
/= :: CachedFile -> CachedFile -> Bool
Eq, Eq CachedFile
Eq CachedFile =>
(CachedFile -> CachedFile -> Ordering)
-> (CachedFile -> CachedFile -> Bool)
-> (CachedFile -> CachedFile -> Bool)
-> (CachedFile -> CachedFile -> Bool)
-> (CachedFile -> CachedFile -> Bool)
-> (CachedFile -> CachedFile -> CachedFile)
-> (CachedFile -> CachedFile -> CachedFile)
-> Ord CachedFile
CachedFile -> CachedFile -> Bool
CachedFile -> CachedFile -> Ordering
CachedFile -> CachedFile -> CachedFile
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: CachedFile -> CachedFile -> Ordering
compare :: CachedFile -> CachedFile -> Ordering
$c< :: CachedFile -> CachedFile -> Bool
< :: CachedFile -> CachedFile -> Bool
$c<= :: CachedFile -> CachedFile -> Bool
<= :: CachedFile -> CachedFile -> Bool
$c> :: CachedFile -> CachedFile -> Bool
> :: CachedFile -> CachedFile -> Bool
$c>= :: CachedFile -> CachedFile -> Bool
>= :: CachedFile -> CachedFile -> Bool
$cmax :: CachedFile -> CachedFile -> CachedFile
max :: CachedFile -> CachedFile -> CachedFile
$cmin :: CachedFile -> CachedFile -> CachedFile
min :: CachedFile -> CachedFile -> CachedFile
Ord, Int -> CachedFile -> ShowS
[CachedFile] -> ShowS
CachedFile -> String
(Int -> CachedFile -> ShowS)
-> (CachedFile -> String)
-> ([CachedFile] -> ShowS)
-> Show CachedFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CachedFile -> ShowS
showsPrec :: Int -> CachedFile -> ShowS
$cshow :: CachedFile -> String
show :: CachedFile -> String
$cshowList :: [CachedFile] -> ShowS
showList :: [CachedFile] -> ShowS
Show)
instance Pretty CachedFile where
pretty :: CachedFile -> String
pretty CachedFile
CachedTimestamp = String
"timestamp"
pretty CachedFile
CachedRoot = String
"root"
pretty CachedFile
CachedSnapshot = String
"snapshot"
pretty CachedFile
CachedMirrors = String
"mirrors"
remoteFileDefaultFormat :: RemoteFile fs typ -> Some (HasFormat fs)
remoteFileDefaultFormat :: forall fs typ. RemoteFile fs typ -> Some (HasFormat fs)
remoteFileDefaultFormat RemoteFile fs typ
RemoteTimestamp = HasFormat fs FormatUn -> Some (HasFormat fs)
forall (f :: * -> *) a. f a -> Some f
Some (HasFormat fs FormatUn -> Some (HasFormat fs))
-> HasFormat fs FormatUn -> Some (HasFormat fs)
forall a b. (a -> b) -> a -> b
$ Format FormatUn -> HasFormat (FormatUn :- ()) FormatUn
forall b fs. Format b -> HasFormat (b :- fs) b
HFZ Format FormatUn
FUn
remoteFileDefaultFormat (RemoteRoot Maybe (Trusted FileInfo)
_) = HasFormat fs FormatUn -> Some (HasFormat fs)
forall (f :: * -> *) a. f a -> Some f
Some (HasFormat fs FormatUn -> Some (HasFormat fs))
-> HasFormat fs FormatUn -> Some (HasFormat fs)
forall a b. (a -> b) -> a -> b
$ Format FormatUn -> HasFormat (FormatUn :- ()) FormatUn
forall b fs. Format b -> HasFormat (b :- fs) b
HFZ Format FormatUn
FUn
remoteFileDefaultFormat (RemoteSnapshot Trusted FileInfo
_) = HasFormat fs FormatUn -> Some (HasFormat fs)
forall (f :: * -> *) a. f a -> Some f
Some (HasFormat fs FormatUn -> Some (HasFormat fs))
-> HasFormat fs FormatUn -> Some (HasFormat fs)
forall a b. (a -> b) -> a -> b
$ Format FormatUn -> HasFormat (FormatUn :- ()) FormatUn
forall b fs. Format b -> HasFormat (b :- fs) b
HFZ Format FormatUn
FUn
remoteFileDefaultFormat (RemoteMirrors Trusted FileInfo
_) = HasFormat fs FormatUn -> Some (HasFormat fs)
forall (f :: * -> *) a. f a -> Some f
Some (HasFormat fs FormatUn -> Some (HasFormat fs))
-> HasFormat fs FormatUn -> Some (HasFormat fs)
forall a b. (a -> b) -> a -> b
$ Format FormatUn -> HasFormat (FormatUn :- ()) FormatUn
forall b fs. Format b -> HasFormat (b :- fs) b
HFZ Format FormatUn
FUn
remoteFileDefaultFormat (RemotePkgTarGz PackageIdentifier
_ Trusted FileInfo
_) = HasFormat fs FormatGz -> Some (HasFormat fs)
forall (f :: * -> *) a. f a -> Some f
Some (HasFormat fs FormatGz -> Some (HasFormat fs))
-> HasFormat fs FormatGz -> Some (HasFormat fs)
forall a b. (a -> b) -> a -> b
$ Format FormatGz -> HasFormat (FormatGz :- ()) FormatGz
forall b fs. Format b -> HasFormat (b :- fs) b
HFZ Format FormatGz
FGz
remoteFileDefaultFormat (RemoteIndex HasFormat fs FormatGz
pf Formats fs (Trusted FileInfo)
_) = HasFormat fs FormatGz -> Some (HasFormat fs)
forall (f :: * -> *) a. f a -> Some f
Some HasFormat fs FormatGz
pf
remoteFileDefaultInfo :: RemoteFile fs typ -> Maybe (Trusted FileInfo)
remoteFileDefaultInfo :: forall fs typ. RemoteFile fs typ -> Maybe (Trusted FileInfo)
remoteFileDefaultInfo RemoteFile fs typ
RemoteTimestamp = Maybe (Trusted FileInfo)
forall a. Maybe a
Nothing
remoteFileDefaultInfo (RemoteRoot Maybe (Trusted FileInfo)
info) = Maybe (Trusted FileInfo)
info
remoteFileDefaultInfo (RemoteSnapshot Trusted FileInfo
info) = Trusted FileInfo -> Maybe (Trusted FileInfo)
forall a. a -> Maybe a
Just Trusted FileInfo
info
remoteFileDefaultInfo (RemoteMirrors Trusted FileInfo
info) = Trusted FileInfo -> Maybe (Trusted FileInfo)
forall a. a -> Maybe a
Just Trusted FileInfo
info
remoteFileDefaultInfo (RemotePkgTarGz PackageIdentifier
_ Trusted FileInfo
info) = Trusted FileInfo -> Maybe (Trusted FileInfo)
forall a. a -> Maybe a
Just Trusted FileInfo
info
remoteFileDefaultInfo (RemoteIndex HasFormat fs FormatGz
pf Formats fs (Trusted FileInfo)
info) = Trusted FileInfo -> Maybe (Trusted FileInfo)
forall a. a -> Maybe a
Just (Trusted FileInfo -> Maybe (Trusted FileInfo))
-> Trusted FileInfo -> Maybe (Trusted FileInfo)
forall a b. (a -> b) -> a -> b
$ HasFormat fs FormatGz
-> Formats fs (Trusted FileInfo) -> Trusted FileInfo
forall fs f a. HasFormat fs f -> Formats fs a -> a
formatsLookup HasFormat fs FormatGz
pf Formats fs (Trusted FileInfo)
info
data Repository down = DownloadedFile down => Repository {
forall (down :: * -> *).
Repository down
-> forall fs typ.
Throws SomeRemoteError =>
AttemptNr
-> RemoteFile fs typ -> Verify (Some (HasFormat fs), down typ)
repGetRemote :: forall fs typ. Throws SomeRemoteError
=> AttemptNr
-> RemoteFile fs typ
-> Verify (Some (HasFormat fs), down typ)
, forall (down :: * -> *).
Repository down -> CachedFile -> IO (Maybe (Path Absolute))
repGetCached :: CachedFile -> IO (Maybe (Path Absolute))
, forall (down :: * -> *). Repository down -> IO (Path Absolute)
repGetCachedRoot :: IO (Path Absolute)
, forall (down :: * -> *). Repository down -> IO ()
repClearCache :: IO ()
, forall (down :: * -> *).
Repository down -> forall a. (Handle -> IO a) -> IO a
repWithIndex :: forall a. (Handle -> IO a) -> IO a
, forall (down :: * -> *). Repository down -> IO TarIndex
repGetIndexIdx :: IO Tar.TarIndex
, forall (down :: * -> *). Repository down -> IO () -> IO ()
repLockCache :: IO () -> IO ()
, forall (down :: * -> *).
Repository down -> forall a. Maybe [Mirror] -> IO a -> IO a
repWithMirror :: forall a. Maybe [Mirror] -> IO a -> IO a
, forall (down :: * -> *). Repository down -> LogMessage -> IO ()
repLog :: LogMessage -> IO ()
, forall (down :: * -> *). Repository down -> RepoLayout
repLayout :: RepoLayout
, forall (down :: * -> *). Repository down -> IndexLayout
repIndexLayout :: IndexLayout
, forall (down :: * -> *). Repository down -> String
repDescription :: String
}
instance Show (Repository down) where
show :: Repository down -> String
show = Repository down -> String
forall (down :: * -> *). Repository down -> String
repDescription
mirrorsUnsupported :: Maybe [Mirror] -> IO a -> IO a
mirrorsUnsupported :: forall a. Maybe [Mirror] -> IO a -> IO a
mirrorsUnsupported Maybe [Mirror]
_ = IO a -> IO a
forall a. a -> a
id
newtype AttemptNr = AttemptNr Int
deriving (AttemptNr -> AttemptNr -> Bool
(AttemptNr -> AttemptNr -> Bool)
-> (AttemptNr -> AttemptNr -> Bool) -> Eq AttemptNr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AttemptNr -> AttemptNr -> Bool
== :: AttemptNr -> AttemptNr -> Bool
$c/= :: AttemptNr -> AttemptNr -> Bool
/= :: AttemptNr -> AttemptNr -> Bool
Eq, Eq AttemptNr
Eq AttemptNr =>
(AttemptNr -> AttemptNr -> Ordering)
-> (AttemptNr -> AttemptNr -> Bool)
-> (AttemptNr -> AttemptNr -> Bool)
-> (AttemptNr -> AttemptNr -> Bool)
-> (AttemptNr -> AttemptNr -> Bool)
-> (AttemptNr -> AttemptNr -> AttemptNr)
-> (AttemptNr -> AttemptNr -> AttemptNr)
-> Ord AttemptNr
AttemptNr -> AttemptNr -> Bool
AttemptNr -> AttemptNr -> Ordering
AttemptNr -> AttemptNr -> AttemptNr
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AttemptNr -> AttemptNr -> Ordering
compare :: AttemptNr -> AttemptNr -> Ordering
$c< :: AttemptNr -> AttemptNr -> Bool
< :: AttemptNr -> AttemptNr -> Bool
$c<= :: AttemptNr -> AttemptNr -> Bool
<= :: AttemptNr -> AttemptNr -> Bool
$c> :: AttemptNr -> AttemptNr -> Bool
> :: AttemptNr -> AttemptNr -> Bool
$c>= :: AttemptNr -> AttemptNr -> Bool
>= :: AttemptNr -> AttemptNr -> Bool
$cmax :: AttemptNr -> AttemptNr -> AttemptNr
max :: AttemptNr -> AttemptNr -> AttemptNr
$cmin :: AttemptNr -> AttemptNr -> AttemptNr
min :: AttemptNr -> AttemptNr -> AttemptNr
Ord, Integer -> AttemptNr
AttemptNr -> AttemptNr
AttemptNr -> AttemptNr -> AttemptNr
(AttemptNr -> AttemptNr -> AttemptNr)
-> (AttemptNr -> AttemptNr -> AttemptNr)
-> (AttemptNr -> AttemptNr -> AttemptNr)
-> (AttemptNr -> AttemptNr)
-> (AttemptNr -> AttemptNr)
-> (AttemptNr -> AttemptNr)
-> (Integer -> AttemptNr)
-> Num AttemptNr
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: AttemptNr -> AttemptNr -> AttemptNr
+ :: AttemptNr -> AttemptNr -> AttemptNr
$c- :: AttemptNr -> AttemptNr -> AttemptNr
- :: AttemptNr -> AttemptNr -> AttemptNr
$c* :: AttemptNr -> AttemptNr -> AttemptNr
* :: AttemptNr -> AttemptNr -> AttemptNr
$cnegate :: AttemptNr -> AttemptNr
negate :: AttemptNr -> AttemptNr
$cabs :: AttemptNr -> AttemptNr
abs :: AttemptNr -> AttemptNr
$csignum :: AttemptNr -> AttemptNr
signum :: AttemptNr -> AttemptNr
$cfromInteger :: Integer -> AttemptNr
fromInteger :: Integer -> AttemptNr
Num)
data LogMessage =
LogRootUpdated
| LogVerificationError VerificationError
| forall fs typ. LogDownloading (RemoteFile fs typ)
| forall fs. LogUpdating (RemoteFile fs Binary)
| LogSelectedMirror MirrorDescription
| forall fs. LogCannotUpdate (RemoteFile fs Binary) UpdateFailure
| LogMirrorFailed MirrorDescription SomeException
| LogLockWait (Path Absolute)
| LogLockWaitDone (Path Absolute)
| LogUnlock (Path Absolute)
data UpdateFailure =
UpdateImpossibleUnsupported
| UpdateImpossibleNoLocalCopy
| UpdateFailedTwice
| UpdateFailed SomeException
class DownloadedFile (down :: * -> *) where
downloadedVerify :: down a -> Trusted FileInfo -> IO Bool
downloadedRead :: down Metadata -> IO BS.L.ByteString
downloadedCopyTo :: down a -> Path Absolute -> IO ()
data SomeRemoteError :: * where
SomeRemoteError :: Exception e => e -> SomeRemoteError
deriving (Typeable)
#if MIN_VERSION_base(4,8,0)
deriving instance Show SomeRemoteError
instance Exception SomeRemoteError where displayException :: SomeRemoteError -> String
displayException = SomeRemoteError -> String
forall a. Pretty a => a -> String
pretty
#else
instance Exception SomeRemoteError
instance Show SomeRemoteError where show = pretty
#endif
instance Pretty SomeRemoteError where
pretty :: SomeRemoteError -> String
pretty (SomeRemoteError e
ex) = e -> String
forall e. Exception e => e -> String
displayException e
ex
remoteRepoPath :: RepoLayout -> RemoteFile fs typ -> Formats fs RepoPath
remoteRepoPath :: forall fs typ.
RepoLayout -> RemoteFile fs typ -> Formats fs RepoPath
remoteRepoPath RepoLayout{RepoPath
PackageIdentifier -> RepoPath
repoLayoutRoot :: RepoPath
repoLayoutTimestamp :: RepoPath
repoLayoutSnapshot :: RepoPath
repoLayoutMirrors :: RepoPath
repoLayoutIndexTarGz :: RepoPath
repoLayoutIndexTar :: RepoPath
repoLayoutPkgTarGz :: PackageIdentifier -> RepoPath
repoLayoutPkgTarGz :: RepoLayout -> PackageIdentifier -> RepoPath
repoLayoutIndexTar :: RepoLayout -> RepoPath
repoLayoutIndexTarGz :: RepoLayout -> RepoPath
repoLayoutMirrors :: RepoLayout -> RepoPath
repoLayoutSnapshot :: RepoLayout -> RepoPath
repoLayoutTimestamp :: RepoLayout -> RepoPath
repoLayoutRoot :: RepoLayout -> RepoPath
..} = RemoteFile fs typ -> Formats fs RepoPath
forall fs typ. RemoteFile fs typ -> Formats fs RepoPath
go
where
go :: RemoteFile fs typ -> Formats fs RepoPath
go :: forall fs typ. RemoteFile fs typ -> Formats fs RepoPath
go RemoteFile fs typ
RemoteTimestamp = RepoPath -> Formats (FormatUn :- ()) RepoPath
forall b. b -> Formats (FormatUn :- ()) b
FsUn (RepoPath -> Formats (FormatUn :- ()) RepoPath)
-> RepoPath -> Formats (FormatUn :- ()) RepoPath
forall a b. (a -> b) -> a -> b
$ RepoPath
repoLayoutTimestamp
go (RemoteRoot Maybe (Trusted FileInfo)
_) = RepoPath -> Formats (FormatUn :- ()) RepoPath
forall b. b -> Formats (FormatUn :- ()) b
FsUn (RepoPath -> Formats (FormatUn :- ()) RepoPath)
-> RepoPath -> Formats (FormatUn :- ()) RepoPath
forall a b. (a -> b) -> a -> b
$ RepoPath
repoLayoutRoot
go (RemoteSnapshot Trusted FileInfo
_) = RepoPath -> Formats (FormatUn :- ()) RepoPath
forall b. b -> Formats (FormatUn :- ()) b
FsUn (RepoPath -> Formats (FormatUn :- ()) RepoPath)
-> RepoPath -> Formats (FormatUn :- ()) RepoPath
forall a b. (a -> b) -> a -> b
$ RepoPath
repoLayoutSnapshot
go (RemoteMirrors Trusted FileInfo
_) = RepoPath -> Formats (FormatUn :- ()) RepoPath
forall b. b -> Formats (FormatUn :- ()) b
FsUn (RepoPath -> Formats (FormatUn :- ()) RepoPath)
-> RepoPath -> Formats (FormatUn :- ()) RepoPath
forall a b. (a -> b) -> a -> b
$ RepoPath
repoLayoutMirrors
go (RemotePkgTarGz PackageIdentifier
pId Trusted FileInfo
_) = RepoPath -> Formats (FormatGz :- ()) RepoPath
forall b. b -> Formats (FormatGz :- ()) b
FsGz (RepoPath -> Formats (FormatGz :- ()) RepoPath)
-> RepoPath -> Formats (FormatGz :- ()) RepoPath
forall a b. (a -> b) -> a -> b
$ PackageIdentifier -> RepoPath
repoLayoutPkgTarGz PackageIdentifier
pId
go (RemoteIndex HasFormat fs FormatGz
_ Formats fs (Trusted FileInfo)
lens) = (forall f. Format f -> Trusted FileInfo -> RepoPath)
-> Formats fs (Trusted FileInfo) -> Formats fs RepoPath
forall a b fs.
(forall f. Format f -> a -> b) -> Formats fs a -> Formats fs b
formatsMap Format f -> Trusted FileInfo -> RepoPath
forall f. Format f -> Trusted FileInfo -> RepoPath
forall f a. Format f -> a -> RepoPath
goIndex Formats fs (Trusted FileInfo)
lens
goIndex :: Format f -> a -> RepoPath
goIndex :: forall f a. Format f -> a -> RepoPath
goIndex Format f
FUn a
_ = RepoPath
repoLayoutIndexTar
goIndex Format f
FGz a
_ = RepoPath
repoLayoutIndexTarGz
remoteRepoPath' :: RepoLayout -> RemoteFile fs typ -> HasFormat fs f -> RepoPath
remoteRepoPath' :: forall fs typ f.
RepoLayout -> RemoteFile fs typ -> HasFormat fs f -> RepoPath
remoteRepoPath' RepoLayout
repoLayout RemoteFile fs typ
file HasFormat fs f
format =
HasFormat fs f -> Formats fs RepoPath -> RepoPath
forall fs f a. HasFormat fs f -> Formats fs a -> a
formatsLookup HasFormat fs f
format (Formats fs RepoPath -> RepoPath)
-> Formats fs RepoPath -> RepoPath
forall a b. (a -> b) -> a -> b
$ RepoLayout -> RemoteFile fs typ -> Formats fs RepoPath
forall fs typ.
RepoLayout -> RemoteFile fs typ -> Formats fs RepoPath
remoteRepoPath RepoLayout
repoLayout RemoteFile fs typ
file
data IsCached :: * -> * where
CacheAs :: CachedFile -> IsCached Metadata
DontCache :: IsCached Binary
CacheIndex :: IsCached Binary
deriving instance Eq (IsCached typ)
deriving instance Show (IsCached typ)
mustCache :: RemoteFile fs typ -> IsCached typ
mustCache :: forall fs typ. RemoteFile fs typ -> IsCached typ
mustCache RemoteFile fs typ
RemoteTimestamp = CachedFile -> IsCached Metadata
CacheAs CachedFile
CachedTimestamp
mustCache (RemoteRoot Maybe (Trusted FileInfo)
_) = CachedFile -> IsCached Metadata
CacheAs CachedFile
CachedRoot
mustCache (RemoteSnapshot Trusted FileInfo
_) = CachedFile -> IsCached Metadata
CacheAs CachedFile
CachedSnapshot
mustCache (RemoteMirrors Trusted FileInfo
_) = CachedFile -> IsCached Metadata
CacheAs CachedFile
CachedMirrors
mustCache (RemoteIndex {}) = IsCached typ
IsCached Binary
CacheIndex
mustCache (RemotePkgTarGz PackageIdentifier
_ Trusted FileInfo
_) = IsCached typ
IsCached Binary
DontCache
instance Pretty LogMessage where
pretty :: LogMessage -> String
pretty LogMessage
LogRootUpdated =
String
"Root info updated"
pretty (LogVerificationError VerificationError
err) =
String
"Verification error: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ VerificationError -> String
forall a. Pretty a => a -> String
pretty VerificationError
err
pretty (LogDownloading RemoteFile fs typ
file) =
String
"Downloading " String -> ShowS
forall a. [a] -> [a] -> [a]
++ RemoteFile fs typ -> String
forall a. Pretty a => a -> String
pretty RemoteFile fs typ
file
pretty (LogUpdating RemoteFile fs Binary
file) =
String
"Updating " String -> ShowS
forall a. [a] -> [a] -> [a]
++ RemoteFile fs Binary -> String
forall a. Pretty a => a -> String
pretty RemoteFile fs Binary
file
pretty (LogSelectedMirror String
mirror) =
String
"Selected mirror " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
mirror
pretty (LogCannotUpdate RemoteFile fs Binary
file UpdateFailure
ex) =
String
"Cannot update " String -> ShowS
forall a. [a] -> [a] -> [a]
++ RemoteFile fs Binary -> String
forall a. Pretty a => a -> String
pretty RemoteFile fs Binary
file String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" (" String -> ShowS
forall a. [a] -> [a] -> [a]
++ UpdateFailure -> String
forall a. Pretty a => a -> String
pretty UpdateFailure
ex String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")"
pretty (LogMirrorFailed String
mirror SomeException
ex) =
String
"Exception " String -> ShowS
forall a. [a] -> [a] -> [a]
++ SomeException -> String
forall e. Exception e => e -> String
displayException SomeException
ex String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" when using mirror " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
mirror
pretty (LogLockWait Path Absolute
file) =
String
"Waiting to acquire cache lock on " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Path Absolute -> String
forall a. Pretty a => a -> String
pretty Path Absolute
file
pretty (LogLockWaitDone Path Absolute
file) =
String
"Acquired cache lock on " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Path Absolute -> String
forall a. Pretty a => a -> String
pretty Path Absolute
file
pretty (LogUnlock Path Absolute
file) =
String
"Released cache lock on " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Path Absolute -> String
forall a. Pretty a => a -> String
pretty Path Absolute
file
instance Pretty UpdateFailure where
pretty :: UpdateFailure -> String
pretty UpdateFailure
UpdateImpossibleUnsupported =
String
"server does not provide incremental downloads"
pretty UpdateFailure
UpdateImpossibleNoLocalCopy =
String
"no local copy"
pretty UpdateFailure
UpdateFailedTwice =
String
"update failed twice"
pretty (UpdateFailed SomeException
ex) =
SomeException -> String
forall e. Exception e => e -> String
displayException SomeException
ex