| Pretty Bool Source # |  | 
| Instance detailsDefined in Distribution.Pretty | 
| Pretty Int Source # |  | 
| Instance detailsDefined in Distribution.Pretty | 
| Pretty Doc Source # | Since: 3.4.0.0 | 
| Instance detailsDefined in Distribution.Pretty | 
| Pretty Version Source # |  | 
| Instance detailsDefined in Distribution.Types.Version | 
| Pretty VersionRange Source # | >>> 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 detailsDefined in Distribution.Types.VersionRange.Internal | 
| Pretty RepoType Source # |  | 
| Instance detailsDefined in Distribution.Types.SourceRepo | 
| Pretty KnownRepoType Source # |  | 
| Instance detailsDefined in Distribution.Types.SourceRepo | 
| Pretty RepoKind Source # |  | 
| Instance detailsDefined in Distribution.Types.SourceRepo | 
| Pretty PkgconfigVersion Source # |  | 
| Instance detailsDefined in Distribution.Types.PkgconfigVersion | 
| Pretty PkgconfigVersionRange Source # |  | 
| Instance detailsDefined in Distribution.Types.PkgconfigVersionRange | 
| Pretty PkgconfigName Source # |  | 
| Instance detailsDefined in Distribution.Types.PkgconfigName | 
| Pretty PkgconfigDependency Source # |  | 
| Instance detailsDefined in Distribution.Types.PkgconfigDependency | 
| Pretty PackageName Source # |  | 
| Instance detailsDefined in Distribution.Types.PackageName | 
| Pretty UnqualComponentName Source # |  | 
| Instance detailsDefined in Distribution.Types.UnqualComponentName | 
| Pretty LibraryVisibility Source # |  | 
| Instance detailsDefined in Distribution.Types.LibraryVisibility | 
| Pretty MungedPackageName Source # | 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 packagefoo.  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 detailsDefined in Distribution.Types.MungedPackageName | 
| Pretty ForeignLibType Source # |  | 
| Instance detailsDefined in Distribution.Types.ForeignLibType | 
| Pretty ForeignLibOption Source # |  | 
| Instance detailsDefined in Distribution.Types.ForeignLibOption | 
| Pretty FlagAssignment Source # | Since: 3.4.0.0 | 
| Instance detailsDefined in Distribution.Types.Flag | 
| Pretty FlagName Source # |  | 
| Instance detailsDefined in Distribution.Types.Flag | 
| Pretty ExecutableScope Source # |  | 
| Instance detailsDefined in Distribution.Types.ExecutableScope | 
| Pretty ComponentName Source # |  | 
| Instance detailsDefined in Distribution.Types.ComponentName | 
| Pretty ComponentId Source # |  | 
| Instance detailsDefined in Distribution.Types.ComponentId | 
| Pretty BuildType Source # |  | 
| Instance detailsDefined in Distribution.Types.BuildType | 
| Pretty AbiHash Source # |  | 
| Instance detailsDefined in Distribution.Types.AbiHash | 
| Pretty Platform Source # |  | 
| Instance detailsDefined in Distribution.System | 
| Pretty Arch Source # |  | 
| Instance detailsDefined in Distribution.System | 
| Pretty OS Source # |  | 
| Instance detailsDefined in Distribution.System | 
| Pretty LicenseRef Source # |  | 
| Instance detailsDefined in Distribution.SPDX.LicenseReference | 
| Pretty LicenseId Source # |  | 
| Instance detailsDefined in Distribution.SPDX.LicenseId | 
| Pretty LicenseExceptionId Source # |  | 
| Instance detailsDefined in Distribution.SPDX.LicenseExceptionId | 
| Pretty SimpleLicenseExpression Source # |  | 
| Instance detailsDefined in Distribution.SPDX.LicenseExpression | 
| Pretty LicenseExpression Source # |  | 
| Instance detailsDefined in Distribution.SPDX.LicenseExpression | 
| Pretty License Source # |  | 
| Instance detailsDefined in Distribution.SPDX.License | 
| Pretty ModuleName Source # |  | 
| Instance detailsDefined in Distribution.ModuleName | 
| Pretty ModuleRenaming Source # |  | 
| Instance detailsDefined in Distribution.Types.ModuleRenaming | 
| Pretty IncludeRenaming Source # |  | 
| Instance detailsDefined in Distribution.Types.IncludeRenaming | 
| Pretty Mixin Source # |  | 
| Instance detailsDefined in Distribution.Types.Mixin | 
| Pretty ModuleReexport Source # |  | 
| Instance detailsDefined in Distribution.Types.ModuleReexport | 
| Pretty Verbosity Source # |  | 
| Instance detailsDefined in Distribution.Verbosity | 
| Pretty TestType Source # |  | 
| Instance detailsDefined in Distribution.Types.TestType | 
| Pretty PackageIdentifier Source # |  | 
| Instance detailsDefined in Distribution.Types.PackageId | 
| Pretty DefUnitId Source # |  | 
| Instance detailsDefined in Distribution.Types.UnitId | 
| Pretty UnitId Source # | The textual format for UnitIdcoincides with the format
 GHC accepts for-package-id. | 
| Instance detailsDefined in Distribution.Types.UnitId | 
| Pretty Module Source # |  | 
| Instance detailsDefined in Distribution.Types.Module | 
| Pretty OpenModule Source # |  | 
| Instance detailsDefined in Distribution.Backpack | 
| Pretty OpenUnitId Source # |  | 
| Instance detailsDefined in Distribution.Backpack | 
| Pretty ExposedModule Source # |  | 
| Instance detailsDefined in Distribution.Types.ExposedModule | 
| Pretty PackageVersionConstraint Source # |  | 
| Instance detailsDefined in Distribution.Types.PackageVersionConstraint | 
| Pretty MungedPackageId Source # | >>> 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 detailsDefined in Distribution.Types.MungedPackageId | 
| Pretty LegacyExeDependency Source # |  | 
| Instance detailsDefined in Distribution.Types.LegacyExeDependency | 
| Pretty ExeDependency Source # |  | 
| Instance detailsDefined in Distribution.Types.ExeDependency | 
| Pretty Dependency Source # | >>> 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 detailsDefined in Distribution.Types.Dependency | 
| Pretty BenchmarkType Source # |  | 
| Instance detailsDefined in Distribution.Types.BenchmarkType | 
| Pretty AbiDependency Source # |  | 
| Instance detailsDefined in Distribution.Types.AbiDependency | 
| Pretty License Source # |  | 
| Instance detailsDefined in Distribution.License | 
| Pretty KnownExtension Source # |  | 
| Instance detailsDefined in Language.Haskell.Extension | 
| Pretty Extension Source # |  | 
| Instance detailsDefined in Language.Haskell.Extension | 
| Pretty Language Source # |  | 
| Instance detailsDefined in Language.Haskell.Extension | 
| Pretty AbiTag Source # |  | 
| Instance detailsDefined in Distribution.Compiler | 
| Pretty CompilerId Source # |  | 
| Instance detailsDefined in Distribution.Compiler | 
| Pretty CompilerFlavor Source # |  | 
| Instance detailsDefined in Distribution.Compiler | 
| Pretty LibVersionInfo Source # |  | 
| Instance detailsDefined in Distribution.Types.ForeignLib | 
| Pretty TestedWith Source # |  | 
| Instance detailsDefined in Distribution.FieldGrammar.Newtypes | 
| Pretty SpecLicense Source # |  | 
| Instance detailsDefined in Distribution.FieldGrammar.Newtypes | 
| Pretty SpecVersion Source # |  | 
| Instance detailsDefined in Distribution.FieldGrammar.Newtypes | 
| Pretty FilePathNT Source # |  | 
| Instance detailsDefined in Distribution.FieldGrammar.Newtypes | 
| Pretty Token' Source # |  | 
| Instance detailsDefined in Distribution.FieldGrammar.Newtypes | 
| Pretty Token Source # |  | 
| Instance detailsDefined in Distribution.FieldGrammar.Newtypes | 
| Pretty TestShowDetails Source # |  | 
| Instance detailsDefined in Distribution.Simple.Setup | 
| Pretty HaddockTarget Source # |  | 
| Instance detailsDefined in Distribution.Simple.Setup | 
| FieldGrammar Pretty PrettyFieldGrammar Source # |  | 
| Instance detailsDefined in Distribution.FieldGrammar.Pretty | 
| Pretty a => Pretty (Identity a) Source # |  | 
| Instance detailsDefined in Distribution.Pretty | 
| Pretty a => Pretty (MQuoted a) Source # |  | 
| Instance detailsDefined in Distribution.FieldGrammar.Newtypes | 
| Pretty (SymbolicPath from to) Source # |  | 
| Instance detailsDefined in Distribution.Utils.Path | 
| (Newtype a b, Sep sep, Pretty b) => Pretty (NonEmpty' sep b a) Source # |  | 
| Instance detailsDefined in Distribution.FieldGrammar.Newtypes | 
| (Newtype a b, Sep sep, Pretty b) => Pretty (Set' sep b a) Source # |  | 
| Instance detailsDefined in Distribution.FieldGrammar.Newtypes | 
| (Newtype a b, Sep sep, Pretty b) => Pretty (List sep b a) Source # |  | 
| Instance detailsDefined in Distribution.FieldGrammar.Newtypes |