stylish-cabal-0.2.0.0: Format Cabal files

Safe HaskellNone
LanguageHaskell2010

StylishCabal

Contents

Description

Cabal file formatter.

Synopsis

Formatting Cabal files

pretty :: GenericPackageDescription -> Doc Source #

pretty pkg produces a colorized, formatted textual representation of a given GenericPackageDescription, with a default indent width of 2.

To remove syntax highlighting, you can use plain.

prettyWithIndent :: Int -> GenericPackageDescription -> Doc Source #

Like pretty, but allows you to specify an indent size.

render :: Int -> Doc -> SimpleDoc Source #

Render the given Doc with the given width.

Parsing utilities

parseCabalFile :: String -> 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.

readCabalFile :: Maybe FilePath -> String -> IO GenericPackageDescription Source #

Shorthand to combine parseCabalFile and one of printWarnings or displayError. The given FilePath is used only for error messages and is not read from.

data Result a Source #

Like Cabal's ParseResult, but treats warnings as a separate failure case.

Constructors

Error (Maybe LineNo) String

Parse error on the given line.

Warn [PWarning]

Warnings emitted during parse.

Success a

The input is a compliant package description.

Instances

Functor Result Source # 

Methods

fmap :: (a -> b) -> Result a -> Result b #

(<$) :: a -> Result b -> Result a #

Eq a => Eq (Result a) Source # 

Methods

(==) :: Result a -> Result a -> Bool #

(/=) :: Result a -> Result a -> Bool #

Data a => Data (Result a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Result a -> c (Result a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Result a) #

toConstr :: Result a -> Constr #

dataTypeOf :: Result a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Result a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Result a)) #

gmapT :: (forall b. Data b => b -> b) -> Result a -> Result a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Result a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Result a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Result a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Result a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Result a -> m (Result a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Result a -> m (Result a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Result a -> m (Result a) #

Show a => Show (Result a) Source # 

Methods

showsPrec :: Int -> Result a -> ShowS #

show :: Result a -> String #

showList :: [Result a] -> ShowS #

Generic (Result a) Source # 

Associated Types

type Rep (Result a) :: * -> * #

Methods

from :: Result a -> Rep (Result a) x #

to :: Rep (Result a) x -> Result a #

NFData a => NFData (Result a) Source # 

Methods

rnf :: Result a -> () #

type Rep (Result a) Source # 

result :: (Maybe LineNo -> String -> b) -> ([PWarning] -> b) -> (a -> b) -> Result a -> b Source #

Case analysis for Result.

printWarnings :: Foldable t => t PWarning -> IO b Source #

Print some warnings to stderr and exit.

displayError :: Maybe FilePath -> Maybe LineNo -> String -> IO a Source #

Print a parse error to stderr, annotated with filepath and line number (if available), then exit.

Reexports

data Doc :: * #

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

Instances

Show Doc 

Methods

showsPrec :: Int -> Doc -> ShowS #

show :: Doc -> String #

showList :: [Doc] -> ShowS #

IsString Doc 

Methods

fromString :: String -> Doc #

Semigroup Doc 

Methods

(<>) :: Doc -> Doc -> Doc #

sconcat :: NonEmpty Doc -> Doc #

stimes :: Integral b => b -> Doc -> Doc #

Monoid Doc 

Methods

mempty :: Doc #

mappend :: Doc -> Doc -> Doc #

mconcat :: [Doc] -> Doc #

Pretty Doc 

Methods

pretty :: Doc -> Doc #

prettyList :: [Doc] -> Doc #

plain :: Doc -> Doc #

Removes all colorisation, emboldening and underlining from a document

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.