Safe Haskell | None |
---|---|
Language | Haskell2010 |
Utilitiies 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, [PError]) a)
- parseString :: (ByteString -> ParseResult a) -> Verbosity -> String -> ByteString -> IO 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
- | PWTVersionLeadingZeros
- data PWarning = PWarning !PWarnType !Position String
- showPWarning :: FilePath -> PWarning -> String
- data PError = PError Position String
- showPError :: FilePath -> PError -> String
- data PrettyField
- showFields :: [PrettyField] -> String
- genericFromParsecFields :: Applicative f => (FieldName -> [FieldLine ann] -> f Doc) -> (FieldName -> [SectionArg ann] -> f [Doc]) -> [Field ann] -> f [PrettyField]
- fromParsecFields :: [Field ann] -> [PrettyField]
Types
A Cabal-like file consists of a series of fields (foo: bar
) and sections (library ...
).
A field name.
Invariant: ByteString
is lower-case ASCII.
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 |
data SectionArg ann Source #
Section arguments, e.g. name of the library
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
Functor SectionArg # | |
Defined in Distribution.Fields.Field fmap :: (a -> b) -> SectionArg a -> SectionArg b Source # (<$) :: a -> SectionArg b -> SectionArg a Source # | |
Eq ann => Eq (SectionArg ann) # | |
Defined in Distribution.Fields.Field (==) :: SectionArg ann -> SectionArg ann -> Bool # (/=) :: SectionArg ann -> SectionArg ann -> Bool # | |
Show ann => Show (SectionArg ann) # | |
Defined in Distribution.Fields.Field |
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' :: 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
Monad ParseResult # | |
Defined in Distribution.Fields.ParseResult (>>=) :: ParseResult a -> (a -> ParseResult b) -> ParseResult b Source # (>>) :: ParseResult a -> ParseResult b -> ParseResult b Source # return :: a -> ParseResult a Source # | |
Functor ParseResult # | |
Defined in Distribution.Fields.ParseResult fmap :: (a -> b) -> ParseResult a -> ParseResult b Source # (<$) :: a -> ParseResult b -> ParseResult a Source # | |
Applicative ParseResult # | |
Defined in Distribution.Fields.ParseResult pure :: a -> ParseResult a Source # (<*>) :: ParseResult (a -> b) -> ParseResult a -> ParseResult b Source # liftA2 :: (a -> b -> c) -> ParseResult a -> ParseResult b -> ParseResult c Source # (*>) :: ParseResult a -> ParseResult b -> ParseResult b Source # (<*) :: ParseResult a -> ParseResult b -> ParseResult a Source # |
runParseResult :: ParseResult a -> ([PWarning], Either (Maybe Version, [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.
:: (ByteString -> ParseResult a) | File contents to final value parser |
-> Verbosity | Verbosity level |
-> String | File name |
-> ByteString | |
-> IO a |
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. |
PWTVersionLeadingZeros | See https://github.com/haskell-infra/hackage-trustees/issues/128 |
Instances
Parser warning.
Instances
Show PWarning # | |
Generic PWarning # | |
Binary PWarning # | |
NFData PWarning # | |
Defined in Distribution.Parsec.Warning | |
type Rep PWarning # | |
Defined in Distribution.Parsec.Warning type Rep PWarning = D1 ('MetaData "PWarning" "Distribution.Parsec.Warning" "Cabal-2.5.0.0" 'False) (C1 ('MetaCons "PWarning" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PWarnType) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Position) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))) |
Errors
Parser error.
Instances
Show PError # | |
Generic PError # | |
Binary PError # | |
NFData PError # | |
Defined in Distribution.Parsec.Error | |
type Rep PError # | |
Defined in Distribution.Parsec.Error type Rep PError = D1 ('MetaData "PError" "Distribution.Parsec.Error" "Cabal-2.5.0.0" '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
showFields :: [PrettyField] -> String Source #
Prettyprint a list of fields.
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] |
fromParsecFields :: [Field ann] -> [PrettyField] Source #
Simple variant of genericFromParsecField