-- | Paths used in the TUF data structures
module Hackage.Security.TUF.Paths (
    -- * Repository
    RepoRoot
  , RepoPath
  , anchorRepoPathLocally
  , anchorRepoPathRemotely
    -- * Index
  , IndexRoot
  , IndexPath
    -- * Cache
  , CacheRoot
  , CachePath
  , anchorCachePath
  ) where

import Hackage.Security.Util.Path
import Hackage.Security.Util.Pretty

{-------------------------------------------------------------------------------
  Repo
-------------------------------------------------------------------------------}

-- | The root of the repository
--
-- Repository roots can be anchored at a remote URL or a local directory.
--
-- Note that even for remote repos 'RepoRoot' is (potentially) different from
-- 'Web' -- for a repository located at, say, @http://hackage.haskell.org@
-- they happen to coincide, but for one location at
-- @http://example.com/some/subdirectory@ they do not.
data RepoRoot

-- | Paths relative to the root of the repository
type RepoPath = Path RepoRoot

instance Pretty (Path RepoRoot) where
  pretty :: Path RepoRoot -> String
pretty (Path String
fp) = String
"<repo>/" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fp

anchorRepoPathLocally :: Path root -> RepoPath -> Path root
anchorRepoPathLocally :: Path root -> Path RepoRoot -> Path root
anchorRepoPathLocally Path root
localRoot Path RepoRoot
repoPath = Path root
localRoot Path root -> Path Unrooted -> Path root
forall a. Path a -> Path Unrooted -> Path a
</> Path RepoRoot -> Path Unrooted
forall root. Path root -> Path Unrooted
unrootPath Path RepoRoot
repoPath

anchorRepoPathRemotely :: Path Web -> RepoPath -> Path Web
anchorRepoPathRemotely :: Path Web -> Path RepoRoot -> Path Web
anchorRepoPathRemotely Path Web
remoteRoot Path RepoRoot
repoPath = Path Web
remoteRoot Path Web -> Path Unrooted -> Path Web
forall a. Path a -> Path Unrooted -> Path a
</> Path RepoRoot -> Path Unrooted
forall root. Path root -> Path Unrooted
unrootPath Path RepoRoot
repoPath

{-------------------------------------------------------------------------------
  Index
-------------------------------------------------------------------------------}

-- | The root of the index tarball
data IndexRoot

-- | Paths relative to the root of the index tarball
type IndexPath = Path IndexRoot

instance Pretty (Path IndexRoot) where
    pretty :: Path IndexRoot -> String
pretty (Path String
fp) = String
"<index>/" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fp

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

-- | The cache directory
data CacheRoot
type CachePath = Path CacheRoot

instance Pretty (Path CacheRoot) where
    pretty :: Path CacheRoot -> String
pretty (Path String
fp) = String
"<cache>/" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fp

-- | Anchor a cache path to the location of the cache
anchorCachePath :: Path root -> CachePath -> Path root
anchorCachePath :: Path root -> Path CacheRoot -> Path root
anchorCachePath Path root
cacheRoot Path CacheRoot
cachePath = Path root
cacheRoot Path root -> Path Unrooted -> Path root
forall a. Path a -> Path Unrooted -> Path a
</> Path CacheRoot -> Path Unrooted
forall root. Path root -> Path Unrooted
unrootPath Path CacheRoot
cachePath