| License | BSD3 | 
|---|---|
| Maintainer | cabal-devel@haskell.org | 
| Portability | portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Distribution.Fields.Parser
Contents
Description
Synopsis
- data Field ann
- data Name ann = Name !ann !FieldName
- data FieldLine ann = FieldLine !ann !ByteString
- data SectionArg ann- = SecArgName !ann !ByteString
- | SecArgStr !ann !ByteString
- | SecArgOther !ann !ByteString
 
- readFields :: ByteString -> Either ParseError [Field Position]
- readFields' :: ByteString -> Either ParseError ([Field Position], [LexWarning])
Types
A Cabal-like file consists of a series of fields (foo: bar) and sections (library ...).
Instances
| Functor Field Source # | |
| Foldable Field Source # | |
| 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 # elem :: Eq a => a -> Field a -> Bool # maximum :: Ord a => Field a -> a # minimum :: Ord a => Field a -> a # | |
| Traversable Field Source # | |
| Eq ann => Eq (Field ann) Source # | |
| Show ann => Show (Field ann) Source # | |
A field name.
Invariant: ByteString is lower-case ASCII.
Instances
| Functor Name Source # | |
| Foldable Name Source # | |
| 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 # elem :: Eq a => a -> Name a -> Bool # maximum :: Ord a => Name a -> a # | |
| Traversable Name Source # | |
| Eq ann => Eq (Name ann) Source # | |
| Show ann => Show (Name 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 # | |
| Foldable FieldLine Source # | |
| 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] # length :: FieldLine a -> Int # elem :: Eq a => a -> FieldLine a -> Bool # maximum :: Ord a => FieldLine a -> a # minimum :: Ord a => FieldLine a -> a # | |
| Traversable FieldLine Source # | |
| Defined in Distribution.Fields.Field | |
| Eq ann => Eq (FieldLine ann) Source # | |
| Show ann => Show (FieldLine ann) Source # | |
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
Grammar and parsing
CabalStyleFile ::= SecElems SecElems ::= SecElem* '\\n'? SecElem ::= '\\n' SecElemLayout | SecElemBraces SecElemLayout ::= FieldLayout | FieldBraces | SectionLayout | SectionBraces SecElemBraces ::= FieldInline | FieldBraces | SectionBraces FieldLayout ::= name:line? ('\\n' line)* FieldBraces ::= name:'\\n'? '{' content '}' FieldInline ::= name:content SectionLayout ::= name arg* SecElems SectionBraces ::= name arg* '\\n'? '{' SecElems '}'
and the same thing but left factored...
SecElems              ::= SecElem*
SecElem               ::= '\\n' name SecElemLayout
                        |      name SecElemBraces
SecElemLayout         ::= :   FieldLayoutOrBraces
                        | arg*  SectionLayoutOrBraces
FieldLayoutOrBraces   ::= '\\n'? '{' content '}'
                        | line? ('\\n' line)*
SectionLayoutOrBraces ::= '\\n'? '{' SecElems '\\n'? '}'
                        | SecElems
SecElemBraces         ::= : FieldInlineOrBraces
                        | arg* '\\n'? '{' SecElems '\\n'? '}'
FieldInlineOrBraces   ::= '\\n'? '{' content '}'
                        | content
Note how we have several productions with the sequence:
'\\n'? '{'That is, an optional newline (and indent) followed by a { token.
 In the SectionLayoutOrBraces case you can see that this makes it
 not fully left factored (because SecElems can start with a \n).
 Fully left factoring here would be ugly, and though we could use a
 lookahead of two tokens to resolve the alternatives, we can't
 conveniently use Parsec's try here to get a lookahead of only two.
 So instead we deal with this case in the lexer by making a line
 where the first non-space is { lex as just the { token, without
 the usual indent token. Then in the parser we can resolve everything
 with just one token of lookahead and so without using try.
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