Portability | portable |
---|---|
Maintainer | cabal-devel@haskell.org |
Safe Haskell | Safe-Infered |
Utilities for parsing PackageDescription
and InstalledPackageInfo
.
The .cabal
file format is not trivial, especially with the introduction
of configurations and the section syntax that goes with that. This module
has a bunch of parsing functions that is used by the .cabal
parser and a
couple others. It has the parsing framework code and also little parsers for
many of the formats we get in various .cabal
file fields, like module
names, comma separated lists etc.
- type LineNo = Int
- data PError
- data PWarning
- locatedErrorMsg :: PError -> (Maybe LineNo, String)
- syntaxError :: LineNo -> String -> ParseResult a
- warning :: String -> ParseResult ()
- runP :: LineNo -> String -> ReadP a a -> String -> ParseResult a
- runE :: LineNo -> String -> ReadE a -> String -> ParseResult a
- data ParseResult a
- = ParseFailed PError
- | ParseOk [PWarning] a
- catchParseError :: ParseResult a -> (PError -> ParseResult a) -> ParseResult a
- parseFail :: PError -> ParseResult a
- showPWarning :: FilePath -> PWarning -> String
- data Field
- fName :: Field -> String
- lineNo :: Field -> LineNo
- data FieldDescr a = FieldDescr {}
- ppField :: String -> Doc -> Doc
- ppFields :: [FieldDescr a] -> a -> Doc
- readFields :: String -> ParseResult [Field]
- readFieldsFlat :: String -> ParseResult [Field]
- showFields :: [FieldDescr a] -> a -> String
- showSingleNamedField :: [FieldDescr a] -> String -> Maybe (a -> String)
- parseFields :: [FieldDescr a] -> a -> String -> ParseResult a
- parseFieldsFlat :: [FieldDescr a] -> a -> String -> ParseResult a
- parseFilePathQ :: ReadP r FilePath
- parseTokenQ :: ReadP r String
- parseTokenQ' :: ReadP r String
- parseModuleNameQ :: ReadP r ModuleName
- parseBuildTool :: ReadP r Dependency
- parsePkgconfigDependency :: ReadP r Dependency
- parseOptVersion :: ReadP r Version
- parsePackageNameQ :: ReadP r PackageName
- parseVersionRangeQ :: ReadP r VersionRange
- parseTestedWithQ :: ReadP r (CompilerFlavor, VersionRange)
- parseLicenseQ :: ReadP r License
- parseLanguageQ :: ReadP r Language
- parseExtensionQ :: ReadP r Extension
- parseSepList :: ReadP r b -> ReadP r a -> ReadP r [a]
- parseCommaList :: ReadP r a -> ReadP r [a]
- parseOptCommaList :: ReadP r a -> ReadP r [a]
- showFilePath :: FilePath -> Doc
- showToken :: String -> Doc
- showTestedWith :: (CompilerFlavor, VersionRange) -> Doc
- showFreeText :: String -> Doc
- parseFreeText :: ReadP s String
- field :: String -> (a -> Doc) -> ReadP a a -> FieldDescr a
- simpleField :: String -> (a -> Doc) -> ReadP a a -> (b -> a) -> (a -> b -> b) -> FieldDescr b
- listField :: String -> (a -> Doc) -> ReadP [a] a -> (b -> [a]) -> ([a] -> b -> b) -> FieldDescr b
- spaceListField :: String -> (a -> Doc) -> ReadP [a] a -> (b -> [a]) -> ([a] -> b -> b) -> FieldDescr b
- commaListField :: String -> (a -> Doc) -> ReadP [a] a -> (b -> [a]) -> ([a] -> b -> b) -> FieldDescr b
- optsField :: String -> CompilerFlavor -> (b -> [(CompilerFlavor, [String])]) -> ([(CompilerFlavor, [String])] -> b -> b) -> FieldDescr b
- liftField :: (b -> a) -> (a -> b -> b) -> FieldDescr a -> FieldDescr b
- boolField :: String -> (b -> Bool) -> (Bool -> b -> b) -> FieldDescr b
- parseQuoted :: ReadP r a -> ReadP r a
- type UnrecFieldParser a = (String, String) -> a -> Maybe a
- warnUnrec :: UnrecFieldParser a
- ignoreUnrec :: UnrecFieldParser a
Documentation
syntaxError :: LineNo -> String -> ParseResult aSource
warning :: String -> ParseResult ()Source
data ParseResult a Source
Monad ParseResult | |
Show a => Show (ParseResult a) |
catchParseError :: ParseResult a -> (PError -> ParseResult a) -> ParseResult aSource
parseFail :: PError -> ParseResult aSource
showPWarning :: FilePath -> PWarning -> StringSource
data FieldDescr a Source
Field descriptor. The parameter a
parameterizes over where the field's
value is stored in.
ppFields :: [FieldDescr a] -> a -> DocSource
readFields :: String -> ParseResult [Field]Source
readFieldsFlat :: String -> ParseResult [Field]Source
showFields :: [FieldDescr a] -> a -> StringSource
showSingleNamedField :: [FieldDescr a] -> String -> Maybe (a -> String)Source
parseFields :: [FieldDescr a] -> a -> String -> ParseResult aSource
parseFieldsFlat :: [FieldDescr a] -> a -> String -> ParseResult aSource
parseTokenQ :: ReadP r StringSource
parseModuleNameQ :: ReadP r ModuleNameSource
parse a module name
showFilePath :: FilePath -> DocSource
showFreeText :: String -> DocSource
Pretty-print free-format text, ensuring that it is vertically aligned, and with blank lines replaced by dots for correct re-parsing.
simpleField :: String -> (a -> Doc) -> ReadP a a -> (b -> a) -> (a -> b -> b) -> FieldDescr bSource
listField :: String -> (a -> Doc) -> ReadP [a] a -> (b -> [a]) -> ([a] -> b -> b) -> FieldDescr bSource
spaceListField :: String -> (a -> Doc) -> ReadP [a] a -> (b -> [a]) -> ([a] -> b -> b) -> FieldDescr bSource
commaListField :: String -> (a -> Doc) -> ReadP [a] a -> (b -> [a]) -> ([a] -> b -> b) -> FieldDescr bSource
optsField :: String -> CompilerFlavor -> (b -> [(CompilerFlavor, [String])]) -> ([(CompilerFlavor, [String])] -> b -> b) -> FieldDescr bSource
liftField :: (b -> a) -> (a -> b -> b) -> FieldDescr a -> FieldDescr bSource
parseQuoted :: ReadP r a -> ReadP r aSource
type UnrecFieldParser a = (String, String) -> a -> Maybe aSource
The type of a function which, given a name-value pair of an unrecognized field, and the current structure being built, decides whether to incorporate the unrecognized field (by returning Just x, where x is a possibly modified version of the structure being built), or not (by returning Nothing).
warnUnrec :: UnrecFieldParser aSource
A default unrecognized field parser which simply returns Nothing, i.e. ignores all unrecognized fields, so warnings will be generated.
ignoreUnrec :: UnrecFieldParser aSource
A default unrecognized field parser which silently (i.e. no warnings will be generated) ignores unrecognized fields, by returning the structure being built unmodified.