Safe Haskell | None |
---|---|
Language | Haskell2010 |
Utilities to work with .cabal
like file structure.
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
- type FieldName = ByteString
- readFields :: ByteString -> Either ParseError [Field Position]
- readFields' :: ByteString -> Either ParseError ([Field Position], [LexWarning])
- data ParseResult a
- runParseResult :: ParseResult a -> ([PWarning], Either (Maybe Version, NonEmpty PError) a)
- parseWarning :: Position -> PWarnType -> String -> ParseResult ()
- parseWarnings :: [PWarning] -> ParseResult ()
- parseFailure :: Position -> String -> ParseResult ()
- parseFatalFailure :: Position -> String -> ParseResult a
- data PWarnType
- = PWTOther
- | PWTUTF
- | PWTBoolCase
- | PWTVersionTag
- | PWTNewSyntax
- | PWTOldSyntax
- | PWTDeprecatedField
- | PWTInvalidSubsection
- | PWTUnknownField
- | PWTUnknownSection
- | PWTTrailingFields
- | PWTExtraMainIs
- | PWTExtraTestModule
- | PWTExtraBenchmarkModule
- | PWTLexNBSP
- | PWTLexBOM
- | PWTLexTab
- | PWTQuirkyCabalFile
- | PWTDoubleDash
- | PWTMultipleSingularField
- | PWTBuildTypeDefault
- | PWTVersionOperator
- | PWTVersionWildcard
- | PWTSpecVersion
- | PWTEmptyFilePath
- | PWTInconsistentIndentation
- | PWTExperimental
- data PWarning = PWarning !PWarnType !Position String
- showPWarning :: FilePath -> PWarning -> String
- data PError = PError Position String
- showPError :: FilePath -> PError -> String
- data CommentPosition
- = CommentBefore [String]
- | CommentAfter [String]
- | NoComment
- data PrettyField ann
- = PrettyField ann FieldName Doc
- | PrettySection ann FieldName [Doc] [PrettyField ann]
- | PrettyEmpty
- showFields :: (ann -> CommentPosition) -> [PrettyField ann] -> String
- genericFromParsecFields :: Applicative f => (FieldName -> [FieldLine ann] -> f Doc) -> (FieldName -> [SectionArg ann] -> f [Doc]) -> [Field ann] -> f [PrettyField ann]
- fromParsecFields :: [Field ann] -> [PrettyField ann]
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
type FieldName = ByteString Source #
Grammar and parsing
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.
ParseResult
data ParseResult a Source #
A monad with failure and accumulating errors and warnings.
Instances
Applicative ParseResult Source # | |
Defined in Distribution.Fields.ParseResult pure :: a -> ParseResult a # (<*>) :: ParseResult (a -> b) -> ParseResult a -> ParseResult b # liftA2 :: (a -> b -> c) -> ParseResult a -> ParseResult b -> ParseResult c # (*>) :: ParseResult a -> ParseResult b -> ParseResult b # (<*) :: ParseResult a -> ParseResult b -> ParseResult a # | |
Functor ParseResult Source # | |
Defined in Distribution.Fields.ParseResult fmap :: (a -> b) -> ParseResult a -> ParseResult b # (<$) :: a -> ParseResult b -> ParseResult a # | |
Monad ParseResult Source # | |
Defined in Distribution.Fields.ParseResult (>>=) :: ParseResult a -> (a -> ParseResult b) -> ParseResult b # (>>) :: ParseResult a -> ParseResult b -> ParseResult b # return :: a -> ParseResult a # |
runParseResult :: ParseResult a -> ([PWarning], Either (Maybe Version, NonEmpty PError) a) Source #
Destruct a ParseResult
into the emitted warnings and either
a successful value or
list of errors and possibly recovered a spec-version declaration.
parseWarning :: Position -> PWarnType -> String -> ParseResult () Source #
Add a warning. This doesn't fail the parsing process.
parseWarnings :: [PWarning] -> ParseResult () Source #
Add multiple warnings at once.
parseFailure :: Position -> String -> ParseResult () Source #
Add an error, but not fail the parser yet.
For fatal failure use parseFatalFailure
parseFatalFailure :: Position -> String -> ParseResult a Source #
Add an fatal error.
Warnings
Type of parser warning. We do classify warnings.
Different application may decide not to show some, or have fatal behaviour on others
PWTOther | Unclassified warning |
PWTUTF | Invalid UTF encoding |
PWTBoolCase |
|
PWTVersionTag | there are version with tags |
PWTNewSyntax | New syntax used, but no |
PWTOldSyntax | Old syntax used, and |
PWTDeprecatedField | |
PWTInvalidSubsection | |
PWTUnknownField | |
PWTUnknownSection | |
PWTTrailingFields | |
PWTExtraMainIs | extra main-is field |
PWTExtraTestModule | extra test-module field |
PWTExtraBenchmarkModule | extra benchmark-module field |
PWTLexNBSP | |
PWTLexBOM | |
PWTLexTab | |
PWTQuirkyCabalFile | legacy cabal file that we know how to patch |
PWTDoubleDash | Double dash token, most likely it's a mistake - it's not a comment |
PWTMultipleSingularField | e.g. name or version should be specified only once. |
PWTBuildTypeDefault | Workaround for derive-package having build-type: Default. See https://github.com/haskell/cabal/issues/5020. |
PWTVersionOperator | Version operators used (without cabal-version: 1.8) |
PWTVersionWildcard | Version wildcard used (without cabal-version: 1.6) |
PWTSpecVersion | Warnings about cabal-version format. |
PWTEmptyFilePath | Empty filepath, i.e. literally "" |
PWTInconsistentIndentation | sections contents (sections and fields) are indented inconsistently |
PWTExperimental | Experimental feature |
Instances
Binary PWarnType Source # | |||||
NFData PWarnType Source # | |||||
Defined in Distribution.Parsec.Warning | |||||
Bounded PWarnType Source # | |||||
Enum PWarnType Source # | |||||
Defined in Distribution.Parsec.Warning succ :: PWarnType -> PWarnType # pred :: PWarnType -> PWarnType # fromEnum :: PWarnType -> Int # enumFrom :: PWarnType -> [PWarnType] # enumFromThen :: PWarnType -> PWarnType -> [PWarnType] # enumFromTo :: PWarnType -> PWarnType -> [PWarnType] # enumFromThenTo :: PWarnType -> PWarnType -> PWarnType -> [PWarnType] # | |||||
Generic PWarnType Source # | |||||
Defined in Distribution.Parsec.Warning
| |||||
Show PWarnType Source # | |||||
Eq PWarnType Source # | |||||
Ord PWarnType Source # | |||||
Defined in Distribution.Parsec.Warning | |||||
type Rep PWarnType Source # | |||||
Defined in Distribution.Parsec.Warning type Rep PWarnType = D1 ('MetaData "PWarnType" "Distribution.Parsec.Warning" "Cabal-syntax-3.14.0.0-e3f5" 'False) ((((C1 ('MetaCons "PWTOther" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PWTUTF" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PWTBoolCase" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "PWTVersionTag" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PWTNewSyntax" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PWTOldSyntax" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "PWTDeprecatedField" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PWTInvalidSubsection" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PWTUnknownField" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PWTUnknownSection" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PWTTrailingFields" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PWTExtraMainIs" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PWTExtraTestModule" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "PWTExtraBenchmarkModule" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PWTLexNBSP" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PWTLexBOM" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PWTLexTab" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PWTQuirkyCabalFile" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PWTDoubleDash" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PWTMultipleSingularField" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "PWTBuildTypeDefault" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PWTVersionOperator" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PWTVersionWildcard" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PWTSpecVersion" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PWTEmptyFilePath" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PWTInconsistentIndentation" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PWTExperimental" 'PrefixI 'False) (U1 :: Type -> Type)))))) |
Parser warning.
Instances
Errors
Parser error.
Instances
Binary PError Source # | |||||
NFData PError Source # | |||||
Defined in Distribution.Parsec.Error | |||||
Generic PError Source # | |||||
Defined in Distribution.Parsec.Error
| |||||
Show PError Source # | |||||
type Rep PError Source # | |||||
Defined in Distribution.Parsec.Error type Rep PError = D1 ('MetaData "PError" "Distribution.Parsec.Error" "Cabal-syntax-3.14.0.0-e3f5" 'False) (C1 ('MetaCons "PError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Position) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) |
Pretty printing
data CommentPosition Source #
This type is used to discern when a comment block should go
before or after a cabal-like file field, otherwise it would
be hardcoded to a single position. It is often used in
conjunction with PrettyField
.
data PrettyField ann Source #
PrettyField ann FieldName Doc | |
PrettySection ann FieldName [Doc] [PrettyField ann] | |
PrettyEmpty |
Instances
Functor PrettyField Source # | |
Defined in Distribution.Fields.Pretty fmap :: (a -> b) -> PrettyField a -> PrettyField b # (<$) :: a -> PrettyField b -> PrettyField a # | |
Foldable PrettyField Source # | |
Defined in Distribution.Fields.Pretty fold :: Monoid m => PrettyField m -> m # foldMap :: Monoid m => (a -> m) -> PrettyField a -> m # foldMap' :: Monoid m => (a -> m) -> PrettyField a -> m # foldr :: (a -> b -> b) -> b -> PrettyField a -> b # foldr' :: (a -> b -> b) -> b -> PrettyField a -> b # foldl :: (b -> a -> b) -> b -> PrettyField a -> b # foldl' :: (b -> a -> b) -> b -> PrettyField a -> b # foldr1 :: (a -> a -> a) -> PrettyField a -> a # foldl1 :: (a -> a -> a) -> PrettyField a -> a # toList :: PrettyField a -> [a] # null :: PrettyField a -> Bool # length :: PrettyField a -> Int # elem :: Eq a => a -> PrettyField a -> Bool # maximum :: Ord a => PrettyField a -> a # minimum :: Ord a => PrettyField a -> a # sum :: Num a => PrettyField a -> a # product :: Num a => PrettyField a -> a # | |
Traversable PrettyField Source # | |
Defined in Distribution.Fields.Pretty traverse :: Applicative f => (a -> f b) -> PrettyField a -> f (PrettyField b) # sequenceA :: Applicative f => PrettyField (f a) -> f (PrettyField a) # mapM :: Monad m => (a -> m b) -> PrettyField a -> m (PrettyField b) # sequence :: Monad m => PrettyField (m a) -> m (PrettyField a) # |
showFields :: (ann -> CommentPosition) -> [PrettyField ann] -> String Source #
Prettyprint a list of fields.
Note: the first argument should return String
s without newlines
and properly prefixes (with --
) to count as comments.
This unsafety is left in place so one could generate empty lines
between comment lines.
Transformation from Field
genericFromParsecFields Source #
:: Applicative f | |
=> (FieldName -> [FieldLine ann] -> f Doc) | transform field contents |
-> (FieldName -> [SectionArg ann] -> f [Doc]) | transform section arguments |
-> [Field ann] | |
-> f [PrettyField ann] |
fromParsecFields :: [Field ann] -> [PrettyField ann] Source #
Simple variant of genericFromParsecField