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

Distribution.FieldGrammar.Parsec

Contents

Description

This module provides a FieldGrammarParser, one way to parse .cabal -like files.

Fields can be specified multiple times in the .cabal files. The order of such entries is important, but the mutual ordering of different fields is not.Also conditional sections are considered after non-conditional data. The example of this silent-commutation quirk is the fact that

buildable: True
if os(linux)
  buildable: False

and

if os(linux)
  buildable: False
buildable: True

behave the same! This is the limitation of GeneralPackageDescription structure.

So we transform the list of fields [Field ann] into a map of grouped ordinary fields and a list of lists of sections: Fields ann = Map FieldName [NamelessField ann] and [[Section ann]].

We need list of list of sections, because we need to distinguish situations where there are fields in between. For example

if flag(bytestring-lt-0_10_4)
  build-depends: bytestring < 0.10.4

default-language: Haskell2020

else
  build-depends: bytestring >= 0.10.4

is obviously invalid specification.

We can parse Fields like we parse aeson objects, yet we use slightly higher-level API, so we can process unspecified fields, to report unknown fields and save custom x-fields.

Synopsis

Documentation

data ParsecFieldGrammar s a Source #

Instances

Instances details
FieldGrammar Parsec ParsecFieldGrammar Source # 
Instance details

Defined in Distribution.FieldGrammar.Parsec

Methods

blurFieldGrammar :: ALens' a b -> ParsecFieldGrammar b d -> ParsecFieldGrammar a d Source #

uniqueFieldAla :: (Parsec b, Newtype a b) => FieldName -> (a -> b) -> ALens' s a -> ParsecFieldGrammar s a Source #

booleanFieldDef :: FieldName -> ALens' s Bool -> Bool -> ParsecFieldGrammar s Bool Source #

optionalFieldAla :: (Parsec b, Newtype a b) => FieldName -> (a -> b) -> ALens' s (Maybe a) -> ParsecFieldGrammar s (Maybe a) Source #

optionalFieldDefAla :: (Parsec b, Newtype a b, Eq a) => FieldName -> (a -> b) -> ALens' s a -> a -> ParsecFieldGrammar s a Source #

freeTextField :: FieldName -> ALens' s (Maybe String) -> ParsecFieldGrammar s (Maybe String) Source #

freeTextFieldDef :: FieldName -> ALens' s String -> ParsecFieldGrammar s String Source #

freeTextFieldDefST :: FieldName -> ALens' s ShortText -> ParsecFieldGrammar s ShortText Source #

monoidalFieldAla :: (Parsec b, Monoid a, Newtype a b) => FieldName -> (a -> b) -> ALens' s a -> ParsecFieldGrammar s a Source #

prefixedFields :: FieldName -> ALens' s [(String, String)] -> ParsecFieldGrammar s [(String, String)] Source #

knownField :: FieldName -> ParsecFieldGrammar s () Source #

hiddenField :: ParsecFieldGrammar s a -> ParsecFieldGrammar s a Source #

deprecatedSince :: CabalSpecVersion -> String -> ParsecFieldGrammar s a -> ParsecFieldGrammar s a Source #

removedIn :: CabalSpecVersion -> String -> ParsecFieldGrammar s a -> ParsecFieldGrammar s a Source #

availableSince :: CabalSpecVersion -> a -> ParsecFieldGrammar s a -> ParsecFieldGrammar s a Source #

availableSinceWarn :: CabalSpecVersion -> ParsecFieldGrammar s a -> ParsecFieldGrammar s a Source #

Applicative (ParsecFieldGrammar s) Source # 
Instance details

Defined in Distribution.FieldGrammar.Parsec

Functor (ParsecFieldGrammar s) Source # 
Instance details

Defined in Distribution.FieldGrammar.Parsec

Auxiliary

data NamelessField ann Source #

Single field, without name, but with its annotation.

Constructors

MkNamelessField !ann [FieldLine ann] 

Instances

Instances details
Functor NamelessField Source # 
Instance details

Defined in Distribution.FieldGrammar.Parsec

Methods

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

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

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

Defined in Distribution.FieldGrammar.Parsec

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

Defined in Distribution.FieldGrammar.Parsec

Methods

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

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

data Section ann Source #

The Section constructor of Field.

Constructors

MkSection !(Name ann) [SectionArg ann] [Field ann] 

Instances

Instances details
Functor Section Source # 
Instance details

Defined in Distribution.FieldGrammar.Parsec

Methods

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

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

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

Defined in Distribution.FieldGrammar.Parsec

Methods

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

show :: Section ann -> String Source #

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

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

Defined in Distribution.FieldGrammar.Parsec

Methods

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

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