License | BSD3 |
---|---|
Maintainer | cabal-devel@haskell.org |
Portability | portable |
Safe Haskell | None |
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
Foldable1 Field Source # | Since: Cabal-syntax-3.12.0.0 |
Defined in Distribution.Fields.Field fold1 :: Semigroup m => Field m -> m Source # foldMap1 :: Semigroup m => (a -> m) -> Field a -> m Source # foldMap1' :: Semigroup m => (a -> m) -> Field a -> m Source # toNonEmpty :: Field a -> NonEmpty a Source # maximum :: Ord a => Field a -> a Source # minimum :: Ord a => Field a -> a Source # foldrMap1 :: (a -> b) -> (a -> b -> b) -> Field a -> b Source # foldlMap1' :: (a -> b) -> (b -> a -> b) -> Field a -> b Source # foldlMap1 :: (a -> b) -> (b -> a -> b) -> Field a -> b Source # foldrMap1' :: (a -> b) -> (a -> b -> b) -> Field a -> b Source # | |
Functor Field Source # | |
Foldable Field Source # | |
Defined in Distribution.Fields.Field fold :: Monoid m => Field m -> m # foldMap :: Monoid m => (a -> m) -> Field a -> 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 # | |
Show ann => Show (Field ann) Source # | |
Eq ann => Eq (Field ann) Source # | |
Ord ann => Ord (Field ann) Source # | Since: Cabal-syntax-3.12.0.0 |
Defined in Distribution.Fields.Field |
A field name.
Invariant: ByteString
is lower-case ASCII.
Instances
Foldable1 Name Source # | Since: Cabal-syntax-3.12.0.0 |
Defined in Distribution.Fields.Field fold1 :: Semigroup m => Name m -> m Source # foldMap1 :: Semigroup m => (a -> m) -> Name a -> m Source # foldMap1' :: Semigroup m => (a -> m) -> Name a -> m Source # toNonEmpty :: Name a -> NonEmpty a Source # maximum :: Ord a => Name a -> a Source # minimum :: Ord a => Name a -> a Source # foldrMap1 :: (a -> b) -> (a -> b -> b) -> Name a -> b Source # foldlMap1' :: (a -> b) -> (b -> a -> b) -> Name a -> b Source # foldlMap1 :: (a -> b) -> (b -> a -> b) -> Name a -> b Source # foldrMap1' :: (a -> b) -> (a -> b -> b) -> Name a -> b Source # | |
Functor Name Source # | |
Foldable Name Source # | |
Defined in Distribution.Fields.Field fold :: Monoid m => Name m -> m # foldMap :: Monoid m => (a -> m) -> Name a -> 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 # | |
Show ann => Show (Name ann) Source # | |
Eq ann => Eq (Name ann) Source # | |
Ord ann => Ord (Name ann) Source # | Since: Cabal-syntax-3.12.0.0 |
Defined in Distribution.Fields.Field |
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
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
assumes that input ByteString
is valid UTF8, specifically it doesn't validate that file is valid UTF8.
Therefore bytestrings inside returned Field
will be invalid as UTF8 if the input were.
>>>
readFields "foo: \223"
Right [Field (Name (Position 1 1) "foo") [FieldLine (Position 1 6) "\223"]]
readFields
won't (necessarily) fail on invalid UTF8 data, but the reported positions may be off.
You may get weird errors on non-UTF8 input, for example readFields
will fail on latin1 encoded non-breaking space:
>>>
isLeft (readFields "\xa0 foo: bar")
True
That is rejected because parser thinks \xa0
is a section name,
and section arguments may not contain colon.
If there are just latin1 non-breaking spaces, they become part of the name:
>>>
readFields "\xa0\&foo: bar"
Right [Field (Name (Position 1 1) "\160foo") [FieldLine (Position 1 7) "bar"]]
The UTF8 non-breaking space is accepted as an indentation character (but warned about by readFields'
).
>>>
readFields' "\xc2\xa0 foo: bar"
Right ([Field (Name (Position 1 3) "foo") [FieldLine (Position 1 8) "bar"]],[LexWarning LexWarningNBSP (Position 1 1)])
readFields' :: ByteString -> Either ParseError ([Field Position], [LexWarning]) Source #
Like readFields
but also return lexer warnings.