Cabal-3.5.0.0: A framework for packaging Haskell software
Safe HaskellSafe-Inferred
LanguageHaskell2010

Distribution.Pretty

Synopsis

Documentation

class Pretty a where Source #

Minimal complete definition

pretty

Instances

Instances details
Pretty OpenModule # 
Instance details

Defined in Distribution.Backpack

Pretty OpenUnitId # 
Instance details

Defined in Distribution.Backpack

Pretty AbiTag # 
Instance details

Defined in Distribution.Compiler

Pretty CompilerFlavor # 
Instance details

Defined in Distribution.Compiler

Pretty CompilerId # 
Instance details

Defined in Distribution.Compiler

Pretty FilePathNT # 
Instance details

Defined in Distribution.FieldGrammar.Newtypes

Pretty SpecLicense # 
Instance details

Defined in Distribution.FieldGrammar.Newtypes

Pretty SpecVersion # 
Instance details

Defined in Distribution.FieldGrammar.Newtypes

Pretty TestedWith # 
Instance details

Defined in Distribution.FieldGrammar.Newtypes

Pretty Token # 
Instance details

Defined in Distribution.FieldGrammar.Newtypes

Pretty Token' # 
Instance details

Defined in Distribution.FieldGrammar.Newtypes

Pretty License # 
Instance details

Defined in Distribution.License

Pretty ModuleName # 
Instance details

Defined in Distribution.ModuleName

Pretty License # 
Instance details

Defined in Distribution.SPDX.License

Pretty LicenseExceptionId # 
Instance details

Defined in Distribution.SPDX.LicenseExceptionId

Pretty LicenseExpression # 
Instance details

Defined in Distribution.SPDX.LicenseExpression

Pretty SimpleLicenseExpression # 
Instance details

Defined in Distribution.SPDX.LicenseExpression

Pretty LicenseId # 
Instance details

Defined in Distribution.SPDX.LicenseId

Pretty LicenseRef # 
Instance details

Defined in Distribution.SPDX.LicenseReference

Pretty HaddockTarget # 
Instance details

Defined in Distribution.Simple.Setup

Pretty TestShowDetails # 
Instance details

Defined in Distribution.Simple.Setup

Pretty Arch # 
Instance details

Defined in Distribution.System

Pretty OS # 
Instance details

Defined in Distribution.System

Pretty Platform # 
Instance details

Defined in Distribution.System

Pretty AbiDependency # 
Instance details

Defined in Distribution.Types.AbiDependency

Pretty AbiHash # 
Instance details

Defined in Distribution.Types.AbiHash

Pretty BenchmarkType # 
Instance details

Defined in Distribution.Types.BenchmarkType

Pretty BuildType # 
Instance details

Defined in Distribution.Types.BuildType

Pretty ComponentId # 
Instance details

Defined in Distribution.Types.ComponentId

Pretty ComponentName # 
Instance details

Defined in Distribution.Types.ComponentName

Pretty Dependency #
>>> prettyShow $ Dependency "pkg" anyVersion mainLibSet
"pkg"
>>> prettyShow $ Dependency "pkg" anyVersion $ NES.insert (LSubLibName "sublib") mainLibSet
"pkg:{pkg, sublib}"
>>> prettyShow $ Dependency "pkg" anyVersion $ NES.singleton (LSubLibName "sublib")
"pkg:sublib"
>>> prettyShow $ Dependency "pkg" anyVersion $ NES.insert (LSubLibName "sublib-b") $ NES.singleton (LSubLibName "sublib-a")
"pkg:{sublib-a, sublib-b}"
Instance details

Defined in Distribution.Types.Dependency

Pretty ExeDependency # 
Instance details

Defined in Distribution.Types.ExeDependency

Pretty ExecutableScope # 
Instance details

Defined in Distribution.Types.ExecutableScope

Pretty ExposedModule # 
Instance details

Defined in Distribution.Types.ExposedModule

Pretty FlagAssignment #

Since: Cabal-3.4.0.0

Instance details

Defined in Distribution.Types.Flag

Pretty FlagName # 
Instance details

Defined in Distribution.Types.Flag

Pretty LibVersionInfo # 
Instance details

Defined in Distribution.Types.ForeignLib

Pretty ForeignLibOption # 
Instance details

Defined in Distribution.Types.ForeignLibOption

Pretty ForeignLibType # 
Instance details

Defined in Distribution.Types.ForeignLibType

Pretty IncludeRenaming # 
Instance details

Defined in Distribution.Types.IncludeRenaming

Pretty LegacyExeDependency # 
Instance details

Defined in Distribution.Types.LegacyExeDependency

Pretty LibraryVisibility # 
Instance details

Defined in Distribution.Types.LibraryVisibility

Pretty Mixin # 
Instance details

Defined in Distribution.Types.Mixin

Pretty Module # 
Instance details

Defined in Distribution.Types.Module

Pretty ModuleReexport # 
Instance details

Defined in Distribution.Types.ModuleReexport

Pretty ModuleRenaming # 
Instance details

Defined in Distribution.Types.ModuleRenaming

Pretty MungedPackageId #
>>> prettyShow $ MungedPackageId (MungedPackageName "servant" LMainLibName) (mkVersion [1,2,3])
"servant-1.2.3"
>>> prettyShow $ MungedPackageId (MungedPackageName "servant" (LSubLibName "lackey")) (mkVersion [0,1,2])
"z-servant-z-lackey-0.1.2"
Instance details

Defined in Distribution.Types.MungedPackageId

Pretty MungedPackageName #

Computes the package name for a library. If this is the public library, it will just be the original package name; otherwise, it will be a munged package name recording the original package name as well as the name of the internal library.

A lot of tooling in the Haskell ecosystem assumes that if something is installed to the package database with the package name foo, then it actually is an entry for the (only public) library in package foo. With internal packages, this is not necessarily true: a public library as well as arbitrarily many internal libraries may come from the same package. To prevent tools from getting confused in this case, the package name of these internal libraries is munged so that they do not conflict the public library proper. A particular case where this matters is ghc-pkg: if we don't munge the package name, the inplace registration will OVERRIDE a different internal library.

We munge into a reserved namespace, "z-", and encode both the component name and the package name of an internal library using the following format:

compat-pkg-name ::= "z-" package-name "-z-" library-name

where package-name and library-name have "-" ( "z" + ) "-" segments encoded by adding an extra "z".

When we have the public library, the compat-pkg-name is just the package-name, no surprises there!

>>> prettyShow $ MungedPackageName "servant" LMainLibName
"servant"
>>> prettyShow $ MungedPackageName "servant" (LSubLibName "lackey")
"z-servant-z-lackey"
Instance details

Defined in Distribution.Types.MungedPackageName

Pretty PackageIdentifier # 
Instance details

Defined in Distribution.Types.PackageId

Pretty PackageName # 
Instance details

Defined in Distribution.Types.PackageName

Pretty PackageVersionConstraint # 
Instance details

Defined in Distribution.Types.PackageVersionConstraint

Pretty PkgconfigDependency # 
Instance details

Defined in Distribution.Types.PkgconfigDependency

Pretty PkgconfigName # 
Instance details

Defined in Distribution.Types.PkgconfigName

Pretty PkgconfigVersion # 
Instance details

Defined in Distribution.Types.PkgconfigVersion

Pretty PkgconfigVersionRange # 
Instance details

Defined in Distribution.Types.PkgconfigVersionRange

Pretty KnownRepoType # 
Instance details

Defined in Distribution.Types.SourceRepo

Pretty RepoKind # 
Instance details

Defined in Distribution.Types.SourceRepo

Pretty RepoType # 
Instance details

Defined in Distribution.Types.SourceRepo

Pretty TestType # 
Instance details

Defined in Distribution.Types.TestType

Pretty DefUnitId # 
Instance details

Defined in Distribution.Types.UnitId

Pretty UnitId #

The textual format for UnitId coincides with the format GHC accepts for -package-id.

Instance details

Defined in Distribution.Types.UnitId

Pretty UnqualComponentName # 
Instance details

Defined in Distribution.Types.UnqualComponentName

Pretty Version # 
Instance details

Defined in Distribution.Types.Version

Pretty VersionRange #
>>> fmap pretty (simpleParsec' CabalSpecV1_6 "== 3.2.*" :: Maybe VersionRange)
Just >=3.2 && <3.3
>>> fmap (prettyVersioned CabalSpecV1_6) (simpleParsec' CabalSpecV1_6 "== 3.2.*" :: Maybe VersionRange)
Just ==3.2.*
>>> fmap pretty (simpleParsec' CabalSpecV1_6 "-any" :: Maybe VersionRange)
Just >=0
>>> fmap (prettyVersioned CabalSpecV1_6) (simpleParsec' CabalSpecV1_6 "-any" :: Maybe VersionRange)
Just >=0
Instance details

Defined in Distribution.Types.VersionRange.Internal

Pretty Verbosity # 
Instance details

Defined in Distribution.Verbosity

Pretty Extension # 
Instance details

Defined in Language.Haskell.Extension

Pretty KnownExtension # 
Instance details

Defined in Language.Haskell.Extension

Pretty Language # 
Instance details

Defined in Language.Haskell.Extension

Pretty Doc #

Since: Cabal-3.4.0.0

Instance details

Defined in Distribution.Pretty

Pretty Bool # 
Instance details

Defined in Distribution.Pretty

Pretty Int # 
Instance details

Defined in Distribution.Pretty

FieldGrammar Pretty PrettyFieldGrammar # 
Instance details

Defined in Distribution.FieldGrammar.Pretty

Methods

blurFieldGrammar :: ALens' a b -> PrettyFieldGrammar b d -> PrettyFieldGrammar a d Source #

uniqueFieldAla :: (Pretty b, Newtype a b) => FieldName -> (a -> b) -> ALens' s a -> PrettyFieldGrammar s a Source #

booleanFieldDef :: FieldName -> ALens' s Bool -> Bool -> PrettyFieldGrammar s Bool Source #

optionalFieldAla :: (Pretty b, Newtype a b) => FieldName -> (a -> b) -> ALens' s (Maybe a) -> PrettyFieldGrammar s (Maybe a) Source #

optionalFieldDefAla :: (Pretty b, Newtype a b, Eq a) => FieldName -> (a -> b) -> ALens' s a -> a -> PrettyFieldGrammar s a Source #

freeTextField :: FieldName -> ALens' s (Maybe String) -> PrettyFieldGrammar s (Maybe String) Source #

freeTextFieldDef :: FieldName -> ALens' s String -> PrettyFieldGrammar s String Source #

freeTextFieldDefST :: FieldName -> ALens' s ShortText -> PrettyFieldGrammar s ShortText Source #

monoidalFieldAla :: (Pretty b, Monoid a, Newtype a b) => FieldName -> (a -> b) -> ALens' s a -> PrettyFieldGrammar s a Source #

prefixedFields :: FieldName -> ALens' s [(String, String)] -> PrettyFieldGrammar s [(String, String)] Source #

knownField :: FieldName -> PrettyFieldGrammar s () Source #

hiddenField :: PrettyFieldGrammar s a -> PrettyFieldGrammar s a Source #

deprecatedSince :: CabalSpecVersion -> String -> PrettyFieldGrammar s a -> PrettyFieldGrammar s a Source #

removedIn :: CabalSpecVersion -> String -> PrettyFieldGrammar s a -> PrettyFieldGrammar s a Source #

availableSince :: CabalSpecVersion -> a -> PrettyFieldGrammar s a -> PrettyFieldGrammar s a Source #

availableSinceWarn :: CabalSpecVersion -> PrettyFieldGrammar s a -> PrettyFieldGrammar s a Source #

Pretty a => Pretty (MQuoted a) # 
Instance details

Defined in Distribution.FieldGrammar.Newtypes

Pretty a => Pretty (Identity a) # 
Instance details

Defined in Distribution.Pretty

Pretty (SymbolicPath from to) # 
Instance details

Defined in Distribution.Utils.Path

(Newtype a b, Sep sep, Pretty b) => Pretty (List sep b a) # 
Instance details

Defined in Distribution.FieldGrammar.Newtypes

Methods

pretty :: List sep b a -> Doc Source #

prettyVersioned :: CabalSpecVersion -> List sep b a -> Doc Source #

(Newtype a b, Sep sep, Pretty b) => Pretty (NonEmpty' sep b a) # 
Instance details

Defined in Distribution.FieldGrammar.Newtypes

(Newtype a b, Sep sep, Pretty b) => Pretty (Set' sep b a) # 
Instance details

Defined in Distribution.FieldGrammar.Newtypes

Methods

pretty :: Set' sep b a -> Doc Source #

prettyVersioned :: CabalSpecVersion -> Set' sep b a -> Doc Source #

defaultStyle :: Style Source #

The default rendering style used in Cabal for console output. It has a fixed page width and adds line breaks automatically.

flatStyle :: Style Source #

A style for rendering all on one line.

Utilities

showFreeText :: String -> Doc Source #

Pretty-print free-format text, ensuring that it is vertically aligned, and with blank lines replaced by dots for correct re-parsing.

showFreeTextV3 :: String -> Doc Source #

Pretty-print free-format text. Since cabal-version: 3.0 we don't replace blank lines with dots.

Since: Cabal-3.0.0.0

Deprecated

type Separator = [Doc] -> Doc Source #