Cabal-3.0.0.0: A framework for packaging Haskell software

Safe HaskellNone
LanguageHaskell2010

Distribution.Fields

Contents

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

Defined in Distribution.Fields.Field

Methods

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

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

Foldable Field Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

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

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

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

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

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

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

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

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

toList :: Field a -> [a] #

null :: Field a -> Bool #

length :: Field a -> Int #

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

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

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

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

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

Traversable Field Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

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

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

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

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

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

Defined in Distribution.Fields.Field

Methods

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

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

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

Defined in Distribution.Fields.Field

Methods

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

show :: Field ann -> String #

showList :: [Field ann] -> ShowS #

data Name ann Source #

A field name.

Invariant: ByteString is lower-case ASCII.

Constructors

Name !ann !FieldName 
Instances
Functor Name Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

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

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

Foldable Name Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

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

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

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

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

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

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

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

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

toList :: Name a -> [a] #

null :: Name a -> Bool #

length :: Name a -> Int #

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

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

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

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

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

Traversable Name Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

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

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

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

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

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

Defined in Distribution.Fields.Field

Methods

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

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

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

Defined in Distribution.Fields.Field

Methods

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

show :: Name ann -> String #

showList :: [Name ann] -> ShowS #

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

Defined in Distribution.Fields.Field

Methods

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

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

Foldable FieldLine Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

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

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

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

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

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

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

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

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

toList :: FieldLine a -> [a] #

null :: FieldLine a -> Bool #

length :: FieldLine a -> Int #

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

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

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

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

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

Traversable FieldLine Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

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

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

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

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

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

Defined in Distribution.Fields.Field

Methods

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

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

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

Defined in Distribution.Fields.Field

Methods

showsPrec :: Int -> FieldLine ann -> ShowS #

show :: FieldLine ann -> String #

showList :: [FieldLine ann] -> ShowS #

data SectionArg ann Source #

Section arguments, e.g. name of the library

Constructors

SecArgName !ann !ByteString

identifier, or omething which loos 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
Functor SectionArg Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

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

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

Foldable SectionArg Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

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

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

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

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

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

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

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

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

toList :: SectionArg a -> [a] #

null :: SectionArg a -> Bool #

length :: SectionArg a -> Int #

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

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

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

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

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

Traversable SectionArg Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

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

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

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

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

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

Defined in Distribution.Fields.Field

Methods

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

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

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

Defined in Distribution.Fields.Field

Methods

showsPrec :: Int -> SectionArg ann -> ShowS #

show :: SectionArg ann -> String #

showList :: [SectionArg ann] -> ShowS #

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
Monad ParseResult Source # 
Instance details

Defined in Distribution.Fields.ParseResult

Functor ParseResult Source # 
Instance details

Defined in Distribution.Fields.ParseResult

Methods

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

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

Applicative ParseResult Source # 
Instance details

Defined in Distribution.Fields.ParseResult

Methods

pure :: a -> ParseResult a #

(<*>) :: ParseResult (a -> b) -> ParseResult a -> ParseResult b #

liftA2 :: (a -> b -> c) -> ParseResult a -> ParseResult b -> ParseResult c #

(*>) :: ParseResult a -> ParseResult b -> ParseResult b #

(<*) :: ParseResult a -> ParseResult b -> ParseResult a #

runParseResult :: ParseResult a -> ([PWarning], Either (Maybe Version, [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
Bounded PWarnType Source # 
Instance details

Defined in Distribution.Parsec.Warning

Enum PWarnType Source # 
Instance details

Defined in Distribution.Parsec.Warning

Eq PWarnType Source # 
Instance details

Defined in Distribution.Parsec.Warning

Ord PWarnType Source # 
Instance details

Defined in Distribution.Parsec.Warning

Show PWarnType Source # 
Instance details

Defined in Distribution.Parsec.Warning

Generic PWarnType Source # 
Instance details

Defined in Distribution.Parsec.Warning

Associated Types

type Rep PWarnType :: Type -> Type #

Binary PWarnType Source # 
Instance details

Defined in Distribution.Parsec.Warning

NFData PWarnType Source # 
Instance details

Defined in Distribution.Parsec.Warning

Methods

rnf :: PWarnType -> () #

type Rep PWarnType Source # 
Instance details

Defined in Distribution.Parsec.Warning

type Rep PWarnType = D1 (MetaData "PWarnType" "Distribution.Parsec.Warning" "Cabal-3.0.0.0-Gy7jp3IKeIKC3g3Vs5T0x1" 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
Show PWarning Source # 
Instance details

Defined in Distribution.Parsec.Warning

Generic PWarning Source # 
Instance details

Defined in Distribution.Parsec.Warning

Associated Types

type Rep PWarning :: Type -> Type #

Methods

from :: PWarning -> Rep PWarning x #

to :: Rep PWarning x -> PWarning #

Binary PWarning Source # 
Instance details

Defined in Distribution.Parsec.Warning

Methods

put :: PWarning -> Put #

get :: Get PWarning #

putList :: [PWarning] -> Put #

NFData PWarning Source # 
Instance details

Defined in Distribution.Parsec.Warning

Methods

rnf :: PWarning -> () #

type Rep PWarning Source # 
Instance details

Defined in Distribution.Parsec.Warning

Errors

data PError Source #

Parser error.

Constructors

PError Position String 
Instances
Show PError Source # 
Instance details

Defined in Distribution.Parsec.Error

Generic PError Source # 
Instance details

Defined in Distribution.Parsec.Error

Associated Types

type Rep PError :: Type -> Type #

Methods

from :: PError -> Rep PError x #

to :: Rep PError x -> PError #

Binary PError Source # 
Instance details

Defined in Distribution.Parsec.Error

Methods

put :: PError -> Put #

get :: Get PError #

putList :: [PError] -> Put #

NFData PError Source # 
Instance details

Defined in Distribution.Parsec.Error

Methods

rnf :: PError -> () #

type Rep PError Source # 
Instance details

Defined in Distribution.Parsec.Error

Pretty printing

data PrettyField ann Source #

Instances
Functor PrettyField Source # 
Instance details

Defined in Distribution.Fields.Pretty

Methods

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

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

Foldable PrettyField Source # 
Instance details

Defined in Distribution.Fields.Pretty

Methods

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

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

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

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

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

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

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

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

toList :: PrettyField a -> [a] #

null :: PrettyField a -> Bool #

length :: PrettyField a -> Int #

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

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

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

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

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

Traversable PrettyField Source # 
Instance details

Defined in Distribution.Fields.Pretty

Methods

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

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

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

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

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