-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | The command-line interface for Cabal and Hackage. -- -- The 'cabal' command-line program simplifies the process of managing -- Haskell software by automating the fetching, configuration, -- compilation and installation of Haskell libraries and programs. @package cabal-install @version 3.10.1.0 module Distribution.Client.Compat.Directory -- | Change the time at which the file or directory was last modified. -- -- The operation may fail with: -- -- -- -- Some caveats for POSIX systems: -- -- setModificationTime :: FilePath -> UTCTime -> IO () -- | Create a file symbolic link. The target path can be either -- absolute or relative and need not refer to an existing file. The order -- of arguments follows the POSIX convention. -- -- To remove an existing file symbolic link, use removeFile. -- -- Although the distinction between file symbolic links and -- directory symbolic links does not exist on POSIX systems, on -- Windows this is an intrinsic property of every symbolic link and -- cannot be changed without recreating the link. A file symbolic link -- that actually points to a directory will fail to dereference and vice -- versa. Moreover, creating symbolic links on Windows may require -- privileges unavailable to users outside the Administrators group. -- Portable programs that use symbolic links should take both into -- consideration. -- -- On Windows, the function is implemented using -- CreateSymbolicLink. Since 1.3.3.0, the -- SYMBOLIC_LINK_FLAG_ALLOW_UNPRIVILEGED_CREATE flag is included -- if supported by the operating system. On POSIX, the function uses -- symlink and is therefore atomic. -- -- Windows-specific errors: This operation may fail with -- permissionErrorType if the user lacks the privileges to create -- symbolic links. It may also fail with illegalOperationErrorType -- if the file system does not support symbolic links. createFileLink :: FilePath -> FilePath -> IO () -- | Check whether an existing path is a symbolic link. If -- path is a regular file or directory, False is -- returned. If path does not exist or is otherwise -- inaccessible, an exception is thrown (see below). -- -- On Windows, this checks for FILE_ATTRIBUTE_REPARSE_POINT. In -- addition to symbolic links, the function also returns true on junction -- points. On POSIX systems, this checks for S_IFLNK. -- -- The operation may fail with: -- -- pathIsSymbolicLink :: FilePath -> IO Bool -- | Retrieve the target path of either a file or directory symbolic link. -- The returned path may not be absolute, may not exist, and may not even -- be a valid path. -- -- On Windows systems, this calls DeviceIoControl with -- FSCTL_GET_REPARSE_POINT. In addition to symbolic links, the -- function also works on junction points. On POSIX systems, this calls -- readlink. -- -- Windows-specific errors: This operation may fail with -- illegalOperationErrorType if the file system does not support -- symbolic links. getSymbolicLinkTarget :: FilePath -> IO FilePath module Distribution.Client.Compat.ExecutablePath -- | Returns the absolute pathname of the current executable. -- -- Note that for scripts and interactive sessions, this is the path to -- the interpreter (e.g. ghci.) -- -- Since: 4.6.0.0 getExecutablePath :: IO FilePath module Distribution.Client.Compat.Orphans instance Data.Binary.Class.Binary Network.URI.URI instance Distribution.Utils.Structured.Structured Network.URI.URI instance Data.Binary.Class.Binary Network.URI.URIAuth instance Data.Binary.Class.Binary GHC.Exception.Type.SomeException instance Distribution.Utils.Structured.Structured GHC.Exception.Type.SomeException -- | This module does two things: -- -- -- -- This module is a superset of Distribution.Compat.Prelude (which -- this module re-exports) module Distribution.Client.Compat.Prelude prettyShow :: Pretty a => a -> String data Verbosity -- | Parse a String with given ParsecParser. Trailing -- whitespace is accepted. explicitEitherParsec :: ParsecParser a -> String -> Either String a -- | Parse a String with lexemeParsec. eitherParsec :: Parsec a => String -> Either String a -- | Parse a String with lexemeParsec. simpleParsec :: Parsec a => String -> Maybe a -- | Class for parsing with parsec. Mainly used for -- .cabal file fields. -- -- For parsing .cabal like file structure, see -- Distribution.Fields. class Parsec a parsec :: (Parsec a, CabalParsing m) => m a -- | Parsing class which -- -- class (CharParsing m, MonadPlus m, MonadFail m) => CabalParsing (m :: Type -> Type) class Pretty a pretty :: Pretty a => a -> Doc prettyVersioned :: Pretty a => CabalSpecVersion -> a -> Doc -- | Types related to build reporting module Distribution.Client.BuildReports.Types data ReportLevel NoReports :: ReportLevel AnonymousReports :: ReportLevel DetailedReports :: ReportLevel data BuildReport BuildReport :: PackageIdentifier -> OS -> Arch -> CompilerId -> PackageIdentifier -> FlagAssignment -> [PackageIdentifier] -> InstallOutcome -> Outcome -> Outcome -> BuildReport -- | The package this build report is about [package] :: BuildReport -> PackageIdentifier -- | The OS and Arch the package was built on [os] :: BuildReport -> OS [arch] :: BuildReport -> Arch -- | The Haskell compiler (and hopefully version) used [compiler] :: BuildReport -> CompilerId -- | The uploading client, ie cabal-install-x.y.z [client] :: BuildReport -> PackageIdentifier -- | Which configurations flags we used [flagAssignment] :: BuildReport -> FlagAssignment -- | Which dependent packages we were using exactly [dependencies] :: BuildReport -> [PackageIdentifier] -- | Did installing work ok? [installOutcome] :: BuildReport -> InstallOutcome -- | Configure outcome, did configure work ok? [docsOutcome] :: BuildReport -> Outcome -- | Configure outcome, did configure work ok? [testsOutcome] :: BuildReport -> Outcome data InstallOutcome PlanningFailed :: InstallOutcome DependencyFailed :: PackageIdentifier -> InstallOutcome DownloadFailed :: InstallOutcome UnpackFailed :: InstallOutcome SetupFailed :: InstallOutcome ConfigureFailed :: InstallOutcome BuildFailed :: InstallOutcome TestsFailed :: InstallOutcome InstallFailed :: InstallOutcome InstallOk :: InstallOutcome data Outcome NotTried :: Outcome Failed :: Outcome Ok :: Outcome instance GHC.Generics.Generic Distribution.Client.BuildReports.Types.ReportLevel instance GHC.Show.Show Distribution.Client.BuildReports.Types.ReportLevel instance GHC.Enum.Bounded Distribution.Client.BuildReports.Types.ReportLevel instance GHC.Enum.Enum Distribution.Client.BuildReports.Types.ReportLevel instance GHC.Classes.Ord Distribution.Client.BuildReports.Types.ReportLevel instance GHC.Classes.Eq Distribution.Client.BuildReports.Types.ReportLevel instance GHC.Generics.Generic Distribution.Client.BuildReports.Types.InstallOutcome instance GHC.Show.Show Distribution.Client.BuildReports.Types.InstallOutcome instance GHC.Classes.Eq Distribution.Client.BuildReports.Types.InstallOutcome instance GHC.Generics.Generic Distribution.Client.BuildReports.Types.Outcome instance GHC.Enum.Bounded Distribution.Client.BuildReports.Types.Outcome instance GHC.Enum.Enum Distribution.Client.BuildReports.Types.Outcome instance GHC.Show.Show Distribution.Client.BuildReports.Types.Outcome instance GHC.Classes.Eq Distribution.Client.BuildReports.Types.Outcome instance GHC.Generics.Generic Distribution.Client.BuildReports.Types.BuildReport instance GHC.Show.Show Distribution.Client.BuildReports.Types.BuildReport instance GHC.Classes.Eq Distribution.Client.BuildReports.Types.BuildReport instance Distribution.Pretty.Pretty Distribution.Client.BuildReports.Types.Outcome instance Distribution.Parsec.Parsec Distribution.Client.BuildReports.Types.Outcome instance Distribution.Pretty.Pretty Distribution.Client.BuildReports.Types.InstallOutcome instance Distribution.Parsec.Parsec Distribution.Client.BuildReports.Types.InstallOutcome instance Data.Binary.Class.Binary Distribution.Client.BuildReports.Types.ReportLevel instance Distribution.Utils.Structured.Structured Distribution.Client.BuildReports.Types.ReportLevel instance Distribution.Pretty.Pretty Distribution.Client.BuildReports.Types.ReportLevel instance Distribution.Parsec.Parsec Distribution.Client.BuildReports.Types.ReportLevel module Distribution.Client.BuildReports.Lens data BuildReport package :: Lens' BuildReport PackageIdentifier os :: Lens' BuildReport OS arch :: Lens' BuildReport Arch compiler :: Lens' BuildReport CompilerId client :: Lens' BuildReport PackageIdentifier flagAssignment :: Lens' BuildReport FlagAssignment dependencies :: Lens' BuildReport [PackageIdentifier] installOutcome :: Lens' BuildReport InstallOutcome docsOutcome :: Lens' BuildReport Outcome testsOutcome :: Lens' BuildReport Outcome module Distribution.Client.Compat.Semaphore -- | QSem is a quantity semaphore in which the resource is acquired -- and released in units of one. It provides guaranteed FIFO ordering for -- satisfying blocked waitQSem calls. data QSem newQSem :: Int -> IO QSem waitQSem :: QSem -> IO () signalQSem :: QSem -> IO () instance GHC.Classes.Eq Distribution.Client.Compat.Semaphore.QSem module Distribution.Client.Dependency.Types -- | All the solvers that can be selected. data PreSolver AlwaysModular :: PreSolver -- | All the solvers that can be used. data Solver Modular :: Solver -- | Global policy for all packages to say if we prefer package versions -- that are already installed locally or if we just prefer the latest -- available. data PackagesPreferenceDefault -- | Always prefer the latest version irrespective of any existing -- installed version. -- -- PreferAllLatest :: PackagesPreferenceDefault -- | Always prefer the oldest version irrespective of any existing -- installed version or packages explicitly requested. -- -- PreferAllOldest :: PackagesPreferenceDefault -- | Always prefer the installed versions over ones that would need to be -- installed. Secondarily, prefer latest versions (eg the latest -- installed version or if there are none then the latest source -- version). PreferAllInstalled :: PackagesPreferenceDefault -- | Prefer the latest version for packages that are explicitly requested -- but prefers the installed version for any other packages. -- -- PreferLatestForSelected :: PackagesPreferenceDefault instance GHC.Generics.Generic Distribution.Client.Dependency.Types.PreSolver instance GHC.Enum.Enum Distribution.Client.Dependency.Types.PreSolver instance GHC.Enum.Bounded Distribution.Client.Dependency.Types.PreSolver instance GHC.Show.Show Distribution.Client.Dependency.Types.PreSolver instance GHC.Classes.Ord Distribution.Client.Dependency.Types.PreSolver instance GHC.Classes.Eq Distribution.Client.Dependency.Types.PreSolver instance GHC.Generics.Generic Distribution.Client.Dependency.Types.Solver instance GHC.Enum.Enum Distribution.Client.Dependency.Types.Solver instance GHC.Enum.Bounded Distribution.Client.Dependency.Types.Solver instance GHC.Show.Show Distribution.Client.Dependency.Types.Solver instance GHC.Classes.Ord Distribution.Client.Dependency.Types.Solver instance GHC.Classes.Eq Distribution.Client.Dependency.Types.Solver instance GHC.Show.Show Distribution.Client.Dependency.Types.PackagesPreferenceDefault instance Data.Binary.Class.Binary Distribution.Client.Dependency.Types.Solver instance Distribution.Utils.Structured.Structured Distribution.Client.Dependency.Types.Solver instance Data.Binary.Class.Binary Distribution.Client.Dependency.Types.PreSolver instance Distribution.Utils.Structured.Structured Distribution.Client.Dependency.Types.PreSolver instance Distribution.Pretty.Pretty Distribution.Client.Dependency.Types.PreSolver instance Distribution.Parsec.Parsec Distribution.Client.Dependency.Types.PreSolver -- | Provides a convenience functions for working with files that may or -- may not be zipped. module Distribution.Client.GZipUtils -- | Attempts to decompress the bytes under the assumption that -- "data format" error at the very beginning of the stream means that it -- is already decompressed. Caller should make sanity checks to verify -- that it is not, in fact, garbage. -- -- This is to deal with http proxies that lie to us and transparently -- decompress without removing the content-encoding header. See: -- https://github.com/haskell/cabal/issues/678 maybeDecompress :: ByteString -> ByteString module Distribution.Client.Glob -- | A file path specified by globbing data FilePathGlob FilePathGlob :: FilePathRoot -> FilePathGlobRel -> FilePathGlob data FilePathRoot FilePathRelative :: FilePathRoot -- | e.g. "/", "c:" or result of takeDrive FilePathRoot :: FilePath -> FilePathRoot FilePathHomeDir :: FilePathRoot data FilePathGlobRel GlobDir :: !Glob -> !FilePathGlobRel -> FilePathGlobRel GlobFile :: !Glob -> FilePathGlobRel -- | trailing dir, a glob ending in / GlobDirTrailing :: FilePathGlobRel -- | A single directory or file component of a globbed path type Glob = [GlobPiece] -- | A piece of a globbing pattern data GlobPiece WildCard :: GlobPiece Literal :: String -> GlobPiece Union :: [Glob] -> GlobPiece -- | Match a FilePathGlob against the file system, starting from a -- given root directory for relative paths. The results of relative globs -- are relative to the given root. Matches for absolute globs are -- absolute. matchFileGlob :: FilePath -> FilePathGlob -> IO [FilePath] -- | Match a FilePathGlobRel against the file system, starting from -- a given root directory. The results are all relative to the given -- root. matchFileGlobRel :: FilePath -> FilePathGlobRel -> IO [FilePath] -- | Match a globbing pattern against a file path component matchGlob :: Glob -> String -> Bool -- | Check if a FilePathGlob doesn't actually make use of any -- globbing and is in fact equivalent to a non-glob FilePath. -- -- If it is trivial in this sense then the result is the equivalent -- constant FilePath. On the other hand if it is not trivial (so -- could in principle match more than one file) then the result is -- Nothing. isTrivialFilePathGlob :: FilePathGlob -> Maybe FilePath -- | Get the FilePath corresponding to a FilePathRoot. -- -- The FilePath argument is required to supply the path for the -- FilePathRelative case. getFilePathRootDirectory :: FilePathRoot -> FilePath -> IO FilePath instance GHC.Generics.Generic Distribution.Client.Glob.GlobPiece instance GHC.Show.Show Distribution.Client.Glob.GlobPiece instance GHC.Classes.Eq Distribution.Client.Glob.GlobPiece instance GHC.Generics.Generic Distribution.Client.Glob.FilePathGlobRel instance GHC.Show.Show Distribution.Client.Glob.FilePathGlobRel instance GHC.Classes.Eq Distribution.Client.Glob.FilePathGlobRel instance GHC.Generics.Generic Distribution.Client.Glob.FilePathRoot instance GHC.Show.Show Distribution.Client.Glob.FilePathRoot instance GHC.Classes.Eq Distribution.Client.Glob.FilePathRoot instance GHC.Generics.Generic Distribution.Client.Glob.FilePathGlob instance GHC.Show.Show Distribution.Client.Glob.FilePathGlob instance GHC.Classes.Eq Distribution.Client.Glob.FilePathGlob instance Data.Binary.Class.Binary Distribution.Client.Glob.FilePathGlob instance Distribution.Utils.Structured.Structured Distribution.Client.Glob.FilePathGlob instance Distribution.Pretty.Pretty Distribution.Client.Glob.FilePathGlob instance Distribution.Parsec.Parsec Distribution.Client.Glob.FilePathGlob instance Data.Binary.Class.Binary Distribution.Client.Glob.FilePathRoot instance Distribution.Utils.Structured.Structured Distribution.Client.Glob.FilePathRoot instance Distribution.Pretty.Pretty Distribution.Client.Glob.FilePathRoot instance Distribution.Parsec.Parsec Distribution.Client.Glob.FilePathRoot instance Data.Binary.Class.Binary Distribution.Client.Glob.FilePathGlobRel instance Distribution.Utils.Structured.Structured Distribution.Client.Glob.FilePathGlobRel instance Distribution.Pretty.Pretty Distribution.Client.Glob.FilePathGlobRel instance Distribution.Parsec.Parsec Distribution.Client.Glob.FilePathGlobRel instance Data.Binary.Class.Binary Distribution.Client.Glob.GlobPiece instance Distribution.Utils.Structured.Structured Distribution.Client.Glob.GlobPiece -- | Interfacing with Haddock module Distribution.Client.Haddock regenerateHaddockIndex :: Verbosity -> InstalledPackageIndex -> ProgramDb -> FilePath -> IO () module Distribution.Client.HashValue data HashValue -- | Hash some data. Currently uses SHA256. hashValue :: ByteString -> HashValue -- | Truncate a 32 byte SHA256 hash to -- -- For example 20 bytes render as 40 hex chars, which we use for -- unit-ids. Or even 4 bytes for hashedInstalledPackageIdShort truncateHash :: Int -> HashValue -> HashValue showHashValue :: HashValue -> String -- | Hash the content of a file. Uses SHA256. readFileHashValue :: FilePath -> IO HashValue -- | Convert a hash from TUF metadata into a PackageSourceHash. -- -- Note that TUF hashes don't necessarily have to be SHA256, since it can -- support new algorithms in future. hashFromTUF :: Hash -> HashValue instance GHC.Show.Show Distribution.Client.HashValue.HashValue instance GHC.Generics.Generic Distribution.Client.HashValue.HashValue instance GHC.Classes.Eq Distribution.Client.HashValue.HashValue instance Data.Binary.Class.Binary Distribution.Client.HashValue.HashValue instance Distribution.Utils.Structured.Structured Distribution.Client.HashValue.HashValue -- | Timestamp type used in package indexes module Distribution.Client.IndexUtils.Timestamp -- | UNIX timestamp (expressed in seconds since unix epoch, i.e. 1970). data Timestamp -- | Special timestamp value to be used when timestamp is -- missingunknowninvalid nullTimestamp :: Timestamp epochTimeToTimestamp :: EpochTime -> Maybe Timestamp timestampToUTCTime :: Timestamp -> Maybe UTCTime utcTimeToTimestamp :: UTCTime -> Maybe Timestamp -- | Compute the maximum Timestamp value -- -- Returns nullTimestamp for the empty list. Also note that -- nullTimestamp compares as smaller to all -- non-nullTimestamp values. maximumTimestamp :: [Timestamp] -> Timestamp instance GHC.Generics.Generic Distribution.Client.IndexUtils.Timestamp.Timestamp instance GHC.Show.Show Distribution.Client.IndexUtils.Timestamp.Timestamp instance Control.DeepSeq.NFData Distribution.Client.IndexUtils.Timestamp.Timestamp instance GHC.Enum.Enum Distribution.Client.IndexUtils.Timestamp.Timestamp instance GHC.Classes.Ord Distribution.Client.IndexUtils.Timestamp.Timestamp instance GHC.Classes.Eq Distribution.Client.IndexUtils.Timestamp.Timestamp instance Data.Binary.Class.Binary Distribution.Client.IndexUtils.Timestamp.Timestamp instance Distribution.Utils.Structured.Structured Distribution.Client.IndexUtils.Timestamp.Timestamp instance Distribution.Pretty.Pretty Distribution.Client.IndexUtils.Timestamp.Timestamp instance Distribution.Parsec.Parsec Distribution.Client.IndexUtils.Timestamp.Timestamp module Distribution.Client.Init.Licenses type License = String bsd2 :: String -> String -> License bsd3 :: String -> String -> License gplv2 :: License gplv3 :: License lgpl21 :: License lgpl3 :: License agplv3 :: License apache20 :: License mit :: String -> String -> License mpl20 :: License isc :: String -> String -> License -- | A job control concurrency abstraction module Distribution.Client.JobControl -- | A simple concurrency abstraction. Jobs can be spawned and can complete -- in any order. This allows both serial and parallel implementations. data JobControl m a -- | Make a JobControl that executes all jobs serially and in order. -- It only executes jobs on demand when they are collected, not eagerly. -- -- Cancelling will cancel all jobs that have not been collected -- yet. newSerialJobControl :: IO (JobControl IO a) -- | Make a JobControl that eagerly executes jobs in parallel, with -- a given maximum degree of parallelism. -- -- Cancelling will cancel jobs that have not yet begun executing, but -- jobs that have already been executed or are currently executing cannot -- be cancelled. newParallelJobControl :: WithCallStack (Int -> IO (JobControl IO a)) -- | Add a new job to the pool of jobs spawnJob :: JobControl m a -> m a -> m () -- | Wait until one job is complete collectJob :: JobControl m a -> m a -- | Returns True if there are any outstanding jobs (ie spawned but yet to -- be collected) remainingJobs :: JobControl m a -> m Bool -- | Try to cancel any outstanding but not-yet-started jobs. Call -- remainingJobs after this to find out if any jobs are left (ie -- could not be cancelled). cancelJobs :: JobControl m a -> m () data JobLimit newJobLimit :: Int -> IO JobLimit withJobLimit :: JobLimit -> IO a -> IO a data Lock newLock :: IO Lock criticalSection :: Lock -> IO a -> IO a module Distribution.Client.ManpageFlags data ManpageFlags ManpageFlags :: Flag Verbosity -> Flag Bool -> ManpageFlags [manpageVerbosity] :: ManpageFlags -> Flag Verbosity [manpageRaw] :: ManpageFlags -> Flag Bool defaultManpageFlags :: ManpageFlags manpageOptions :: ShowOrParseArgs -> [OptionField ManpageFlags] instance GHC.Generics.Generic Distribution.Client.ManpageFlags.ManpageFlags instance GHC.Show.Show Distribution.Client.ManpageFlags.ManpageFlags instance GHC.Classes.Eq Distribution.Client.ManpageFlags.ManpageFlags instance GHC.Base.Monoid Distribution.Client.ManpageFlags.ManpageFlags instance GHC.Base.Semigroup Distribution.Client.ManpageFlags.ManpageFlags module Distribution.Client.ProjectFlags data ProjectFlags ProjectFlags :: Flag FilePath -> Flag Bool -> ProjectFlags -- | The cabal project file name; defaults to cabal.project. The -- name itself denotes the cabal project file name, but it also is the -- base of auxiliary project files, such as cabal.project.local -- and cabal.project.freeze which are also read and written out -- in some cases. If the path is not found in the current working -- directory, we will successively probe relative to parent directories -- until this name is found. [flagProjectFileName] :: ProjectFlags -> Flag FilePath -- | Whether to ignore the local project (i.e. don't search for -- cabal.project) The exact interpretation might be slightly different -- per command. [flagIgnoreProject] :: ProjectFlags -> Flag Bool defaultProjectFlags :: ProjectFlags projectFlagsOptions :: ShowOrParseArgs -> [OptionField ProjectFlags] -- | As almost all commands use ProjectFlags but not all can honour -- "ignore-project" flag, provide this utility to remove the flag parsing -- from the help message. removeIgnoreProjectOption :: [OptionField a] -> [OptionField a] instance GHC.Generics.Generic Distribution.Client.ProjectFlags.ProjectFlags instance GHC.Show.Show Distribution.Client.ProjectFlags.ProjectFlags instance GHC.Base.Monoid Distribution.Client.ProjectFlags.ProjectFlags instance GHC.Base.Semigroup Distribution.Client.ProjectFlags.ProjectFlags module Distribution.Client.SavedFlags -- | Read command-line arguments, separated by null characters, from a -- file. Returns the default flags if the file does not exist. readCommandFlags :: FilePath -> CommandUI flags -> IO flags -- | Write command-line flags to a file, separated by null characters. This -- format is also suitable for the xargs -0 command. Using the -- null character also avoids the problem of escaping newlines or spaces, -- because unlike other whitespace characters, the null character is not -- valid in command-line arguments. writeCommandFlags :: Verbosity -> FilePath -> CommandUI flags -> flags -> IO () readSavedArgs :: FilePath -> IO (Maybe [String]) writeSavedArgs :: Verbosity -> FilePath -> [String] -> IO () instance GHC.Show.Show Distribution.Client.SavedFlags.SavedArgsError instance GHC.Exception.Type.Exception Distribution.Client.SavedFlags.SavedArgsError module Distribution.Client.Security.DNS -- | Try to lookup RFC1464-encoded mirror urls for a Hackage repository url -- by performing a DNS TXT lookup on the _mirrors.-prefixed URL -- hostname. -- -- Example: for http://hackage.haskell.org/ perform a DNS -- TXT query for the hostname _mirrors.hackage.haskell.org which -- may look like e.g. -- --
--   _mirrors.hackage.haskell.org. 300 IN TXT
--      "0.urlbase=http://hackage.fpcomplete.com/"
--      "1.urlbase=http://objects-us-west-1.dream.io/hackage-mirror/"
--   
-- -- NB: hackage-security doesn't require DNS lookups being trustworthy, as -- the trust is established via the cryptographically signed TUF -- meta-data that is retrieved from the resolved Hackage repository. -- Moreover, we already have to protect against a compromised -- hackage.haskell.org DNS entry, so an the additional -- _mirrors.hackage.haskell.org DNS entry in the same SOA -- doesn't constitute a significant new attack vector anyway. queryBootstrapMirrors :: Verbosity -> URI -> IO [URI] module Distribution.Client.Signal -- | Install a signal handler that initiates a controlled shutdown on -- receiving SIGTERM by throwing an asynchronous exception at the main -- thread. Must be called from the main thread. -- -- It is a noop on Windows. installTerminationHandler :: IO () -- | Terminated is an asynchronous exception, thrown when SIGTERM is -- received. It's to kill what UserInterrupt is to -- Ctrl-C. data Terminated Terminated :: Terminated instance GHC.Exception.Type.Exception Distribution.Client.Signal.Terminated instance GHC.Show.Show Distribution.Client.Signal.Terminated -- | Reading, writing and manipulating ".tar" archive files. module Distribution.Client.Tar createTarGzFile :: FilePath -> FilePath -> FilePath -> IO () extractTarGzFile :: FilePath -> FilePath -> FilePath -> IO () -- | Type code for the local build tree reference entry type. We don't use -- the symbolic link entry type because it allows only 100 ASCII -- characters for the path. buildTreeRefTypeCode :: TypeCode -- | Type code for the local build tree snapshot entry type. buildTreeSnapshotTypeCode :: TypeCode -- | Is this a type code for a build tree reference? isBuildTreeRefTypeCode :: TypeCode -> Bool filterEntries :: (Entry -> Bool) -> Entries e -> Entries e filterEntriesM :: Monad m => (Entry -> m Bool) -> Entries e -> m (Entries e) entriesToList :: Exception e => Entries e -> [Entry] instance (GHC.Exception.Type.Exception a, GHC.Exception.Type.Exception b) => GHC.Exception.Type.Exception (Data.Either.Either a b) module Distribution.Client.Types.AllowNewer -- | RelaxDeps in the context of upper bounds (i.e. for -- --allow-newer flag) newtype AllowNewer AllowNewer :: RelaxDeps -> AllowNewer [unAllowNewer] :: AllowNewer -> RelaxDeps -- | RelaxDeps in the context of lower bounds (i.e. for -- --allow-older flag) newtype AllowOlder AllowOlder :: RelaxDeps -> AllowOlder [unAllowOlder] :: AllowOlder -> RelaxDeps -- | Generic data type for policy when relaxing bounds in dependencies. -- Don't use this directly: use AllowOlder or AllowNewer -- depending on whether or not you are relaxing an lower or upper bound -- (respectively). data RelaxDeps -- | Ignore upper (resp. lower) bounds in some (or no) dependencies on the -- given packages. -- -- RelaxDepsSome [] is the default, i.e. honor the bounds in all -- dependencies, never choose versions newer (resp. older) than allowed. RelaxDepsSome :: [RelaxedDep] -> RelaxDeps -- | Ignore upper (resp. lower) bounds in dependencies on all packages. -- -- Note: This is should be semantically equivalent to -- --
--   RelaxDepsSome [RelaxedDep RelaxDepScopeAll RelaxDepModNone RelaxDepSubjectAll]
--   
-- -- (TODO: consider normalising RelaxDeps and/or RelaxedDep) RelaxDepsAll :: RelaxDeps -- | A smarter RelaxedDepsSome, *:* is the same as -- all. mkRelaxDepSome :: [RelaxedDep] -> RelaxDeps -- | Modifier for dependency relaxation data RelaxDepMod -- | Default semantics RelaxDepModNone :: RelaxDepMod -- | Apply relaxation only to ^>= constraints RelaxDepModCaret :: RelaxDepMod -- | Specify the scope of a relaxation, i.e. limit which depending packages -- are allowed to have their version constraints relaxed. data RelaxDepScope -- | Apply relaxation in any package RelaxDepScopeAll :: RelaxDepScope -- | Apply relaxation to in all versions of a package RelaxDepScopePackage :: !PackageName -> RelaxDepScope -- | Apply relaxation to a specific version of a package only RelaxDepScopePackageId :: !PackageId -> RelaxDepScope -- | Express whether to relax bounds on all packages, or a -- single package data RelaxDepSubject RelaxDepSubjectAll :: RelaxDepSubject RelaxDepSubjectPkg :: !PackageName -> RelaxDepSubject -- | Dependencies can be relaxed either for all packages in the install -- plan, or only for some packages. data RelaxedDep RelaxedDep :: !RelaxDepScope -> !RelaxDepMod -> !RelaxDepSubject -> RelaxedDep -- | Return True if RelaxDeps specifies a non-empty set of -- relaxations -- -- Equivalent to isRelaxDeps = (/= mempty) isRelaxDeps :: RelaxDeps -> Bool instance GHC.Generics.Generic Distribution.Client.Types.AllowNewer.RelaxDepScope instance GHC.Show.Show Distribution.Client.Types.AllowNewer.RelaxDepScope instance GHC.Read.Read Distribution.Client.Types.AllowNewer.RelaxDepScope instance GHC.Classes.Eq Distribution.Client.Types.AllowNewer.RelaxDepScope instance GHC.Generics.Generic Distribution.Client.Types.AllowNewer.RelaxDepMod instance GHC.Show.Show Distribution.Client.Types.AllowNewer.RelaxDepMod instance GHC.Read.Read Distribution.Client.Types.AllowNewer.RelaxDepMod instance GHC.Classes.Eq Distribution.Client.Types.AllowNewer.RelaxDepMod instance GHC.Generics.Generic Distribution.Client.Types.AllowNewer.RelaxDepSubject instance GHC.Show.Show Distribution.Client.Types.AllowNewer.RelaxDepSubject instance GHC.Read.Read Distribution.Client.Types.AllowNewer.RelaxDepSubject instance GHC.Classes.Ord Distribution.Client.Types.AllowNewer.RelaxDepSubject instance GHC.Classes.Eq Distribution.Client.Types.AllowNewer.RelaxDepSubject instance GHC.Generics.Generic Distribution.Client.Types.AllowNewer.RelaxedDep instance GHC.Show.Show Distribution.Client.Types.AllowNewer.RelaxedDep instance GHC.Read.Read Distribution.Client.Types.AllowNewer.RelaxedDep instance GHC.Classes.Eq Distribution.Client.Types.AllowNewer.RelaxedDep instance GHC.Generics.Generic Distribution.Client.Types.AllowNewer.RelaxDeps instance GHC.Show.Show Distribution.Client.Types.AllowNewer.RelaxDeps instance GHC.Read.Read Distribution.Client.Types.AllowNewer.RelaxDeps instance GHC.Classes.Eq Distribution.Client.Types.AllowNewer.RelaxDeps instance GHC.Generics.Generic Distribution.Client.Types.AllowNewer.AllowOlder instance GHC.Show.Show Distribution.Client.Types.AllowNewer.AllowOlder instance GHC.Read.Read Distribution.Client.Types.AllowNewer.AllowOlder instance GHC.Classes.Eq Distribution.Client.Types.AllowNewer.AllowOlder instance GHC.Generics.Generic Distribution.Client.Types.AllowNewer.AllowNewer instance GHC.Show.Show Distribution.Client.Types.AllowNewer.AllowNewer instance GHC.Read.Read Distribution.Client.Types.AllowNewer.AllowNewer instance GHC.Classes.Eq Distribution.Client.Types.AllowNewer.AllowNewer instance Data.Binary.Class.Binary Distribution.Client.Types.AllowNewer.AllowNewer instance Distribution.Utils.Structured.Structured Distribution.Client.Types.AllowNewer.AllowNewer instance GHC.Base.Semigroup Distribution.Client.Types.AllowNewer.AllowNewer instance GHC.Base.Monoid Distribution.Client.Types.AllowNewer.AllowNewer instance Data.Binary.Class.Binary Distribution.Client.Types.AllowNewer.AllowOlder instance Distribution.Utils.Structured.Structured Distribution.Client.Types.AllowNewer.AllowOlder instance GHC.Base.Semigroup Distribution.Client.Types.AllowNewer.AllowOlder instance GHC.Base.Monoid Distribution.Client.Types.AllowNewer.AllowOlder instance Distribution.Pretty.Pretty Distribution.Client.Types.AllowNewer.RelaxDeps instance Distribution.Parsec.Parsec Distribution.Client.Types.AllowNewer.RelaxDeps instance Data.Binary.Class.Binary Distribution.Client.Types.AllowNewer.RelaxDeps instance Distribution.Utils.Structured.Structured Distribution.Client.Types.AllowNewer.RelaxDeps instance GHC.Base.Semigroup Distribution.Client.Types.AllowNewer.RelaxDeps instance GHC.Base.Monoid Distribution.Client.Types.AllowNewer.RelaxDeps instance Distribution.Pretty.Pretty Distribution.Client.Types.AllowNewer.RelaxedDep instance Distribution.Parsec.Parsec Distribution.Client.Types.AllowNewer.RelaxedDep instance Data.Binary.Class.Binary Distribution.Client.Types.AllowNewer.RelaxedDep instance Distribution.Utils.Structured.Structured Distribution.Client.Types.AllowNewer.RelaxedDep instance Distribution.Pretty.Pretty Distribution.Client.Types.AllowNewer.RelaxDepSubject instance Distribution.Parsec.Parsec Distribution.Client.Types.AllowNewer.RelaxDepSubject instance Data.Binary.Class.Binary Distribution.Client.Types.AllowNewer.RelaxDepSubject instance Distribution.Utils.Structured.Structured Distribution.Client.Types.AllowNewer.RelaxDepSubject instance Data.Binary.Class.Binary Distribution.Client.Types.AllowNewer.RelaxDepMod instance Distribution.Utils.Structured.Structured Distribution.Client.Types.AllowNewer.RelaxDepMod instance Data.Binary.Class.Binary Distribution.Client.Types.AllowNewer.RelaxDepScope instance Distribution.Utils.Structured.Structured Distribution.Client.Types.AllowNewer.RelaxDepScope module Distribution.Client.Types.BuildResults -- | A summary of the outcome for building a single package. type BuildOutcome = Either BuildFailure BuildResult -- | A summary of the outcome for building a whole set of packages. type BuildOutcomes = Map UnitId BuildOutcome data BuildFailure PlanningFailed :: BuildFailure DependentFailed :: PackageId -> BuildFailure DownloadFailed :: SomeException -> BuildFailure UnpackFailed :: SomeException -> BuildFailure ConfigureFailed :: SomeException -> BuildFailure BuildFailed :: SomeException -> BuildFailure TestsFailed :: SomeException -> BuildFailure InstallFailed :: SomeException -> BuildFailure data BuildResult BuildResult :: DocsResult -> TestsResult -> Maybe InstalledPackageInfo -> BuildResult data TestsResult TestsNotTried :: TestsResult TestsOk :: TestsResult data DocsResult DocsNotTried :: DocsResult DocsFailed :: DocsResult DocsOk :: DocsResult instance GHC.Generics.Generic Distribution.Client.Types.BuildResults.BuildFailure instance GHC.Show.Show Distribution.Client.Types.BuildResults.BuildFailure instance GHC.Generics.Generic Distribution.Client.Types.BuildResults.DocsResult instance GHC.Show.Show Distribution.Client.Types.BuildResults.DocsResult instance GHC.Generics.Generic Distribution.Client.Types.BuildResults.TestsResult instance GHC.Show.Show Distribution.Client.Types.BuildResults.TestsResult instance GHC.Generics.Generic Distribution.Client.Types.BuildResults.BuildResult instance GHC.Show.Show Distribution.Client.Types.BuildResults.BuildResult instance Data.Binary.Class.Binary Distribution.Client.Types.BuildResults.BuildResult instance Distribution.Utils.Structured.Structured Distribution.Client.Types.BuildResults.BuildResult instance Data.Binary.Class.Binary Distribution.Client.Types.BuildResults.TestsResult instance Distribution.Utils.Structured.Structured Distribution.Client.Types.BuildResults.TestsResult instance Data.Binary.Class.Binary Distribution.Client.Types.BuildResults.DocsResult instance Distribution.Utils.Structured.Structured Distribution.Client.Types.BuildResults.DocsResult instance GHC.Exception.Type.Exception Distribution.Client.Types.BuildResults.BuildFailure instance Data.Binary.Class.Binary Distribution.Client.Types.BuildResults.BuildFailure instance Distribution.Utils.Structured.Structured Distribution.Client.Types.BuildResults.BuildFailure module Distribution.Client.Types.ConfiguredId -- | Within Cabal the library we no longer have a -- InstalledPackageId type. That's because it deals with the -- compilers' notion of a registered library, and those really are -- libraries not packages. Those are now named units. -- -- The package management layer does however deal with installed -- packages, as whole packages not just as libraries. So we do still need -- a type for installed package ids. At the moment however we track -- installed packages via their primary library, which is a unit id. In -- future this may change slightly and we may distinguish these two types -- and have an explicit conversion when we register units with the -- compiler. type InstalledPackageId = ComponentId -- | A ConfiguredId is a package ID for a configured package. -- -- Once we configure a source package we know its UnitId. It is still -- however useful in lots of places to also know the source ID for the -- package. We therefore bundle the two. -- -- An already installed package of course is also "configured" (all its -- configuration parameters and dependencies have been specified). data ConfiguredId ConfiguredId :: PackageId -> Maybe ComponentName -> ComponentId -> ConfiguredId [confSrcId] :: ConfiguredId -> PackageId [confCompName] :: ConfiguredId -> Maybe ComponentName [confInstId] :: ConfiguredId -> ComponentId annotatedIdToConfiguredId :: AnnotatedId ComponentId -> ConfiguredId class HasConfiguredId a configuredId :: HasConfiguredId a => a -> ConfiguredId instance GHC.Generics.Generic Distribution.Client.Types.ConfiguredId.ConfiguredId instance GHC.Classes.Ord Distribution.Client.Types.ConfiguredId.ConfiguredId instance GHC.Classes.Eq Distribution.Client.Types.ConfiguredId.ConfiguredId instance Distribution.Client.Types.ConfiguredId.HasConfiguredId Distribution.Types.InstalledPackageInfo.InstalledPackageInfo instance Data.Binary.Class.Binary Distribution.Client.Types.ConfiguredId.ConfiguredId instance Distribution.Utils.Structured.Structured Distribution.Client.Types.ConfiguredId.ConfiguredId instance GHC.Show.Show Distribution.Client.Types.ConfiguredId.ConfiguredId instance Distribution.Package.Package Distribution.Client.Types.ConfiguredId.ConfiguredId module Distribution.Client.Types.ConfiguredPackage -- | A ConfiguredPackage is a not-yet-installed package along with -- the total configuration information. The configuration information is -- total in the sense that it provides all the configuration information -- and so the final configure process will be independent of the -- environment. -- -- ConfiguredPackage is assumed to not support Backpack. Only the -- v2-build codepath supports Backpack. data ConfiguredPackage loc ConfiguredPackage :: InstalledPackageId -> SourcePackage loc -> FlagAssignment -> OptionalStanzaSet -> ComponentDeps [ConfiguredId] -> ConfiguredPackage loc [confPkgId] :: ConfiguredPackage loc -> InstalledPackageId -- | package info, including repo [confPkgSource] :: ConfiguredPackage loc -> SourcePackage loc -- | complete flag assignment for the package [confPkgFlags] :: ConfiguredPackage loc -> FlagAssignment -- | list of enabled optional stanzas for the package [confPkgStanzas] :: ConfiguredPackage loc -> OptionalStanzaSet -- | set of exact dependencies (installed or source). -- -- These must be consistent with the buildDepends in the -- PackageDescription that you'd get by applying the flag -- assignment and optional stanzas. [confPkgDeps] :: ConfiguredPackage loc -> ComponentDeps [ConfiguredId] instance GHC.Generics.Generic (Distribution.Client.Types.ConfiguredPackage.ConfiguredPackage loc) instance GHC.Show.Show loc => GHC.Show.Show (Distribution.Client.Types.ConfiguredPackage.ConfiguredPackage loc) instance GHC.Classes.Eq loc => GHC.Classes.Eq (Distribution.Client.Types.ConfiguredPackage.ConfiguredPackage loc) instance Distribution.Client.Types.ConfiguredId.HasConfiguredId (Distribution.Client.Types.ConfiguredPackage.ConfiguredPackage loc) instance Distribution.Solver.Types.PackageFixedDeps.PackageFixedDeps (Distribution.Client.Types.ConfiguredPackage.ConfiguredPackage loc) instance Distribution.Compat.Graph.IsNode (Distribution.Client.Types.ConfiguredPackage.ConfiguredPackage loc) instance Data.Binary.Class.Binary loc => Data.Binary.Class.Binary (Distribution.Client.Types.ConfiguredPackage.ConfiguredPackage loc) instance Distribution.Package.Package (Distribution.Client.Types.ConfiguredPackage.ConfiguredPackage loc) instance Distribution.Package.HasMungedPackageId (Distribution.Client.Types.ConfiguredPackage.ConfiguredPackage loc) instance Distribution.Package.HasUnitId (Distribution.Client.Types.ConfiguredPackage.ConfiguredPackage loc) instance Distribution.Package.PackageInstalled (Distribution.Client.Types.ConfiguredPackage.ConfiguredPackage loc) module Distribution.Client.Types.Credentials newtype Username Username :: String -> Username [unUsername] :: Username -> String newtype Password Password :: String -> Password [unPassword] :: Password -> String module Distribution.Client.Types.InstallMethod data InstallMethod InstallMethodCopy :: InstallMethod InstallMethodSymlink :: InstallMethod instance GHC.Enum.Enum Distribution.Client.Types.InstallMethod.InstallMethod instance GHC.Enum.Bounded Distribution.Client.Types.InstallMethod.InstallMethod instance GHC.Generics.Generic Distribution.Client.Types.InstallMethod.InstallMethod instance GHC.Show.Show Distribution.Client.Types.InstallMethod.InstallMethod instance GHC.Classes.Eq Distribution.Client.Types.InstallMethod.InstallMethod instance Data.Binary.Class.Binary Distribution.Client.Types.InstallMethod.InstallMethod instance Distribution.Utils.Structured.Structured Distribution.Client.Types.InstallMethod.InstallMethod instance GHC.Base.Semigroup Distribution.Client.Types.InstallMethod.InstallMethod instance Distribution.Parsec.Parsec Distribution.Client.Types.InstallMethod.InstallMethod instance Distribution.Pretty.Pretty Distribution.Client.Types.InstallMethod.InstallMethod module Distribution.Client.Types.OverwritePolicy data OverwritePolicy NeverOverwrite :: OverwritePolicy AlwaysOverwrite :: OverwritePolicy PromptOverwrite :: OverwritePolicy instance GHC.Enum.Enum Distribution.Client.Types.OverwritePolicy.OverwritePolicy instance GHC.Enum.Bounded Distribution.Client.Types.OverwritePolicy.OverwritePolicy instance GHC.Generics.Generic Distribution.Client.Types.OverwritePolicy.OverwritePolicy instance GHC.Classes.Eq Distribution.Client.Types.OverwritePolicy.OverwritePolicy instance GHC.Show.Show Distribution.Client.Types.OverwritePolicy.OverwritePolicy instance Data.Binary.Class.Binary Distribution.Client.Types.OverwritePolicy.OverwritePolicy instance Distribution.Utils.Structured.Structured Distribution.Client.Types.OverwritePolicy.OverwritePolicy instance Distribution.Parsec.Parsec Distribution.Client.Types.OverwritePolicy.OverwritePolicy instance Distribution.Pretty.Pretty Distribution.Client.Types.OverwritePolicy.OverwritePolicy module Distribution.Client.CmdInstall.ClientInstallFlags data InstallMethod InstallMethodCopy :: InstallMethod InstallMethodSymlink :: InstallMethod data ClientInstallFlags ClientInstallFlags :: Flag Bool -> Flag FilePath -> Flag OverwritePolicy -> Flag InstallMethod -> Flag FilePath -> ClientInstallFlags [cinstInstallLibs] :: ClientInstallFlags -> Flag Bool [cinstEnvironmentPath] :: ClientInstallFlags -> Flag FilePath [cinstOverwritePolicy] :: ClientInstallFlags -> Flag OverwritePolicy [cinstInstallMethod] :: ClientInstallFlags -> Flag InstallMethod [cinstInstalldir] :: ClientInstallFlags -> Flag FilePath defaultClientInstallFlags :: ClientInstallFlags clientInstallOptions :: ShowOrParseArgs -> [OptionField ClientInstallFlags] instance GHC.Generics.Generic Distribution.Client.CmdInstall.ClientInstallFlags.ClientInstallFlags instance GHC.Show.Show Distribution.Client.CmdInstall.ClientInstallFlags.ClientInstallFlags instance GHC.Classes.Eq Distribution.Client.CmdInstall.ClientInstallFlags.ClientInstallFlags instance GHC.Base.Monoid Distribution.Client.CmdInstall.ClientInstallFlags.ClientInstallFlags instance GHC.Base.Semigroup Distribution.Client.CmdInstall.ClientInstallFlags.ClientInstallFlags instance Data.Binary.Class.Binary Distribution.Client.CmdInstall.ClientInstallFlags.ClientInstallFlags instance Distribution.Utils.Structured.Structured Distribution.Client.CmdInstall.ClientInstallFlags.ClientInstallFlags module Distribution.Client.Types.PackageSpecifier -- | A fully or partially resolved reference to a package. data PackageSpecifier pkg -- | A partially specified reference to a package (either source or -- installed). It is specified by package name and optionally some -- required properties. Use a dependency resolver to pick a specific -- package satisfying these properties. NamedPackage :: PackageName -> [PackageProperty] -> PackageSpecifier pkg -- | A fully specified source package. SpecificSourcePackage :: pkg -> PackageSpecifier pkg pkgSpecifierTarget :: Package pkg => PackageSpecifier pkg -> PackageName pkgSpecifierConstraints :: Package pkg => PackageSpecifier pkg -> [LabeledPackageConstraint] instance GHC.Generics.Generic (Distribution.Client.Types.PackageSpecifier.PackageSpecifier pkg) instance GHC.Base.Functor Distribution.Client.Types.PackageSpecifier.PackageSpecifier instance GHC.Show.Show pkg => GHC.Show.Show (Distribution.Client.Types.PackageSpecifier.PackageSpecifier pkg) instance GHC.Classes.Eq pkg => GHC.Classes.Eq (Distribution.Client.Types.PackageSpecifier.PackageSpecifier pkg) instance Data.Binary.Class.Binary pkg => Data.Binary.Class.Binary (Distribution.Client.Types.PackageSpecifier.PackageSpecifier pkg) instance Distribution.Utils.Structured.Structured pkg => Distribution.Utils.Structured.Structured (Distribution.Client.Types.PackageSpecifier.PackageSpecifier pkg) module Distribution.Client.Types.RepoName -- | Repository name. -- -- May be used as path segment. newtype RepoName RepoName :: String -> RepoName [unRepoName] :: RepoName -> String instance GHC.Generics.Generic Distribution.Client.Types.RepoName.RepoName instance GHC.Classes.Ord Distribution.Client.Types.RepoName.RepoName instance GHC.Classes.Eq Distribution.Client.Types.RepoName.RepoName instance GHC.Show.Show Distribution.Client.Types.RepoName.RepoName instance Data.Binary.Class.Binary Distribution.Client.Types.RepoName.RepoName instance Distribution.Utils.Structured.Structured Distribution.Client.Types.RepoName.RepoName instance Control.DeepSeq.NFData Distribution.Client.Types.RepoName.RepoName instance Distribution.Pretty.Pretty Distribution.Client.Types.RepoName.RepoName instance Distribution.Parsec.Parsec Distribution.Client.Types.RepoName.RepoName module Distribution.Client.Types.Repo data RemoteRepo RemoteRepo :: RepoName -> URI -> Maybe Bool -> [String] -> Int -> Bool -> RemoteRepo [remoteRepoName] :: RemoteRepo -> RepoName [remoteRepoURI] :: RemoteRepo -> URI -- | Enable secure access? -- -- Nothing here represents "whatever the default is"; this is -- important to allow for a smooth transition from opt-in to opt-out -- security (once we switch to opt-out, all access to the central Hackage -- repository should be secure by default) [remoteRepoSecure] :: RemoteRepo -> Maybe Bool -- | Root key IDs (for bootstrapping) [remoteRepoRootKeys] :: RemoteRepo -> [String] -- | Threshold for verification during bootstrapping [remoteRepoKeyThreshold] :: RemoteRepo -> Int -- | Normally a repo just specifies an HTTP or HTTPS URI, but as a special -- case we may know a repo supports both and want to try HTTPS if we can, -- but still allow falling back to HTTP. -- -- This field is not currently stored in the config file, but is filled -- in automagically for known repos. [remoteRepoShouldTryHttps] :: RemoteRepo -> Bool -- | Construct a partial RemoteRepo value to fold the field parser -- list over. emptyRemoteRepo :: RepoName -> RemoteRepo -- | no-index style local repositories. -- -- https://github.com/haskell/cabal/issues/6359 data LocalRepo LocalRepo :: RepoName -> FilePath -> Bool -> LocalRepo [localRepoName] :: LocalRepo -> RepoName [localRepoPath] :: LocalRepo -> FilePath [localRepoSharedCache] :: LocalRepo -> Bool -- | Construct a partial LocalRepo value to fold the field parser -- list over. emptyLocalRepo :: RepoName -> LocalRepo -- | Calculate a cache key for local-repo. -- -- For remote repositories we just use name, but local repositories may -- all be named "local", so we add a bit of localRepoPath into the -- mix. localRepoCacheKey :: LocalRepo -> String -- | Different kinds of repositories -- -- NOTE: It is important that this type remains serializable. data Repo -- | Local repository, without index. -- -- https://github.com/haskell/cabal/issues/6359 RepoLocalNoIndex :: LocalRepo -> FilePath -> Repo [repoLocal] :: Repo -> LocalRepo [repoLocalDir] :: Repo -> FilePath -- | Standard (unsecured) remote repositories RepoRemote :: RemoteRepo -> FilePath -> Repo [repoRemote] :: Repo -> RemoteRepo [repoLocalDir] :: Repo -> FilePath -- | Secure repositories -- -- Although this contains the same fields as RepoRemote, we use a -- separate constructor to avoid confusing the two. -- -- Not all access to a secure repo goes through the hackage-security -- library currently; code paths that do not still make use of the -- repoRemote and repoLocalDir fields directly. RepoSecure :: RemoteRepo -> FilePath -> Repo [repoRemote] :: Repo -> RemoteRepo [repoLocalDir] :: Repo -> FilePath repoName :: Repo -> RepoName -- | Check if this is a remote repo isRepoRemote :: Repo -> Bool -- | Extract RemoteRepo from Repo if remote. maybeRepoRemote :: Repo -> Maybe RemoteRepo instance GHC.Generics.Generic Distribution.Client.Types.Repo.RemoteRepo instance GHC.Classes.Ord Distribution.Client.Types.Repo.RemoteRepo instance GHC.Classes.Eq Distribution.Client.Types.Repo.RemoteRepo instance GHC.Show.Show Distribution.Client.Types.Repo.RemoteRepo instance GHC.Generics.Generic Distribution.Client.Types.Repo.LocalRepo instance GHC.Classes.Ord Distribution.Client.Types.Repo.LocalRepo instance GHC.Classes.Eq Distribution.Client.Types.Repo.LocalRepo instance GHC.Show.Show Distribution.Client.Types.Repo.LocalRepo instance GHC.Generics.Generic Distribution.Client.Types.Repo.Repo instance GHC.Classes.Ord Distribution.Client.Types.Repo.Repo instance GHC.Classes.Eq Distribution.Client.Types.Repo.Repo instance GHC.Show.Show Distribution.Client.Types.Repo.Repo instance Data.Binary.Class.Binary Distribution.Client.Types.Repo.Repo instance Distribution.Utils.Structured.Structured Distribution.Client.Types.Repo.Repo instance Data.Binary.Class.Binary Distribution.Client.Types.Repo.LocalRepo instance Distribution.Utils.Structured.Structured Distribution.Client.Types.Repo.LocalRepo instance Distribution.Parsec.Parsec Distribution.Client.Types.Repo.LocalRepo instance Distribution.Pretty.Pretty Distribution.Client.Types.Repo.LocalRepo instance Data.Binary.Class.Binary Distribution.Client.Types.Repo.RemoteRepo instance Distribution.Utils.Structured.Structured Distribution.Client.Types.Repo.RemoteRepo instance Distribution.Pretty.Pretty Distribution.Client.Types.Repo.RemoteRepo instance Distribution.Parsec.Parsec Distribution.Client.Types.Repo.RemoteRepo -- | Package repositories index state. module Distribution.Client.IndexUtils.IndexState -- | Specification of the state of a specific repo package index data RepoIndexState -- | Use all available entries IndexStateHead :: RepoIndexState -- | Use all entries that existed at the specified time IndexStateTime :: !Timestamp -> RepoIndexState -- | Index state of multiple repositories data TotalIndexState -- | TotalIndexState where all repositories are at HEAD -- index state. headTotalIndexState :: TotalIndexState -- | Create TotalIndexState. makeTotalIndexState :: RepoIndexState -> Map RepoName RepoIndexState -> TotalIndexState -- | Lookup a RepoIndexState for an individual repository from -- TotalIndexState. lookupIndexState :: RepoName -> TotalIndexState -> RepoIndexState -- | Insert a RepoIndexState to TotalIndexState. insertIndexState :: RepoName -> RepoIndexState -> TotalIndexState -> TotalIndexState instance GHC.Show.Show Distribution.Client.IndexUtils.IndexState.RepoIndexState instance GHC.Generics.Generic Distribution.Client.IndexUtils.IndexState.RepoIndexState instance GHC.Classes.Eq Distribution.Client.IndexUtils.IndexState.RepoIndexState instance GHC.Generics.Generic Distribution.Client.IndexUtils.IndexState.TotalIndexState instance GHC.Show.Show Distribution.Client.IndexUtils.IndexState.TotalIndexState instance GHC.Classes.Eq Distribution.Client.IndexUtils.IndexState.TotalIndexState instance Data.Binary.Class.Binary Distribution.Client.IndexUtils.IndexState.TotalIndexState instance Distribution.Utils.Structured.Structured Distribution.Client.IndexUtils.IndexState.TotalIndexState instance Control.DeepSeq.NFData Distribution.Client.IndexUtils.IndexState.TotalIndexState instance Distribution.Pretty.Pretty Distribution.Client.IndexUtils.IndexState.TotalIndexState instance Distribution.Parsec.Parsec Distribution.Client.IndexUtils.IndexState.TotalIndexState instance Data.Binary.Class.Binary Distribution.Client.IndexUtils.IndexState.RepoIndexState instance Distribution.Utils.Structured.Structured Distribution.Client.IndexUtils.IndexState.RepoIndexState instance Control.DeepSeq.NFData Distribution.Client.IndexUtils.IndexState.RepoIndexState instance Distribution.Pretty.Pretty Distribution.Client.IndexUtils.IndexState.RepoIndexState instance Distribution.Parsec.Parsec Distribution.Client.IndexUtils.IndexState.RepoIndexState module Distribution.Client.IndexUtils.ActiveRepos -- | Ordered list of active repositories. newtype ActiveRepos ActiveRepos :: [ActiveRepoEntry] -> ActiveRepos defaultActiveRepos :: ActiveRepos -- | Note, this does nothing if ActiveRepoRest is present. filterSkippedActiveRepos :: ActiveRepos -> ActiveRepos data ActiveRepoEntry -- | rest repositories, i.e. not explicitly listed as ActiveRepo ActiveRepoRest :: CombineStrategy -> ActiveRepoEntry -- | explicit repository name ActiveRepo :: RepoName -> CombineStrategy -> ActiveRepoEntry data CombineStrategy -- | skip this repository CombineStrategySkip :: CombineStrategy -- | merge existing versions CombineStrategyMerge :: CombineStrategy -- | if later repository specifies a package, all package versions are -- replaced CombineStrategyOverride :: CombineStrategy -- | Sort values RepoName according to ActiveRepos list. -- --
--   >>> let repos = [RepoName "a", RepoName "b", RepoName "c"]
--   
--   >>> organizeByRepos (ActiveRepos [ActiveRepoRest CombineStrategyMerge]) id repos
--   Right [(RepoName "a",CombineStrategyMerge),(RepoName "b",CombineStrategyMerge),(RepoName "c",CombineStrategyMerge)]
--   
-- --
--   >>> organizeByRepos (ActiveRepos [ActiveRepo (RepoName "b") CombineStrategyOverride, ActiveRepoRest CombineStrategyMerge]) id repos
--   Right [(RepoName "b",CombineStrategyOverride),(RepoName "a",CombineStrategyMerge),(RepoName "c",CombineStrategyMerge)]
--   
-- --
--   >>> organizeByRepos (ActiveRepos [ActiveRepoRest CombineStrategyMerge, ActiveRepo (RepoName "b") CombineStrategyOverride]) id repos
--   Right [(RepoName "a",CombineStrategyMerge),(RepoName "c",CombineStrategyMerge),(RepoName "b",CombineStrategyOverride)]
--   
-- --
--   >>> organizeByRepos (ActiveRepos [ActiveRepoRest CombineStrategyMerge, ActiveRepo (RepoName "d") CombineStrategyOverride]) id repos
--   Left "no repository provided d"
--   
-- -- Note: currently if ActiveRepoRest is provided more than once, -- rest-repositories will be multiple times in the output. organizeByRepos :: forall a. ActiveRepos -> (a -> RepoName) -> [a] -> Either String [(a, CombineStrategy)] instance GHC.Generics.Generic Distribution.Client.IndexUtils.ActiveRepos.CombineStrategy instance GHC.Enum.Bounded Distribution.Client.IndexUtils.ActiveRepos.CombineStrategy instance GHC.Enum.Enum Distribution.Client.IndexUtils.ActiveRepos.CombineStrategy instance GHC.Show.Show Distribution.Client.IndexUtils.ActiveRepos.CombineStrategy instance GHC.Classes.Eq Distribution.Client.IndexUtils.ActiveRepos.CombineStrategy instance GHC.Generics.Generic Distribution.Client.IndexUtils.ActiveRepos.ActiveRepoEntry instance GHC.Show.Show Distribution.Client.IndexUtils.ActiveRepos.ActiveRepoEntry instance GHC.Classes.Eq Distribution.Client.IndexUtils.ActiveRepos.ActiveRepoEntry instance GHC.Generics.Generic Distribution.Client.IndexUtils.ActiveRepos.ActiveRepos instance GHC.Show.Show Distribution.Client.IndexUtils.ActiveRepos.ActiveRepos instance GHC.Classes.Eq Distribution.Client.IndexUtils.ActiveRepos.ActiveRepos instance Data.Binary.Class.Binary Distribution.Client.IndexUtils.ActiveRepos.ActiveRepos instance Distribution.Utils.Structured.Structured Distribution.Client.IndexUtils.ActiveRepos.ActiveRepos instance Control.DeepSeq.NFData Distribution.Client.IndexUtils.ActiveRepos.ActiveRepos instance Distribution.Pretty.Pretty Distribution.Client.IndexUtils.ActiveRepos.ActiveRepos instance Distribution.Parsec.Parsec Distribution.Client.IndexUtils.ActiveRepos.ActiveRepos instance Data.Binary.Class.Binary Distribution.Client.IndexUtils.ActiveRepos.ActiveRepoEntry instance Distribution.Utils.Structured.Structured Distribution.Client.IndexUtils.ActiveRepos.ActiveRepoEntry instance Control.DeepSeq.NFData Distribution.Client.IndexUtils.ActiveRepos.ActiveRepoEntry instance Distribution.Pretty.Pretty Distribution.Client.IndexUtils.ActiveRepos.ActiveRepoEntry instance Distribution.Parsec.Parsec Distribution.Client.IndexUtils.ActiveRepos.ActiveRepoEntry instance Data.Binary.Class.Binary Distribution.Client.IndexUtils.ActiveRepos.CombineStrategy instance Distribution.Utils.Structured.Structured Distribution.Client.IndexUtils.ActiveRepos.CombineStrategy instance Control.DeepSeq.NFData Distribution.Client.IndexUtils.ActiveRepos.CombineStrategy instance Distribution.Pretty.Pretty Distribution.Client.IndexUtils.ActiveRepos.CombineStrategy instance Distribution.Parsec.Parsec Distribution.Client.IndexUtils.ActiveRepos.CombineStrategy module Distribution.Client.Types.SourceRepo -- | source-repository-package definition data SourceRepositoryPackage f SourceRepositoryPackage :: !RepoType -> !String -> !Maybe String -> !Maybe String -> !f FilePath -> ![String] -> SourceRepositoryPackage f [srpType] :: SourceRepositoryPackage f -> !RepoType [srpLocation] :: SourceRepositoryPackage f -> !String [srpTag] :: SourceRepositoryPackage f -> !Maybe String [srpBranch] :: SourceRepositoryPackage f -> !Maybe String [srpSubdir] :: SourceRepositoryPackage f -> !f FilePath [srpCommand] :: SourceRepositoryPackage f -> ![String] -- | Read from cabal.project type SourceRepoList = SourceRepositoryPackage [] -- | Distilled from SourceRepo type SourceRepoMaybe = SourceRepositoryPackage Maybe -- | SourceRepositoryPackage without subdir. Used in clone errors. -- Cloning doesn't care about subdirectory. type SourceRepoProxy = SourceRepositoryPackage Proxy srpHoist :: (forall x. f x -> g x) -> SourceRepositoryPackage f -> SourceRepositoryPackage g srpToProxy :: SourceRepositoryPackage f -> SourceRepositoryPackage Proxy -- | Split single source-repository-package declaration with -- multiple subdirs, into multiple ones with at most single subdir. srpFanOut :: SourceRepositoryPackage [] -> NonEmpty (SourceRepositoryPackage Maybe) sourceRepositoryPackageGrammar :: (FieldGrammar c g, Applicative (g SourceRepoList), c (Identity RepoType), c (List NoCommaFSep FilePathNT String), c (NonEmpty' NoCommaFSep Token String)) => g SourceRepoList SourceRepoList instance GHC.Generics.Generic (Distribution.Client.Types.SourceRepo.SourceRepositoryPackage f) instance GHC.Classes.Eq (f GHC.IO.FilePath) => GHC.Classes.Eq (Distribution.Client.Types.SourceRepo.SourceRepositoryPackage f) instance GHC.Classes.Ord (f GHC.IO.FilePath) => GHC.Classes.Ord (Distribution.Client.Types.SourceRepo.SourceRepositoryPackage f) instance GHC.Show.Show (f GHC.IO.FilePath) => GHC.Show.Show (Distribution.Client.Types.SourceRepo.SourceRepositoryPackage f) instance Data.Binary.Class.Binary (f GHC.IO.FilePath) => Data.Binary.Class.Binary (Distribution.Client.Types.SourceRepo.SourceRepositoryPackage f) instance (Data.Typeable.Internal.Typeable f, Distribution.Utils.Structured.Structured (f GHC.IO.FilePath)) => Distribution.Utils.Structured.Structured (Distribution.Client.Types.SourceRepo.SourceRepositoryPackage f) module Distribution.Client.Types.PackageLocation data PackageLocation local -- | An unpacked package in the given dir, or current dir LocalUnpackedPackage :: FilePath -> PackageLocation local -- | A package as a tarball that's available as a local tarball LocalTarballPackage :: FilePath -> PackageLocation local -- | A package as a tarball from a remote URI RemoteTarballPackage :: URI -> local -> PackageLocation local -- | A package available as a tarball from a repository. -- -- It may be from a local repository or from a remote repository, with a -- locally cached copy. ie a package available from hackage RepoTarballPackage :: Repo -> PackageId -> local -> PackageLocation local -- | A package available from a version control system source repository RemoteSourceRepoPackage :: SourceRepoMaybe -> local -> PackageLocation local type UnresolvedPkgLoc = PackageLocation (Maybe FilePath) type ResolvedPkgLoc = PackageLocation FilePath -- | Convenience alias for 'SourcePackage UnresolvedPkgLoc'. type UnresolvedSourcePackage = SourcePackage UnresolvedPkgLoc instance GHC.Generics.Generic (Distribution.Client.Types.PackageLocation.PackageLocation local) instance GHC.Classes.Ord local => GHC.Classes.Ord (Distribution.Client.Types.PackageLocation.PackageLocation local) instance GHC.Classes.Eq local => GHC.Classes.Eq (Distribution.Client.Types.PackageLocation.PackageLocation local) instance GHC.Base.Functor Distribution.Client.Types.PackageLocation.PackageLocation instance GHC.Show.Show local => GHC.Show.Show (Distribution.Client.Types.PackageLocation.PackageLocation local) instance Data.Binary.Class.Binary local => Data.Binary.Class.Binary (Distribution.Client.Types.PackageLocation.PackageLocation local) instance Distribution.Utils.Structured.Structured local => Distribution.Utils.Structured.Structured (Distribution.Client.Types.PackageLocation.PackageLocation local) module Distribution.Client.Types.SourcePackageDb -- | This is the information we get from a 00-index.tar.gz hackage -- index. data SourcePackageDb SourcePackageDb :: PackageIndex UnresolvedSourcePackage -> Map PackageName VersionRange -> SourcePackageDb [packageIndex] :: SourcePackageDb -> PackageIndex UnresolvedSourcePackage [packagePreferences] :: SourcePackageDb -> Map PackageName VersionRange -- | Does a case-sensitive search by package name and a range of versions. -- -- We get back any number of versions of the specified package name, all -- satisfying the version range constraint. -- -- Additionally, `preferred-versions` (such as version deprecation) are -- honoured in this lookup, which is the only difference to -- lookupDependency lookupDependency :: SourcePackageDb -> PackageName -> VersionRange -> [UnresolvedSourcePackage] -- | Does a case-sensitive search by package name. -- -- Additionally, `preferred-versions` (such as version deprecation) are -- honoured in this lookup, which is the only difference to -- lookupPackageName lookupPackageName :: SourcePackageDb -> PackageName -> [UnresolvedSourcePackage] instance GHC.Generics.Generic Distribution.Client.Types.SourcePackageDb.SourcePackageDb instance GHC.Classes.Eq Distribution.Client.Types.SourcePackageDb.SourcePackageDb instance Data.Binary.Class.Binary Distribution.Client.Types.SourcePackageDb.SourcePackageDb module Distribution.Client.Types.ReadyPackage -- | Like ConfiguredPackage, but with all dependencies guaranteed to -- be installed already, hence itself ready to be installed. newtype GenericReadyPackage srcpkg ReadyPackage :: srcpkg -> GenericReadyPackage srcpkg type ReadyPackage = GenericReadyPackage (ConfiguredPackage UnresolvedPkgLoc) instance Data.Binary.Class.Binary srcpkg => Data.Binary.Class.Binary (Distribution.Client.Types.ReadyPackage.GenericReadyPackage srcpkg) instance Distribution.Package.PackageInstalled srcpkg => Distribution.Package.PackageInstalled (Distribution.Client.Types.ReadyPackage.GenericReadyPackage srcpkg) instance Distribution.Package.HasUnitId srcpkg => Distribution.Package.HasUnitId (Distribution.Client.Types.ReadyPackage.GenericReadyPackage srcpkg) instance Distribution.Package.HasMungedPackageId srcpkg => Distribution.Package.HasMungedPackageId (Distribution.Client.Types.ReadyPackage.GenericReadyPackage srcpkg) instance Distribution.Solver.Types.PackageFixedDeps.PackageFixedDeps srcpkg => Distribution.Solver.Types.PackageFixedDeps.PackageFixedDeps (Distribution.Client.Types.ReadyPackage.GenericReadyPackage srcpkg) instance Distribution.Package.Package srcpkg => Distribution.Package.Package (Distribution.Client.Types.ReadyPackage.GenericReadyPackage srcpkg) instance GHC.Generics.Generic (Distribution.Client.Types.ReadyPackage.GenericReadyPackage srcpkg) instance GHC.Show.Show srcpkg => GHC.Show.Show (Distribution.Client.Types.ReadyPackage.GenericReadyPackage srcpkg) instance GHC.Classes.Eq srcpkg => GHC.Classes.Eq (Distribution.Client.Types.ReadyPackage.GenericReadyPackage srcpkg) instance Distribution.Compat.Graph.IsNode srcpkg => Distribution.Compat.Graph.IsNode (Distribution.Client.Types.ReadyPackage.GenericReadyPackage srcpkg) module Distribution.Client.Types.WriteGhcEnvironmentFilesPolicy -- | Whether 'v2-build' should write a .ghc.environment file after success. -- Possible values: always, never (the default), -- 'ghc8.4.4+' (8.4.4 is the earliest version that supports '-package-env -- -'). data WriteGhcEnvironmentFilesPolicy AlwaysWriteGhcEnvironmentFiles :: WriteGhcEnvironmentFilesPolicy NeverWriteGhcEnvironmentFiles :: WriteGhcEnvironmentFilesPolicy WriteGhcEnvironmentFilesOnlyForGhc844AndNewer :: WriteGhcEnvironmentFilesPolicy instance GHC.Show.Show Distribution.Client.Types.WriteGhcEnvironmentFilesPolicy.WriteGhcEnvironmentFilesPolicy instance GHC.Generics.Generic Distribution.Client.Types.WriteGhcEnvironmentFilesPolicy.WriteGhcEnvironmentFilesPolicy instance GHC.Enum.Bounded Distribution.Client.Types.WriteGhcEnvironmentFilesPolicy.WriteGhcEnvironmentFilesPolicy instance GHC.Enum.Enum Distribution.Client.Types.WriteGhcEnvironmentFilesPolicy.WriteGhcEnvironmentFilesPolicy instance GHC.Classes.Eq Distribution.Client.Types.WriteGhcEnvironmentFilesPolicy.WriteGhcEnvironmentFilesPolicy instance Data.Binary.Class.Binary Distribution.Client.Types.WriteGhcEnvironmentFilesPolicy.WriteGhcEnvironmentFilesPolicy instance Distribution.Utils.Structured.Structured Distribution.Client.Types.WriteGhcEnvironmentFilesPolicy.WriteGhcEnvironmentFilesPolicy -- | Various common data types for the entire cabal-install system module Distribution.Client.Types -- | The SolverInstallPlan is the graph of packages produced by the -- dependency solver, and specifies at the package-granularity what -- things are going to be installed. To put it another way: the -- dependency solver produces a SolverInstallPlan, which is then -- consumed by various other parts of Cabal. module Distribution.Client.SolverInstallPlan data SolverInstallPlan SolverInstallPlan :: !SolverPlanIndex -> !IndependentGoals -> SolverInstallPlan [planIndex] :: SolverInstallPlan -> !SolverPlanIndex [planIndepGoals] :: SolverInstallPlan -> !IndependentGoals type SolverPlanPackage = ResolverPackage UnresolvedPkgLoc -- | The dependency resolver picks either pre-existing installed packages -- or it picks source packages along with package configuration. -- -- This is like the PlanPackage but with fewer cases. data ResolverPackage loc PreExisting :: InstSolverPackage -> ResolverPackage loc Configured :: SolverPackage loc -> ResolverPackage loc -- | Build an installation plan from a valid set of resolved packages. new :: IndependentGoals -> SolverPlanIndex -> Either [SolverPlanProblem] SolverInstallPlan toList :: SolverInstallPlan -> [SolverPlanPackage] toMap :: SolverInstallPlan -> Map SolverId SolverPlanPackage -- | Remove packages from the install plan. This will result in an error if -- there are remaining packages that depend on any matching package. This -- is primarily useful for obtaining an install plan for the dependencies -- of a package or set of packages without actually installing the -- package itself, as when doing development. remove :: (SolverPlanPackage -> Bool) -> SolverInstallPlan -> Either [SolverPlanProblem] SolverInstallPlan showPlanIndex :: [SolverPlanPackage] -> String showInstallPlan :: SolverInstallPlan -> String -- | A valid installation plan is a set of packages that is acyclic, -- closed and consistent. Also, every -- ConfiguredPackage in the plan has to have a valid -- configuration (see configuredPackageValid). -- -- valid :: IndependentGoals -> SolverPlanIndex -> Bool -- | An installation plan is closed if for every package in the set, all of -- its dependencies are also in the set. That is, the set is closed under -- the dependency relation. -- -- closed :: SolverPlanIndex -> Bool -- | An installation plan is consistent if all dependencies that target a -- single package name, target the same version. -- -- This is slightly subtle. It is not the same as requiring that there be -- at most one version of any package in the set. It only requires that -- of packages which have more than one other package depending on them. -- We could actually make the condition even more precise and say that -- different versions are OK so long as they are not both in the -- transitive closure of any other package (or equivalently that their -- inverse closures do not intersect). The point is we do not want to -- have any packages depending directly or indirectly on two different -- versions of the same package. The current definition is just a safe -- approximation of that. -- -- consistent :: SolverPlanIndex -> Bool -- | The graph of packages (nodes) and dependencies (edges) must be -- acyclic. -- -- acyclic :: SolverPlanIndex -> Bool data SolverPlanProblem PackageMissingDeps :: SolverPlanPackage -> [PackageIdentifier] -> SolverPlanProblem PackageCycle :: [SolverPlanPackage] -> SolverPlanProblem PackageInconsistency :: PackageName -> [(PackageIdentifier, Version)] -> SolverPlanProblem PackageStateInvalid :: SolverPlanPackage -> SolverPlanPackage -> SolverPlanProblem showPlanProblem :: SolverPlanProblem -> String -- | For an invalid plan, produce a detailed list of problems as human -- readable error messages. This is mainly intended for debugging -- purposes. Use showPlanProblem for a human readable explanation. problems :: IndependentGoals -> SolverPlanIndex -> [SolverPlanProblem] -- | Compute the dependency closure of a package in a install plan dependencyClosure :: SolverInstallPlan -> [SolverId] -> [SolverPlanPackage] reverseDependencyClosure :: SolverInstallPlan -> [SolverId] -> [SolverPlanPackage] topologicalOrder :: SolverInstallPlan -> [SolverPlanPackage] reverseTopologicalOrder :: SolverInstallPlan -> [SolverPlanPackage] instance GHC.Generics.Generic Distribution.Client.SolverInstallPlan.SolverInstallPlan instance Data.Binary.Class.Binary Distribution.Client.SolverInstallPlan.SolverInstallPlan instance Distribution.Utils.Structured.Structured Distribution.Client.SolverInstallPlan.SolverInstallPlan -- | Functions to calculate nix-style hashes for package ids. -- -- The basic idea is simple, hash the combination of: -- -- module Distribution.Client.PackageHash -- | All the information that contributes to a package's hash, and thus its -- InstalledPackageId. data PackageHashInputs PackageHashInputs :: PackageId -> Maybe Component -> PackageSourceHash -> Set (PkgconfigName, Maybe PkgconfigVersion) -> Set InstalledPackageId -> PackageHashConfigInputs -> PackageHashInputs [pkgHashPkgId] :: PackageHashInputs -> PackageId [pkgHashComponent] :: PackageHashInputs -> Maybe Component [pkgHashSourceHash] :: PackageHashInputs -> PackageSourceHash [pkgHashPkgConfigDeps] :: PackageHashInputs -> Set (PkgconfigName, Maybe PkgconfigVersion) [pkgHashDirectDeps] :: PackageHashInputs -> Set InstalledPackageId [pkgHashOtherConfig] :: PackageHashInputs -> PackageHashConfigInputs -- | Those parts of the package configuration that contribute to the -- package hash. data PackageHashConfigInputs PackageHashConfigInputs :: CompilerId -> Platform -> FlagAssignment -> [String] -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> ProfDetailLevel -> ProfDetailLevel -> Bool -> OptimisationLevel -> Bool -> Bool -> Bool -> Bool -> DebugInfoLevel -> Map String [String] -> [FilePath] -> [FilePath] -> [FilePath] -> [FilePath] -> Maybe PathTemplate -> Maybe PathTemplate -> [Maybe PackageDB] -> Bool -> Bool -> Bool -> Maybe String -> Bool -> Bool -> Bool -> Bool -> Bool -> Maybe FilePath -> Bool -> Bool -> Maybe PathTemplate -> Maybe PathTemplate -> Maybe String -> Maybe String -> PackageHashConfigInputs [pkgHashCompilerId] :: PackageHashConfigInputs -> CompilerId [pkgHashPlatform] :: PackageHashConfigInputs -> Platform [pkgHashFlagAssignment] :: PackageHashConfigInputs -> FlagAssignment [pkgHashConfigureScriptArgs] :: PackageHashConfigInputs -> [String] [pkgHashVanillaLib] :: PackageHashConfigInputs -> Bool [pkgHashSharedLib] :: PackageHashConfigInputs -> Bool [pkgHashDynExe] :: PackageHashConfigInputs -> Bool [pkgHashFullyStaticExe] :: PackageHashConfigInputs -> Bool [pkgHashGHCiLib] :: PackageHashConfigInputs -> Bool [pkgHashProfLib] :: PackageHashConfigInputs -> Bool [pkgHashProfExe] :: PackageHashConfigInputs -> Bool [pkgHashProfLibDetail] :: PackageHashConfigInputs -> ProfDetailLevel [pkgHashProfExeDetail] :: PackageHashConfigInputs -> ProfDetailLevel [pkgHashCoverage] :: PackageHashConfigInputs -> Bool [pkgHashOptimization] :: PackageHashConfigInputs -> OptimisationLevel [pkgHashSplitObjs] :: PackageHashConfigInputs -> Bool [pkgHashSplitSections] :: PackageHashConfigInputs -> Bool [pkgHashStripLibs] :: PackageHashConfigInputs -> Bool [pkgHashStripExes] :: PackageHashConfigInputs -> Bool [pkgHashDebugInfo] :: PackageHashConfigInputs -> DebugInfoLevel [pkgHashProgramArgs] :: PackageHashConfigInputs -> Map String [String] [pkgHashExtraLibDirs] :: PackageHashConfigInputs -> [FilePath] [pkgHashExtraLibDirsStatic] :: PackageHashConfigInputs -> [FilePath] [pkgHashExtraFrameworkDirs] :: PackageHashConfigInputs -> [FilePath] [pkgHashExtraIncludeDirs] :: PackageHashConfigInputs -> [FilePath] [pkgHashProgPrefix] :: PackageHashConfigInputs -> Maybe PathTemplate [pkgHashProgSuffix] :: PackageHashConfigInputs -> Maybe PathTemplate [pkgHashPackageDbs] :: PackageHashConfigInputs -> [Maybe PackageDB] [pkgHashDocumentation] :: PackageHashConfigInputs -> Bool [pkgHashHaddockHoogle] :: PackageHashConfigInputs -> Bool [pkgHashHaddockHtml] :: PackageHashConfigInputs -> Bool [pkgHashHaddockHtmlLocation] :: PackageHashConfigInputs -> Maybe String [pkgHashHaddockForeignLibs] :: PackageHashConfigInputs -> Bool [pkgHashHaddockExecutables] :: PackageHashConfigInputs -> Bool [pkgHashHaddockTestSuites] :: PackageHashConfigInputs -> Bool [pkgHashHaddockBenchmarks] :: PackageHashConfigInputs -> Bool [pkgHashHaddockInternal] :: PackageHashConfigInputs -> Bool [pkgHashHaddockCss] :: PackageHashConfigInputs -> Maybe FilePath [pkgHashHaddockLinkedSource] :: PackageHashConfigInputs -> Bool [pkgHashHaddockQuickJump] :: PackageHashConfigInputs -> Bool [pkgHashHaddockContents] :: PackageHashConfigInputs -> Maybe PathTemplate [pkgHashHaddockIndex] :: PackageHashConfigInputs -> Maybe PathTemplate [pkgHashHaddockBaseUrl] :: PackageHashConfigInputs -> Maybe String [pkgHashHaddockLib] :: PackageHashConfigInputs -> Maybe String type PackageSourceHash = HashValue -- | Calculate a InstalledPackageId for a package using our -- nix-style inputs hashing method. -- -- Note that due to path length limitations on Windows, this function -- uses a different method on Windows that produces shorted package ids. -- See hashedInstalledPackageIdLong vs -- hashedInstalledPackageIdShort. hashedInstalledPackageId :: PackageHashInputs -> InstalledPackageId -- | Calculate the overall hash to be used for an -- InstalledPackageId. hashPackageHashInputs :: PackageHashInputs -> HashValue -- | Render a textual representation of the PackageHashInputs. -- -- The hashValue of this text is the overall package hash. renderPackageHashInputs :: PackageHashInputs -> ByteString -- | Calculate a InstalledPackageId for a package using our -- nix-style inputs hashing method. -- -- This produces large ids with big hashes. It is only suitable for -- systems without significant path length limitations (ie not Windows). hashedInstalledPackageIdLong :: PackageHashInputs -> InstalledPackageId -- | On Windows we have serious problems with path lengths. Windows imposes -- a maximum path length of 260 chars, and even if we can use the windows -- long path APIs ourselves, we cannot guarantee that ghc, gcc, ld, ar, -- etc etc all do so too. -- -- So our only choice is to limit the lengths of the paths, and the only -- real way to do that is to limit the size of the -- InstalledPackageIds that we generate. We do this by truncating -- the package names and versions and also by truncating the hash sizes. -- -- Truncating the package names and versions is technically ok because -- they are just included for human convenience, the full source package -- id is included in the hash. -- -- Truncating the hash size is disappointing but also technically ok. We -- rely on the hash primarily for collision avoidance not for any -- security properties (at least for now). hashedInstalledPackageIdShort :: PackageHashInputs -> InstalledPackageId instance GHC.Show.Show Distribution.Client.PackageHash.PackageHashConfigInputs -- | Package installation plan module Distribution.Client.InstallPlan -- | GenericInstallPlan specialised to most commonly used types. type InstallPlan = GenericInstallPlan InstalledPackageInfo (ConfiguredPackage UnresolvedPkgLoc) data GenericInstallPlan ipkg srcpkg type PlanPackage = GenericPlanPackage InstalledPackageInfo (ConfiguredPackage UnresolvedPkgLoc) -- | Packages in an install plan -- -- NOTE: ConfiguredPackage, GenericReadyPackage and -- GenericPlanPackage intentionally have no -- PackageInstalled instance. `This is important: -- PackageInstalled returns only library dependencies, but for package -- that aren't yet installed we know many more kinds of dependencies -- (setup dependencies, exe, test-suite, benchmark, ..). Any functions -- that operate on dependencies in cabal-install should consider what to -- do with these dependencies; if we give a PackageInstalled -- instance it would be too easy to get this wrong (and, for instance, -- call graph traversal functions from Cabal rather than from -- cabal-install). Instead, see PackageInstalled. data GenericPlanPackage ipkg srcpkg PreExisting :: ipkg -> GenericPlanPackage ipkg srcpkg Configured :: srcpkg -> GenericPlanPackage ipkg srcpkg Installed :: srcpkg -> GenericPlanPackage ipkg srcpkg -- | Convenience combinator for destructing GenericPlanPackage. This -- is handy because if you case manually, you have to handle -- Configured and Installed separately (where often you -- want them to be the same.) foldPlanPackage :: (ipkg -> a) -> (srcpkg -> a) -> GenericPlanPackage ipkg srcpkg -> a type IsUnit a = (IsNode a, Key a ~ UnitId) -- | Build an installation plan from a valid set of resolved packages. new :: (IsUnit ipkg, IsUnit srcpkg) => IndependentGoals -> Graph (GenericPlanPackage ipkg srcpkg) -> GenericInstallPlan ipkg srcpkg toGraph :: GenericInstallPlan ipkg srcpkg -> Graph (GenericPlanPackage ipkg srcpkg) toList :: GenericInstallPlan ipkg srcpkg -> [GenericPlanPackage ipkg srcpkg] toMap :: GenericInstallPlan ipkg srcpkg -> Map UnitId (GenericPlanPackage ipkg srcpkg) keys :: GenericInstallPlan ipkg srcpkg -> [UnitId] keysSet :: GenericInstallPlan ipkg srcpkg -> Set UnitId planIndepGoals :: GenericInstallPlan ipkg srcpkg -> IndependentGoals depends :: IsUnit a => a -> [UnitId] fromSolverInstallPlan :: (IsUnit ipkg, IsUnit srcpkg) => ((SolverId -> [GenericPlanPackage ipkg srcpkg]) -> SolverPlanPackage -> [GenericPlanPackage ipkg srcpkg]) -> SolverInstallPlan -> GenericInstallPlan ipkg srcpkg fromSolverInstallPlanWithProgress :: (IsUnit ipkg, IsUnit srcpkg) => ((SolverId -> [GenericPlanPackage ipkg srcpkg]) -> SolverPlanPackage -> LogProgress [GenericPlanPackage ipkg srcpkg]) -> SolverInstallPlan -> LogProgress (GenericInstallPlan ipkg srcpkg) -- | Conversion of SolverInstallPlan to InstallPlan. Similar -- to elaboratedInstallPlan configureInstallPlan :: ConfigFlags -> SolverInstallPlan -> InstallPlan -- | Remove packages from the install plan. This will result in an error if -- there are remaining packages that depend on any matching package. This -- is primarily useful for obtaining an install plan for the dependencies -- of a package or set of packages without actually installing the -- package itself, as when doing development. remove :: (IsUnit ipkg, IsUnit srcpkg) => (GenericPlanPackage ipkg srcpkg -> Bool) -> GenericInstallPlan ipkg srcpkg -> GenericInstallPlan ipkg srcpkg -- | Change a number of packages in the Configured state to the -- Installed state. -- -- To preserve invariants, the package must have all of its dependencies -- already installed too (that is PreExisting or -- Installed). installed :: (IsUnit ipkg, IsUnit srcpkg) => (srcpkg -> Bool) -> GenericInstallPlan ipkg srcpkg -> GenericInstallPlan ipkg srcpkg -- | Lookup a package in the plan. lookup :: (IsUnit ipkg, IsUnit srcpkg) => GenericInstallPlan ipkg srcpkg -> UnitId -> Maybe (GenericPlanPackage ipkg srcpkg) -- | Find all the direct dependencies of the given package. -- -- Note that the package must exist in the plan or it is an error. directDeps :: GenericInstallPlan ipkg srcpkg -> UnitId -> [GenericPlanPackage ipkg srcpkg] -- | Find all the direct reverse dependencies of the given package. -- -- Note that the package must exist in the plan or it is an error. revDirectDeps :: GenericInstallPlan ipkg srcpkg -> UnitId -> [GenericPlanPackage ipkg srcpkg] -- | Flatten an InstallPlan, producing the sequence of source -- packages in the order in which they would be processed when the plan -- is executed. This can be used for simulations or presenting execution -- dry-runs. -- -- It is guaranteed to give the same order as using execute (with -- a serial in-order JobControl), which is a reverse topological -- orderings of the source packages in the dependency graph, albeit not -- necessarily exactly the same ordering as that produced by -- reverseTopologicalOrder. executionOrder :: (IsUnit ipkg, IsUnit srcpkg) => GenericInstallPlan ipkg srcpkg -> [GenericReadyPackage srcpkg] -- | Execute an install plan. This traverses the plan in dependency order. -- -- Executing each individual package can fail and if so all dependents -- fail too. The result for each package is collected as a -- BuildOutcomes map. -- -- Visiting each package happens with optional parallelism, as determined -- by the JobControl. By default, after any failure we stop as -- soon as possible (using the JobControl to try to cancel -- in-progress tasks). This behaviour can be reversed to keep going and -- build as many packages as possible. -- -- Note that the BuildOutcomes is not guaranteed to cover -- all the packages in the plan. In particular in the default mode where -- we stop as soon as possible after a failure then there may be packages -- which are skipped and these will have no BuildOutcome. execute :: forall m ipkg srcpkg result failure. (IsUnit ipkg, IsUnit srcpkg, Monad m) => JobControl m (UnitId, Either failure result) -> Bool -> (srcpkg -> failure) -> GenericInstallPlan ipkg srcpkg -> (GenericReadyPackage srcpkg -> m (Either failure result)) -> m (BuildOutcomes failure result) -- | The set of results we get from executing an install plan. type BuildOutcomes failure result = Map UnitId (Either failure result) -- | Lookup the build result for a single package. lookupBuildOutcome :: HasUnitId pkg => pkg -> BuildOutcomes failure result -> Maybe (Either failure result) -- | The Processing type is used to keep track of the state of a -- traversal and includes the set of packages that are in the processing -- state, e.g. in the process of being installed, plus those that have -- been completed and those where processing failed. data Processing -- | The packages in the plan that are initially ready to be installed. -- That is they are in the configured state and have all their -- dependencies installed already. -- -- The result is both the packages that are now ready to be installed and -- also a Processing state containing those same packages. The -- assumption is that all the packages that are ready will now be -- processed and so we can consider them to be in the processing state. ready :: (IsUnit ipkg, IsUnit srcpkg) => GenericInstallPlan ipkg srcpkg -> ([GenericReadyPackage srcpkg], Processing) -- | Given a package in the processing state, mark the package as completed -- and return any packages that are newly in the processing state (ie -- ready to process), along with the updated Processing state. completed :: forall ipkg srcpkg. (IsUnit ipkg, IsUnit srcpkg) => GenericInstallPlan ipkg srcpkg -> Processing -> UnitId -> ([GenericReadyPackage srcpkg], Processing) failed :: (IsUnit ipkg, IsUnit srcpkg) => GenericInstallPlan ipkg srcpkg -> Processing -> UnitId -> ([srcpkg], Processing) showPlanGraph :: (Package ipkg, Package srcpkg, IsUnit ipkg, IsUnit srcpkg) => Graph (GenericPlanPackage ipkg srcpkg) -> String showInstallPlan :: (Package ipkg, Package srcpkg, IsUnit ipkg, IsUnit srcpkg) => GenericInstallPlan ipkg srcpkg -> String -- | Return the packages in the plan that are direct or indirect -- dependencies of the given packages. dependencyClosure :: GenericInstallPlan ipkg srcpkg -> [UnitId] -> [GenericPlanPackage ipkg srcpkg] -- | Return all the packages in the InstallPlan in reverse -- topological order. That is, for each package, all dependencies of the -- package appear first. -- -- Compared to executionOrder, this function returns all the -- installed and source packages rather than just the source ones. Also, -- while both this and executionOrder produce reverse topological -- orderings of the package dependency graph, it is not necessarily -- exactly the same order. reverseTopologicalOrder :: GenericInstallPlan ipkg srcpkg -> [GenericPlanPackage ipkg srcpkg] -- | Return the packages in the plan that depend directly or indirectly on -- the given packages. reverseDependencyClosure :: GenericInstallPlan ipkg srcpkg -> [UnitId] -> [GenericPlanPackage ipkg srcpkg] instance GHC.Generics.Generic (Distribution.Client.InstallPlan.GenericPlanPackage ipkg srcpkg) instance (GHC.Show.Show ipkg, GHC.Show.Show srcpkg) => GHC.Show.Show (Distribution.Client.InstallPlan.GenericPlanPackage ipkg srcpkg) instance (GHC.Classes.Eq ipkg, GHC.Classes.Eq srcpkg) => GHC.Classes.Eq (Distribution.Client.InstallPlan.GenericPlanPackage ipkg srcpkg) instance (Distribution.Utils.Structured.Structured ipkg, Distribution.Utils.Structured.Structured srcpkg) => Distribution.Utils.Structured.Structured (Distribution.Client.InstallPlan.GenericInstallPlan ipkg srcpkg) instance (Distribution.Compat.Graph.IsNode ipkg, Distribution.Compat.Graph.Key ipkg GHC.Types.~ Distribution.Types.UnitId.UnitId, Distribution.Compat.Graph.IsNode srcpkg, Distribution.Compat.Graph.Key srcpkg GHC.Types.~ Distribution.Types.UnitId.UnitId, Data.Binary.Class.Binary ipkg, Data.Binary.Class.Binary srcpkg) => Data.Binary.Class.Binary (Distribution.Client.InstallPlan.GenericInstallPlan ipkg srcpkg) instance (Distribution.Compat.Graph.IsNode ipkg, Distribution.Compat.Graph.IsNode srcpkg, Distribution.Compat.Graph.Key ipkg GHC.Types.~ Distribution.Types.UnitId.UnitId, Distribution.Compat.Graph.Key srcpkg GHC.Types.~ Distribution.Types.UnitId.UnitId) => Distribution.Compat.Graph.IsNode (Distribution.Client.InstallPlan.GenericPlanPackage ipkg srcpkg) instance (Data.Binary.Class.Binary ipkg, Data.Binary.Class.Binary srcpkg) => Data.Binary.Class.Binary (Distribution.Client.InstallPlan.GenericPlanPackage ipkg srcpkg) instance (Distribution.Utils.Structured.Structured ipkg, Distribution.Utils.Structured.Structured srcpkg) => Distribution.Utils.Structured.Structured (Distribution.Client.InstallPlan.GenericPlanPackage ipkg srcpkg) instance (Distribution.Package.Package ipkg, Distribution.Package.Package srcpkg) => Distribution.Package.Package (Distribution.Client.InstallPlan.GenericPlanPackage ipkg srcpkg) instance (Distribution.Package.HasMungedPackageId ipkg, Distribution.Package.HasMungedPackageId srcpkg) => Distribution.Package.HasMungedPackageId (Distribution.Client.InstallPlan.GenericPlanPackage ipkg srcpkg) instance (Distribution.Package.HasUnitId ipkg, Distribution.Package.HasUnitId srcpkg) => Distribution.Package.HasUnitId (Distribution.Client.InstallPlan.GenericPlanPackage ipkg srcpkg) instance (Distribution.Client.Types.ConfiguredId.HasConfiguredId ipkg, Distribution.Client.Types.ConfiguredId.HasConfiguredId srcpkg) => Distribution.Client.Types.ConfiguredId.HasConfiguredId (Distribution.Client.InstallPlan.GenericPlanPackage ipkg srcpkg) module Distribution.Client.Utils data MergeResult a b OnlyInLeft :: a -> MergeResult a b InBoth :: a -> b -> MergeResult a b OnlyInRight :: b -> MergeResult a b -- | Generic merging utility. For sorted input lists this is a full outer -- join. mergeBy :: forall a b. (a -> b -> Ordering) -> [a] -> [b] -> [MergeResult a b] duplicates :: Ord a => [a] -> [[a]] duplicatesBy :: forall a. (a -> a -> Ordering) -> [a] -> [[a]] -- | Parse a string using the Read instance. Succeeds if there is -- exactly one valid result. -- --
--   >>> readMaybe "123" :: Maybe Int
--   Just 123
--   
-- --
--   >>> readMaybe "hello" :: Maybe Int
--   Nothing
--   
readMaybe :: Read a => String -> Maybe a -- | Executes the action in the specified directory. -- -- Warning: This operation is NOT thread-safe, because current working -- directory is a process-global concept. inDir :: Maybe FilePath -> IO a -> IO a -- | Executes the action with an environment variable set to some value. -- -- Warning: This operation is NOT thread-safe, because current -- environment is a process-global concept. withEnv :: String -> String -> IO a -> IO a -- | Executes the action with a list of environment variables and -- corresponding overrides, where -- -- -- -- Warning: This operation is NOT thread-safe, because current -- environment is a process-global concept. withEnvOverrides :: [(String, Maybe FilePath)] -> IO a -> IO a -- | Log directory change in make compatible syntax logDirChange :: (String -> IO ()) -> Maybe FilePath -> IO a -> IO a -- | Executes the action, increasing the PATH environment in some way -- -- Warning: This operation is NOT thread-safe, because the environment -- variables are a process-global concept. withExtraPathEnv :: [FilePath] -> IO a -> IO a -- | Determine the number of jobs to use given the value of the '-j' flag. determineNumJobs :: Flag (Maybe Int) -> Int numberOfProcessors :: Int -- | Like removeFile, but does not throw an exception when the file -- does not exist. removeExistingFile :: FilePath -> IO () -- | A variant of withTempFile that only gives us the file name, -- and while it will clean up the file afterwards, it's lenient if the -- file is moved/deleted. withTempFileName :: FilePath -> String -> (FilePath -> IO a) -> IO a -- | Given a relative path, make it absolute relative to the current -- directory. Absolute paths are returned unmodified. makeAbsoluteToCwd :: FilePath -> IO FilePath -- | Given a path (relative or absolute), make it relative to the current -- directory, including using ../.. if necessary. makeRelativeToCwd :: FilePath -> IO FilePath -- | Given a path (relative or absolute), make it relative to the given -- directory, including using ../.. if necessary. makeRelativeToDir :: FilePath -> FilePath -> IO FilePath -- | Given a canonical absolute path and canonical absolute dir, make the -- path relative to the directory, including using ../.. if -- necessary. Returns the original absolute path if it is not on the same -- drive as the given dir. makeRelativeCanonical :: FilePath -> FilePath -> FilePath -- | Convert a FilePath to a lazy ByteString. Each -- Char is encoded as a little-endian Word32. filePathToByteString :: FilePath -> ByteString -- | Reverse operation to filePathToByteString. byteStringToFilePath :: ByteString -> FilePath -- | Workaround for the inconsistent behaviour of canonicalizePath. -- Always throws an error if the path refers to a non-existent file. tryCanonicalizePath :: FilePath -> IO FilePath -- | A non-throwing wrapper for canonicalizePath. If -- canonicalizePath throws an exception, returns the path argument -- unmodified. canonicalizePathNoThrow :: FilePath -> IO FilePath -- | Like Distribution.Simple.Utils.moreRecentFile, but uses getModTime -- instead of getModificationTime for higher precision. We can't merge -- the two because Distribution.Client.Time uses MIN_VERSION macros. moreRecentFile :: FilePath -> FilePath -> IO Bool -- | Like moreRecentFile, but also checks that the first file -- exists. existsAndIsMoreRecentThan :: FilePath -> FilePath -> IO Bool -- | Like tryFindPackageDesc, but with error specific to add-source -- deps. tryFindAddSourcePackageDesc :: Verbosity -> FilePath -> String -> IO FilePath -- | Try to find a .cabal file, in directory depPath. -- Fails if one cannot be found, with err prefixing the error -- message. This function simply allows us to give a more descriptive -- error than that provided by findPackageDesc. tryFindPackageDesc :: Verbosity -> FilePath -> String -> IO FilePath findOpenProgramLocation :: Platform -> IO (Either String FilePath) -- | Sets the handler for encoding errors to one that transliterates -- invalid characters into one present in the encoding (i.e., '?'). This -- is opposed to the default behavior, which is to throw an exception on -- error. This function will ignore file handles that have a Unicode -- encoding set. It's a no-op for versions of base less than -- 4.4. relaxEncodingErrors :: Handle -> IO () -- | Phase of building a dependency. Represents current status of package -- dependency processing. See #4040 for details. data ProgressPhase ProgressDownloading :: ProgressPhase ProgressDownloaded :: ProgressPhase ProgressStarting :: ProgressPhase ProgressBuilding :: ProgressPhase ProgressHaddock :: ProgressPhase ProgressInstalling :: ProgressPhase ProgressCompleted :: ProgressPhase progressMessage :: Verbosity -> ProgressPhase -> String -> IO () -- | Given a version, return an API-compatible (according to PVP) version -- range. -- -- If the boolean argument denotes whether to use a desugared -- representation (if True) or the new-style ^>=-form -- (if False). -- -- Example: pvpize True (mkVersion [0,4,1]) produces the version -- range >= 0.4 && < 0.5 (which is the same as -- 0.4.*). pvpize :: Bool -> Version -> VersionRange -- | Increment the nth version component (counting from 0). incVersion :: Int -> Version -> Version -- | Returns the current calendar year. getCurrentYear :: IO Integer -- | From System.Directory.Extra -- https://hackage.haskell.org/package/extra-1.7.9 listFilesRecursive :: FilePath -> IO [FilePath] -- | From System.Directory.Extra -- https://hackage.haskell.org/package/extra-1.7.9 listFilesInside :: (FilePath -> IO Bool) -> FilePath -> IO [FilePath] safeRead :: Read a => String -> Maybe a -- | hasElem xs x = elem x xs except that xs is turned -- into a Set first. Use underapplied to speed up subsequent -- lookups, e.g. filter (hasElem xs) ys. Only amortized when -- used several times! -- -- Time complexity <math> for <math> lookups in a list of -- length <math>. (Compare this to elem's <math>.) -- -- This is Agda.Utils.List.hasElem. hasElem :: Ord a => [a] -> a -> Bool -- | Utilities to implement cabal v2-sdist. module Distribution.Client.SrcDist -- | List all source files of a given add-source dependency. Exits with -- error if something is wrong (e.g. there is no .cabal file in the given -- directory). -- -- Used in sandbox and projectbuilding. TODO: when sandboxes are removed, -- move to ProjectBuilding. allPackageSourceFiles :: Verbosity -> FilePath -> IO [FilePath] -- | Create a tarball for a package in a directory packageDirToSdist :: Verbosity -> GenericPackageDescription -> FilePath -> IO ByteString -- | Implementation of the run command. module Distribution.Client.Run -- | Run a given executable. run :: Verbosity -> LocalBuildInfo -> Executable -> [String] -> IO () -- | Return the executable to run and any extra arguments that should be -- forwarded to it. Die in case of error. splitRunArgs :: Verbosity -> LocalBuildInfo -> [String] -> IO (Executable, [String]) -- | Some types used by the 'cabal init' command. module Distribution.Client.Init.Types -- | InitFlags is a subset of flags available in the .cabal file -- that represent options that are relevant to the init command process. data InitFlags InitFlags :: Flag Bool -> Flag Bool -> Flag FilePath -> Flag Bool -> Flag Bool -> Flag Bool -> Flag PackageName -> Flag Version -> Flag CabalSpecVersion -> Flag SpecLicense -> Flag String -> Flag String -> Flag String -> Flag String -> Flag String -> Flag [String] -> Flag [String] -> Flag PackageType -> Flag FilePath -> Flag Language -> Flag [ModuleName] -> Flag [ModuleName] -> Flag [Extension] -> Flag [Dependency] -> Flag [String] -> Flag [String] -> Flag [String] -> Flag Bool -> Flag [String] -> Flag FilePath -> Flag Verbosity -> Flag Bool -> InitFlags [interactive] :: InitFlags -> Flag Bool [quiet] :: InitFlags -> Flag Bool [packageDir] :: InitFlags -> Flag FilePath [noComments] :: InitFlags -> Flag Bool [minimal] :: InitFlags -> Flag Bool [simpleProject] :: InitFlags -> Flag Bool [packageName] :: InitFlags -> Flag PackageName [version] :: InitFlags -> Flag Version [cabalVersion] :: InitFlags -> Flag CabalSpecVersion [license] :: InitFlags -> Flag SpecLicense [author] :: InitFlags -> Flag String [email] :: InitFlags -> Flag String [homepage] :: InitFlags -> Flag String [synopsis] :: InitFlags -> Flag String [category] :: InitFlags -> Flag String [extraSrc] :: InitFlags -> Flag [String] [extraDoc] :: InitFlags -> Flag [String] [packageType] :: InitFlags -> Flag PackageType [mainIs] :: InitFlags -> Flag FilePath [language] :: InitFlags -> Flag Language [exposedModules] :: InitFlags -> Flag [ModuleName] [otherModules] :: InitFlags -> Flag [ModuleName] [otherExts] :: InitFlags -> Flag [Extension] [dependencies] :: InitFlags -> Flag [Dependency] [applicationDirs] :: InitFlags -> Flag [String] [sourceDirs] :: InitFlags -> Flag [String] [buildTools] :: InitFlags -> Flag [String] [initializeTestSuite] :: InitFlags -> Flag Bool [testDirs] :: InitFlags -> Flag [String] [initHcPath] :: InitFlags -> Flag FilePath [initVerbosity] :: InitFlags -> Flag Verbosity [overwrite] :: InitFlags -> Flag Bool -- | PkgDescription represents the relevant options set by the user -- when building a package description during the init command process. data PkgDescription PkgDescription :: CabalSpecVersion -> PackageName -> Version -> SpecLicense -> String -> String -> String -> String -> String -> Set String -> Maybe (Set String) -> PkgDescription [_pkgCabalVersion] :: PkgDescription -> CabalSpecVersion [_pkgName] :: PkgDescription -> PackageName [_pkgVersion] :: PkgDescription -> Version [_pkgLicense] :: PkgDescription -> SpecLicense [_pkgAuthor] :: PkgDescription -> String [_pkgEmail] :: PkgDescription -> String [_pkgHomePage] :: PkgDescription -> String [_pkgSynopsis] :: PkgDescription -> String [_pkgCategory] :: PkgDescription -> String [_pkgExtraSrcFiles] :: PkgDescription -> Set String [_pkgExtraDocFiles] :: PkgDescription -> Maybe (Set String) -- | LibTarget represents the relevant options set by the user when -- building a library package during the init command process. data LibTarget LibTarget :: [String] -> Language -> NonEmpty ModuleName -> [ModuleName] -> [Extension] -> [Dependency] -> [Dependency] -> LibTarget [_libSourceDirs] :: LibTarget -> [String] [_libLanguage] :: LibTarget -> Language [_libExposedModules] :: LibTarget -> NonEmpty ModuleName [_libOtherModules] :: LibTarget -> [ModuleName] [_libOtherExts] :: LibTarget -> [Extension] [_libDependencies] :: LibTarget -> [Dependency] [_libBuildTools] :: LibTarget -> [Dependency] -- | ExeTarget represents the relevant options set by the user when -- building an executable package. data ExeTarget ExeTarget :: HsFilePath -> [String] -> Language -> [ModuleName] -> [Extension] -> [Dependency] -> [Dependency] -> ExeTarget [_exeMainIs] :: ExeTarget -> HsFilePath [_exeApplicationDirs] :: ExeTarget -> [String] [_exeLanguage] :: ExeTarget -> Language [_exeOtherModules] :: ExeTarget -> [ModuleName] [_exeOtherExts] :: ExeTarget -> [Extension] [_exeDependencies] :: ExeTarget -> [Dependency] [_exeBuildTools] :: ExeTarget -> [Dependency] -- | TestTarget represents the relevant options set by the user when -- building a library package. data TestTarget TestTarget :: HsFilePath -> [String] -> Language -> [ModuleName] -> [Extension] -> [Dependency] -> [Dependency] -> TestTarget [_testMainIs] :: TestTarget -> HsFilePath [_testDirs] :: TestTarget -> [String] [_testLanguage] :: TestTarget -> Language [_testOtherModules] :: TestTarget -> [ModuleName] [_testOtherExts] :: TestTarget -> [Extension] [_testDependencies] :: TestTarget -> [Dependency] [_testBuildTools] :: TestTarget -> [Dependency] -- | Enum to denote whether the user wants to build a library target, -- executable target, library and executable targets, or a standalone -- test suite. data PackageType Library :: PackageType Executable :: PackageType LibraryAndExecutable :: PackageType TestSuite :: PackageType data HsFilePath HsFilePath :: FilePath -> HsFileType -> HsFilePath [_hsFilePath] :: HsFilePath -> FilePath [_hsFileType] :: HsFilePath -> HsFileType data HsFileType Literate :: HsFileType Standard :: HsFileType InvalidHsPath :: HsFileType fromHsFilePath :: HsFilePath -> Maybe FilePath toHsFilePath :: FilePath -> HsFilePath toLiterateHs :: HsFilePath -> HsFilePath toStandardHs :: HsFilePath -> HsFilePath mkLiterate :: HsFilePath -> [String] -> [String] isHsFilePath :: FilePath -> Bool class Monad m => Interactive m getLine :: Interactive m => m String readFile :: Interactive m => FilePath -> m String getCurrentDirectory :: Interactive m => m FilePath getHomeDirectory :: Interactive m => m FilePath getDirectoryContents :: Interactive m => FilePath -> m [FilePath] listDirectory :: Interactive m => FilePath -> m [FilePath] doesDirectoryExist :: Interactive m => FilePath -> m Bool doesFileExist :: Interactive m => FilePath -> m Bool canonicalizePathNoThrow :: Interactive m => FilePath -> m FilePath readProcessWithExitCode :: Interactive m => FilePath -> [String] -> String -> m (ExitCode, String, String) getEnvironment :: Interactive m => m [(String, String)] getCurrentYear :: Interactive m => m Integer listFilesInside :: Interactive m => (FilePath -> m Bool) -> FilePath -> m [FilePath] listFilesRecursive :: Interactive m => FilePath -> m [FilePath] putStr :: Interactive m => String -> m () putStrLn :: Interactive m => String -> m () createDirectory :: Interactive m => FilePath -> m () removeDirectory :: Interactive m => FilePath -> m () writeFile :: Interactive m => FilePath -> String -> m () removeExistingFile :: Interactive m => FilePath -> m () copyFile :: Interactive m => FilePath -> FilePath -> m () renameDirectory :: Interactive m => FilePath -> FilePath -> m () hFlush :: Interactive m => Handle -> m () message :: Interactive m => Verbosity -> Severity -> String -> m () break :: Interactive m => m Bool throwPrompt :: Interactive m => BreakException -> m a -- | A pure exception thrown exclusively by the pure prompter to cancel -- infinite loops in the prompting process. -- -- For example, in order to break on parse errors, or user-driven -- continuations that do not make sense to test. newtype BreakException BreakException :: String -> BreakException newtype PurePrompt a PurePrompt :: (NonEmpty String -> Either BreakException (a, NonEmpty String)) -> PurePrompt a [_runPrompt] :: PurePrompt a -> NonEmpty String -> Either BreakException (a, NonEmpty String) evalPrompt :: PurePrompt a -> NonEmpty String -> a -- | Used to inform the intent of prompted messages. data Severity Log :: Severity Info :: Severity Warning :: Severity Error :: Severity -- | Convenience alias for the literate haskell flag type IsLiterate = Bool -- | Convenience alias for generating simple projects type IsSimple = Bool data WriteOpts WriteOpts :: Bool -> Bool -> Bool -> Verbosity -> FilePath -> PackageType -> PackageName -> CabalSpecVersion -> WriteOpts [_optOverwrite] :: WriteOpts -> Bool [_optMinimal] :: WriteOpts -> Bool [_optNoComments] :: WriteOpts -> Bool [_optVerbosity] :: WriteOpts -> Verbosity [_optPkgDir] :: WriteOpts -> FilePath [_optPkgType] :: WriteOpts -> PackageType [_optPkgName] :: WriteOpts -> PackageName [_optCabalSpec] :: WriteOpts -> CabalSpecVersion data ProjectSettings ProjectSettings :: WriteOpts -> PkgDescription -> Maybe LibTarget -> Maybe ExeTarget -> Maybe TestTarget -> ProjectSettings [_pkgOpts] :: ProjectSettings -> WriteOpts [_pkgDesc] :: ProjectSettings -> PkgDescription [_pkgLibTarget] :: ProjectSettings -> Maybe LibTarget [_pkgExeTarget] :: ProjectSettings -> Maybe ExeTarget [_pkgTestTarget] :: ProjectSettings -> Maybe TestTarget -- | Annotations for cabal file PrettyField. data FieldAnnotation FieldAnnotation :: Bool -> CommentPosition -> FieldAnnotation -- | True iif the field and its contents should be commented out. [annCommentedOut] :: FieldAnnotation -> Bool -- | Comment lines to place before the field or section. [annCommentLines] :: FieldAnnotation -> CommentPosition -- | Defines whether or not a prompt will have a default value, is -- optional, or is mandatory. data DefaultPrompt t DefaultPrompt :: t -> DefaultPrompt t OptionalPrompt :: DefaultPrompt t MandatoryPrompt :: DefaultPrompt t instance GHC.Classes.Eq Distribution.Client.Init.Types.PkgDescription instance GHC.Show.Show Distribution.Client.Init.Types.PkgDescription instance GHC.Classes.Eq Distribution.Client.Init.Types.LibTarget instance GHC.Show.Show Distribution.Client.Init.Types.LibTarget instance GHC.Generics.Generic Distribution.Client.Init.Types.PackageType instance GHC.Show.Show Distribution.Client.Init.Types.PackageType instance GHC.Classes.Eq Distribution.Client.Init.Types.PackageType instance GHC.Show.Show Distribution.Client.Init.Types.WriteOpts instance GHC.Classes.Eq Distribution.Client.Init.Types.WriteOpts instance GHC.Generics.Generic Distribution.Client.Init.Types.InitFlags instance GHC.Show.Show Distribution.Client.Init.Types.InitFlags instance GHC.Classes.Eq Distribution.Client.Init.Types.InitFlags instance GHC.Show.Show Distribution.Client.Init.Types.HsFileType instance GHC.Classes.Eq Distribution.Client.Init.Types.HsFileType instance GHC.Classes.Eq Distribution.Client.Init.Types.HsFilePath instance GHC.Classes.Eq Distribution.Client.Init.Types.TestTarget instance GHC.Show.Show Distribution.Client.Init.Types.TestTarget instance GHC.Classes.Eq Distribution.Client.Init.Types.ExeTarget instance GHC.Show.Show Distribution.Client.Init.Types.ExeTarget instance GHC.Show.Show Distribution.Client.Init.Types.ProjectSettings instance GHC.Classes.Eq Distribution.Client.Init.Types.ProjectSettings instance GHC.Show.Show Distribution.Client.Init.Types.BreakException instance GHC.Classes.Eq Distribution.Client.Init.Types.BreakException instance GHC.Base.Functor Distribution.Client.Init.Types.PurePrompt instance GHC.Show.Show Distribution.Client.Init.Types.Severity instance GHC.Classes.Eq Distribution.Client.Init.Types.Severity instance GHC.Base.Functor Distribution.Client.Init.Types.DefaultPrompt instance GHC.Classes.Eq t => GHC.Classes.Eq (Distribution.Client.Init.Types.DefaultPrompt t) instance Distribution.Client.Init.Types.Interactive GHC.Types.IO instance Distribution.Client.Init.Types.Interactive Distribution.Client.Init.Types.PurePrompt instance GHC.Base.Applicative Distribution.Client.Init.Types.PurePrompt instance GHC.Base.Monad Distribution.Client.Init.Types.PurePrompt instance GHC.Exception.Type.Exception Distribution.Client.Init.Types.BreakException instance GHC.Show.Show Distribution.Client.Init.Types.HsFilePath instance GHC.Base.Monoid Distribution.Client.Init.Types.InitFlags instance GHC.Base.Semigroup Distribution.Client.Init.Types.InitFlags -- | User prompt utility functions for use by the 'cabal init' command. module Distribution.Client.Init.Prompt -- | Create a prompt with optional default value that returns a value of -- some Text instance. prompt :: (Interactive m, Parsec t, Pretty t) => String -> DefaultPrompt t -> m t -- | Create a yes/no prompt with optional default value. promptYesNo :: Interactive m => String -> DefaultPrompt Bool -> m Bool -- | Create a prompt with optional default value that returns a String. promptStr :: Interactive m => String -> DefaultPrompt String -> m String -- | Create a prompt from a list of strings promptList :: Interactive m => String -> [String] -> DefaultPrompt String -> Maybe (String -> String) -> Bool -> m String -- | Pretty printing and field formatting utilities used for file creation. module Distribution.Client.Init.Format listFieldS :: [String] -> Doc -- | Construct a PrettyField from a field that can be automatically -- converted to a Doc via display. field :: Pretty b => FieldName -> (a -> b) -> a -> [String] -> Bool -> WriteOpts -> PrettyField FieldAnnotation -- | Construct a PrettyField from a Doc Flag. fieldD :: FieldName -> Doc -> [String] -> Bool -> WriteOpts -> PrettyField FieldAnnotation -- | A field annotation instructing the pretty printer to comment out the -- field and any contents, with no comments. commentedOutWithComments :: CommentPosition -> FieldAnnotation -- | A field annotation with the specified comment lines. withComments :: CommentPosition -> FieldAnnotation -- | A field annotation with no comments. annNoComments :: FieldAnnotation postProcessFieldLines :: FieldAnnotation -> [String] -> [String] mkCommonStanza :: WriteOpts -> PrettyField FieldAnnotation mkLibStanza :: WriteOpts -> LibTarget -> PrettyField FieldAnnotation mkExeStanza :: WriteOpts -> ExeTarget -> PrettyField FieldAnnotation mkTestStanza :: WriteOpts -> TestTarget -> PrettyField FieldAnnotation mkPkgDescription :: WriteOpts -> PkgDescription -> [PrettyField FieldAnnotation] -- | Default values to use in cabal init (if not specified in -- config/flags). module Distribution.Client.Init.Defaults defaultApplicationDir :: String defaultSourceDir :: String defaultCabalVersion :: CabalSpecVersion defaultCabalVersions :: [CabalSpecVersion] defaultPackageType :: PackageType defaultLicense :: CabalSpecVersion -> SpecLicense defaultLicenseIds :: [LicenseId] defaultMainIs :: HsFilePath defaultChangelog :: FilePath defaultCategories :: [String] defaultInitFlags :: InitFlags defaultLanguage :: Language defaultVersion :: Version defaultTestDir :: String myLibModule :: ModuleName myLibTestFile :: HsFilePath myLibFile :: HsFilePath -- | Default MyLib.hs file. Used when no Lib.hs exists. myLibHs :: String myExeHs :: [String] myLibExeHs :: [String] -- | Default MyLibTest.hs file. myTestHs :: String module Distribution.Client.Init.Utils -- | Data type of source files found in the working directory data SourceFileEntry SourceFileEntry :: FilePath -> ModuleName -> String -> [ModuleName] -> [Extension] -> SourceFileEntry [relativeSourcePath] :: SourceFileEntry -> FilePath [moduleName] :: SourceFileEntry -> ModuleName [fileExtension] :: SourceFileEntry -> String [imports] :: SourceFileEntry -> [ModuleName] [extensions] :: SourceFileEntry -> [Extension] retrieveSourceFiles :: Interactive m => FilePath -> m [SourceFileEntry] -- | Given a module, retrieve its name retrieveModuleName :: Interactive m => FilePath -> m (Maybe ModuleName) -- | Given a module, retrieve all of its imports retrieveModuleImports :: Interactive m => FilePath -> m [ModuleName] -- | Given a module, retrieve all of its language pragmas retrieveModuleExtensions :: Interactive m => FilePath -> m [Extension] retrieveBuildTools :: Interactive m => CabalSpecVersion -> FilePath -> m [Dependency] retrieveDependencies :: Interactive m => Verbosity -> InitFlags -> [(ModuleName, ModuleName)] -> InstalledPackageIndex -> m [Dependency] -- | Check if a given file has main file characteristics isMain :: String -> Bool -- | Check if a given file has a Haskell extension isHaskell :: String -> Bool -- | Check whether a potential source file is located in one of the source -- directories. isSourceFile :: Maybe [FilePath] -> SourceFileEntry -> Bool trim :: String -> String currentDirPkgName :: Interactive m => m PackageName filePathToPkgName :: Interactive m => FilePath -> m PackageName mkPackageNameDep :: PackageName -> Dependency fixupDocFiles :: Interactive m => Verbosity -> PkgDescription -> m PkgDescription mkStringyDep :: String -> Dependency getBaseDep :: Interactive m => InstalledPackageIndex -> InitFlags -> m [Dependency] addLibDepToExe :: PackageName -> ExeTarget -> ExeTarget addLibDepToTest :: PackageName -> Maybe TestTarget -> Maybe TestTarget instance GHC.Show.Show Distribution.Client.Init.Utils.SourceFileEntry module Distribution.Client.Init.FlagExtractors getPackageDir :: Interactive m => InitFlags -> m FilePath -- | Ask if a simple project with sensible defaults should be created. getSimpleProject :: Interactive m => InitFlags -> m Bool -> m Bool -- | Extract minimal cabal file flag (implies nocomments) getMinimal :: Interactive m => InitFlags -> m Bool -- | Get the version of the cabal spec to use. -- -- The spec version can be specified by the InitFlags cabalVersion field. -- If none is specified then the user is prompted to pick from a list of -- supported versions (see code below). getCabalVersion :: Interactive m => InitFlags -> m CabalSpecVersion -> m CabalSpecVersion getCabalVersionNoPrompt :: InitFlags -> CabalSpecVersion -- | Get the package name: use the package directory (supplied, or the -- current directory by default) as a guess. It looks at the -- SourcePackageDb to avoid using an existing package name. getPackageName :: Interactive m => InitFlags -> m PackageName -> m PackageName -- | Package version: use 0.1.0.0 as a last resort, but try prompting the -- user if possible. getVersion :: Interactive m => InitFlags -> m Version -> m Version -- | Choose a license for the package. The license can come from Initflags -- (license field), if it is not present then prompt the user from a -- predefined list of licenses. getLicense :: Interactive m => InitFlags -> m SpecLicense -> m SpecLicense -- | The author's name. Prompt, or try to guess from an existing darcs -- repo. getAuthor :: Interactive m => InitFlags -> m String -> m String -- | The author's email. Prompt, or try to guess from an existing darcs -- repo. getEmail :: Interactive m => InitFlags -> m String -> m String -- | Prompt for a homepage URL for the package. getHomepage :: Interactive m => InitFlags -> m String -> m String -- | Prompt for a project synopsis. getSynopsis :: Interactive m => InitFlags -> m String -> m String -- | Prompt for a package category. Note that it should be possible to do -- some smarter guessing here too, i.e. look at the name of the top level -- source directory. getCategory :: Interactive m => InitFlags -> m String -> m String -- | Try to guess extra source files (don't prompt the user). getExtraSrcFiles :: Interactive m => InitFlags -> m (Set String) -- | Try to guess extra source files (don't prompt the user). getExtraDocFiles :: Interactive m => InitFlags -> m (Maybe (Set String)) -- | Ask whether the project builds a library or executable. getPackageType :: Interactive m => InitFlags -> m PackageType -> m PackageType getMainFile :: Interactive m => InitFlags -> m HsFilePath -> m HsFilePath getInitializeTestSuite :: Interactive m => InitFlags -> m Bool -> m Bool getTestDirs :: Interactive m => InitFlags -> m [String] -> m [String] -- | Ask for the Haskell base language of the package. getLanguage :: Interactive m => InitFlags -> m Language -> m Language -- | Ask whether to generate explanatory comments. getNoComments :: Interactive m => InitFlags -> m Bool -> m Bool -- | Ask for the application root directory. getAppDirs :: Interactive m => InitFlags -> m [String] -> m [String] -- | Ask for the source (library) root directory. getSrcDirs :: Interactive m => InitFlags -> m [String] -> m [String] -- | Retrieve the list of exposed modules getExposedModules :: Interactive m => InitFlags -> m (NonEmpty ModuleName) -- | Retrieve the list of build tools getBuildTools :: Interactive m => InitFlags -> m [Dependency] -- | Retrieve the list of dependencies getDependencies :: Interactive m => InitFlags -> m [Dependency] -> m [Dependency] -- | Retrieve the list of extensions getOtherExts :: Interactive m => InitFlags -> m [Extension] -- | Tell whether to overwrite files on write getOverwrite :: Interactive m => InitFlags -> m Bool -- | Retrieve the list of other modules getOtherModules :: Interactive m => InitFlags -> m [ModuleName] simpleProjectPrompt :: Interactive m => InitFlags -> m Bool initializeTestSuitePrompt :: Interactive m => InitFlags -> m Bool packageTypePrompt :: Interactive m => InitFlags -> m PackageType testMainPrompt :: Interactive m => m HsFilePath dependenciesPrompt :: Interactive m => InstalledPackageIndex -> InitFlags -> m [Dependency] module Distribution.Client.Init.Simple createProject :: Interactive m => Verbosity -> InstalledPackageIndex -> SourcePackageDb -> InitFlags -> m ProjectSettings genSimplePkgDesc :: Interactive m => InitFlags -> m PkgDescription genSimpleLibTarget :: Interactive m => InitFlags -> m LibTarget genSimpleExeTarget :: Interactive m => InitFlags -> m ExeTarget genSimpleTestTarget :: Interactive m => InitFlags -> m (Maybe TestTarget) -- | Heuristics for creating initial cabal files. module Distribution.Client.Init.NonInteractive.Heuristics -- | Guess the package name based on the given root directory. guessPackageName :: Interactive m => FilePath -> m PackageName -- | Guess the main file, returns a default value if none is found. guessMainFile :: Interactive m => FilePath -> m HsFilePath -- | Try to guess the license from an already existing LICENSE -- file in the package directory, comparing the file contents with the -- ones listed in Licenses.hs, for now it only returns a default -- value. guessLicense :: Interactive m => InitFlags -> m SpecLicense guessExtraDocFiles :: Interactive m => InitFlags -> m (Maybe (Set FilePath)) -- | Guess author and email using git configuration options. guessAuthorName :: Interactive m => m String guessAuthorEmail :: Interactive m => m String -- | Juggling characters around to guess the desired cabal version based on -- the system's cabal version. guessCabalSpecVersion :: Interactive m => m CabalSpecVersion -- | Guess the language specification based on the GHC version guessLanguage :: Interactive m => Compiler -> m Language -- | Try to guess the package type from the files in the package directory, -- looking for unique characteristics from each type, defaults to -- Executable. guessPackageType :: Interactive m => InitFlags -> m PackageType -- | Try to guess the source directories, using a default value as -- fallback. guessSourceDirectories :: Interactive m => InitFlags -> m [FilePath] -- | Try to guess the application directories from the package directory, -- using a default value as fallback. guessApplicationDirectories :: Interactive m => InitFlags -> m [FilePath] module Distribution.Client.Init.NonInteractive.Command genPkgDescription :: Interactive m => InitFlags -> SourcePackageDb -> m PkgDescription genLibTarget :: Interactive m => InitFlags -> Compiler -> InstalledPackageIndex -> CabalSpecVersion -> m LibTarget genExeTarget :: Interactive m => InitFlags -> Compiler -> InstalledPackageIndex -> CabalSpecVersion -> m ExeTarget genTestTarget :: Interactive m => InitFlags -> Compiler -> InstalledPackageIndex -> CabalSpecVersion -> m (Maybe TestTarget) -- | Main driver for interactive prompt code. createProject :: Interactive m => Compiler -> Verbosity -> InstalledPackageIndex -> SourcePackageDb -> InitFlags -> m ProjectSettings -- | Try to guess if the project builds a library, an executable, or both. packageTypeHeuristics :: Interactive m => InitFlags -> m PackageType -- | The author's name. Prompt, or try to guess from an existing darcs -- repo. authorHeuristics :: Interactive m => InitFlags -> m String -- | The author's email. Prompt, or try to guess from an existing darcs -- repo. emailHeuristics :: Interactive m => InitFlags -> m String -- | Get the version of the cabal spec to use. The spec version can be -- specified by the InitFlags cabalVersion field. If none is specified -- then the default version is used. cabalVersionHeuristics :: Interactive m => InitFlags -> m CabalSpecVersion -- | Get the package name: use the package directory (supplied, or the -- current directory by default) as a guess. It looks at the -- SourcePackageDb to avoid using an existing package name. packageNameHeuristics :: Interactive m => SourcePackageDb -> InitFlags -> m PackageName -- | Package version: use 0.1.0.0 as a last resort versionHeuristics :: Interactive m => InitFlags -> m Version -- | Try to guess the main file, if nothing is found, fallback to a default -- value. mainFileHeuristics :: Interactive m => InitFlags -> m HsFilePath testDirsHeuristics :: Interactive m => InitFlags -> m [String] initializeTestSuiteHeuristics :: Interactive m => InitFlags -> m Bool -- | Retrieve the list of exposed modules exposedModulesHeuristics :: Interactive m => InitFlags -> m (NonEmpty ModuleName) -- | Retrieve the list of other modules for Libraries, filtering them based -- on the last component of the module name libOtherModulesHeuristics :: Interactive m => InitFlags -> m [ModuleName] -- | Retrieve the list of other modules for Executables, it lists -- everything that is a Haskell file within the application directory, -- excluding the main file exeOtherModulesHeuristics :: Interactive m => InitFlags -> m [ModuleName] -- | Retrieve the list of other modules for Tests, it lists everything that -- is a Haskell file within the tests directory, excluding the main file testOtherModulesHeuristics :: Interactive m => InitFlags -> m [ModuleName] -- | Retrieve the list of build tools buildToolsHeuristics :: Interactive m => InitFlags -> FilePath -> CabalSpecVersion -> m [Dependency] -- | Retrieve the list of dependencies dependenciesHeuristics :: Interactive m => InitFlags -> FilePath -> InstalledPackageIndex -> m [Dependency] -- | Retrieve the list of extensions otherExtsHeuristics :: Interactive m => InitFlags -> FilePath -> m [Extension] -- | Choose a license for the package. The license can come from Initflags -- (license field), if it is not present then prompt the user from a -- predefined list of licenses. licenseHeuristics :: Interactive m => InitFlags -> m SpecLicense -- | Prompt for a homepage URL for the package. homepageHeuristics :: Interactive m => InitFlags -> m String -- | Prompt for a project synopsis. synopsisHeuristics :: Interactive m => InitFlags -> m String -- | Prompt for a package category. Note that it should be possible to do -- some smarter guessing here too, i.e. look at the name of the top level -- source directory. categoryHeuristics :: Interactive m => InitFlags -> m String -- | Try to guess extra source files. extraDocFileHeuristics :: Interactive m => InitFlags -> m (Maybe (Set FilePath)) -- | Ask for the application root directory. appDirsHeuristics :: Interactive m => InitFlags -> m [String] -- | Ask for the source (library) root directory. srcDirsHeuristics :: Interactive m => InitFlags -> m [String] -- | Ask for the Haskell base language of the package. languageHeuristics :: Interactive m => InitFlags -> Compiler -> m Language -- | Ask whether to generate explanatory comments. noCommentsHeuristics :: Interactive m => InitFlags -> m Bool minimalHeuristics :: Interactive m => InitFlags -> m Bool overwriteHeuristics :: Interactive m => InitFlags -> m Bool -- | Implementation of the 'cabal init' command, which creates an initial -- .cabal file for a project. module Distribution.Client.Init.Interactive.Command -- | Main driver for interactive prompt code. createProject :: Interactive m => Verbosity -> InstalledPackageIndex -> SourcePackageDb -> InitFlags -> m ProjectSettings -- | Extract flags relevant to a package description and interactively -- generate a PkgDescription object for creation. If the user -- specifies the generation of a simple package, then a simple target -- with defaults is generated. genPkgDescription :: Interactive m => InitFlags -> SourcePackageDb -> m PkgDescription -- | Extract flags relevant to a library target and interactively generate -- a LibTarget object for creation. If the user specifies the -- generation of a simple package, then a simple target with defaults is -- generated. genLibTarget :: Interactive m => InitFlags -> InstalledPackageIndex -> m LibTarget -- | Extract flags relevant to a executable target and interactively -- generate a ExeTarget object for creation. If the user specifies -- the generation of a simple package, then a simple target with defaults -- is generated. genExeTarget :: Interactive m => InitFlags -> InstalledPackageIndex -> m ExeTarget -- | Extract flags relevant to a test target and interactively generate a -- TestTarget object for creation. If the user specifies the -- generation of a simple package, then a simple target with defaults is -- generated. -- -- Note: this workflow is only enabled if the user answers affirmatively -- when prompted, or if the user passes in the flag to enable test suites -- at command line. genTestTarget :: Interactive m => InitFlags -> InstalledPackageIndex -> m (Maybe TestTarget) cabalVersionPrompt :: Interactive m => InitFlags -> m CabalSpecVersion packageNamePrompt :: Interactive m => SourcePackageDb -> InitFlags -> m PackageName versionPrompt :: Interactive m => InitFlags -> m Version licensePrompt :: Interactive m => InitFlags -> m SpecLicense authorPrompt :: Interactive m => InitFlags -> m String emailPrompt :: Interactive m => InitFlags -> m String homepagePrompt :: Interactive m => InitFlags -> m String synopsisPrompt :: Interactive m => InitFlags -> m String categoryPrompt :: Interactive m => InitFlags -> m String mainFilePrompt :: Interactive m => InitFlags -> m HsFilePath testDirsPrompt :: Interactive m => InitFlags -> m [String] languagePrompt :: Interactive m => InitFlags -> String -> m Language noCommentsPrompt :: Interactive m => InitFlags -> m Bool -- | Ask for the application root directory. appDirsPrompt :: Interactive m => InitFlags -> m [String] dependenciesPrompt :: Interactive m => InstalledPackageIndex -> InitFlags -> m [Dependency] -- | Ask for the source (library) root directory. srcDirsPrompt :: Interactive m => InitFlags -> m [String] -- | Functions to create files during 'cabal init'. module Distribution.Client.Init.FileCreators writeProject :: Interactive m => ProjectSettings -> m () -- | Write the LICENSE file. -- -- For licenses that contain the author's name(s), the values are taken -- from the authors field of InitFlags, and if not -- specified will be the string "???". -- -- If the license type is unknown no license file will be prepared and a -- warning will be raised. writeLicense :: Interactive m => WriteOpts -> PkgDescription -> m () -- | Writes the changelog to the current directory. writeChangeLog :: Interactive m => WriteOpts -> PkgDescription -> m () prepareLibTarget :: Interactive m => WriteOpts -> Maybe LibTarget -> m (PrettyField FieldAnnotation) prepareExeTarget :: Interactive m => WriteOpts -> Maybe ExeTarget -> m (PrettyField FieldAnnotation) prepareTestTarget :: Interactive m => WriteOpts -> Maybe TestTarget -> m (PrettyField FieldAnnotation) instance GHC.Classes.Eq Distribution.Client.Init.FileCreators.WriteAction instance GHC.Show.Show Distribution.Client.Init.FileCreators.WriteAction -- | An abstraction to help with re-running actions when files or other -- input values they depend on have changed. module Distribution.Client.FileMonitor -- | A description of a file (or set of files) to monitor for changes. -- -- Where file paths are relative they are relative to a common directory -- (e.g. project root), not necessarily the process current directory. data MonitorFilePath MonitorFile :: !MonitorKindFile -> !MonitorKindDir -> !FilePath -> MonitorFilePath [monitorKindFile] :: MonitorFilePath -> !MonitorKindFile [monitorKindDir] :: MonitorFilePath -> !MonitorKindDir [monitorPath] :: MonitorFilePath -> !FilePath MonitorFileGlob :: !MonitorKindFile -> !MonitorKindDir -> !FilePathGlob -> MonitorFilePath [monitorKindFile] :: MonitorFilePath -> !MonitorKindFile [monitorKindDir] :: MonitorFilePath -> !MonitorKindDir [monitorPathGlob] :: MonitorFilePath -> !FilePathGlob data MonitorKindFile FileExists :: MonitorKindFile FileModTime :: MonitorKindFile FileHashed :: MonitorKindFile FileNotExists :: MonitorKindFile data MonitorKindDir DirExists :: MonitorKindDir DirModTime :: MonitorKindDir DirNotExists :: MonitorKindDir -- | A file path specified by globbing data FilePathGlob FilePathGlob :: FilePathRoot -> FilePathGlobRel -> FilePathGlob -- | Monitor a single file for changes, based on its modification time. The -- monitored file is considered to have changed if it no longer exists or -- if its modification time has changed. monitorFile :: FilePath -> MonitorFilePath -- | Monitor a single file for changes, based on its modification time and -- content hash. The monitored file is considered to have changed if it -- no longer exists or if its modification time and content hash have -- changed. monitorFileHashed :: FilePath -> MonitorFilePath -- | Monitor a single non-existent file for changes. The monitored file is -- considered to have changed if it exists. monitorNonExistentFile :: FilePath -> MonitorFilePath -- | Monitor a single file for existence only. The monitored file is -- considered to have changed if it no longer exists. monitorFileExistence :: FilePath -> MonitorFilePath -- | Monitor a single directory for changes, based on its modification -- time. The monitored directory is considered to have changed if it no -- longer exists or if its modification time has changed. monitorDirectory :: FilePath -> MonitorFilePath -- | Monitor a single non-existent directory for changes. The monitored -- directory is considered to have changed if it exists. monitorNonExistentDirectory :: FilePath -> MonitorFilePath -- | Monitor a single directory for existence. The monitored directory is -- considered to have changed only if it no longer exists. monitorDirectoryExistence :: FilePath -> MonitorFilePath -- | Monitor a single file or directory for changes, based on its -- modification time. The monitored file is considered to have changed if -- it no longer exists or if its modification time has changed. monitorFileOrDirectory :: FilePath -> MonitorFilePath -- | Monitor a set of files (or directories) identified by a file glob. The -- monitored glob is considered to have changed if the set of files -- matching the glob changes (i.e. creations or deletions), or for files -- if the modification time and content hash of any matching file has -- changed. monitorFileGlob :: FilePathGlob -> MonitorFilePath -- | Monitor a set of files (or directories) identified by a file glob for -- existence only. The monitored glob is considered to have changed if -- the set of files matching the glob changes (i.e. creations or -- deletions). monitorFileGlobExistence :: FilePathGlob -> MonitorFilePath -- | Creates a list of files to monitor when you search for a file which -- unsuccessfully looked in notFoundAtPaths before finding it at -- foundAtPath. monitorFileSearchPath :: [FilePath] -> FilePath -> [MonitorFilePath] -- | Similar to monitorFileSearchPath, but also instructs us to -- monitor the hash of the found file. monitorFileHashedSearchPath :: [FilePath] -> FilePath -> [MonitorFilePath] -- | A monitor for detecting changes to a set of files. It can be used to -- efficiently test if any of a set of files (specified individually or -- by glob patterns) has changed since some snapshot. In addition, it -- also checks for changes in a value (of type a), and when -- there are no changes in either it returns a saved value (of type -- b). -- -- The main use case looks like this: suppose we have some expensive -- action that depends on certain pure inputs and reads some set of -- files, and produces some pure result. We want to avoid re-running this -- action when it would produce the same result. So we need to monitor -- the files the action looked at, the other pure input values, and we -- need to cache the result. Then at some later point, if the input value -- didn't change, and none of the files changed, then we can re-use the -- cached result rather than re-running the action. -- -- This can be achieved using a FileMonitor. Each -- FileMonitor instance saves state in a disk file, so the file -- for that has to be specified, making sure it is unique. The pattern is -- to use checkFileMonitorChanged to see if there's been any -- change. If there is, re-run the action, keeping track of the files, -- then use updateFileMonitor to record the current set of files -- to monitor, the current input value for the action, and the result of -- the action. -- -- The typical occurrence of this pattern is captured by -- rerunIfChanged and the Rebuild monad. More -- complicated cases may need to use checkFileMonitorChanged and -- updateFileMonitor directly. data FileMonitor a b FileMonitor :: FilePath -> (a -> a -> Bool) -> Bool -> FileMonitor a b -- | The file where this FileMonitor should store its state. [fileMonitorCacheFile] :: FileMonitor a b -> FilePath -- | Compares a new cache key with old one to determine if a corresponding -- cached value is still valid. -- -- Typically this is just an equality test, but in some circumstances it -- can make sense to do things like subset comparisons. -- -- The first arg is the new value, the second is the old cached value. [fileMonitorKeyValid] :: FileMonitor a b -> a -> a -> Bool -- | When this mode is enabled, if checkFileMonitorChanged returns -- MonitoredValueChanged then we have the guarantee that no files -- changed, that the value change was the only change. In the default -- mode no such guarantee is provided which is slightly faster. [fileMonitorCheckIfOnlyValueChanged] :: FileMonitor a b -> Bool -- | Define a new file monitor. -- -- It's best practice to define file monitor values once, and then use -- the same value for checkFileMonitorChanged and -- updateFileMonitor as this ensures you get the same types -- a and b for reading and writing. -- -- The path of the file monitor itself must be unique because it keeps -- state on disk and these would clash. newFileMonitor :: Eq a => FilePath -> FileMonitor a b -- | The result of checkFileMonitorChanged: either the monitored -- files or value changed (and it tells us which it was) or nothing -- changed and we get the cached result. data MonitorChanged a b -- | The monitored files and value did not change. The cached result is -- b. -- -- The set of monitored files is also returned. This is useful for -- composing or nesting FileMonitors. MonitorUnchanged :: b -> [MonitorFilePath] -> MonitorChanged a b -- | The monitor found that something changed. The reason is given. MonitorChanged :: MonitorChangedReason a -> MonitorChanged a b -- | What kind of change checkFileMonitorChanged detected. data MonitorChangedReason a -- | One of the files changed (existence, file type, mtime or file content, -- depending on the MonitorFilePath in question) MonitoredFileChanged :: FilePath -> MonitorChangedReason a -- | The pure input value changed. -- -- The previous cached key value is also returned. This is sometimes -- useful when using a fileMonitorKeyValid function that is not -- simply (==), when invalidation can be partial. In such cases it -- can make sense to updateFileMonitor with a key value that's a -- combination of the new and old (e.g. set union). MonitoredValueChanged :: a -> MonitorChangedReason a -- | There was no saved monitor state, cached value etc. Ie the file for -- the FileMonitor does not exist. MonitorFirstRun :: MonitorChangedReason a -- | There was existing state, but we could not read it. This typically -- happens when the code has changed compared to an existing -- FileMonitor cache file and type of the input value or cached -- value has changed such that we cannot decode the values. This is -- completely benign as we can treat is just as if there were no cache -- file and re-run. MonitorCorruptCache :: MonitorChangedReason a -- | Test if the input value or files monitored by the FileMonitor -- have changed. If not, return the cached value. -- -- See FileMonitor for a full explanation. checkFileMonitorChanged :: forall a b. (Binary a, Structured a, Binary b, Structured b) => FileMonitor a b -> FilePath -> a -> IO (MonitorChanged a b) -- | Update the input value and the set of files monitored by the -- FileMonitor, plus the cached value that may be returned in -- future. -- -- This takes a snapshot of the state of the monitored files right now, -- so checkFileMonitorChanged will look for file system changes -- relative to this snapshot. -- -- This is typically done once the action has been completed successfully -- and we have the action's result and we know what files it looked at. -- See FileMonitor for a full explanation. -- -- If we do take the snapshot after the action has completed then we have -- a problem. The problem is that files might have changed while -- the action was running but after the action read them. If we -- take the snapshot after the action completes then we will miss these -- changes. The solution is to record a timestamp before beginning -- execution of the action and then we make the conservative assumption -- that any file that has changed since then has already changed, ie the -- file monitor state for these files will be such that -- checkFileMonitorChanged will report that they have changed. -- -- So if you do use updateFileMonitor after the action (so you can -- discover the files used rather than predicting them in advance) then -- use beginUpdateFileMonitor to get a timestamp and pass that. -- Alternatively, if you take the snapshot in advance of the action, or -- you're not monitoring any files then you can use Nothing for -- the timestamp parameter. updateFileMonitor :: (Binary a, Structured a, Binary b, Structured b) => FileMonitor a b -> FilePath -> Maybe MonitorTimestamp -> [MonitorFilePath] -> a -> b -> IO () -- | A timestamp to help with the problem of file changes during actions. -- See updateFileMonitor for details. data MonitorTimestamp -- | Record a timestamp at the beginning of an action, and when the action -- completes call updateFileMonitor passing it the timestamp. See -- updateFileMonitor for details. beginUpdateFileMonitor :: IO MonitorTimestamp -- | The state necessary to determine whether a set of monitored files has -- changed. It consists of two parts: a set of specific files to be -- monitored (index by their path), and a list of globs, which monitor -- may files at once. data MonitorStateFileSet -- | The state necessary to determine whether a monitored file has changed. -- -- This covers all the cases of MonitorFilePath except for globs -- which is covered separately by MonitorStateGlob. -- -- The Maybe ModTime is to cover the case where we already -- consider the file to have changed, either because it had already -- changed by the time we did the snapshot (i.e. too new, changed since -- start of update process) or it no longer exists at all. data MonitorStateFile -- | The state necessary to determine whether the files matched by a -- globbing match have changed. data MonitorStateGlob instance GHC.Generics.Generic Distribution.Client.FileMonitor.MonitorKindFile instance GHC.Show.Show Distribution.Client.FileMonitor.MonitorKindFile instance GHC.Classes.Eq Distribution.Client.FileMonitor.MonitorKindFile instance GHC.Generics.Generic Distribution.Client.FileMonitor.MonitorKindDir instance GHC.Show.Show Distribution.Client.FileMonitor.MonitorKindDir instance GHC.Classes.Eq Distribution.Client.FileMonitor.MonitorKindDir instance GHC.Generics.Generic Distribution.Client.FileMonitor.MonitorFilePath instance GHC.Show.Show Distribution.Client.FileMonitor.MonitorFilePath instance GHC.Classes.Eq Distribution.Client.FileMonitor.MonitorFilePath instance GHC.Generics.Generic Distribution.Client.FileMonitor.MonitorStateFileStatus instance GHC.Show.Show Distribution.Client.FileMonitor.MonitorStateFileStatus instance GHC.Generics.Generic Distribution.Client.FileMonitor.MonitorStateFile instance GHC.Show.Show Distribution.Client.FileMonitor.MonitorStateFile instance GHC.Generics.Generic Distribution.Client.FileMonitor.MonitorStateGlobRel instance GHC.Show.Show Distribution.Client.FileMonitor.MonitorStateGlobRel instance GHC.Generics.Generic Distribution.Client.FileMonitor.MonitorStateGlob instance GHC.Show.Show Distribution.Client.FileMonitor.MonitorStateGlob instance GHC.Generics.Generic Distribution.Client.FileMonitor.MonitorStateFileSet instance GHC.Show.Show Distribution.Client.FileMonitor.MonitorStateFileSet instance GHC.Base.Functor Distribution.Client.FileMonitor.MonitorChangedReason instance GHC.Show.Show a => GHC.Show.Show (Distribution.Client.FileMonitor.MonitorChangedReason a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Distribution.Client.FileMonitor.MonitorChangedReason a) instance (GHC.Show.Show b, GHC.Show.Show a) => GHC.Show.Show (Distribution.Client.FileMonitor.MonitorChanged a b) instance Control.Monad.IO.Class.MonadIO Distribution.Client.FileMonitor.ChangedM instance GHC.Base.Monad Distribution.Client.FileMonitor.ChangedM instance GHC.Base.Applicative Distribution.Client.FileMonitor.ChangedM instance GHC.Base.Functor Distribution.Client.FileMonitor.ChangedM instance Data.Binary.Class.Binary Distribution.Client.FileMonitor.MonitorStateFileSet instance Distribution.Utils.Structured.Structured Distribution.Client.FileMonitor.MonitorStateFileSet instance Data.Binary.Class.Binary Distribution.Client.FileMonitor.MonitorStateGlob instance Distribution.Utils.Structured.Structured Distribution.Client.FileMonitor.MonitorStateGlob instance Data.Binary.Class.Binary Distribution.Client.FileMonitor.MonitorStateGlobRel instance Distribution.Utils.Structured.Structured Distribution.Client.FileMonitor.MonitorStateGlobRel instance Data.Binary.Class.Binary Distribution.Client.FileMonitor.MonitorStateFile instance Distribution.Utils.Structured.Structured Distribution.Client.FileMonitor.MonitorStateFile instance Data.Binary.Class.Binary Distribution.Client.FileMonitor.MonitorStateFileStatus instance Distribution.Utils.Structured.Structured Distribution.Client.FileMonitor.MonitorStateFileStatus instance Data.Binary.Class.Binary Distribution.Client.FileMonitor.MonitorFilePath instance Distribution.Utils.Structured.Structured Distribution.Client.FileMonitor.MonitorFilePath instance Data.Binary.Class.Binary Distribution.Client.FileMonitor.MonitorKindDir instance Distribution.Utils.Structured.Structured Distribution.Client.FileMonitor.MonitorKindDir instance Data.Binary.Class.Binary Distribution.Client.FileMonitor.MonitorKindFile instance Distribution.Utils.Structured.Structured Distribution.Client.FileMonitor.MonitorKindFile -- | An abstraction for re-running actions if values or files have changed. -- -- This is not a full-blown make-style incremental build system, it's a -- bit more ad-hoc than that, but it's easier to integrate with existing -- code. -- -- It's a convenient interface to the -- Distribution.Client.FileMonitor functions. module Distribution.Client.RebuildMonad -- | A monad layered on top of IO to help with re-running actions -- when the input files and values they depend on change. The crucial -- operations are rerunIfChanged and monitorFiles. data Rebuild a -- | Run a Rebuild IO action. runRebuild :: FilePath -> Rebuild a -> IO a -- | Run a Rebuild IO action. execRebuild :: FilePath -> Rebuild a -> IO [MonitorFilePath] -- | The root that relative paths are interpreted as being relative to. askRoot :: Rebuild FilePath -- | Use this within the body action of rerunIfChanged to declare -- that the action depends on the given files. This can be based on what -- the action actually did. It is these files that will be checked for -- changes next time rerunIfChanged is called for that -- FileMonitor. -- -- Relative paths are interpreted as relative to an implicit root, -- ultimately passed in to runRebuild. monitorFiles :: [MonitorFilePath] -> Rebuild () -- | A description of a file (or set of files) to monitor for changes. -- -- Where file paths are relative they are relative to a common directory -- (e.g. project root), not necessarily the process current directory. data MonitorFilePath -- | Monitor a single file for changes, based on its modification time. The -- monitored file is considered to have changed if it no longer exists or -- if its modification time has changed. monitorFile :: FilePath -> MonitorFilePath -- | Monitor a single file for changes, based on its modification time and -- content hash. The monitored file is considered to have changed if it -- no longer exists or if its modification time and content hash have -- changed. monitorFileHashed :: FilePath -> MonitorFilePath -- | Monitor a single non-existent file for changes. The monitored file is -- considered to have changed if it exists. monitorNonExistentFile :: FilePath -> MonitorFilePath -- | Monitor a single directory for changes, based on its modification -- time. The monitored directory is considered to have changed if it no -- longer exists or if its modification time has changed. monitorDirectory :: FilePath -> MonitorFilePath -- | Monitor a single non-existent directory for changes. The monitored -- directory is considered to have changed if it exists. monitorNonExistentDirectory :: FilePath -> MonitorFilePath -- | Monitor a single directory for existence. The monitored directory is -- considered to have changed only if it no longer exists. monitorDirectoryExistence :: FilePath -> MonitorFilePath -- | Monitor a single file or directory for changes, based on its -- modification time. The monitored file is considered to have changed if -- it no longer exists or if its modification time has changed. monitorFileOrDirectory :: FilePath -> MonitorFilePath -- | Creates a list of files to monitor when you search for a file which -- unsuccessfully looked in notFoundAtPaths before finding it at -- foundAtPath. monitorFileSearchPath :: [FilePath] -> FilePath -> [MonitorFilePath] -- | Similar to monitorFileSearchPath, but also instructs us to -- monitor the hash of the found file. monitorFileHashedSearchPath :: [FilePath] -> FilePath -> [MonitorFilePath] -- | Monitor a set of files (or directories) identified by a file glob. The -- monitored glob is considered to have changed if the set of files -- matching the glob changes (i.e. creations or deletions), or for files -- if the modification time and content hash of any matching file has -- changed. monitorFileGlob :: FilePathGlob -> MonitorFilePath -- | Monitor a set of files (or directories) identified by a file glob for -- existence only. The monitored glob is considered to have changed if -- the set of files matching the glob changes (i.e. creations or -- deletions). monitorFileGlobExistence :: FilePathGlob -> MonitorFilePath -- | A file path specified by globbing data FilePathGlob FilePathGlob :: FilePathRoot -> FilePathGlobRel -> FilePathGlob data FilePathRoot FilePathRelative :: FilePathRoot -- | e.g. "/", "c:" or result of takeDrive FilePathRoot :: FilePath -> FilePathRoot FilePathHomeDir :: FilePathRoot data FilePathGlobRel GlobDir :: !Glob -> !FilePathGlobRel -> FilePathGlobRel GlobFile :: !Glob -> FilePathGlobRel -- | trailing dir, a glob ending in / GlobDirTrailing :: FilePathGlobRel -- | A piece of a globbing pattern data GlobPiece WildCard :: GlobPiece Literal :: String -> GlobPiece Union :: [Glob] -> GlobPiece -- | A monitor for detecting changes to a set of files. It can be used to -- efficiently test if any of a set of files (specified individually or -- by glob patterns) has changed since some snapshot. In addition, it -- also checks for changes in a value (of type a), and when -- there are no changes in either it returns a saved value (of type -- b). -- -- The main use case looks like this: suppose we have some expensive -- action that depends on certain pure inputs and reads some set of -- files, and produces some pure result. We want to avoid re-running this -- action when it would produce the same result. So we need to monitor -- the files the action looked at, the other pure input values, and we -- need to cache the result. Then at some later point, if the input value -- didn't change, and none of the files changed, then we can re-use the -- cached result rather than re-running the action. -- -- This can be achieved using a FileMonitor. Each -- FileMonitor instance saves state in a disk file, so the file -- for that has to be specified, making sure it is unique. The pattern is -- to use checkFileMonitorChanged to see if there's been any -- change. If there is, re-run the action, keeping track of the files, -- then use updateFileMonitor to record the current set of files -- to monitor, the current input value for the action, and the result of -- the action. -- -- The typical occurrence of this pattern is captured by -- rerunIfChanged and the Rebuild monad. More -- complicated cases may need to use checkFileMonitorChanged and -- updateFileMonitor directly. data FileMonitor a b FileMonitor :: FilePath -> (a -> a -> Bool) -> Bool -> FileMonitor a b -- | The file where this FileMonitor should store its state. [fileMonitorCacheFile] :: FileMonitor a b -> FilePath -- | Compares a new cache key with old one to determine if a corresponding -- cached value is still valid. -- -- Typically this is just an equality test, but in some circumstances it -- can make sense to do things like subset comparisons. -- -- The first arg is the new value, the second is the old cached value. [fileMonitorKeyValid] :: FileMonitor a b -> a -> a -> Bool -- | When this mode is enabled, if checkFileMonitorChanged returns -- MonitoredValueChanged then we have the guarantee that no files -- changed, that the value change was the only change. In the default -- mode no such guarantee is provided which is slightly faster. [fileMonitorCheckIfOnlyValueChanged] :: FileMonitor a b -> Bool -- | Define a new file monitor. -- -- It's best practice to define file monitor values once, and then use -- the same value for checkFileMonitorChanged and -- updateFileMonitor as this ensures you get the same types -- a and b for reading and writing. -- -- The path of the file monitor itself must be unique because it keeps -- state on disk and these would clash. newFileMonitor :: Eq a => FilePath -> FileMonitor a b -- | This captures the standard use pattern for a FileMonitor: given -- a monitor, an action and the input value the action depends on, either -- re-run the action to get its output, or if the value and files the -- action depends on have not changed then return a previously cached -- action result. -- -- The result is still in the Rebuild monad, so these can be -- nested. -- -- Do not share FileMonitors between different uses of -- rerunIfChanged. rerunIfChanged :: (Binary a, Structured a, Binary b, Structured b) => Verbosity -> FileMonitor a b -> a -> Rebuild b -> Rebuild b -- | When using rerunIfChanged for each element of a list of -- actions, it is sometimes the case that each action needs to make use -- of some resource. e.g. -- --
--   sequence
--     [ rerunIfChanged verbosity monitor key $ do
--         resource <- mkResource
--         ... -- use the resource
--     | ... ]
--   
-- -- For efficiency one would like to share the resource between the -- actions but the straightforward way of doing this means initialising -- it every time even when no actions need re-running. -- --
--   resource <- mkResource
--   sequence
--     [ rerunIfChanged verbosity monitor key $ do
--         ... -- use the resource
--     | ... ]
--   
-- -- This utility allows one to get the best of both worlds: -- --
--   getResource <- delayInitSharedResource mkResource
--   sequence
--     [ rerunIfChanged verbosity monitor key $ do
--         resource <- getResource
--         ... -- use the resource
--     | ... ]
--   
delayInitSharedResource :: forall a. IO a -> Rebuild (Rebuild a) -- | Much like delayInitSharedResource but for a keyed set of -- resources. -- --
--   getResource <- delayInitSharedResource mkResource
--   sequence
--     [ rerunIfChanged verbosity monitor key $ do
--         resource <- getResource key
--         ... -- use the resource
--     | ... ]
--   
delayInitSharedResources :: forall k v. Ord k => (k -> IO v) -> Rebuild (k -> Rebuild v) -- | Utility to match a file glob against the file system, starting from a -- given root directory. The results are all relative to the given root. -- -- Since this operates in the Rebuild monad, it also monitors the -- given glob for changes. matchFileGlob :: FilePathGlob -> Rebuild [FilePath] getDirectoryContentsMonitored :: FilePath -> Rebuild [FilePath] createDirectoryMonitored :: Bool -> FilePath -> Rebuild () -- | Monitor a directory as in monitorDirectory if it currently -- exists or as monitorNonExistentDirectory if it does not. monitorDirectoryStatus :: FilePath -> Rebuild Bool -- | Like doesFileExist, but in the Rebuild monad. This does -- NOT track the contents of FilePath; use need in that -- case. doesFileExistMonitored :: FilePath -> Rebuild Bool -- | Monitor a single file need :: FilePath -> Rebuild () -- | Monitor a file if it exists; otherwise check for when it gets created. -- This is a bit better for recompilation avoidance because sometimes -- users give bad package metadata, and we don't want to repeatedly -- rebuild in this case (which we would if we need'ed a non-existent -- file). needIfExists :: FilePath -> Rebuild () -- | Like findFileWithExtension, but in the Rebuild monad. findFileWithExtensionMonitored :: [String] -> [FilePath] -> FilePath -> Rebuild (Maybe FilePath) -- | Like findFirstFile, but in the Rebuild monad. findFirstFileMonitored :: forall a. (a -> FilePath) -> [a] -> Rebuild (Maybe a) -- | Like findFile, but in the Rebuild monad. findFileMonitored :: [FilePath] -> FilePath -> Rebuild (Maybe FilePath) instance Control.Monad.IO.Class.MonadIO Distribution.Client.RebuildMonad.Rebuild instance GHC.Base.Monad Distribution.Client.RebuildMonad.Rebuild instance GHC.Base.Applicative Distribution.Client.RebuildMonad.Rebuild instance GHC.Base.Functor Distribution.Client.RebuildMonad.Rebuild -- | Types for the Distribution.Client.ProjectBuilding -- -- Moved out to avoid module cycles. module Distribution.Client.ProjectBuilding.Types -- | The BuildStatus of every package in the -- ElaboratedInstallPlan. -- -- This is used as the result of the dry-run of building an install plan. type BuildStatusMap = Map UnitId BuildStatus -- | The build status for an individual package is the state that the -- package is in prior to initiating a (re)build. -- -- This should not be confused with a BuildResult which is the -- result after successfully building a package. -- -- It serves two purposes: -- -- data BuildStatus -- | The package is in the PreExisting state, so does not need -- building. BuildStatusPreExisting :: BuildStatus -- | The package is in the Installed state, so does not need -- building. BuildStatusInstalled :: BuildStatus -- | The package has not been downloaded yet, so it will have to be -- downloaded, unpacked and built. BuildStatusDownload :: BuildStatus -- | The package has not been unpacked yet, so it will have to be unpacked -- and built. BuildStatusUnpack :: FilePath -> BuildStatus -- | The package exists in a local dir already, and just needs building or -- rebuilding. So this can only happen for BuildInplaceOnly -- style packages. BuildStatusRebuild :: FilePath -> BuildStatusRebuild -> BuildStatus -- | The package exists in a local dir already, and is fully up to date. So -- this package can be put into the Installed state and it does -- not need to be built. BuildStatusUpToDate :: BuildResult -> BuildStatus -- | Which BuildStatus values indicate we'll have to do some build -- work of some sort. In particular we use this as part of checking if -- any of a package's deps have changed. buildStatusRequiresBuild :: BuildStatus -> Bool -- | This is primarily here for debugging. It's not actually used anywhere. buildStatusToString :: BuildStatus -> String -- | For a package that is going to be built or rebuilt, the state it's in -- now. -- -- So again, this tells us why a package needs to be rebuilt and what -- build phases need to be run. The MonitorChangedReason gives us -- details like which file changed, which is mainly for high verbosity -- debug output. data BuildStatusRebuild -- | The package configuration changed, so the configure and build phases -- needs to be (re)run. BuildStatusConfigure :: MonitorChangedReason () -> BuildStatusRebuild -- | The configuration has not changed but the build phase needs to be -- rerun. We record the reason the (re)build is needed. -- -- The optional registration info here tells us if we've registered the -- package already, or if we still need to do that after building. -- Just Nothing indicates that we know that no registration is -- necessary (e.g., executable.) BuildStatusBuild :: Maybe (Maybe InstalledPackageInfo) -> BuildReason -> BuildStatusRebuild data BuildReason -- | The dependencies of this package have been (re)built so the build -- phase needs to be rerun. BuildReasonDepsRebuilt :: BuildReason -- | Changes in files within the package (or first run or corrupt cache) BuildReasonFilesChanged :: MonitorChangedReason () -> BuildReason -- | An important special case is that no files have changed but the set of -- components the user asked to build has changed. We track the -- set of components we have built, which of course only grows -- (until some other change resets it). -- -- The Set ComponentName is the set of components we have -- built previously. When we update the monitor we take the union of the -- ones we have built previously with the ones the user has asked for -- this time and save those. See updatePackageBuildFileMonitor. BuildReasonExtraTargets :: Set ComponentName -> BuildReason -- | Although we're not going to build any additional targets as a whole, -- we're going to build some part of a component or run a repl or any -- other action that does not result in additional persistent artifacts. BuildReasonEphemeralTargets :: BuildReason -- | What kind of change checkFileMonitorChanged detected. data MonitorChangedReason a -- | One of the files changed (existence, file type, mtime or file content, -- depending on the MonitorFilePath in question) MonitoredFileChanged :: FilePath -> MonitorChangedReason a -- | The pure input value changed. -- -- The previous cached key value is also returned. This is sometimes -- useful when using a fileMonitorKeyValid function that is not -- simply (==), when invalidation can be partial. In such cases it -- can make sense to updateFileMonitor with a key value that's a -- combination of the new and old (e.g. set union). MonitoredValueChanged :: a -> MonitorChangedReason a -- | There was no saved monitor state, cached value etc. Ie the file for -- the FileMonitor does not exist. MonitorFirstRun :: MonitorChangedReason a -- | There was existing state, but we could not read it. This typically -- happens when the code has changed compared to an existing -- FileMonitor cache file and type of the input value or cached -- value has changed such that we cannot decode the values. This is -- completely benign as we can treat is just as if there were no cache -- file and re-run. MonitorCorruptCache :: MonitorChangedReason a -- | A summary of the outcome for building a whole set of packages. type BuildOutcomes = Map UnitId BuildOutcome -- | A summary of the outcome for building a single package: either success -- or failure. type BuildOutcome = Either BuildFailure BuildResult -- | Information arising from successfully building a single package. data BuildResult BuildResult :: DocsResult -> TestsResult -> Maybe FilePath -> BuildResult [buildResultDocs] :: BuildResult -> DocsResult [buildResultTests] :: BuildResult -> TestsResult [buildResultLogFile] :: BuildResult -> Maybe FilePath -- | Information arising from the failure to build a single package. data BuildFailure BuildFailure :: Maybe FilePath -> BuildFailureReason -> BuildFailure [buildFailureLogFile] :: BuildFailure -> Maybe FilePath [buildFailureReason] :: BuildFailure -> BuildFailureReason -- | Detail on the reason that a package failed to build. data BuildFailureReason DependentFailed :: PackageId -> BuildFailureReason DownloadFailed :: SomeException -> BuildFailureReason UnpackFailed :: SomeException -> BuildFailureReason ConfigureFailed :: SomeException -> BuildFailureReason BuildFailed :: SomeException -> BuildFailureReason ReplFailed :: SomeException -> BuildFailureReason HaddocksFailed :: SomeException -> BuildFailureReason TestsFailed :: SomeException -> BuildFailureReason BenchFailed :: SomeException -> BuildFailureReason InstallFailed :: SomeException -> BuildFailureReason instance GHC.Show.Show Distribution.Client.ProjectBuilding.Types.BuildResult instance GHC.Show.Show Distribution.Client.ProjectBuilding.Types.BuildFailureReason instance GHC.Show.Show Distribution.Client.ProjectBuilding.Types.BuildFailure instance GHC.Exception.Type.Exception Distribution.Client.ProjectBuilding.Types.BuildFailure -- | Top level interface to dependency resolution. module Distribution.Client.Dependency -- | The set of parameters to the dependency resolver. These parameters are -- relatively low level but many kinds of high level policies can be -- implemented in terms of adjustments to the parameters. data DepResolverParams chooseSolver :: Verbosity -> PreSolver -> CompilerInfo -> IO Solver -- | Run the dependency solver. -- -- Since this is potentially an expensive operation, the result is -- wrapped in a a Progress structure that can be unfolded to -- provide progress information, logging messages and the final result or -- an error. resolveDependencies :: Platform -> CompilerInfo -> PkgConfigDb -> Solver -> DepResolverParams -> Progress String String SolverInstallPlan -- | A type to represent the unfolding of an expensive long running -- calculation that may fail. We may get intermediate steps before the -- final result which may be used to indicate progress and/or logging -- messages. data Progress step fail done Step :: step -> Progress step fail done -> Progress step fail done Fail :: fail -> Progress step fail done Done :: done -> Progress step fail done -- | Consume a Progress calculation. Much like foldr for -- lists but with two base cases, one for a final result and one for -- failure. -- -- Eg to convert into a simple Either result use: -- --
--   foldProgress (flip const) Left Right
--   
foldProgress :: (step -> a -> a) -> (fail -> a) -> (done -> a) -> Progress step fail done -> a -- | A simplistic method of resolving a list of target package names to -- available packages. -- -- Specifically, it does not consider package dependencies at all. Unlike -- resolveDependencies, no attempt is made to ensure that the -- selected packages have dependencies that are satisfiable or consistent -- with each other. -- -- It is suitable for tasks such as selecting packages to download for -- user inspection. It is not suitable for selecting packages to install. -- -- Note: if no installed package index is available, it is OK to pass -- mempty. It simply means preferences for installed packages will -- be ignored. resolveWithoutDependencies :: DepResolverParams -> Either [ResolveNoDepsError] [UnresolvedSourcePackage] -- | A package property is a logical predicate on packages. data PackageProperty PackagePropertyVersion :: VersionRange -> PackageProperty PackagePropertyInstalled :: PackageProperty PackagePropertySource :: PackageProperty PackagePropertyFlags :: FlagAssignment -> PackageProperty PackagePropertyStanzas :: [OptionalStanza] -> PackageProperty -- | A package constraint consists of a scope plus a property that must -- hold for all packages within that scope. data PackageConstraint PackageConstraint :: ConstraintScope -> PackageProperty -> PackageConstraint -- | Constructor for a common use case: the constraint applies to the -- package with the specified name when that package is a top-level -- dependency in the default namespace. scopeToplevel :: PackageName -> ConstraintScope -- | Global policy for all packages to say if we prefer package versions -- that are already installed locally or if we just prefer the latest -- available. data PackagesPreferenceDefault -- | Always prefer the latest version irrespective of any existing -- installed version. -- -- PreferAllLatest :: PackagesPreferenceDefault -- | Always prefer the oldest version irrespective of any existing -- installed version or packages explicitly requested. -- -- PreferAllOldest :: PackagesPreferenceDefault -- | Always prefer the installed versions over ones that would need to be -- installed. Secondarily, prefer latest versions (eg the latest -- installed version or if there are none then the latest source -- version). PreferAllInstalled :: PackagesPreferenceDefault -- | Prefer the latest version for packages that are explicitly requested -- but prefers the installed version for any other packages. -- -- PreferLatestForSelected :: PackagesPreferenceDefault -- | A package selection preference for a particular package. -- -- Preferences are soft constraints that the dependency resolver should -- try to respect where possible. It is not specified if preferences on -- some packages are more important than others. data PackagePreference -- | A suggested constraint on the version number. PackageVersionPreference :: PackageName -> VersionRange -> PackagePreference -- | If we prefer versions of packages that are already installed. PackageInstalledPreference :: PackageName -> InstalledPreference -> PackagePreference -- | If we would prefer to enable these optional stanzas (i.e. test suites -- and/or benchmarks) PackageStanzasPreference :: PackageName -> [OptionalStanza] -> PackagePreference -- | A basic solver policy on which all others are built. basicInstallPolicy :: InstalledPackageIndex -> SourcePackageDb -> [PackageSpecifier UnresolvedSourcePackage] -> DepResolverParams -- | The policy used by all the standard commands, install, fetch, freeze -- etc (but not the v2-build and related commands). -- -- It extends the basicInstallPolicy with a policy on setup deps. standardInstallPolicy :: InstalledPackageIndex -> SourcePackageDb -> [PackageSpecifier UnresolvedSourcePackage] -> DepResolverParams -- | A fully or partially resolved reference to a package. data PackageSpecifier pkg -- | A partially specified reference to a package (either source or -- installed). It is specified by package name and optionally some -- required properties. Use a dependency resolver to pick a specific -- package satisfying these properties. NamedPackage :: PackageName -> [PackageProperty] -> PackageSpecifier pkg -- | A fully specified source package. SpecificSourcePackage :: pkg -> PackageSpecifier pkg upgradeDependencies :: DepResolverParams -> DepResolverParams reinstallTargets :: DepResolverParams -> DepResolverParams addConstraints :: [LabeledPackageConstraint] -> DepResolverParams -> DepResolverParams addPreferences :: [PackagePreference] -> DepResolverParams -> DepResolverParams setPreferenceDefault :: PackagesPreferenceDefault -> DepResolverParams -> DepResolverParams setReorderGoals :: ReorderGoals -> DepResolverParams -> DepResolverParams setCountConflicts :: CountConflicts -> DepResolverParams -> DepResolverParams setFineGrainedConflicts :: FineGrainedConflicts -> DepResolverParams -> DepResolverParams setMinimizeConflictSet :: MinimizeConflictSet -> DepResolverParams -> DepResolverParams setIndependentGoals :: IndependentGoals -> DepResolverParams -> DepResolverParams setAvoidReinstalls :: AvoidReinstalls -> DepResolverParams -> DepResolverParams setShadowPkgs :: ShadowPkgs -> DepResolverParams -> DepResolverParams setStrongFlags :: StrongFlags -> DepResolverParams -> DepResolverParams setAllowBootLibInstalls :: AllowBootLibInstalls -> DepResolverParams -> DepResolverParams setOnlyConstrained :: OnlyConstrained -> DepResolverParams -> DepResolverParams setMaxBackjumps :: Maybe Int -> DepResolverParams -> DepResolverParams setEnableBackjumping :: EnableBackjumping -> DepResolverParams -> DepResolverParams setSolveExecutables :: SolveExecutables -> DepResolverParams -> DepResolverParams setGoalOrder :: Maybe (Variable QPN -> Variable QPN -> Ordering) -> DepResolverParams -> DepResolverParams setSolverVerbosity :: Verbosity -> DepResolverParams -> DepResolverParams -- | Dual of removeUpperBounds removeLowerBounds :: AllowOlder -> DepResolverParams -> DepResolverParams -- | Remove upper bounds in dependencies using the policy specified by the -- AllowNewer argument (allsomenone). -- -- Note: It's important to apply removeUpperBounds after -- addSourcePackages. Otherwise, the packages inserted by -- addSourcePackages won't have upper bounds in dependencies -- relaxed. removeUpperBounds :: AllowNewer -> DepResolverParams -> DepResolverParams -- | Supply defaults for packages without explicit Setup dependencies -- -- Note: It's important to apply addDefaultSetupDepends after -- addSourcePackages. Otherwise, the packages inserted by -- addSourcePackages won't have upper bounds in dependencies -- relaxed. addDefaultSetupDependencies :: (UnresolvedSourcePackage -> Maybe [Dependency]) -> DepResolverParams -> DepResolverParams -- | If a package has a custom setup then we need to add a setup-depends on -- Cabal. addSetupCabalMinVersionConstraint :: Version -> DepResolverParams -> DepResolverParams -- | Variant of addSetupCabalMinVersionConstraint which sets an -- upper bound on setup.Cabal labeled with -- ConstraintSetupCabalMaxVersion. addSetupCabalMaxVersionConstraint :: Version -> DepResolverParams -> DepResolverParams instance GHC.Show.Show Distribution.Client.Dependency.ResolveNoDepsError -- | Minimal JSON / RFC 7159 support -- -- The API is heavily inspired by aeson's API but puts emphasis -- on simplicity rather than performance. The ToJSON instances are -- intended to have an encoding compatible with aeson's -- encoding. module Distribution.Client.Utils.Json -- | A JSON value represented as a Haskell value. data Value Object :: !Object -> Value Array :: [Value] -> Value String :: String -> Value Number :: !Double -> Value Bool :: !Bool -> Value Null :: Value -- | A JSON "object" (key/value map). type Object = [Pair] -- | Create a Value from a list of name/value Pairs. object :: [Pair] -> Value -- | A key/value pair for an Value type Pair = (String, Value) -- | A key-value pair for encoding a JSON object. (.=) :: ToJSON v => String -> v -> Pair infixr 8 .= -- | Serialise value as JSON-encoded Unicode Value encodeToString :: ToJSON a => a -> String -- | Serialise value as JSON/UTF8-encoded Builder encodeToBuilder :: ToJSON a => a -> Builder -- | A type that can be converted to JSON. class ToJSON a -- | Convert a Haskell value to a JSON-friendly intermediate type. toJSON :: ToJSON a => a -> Value instance GHC.Show.Show Distribution.Client.Utils.Json.Value instance GHC.Read.Read Distribution.Client.Utils.Json.Value instance GHC.Classes.Eq Distribution.Client.Utils.Json.Value instance Distribution.Client.Utils.Json.ToJSON () instance Distribution.Client.Utils.Json.ToJSON Distribution.Client.Utils.Json.Value instance Distribution.Client.Utils.Json.ToJSON GHC.Types.Bool instance Distribution.Client.Utils.Json.ToJSON a => Distribution.Client.Utils.Json.ToJSON [a] instance Distribution.Client.Utils.Json.ToJSON a => Distribution.Client.Utils.Json.ToJSON (GHC.Maybe.Maybe a) instance (Distribution.Client.Utils.Json.ToJSON a, Distribution.Client.Utils.Json.ToJSON b) => Distribution.Client.Utils.Json.ToJSON (a, b) instance (Distribution.Client.Utils.Json.ToJSON a, Distribution.Client.Utils.Json.ToJSON b, Distribution.Client.Utils.Json.ToJSON c) => Distribution.Client.Utils.Json.ToJSON (a, b, c) instance (Distribution.Client.Utils.Json.ToJSON a, Distribution.Client.Utils.Json.ToJSON b, Distribution.Client.Utils.Json.ToJSON c, Distribution.Client.Utils.Json.ToJSON d) => Distribution.Client.Utils.Json.ToJSON (a, b, c, d) instance Distribution.Client.Utils.Json.ToJSON GHC.Types.Float instance Distribution.Client.Utils.Json.ToJSON GHC.Types.Double instance Distribution.Client.Utils.Json.ToJSON GHC.Types.Int instance Distribution.Client.Utils.Json.ToJSON GHC.Int.Int8 instance Distribution.Client.Utils.Json.ToJSON GHC.Int.Int16 instance Distribution.Client.Utils.Json.ToJSON GHC.Int.Int32 instance Distribution.Client.Utils.Json.ToJSON GHC.Types.Word instance Distribution.Client.Utils.Json.ToJSON GHC.Word.Word8 instance Distribution.Client.Utils.Json.ToJSON GHC.Word.Word16 instance Distribution.Client.Utils.Json.ToJSON GHC.Word.Word32 instance Distribution.Client.Utils.Json.ToJSON GHC.Int.Int64 instance Distribution.Client.Utils.Json.ToJSON GHC.Word.Word64 instance Distribution.Client.Utils.Json.ToJSON GHC.Num.Integer.Integer instance Data.String.IsString Distribution.Client.Utils.Json.Value module Distribution.Client.Utils.Parsec -- | Render parse error highlighting the part of the input file. renderParseError :: FilePath -> ByteString -> NonEmpty PError -> [PWarning] -> String -- | Check a package for common mistakes module Distribution.Client.Check -- | Note: must be called with the CWD set to the directory containing the -- '.cabal' file. check :: Verbosity -> IO Bool module Distribution.Client.VCS -- | A driver for a version control system, e.g. git, darcs etc. data VCS program -- | The type of repository this driver is for. vcsRepoType :: VCS program -> RepoType -- | The vcs program itself. This is used at type Program and -- ConfiguredProgram. vcsProgram :: VCS program -> program data RepoType -- | Represents a program which can be configured. -- -- Note: rather than constructing this directly, start with -- simpleProgram and override any extra fields. data Program -- | Represents a program which has been configured and is thus ready to be -- run. -- -- These are usually made by configuring a Program, but if you -- have to construct one directly then start with -- simpleConfiguredProgram and override any extra fields. data ConfiguredProgram validatePDSourceRepo :: SourceRepo -> Either SourceRepoProblem (SourceRepoMaybe, String, RepoType, VCS Program) -- | Validates that the SourceRepo specifies a location URI and a -- repository type that is supported by a VCS driver. -- -- | It also returns the VCS driver we should use to work with it. validateSourceRepo :: SourceRepositoryPackage f -> Either SourceRepoProblem (SourceRepositoryPackage f, String, RepoType, VCS Program) -- | As validateSourceRepo but for a bunch of SourceRepos, -- and return things in a convenient form to pass to -- configureVCSs, or to report problems. validateSourceRepos :: [SourceRepositoryPackage f] -> Either [(SourceRepositoryPackage f, SourceRepoProblem)] [(SourceRepositoryPackage f, String, RepoType, VCS Program)] data SourceRepoProblem SourceRepoRepoTypeUnspecified :: SourceRepoProblem SourceRepoRepoTypeUnsupported :: SourceRepositoryPackage Proxy -> RepoType -> SourceRepoProblem SourceRepoLocationUnspecified :: SourceRepoProblem configureVCS :: Verbosity -> VCS Program -> IO (VCS ConfiguredProgram) configureVCSs :: Verbosity -> Map RepoType (VCS Program) -> IO (Map RepoType (VCS ConfiguredProgram)) -- | Clone a single source repo into a fresh directory, using a configured -- VCS. -- -- This is for making a new copy, not synchronising an existing copy. It -- will fail if the destination directory already exists. -- -- Make sure to validate the SourceRepo using -- validateSourceRepo first. cloneSourceRepo :: Verbosity -> VCS ConfiguredProgram -> SourceRepositoryPackage f -> [Char] -> IO () -- | Synchronise a set of SourceRepos referring to the same -- repository with corresponding local directories. The local directories -- may or may not already exist. -- -- The SourceRepo values used in a single invocation of -- syncSourceRepos, or used across a series of invocations with -- any local directory must refer to the same repository. That -- means it must be the same location but they can differ in the branch, -- or tag or subdir. -- -- The reason to allow multiple related SourceRepos is to allow -- for the network or storage to be shared between different checkouts of -- the repo. For example if a single repo contains multiple packages in -- different subdirs and in some project it may make sense to use a -- different state of the repo for one subdir compared to another. syncSourceRepos :: Verbosity -> VCS ConfiguredProgram -> [(SourceRepositoryPackage f, FilePath)] -> Rebuild () -- | The set of all supported VCS drivers, organised by RepoType. knownVCSs :: Map RepoType (VCS Program) -- | VCS driver for Bazaar. vcsBzr :: VCS Program -- | VCS driver for Darcs. vcsDarcs :: VCS Program -- | VCS driver for Git. vcsGit :: VCS Program -- | VCS driver for Mercurial. vcsHg :: VCS Program -- | VCS driver for Subversion. vcsSvn :: VCS Program -- | VCS driver for Pijul. Documentation for Pijul can be found at -- https://pijul.org/manual/introduction.html -- -- 2020-04-09 Oleg: -- -- As far as I understand pijul, there are branches and "tags" in pijul, -- but there aren't a "commit hash" identifying an arbitrary state. -- -- One can create `a pijul tag`, which will make a patch hash, which -- depends on everything currently in the repository. I guess if you try -- to apply that patch, you'll be forced to apply all the dependencies -- too. In other words, there are no named tags. -- -- It's not clear to me whether there is an option to "apply this patch -- *and* all of its dependencies". And relatedly, whether how to make -- sure that there are no other patches applied. -- -- With branches it's easier, as you can pull and -- checkout them, and they seem to be similar enough. Yet, pijul -- documentations says -- --
--   Note that the purpose of branches in Pijul is quite different from Git,
--   
-- -- since Git's "feature branches" can usually be implemented by just -- patches. -- -- I guess it means that indeed instead of creating a branch and making -- PR in GitHub workflow, you'd just create a patch and offer it. -- You can do that with git too. Push (a branch with) commit to -- remote and ask other to cherry-pick that commit. Yet, in git identity -- of commit changes when it applied to other trees, where patches in -- pijul have will continue to have the same hash. -- -- Unfortunately pijul doesn't talk about conflict resolution. It seems -- that you get something like: -- -- % pijul status On branch merge -- -- Unresolved conflicts: (fix conflicts and record the resolution with -- "pijul record ...") -- -- foo -- -- % cat foo first line >> -- >>>>>>>>>>>>>>>>>>>>>>>>>>>>> -- branch BBB ================================ branch AAA -- <<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< -- last line -- -- And then the `pijul dependencies` would draw you a graph like -- -- -- -- Which is seems reasonable. -- -- So currently, pijul support is very experimental, and most likely -- won't work, even the basics are in place. Tests are also written but -- disabled, as the branching model differs from git one, for -- which tests are written. vcsPijul :: VCS Program instance GHC.Show.Show Distribution.Client.VCS.SourceRepoProblem -- | Provides the version number of cabal-install. module Distribution.Client.Version cabalInstallVersion :: Version -- | Separate module for HTTP actions, using a proxy server if one exists. module Distribution.Client.HttpUtils data DownloadResult FileAlreadyInCache :: DownloadResult FileDownloaded :: FilePath -> DownloadResult configureTransport :: Verbosity -> [FilePath] -> Maybe String -> IO HttpTransport data HttpTransport HttpTransport :: (Verbosity -> URI -> Maybe ETag -> FilePath -> [Header] -> IO (HttpCode, Maybe ETag)) -> (Verbosity -> URI -> String -> Maybe Auth -> IO (HttpCode, String)) -> (Verbosity -> URI -> FilePath -> Maybe Auth -> IO (HttpCode, String)) -> (Verbosity -> URI -> FilePath -> Maybe Auth -> [Header] -> IO (HttpCode, String)) -> Bool -> Bool -> HttpTransport -- | GET a URI, with an optional ETag (to do a conditional fetch), write -- the resource to the given file and return the HTTP status code, and -- optional ETag. [getHttp] :: HttpTransport -> Verbosity -> URI -> Maybe ETag -> FilePath -> [Header] -> IO (HttpCode, Maybe ETag) -- | POST a resource to a URI, with optional auth (username, password) and -- return the HTTP status code and any redirect URL. [postHttp] :: HttpTransport -> Verbosity -> URI -> String -> Maybe Auth -> IO (HttpCode, String) -- | POST a file resource to a URI using multipart/form-data encoding, with -- optional auth (username, password) and return the HTTP status code and -- any error string. [postHttpFile] :: HttpTransport -> Verbosity -> URI -> FilePath -> Maybe Auth -> IO (HttpCode, String) -- | PUT a file resource to a URI, with optional auth (username, password), -- extra headers and return the HTTP status code and any error string. [putHttpFile] :: HttpTransport -> Verbosity -> URI -> FilePath -> Maybe Auth -> [Header] -> IO (HttpCode, String) -- | Whether this transport supports https or just http. [transportSupportsHttps] :: HttpTransport -> Bool -- | Whether this transport implementation was specifically chosen by the -- user via configuration, or whether it was automatically selected. -- Strictly speaking this is not a property of the transport itself but -- about how it was chosen. Nevertheless it's convenient to keep here. [transportManuallySelected] :: HttpTransport -> Bool type HttpCode = Int downloadURI :: HttpTransport -> Verbosity -> URI -> FilePath -> IO DownloadResult transportCheckHttps :: Verbosity -> HttpTransport -> URI -> IO () remoteRepoCheckHttps :: Verbosity -> HttpTransport -> RemoteRepo -> IO () remoteRepoTryUpgradeToHttps :: Verbosity -> HttpTransport -> RemoteRepo -> IO RemoteRepo -- | Utility function for legacy support. isOldHackageURI :: URI -> Bool instance GHC.Classes.Eq Distribution.Client.HttpUtils.DownloadResult instance GHC.Classes.Eq Distribution.Client.HttpUtils.DownloadCheck -- | Implementation of HttpLib using cabal-install's own -- HttpTransport module Distribution.Client.Security.HTTP -- | Abstraction over HTTP clients -- -- This avoids insisting on a particular implementation (such as the HTTP -- package) and allows for other implementations (such as a conduit based -- one). -- -- NOTE: Library-specific exceptions MUST be wrapped in -- SomeRemoteError. data HttpLib -- | Translate from hackage-security's HttpLib to cabal-install's -- HttpTransport -- -- NOTE: The match between these two APIs is currently not perfect: -- -- transportAdapter :: Verbosity -> IO HttpTransport -> HttpLib instance GHC.Show.Show Distribution.Client.Security.HTTP.UnexpectedResponse instance Hackage.Security.Util.Pretty.Pretty Distribution.Client.Security.HTTP.UnexpectedResponse instance GHC.Exception.Type.Exception Distribution.Client.Security.HTTP.UnexpectedResponse module Distribution.Client.GlobalFlags -- | Flags that apply at the top level, not to any sub-command. data GlobalFlags GlobalFlags :: Flag Bool -> Flag Bool -> Flag FilePath -> Flag FilePath -> NubList RemoteRepo -> Flag FilePath -> NubList LocalRepo -> Flag ActiveRepos -> Flag FilePath -> Flag Bool -> Flag String -> Flag Bool -> Flag FilePath -> NubList FilePath -> GlobalFlags [globalVersion] :: GlobalFlags -> Flag Bool [globalNumericVersion] :: GlobalFlags -> Flag Bool [globalConfigFile] :: GlobalFlags -> Flag FilePath [globalConstraintsFile] :: GlobalFlags -> Flag FilePath -- | Available Hackage servers. [globalRemoteRepos] :: GlobalFlags -> NubList RemoteRepo [globalCacheDir] :: GlobalFlags -> Flag FilePath [globalLocalNoIndexRepos] :: GlobalFlags -> NubList LocalRepo [globalActiveRepos] :: GlobalFlags -> Flag ActiveRepos [globalLogsDir] :: GlobalFlags -> Flag FilePath -- | Ignore security expiry dates [globalIgnoreExpiry] :: GlobalFlags -> Flag Bool [globalHttpTransport] :: GlobalFlags -> Flag String -- | Integrate with Nix [globalNix] :: GlobalFlags -> Flag Bool [globalStoreDir] :: GlobalFlags -> Flag FilePath -- | Extra program path used for packagedb lookups in a global context -- (i.e. for http transports) [globalProgPathExtra] :: GlobalFlags -> NubList FilePath defaultGlobalFlags :: GlobalFlags -- | Access to repositories data RepoContext RepoContext :: [Repo] -> IO HttpTransport -> (forall a. Repo -> (forall down. Repository down -> IO a) -> IO a) -> Bool -> RepoContext -- | All user-specified repositories [repoContextRepos] :: RepoContext -> [Repo] -- | Get the HTTP transport -- -- The transport will be initialized on the first call to this function. -- -- NOTE: It is important that we don't eagerly initialize the transport. -- Initializing the transport is not free, and especially in contexts -- where we don't know a priori whether or not we need the transport (for -- instance when using cabal in "nix mode") incurring the overhead of -- transport initialization on _every_ invocation (eg cabal -- build) is undesirable. [repoContextGetTransport] :: RepoContext -> IO HttpTransport -- | Get the (initialized) secure repo -- -- (the Repo type itself is stateless and must remain so, because -- it must be serializable) [repoContextWithSecureRepo] :: RepoContext -> forall a. Repo -> (forall down. Repository down -> IO a) -> IO a -- | Should we ignore expiry times (when checking security)? [repoContextIgnoreExpiry] :: RepoContext -> Bool withRepoContext :: Verbosity -> GlobalFlags -> (RepoContext -> IO a) -> IO a withRepoContext' :: Verbosity -> [RemoteRepo] -> [LocalRepo] -> FilePath -> Maybe String -> Maybe Bool -> [FilePath] -> (RepoContext -> IO a) -> IO a instance GHC.Generics.Generic Distribution.Client.GlobalFlags.GlobalFlags instance GHC.Show.Show Distribution.Client.GlobalFlags.GlobalFlags instance GHC.Base.Monoid Distribution.Client.GlobalFlags.GlobalFlags instance GHC.Base.Semigroup Distribution.Client.GlobalFlags.GlobalFlags -- | Functions for fetching packages module Distribution.Client.FetchUtils -- | Fetch a package if we don't have it already. fetchPackage :: Verbosity -> RepoContext -> UnresolvedPkgLoc -> IO ResolvedPkgLoc -- | Returns True if the package has already been fetched or does -- not need fetching. isFetched :: UnresolvedPkgLoc -> IO Bool -- | Checks if the package has already been fetched (or does not need -- fetching) and if so returns evidence in the form of a -- PackageLocation with a resolved local file location. checkFetched :: UnresolvedPkgLoc -> IO (Maybe ResolvedPkgLoc) -- | Like checkFetched but for the specific case of a -- RepoTarballPackage. checkRepoTarballFetched :: Repo -> PackageId -> IO (Maybe FilePath) -- | Fetch a repo package if we don't have it already. fetchRepoTarball :: Verbosity -> RepoContext -> Repo -> PackageId -> IO FilePath verifyFetchedTarball :: Verbosity -> RepoContext -> Repo -> PackageId -> IO Bool -- | Fork off an async action to download the given packages (by location). -- -- The downloads are initiated in order, so you can arrange for packages -- that will likely be needed sooner to be earlier in the list. -- -- The body action is passed a map from those packages (identified by -- their location) to a completion var for that package. So the body -- action should lookup the location and use waitAsyncFetchPackage -- to get the result. -- -- Synchronous exceptions raised by the download actions are delivered -- via waitAsyncFetchPackage. asyncFetchPackages :: Verbosity -> RepoContext -> [UnresolvedPkgLoc] -> (AsyncFetchMap -> IO a) -> IO a -- | Expect to find a download in progress in the given -- AsyncFetchMap and wait on it to finish. -- -- If the download failed with an exception then this will be thrown. -- -- Note: This function is supposed to be idempotent, as our install plans -- can now use the same tarball for many builds, e.g. different -- components and/or qualified goals, and these all go through the -- download phase so we end up using waitAsyncFetchPackage twice -- on the same package. C.f. #4461. waitAsyncFetchPackage :: Verbosity -> AsyncFetchMap -> UnresolvedPkgLoc -> IO ResolvedPkgLoc type AsyncFetchMap = Map UnresolvedPkgLoc (MVar (Either SomeException ResolvedPkgLoc)) -- | Downloads an index file to [config-dirpackagesserv-id] without -- hackage-security. You probably don't want to call this directly; use -- updateRepo instead. downloadIndex :: HttpTransport -> Verbosity -> RemoteRepo -> FilePath -> IO DownloadResult -- | Handling for user-specified targets module Distribution.Client.Targets -- | Various ways that a user may specify a package or package collection. data UserTarget -- | A partially specified package, identified by name and possibly with an -- exact version or a version constraint. -- --
--   cabal install foo
--   cabal install foo-1.0
--   cabal install 'foo < 2'
--   
UserTargetNamed :: PackageVersionConstraint -> UserTarget -- | A specific package that is unpacked in a local directory, often the -- current directory. -- --
--   cabal install .
--   cabal install ../lib/other
--   
-- -- UserTargetLocalDir :: FilePath -> UserTarget -- | A specific local unpacked package, identified by its .cabal -- file. -- --
--   cabal install foo.cabal
--   cabal install ../lib/other/bar.cabal
--   
UserTargetLocalCabalFile :: FilePath -> UserTarget -- | A specific package that is available as a local tarball file -- --
--   cabal install dist/foo-1.0.tar.gz
--   cabal install ../build/baz-1.0.tar.gz
--   
UserTargetLocalTarball :: FilePath -> UserTarget -- | A specific package that is available as a remote tarball file -- --
--   cabal install http://code.haskell.org/~user/foo/foo-0.9.tar.gz
--   
UserTargetRemoteTarball :: URI -> UserTarget readUserTargets :: Verbosity -> [String] -> IO [UserTarget] -- | Given a bunch of user-specified targets, try to resolve what it is -- they refer to. They can either be specific packages (local dirs, -- tarballs etc) or they can be named packages (with or without version -- info). resolveUserTargets :: Package pkg => Verbosity -> RepoContext -> PackageIndex pkg -> [UserTarget] -> IO [PackageSpecifier UnresolvedSourcePackage] data UserTargetProblem UserTargetUnexpectedFile :: String -> UserTargetProblem UserTargetNonexistantFile :: String -> UserTargetProblem UserTargetUnexpectedUriScheme :: String -> UserTargetProblem UserTargetUnrecognisedUri :: String -> UserTargetProblem UserTargetUnrecognised :: String -> UserTargetProblem readUserTarget :: String -> IO (Either UserTargetProblem UserTarget) reportUserTargetProblems :: Verbosity -> [UserTargetProblem] -> IO () -- | Given a user-specified target, expand it to a bunch of package targets -- (each of which refers to only one package). expandUserTarget :: Verbosity -> UserTarget -> IO [PackageTarget (PackageLocation ())] -- | An intermediate between a UserTarget and a resolved -- PackageSpecifier. Unlike a UserTarget, a -- PackageTarget refers only to a single package. data PackageTarget pkg PackageTargetNamed :: PackageName -> [PackageProperty] -> UserTarget -> PackageTarget pkg -- | A package identified by name, but case insensitively, so it needs to -- be resolved to the right case-sensitive name. PackageTargetNamedFuzzy :: PackageName -> [PackageProperty] -> UserTarget -> PackageTarget pkg PackageTargetLocation :: pkg -> PackageTarget pkg -- | Fetch any remote targets so that they can be read. fetchPackageTarget :: Verbosity -> RepoContext -> PackageTarget (PackageLocation ()) -> IO (PackageTarget ResolvedPkgLoc) -- | Given a package target that has been fetched, read the .cabal file. -- -- This only affects targets given by location, named targets are -- unaffected. readPackageTarget :: Verbosity -> PackageTarget ResolvedPkgLoc -> IO (PackageTarget UnresolvedSourcePackage) data PackageTargetProblem PackageNameUnknown :: PackageName -> UserTarget -> PackageTargetProblem PackageNameAmbiguous :: PackageName -> [PackageName] -> UserTarget -> PackageTargetProblem -- | Report problems to the user. That is, if there are any problems then -- raise an exception. reportPackageTargetProblems :: Verbosity -> [PackageTargetProblem] -> IO () -- | Users are allowed to give package names case-insensitively, so we must -- disambiguate named package references. disambiguatePackageTargets :: Package pkg' => PackageIndex pkg' -> [PackageName] -> [PackageTarget pkg] -> ([PackageTargetProblem], [PackageSpecifier pkg]) -- | Given a package name and a list of matching names, figure out which -- one it might be referring to. If there is an exact case-sensitive -- match then that's ok (i.e. returned via Unambiguous). If it -- matches just one package case-insensitively or if it matches multiple -- packages case-insensitively, in that case the result is -- Ambiguous. -- -- Note: Before cabal 2.2, when only a single package matched -- case-insensitively it would be considered Unambiguous. disambiguatePackageName :: PackageNameEnv -> PackageName -> MaybeAmbiguous PackageName -- | Version of Qualifier that a user may specify on the command -- line. data UserQualifier -- | Top-level dependency. UserQualToplevel :: UserQualifier -- | Setup dependency. UserQualSetup :: PackageName -> UserQualifier -- | Executable dependency. UserQualExe :: PackageName -> PackageName -> UserQualifier -- | Version of ConstraintScope that a user may specify on the -- command line. data UserConstraintScope -- | Scope that applies to the package when it has the specified qualifier. UserQualified :: UserQualifier -> PackageName -> UserConstraintScope -- | Scope that applies to the package when it has a setup qualifier. UserAnySetupQualifier :: PackageName -> UserConstraintScope -- | Scope that applies to the package when it has any qualifier. UserAnyQualifier :: PackageName -> UserConstraintScope -- | Version of PackageConstraint that the user can specify on the -- command line. data UserConstraint UserConstraint :: UserConstraintScope -> PackageProperty -> UserConstraint userConstraintPackageName :: UserConstraint -> PackageName readUserConstraint :: String -> Either String UserConstraint userToPackageConstraint :: UserConstraint -> PackageConstraint instance GHC.Classes.Eq Distribution.Client.Targets.UserTarget instance GHC.Show.Show Distribution.Client.Targets.UserTarget instance GHC.Show.Show Distribution.Client.Targets.UserTargetProblem instance Data.Traversable.Traversable Distribution.Client.Targets.PackageTarget instance Data.Foldable.Foldable Distribution.Client.Targets.PackageTarget instance GHC.Base.Functor Distribution.Client.Targets.PackageTarget instance GHC.Show.Show pkg => GHC.Show.Show (Distribution.Client.Targets.PackageTarget pkg) instance GHC.Show.Show Distribution.Client.Targets.PackageTargetProblem instance GHC.Generics.Generic Distribution.Client.Targets.UserQualifier instance GHC.Show.Show Distribution.Client.Targets.UserQualifier instance GHC.Classes.Eq Distribution.Client.Targets.UserQualifier instance GHC.Generics.Generic Distribution.Client.Targets.UserConstraintScope instance GHC.Show.Show Distribution.Client.Targets.UserConstraintScope instance GHC.Classes.Eq Distribution.Client.Targets.UserConstraintScope instance GHC.Generics.Generic Distribution.Client.Targets.UserConstraint instance GHC.Show.Show Distribution.Client.Targets.UserConstraint instance GHC.Classes.Eq Distribution.Client.Targets.UserConstraint instance Data.Binary.Class.Binary Distribution.Client.Targets.UserConstraint instance Distribution.Utils.Structured.Structured Distribution.Client.Targets.UserConstraint instance Distribution.Pretty.Pretty Distribution.Client.Targets.UserConstraint instance Distribution.Parsec.Parsec Distribution.Client.Targets.UserConstraint instance Data.Binary.Class.Binary Distribution.Client.Targets.UserConstraintScope instance Distribution.Utils.Structured.Structured Distribution.Client.Targets.UserConstraintScope instance Data.Binary.Class.Binary Distribution.Client.Targets.UserQualifier instance Distribution.Utils.Structured.Structured Distribution.Client.Targets.UserQualifier instance GHC.Base.Monoid Distribution.Client.Targets.PackageNameEnv instance GHC.Base.Semigroup Distribution.Client.Targets.PackageNameEnv module Distribution.Client.Setup globalCommand :: [Command action] -> CommandUI GlobalFlags -- | Flags that apply at the top level, not to any sub-command. data GlobalFlags GlobalFlags :: Flag Bool -> Flag Bool -> Flag FilePath -> Flag FilePath -> NubList RemoteRepo -> Flag FilePath -> NubList LocalRepo -> Flag ActiveRepos -> Flag FilePath -> Flag Bool -> Flag String -> Flag Bool -> Flag FilePath -> NubList FilePath -> GlobalFlags [globalVersion] :: GlobalFlags -> Flag Bool [globalNumericVersion] :: GlobalFlags -> Flag Bool [globalConfigFile] :: GlobalFlags -> Flag FilePath [globalConstraintsFile] :: GlobalFlags -> Flag FilePath -- | Available Hackage servers. [globalRemoteRepos] :: GlobalFlags -> NubList RemoteRepo [globalCacheDir] :: GlobalFlags -> Flag FilePath [globalLocalNoIndexRepos] :: GlobalFlags -> NubList LocalRepo [globalActiveRepos] :: GlobalFlags -> Flag ActiveRepos [globalLogsDir] :: GlobalFlags -> Flag FilePath -- | Ignore security expiry dates [globalIgnoreExpiry] :: GlobalFlags -> Flag Bool [globalHttpTransport] :: GlobalFlags -> Flag String -- | Integrate with Nix [globalNix] :: GlobalFlags -> Flag Bool [globalStoreDir] :: GlobalFlags -> Flag FilePath -- | Extra program path used for packagedb lookups in a global context -- (i.e. for http transports) [globalProgPathExtra] :: GlobalFlags -> NubList FilePath defaultGlobalFlags :: GlobalFlags -- | Access to repositories data RepoContext RepoContext :: [Repo] -> IO HttpTransport -> (forall a. Repo -> (forall down. Repository down -> IO a) -> IO a) -> Bool -> RepoContext -- | All user-specified repositories [repoContextRepos] :: RepoContext -> [Repo] -- | Get the HTTP transport -- -- The transport will be initialized on the first call to this function. -- -- NOTE: It is important that we don't eagerly initialize the transport. -- Initializing the transport is not free, and especially in contexts -- where we don't know a priori whether or not we need the transport (for -- instance when using cabal in "nix mode") incurring the overhead of -- transport initialization on _every_ invocation (eg cabal -- build) is undesirable. [repoContextGetTransport] :: RepoContext -> IO HttpTransport -- | Get the (initialized) secure repo -- -- (the Repo type itself is stateless and must remain so, because -- it must be serializable) [repoContextWithSecureRepo] :: RepoContext -> forall a. Repo -> (forall down. Repository down -> IO a) -> IO a -- | Should we ignore expiry times (when checking security)? [repoContextIgnoreExpiry] :: RepoContext -> Bool withRepoContext :: Verbosity -> GlobalFlags -> (RepoContext -> IO a) -> IO a configureCommand :: CommandUI ConfigFlags -- | Flags to configure command. -- -- IMPORTANT: every time a new flag is added, filterConfigureFlags -- should be updated. IMPORTANT: every time a new flag is added, it -- should be added to the Eq instance data ConfigFlags ConfigFlags :: [String] -> Option' (Last' ProgramDb) -> [(String, FilePath)] -> [(String, [String])] -> NubList FilePath -> Flag CompilerFlavor -> Flag FilePath -> Flag FilePath -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag ProfDetailLevel -> Flag ProfDetailLevel -> [String] -> Flag OptimisationLevel -> Flag PathTemplate -> Flag PathTemplate -> InstallDirs (Flag PathTemplate) -> Flag FilePath -> [FilePath] -> [FilePath] -> [FilePath] -> [FilePath] -> Flag String -> Flag ComponentId -> Flag Bool -> Flag FilePath -> Flag FilePath -> Flag Verbosity -> Flag Bool -> [Maybe PackageDB] -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> [PackageVersionConstraint] -> [GivenComponent] -> [(ModuleName, Module)] -> FlagAssignment -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag String -> Flag Bool -> Flag DebugInfoLevel -> Flag DumpBuildInfo -> Flag Bool -> Flag Bool -> ConfigFlags [configArgs] :: ConfigFlags -> [String] -- | All programs that cabal may run [configPrograms_] :: ConfigFlags -> Option' (Last' ProgramDb) -- | user specified programs paths [configProgramPaths] :: ConfigFlags -> [(String, FilePath)] -- | user specified programs args [configProgramArgs] :: ConfigFlags -> [(String, [String])] -- | Extend the $PATH [configProgramPathExtra] :: ConfigFlags -> NubList FilePath -- | The "flavor" of the compiler, e.g. GHC. [configHcFlavor] :: ConfigFlags -> Flag CompilerFlavor -- | given compiler location [configHcPath] :: ConfigFlags -> Flag FilePath -- | given hc-pkg location [configHcPkg] :: ConfigFlags -> Flag FilePath -- | Enable vanilla library [configVanillaLib] :: ConfigFlags -> Flag Bool -- | Enable profiling in the library [configProfLib] :: ConfigFlags -> Flag Bool -- | Build shared library [configSharedLib] :: ConfigFlags -> Flag Bool -- | Build static library [configStaticLib] :: ConfigFlags -> Flag Bool -- | Enable dynamic linking of the executables. [configDynExe] :: ConfigFlags -> Flag Bool -- | Enable fully static linking of the executables. [configFullyStaticExe] :: ConfigFlags -> Flag Bool -- | Enable profiling in the executables. [configProfExe] :: ConfigFlags -> Flag Bool -- | Enable profiling in the library and executables. [configProf] :: ConfigFlags -> Flag Bool -- | Profiling detail level in the library and executables. [configProfDetail] :: ConfigFlags -> Flag ProfDetailLevel -- | Profiling detail level in the library [configProfLibDetail] :: ConfigFlags -> Flag ProfDetailLevel -- | Extra arguments to configure [configConfigureArgs] :: ConfigFlags -> [String] -- | Enable optimization. [configOptimization] :: ConfigFlags -> Flag OptimisationLevel -- | Installed executable prefix. [configProgPrefix] :: ConfigFlags -> Flag PathTemplate -- | Installed executable suffix. [configProgSuffix] :: ConfigFlags -> Flag PathTemplate -- | Installation paths [configInstallDirs] :: ConfigFlags -> InstallDirs (Flag PathTemplate) [configScratchDir] :: ConfigFlags -> Flag FilePath -- | path to search for extra libraries [configExtraLibDirs] :: ConfigFlags -> [FilePath] -- | path to search for extra libraries when linking fully static -- executables [configExtraLibDirsStatic] :: ConfigFlags -> [FilePath] -- | path to search for extra frameworks (OS X only) [configExtraFrameworkDirs] :: ConfigFlags -> [FilePath] -- | path to search for header files [configExtraIncludeDirs] :: ConfigFlags -> [FilePath] -- | explicit IPID to be used [configIPID] :: ConfigFlags -> Flag String -- | explicit CID to be used [configCID] :: ConfigFlags -> Flag ComponentId -- | be as deterministic as possible (e.g., invariant over GHC, database, -- etc). Used by the test suite [configDeterministic] :: ConfigFlags -> Flag Bool -- | "dist" prefix [configDistPref] :: ConfigFlags -> Flag FilePath -- | Cabal file to use [configCabalFilePath] :: ConfigFlags -> Flag FilePath -- | verbosity level [configVerbosity] :: ConfigFlags -> Flag Verbosity -- | The --user/--global flag [configUserInstall] :: ConfigFlags -> Flag Bool -- | Which package DBs to use [configPackageDBs] :: ConfigFlags -> [Maybe PackageDB] -- | Enable compiling library for GHCi [configGHCiLib] :: ConfigFlags -> Flag Bool -- | Enable -split-sections with GHC [configSplitSections] :: ConfigFlags -> Flag Bool -- | Enable -split-objs with GHC [configSplitObjs] :: ConfigFlags -> Flag Bool -- | Enable executable stripping [configStripExes] :: ConfigFlags -> Flag Bool -- | Enable library stripping [configStripLibs] :: ConfigFlags -> Flag Bool -- | Additional constraints for dependencies. [configConstraints] :: ConfigFlags -> [PackageVersionConstraint] -- | The packages depended on. [configDependencies] :: ConfigFlags -> [GivenComponent] -- | The requested Backpack instantiation. If empty, either this package -- does not use Backpack, or we just want to typecheck the indefinite -- package. [configInstantiateWith] :: ConfigFlags -> [(ModuleName, Module)] [configConfigurationsFlags] :: ConfigFlags -> FlagAssignment -- | Enable test suite compilation [configTests] :: ConfigFlags -> Flag Bool -- | Enable benchmark compilation [configBenchmarks] :: ConfigFlags -> Flag Bool -- | Enable program coverage [configCoverage] :: ConfigFlags -> Flag Bool -- | Enable program coverage (deprecated) [configLibCoverage] :: ConfigFlags -> Flag Bool -- | All direct dependencies and flags are provided on the command line by -- the user via the '--dependency' and '--flags' options. [configExactConfiguration] :: ConfigFlags -> Flag Bool -- | Halt and show an error message indicating an error in flag assignment [configFlagError] :: ConfigFlags -> Flag String -- | Enable relocatable package built [configRelocatable] :: ConfigFlags -> Flag Bool -- | Emit debug info. [configDebugInfo] :: ConfigFlags -> Flag DebugInfoLevel -- | Should we dump available build information on build? Dump build -- information to disk before attempting to build, tooling can parse -- these files and use them to compile the source files themselves. [configDumpBuildInfo] :: ConfigFlags -> Flag DumpBuildInfo -- | Whether to use response files at all. They're used for such tools as -- haddock, or ld. [configUseResponseFiles] :: ConfigFlags -> Flag Bool -- | Allow depending on private sublibraries. This is used by external -- tools (like cabal-install) so they can add multiple-public-libraries -- compatibility to older ghcs by checking visibility externally. [configAllowDependingOnPrivateLibs] :: ConfigFlags -> Flag Bool configureOptions :: ShowOrParseArgs -> [OptionField ConfigFlags] -- | Given some ConfigFlags for the version of Cabal that -- cabal-install was built with, and a target older Version of -- Cabal that we want to pass these flags to, convert the flags into a -- form that will be accepted by the older Setup script. Generally -- speaking, this just means filtering out flags that the old Cabal -- library doesn't understand, but in some cases it may also mean -- "emulating" a feature using some more legacy flags. filterConfigureFlags :: ConfigFlags -> Version -> ConfigFlags -- | Get the package database settings from ConfigFlags, accounting -- for --package-db and --user flags. configPackageDB' :: ConfigFlags -> PackageDBStack -- | Configure the compiler, but reduce verbosity during this step. configCompilerAux' :: ConfigFlags -> IO (Compiler, Platform, ProgramDb) configureExCommand :: CommandUI (ConfigFlags, ConfigExFlags) -- | cabal configure takes some extra flags beyond runghc Setup configure data ConfigExFlags ConfigExFlags :: Flag Version -> Flag Bool -> Flag Bool -> [(UserConstraint, ConstraintSource)] -> [PackageVersionConstraint] -> Flag PreSolver -> Maybe AllowNewer -> Maybe AllowOlder -> Flag WriteGhcEnvironmentFilesPolicy -> ConfigExFlags [configCabalVersion] :: ConfigExFlags -> Flag Version [configAppend] :: ConfigExFlags -> Flag Bool [configBackup] :: ConfigExFlags -> Flag Bool [configExConstraints] :: ConfigExFlags -> [(UserConstraint, ConstraintSource)] [configPreferences] :: ConfigExFlags -> [PackageVersionConstraint] [configSolver] :: ConfigExFlags -> Flag PreSolver [configAllowNewer] :: ConfigExFlags -> Maybe AllowNewer [configAllowOlder] :: ConfigExFlags -> Maybe AllowOlder [configWriteGhcEnvironmentFilesPolicy] :: ConfigExFlags -> Flag WriteGhcEnvironmentFilesPolicy defaultConfigExFlags :: ConfigExFlags buildCommand :: CommandUI BuildFlags data BuildFlags BuildFlags :: [(String, FilePath)] -> [(String, [String])] -> Flag FilePath -> Flag Verbosity -> Flag (Maybe Int) -> [String] -> Flag FilePath -> BuildFlags [buildProgramPaths] :: BuildFlags -> [(String, FilePath)] [buildProgramArgs] :: BuildFlags -> [(String, [String])] [buildDistPref] :: BuildFlags -> Flag FilePath [buildVerbosity] :: BuildFlags -> Flag Verbosity [buildNumJobs] :: BuildFlags -> Flag (Maybe Int) [buildArgs] :: BuildFlags -> [String] [buildCabalFilePath] :: BuildFlags -> Flag FilePath -- | Given some TestFlags for the version of Cabal that -- cabal-install was built with, and a target older Version of -- Cabal that we want to pass these flags to, convert the flags into a -- form that will be accepted by the older Setup script. Generally -- speaking, this just means filtering out flags that the old Cabal -- library doesn't understand, but in some cases it may also mean -- "emulating" a feature using some more legacy flags. filterTestFlags :: TestFlags -> Version -> TestFlags replCommand :: CommandUI ReplFlags testCommand :: CommandUI (BuildFlags, TestFlags) benchmarkCommand :: CommandUI (BuildFlags, BenchmarkFlags) testOptions :: ShowOrParseArgs -> [OptionField TestFlags] benchmarkOptions :: ShowOrParseArgs -> [OptionField BenchmarkFlags] configureExOptions :: ShowOrParseArgs -> ConstraintSource -> [OptionField ConfigExFlags] reconfigureCommand :: CommandUI (ConfigFlags, ConfigExFlags) installCommand :: CommandUI (ConfigFlags, ConfigExFlags, InstallFlags, HaddockFlags, TestFlags, BenchmarkFlags) -- | Install takes the same flags as configure along with a few extras. data InstallFlags InstallFlags :: Flag Bool -> Flag PathTemplate -> Flag CopyDest -> Flag Bool -> Flag Bool -> Flag Int -> Flag ReorderGoals -> Flag CountConflicts -> Flag FineGrainedConflicts -> Flag MinimizeConflictSet -> Flag IndependentGoals -> Flag PreferOldest -> Flag ShadowPkgs -> Flag StrongFlags -> Flag AllowBootLibInstalls -> Flag OnlyConstrained -> Flag Bool -> Flag AvoidReinstalls -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag TotalIndexState -> Flag String -> NubList PathTemplate -> Flag PathTemplate -> Flag ReportLevel -> Flag Bool -> Flag FilePath -> Flag Bool -> Flag (Maybe Int) -> Flag Bool -> Flag Bool -> Flag Bool -> InstallFlags [installDocumentation] :: InstallFlags -> Flag Bool [installHaddockIndex] :: InstallFlags -> Flag PathTemplate [installDest] :: InstallFlags -> Flag CopyDest [installDryRun] :: InstallFlags -> Flag Bool [installOnlyDownload] :: InstallFlags -> Flag Bool [installMaxBackjumps] :: InstallFlags -> Flag Int [installReorderGoals] :: InstallFlags -> Flag ReorderGoals [installCountConflicts] :: InstallFlags -> Flag CountConflicts [installFineGrainedConflicts] :: InstallFlags -> Flag FineGrainedConflicts [installMinimizeConflictSet] :: InstallFlags -> Flag MinimizeConflictSet [installIndependentGoals] :: InstallFlags -> Flag IndependentGoals [installPreferOldest] :: InstallFlags -> Flag PreferOldest [installShadowPkgs] :: InstallFlags -> Flag ShadowPkgs [installStrongFlags] :: InstallFlags -> Flag StrongFlags [installAllowBootLibInstalls] :: InstallFlags -> Flag AllowBootLibInstalls [installOnlyConstrained] :: InstallFlags -> Flag OnlyConstrained [installReinstall] :: InstallFlags -> Flag Bool [installAvoidReinstalls] :: InstallFlags -> Flag AvoidReinstalls [installOverrideReinstall] :: InstallFlags -> Flag Bool [installUpgradeDeps] :: InstallFlags -> Flag Bool [installOnly] :: InstallFlags -> Flag Bool [installOnlyDeps] :: InstallFlags -> Flag Bool [installIndexState] :: InstallFlags -> Flag TotalIndexState [installRootCmd] :: InstallFlags -> Flag String [installSummaryFile] :: InstallFlags -> NubList PathTemplate [installLogFile] :: InstallFlags -> Flag PathTemplate [installBuildReports] :: InstallFlags -> Flag ReportLevel [installReportPlanningFailure] :: InstallFlags -> Flag Bool [installSymlinkBinDir] :: InstallFlags -> Flag FilePath [installPerComponent] :: InstallFlags -> Flag Bool [installNumJobs] :: InstallFlags -> Flag (Maybe Int) [installKeepGoing] :: InstallFlags -> Flag Bool [installRunTests] :: InstallFlags -> Flag Bool [installOfflineMode] :: InstallFlags -> Flag Bool installOptions :: ShowOrParseArgs -> [OptionField InstallFlags] defaultInstallFlags :: InstallFlags filterHaddockArgs :: [String] -> Version -> [String] filterHaddockFlags :: HaddockFlags -> Version -> HaddockFlags haddockOptions :: ShowOrParseArgs -> [OptionField HaddockFlags] defaultSolver :: PreSolver defaultMaxBackjumps :: Int listCommand :: CommandUI ListFlags data ListFlags ListFlags :: Flag Bool -> Flag Bool -> Flag Bool -> Flag Verbosity -> [Maybe PackageDB] -> Flag FilePath -> ListFlags [listInstalled] :: ListFlags -> Flag Bool [listSimpleOutput] :: ListFlags -> Flag Bool [listCaseInsensitive] :: ListFlags -> Flag Bool [listVerbosity] :: ListFlags -> Flag Verbosity [listPackageDBs] :: ListFlags -> [Maybe PackageDB] [listHcPath] :: ListFlags -> Flag FilePath listNeedsCompiler :: ListFlags -> Bool data UpdateFlags UpdateFlags :: Flag Verbosity -> Flag TotalIndexState -> UpdateFlags [updateVerbosity] :: UpdateFlags -> Flag Verbosity [updateIndexState] :: UpdateFlags -> Flag TotalIndexState defaultUpdateFlags :: UpdateFlags infoCommand :: CommandUI InfoFlags data InfoFlags InfoFlags :: Flag Verbosity -> [Maybe PackageDB] -> InfoFlags [infoVerbosity] :: InfoFlags -> Flag Verbosity [infoPackageDBs] :: InfoFlags -> [Maybe PackageDB] fetchCommand :: CommandUI FetchFlags data FetchFlags FetchFlags :: Flag Bool -> Flag Bool -> Flag PreSolver -> Flag Int -> Flag ReorderGoals -> Flag CountConflicts -> Flag FineGrainedConflicts -> Flag MinimizeConflictSet -> Flag IndependentGoals -> Flag PreferOldest -> Flag ShadowPkgs -> Flag StrongFlags -> Flag AllowBootLibInstalls -> Flag OnlyConstrained -> Flag Bool -> Flag Bool -> Flag Verbosity -> FetchFlags [fetchDeps] :: FetchFlags -> Flag Bool [fetchDryRun] :: FetchFlags -> Flag Bool [fetchSolver] :: FetchFlags -> Flag PreSolver [fetchMaxBackjumps] :: FetchFlags -> Flag Int [fetchReorderGoals] :: FetchFlags -> Flag ReorderGoals [fetchCountConflicts] :: FetchFlags -> Flag CountConflicts [fetchFineGrainedConflicts] :: FetchFlags -> Flag FineGrainedConflicts [fetchMinimizeConflictSet] :: FetchFlags -> Flag MinimizeConflictSet [fetchIndependentGoals] :: FetchFlags -> Flag IndependentGoals [fetchPreferOldest] :: FetchFlags -> Flag PreferOldest [fetchShadowPkgs] :: FetchFlags -> Flag ShadowPkgs [fetchStrongFlags] :: FetchFlags -> Flag StrongFlags [fetchAllowBootLibInstalls] :: FetchFlags -> Flag AllowBootLibInstalls [fetchOnlyConstrained] :: FetchFlags -> Flag OnlyConstrained [fetchTests] :: FetchFlags -> Flag Bool [fetchBenchmarks] :: FetchFlags -> Flag Bool [fetchVerbosity] :: FetchFlags -> Flag Verbosity freezeCommand :: CommandUI FreezeFlags data FreezeFlags FreezeFlags :: Flag Bool -> Flag Bool -> Flag Bool -> Flag PreSolver -> Flag Int -> Flag ReorderGoals -> Flag CountConflicts -> Flag FineGrainedConflicts -> Flag MinimizeConflictSet -> Flag IndependentGoals -> Flag PreferOldest -> Flag ShadowPkgs -> Flag StrongFlags -> Flag AllowBootLibInstalls -> Flag OnlyConstrained -> Flag Verbosity -> FreezeFlags [freezeDryRun] :: FreezeFlags -> Flag Bool [freezeTests] :: FreezeFlags -> Flag Bool [freezeBenchmarks] :: FreezeFlags -> Flag Bool [freezeSolver] :: FreezeFlags -> Flag PreSolver [freezeMaxBackjumps] :: FreezeFlags -> Flag Int [freezeReorderGoals] :: FreezeFlags -> Flag ReorderGoals [freezeCountConflicts] :: FreezeFlags -> Flag CountConflicts [freezeFineGrainedConflicts] :: FreezeFlags -> Flag FineGrainedConflicts [freezeMinimizeConflictSet] :: FreezeFlags -> Flag MinimizeConflictSet [freezeIndependentGoals] :: FreezeFlags -> Flag IndependentGoals [freezePreferOldest] :: FreezeFlags -> Flag PreferOldest [freezeShadowPkgs] :: FreezeFlags -> Flag ShadowPkgs [freezeStrongFlags] :: FreezeFlags -> Flag StrongFlags [freezeAllowBootLibInstalls] :: FreezeFlags -> Flag AllowBootLibInstalls [freezeOnlyConstrained] :: FreezeFlags -> Flag OnlyConstrained [freezeVerbosity] :: FreezeFlags -> Flag Verbosity genBoundsCommand :: CommandUI FreezeFlags getCommand :: CommandUI GetFlags unpackCommand :: CommandUI GetFlags data GetFlags GetFlags :: Flag FilePath -> Flag Bool -> Flag Bool -> Flag TotalIndexState -> Flag ActiveRepos -> Flag (Maybe RepoKind) -> Flag Verbosity -> GetFlags [getDestDir] :: GetFlags -> Flag FilePath [getOnlyPkgDescr] :: GetFlags -> Flag Bool [getPristine] :: GetFlags -> Flag Bool [getIndexState] :: GetFlags -> Flag TotalIndexState [getActiveRepos] :: GetFlags -> Flag ActiveRepos [getSourceRepository] :: GetFlags -> Flag (Maybe RepoKind) [getVerbosity] :: GetFlags -> Flag Verbosity checkCommand :: CommandUI (Flag Verbosity) formatCommand :: CommandUI (Flag Verbosity) uploadCommand :: CommandUI UploadFlags data UploadFlags UploadFlags :: Flag IsCandidate -> Flag Bool -> Flag Username -> Flag Password -> Flag [String] -> Flag Verbosity -> UploadFlags [uploadCandidate] :: UploadFlags -> Flag IsCandidate [uploadDoc] :: UploadFlags -> Flag Bool [uploadUsername] :: UploadFlags -> Flag Username [uploadPassword] :: UploadFlags -> Flag Password [uploadPasswordCmd] :: UploadFlags -> Flag [String] [uploadVerbosity] :: UploadFlags -> Flag Verbosity -- | Is this a candidate package or a package to be published? data IsCandidate IsCandidate :: IsCandidate IsPublished :: IsCandidate reportCommand :: CommandUI ReportFlags data ReportFlags ReportFlags :: Flag Username -> Flag Password -> Flag Verbosity -> ReportFlags [reportUsername] :: ReportFlags -> Flag Username [reportPassword] :: ReportFlags -> Flag Password [reportVerbosity] :: ReportFlags -> Flag Verbosity runCommand :: CommandUI BuildFlags initCommand :: CommandUI InitFlags initOptions :: ShowOrParseArgs -> [OptionField InitFlags] -- | InitFlags is a subset of flags available in the .cabal file -- that represent options that are relevant to the init command process. data InitFlags InitFlags :: Flag Bool -> Flag Bool -> Flag FilePath -> Flag Bool -> Flag Bool -> Flag Bool -> Flag PackageName -> Flag Version -> Flag CabalSpecVersion -> Flag SpecLicense -> Flag String -> Flag String -> Flag String -> Flag String -> Flag String -> Flag [String] -> Flag [String] -> Flag PackageType -> Flag FilePath -> Flag Language -> Flag [ModuleName] -> Flag [ModuleName] -> Flag [Extension] -> Flag [Dependency] -> Flag [String] -> Flag [String] -> Flag [String] -> Flag Bool -> Flag [String] -> Flag FilePath -> Flag Verbosity -> Flag Bool -> InitFlags [interactive] :: InitFlags -> Flag Bool [quiet] :: InitFlags -> Flag Bool [packageDir] :: InitFlags -> Flag FilePath [noComments] :: InitFlags -> Flag Bool [minimal] :: InitFlags -> Flag Bool [simpleProject] :: InitFlags -> Flag Bool [packageName] :: InitFlags -> Flag PackageName [version] :: InitFlags -> Flag Version [cabalVersion] :: InitFlags -> Flag CabalSpecVersion [license] :: InitFlags -> Flag SpecLicense [author] :: InitFlags -> Flag String [email] :: InitFlags -> Flag String [homepage] :: InitFlags -> Flag String [synopsis] :: InitFlags -> Flag String [category] :: InitFlags -> Flag String [extraSrc] :: InitFlags -> Flag [String] [extraDoc] :: InitFlags -> Flag [String] [packageType] :: InitFlags -> Flag PackageType [mainIs] :: InitFlags -> Flag FilePath [language] :: InitFlags -> Flag Language [exposedModules] :: InitFlags -> Flag [ModuleName] [otherModules] :: InitFlags -> Flag [ModuleName] [otherExts] :: InitFlags -> Flag [Extension] [dependencies] :: InitFlags -> Flag [Dependency] [applicationDirs] :: InitFlags -> Flag [String] [sourceDirs] :: InitFlags -> Flag [String] [buildTools] :: InitFlags -> Flag [String] [initializeTestSuite] :: InitFlags -> Flag Bool [testDirs] :: InitFlags -> Flag [String] [initHcPath] :: InitFlags -> Flag FilePath [initVerbosity] :: InitFlags -> Flag Verbosity [overwrite] :: InitFlags -> Flag Bool actAsSetupCommand :: CommandUI ActAsSetupFlags data ActAsSetupFlags ActAsSetupFlags :: Flag BuildType -> ActAsSetupFlags [actAsSetupBuildType] :: ActAsSetupFlags -> Flag BuildType userConfigCommand :: CommandUI UserConfigFlags data UserConfigFlags UserConfigFlags :: Flag Verbosity -> Flag Bool -> Flag [String] -> UserConfigFlags [userConfigVerbosity] :: UserConfigFlags -> Flag Verbosity [userConfigForce] :: UserConfigFlags -> Flag Bool [userConfigAppendLines] :: UserConfigFlags -> Flag [String] manpageCommand :: CommandUI ManpageFlags haddockCommand :: CommandUI HaddockFlags cleanCommand :: CommandUI CleanFlags copyCommand :: CommandUI CopyFlags registerCommand :: CommandUI RegisterFlags liftOptions :: (b -> a) -> (a -> b -> b) -> [OptionField a] -> [OptionField b] yesNoOpt :: ShowOrParseArgs -> MkOptDescr (b -> Flag Bool) (Flag Bool -> b -> b) b instance GHC.Generics.Generic Distribution.Client.Setup.ConfigExFlags instance GHC.Show.Show Distribution.Client.Setup.ConfigExFlags instance GHC.Classes.Eq Distribution.Client.Setup.ConfigExFlags instance GHC.Generics.Generic Distribution.Client.Setup.UpdateFlags instance GHC.Generics.Generic Distribution.Client.Setup.ReportFlags instance GHC.Generics.Generic Distribution.Client.Setup.GetFlags instance GHC.Generics.Generic Distribution.Client.Setup.ListFlags instance GHC.Generics.Generic Distribution.Client.Setup.InfoFlags instance GHC.Generics.Generic Distribution.Client.Setup.InstallFlags instance GHC.Show.Show Distribution.Client.Setup.InstallFlags instance GHC.Classes.Eq Distribution.Client.Setup.InstallFlags instance GHC.Classes.Eq Distribution.Client.Setup.IsCandidate instance GHC.Generics.Generic Distribution.Client.Setup.UploadFlags instance GHC.Generics.Generic Distribution.Client.Setup.ActAsSetupFlags instance GHC.Generics.Generic Distribution.Client.Setup.UserConfigFlags instance GHC.Base.Monoid Distribution.Client.Setup.UserConfigFlags instance GHC.Base.Semigroup Distribution.Client.Setup.UserConfigFlags instance GHC.Base.Monoid Distribution.Client.Setup.ActAsSetupFlags instance GHC.Base.Semigroup Distribution.Client.Setup.ActAsSetupFlags instance GHC.Base.Monoid Distribution.Client.Setup.UploadFlags instance GHC.Base.Semigroup Distribution.Client.Setup.UploadFlags instance Data.Binary.Class.Binary Distribution.Client.Setup.InstallFlags instance GHC.Base.Monoid Distribution.Client.Setup.InstallFlags instance GHC.Base.Semigroup Distribution.Client.Setup.InstallFlags instance GHC.Base.Monoid Distribution.Client.Setup.InfoFlags instance GHC.Base.Semigroup Distribution.Client.Setup.InfoFlags instance GHC.Base.Monoid Distribution.Client.Setup.ListFlags instance GHC.Base.Semigroup Distribution.Client.Setup.ListFlags instance GHC.Base.Monoid Distribution.Client.Setup.GetFlags instance GHC.Base.Semigroup Distribution.Client.Setup.GetFlags instance GHC.Base.Monoid Distribution.Client.Setup.ReportFlags instance GHC.Base.Semigroup Distribution.Client.Setup.ReportFlags instance GHC.Base.Monoid Distribution.Client.Setup.ConfigExFlags instance GHC.Base.Semigroup Distribution.Client.Setup.ConfigExFlags -- | Command line options for nix-style / v2 commands. -- -- The commands take a lot of the same options, which affect how install -- plan is constructed. module Distribution.Client.NixStyleOptions data NixStyleFlags a NixStyleFlags :: ConfigFlags -> ConfigExFlags -> InstallFlags -> HaddockFlags -> TestFlags -> BenchmarkFlags -> ProjectFlags -> a -> NixStyleFlags a [configFlags] :: NixStyleFlags a -> ConfigFlags [configExFlags] :: NixStyleFlags a -> ConfigExFlags [installFlags] :: NixStyleFlags a -> InstallFlags [haddockFlags] :: NixStyleFlags a -> HaddockFlags [testFlags] :: NixStyleFlags a -> TestFlags [benchmarkFlags] :: NixStyleFlags a -> BenchmarkFlags [projectFlags] :: NixStyleFlags a -> ProjectFlags [extraFlags] :: NixStyleFlags a -> a nixStyleOptions :: (ShowOrParseArgs -> [OptionField a]) -> ShowOrParseArgs -> [OptionField (NixStyleFlags a)] defaultNixStyleFlags :: a -> NixStyleFlags a -- | Functions for building the manual page. module Distribution.Client.Manpage -- | Produces a manual page with troff markup. manpage :: String -> [CommandSpec a] -> String manpageCmd :: String -> [CommandSpec a] -> ManpageFlags -> IO () data ManpageFlags defaultManpageFlags :: ManpageFlags manpageOptions :: ShowOrParseArgs -> [OptionField ManpageFlags] -- | Managing installing binaries with symlinks. module Distribution.Client.InstallSymlink -- | We would like by default to install binaries into some location that -- is on the user's PATH. For per-user installations on Unix systems that -- basically means the ~bin directory. On the majority of -- platforms the ~bin directory will be on the user's -- PATH. However some people are a bit nervous about letting a package -- manager install programs into ~bin. -- -- A compromise solution is that instead of installing binaries directly -- into ~bin, we could install them in a private location -- under ~.cabalbin and then create symlinks in -- ~bin. We can be careful when setting up the symlinks -- that we do not overwrite any binary that the user installed. We can -- check if it was a symlink we made because it would point to the -- private dir where we install our binaries. This means we can install -- normally without worrying and in a later phase set up symlinks, and if -- that fails then we report it to the user, but even in this case the -- package is still in an OK installed state. -- -- This is an optional feature that users can choose to use or not. It is -- controlled from the config file. Of course it only works on POSIX -- systems with symlinks so is not available to Windows users. symlinkBinaries :: Platform -> Compiler -> OverwritePolicy -> ConfigFlags -> InstallFlags -> InstallPlan -> BuildOutcomes -> IO [(PackageIdentifier, UnqualComponentName, FilePath)] -- | Symlink binary. -- -- The paths are take in pieces, so we can make relative link when -- possible. symlinkBinary :: OverwritePolicy -> FilePath -> FilePath -> FilePath -> String -> IO Bool -- | Try to make a symlink in a temporary directory. -- -- If this works, we can try to symlink: even on Windows. trySymlink :: Verbosity -> IO Bool promptRun :: String -> IO Bool -> IO Bool instance GHC.Show.Show Distribution.Client.InstallSymlink.SymlinkStatus -- | Extra utils related to the package indexes. module Distribution.Client.IndexUtils -- | Return the age of the index file in days (as a Double). getIndexFileAge :: Repo -> IO Double -- | Reduced-verbosity version of getInstalledPackages getInstalledPackages :: Verbosity -> Compiler -> PackageDBStack -> ProgramDb -> IO InstalledPackageIndex -- | Get filename base (i.e. without file extension) for index-related -- files -- -- Secure cabal repositories use a new extended & incremental -- 01-index.tar. In order to avoid issues resulting from -- clobbering new/old-style index data, we save them locally to different -- names. -- -- Example: Use indexBaseName repo . "tar.gz" to compute -- the FilePath of the -- 00-index.tar.gz/01-index.tar.gz file. indexBaseName :: Repo -> FilePath -- | A set of files (or directories) that can be monitored to detect when -- there might have been a change in the installed packages. getInstalledPackagesMonitorFiles :: Verbosity -> Compiler -> PackageDBStack -> ProgramDb -> Platform -> IO [FilePath] -- | Read a repository index from disk, from the local files specified by a -- list of Repos. -- -- All the SourcePackages are marked as having come from the -- appropriate Repo. -- -- This is a higher level wrapper used internally in cabal-install. getSourcePackages :: Verbosity -> RepoContext -> IO SourcePackageDb -- | A set of files (or directories) that can be monitored to detect when -- there might have been a change in the source packages. getSourcePackagesMonitorFiles :: [Repo] -> [FilePath] -- | Index state of multiple repositories data TotalIndexState -- | Variant of getSourcePackages which allows getting the source -- packages at a particular IndexState. -- -- Current choices are either the latest (aka HEAD), or the index as it -- was at a particular time. -- -- Returns also the total index where repositories' RepoIndexState's are -- not HEAD. This is used in v2-freeze. getSourcePackagesAtIndexState :: Verbosity -> RepoContext -> Maybe TotalIndexState -> Maybe ActiveRepos -> IO (SourcePackageDb, TotalIndexState, ActiveRepos) -- | Ordered list of active repositories. data ActiveRepos -- | Note, this does nothing if ActiveRepoRest is present. filterSkippedActiveRepos :: ActiveRepos -> ActiveRepos -- | Which index do we mean? data Index -- | The main index for the specified repository RepoIndex :: RepoContext -> Repo -> Index -- | A sandbox-local repository Argument is the location of the index file SandboxIndex :: FilePath -> Index -- | Specification of the state of a specific repo package index data RepoIndexState -- | Use all available entries IndexStateHead :: RepoIndexState -- | Use all entries that existed at the specified time IndexStateTime :: !Timestamp -> RepoIndexState -- | An index entry is either a normal package, or a local build tree -- reference. data PackageEntry NormalPackage :: PackageId -> GenericPackageDescription -> ByteString -> BlockNo -> PackageEntry BuildTreeRef :: BuildTreeRefType -> PackageId -> GenericPackageDescription -> FilePath -> BlockNo -> PackageEntry -- | Read 00-index.tar.gz and extract .cabal and -- preferred-versions files -- -- We read the index using read, which gives us a lazily -- constructed TarEntries. We translate it to a list of entries -- using tarEntriesList, which preserves the lazy nature of -- TarEntries, and finally concatMap a function over this -- to translate it to a list of IO actions returning -- PackageOrDeps. We can use lazySequence to turn this into -- a list of PackageOrDeps, still maintaining the lazy nature of -- the original tar read. parsePackageIndex :: Verbosity -> ByteString -> [IO (Maybe PackageOrDep)] -- | It is not necessary to call this, as the cache will be updated when -- the index is read normally. However you can do the work earlier if you -- like. updateRepoIndexCache :: Verbosity -> Index -> IO () updatePackageIndexCacheFile :: Verbosity -> Index -> IO () -- | Write the IndexState to the filesystem writeIndexTimestamp :: Index -> RepoIndexState -> IO () -- | Read out the "current" index timestamp, i.e., what timestamp you would -- use to revert to this version currentIndexTimestamp :: Verbosity -> RepoContext -> Repo -> IO Timestamp -- | A build tree reference is either a link or a snapshot. data BuildTreeRefType SnapshotRef :: BuildTreeRefType LinkRef :: BuildTreeRefType refTypeFromTypeCode :: TypeCode -> BuildTreeRefType typeCodeFromRefType :: BuildTreeRefType -> TypeCode -- | Expected name of the 'preferred-versions' file. -- -- Contains special constraints, such as a preferred version of a package -- or deprecations of certain package versions. -- -- Expected format: -- --
--   binary > 0.9.0.0 || < 0.9.0.0
--   text == 1.2.1.0
--   
preferredVersions :: FilePath -- | Does the given filename match with the expected name of -- 'preferred-versions'? isPreferredVersions :: FilePath -> Bool -- | Parse `preferred-versions` file, collecting parse errors that can be -- shown in error messages. parsePreferredVersionsWarnings :: ByteString -> [Either PreferredVersionsParseError Dependency] -- | Parser error of the `preferred-versions` file. data PreferredVersionsParseError PreferredVersionsParseError :: String -> String -> PreferredVersionsParseError -- | Parser error to show to a user. [preferredVersionsParsecError] :: PreferredVersionsParseError -> String -- | Original input that produced the parser error. [preferredVersionsOriginalDependency] :: PreferredVersionsParseError -> String instance GHC.Generics.Generic Distribution.Client.IndexUtils.BuildTreeRefType instance GHC.Show.Show Distribution.Client.IndexUtils.BuildTreeRefType instance GHC.Classes.Eq Distribution.Client.IndexUtils.BuildTreeRefType instance GHC.Classes.Ord Distribution.Client.IndexUtils.PreferredVersionsParseError instance GHC.Classes.Eq Distribution.Client.IndexUtils.PreferredVersionsParseError instance GHC.Show.Show Distribution.Client.IndexUtils.PreferredVersionsParseError instance GHC.Read.Read Distribution.Client.IndexUtils.PreferredVersionsParseError instance GHC.Generics.Generic Distribution.Client.IndexUtils.PreferredVersionsParseError instance GHC.Generics.Generic Distribution.Client.IndexUtils.IndexCacheEntry instance GHC.Show.Show Distribution.Client.IndexUtils.IndexCacheEntry instance GHC.Classes.Eq Distribution.Client.IndexUtils.IndexCacheEntry instance GHC.Generics.Generic Distribution.Client.IndexUtils.Cache instance GHC.Show.Show Distribution.Client.IndexUtils.Cache instance GHC.Generics.Generic Distribution.Client.IndexUtils.NoIndexCacheEntry instance GHC.Show.Show Distribution.Client.IndexUtils.NoIndexCacheEntry instance GHC.Classes.Eq Distribution.Client.IndexUtils.NoIndexCacheEntry instance GHC.Generics.Generic Distribution.Client.IndexUtils.NoIndexCache instance GHC.Show.Show Distribution.Client.IndexUtils.NoIndexCache instance Control.DeepSeq.NFData Distribution.Client.IndexUtils.NoIndexCache instance Data.Binary.Class.Binary Distribution.Client.IndexUtils.NoIndexCache instance Distribution.Utils.Structured.Structured Distribution.Client.IndexUtils.NoIndexCache instance Control.DeepSeq.NFData Distribution.Client.IndexUtils.NoIndexCacheEntry instance Data.Binary.Class.Binary Distribution.Client.IndexUtils.NoIndexCacheEntry instance Distribution.Utils.Structured.Structured Distribution.Client.IndexUtils.NoIndexCacheEntry instance Control.DeepSeq.NFData Distribution.Client.IndexUtils.Cache instance Data.Binary.Class.Binary Distribution.Client.IndexUtils.Cache instance Distribution.Utils.Structured.Structured Distribution.Client.IndexUtils.Cache instance Control.DeepSeq.NFData Distribution.Client.IndexUtils.IndexCacheEntry instance Data.Binary.Class.Binary Distribution.Client.IndexUtils.IndexCacheEntry instance Distribution.Utils.Structured.Structured Distribution.Client.IndexUtils.IndexCacheEntry instance Distribution.Package.Package Distribution.Client.IndexUtils.PackageEntry instance Data.Binary.Class.Binary Distribution.Client.IndexUtils.BuildTreeRefType instance Distribution.Utils.Structured.Structured Distribution.Client.IndexUtils.BuildTreeRefType -- | Implementation of the 'cabal init' command, which creates an initial -- .cabal file for a project. module Distribution.Client.Init -- | This is the main driver for the init script. initCmd :: Verbosity -> PackageDBStack -> RepoContext -> Compiler -> ProgramDb -> InitFlags -> IO () -- | Handling project configuration, types. module Distribution.Client.ProjectConfig.Types -- | This type corresponds directly to what can be written in the -- cabal.project file. Other sources of configuration can also -- be injected into this type, such as the user-wide config file and the -- command line of cabal configure or cabal build. -- -- Since it corresponds to the external project file it is an instance of -- Monoid and all the fields can be empty. This also means there -- has to be a step where we resolve configuration. At a minimum -- resolving means applying defaults but it can also mean merging -- information from multiple sources. For example for package-specific -- configuration the project file can specify configuration that applies -- to all local packages, and then additional configuration for a -- specific package. -- -- Future directions: multiple profiles, conditionals. If we add these -- features then the gap between configuration as written in the config -- file and resolved settings we actually use will become even bigger. data ProjectConfig ProjectConfig :: [String] -> [String] -> [SourceRepoList] -> [PackageVersionConstraint] -> ProjectConfigBuildOnly -> ProjectConfigShared -> Set ProjectConfigProvenance -> PackageConfig -> PackageConfig -> MapMappend PackageName PackageConfig -> ProjectConfig -- | Packages in this project, including local dirs, local .cabal files -- local and remote tarballs. When these are file globs, they must match -- at least one package. [projectPackages] :: ProjectConfig -> [String] -- | Like projectConfigPackageGlobs but optional in the -- sense that file globs are allowed to match nothing. The primary use -- case for this is to be able to say optional-packages: */ to -- automagically pick up deps that we unpack locally without erroring -- when there aren't any. [projectPackagesOptional] :: ProjectConfig -> [String] -- | Packages in this project from remote source repositories. [projectPackagesRepo] :: ProjectConfig -> [SourceRepoList] -- | Packages in this project from hackage repositories. [projectPackagesNamed] :: ProjectConfig -> [PackageVersionConstraint] [projectConfigBuildOnly] :: ProjectConfig -> ProjectConfigBuildOnly [projectConfigShared] :: ProjectConfig -> ProjectConfigShared [projectConfigProvenance] :: ProjectConfig -> Set ProjectConfigProvenance -- | Configuration to be applied to *all* packages, whether named in -- `cabal.project` or not. [projectConfigAllPackages] :: ProjectConfig -> PackageConfig -- | Configuration to be applied to *local* packages; i.e., any packages -- which are explicitly named in `cabal.project`. [projectConfigLocalPackages] :: ProjectConfig -> PackageConfig [projectConfigSpecificPackage] :: ProjectConfig -> MapMappend PackageName PackageConfig -- | That part of the project configuration that only affects how we -- build and not the value of the things we build. This means this -- information does not need to be tracked for changes since it does not -- affect the outcome. data ProjectConfigBuildOnly ProjectConfigBuildOnly :: Flag Verbosity -> Flag Bool -> Flag Bool -> Flag Bool -> NubList PathTemplate -> Flag PathTemplate -> Flag ReportLevel -> Flag Bool -> Flag FilePath -> Flag (Maybe Int) -> Flag Bool -> Flag Bool -> Flag Bool -> Flag String -> Flag Bool -> Flag FilePath -> Flag FilePath -> ClientInstallFlags -> ProjectConfigBuildOnly [projectConfigVerbosity] :: ProjectConfigBuildOnly -> Flag Verbosity [projectConfigDryRun] :: ProjectConfigBuildOnly -> Flag Bool [projectConfigOnlyDeps] :: ProjectConfigBuildOnly -> Flag Bool [projectConfigOnlyDownload] :: ProjectConfigBuildOnly -> Flag Bool [projectConfigSummaryFile] :: ProjectConfigBuildOnly -> NubList PathTemplate [projectConfigLogFile] :: ProjectConfigBuildOnly -> Flag PathTemplate [projectConfigBuildReports] :: ProjectConfigBuildOnly -> Flag ReportLevel [projectConfigReportPlanningFailure] :: ProjectConfigBuildOnly -> Flag Bool [projectConfigSymlinkBinDir] :: ProjectConfigBuildOnly -> Flag FilePath [projectConfigNumJobs] :: ProjectConfigBuildOnly -> Flag (Maybe Int) [projectConfigKeepGoing] :: ProjectConfigBuildOnly -> Flag Bool [projectConfigOfflineMode] :: ProjectConfigBuildOnly -> Flag Bool [projectConfigKeepTempFiles] :: ProjectConfigBuildOnly -> Flag Bool [projectConfigHttpTransport] :: ProjectConfigBuildOnly -> Flag String [projectConfigIgnoreExpiry] :: ProjectConfigBuildOnly -> Flag Bool [projectConfigCacheDir] :: ProjectConfigBuildOnly -> Flag FilePath [projectConfigLogsDir] :: ProjectConfigBuildOnly -> Flag FilePath [projectConfigClientInstallFlags] :: ProjectConfigBuildOnly -> ClientInstallFlags -- | Project configuration that is shared between all packages in the -- project. In particular this includes configuration that affects the -- solver. data ProjectConfigShared ProjectConfigShared :: Flag FilePath -> Flag FilePath -> Flag FilePath -> Flag Bool -> Flag CompilerFlavor -> Flag FilePath -> Flag FilePath -> Flag PathTemplate -> InstallDirs (Flag PathTemplate) -> [Maybe PackageDB] -> NubList RemoteRepo -> NubList LocalRepo -> Flag ActiveRepos -> Flag TotalIndexState -> Flag FilePath -> [(UserConstraint, ConstraintSource)] -> [PackageVersionConstraint] -> Flag Version -> Flag PreSolver -> Maybe AllowOlder -> Maybe AllowNewer -> Flag WriteGhcEnvironmentFilesPolicy -> Flag Int -> Flag ReorderGoals -> Flag CountConflicts -> Flag FineGrainedConflicts -> Flag MinimizeConflictSet -> Flag StrongFlags -> Flag AllowBootLibInstalls -> Flag OnlyConstrained -> Flag Bool -> Flag IndependentGoals -> Flag PreferOldest -> NubList FilePath -> ProjectConfigShared [projectConfigDistDir] :: ProjectConfigShared -> Flag FilePath [projectConfigConfigFile] :: ProjectConfigShared -> Flag FilePath [projectConfigProjectFile] :: ProjectConfigShared -> Flag FilePath [projectConfigIgnoreProject] :: ProjectConfigShared -> Flag Bool [projectConfigHcFlavor] :: ProjectConfigShared -> Flag CompilerFlavor [projectConfigHcPath] :: ProjectConfigShared -> Flag FilePath [projectConfigHcPkg] :: ProjectConfigShared -> Flag FilePath [projectConfigHaddockIndex] :: ProjectConfigShared -> Flag PathTemplate [projectConfigInstallDirs] :: ProjectConfigShared -> InstallDirs (Flag PathTemplate) [projectConfigPackageDBs] :: ProjectConfigShared -> [Maybe PackageDB] -- | Available Hackage servers. [projectConfigRemoteRepos] :: ProjectConfigShared -> NubList RemoteRepo [projectConfigLocalNoIndexRepos] :: ProjectConfigShared -> NubList LocalRepo [projectConfigActiveRepos] :: ProjectConfigShared -> Flag ActiveRepos [projectConfigIndexState] :: ProjectConfigShared -> Flag TotalIndexState [projectConfigStoreDir] :: ProjectConfigShared -> Flag FilePath [projectConfigConstraints] :: ProjectConfigShared -> [(UserConstraint, ConstraintSource)] [projectConfigPreferences] :: ProjectConfigShared -> [PackageVersionConstraint] [projectConfigCabalVersion] :: ProjectConfigShared -> Flag Version [projectConfigSolver] :: ProjectConfigShared -> Flag PreSolver [projectConfigAllowOlder] :: ProjectConfigShared -> Maybe AllowOlder [projectConfigAllowNewer] :: ProjectConfigShared -> Maybe AllowNewer [projectConfigWriteGhcEnvironmentFilesPolicy] :: ProjectConfigShared -> Flag WriteGhcEnvironmentFilesPolicy [projectConfigMaxBackjumps] :: ProjectConfigShared -> Flag Int [projectConfigReorderGoals] :: ProjectConfigShared -> Flag ReorderGoals [projectConfigCountConflicts] :: ProjectConfigShared -> Flag CountConflicts [projectConfigFineGrainedConflicts] :: ProjectConfigShared -> Flag FineGrainedConflicts [projectConfigMinimizeConflictSet] :: ProjectConfigShared -> Flag MinimizeConflictSet [projectConfigStrongFlags] :: ProjectConfigShared -> Flag StrongFlags [projectConfigAllowBootLibInstalls] :: ProjectConfigShared -> Flag AllowBootLibInstalls [projectConfigOnlyConstrained] :: ProjectConfigShared -> Flag OnlyConstrained [projectConfigPerComponent] :: ProjectConfigShared -> Flag Bool [projectConfigIndependentGoals] :: ProjectConfigShared -> Flag IndependentGoals [projectConfigPreferOldest] :: ProjectConfigShared -> Flag PreferOldest [projectConfigProgPathExtra] :: ProjectConfigShared -> NubList FilePath -- | Specifies the provenance of project configuration, whether defaults -- were used or if the configuration was read from an explicit file path. data ProjectConfigProvenance -- | The configuration is implicit due to no explicit configuration being -- found. See readProjectConfig for how implicit configuration is -- determined. Implicit :: ProjectConfigProvenance -- | The path the project configuration was explicitly read from. | The -- configuration was explicitly read from the specified FilePath. Explicit :: FilePath -> ProjectConfigProvenance -- | Project configuration that is specific to each package, that is where -- we can in principle have different values for different packages in -- the same project. data PackageConfig PackageConfig :: MapLast String FilePath -> MapMappend String [String] -> NubList FilePath -> FlagAssignment -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag ProfDetailLevel -> Flag ProfDetailLevel -> [String] -> Flag OptimisationLevel -> Flag PathTemplate -> Flag PathTemplate -> [FilePath] -> [FilePath] -> [FilePath] -> [FilePath] -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag DebugInfoLevel -> Flag DumpBuildInfo -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag String -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag FilePath -> Flag Bool -> Flag Bool -> Flag FilePath -> Flag PathTemplate -> Flag PathTemplate -> Flag String -> Flag String -> Flag HaddockTarget -> Flag PathTemplate -> Flag PathTemplate -> Flag TestShowDetails -> Flag Bool -> Flag FilePath -> Flag Bool -> [PathTemplate] -> [PathTemplate] -> PackageConfig [packageConfigProgramPaths] :: PackageConfig -> MapLast String FilePath [packageConfigProgramArgs] :: PackageConfig -> MapMappend String [String] [packageConfigProgramPathExtra] :: PackageConfig -> NubList FilePath [packageConfigFlagAssignment] :: PackageConfig -> FlagAssignment [packageConfigVanillaLib] :: PackageConfig -> Flag Bool [packageConfigSharedLib] :: PackageConfig -> Flag Bool [packageConfigStaticLib] :: PackageConfig -> Flag Bool [packageConfigDynExe] :: PackageConfig -> Flag Bool [packageConfigFullyStaticExe] :: PackageConfig -> Flag Bool [packageConfigProf] :: PackageConfig -> Flag Bool [packageConfigProfLib] :: PackageConfig -> Flag Bool [packageConfigProfExe] :: PackageConfig -> Flag Bool [packageConfigProfDetail] :: PackageConfig -> Flag ProfDetailLevel [packageConfigProfLibDetail] :: PackageConfig -> Flag ProfDetailLevel [packageConfigConfigureArgs] :: PackageConfig -> [String] [packageConfigOptimization] :: PackageConfig -> Flag OptimisationLevel [packageConfigProgPrefix] :: PackageConfig -> Flag PathTemplate [packageConfigProgSuffix] :: PackageConfig -> Flag PathTemplate [packageConfigExtraLibDirs] :: PackageConfig -> [FilePath] [packageConfigExtraLibDirsStatic] :: PackageConfig -> [FilePath] [packageConfigExtraFrameworkDirs] :: PackageConfig -> [FilePath] [packageConfigExtraIncludeDirs] :: PackageConfig -> [FilePath] [packageConfigGHCiLib] :: PackageConfig -> Flag Bool [packageConfigSplitSections] :: PackageConfig -> Flag Bool [packageConfigSplitObjs] :: PackageConfig -> Flag Bool [packageConfigStripExes] :: PackageConfig -> Flag Bool [packageConfigStripLibs] :: PackageConfig -> Flag Bool [packageConfigTests] :: PackageConfig -> Flag Bool [packageConfigBenchmarks] :: PackageConfig -> Flag Bool [packageConfigCoverage] :: PackageConfig -> Flag Bool [packageConfigRelocatable] :: PackageConfig -> Flag Bool [packageConfigDebugInfo] :: PackageConfig -> Flag DebugInfoLevel [packageConfigDumpBuildInfo] :: PackageConfig -> Flag DumpBuildInfo [packageConfigRunTests] :: PackageConfig -> Flag Bool [packageConfigDocumentation] :: PackageConfig -> Flag Bool [packageConfigHaddockHoogle] :: PackageConfig -> Flag Bool [packageConfigHaddockHtml] :: PackageConfig -> Flag Bool [packageConfigHaddockHtmlLocation] :: PackageConfig -> Flag String [packageConfigHaddockForeignLibs] :: PackageConfig -> Flag Bool [packageConfigHaddockExecutables] :: PackageConfig -> Flag Bool [packageConfigHaddockTestSuites] :: PackageConfig -> Flag Bool [packageConfigHaddockBenchmarks] :: PackageConfig -> Flag Bool [packageConfigHaddockInternal] :: PackageConfig -> Flag Bool [packageConfigHaddockCss] :: PackageConfig -> Flag FilePath [packageConfigHaddockLinkedSource] :: PackageConfig -> Flag Bool [packageConfigHaddockQuickJump] :: PackageConfig -> Flag Bool [packageConfigHaddockHscolourCss] :: PackageConfig -> Flag FilePath [packageConfigHaddockContents] :: PackageConfig -> Flag PathTemplate [packageConfigHaddockIndex] :: PackageConfig -> Flag PathTemplate [packageConfigHaddockBaseUrl] :: PackageConfig -> Flag String [packageConfigHaddockLib] :: PackageConfig -> Flag String [packageConfigHaddockForHackage] :: PackageConfig -> Flag HaddockTarget [packageConfigTestHumanLog] :: PackageConfig -> Flag PathTemplate [packageConfigTestMachineLog] :: PackageConfig -> Flag PathTemplate [packageConfigTestShowDetails] :: PackageConfig -> Flag TestShowDetails [packageConfigTestKeepTix] :: PackageConfig -> Flag Bool [packageConfigTestWrapper] :: PackageConfig -> Flag FilePath [packageConfigTestFailWhenNoTestSuites] :: PackageConfig -> Flag Bool [packageConfigTestTestOptions] :: PackageConfig -> [PathTemplate] [packageConfigBenchmarkOptions] :: PackageConfig -> [PathTemplate] -- | Resolved configuration for the solver. The idea is that this is easier -- to use than the raw configuration because in the raw configuration -- everything is optional (monoidial). In the BuildTimeSettings -- every field is filled in, if only with the defaults. -- -- Use resolveSolverSettings to make one from the project config -- (by applying defaults etc). data SolverSettings SolverSettings :: [RemoteRepo] -> [LocalRepo] -> [(UserConstraint, ConstraintSource)] -> [PackageVersionConstraint] -> FlagAssignment -> Map PackageName FlagAssignment -> Maybe Version -> PreSolver -> AllowOlder -> AllowNewer -> Maybe Int -> ReorderGoals -> CountConflicts -> FineGrainedConflicts -> MinimizeConflictSet -> StrongFlags -> AllowBootLibInstalls -> OnlyConstrained -> Maybe TotalIndexState -> Maybe ActiveRepos -> IndependentGoals -> PreferOldest -> SolverSettings -- | Available Hackage servers. [solverSettingRemoteRepos] :: SolverSettings -> [RemoteRepo] [solverSettingLocalNoIndexRepos] :: SolverSettings -> [LocalRepo] [solverSettingConstraints] :: SolverSettings -> [(UserConstraint, ConstraintSource)] [solverSettingPreferences] :: SolverSettings -> [PackageVersionConstraint] -- | For all local packages [solverSettingFlagAssignment] :: SolverSettings -> FlagAssignment [solverSettingFlagAssignments] :: SolverSettings -> Map PackageName FlagAssignment [solverSettingCabalVersion] :: SolverSettings -> Maybe Version [solverSettingSolver] :: SolverSettings -> PreSolver [solverSettingAllowOlder] :: SolverSettings -> AllowOlder [solverSettingAllowNewer] :: SolverSettings -> AllowNewer [solverSettingMaxBackjumps] :: SolverSettings -> Maybe Int [solverSettingReorderGoals] :: SolverSettings -> ReorderGoals [solverSettingCountConflicts] :: SolverSettings -> CountConflicts [solverSettingFineGrainedConflicts] :: SolverSettings -> FineGrainedConflicts [solverSettingMinimizeConflictSet] :: SolverSettings -> MinimizeConflictSet [solverSettingStrongFlags] :: SolverSettings -> StrongFlags [solverSettingAllowBootLibInstalls] :: SolverSettings -> AllowBootLibInstalls [solverSettingOnlyConstrained] :: SolverSettings -> OnlyConstrained [solverSettingIndexState] :: SolverSettings -> Maybe TotalIndexState [solverSettingActiveRepos] :: SolverSettings -> Maybe ActiveRepos [solverSettingIndependentGoals] :: SolverSettings -> IndependentGoals [solverSettingPreferOldest] :: SolverSettings -> PreferOldest -- | Resolved configuration for things that affect how we build and not the -- value of the things we build. The idea is that this is easier to use -- than the raw configuration because in the raw configuration everything -- is optional (monoidial). In the BuildTimeSettings every field -- is filled in, if only with the defaults. -- -- Use resolveBuildTimeSettings to make one from the project -- config (by applying defaults etc). data BuildTimeSettings BuildTimeSettings :: Bool -> Bool -> Bool -> [PathTemplate] -> Maybe (Compiler -> Platform -> PackageId -> UnitId -> FilePath) -> Verbosity -> ReportLevel -> Bool -> [FilePath] -> Int -> Bool -> Bool -> Bool -> [RemoteRepo] -> [LocalRepo] -> FilePath -> Maybe String -> Bool -> [FilePath] -> Bool -> BuildTimeSettings [buildSettingDryRun] :: BuildTimeSettings -> Bool [buildSettingOnlyDeps] :: BuildTimeSettings -> Bool [buildSettingOnlyDownload] :: BuildTimeSettings -> Bool [buildSettingSummaryFile] :: BuildTimeSettings -> [PathTemplate] [buildSettingLogFile] :: BuildTimeSettings -> Maybe (Compiler -> Platform -> PackageId -> UnitId -> FilePath) [buildSettingLogVerbosity] :: BuildTimeSettings -> Verbosity [buildSettingBuildReports] :: BuildTimeSettings -> ReportLevel [buildSettingReportPlanningFailure] :: BuildTimeSettings -> Bool [buildSettingSymlinkBinDir] :: BuildTimeSettings -> [FilePath] [buildSettingNumJobs] :: BuildTimeSettings -> Int [buildSettingKeepGoing] :: BuildTimeSettings -> Bool [buildSettingOfflineMode] :: BuildTimeSettings -> Bool [buildSettingKeepTempFiles] :: BuildTimeSettings -> Bool [buildSettingRemoteRepos] :: BuildTimeSettings -> [RemoteRepo] [buildSettingLocalNoIndexRepos] :: BuildTimeSettings -> [LocalRepo] [buildSettingCacheDir] :: BuildTimeSettings -> FilePath [buildSettingHttpTransport] :: BuildTimeSettings -> Maybe String [buildSettingIgnoreExpiry] :: BuildTimeSettings -> Bool [buildSettingProgPathExtra] :: BuildTimeSettings -> [FilePath] [buildSettingHaddockOpen] :: BuildTimeSettings -> Bool -- | Newtype wrapper for Map that provides a Monoid instance -- that takes the last value rather than the first value for overlapping -- keys. newtype MapLast k v MapLast :: Map k v -> MapLast k v [getMapLast] :: MapLast k v -> Map k v -- | Newtype wrapper for Map that provides a Monoid instance -- that mappends values of overlapping keys rather than taking the -- first. newtype MapMappend k v MapMappend :: Map k v -> MapMappend k v [getMapMappend] :: MapMappend k v -> Map k v instance GHC.Generics.Generic Distribution.Client.ProjectConfig.Types.ProjectConfigBuildOnly instance GHC.Show.Show Distribution.Client.ProjectConfig.Types.ProjectConfigBuildOnly instance GHC.Classes.Eq Distribution.Client.ProjectConfig.Types.ProjectConfigBuildOnly instance GHC.Generics.Generic Distribution.Client.ProjectConfig.Types.ProjectConfigShared instance GHC.Show.Show Distribution.Client.ProjectConfig.Types.ProjectConfigShared instance GHC.Classes.Eq Distribution.Client.ProjectConfig.Types.ProjectConfigShared instance GHC.Generics.Generic Distribution.Client.ProjectConfig.Types.ProjectConfigProvenance instance GHC.Show.Show Distribution.Client.ProjectConfig.Types.ProjectConfigProvenance instance GHC.Classes.Ord Distribution.Client.ProjectConfig.Types.ProjectConfigProvenance instance GHC.Classes.Eq Distribution.Client.ProjectConfig.Types.ProjectConfigProvenance instance (Data.Binary.Class.Binary k, Data.Binary.Class.Binary v) => Data.Binary.Class.Binary (Distribution.Client.ProjectConfig.Types.MapLast k v) instance GHC.Generics.Generic (Distribution.Client.ProjectConfig.Types.MapLast k v) instance GHC.Base.Functor (Distribution.Client.ProjectConfig.Types.MapLast k) instance (GHC.Show.Show k, GHC.Show.Show v) => GHC.Show.Show (Distribution.Client.ProjectConfig.Types.MapLast k v) instance (GHC.Classes.Eq k, GHC.Classes.Eq v) => GHC.Classes.Eq (Distribution.Client.ProjectConfig.Types.MapLast k v) instance (Data.Binary.Class.Binary k, Data.Binary.Class.Binary v) => Data.Binary.Class.Binary (Distribution.Client.ProjectConfig.Types.MapMappend k v) instance GHC.Generics.Generic (Distribution.Client.ProjectConfig.Types.MapMappend k v) instance GHC.Base.Functor (Distribution.Client.ProjectConfig.Types.MapMappend k) instance (GHC.Show.Show k, GHC.Show.Show v) => GHC.Show.Show (Distribution.Client.ProjectConfig.Types.MapMappend k v) instance (GHC.Classes.Eq k, GHC.Classes.Eq v) => GHC.Classes.Eq (Distribution.Client.ProjectConfig.Types.MapMappend k v) instance GHC.Generics.Generic Distribution.Client.ProjectConfig.Types.PackageConfig instance GHC.Show.Show Distribution.Client.ProjectConfig.Types.PackageConfig instance GHC.Classes.Eq Distribution.Client.ProjectConfig.Types.PackageConfig instance GHC.Generics.Generic Distribution.Client.ProjectConfig.Types.ProjectConfig instance GHC.Show.Show Distribution.Client.ProjectConfig.Types.ProjectConfig instance GHC.Classes.Eq Distribution.Client.ProjectConfig.Types.ProjectConfig instance GHC.Generics.Generic Distribution.Client.ProjectConfig.Types.SolverSettings instance GHC.Show.Show Distribution.Client.ProjectConfig.Types.SolverSettings instance GHC.Classes.Eq Distribution.Client.ProjectConfig.Types.SolverSettings instance Data.Binary.Class.Binary Distribution.Client.ProjectConfig.Types.SolverSettings instance Distribution.Utils.Structured.Structured Distribution.Client.ProjectConfig.Types.SolverSettings instance Data.Binary.Class.Binary Distribution.Client.ProjectConfig.Types.ProjectConfig instance Distribution.Utils.Structured.Structured Distribution.Client.ProjectConfig.Types.ProjectConfig instance GHC.Base.Monoid Distribution.Client.ProjectConfig.Types.ProjectConfig instance GHC.Base.Semigroup Distribution.Client.ProjectConfig.Types.ProjectConfig instance Data.Binary.Class.Binary Distribution.Client.ProjectConfig.Types.PackageConfig instance Distribution.Utils.Structured.Structured Distribution.Client.ProjectConfig.Types.PackageConfig instance GHC.Base.Monoid Distribution.Client.ProjectConfig.Types.PackageConfig instance GHC.Base.Semigroup Distribution.Client.ProjectConfig.Types.PackageConfig instance (Distribution.Utils.Structured.Structured k, Distribution.Utils.Structured.Structured v) => Distribution.Utils.Structured.Structured (Distribution.Client.ProjectConfig.Types.MapMappend k v) instance (GHC.Base.Semigroup v, GHC.Classes.Ord k) => GHC.Base.Monoid (Distribution.Client.ProjectConfig.Types.MapMappend k v) instance (GHC.Base.Semigroup v, GHC.Classes.Ord k) => GHC.Base.Semigroup (Distribution.Client.ProjectConfig.Types.MapMappend k v) instance (Distribution.Utils.Structured.Structured k, Distribution.Utils.Structured.Structured v) => Distribution.Utils.Structured.Structured (Distribution.Client.ProjectConfig.Types.MapLast k v) instance GHC.Classes.Ord k => GHC.Base.Monoid (Distribution.Client.ProjectConfig.Types.MapLast k v) instance GHC.Classes.Ord k => GHC.Base.Semigroup (Distribution.Client.ProjectConfig.Types.MapLast k v) instance Data.Binary.Class.Binary Distribution.Client.ProjectConfig.Types.ProjectConfigProvenance instance Distribution.Utils.Structured.Structured Distribution.Client.ProjectConfig.Types.ProjectConfigProvenance instance Data.Binary.Class.Binary Distribution.Client.ProjectConfig.Types.ProjectConfigShared instance Distribution.Utils.Structured.Structured Distribution.Client.ProjectConfig.Types.ProjectConfigShared instance GHC.Base.Monoid Distribution.Client.ProjectConfig.Types.ProjectConfigShared instance GHC.Base.Semigroup Distribution.Client.ProjectConfig.Types.ProjectConfigShared instance Data.Binary.Class.Binary Distribution.Client.ProjectConfig.Types.ProjectConfigBuildOnly instance Distribution.Utils.Structured.Structured Distribution.Client.ProjectConfig.Types.ProjectConfigBuildOnly instance GHC.Base.Monoid Distribution.Client.ProjectConfig.Types.ProjectConfigBuildOnly instance GHC.Base.Semigroup Distribution.Client.ProjectConfig.Types.ProjectConfigBuildOnly -- | Search for and print information about packages module Distribution.Client.List -- | Show information about packages. list :: Verbosity -> PackageDBStack -> RepoContext -> Maybe (Compiler, ProgramDb) -> ListFlags -> [String] -> IO () info :: Verbosity -> PackageDBStack -> RepoContext -> Compiler -> ProgramDb -> GlobalFlags -> InfoFlags -> [UserTarget] -> IO () -- | The 'cabal get' command. module Distribution.Client.Get -- | Entry point for the 'cabal get' command. get :: Verbosity -> RepoContext -> GlobalFlags -> GetFlags -> [UserTarget] -> IO () -- | Given a bunch of package ids and their corresponding available -- SourceRepos, pick a single SourceRepo for each one -- and clone into new subdirs of the given directory. clonePackagesFromSourceRepo :: Verbosity -> FilePath -> Maybe RepoKind -> [(PackageId, [SourceRepo])] -> IO () data ClonePackageException ClonePackageNoSourceRepos :: PackageId -> ClonePackageException ClonePackageNoSourceReposOfKind :: PackageId -> Maybe RepoKind -> ClonePackageException ClonePackageNoRepoType :: PackageId -> SourceRepo -> ClonePackageException ClonePackageUnsupportedRepoType :: PackageId -> SourceRepoProxy -> RepoType -> ClonePackageException ClonePackageNoRepoLocation :: PackageId -> SourceRepo -> ClonePackageException ClonePackageDestinationExists :: PackageId -> FilePath -> Bool -> ClonePackageException ClonePackageFailedWithExitCode :: PackageId -> SourceRepoProxy -> String -> ExitCode -> ClonePackageException instance GHC.Classes.Eq Distribution.Client.Get.ClonePackageException instance GHC.Show.Show Distribution.Client.Get.ClonePackageException instance GHC.Exception.Type.Exception Distribution.Client.Get.ClonePackageException module Distribution.Client.Fetch -- | Fetch a list of packages and their dependencies. fetch :: Verbosity -> PackageDBStack -> RepoContext -> Compiler -> Platform -> ProgramDb -> GlobalFlags -> FetchFlags -> [UserTarget] -> IO () -- | Anonymous build report data structure, printing and parsing module Distribution.Client.BuildReports.Anonymous data BuildReport BuildReport :: PackageIdentifier -> OS -> Arch -> CompilerId -> PackageIdentifier -> FlagAssignment -> [PackageIdentifier] -> InstallOutcome -> Outcome -> Outcome -> BuildReport -- | The package this build report is about [package] :: BuildReport -> PackageIdentifier -- | The OS and Arch the package was built on [os] :: BuildReport -> OS [arch] :: BuildReport -> Arch -- | The Haskell compiler (and hopefully version) used [compiler] :: BuildReport -> CompilerId -- | The uploading client, ie cabal-install-x.y.z [client] :: BuildReport -> PackageIdentifier -- | Which configurations flags we used [flagAssignment] :: BuildReport -> FlagAssignment -- | Which dependent packages we were using exactly [dependencies] :: BuildReport -> [PackageIdentifier] -- | Did installing work ok? [installOutcome] :: BuildReport -> InstallOutcome -- | Configure outcome, did configure work ok? [docsOutcome] :: BuildReport -> Outcome -- | Configure outcome, did configure work ok? [testsOutcome] :: BuildReport -> Outcome data InstallOutcome PlanningFailed :: InstallOutcome DependencyFailed :: PackageIdentifier -> InstallOutcome DownloadFailed :: InstallOutcome UnpackFailed :: InstallOutcome SetupFailed :: InstallOutcome ConfigureFailed :: InstallOutcome BuildFailed :: InstallOutcome TestsFailed :: InstallOutcome InstallFailed :: InstallOutcome InstallOk :: InstallOutcome data Outcome NotTried :: Outcome Failed :: Outcome Ok :: Outcome newBuildReport :: OS -> Arch -> CompilerId -> PackageIdentifier -> FlagAssignment -> [PackageIdentifier] -> BuildOutcome -> BuildReport parseBuildReport :: ByteString -> Either String BuildReport parseBuildReportList :: ByteString -> [BuildReport] showBuildReport :: BuildReport -> String cabalInstallID :: PackageIdentifier module Distribution.Client.BuildReports.Upload type BuildLog = String type BuildReportId = URI uploadReports :: Verbosity -> RepoContext -> (String, String) -> URI -> [(BuildReport, Maybe BuildLog)] -> IO () -- | Anonymous build report data structure, printing and parsing module Distribution.Client.BuildReports.Storage storeAnonymous :: [(BuildReport, Maybe Repo)] -> IO () storeLocal :: CompilerInfo -> [PathTemplate] -> [(BuildReport, Maybe Repo)] -> Platform -> IO () fromInstallPlan :: Platform -> CompilerId -> InstallPlan -> BuildOutcomes -> [(BuildReport, Maybe Repo)] fromPlanningFailure :: Platform -> CompilerId -> [PackageId] -> FlagAssignment -> [(BuildReport, Maybe Repo)] -- | Support for self-upgrading executables on Windows platforms. module Distribution.Client.Win32SelfUpgrade possibleSelfUpgrade :: Verbosity -> [FilePath] -> IO a -> IO a deleteOldExeFile :: Verbosity -> Int -> FilePath -> IO () -- | This is a library of parser combinators, originally written by Koen -- Claessen. It parses all alternatives in parallel, so it never keeps -- hold of the beginning of the input string, a common source of space -- leaks with other parsers. The (+++) choice combinator is -- genuinely commutative; it makes no difference which branch is -- "shorter". -- -- See also Koen's paper Parallel Parsing Processes -- (http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.19.9217). -- -- This version of ReadP has been locally hacked to make it H98, by -- Martin Sjögren mailto:msjogren@gmail.com -- -- The unit tests have been moved to -- UnitTest.Distribution.Deprecated.ReadP, by Mark Lentczner -- mailto:mark@glyphic.com module Distribution.Deprecated.ReadP type ReadP r a = Parser r Char a -- | Consumes and returns the next character. Fails if there is no input -- left. get :: ReadP r Char -- | Look-ahead: returns the part of the input that is left, without -- consuming it. look :: ReadP r String -- | Symmetric choice. (+++) :: ReadP r a -> ReadP r a -> ReadP r a infixr 5 +++ -- | Local, exclusive, left-biased choice: If left parser locally produces -- any result at all, then right parser is not used. (<++) :: ReadP a a -> ReadP r a -> ReadP r a infixr 5 <++ -- | Transforms a parser into one that does the same, but in addition -- returns the exact characters read. IMPORTANT NOTE: gather gives -- a runtime error if its first argument is built using any occurrences -- of readS_to_P. gather :: ReadP (String -> P Char r) a -> ReadP r (String, a) -- | Always fails. pfail :: ReadP r a -- | Succeeds iff we are at the end of input eof :: ReadP r () -- | Consumes and returns the next character, if it satisfies the specified -- predicate. satisfy :: (Char -> Bool) -> ReadP r Char -- | Parses and returns the specified character. char :: Char -> ReadP r Char -- | Parses and returns the specified string. string :: String -> ReadP r String -- | Parses the first zero or more characters satisfying the predicate. munch :: (Char -> Bool) -> ReadP r String -- | Parses the first one or more characters satisfying the predicate. munch1 :: (Char -> Bool) -> ReadP r String -- | Skips all whitespace. skipSpaces :: ReadP r () -- | Like skipSpaces but succeeds only if there is at least one -- whitespace character to skip. skipSpaces1 :: ReadP r () -- | Combines all parsers in the specified list. choice :: [ReadP r a] -> ReadP r a -- | count n p parses n occurrences of p in -- sequence. A list of results is returned. count :: Int -> ReadP r a -> ReadP r [a] -- | between open close p parses open, followed by -- p and finally close. Only the value of p is -- returned. between :: ReadP r open -> ReadP r close -> ReadP r a -> ReadP r a -- | option x p will either parse p or return x -- without consuming any input. option :: a -> ReadP r a -> ReadP r a -- | optional p optionally parses p and always returns -- (). optional :: ReadP r a -> ReadP r () -- | Parses zero or more occurrences of the given parser. many :: ReadP r a -> ReadP r [a] -- | Parses one or more occurrences of the given parser. many1 :: ReadP r a -> ReadP r [a] -- | Like many, but discards the result. skipMany :: ReadP r a -> ReadP r () -- | Like many1, but discards the result. skipMany1 :: ReadP r a -> ReadP r () -- | sepBy p sep parses zero or more occurrences of p, -- separated by sep. Returns a list of values returned by -- p. sepBy :: ReadP r a -> ReadP r sep -> ReadP r [a] -- | sepBy1 p sep parses one or more occurrences of p, -- separated by sep. Returns a list of values returned by -- p. sepBy1 :: ReadP r a -> ReadP r sep -> ReadP r [a] -- | endBy p sep parses zero or more occurrences of p, -- separated and ended by sep. endBy :: ReadP r a -> ReadP r sep -> ReadP r [a] -- | endBy p sep parses one or more occurrences of p, -- separated and ended by sep. endBy1 :: ReadP r a -> ReadP r sep -> ReadP r [a] -- | chainr p op x parses zero or more occurrences of p, -- separated by op. Returns a value produced by a right -- associative application of all functions returned by op. If -- there are no occurrences of p, x is returned. chainr :: ReadP r a -> ReadP r (a -> a -> a) -> a -> ReadP r a -- | chainl p op x parses zero or more occurrences of p, -- separated by op. Returns a value produced by a left -- associative application of all functions returned by op. If -- there are no occurrences of p, x is returned. chainl :: ReadP r a -> ReadP r (a -> a -> a) -> a -> ReadP r a -- | Like chainl, but parses one or more occurrences of p. chainl1 :: ReadP r a -> ReadP r (a -> a -> a) -> ReadP r a -- | Like chainr, but parses one or more occurrences of p. chainr1 :: ReadP r a -> ReadP r (a -> a -> a) -> ReadP r a -- | manyTill p end parses zero or more occurrences of p, -- until end succeeds. Returns a list of values returned by -- p. manyTill :: ReadP r a -> ReadP [a] end -> ReadP r [a] -- | A parser for a type a, represented as a function that takes a -- String and returns a list of possible parses as -- (a,String) pairs. -- -- Note that this kind of backtracking parser is very inefficient; -- reading a large structure may be quite slow (cf ReadP). type ReadS a = String -> [(a, String)] -- | Converts a parser into a Haskell ReadS-style function. This is the -- main way in which you can "run" a ReadP parser: the expanded -- type is readP_to_S :: ReadP a -> String -> [(a,String)] -- readP_to_S :: ReadP a a -> ReadS a -- | Converts a Haskell ReadS-style function into a parser. Warning: This -- introduces local backtracking in the resulting parser, and therefore a -- possible inefficiency. readS_to_P :: ReadS a -> ReadP r a readP_to_E :: (String -> String) -> ReadP a a -> ReadE a data Parser r s a instance GHC.Base.Functor (Distribution.Deprecated.ReadP.Parser r s) instance GHC.Base.Applicative (Distribution.Deprecated.ReadP.Parser r s) instance (s GHC.Types.~ GHC.Types.Char) => GHC.Base.Alternative (Distribution.Deprecated.ReadP.Parser r s) instance GHC.Base.Monad (Distribution.Deprecated.ReadP.Parser r s) instance Control.Monad.Fail.MonadFail (Distribution.Deprecated.ReadP.Parser r s) instance (s GHC.Types.~ GHC.Types.Char) => GHC.Base.MonadPlus (Distribution.Deprecated.ReadP.Parser r s) instance GHC.Base.Functor (Distribution.Deprecated.ReadP.P s) instance GHC.Base.Applicative (Distribution.Deprecated.ReadP.P s) instance GHC.Base.Monad (Distribution.Deprecated.ReadP.P s) instance Control.Monad.Fail.MonadFail (Distribution.Deprecated.ReadP.P s) instance GHC.Base.Alternative (Distribution.Deprecated.ReadP.P s) instance GHC.Base.MonadPlus (Distribution.Deprecated.ReadP.P s) -- | Handling for user-specified target selectors. module Distribution.Client.TargetSelector -- | A target selector is expression selecting a set of components (as -- targets for a actions like build, run, test -- etc). A target selector corresponds to the user syntax for referring -- to targets on the command line. -- -- From the users point of view a target can be many things: packages, -- dirs, component names, files etc. Internally we consider a target to -- be a specific component (or module/file within a component), and all -- the users' notions of targets are just different ways of referring to -- these component targets. -- -- So target selectors are expressions in the sense that they are -- interpreted to refer to one or more components. For example a -- TargetPackage gets interpreted differently by different -- commands to refer to all or a subset of components within the package. -- -- The syntax has lots of optional parts: -- --
--   [ package name | package dir | package .cabal file ]
--   [ [lib:|exe:] component name ]
--   [ module name | source file ]
--   
data TargetSelector -- | One (or more) packages as a whole, or all the components of a -- particular kind within the package(s). -- -- These are always packages that are local to the project. In the case -- that there is more than one, they all share the same directory -- location. TargetPackage :: TargetImplicitCwd -> [PackageId] -> Maybe ComponentKindFilter -> TargetSelector -- | A package specified by name. This may refer to extra-packages -- from the cabal.project file, or a dependency of a known -- project package or could refer to a package from a hackage archive. It -- needs further context to resolve to a specific package. TargetPackageNamed :: PackageName -> Maybe ComponentKindFilter -> TargetSelector -- | All packages, or all components of a particular kind in all packages. TargetAllPackages :: Maybe ComponentKindFilter -> TargetSelector -- | A specific component in a package within the project. TargetComponent :: PackageId -> ComponentName -> SubComponentTarget -> TargetSelector -- | A component in a package, but where it cannot be verified that the -- package has such a component, or because the package is itself not -- known. TargetComponentUnknown :: PackageName -> Either UnqualComponentName ComponentName -> SubComponentTarget -> TargetSelector -- | Does this TargetPackage selector arise from syntax referring to -- a package in the current directory (e.g. tests or no giving -- no explicit target at all) or does it come from syntax referring to a -- package name or location. data TargetImplicitCwd TargetImplicitCwd :: TargetImplicitCwd TargetExplicitNamed :: TargetImplicitCwd data ComponentKind LibKind :: ComponentKind FLibKind :: ComponentKind ExeKind :: ComponentKind TestKind :: ComponentKind BenchKind :: ComponentKind type ComponentKindFilter = ComponentKind -- | Either the component as a whole or detail about a file or module -- target within a component. data SubComponentTarget -- | The component as a whole WholeComponent :: SubComponentTarget -- | A specific module within a component. ModuleTarget :: ModuleName -> SubComponentTarget -- | A specific file within a component. Note that this does not carry the -- file extension. FileTarget :: FilePath -> SubComponentTarget -- | Qualification levels. Given the filepath src/F, executable component -- A, and package foo: data QualLevel -- |
--   src/F
--   
QL1 :: QualLevel -- |
--   foo:srcF | A:srcF
--   
QL2 :: QualLevel -- |
--   foo:A:srcF | exe:A:srcF
--   
QL3 :: QualLevel -- |
--   pkg:foo:exe:A:file:src/F
--   
QLFull :: QualLevel componentKind :: ComponentName -> ComponentKind -- | Parse a bunch of command line args as TargetSelectors, failing -- with an error if any are unrecognised. The possible target selectors -- are based on the available packages (and their locations). readTargetSelectors :: [PackageSpecifier (SourcePackage (PackageLocation a))] -> Maybe ComponentKindFilter -> [String] -> IO (Either [TargetSelectorProblem] [TargetSelector]) -- | The various ways that trying to resolve a TargetString to a -- TargetSelector can fail. data TargetSelectorProblem -- | TargetSelectorExpected :: TargetString -> [String] -> String -> TargetSelectorProblem -- | TargetSelectorNoSuch :: TargetString -> [(Maybe (String, String), String, String, [String])] -> TargetSelectorProblem TargetSelectorAmbiguous :: TargetString -> [(TargetString, TargetSelector)] -> TargetSelectorProblem MatchingInternalError :: TargetString -> TargetSelector -> [(TargetString, [TargetSelector])] -> TargetSelectorProblem -- | Syntax error when trying to parse a target string. TargetSelectorUnrecognised :: String -> TargetSelectorProblem TargetSelectorNoCurrentPackage :: TargetString -> TargetSelectorProblem -- | bool that flags when it is acceptable to suggest "all" as a target TargetSelectorNoTargetsInCwd :: Bool -> TargetSelectorProblem TargetSelectorNoTargetsInProject :: TargetSelectorProblem TargetSelectorNoScript :: TargetString -> TargetSelectorProblem -- | Throw an exception with a formatted message if there are any problems. reportTargetSelectorProblems :: Verbosity -> [TargetSelectorProblem] -> IO a showTargetSelector :: TargetSelector -> String -- | The outline parse of a target selector. It takes one of the forms: -- --
--   str1
--   str1:str2
--   str1:str2:str3
--   str1:str2:str3:str4
--   
data TargetString TargetString1 :: String -> TargetString TargetString2 :: String -> String -> TargetString TargetString3 :: String -> String -> String -> TargetString TargetString4 :: String -> String -> String -> String -> TargetString TargetString5 :: String -> String -> String -> String -> String -> TargetString TargetString7 :: String -> String -> String -> String -> String -> String -> String -> TargetString -- | Render a TargetString back as the external syntax. This is -- mainly for error messages. showTargetString :: TargetString -> String parseTargetString :: String -> Maybe TargetString readTargetSelectorsWith :: (Applicative m, Monad m) => DirActions m -> [PackageSpecifier (SourcePackage (PackageLocation a))] -> Maybe ComponentKindFilter -> [String] -> m (Either [TargetSelectorProblem] [TargetSelector]) data DirActions m DirActions :: (FilePath -> m Bool) -> (FilePath -> m Bool) -> (FilePath -> m FilePath) -> m FilePath -> DirActions m [doesFileExist] :: DirActions m -> FilePath -> m Bool [doesDirectoryExist] :: DirActions m -> FilePath -> m Bool [canonicalizePath] :: DirActions m -> FilePath -> m FilePath [getCurrentDirectory] :: DirActions m -> m FilePath defaultDirActions :: DirActions IO instance GHC.Generics.Generic Distribution.Client.TargetSelector.TargetImplicitCwd instance GHC.Show.Show Distribution.Client.TargetSelector.TargetImplicitCwd instance GHC.Classes.Ord Distribution.Client.TargetSelector.TargetImplicitCwd instance GHC.Classes.Eq Distribution.Client.TargetSelector.TargetImplicitCwd instance GHC.Show.Show Distribution.Client.TargetSelector.ComponentKind instance GHC.Enum.Enum Distribution.Client.TargetSelector.ComponentKind instance GHC.Classes.Ord Distribution.Client.TargetSelector.ComponentKind instance GHC.Classes.Eq Distribution.Client.TargetSelector.ComponentKind instance GHC.Generics.Generic Distribution.Client.TargetSelector.SubComponentTarget instance GHC.Show.Show Distribution.Client.TargetSelector.SubComponentTarget instance GHC.Classes.Ord Distribution.Client.TargetSelector.SubComponentTarget instance GHC.Classes.Eq Distribution.Client.TargetSelector.SubComponentTarget instance GHC.Generics.Generic Distribution.Client.TargetSelector.TargetSelector instance GHC.Show.Show Distribution.Client.TargetSelector.TargetSelector instance GHC.Classes.Ord Distribution.Client.TargetSelector.TargetSelector instance GHC.Classes.Eq Distribution.Client.TargetSelector.TargetSelector instance GHC.Classes.Eq Distribution.Client.TargetSelector.TargetString instance GHC.Show.Show Distribution.Client.TargetSelector.TargetString instance GHC.Show.Show Distribution.Client.TargetSelector.FileStatus instance GHC.Classes.Ord Distribution.Client.TargetSelector.FileStatus instance GHC.Classes.Eq Distribution.Client.TargetSelector.FileStatus instance GHC.Show.Show Distribution.Client.TargetSelector.TargetStringFileStatus instance GHC.Classes.Ord Distribution.Client.TargetSelector.TargetStringFileStatus instance GHC.Classes.Eq Distribution.Client.TargetSelector.TargetStringFileStatus instance GHC.Classes.Eq Distribution.Client.TargetSelector.TargetSelectorProblem instance GHC.Show.Show Distribution.Client.TargetSelector.TargetSelectorProblem instance GHC.Show.Show Distribution.Client.TargetSelector.QualLevel instance GHC.Enum.Enum Distribution.Client.TargetSelector.QualLevel instance GHC.Classes.Eq Distribution.Client.TargetSelector.QualLevel instance GHC.Show.Show Distribution.Client.TargetSelector.KnownComponent instance GHC.Show.Show Distribution.Client.TargetSelector.KnownPackage instance GHC.Show.Show Distribution.Client.TargetSelector.KnownTargets instance GHC.Classes.Ord Distribution.Client.TargetSelector.MatchClass instance GHC.Classes.Eq Distribution.Client.TargetSelector.MatchClass instance GHC.Show.Show Distribution.Client.TargetSelector.MatchClass instance GHC.Classes.Eq Distribution.Client.TargetSelector.MatchError instance GHC.Show.Show Distribution.Client.TargetSelector.MatchError instance GHC.Show.Show a => GHC.Show.Show (Distribution.Client.TargetSelector.Match a) instance GHC.Show.Show a => GHC.Show.Show (Distribution.Client.TargetSelector.MaybeAmbiguous a) instance GHC.Base.Functor Distribution.Client.TargetSelector.Match instance GHC.Base.Applicative Distribution.Client.TargetSelector.Match instance GHC.Base.Alternative Distribution.Client.TargetSelector.Match instance GHC.Base.Monad Distribution.Client.TargetSelector.Match instance GHC.Base.MonadPlus Distribution.Client.TargetSelector.Match instance Data.Binary.Class.Binary Distribution.Client.TargetSelector.SubComponentTarget instance Distribution.Utils.Structured.Structured Distribution.Client.TargetSelector.SubComponentTarget module Distribution.Client.CmdInstall.ClientInstallTargetSelector data WithoutProjectTargetSelector WoPackageId :: PackageId -> WithoutProjectTargetSelector WoPackageComponent :: PackageId -> ComponentName -> WithoutProjectTargetSelector WoURI :: URI -> WithoutProjectTargetSelector parseWithoutProjectTargetSelector :: Verbosity -> String -> IO WithoutProjectTargetSelector woPackageNames :: WithoutProjectTargetSelector -> [PackageName] woPackageTargets :: WithoutProjectTargetSelector -> TargetSelector woPackageSpecifiers :: WithoutProjectTargetSelector -> Either URI (PackageSpecifier pkg) instance GHC.Show.Show Distribution.Client.CmdInstall.ClientInstallTargetSelector.WithoutProjectTargetSelector module Distribution.Deprecated.ViewAsFieldDescr -- | to view as a FieldDescr, we sort the list of interfaces (Req > Bool -- > Choice > Opt) and consider only the first one. viewAsFieldDescr :: OptionField a -> FieldDescr a -- | Parsing utilities. module Distribution.Client.ParseUtils -- | Field descriptor. The parameter a parameterizes over where -- the field's value is stored in. data FieldDescr a FieldDescr :: String -> (a -> Doc) -> (LineNo -> String -> a -> ParseResult a) -> FieldDescr a [fieldName] :: FieldDescr a -> String [fieldGet] :: FieldDescr a -> a -> Doc -- | fieldSet n str x Parses the field value from the given input -- string str and stores the result in x if the parse -- was successful. Otherwise, reports an error on line number n. [fieldSet] :: FieldDescr a -> LineNo -> String -> a -> ParseResult a liftField :: (b -> a) -> (a -> b -> b) -> FieldDescr a -> FieldDescr b liftFields :: (b -> a) -> (a -> b -> b) -> [FieldDescr a] -> [FieldDescr b] -- | Given a collection of field descriptions, keep only a given list of -- them, identified by name. filterFields :: [String] -> [FieldDescr a] -> [FieldDescr a] -- | Apply a name mangling function to the field names of all the field -- descriptions. The typical use case is to apply some prefix. mapFieldNames :: (String -> String) -> [FieldDescr a] -> [FieldDescr a] -- | Reuse a command line OptionField as a config file -- FieldDescr. commandOptionToField :: OptionField a -> FieldDescr a -- | Reuse a bunch of command line OptionFields as config file -- FieldDescrs. commandOptionsToFields :: [OptionField a] -> [FieldDescr a] -- | The description of a section in a config file. It can contain both -- fields and optionally further subsections. See also FieldDescr. data SectionDescr a SectionDescr :: String -> [FieldDescr b] -> [SectionDescr b] -> (a -> [(String, b)]) -> (LineNo -> String -> b -> a -> ParseResult a) -> b -> SectionDescr a [sectionName] :: SectionDescr a -> String [sectionFields] :: SectionDescr a -> [FieldDescr b] [sectionSubsections] :: SectionDescr a -> [SectionDescr b] [sectionGet] :: SectionDescr a -> a -> [(String, b)] [sectionSet] :: SectionDescr a -> LineNo -> String -> b -> a -> ParseResult a [sectionEmpty] :: SectionDescr a -> b -- | To help construction of config file descriptions in a modular way it -- is useful to define fields and sections on local types and then hoist -- them into the parent types when combining them in bigger descriptions. -- -- This is essentially a lens operation for SectionDescr to help -- embedding one inside another. liftSection :: (b -> a) -> (a -> b -> b) -> SectionDescr a -> SectionDescr b -- | FieldGrammar section description data FGSectionDescr g a FGSectionDescr :: String -> g s s -> (a -> [(String, s)]) -> (LineNo -> String -> s -> a -> ParseResult a) -> FGSectionDescr g a [fgSectionName] :: FGSectionDescr g a -> String [fgSectionGrammar] :: FGSectionDescr g a -> g s s [fgSectionGet] :: FGSectionDescr g a -> a -> [(String, s)] [fgSectionSet] :: FGSectionDescr g a -> LineNo -> String -> s -> a -> ParseResult a -- | Parse a bunch of semi-parsed Fields according to a set of field -- descriptions. It accumulates the result on top of a given initial -- value. -- -- This only covers the case of flat configuration without subsections. -- See also parseFieldsAndSections. parseFields :: [FieldDescr a] -> a -> [Field] -> ParseResult a -- | This is a customised version of the functions from -- Distribution.Deprecated.ParseUtils that also optionally print default -- values for empty fields as comments. ppFields :: [FieldDescr a] -> Maybe a -> a -> Doc -- | Pretty print a section. -- -- Since ppFields does not cover subsections you can use this to -- add them. Or alternatively use a SectionDescr and use -- ppFieldsAndSections. ppSection :: String -> String -> [FieldDescr a] -> Maybe a -> a -> Doc -- | Much like parseFields but it also allows subsections. The -- permitted subsections are given by a list of SectionDescrs. parseFieldsAndSections :: [FieldDescr a] -> [SectionDescr a] -> [FGSectionDescr ParsecFieldGrammar a] -> a -> [Field] -> ParseResult a -- | Much like ppFields but also pretty prints any subsections. -- Subsection are only shown if they are non-empty. -- -- Note that unlike ppFields, at present it does not support -- printing default values. If needed, adding such support would be quite -- reasonable. ppFieldsAndSections :: [FieldDescr a] -> [SectionDescr a] -> [FGSectionDescr PrettyFieldGrammar a] -> a -> Doc -- | Parse a string in the config file syntax into a value, based on a -- description of the configuration file in terms of its fields and -- sections. -- -- It accumulates the result on top of a given initial (typically empty) -- value. parseConfig :: [FieldDescr a] -> [SectionDescr a] -> [FGSectionDescr ParsecFieldGrammar a] -> a -> ByteString -> ParseResult a -- | Render a value in the config file syntax, based on a description of -- the configuration file in terms of its fields and sections. showConfig :: [FieldDescr a] -> [SectionDescr a] -> [FGSectionDescr PrettyFieldGrammar a] -> a -> Doc -- | Utilities for handling saved state such as known packages, known -- servers and downloaded packages. module Distribution.Client.Config data SavedConfig SavedConfig :: GlobalFlags -> InitFlags -> InstallFlags -> ClientInstallFlags -> ConfigFlags -> ConfigExFlags -> InstallDirs (Flag PathTemplate) -> InstallDirs (Flag PathTemplate) -> UploadFlags -> ReportFlags -> HaddockFlags -> TestFlags -> BenchmarkFlags -> ProjectFlags -> SavedConfig [savedGlobalFlags] :: SavedConfig -> GlobalFlags [savedInitFlags] :: SavedConfig -> InitFlags [savedInstallFlags] :: SavedConfig -> InstallFlags [savedClientInstallFlags] :: SavedConfig -> ClientInstallFlags [savedConfigureFlags] :: SavedConfig -> ConfigFlags [savedConfigureExFlags] :: SavedConfig -> ConfigExFlags [savedUserInstallDirs] :: SavedConfig -> InstallDirs (Flag PathTemplate) [savedGlobalInstallDirs] :: SavedConfig -> InstallDirs (Flag PathTemplate) [savedUploadFlags] :: SavedConfig -> UploadFlags [savedReportFlags] :: SavedConfig -> ReportFlags [savedHaddockFlags] :: SavedConfig -> HaddockFlags [savedTestFlags] :: SavedConfig -> TestFlags [savedBenchmarkFlags] :: SavedConfig -> BenchmarkFlags [savedProjectFlags] :: SavedConfig -> ProjectFlags -- | Loads the main configuration, and applies additional defaults to give -- the effective configuration. To loads just what is actually in the -- config file, use loadRawConfig. loadConfig :: Verbosity -> Flag FilePath -> IO SavedConfig -- | Returns the config file path, without checking that the file exists. -- The order of precedence is: input flag, CABAL_CONFIG, default -- location. getConfigFilePath :: Flag FilePath -> IO FilePath showConfig :: SavedConfig -> String showConfigWithComments :: SavedConfig -> SavedConfig -> String parseConfig :: ConstraintSource -> SavedConfig -> ByteString -> ParseResult SavedConfig defaultConfigFile :: IO FilePath defaultCacheDir :: IO FilePath defaultScriptBuildsDir :: IO FilePath defaultStoreDir :: IO FilePath defaultCompiler :: CompilerFlavor defaultInstallPath :: IO FilePath defaultLogsDir :: IO FilePath defaultReportsDir :: IO FilePath defaultUserInstall :: Bool -- | These are the absolute basic defaults. The fields that must be -- initialised. When we load the config from the file we layer the loaded -- values over these ones, so any missing fields in the file take their -- values from here. baseSavedConfig :: IO SavedConfig -- | These are the default values that get used in Cabal if a no value is -- given. We use these here to include in comments when we write out the -- initial config file so that the user can see what default value they -- are overriding. commentSavedConfig :: IO SavedConfig -- | This is the initial configuration that we write out to the config file -- if the file does not exist (or the config we use if the file cannot be -- read for some other reason). When the config gets loaded it gets -- layered on top of baseSavedConfig so we do not need to include -- it into the initial values we save into the config file. initialSavedConfig :: IO SavedConfig -- | All config file fields. configFieldDescriptions :: ConstraintSource -> [FieldDescr SavedConfig] -- | Fields for the haddock section. haddockFlagsFields :: [FieldDescr HaddockFlags] -- | Fields for the 'install-dirs' sections. installDirsFields :: [FieldDescr (InstallDirs (Flag PathTemplate))] -- | Fields for the 'program-locations' section. withProgramsFields :: [FieldDescr [(String, FilePath)]] -- | Fields for the 'program-default-options' section. withProgramOptionsFields :: [FieldDescr [(String, [String])]] -- | Get the differences (as a pseudo code diff) between the user's config -- file and the one that cabal would generate if it didn't exist. userConfigDiff :: Verbosity -> GlobalFlags -> [String] -> IO [String] -- | Update the user's config file keeping the user's customizations. userConfigUpdate :: Verbosity -> GlobalFlags -> [String] -> IO () createDefaultConfigFile :: Verbosity -> [String] -> FilePath -> IO SavedConfig remoteRepoFields :: [FieldDescr RemoteRepo] postProcessRepo :: Int -> String -> RemoteRepo -> ParseResult (Either LocalRepo RemoteRepo) instance GHC.Generics.Generic Distribution.Client.Config.SavedConfig instance GHC.Base.Monoid Distribution.Client.Config.SavedConfig instance GHC.Base.Semigroup Distribution.Client.Config.SavedConfig module Distribution.Client.Upload upload :: Verbosity -> RepoContext -> Maybe Username -> Maybe Password -> IsCandidate -> [FilePath] -> IO () uploadDoc :: Verbosity -> RepoContext -> Maybe Username -> Maybe Password -> IsCandidate -> FilePath -> IO () report :: Verbosity -> RepoContext -> Maybe Username -> Maybe Password -> IO () -- | An interface to building and installing Cabal packages. If the -- Built-Type field is specified as something other than -- Custom, and the current version of Cabal is acceptable, this -- performs setup actions directly. Otherwise it builds the setup script -- and runs it with the given arguments. module Distribution.Client.SetupWrapper -- | Prepare to build a package by configuring a SetupMethod. The -- returned Setup object identifies the method. The -- SetupScriptOptions may be changed during the configuration -- process; the final values are given by setupScriptOptions. getSetup :: Verbosity -> SetupScriptOptions -> Maybe PackageDescription -> IO Setup -- | Run a configured Setup with specific arguments. runSetup :: Verbosity -> Setup -> [String] -> IO () -- | Run a command through a configured Setup. runSetupCommand :: Verbosity -> Setup -> CommandUI flags -> flags -> [String] -> IO () -- | Configure a Setup and run a command in one step. The command -- flags may depend on the Cabal library version in use. setupWrapper :: Verbosity -> SetupScriptOptions -> Maybe PackageDescription -> CommandUI flags -> (Version -> flags) -> (Version -> [String]) -> IO () -- | SetupScriptOptions are options used to configure and run -- Setup, as opposed to options given to the Cabal command at -- runtime. data SetupScriptOptions SetupScriptOptions :: VersionRange -> Maybe Version -> Maybe Compiler -> Maybe Platform -> PackageDBStack -> Maybe InstalledPackageIndex -> ProgramDb -> FilePath -> Maybe Handle -> Maybe FilePath -> [FilePath] -> [(String, Maybe FilePath)] -> Bool -> [(ComponentId, PackageId)] -> Bool -> Bool -> Bool -> Maybe Lock -> Bool -> SetupScriptOptions -- | The version of the Cabal library to use (if -- useDependenciesExclusive is not set). A suitable version of the -- Cabal library must be installed (or for some build-types be the one -- cabal-install was built with). -- -- The version found also determines the version of the Cabal -- specification that we us for talking to the Setup.hs, unless -- overridden by useCabalSpecVersion. [useCabalVersion] :: SetupScriptOptions -> VersionRange -- | This is the version of the Cabal specification that we believe that -- this package uses. This affects the semantics and in particular the -- Setup command line interface. -- -- This is similar to useCabalVersion but instead of probing the -- system for a version of the Cabal library you just say exactly -- which version of the spec we will use. Using this also avoid -- adding the Cabal library as an additional dependency, so add it to -- useDependencies if needed. [useCabalSpecVersion] :: SetupScriptOptions -> Maybe Version [useCompiler] :: SetupScriptOptions -> Maybe Compiler [usePlatform] :: SetupScriptOptions -> Maybe Platform [usePackageDB] :: SetupScriptOptions -> PackageDBStack [usePackageIndex] :: SetupScriptOptions -> Maybe InstalledPackageIndex [useProgramDb] :: SetupScriptOptions -> ProgramDb [useDistPref] :: SetupScriptOptions -> FilePath [useLoggingHandle] :: SetupScriptOptions -> Maybe Handle [useWorkingDir] :: SetupScriptOptions -> Maybe FilePath -- | Extra things to add to PATH when invoking the setup script. [useExtraPathEnv] :: SetupScriptOptions -> [FilePath] -- | Extra environment variables paired with overrides, where -- -- [useExtraEnvOverrides] :: SetupScriptOptions -> [(String, Maybe FilePath)] [forceExternalSetupMethod] :: SetupScriptOptions -> Bool -- | List of dependencies to use when building Setup.hs. [useDependencies] :: SetupScriptOptions -> [(ComponentId, PackageId)] -- | Is the list of setup dependencies exclusive? -- -- When this is False, if we compile the Setup.hs script we do -- so with the list in useDependencies but all other packages in -- the environment are also visible. A suitable version of Cabal -- library (see useCabalVersion) is also added to the list of -- dependencies, unless useDependencies already contains a Cabal -- dependency. -- -- When True, only the useDependencies packages are used, -- with other packages in the environment hidden. -- -- This feature is here to support the setup stanza in .cabal files that -- specifies explicit (and exclusive) dependencies, as well as the old -- style with no dependencies. [useDependenciesExclusive] :: SetupScriptOptions -> Bool -- | Should we build the Setup.hs with CPP version macros available? We -- turn this on when we have a setup stanza in .cabal that declares -- explicit setup dependencies. [useVersionMacros] :: SetupScriptOptions -> Bool [useWin32CleanHack] :: SetupScriptOptions -> Bool [setupCacheLock] :: SetupScriptOptions -> Maybe Lock -- | Is the task we are going to run an interactive foreground task, or an -- non-interactive background task? Based on this flag we decide whether -- or not to delegate ctrl+c to the spawned task [isInteractive] :: SetupScriptOptions -> Bool defaultSetupScriptOptions :: SetupScriptOptions -- | High level interface to configuring a package. module Distribution.Client.Configure -- | Configure the package found in the local directory configure :: Verbosity -> PackageDBStack -> RepoContext -> Compiler -> Platform -> ProgramDb -> ConfigFlags -> ConfigExFlags -> [String] -> IO () configureSetupScript :: PackageDBStack -> Compiler -> Platform -> ProgramDb -> FilePath -> VersionRange -> Maybe Lock -> Bool -> InstalledPackageIndex -> Maybe ReadyPackage -> SetupScriptOptions -- | Choose the Cabal version such that the setup scripts compiled against -- this version will support the given command-line flags. Currently, it -- implements no specific restrictions and allows any version, unless the -- second argument is filled with a Version, in which case this -- version is picked. chooseCabalVersion :: ConfigExFlags -> Maybe Version -> VersionRange -- | Warn if any constraints or preferences name packages that are not in -- the source package index or installed package index. checkConfigExFlags :: Package pkg => Verbosity -> InstalledPackageIndex -> PackageIndex pkg -> ConfigExFlags -> IO () -- | Read saved configure flags and restore the saved environment from the -- specified files. readConfigFlagsFrom :: FilePath -> IO (ConfigFlags, ConfigExFlags) -- | Read saved configure flags and restore the saved environment from the -- usual location. readConfigFlags :: FilePath -> IO (ConfigFlags, ConfigExFlags) -- | The path (relative to --build-dir) where the arguments to -- configure should be saved. cabalConfigFlagsFile :: FilePath -> FilePath -- | Save the configure flags and environment to the specified files. writeConfigFlagsTo :: FilePath -> Verbosity -> (ConfigFlags, ConfigExFlags) -> IO () -- | Save the build flags to the usual location. writeConfigFlags :: Verbosity -> FilePath -> (ConfigFlags, ConfigExFlags) -> IO () -- | Utilities for working with the package environment file. Patterned -- after Distribution.Client.Config. module Distribution.Client.Sandbox.PackageEnvironment data PackageEnvironment PackageEnvironment :: SavedConfig -> PackageEnvironment [pkgEnvSavedConfig] :: PackageEnvironment -> SavedConfig -- | Type of the current package environment. data PackageEnvironmentType -- | './cabal.config' UserPackageEnvironment :: PackageEnvironmentType -- | '~.configcabal/config' AmbientPackageEnvironment :: PackageEnvironmentType -- | Is there a 'cabal.config' in this directory? classifyPackageEnvironment :: FilePath -> IO PackageEnvironmentType -- | Read the package environment file. readPackageEnvironmentFile :: ConstraintSource -> PackageEnvironment -> FilePath -> IO (Maybe (ParseResult PackageEnvironment)) -- | Pretty-print the package environment. showPackageEnvironment :: PackageEnvironment -> String -- | Pretty-print the package environment with default values for empty -- fields commented out (just like the default Cabal config file). showPackageEnvironmentWithComments :: Maybe PackageEnvironment -> PackageEnvironment -> String -- | Same as userPackageEnvironmentFile, but returns a -- SavedConfig. loadUserConfig :: Verbosity -> FilePath -> Maybe FilePath -> IO SavedConfig -- | Optional package environment file that can be used to customize the -- default settings. Created by the user. userPackageEnvironmentFile :: FilePath instance GHC.Generics.Generic Distribution.Client.Sandbox.PackageEnvironment.PackageEnvironment instance GHC.Base.Monoid Distribution.Client.Sandbox.PackageEnvironment.PackageEnvironment instance GHC.Base.Semigroup Distribution.Client.Sandbox.PackageEnvironment.PackageEnvironment -- | UI for the sandboxing functionality. module Distribution.Client.Sandbox -- | Check which type of package environment we're in and return a -- correctly-initialised SavedConfig and a UseSandbox -- value that indicates whether we're working in a sandbox. loadConfigOrSandboxConfig :: Verbosity -> GlobalFlags -> IO SavedConfig -- | Return the saved "dist/" prefix, or the default prefix. findSavedDistPref :: SavedConfig -> Flag FilePath -> IO FilePath updateInstallDirs :: Flag Bool -> SavedConfig -> SavedConfig -- | Try to read the most recently configured compiler from the -- localBuildInfoFile, falling back on -- configCompilerAuxEx if it cannot be read. getPersistOrConfigCompiler :: ConfigFlags -> IO (Compiler, Platform, ProgramDb) module Distribution.Client.CmdLegacy legacyCmd :: HasVerbosity flags => CommandUI flags -> (flags -> [String] -> globals -> IO action) -> [CommandSpec (globals -> IO action)] legacyWrapperCmd :: Monoid flags => CommandUI flags -> (flags -> Flag Verbosity) -> (flags -> Flag String) -> [CommandSpec (GlobalFlags -> IO ())] newCmd :: CommandUI flags -> (flags -> [String] -> globals -> IO action) -> [CommandSpec (globals -> IO action)] instance Distribution.Client.CmdLegacy.HasVerbosity (Distribution.Simple.Flag.Flag Distribution.Verbosity.Verbosity) instance Distribution.Client.CmdLegacy.HasVerbosity a => Distribution.Client.CmdLegacy.HasVerbosity (a, b) instance Distribution.Client.CmdLegacy.HasVerbosity a => Distribution.Client.CmdLegacy.HasVerbosity (a, b, c) instance Distribution.Client.CmdLegacy.HasVerbosity a => Distribution.Client.CmdLegacy.HasVerbosity (a, b, c, d) instance Distribution.Client.CmdLegacy.HasVerbosity a => Distribution.Client.CmdLegacy.HasVerbosity (a, b, c, d, e) instance Distribution.Client.CmdLegacy.HasVerbosity a => Distribution.Client.CmdLegacy.HasVerbosity (a, b, c, d, e, f) instance Distribution.Client.CmdLegacy.HasVerbosity Distribution.Simple.Setup.BuildFlags instance Distribution.Client.CmdLegacy.HasVerbosity Distribution.Simple.Setup.ConfigFlags instance Distribution.Client.CmdLegacy.HasVerbosity Distribution.Simple.Setup.ReplFlags instance Distribution.Client.CmdLegacy.HasVerbosity Distribution.Client.Setup.FreezeFlags instance Distribution.Client.CmdLegacy.HasVerbosity Distribution.Simple.Setup.HaddockFlags instance Distribution.Client.CmdLegacy.HasVerbosity Distribution.Client.Setup.UpdateFlags instance Distribution.Client.CmdLegacy.HasVerbosity Distribution.Simple.Setup.CleanFlags -- | Project configuration, implementation in terms of legacy types. module Distribution.Client.ProjectConfig.Legacy -- | ProjectConfigSkeleton is a tree of conditional blocks and imports -- wrapping a config. It can be finalized by providing the conditional -- resolution info and then resolving and downloading the imports type ProjectConfigSkeleton = CondTree ConfVar [ProjectConfigImport] ProjectConfig parseProjectSkeleton :: FilePath -> HttpTransport -> Verbosity -> [ProjectConfigImport] -> FilePath -> ByteString -> IO (ParseResult ProjectConfigSkeleton) instantiateProjectConfigSkeletonFetchingCompiler :: Monad m => m (OS, Arch, CompilerInfo) -> FlagAssignment -> ProjectConfigSkeleton -> m ProjectConfig instantiateProjectConfigSkeletonWithCompiler :: OS -> Arch -> CompilerInfo -> FlagAssignment -> ProjectConfigSkeleton -> ProjectConfig singletonProjectConfigSkeleton :: ProjectConfig -> ProjectConfigSkeleton projectSkeletonImports :: ProjectConfigSkeleton -> [ProjectConfigImport] -- | We already have parsers/pretty-printers for almost all the fields in -- the project config file, but they're in terms of the types used for -- the command line flags for Setup.hs or cabal commands. We don't want -- to redefine them all, at least not yet so for the moment we use the -- parsers at the old types and use conversion functions. -- -- Ultimately if/when this project-based approach becomes the default -- then we can redefine the parsers directly for the new types. data LegacyProjectConfig parseLegacyProjectConfig :: FilePath -> ByteString -> ParseResult LegacyProjectConfig showLegacyProjectConfig :: LegacyProjectConfig -> String -- | Convert configuration from the cabal configure or cabal -- build command line into a ProjectConfig value that can -- combined with configuration from other sources. -- -- At the moment this uses the legacy command line flag types. See -- LegacyProjectConfig for an explanation. commandLineFlagsToProjectConfig :: GlobalFlags -> NixStyleFlags a -> ClientInstallFlags -> ProjectConfig -- | Convert the project config from the legacy types to the -- ProjectConfig and associated types. See -- LegacyProjectConfig for an explanation of the approach. convertLegacyProjectConfig :: LegacyProjectConfig -> ProjectConfig -- | Convert from the types currently used for the user-wide Cabal config -- file into the ProjectConfig type. -- -- Only a subset of the ProjectConfig can be represented in the -- user-wide config. In particular it does not include packages that are -- in the project, and it also doesn't support package-specific -- configuration (only configuration that applies to all packages). convertLegacyGlobalConfig :: SavedConfig -> ProjectConfig convertToLegacyProjectConfig :: ProjectConfig -> LegacyProjectConfig -- | This is a bit tricky since it has to cover globs which have embedded -- , chars. But we don't just want to parse strictly as a glob -- since we want to allow http urls which don't parse as globs, and -- possibly some system-dependent file paths. So we parse fairly -- liberally as a token, but we allow , inside matched -- {} braces. parsePackageLocationTokenQ :: ReadP r String renderPackageLocationToken :: String -> String instance GHC.Generics.Generic Distribution.Client.ProjectConfig.Legacy.LegacyPackageConfig instance GHC.Show.Show Distribution.Client.ProjectConfig.Legacy.LegacyPackageConfig instance GHC.Generics.Generic Distribution.Client.ProjectConfig.Legacy.LegacySharedConfig instance GHC.Show.Show Distribution.Client.ProjectConfig.Legacy.LegacySharedConfig instance GHC.Generics.Generic Distribution.Client.ProjectConfig.Legacy.LegacyProjectConfig instance GHC.Show.Show Distribution.Client.ProjectConfig.Legacy.LegacyProjectConfig instance GHC.Base.Monoid Distribution.Client.ProjectConfig.Legacy.LegacyProjectConfig instance GHC.Base.Semigroup Distribution.Client.ProjectConfig.Legacy.LegacyProjectConfig instance GHC.Base.Monoid Distribution.Client.ProjectConfig.Legacy.LegacySharedConfig instance GHC.Base.Semigroup Distribution.Client.ProjectConfig.Legacy.LegacySharedConfig instance GHC.Base.Monoid Distribution.Client.ProjectConfig.Legacy.LegacyPackageConfig instance GHC.Base.Semigroup Distribution.Client.ProjectConfig.Legacy.LegacyPackageConfig module Distribution.Client.Nix findNixExpr :: GlobalFlags -> SavedConfig -> IO (Maybe FilePath) inNixShell :: IO Bool nixInstantiate :: Verbosity -> FilePath -> Bool -> GlobalFlags -> SavedConfig -> IO () nixShell :: Verbosity -> FilePath -> GlobalFlags -> SavedConfig -> IO () -> IO () module Distribution.Client.Reconfigure -- | Check represents a function to check some condition on type -- a. The returned Any is True if any part of the -- condition failed. newtype Check a Check :: (Any -> a -> IO (Any, a)) -> Check a [runCheck] :: Check a -> Any -> a -> IO (Any, a) -- | Re-configure the package in the current directory if needed. Deciding -- when to reconfigure and with which options is convoluted: -- -- If we are reconfiguring, we must always run configure with -- the verbosity option we are given; however, that a previous -- configuration uses a different verbosity setting is not reason enough -- to reconfigure. -- -- The package should be configured to use the same "dist" prefix as -- given to the build command, otherwise the build will probably -- fail. Not only does this determine the "dist" prefix setting if we -- need to reconfigure anyway, but an existing configuration should be -- invalidated if its "dist" prefix differs. -- -- If the package has never been configured (i.e., there is no -- LocalBuildInfo), we must configure first, using the default options. -- -- If the package has been configured, there will be a -- LocalBuildInfo. If there no package description file, we -- assume that the PackageDescription is up to date, though the -- configuration may need to be updated for other reasons (see above). If -- there is a package description file, and it has been modified since -- the LocalBuildInfo was generated, then we need to -- reconfigure. -- -- The caller of this function may also have specific requirements -- regarding the flags the last configuration used. For example, -- testAction requires that the package be configured with test -- suites enabled. The caller may pass the required settings to this -- function along with a function to check the validity of the saved -- ConfigFlags; these required settings will be checked first upon -- determining that a previous configuration exists. reconfigure :: ((ConfigFlags, ConfigExFlags) -> [String] -> GlobalFlags -> IO ()) -> Verbosity -> FilePath -> Flag (Maybe Int) -> Check (ConfigFlags, ConfigExFlags) -> [String] -> GlobalFlags -> SavedConfig -> IO SavedConfig instance GHC.Base.Semigroup (Distribution.Client.Reconfigure.Check a) instance GHC.Base.Monoid (Distribution.Client.Reconfigure.Check a) -- | High level interface to package installation. module Distribution.Client.Install -- | Installs the packages needed to satisfy a list of dependencies. install :: Verbosity -> PackageDBStack -> RepoContext -> Compiler -> Platform -> ProgramDb -> GlobalFlags -> ConfigFlags -> ConfigExFlags -> InstallFlags -> HaddockFlags -> TestFlags -> BenchmarkFlags -> [UserTarget] -> IO () -- | Make an install context given install arguments. makeInstallContext :: Verbosity -> InstallArgs -> Maybe [UserTarget] -> IO InstallContext -- | Make an install plan given install context and install arguments. makeInstallPlan :: Verbosity -> InstallArgs -> InstallContext -> IO (Progress String String SolverInstallPlan) -- | Given an install plan, perform the actual installations. processInstallPlan :: Verbosity -> InstallArgs -> InstallContext -> SolverInstallPlan -> IO () -- | Initial arguments given to install or -- makeInstallContext. type InstallArgs = (PackageDBStack, RepoContext, Compiler, Platform, ProgramDb, GlobalFlags, ConfigFlags, ConfigExFlags, InstallFlags, HaddockFlags, TestFlags, BenchmarkFlags) -- | Common context for makeInstallPlan and processInstallPlan. type InstallContext = (InstalledPackageIndex, SourcePackageDb, PkgConfigDb, [UserTarget], [PackageSpecifier UnresolvedSourcePackage], HttpTransport) -- | Remove the provided targets from the install plan. pruneInstallPlan :: Package targetpkg => [PackageSpecifier targetpkg] -> SolverInstallPlan -> Progress String String SolverInstallPlan -- | The cabal freeze command module Distribution.Client.Freeze -- | Freeze all of the dependencies by writing a constraints section -- constraining each dependency to an exact version. freeze :: Verbosity -> PackageDBStack -> RepoContext -> Compiler -> Platform -> ProgramDb -> GlobalFlags -> FreezeFlags -> IO () -- | Get the list of packages whose versions would be frozen by the -- freeze command. getFreezePkgs :: Verbosity -> PackageDBStack -> RepoContext -> Compiler -> Platform -> ProgramDb -> GlobalFlags -> FreezeFlags -> IO [SolverPlanPackage] -- | The cabal gen-bounds command for generating PVP-compliant version -- bounds. module Distribution.Client.GenBounds -- | Entry point for the gen-bounds command. genBounds :: Verbosity -> PackageDBStack -> RepoContext -> Compiler -> Platform -> ProgramDb -> GlobalFlags -> FreezeFlags -> IO () -- | The layout of the ./dist/ directory where cabal keeps all of its state -- and build artifacts. module Distribution.Client.DistDirLayout -- | The layout of the project state directory. Traditionally this has been -- called the dist directory. data DistDirLayout DistDirLayout :: FilePath -> (String -> FilePath) -> FilePath -> (DistDirParams -> FilePath) -> FilePath -> FilePath -> (PackageId -> FilePath) -> FilePath -> (String -> FilePath) -> FilePath -> (DistDirParams -> String -> FilePath) -> (DistDirParams -> FilePath) -> (PackageId -> FilePath) -> FilePath -> FilePath -> FilePath -> (CompilerId -> PackageDB) -> DistDirLayout -- | The root directory of the project. Many other files are relative to -- this location. In particular, the cabal.project lives here. [distProjectRootDirectory] :: DistDirLayout -> FilePath -- | The cabal.project file and related like -- cabal.project.freeze. The parameter is for the extension, -- like "freeze", or "" for the main file. [distProjectFile] :: DistDirLayout -> String -> FilePath -- | The "dist" directory, which is the root of where cabal keeps all its -- state including the build artifacts from each package we build. [distDirectory] :: DistDirLayout -> FilePath -- | The directory under dist where we keep the build artifacts for a -- package we're building from a local directory. -- -- This uses a UnitId not just a PackageName because -- technically we can have multiple instances of the same package in a -- solution (e.g. setup deps). [distBuildDirectory] :: DistDirLayout -> DistDirParams -> FilePath [distBuildRootDirectory] :: DistDirLayout -> FilePath -- | The directory under dist where we download tarballs and source control -- repos to. [distDownloadSrcDirectory] :: DistDirLayout -> FilePath -- | The directory under dist where we put the unpacked sources of -- packages, in those cases where it makes sense to keep the build -- artifacts to reduce rebuild times. [distUnpackedSrcDirectory] :: DistDirLayout -> PackageId -> FilePath [distUnpackedSrcRootDirectory] :: DistDirLayout -> FilePath -- | The location for project-wide cache files (e.g. state used in -- incremental rebuilds). [distProjectCacheFile] :: DistDirLayout -> String -> FilePath [distProjectCacheDirectory] :: DistDirLayout -> FilePath -- | The location for package-specific cache files (e.g. state used in -- incremental rebuilds). [distPackageCacheFile] :: DistDirLayout -> DistDirParams -> String -> FilePath [distPackageCacheDirectory] :: DistDirLayout -> DistDirParams -> FilePath -- | The location that sdists are placed by default. [distSdistFile] :: DistDirLayout -> PackageId -> FilePath [distSdistDirectory] :: DistDirLayout -> FilePath [distTempDirectory] :: DistDirLayout -> FilePath [distBinDirectory] :: DistDirLayout -> FilePath [distPackageDB] :: DistDirLayout -> CompilerId -> PackageDB -- | Information which can be used to construct the path to the build -- directory of a build. This is LESS fine-grained than what goes into -- the hashed InstalledPackageId, and for good reason: we don't -- want this path to change if the user, say, adds a dependency to their -- project. data DistDirParams DistDirParams :: UnitId -> PackageId -> ComponentId -> Maybe ComponentName -> CompilerId -> Platform -> OptimisationLevel -> DistDirParams [distParamUnitId] :: DistDirParams -> UnitId [distParamPackageId] :: DistDirParams -> PackageId [distParamComponentId] :: DistDirParams -> ComponentId [distParamComponentName] :: DistDirParams -> Maybe ComponentName [distParamCompilerId] :: DistDirParams -> CompilerId [distParamPlatform] :: DistDirParams -> Platform [distParamOptimization] :: DistDirParams -> OptimisationLevel -- | Make the default DistDirLayout based on the project root dir -- and optional overrides for the location of the dist directory -- and the cabal.project file. defaultDistDirLayout :: ProjectRoot -> Maybe FilePath -> DistDirLayout -- | Information about the root directory of the project. -- -- It can either be an implicit project root in the current dir if no -- cabal.project file is found, or an explicit root if the file -- is found. data ProjectRoot -- | ProjectRootImplicit :: FilePath -> ProjectRoot -- | ProjectRootExplicit :: FilePath -> FilePath -> ProjectRoot -- | The layout of a cabal nix-style store. data StoreDirLayout StoreDirLayout :: (CompilerId -> FilePath) -> (CompilerId -> UnitId -> FilePath) -> (CompilerId -> FilePath) -> (CompilerId -> PackageDB) -> (CompilerId -> PackageDBStack) -> (CompilerId -> FilePath) -> (CompilerId -> UnitId -> FilePath) -> StoreDirLayout [storeDirectory] :: StoreDirLayout -> CompilerId -> FilePath [storePackageDirectory] :: StoreDirLayout -> CompilerId -> UnitId -> FilePath [storePackageDBPath] :: StoreDirLayout -> CompilerId -> FilePath [storePackageDB] :: StoreDirLayout -> CompilerId -> PackageDB [storePackageDBStack] :: StoreDirLayout -> CompilerId -> PackageDBStack [storeIncomingDirectory] :: StoreDirLayout -> CompilerId -> FilePath [storeIncomingLock] :: StoreDirLayout -> CompilerId -> UnitId -> FilePath defaultStoreDirLayout :: FilePath -> StoreDirLayout -- | The layout of the user-wide cabal directory, that is the -- ~/.cabal dir on unix, and equivalents on other systems. -- -- At the moment this is just a partial specification, but the idea is -- eventually to cover it all. data CabalDirLayout CabalDirLayout :: StoreDirLayout -> FilePath -> CabalDirLayout [cabalStoreDirLayout] :: CabalDirLayout -> StoreDirLayout [cabalLogsDirectory] :: CabalDirLayout -> FilePath mkCabalDirLayout :: Maybe FilePath -> Maybe FilePath -> IO CabalDirLayout defaultCabalDirLayout :: IO CabalDirLayout instance GHC.Show.Show Distribution.Client.DistDirLayout.ProjectRoot instance GHC.Classes.Eq Distribution.Client.DistDirLayout.ProjectRoot -- | Management for the installed package store. module Distribution.Client.Store -- | The layout of a cabal nix-style store. data StoreDirLayout StoreDirLayout :: (CompilerId -> FilePath) -> (CompilerId -> UnitId -> FilePath) -> (CompilerId -> FilePath) -> (CompilerId -> PackageDB) -> (CompilerId -> PackageDBStack) -> (CompilerId -> FilePath) -> (CompilerId -> UnitId -> FilePath) -> StoreDirLayout [storeDirectory] :: StoreDirLayout -> CompilerId -> FilePath [storePackageDirectory] :: StoreDirLayout -> CompilerId -> UnitId -> FilePath [storePackageDBPath] :: StoreDirLayout -> CompilerId -> FilePath [storePackageDB] :: StoreDirLayout -> CompilerId -> PackageDB [storePackageDBStack] :: StoreDirLayout -> CompilerId -> PackageDBStack [storeIncomingDirectory] :: StoreDirLayout -> CompilerId -> FilePath [storeIncomingLock] :: StoreDirLayout -> CompilerId -> UnitId -> FilePath defaultStoreDirLayout :: FilePath -> StoreDirLayout -- | Return the UnitIds of all packages/components already installed -- in the store. getStoreEntries :: StoreDirLayout -> CompilerId -> Rebuild (Set UnitId) -- | Check if a particular UnitId exists in the store. doesStoreEntryExist :: StoreDirLayout -> CompilerId -> UnitId -> IO Bool -- | Place a new entry into the store. See the concurrency strategy -- description for full details. -- -- In particular, it takes two actions: one to place files into a -- temporary location, and a second to perform any necessary -- registration. The first action is executed without any locks held (the -- temp dir is unique). The second action holds a lock that guarantees -- that only one cabal process is able to install this store entry. This -- means it is safe to register into the compiler package DB or do other -- similar actions. -- -- Note that if you need to use the registration information later then -- you must check the NewStoreEntryOutcome and if -- its'UseExistingStoreEntry then you must read the existing -- registration information (unless your registration information is -- constructed fully deterministically). newStoreEntry :: Verbosity -> StoreDirLayout -> CompilerId -> UnitId -> (FilePath -> IO (FilePath, [FilePath])) -> IO () -> IO NewStoreEntryOutcome -- | The outcome of newStoreEntry: either the store entry was newly -- created or it existed already. The latter case happens if there was a -- race between two builds of the same store entry. data NewStoreEntryOutcome UseNewStoreEntry :: NewStoreEntryOutcome UseExistingStoreEntry :: NewStoreEntryOutcome instance GHC.Show.Show Distribution.Client.Store.NewStoreEntryOutcome instance GHC.Classes.Eq Distribution.Client.Store.NewStoreEntryOutcome -- | Types used while planning how to build everything in a project. -- -- Primarily this is the ElaboratedInstallPlan. module Distribution.Client.ProjectPlanning.Types data SolverInstallPlan -- | The combination of an elaborated install plan plus a -- ElaboratedSharedConfig contains all the details necessary to be -- able to execute the plan without having to make further policy -- decisions. -- -- It does not include dynamic elements such as resources (such as http -- connections). type ElaboratedInstallPlan = GenericInstallPlan InstalledPackageInfo ElaboratedConfiguredPackage normaliseConfiguredPackage :: ElaboratedSharedConfig -> ElaboratedConfiguredPackage -> ElaboratedConfiguredPackage data ElaboratedConfiguredPackage ElaboratedConfiguredPackage :: UnitId -> ComponentId -> Map ModuleName Module -> Map ModuleName OpenModule -> Bool -> PackageId -> ModuleShape -> FlagAssignment -> FlagAssignment -> PackageDescription -> PackageLocation (Maybe FilePath) -> Maybe PackageSourceHash -> Bool -> BuildStyle -> ComponentRequestedSpec -> OptionalStanzaSet -> OptionalStanzaMap (Maybe Bool) -> [Maybe PackageDB] -> PackageDBStack -> PackageDBStack -> PackageDBStack -> PackageDBStack -> PackageDBStack -> PackageDBStack -> Maybe CabalFileText -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> ProfDetailLevel -> ProfDetailLevel -> Bool -> OptimisationLevel -> Bool -> Bool -> Bool -> Bool -> DebugInfoLevel -> DumpBuildInfo -> Map String FilePath -> Map String [String] -> [FilePath] -> [String] -> [FilePath] -> [FilePath] -> [FilePath] -> [FilePath] -> Maybe PathTemplate -> Maybe PathTemplate -> InstallDirs FilePath -> Bool -> Bool -> Maybe String -> Bool -> HaddockTarget -> Bool -> Bool -> Bool -> Bool -> Maybe FilePath -> Bool -> Bool -> Maybe FilePath -> Maybe PathTemplate -> Maybe PathTemplate -> Maybe String -> Maybe String -> Maybe PathTemplate -> Maybe PathTemplate -> Maybe TestShowDetails -> Bool -> Maybe FilePath -> Bool -> [PathTemplate] -> [PathTemplate] -> SetupScriptStyle -> Version -> [ComponentTarget] -> [ComponentTarget] -> [ComponentTarget] -> [ComponentTarget] -> Maybe ComponentTarget -> [ComponentTarget] -> Bool -> ElaboratedPackageOrComponent -> ElaboratedConfiguredPackage -- | The UnitId which uniquely identifies this item in a build plan [elabUnitId] :: ElaboratedConfiguredPackage -> UnitId [elabComponentId] :: ElaboratedConfiguredPackage -> ComponentId [elabInstantiatedWith] :: ElaboratedConfiguredPackage -> Map ModuleName Module [elabLinkedInstantiatedWith] :: ElaboratedConfiguredPackage -> Map ModuleName OpenModule -- | This is true if this is an indefinite package, or this is a package -- with no signatures. (Notably, it's not true for instantiated -- packages.) The motivation for this is if you ask to build -- foo-indef, this probably means that you want to typecheck it, -- NOT that you want to rebuild all of the various instantiations of it. [elabIsCanonical] :: ElaboratedConfiguredPackage -> Bool -- | The PackageId of the originating package [elabPkgSourceId] :: ElaboratedConfiguredPackage -> PackageId -- | Shape of the package/component, for Backpack. [elabModuleShape] :: ElaboratedConfiguredPackage -> ModuleShape -- | A total flag assignment for the package. TODO: Actually this can be -- per-component if we drop all flags that don't affect a component. [elabFlagAssignment] :: ElaboratedConfiguredPackage -> FlagAssignment -- | The original default flag assignment, used only for reporting. [elabFlagDefaults] :: ElaboratedConfiguredPackage -> FlagAssignment [elabPkgDescription] :: ElaboratedConfiguredPackage -> PackageDescription -- | Where the package comes from, e.g. tarball, local dir etc. This is not -- the same as where it may be unpacked to for the build. [elabPkgSourceLocation] :: ElaboratedConfiguredPackage -> PackageLocation (Maybe FilePath) -- | The hash of the source, e.g. the tarball. We don't have this for local -- source dir packages. [elabPkgSourceHash] :: ElaboratedConfiguredPackage -> Maybe PackageSourceHash -- | Is this package one of the ones specified by location in the project -- file? (As opposed to a dependency, or a named package pulled in) [elabLocalToProject] :: ElaboratedConfiguredPackage -> Bool -- | Are we going to build and install this package to the store, or are we -- going to build it and register it locally. [elabBuildStyle] :: ElaboratedConfiguredPackage -> BuildStyle -- | Another way of phrasing pkgStanzasAvailable. [elabEnabledSpec] :: ElaboratedConfiguredPackage -> ComponentRequestedSpec -- | Which optional stanzas (ie testsuites, benchmarks) can be built. This -- means the solver produced a plan that has them available. This doesn't -- necessary mean we build them by default. [elabStanzasAvailable] :: ElaboratedConfiguredPackage -> OptionalStanzaSet -- | Which optional stanzas the user explicitly asked to enable or to -- disable. This tells us which ones we build by default, and helps with -- error messages when the user asks to build something they explicitly -- disabled. -- -- TODO: The Bool here should be refined into an ADT with three -- cases: NotRequested, ExplicitlyRequested and ImplicitlyRequested. A -- stanza is explicitly requested if the user asked, for this *specific* -- package, that the stanza be enabled; it's implicitly requested if the -- user asked for all global packages to have this stanza enabled. The -- difference between an explicit and implicit request is error reporting -- behavior: if a user asks for tests to be enabled for a specific -- package that doesn't have any tests, we should warn them about it, but -- we shouldn't complain that a user enabled tests globally, and some -- local packages just happen not to have any tests. (But perhaps we -- should warn if ALL local packages don't have any tests.) [elabStanzasRequested] :: ElaboratedConfiguredPackage -> OptionalStanzaMap (Maybe Bool) [elabPackageDbs] :: ElaboratedConfiguredPackage -> [Maybe PackageDB] [elabSetupPackageDBStack] :: ElaboratedConfiguredPackage -> PackageDBStack [elabBuildPackageDBStack] :: ElaboratedConfiguredPackage -> PackageDBStack [elabRegisterPackageDBStack] :: ElaboratedConfiguredPackage -> PackageDBStack [elabInplaceSetupPackageDBStack] :: ElaboratedConfiguredPackage -> PackageDBStack [elabInplaceBuildPackageDBStack] :: ElaboratedConfiguredPackage -> PackageDBStack [elabInplaceRegisterPackageDBStack] :: ElaboratedConfiguredPackage -> PackageDBStack [elabPkgDescriptionOverride] :: ElaboratedConfiguredPackage -> Maybe CabalFileText [elabVanillaLib] :: ElaboratedConfiguredPackage -> Bool [elabSharedLib] :: ElaboratedConfiguredPackage -> Bool [elabStaticLib] :: ElaboratedConfiguredPackage -> Bool [elabDynExe] :: ElaboratedConfiguredPackage -> Bool [elabFullyStaticExe] :: ElaboratedConfiguredPackage -> Bool [elabGHCiLib] :: ElaboratedConfiguredPackage -> Bool [elabProfLib] :: ElaboratedConfiguredPackage -> Bool [elabProfExe] :: ElaboratedConfiguredPackage -> Bool [elabProfLibDetail] :: ElaboratedConfiguredPackage -> ProfDetailLevel [elabProfExeDetail] :: ElaboratedConfiguredPackage -> ProfDetailLevel [elabCoverage] :: ElaboratedConfiguredPackage -> Bool [elabOptimization] :: ElaboratedConfiguredPackage -> OptimisationLevel [elabSplitObjs] :: ElaboratedConfiguredPackage -> Bool [elabSplitSections] :: ElaboratedConfiguredPackage -> Bool [elabStripLibs] :: ElaboratedConfiguredPackage -> Bool [elabStripExes] :: ElaboratedConfiguredPackage -> Bool [elabDebugInfo] :: ElaboratedConfiguredPackage -> DebugInfoLevel [elabDumpBuildInfo] :: ElaboratedConfiguredPackage -> DumpBuildInfo [elabProgramPaths] :: ElaboratedConfiguredPackage -> Map String FilePath [elabProgramArgs] :: ElaboratedConfiguredPackage -> Map String [String] [elabProgramPathExtra] :: ElaboratedConfiguredPackage -> [FilePath] [elabConfigureScriptArgs] :: ElaboratedConfiguredPackage -> [String] [elabExtraLibDirs] :: ElaboratedConfiguredPackage -> [FilePath] [elabExtraLibDirsStatic] :: ElaboratedConfiguredPackage -> [FilePath] [elabExtraFrameworkDirs] :: ElaboratedConfiguredPackage -> [FilePath] [elabExtraIncludeDirs] :: ElaboratedConfiguredPackage -> [FilePath] [elabProgPrefix] :: ElaboratedConfiguredPackage -> Maybe PathTemplate [elabProgSuffix] :: ElaboratedConfiguredPackage -> Maybe PathTemplate [elabInstallDirs] :: ElaboratedConfiguredPackage -> InstallDirs FilePath [elabHaddockHoogle] :: ElaboratedConfiguredPackage -> Bool [elabHaddockHtml] :: ElaboratedConfiguredPackage -> Bool [elabHaddockHtmlLocation] :: ElaboratedConfiguredPackage -> Maybe String [elabHaddockForeignLibs] :: ElaboratedConfiguredPackage -> Bool [elabHaddockForHackage] :: ElaboratedConfiguredPackage -> HaddockTarget [elabHaddockExecutables] :: ElaboratedConfiguredPackage -> Bool [elabHaddockTestSuites] :: ElaboratedConfiguredPackage -> Bool [elabHaddockBenchmarks] :: ElaboratedConfiguredPackage -> Bool [elabHaddockInternal] :: ElaboratedConfiguredPackage -> Bool [elabHaddockCss] :: ElaboratedConfiguredPackage -> Maybe FilePath [elabHaddockLinkedSource] :: ElaboratedConfiguredPackage -> Bool [elabHaddockQuickJump] :: ElaboratedConfiguredPackage -> Bool [elabHaddockHscolourCss] :: ElaboratedConfiguredPackage -> Maybe FilePath [elabHaddockContents] :: ElaboratedConfiguredPackage -> Maybe PathTemplate [elabHaddockIndex] :: ElaboratedConfiguredPackage -> Maybe PathTemplate [elabHaddockBaseUrl] :: ElaboratedConfiguredPackage -> Maybe String [elabHaddockLib] :: ElaboratedConfiguredPackage -> Maybe String [elabTestMachineLog] :: ElaboratedConfiguredPackage -> Maybe PathTemplate [elabTestHumanLog] :: ElaboratedConfiguredPackage -> Maybe PathTemplate [elabTestShowDetails] :: ElaboratedConfiguredPackage -> Maybe TestShowDetails [elabTestKeepTix] :: ElaboratedConfiguredPackage -> Bool [elabTestWrapper] :: ElaboratedConfiguredPackage -> Maybe FilePath [elabTestFailWhenNoTestSuites] :: ElaboratedConfiguredPackage -> Bool [elabTestTestOptions] :: ElaboratedConfiguredPackage -> [PathTemplate] [elabBenchmarkOptions] :: ElaboratedConfiguredPackage -> [PathTemplate] -- | One of four modes for how we build and interact with the Setup.hs -- script, based on whether it's a build-type Custom, with or without -- explicit deps and the cabal spec version the .cabal file needs. [elabSetupScriptStyle] :: ElaboratedConfiguredPackage -> SetupScriptStyle -- | The version of the Cabal command line interface that we are using for -- this package. This is typically the version of the Cabal lib that the -- Setup.hs is built against. -- -- TODO: We might want to turn this into a enum, yet different enum than -- CabalSpecVersion. [elabSetupScriptCliVersion] :: ElaboratedConfiguredPackage -> Version [elabConfigureTargets] :: ElaboratedConfiguredPackage -> [ComponentTarget] [elabBuildTargets] :: ElaboratedConfiguredPackage -> [ComponentTarget] [elabTestTargets] :: ElaboratedConfiguredPackage -> [ComponentTarget] [elabBenchTargets] :: ElaboratedConfiguredPackage -> [ComponentTarget] [elabReplTarget] :: ElaboratedConfiguredPackage -> Maybe ComponentTarget [elabHaddockTargets] :: ElaboratedConfiguredPackage -> [ComponentTarget] [elabBuildHaddocks] :: ElaboratedConfiguredPackage -> Bool -- | Component/package specific information [elabPkgOrComp] :: ElaboratedConfiguredPackage -> ElaboratedPackageOrComponent elabDistDirParams :: ElaboratedSharedConfig -> ElaboratedConfiguredPackage -> DistDirParams -- | This returns the paths of all the executables we depend on; we must -- add these paths to PATH before invoking the setup script. (This is -- usually what you want, not elabExeDependencies, if you actually -- want to build something.) elabExeDependencyPaths :: ElaboratedConfiguredPackage -> [FilePath] -- | The library dependencies (i.e., the libraries we depend on, NOT the -- dependencies of the library), NOT including setup dependencies. These -- are passed to the Setup script via --dependency. elabLibDependencies :: ElaboratedConfiguredPackage -> [ConfiguredId] -- | Like elabOrderDependencies, but only returns dependencies on -- libraries. elabOrderLibDependencies :: ElaboratedConfiguredPackage -> [UnitId] -- | The executable dependencies (i.e., the executables we depend on); -- these are the executables we must add to the PATH before we invoke the -- setup script. elabExeDependencies :: ElaboratedConfiguredPackage -> [ComponentId] -- | Like elabOrderDependencies, but only returns dependencies on -- executables. (This coincides with elabExeDependencies.) elabOrderExeDependencies :: ElaboratedConfiguredPackage -> [UnitId] -- | The setup dependencies (the library dependencies of the setup -- executable; note that it is not legal for setup scripts to have -- executable dependencies at the moment.) elabSetupDependencies :: ElaboratedConfiguredPackage -> [ConfiguredId] elabPkgConfigDependencies :: ElaboratedConfiguredPackage -> [(PkgconfigName, Maybe PkgconfigVersion)] -- | The cache files of all our inplace dependencies which, when updated, -- require us to rebuild. See #4202 for more details. Essentially, this -- is a list of filepaths that, if our dependencies get rebuilt, will -- themselves get updated. -- -- Note: the hash of these cache files gets built into the build cache -- ourselves, which means that we end up tracking transitive -- dependencies! -- -- Note: This tracks the "build" cache file, but not "registration" or -- "config" cache files. Why not? Arguably we should... -- -- Note: This is a bit of a hack, because it is not really the hashes of -- the SOURCES of our (transitive) dependencies that we should use to -- decide whether or not to rebuild, but the output BUILD PRODUCTS. The -- strategy we use here will never work if we want to implement -- unchanging rebuilds. elabInplaceDependencyBuildCacheFiles :: DistDirLayout -> ElaboratedSharedConfig -> ElaboratedInstallPlan -> ElaboratedConfiguredPackage -> [FilePath] -- | The packagecomponent containsis a library and so must be -- registered elabRequiresRegistration :: ElaboratedConfiguredPackage -> Bool -- | Construct the environment needed for the data files to work. This -- consists of a separate *_datadir variable for each inplace -- package in the plan. dataDirsEnvironmentForPlan :: DistDirLayout -> ElaboratedInstallPlan -> [(String, Maybe FilePath)] -- | User-friendly display string for an ElaboratedPlanPackage. elabPlanPackageName :: Verbosity -> ElaboratedPlanPackage -> String -- | A user-friendly descriptor for an ElaboratedConfiguredPackage. elabConfiguredName :: Verbosity -> ElaboratedConfiguredPackage -> String elabComponentName :: ElaboratedConfiguredPackage -> Maybe ComponentName data ElaboratedPackageOrComponent ElabPackage :: ElaboratedPackage -> ElaboratedPackageOrComponent ElabComponent :: ElaboratedComponent -> ElaboratedPackageOrComponent -- | Some extra metadata associated with an -- ElaboratedConfiguredPackage which indicates that the "package" -- in question is actually a single component to be built. Arguably it -- would be clearer if there were an ADT which branched into package work -- items and component work items, but I've structured it this way to -- minimize change to the existing code (which I don't feel qualified to -- rewrite.) data ElaboratedComponent ElaboratedComponent :: Component -> Maybe ComponentName -> [ConfiguredId] -> [OpenUnitId] -> [ConfiguredId] -> [(PkgconfigName, Maybe PkgconfigVersion)] -> [(ConfiguredId, FilePath)] -> [UnitId] -> ElaboratedComponent -- | The name of the component to be built according to the solver [compSolverName] :: ElaboratedComponent -> Component -- | The name of the component to be built. Nothing if it's a setup dep. [compComponentName] :: ElaboratedComponent -> Maybe ComponentName -- | The *external* library dependencies of this component. We pass this to -- the configure script. [compLibDependencies] :: ElaboratedComponent -> [ConfiguredId] -- | In a component prior to instantiation, this list specifies the -- OpenUnitIds which, after instantiation, are the actual -- dependencies of this package. Note that this does NOT include -- signature packages, which do not turn into real ordering dependencies -- when we instantiate. This is intended to be a purely temporary field, -- to carry some information to the instantiation phase. It's more -- precise than compLibDependencies, and also stores information -- about internal dependencies. [compLinkedLibDependencies] :: ElaboratedComponent -> [OpenUnitId] -- | The executable dependencies of this component (including internal -- executables). [compExeDependencies] :: ElaboratedComponent -> [ConfiguredId] -- | The pkg-config dependencies of the component [compPkgConfigDependencies] :: ElaboratedComponent -> [(PkgconfigName, Maybe PkgconfigVersion)] -- | The paths all our executable dependencies will be installed to once -- they are installed. [compExeDependencyPaths] :: ElaboratedComponent -> [(ConfiguredId, FilePath)] -- | The UnitIds of the libraries (identifying elaborated packages/ -- components) that must be built before this project. This is used -- purely for ordering purposes. It can contain both references to -- definite and indefinite packages; an indefinite UnitId indicates that -- we must typecheck that indefinite package before we can build this -- one. [compOrderLibDependencies] :: ElaboratedComponent -> [UnitId] data ElaboratedPackage ElaboratedPackage :: InstalledPackageId -> ComponentDeps [ConfiguredId] -> ComponentDeps [()] -> ComponentDeps [ConfiguredId] -> ComponentDeps [(ConfiguredId, FilePath)] -> [(PkgconfigName, Maybe PkgconfigVersion)] -> OptionalStanzaSet -> ElaboratedPackage [pkgInstalledId] :: ElaboratedPackage -> InstalledPackageId -- | The exact dependencies (on other plan packages) [pkgLibDependencies] :: ElaboratedPackage -> ComponentDeps [ConfiguredId] -- | Components which depend (transitively) on an internally defined -- library. These are used by elabRequiresRegistration, to -- determine if a user-requested build is going to need a library -- registration [pkgDependsOnSelfLib] :: ElaboratedPackage -> ComponentDeps [()] -- | Dependencies on executable packages. [pkgExeDependencies] :: ElaboratedPackage -> ComponentDeps [ConfiguredId] -- | Paths where executable dependencies live. [pkgExeDependencyPaths] :: ElaboratedPackage -> ComponentDeps [(ConfiguredId, FilePath)] -- | Dependencies on pkg-config packages. NB: this is NOT -- per-component (although it could be) because Cabal library does not -- track per-component pkg-config depends; it always does them all at -- once. [pkgPkgConfigDependencies] :: ElaboratedPackage -> [(PkgconfigName, Maybe PkgconfigVersion)] -- | Which optional stanzas (ie testsuites, benchmarks) will actually be -- enabled during the package configure step. [pkgStanzasEnabled] :: ElaboratedPackage -> OptionalStanzaSet -- | See elabOrderDependencies. This gives the unflattened version, -- which can be useful in some circumstances. pkgOrderDependencies :: ElaboratedPackage -> ComponentDeps [UnitId] type ElaboratedPlanPackage = GenericPlanPackage InstalledPackageInfo ElaboratedConfiguredPackage data ElaboratedSharedConfig ElaboratedSharedConfig :: Platform -> Compiler -> ProgramDb -> ReplOptions -> ElaboratedSharedConfig [pkgConfigPlatform] :: ElaboratedSharedConfig -> Platform [pkgConfigCompiler] :: ElaboratedSharedConfig -> Compiler -- | The programs that the compiler configured (e.g. for GHC, the progs ghc -- & ghc-pkg). Once constructed, only the configuredPrograms -- are used. [pkgConfigCompilerProgs] :: ElaboratedSharedConfig -> ProgramDb [pkgConfigReplOptions] :: ElaboratedSharedConfig -> ReplOptions type ElaboratedReadyPackage = GenericReadyPackage ElaboratedConfiguredPackage -- | This is used in the install plan to indicate how the package will be -- built. data BuildStyle -- | The classic approach where the package is built, then the files -- installed into some location and the result registered in a package -- db. -- -- If the package came from a tarball then it's built in a temp dir and -- the results discarded. BuildAndInstall :: BuildStyle -- | The package is built, but the files are not installed anywhere, rather -- the build dir is kept and the package is registered inplace. -- -- Such packages can still subsequently be installed. -- -- Typically BuildAndInstall packages will only depend on other -- BuildAndInstall style packages and not on -- BuildInplaceOnly ones. BuildInplaceOnly :: BuildStyle type CabalFileText = ByteString -- | Specific targets within a package or component to act on e.g. to -- build, haddock or open a repl. data ComponentTarget ComponentTarget :: ComponentName -> SubComponentTarget -> ComponentTarget -- | Unambiguously render a ComponentTarget, e.g., to pass to a -- Cabal Setup script. showComponentTarget :: PackageId -> ComponentTarget -> String showTestComponentTarget :: PackageId -> ComponentTarget -> Maybe String showBenchComponentTarget :: PackageId -> ComponentTarget -> Maybe String -- | Either the component as a whole or detail about a file or module -- target within a component. data SubComponentTarget -- | The component as a whole WholeComponent :: SubComponentTarget -- | A specific module within a component. ModuleTarget :: ModuleName -> SubComponentTarget -- | A specific file within a component. Note that this does not carry the -- file extension. FileTarget :: FilePath -> SubComponentTarget isSubLibComponentTarget :: ComponentTarget -> Bool isForeignLibComponentTarget :: ComponentTarget -> Bool isExeComponentTarget :: ComponentTarget -> Bool isTestComponentTarget :: ComponentTarget -> Bool isBenchComponentTarget :: ComponentTarget -> Bool componentOptionalStanza :: Component -> Maybe OptionalStanza -- | There are four major cases for Setup.hs handling: -- --
    --
  1. build-type Custom with a custom-setup -- section
  2. --
  3. build-type Custom without a custom-setup -- section
  4. --
  5. build-type not Custom with cabal-version > -- $our-cabal-version
  6. --
  7. build-type not Custom with cabal-version <= -- $our-cabal-version
  8. --
-- -- It's also worth noting that packages specifying cabal-version: -- >= 1.23 or later that have build-type Custom will -- always have a custom-setup section. Therefore in case 2, the -- specified cabal-version will always be less than 1.23. -- -- In cases 1 and 2 we obviously have to build an external Setup.hs -- script, while in case 4 we can use the internal library API. In case 3 -- we also have to build an external Setup.hs script because the package -- needs a later Cabal lib version than we can support internally. data SetupScriptStyle SetupCustomExplicitDeps :: SetupScriptStyle SetupCustomImplicitDeps :: SetupScriptStyle SetupNonCustomExternalLib :: SetupScriptStyle SetupNonCustomInternalLib :: SetupScriptStyle instance GHC.Generics.Generic Distribution.Client.ProjectPlanning.Types.ElaboratedSharedConfig instance GHC.Show.Show Distribution.Client.ProjectPlanning.Types.ElaboratedSharedConfig instance GHC.Generics.Generic Distribution.Client.ProjectPlanning.Types.ElaboratedComponent instance GHC.Show.Show Distribution.Client.ProjectPlanning.Types.ElaboratedComponent instance GHC.Classes.Eq Distribution.Client.ProjectPlanning.Types.ElaboratedComponent instance GHC.Generics.Generic Distribution.Client.ProjectPlanning.Types.ElaboratedPackage instance GHC.Show.Show Distribution.Client.ProjectPlanning.Types.ElaboratedPackage instance GHC.Classes.Eq Distribution.Client.ProjectPlanning.Types.ElaboratedPackage instance GHC.Generics.Generic Distribution.Client.ProjectPlanning.Types.ElaboratedPackageOrComponent instance GHC.Show.Show Distribution.Client.ProjectPlanning.Types.ElaboratedPackageOrComponent instance GHC.Classes.Eq Distribution.Client.ProjectPlanning.Types.ElaboratedPackageOrComponent instance GHC.Generics.Generic Distribution.Client.ProjectPlanning.Types.BuildStyle instance GHC.Show.Show Distribution.Client.ProjectPlanning.Types.BuildStyle instance GHC.Classes.Eq Distribution.Client.ProjectPlanning.Types.BuildStyle instance GHC.Generics.Generic Distribution.Client.ProjectPlanning.Types.ComponentTarget instance GHC.Show.Show Distribution.Client.ProjectPlanning.Types.ComponentTarget instance GHC.Classes.Ord Distribution.Client.ProjectPlanning.Types.ComponentTarget instance GHC.Classes.Eq Distribution.Client.ProjectPlanning.Types.ComponentTarget instance GHC.Generics.Generic Distribution.Client.ProjectPlanning.Types.SetupScriptStyle instance GHC.Show.Show Distribution.Client.ProjectPlanning.Types.SetupScriptStyle instance GHC.Classes.Eq Distribution.Client.ProjectPlanning.Types.SetupScriptStyle instance GHC.Generics.Generic Distribution.Client.ProjectPlanning.Types.ElaboratedConfiguredPackage instance GHC.Show.Show Distribution.Client.ProjectPlanning.Types.ElaboratedConfiguredPackage instance GHC.Classes.Eq Distribution.Client.ProjectPlanning.Types.ElaboratedConfiguredPackage instance Distribution.Package.Package Distribution.Client.ProjectPlanning.Types.ElaboratedConfiguredPackage instance Distribution.Client.Types.ConfiguredId.HasConfiguredId Distribution.Client.ProjectPlanning.Types.ElaboratedConfiguredPackage instance Distribution.Package.HasUnitId Distribution.Client.ProjectPlanning.Types.ElaboratedConfiguredPackage instance Distribution.Compat.Graph.IsNode Distribution.Client.ProjectPlanning.Types.ElaboratedConfiguredPackage instance Data.Binary.Class.Binary Distribution.Client.ProjectPlanning.Types.ElaboratedConfiguredPackage instance Distribution.Utils.Structured.Structured Distribution.Client.ProjectPlanning.Types.ElaboratedConfiguredPackage instance Data.Binary.Class.Binary Distribution.Client.ProjectPlanning.Types.SetupScriptStyle instance Distribution.Utils.Structured.Structured Distribution.Client.ProjectPlanning.Types.SetupScriptStyle instance Data.Binary.Class.Binary Distribution.Client.ProjectPlanning.Types.ComponentTarget instance Distribution.Utils.Structured.Structured Distribution.Client.ProjectPlanning.Types.ComponentTarget instance Data.Binary.Class.Binary Distribution.Client.ProjectPlanning.Types.BuildStyle instance Distribution.Utils.Structured.Structured Distribution.Client.ProjectPlanning.Types.BuildStyle instance GHC.Base.Semigroup Distribution.Client.ProjectPlanning.Types.BuildStyle instance GHC.Base.Monoid Distribution.Client.ProjectPlanning.Types.BuildStyle instance Data.Binary.Class.Binary Distribution.Client.ProjectPlanning.Types.ElaboratedPackageOrComponent instance Distribution.Utils.Structured.Structured Distribution.Client.ProjectPlanning.Types.ElaboratedPackageOrComponent instance Data.Binary.Class.Binary Distribution.Client.ProjectPlanning.Types.ElaboratedPackage instance Distribution.Utils.Structured.Structured Distribution.Client.ProjectPlanning.Types.ElaboratedPackage instance Data.Binary.Class.Binary Distribution.Client.ProjectPlanning.Types.ElaboratedComponent instance Distribution.Utils.Structured.Structured Distribution.Client.ProjectPlanning.Types.ElaboratedComponent instance Data.Binary.Class.Binary Distribution.Client.ProjectPlanning.Types.ElaboratedSharedConfig instance Distribution.Utils.Structured.Structured Distribution.Client.ProjectPlanning.Types.ElaboratedSharedConfig -- | Contains an sdist like function which computes the source -- files that we should track to determine if a rebuild is necessary. -- Unlike sdist, we can operate directly on the true -- PackageDescription (not flattened). -- -- The naming convention, roughly, is that to declare we need the source -- for some type T, you use the function needT; some functions need -- auxiliary information. -- -- We can only use this code for non-Custom scripts; Custom scripts may -- have arbitrary extra dependencies (esp. new preprocessors) which we -- cannot "see" easily. module Distribution.Client.SourceFiles needElaboratedConfiguredPackage :: ElaboratedConfiguredPackage -> Rebuild () module Distribution.Client.ProjectPlanOutput -- | Write out a representation of the elaborated install plan. -- -- This is for the benefit of debugging and external tools like editors. writePlanExternalRepresentation :: DistDirLayout -> ElaboratedInstallPlan -> ElaboratedSharedConfig -> IO () data PostBuildProjectStatus PostBuildProjectStatus :: PackageIdSet -> PackageIdSet -> PackageIdSet -> PackageIdSet -> PackageIdSet -> Graph (Node UnitId ElaboratedPlanPackage) -> PackageIdSet -> PackageIdSet -> PackageIdSet -> PostBuildProjectStatus -- | Packages that are known to be up to date. These were found to be up to -- date before the build, or they have a successful build outcome -- afterwards. -- -- This does not include any packages outside of the subset of the plan -- that was executed because we did not check those and so don't know for -- sure that they're still up to date. [packagesDefinitelyUpToDate] :: PostBuildProjectStatus -> PackageIdSet -- | Packages that are probably still up to date (and at least not known to -- be out of date, and certainly not invalid). This includes -- packagesDefinitelyUpToDate plus packages that were up to date -- previously and are outside of the subset of the plan that was -- executed. It excludes packagesOutOfDate. [packagesProbablyUpToDate] :: PostBuildProjectStatus -> PackageIdSet -- | Packages that are known to be out of date. These are packages that -- were determined to be out of date before the build, and they do not -- have a successful build outcome afterwards. -- -- Note that this can sometimes include packages outside of the subset of -- the plan that was executed. For example suppose package A and B depend -- on C, and A is the target so only A and C are in the subset to be -- built. Now suppose C is found to have changed, then both A and B are -- out-of-date before the build and since B is outside the subset to be -- built then it will remain out of date. -- -- Note also that this is not the inverse of -- packagesDefinitelyUpToDate or packagesProbablyUpToDate. -- There are packages where we have no information (ones that were not in -- the subset of the plan that was executed). [packagesOutOfDate] :: PostBuildProjectStatus -> PackageIdSet -- | Packages that depend on libraries that have changed during the build -- (either build success or failure). -- -- This corresponds to the fact that libraries and dynamic executables -- are invalid once any of the libs they depend on change. -- -- This does include packages that themselves failed (i.e. it is a -- superset of packagesInvalidByFailedBuild). It does not include -- changes in dependencies on executables (i.e. build tools). [packagesInvalidByChangedLibDeps] :: PostBuildProjectStatus -> PackageIdSet -- | Packages that themselves failed during the build (i.e. them directly -- not a dep). -- -- This corresponds to the fact that static executables are invalid in -- unlucky circumstances such as linking failing half way though, or data -- file generation failing. -- -- This is a subset of packagesInvalidByChangedLibDeps. [packagesInvalidByFailedBuild] :: PostBuildProjectStatus -> PackageIdSet -- | A subset of the plan graph, including only dependency-on-library -- edges. That is, dependencies on libraries, not dependencies -- of libraries. This tells us all the libraries that packages -- link to. -- -- This is here as a convenience, as strictly speaking it's not status as -- it's just a function of the original ElaboratedInstallPlan. [packagesLibDepGraph] :: PostBuildProjectStatus -> Graph (Node UnitId ElaboratedPlanPackage) -- | As a convenience for intersection with any of the other -- PackageIdSets to select only packages that are part of the -- project locally (i.e. with a local source dir). [packagesBuildLocal] :: PostBuildProjectStatus -> PackageIdSet -- | As a convenience for intersection with any of the other -- PackageIdSets to select only packages that are being built -- in-place within the project (i.e. not destined for the store). [packagesBuildInplace] :: PostBuildProjectStatus -> PackageIdSet -- | As a convenience for intersection or difference with any -- of the other PackageIdSets to select only packages that were -- pre-installed or already in the store prior to the build. [packagesAlreadyInStore] :: PostBuildProjectStatus -> PackageIdSet updatePostBuildProjectStatus :: Verbosity -> DistDirLayout -> ElaboratedInstallPlan -> BuildStatusMap -> BuildOutcomes -> IO PostBuildProjectStatus -- | Prepare a package environment that includes all the library -- dependencies for a plan. -- -- When running cabal new-exec, we want to set things up so that the -- compiler can find all the right packages (and nothing else). This -- function is intended to do that work. It takes a location where it can -- write files temporarily, in case the compiler wants to learn this -- information via the filesystem, and returns any environment variable -- overrides the compiler needs. createPackageEnvironment :: Verbosity -> FilePath -> ElaboratedInstallPlan -> ElaboratedSharedConfig -> PostBuildProjectStatus -> IO [(String, Maybe String)] writePlanGhcEnvironment :: FilePath -> ElaboratedInstallPlan -> ElaboratedSharedConfig -> PostBuildProjectStatus -> IO (Maybe FilePath) argsEquivalentOfGhcEnvironmentFile :: Compiler -> DistDirLayout -> ElaboratedInstallPlan -> PostBuildProjectStatus -> [String] -- | Handling project configuration. module Distribution.Client.ProjectConfig -- | This type corresponds directly to what can be written in the -- cabal.project file. Other sources of configuration can also -- be injected into this type, such as the user-wide config file and the -- command line of cabal configure or cabal build. -- -- Since it corresponds to the external project file it is an instance of -- Monoid and all the fields can be empty. This also means there -- has to be a step where we resolve configuration. At a minimum -- resolving means applying defaults but it can also mean merging -- information from multiple sources. For example for package-specific -- configuration the project file can specify configuration that applies -- to all local packages, and then additional configuration for a -- specific package. -- -- Future directions: multiple profiles, conditionals. If we add these -- features then the gap between configuration as written in the config -- file and resolved settings we actually use will become even bigger. data ProjectConfig ProjectConfig :: [String] -> [String] -> [SourceRepoList] -> [PackageVersionConstraint] -> ProjectConfigBuildOnly -> ProjectConfigShared -> Set ProjectConfigProvenance -> PackageConfig -> PackageConfig -> MapMappend PackageName PackageConfig -> ProjectConfig -- | Packages in this project, including local dirs, local .cabal files -- local and remote tarballs. When these are file globs, they must match -- at least one package. [projectPackages] :: ProjectConfig -> [String] -- | Like projectConfigPackageGlobs but optional in the -- sense that file globs are allowed to match nothing. The primary use -- case for this is to be able to say optional-packages: */ to -- automagically pick up deps that we unpack locally without erroring -- when there aren't any. [projectPackagesOptional] :: ProjectConfig -> [String] -- | Packages in this project from remote source repositories. [projectPackagesRepo] :: ProjectConfig -> [SourceRepoList] -- | Packages in this project from hackage repositories. [projectPackagesNamed] :: ProjectConfig -> [PackageVersionConstraint] [projectConfigBuildOnly] :: ProjectConfig -> ProjectConfigBuildOnly [projectConfigShared] :: ProjectConfig -> ProjectConfigShared [projectConfigProvenance] :: ProjectConfig -> Set ProjectConfigProvenance -- | Configuration to be applied to *all* packages, whether named in -- `cabal.project` or not. [projectConfigAllPackages] :: ProjectConfig -> PackageConfig -- | Configuration to be applied to *local* packages; i.e., any packages -- which are explicitly named in `cabal.project`. [projectConfigLocalPackages] :: ProjectConfig -> PackageConfig [projectConfigSpecificPackage] :: ProjectConfig -> MapMappend PackageName PackageConfig -- | That part of the project configuration that only affects how we -- build and not the value of the things we build. This means this -- information does not need to be tracked for changes since it does not -- affect the outcome. data ProjectConfigBuildOnly ProjectConfigBuildOnly :: Flag Verbosity -> Flag Bool -> Flag Bool -> Flag Bool -> NubList PathTemplate -> Flag PathTemplate -> Flag ReportLevel -> Flag Bool -> Flag FilePath -> Flag (Maybe Int) -> Flag Bool -> Flag Bool -> Flag Bool -> Flag String -> Flag Bool -> Flag FilePath -> Flag FilePath -> ClientInstallFlags -> ProjectConfigBuildOnly [projectConfigVerbosity] :: ProjectConfigBuildOnly -> Flag Verbosity [projectConfigDryRun] :: ProjectConfigBuildOnly -> Flag Bool [projectConfigOnlyDeps] :: ProjectConfigBuildOnly -> Flag Bool [projectConfigOnlyDownload] :: ProjectConfigBuildOnly -> Flag Bool [projectConfigSummaryFile] :: ProjectConfigBuildOnly -> NubList PathTemplate [projectConfigLogFile] :: ProjectConfigBuildOnly -> Flag PathTemplate [projectConfigBuildReports] :: ProjectConfigBuildOnly -> Flag ReportLevel [projectConfigReportPlanningFailure] :: ProjectConfigBuildOnly -> Flag Bool [projectConfigSymlinkBinDir] :: ProjectConfigBuildOnly -> Flag FilePath [projectConfigNumJobs] :: ProjectConfigBuildOnly -> Flag (Maybe Int) [projectConfigKeepGoing] :: ProjectConfigBuildOnly -> Flag Bool [projectConfigOfflineMode] :: ProjectConfigBuildOnly -> Flag Bool [projectConfigKeepTempFiles] :: ProjectConfigBuildOnly -> Flag Bool [projectConfigHttpTransport] :: ProjectConfigBuildOnly -> Flag String [projectConfigIgnoreExpiry] :: ProjectConfigBuildOnly -> Flag Bool [projectConfigCacheDir] :: ProjectConfigBuildOnly -> Flag FilePath [projectConfigLogsDir] :: ProjectConfigBuildOnly -> Flag FilePath [projectConfigClientInstallFlags] :: ProjectConfigBuildOnly -> ClientInstallFlags -- | Project configuration that is shared between all packages in the -- project. In particular this includes configuration that affects the -- solver. data ProjectConfigShared ProjectConfigShared :: Flag FilePath -> Flag FilePath -> Flag FilePath -> Flag Bool -> Flag CompilerFlavor -> Flag FilePath -> Flag FilePath -> Flag PathTemplate -> InstallDirs (Flag PathTemplate) -> [Maybe PackageDB] -> NubList RemoteRepo -> NubList LocalRepo -> Flag ActiveRepos -> Flag TotalIndexState -> Flag FilePath -> [(UserConstraint, ConstraintSource)] -> [PackageVersionConstraint] -> Flag Version -> Flag PreSolver -> Maybe AllowOlder -> Maybe AllowNewer -> Flag WriteGhcEnvironmentFilesPolicy -> Flag Int -> Flag ReorderGoals -> Flag CountConflicts -> Flag FineGrainedConflicts -> Flag MinimizeConflictSet -> Flag StrongFlags -> Flag AllowBootLibInstalls -> Flag OnlyConstrained -> Flag Bool -> Flag IndependentGoals -> Flag PreferOldest -> NubList FilePath -> ProjectConfigShared [projectConfigDistDir] :: ProjectConfigShared -> Flag FilePath [projectConfigConfigFile] :: ProjectConfigShared -> Flag FilePath [projectConfigProjectFile] :: ProjectConfigShared -> Flag FilePath [projectConfigIgnoreProject] :: ProjectConfigShared -> Flag Bool [projectConfigHcFlavor] :: ProjectConfigShared -> Flag CompilerFlavor [projectConfigHcPath] :: ProjectConfigShared -> Flag FilePath [projectConfigHcPkg] :: ProjectConfigShared -> Flag FilePath [projectConfigHaddockIndex] :: ProjectConfigShared -> Flag PathTemplate [projectConfigInstallDirs] :: ProjectConfigShared -> InstallDirs (Flag PathTemplate) [projectConfigPackageDBs] :: ProjectConfigShared -> [Maybe PackageDB] -- | Available Hackage servers. [projectConfigRemoteRepos] :: ProjectConfigShared -> NubList RemoteRepo [projectConfigLocalNoIndexRepos] :: ProjectConfigShared -> NubList LocalRepo [projectConfigActiveRepos] :: ProjectConfigShared -> Flag ActiveRepos [projectConfigIndexState] :: ProjectConfigShared -> Flag TotalIndexState [projectConfigStoreDir] :: ProjectConfigShared -> Flag FilePath [projectConfigConstraints] :: ProjectConfigShared -> [(UserConstraint, ConstraintSource)] [projectConfigPreferences] :: ProjectConfigShared -> [PackageVersionConstraint] [projectConfigCabalVersion] :: ProjectConfigShared -> Flag Version [projectConfigSolver] :: ProjectConfigShared -> Flag PreSolver [projectConfigAllowOlder] :: ProjectConfigShared -> Maybe AllowOlder [projectConfigAllowNewer] :: ProjectConfigShared -> Maybe AllowNewer [projectConfigWriteGhcEnvironmentFilesPolicy] :: ProjectConfigShared -> Flag WriteGhcEnvironmentFilesPolicy [projectConfigMaxBackjumps] :: ProjectConfigShared -> Flag Int [projectConfigReorderGoals] :: ProjectConfigShared -> Flag ReorderGoals [projectConfigCountConflicts] :: ProjectConfigShared -> Flag CountConflicts [projectConfigFineGrainedConflicts] :: ProjectConfigShared -> Flag FineGrainedConflicts [projectConfigMinimizeConflictSet] :: ProjectConfigShared -> Flag MinimizeConflictSet [projectConfigStrongFlags] :: ProjectConfigShared -> Flag StrongFlags [projectConfigAllowBootLibInstalls] :: ProjectConfigShared -> Flag AllowBootLibInstalls [projectConfigOnlyConstrained] :: ProjectConfigShared -> Flag OnlyConstrained [projectConfigPerComponent] :: ProjectConfigShared -> Flag Bool [projectConfigIndependentGoals] :: ProjectConfigShared -> Flag IndependentGoals [projectConfigPreferOldest] :: ProjectConfigShared -> Flag PreferOldest [projectConfigProgPathExtra] :: ProjectConfigShared -> NubList FilePath -- | Specifies the provenance of project configuration, whether defaults -- were used or if the configuration was read from an explicit file path. data ProjectConfigProvenance -- | The configuration is implicit due to no explicit configuration being -- found. See readProjectConfig for how implicit configuration is -- determined. Implicit :: ProjectConfigProvenance -- | The path the project configuration was explicitly read from. | The -- configuration was explicitly read from the specified FilePath. Explicit :: FilePath -> ProjectConfigProvenance -- | Project configuration that is specific to each package, that is where -- we can in principle have different values for different packages in -- the same project. data PackageConfig PackageConfig :: MapLast String FilePath -> MapMappend String [String] -> NubList FilePath -> FlagAssignment -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag ProfDetailLevel -> Flag ProfDetailLevel -> [String] -> Flag OptimisationLevel -> Flag PathTemplate -> Flag PathTemplate -> [FilePath] -> [FilePath] -> [FilePath] -> [FilePath] -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag DebugInfoLevel -> Flag DumpBuildInfo -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag String -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag FilePath -> Flag Bool -> Flag Bool -> Flag FilePath -> Flag PathTemplate -> Flag PathTemplate -> Flag String -> Flag String -> Flag HaddockTarget -> Flag PathTemplate -> Flag PathTemplate -> Flag TestShowDetails -> Flag Bool -> Flag FilePath -> Flag Bool -> [PathTemplate] -> [PathTemplate] -> PackageConfig [packageConfigProgramPaths] :: PackageConfig -> MapLast String FilePath [packageConfigProgramArgs] :: PackageConfig -> MapMappend String [String] [packageConfigProgramPathExtra] :: PackageConfig -> NubList FilePath [packageConfigFlagAssignment] :: PackageConfig -> FlagAssignment [packageConfigVanillaLib] :: PackageConfig -> Flag Bool [packageConfigSharedLib] :: PackageConfig -> Flag Bool [packageConfigStaticLib] :: PackageConfig -> Flag Bool [packageConfigDynExe] :: PackageConfig -> Flag Bool [packageConfigFullyStaticExe] :: PackageConfig -> Flag Bool [packageConfigProf] :: PackageConfig -> Flag Bool [packageConfigProfLib] :: PackageConfig -> Flag Bool [packageConfigProfExe] :: PackageConfig -> Flag Bool [packageConfigProfDetail] :: PackageConfig -> Flag ProfDetailLevel [packageConfigProfLibDetail] :: PackageConfig -> Flag ProfDetailLevel [packageConfigConfigureArgs] :: PackageConfig -> [String] [packageConfigOptimization] :: PackageConfig -> Flag OptimisationLevel [packageConfigProgPrefix] :: PackageConfig -> Flag PathTemplate [packageConfigProgSuffix] :: PackageConfig -> Flag PathTemplate [packageConfigExtraLibDirs] :: PackageConfig -> [FilePath] [packageConfigExtraLibDirsStatic] :: PackageConfig -> [FilePath] [packageConfigExtraFrameworkDirs] :: PackageConfig -> [FilePath] [packageConfigExtraIncludeDirs] :: PackageConfig -> [FilePath] [packageConfigGHCiLib] :: PackageConfig -> Flag Bool [packageConfigSplitSections] :: PackageConfig -> Flag Bool [packageConfigSplitObjs] :: PackageConfig -> Flag Bool [packageConfigStripExes] :: PackageConfig -> Flag Bool [packageConfigStripLibs] :: PackageConfig -> Flag Bool [packageConfigTests] :: PackageConfig -> Flag Bool [packageConfigBenchmarks] :: PackageConfig -> Flag Bool [packageConfigCoverage] :: PackageConfig -> Flag Bool [packageConfigRelocatable] :: PackageConfig -> Flag Bool [packageConfigDebugInfo] :: PackageConfig -> Flag DebugInfoLevel [packageConfigDumpBuildInfo] :: PackageConfig -> Flag DumpBuildInfo [packageConfigRunTests] :: PackageConfig -> Flag Bool [packageConfigDocumentation] :: PackageConfig -> Flag Bool [packageConfigHaddockHoogle] :: PackageConfig -> Flag Bool [packageConfigHaddockHtml] :: PackageConfig -> Flag Bool [packageConfigHaddockHtmlLocation] :: PackageConfig -> Flag String [packageConfigHaddockForeignLibs] :: PackageConfig -> Flag Bool [packageConfigHaddockExecutables] :: PackageConfig -> Flag Bool [packageConfigHaddockTestSuites] :: PackageConfig -> Flag Bool [packageConfigHaddockBenchmarks] :: PackageConfig -> Flag Bool [packageConfigHaddockInternal] :: PackageConfig -> Flag Bool [packageConfigHaddockCss] :: PackageConfig -> Flag FilePath [packageConfigHaddockLinkedSource] :: PackageConfig -> Flag Bool [packageConfigHaddockQuickJump] :: PackageConfig -> Flag Bool [packageConfigHaddockHscolourCss] :: PackageConfig -> Flag FilePath [packageConfigHaddockContents] :: PackageConfig -> Flag PathTemplate [packageConfigHaddockIndex] :: PackageConfig -> Flag PathTemplate [packageConfigHaddockBaseUrl] :: PackageConfig -> Flag String [packageConfigHaddockLib] :: PackageConfig -> Flag String [packageConfigHaddockForHackage] :: PackageConfig -> Flag HaddockTarget [packageConfigTestHumanLog] :: PackageConfig -> Flag PathTemplate [packageConfigTestMachineLog] :: PackageConfig -> Flag PathTemplate [packageConfigTestShowDetails] :: PackageConfig -> Flag TestShowDetails [packageConfigTestKeepTix] :: PackageConfig -> Flag Bool [packageConfigTestWrapper] :: PackageConfig -> Flag FilePath [packageConfigTestFailWhenNoTestSuites] :: PackageConfig -> Flag Bool [packageConfigTestTestOptions] :: PackageConfig -> [PathTemplate] [packageConfigBenchmarkOptions] :: PackageConfig -> [PathTemplate] -- | Newtype wrapper for Map that provides a Monoid instance -- that takes the last value rather than the first value for overlapping -- keys. newtype MapLast k v MapLast :: Map k v -> MapLast k v [getMapLast] :: MapLast k v -> Map k v -- | Newtype wrapper for Map that provides a Monoid instance -- that mappends values of overlapping keys rather than taking the -- first. newtype MapMappend k v MapMappend :: Map k v -> MapMappend k v [getMapMappend] :: MapMappend k v -> Map k v -- | Find the root of this project. -- -- Searches for an explicit cabal.project file, in the current -- directory or parent directories. If no project file is found then the -- current dir is the project root (and the project will use an implicit -- config). findProjectRoot :: Maybe FilePath -> Maybe FilePath -> IO (Either BadProjectRoot ProjectRoot) -- | Information about the root directory of the project. -- -- It can either be an implicit project root in the current dir if no -- cabal.project file is found, or an explicit root if the file -- is found. data ProjectRoot -- | ProjectRootImplicit :: FilePath -> ProjectRoot -- | ProjectRootExplicit :: FilePath -> FilePath -> ProjectRoot -- | Errors returned by findProjectRoot. data BadProjectRoot BadProjectRootExplicitFile :: FilePath -> BadProjectRoot -- | Read all the config relevant for a project. This includes the project -- file if any, plus other global config. readProjectConfig :: Verbosity -> HttpTransport -> Flag Bool -> Flag FilePath -> DistDirLayout -> Rebuild ProjectConfigSkeleton -- | Read the user's cabal-install config file. readGlobalConfig :: Verbosity -> Flag FilePath -> Rebuild ProjectConfig -- | Reads a cabal.project.local file in the given project root -- dir, or returns empty. This file gets written by cabal -- configure, or in principle can be edited manually or by other -- tools. readProjectLocalExtraConfig :: Verbosity -> HttpTransport -> DistDirLayout -> Rebuild ProjectConfigSkeleton -- | Reads a cabal.project.freeze file in the given project root -- dir, or returns empty. This file gets written by cabal -- freeze, or in principle can be edited manually or by other tools. readProjectLocalFreezeConfig :: Verbosity -> HttpTransport -> DistDirLayout -> Rebuild ProjectConfigSkeleton reportParseResult :: Verbosity -> String -> FilePath -> ParseResult ProjectConfigSkeleton -> IO ProjectConfigSkeleton -- | Render the ProjectConfig format. -- -- For the moment this is implemented in terms of a pretty printer for -- the legacy configuration types, plus a conversion. showProjectConfig :: ProjectConfig -> String withProjectOrGlobalConfig :: Verbosity -> Flag Bool -> Flag FilePath -> IO a -> (ProjectConfig -> IO a) -> IO a -- | Write a cabal.project.local file in the given project root -- dir. writeProjectLocalExtraConfig :: DistDirLayout -> ProjectConfig -> IO () -- | Write a cabal.project.freeze file in the given project root -- dir. writeProjectLocalFreezeConfig :: DistDirLayout -> ProjectConfig -> IO () -- | Write in the cabal.project format to the given file. writeProjectConfigFile :: FilePath -> ProjectConfig -> IO () -- | Convert configuration from the cabal configure or cabal -- build command line into a ProjectConfig value that can -- combined with configuration from other sources. -- -- At the moment this uses the legacy command line flag types. See -- LegacyProjectConfig for an explanation. commandLineFlagsToProjectConfig :: GlobalFlags -> NixStyleFlags a -> ClientInstallFlags -> ProjectConfig -- | The location of a package as part of a project. Local file paths are -- either absolute (if the user specified it as such) or they are -- relative to the project root. data ProjectPackageLocation ProjectPackageLocalCabalFile :: FilePath -> ProjectPackageLocation ProjectPackageLocalDirectory :: FilePath -> FilePath -> ProjectPackageLocation ProjectPackageLocalTarball :: FilePath -> ProjectPackageLocation ProjectPackageRemoteTarball :: URI -> ProjectPackageLocation ProjectPackageRemoteRepo :: SourceRepoList -> ProjectPackageLocation ProjectPackageNamed :: PackageVersionConstraint -> ProjectPackageLocation -- | Exception thrown by findProjectPackages. data BadPackageLocations BadPackageLocations :: Set ProjectConfigProvenance -> [BadPackageLocation] -> BadPackageLocations data BadPackageLocation BadPackageLocationFile :: BadPackageLocationMatch -> BadPackageLocation BadLocGlobEmptyMatch :: String -> BadPackageLocation BadLocGlobBadMatches :: String -> [BadPackageLocationMatch] -> BadPackageLocation BadLocUnexpectedUriScheme :: String -> BadPackageLocation BadLocUnrecognisedUri :: String -> BadPackageLocation BadLocUnrecognised :: String -> BadPackageLocation data BadPackageLocationMatch BadLocUnexpectedFile :: String -> BadPackageLocationMatch BadLocNonexistantFile :: String -> BadPackageLocationMatch BadLocDirNoCabalFile :: String -> BadPackageLocationMatch BadLocDirManyCabalFiles :: String -> BadPackageLocationMatch -- | Given the project config, -- -- Throws BadPackageLocations. findProjectPackages :: DistDirLayout -> ProjectConfig -> Rebuild [ProjectPackageLocation] -- | Read the .cabal files for a set of packages. For remote -- tarballs and VCS source repos this also fetches them if needed. -- -- Note here is where we convert from project-root relative paths to -- absolute paths. fetchAndReadSourcePackages :: Verbosity -> DistDirLayout -> ProjectConfigShared -> ProjectConfigBuildOnly -> [ProjectPackageLocation] -> Rebuild [PackageSpecifier (SourcePackage UnresolvedPkgLoc)] -- | Look up a PackageConfig field in the ProjectConfig for a -- specific PackageName. This returns the configuration that -- applies to all local packages plus any package-specific configuration -- for this package. lookupLocalPackageConfig :: (Semigroup a, Monoid a) => (PackageConfig -> a) -> ProjectConfig -> PackageName -> a -- | Use a RepoContext based on the BuildTimeSettings. projectConfigWithBuilderRepoContext :: Verbosity -> BuildTimeSettings -> (RepoContext -> IO a) -> IO a -- | Use a RepoContext, but only for the solver. The solver does not -- use the full facilities of the RepoContext so we can get away -- with making one that doesn't have an http transport. And that avoids -- having to have access to the BuildTimeSettings projectConfigWithSolverRepoContext :: Verbosity -> ProjectConfigShared -> ProjectConfigBuildOnly -> (RepoContext -> IO a) -> IO a -- | Resolved configuration for the solver. The idea is that this is easier -- to use than the raw configuration because in the raw configuration -- everything is optional (monoidial). In the BuildTimeSettings -- every field is filled in, if only with the defaults. -- -- Use resolveSolverSettings to make one from the project config -- (by applying defaults etc). data SolverSettings SolverSettings :: [RemoteRepo] -> [LocalRepo] -> [(UserConstraint, ConstraintSource)] -> [PackageVersionConstraint] -> FlagAssignment -> Map PackageName FlagAssignment -> Maybe Version -> PreSolver -> AllowOlder -> AllowNewer -> Maybe Int -> ReorderGoals -> CountConflicts -> FineGrainedConflicts -> MinimizeConflictSet -> StrongFlags -> AllowBootLibInstalls -> OnlyConstrained -> Maybe TotalIndexState -> Maybe ActiveRepos -> IndependentGoals -> PreferOldest -> SolverSettings -- | Available Hackage servers. [solverSettingRemoteRepos] :: SolverSettings -> [RemoteRepo] [solverSettingLocalNoIndexRepos] :: SolverSettings -> [LocalRepo] [solverSettingConstraints] :: SolverSettings -> [(UserConstraint, ConstraintSource)] [solverSettingPreferences] :: SolverSettings -> [PackageVersionConstraint] -- | For all local packages [solverSettingFlagAssignment] :: SolverSettings -> FlagAssignment [solverSettingFlagAssignments] :: SolverSettings -> Map PackageName FlagAssignment [solverSettingCabalVersion] :: SolverSettings -> Maybe Version [solverSettingSolver] :: SolverSettings -> PreSolver [solverSettingAllowOlder] :: SolverSettings -> AllowOlder [solverSettingAllowNewer] :: SolverSettings -> AllowNewer [solverSettingMaxBackjumps] :: SolverSettings -> Maybe Int [solverSettingReorderGoals] :: SolverSettings -> ReorderGoals [solverSettingCountConflicts] :: SolverSettings -> CountConflicts [solverSettingFineGrainedConflicts] :: SolverSettings -> FineGrainedConflicts [solverSettingMinimizeConflictSet] :: SolverSettings -> MinimizeConflictSet [solverSettingStrongFlags] :: SolverSettings -> StrongFlags [solverSettingAllowBootLibInstalls] :: SolverSettings -> AllowBootLibInstalls [solverSettingOnlyConstrained] :: SolverSettings -> OnlyConstrained [solverSettingIndexState] :: SolverSettings -> Maybe TotalIndexState [solverSettingActiveRepos] :: SolverSettings -> Maybe ActiveRepos [solverSettingIndependentGoals] :: SolverSettings -> IndependentGoals [solverSettingPreferOldest] :: SolverSettings -> PreferOldest -- | Resolve the project configuration, with all its optional fields, into -- SolverSettings with no optional fields (by applying defaults). resolveSolverSettings :: ProjectConfig -> SolverSettings -- | Resolved configuration for things that affect how we build and not the -- value of the things we build. The idea is that this is easier to use -- than the raw configuration because in the raw configuration everything -- is optional (monoidial). In the BuildTimeSettings every field -- is filled in, if only with the defaults. -- -- Use resolveBuildTimeSettings to make one from the project -- config (by applying defaults etc). data BuildTimeSettings BuildTimeSettings :: Bool -> Bool -> Bool -> [PathTemplate] -> Maybe (Compiler -> Platform -> PackageId -> UnitId -> FilePath) -> Verbosity -> ReportLevel -> Bool -> [FilePath] -> Int -> Bool -> Bool -> Bool -> [RemoteRepo] -> [LocalRepo] -> FilePath -> Maybe String -> Bool -> [FilePath] -> Bool -> BuildTimeSettings [buildSettingDryRun] :: BuildTimeSettings -> Bool [buildSettingOnlyDeps] :: BuildTimeSettings -> Bool [buildSettingOnlyDownload] :: BuildTimeSettings -> Bool [buildSettingSummaryFile] :: BuildTimeSettings -> [PathTemplate] [buildSettingLogFile] :: BuildTimeSettings -> Maybe (Compiler -> Platform -> PackageId -> UnitId -> FilePath) [buildSettingLogVerbosity] :: BuildTimeSettings -> Verbosity [buildSettingBuildReports] :: BuildTimeSettings -> ReportLevel [buildSettingReportPlanningFailure] :: BuildTimeSettings -> Bool [buildSettingSymlinkBinDir] :: BuildTimeSettings -> [FilePath] [buildSettingNumJobs] :: BuildTimeSettings -> Int [buildSettingKeepGoing] :: BuildTimeSettings -> Bool [buildSettingOfflineMode] :: BuildTimeSettings -> Bool [buildSettingKeepTempFiles] :: BuildTimeSettings -> Bool [buildSettingRemoteRepos] :: BuildTimeSettings -> [RemoteRepo] [buildSettingLocalNoIndexRepos] :: BuildTimeSettings -> [LocalRepo] [buildSettingCacheDir] :: BuildTimeSettings -> FilePath [buildSettingHttpTransport] :: BuildTimeSettings -> Maybe String [buildSettingIgnoreExpiry] :: BuildTimeSettings -> Bool [buildSettingProgPathExtra] :: BuildTimeSettings -> [FilePath] [buildSettingHaddockOpen] :: BuildTimeSettings -> Bool -- | Resolve the project configuration, with all its optional fields, into -- BuildTimeSettings with no optional fields (by applying -- defaults). resolveBuildTimeSettings :: Verbosity -> CabalDirLayout -> ProjectConfig -> BuildTimeSettings -- | The project configuration is not allowed to specify program locations -- for programs used by the compiler as these have to be the same for -- each set of packages. -- -- We cannot check this until we know which programs the compiler uses, -- which in principle is not until we've configured the compiler. -- -- Throws BadPerPackageCompilerPaths checkBadPerPackageCompilerPaths :: [ConfiguredProgram] -> Map PackageName PackageConfig -> IO () data BadPerPackageCompilerPaths BadPerPackageCompilerPaths :: [(PackageName, String)] -> BadPerPackageCompilerPaths instance GHC.Show.Show Distribution.Client.ProjectConfig.BadProjectRoot instance GHC.Show.Show Distribution.Client.ProjectConfig.ProjectPackageLocation instance GHC.Show.Show Distribution.Client.ProjectConfig.BadPackageLocationMatch instance GHC.Show.Show Distribution.Client.ProjectConfig.BadPackageLocation instance GHC.Show.Show Distribution.Client.ProjectConfig.BadPackageLocations instance GHC.Show.Show Distribution.Client.ProjectConfig.CabalFileSearchFailure instance GHC.Show.Show Distribution.Client.ProjectConfig.BadPerPackageCompilerPaths instance GHC.Exception.Type.Exception Distribution.Client.ProjectConfig.BadPerPackageCompilerPaths instance GHC.Exception.Type.Exception Distribution.Client.ProjectConfig.CabalFileSearchFailure instance GHC.Show.Show Distribution.Client.ProjectConfig.CabalFileParseError instance GHC.Exception.Type.Exception Distribution.Client.ProjectConfig.CabalFileParseError instance GHC.Exception.Type.Exception Distribution.Client.ProjectConfig.BadPackageLocations instance GHC.Exception.Type.Exception Distribution.Client.ProjectConfig.BadProjectRoot -- | Planning how to build everything in a project. module Distribution.Client.ProjectPlanning -- | The combination of an elaborated install plan plus a -- ElaboratedSharedConfig contains all the details necessary to be -- able to execute the plan without having to make further policy -- decisions. -- -- It does not include dynamic elements such as resources (such as http -- connections). type ElaboratedInstallPlan = GenericInstallPlan InstalledPackageInfo ElaboratedConfiguredPackage data ElaboratedConfiguredPackage ElaboratedConfiguredPackage :: UnitId -> ComponentId -> Map ModuleName Module -> Map ModuleName OpenModule -> Bool -> PackageId -> ModuleShape -> FlagAssignment -> FlagAssignment -> PackageDescription -> PackageLocation (Maybe FilePath) -> Maybe PackageSourceHash -> Bool -> BuildStyle -> ComponentRequestedSpec -> OptionalStanzaSet -> OptionalStanzaMap (Maybe Bool) -> [Maybe PackageDB] -> PackageDBStack -> PackageDBStack -> PackageDBStack -> PackageDBStack -> PackageDBStack -> PackageDBStack -> Maybe CabalFileText -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> ProfDetailLevel -> ProfDetailLevel -> Bool -> OptimisationLevel -> Bool -> Bool -> Bool -> Bool -> DebugInfoLevel -> DumpBuildInfo -> Map String FilePath -> Map String [String] -> [FilePath] -> [String] -> [FilePath] -> [FilePath] -> [FilePath] -> [FilePath] -> Maybe PathTemplate -> Maybe PathTemplate -> InstallDirs FilePath -> Bool -> Bool -> Maybe String -> Bool -> HaddockTarget -> Bool -> Bool -> Bool -> Bool -> Maybe FilePath -> Bool -> Bool -> Maybe FilePath -> Maybe PathTemplate -> Maybe PathTemplate -> Maybe String -> Maybe String -> Maybe PathTemplate -> Maybe PathTemplate -> Maybe TestShowDetails -> Bool -> Maybe FilePath -> Bool -> [PathTemplate] -> [PathTemplate] -> SetupScriptStyle -> Version -> [ComponentTarget] -> [ComponentTarget] -> [ComponentTarget] -> [ComponentTarget] -> Maybe ComponentTarget -> [ComponentTarget] -> Bool -> ElaboratedPackageOrComponent -> ElaboratedConfiguredPackage -- | The UnitId which uniquely identifies this item in a build plan [elabUnitId] :: ElaboratedConfiguredPackage -> UnitId [elabComponentId] :: ElaboratedConfiguredPackage -> ComponentId [elabInstantiatedWith] :: ElaboratedConfiguredPackage -> Map ModuleName Module [elabLinkedInstantiatedWith] :: ElaboratedConfiguredPackage -> Map ModuleName OpenModule -- | This is true if this is an indefinite package, or this is a package -- with no signatures. (Notably, it's not true for instantiated -- packages.) The motivation for this is if you ask to build -- foo-indef, this probably means that you want to typecheck it, -- NOT that you want to rebuild all of the various instantiations of it. [elabIsCanonical] :: ElaboratedConfiguredPackage -> Bool -- | The PackageId of the originating package [elabPkgSourceId] :: ElaboratedConfiguredPackage -> PackageId -- | Shape of the package/component, for Backpack. [elabModuleShape] :: ElaboratedConfiguredPackage -> ModuleShape -- | A total flag assignment for the package. TODO: Actually this can be -- per-component if we drop all flags that don't affect a component. [elabFlagAssignment] :: ElaboratedConfiguredPackage -> FlagAssignment -- | The original default flag assignment, used only for reporting. [elabFlagDefaults] :: ElaboratedConfiguredPackage -> FlagAssignment [elabPkgDescription] :: ElaboratedConfiguredPackage -> PackageDescription -- | Where the package comes from, e.g. tarball, local dir etc. This is not -- the same as where it may be unpacked to for the build. [elabPkgSourceLocation] :: ElaboratedConfiguredPackage -> PackageLocation (Maybe FilePath) -- | The hash of the source, e.g. the tarball. We don't have this for local -- source dir packages. [elabPkgSourceHash] :: ElaboratedConfiguredPackage -> Maybe PackageSourceHash -- | Is this package one of the ones specified by location in the project -- file? (As opposed to a dependency, or a named package pulled in) [elabLocalToProject] :: ElaboratedConfiguredPackage -> Bool -- | Are we going to build and install this package to the store, or are we -- going to build it and register it locally. [elabBuildStyle] :: ElaboratedConfiguredPackage -> BuildStyle -- | Another way of phrasing pkgStanzasAvailable. [elabEnabledSpec] :: ElaboratedConfiguredPackage -> ComponentRequestedSpec -- | Which optional stanzas (ie testsuites, benchmarks) can be built. This -- means the solver produced a plan that has them available. This doesn't -- necessary mean we build them by default. [elabStanzasAvailable] :: ElaboratedConfiguredPackage -> OptionalStanzaSet -- | Which optional stanzas the user explicitly asked to enable or to -- disable. This tells us which ones we build by default, and helps with -- error messages when the user asks to build something they explicitly -- disabled. -- -- TODO: The Bool here should be refined into an ADT with three -- cases: NotRequested, ExplicitlyRequested and ImplicitlyRequested. A -- stanza is explicitly requested if the user asked, for this *specific* -- package, that the stanza be enabled; it's implicitly requested if the -- user asked for all global packages to have this stanza enabled. The -- difference between an explicit and implicit request is error reporting -- behavior: if a user asks for tests to be enabled for a specific -- package that doesn't have any tests, we should warn them about it, but -- we shouldn't complain that a user enabled tests globally, and some -- local packages just happen not to have any tests. (But perhaps we -- should warn if ALL local packages don't have any tests.) [elabStanzasRequested] :: ElaboratedConfiguredPackage -> OptionalStanzaMap (Maybe Bool) [elabPackageDbs] :: ElaboratedConfiguredPackage -> [Maybe PackageDB] [elabSetupPackageDBStack] :: ElaboratedConfiguredPackage -> PackageDBStack [elabBuildPackageDBStack] :: ElaboratedConfiguredPackage -> PackageDBStack [elabRegisterPackageDBStack] :: ElaboratedConfiguredPackage -> PackageDBStack [elabInplaceSetupPackageDBStack] :: ElaboratedConfiguredPackage -> PackageDBStack [elabInplaceBuildPackageDBStack] :: ElaboratedConfiguredPackage -> PackageDBStack [elabInplaceRegisterPackageDBStack] :: ElaboratedConfiguredPackage -> PackageDBStack [elabPkgDescriptionOverride] :: ElaboratedConfiguredPackage -> Maybe CabalFileText [elabVanillaLib] :: ElaboratedConfiguredPackage -> Bool [elabSharedLib] :: ElaboratedConfiguredPackage -> Bool [elabStaticLib] :: ElaboratedConfiguredPackage -> Bool [elabDynExe] :: ElaboratedConfiguredPackage -> Bool [elabFullyStaticExe] :: ElaboratedConfiguredPackage -> Bool [elabGHCiLib] :: ElaboratedConfiguredPackage -> Bool [elabProfLib] :: ElaboratedConfiguredPackage -> Bool [elabProfExe] :: ElaboratedConfiguredPackage -> Bool [elabProfLibDetail] :: ElaboratedConfiguredPackage -> ProfDetailLevel [elabProfExeDetail] :: ElaboratedConfiguredPackage -> ProfDetailLevel [elabCoverage] :: ElaboratedConfiguredPackage -> Bool [elabOptimization] :: ElaboratedConfiguredPackage -> OptimisationLevel [elabSplitObjs] :: ElaboratedConfiguredPackage -> Bool [elabSplitSections] :: ElaboratedConfiguredPackage -> Bool [elabStripLibs] :: ElaboratedConfiguredPackage -> Bool [elabStripExes] :: ElaboratedConfiguredPackage -> Bool [elabDebugInfo] :: ElaboratedConfiguredPackage -> DebugInfoLevel [elabDumpBuildInfo] :: ElaboratedConfiguredPackage -> DumpBuildInfo [elabProgramPaths] :: ElaboratedConfiguredPackage -> Map String FilePath [elabProgramArgs] :: ElaboratedConfiguredPackage -> Map String [String] [elabProgramPathExtra] :: ElaboratedConfiguredPackage -> [FilePath] [elabConfigureScriptArgs] :: ElaboratedConfiguredPackage -> [String] [elabExtraLibDirs] :: ElaboratedConfiguredPackage -> [FilePath] [elabExtraLibDirsStatic] :: ElaboratedConfiguredPackage -> [FilePath] [elabExtraFrameworkDirs] :: ElaboratedConfiguredPackage -> [FilePath] [elabExtraIncludeDirs] :: ElaboratedConfiguredPackage -> [FilePath] [elabProgPrefix] :: ElaboratedConfiguredPackage -> Maybe PathTemplate [elabProgSuffix] :: ElaboratedConfiguredPackage -> Maybe PathTemplate [elabInstallDirs] :: ElaboratedConfiguredPackage -> InstallDirs FilePath [elabHaddockHoogle] :: ElaboratedConfiguredPackage -> Bool [elabHaddockHtml] :: ElaboratedConfiguredPackage -> Bool [elabHaddockHtmlLocation] :: ElaboratedConfiguredPackage -> Maybe String [elabHaddockForeignLibs] :: ElaboratedConfiguredPackage -> Bool [elabHaddockForHackage] :: ElaboratedConfiguredPackage -> HaddockTarget [elabHaddockExecutables] :: ElaboratedConfiguredPackage -> Bool [elabHaddockTestSuites] :: ElaboratedConfiguredPackage -> Bool [elabHaddockBenchmarks] :: ElaboratedConfiguredPackage -> Bool [elabHaddockInternal] :: ElaboratedConfiguredPackage -> Bool [elabHaddockCss] :: ElaboratedConfiguredPackage -> Maybe FilePath [elabHaddockLinkedSource] :: ElaboratedConfiguredPackage -> Bool [elabHaddockQuickJump] :: ElaboratedConfiguredPackage -> Bool [elabHaddockHscolourCss] :: ElaboratedConfiguredPackage -> Maybe FilePath [elabHaddockContents] :: ElaboratedConfiguredPackage -> Maybe PathTemplate [elabHaddockIndex] :: ElaboratedConfiguredPackage -> Maybe PathTemplate [elabHaddockBaseUrl] :: ElaboratedConfiguredPackage -> Maybe String [elabHaddockLib] :: ElaboratedConfiguredPackage -> Maybe String [elabTestMachineLog] :: ElaboratedConfiguredPackage -> Maybe PathTemplate [elabTestHumanLog] :: ElaboratedConfiguredPackage -> Maybe PathTemplate [elabTestShowDetails] :: ElaboratedConfiguredPackage -> Maybe TestShowDetails [elabTestKeepTix] :: ElaboratedConfiguredPackage -> Bool [elabTestWrapper] :: ElaboratedConfiguredPackage -> Maybe FilePath [elabTestFailWhenNoTestSuites] :: ElaboratedConfiguredPackage -> Bool [elabTestTestOptions] :: ElaboratedConfiguredPackage -> [PathTemplate] [elabBenchmarkOptions] :: ElaboratedConfiguredPackage -> [PathTemplate] -- | One of four modes for how we build and interact with the Setup.hs -- script, based on whether it's a build-type Custom, with or without -- explicit deps and the cabal spec version the .cabal file needs. [elabSetupScriptStyle] :: ElaboratedConfiguredPackage -> SetupScriptStyle -- | The version of the Cabal command line interface that we are using for -- this package. This is typically the version of the Cabal lib that the -- Setup.hs is built against. -- -- TODO: We might want to turn this into a enum, yet different enum than -- CabalSpecVersion. [elabSetupScriptCliVersion] :: ElaboratedConfiguredPackage -> Version [elabConfigureTargets] :: ElaboratedConfiguredPackage -> [ComponentTarget] [elabBuildTargets] :: ElaboratedConfiguredPackage -> [ComponentTarget] [elabTestTargets] :: ElaboratedConfiguredPackage -> [ComponentTarget] [elabBenchTargets] :: ElaboratedConfiguredPackage -> [ComponentTarget] [elabReplTarget] :: ElaboratedConfiguredPackage -> Maybe ComponentTarget [elabHaddockTargets] :: ElaboratedConfiguredPackage -> [ComponentTarget] [elabBuildHaddocks] :: ElaboratedConfiguredPackage -> Bool -- | Component/package specific information [elabPkgOrComp] :: ElaboratedConfiguredPackage -> ElaboratedPackageOrComponent type ElaboratedPlanPackage = GenericPlanPackage InstalledPackageInfo ElaboratedConfiguredPackage data ElaboratedSharedConfig ElaboratedSharedConfig :: Platform -> Compiler -> ProgramDb -> ReplOptions -> ElaboratedSharedConfig [pkgConfigPlatform] :: ElaboratedSharedConfig -> Platform [pkgConfigCompiler] :: ElaboratedSharedConfig -> Compiler -- | The programs that the compiler configured (e.g. for GHC, the progs ghc -- & ghc-pkg). Once constructed, only the configuredPrograms -- are used. [pkgConfigCompilerProgs] :: ElaboratedSharedConfig -> ProgramDb [pkgConfigReplOptions] :: ElaboratedSharedConfig -> ReplOptions type ElaboratedReadyPackage = GenericReadyPackage ElaboratedConfiguredPackage -- | This is used in the install plan to indicate how the package will be -- built. data BuildStyle -- | The classic approach where the package is built, then the files -- installed into some location and the result registered in a package -- db. -- -- If the package came from a tarball then it's built in a temp dir and -- the results discarded. BuildAndInstall :: BuildStyle -- | The package is built, but the files are not installed anywhere, rather -- the build dir is kept and the package is registered inplace. -- -- Such packages can still subsequently be installed. -- -- Typically BuildAndInstall packages will only depend on other -- BuildAndInstall style packages and not on -- BuildInplaceOnly ones. BuildInplaceOnly :: BuildStyle type CabalFileText = ByteString -- | Return the up-to-date project config and information about the local -- packages within the project. rebuildProjectConfig :: Verbosity -> HttpTransport -> DistDirLayout -> ProjectConfig -> IO (ProjectConfig, [PackageSpecifier UnresolvedSourcePackage]) -- | Return an up-to-date elaborated install plan. -- -- Two variants of the install plan are returned: with and without -- packages from the store. That is, the "improved" plan where source -- packages are replaced by pre-existing installed packages from the -- store (when their ids match), and also the original elaborated plan -- which uses primarily source packages. rebuildInstallPlan :: Verbosity -> DistDirLayout -> CabalDirLayout -> ProjectConfig -> [PackageSpecifier UnresolvedSourcePackage] -> Maybe InstalledPackageIndex -> IO (ElaboratedInstallPlan, ElaboratedInstallPlan, ElaboratedSharedConfig, TotalIndexState, ActiveRepos) -- | Given the install plan, produce the set of AvailableTargets for -- each package-component pair. -- -- Typically there will only be one such target for each component, but -- for example if we have a plan with both normal and profiling variants -- of a component then we would get both as available targets, or -- similarly if we had a plan that contained two instances of the same -- version of a package. This approach makes it relatively easy to select -- all instances/variants of a component. availableTargets :: ElaboratedInstallPlan -> Map (PackageId, ComponentName) [AvailableTarget (UnitId, ComponentName)] -- | An available target represents a component within a package that a -- user command could plausibly refer to. In this sense, all the -- components defined within the package are things the user could refer -- to, whether or not it would actually be possible to build that -- component. -- -- In particular the available target contains an -- AvailableTargetStatus which informs us about whether it's -- actually possible to select this component to be built, and if not why -- not. This detail makes it possible for command implementations (like -- build, test etc) to accurately report why a target -- cannot be used. -- -- Note that the type parameter is used to help enforce that command -- implementations can only select targets that can actually be built (by -- forcing them to return the k value for the selected targets). -- In particular resolveTargets makes use of this (with -- k as (UnitId, ComponentName')) to identify -- the targets thus selected. data AvailableTarget k AvailableTarget :: PackageId -> ComponentName -> AvailableTargetStatus k -> Bool -> AvailableTarget k [availableTargetPackageId] :: AvailableTarget k -> PackageId [availableTargetComponentName] :: AvailableTarget k -> ComponentName [availableTargetStatus] :: AvailableTarget k -> AvailableTargetStatus k [availableTargetLocalToProject] :: AvailableTarget k -> Bool -- | The status of a an AvailableTarget component. This tells us -- whether it's actually possible to select this component to be built, -- and if not why not. data AvailableTargetStatus k -- | When the user does tests: False TargetDisabledByUser :: AvailableTargetStatus k -- | When the solver could not enable tests TargetDisabledBySolver :: AvailableTargetStatus k -- | When the component has buildable: False TargetNotBuildable :: AvailableTargetStatus k -- | When the component is non-core in a non-local package TargetNotLocal :: AvailableTargetStatus k -- | The target can or should be built TargetBuildable :: k -> TargetRequested -> AvailableTargetStatus k -- | This tells us whether a target ought to be built by default, or only -- if specifically requested. The policy is that components like -- libraries and executables are built by default by build, but -- test suites and benchmarks are not, unless this is overridden in the -- project configuration. data TargetRequested -- | To be built by default TargetRequestedByDefault :: TargetRequested -- | Not to be built by default TargetNotRequestedByDefault :: TargetRequested -- | Specific targets within a package or component to act on e.g. to -- build, haddock or open a repl. data ComponentTarget ComponentTarget :: ComponentName -> SubComponentTarget -> ComponentTarget -- | Either the component as a whole or detail about a file or module -- target within a component. data SubComponentTarget -- | The component as a whole WholeComponent :: SubComponentTarget -- | A specific module within a component. ModuleTarget :: ModuleName -> SubComponentTarget -- | A specific file within a component. Note that this does not carry the -- file extension. FileTarget :: FilePath -> SubComponentTarget -- | Unambiguously render a ComponentTarget, e.g., to pass to a -- Cabal Setup script. showComponentTarget :: PackageId -> ComponentTarget -> String -- | Merge component targets that overlap each other. Specially when we -- have multiple targets for the same component and one of them refers to -- the whole component (rather than a module or file within) then all the -- other targets for that component are subsumed. -- -- We also allow for information associated with each component target, -- and whenever we targets subsume each other we aggregate their -- associated info. nubComponentTargets :: [(ComponentTarget, a)] -> [(ComponentTarget, NonEmpty a)] -- | Given a set of per-package/per-component targets, take the subset of -- the install plan needed to build those targets. Also, update the -- package config to specify which optional stanzas to enable, and which -- targets within each package to build. -- -- NB: Pruning happens after improvement, which is important because we -- will prune differently depending on what is already installed (to -- implement "sticky" test suite enabling behavior). pruneInstallPlanToTargets :: TargetAction -> Map UnitId [ComponentTarget] -> ElaboratedInstallPlan -> ElaboratedInstallPlan -- | How pruneInstallPlanToTargets should interpret the per-package -- ComponentTargets: as build, repl or haddock targets. data TargetAction TargetActionConfigure :: TargetAction TargetActionBuild :: TargetAction TargetActionRepl :: TargetAction TargetActionTest :: TargetAction TargetActionBench :: TargetAction TargetActionHaddock :: TargetAction -- | Try to remove the given targets from the install plan. -- -- This is not always possible. pruneInstallPlanToDependencies :: Set UnitId -> ElaboratedInstallPlan -> Either CannotPruneDependencies ElaboratedInstallPlan -- | It is not always possible to prune to only the dependencies of a set -- of targets. It may be the case that removing a package leaves -- something else that still needed the pruned package. -- -- This lists all the packages that would be broken, and their -- dependencies that would be missing if we did prune. newtype CannotPruneDependencies CannotPruneDependencies :: [(ElaboratedPlanPackage, [ElaboratedPlanPackage])] -> CannotPruneDependencies pkgHasEphemeralBuildTargets :: ElaboratedConfiguredPackage -> Bool -- | The components that we'll build all of, meaning that after they're -- built we can skip building them again (unlike with building just some -- modules or other files within a component). elabBuildTargetWholeComponents :: ElaboratedConfiguredPackage -> Set ComponentName configureCompiler :: Verbosity -> DistDirLayout -> ProjectConfig -> Rebuild (Compiler, Platform, ProgramDb) setupHsScriptOptions :: ElaboratedReadyPackage -> ElaboratedInstallPlan -> ElaboratedSharedConfig -> DistDirLayout -> FilePath -> FilePath -> Bool -> Lock -> SetupScriptOptions setupHsConfigureFlags :: ElaboratedReadyPackage -> ElaboratedSharedConfig -> Verbosity -> FilePath -> ConfigFlags setupHsConfigureArgs :: ElaboratedConfiguredPackage -> [String] setupHsBuildFlags :: ElaboratedConfiguredPackage -> ElaboratedSharedConfig -> Verbosity -> FilePath -> BuildFlags setupHsBuildArgs :: ElaboratedConfiguredPackage -> [String] setupHsReplFlags :: ElaboratedConfiguredPackage -> ElaboratedSharedConfig -> Verbosity -> FilePath -> ReplFlags setupHsReplArgs :: ElaboratedConfiguredPackage -> [String] setupHsTestFlags :: ElaboratedConfiguredPackage -> ElaboratedSharedConfig -> Verbosity -> FilePath -> TestFlags setupHsTestArgs :: ElaboratedConfiguredPackage -> [String] setupHsBenchFlags :: ElaboratedConfiguredPackage -> ElaboratedSharedConfig -> Verbosity -> FilePath -> BenchmarkFlags setupHsBenchArgs :: ElaboratedConfiguredPackage -> [String] setupHsCopyFlags :: ElaboratedConfiguredPackage -> ElaboratedSharedConfig -> Verbosity -> FilePath -> FilePath -> CopyFlags setupHsRegisterFlags :: ElaboratedConfiguredPackage -> ElaboratedSharedConfig -> Verbosity -> FilePath -> FilePath -> RegisterFlags setupHsHaddockFlags :: ElaboratedConfiguredPackage -> ElaboratedSharedConfig -> Verbosity -> FilePath -> HaddockFlags setupHsHaddockArgs :: ElaboratedConfiguredPackage -> [String] packageHashInputs :: ElaboratedSharedConfig -> ElaboratedConfiguredPackage -> PackageHashInputs -- | The path to the directory that contains a specific executable. NB: For -- inplace NOT InstallPaths.bindir installDirs; for an inplace build -- those values are utter nonsense. So we have to guess where the -- directory is going to be. Fortunately this is "stable" part of Cabal -- API. But the way we get the build directory is A HORRIBLE HACK. binDirectoryFor :: DistDirLayout -> ElaboratedSharedConfig -> ElaboratedConfiguredPackage -> FilePath -> FilePath -- | Get the bin/ directories that a package's executables should reside -- in. -- -- The result may be empty if the package does not build any executables. -- -- The result may have several entries if this is an inplace build of a -- package with multiple executables. binDirectories :: DistDirLayout -> ElaboratedSharedConfig -> ElaboratedConfiguredPackage -> [FilePath] storePackageInstallDirs :: StoreDirLayout -> CompilerId -> InstalledPackageId -> InstallDirs FilePath storePackageInstallDirs' :: StoreDirLayout -> CompilerId -> UnitId -> InstallDirs FilePath instance GHC.Show.Show Distribution.Client.ProjectPlanning.TargetRequested instance GHC.Classes.Ord Distribution.Client.ProjectPlanning.TargetRequested instance GHC.Classes.Eq Distribution.Client.ProjectPlanning.TargetRequested instance GHC.Base.Functor Distribution.Client.ProjectPlanning.AvailableTargetStatus instance GHC.Show.Show k => GHC.Show.Show (Distribution.Client.ProjectPlanning.AvailableTargetStatus k) instance GHC.Classes.Ord k => GHC.Classes.Ord (Distribution.Client.ProjectPlanning.AvailableTargetStatus k) instance GHC.Classes.Eq k => GHC.Classes.Eq (Distribution.Client.ProjectPlanning.AvailableTargetStatus k) instance GHC.Base.Functor Distribution.Client.ProjectPlanning.AvailableTarget instance GHC.Show.Show k => GHC.Show.Show (Distribution.Client.ProjectPlanning.AvailableTarget k) instance GHC.Classes.Eq k => GHC.Classes.Eq (Distribution.Client.ProjectPlanning.AvailableTarget k) instance GHC.Show.Show Distribution.Client.ProjectPlanning.CannotPruneDependencies instance Distribution.Package.Package Distribution.Client.ProjectPlanning.PrunedPackage instance Distribution.Package.HasUnitId Distribution.Client.ProjectPlanning.PrunedPackage instance Distribution.Compat.Graph.IsNode Distribution.Client.ProjectPlanning.PrunedPackage instance Distribution.Package.Package Distribution.Client.ProjectPlanning.NonSetupLibDepSolverPlanPackage instance Distribution.Compat.Graph.IsNode Distribution.Client.ProjectPlanning.NonSetupLibDepSolverPlanPackage module Distribution.Client.TargetProblem -- | Target problems that occur during project orchestration. data TargetProblem a TargetNotInProject :: PackageName -> TargetProblem a TargetAvailableInIndex :: PackageName -> TargetProblem a TargetComponentNotProjectLocal :: PackageId -> ComponentName -> SubComponentTarget -> TargetProblem a TargetComponentNotBuildable :: PackageId -> ComponentName -> SubComponentTarget -> TargetProblem a TargetOptionalStanzaDisabledByUser :: PackageId -> ComponentName -> SubComponentTarget -> TargetProblem a TargetOptionalStanzaDisabledBySolver :: PackageId -> ComponentName -> SubComponentTarget -> TargetProblem a TargetProblemUnknownComponent :: PackageName -> Either UnqualComponentName ComponentName -> TargetProblem a -- | The TargetSelector matches component (testbenchmark...) -- but none are buildable TargetProblemNoneEnabled :: TargetSelector -> [AvailableTarget ()] -> TargetProblem a -- | There are no targets at all TargetProblemNoTargets :: TargetSelector -> TargetProblem a TargetProblemNoSuchPackage :: PackageId -> TargetProblem a TargetProblemNoSuchComponent :: PackageId -> ComponentName -> TargetProblem a -- | A custom target problem CustomTargetProblem :: a -> TargetProblem a -- | Type alias for a TargetProblem with no user-defined -- problems/errors. -- -- Can use the utilities below for reporting/rendering problems. type TargetProblem' = TargetProblem Void instance GHC.Base.Functor Distribution.Client.TargetProblem.TargetProblem instance GHC.Show.Show a => GHC.Show.Show (Distribution.Client.TargetProblem.TargetProblem a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Distribution.Client.TargetProblem.TargetProblem a) -- | Utilities to help format error messages for the various CLI commands. module Distribution.Client.CmdErrorMessages -- | A tag used in rendering messages to distinguish singular or plural. data Plural Singular :: Plural Plural :: Plural -- | Used to render a singular or plural version of something -- --
--   plural (listPlural theThings) "it is" "they are"
--   
plural :: Plural -> a -> a -> a -- | Singular for singleton lists and plural otherwise. listPlural :: [a] -> Plural -- | Render a list of things in the style foo, bar and baz renderListCommaAnd :: [String] -> String renderListTabular :: [String] -> String renderListPretty :: [String] -> String -- | Render a list of things in the style blah blah; this that; and the -- other renderListSemiAnd :: [String] -> String -- | When rendering lists of things it often reads better to group related -- things, e.g. grouping components by package name -- --
--   renderListSemiAnd
--     [     "the package " ++ prettyShow pkgname ++ " components "
--        ++ renderListCommaAnd showComponentName components
--     | (pkgname, components) <- sortGroupOn packageName allcomponents ]
--   
sortGroupOn :: Ord b => (a -> b) -> [a] -> [(b, [a])] renderTargetSelector :: TargetSelector -> String renderSubComponentTarget :: SubComponentTarget -> String renderOptionalStanza :: Plural -> OptionalStanza -> String -- | The optional stanza type (test suite or benchmark), if it is one. optionalStanza :: ComponentName -> Maybe OptionalStanza -- | Does the TargetSelector potentially refer to one package or -- many? targetSelectorPluralPkgs :: TargetSelector -> Plural -- | Does the TargetSelector refer to packages or to components? targetSelectorRefersToPkgs :: TargetSelector -> Bool targetSelectorFilter :: TargetSelector -> Maybe ComponentKindFilter renderComponentName :: PackageName -> ComponentName -> String renderComponentKind :: Plural -> ComponentKind -> String -- | Default implementation of reportTargetProblems simply renders -- one problem per line. reportTargetProblems :: Verbosity -> String -> [TargetProblem'] -> IO a -- | Default implementation of renderTargetProblem. renderTargetProblem :: String -> (a -> String) -> TargetProblem a -> String -- | Several commands have a TargetProblemNoneEnabled problem -- constructor. This renders an error message for those cases. renderTargetProblemNoneEnabled :: String -> TargetSelector -> [AvailableTarget ()] -> String -- | Several commands have a TargetProblemNoTargets problem -- constructor. This renders an error message for those cases. renderTargetProblemNoTargets :: String -> TargetSelector -> String renderCannotPruneDependencies :: CannotPruneDependencies -> String -- | Either the component as a whole or detail about a file or module -- target within a component. data SubComponentTarget -- | The component as a whole WholeComponent :: SubComponentTarget -- | A specific module within a component. ModuleTarget :: ModuleName -> SubComponentTarget -- | A specific file within a component. Note that this does not carry the -- file extension. FileTarget :: FilePath -> SubComponentTarget type ComponentKindFilter = ComponentKind data ComponentKind LibKind :: ComponentKind FLibKind :: ComponentKind ExeKind :: ComponentKind TestKind :: ComponentKind BenchKind :: ComponentKind -- | A target selector is expression selecting a set of components (as -- targets for a actions like build, run, test -- etc). A target selector corresponds to the user syntax for referring -- to targets on the command line. -- -- From the users point of view a target can be many things: packages, -- dirs, component names, files etc. Internally we consider a target to -- be a specific component (or module/file within a component), and all -- the users' notions of targets are just different ways of referring to -- these component targets. -- -- So target selectors are expressions in the sense that they are -- interpreted to refer to one or more components. For example a -- TargetPackage gets interpreted differently by different -- commands to refer to all or a subset of components within the package. -- -- The syntax has lots of optional parts: -- --
--   [ package name | package dir | package .cabal file ]
--   [ [lib:|exe:] component name ]
--   [ module name | source file ]
--   
data TargetSelector -- | One (or more) packages as a whole, or all the components of a -- particular kind within the package(s). -- -- These are always packages that are local to the project. In the case -- that there is more than one, they all share the same directory -- location. TargetPackage :: TargetImplicitCwd -> [PackageId] -> Maybe ComponentKindFilter -> TargetSelector -- | A package specified by name. This may refer to extra-packages -- from the cabal.project file, or a dependency of a known -- project package or could refer to a package from a hackage archive. It -- needs further context to resolve to a specific package. TargetPackageNamed :: PackageName -> Maybe ComponentKindFilter -> TargetSelector -- | All packages, or all components of a particular kind in all packages. TargetAllPackages :: Maybe ComponentKindFilter -> TargetSelector -- | A specific component in a package within the project. TargetComponent :: PackageId -> ComponentName -> SubComponentTarget -> TargetSelector -- | A component in a package, but where it cannot be verified that the -- package has such a component, or because the package is itself not -- known. TargetComponentUnknown :: PackageName -> Either UnqualComponentName ComponentName -> SubComponentTarget -> TargetSelector showTargetSelector :: TargetSelector -> String componentKind :: ComponentName -> ComponentKind module Distribution.Client.ProjectBuilding -- | Do the dry run pass. This is a prerequisite of rebuildTargets. -- -- It gives us the BuildStatusMap. This should be used with -- improveInstallPlanWithUpToDatePackages to give an improved -- version of the ElaboratedInstallPlan with packages switched to -- the Installed state when we find that they're already up to -- date. rebuildTargetsDryRun :: DistDirLayout -> ElaboratedSharedConfig -> ElaboratedInstallPlan -> IO BuildStatusMap improveInstallPlanWithUpToDatePackages :: BuildStatusMap -> ElaboratedInstallPlan -> ElaboratedInstallPlan -- | The BuildStatus of every package in the -- ElaboratedInstallPlan. -- -- This is used as the result of the dry-run of building an install plan. type BuildStatusMap = Map UnitId BuildStatus -- | The build status for an individual package is the state that the -- package is in prior to initiating a (re)build. -- -- This should not be confused with a BuildResult which is the -- result after successfully building a package. -- -- It serves two purposes: -- -- data BuildStatus -- | The package is in the PreExisting state, so does not need -- building. BuildStatusPreExisting :: BuildStatus -- | The package is in the Installed state, so does not need -- building. BuildStatusInstalled :: BuildStatus -- | The package has not been downloaded yet, so it will have to be -- downloaded, unpacked and built. BuildStatusDownload :: BuildStatus -- | The package has not been unpacked yet, so it will have to be unpacked -- and built. BuildStatusUnpack :: FilePath -> BuildStatus -- | The package exists in a local dir already, and just needs building or -- rebuilding. So this can only happen for BuildInplaceOnly -- style packages. BuildStatusRebuild :: FilePath -> BuildStatusRebuild -> BuildStatus -- | The package exists in a local dir already, and is fully up to date. So -- this package can be put into the Installed state and it does -- not need to be built. BuildStatusUpToDate :: BuildResult -> BuildStatus -- | For a package that is going to be built or rebuilt, the state it's in -- now. -- -- So again, this tells us why a package needs to be rebuilt and what -- build phases need to be run. The MonitorChangedReason gives us -- details like which file changed, which is mainly for high verbosity -- debug output. data BuildStatusRebuild -- | The package configuration changed, so the configure and build phases -- needs to be (re)run. BuildStatusConfigure :: MonitorChangedReason () -> BuildStatusRebuild -- | The configuration has not changed but the build phase needs to be -- rerun. We record the reason the (re)build is needed. -- -- The optional registration info here tells us if we've registered the -- package already, or if we still need to do that after building. -- Just Nothing indicates that we know that no registration is -- necessary (e.g., executable.) BuildStatusBuild :: Maybe (Maybe InstalledPackageInfo) -> BuildReason -> BuildStatusRebuild data BuildReason -- | The dependencies of this package have been (re)built so the build -- phase needs to be rerun. BuildReasonDepsRebuilt :: BuildReason -- | Changes in files within the package (or first run or corrupt cache) BuildReasonFilesChanged :: MonitorChangedReason () -> BuildReason -- | An important special case is that no files have changed but the set of -- components the user asked to build has changed. We track the -- set of components we have built, which of course only grows -- (until some other change resets it). -- -- The Set ComponentName is the set of components we have -- built previously. When we update the monitor we take the union of the -- ones we have built previously with the ones the user has asked for -- this time and save those. See updatePackageBuildFileMonitor. BuildReasonExtraTargets :: Set ComponentName -> BuildReason -- | Although we're not going to build any additional targets as a whole, -- we're going to build some part of a component or run a repl or any -- other action that does not result in additional persistent artifacts. BuildReasonEphemeralTargets :: BuildReason -- | What kind of change checkFileMonitorChanged detected. data MonitorChangedReason a -- | One of the files changed (existence, file type, mtime or file content, -- depending on the MonitorFilePath in question) MonitoredFileChanged :: FilePath -> MonitorChangedReason a -- | The pure input value changed. -- -- The previous cached key value is also returned. This is sometimes -- useful when using a fileMonitorKeyValid function that is not -- simply (==), when invalidation can be partial. In such cases it -- can make sense to updateFileMonitor with a key value that's a -- combination of the new and old (e.g. set union). MonitoredValueChanged :: a -> MonitorChangedReason a -- | There was no saved monitor state, cached value etc. Ie the file for -- the FileMonitor does not exist. MonitorFirstRun :: MonitorChangedReason a -- | There was existing state, but we could not read it. This typically -- happens when the code has changed compared to an existing -- FileMonitor cache file and type of the input value or cached -- value has changed such that we cannot decode the values. This is -- completely benign as we can treat is just as if there were no cache -- file and re-run. MonitorCorruptCache :: MonitorChangedReason a -- | This is primarily here for debugging. It's not actually used anywhere. buildStatusToString :: BuildStatus -> String -- | Build things for real. -- -- It requires the BuildStatusMap gathered by -- rebuildTargetsDryRun. rebuildTargets :: Verbosity -> DistDirLayout -> StoreDirLayout -> ElaboratedInstallPlan -> ElaboratedSharedConfig -> BuildStatusMap -> BuildTimeSettings -> IO BuildOutcomes -- | A summary of the outcome for building a whole set of packages. type BuildOutcomes = Map UnitId BuildOutcome -- | A summary of the outcome for building a single package: either success -- or failure. type BuildOutcome = Either BuildFailure BuildResult -- | Information arising from successfully building a single package. data BuildResult BuildResult :: DocsResult -> TestsResult -> Maybe FilePath -> BuildResult [buildResultDocs] :: BuildResult -> DocsResult [buildResultTests] :: BuildResult -> TestsResult [buildResultLogFile] :: BuildResult -> Maybe FilePath -- | Information arising from the failure to build a single package. data BuildFailure BuildFailure :: Maybe FilePath -> BuildFailureReason -> BuildFailure [buildFailureLogFile] :: BuildFailure -> Maybe FilePath [buildFailureReason] :: BuildFailure -> BuildFailureReason -- | Detail on the reason that a package failed to build. data BuildFailureReason DependentFailed :: PackageId -> BuildFailureReason DownloadFailed :: SomeException -> BuildFailureReason UnpackFailed :: SomeException -> BuildFailureReason ConfigureFailed :: SomeException -> BuildFailureReason BuildFailed :: SomeException -> BuildFailureReason ReplFailed :: SomeException -> BuildFailureReason HaddocksFailed :: SomeException -> BuildFailureReason TestsFailed :: SomeException -> BuildFailureReason BenchFailed :: SomeException -> BuildFailureReason InstallFailed :: SomeException -> BuildFailureReason -- | This module deals with building and incrementally rebuilding a -- collection of packages. It is what backs the cabal build and -- configure commands, as well as being a core part of -- run, test, bench and others. -- -- The primary thing is in fact rebuilding (and trying to make that quick -- by not redoing unnecessary work), so building from scratch is just a -- special case. -- -- The build process and the code can be understood by breaking it down -- into three major parts: -- -- -- -- As far as possible, the "what to do" phase embodies all the policy, -- leaving the "do it" phase policy free. The first phase contains more -- of the complicated logic, but it is contained in code that is either -- pure or just has read effects (except cache updates). Then the second -- phase does all the actions to build packages, but as far as possible -- it just follows the instructions and avoids any logic for deciding -- what to do (apart from recompilation avoidance in executing the plan). -- -- This division helps us keep the code under control, making it easier -- to understand, test and debug. So when you are extending these -- modules, please think about which parts of your change belong in which -- part. It is perfectly ok to extend the description of what to do (i.e. -- the ElaboratedInstallPlan) if that helps keep the policy -- decisions in the first phase. Also, the second phase does not have -- direct access to any of the input configuration anyway; all the -- information has to flow via the ElaboratedInstallPlan. module Distribution.Client.ProjectOrchestration -- | Tracks what command is being executed, because we need to hide this -- somewhere for cases that need special handling (usually for error -- reporting). data CurrentCommand InstallCommand :: CurrentCommand HaddockCommand :: CurrentCommand BuildCommand :: CurrentCommand ReplCommand :: CurrentCommand OtherCommand :: CurrentCommand establishProjectBaseContext :: Verbosity -> ProjectConfig -> CurrentCommand -> IO ProjectBaseContext -- | Like establishProjectBaseContext but doesn't search for project -- root. establishProjectBaseContextWithRoot :: Verbosity -> ProjectConfig -> ProjectRoot -> CurrentCommand -> IO ProjectBaseContext -- | This holds the context of a project prior to solving: the content of -- the cabal.project and all the local package .cabal -- files. data ProjectBaseContext ProjectBaseContext :: DistDirLayout -> CabalDirLayout -> ProjectConfig -> [PackageSpecifier UnresolvedSourcePackage] -> BuildTimeSettings -> CurrentCommand -> Maybe InstalledPackageIndex -> ProjectBaseContext [distDirLayout] :: ProjectBaseContext -> DistDirLayout [cabalDirLayout] :: ProjectBaseContext -> CabalDirLayout [projectConfig] :: ProjectBaseContext -> ProjectConfig [localPackages] :: ProjectBaseContext -> [PackageSpecifier UnresolvedSourcePackage] [buildSettings] :: ProjectBaseContext -> BuildTimeSettings [currentCommand] :: ProjectBaseContext -> CurrentCommand [installedPackages] :: ProjectBaseContext -> Maybe InstalledPackageIndex -- | Resolved configuration for things that affect how we build and not the -- value of the things we build. The idea is that this is easier to use -- than the raw configuration because in the raw configuration everything -- is optional (monoidial). In the BuildTimeSettings every field -- is filled in, if only with the defaults. -- -- Use resolveBuildTimeSettings to make one from the project -- config (by applying defaults etc). data BuildTimeSettings BuildTimeSettings :: Bool -> Bool -> Bool -> [PathTemplate] -> Maybe (Compiler -> Platform -> PackageId -> UnitId -> FilePath) -> Verbosity -> ReportLevel -> Bool -> [FilePath] -> Int -> Bool -> Bool -> Bool -> [RemoteRepo] -> [LocalRepo] -> FilePath -> Maybe String -> Bool -> [FilePath] -> Bool -> BuildTimeSettings [buildSettingDryRun] :: BuildTimeSettings -> Bool [buildSettingOnlyDeps] :: BuildTimeSettings -> Bool [buildSettingOnlyDownload] :: BuildTimeSettings -> Bool [buildSettingSummaryFile] :: BuildTimeSettings -> [PathTemplate] [buildSettingLogFile] :: BuildTimeSettings -> Maybe (Compiler -> Platform -> PackageId -> UnitId -> FilePath) [buildSettingLogVerbosity] :: BuildTimeSettings -> Verbosity [buildSettingBuildReports] :: BuildTimeSettings -> ReportLevel [buildSettingReportPlanningFailure] :: BuildTimeSettings -> Bool [buildSettingSymlinkBinDir] :: BuildTimeSettings -> [FilePath] [buildSettingNumJobs] :: BuildTimeSettings -> Int [buildSettingKeepGoing] :: BuildTimeSettings -> Bool [buildSettingOfflineMode] :: BuildTimeSettings -> Bool [buildSettingKeepTempFiles] :: BuildTimeSettings -> Bool [buildSettingRemoteRepos] :: BuildTimeSettings -> [RemoteRepo] [buildSettingLocalNoIndexRepos] :: BuildTimeSettings -> [LocalRepo] [buildSettingCacheDir] :: BuildTimeSettings -> FilePath [buildSettingHttpTransport] :: BuildTimeSettings -> Maybe String [buildSettingIgnoreExpiry] :: BuildTimeSettings -> Bool [buildSettingProgPathExtra] :: BuildTimeSettings -> [FilePath] [buildSettingHaddockOpen] :: BuildTimeSettings -> Bool -- | Convert configuration from the cabal configure or cabal -- build command line into a ProjectConfig value that can -- combined with configuration from other sources. -- -- At the moment this uses the legacy command line flag types. See -- LegacyProjectConfig for an explanation. commandLineFlagsToProjectConfig :: GlobalFlags -> NixStyleFlags a -> ClientInstallFlags -> ProjectConfig -- | Pre-build phase: decide what to do. withInstallPlan :: Verbosity -> ProjectBaseContext -> (ElaboratedInstallPlan -> ElaboratedSharedConfig -> IO a) -> IO a runProjectPreBuildPhase :: Verbosity -> ProjectBaseContext -> (ElaboratedInstallPlan -> IO (ElaboratedInstallPlan, TargetsMap)) -> IO ProjectBuildContext -- | This holds the context between the pre-build, build and post-build -- phases. data ProjectBuildContext ProjectBuildContext :: ElaboratedInstallPlan -> ElaboratedInstallPlan -> ElaboratedSharedConfig -> BuildStatusMap -> TargetsMap -> ProjectBuildContext -- | This is the improved plan, before we select a plan subset based on the -- build targets, and before we do the dry-run. So this contains all -- packages in the project. [elaboratedPlanOriginal] :: ProjectBuildContext -> ElaboratedInstallPlan -- | This is the elaboratedPlanOriginal after we select a plan -- subset and do the dry-run phase to find out what is up-to or out-of -- date. This is the plan that will be executed during the build phase. -- So this contains only a subset of packages in the project. [elaboratedPlanToExecute] :: ProjectBuildContext -> ElaboratedInstallPlan -- | The part of the install plan that's shared between all packages in the -- plan. This does not change between the two plan variants above, so -- there is just the one copy. [elaboratedShared] :: ProjectBuildContext -> ElaboratedSharedConfig -- | The result of the dry-run phase. This tells us about each member of -- the elaboratedPlanToExecute. [pkgsBuildStatus] :: ProjectBuildContext -> BuildStatusMap -- | The targets selected by selectPlanSubset. This is useful eg. -- in CmdRun, where we need a valid target to execute. [targetsMap] :: ProjectBuildContext -> TargetsMap -- | Parse a bunch of command line args as TargetSelectors, failing -- with an error if any are unrecognised. The possible target selectors -- are based on the available packages (and their locations). readTargetSelectors :: [PackageSpecifier (SourcePackage (PackageLocation a))] -> Maybe ComponentKindFilter -> [String] -> IO (Either [TargetSelectorProblem] [TargetSelector]) -- | Throw an exception with a formatted message if there are any problems. reportTargetSelectorProblems :: Verbosity -> [TargetSelectorProblem] -> IO a -- | Given a set of TargetSelectors, resolve which UnitIds -- and ComponentTargets they ought to refer to. -- -- The idea is that every user target identifies one or more roots in the -- ElaboratedInstallPlan, which we will use to determine the -- closure of what packages need to be built, dropping everything from -- the plan that is unnecessary. This closure and pruning is done by -- pruneInstallPlanToTargets and this needs to be told the roots -- in terms of UnitIds and the ComponentTargets within -- those. -- -- This means we first need to translate the TargetSelectors into -- the UnitIds and ComponentTargets. This translation has -- to be different for the different command line commands, like -- build, repl etc. For example the command build -- pkgfoo could select a different set of components in pkgfoo than -- repl pkgfoo. The build command would select any -- library and all executables, whereas repl would select the -- library or a single executable. Furthermore, both of these examples -- could fail, and fail in different ways and each needs to be able to -- produce helpful error messages. -- -- So resolveTargets takes two helpers: one to select the targets -- to be used by user targets that refer to a whole package -- (TargetPackage), and another to check user targets that refer -- to a component (or a module or file within a component). These helpers -- can fail, and use their own error type. Both helpers get given the -- AvailableTarget info about the component(s). -- -- While commands vary quite a bit in their behaviour about which -- components to select for a whole-package target, most commands have -- the same behaviour for checking a user target that refers to a -- specific component. To help with this commands can use -- selectComponentTargetBasic, either directly or as a basis for -- their own selectComponentTarget implementation. resolveTargets :: forall err. (forall k. TargetSelector -> [AvailableTarget k] -> Either (TargetProblem err) [k]) -> (forall k. SubComponentTarget -> AvailableTarget k -> Either (TargetProblem err) k) -> ElaboratedInstallPlan -> Maybe SourcePackageDb -> [TargetSelector] -> Either [TargetProblem err] TargetsMap -- | The set of components to build, represented as a mapping from -- UnitIds to the ComponentTargets within the unit that -- will be selected (e.g. selected to build, test or repl). -- -- Associated with each ComponentTarget is the set of -- TargetSelectors that matched this target. Typically this is -- exactly one, but in general it is possible to for different selectors -- to match the same target. This extra information is primarily to help -- make helpful error messages. type TargetsMap = Map UnitId [(ComponentTarget, NonEmpty TargetSelector)] -- | Get all target selectors. allTargetSelectors :: TargetsMap -> [TargetSelector] -- | Get all unique target selectors. uniqueTargetSelectors :: TargetsMap -> [TargetSelector] -- | A target selector is expression selecting a set of components (as -- targets for a actions like build, run, test -- etc). A target selector corresponds to the user syntax for referring -- to targets on the command line. -- -- From the users point of view a target can be many things: packages, -- dirs, component names, files etc. Internally we consider a target to -- be a specific component (or module/file within a component), and all -- the users' notions of targets are just different ways of referring to -- these component targets. -- -- So target selectors are expressions in the sense that they are -- interpreted to refer to one or more components. For example a -- TargetPackage gets interpreted differently by different -- commands to refer to all or a subset of components within the package. -- -- The syntax has lots of optional parts: -- --
--   [ package name | package dir | package .cabal file ]
--   [ [lib:|exe:] component name ]
--   [ module name | source file ]
--   
data TargetSelector -- | One (or more) packages as a whole, or all the components of a -- particular kind within the package(s). -- -- These are always packages that are local to the project. In the case -- that there is more than one, they all share the same directory -- location. TargetPackage :: TargetImplicitCwd -> [PackageId] -> Maybe ComponentKindFilter -> TargetSelector -- | A package specified by name. This may refer to extra-packages -- from the cabal.project file, or a dependency of a known -- project package or could refer to a package from a hackage archive. It -- needs further context to resolve to a specific package. TargetPackageNamed :: PackageName -> Maybe ComponentKindFilter -> TargetSelector -- | All packages, or all components of a particular kind in all packages. TargetAllPackages :: Maybe ComponentKindFilter -> TargetSelector -- | A specific component in a package within the project. TargetComponent :: PackageId -> ComponentName -> SubComponentTarget -> TargetSelector -- | A component in a package, but where it cannot be verified that the -- package has such a component, or because the package is itself not -- known. TargetComponentUnknown :: PackageName -> Either UnqualComponentName ComponentName -> SubComponentTarget -> TargetSelector -- | Does this TargetPackage selector arise from syntax referring to -- a package in the current directory (e.g. tests or no giving -- no explicit target at all) or does it come from syntax referring to a -- package name or location. data TargetImplicitCwd TargetImplicitCwd :: TargetImplicitCwd TargetExplicitNamed :: TargetImplicitCwd -- | Type alias so we can use the shorter name PackageId. type PackageId = PackageIdentifier -- | An available target represents a component within a package that a -- user command could plausibly refer to. In this sense, all the -- components defined within the package are things the user could refer -- to, whether or not it would actually be possible to build that -- component. -- -- In particular the available target contains an -- AvailableTargetStatus which informs us about whether it's -- actually possible to select this component to be built, and if not why -- not. This detail makes it possible for command implementations (like -- build, test etc) to accurately report why a target -- cannot be used. -- -- Note that the type parameter is used to help enforce that command -- implementations can only select targets that can actually be built (by -- forcing them to return the k value for the selected targets). -- In particular resolveTargets makes use of this (with -- k as (UnitId, ComponentName')) to identify -- the targets thus selected. data AvailableTarget k AvailableTarget :: PackageId -> ComponentName -> AvailableTargetStatus k -> Bool -> AvailableTarget k [availableTargetPackageId] :: AvailableTarget k -> PackageId [availableTargetComponentName] :: AvailableTarget k -> ComponentName [availableTargetStatus] :: AvailableTarget k -> AvailableTargetStatus k [availableTargetLocalToProject] :: AvailableTarget k -> Bool -- | The status of a an AvailableTarget component. This tells us -- whether it's actually possible to select this component to be built, -- and if not why not. data AvailableTargetStatus k -- | When the user does tests: False TargetDisabledByUser :: AvailableTargetStatus k -- | When the solver could not enable tests TargetDisabledBySolver :: AvailableTargetStatus k -- | When the component has buildable: False TargetNotBuildable :: AvailableTargetStatus k -- | When the component is non-core in a non-local package TargetNotLocal :: AvailableTargetStatus k -- | The target can or should be built TargetBuildable :: k -> TargetRequested -> AvailableTargetStatus k -- | This tells us whether a target ought to be built by default, or only -- if specifically requested. The policy is that components like -- libraries and executables are built by default by build, but -- test suites and benchmarks are not, unless this is overridden in the -- project configuration. data TargetRequested -- | To be built by default TargetRequestedByDefault :: TargetRequested -- | Not to be built by default TargetNotRequestedByDefault :: TargetRequested data ComponentName CLibName :: LibraryName -> ComponentName CNotLibName :: NotLibComponentName -> ComponentName pattern CFLibName :: UnqualComponentName -> ComponentName pattern CExeName :: UnqualComponentName -> ComponentName pattern CTestName :: UnqualComponentName -> ComponentName pattern CBenchName :: UnqualComponentName -> ComponentName data ComponentKind LibKind :: ComponentKind FLibKind :: ComponentKind ExeKind :: ComponentKind TestKind :: ComponentKind BenchKind :: ComponentKind -- | Specific targets within a package or component to act on e.g. to -- build, haddock or open a repl. data ComponentTarget ComponentTarget :: ComponentName -> SubComponentTarget -> ComponentTarget -- | Either the component as a whole or detail about a file or module -- target within a component. data SubComponentTarget -- | The component as a whole WholeComponent :: SubComponentTarget -- | A specific module within a component. ModuleTarget :: ModuleName -> SubComponentTarget -- | A specific file within a component. Note that this does not carry the -- file extension. FileTarget :: FilePath -> SubComponentTarget -- | A basic selectComponentTarget implementation to use or pass -- to resolveTargets, that does the basic checks that the -- component is buildable and isn't a test suite or benchmark that is -- disabled. This can also be used to do these basic checks as part of a -- custom impl that selectComponentTargetBasic :: SubComponentTarget -> AvailableTarget k -> Either (TargetProblem a) k -- | Utility used by repl and run to check if the targets spans multiple -- components, since those commands do not support multiple components. distinctTargetComponents :: TargetsMap -> Set (UnitId, ComponentName) filterTargetsKind :: ComponentKind -> [AvailableTarget k] -> [AvailableTarget k] filterTargetsKindWith :: (ComponentKind -> Bool) -> [AvailableTarget k] -> [AvailableTarget k] selectBuildableTargets :: [AvailableTarget k] -> [k] selectBuildableTargetsWith :: (TargetRequested -> Bool) -> [AvailableTarget k] -> [k] selectBuildableTargets' :: [AvailableTarget k] -> ([k], [AvailableTarget ()]) selectBuildableTargetsWith' :: (TargetRequested -> Bool) -> [AvailableTarget k] -> ([k], [AvailableTarget ()]) forgetTargetsDetail :: [AvailableTarget k] -> [AvailableTarget ()] -- | Wrapper around pruneInstallPlanToTargets that adjusts for the -- extra unneeded info in the TargetsMap. pruneInstallPlanToTargets :: TargetAction -> TargetsMap -> ElaboratedInstallPlan -> ElaboratedInstallPlan -- | How pruneInstallPlanToTargets should interpret the per-package -- ComponentTargets: as build, repl or haddock targets. data TargetAction TargetActionConfigure :: TargetAction TargetActionBuild :: TargetAction TargetActionRepl :: TargetAction TargetActionTest :: TargetAction TargetActionBench :: TargetAction TargetActionHaddock :: TargetAction -- | Try to remove the given targets from the install plan. -- -- This is not always possible. pruneInstallPlanToDependencies :: Set UnitId -> ElaboratedInstallPlan -> Either CannotPruneDependencies ElaboratedInstallPlan -- | It is not always possible to prune to only the dependencies of a set -- of targets. It may be the case that removing a package leaves -- something else that still needed the pruned package. -- -- This lists all the packages that would be broken, and their -- dependencies that would be missing if we did prune. newtype CannotPruneDependencies CannotPruneDependencies :: [(ElaboratedPlanPackage, [ElaboratedPlanPackage])] -> CannotPruneDependencies -- | Print a user-oriented presentation of the install plan, indicating -- what will be built. printPlan :: Verbosity -> ProjectBaseContext -> ProjectBuildContext -> IO () -- | Build phase: now do it. -- -- Execute all or parts of the description of what to do to build or -- rebuild the various packages needed. runProjectBuildPhase :: Verbosity -> ProjectBaseContext -> ProjectBuildContext -> IO BuildOutcomes -- | Post-build phase: various administrative tasks -- -- Update bits of state based on the build outcomes and report any -- failures. runProjectPostBuildPhase :: Verbosity -> ProjectBaseContext -> ProjectBuildContext -> BuildOutcomes -> IO () -- | If there are build failures then report them and throw an exception. dieOnBuildFailures :: Verbosity -> CurrentCommand -> ElaboratedInstallPlan -> BuildOutcomes -> IO () -- | Create a dummy project context, without a .cabal or a .cabal.project -- file (a place where to put a temporary dist directory is still needed) establishDummyProjectBaseContext :: Verbosity -> ProjectConfig -> DistDirLayout -> [PackageSpecifier UnresolvedSourcePackage] -> CurrentCommand -> IO ProjectBaseContext establishDummyDistDirLayout :: Verbosity -> ProjectConfig -> FilePath -> IO DistDirLayout instance GHC.Classes.Eq Distribution.Client.ProjectOrchestration.CurrentCommand instance GHC.Show.Show Distribution.Client.ProjectOrchestration.CurrentCommand -- | Utilities to help commands with scripts module Distribution.Client.ScriptUtils -- | Get the hash of a script's absolute path) -- -- Two hashes will be the same as long as the absolute paths are the -- same. getScriptHash :: FilePath -> IO String -- | Get the directory for caching a script build. -- -- The only identity of a script is it's absolute path, so append the -- hashed path to the script-builds dir to get the cache -- directory. getScriptCacheDirectory :: FilePath -> IO FilePath -- | Get the directory for caching a script build and ensure it exists. -- -- The only identity of a script is it's absolute path, so append the -- hashed path to the script-builds dir to get the cache -- directory. ensureScriptCacheDirectory :: Verbosity -> FilePath -> IO FilePath -- | Determine whether the targets represent regular targets or a script -- and return the proper context and target selectors. Die with an error -- message if selectors are valid as neither regular targets or as a -- script. -- -- In the case that the context refers to a temporary directory, delete -- it after the action finishes. withContextAndSelectors :: AcceptNoTargets -> Maybe ComponentKind -> NixStyleFlags a -> [String] -> GlobalFlags -> CurrentCommand -> (TargetContext -> ProjectBaseContext -> [TargetSelector] -> IO b) -> IO b -- | What your command should do when no targets are found. data AcceptNoTargets -- | die on TargetSelectorNoTargetsInProject RejectNoTargets :: AcceptNoTargets -- | return a default TargetSelector AcceptNoTargets :: AcceptNoTargets -- | Information about the context in which we found the -- TargetSelectors. data TargetContext -- | The target selectors are part of a project. ProjectContext :: TargetContext -- | The target selectors are from the global context. GlobalContext :: TargetContext -- | The target selectors refer to a script. Contains the path to the -- script and the executable metadata parsed from the script ScriptContext :: FilePath -> Executable -> TargetContext -- | Add add the executable metadata to the context and write a .cabal -- file. updateContextAndWriteProjectFile :: ProjectBaseContext -> FilePath -> Executable -> IO ProjectBaseContext -- | Add the SourcePackage to the context and use it to write a -- .cabal file. updateContextAndWriteProjectFile' :: ProjectBaseContext -> SourcePackage (PackageLocation (Maybe FilePath)) -> IO ProjectBaseContext -- | The base for making a SourcePackage for a fake project. It -- needs a Library or Executable depending on the command. fakeProjectSourcePackage :: FilePath -> SourcePackage (PackageLocation loc) -- | A lens for the srcpkgDescription field of SourcePackage lSrcpkgDescription :: Lens' (SourcePackage loc) GenericPackageDescription instance GHC.Show.Show Distribution.Client.ScriptUtils.AcceptNoTargets instance GHC.Classes.Eq Distribution.Client.ScriptUtils.AcceptNoTargets instance GHC.Show.Show Distribution.Client.ScriptUtils.TargetContext instance GHC.Classes.Eq Distribution.Client.ScriptUtils.TargetContext -- | cabal-install CLI command: update module Distribution.Client.CmdUpdate updateCommand :: CommandUI (NixStyleFlags ()) updateAction :: NixStyleFlags () -> [String] -> GlobalFlags -> IO () instance GHC.Show.Show Distribution.Client.CmdUpdate.UpdateRequest instance Distribution.Pretty.Pretty Distribution.Client.CmdUpdate.UpdateRequest instance Distribution.Parsec.Parsec Distribution.Client.CmdUpdate.UpdateRequest -- | cabal-install CLI command: test module Distribution.Client.CmdTest testCommand :: CommandUI (NixStyleFlags ()) -- | The test command is very much like build. It brings -- the install plan up to date, selects that part of the plan needed by -- the given or implicit test target(s) and then executes the plan. -- -- Compared to build the difference is that there's also test -- targets which are ephemeral. -- -- For more details on how this works, see the module -- Distribution.Client.ProjectOrchestration testAction :: NixStyleFlags () -> [String] -> GlobalFlags -> IO () isSubComponentProblem :: PackageId -> ComponentName -> SubComponentTarget -> TargetProblem TestProblem notTestProblem :: PackageId -> ComponentName -> TargetProblem TestProblem noTestsProblem :: TargetSelector -> TargetProblem TestProblem -- | This defines what a TargetSelector means for the test -- command. It selects the AvailableTargets that the -- TargetSelector refers to, or otherwise classifies the problem. -- -- For the test command we select all buildable test-suites, or -- fail if there are no test-suites or no buildable test-suites. selectPackageTargets :: TargetSelector -> [AvailableTarget k] -> Either TestTargetProblem [k] -- | For a TargetComponent TargetSelector, check if the -- component can be selected. -- -- For the test command we just need to check it is a -- test-suite, in addition to the basic checks on being buildable etc. selectComponentTarget :: SubComponentTarget -> AvailableTarget k -> Either TestTargetProblem k instance GHC.Show.Show Distribution.Client.CmdTest.TestProblem instance GHC.Classes.Eq Distribution.Client.CmdTest.TestProblem -- | cabal-install CLI command: run module Distribution.Client.CmdRun runCommand :: CommandUI (NixStyleFlags ()) -- | The run command runs a specified executable-like component, -- building it first if necessary. The component can be either an -- executable, a test, or a benchmark. This is particularly useful for -- passing arguments to exestestsbenchs by simply appending them -- after a --. -- -- For more details on how this works, see the module -- Distribution.Client.ProjectOrchestration runAction :: NixStyleFlags () -> [String] -> GlobalFlags -> IO () -- | Handle cabal invoked as script interpreter, see also -- validScript -- -- First argument is the FilePath to the script to be executed; -- second argument is a list of arguments to be passed to the script. handleShebang :: FilePath -> [String] -> IO () -- | Used by the main CLI parser as heuristic to decide whether -- cabal was invoked as a script interpreter, i.e. via -- --
--   #! /usr/bin/env cabal
--   
-- -- or -- --
--   #! /usr/bin/cabal
--   
-- -- As the first argument passed to cabal will be a filepath to -- the script to be interpreted. -- -- See also handleShebang validScript :: String -> IO Bool matchesMultipleProblem :: TargetSelector -> [AvailableTarget ()] -> RunTargetProblem noExesProblem :: TargetSelector -> RunTargetProblem -- | This defines what a TargetSelector means for the run -- command. It selects the AvailableTargets that the -- TargetSelector refers to, or otherwise classifies the problem. -- -- For the run command we select the exe if there is only one -- and it's buildable. Fail if there are no or multiple buildable exe -- components. selectPackageTargets :: TargetSelector -> [AvailableTarget k] -> Either RunTargetProblem [k] -- | For a TargetComponent TargetSelector, check if the -- component can be selected. -- -- For the run command we just need to check it is a -- executable-like (an executable, a test, or a benchmark), in addition -- to the basic checks on being buildable etc. selectComponentTarget :: SubComponentTarget -> AvailableTarget k -> Either RunTargetProblem k instance GHC.Show.Show Distribution.Client.CmdRun.RunProblem instance GHC.Classes.Eq Distribution.Client.CmdRun.RunProblem -- | cabal-install CLI command: haddock module Distribution.Client.CmdHaddock haddockCommand :: CommandUI (NixStyleFlags ClientHaddockFlags) -- | The haddock command is TODO. -- -- For more details on how this works, see the module -- Distribution.Client.ProjectOrchestration haddockAction :: NixStyleFlags ClientHaddockFlags -> [String] -> GlobalFlags -> IO () newtype ClientHaddockFlags ClientHaddockFlags :: Flag Bool -> ClientHaddockFlags [openInBrowser] :: ClientHaddockFlags -> Flag Bool -- | This defines what a TargetSelector means for the -- haddock command. It selects the AvailableTargets that -- the TargetSelector refers to, or otherwise classifies the -- problem. -- -- For the haddock command we select all buildable libraries. -- Additionally, depending on the --executables flag we also -- select all the buildable exes. We do similarly for test-suites, -- benchmarks and foreign libs. selectPackageTargets :: HaddockFlags -> TargetSelector -> [AvailableTarget k] -> Either TargetProblem' [k] -- | For a TargetComponent TargetSelector, check if the -- component can be selected. -- -- For the haddock command we just need the basic checks on -- being buildable etc. selectComponentTarget :: SubComponentTarget -> AvailableTarget k -> Either TargetProblem' k -- | cabal-install CLI command: build module Distribution.Client.CmdBuild buildCommand :: CommandUI (NixStyleFlags BuildFlags) -- | The build command does a lot. It brings the install plan up -- to date, selects that part of the plan needed by the given or implicit -- targets and then executes the plan. -- -- For more details on how this works, see the module -- Distribution.Client.ProjectOrchestration buildAction :: NixStyleFlags BuildFlags -> [String] -> GlobalFlags -> IO () data BuildFlags BuildFlags :: Flag Bool -> BuildFlags [buildOnlyConfigure] :: BuildFlags -> Flag Bool defaultBuildFlags :: BuildFlags -- | This defines what a TargetSelector means for the bench -- command. It selects the AvailableTargets that the -- TargetSelector refers to, or otherwise classifies the problem. -- -- For the build command select all components except -- non-buildable and disabled tests/benchmarks, fail if there are no such -- components selectPackageTargets :: TargetSelector -> [AvailableTarget k] -> Either TargetProblem' [k] -- | For a TargetComponent TargetSelector, check if the -- component can be selected. -- -- For the build command we just need the basic checks on being -- buildable etc. selectComponentTarget :: SubComponentTarget -> AvailableTarget k -> Either TargetProblem' k -- | cabal-install CLI command: bench module Distribution.Client.CmdBench benchCommand :: CommandUI (NixStyleFlags ()) -- | The build command does a lot. It brings the install plan up -- to date, selects that part of the plan needed by the given or implicit -- targets and then executes the plan. -- -- For more details on how this works, see the module -- Distribution.Client.ProjectOrchestration benchAction :: NixStyleFlags () -> [String] -> GlobalFlags -> IO () componentNotBenchmarkProblem :: PackageId -> ComponentName -> TargetProblem BenchProblem isSubComponentProblem :: PackageId -> ComponentName -> SubComponentTarget -> TargetProblem BenchProblem noBenchmarksProblem :: TargetSelector -> TargetProblem BenchProblem -- | This defines what a TargetSelector means for the bench -- command. It selects the AvailableTargets that the -- TargetSelector refers to, or otherwise classifies the problem. -- -- For the bench command we select all buildable benchmarks, or -- fail if there are no benchmarks or no buildable benchmarks. selectPackageTargets :: TargetSelector -> [AvailableTarget k] -> Either BenchTargetProblem [k] -- | For a TargetComponent TargetSelector, check if the -- component can be selected. -- -- For the bench command we just need to check it is a -- benchmark, in addition to the basic checks on being buildable etc. selectComponentTarget :: SubComponentTarget -> AvailableTarget k -> Either BenchTargetProblem k instance GHC.Show.Show Distribution.Client.CmdBench.BenchProblem instance GHC.Classes.Eq Distribution.Client.CmdBench.BenchProblem module Distribution.Client.CmdSdist sdistCommand :: CommandUI (ProjectFlags, SdistFlags) sdistAction :: (ProjectFlags, SdistFlags) -> [String] -> GlobalFlags -> IO () packageToSdist :: Verbosity -> FilePath -> OutputFormat -> FilePath -> UnresolvedSourcePackage -> IO () data OutputFormat SourceList :: Char -> OutputFormat TarGzArchive :: OutputFormat instance GHC.Classes.Eq Distribution.Client.CmdSdist.OutputFormat instance GHC.Show.Show Distribution.Client.CmdSdist.OutputFormat -- | cabal-install CLI command: repl module Distribution.Client.CmdRepl replCommand :: CommandUI (NixStyleFlags (ReplOptions, EnvFlags)) -- | The repl command is very much like build. It brings -- the install plan up to date, selects that part of the plan needed by -- the given or implicit repl target and then executes the plan. -- -- Compared to build the difference is that only one target is -- allowed (given or implicit) and the target type is repl rather than -- build. The general plan execution infrastructure handles both build -- and repl targets. -- -- For more details on how this works, see the module -- Distribution.Client.ProjectOrchestration replAction :: NixStyleFlags (ReplOptions, EnvFlags) -> [String] -> GlobalFlags -> IO () matchesMultipleProblem :: TargetSelector -> [AvailableTarget ()] -> ReplTargetProblem -- | This defines what a TargetSelector means for the repl -- command. It selects the AvailableTargets that the -- TargetSelector refers to, or otherwise classifies the problem. -- -- For repl we select: -- -- -- -- Fail if there are no buildable lib/exe components, or if there are -- multiple libs or exes. selectPackageTargets :: TargetSelector -> [AvailableTarget k] -> Either ReplTargetProblem [k] -- | For a TargetComponent TargetSelector, check if the -- component can be selected. -- -- For the repl command we just need the basic checks on being -- buildable etc. selectComponentTarget :: SubComponentTarget -> AvailableTarget k -> Either ReplTargetProblem k instance GHC.Show.Show Distribution.Client.CmdRepl.OriginalComponentInfo instance GHC.Show.Show Distribution.Client.CmdRepl.ReplProblem instance GHC.Classes.Eq Distribution.Client.CmdRepl.ReplProblem module Distribution.Client.CmdListBin listbinCommand :: CommandUI (NixStyleFlags ()) listbinAction :: NixStyleFlags () -> [String] -> GlobalFlags -> IO () -- | This defines what a TargetSelector means for the -- list-bin command. It selects the AvailableTargets that -- the TargetSelector refers to, or otherwise classifies the -- problem. -- -- For the list-bin command we select the exe or flib if there -- is only one and it's buildable. Fail if there are no or multiple -- buildable exe components. selectPackageTargets :: TargetSelector -> [AvailableTarget k] -> Either ListBinTargetProblem [k] -- | For a TargetComponent TargetSelector, check if the -- component can be selected. -- -- For the run command we just need to check it is a -- executable-like (an executable, a test, or a benchmark), in addition -- to the basic checks on being buildable etc. selectComponentTarget :: SubComponentTarget -> AvailableTarget k -> Either ListBinTargetProblem k noComponentsProblem :: TargetSelector -> ListBinTargetProblem matchesMultipleProblem :: TargetSelector -> [AvailableTarget ()] -> ListBinTargetProblem multipleTargetsProblem :: TargetsMap -> TargetProblem ListBinProblem componentNotRightKindProblem :: PackageId -> ComponentName -> TargetProblem ListBinProblem instance GHC.Show.Show Distribution.Client.CmdListBin.ListBinProblem instance GHC.Classes.Eq Distribution.Client.CmdListBin.ListBinProblem module Distribution.Client.CmdHaddockProject haddockProjectCommand :: CommandUI HaddockProjectFlags haddockProjectAction :: HaddockProjectFlags -> [String] -> GlobalFlags -> IO () -- | cabal-install CLI command: freeze module Distribution.Client.CmdFreeze freezeCommand :: CommandUI (NixStyleFlags ()) -- | To a first approximation, the freeze command runs the first -- phase of the build command where we bring the install plan up -- to date, and then based on the install plan we write out a -- cabal.project.freeze config file. -- -- For more details on how this works, see the module -- Distribution.Client.ProjectOrchestration freezeAction :: NixStyleFlags () -> [String] -> GlobalFlags -> IO () -- | Implementation of the 'v2-exec' command for running an arbitrary -- executable in an environment suited to the part of the store built for -- a project. module Distribution.Client.CmdExec execAction :: NixStyleFlags () -> [String] -> GlobalFlags -> IO () execCommand :: CommandUI (NixStyleFlags ()) -- | cabal-install CLI command: configure module Distribution.Client.CmdConfigure configureCommand :: CommandUI (NixStyleFlags ()) -- | To a first approximation, the configure just runs the first -- phase of the build command where we bring the install plan up -- to date (thus checking that it's possible). -- -- The only difference is that configure also allows the user to -- specify some extra config flags which we save in the file -- cabal.project.local. -- -- For more details on how this works, see the module -- Distribution.Client.ProjectOrchestration configureAction :: NixStyleFlags () -> [String] -> GlobalFlags -> IO () configureAction' :: NixStyleFlags () -> [String] -> GlobalFlags -> IO (ProjectBaseContext, ProjectConfig) -- | Implementation of the outdated command. Checks for outdated -- dependencies in the package description file or freeze file. module Distribution.Client.CmdOutdated outdatedCommand :: CommandUI (ProjectFlags, OutdatedFlags) -- | Entry point for the outdated command. outdatedAction :: (ProjectFlags, OutdatedFlags) -> [String] -> GlobalFlags -> IO () -- | Various knobs for customising the behaviour of listOutdated. data ListOutdatedSettings ListOutdatedSettings :: (PackageName -> Bool) -> (PackageName -> Bool) -> ListOutdatedSettings -- | Should this package be ignored? [listOutdatedIgnorePred] :: ListOutdatedSettings -> PackageName -> Bool -- | Should major version bumps be ignored for this package? [listOutdatedMinorPred] :: ListOutdatedSettings -> PackageName -> Bool -- | Find all outdated dependencies. listOutdated :: [PackageVersionConstraint] -> SourcePackageDb -> ListOutdatedSettings -> [(PackageVersionConstraint, Version)] instance GHC.Base.Monoid Distribution.Client.CmdOutdated.IgnoreMajorVersionBumps instance GHC.Base.Semigroup Distribution.Client.CmdOutdated.IgnoreMajorVersionBumps -- | cabal-install CLI command: build module Distribution.Client.CmdInstall installCommand :: CommandUI (NixStyleFlags ClientInstallFlags) -- | The install command actually serves four different needs. It -- installs: * exes: For example a program from hackage. The behavior is -- similar to the old install command, except that now conflicts between -- separate runs of the command are impossible thanks to the store. Exes -- are installed in the store like a normal dependency, then they are -- symlinked/copied in the directory specified by --installdir. To do -- this we need a dummy projectBaseContext containing the targets as -- extra packages and using a temporary dist directory. * libraries -- Libraries install through a similar process, but using GHC environment -- files instead of symlinks. This means that 'v2-install'ing libraries -- only works on GHC >= 8.0. -- -- For more details on how this works, see the module -- Distribution.Client.ProjectOrchestration installAction :: NixStyleFlags ClientInstallFlags -> [String] -> GlobalFlags -> IO () -- | This defines what a TargetSelector means for the bench -- command. It selects the AvailableTargets that the -- TargetSelector refers to, or otherwise classifies the problem. -- -- For the build command select all components except -- non-buildable and disabled tests/benchmarks, fail if there are no such -- components selectPackageTargets :: TargetSelector -> [AvailableTarget k] -> Either TargetProblem' [k] -- | For a TargetComponent TargetSelector, check if the -- component can be selected. -- -- For the build command we just need the basic checks on being -- buildable etc. selectComponentTarget :: SubComponentTarget -> AvailableTarget k -> Either TargetProblem' k establishDummyDistDirLayout :: Verbosity -> ProjectConfig -> FilePath -> IO DistDirLayout -- | Create a dummy project context, without a .cabal or a .cabal.project -- file (a place where to put a temporary dist directory is still needed) establishDummyProjectBaseContext :: Verbosity -> ProjectConfig -> DistDirLayout -> [PackageSpecifier UnresolvedSourcePackage] -> CurrentCommand -> IO ProjectBaseContext module Distribution.Client.CmdClean cleanCommand :: CommandUI CleanFlags cleanAction :: CleanFlags -> [String] -> GlobalFlags -> IO () instance GHC.Classes.Eq Distribution.Client.CmdClean.CleanFlags