| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Distribution.FieldGrammar
Description
This module provides a way to specify a grammar of .cabal -like files.
Synopsis
- class (c SpecVersion, c TestedWith, c SpecLicense, c Token, c Token', c FilePathNT) => FieldGrammar c g | g -> c where- blurFieldGrammar :: ALens' a b -> g b d -> g a d
- uniqueFieldAla :: (c b, Newtype a b) => FieldName -> (a -> b) -> ALens' s a -> g s a
- booleanFieldDef :: FieldName -> ALens' s Bool -> Bool -> g s Bool
- optionalFieldAla :: (c b, Newtype a b) => FieldName -> (a -> b) -> ALens' s (Maybe a) -> g s (Maybe a)
- optionalFieldDefAla :: (c b, Newtype a b, Eq a) => FieldName -> (a -> b) -> ALens' s a -> a -> g s a
- freeTextField :: FieldName -> ALens' s (Maybe String) -> g s (Maybe String)
- freeTextFieldDef :: FieldName -> ALens' s String -> g s String
- freeTextFieldDefST :: FieldName -> ALens' s ShortText -> g s ShortText
- monoidalFieldAla :: (c b, Monoid a, Newtype a b) => FieldName -> (a -> b) -> ALens' s a -> g s a
- prefixedFields :: FieldName -> ALens' s [(String, String)] -> g s [(String, String)]
- knownField :: FieldName -> g s ()
- hiddenField :: g s a -> g s a
- deprecatedSince :: CabalSpecVersion -> String -> g s a -> g s a
- removedIn :: CabalSpecVersion -> String -> g s a -> g s a
- availableSince :: CabalSpecVersion -> a -> g s a -> g s a
- availableSinceWarn :: CabalSpecVersion -> g s a -> g s a
 
- uniqueField :: (FieldGrammar c g, c (Identity a)) => FieldName -> ALens' s a -> g s a
- optionalField :: (FieldGrammar c g, c (Identity a)) => FieldName -> ALens' s (Maybe a) -> g s (Maybe a)
- optionalFieldDef :: (FieldGrammar c g, Functor (g s), c (Identity a), Eq a) => FieldName -> ALens' s a -> a -> g s a
- monoidalField :: (FieldGrammar c g, c (Identity a), Monoid a) => FieldName -> ALens' s a -> g s a
- data ParsecFieldGrammar s a
- type ParsecFieldGrammar' a = ParsecFieldGrammar a a
- parseFieldGrammar :: CabalSpecVersion -> Fields Position -> ParsecFieldGrammar s a -> ParseResult a
- fieldGrammarKnownFieldList :: ParsecFieldGrammar s a -> [FieldName]
- data PrettyFieldGrammar s a
- type PrettyFieldGrammar' a = PrettyFieldGrammar a a
- prettyFieldGrammar :: CabalSpecVersion -> PrettyFieldGrammar s a -> s -> [PrettyField ()]
- (^^^) :: a -> (a -> b) -> b
- data Section ann = MkSection !(Name ann) [SectionArg ann] [Field ann]
- type Fields ann = Map FieldName [NamelessField ann]
- partitionFields :: [Field ann] -> (Fields ann, [[Section ann]])
- takeFields :: [Field ann] -> (Fields ann, [Field ann])
- runFieldParser :: Position -> ParsecParser a -> CabalSpecVersion -> [FieldLine Position] -> ParseResult a
- runFieldParser' :: [Position] -> ParsecParser a -> CabalSpecVersion -> FieldLineStream -> ParseResult a
- defaultFreeTextFieldDefST :: (Functor (g s), FieldGrammar c g) => FieldName -> ALens' s ShortText -> g s ShortText
- module Distribution.FieldGrammar.Newtypes
Field grammar type
class (c SpecVersion, c TestedWith, c SpecLicense, c Token, c Token', c FilePathNT) => FieldGrammar c g | g -> c where Source #
FieldGrammar is parametrised by
- swhich is a structure we are parsing. We need this to provide prettyprinter functionality
- atype of the field.
Note: We'd like to have forall s. Applicative (f s) context.
Minimal complete definition
blurFieldGrammar, uniqueFieldAla, booleanFieldDef, optionalFieldAla, optionalFieldDefAla, freeTextField, freeTextFieldDef, freeTextFieldDefST, monoidalFieldAla, prefixedFields, knownField, hiddenField, deprecatedSince, removedIn, availableSince
Methods
blurFieldGrammar :: ALens' a b -> g b d -> g a d Source #
Unfocus, zoom out, blur FieldGrammar.
Arguments
| :: (c b, Newtype a b) | |
| => FieldName | field name | 
| -> (a -> b) | 
 | 
| -> ALens' s a | lens into the field | 
| -> g s a | 
Field which should be defined, exactly once.
Boolean field with a default value.
Arguments
| :: (c b, Newtype a b) | |
| => FieldName | field name | 
| -> (a -> b) | 
 | 
| -> ALens' s (Maybe a) | lens into the field | 
| -> g s (Maybe a) | 
Optional field.
Arguments
| :: (c b, Newtype a b, Eq a) | |
| => FieldName | field name | 
| -> (a -> b) | 
 | 
| -> ALens' s a | 
 | 
| -> a | default value | 
| -> g s a | 
Optional field with default value.
Since: 3.2.0.0
Arguments
| :: (c b, Monoid a, Newtype a b) | |
| => FieldName | field name | 
| -> (a -> b) | 
 | 
| -> 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.
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.
Field which is parsed but not pretty printed.
Arguments
| :: CabalSpecVersion | version | 
| -> String | deprecation message | 
| -> g s a | |
| -> g s a | 
Deprecated since
Arguments
| :: CabalSpecVersion | version | 
| -> String | removal message | 
| -> g s a | |
| -> g s a | 
Removed in. If we occur removed field, parsing fails.
Arguments
| :: CabalSpecVersion | spec version | 
| -> a | default value | 
| -> g s a | |
| -> g s a | 
Annotate field with since spec-version.
Arguments
| :: CabalSpecVersion | spec version | 
| -> g s a | |
| -> g s a | 
Annotate field with since spec-version.
 This is used to recognise, but warn about the field.
 It is used to process other-extensions field.
Default implementation is to not warn.
Since: 3.4.0.0
Instances
Arguments
| :: (FieldGrammar c g, c (Identity a)) | |
| => FieldName | field name | 
| -> ALens' s a | lens into the field | 
| -> g s a | 
Field which can be defined at most once.
Arguments
| :: (FieldGrammar c g, c (Identity a)) | |
| => FieldName | field name | 
| -> ALens' s (Maybe a) | lens into the field | 
| -> g s (Maybe a) | 
Field which can be defined at most once.
Arguments
| :: (FieldGrammar c g, Functor (g s), c (Identity a), Eq a) | |
| => FieldName | field name | 
| -> ALens' s a | 
 | 
| -> a | default value | 
| -> g s a | 
Optional field with default value.
Arguments
| :: (FieldGrammar c g, c (Identity 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
type ParsecFieldGrammar' a = ParsecFieldGrammar a a Source #
parseFieldGrammar :: CabalSpecVersion -> Fields Position -> ParsecFieldGrammar s a -> ParseResult a Source #
fieldGrammarKnownFieldList :: ParsecFieldGrammar s a -> [FieldName] Source #
data PrettyFieldGrammar s a Source #
Instances
type PrettyFieldGrammar' a = PrettyFieldGrammar a a Source #
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."
Constructors
| MkSection !(Name ann) [SectionArg ann] [Field ann] | 
partitionFields :: [Field ann] -> (Fields ann, [[Section ann]]) Source #
Partition field list into field map and groups of sections.
runFieldParser :: Position -> ParsecParser a -> CabalSpecVersion -> [FieldLine Position] -> ParseResult a Source #
runFieldParser' :: [Position] -> ParsecParser a -> CabalSpecVersion -> FieldLineStream -> ParseResult a Source #
defaultFreeTextFieldDefST Source #
Arguments
| :: (Functor (g s), FieldGrammar c g) | |
| => FieldName | |
| -> ALens' s ShortText | lens into the field | 
| -> g s ShortText | 
Default implementation for freeTextFieldDefST.