Cabal-3.2.1.0: A framework for packaging Haskell software

Safe HaskellNone
LanguageHaskell2010

Distribution.FieldGrammar

Contents

Description

This module provides a way to specify a grammar of .cabal -like files.

Synopsis

Field grammar type

class FieldGrammar g where Source #

FieldGrammar is parametrised by

  • s which is a structure we are parsing. We need this to provide prettyprinter functionality
  • a type of the field.

Note: We'd like to have forall s. Applicative (f s) context.

Methods

blurFieldGrammar :: ALens' a b -> g b c -> g a c Source #

Unfocus, zoom out, blur FieldGrammar.

uniqueFieldAla Source #

Arguments

:: (Parsec b, Pretty b, Newtype a b) 
=> FieldName

field name

-> (a -> b)

Newtype pack

-> ALens' s a

lens into the field

-> g s a 

Field which should be defined, exactly once.

booleanFieldDef Source #

Arguments

:: FieldName

field name

-> ALens' s Bool

lens into the field

-> Bool

default

-> g s Bool 

Boolean field with a default value.

optionalFieldAla Source #

Arguments

:: (Parsec b, Pretty b, Newtype a b) 
=> FieldName

field name

-> (a -> b)

pack

-> ALens' s (Maybe a)

lens into the field

-> g s (Maybe a) 

Optional field.

optionalFieldDefAla Source #

Arguments

:: (Parsec b, Pretty b, Newtype a b, Eq a) 
=> FieldName

field name

-> (a -> b)

Newtype pack

-> ALens' s a

Lens' s a: lens into the field

-> a

default value

-> g s a 

Optional field with default value.

freeTextField Source #

Arguments

:: FieldName 
-> ALens' s (Maybe String)

lens into the field

-> g s (Maybe String) 

freeTextFieldDef Source #

Arguments

:: FieldName 
-> ALens' s String

lens into the field

-> g s String 

freeTextFieldDefST Source #

Arguments

:: FieldName 
-> ALens' s ShortText

lens into the field

-> g s ShortText 

Since: 3.2.0.0

monoidalFieldAla Source #

Arguments

:: (Parsec b, Pretty b, Monoid a, Newtype a b) 
=> FieldName

field name

-> (a -> b)

pack

-> ALens' s a

lens into the field

-> g s a 

Monoidal field.

Values are combined with mappend.

Note: optionalFieldAla is a monoidalField with Last monoid.

prefixedFields Source #

Arguments

:: FieldName

field name prefix

-> ALens' s [(String, String)]

lens into the field

-> g s [(String, String)] 

Parser matching all fields with a name starting with a prefix.

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

Known field, which we don't parse, neither pretty print.

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

Field which is parsed but not pretty printed.

deprecatedSince Source #

Arguments

:: CabalSpecVersion

version

-> String

deprecation message

-> g s a 
-> g s a 

Deprecated since

removedIn Source #

Arguments

:: CabalSpecVersion

version

-> String

removal message

-> g s a 
-> g s a 

Removed in. If we occur removed field, parsing fails.

availableSince Source #

Arguments

:: CabalSpecVersion

spec version

-> a

default value

-> g s a 
-> g s a 

Annotate field with since spec-version.

Instances
FieldGrammar PrettyFieldGrammar Source # 
Instance details

Defined in Distribution.FieldGrammar.Pretty

Methods

blurFieldGrammar :: ALens' a b -> PrettyFieldGrammar b c -> PrettyFieldGrammar a c Source #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

FieldGrammar ParsecFieldGrammar Source # 
Instance details

Defined in Distribution.FieldGrammar.Parsec

Methods

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

uniqueFieldAla :: (Parsec b, Pretty 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, Pretty b, Newtype a b) => FieldName -> (a -> b) -> ALens' s (Maybe a) -> ParsecFieldGrammar s (Maybe a) Source #

optionalFieldDefAla :: (Parsec b, Pretty 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, Pretty 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 #

FieldGrammar FieldDescrs Source #

Note: default values are printed.

Instance details

Defined in Distribution.FieldGrammar.FieldDescrs

uniqueField Source #

Arguments

:: (FieldGrammar g, Parsec a, Pretty a) 
=> FieldName

field name

-> ALens' s a

lens into the field

-> g s a 

Field which can be defined at most once.

optionalField Source #

Arguments

:: (FieldGrammar g, Parsec a, Pretty a) 
=> FieldName

field name

-> ALens' s (Maybe a)

lens into the field

-> g s (Maybe a) 

Field which can be defined at most once.

optionalFieldDef Source #

Arguments

:: (FieldGrammar g, Functor (g s), Parsec a, Pretty a, Eq a) 
=> FieldName

field name

-> ALens' s a

Lens' s a: lens into the field

-> a

default value

-> g s a 

Optional field with default value.

monoidalField Source #

Arguments

:: (FieldGrammar g, Parsec a, Pretty a, Monoid a) 
=> FieldName

field name

-> ALens' s a

lens into the field

-> g s a 

Field which can be define multiple times, and the results are mappended.

Concrete grammar implementations

data ParsecFieldGrammar s a Source #

Instances
FieldGrammar ParsecFieldGrammar Source # 
Instance details

Defined in Distribution.FieldGrammar.Parsec

Methods

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

uniqueFieldAla :: (Parsec b, Pretty 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, Pretty b, Newtype a b) => FieldName -> (a -> b) -> ALens' s (Maybe a) -> ParsecFieldGrammar s (Maybe a) Source #

optionalFieldDefAla :: (Parsec b, Pretty 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, Pretty 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 #

Functor (ParsecFieldGrammar s) Source # 
Instance details

Defined in Distribution.FieldGrammar.Parsec

Methods

fmap :: (a -> b) -> ParsecFieldGrammar s a -> ParsecFieldGrammar s b #

(<$) :: a -> ParsecFieldGrammar s b -> ParsecFieldGrammar s a #

Applicative (ParsecFieldGrammar s) Source # 
Instance details

Defined in Distribution.FieldGrammar.Parsec

data PrettyFieldGrammar s a Source #

Instances
FieldGrammar PrettyFieldGrammar Source # 
Instance details

Defined in Distribution.FieldGrammar.Pretty

Methods

blurFieldGrammar :: ALens' a b -> PrettyFieldGrammar b c -> PrettyFieldGrammar a c Source #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Functor (PrettyFieldGrammar s) Source # 
Instance details

Defined in Distribution.FieldGrammar.Pretty

Methods

fmap :: (a -> b) -> PrettyFieldGrammar s a -> PrettyFieldGrammar s b #

(<$) :: a -> PrettyFieldGrammar s b -> PrettyFieldGrammar s a #

Applicative (PrettyFieldGrammar s) Source # 
Instance details

Defined in Distribution.FieldGrammar.Pretty

prettyFieldGrammar :: CabalSpecVersion -> PrettyFieldGrammar s a -> s -> [PrettyField ()] Source #

We can use PrettyFieldGrammar to pp print the s.

Note: there is not trailing ($+$ text "").

Auxlilary

(^^^) :: a -> (a -> b) -> b infixl 5 Source #

Reverse function application which binds tighter than <$> and <*>. Useful for refining grammar specification.

<*> monoidalFieldAla "extensions"           (alaList' FSep MQuoted)       oldExtensions
    ^^^ deprecatedSince [1,12] "Please use 'default-extensions' or 'other-extensions' fields."

data Section ann Source #

The Section constructor of Field.

Constructors

MkSection !(Name ann) [SectionArg ann] [Field ann] 
Instances
Functor Section Source # 
Instance details

Defined in Distribution.FieldGrammar.Parsec

Methods

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

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

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

Defined in Distribution.FieldGrammar.Parsec

Methods

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

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

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

Defined in Distribution.FieldGrammar.Parsec

Methods

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

show :: Section ann -> String #

showList :: [Section ann] -> ShowS #

partitionFields :: [Field ann] -> (Fields ann, [[Section ann]]) Source #

Partition field list into field map and groups of sections.

takeFields :: [Field ann] -> (Fields ann, [Field ann]) Source #

Take all fields from the front.

defaultFreeTextFieldDefST Source #

Arguments

:: (Functor (g s), FieldGrammar g) 
=> FieldName 
-> ALens' s ShortText

lens into the field

-> g s ShortText 

Default implementation for freeTextFieldDefST.