Cabal-3.2.0.0: A framework for packaging Haskell software
Safe HaskellNone
LanguageHaskell2010

Distribution.Fields

Description

Utilitiies to work with .cabal like file structure.

Synopsis

Types

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
Functor Field # 
Instance details

Defined in Distribution.Fields.Field

Methods

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

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

Foldable Field # 
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 # 
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 #

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

Defined in Distribution.Fields.Field

Methods

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

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

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

Defined in Distribution.Fields.Field

Methods

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

show :: Field ann -> String Source #

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

data Name ann Source #

A field name.

Invariant: ByteString is lower-case ASCII.

Constructors

Name !ann !FieldName 

Instances

Instances details
Functor Name # 
Instance details

Defined in Distribution.Fields.Field

Methods

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

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

Foldable Name # 
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 # 
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 #

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

Defined in Distribution.Fields.Field

Methods

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

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

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

Defined in Distribution.Fields.Field

Methods

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

show :: Name ann -> String Source #

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

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
Functor FieldLine # 
Instance details

Defined in Distribution.Fields.Field

Methods

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

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

Foldable FieldLine # 
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 # 
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 #

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

Defined in Distribution.Fields.Field

Methods

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

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

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

Defined in Distribution.Fields.Field

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
Functor SectionArg # 
Instance details

Defined in Distribution.Fields.Field

Methods

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

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

Foldable SectionArg # 
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 # 
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 #

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

Defined in Distribution.Fields.Field

Methods

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

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

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

Defined in Distribution.Fields.Field

Grammar and parsing

readFields :: ByteString -> Either ParseError [Field Position] Source #

Parse cabal style ByteString into list of Fields, i.e. the cabal AST.

readFields' :: ByteString -> Either ParseError ([Field Position], [LexWarning]) Source #

Like readFields but also return lexer warnings

ParseResult

data ParseResult a Source #

A monad with failure and accumulating errors and warnings.

Instances

Instances details
Monad ParseResult # 
Instance details

Defined in Distribution.Fields.ParseResult

Functor ParseResult # 
Instance details

Defined in Distribution.Fields.ParseResult

Methods

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

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

Applicative ParseResult # 
Instance details

Defined in Distribution.Fields.ParseResult

runParseResult :: ParseResult a -> ([PWarning], Either (Maybe Version, NonEmpty PError) a) Source #

Destruct a ParseResult into the emitted warnings and either a successful value or list of errors and possibly recovered a spec-version declaration.

parseString Source #

Arguments

:: (ByteString -> ParseResult a)

File contents to final value parser

-> Verbosity

Verbosity level

-> String

File name

-> ByteString 
-> IO a 

parseWarning :: Position -> PWarnType -> String -> ParseResult () Source #

Add a warning. This doesn't fail the parsing process.

parseWarnings :: [PWarning] -> ParseResult () Source #

Add multiple warnings at once.

parseFailure :: Position -> String -> ParseResult () Source #

Add an error, but not fail the parser yet.

For fatal failure use parseFatalFailure

parseFatalFailure :: Position -> String -> ParseResult a Source #

Add an fatal error.

Warnings

data PWarnType Source #

Type of parser warning. We do classify warnings.

Different application may decide not to show some, or have fatal behaviour on others

Constructors

PWTOther

Unclassified warning

PWTUTF

Invalid UTF encoding

PWTBoolCase

true or false, not True or False

PWTVersionTag

there are version with tags

PWTNewSyntax

New syntax used, but no cabal-version: >= 1.2 specified

PWTOldSyntax

Old syntax used, and cabal-version >= 1.2 specified

PWTDeprecatedField 
PWTInvalidSubsection 
PWTUnknownField 
PWTUnknownSection 
PWTTrailingFields 
PWTExtraMainIs

extra main-is field

PWTExtraTestModule

extra test-module field

PWTExtraBenchmarkModule

extra benchmark-module field

PWTLexNBSP 
PWTLexBOM 
PWTLexTab 
PWTQuirkyCabalFile

legacy cabal file that we know how to patch

PWTDoubleDash

Double dash token, most likely it's a mistake - it's not a comment

PWTMultipleSingularField

e.g. name or version should be specified only once.

PWTBuildTypeDefault

Workaround for derive-package having build-type: Default. See https://github.com/haskell/cabal/issues/5020.

Instances

Instances details
Bounded PWarnType # 
Instance details

Defined in Distribution.Parsec.Warning

Enum PWarnType # 
Instance details

Defined in Distribution.Parsec.Warning

Eq PWarnType # 
Instance details

Defined in Distribution.Parsec.Warning

Ord PWarnType # 
Instance details

Defined in Distribution.Parsec.Warning

Show PWarnType # 
Instance details

Defined in Distribution.Parsec.Warning

Generic PWarnType # 
Instance details

Defined in Distribution.Parsec.Warning

Associated Types

type Rep PWarnType :: Type -> Type Source #

Binary PWarnType # 
Instance details

Defined in Distribution.Parsec.Warning

NFData PWarnType # 
Instance details

Defined in Distribution.Parsec.Warning

Methods

rnf :: PWarnType -> () Source #

type Rep PWarnType # 
Instance details

Defined in Distribution.Parsec.Warning

type Rep PWarnType = D1 ('MetaData "PWarnType" "Distribution.Parsec.Warning" "Cabal-3.2.0.0" 'False) ((((C1 ('MetaCons "PWTOther" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PWTUTF" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PWTBoolCase" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PWTVersionTag" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PWTNewSyntax" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "PWTOldSyntax" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PWTDeprecatedField" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PWTInvalidSubsection" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PWTUnknownField" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PWTUnknownSection" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "PWTTrailingFields" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PWTExtraMainIs" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PWTExtraTestModule" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PWTExtraBenchmarkModule" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PWTLexNBSP" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "PWTLexBOM" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PWTLexTab" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PWTQuirkyCabalFile" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "PWTDoubleDash" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PWTMultipleSingularField" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PWTBuildTypeDefault" 'PrefixI 'False) (U1 :: Type -> Type))))))

data PWarning Source #

Parser warning.

Instances

Instances details
Show PWarning # 
Instance details

Defined in Distribution.Parsec.Warning

Generic PWarning # 
Instance details

Defined in Distribution.Parsec.Warning

Associated Types

type Rep PWarning :: Type -> Type Source #

Binary PWarning # 
Instance details

Defined in Distribution.Parsec.Warning

NFData PWarning # 
Instance details

Defined in Distribution.Parsec.Warning

Methods

rnf :: PWarning -> () Source #

type Rep PWarning # 
Instance details

Defined in Distribution.Parsec.Warning

Errors

data PError Source #

Parser error.

Constructors

PError Position String 

Instances

Instances details
Show PError # 
Instance details

Defined in Distribution.Parsec.Error

Generic PError # 
Instance details

Defined in Distribution.Parsec.Error

Associated Types

type Rep PError :: Type -> Type Source #

Binary PError # 
Instance details

Defined in Distribution.Parsec.Error

NFData PError # 
Instance details

Defined in Distribution.Parsec.Error

Methods

rnf :: PError -> () Source #

type Rep PError # 
Instance details

Defined in Distribution.Parsec.Error

Pretty printing

data PrettyField ann Source #

Instances

Instances details
Functor PrettyField # 
Instance details

Defined in Distribution.Fields.Pretty

Methods

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

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

Foldable PrettyField # 
Instance details

Defined in Distribution.Fields.Pretty

Methods

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

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

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

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

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

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

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

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

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

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

null :: PrettyField a -> Bool Source #

length :: PrettyField a -> Int Source #

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

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

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

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

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

Traversable PrettyField # 
Instance details

Defined in Distribution.Fields.Pretty

Methods

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

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

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

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

showFields :: (ann -> [String]) -> [PrettyField ann] -> String Source #

Prettyprint a list of fields.

Note: the first argument should return Strings without newlines and properly prefixes (with --) to count as comments. This unsafety is left in place so one could generate empty lines between comment lines.

Transformation from Field

genericFromParsecFields Source #

Arguments

:: Applicative f 
=> (FieldName -> [FieldLine ann] -> f Doc)

transform field contents

-> (FieldName -> [SectionArg ann] -> f [Doc])

transform section arguments

-> [Field ann] 
-> f [PrettyField ann] 

fromParsecFields :: [Field ann] -> [PrettyField ann] Source #

Simple variant of genericFromParsecField