{-# LANGUAGE CPP #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE GADTs #-}
module Hackage.Index (
  getCabal,
  getCabals,
  withCabalFile,
  listPackages,
  packageVersions,
  latestVersion,
  preferredVersions,
  getTimestamp,
  indexFiles,
  getPackageDescription,
  getPackageDescription',
  packageIdOrLatest,
  getFileInfo,
  
  FileInfo(..),
  FileLength(..),
  fileInfoSHA256
  ) where
import qualified Data.ByteString.Lazy.Char8 as BL
import qualified Data.List as L
import Data.Maybe
import Data.Time.Clock
import Data.Time.Clock.POSIX
import Data.Version.Extra (readVersion)
import System.Directory
import System.FilePath
import System.IO.Extra (withTempDir)
import Distribution.Version
#if MIN_VERSION_Cabal(3,0,0)
#else
  hiding (showVersion)
#endif
import Hackage.Security.Client
import qualified Hackage.Security.Client.Repository.Local as Local
import qualified Hackage.Security.Util.Path as Path
import qualified Hackage.Security.Client.Repository.Cache as Cache
import Hackage.Security.Util.Pretty
import SimpleCabal
getCabal  :: PackageIdentifier -> IO BL.ByteString
getCabal :: PackageIdentifier -> IO ByteString
getCabal PackageIdentifier
pkgid =
  (Repository LocalFile -> IO ByteString) -> IO ByteString
forall a. (Repository LocalFile -> IO a) -> IO a
withLocalRepo ((Repository LocalFile -> IO ByteString) -> IO ByteString)
-> (Repository LocalFile -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Repository LocalFile
rep -> ((Throws VerificationError, Throws SomeRemoteError,
  Throws InvalidPackageException) =>
 IO ByteString)
-> IO ByteString
forall a.
((Throws VerificationError, Throws SomeRemoteError,
  Throws InvalidPackageException) =>
 IO a)
-> IO a
uncheckClientErrors (((Throws VerificationError, Throws SomeRemoteError,
   Throws InvalidPackageException) =>
  IO ByteString)
 -> IO ByteString)
-> ((Throws VerificationError, Throws SomeRemoteError,
     Throws InvalidPackageException) =>
    IO ByteString)
-> IO ByteString
forall a b. (a -> b) -> a -> b
$
    Repository LocalFile
-> (IndexCallbacks -> IO ByteString) -> IO ByteString
forall (down :: * -> *) a.
Repository down -> (IndexCallbacks -> IO a) -> IO a
withIndex Repository LocalFile
rep ((IndexCallbacks -> IO ByteString) -> IO ByteString)
-> (IndexCallbacks -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \ IndexCallbacks{Directory
DirectoryEntry -> IO (Some IndexEntry, Maybe DirectoryEntry)
Throws InvalidPackageException =>
PackageIdentifier -> IO (Trusted ByteString)
Throws InvalidPackageException =>
PackageIdentifier -> IO (Trusted Targets)
(Throws InvalidPackageException, Throws VerificationError) =>
PackageIdentifier -> IO (Trusted FileInfo)
(Throws InvalidPackageException, Throws VerificationError) =>
PackageIdentifier -> IO (Trusted Hash)
forall dec. DirectoryEntry -> IndexFile dec -> IO (IndexEntry dec)
forall dec. IndexFile dec -> IO (Maybe (IndexEntry dec))
indexLookupEntry :: IndexCallbacks
-> DirectoryEntry -> IO (Some IndexEntry, Maybe DirectoryEntry)
indexLookupFile :: IndexCallbacks
-> forall dec. IndexFile dec -> IO (Maybe (IndexEntry dec))
indexLookupFileEntry :: IndexCallbacks
-> forall dec.
   DirectoryEntry -> IndexFile dec -> IO (IndexEntry dec)
indexLookupCabal :: IndexCallbacks
-> Throws InvalidPackageException =>
   PackageIdentifier -> IO (Trusted ByteString)
indexLookupMetadata :: IndexCallbacks
-> Throws InvalidPackageException =>
   PackageIdentifier -> IO (Trusted Targets)
indexLookupFileInfo :: IndexCallbacks
-> (Throws InvalidPackageException, Throws VerificationError) =>
   PackageIdentifier -> IO (Trusted FileInfo)
indexLookupHash :: IndexCallbacks
-> (Throws InvalidPackageException, Throws VerificationError) =>
   PackageIdentifier -> IO (Trusted Hash)
indexDirectory :: IndexCallbacks -> Directory
indexDirectory :: Directory
indexLookupHash :: (Throws InvalidPackageException, Throws VerificationError) =>
PackageIdentifier -> IO (Trusted Hash)
indexLookupFileInfo :: (Throws InvalidPackageException, Throws VerificationError) =>
PackageIdentifier -> IO (Trusted FileInfo)
indexLookupMetadata :: Throws InvalidPackageException =>
PackageIdentifier -> IO (Trusted Targets)
indexLookupCabal :: Throws InvalidPackageException =>
PackageIdentifier -> IO (Trusted ByteString)
indexLookupFileEntry :: forall dec. DirectoryEntry -> IndexFile dec -> IO (IndexEntry dec)
indexLookupFile :: forall dec. IndexFile dec -> IO (Maybe (IndexEntry dec))
indexLookupEntry :: DirectoryEntry -> IO (Some IndexEntry, Maybe DirectoryEntry)
..} ->
    Trusted ByteString -> ByteString
forall a. Trusted a -> a
trusted (Trusted ByteString -> ByteString)
-> IO (Trusted ByteString) -> IO ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PackageIdentifier -> IO (Trusted ByteString)
Throws InvalidPackageException =>
PackageIdentifier -> IO (Trusted ByteString)
indexLookupCabal PackageIdentifier
pkgid
withCabalFile :: PackageIdentifier -> (FilePath -> IO a) -> IO a
withCabalFile :: PackageIdentifier -> (FilePath -> IO a) -> IO a
withCabalFile PackageIdentifier
pkgid FilePath -> IO a
act =
  (FilePath -> IO a) -> IO a
forall a. (FilePath -> IO a) -> IO a
withTempDir ((FilePath -> IO a) -> IO a) -> (FilePath -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \ FilePath
tmpdir -> do
    ByteString
bs <- PackageIdentifier -> IO ByteString
getCabal PackageIdentifier
pkgid
    let filepath :: FilePath
filepath = FilePath
tmpdir FilePath -> FilePath -> FilePath
</> PackageIdentifier -> FilePath
showPkgId PackageIdentifier
pkgid FilePath -> FilePath -> FilePath
<.> FilePath
"cabal"
    FilePath -> ByteString -> IO ()
BL.writeFile FilePath
filepath ByteString
bs
    FilePath -> IO a
act FilePath
filepath
getCabals  :: PackageIdentifier -> PackageIdentifier
           -> IO (BL.ByteString, BL.ByteString)
getCabals :: PackageIdentifier
-> PackageIdentifier -> IO (ByteString, ByteString)
getCabals PackageIdentifier
pkgid1 PackageIdentifier
pkgid2 =
  (Repository LocalFile -> IO (ByteString, ByteString))
-> IO (ByteString, ByteString)
forall a. (Repository LocalFile -> IO a) -> IO a
withLocalRepo ((Repository LocalFile -> IO (ByteString, ByteString))
 -> IO (ByteString, ByteString))
-> (Repository LocalFile -> IO (ByteString, ByteString))
-> IO (ByteString, ByteString)
forall a b. (a -> b) -> a -> b
$ \Repository LocalFile
rep -> ((Throws VerificationError, Throws SomeRemoteError,
  Throws InvalidPackageException) =>
 IO (ByteString, ByteString))
-> IO (ByteString, ByteString)
forall a.
((Throws VerificationError, Throws SomeRemoteError,
  Throws InvalidPackageException) =>
 IO a)
-> IO a
uncheckClientErrors (((Throws VerificationError, Throws SomeRemoteError,
   Throws InvalidPackageException) =>
  IO (ByteString, ByteString))
 -> IO (ByteString, ByteString))
-> ((Throws VerificationError, Throws SomeRemoteError,
     Throws InvalidPackageException) =>
    IO (ByteString, ByteString))
-> IO (ByteString, ByteString)
forall a b. (a -> b) -> a -> b
$
    Repository LocalFile
-> (IndexCallbacks -> IO (ByteString, ByteString))
-> IO (ByteString, ByteString)
forall (down :: * -> *) a.
Repository down -> (IndexCallbacks -> IO a) -> IO a
withIndex Repository LocalFile
rep ((IndexCallbacks -> IO (ByteString, ByteString))
 -> IO (ByteString, ByteString))
-> (IndexCallbacks -> IO (ByteString, ByteString))
-> IO (ByteString, ByteString)
forall a b. (a -> b) -> a -> b
$ \ IndexCallbacks{Directory
DirectoryEntry -> IO (Some IndexEntry, Maybe DirectoryEntry)
Throws InvalidPackageException =>
PackageIdentifier -> IO (Trusted ByteString)
Throws InvalidPackageException =>
PackageIdentifier -> IO (Trusted Targets)
(Throws InvalidPackageException, Throws VerificationError) =>
PackageIdentifier -> IO (Trusted FileInfo)
(Throws InvalidPackageException, Throws VerificationError) =>
PackageIdentifier -> IO (Trusted Hash)
forall dec. DirectoryEntry -> IndexFile dec -> IO (IndexEntry dec)
forall dec. IndexFile dec -> IO (Maybe (IndexEntry dec))
indexDirectory :: Directory
indexLookupHash :: (Throws InvalidPackageException, Throws VerificationError) =>
PackageIdentifier -> IO (Trusted Hash)
indexLookupFileInfo :: (Throws InvalidPackageException, Throws VerificationError) =>
PackageIdentifier -> IO (Trusted FileInfo)
indexLookupMetadata :: Throws InvalidPackageException =>
PackageIdentifier -> IO (Trusted Targets)
indexLookupCabal :: Throws InvalidPackageException =>
PackageIdentifier -> IO (Trusted ByteString)
indexLookupFileEntry :: forall dec. DirectoryEntry -> IndexFile dec -> IO (IndexEntry dec)
indexLookupFile :: forall dec. IndexFile dec -> IO (Maybe (IndexEntry dec))
indexLookupEntry :: DirectoryEntry -> IO (Some IndexEntry, Maybe DirectoryEntry)
indexLookupEntry :: IndexCallbacks
-> DirectoryEntry -> IO (Some IndexEntry, Maybe DirectoryEntry)
indexLookupFile :: IndexCallbacks
-> forall dec. IndexFile dec -> IO (Maybe (IndexEntry dec))
indexLookupFileEntry :: IndexCallbacks
-> forall dec.
   DirectoryEntry -> IndexFile dec -> IO (IndexEntry dec)
indexLookupCabal :: IndexCallbacks
-> Throws InvalidPackageException =>
   PackageIdentifier -> IO (Trusted ByteString)
indexLookupMetadata :: IndexCallbacks
-> Throws InvalidPackageException =>
   PackageIdentifier -> IO (Trusted Targets)
indexLookupFileInfo :: IndexCallbacks
-> (Throws InvalidPackageException, Throws VerificationError) =>
   PackageIdentifier -> IO (Trusted FileInfo)
indexLookupHash :: IndexCallbacks
-> (Throws InvalidPackageException, Throws VerificationError) =>
   PackageIdentifier -> IO (Trusted Hash)
indexDirectory :: IndexCallbacks -> Directory
..} -> do
    ByteString
bs1 <- Trusted ByteString -> ByteString
forall a. Trusted a -> a
trusted (Trusted ByteString -> ByteString)
-> IO (Trusted ByteString) -> IO ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PackageIdentifier -> IO (Trusted ByteString)
Throws InvalidPackageException =>
PackageIdentifier -> IO (Trusted ByteString)
indexLookupCabal PackageIdentifier
pkgid1
    ByteString
bs2 <- Trusted ByteString -> ByteString
forall a. Trusted a -> a
trusted (Trusted ByteString -> ByteString)
-> IO (Trusted ByteString) -> IO ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PackageIdentifier -> IO (Trusted ByteString)
Throws InvalidPackageException =>
PackageIdentifier -> IO (Trusted ByteString)
indexLookupCabal PackageIdentifier
pkgid2
    (ByteString, ByteString) -> IO (ByteString, ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString
bs1,ByteString
bs2)
getFileInfo :: PackageIdentifier -> IO FileInfo
getFileInfo :: PackageIdentifier -> IO FileInfo
getFileInfo PackageIdentifier
pkgid =
  (Repository LocalFile -> IO FileInfo) -> IO FileInfo
forall a. (Repository LocalFile -> IO a) -> IO a
withLocalRepo ((Repository LocalFile -> IO FileInfo) -> IO FileInfo)
-> (Repository LocalFile -> IO FileInfo) -> IO FileInfo
forall a b. (a -> b) -> a -> b
$ \Repository LocalFile
rep -> ((Throws VerificationError, Throws SomeRemoteError,
  Throws InvalidPackageException) =>
 IO FileInfo)
-> IO FileInfo
forall a.
((Throws VerificationError, Throws SomeRemoteError,
  Throws InvalidPackageException) =>
 IO a)
-> IO a
uncheckClientErrors (((Throws VerificationError, Throws SomeRemoteError,
   Throws InvalidPackageException) =>
  IO FileInfo)
 -> IO FileInfo)
-> ((Throws VerificationError, Throws SomeRemoteError,
     Throws InvalidPackageException) =>
    IO FileInfo)
-> IO FileInfo
forall a b. (a -> b) -> a -> b
$
      Repository LocalFile
-> (IndexCallbacks -> IO FileInfo) -> IO FileInfo
forall (down :: * -> *) a.
Repository down -> (IndexCallbacks -> IO a) -> IO a
withIndex Repository LocalFile
rep ((IndexCallbacks -> IO FileInfo) -> IO FileInfo)
-> (IndexCallbacks -> IO FileInfo) -> IO FileInfo
forall a b. (a -> b) -> a -> b
$ \ IndexCallbacks{Directory
DirectoryEntry -> IO (Some IndexEntry, Maybe DirectoryEntry)
Throws InvalidPackageException =>
PackageIdentifier -> IO (Trusted ByteString)
Throws InvalidPackageException =>
PackageIdentifier -> IO (Trusted Targets)
(Throws InvalidPackageException, Throws VerificationError) =>
PackageIdentifier -> IO (Trusted FileInfo)
(Throws InvalidPackageException, Throws VerificationError) =>
PackageIdentifier -> IO (Trusted Hash)
forall dec. DirectoryEntry -> IndexFile dec -> IO (IndexEntry dec)
forall dec. IndexFile dec -> IO (Maybe (IndexEntry dec))
indexDirectory :: Directory
indexLookupHash :: (Throws InvalidPackageException, Throws VerificationError) =>
PackageIdentifier -> IO (Trusted Hash)
indexLookupFileInfo :: (Throws InvalidPackageException, Throws VerificationError) =>
PackageIdentifier -> IO (Trusted FileInfo)
indexLookupMetadata :: Throws InvalidPackageException =>
PackageIdentifier -> IO (Trusted Targets)
indexLookupCabal :: Throws InvalidPackageException =>
PackageIdentifier -> IO (Trusted ByteString)
indexLookupFileEntry :: forall dec. DirectoryEntry -> IndexFile dec -> IO (IndexEntry dec)
indexLookupFile :: forall dec. IndexFile dec -> IO (Maybe (IndexEntry dec))
indexLookupEntry :: DirectoryEntry -> IO (Some IndexEntry, Maybe DirectoryEntry)
indexLookupEntry :: IndexCallbacks
-> DirectoryEntry -> IO (Some IndexEntry, Maybe DirectoryEntry)
indexLookupFile :: IndexCallbacks
-> forall dec. IndexFile dec -> IO (Maybe (IndexEntry dec))
indexLookupFileEntry :: IndexCallbacks
-> forall dec.
   DirectoryEntry -> IndexFile dec -> IO (IndexEntry dec)
indexLookupCabal :: IndexCallbacks
-> Throws InvalidPackageException =>
   PackageIdentifier -> IO (Trusted ByteString)
indexLookupMetadata :: IndexCallbacks
-> Throws InvalidPackageException =>
   PackageIdentifier -> IO (Trusted Targets)
indexLookupFileInfo :: IndexCallbacks
-> (Throws InvalidPackageException, Throws VerificationError) =>
   PackageIdentifier -> IO (Trusted FileInfo)
indexLookupHash :: IndexCallbacks
-> (Throws InvalidPackageException, Throws VerificationError) =>
   PackageIdentifier -> IO (Trusted Hash)
indexDirectory :: IndexCallbacks -> Directory
..} ->
        Trusted FileInfo -> FileInfo
forall a. Trusted a -> a
trusted (Trusted FileInfo -> FileInfo)
-> IO (Trusted FileInfo) -> IO FileInfo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PackageIdentifier -> IO (Trusted FileInfo)
(Throws InvalidPackageException, Throws VerificationError) =>
PackageIdentifier -> IO (Trusted FileInfo)
indexLookupFileInfo PackageIdentifier
pkgid
getPackageDescription :: PackageIdentifier -> IO (Maybe PackageDescription)
getPackageDescription :: PackageIdentifier -> IO (Maybe PackageDescription)
getPackageDescription PackageIdentifier
pkgid =
#if (defined(MIN_VERSION_simple_cabal) && MIN_VERSION_simple_cabal(0,1,2))
  do
  ByteString
cabal <- PackageIdentifier -> IO ByteString
getCabal PackageIdentifier
pkgid
  [(FlagName, Bool)] -> ByteString -> IO (Maybe PackageDescription)
parseFinalPackageDescription [] (ByteString -> IO (Maybe PackageDescription))
-> ByteString -> IO (Maybe PackageDescription)
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
BL.toStrict ByteString
cabal
#else
  Just <$> withCabalFile pkgid (finalPackageDescription [])
#endif
getPackageDescription' :: PackageIdentifier -> IO PackageDescription
getPackageDescription' :: PackageIdentifier -> IO PackageDescription
getPackageDescription' PackageIdentifier
pkgid = do
  Maybe PackageDescription
mfpd <- PackageIdentifier -> IO (Maybe PackageDescription)
getPackageDescription PackageIdentifier
pkgid
  IO PackageDescription
-> (PackageDescription -> IO PackageDescription)
-> Maybe PackageDescription
-> IO PackageDescription
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (FilePath -> IO PackageDescription
forall a. HasCallStack => FilePath -> a
error FilePath
"Failed to parse cabal file") PackageDescription -> IO PackageDescription
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PackageDescription
mfpd
withLocalRepo :: (Repository Local.LocalFile -> IO a) -> IO a
withLocalRepo :: (Repository LocalFile -> IO a) -> IO a
withLocalRepo Repository LocalFile -> IO a
action = do
  FilePath
home <- IO FilePath
getHomeDirectory
  Path Absolute
localrepo <- (FsPath -> IO (Path Absolute)
Path.makeAbsolute (FsPath -> IO (Path Absolute))
-> (FilePath -> FsPath) -> FilePath -> IO (Path Absolute)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FsPath
Path.fromFilePath) (FilePath
home FilePath -> FilePath -> FilePath
</> FilePath
".cabal")
  Path Absolute
localcache <- (FsPath -> IO (Path Absolute)
Path.makeAbsolute (FsPath -> IO (Path Absolute))
-> (FilePath -> FsPath) -> FilePath -> IO (Path Absolute)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FsPath
Path.fromFilePath) (FilePath
home FilePath -> FilePath -> FilePath
</> FilePath
".cabal/packages/hackage.haskell.org")
  Path Absolute
-> Cache
-> RepoLayout
-> IndexLayout
-> (LogMessage -> IO ())
-> (Repository LocalFile -> IO a)
-> IO a
forall a.
Path Absolute
-> Cache
-> RepoLayout
-> IndexLayout
-> (LogMessage -> IO ())
-> (Repository LocalFile -> IO a)
-> IO a
Local.withRepository Path Absolute
localrepo (Path Absolute -> Cache
cache Path Absolute
localcache) RepoLayout
hackageRepoLayout IndexLayout
hackageIndexLayout LogMessage -> IO ()
forall a. Pretty a => a -> IO ()
logTUF Repository LocalFile -> IO a
action
  where
    
    cache :: Path Absolute -> Cache
cache Path Absolute
localcache = Cache :: Path Absolute -> CacheLayout -> Cache
Cache.Cache {
        cacheRoot :: Path Absolute
Cache.cacheRoot   = Path Absolute
localcache
      , cacheLayout :: CacheLayout
Cache.cacheLayout = CacheLayout
cabalCacheLayout
        { cacheLayoutIndexTar :: CachePath
cacheLayoutIndexTar   = Path Unrooted -> CachePath
forall root. Path Unrooted -> Path root
Path.rootPath (Path Unrooted -> CachePath) -> Path Unrooted -> CachePath
forall a b. (a -> b) -> a -> b
$ FilePath -> Path Unrooted
Path.fragment FilePath
"01-index.tar"
        , cacheLayoutIndexIdx :: CachePath
cacheLayoutIndexIdx   = Path Unrooted -> CachePath
forall root. Path Unrooted -> Path root
Path.rootPath (Path Unrooted -> CachePath) -> Path Unrooted -> CachePath
forall a b. (a -> b) -> a -> b
$ FilePath -> Path Unrooted
Path.fragment FilePath
"01-index.tar.idx"
        , cacheLayoutIndexTarGz :: CachePath
cacheLayoutIndexTarGz = Path Unrooted -> CachePath
forall root. Path Unrooted -> Path root
Path.rootPath (Path Unrooted -> CachePath) -> Path Unrooted -> CachePath
forall a b. (a -> b) -> a -> b
$ FilePath -> Path Unrooted
Path.fragment FilePath
"01-index.tar.gz"}
    }
    logTUF :: a -> IO ()
logTUF a
msg = FilePath -> IO ()
putStrLn (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"# " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ a -> FilePath
forall a. Pretty a => a -> FilePath
pretty a
msg
packageVersions :: PackageName -> IO [Version]
packageVersions :: PackageName -> IO [Version]
packageVersions PackageName
pkgname =
  (Repository LocalFile -> IO [Version]) -> IO [Version]
forall a. (Repository LocalFile -> IO a) -> IO a
withLocalRepo ((Repository LocalFile -> IO [Version]) -> IO [Version])
-> (Repository LocalFile -> IO [Version]) -> IO [Version]
forall a b. (a -> b) -> a -> b
$ \Repository LocalFile
rep -> ((Throws VerificationError, Throws SomeRemoteError,
  Throws InvalidPackageException) =>
 IO [Version])
-> IO [Version]
forall a.
((Throws VerificationError, Throws SomeRemoteError,
  Throws InvalidPackageException) =>
 IO a)
-> IO a
uncheckClientErrors (((Throws VerificationError, Throws SomeRemoteError,
   Throws InvalidPackageException) =>
  IO [Version])
 -> IO [Version])
-> ((Throws VerificationError, Throws SomeRemoteError,
     Throws InvalidPackageException) =>
    IO [Version])
-> IO [Version]
forall a b. (a -> b) -> a -> b
$ do
    Directory
dir <- Repository LocalFile -> IO Directory
forall (down :: * -> *). Repository down -> IO Directory
getDirectory Repository LocalFile
rep
    let pkg :: FilePath
pkg = PackageName -> FilePath
unPackageName PackageName
pkgname
    [Version] -> IO [Version]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Version] -> IO [Version]) -> [Version] -> IO [Version]
forall a b. (a -> b) -> a -> b
$ [Version] -> [Version]
forall a. Ord a => [a] -> [a]
L.sort ([Version] -> [Version])
-> ([(DirectoryEntry, IndexPath, Maybe (Some IndexFile))]
    -> [Version])
-> [(DirectoryEntry, IndexPath, Maybe (Some IndexFile))]
-> [Version]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((DirectoryEntry, IndexPath, Maybe (Some IndexFile))
 -> Maybe Version)
-> [(DirectoryEntry, IndexPath, Maybe (Some IndexFile))]
-> [Version]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (FilePath -> IndexPath -> Maybe Version
extractPkgVersion FilePath
pkg (IndexPath -> Maybe Version)
-> ((DirectoryEntry, IndexPath, Maybe (Some IndexFile))
    -> IndexPath)
-> (DirectoryEntry, IndexPath, Maybe (Some IndexFile))
-> Maybe Version
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DirectoryEntry, IndexPath, Maybe (Some IndexFile)) -> IndexPath
forall a b c. (a, b, c) -> b
second) ([(DirectoryEntry, IndexPath, Maybe (Some IndexFile))]
 -> [Version])
-> [(DirectoryEntry, IndexPath, Maybe (Some IndexFile))]
-> [Version]
forall a b. (a -> b) -> a -> b
$ Directory -> [(DirectoryEntry, IndexPath, Maybe (Some IndexFile))]
directoryEntries Directory
dir
  where
    second :: (a, b, c) -> b
second (a
_,b
b,c
_) = b
b
    extractPkgVersion :: String -> IndexPath -> Maybe Version
    extractPkgVersion :: FilePath -> IndexPath -> Maybe Version
extractPkgVersion FilePath
pkg IndexPath
path =
      if IndexPath -> FilePath
forall a. Path a -> FilePath
Path.takeExtension IndexPath
path FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
".cabal" then
        let namever :: FilePath
namever = (Path Unrooted -> FilePath
Path.toUnrootedFilePath (Path Unrooted -> FilePath)
-> (IndexPath -> Path Unrooted) -> IndexPath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IndexPath -> Path Unrooted
forall root. Path root -> Path Unrooted
Path.unrootPath (IndexPath -> Path Unrooted)
-> (IndexPath -> IndexPath) -> IndexPath -> Path Unrooted
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IndexPath -> IndexPath
forall a. Path a -> Path a
Path.takeDirectory) IndexPath
path
        in if FilePath -> FilePath
takeDirectory FilePath
namever FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
pkg
           then Version -> Maybe Version
forall a. a -> Maybe a
Just (Version -> Maybe Version) -> Version -> Maybe Version
forall a b. (a -> b) -> a -> b
$ Version -> Version
mkVersion' (Version -> Version)
-> (FilePath -> Version) -> FilePath -> Version
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HasCallStack => FilePath -> Version
FilePath -> Version
readVersion (FilePath -> Version) -> FilePath -> Version
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
takeFileName FilePath
namever
           else Maybe Version
forall a. Maybe a
Nothing
      else Maybe Version
forall a. Maybe a
Nothing
preferredVersions :: PackageName -> IO (Maybe BL.ByteString)
preferredVersions :: PackageName -> IO (Maybe ByteString)
preferredVersions PackageName
pkgname =
  (Repository LocalFile -> IO (Maybe ByteString))
-> IO (Maybe ByteString)
forall a. (Repository LocalFile -> IO a) -> IO a
withLocalRepo ((Repository LocalFile -> IO (Maybe ByteString))
 -> IO (Maybe ByteString))
-> (Repository LocalFile -> IO (Maybe ByteString))
-> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \Repository LocalFile
rep -> ((Throws VerificationError, Throws SomeRemoteError,
  Throws InvalidPackageException) =>
 IO (Maybe ByteString))
-> IO (Maybe ByteString)
forall a.
((Throws VerificationError, Throws SomeRemoteError,
  Throws InvalidPackageException) =>
 IO a)
-> IO a
uncheckClientErrors (((Throws VerificationError, Throws SomeRemoteError,
   Throws InvalidPackageException) =>
  IO (Maybe ByteString))
 -> IO (Maybe ByteString))
-> ((Throws VerificationError, Throws SomeRemoteError,
     Throws InvalidPackageException) =>
    IO (Maybe ByteString))
-> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$
    Repository LocalFile
-> (IndexCallbacks -> IO (Maybe ByteString))
-> IO (Maybe ByteString)
forall (down :: * -> *) a.
Repository down -> (IndexCallbacks -> IO a) -> IO a
withIndex Repository LocalFile
rep ((IndexCallbacks -> IO (Maybe ByteString))
 -> IO (Maybe ByteString))
-> (IndexCallbacks -> IO (Maybe ByteString))
-> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \ IndexCallbacks{Directory
DirectoryEntry -> IO (Some IndexEntry, Maybe DirectoryEntry)
Throws InvalidPackageException =>
PackageIdentifier -> IO (Trusted ByteString)
Throws InvalidPackageException =>
PackageIdentifier -> IO (Trusted Targets)
(Throws InvalidPackageException, Throws VerificationError) =>
PackageIdentifier -> IO (Trusted FileInfo)
(Throws InvalidPackageException, Throws VerificationError) =>
PackageIdentifier -> IO (Trusted Hash)
forall dec. DirectoryEntry -> IndexFile dec -> IO (IndexEntry dec)
forall dec. IndexFile dec -> IO (Maybe (IndexEntry dec))
indexDirectory :: Directory
indexLookupHash :: (Throws InvalidPackageException, Throws VerificationError) =>
PackageIdentifier -> IO (Trusted Hash)
indexLookupFileInfo :: (Throws InvalidPackageException, Throws VerificationError) =>
PackageIdentifier -> IO (Trusted FileInfo)
indexLookupMetadata :: Throws InvalidPackageException =>
PackageIdentifier -> IO (Trusted Targets)
indexLookupCabal :: Throws InvalidPackageException =>
PackageIdentifier -> IO (Trusted ByteString)
indexLookupFileEntry :: forall dec. DirectoryEntry -> IndexFile dec -> IO (IndexEntry dec)
indexLookupFile :: forall dec. IndexFile dec -> IO (Maybe (IndexEntry dec))
indexLookupEntry :: DirectoryEntry -> IO (Some IndexEntry, Maybe DirectoryEntry)
indexLookupEntry :: IndexCallbacks
-> DirectoryEntry -> IO (Some IndexEntry, Maybe DirectoryEntry)
indexLookupFile :: IndexCallbacks
-> forall dec. IndexFile dec -> IO (Maybe (IndexEntry dec))
indexLookupFileEntry :: IndexCallbacks
-> forall dec.
   DirectoryEntry -> IndexFile dec -> IO (IndexEntry dec)
indexLookupCabal :: IndexCallbacks
-> Throws InvalidPackageException =>
   PackageIdentifier -> IO (Trusted ByteString)
indexLookupMetadata :: IndexCallbacks
-> Throws InvalidPackageException =>
   PackageIdentifier -> IO (Trusted Targets)
indexLookupFileInfo :: IndexCallbacks
-> (Throws InvalidPackageException, Throws VerificationError) =>
   PackageIdentifier -> IO (Trusted FileInfo)
indexLookupHash :: IndexCallbacks
-> (Throws InvalidPackageException, Throws VerificationError) =>
   PackageIdentifier -> IO (Trusted Hash)
indexDirectory :: IndexCallbacks -> Directory
..} ->
    (IndexEntry () -> ByteString)
-> Maybe (IndexEntry ()) -> Maybe ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap IndexEntry () -> ByteString
forall dec. IndexEntry dec -> ByteString
indexEntryContent (Maybe (IndexEntry ()) -> Maybe ByteString)
-> IO (Maybe (IndexEntry ())) -> IO (Maybe ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IndexFile () -> IO (Maybe (IndexEntry ()))
forall dec. IndexFile dec -> IO (Maybe (IndexEntry dec))
indexLookupFile (PackageName -> IndexFile ()
IndexPkgPrefs PackageName
pkgname)
indexFiles :: IO [String]
indexFiles :: IO [FilePath]
indexFiles =
  (Repository LocalFile -> IO [FilePath]) -> IO [FilePath]
forall a. (Repository LocalFile -> IO a) -> IO a
withLocalRepo ((Repository LocalFile -> IO [FilePath]) -> IO [FilePath])
-> (Repository LocalFile -> IO [FilePath]) -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ \Repository LocalFile
rep -> ((Throws VerificationError, Throws SomeRemoteError,
  Throws InvalidPackageException) =>
 IO [FilePath])
-> IO [FilePath]
forall a.
((Throws VerificationError, Throws SomeRemoteError,
  Throws InvalidPackageException) =>
 IO a)
-> IO a
uncheckClientErrors (((Throws VerificationError, Throws SomeRemoteError,
   Throws InvalidPackageException) =>
  IO [FilePath])
 -> IO [FilePath])
-> ((Throws VerificationError, Throws SomeRemoteError,
     Throws InvalidPackageException) =>
    IO [FilePath])
-> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ do
    Directory
dir <- Repository LocalFile -> IO Directory
forall (down :: * -> *). Repository down -> IO Directory
getDirectory Repository LocalFile
rep
    [FilePath] -> IO [FilePath]
forall (m :: * -> *) a. Monad m => a -> m a
return ([FilePath] -> IO [FilePath]) -> [FilePath] -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ ((DirectoryEntry, IndexPath, Maybe (Some IndexFile)) -> FilePath)
-> [(DirectoryEntry, IndexPath, Maybe (Some IndexFile))]
-> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (DirectoryEntry, IndexPath, Maybe (Some IndexFile)) -> FilePath
forall a root c. (a, Path root, c) -> FilePath
dirEntryPath (Directory -> [(DirectoryEntry, IndexPath, Maybe (Some IndexFile))]
directoryEntries Directory
dir)
  where
    second :: (a, b, c) -> b
second (a
_,b
b,c
_) = b
b
    dirEntryPath :: (a, Path root, c) -> FilePath
dirEntryPath = Path Unrooted -> FilePath
Path.toUnrootedFilePath (Path Unrooted -> FilePath)
-> ((a, Path root, c) -> Path Unrooted)
-> (a, Path root, c)
-> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Path root -> Path Unrooted
forall root. Path root -> Path Unrooted
Path.unrootPath (Path root -> Path Unrooted)
-> ((a, Path root, c) -> Path root)
-> (a, Path root, c)
-> Path Unrooted
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, Path root, c) -> Path root
forall a b c. (a, b, c) -> b
second
latestVersion :: PackageName -> IO (Maybe Version)
latestVersion :: PackageName -> IO (Maybe Version)
latestVersion PackageName
pkgname = do
  [Version]
versions <- PackageName -> IO [Version]
packageVersions PackageName
pkgname
  if [Version] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Version]
versions then Maybe Version -> IO (Maybe Version)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Version
forall a. Maybe a
Nothing
    else Maybe Version -> IO (Maybe Version)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Version -> IO (Maybe Version))
-> Maybe Version -> IO (Maybe Version)
forall a b. (a -> b) -> a -> b
$ Version -> Maybe Version
forall a. a -> Maybe a
Just (Version -> Maybe Version) -> Version -> Maybe Version
forall a b. (a -> b) -> a -> b
$ [Version] -> Version
forall a. [a] -> a
last [Version]
versions
getTimestamp :: PackageIdentifier -> IO (Maybe UTCTime)
getTimestamp :: PackageIdentifier -> IO (Maybe UTCTime)
getTimestamp PackageIdentifier
pkgid =
  (Repository LocalFile -> IO (Maybe UTCTime)) -> IO (Maybe UTCTime)
forall a. (Repository LocalFile -> IO a) -> IO a
withLocalRepo ((Repository LocalFile -> IO (Maybe UTCTime))
 -> IO (Maybe UTCTime))
-> (Repository LocalFile -> IO (Maybe UTCTime))
-> IO (Maybe UTCTime)
forall a b. (a -> b) -> a -> b
$ \Repository LocalFile
rep -> ((Throws VerificationError, Throws SomeRemoteError,
  Throws InvalidPackageException) =>
 IO (Maybe UTCTime))
-> IO (Maybe UTCTime)
forall a.
((Throws VerificationError, Throws SomeRemoteError,
  Throws InvalidPackageException) =>
 IO a)
-> IO a
uncheckClientErrors (((Throws VerificationError, Throws SomeRemoteError,
   Throws InvalidPackageException) =>
  IO (Maybe UTCTime))
 -> IO (Maybe UTCTime))
-> ((Throws VerificationError, Throws SomeRemoteError,
     Throws InvalidPackageException) =>
    IO (Maybe UTCTime))
-> IO (Maybe UTCTime)
forall a b. (a -> b) -> a -> b
$
    Repository LocalFile
-> (IndexCallbacks -> IO (Maybe UTCTime)) -> IO (Maybe UTCTime)
forall (down :: * -> *) a.
Repository down -> (IndexCallbacks -> IO a) -> IO a
withIndex Repository LocalFile
rep ((IndexCallbacks -> IO (Maybe UTCTime)) -> IO (Maybe UTCTime))
-> (IndexCallbacks -> IO (Maybe UTCTime)) -> IO (Maybe UTCTime)
forall a b. (a -> b) -> a -> b
$ \ IndexCallbacks{Directory
DirectoryEntry -> IO (Some IndexEntry, Maybe DirectoryEntry)
Throws InvalidPackageException =>
PackageIdentifier -> IO (Trusted ByteString)
Throws InvalidPackageException =>
PackageIdentifier -> IO (Trusted Targets)
(Throws InvalidPackageException, Throws VerificationError) =>
PackageIdentifier -> IO (Trusted FileInfo)
(Throws InvalidPackageException, Throws VerificationError) =>
PackageIdentifier -> IO (Trusted Hash)
forall dec. DirectoryEntry -> IndexFile dec -> IO (IndexEntry dec)
forall dec. IndexFile dec -> IO (Maybe (IndexEntry dec))
indexDirectory :: Directory
indexLookupHash :: (Throws InvalidPackageException, Throws VerificationError) =>
PackageIdentifier -> IO (Trusted Hash)
indexLookupFileInfo :: (Throws InvalidPackageException, Throws VerificationError) =>
PackageIdentifier -> IO (Trusted FileInfo)
indexLookupMetadata :: Throws InvalidPackageException =>
PackageIdentifier -> IO (Trusted Targets)
indexLookupCabal :: Throws InvalidPackageException =>
PackageIdentifier -> IO (Trusted ByteString)
indexLookupFileEntry :: forall dec. DirectoryEntry -> IndexFile dec -> IO (IndexEntry dec)
indexLookupFile :: forall dec. IndexFile dec -> IO (Maybe (IndexEntry dec))
indexLookupEntry :: DirectoryEntry -> IO (Some IndexEntry, Maybe DirectoryEntry)
indexLookupEntry :: IndexCallbacks
-> DirectoryEntry -> IO (Some IndexEntry, Maybe DirectoryEntry)
indexLookupFile :: IndexCallbacks
-> forall dec. IndexFile dec -> IO (Maybe (IndexEntry dec))
indexLookupFileEntry :: IndexCallbacks
-> forall dec.
   DirectoryEntry -> IndexFile dec -> IO (IndexEntry dec)
indexLookupCabal :: IndexCallbacks
-> Throws InvalidPackageException =>
   PackageIdentifier -> IO (Trusted ByteString)
indexLookupMetadata :: IndexCallbacks
-> Throws InvalidPackageException =>
   PackageIdentifier -> IO (Trusted Targets)
indexLookupFileInfo :: IndexCallbacks
-> (Throws InvalidPackageException, Throws VerificationError) =>
   PackageIdentifier -> IO (Trusted FileInfo)
indexLookupHash :: IndexCallbacks
-> (Throws InvalidPackageException, Throws VerificationError) =>
   PackageIdentifier -> IO (Trusted Hash)
indexDirectory :: IndexCallbacks -> Directory
..} ->
    (IndexEntry () -> UTCTime)
-> Maybe (IndexEntry ()) -> Maybe UTCTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (POSIXTime -> UTCTime
posixSecondsToUTCTime (POSIXTime -> UTCTime)
-> (IndexEntry () -> POSIXTime) -> IndexEntry () -> UTCTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EpochTime -> POSIXTime
forall a b. (Real a, Fractional b) => a -> b
realToFrac (EpochTime -> POSIXTime)
-> (IndexEntry () -> EpochTime) -> IndexEntry () -> POSIXTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IndexEntry () -> EpochTime
forall dec. IndexEntry dec -> EpochTime
indexEntryTime) (Maybe (IndexEntry ()) -> Maybe UTCTime)
-> IO (Maybe (IndexEntry ())) -> IO (Maybe UTCTime)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
    IndexFile () -> IO (Maybe (IndexEntry ()))
forall dec. IndexFile dec -> IO (Maybe (IndexEntry dec))
indexLookupFile (PackageIdentifier -> IndexFile ()
IndexPkgCabal PackageIdentifier
pkgid)
packageIdOrLatest :: PackageIdentifier -> IO PackageIdentifier
packageIdOrLatest :: PackageIdentifier -> IO PackageIdentifier
packageIdOrLatest PackageIdentifier
pkgid = do
  let name :: PackageName
name = PackageIdentifier -> PackageName
pkgName PackageIdentifier
pkgid
  if PackageIdentifier -> Version
pkgVersion PackageIdentifier
pkgid Version -> Version -> Bool
forall a. Eq a => a -> a -> Bool
== Version
nullVersion then do
    Maybe Version
mlatest <- PackageName -> IO (Maybe Version)
latestVersion PackageName
name
    PackageIdentifier -> IO PackageIdentifier
forall (m :: * -> *) a. Monad m => a -> m a
return (PackageIdentifier -> IO PackageIdentifier)
-> PackageIdentifier -> IO PackageIdentifier
forall a b. (a -> b) -> a -> b
$ PackageIdentifier
-> (Version -> PackageIdentifier)
-> Maybe Version
-> PackageIdentifier
forall b a. b -> (a -> b) -> Maybe a -> b
maybe PackageIdentifier
pkgid (PackageName -> Version -> PackageIdentifier
PackageIdentifier PackageName
name) Maybe Version
mlatest
    else PackageIdentifier -> IO PackageIdentifier
forall (m :: * -> *) a. Monad m => a -> m a
return PackageIdentifier
pkgid
listPackages :: IO [String]
listPackages :: IO [FilePath]
listPackages =
  (Repository LocalFile -> IO [FilePath]) -> IO [FilePath]
forall a. (Repository LocalFile -> IO a) -> IO a
withLocalRepo ((Repository LocalFile -> IO [FilePath]) -> IO [FilePath])
-> (Repository LocalFile -> IO [FilePath]) -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ \Repository LocalFile
rep -> ((Throws VerificationError, Throws SomeRemoteError,
  Throws InvalidPackageException) =>
 IO [FilePath])
-> IO [FilePath]
forall a.
((Throws VerificationError, Throws SomeRemoteError,
  Throws InvalidPackageException) =>
 IO a)
-> IO a
uncheckClientErrors (((Throws VerificationError, Throws SomeRemoteError,
   Throws InvalidPackageException) =>
  IO [FilePath])
 -> IO [FilePath])
-> ((Throws VerificationError, Throws SomeRemoteError,
     Throws InvalidPackageException) =>
    IO [FilePath])
-> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ do
    Directory
dir <- Repository LocalFile -> IO Directory
forall (down :: * -> *). Repository down -> IO Directory
getDirectory Repository LocalFile
rep
    [FilePath] -> IO [FilePath]
forall (m :: * -> *) a. Monad m => a -> m a
return ([FilePath] -> IO [FilePath]) -> [FilePath] -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ [FilePath] -> [FilePath]
forall a. Eq a => [a] -> [a]
L.nub ([FilePath] -> [FilePath]) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> a -> b
$ ((DirectoryEntry, IndexPath, Maybe (Some IndexFile))
 -> Maybe FilePath)
-> [(DirectoryEntry, IndexPath, Maybe (Some IndexFile))]
-> [FilePath]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (IndexPath -> Maybe FilePath
forall root. Path root -> Maybe FilePath
extractPkg (IndexPath -> Maybe FilePath)
-> ((DirectoryEntry, IndexPath, Maybe (Some IndexFile))
    -> IndexPath)
-> (DirectoryEntry, IndexPath, Maybe (Some IndexFile))
-> Maybe FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DirectoryEntry, IndexPath, Maybe (Some IndexFile)) -> IndexPath
forall a b c. (a, b, c) -> b
second) (Directory -> [(DirectoryEntry, IndexPath, Maybe (Some IndexFile))]
directoryEntries Directory
dir)
  where
    extractPkg :: Path root -> Maybe FilePath
extractPkg Path root
path =
      if Path root -> FilePath
forall a. Path a -> FilePath
Path.takeExtension Path root
path FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
".cabal" then
        (FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just (FilePath -> Maybe FilePath)
-> (Path root -> FilePath) -> Path root -> Maybe FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> FilePath -> FilePath
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'/') (FilePath -> FilePath)
-> (Path root -> FilePath) -> Path root -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Path Unrooted -> FilePath
Path.toUnrootedFilePath (Path Unrooted -> FilePath)
-> (Path root -> Path Unrooted) -> Path root -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Path root -> Path Unrooted
forall root. Path root -> Path Unrooted
Path.unrootPath) Path root
path
        else Maybe FilePath
forall a. Maybe a
Nothing
    second :: (a, b, c) -> b
second (a
_,b
b,c
_) = b
b