Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class FieldGrammar g where
- blurFieldGrammar :: ALens' a b -> g b c -> g a c
- uniqueFieldAla :: (Parsec b, Pretty b, Newtype a b) => FieldName -> (a -> b) -> ALens' s a -> g s a
- booleanFieldDef :: FieldName -> ALens' s Bool -> Bool -> g s Bool
- optionalFieldAla :: (Parsec b, Pretty b, Newtype a b) => FieldName -> (a -> b) -> ALens' s (Maybe a) -> g s (Maybe a)
- optionalFieldDefAla :: (Parsec b, Pretty 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 :: (Parsec b, Pretty 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
- uniqueField :: (FieldGrammar g, Parsec a, Pretty a) => FieldName -> ALens' s a -> g s a
- optionalField :: (FieldGrammar g, Parsec a, Pretty a) => FieldName -> ALens' s (Maybe a) -> g s (Maybe a)
- optionalFieldDef :: (FieldGrammar g, Functor (g s), Parsec a, Pretty a, Eq a) => FieldName -> ALens' s a -> a -> g s a
- monoidalField :: (FieldGrammar g, Parsec a, Pretty a, Monoid a) => FieldName -> ALens' s a -> g s a
- defaultFreeTextFieldDefST :: (Functor (g s), FieldGrammar g) => FieldName -> ALens' s ShortText -> g s ShortText
Documentation
class FieldGrammar g where Source #
FieldGrammar
is parametrised by
s
which is a structure we are parsing. We need this to provide prettyprinter functionalitya
type of the field.
Note: We'd like to have forall s. Applicative (f s)
context.
blurFieldGrammar :: ALens' a b -> g b c -> g a c Source #
Unfocus, zoom out, blur FieldGrammar
.
:: (Parsec b, Pretty 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.
:: (Parsec b, Pretty b, Newtype a b) | |
=> FieldName | field name |
-> (a -> b) |
|
-> ALens' s (Maybe a) | lens into the field |
-> g s (Maybe a) |
Optional field.
:: (Parsec b, Pretty 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: Cabal-3.2.0.0
:: (Parsec b, Pretty 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.
:: 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.
:: CabalSpecVersion | version |
-> String | deprecation message |
-> g s a | |
-> g s a |
Deprecated since
:: CabalSpecVersion | version |
-> String | removal message |
-> g s a | |
-> g s a |
Removed in. If we occur removed field, parsing fails.
:: CabalSpecVersion | spec version |
-> a | default value |
-> g s a | |
-> g s a |
Annotate field with since spec-version.
Instances
:: (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.
:: (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.
:: (FieldGrammar g, Functor (g s), Parsec a, Pretty a, Eq a) | |
=> FieldName | field name |
-> ALens' s a |
|
-> a | default value |
-> g s a |
Optional field with default value.
:: (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 mappend
ed.
defaultFreeTextFieldDefST Source #
:: (Functor (g s), FieldGrammar g) | |
=> FieldName | |
-> ALens' s ShortText | lens into the field |
-> g s ShortText |
Default implementation for freeTextFieldDefST
.