Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- data BuildInfoOpts = BuildInfoOpts {
- bioOpts :: [String]
- bioOneWordOpts :: [String]
- bioPackageFlags :: [String]
- bioCabalMacros :: Path Abs File
- newtype ExeName = ExeName {}
- newtype FileCacheInfo = FileCacheInfo {}
- newtype GetPackageOpts = GetPackageOpts {
- getPackageOpts :: forall env. HasEnvConfig env => InstallMap -> InstalledMap -> [PackageName] -> [PackageName] -> Path Abs File -> RIO env (Map NamedComponent (Map ModuleName (Path Abs File)), Map NamedComponent [DotCabalPath], Map NamedComponent BuildInfoOpts)
- data InstallLocation
- type InstallMap = Map PackageName (InstallLocation, Version)
- data Installed
- data InstalledPackageLocation
- type InstalledMap = Map PackageName (InstallLocation, Installed)
- data LocalPackage = LocalPackage {
- lpPackage :: !Package
- lpComponents :: !(Set NamedComponent)
- lpUnbuildable :: !(Set NamedComponent)
- lpWanted :: !Bool
- lpTestBench :: !(Maybe Package)
- lpCabalFile :: !(Path Abs File)
- lpBuildHaddocks :: !Bool
- lpForceDirty :: !Bool
- lpDirtyFiles :: !(MemoizedWith EnvConfig (Maybe (Set FilePath)))
- lpNewBuildCaches :: !(MemoizedWith EnvConfig (Map NamedComponent (Map FilePath FileCacheInfo)))
- lpComponentFiles :: !(MemoizedWith EnvConfig (Map NamedComponent (Set (Path Abs File))))
- newtype MemoizedWith env a = MemoizedWith {
- unMemoizedWith :: RIO env a
- data Package = Package {
- packageName :: !PackageName
- packageVersion :: !Version
- packageLicense :: !(Either License License)
- packageFiles :: !GetPackageFiles
- packageDeps :: !(Map PackageName DepValue)
- packageUnknownTools :: !(Set ExeName)
- packageAllDeps :: !(Set PackageName)
- packageSubLibDeps :: !(Map MungedPackageName DepValue)
- packageGhcOptions :: ![Text]
- packageCabalConfigOpts :: ![Text]
- packageFlags :: !(Map FlagName Bool)
- packageDefaultFlags :: !(Map FlagName Bool)
- packageLibraries :: !PackageLibraries
- packageInternalLibraries :: !(Set Text)
- packageTests :: !(Map Text TestSuiteInterface)
- packageBenchmarks :: !(Set Text)
- packageExes :: !(Set Text)
- packageOpts :: !GetPackageOpts
- packageHasExposedModules :: !Bool
- packageBuildType :: !BuildType
- packageSetupDeps :: !(Maybe (Map PackageName VersionRange))
- packageCabalSpec :: !CabalSpecVersion
- data PackageConfig = PackageConfig {}
- data PackageException
- data PackageLibraries
- = NoLibraries
- | HasLibraries !(Set Text)
- data PackageSource
- dotCabalCFilePath :: DotCabalPath -> Maybe (Path Abs File)
- dotCabalGetPath :: DotCabalPath -> Path Abs File
- dotCabalMain :: DotCabalDescriptor -> Maybe FilePath
- dotCabalMainPath :: DotCabalPath -> Maybe (Path Abs File)
- dotCabalModule :: DotCabalDescriptor -> Maybe ModuleName
- dotCabalModulePath :: DotCabalPath -> Maybe (Path Abs File)
- installedPackageIdentifier :: Installed -> PackageIdentifier
- installedVersion :: Installed -> Version
- lpFiles :: HasEnvConfig env => LocalPackage -> RIO env (Set (Path Abs File))
- lpFilesForComponents :: HasEnvConfig env => Set NamedComponent -> LocalPackage -> RIO env (Set (Path Abs File))
- memoizeRefWith :: MonadIO m => RIO env a -> m (MemoizedWith env a)
- packageDefinedFlags :: Package -> Set FlagName
- packageIdent :: Package -> PackageIdentifier
- packageIdentifier :: Package -> PackageIdentifier
- psVersion :: PackageSource -> Version
- runMemoizedWith :: (HasEnvConfig env, MonadReader env m, MonadIO m) => MemoizedWith EnvConfig a -> m a
Documentation
data BuildInfoOpts Source #
GHC options based on cabal information and ghc-options.
BuildInfoOpts | |
|
Instances
Show BuildInfoOpts Source # | |
Defined in Stack.Types.Package showsPrec :: Int -> BuildInfoOpts -> ShowS # show :: BuildInfoOpts -> String # showList :: [BuildInfoOpts] -> ShowS # |
Name of an executable.
Instances
Data ExeName Source # | |
Defined in Stack.Types.Package gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExeName -> c ExeName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExeName # toConstr :: ExeName -> Constr # dataTypeOf :: ExeName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ExeName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExeName) # gmapT :: (forall b. Data b => b -> b) -> ExeName -> ExeName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExeName -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExeName -> r # gmapQ :: (forall d. Data d => d -> u) -> ExeName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ExeName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExeName -> m ExeName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExeName -> m ExeName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExeName -> m ExeName # | |
IsString ExeName Source # | |
Defined in Stack.Types.Package fromString :: String -> ExeName # | |
Generic ExeName Source # | |
Show ExeName Source # | |
NFData ExeName Source # | |
Defined in Stack.Types.Package | |
Eq ExeName Source # | |
Ord ExeName Source # | |
Hashable ExeName Source # | |
Defined in Stack.Types.Package | |
type Rep ExeName Source # | |
Defined in Stack.Types.Package |
newtype FileCacheInfo Source #
Instances
newtype GetPackageOpts Source #
Files that the package depends on, relative to package directory. Argument is the location of the Cabal file
GetPackageOpts | |
|
Instances
Show GetPackageOpts Source # | |
Defined in Stack.Types.Package showsPrec :: Int -> GetPackageOpts -> ShowS # show :: GetPackageOpts -> String # showList :: [GetPackageOpts] -> ShowS # |
data InstallLocation Source #
A location to install a package into, either snapshot or local
Instances
Monoid InstallLocation Source # | |
Defined in Stack.Types.Package mappend :: InstallLocation -> InstallLocation -> InstallLocation # mconcat :: [InstallLocation] -> InstallLocation # | |
Semigroup InstallLocation Source # | |
Defined in Stack.Types.Package (<>) :: InstallLocation -> InstallLocation -> InstallLocation # sconcat :: NonEmpty InstallLocation -> InstallLocation # stimes :: Integral b => b -> InstallLocation -> InstallLocation # | |
Show InstallLocation Source # | |
Defined in Stack.Types.Package showsPrec :: Int -> InstallLocation -> ShowS # show :: InstallLocation -> String # showList :: [InstallLocation] -> ShowS # | |
Eq InstallLocation Source # | |
Defined in Stack.Types.Package (==) :: InstallLocation -> InstallLocation -> Bool # (/=) :: InstallLocation -> InstallLocation -> Bool # |
type InstallMap = Map PackageName (InstallLocation, Version) Source #
Instances
data InstalledPackageLocation Source #
Instances
Show InstalledPackageLocation Source # | |
Defined in Stack.Types.Package showsPrec :: Int -> InstalledPackageLocation -> ShowS # show :: InstalledPackageLocation -> String # showList :: [InstalledPackageLocation] -> ShowS # | |
Eq InstalledPackageLocation Source # | |
Defined in Stack.Types.Package |
type InstalledMap = Map PackageName (InstallLocation, Installed) Source #
data LocalPackage Source #
Information on a locally available package of source code.
LocalPackage | |
|
Instances
Show LocalPackage Source # | |
Defined in Stack.Types.Package showsPrec :: Int -> LocalPackage -> ShowS # show :: LocalPackage -> String # showList :: [LocalPackage] -> ShowS # |
newtype MemoizedWith env a Source #
MemoizedWith | |
|
Instances
Some package info.
Package | |
|
data PackageConfig Source #
Package build configuration
PackageConfig | |
|
Instances
Show PackageConfig Source # | |
Defined in Stack.Types.Package showsPrec :: Int -> PackageConfig -> ShowS # show :: PackageConfig -> String # showList :: [PackageConfig] -> ShowS # |
data PackageException Source #
Type representing exceptions thrown by functions exported by the Stack.Package module.
Instances
Exception PackageException Source # | |
Defined in Stack.Types.Package | |
Show PackageException Source # | |
Defined in Stack.Types.Package showsPrec :: Int -> PackageException -> ShowS # show :: PackageException -> String # showList :: [PackageException] -> ShowS # |
data PackageLibraries Source #
Libraries in a package. Since Cabal 2.0, internal libraries are a thing.
NoLibraries | |
HasLibraries !(Set Text) | the foreign library names, sub libraries get built automatically without explicit component name passing |
Instances
Show PackageLibraries Source # | |
Defined in Stack.Types.Package showsPrec :: Int -> PackageLibraries -> ShowS # show :: PackageLibraries -> String # showList :: [PackageLibraries] -> ShowS # |
data PackageSource Source #
Where the package's source is located: local directory or package index
PSFilePath LocalPackage | Package which exist on the filesystem |
PSRemote PackageLocationImmutable Version FromSnapshot CommonPackage | Package which is downloaded remotely. |
Instances
Show PackageSource Source # | |
Defined in Stack.Types.Package showsPrec :: Int -> PackageSource -> ShowS # show :: PackageSource -> String # showList :: [PackageSource] -> ShowS # |
dotCabalCFilePath :: DotCabalPath -> Maybe (Path Abs File) Source #
Get the c file path.
dotCabalGetPath :: DotCabalPath -> Path Abs File Source #
Get the path.
dotCabalMain :: DotCabalDescriptor -> Maybe FilePath Source #
Maybe get the main name from the .cabal descriptor.
dotCabalMainPath :: DotCabalPath -> Maybe (Path Abs File) Source #
Get the main path.
dotCabalModule :: DotCabalDescriptor -> Maybe ModuleName Source #
Maybe get the module name from the .cabal descriptor.
dotCabalModulePath :: DotCabalPath -> Maybe (Path Abs File) Source #
Get the module path.
installedVersion :: Installed -> Version Source #
Get the installed Version.
lpFiles :: HasEnvConfig env => LocalPackage -> RIO env (Set (Path Abs File)) Source #
lpFilesForComponents :: HasEnvConfig env => Set NamedComponent -> LocalPackage -> RIO env (Set (Path Abs File)) Source #
memoizeRefWith :: MonadIO m => RIO env a -> m (MemoizedWith env a) Source #
psVersion :: PackageSource -> Version Source #
runMemoizedWith :: (HasEnvConfig env, MonadReader env m, MonadIO m) => MemoizedWith EnvConfig a -> m a Source #