stack-1.9.1.1: The Haskell Tool Stack

Safe HaskellNone
LanguageHaskell2010

Stack.Types.Package

Synopsis

Documentation

data PackageLibraries Source #

Libraries in a package. Since Cabal 2.0, internal libraries are a thing.

Constructors

NoLibraries 
HasLibraries !(Set Text)

the foreign library names, sub libraries get built automatically without explicit component name passing

data Package Source #

Some package info.

Constructors

Package 

Fields

Instances
Eq Package Source #

Compares the package name.

Instance details

Defined in Stack.Types.Package

Methods

(==) :: Package -> Package -> Bool #

(/=) :: Package -> Package -> Bool #

Ord Package Source #

Compares the package name.

Instance details

Defined in Stack.Types.Package

Show Package Source # 
Instance details

Defined in Stack.Types.Package

data DepValue Source #

The value for a map from dependency name. This contains both the version range and the type of dependency, and provides a semigroup instance.

Constructors

DepValue 
Instances
Show DepValue Source # 
Instance details

Defined in Stack.Types.Package

Semigroup DepValue Source # 
Instance details

Defined in Stack.Types.Package

data DepType Source #

Is this package being used as a library, or just as a build tool? If the former, we need to ensure that a library actually exists. See https://github.com/commercialhaskell/stack/issues/2195

Constructors

AsLibrary 
AsBuildTool 
Instances
Eq DepType Source # 
Instance details

Defined in Stack.Types.Package

Methods

(==) :: DepType -> DepType -> Bool #

(/=) :: DepType -> DepType -> Bool #

Show DepType Source # 
Instance details

Defined in Stack.Types.Package

Semigroup DepType Source # 
Instance details

Defined in Stack.Types.Package

newtype GetPackageOpts Source #

Files that the package depends on, relative to package directory. Argument is the location of the .cabal file

data BuildInfoOpts Source #

GHC options based on cabal information and ghc-options.

Constructors

BuildInfoOpts 

Fields

data CabalFileType Source #

Files to get for a cabal package.

Constructors

AllFiles 
Modules 

newtype GetPackageFiles Source #

Files that the package depends on, relative to package directory. Argument is the location of the .cabal file

data PackageWarning Source #

Warning generated when reading a package

Constructors

UnlistedModulesWarning NamedComponent [ModuleName]

Modules found that are not listed in cabal file

data PackageConfig Source #

Package build configuration

Constructors

PackageConfig 

Fields

data PackageSource Source #

Where the package's source is located: local directory or package index

Constructors

PSFiles LocalPackage InstallLocation

Package which exist on the filesystem (as opposed to an index tarball)

PSIndex InstallLocation (Map FlagName Bool) [Text] PackageIdentifierRevision

Package which is in an index, and the files do not exist on the filesystem yet.

data LocalPackage Source #

Information on a locally available package of source code

Constructors

LocalPackage 

Fields

Instances
Show LocalPackage Source # 
Instance details

Defined in Stack.Types.Package

data FileCacheInfo Source #

Constructors

FileCacheInfo 
Instances
Eq FileCacheInfo Source # 
Instance details

Defined in Stack.Types.Package

Data FileCacheInfo Source # 
Instance details

Defined in Stack.Types.Package

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FileCacheInfo -> c FileCacheInfo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FileCacheInfo #

toConstr :: FileCacheInfo -> Constr #

dataTypeOf :: FileCacheInfo -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FileCacheInfo) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FileCacheInfo) #

gmapT :: (forall b. Data b => b -> b) -> FileCacheInfo -> FileCacheInfo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FileCacheInfo -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FileCacheInfo -> r #

gmapQ :: (forall d. Data d => d -> u) -> FileCacheInfo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FileCacheInfo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FileCacheInfo -> m FileCacheInfo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FileCacheInfo -> m FileCacheInfo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FileCacheInfo -> m FileCacheInfo #

Show FileCacheInfo Source # 
Instance details

Defined in Stack.Types.Package

Generic FileCacheInfo Source # 
Instance details

Defined in Stack.Types.Package

Associated Types

type Rep FileCacheInfo :: Type -> Type #

NFData FileCacheInfo Source # 
Instance details

Defined in Stack.Types.Package

Methods

rnf :: FileCacheInfo -> () #

Store FileCacheInfo Source # 
Instance details

Defined in Stack.Types.Package

type Rep FileCacheInfo Source # 
Instance details

Defined in Stack.Types.Package

type Rep FileCacheInfo = D1 (MetaData "FileCacheInfo" "Stack.Types.Package" "stack-1.9.1.1-6jz2L6XfBym9jbCxt3ojTR" False) (C1 (MetaCons "FileCacheInfo" PrefixI True) (S1 (MetaSel (Just "fciModTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ModTime) :*: (S1 (MetaSel (Just "fciSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word64) :*: S1 (MetaSel (Just "fciHash") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ByteString))))

newtype ModTime Source #

Used for storage and comparison.

Constructors

ModTime (Integer, Rational) 
Instances
Eq ModTime Source # 
Instance details

Defined in Stack.Types.Package

Methods

(==) :: ModTime -> ModTime -> Bool #

(/=) :: ModTime -> ModTime -> Bool #

Data ModTime Source # 
Instance details

Defined in Stack.Types.Package

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModTime -> c ModTime #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModTime #

toConstr :: ModTime -> Constr #

dataTypeOf :: ModTime -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ModTime) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModTime) #

gmapT :: (forall b. Data b => b -> b) -> ModTime -> ModTime #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModTime -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModTime -> r #

gmapQ :: (forall d. Data d => d -> u) -> ModTime -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ModTime -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModTime -> m ModTime #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModTime -> m ModTime #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModTime -> m ModTime #

Ord ModTime Source # 
Instance details

Defined in Stack.Types.Package

Show ModTime Source # 
Instance details

Defined in Stack.Types.Package

Generic ModTime Source # 
Instance details

Defined in Stack.Types.Package

Associated Types

type Rep ModTime :: Type -> Type #

Methods

from :: ModTime -> Rep ModTime x #

to :: Rep ModTime x -> ModTime #

NFData ModTime Source # 
Instance details

Defined in Stack.Types.Package

Methods

rnf :: ModTime -> () #

Store ModTime Source # 
Instance details

Defined in Stack.Types.Package

type Rep ModTime Source # 
Instance details

Defined in Stack.Types.Package

type Rep ModTime = D1 (MetaData "ModTime" "Stack.Types.Package" "stack-1.9.1.1-6jz2L6XfBym9jbCxt3ojTR" True) (C1 (MetaCons "ModTime" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Integer, Rational))))

dotCabalModule :: DotCabalDescriptor -> Maybe ModuleName Source #

Maybe get the module name from the .cabal descriptor.

dotCabalMain :: DotCabalDescriptor -> Maybe FilePath Source #

Maybe get the main name from the .cabal descriptor.

data DotCabalPath Source #

A path resolved from the .cabal file, which is either main-is or an exposedinternalreferenced module.

dotCabalCFilePath :: DotCabalPath -> Maybe (Path Abs File) Source #

Get the c file path.

installedVersion :: Installed -> Version Source #

Get the installed Version.