Cabal-3.6.3.0: A framework for packaging Haskell software
Safe HaskellSafe-Inferred
LanguageHaskell2010

Distribution.Fields.Field

Description

Cabal-like file AST types: Field, Section etc

These types are parametrized by an annotation.

Synopsis

Cabal file

data Field ann Source #

A Cabal-like file consists of a series of fields (foo: bar) and sections (library ...).

Constructors

Field !(Name ann) [FieldLine ann] 
Section !(Name ann) [SectionArg ann] [Field ann] 

Instances

Instances details
Foldable Field Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

fold :: Monoid m => Field m -> m Source #

foldMap :: Monoid m => (a -> m) -> Field a -> m Source #

foldMap' :: Monoid m => (a -> m) -> Field a -> m Source #

foldr :: (a -> b -> b) -> b -> Field a -> b Source #

foldr' :: (a -> b -> b) -> b -> Field a -> b Source #

foldl :: (b -> a -> b) -> b -> Field a -> b Source #

foldl' :: (b -> a -> b) -> b -> Field a -> b Source #

foldr1 :: (a -> a -> a) -> Field a -> a Source #

foldl1 :: (a -> a -> a) -> Field a -> a Source #

toList :: Field a -> [a] Source #

null :: Field a -> Bool Source #

length :: Field a -> Int Source #

elem :: Eq a => a -> Field a -> Bool Source #

maximum :: Ord a => Field a -> a Source #

minimum :: Ord a => Field a -> a Source #

sum :: Num a => Field a -> a Source #

product :: Num a => Field a -> a Source #

Traversable Field Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

traverse :: Applicative f => (a -> f b) -> Field a -> f (Field b) Source #

sequenceA :: Applicative f => Field (f a) -> f (Field a) Source #

mapM :: Monad m => (a -> m b) -> Field a -> m (Field b) Source #

sequence :: Monad m => Field (m a) -> m (Field a) Source #

Functor Field Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

fmap :: (a -> b) -> Field a -> Field b Source #

(<$) :: a -> Field b -> Field a Source #

Show ann => Show (Field ann) Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

showsPrec :: Int -> Field ann -> ShowS Source #

show :: Field ann -> String Source #

showList :: [Field ann] -> ShowS Source #

Eq ann => Eq (Field ann) Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

(==) :: Field ann -> Field ann -> Bool #

(/=) :: Field ann -> Field ann -> Bool #

fieldName :: Field ann -> Name ann Source #

Section of field name

fieldAnn :: Field ann -> ann Source #

fieldUniverse :: Field ann -> [Field ann] Source #

All transitive descendants of Field, including itself.

Note: the resulting list is never empty.

data FieldLine ann Source #

A line of text representing the value of a field from a Cabal file. A field may contain multiple lines.

Invariant: ByteString has no newlines.

Constructors

FieldLine !ann !ByteString 

Instances

Instances details
Foldable FieldLine Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

fold :: Monoid m => FieldLine m -> m Source #

foldMap :: Monoid m => (a -> m) -> FieldLine a -> m Source #

foldMap' :: Monoid m => (a -> m) -> FieldLine a -> m Source #

foldr :: (a -> b -> b) -> b -> FieldLine a -> b Source #

foldr' :: (a -> b -> b) -> b -> FieldLine a -> b Source #

foldl :: (b -> a -> b) -> b -> FieldLine a -> b Source #

foldl' :: (b -> a -> b) -> b -> FieldLine a -> b Source #

foldr1 :: (a -> a -> a) -> FieldLine a -> a Source #

foldl1 :: (a -> a -> a) -> FieldLine a -> a Source #

toList :: FieldLine a -> [a] Source #

null :: FieldLine a -> Bool Source #

length :: FieldLine a -> Int Source #

elem :: Eq a => a -> FieldLine a -> Bool Source #

maximum :: Ord a => FieldLine a -> a Source #

minimum :: Ord a => FieldLine a -> a Source #

sum :: Num a => FieldLine a -> a Source #

product :: Num a => FieldLine a -> a Source #

Traversable FieldLine Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

traverse :: Applicative f => (a -> f b) -> FieldLine a -> f (FieldLine b) Source #

sequenceA :: Applicative f => FieldLine (f a) -> f (FieldLine a) Source #

mapM :: Monad m => (a -> m b) -> FieldLine a -> m (FieldLine b) Source #

sequence :: Monad m => FieldLine (m a) -> m (FieldLine a) Source #

Functor FieldLine Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

fmap :: (a -> b) -> FieldLine a -> FieldLine b Source #

(<$) :: a -> FieldLine b -> FieldLine a Source #

Show ann => Show (FieldLine ann) Source # 
Instance details

Defined in Distribution.Fields.Field

Eq ann => Eq (FieldLine ann) Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

(==) :: FieldLine ann -> FieldLine ann -> Bool #

(/=) :: FieldLine ann -> FieldLine ann -> Bool #

fieldLineAnn :: FieldLine ann -> ann Source #

Since: Cabal-3.0.0.0

fieldLineBS :: FieldLine ann -> ByteString Source #

Since: Cabal-3.0.0.0

data SectionArg ann Source #

Section arguments, e.g. name of the library

Constructors

SecArgName !ann !ByteString

identifier, or something which looks like number. Also many dot numbers, i.e. "7.6.3"

SecArgStr !ann !ByteString

quoted string

SecArgOther !ann !ByteString

everything else, mm. operators (e.g. in if-section conditionals)

Instances

Instances details
Foldable SectionArg Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

fold :: Monoid m => SectionArg m -> m Source #

foldMap :: Monoid m => (a -> m) -> SectionArg a -> m Source #

foldMap' :: Monoid m => (a -> m) -> SectionArg a -> m Source #

foldr :: (a -> b -> b) -> b -> SectionArg a -> b Source #

foldr' :: (a -> b -> b) -> b -> SectionArg a -> b Source #

foldl :: (b -> a -> b) -> b -> SectionArg a -> b Source #

foldl' :: (b -> a -> b) -> b -> SectionArg a -> b Source #

foldr1 :: (a -> a -> a) -> SectionArg a -> a Source #

foldl1 :: (a -> a -> a) -> SectionArg a -> a Source #

toList :: SectionArg a -> [a] Source #

null :: SectionArg a -> Bool Source #

length :: SectionArg a -> Int Source #

elem :: Eq a => a -> SectionArg a -> Bool Source #

maximum :: Ord a => SectionArg a -> a Source #

minimum :: Ord a => SectionArg a -> a Source #

sum :: Num a => SectionArg a -> a Source #

product :: Num a => SectionArg a -> a Source #

Traversable SectionArg Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

traverse :: Applicative f => (a -> f b) -> SectionArg a -> f (SectionArg b) Source #

sequenceA :: Applicative f => SectionArg (f a) -> f (SectionArg a) Source #

mapM :: Monad m => (a -> m b) -> SectionArg a -> m (SectionArg b) Source #

sequence :: Monad m => SectionArg (m a) -> m (SectionArg a) Source #

Functor SectionArg Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

fmap :: (a -> b) -> SectionArg a -> SectionArg b Source #

(<$) :: a -> SectionArg b -> SectionArg a Source #

Show ann => Show (SectionArg ann) Source # 
Instance details

Defined in Distribution.Fields.Field

Eq ann => Eq (SectionArg ann) Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

(==) :: SectionArg ann -> SectionArg ann -> Bool #

(/=) :: SectionArg ann -> SectionArg ann -> Bool #

sectionArgAnn :: SectionArg ann -> ann Source #

Extract annotation from SectionArg.

Name

data Name ann Source #

A field name.

Invariant: ByteString is lower-case ASCII.

Constructors

Name !ann !FieldName 

Instances

Instances details
Foldable Name Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

fold :: Monoid m => Name m -> m Source #

foldMap :: Monoid m => (a -> m) -> Name a -> m Source #

foldMap' :: Monoid m => (a -> m) -> Name a -> m Source #

foldr :: (a -> b -> b) -> b -> Name a -> b Source #

foldr' :: (a -> b -> b) -> b -> Name a -> b Source #

foldl :: (b -> a -> b) -> b -> Name a -> b Source #

foldl' :: (b -> a -> b) -> b -> Name a -> b Source #

foldr1 :: (a -> a -> a) -> Name a -> a Source #

foldl1 :: (a -> a -> a) -> Name a -> a Source #

toList :: Name a -> [a] Source #

null :: Name a -> Bool Source #

length :: Name a -> Int Source #

elem :: Eq a => a -> Name a -> Bool Source #

maximum :: Ord a => Name a -> a Source #

minimum :: Ord a => Name a -> a Source #

sum :: Num a => Name a -> a Source #

product :: Num a => Name a -> a Source #

Traversable Name Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

traverse :: Applicative f => (a -> f b) -> Name a -> f (Name b) Source #

sequenceA :: Applicative f => Name (f a) -> f (Name a) Source #

mapM :: Monad m => (a -> m b) -> Name a -> m (Name b) Source #

sequence :: Monad m => Name (m a) -> m (Name a) Source #

Functor Name Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

fmap :: (a -> b) -> Name a -> Name b Source #

(<$) :: a -> Name b -> Name a Source #

Show ann => Show (Name ann) Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

showsPrec :: Int -> Name ann -> ShowS Source #

show :: Name ann -> String Source #

showList :: [Name ann] -> ShowS Source #

Eq ann => Eq (Name ann) Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

(==) :: Name ann -> Name ann -> Bool #

(/=) :: Name ann -> Name ann -> Bool #

mkName :: ann -> FieldName -> Name ann Source #

nameAnn :: Name ann -> ann Source #

Conversions to String

sectionArgsToString :: [SectionArg ann] -> String Source #

Since: Cabal-3.6.0.0

fieldLinesToString :: [FieldLine ann] -> String Source #

Convert [FieldLine] into String.

Note: this doesn't preserve indentation or empty lines, as the annotations (e.g. positions) are ignored.

Since: Cabal-3.6.0.0