License | GPL-3.0-or-later AND BSD-3-Clause |
---|---|
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data Project uri opt pkg = Project {
- prjPackages :: [pkg]
- prjOptPackages :: [opt]
- prjUriPackages :: [uri]
- prjConstraints :: [String]
- prjAllowNewer :: [String]
- prjReorderGoals :: Bool
- prjMaxBackjumps :: Maybe Int
- prjOptimization :: Optimization
- prjSourceRepos :: [SourceRepositoryPackage Maybe]
- prjOtherFields :: [PrettyField ()]
- triverseProject :: Applicative f => (uri -> f uri') -> (opt -> f opt') -> (pkg -> f pkg') -> Project uri opt pkg -> f (Project uri' opt' pkg')
- emptyProject :: Project c b a
- readProject :: FilePath -> IO (Project URI Void (FilePath, GenericPackageDescription))
- parseProject :: FilePath -> ByteString -> Either (ParseError NonEmpty) (Project Void String String)
- resolveProject :: FilePath -> Project Void String String -> IO (Either ResolveError (Project URI Void FilePath))
- newtype ResolveError = BadPackageLocation String
- renderResolveError :: ResolveError -> String
- readPackagesOfProject :: Project uri opt FilePath -> IO (Either (ParseError NonEmpty) (Project uri opt (FilePath, GenericPackageDescription)))
Project
data Project uri opt pkg Source #
cabal.project
file
Project | |
|
Instances
Bifunctor (Project c) Source # | |
Bitraversable (Project uri) Source # | |
Defined in Cabal.Project bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Project uri a b -> f (Project uri c d) # | |
Bifoldable (Project c) Source # | |
Functor (Project uri opt) Source # | |
Foldable (Project uri opt) Source # | |
Defined in Cabal.Project fold :: Monoid m => Project uri opt m -> m # foldMap :: Monoid m => (a -> m) -> Project uri opt a -> m # foldMap' :: Monoid m => (a -> m) -> Project uri opt a -> m # foldr :: (a -> b -> b) -> b -> Project uri opt a -> b # foldr' :: (a -> b -> b) -> b -> Project uri opt a -> b # foldl :: (b -> a -> b) -> b -> Project uri opt a -> b # foldl' :: (b -> a -> b) -> b -> Project uri opt a -> b # foldr1 :: (a -> a -> a) -> Project uri opt a -> a # foldl1 :: (a -> a -> a) -> Project uri opt a -> a # toList :: Project uri opt a -> [a] # null :: Project uri opt a -> Bool # length :: Project uri opt a -> Int # elem :: Eq a => a -> Project uri opt a -> Bool # maximum :: Ord a => Project uri opt a -> a # minimum :: Ord a => Project uri opt a -> a # | |
Traversable (Project uri opt) Source # | |
Defined in Cabal.Project traverse :: Applicative f => (a -> f b) -> Project uri opt a -> f (Project uri opt b) # sequenceA :: Applicative f => Project uri opt (f a) -> f (Project uri opt a) # mapM :: Monad m => (a -> m b) -> Project uri opt a -> m (Project uri opt b) # sequence :: Monad m => Project uri opt (m a) -> m (Project uri opt a) # | |
(Eq uri, Eq opt, Eq pkg) => Eq (Project uri opt pkg) Source # | Doesn't compare prjOtherFields |
Generic (Project uri opt pkg) Source # | |
(NFData c, NFData b, NFData a) => NFData (Project c b a) Source # | Since: 0.2.1 |
Defined in Cabal.Project | |
type Rep (Project uri opt pkg) Source # | |
Defined in Cabal.Project type Rep (Project uri opt pkg) = D1 ('MetaData "Project" "Cabal.Project" "cabal-install-parsers-0.4.1-BP7tLbeRrCUJ33WiVuP9m7" 'False) (C1 ('MetaCons "Project" 'PrefixI 'True) (((S1 ('MetaSel ('Just "prjPackages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [pkg]) :*: S1 ('MetaSel ('Just "prjOptPackages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [opt])) :*: (S1 ('MetaSel ('Just "prjUriPackages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [uri]) :*: (S1 ('MetaSel ('Just "prjConstraints") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "prjAllowNewer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])))) :*: ((S1 ('MetaSel ('Just "prjReorderGoals") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "prjMaxBackjumps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))) :*: (S1 ('MetaSel ('Just "prjOptimization") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Optimization) :*: (S1 ('MetaSel ('Just "prjSourceRepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SourceRepositoryPackage Maybe]) :*: S1 ('MetaSel ('Just "prjOtherFields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PrettyField ()])))))) |
triverseProject :: Applicative f => (uri -> f uri') -> (opt -> f opt') -> (pkg -> f pkg') -> Project uri opt pkg -> f (Project uri' opt' pkg') Source #
emptyProject :: Project c b a Source #
Empty project.
Parse project
readProject :: FilePath -> IO (Project URI Void (FilePath, GenericPackageDescription)) Source #
High level conviniene function to read and elaborate cabal.project
files
May throw IOException
when file doesn't exist, ParseError
on parse errors, or ResolveError
on package resolution error.
parseProject :: FilePath -> ByteString -> Either (ParseError NonEmpty) (Project Void String String) Source #
Parse project file. Extracts only few fields.
>>>
fmap prjPackages $ parseProject "cabal.project" "packages: foo bar/*.cabal"
Right ["foo","bar/*.cabal"]
Resolve project
:: FilePath | filename of project file |
-> Project Void String String | parsed project file |
-> IO (Either ResolveError (Project URI Void FilePath)) | resolved project |
Resolve project package locations.
Separate URI
packages, glob packages
and optional-packages
into individual fields.
The result prjPackages
FilePath
s will be relative to the
directory of the project file.
newtype ResolveError Source #
A resolveProject
error.
Instances
Show ResolveError Source # | |
Defined in Cabal.Project showsPrec :: Int -> ResolveError -> ShowS # show :: ResolveError -> String # showList :: [ResolveError] -> ShowS # | |
Exception ResolveError Source # | |
Defined in Cabal.Project |
renderResolveError :: ResolveError -> String Source #
Pretty print ResolveError
.
Read packages
readPackagesOfProject :: Project uri opt FilePath -> IO (Either (ParseError NonEmpty) (Project uri opt (FilePath, GenericPackageDescription))) Source #
Read and parse the cabal files of packages in the Project
.
May throw IOException
.