stack-2.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

newtype ExeName Source #

Name of an executable.

Constructors

ExeName 

Fields

Instances
Eq ExeName Source # 
Instance details

Defined in Stack.Types.Package

Methods

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

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

Data ExeName 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) -> 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 :: (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 #

Ord ExeName Source # 
Instance details

Defined in Stack.Types.Package

Show ExeName Source # 
Instance details

Defined in Stack.Types.Package

IsString ExeName Source # 
Instance details

Defined in Stack.Types.Package

Methods

fromString :: String -> ExeName #

Generic ExeName Source # 
Instance details

Defined in Stack.Types.Package

Associated Types

type Rep ExeName :: Type -> Type #

Methods

from :: ExeName -> Rep ExeName x #

to :: Rep ExeName x -> ExeName #

NFData ExeName Source # 
Instance details

Defined in Stack.Types.Package

Methods

rnf :: ExeName -> () #

Hashable ExeName Source # 
Instance details

Defined in Stack.Types.Package

Methods

hashWithSalt :: Int -> ExeName -> Int #

hash :: ExeName -> Int #

type Rep ExeName Source # 
Instance details

Defined in Stack.Types.Package

type Rep ExeName = D1 (MetaData "ExeName" "Stack.Types.Package" "stack-2.1.1-61yUJamJcYLHh5iq4tOGPX" True) (C1 (MetaCons "ExeName" PrefixI True) (S1 (MetaSel (Just "unExeName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

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

PSFilePath LocalPackage

Package which exist on the filesystem

PSRemote PackageLocationImmutable Version FromSnapshot CommonPackage

Package which is downloaded remotely.

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

newtype MemoizedWith env a Source #

Constructors

MemoizedWith 

Fields

Instances
Monad (MemoizedWith env) Source # 
Instance details

Defined in Stack.Types.Package

Methods

(>>=) :: MemoizedWith env a -> (a -> MemoizedWith env b) -> MemoizedWith env b #

(>>) :: MemoizedWith env a -> MemoizedWith env b -> MemoizedWith env b #

return :: a -> MemoizedWith env a #

fail :: String -> MemoizedWith env a #

Functor (MemoizedWith env) Source # 
Instance details

Defined in Stack.Types.Package

Methods

fmap :: (a -> b) -> MemoizedWith env a -> MemoizedWith env b #

(<$) :: a -> MemoizedWith env b -> MemoizedWith env a #

Applicative (MemoizedWith env) Source # 
Instance details

Defined in Stack.Types.Package

Methods

pure :: a -> MemoizedWith env a #

(<*>) :: MemoizedWith env (a -> b) -> MemoizedWith env a -> MemoizedWith env b #

liftA2 :: (a -> b -> c) -> MemoizedWith env a -> MemoizedWith env b -> MemoizedWith env c #

(*>) :: MemoizedWith env a -> MemoizedWith env b -> MemoizedWith env b #

(<*) :: MemoizedWith env a -> MemoizedWith env b -> MemoizedWith env a #

Show (MemoizedWith env a) Source # 
Instance details

Defined in Stack.Types.Package

Methods

showsPrec :: Int -> MemoizedWith env a -> ShowS #

show :: MemoizedWith env a -> String #

showList :: [MemoizedWith env a] -> ShowS #

memoizeRefWith :: MonadIO m => RIO env a -> m (MemoizedWith env a) Source #

data FileCacheInfo Source #

Constructors

FileCacheInfo 
Instances
Eq FileCacheInfo Source # 
Instance details

Defined in Stack.Types.Package

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 -> () #

ToJSON FileCacheInfo Source # 
Instance details

Defined in Stack.Types.Package

FromJSON 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-2.1.1-61yUJamJcYLHh5iq4tOGPX" False) (C1 (MetaCons "FileCacheInfo" PrefixI True) (S1 (MetaSel (Just "fciModTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 CTime) :*: (S1 (MetaSel (Just "fciSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FileSize) :*: S1 (MetaSel (Just "fciHash") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SHA256))))

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.