cabal-install-parsers-0.4: Utilities to work with cabal-install files

LicenseGPL-3.0-or-later AND BSD-3-Clause
Safe HaskellNone
LanguageHaskell2010

Cabal.Project

Contents

Description

 
Synopsis

Project

data Project uri opt pkg Source #

cabal.project file

Constructors

Project 

Fields

Instances
Bifunctor (Project c) Source # 
Instance details

Defined in Cabal.Project

Methods

bimap :: (a -> b) -> (c0 -> d) -> Project c a c0 -> Project c b d #

first :: (a -> b) -> Project c a c0 -> Project c b c0 #

second :: (b -> c0) -> Project c a b -> Project c a c0 #

Bitraversable (Project uri) Source # 
Instance details

Defined in Cabal.Project

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Project uri a b -> f (Project uri c d) #

Bifoldable (Project c) Source # 
Instance details

Defined in Cabal.Project

Methods

bifold :: Monoid m => Project c m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Project c a b -> m #

bifoldr :: (a -> c0 -> c0) -> (b -> c0 -> c0) -> c0 -> Project c a b -> c0 #

bifoldl :: (c0 -> a -> c0) -> (c0 -> b -> c0) -> c0 -> Project c a b -> c0 #

Functor (Project uri opt) Source # 
Instance details

Defined in Cabal.Project

Methods

fmap :: (a -> b) -> Project uri opt a -> Project uri opt b #

(<$) :: a -> Project uri opt b -> Project uri opt a #

Foldable (Project uri opt) Source # 
Instance details

Defined in Cabal.Project

Methods

fold :: Monoid m => Project uri opt m -> 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 #

sum :: Num a => Project uri opt a -> a #

product :: Num a => Project uri opt a -> a #

Traversable (Project uri opt) Source # 
Instance details

Defined in Cabal.Project

Methods

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

Instance details

Defined in Cabal.Project

Methods

(==) :: Project uri opt pkg -> Project uri opt pkg -> Bool #

(/=) :: Project uri opt pkg -> Project uri opt pkg -> Bool #

Generic (Project uri opt pkg) Source # 
Instance details

Defined in Cabal.Project

Associated Types

type Rep (Project uri opt pkg) :: Type -> Type #

Methods

from :: Project uri opt pkg -> Rep (Project uri opt pkg) x #

to :: Rep (Project uri opt pkg) x -> Project uri opt pkg #

(NFData c, NFData b, NFData a) => NFData (Project c b a) Source #

Since: 0.2.1

Instance details

Defined in Cabal.Project

Methods

rnf :: Project c b a -> () #

type Rep (Project uri opt pkg) Source # 
Instance details

Defined in Cabal.Project

triverseProject :: Applicative f => (uri -> f uri') -> (opt -> f opt') -> (pkg -> f pkg') -> Project uri opt pkg -> f (Project uri' opt' pkg') Source #

traverse over all three type arguments of Project.

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

resolveProject Source #

Arguments

:: 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 FilePaths will be relative to the directory of the project file.

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.