stylish-cabal-0.4.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, using Default options.

To remove syntax highlighting, you can use plain.

data RenderOptions Source #

Constructors

RenderOptions 

Fields

Instances

Eq RenderOptions Source # 
Data RenderOptions Source # 

Methods

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

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

toConstr :: RenderOptions -> Constr #

dataTypeOf :: RenderOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Show RenderOptions Source # 
Generic RenderOptions Source # 

Associated Types

type Rep RenderOptions :: * -> * #

Default RenderOptions Source # 

Methods

def :: RenderOptions #

type Rep RenderOptions Source # 
type Rep RenderOptions = D1 * (MetaData "RenderOptions" "Render.Options" "stylish-cabal-0.4.0.0-EenpFJ56e674YnpKmOMu2Z" False) (C1 * (MetaCons "RenderOptions" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "indentSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "simplifyVersions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))))

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

Render the given Doc with the given width.

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.

data Result a Source #

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

Constructors

Error [PError]

Parse errors.

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 #

Eq1 Result Source # 

Methods

liftEq :: (a -> b -> Bool) -> Result a -> Result b -> Bool #

Show1 Result Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Result a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Result a] -> ShowS #

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 -> () #

Generic1 * Result Source # 

Associated Types

type Rep1 Result (f :: Result -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 Result f a #

to1 :: Rep1 Result f a -> f a #

type Rep (Result a) Source # 
type Rep1 * Result Source # 

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

class Default a where #

A class for types with a default value.

Methods

def :: a #

The default value for this type.

Instances

Default Double 

Methods

def :: Double #

Default Float 

Methods

def :: Float #

Default Int 

Methods

def :: Int #

Default Int8 

Methods

def :: Int8 #

Default Int16 

Methods

def :: Int16 #

Default Int32 

Methods

def :: Int32 #

Default Int64 

Methods

def :: Int64 #

Default Integer 

Methods

def :: Integer #

Default Ordering 

Methods

def :: Ordering #

Default Word 

Methods

def :: Word #

Default Word8 

Methods

def :: Word8 #

Default Word16 

Methods

def :: Word16 #

Default Word32 

Methods

def :: Word32 #

Default Word64 

Methods

def :: Word64 #

Default () 

Methods

def :: () #

Default Any 

Methods

def :: Any #

Default All 

Methods

def :: All #

Default CShort 

Methods

def :: CShort #

Default CUShort 

Methods

def :: CUShort #

Default CInt 

Methods

def :: CInt #

Default CUInt 

Methods

def :: CUInt #

Default CLong 

Methods

def :: CLong #

Default CULong 

Methods

def :: CULong #

Default CLLong 

Methods

def :: CLLong #

Default CULLong 

Methods

def :: CULLong #

Default CFloat 

Methods

def :: CFloat #

Default CDouble 

Methods

def :: CDouble #

Default CPtrdiff 

Methods

def :: CPtrdiff #

Default CSize 

Methods

def :: CSize #

Default CSigAtomic 

Methods

def :: CSigAtomic #

Default CClock 

Methods

def :: CClock #

Default CTime 

Methods

def :: CTime #

Default CUSeconds 

Methods

def :: CUSeconds #

Default CSUSeconds 

Methods

def :: CSUSeconds #

Default CIntPtr 

Methods

def :: CIntPtr #

Default CUIntPtr 

Methods

def :: CUIntPtr #

Default CIntMax 

Methods

def :: CIntMax #

Default CUIntMax 

Methods

def :: CUIntMax #

Default RenderOptions # 

Methods

def :: RenderOptions #

Default [a] 

Methods

def :: [a] #

Default (Maybe a) 

Methods

def :: Maybe a #

Integral a => Default (Ratio a) 

Methods

def :: Ratio a #

Default a => Default (IO a) 

Methods

def :: IO a #

(Default a, RealFloat a) => Default (Complex a) 

Methods

def :: Complex a #

Default a => Default (Dual a) 

Methods

def :: Dual a #

Default (Endo a) 

Methods

def :: Endo a #

Num a => Default (Sum a) 

Methods

def :: Sum a #

Num a => Default (Product a) 

Methods

def :: Product a #

Default (First a) 

Methods

def :: First a #

Default (Last a) 

Methods

def :: Last a #

Default r => Default (e -> r) 

Methods

def :: e -> r #

(Default a, Default b) => Default (a, b) 

Methods

def :: (a, b) #

(Default a, Default b, Default c) => Default (a, b, c) 

Methods

def :: (a, b, c) #

(Default a, Default b, Default c, Default d) => Default (a, b, c, d) 

Methods

def :: (a, b, c, d) #

(Default a, Default b, Default c, Default d, Default e) => Default (a, b, c, d, e) 

Methods

def :: (a, b, c, d, e) #

(Default a, Default b, Default c, Default d, Default e, Default f) => Default (a, b, c, d, e, f) 

Methods

def :: (a, b, c, d, e, f) #

(Default a, Default b, Default c, Default d, Default e, Default f, Default g) => Default (a, b, c, d, e, f, g) 

Methods

def :: (a, b, c, d, e, f, g) #

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.