| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Distribution.Fields
Description
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, NonEmpty 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
- | PWTVersionOperator
- | PWTVersionWildcard
- | PWTSpecVersion
- | PWTExperimental
 
- data PWarning = PWarning !PWarnType !Position String
- showPWarning :: FilePath -> PWarning -> String
- data PError = PError Position String
- showPError :: FilePath -> PError -> String
- data PrettyField ann- = PrettyField ann FieldName Doc
- | PrettySection ann FieldName [Doc] [PrettyField ann]
 
- showFields :: (ann -> [String]) -> [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
| Functor Field Source # | |
| Foldable Field Source # | |
| 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 # elem :: Eq a => a -> Field a -> Bool # maximum :: Ord a => Field a -> a # minimum :: Ord a => Field a -> a # | |
| Traversable Field Source # | |
| Eq ann => Eq (Field ann) Source # | |
| Show ann => Show (Field ann) Source # | |
A field name.
Invariant: ByteString is lower-case ASCII.
Instances
| Functor Name Source # | |
| Foldable Name Source # | |
| 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 # elem :: Eq a => a -> Name a -> Bool # maximum :: Ord a => Name a -> a # | |
| Traversable Name Source # | |
| Eq ann => Eq (Name ann) Source # | |
| Show ann => Show (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.
Constructors
| FieldLine !ann !ByteString | 
Instances
| Functor FieldLine Source # | |
| Foldable FieldLine Source # | |
| 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] # length :: FieldLine a -> Int # elem :: Eq a => a -> FieldLine a -> Bool # maximum :: Ord a => FieldLine a -> a # minimum :: Ord a => FieldLine a -> a # | |
| Traversable FieldLine Source # | |
| Defined in Distribution.Fields.Field | |
| Eq ann => Eq (FieldLine ann) Source # | |
| Show ann => Show (FieldLine ann) Source # | |
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
type FieldName = ByteString Source #
Grammar and parsing
readFields :: ByteString -> Either ParseError [Field Position] Source #
Parse cabal style ByteString into list of Fields, 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 Source # | |
| Defined in Distribution.Fields.ParseResult Methods (>>=) :: ParseResult a -> (a -> ParseResult b) -> ParseResult b # (>>) :: ParseResult a -> ParseResult b -> ParseResult b # return :: a -> ParseResult a # | |
| Functor ParseResult Source # | |
| Defined in Distribution.Fields.ParseResult Methods fmap :: (a -> b) -> ParseResult a -> ParseResult b # (<$) :: a -> ParseResult b -> ParseResult a # | |
| Applicative ParseResult Source # | |
| Defined in Distribution.Fields.ParseResult Methods 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 # | |
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.
Arguments
| :: (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
Constructors
| 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. | 
| PWTExperimental | Experimental feature | 
Instances
Parser warning.
Instances
| Show PWarning Source # | |
| Generic PWarning Source # | |
| Binary PWarning Source # | |
| NFData PWarning Source # | |
| Defined in Distribution.Parsec.Warning | |
| type Rep PWarning Source # | |
| Defined in Distribution.Parsec.Warning type Rep PWarning = D1 ('MetaData "PWarning" "Distribution.Parsec.Warning" "Cabal-3.4.0.0-87V2bvTScjS3xdojmsQSEW" '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 Source # | |
| Generic PError Source # | |
| Binary PError Source # | |
| NFData PError Source # | |
| Defined in Distribution.Parsec.Error | |
| type Rep PError Source # | |
| Defined in Distribution.Parsec.Error type Rep PError = D1 ('MetaData "PError" "Distribution.Parsec.Error" "Cabal-3.4.0.0-87V2bvTScjS3xdojmsQSEW" '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 PrettyField ann Source #
Constructors
| PrettyField ann FieldName Doc | |
| PrettySection ann FieldName [Doc] [PrettyField ann] | 
Instances
showFields :: (ann -> [String]) -> [PrettyField ann] -> String Source #
Prettyprint a list of fields.
Note: the first argument should return Strings 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 #
Arguments
| :: 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