Safe Haskell | None |
---|---|
Language | Haskell2010 |
Cabal file formatter.
Synopsis
- pretty :: GenericPackageDescription -> Doc
- prettyOpts :: RenderOptions -> GenericPackageDescription -> Doc
- data RenderOptions = RenderOptions {}
- render :: Int -> Doc -> SimpleDoc
- parsePackageDescription :: ByteString -> Result GenericPackageDescription
- readPackageDescription :: Maybe FilePath -> ByteString -> IO GenericPackageDescription
- data Result a
- data PError = PError Position String
- data PWarning = PWarning !PWarnType !Position String
- result :: ([PError] -> b) -> ([PWarning] -> b) -> (a -> b) -> Result a -> b
- printWarnings :: Maybe FilePath -> [PWarning] -> IO a
- displayError :: Maybe FilePath -> [PError] -> IO a
- class Default a where
- def :: a
- data GenericPackageDescription
- data Doc
- plain :: Doc -> Doc
- displayIO :: Handle -> SimpleDoc -> IO ()
- displayS :: SimpleDoc -> ShowS
Formatting Cabal files
pretty :: GenericPackageDescription -> Doc Source #
pretty pkg
produces a colorized, formatted textual representation of
a given GenericPackageDescription
,
using Default
options.
To remove syntax highlighting, you can use plain
.
prettyOpts :: RenderOptions -> GenericPackageDescription -> Doc Source #
pretty
with specified options.
data RenderOptions Source #
RenderOptions | |
|
Instances
Parsing utilities
parsePackageDescription :: ByteString -> Result GenericPackageDescription Source #
This function is similar to Cabal's own file parser, except that it treats warnings as a separate failure case. There are a wide range of different behaviors accepted by different Cabal parser versions. Parse warnings generally indicate a version-related inconsistency, so we play it safe here.
readPackageDescription :: Maybe FilePath -> ByteString -> IO GenericPackageDescription Source #
Shorthand to combine parsePackageDescription
and one of printWarnings
or
displayError
. The given FilePath
is used only for error messages and
is not read from.
Like Cabal's ParseResult
, but treats warnings as a separate failure
case.
Error [PError] | Parse errors. |
Warn [PWarning] | Warnings emitted during parse. |
Success a | The input is a compliant package description. |
Instances
Parser error.
Instances
Eq PError Source # | |
Data PError Source # | |
Defined in Parse gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PError -> c PError # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PError # toConstr :: PError -> Constr # dataTypeOf :: PError -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PError) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PError) # gmapT :: (forall b. Data b => b -> b) -> PError -> PError # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PError -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PError -> r # gmapQ :: (forall d. Data d => d -> u) -> PError -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PError -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PError -> m PError # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PError -> m PError # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PError -> m PError # | |
Show PError | |
Generic PError | |
NFData PError | |
Defined in Distribution.Parsec.Common | |
Binary PError | |
type Rep PError | |
Defined in Distribution.Parsec.Common type Rep PError = D1 (MetaData "PError" "Distribution.Parsec.Common" "Cabal-2.4.0.1" 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))) |
Parser warning.
Instances
Eq PWarning Source # | |
Data PWarning Source # | |
Defined in Parse gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PWarning -> c PWarning # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PWarning # toConstr :: PWarning -> Constr # dataTypeOf :: PWarning -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PWarning) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PWarning) # gmapT :: (forall b. Data b => b -> b) -> PWarning -> PWarning # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PWarning -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PWarning -> r # gmapQ :: (forall d. Data d => d -> u) -> PWarning -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PWarning -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PWarning -> m PWarning # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PWarning -> m PWarning # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PWarning -> m PWarning # | |
Show PWarning | |
Generic PWarning | |
NFData PWarning | |
Defined in Distribution.Parsec.Common | |
Binary PWarning | |
type Rep PWarning | |
Defined in Distribution.Parsec.Common type Rep PWarning = D1 (MetaData "PWarning" "Distribution.Parsec.Common" "Cabal-2.4.0.1" 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)))) |
result :: ([PError] -> b) -> ([PWarning] -> b) -> (a -> b) -> Result a -> b Source #
Case analysis for Result
.
printWarnings :: Maybe FilePath -> [PWarning] -> IO a Source #
Print some warnings to stderr
and exit.
displayError :: Maybe FilePath -> [PError] -> IO a Source #
Print a parse error to stderr
, annotated with filepath if available,
then exit.
Reexports
A class for types with a default value.
Nothing
Instances
data GenericPackageDescription #
Instances
The abstract data type Doc
represents pretty documents.
More specifically, a value of type Doc
represents a non-empty set of
possible renderings of a document. The rendering functions select one of
these possibilities.
Doc
is an instance of the Show
class. (show doc)
pretty
prints document doc
with a page width of 80 characters and a
ribbon width of 32 characters.
show (text "hello" <$> text "world")
Which would return the string "hello\nworld", i.e.
hello world
displayIO :: Handle -> SimpleDoc -> IO () #
(displayIO handle simpleDoc)
writes simpleDoc
to the file
handle handle
. This function is used for example by hPutDoc
:
hPutDoc handle doc = displayIO handle (renderPretty 0.4 80 doc)
Any ANSI colorisation in simpleDoc
will be output.
displayS :: SimpleDoc -> ShowS #
(displayS simpleDoc)
takes the output simpleDoc
from a
rendering function and transforms it to a ShowS
type (for use in
the Show
class).
showWidth :: Int -> Doc -> String showWidth w x = displayS (renderPretty 0.4 w x) ""
ANSI color information will be discarded by this function unless you are running on a Unix-like operating system. This is due to a technical limitation in Windows ANSI support.