stylish-cabal-0.5.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 # 
Instance details

Defined in Render.Options

Data RenderOptions Source # 
Instance details

Defined in Render.Options

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 # 
Instance details

Defined in Render.Options

Generic RenderOptions Source # 
Instance details

Defined in Render.Options

Associated Types

type Rep RenderOptions :: Type -> Type #

Default RenderOptions Source # 
Instance details

Defined in Render.Options

Methods

def :: RenderOptions #

type Rep RenderOptions Source # 
Instance details

Defined in Render.Options

type Rep RenderOptions = D1 (MetaData "RenderOptions" "Render.Options" "stylish-cabal-0.5.0.0-IlcxGZ1XUub1oNbLnjuTex" False) (C1 (MetaCons "RenderOptions" PrefixI True) (S1 (MetaSel (Just "indentSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "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 # 
Instance details

Defined in Parse

Methods

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

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

Eq1 Result Source # 
Instance details

Defined in Parse

Methods

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

Show1 Result Source # 
Instance details

Defined in Parse

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 # 
Instance details

Defined in Parse

Methods

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

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

Data a => Data (Result a) Source # 
Instance details

Defined in Parse

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 # 
Instance details

Defined in Parse

Methods

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

show :: Result a -> String #

showList :: [Result a] -> ShowS #

Generic (Result a) Source # 
Instance details

Defined in Parse

Associated Types

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

Methods

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

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

NFData a => NFData (Result a) Source # 
Instance details

Defined in Parse

Methods

rnf :: Result a -> () #

Generic1 Result Source # 
Instance details

Defined in Parse

Associated Types

type Rep1 Result :: k -> Type #

Methods

from1 :: Result a -> Rep1 Result a #

to1 :: Rep1 Result a -> Result a #

type Rep (Result a) Source # 
Instance details

Defined in Parse

type Rep1 Result Source # 
Instance details

Defined in Parse

data PError #

Parser error.

Constructors

PError Position String 
Instances
Eq PError Source # 
Instance details

Defined in Parse

Methods

(==) :: PError -> PError -> Bool #

(/=) :: PError -> PError -> Bool #

Data PError Source # 
Instance details

Defined in Parse

Methods

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 
Instance details

Defined in Distribution.Parsec.Common

Generic PError 
Instance details

Defined in Distribution.Parsec.Common

Associated Types

type Rep PError :: Type -> Type #

Methods

from :: PError -> Rep PError x #

to :: Rep PError x -> PError #

NFData PError 
Instance details

Defined in Distribution.Parsec.Common

Methods

rnf :: PError -> () #

Binary PError 
Instance details

Defined in Distribution.Parsec.Common

Methods

put :: PError -> Put #

get :: Get PError #

putList :: [PError] -> Put #

type Rep PError 
Instance details

Defined in Distribution.Parsec.Common

data PWarning #

Parser warning.

Instances
Eq PWarning Source # 
Instance details

Defined in Parse

Data PWarning Source # 
Instance details

Defined in Parse

Methods

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 
Instance details

Defined in Distribution.Parsec.Common

Generic PWarning 
Instance details

Defined in Distribution.Parsec.Common

Associated Types

type Rep PWarning :: Type -> Type #

Methods

from :: PWarning -> Rep PWarning x #

to :: Rep PWarning x -> PWarning #

NFData PWarning 
Instance details

Defined in Distribution.Parsec.Common

Methods

rnf :: PWarning -> () #

Binary PWarning 
Instance details

Defined in Distribution.Parsec.Common

Methods

put :: PWarning -> Put #

get :: Get PWarning #

putList :: [PWarning] -> Put #

type Rep PWarning 
Instance details

Defined in Distribution.Parsec.Common

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.

Minimal complete definition

Nothing

Methods

def :: a #

The default value for this type.

Instances
Default Double 
Instance details

Defined in Data.Default.Class

Methods

def :: Double #

Default Float 
Instance details

Defined in Data.Default.Class

Methods

def :: Float #

Default Int 
Instance details

Defined in Data.Default.Class

Methods

def :: Int #

Default Int8 
Instance details

Defined in Data.Default.Class

Methods

def :: Int8 #

Default Int16 
Instance details

Defined in Data.Default.Class

Methods

def :: Int16 #

Default Int32 
Instance details

Defined in Data.Default.Class

Methods

def :: Int32 #

Default Int64 
Instance details

Defined in Data.Default.Class

Methods

def :: Int64 #

Default Integer 
Instance details

Defined in Data.Default.Class

Methods

def :: Integer #

Default Ordering 
Instance details

Defined in Data.Default.Class

Methods

def :: Ordering #

Default Word 
Instance details

Defined in Data.Default.Class

Methods

def :: Word #

Default Word8 
Instance details

Defined in Data.Default.Class

Methods

def :: Word8 #

Default Word16 
Instance details

Defined in Data.Default.Class

Methods

def :: Word16 #

Default Word32 
Instance details

Defined in Data.Default.Class

Methods

def :: Word32 #

Default Word64 
Instance details

Defined in Data.Default.Class

Methods

def :: Word64 #

Default () 
Instance details

Defined in Data.Default.Class

Methods

def :: () #

Default Any 
Instance details

Defined in Data.Default.Class

Methods

def :: Any #

Default All 
Instance details

Defined in Data.Default.Class

Methods

def :: All #

Default CShort 
Instance details

Defined in Data.Default.Class

Methods

def :: CShort #

Default CUShort 
Instance details

Defined in Data.Default.Class

Methods

def :: CUShort #

Default CInt 
Instance details

Defined in Data.Default.Class

Methods

def :: CInt #

Default CUInt 
Instance details

Defined in Data.Default.Class

Methods

def :: CUInt #

Default CLong 
Instance details

Defined in Data.Default.Class

Methods

def :: CLong #

Default CULong 
Instance details

Defined in Data.Default.Class

Methods

def :: CULong #

Default CLLong 
Instance details

Defined in Data.Default.Class

Methods

def :: CLLong #

Default CULLong 
Instance details

Defined in Data.Default.Class

Methods

def :: CULLong #

Default CFloat 
Instance details

Defined in Data.Default.Class

Methods

def :: CFloat #

Default CDouble 
Instance details

Defined in Data.Default.Class

Methods

def :: CDouble #

Default CPtrdiff 
Instance details

Defined in Data.Default.Class

Methods

def :: CPtrdiff #

Default CSize 
Instance details

Defined in Data.Default.Class

Methods

def :: CSize #

Default CSigAtomic 
Instance details

Defined in Data.Default.Class

Methods

def :: CSigAtomic #

Default CClock 
Instance details

Defined in Data.Default.Class

Methods

def :: CClock #

Default CTime 
Instance details

Defined in Data.Default.Class

Methods

def :: CTime #

Default CUSeconds 
Instance details

Defined in Data.Default.Class

Methods

def :: CUSeconds #

Default CSUSeconds 
Instance details

Defined in Data.Default.Class

Methods

def :: CSUSeconds #

Default CIntPtr 
Instance details

Defined in Data.Default.Class

Methods

def :: CIntPtr #

Default CUIntPtr 
Instance details

Defined in Data.Default.Class

Methods

def :: CUIntPtr #

Default CIntMax 
Instance details

Defined in Data.Default.Class

Methods

def :: CIntMax #

Default CUIntMax 
Instance details

Defined in Data.Default.Class

Methods

def :: CUIntMax #

Default RenderOptions Source # 
Instance details

Defined in Render.Options

Methods

def :: RenderOptions #

Default [a] 
Instance details

Defined in Data.Default.Class

Methods

def :: [a] #

Default (Maybe a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Maybe a #

Integral a => Default (Ratio a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Ratio a #

Default a => Default (IO a) 
Instance details

Defined in Data.Default.Class

Methods

def :: IO a #

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

Defined in Data.Default.Class

Methods

def :: Complex a #

Default (First a) 
Instance details

Defined in Data.Default.Class

Methods

def :: First a #

Default (Last a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Last a #

Default a => Default (Dual a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Dual a #

Default (Endo a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Endo a #

Num a => Default (Sum a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Sum a #

Num a => Default (Product a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Product a #

Default r => Default (e -> r) 
Instance details

Defined in Data.Default.Class

Methods

def :: e -> r #

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

Defined in Data.Default.Class

Methods

def :: (a, b) #

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

Defined in Data.Default.Class

Methods

def :: (a, b, c) #

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

Defined in Data.Default.Class

Methods

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

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

Defined in Data.Default.Class

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) 
Instance details

Defined in Data.Default.Class

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) 
Instance details

Defined in Data.Default.Class

Methods

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

data GenericPackageDescription #

Instances
Eq GenericPackageDescription 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Data GenericPackageDescription 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Methods

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

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

toConstr :: GenericPackageDescription -> Constr #

dataTypeOf :: GenericPackageDescription -> DataType #

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

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

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

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

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

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

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

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

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

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

Show GenericPackageDescription 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Generic GenericPackageDescription 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Associated Types

type Rep GenericPackageDescription :: Type -> Type #

HasBuildInfos GenericPackageDescription 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Package GenericPackageDescription 
Instance details

Defined in Distribution.Types.GenericPackageDescription

NFData GenericPackageDescription 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Binary GenericPackageDescription 
Instance details

Defined in Distribution.Types.GenericPackageDescription

type Rep GenericPackageDescription 
Instance details

Defined in Distribution.Types.GenericPackageDescription

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 
Instance details

Defined in Text.PrettyPrint.ANSI.Leijen.Internal

Methods

showsPrec :: Int -> Doc -> ShowS #

show :: Doc -> String #

showList :: [Doc] -> ShowS #

IsString Doc 
Instance details

Defined in Text.PrettyPrint.ANSI.Leijen.Internal

Methods

fromString :: String -> Doc #

Semigroup Doc 
Instance details

Defined in Text.PrettyPrint.ANSI.Leijen.Internal

Methods

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

sconcat :: NonEmpty Doc -> Doc #

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

Monoid Doc 
Instance details

Defined in Text.PrettyPrint.ANSI.Leijen.Internal

Methods

mempty :: Doc #

mappend :: Doc -> Doc -> Doc #

mconcat :: [Doc] -> Doc #

Pretty Doc 
Instance details

Defined in Text.PrettyPrint.ANSI.Leijen.Internal

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.