Cabal-syntax-3.11.0.0: A library for working with .cabal files
LicenseBSD3
Maintainercabal-devel@haskell.org
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Distribution.Fields.Parser

Description

 
Synopsis

Types

data Field ann Source #

A Cabal-like file consists of a series of fields (foo: bar) and sections (library ...).

Constructors

Field !(Name ann) [FieldLine ann] 
Section !(Name ann) [SectionArg ann] [Field ann] 

Instances

Instances details
Foldable1 Field Source #

Since: Cabal-syntax-3.12.0.0

Instance details

Defined in Distribution.Fields.Field

Methods

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 #

head :: Field a -> a Source #

last :: 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 # 
Instance details

Defined in Distribution.Fields.Field

Methods

fmap :: (a -> b) -> Field a -> Field b #

(<$) :: a -> Field b -> Field a #

Foldable Field Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

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 #

toList :: Field a -> [a] #

null :: Field a -> Bool #

length :: Field a -> Int #

elem :: Eq a => a -> Field a -> Bool #

maximum :: Ord a => Field a -> a #

minimum :: Ord a => Field a -> a #

sum :: Num a => Field a -> a #

product :: Num a => Field a -> a #

Traversable Field Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

traverse :: Applicative f => (a -> f b) -> Field a -> f (Field b) #

sequenceA :: Applicative f => Field (f a) -> f (Field a) #

mapM :: Monad m => (a -> m b) -> Field a -> m (Field b) #

sequence :: Monad m => Field (m a) -> m (Field a) #

Show ann => Show (Field ann) Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

showsPrec :: Int -> Field ann -> ShowS #

show :: Field ann -> String #

showList :: [Field ann] -> ShowS #

Eq ann => Eq (Field ann) Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

(==) :: Field ann -> Field ann -> Bool #

(/=) :: Field ann -> Field ann -> Bool #

Ord ann => Ord (Field ann) Source #

Since: Cabal-syntax-3.12.0.0

Instance details

Defined in Distribution.Fields.Field

Methods

compare :: Field ann -> Field ann -> Ordering #

(<) :: Field ann -> Field ann -> Bool #

(<=) :: Field ann -> Field ann -> Bool #

(>) :: Field ann -> Field ann -> Bool #

(>=) :: Field ann -> Field ann -> Bool #

max :: Field ann -> Field ann -> Field ann #

min :: Field ann -> Field ann -> Field ann #

data Name ann Source #

A field name.

Invariant: ByteString is lower-case ASCII.

Constructors

Name !ann !FieldName 

Instances

Instances details
Foldable1 Name Source #

Since: Cabal-syntax-3.12.0.0

Instance details

Defined in Distribution.Fields.Field

Methods

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 #

head :: Name a -> a Source #

last :: 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 # 
Instance details

Defined in Distribution.Fields.Field

Methods

fmap :: (a -> b) -> Name a -> Name b #

(<$) :: a -> Name b -> Name a #

Foldable Name Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

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 #

toList :: Name a -> [a] #

null :: Name a -> Bool #

length :: Name a -> Int #

elem :: Eq a => a -> Name a -> Bool #

maximum :: Ord a => Name a -> a #

minimum :: Ord a => Name a -> a #

sum :: Num a => Name a -> a #

product :: Num a => Name a -> a #

Traversable Name Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

traverse :: Applicative f => (a -> f b) -> Name a -> f (Name b) #

sequenceA :: Applicative f => Name (f a) -> f (Name a) #

mapM :: Monad m => (a -> m b) -> Name a -> m (Name b) #

sequence :: Monad m => Name (m a) -> m (Name a) #

Show ann => Show (Name ann) Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

showsPrec :: Int -> Name ann -> ShowS #

show :: Name ann -> String #

showList :: [Name ann] -> ShowS #

Eq ann => Eq (Name ann) Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

(==) :: Name ann -> Name ann -> Bool #

(/=) :: Name ann -> Name ann -> Bool #

Ord ann => Ord (Name ann) Source #

Since: Cabal-syntax-3.12.0.0

Instance details

Defined in Distribution.Fields.Field

Methods

compare :: Name ann -> Name ann -> Ordering #

(<) :: Name ann -> Name ann -> Bool #

(<=) :: Name ann -> Name ann -> Bool #

(>) :: Name ann -> Name ann -> Bool #

(>=) :: Name ann -> Name ann -> Bool #

max :: Name ann -> Name ann -> Name ann #

min :: Name ann -> Name ann -> Name ann #

data FieldLine 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

Instances details
Foldable1 FieldLine Source #

Since: Cabal-syntax-3.12.0.0

Instance details

Defined in Distribution.Fields.Field

Methods

fold1 :: Semigroup m => FieldLine m -> m Source #

foldMap1 :: Semigroup m => (a -> m) -> FieldLine a -> m Source #

foldMap1' :: Semigroup m => (a -> m) -> FieldLine a -> m Source #

toNonEmpty :: FieldLine a -> NonEmpty a Source #

maximum :: Ord a => FieldLine a -> a Source #

minimum :: Ord a => FieldLine a -> a Source #

head :: FieldLine a -> a Source #

last :: FieldLine a -> a Source #

foldrMap1 :: (a -> b) -> (a -> b -> b) -> FieldLine a -> b Source #

foldlMap1' :: (a -> b) -> (b -> a -> b) -> FieldLine a -> b Source #

foldlMap1 :: (a -> b) -> (b -> a -> b) -> FieldLine a -> b Source #

foldrMap1' :: (a -> b) -> (a -> b -> b) -> FieldLine a -> b Source #

Functor FieldLine Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

fmap :: (a -> b) -> FieldLine a -> FieldLine b #

(<$) :: a -> FieldLine b -> FieldLine a #

Foldable FieldLine Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

fold :: Monoid m => FieldLine m -> m #

foldMap :: Monoid m => (a -> m) -> FieldLine a -> 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] #

null :: FieldLine a -> Bool #

length :: FieldLine a -> Int #

elem :: Eq a => a -> FieldLine a -> Bool #

maximum :: Ord a => FieldLine a -> a #

minimum :: Ord a => FieldLine a -> a #

sum :: Num a => FieldLine a -> a #

product :: Num a => FieldLine a -> a #

Traversable FieldLine Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

traverse :: Applicative f => (a -> f b) -> FieldLine a -> f (FieldLine b) #

sequenceA :: Applicative f => FieldLine (f a) -> f (FieldLine a) #

mapM :: Monad m => (a -> m b) -> FieldLine a -> m (FieldLine b) #

sequence :: Monad m => FieldLine (m a) -> m (FieldLine a) #

Show ann => Show (FieldLine ann) Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

showsPrec :: Int -> FieldLine ann -> ShowS #

show :: FieldLine ann -> String #

showList :: [FieldLine ann] -> ShowS #

Eq ann => Eq (FieldLine ann) Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

(==) :: FieldLine ann -> FieldLine ann -> Bool #

(/=) :: FieldLine ann -> FieldLine ann -> Bool #

Ord ann => Ord (FieldLine ann) Source #

Since: Cabal-syntax-3.12.0.0

Instance details

Defined in Distribution.Fields.Field

Methods

compare :: FieldLine ann -> FieldLine ann -> Ordering #

(<) :: FieldLine ann -> FieldLine ann -> Bool #

(<=) :: FieldLine ann -> FieldLine ann -> Bool #

(>) :: FieldLine ann -> FieldLine ann -> Bool #

(>=) :: FieldLine ann -> FieldLine ann -> Bool #

max :: FieldLine ann -> FieldLine ann -> FieldLine ann #

min :: FieldLine ann -> FieldLine ann -> FieldLine ann #

data SectionArg ann Source #

Section arguments, e.g. name of the library

Constructors

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

Instances details
Foldable1 SectionArg Source #

Since: Cabal-syntax-3.12.0.0

Instance details

Defined in Distribution.Fields.Field

Methods

fold1 :: Semigroup m => SectionArg m -> m Source #

foldMap1 :: Semigroup m => (a -> m) -> SectionArg a -> m Source #

foldMap1' :: Semigroup m => (a -> m) -> SectionArg a -> m Source #

toNonEmpty :: SectionArg a -> NonEmpty a Source #

maximum :: Ord a => SectionArg a -> a Source #

minimum :: Ord a => SectionArg a -> a Source #

head :: SectionArg a -> a Source #

last :: SectionArg a -> a Source #

foldrMap1 :: (a -> b) -> (a -> b -> b) -> SectionArg a -> b Source #

foldlMap1' :: (a -> b) -> (b -> a -> b) -> SectionArg a -> b Source #

foldlMap1 :: (a -> b) -> (b -> a -> b) -> SectionArg a -> b Source #

foldrMap1' :: (a -> b) -> (a -> b -> b) -> SectionArg a -> b Source #

Functor SectionArg Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

fmap :: (a -> b) -> SectionArg a -> SectionArg b #

(<$) :: a -> SectionArg b -> SectionArg a #

Foldable SectionArg Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

fold :: Monoid m => SectionArg m -> m #

foldMap :: Monoid m => (a -> m) -> SectionArg a -> m #

foldMap' :: Monoid m => (a -> m) -> SectionArg a -> m #

foldr :: (a -> b -> b) -> b -> SectionArg a -> b #

foldr' :: (a -> b -> b) -> b -> SectionArg a -> b #

foldl :: (b -> a -> b) -> b -> SectionArg a -> b #

foldl' :: (b -> a -> b) -> b -> SectionArg a -> b #

foldr1 :: (a -> a -> a) -> SectionArg a -> a #

foldl1 :: (a -> a -> a) -> SectionArg a -> a #

toList :: SectionArg a -> [a] #

null :: SectionArg a -> Bool #

length :: SectionArg a -> Int #

elem :: Eq a => a -> SectionArg a -> Bool #

maximum :: Ord a => SectionArg a -> a #

minimum :: Ord a => SectionArg a -> a #

sum :: Num a => SectionArg a -> a #

product :: Num a => SectionArg a -> a #

Traversable SectionArg Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

traverse :: Applicative f => (a -> f b) -> SectionArg a -> f (SectionArg b) #

sequenceA :: Applicative f => SectionArg (f a) -> f (SectionArg a) #

mapM :: Monad m => (a -> m b) -> SectionArg a -> m (SectionArg b) #

sequence :: Monad m => SectionArg (m a) -> m (SectionArg a) #

Show ann => Show (SectionArg ann) Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

showsPrec :: Int -> SectionArg ann -> ShowS #

show :: SectionArg ann -> String #

showList :: [SectionArg ann] -> ShowS #

Eq ann => Eq (SectionArg ann) Source # 
Instance details

Defined in Distribution.Fields.Field

Methods

(==) :: SectionArg ann -> SectionArg ann -> Bool #

(/=) :: SectionArg ann -> SectionArg ann -> Bool #

Ord ann => Ord (SectionArg ann) Source #

Since: Cabal-syntax-3.12.0.0

Instance details

Defined in Distribution.Fields.Field

Methods

compare :: SectionArg ann -> SectionArg ann -> Ordering #

(<) :: SectionArg ann -> SectionArg ann -> Bool #

(<=) :: SectionArg ann -> SectionArg ann -> Bool #

(>) :: SectionArg ann -> SectionArg ann -> Bool #

(>=) :: SectionArg ann -> SectionArg ann -> Bool #

max :: SectionArg ann -> SectionArg ann -> SectionArg ann #

min :: SectionArg ann -> SectionArg ann -> SectionArg ann #

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 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.