module Hackage.Security.TUF.Layout.Cache (
    -- * Cache layout
    CacheLayout(..)
  , cabalCacheLayout
  ) where

import MyPrelude
import Hackage.Security.TUF.Paths
import Hackage.Security.Util.Path

{-------------------------------------------------------------------------------
  Cache layout
-------------------------------------------------------------------------------}

-- | Location of the various files we cache
--
-- Although the generic TUF algorithms do not care how we organize the cache,
-- we nonetheless specify this here because as long as there are tools which
-- access files in the cache directly we need to define the cache layout.
-- See also comments for 'defaultCacheLayout'.
data CacheLayout = CacheLayout {
    -- | TUF root metadata
    CacheLayout -> CachePath
cacheLayoutRoot :: CachePath

    -- | TUF timestamp
  , CacheLayout -> CachePath
cacheLayoutTimestamp :: CachePath

    -- | TUF snapshot
  , CacheLayout -> CachePath
cacheLayoutSnapshot :: CachePath

    -- | TUF mirrors list
  , CacheLayout -> CachePath
cacheLayoutMirrors :: CachePath

    -- | Uncompressed index tarball
  , CacheLayout -> CachePath
cacheLayoutIndexTar :: CachePath

    -- | Index to the uncompressed index tarball
  , CacheLayout -> CachePath
cacheLayoutIndexIdx :: CachePath

    -- | Compressed index tarball
    --
    -- We cache both the compressed and the uncompressed tarballs, because
    -- incremental updates happen through the compressed tarball, but reads
    -- happen through the uncompressed one (with the help of the tarball index).
  , CacheLayout -> CachePath
cacheLayoutIndexTarGz :: CachePath
  }

-- | The cache layout cabal-install uses
--
-- We cache the index as @<cache>/00-index.tar@; this is important because
-- `cabal-install` expects to find it there (and does not currently go through
-- the hackage-security library to get files from the index).
cabalCacheLayout :: CacheLayout
cabalCacheLayout :: CacheLayout
cabalCacheLayout = CacheLayout {
      cacheLayoutRoot :: CachePath
cacheLayoutRoot       = Path Unrooted -> CachePath
rp forall a b. (a -> b) -> a -> b
$ String -> Path Unrooted
fragment String
"root.json"
    , cacheLayoutTimestamp :: CachePath
cacheLayoutTimestamp  = Path Unrooted -> CachePath
rp forall a b. (a -> b) -> a -> b
$ String -> Path Unrooted
fragment String
"timestamp.json"
    , cacheLayoutSnapshot :: CachePath
cacheLayoutSnapshot   = Path Unrooted -> CachePath
rp forall a b. (a -> b) -> a -> b
$ String -> Path Unrooted
fragment String
"snapshot.json"
    , cacheLayoutMirrors :: CachePath
cacheLayoutMirrors    = Path Unrooted -> CachePath
rp forall a b. (a -> b) -> a -> b
$ String -> Path Unrooted
fragment String
"mirrors.json"
    , cacheLayoutIndexTar :: CachePath
cacheLayoutIndexTar   = Path Unrooted -> CachePath
rp forall a b. (a -> b) -> a -> b
$ String -> Path Unrooted
fragment String
"00-index.tar"
    , cacheLayoutIndexIdx :: CachePath
cacheLayoutIndexIdx   = Path Unrooted -> CachePath
rp forall a b. (a -> b) -> a -> b
$ String -> Path Unrooted
fragment String
"00-index.tar.idx"
    , cacheLayoutIndexTarGz :: CachePath
cacheLayoutIndexTarGz = Path Unrooted -> CachePath
rp forall a b. (a -> b) -> a -> b
$ String -> Path Unrooted
fragment String
"00-index.tar.gz"
    }
  where
    rp :: Path Unrooted -> CachePath
    rp :: Path Unrooted -> CachePath
rp = forall root. Path Unrooted -> Path root
rootPath