License | BSD3 |
---|---|
Maintainer | cabal-devel@haskell.org |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
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
Foldable Field Source # | |
Defined in Distribution.Fields.Field fold :: Monoid m => Field m -> m Source # foldMap :: Monoid m => (a -> m) -> Field a -> m Source # foldMap' :: Monoid m => (a -> m) -> Field a -> m Source # foldr :: (a -> b -> b) -> b -> Field a -> b Source # foldr' :: (a -> b -> b) -> b -> Field a -> b Source # foldl :: (b -> a -> b) -> b -> Field a -> b Source # foldl' :: (b -> a -> b) -> b -> Field a -> b Source # foldr1 :: (a -> a -> a) -> Field a -> a Source # foldl1 :: (a -> a -> a) -> Field a -> a Source # toList :: Field a -> [a] Source # null :: Field a -> Bool Source # length :: Field a -> Int Source # elem :: Eq a => a -> Field a -> Bool Source # maximum :: Ord a => Field a -> a Source # minimum :: Ord a => Field a -> a Source # | |
Traversable Field Source # | |
Functor Field Source # | |
Show ann => Show (Field ann) Source # | |
Eq ann => Eq (Field ann) Source # | |
A field name.
Invariant: ByteString
is lower-case ASCII.
Instances
Foldable Name Source # | |
Defined in Distribution.Fields.Field fold :: Monoid m => Name m -> m Source # foldMap :: Monoid m => (a -> m) -> Name a -> m Source # foldMap' :: Monoid m => (a -> m) -> Name a -> m Source # foldr :: (a -> b -> b) -> b -> Name a -> b Source # foldr' :: (a -> b -> b) -> b -> Name a -> b Source # foldl :: (b -> a -> b) -> b -> Name a -> b Source # foldl' :: (b -> a -> b) -> b -> Name a -> b Source # foldr1 :: (a -> a -> a) -> Name a -> a Source # foldl1 :: (a -> a -> a) -> Name a -> a Source # toList :: Name a -> [a] Source # null :: Name a -> Bool Source # length :: Name a -> Int Source # elem :: Eq a => a -> Name a -> Bool Source # maximum :: Ord a => Name a -> a Source # minimum :: Ord a => Name a -> a Source # | |
Traversable Name Source # | |
Functor Name Source # | |
Show ann => Show (Name ann) Source # | |
Eq ann => Eq (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.
FieldLine !ann !ByteString |
Instances
Foldable FieldLine Source # | |
Defined in Distribution.Fields.Field fold :: Monoid m => FieldLine m -> m Source # foldMap :: Monoid m => (a -> m) -> FieldLine a -> m Source # foldMap' :: Monoid m => (a -> m) -> FieldLine a -> m Source # foldr :: (a -> b -> b) -> b -> FieldLine a -> b Source # foldr' :: (a -> b -> b) -> b -> FieldLine a -> b Source # foldl :: (b -> a -> b) -> b -> FieldLine a -> b Source # foldl' :: (b -> a -> b) -> b -> FieldLine a -> b Source # foldr1 :: (a -> a -> a) -> FieldLine a -> a Source # foldl1 :: (a -> a -> a) -> FieldLine a -> a Source # toList :: FieldLine a -> [a] Source # null :: FieldLine a -> Bool Source # length :: FieldLine a -> Int Source # elem :: Eq a => a -> FieldLine a -> Bool Source # maximum :: Ord a => FieldLine a -> a Source # minimum :: Ord a => FieldLine a -> a Source # | |
Traversable FieldLine Source # | |
Defined in Distribution.Fields.Field | |
Functor FieldLine Source # | |
Show ann => Show (FieldLine ann) Source # | |
Eq ann => Eq (FieldLine ann) Source # | |
data SectionArg ann Source #
Section arguments, e.g. name of the library
SecArgName !ann !ByteString | identifier, or something which looks 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 Field
s, i.e. the cabal AST.
readFields' :: ByteString -> Either ParseError ([Field Position], [LexWarning]) Source #
Like readFields
but also return lexer warnings