| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Distribution.Pretty
Contents
Synopsis
- class Pretty a where
- pretty :: a -> Doc
- prettyVersioned :: CabalSpecVersion -> a -> Doc
- prettyShow :: Pretty a => a -> String
- defaultStyle :: Style
- flatStyle :: Style
- showFilePath :: FilePath -> Doc
- showToken :: String -> Doc
- showTokenStr :: String -> String
- showFreeText :: String -> Doc
- showFreeTextV3 :: String -> Doc
- commaSpaceSep :: Pretty a => [a] -> Doc
- commaSep :: Pretty a => [a] -> Doc
- type Separator = [Doc] -> Doc
Documentation
Minimal complete definition
Instances
Instances details
Instance details
Defined in Distribution.Backpack
Methods
pretty :: OpenModule -> Doc Source #
prettyVersioned :: CabalSpecVersion -> OpenModule -> Doc Source #
Instance details
Defined in Distribution.Backpack
Methods
pretty :: OpenUnitId -> Doc Source #
prettyVersioned :: CabalSpecVersion -> OpenUnitId -> Doc Source #
Instance details
Defined in Distribution.Compiler
Instance details
Defined in Distribution.Compiler
Methods
pretty :: CompilerFlavor -> Doc Source #
prettyVersioned :: CabalSpecVersion -> CompilerFlavor -> Doc Source #
Instance details
Defined in Distribution.Compiler
Methods
pretty :: CompilerId -> Doc Source #
prettyVersioned :: CabalSpecVersion -> CompilerId -> Doc Source #
Instance details
Defined in Distribution.FieldGrammar.Newtypes
Methods
pretty :: FilePathNT -> Doc Source #
prettyVersioned :: CabalSpecVersion -> FilePathNT -> Doc Source #
Instance details
Defined in Distribution.FieldGrammar.Newtypes
Methods
pretty :: SpecLicense -> Doc Source #
prettyVersioned :: CabalSpecVersion -> SpecLicense -> Doc Source #
Instance details
Defined in Distribution.FieldGrammar.Newtypes
Methods
pretty :: SpecVersion -> Doc Source #
prettyVersioned :: CabalSpecVersion -> SpecVersion -> Doc Source #
Instance details
Defined in Distribution.FieldGrammar.Newtypes
Methods
pretty :: TestedWith -> Doc Source #
prettyVersioned :: CabalSpecVersion -> TestedWith -> Doc Source #
Instance details
Defined in Distribution.FieldGrammar.Newtypes
Instance details
Defined in Distribution.FieldGrammar.Newtypes
Instance details
Defined in Distribution.License
Instance details
Defined in Distribution.ModuleName
Methods
pretty :: ModuleName -> Doc Source #
prettyVersioned :: CabalSpecVersion -> ModuleName -> Doc Source #
Instance details
Defined in Distribution.PackageDescription.FieldGrammar
Methods
pretty :: CompatDataDir -> Doc Source #
prettyVersioned :: CabalSpecVersion -> CompatDataDir -> Doc Source #
Instance details
Defined in Distribution.PackageDescription.FieldGrammar
Methods
pretty :: CompatLicenseFile -> Doc Source #
prettyVersioned :: CabalSpecVersion -> CompatLicenseFile -> Doc Source #
Instance details
Defined in Distribution.SPDX.License
Instance details
Defined in Distribution.SPDX.LicenseExceptionId
Methods
pretty :: LicenseExceptionId -> Doc Source #
prettyVersioned :: CabalSpecVersion -> LicenseExceptionId -> Doc Source #
Instance details
Defined in Distribution.SPDX.LicenseExpression
Methods
pretty :: LicenseExpression -> Doc Source #
prettyVersioned :: CabalSpecVersion -> LicenseExpression -> Doc Source #
Instance details
Defined in Distribution.SPDX.LicenseExpression
Methods
pretty :: SimpleLicenseExpression -> Doc Source #
prettyVersioned :: CabalSpecVersion -> SimpleLicenseExpression -> Doc Source #
Instance details
Defined in Distribution.SPDX.LicenseId
Instance details
Defined in Distribution.SPDX.LicenseReference
Methods
pretty :: LicenseRef -> Doc Source #
prettyVersioned :: CabalSpecVersion -> LicenseRef -> Doc Source #
Instance details
Defined in Distribution.System
Instance details
Defined in Distribution.System
Instance details
Defined in Distribution.System
Instance details
Defined in Distribution.Types.AbiDependency
Methods
pretty :: AbiDependency -> Doc Source #
prettyVersioned :: CabalSpecVersion -> AbiDependency -> Doc Source #
Instance details
Defined in Distribution.Types.AbiHash
Instance details
Defined in Distribution.Types.BenchmarkType
Methods
pretty :: BenchmarkType -> Doc Source #
prettyVersioned :: CabalSpecVersion -> BenchmarkType -> Doc Source #
Instance details
Defined in Distribution.Types.BuildType
Instance details
Defined in Distribution.Types.ComponentId
Methods
pretty :: ComponentId -> Doc Source #
prettyVersioned :: CabalSpecVersion -> ComponentId -> Doc Source #
Instance details
Defined in Distribution.Types.ComponentName
Methods
pretty :: ComponentName -> Doc Source #
prettyVersioned :: CabalSpecVersion -> ComponentName -> Doc Source #
>>>prettyShow $ Dependency (mkPackageName "pkg") anyVersion mainLibSet"pkg"
>>>prettyShow $ Dependency (mkPackageName "pkg") anyVersion $ NES.insert (LSubLibName $ mkUnqualComponentName "sublib") mainLibSet"pkg:{pkg,sublib}"
>>>prettyShow $ Dependency (mkPackageName "pkg") anyVersion $ NES.singleton (LSubLibName $ mkUnqualComponentName "sublib")"pkg:sublib"
>>>prettyShow $ Dependency (mkPackageName "pkg") anyVersion $ NES.insert (LSubLibName $ mkUnqualComponentName "sublib-b") $ NES.singleton (LSubLibName $ mkUnqualComponentName "sublib-a")"pkg:{sublib-a,sublib-b}"
Instance details
Defined in Distribution.Types.Dependency
Methods
pretty :: Dependency -> Doc Source #
prettyVersioned :: CabalSpecVersion -> Dependency -> Doc Source #
Instance details
Defined in Distribution.Types.ExeDependency
Methods
pretty :: ExeDependency -> Doc Source #
prettyVersioned :: CabalSpecVersion -> ExeDependency -> Doc Source #
Instance details
Defined in Distribution.Types.ExecutableScope
Methods
pretty :: ExecutableScope -> Doc Source #
prettyVersioned :: CabalSpecVersion -> ExecutableScope -> Doc Source #
Instance details
Defined in Distribution.Types.ExposedModule
Methods
pretty :: ExposedModule -> Doc Source #
prettyVersioned :: CabalSpecVersion -> ExposedModule -> Doc Source #
Instance details
Defined in Distribution.Types.Flag
Methods
pretty :: FlagAssignment -> Doc Source #
prettyVersioned :: CabalSpecVersion -> FlagAssignment -> Doc Source #
Instance details
Defined in Distribution.Types.Flag
Instance details
Defined in Distribution.Types.ForeignLib
Methods
pretty :: LibVersionInfo -> Doc Source #
prettyVersioned :: CabalSpecVersion -> LibVersionInfo -> Doc Source #
Instance details
Defined in Distribution.Types.ForeignLibOption
Methods
pretty :: ForeignLibOption -> Doc Source #
prettyVersioned :: CabalSpecVersion -> ForeignLibOption -> Doc Source #
Instance details
Defined in Distribution.Types.ForeignLibType
Methods
pretty :: ForeignLibType -> Doc Source #
prettyVersioned :: CabalSpecVersion -> ForeignLibType -> Doc Source #
Instance details
Defined in Distribution.Types.IncludeRenaming
Methods
pretty :: IncludeRenaming -> Doc Source #
prettyVersioned :: CabalSpecVersion -> IncludeRenaming -> Doc Source #
Instance details
Defined in Distribution.Types.LegacyExeDependency
Methods
pretty :: LegacyExeDependency -> Doc Source #
prettyVersioned :: CabalSpecVersion -> LegacyExeDependency -> Doc Source #
Instance details
Defined in Distribution.Types.LibraryVisibility
Methods
pretty :: LibraryVisibility -> Doc Source #
prettyVersioned :: CabalSpecVersion -> LibraryVisibility -> Doc Source #
Instance details
Defined in Distribution.Types.MissingDependency
Methods
pretty :: MissingDependency -> Doc Source #
prettyVersioned :: CabalSpecVersion -> MissingDependency -> Doc Source #
Instance details
Defined in Distribution.Types.Mixin
Instance details
Defined in Distribution.Types.Module
Instance details
Defined in Distribution.Types.ModuleReexport
Methods
pretty :: ModuleReexport -> Doc Source #
prettyVersioned :: CabalSpecVersion -> ModuleReexport -> Doc Source #
Instance details
Defined in Distribution.Types.ModuleRenaming
Methods
pretty :: ModuleRenaming -> Doc Source #
prettyVersioned :: CabalSpecVersion -> ModuleRenaming -> Doc 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 details
Defined in Distribution.Types.MungedPackageId
Methods
pretty :: MungedPackageId -> Doc Source #
prettyVersioned :: CabalSpecVersion -> MungedPackageId -> Doc 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 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
Methods
pretty :: MungedPackageName -> Doc Source #
prettyVersioned :: CabalSpecVersion -> MungedPackageName -> Doc Source #
Instance details
Defined in Distribution.Types.PackageId
Methods
pretty :: PackageIdentifier -> Doc Source #
prettyVersioned :: CabalSpecVersion -> PackageIdentifier -> Doc Source #
Instance details
Defined in Distribution.Types.PackageName
Methods
pretty :: PackageName -> Doc Source #
prettyVersioned :: CabalSpecVersion -> PackageName -> Doc Source #
Instance details
Defined in Distribution.Types.PackageVersionConstraint
Methods
pretty :: PackageVersionConstraint -> Doc Source #
prettyVersioned :: CabalSpecVersion -> PackageVersionConstraint -> Doc Source #
Instance details
Defined in Distribution.Types.PkgconfigDependency
Methods
pretty :: PkgconfigDependency -> Doc Source #
prettyVersioned :: CabalSpecVersion -> PkgconfigDependency -> Doc Source #
Instance details
Defined in Distribution.Types.PkgconfigName
Methods
pretty :: PkgconfigName -> Doc Source #
prettyVersioned :: CabalSpecVersion -> PkgconfigName -> Doc Source #
Instance details
Defined in Distribution.Types.PkgconfigVersion
Methods
pretty :: PkgconfigVersion -> Doc Source #
prettyVersioned :: CabalSpecVersion -> PkgconfigVersion -> Doc Source #
Instance details
Defined in Distribution.Types.PkgconfigVersionRange
Methods
pretty :: PkgconfigVersionRange -> Doc Source #
prettyVersioned :: CabalSpecVersion -> PkgconfigVersionRange -> Doc Source #
Instance details
Defined in Distribution.Types.SourceRepo
Methods
pretty :: KnownRepoType -> Doc Source #
prettyVersioned :: CabalSpecVersion -> KnownRepoType -> Doc Source #
Instance details
Defined in Distribution.Types.SourceRepo
Instance details
Defined in Distribution.Types.SourceRepo
Instance details
Defined in Distribution.Types.TestType
Instance details
Defined in Distribution.Types.UnitId
The textual format for UnitId coincides with the format
GHC accepts for -package-id.
Instance details
Defined in Distribution.Types.UnitId
Instance details
Defined in Distribution.Types.UnqualComponentName
Methods
pretty :: UnqualComponentName -> Doc Source #
prettyVersioned :: CabalSpecVersion -> UnqualComponentName -> Doc Source #
Instance details
Defined in Distribution.Types.Version
>>>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
Methods
pretty :: VersionRange -> Doc Source #
prettyVersioned :: CabalSpecVersion -> VersionRange -> Doc Source #
Instance details
Defined in Language.Haskell.Extension
Instance details
Defined in Language.Haskell.Extension
Methods
pretty :: KnownExtension -> Doc Source #
prettyVersioned :: CabalSpecVersion -> KnownExtension -> Doc Source #
Instance details
Defined in Language.Haskell.Extension
Instance details
Defined in Distribution.Pretty
Instance details
Defined in Distribution.Pretty
Instance details
Defined in Distribution.Pretty
Instance details
Defined in Distribution.FieldGrammar.Newtypes
Instance details
Defined in Distribution.Pretty
Instance details
Defined in Distribution.FieldGrammar.Newtypes
Methods
pretty :: RelativePathNT from to -> Doc Source #
prettyVersioned :: CabalSpecVersion -> RelativePathNT from to -> Doc Source #
Instance details
Defined in Distribution.FieldGrammar.Newtypes
Methods
pretty :: SymbolicPathNT from to -> Doc Source #
prettyVersioned :: CabalSpecVersion -> SymbolicPathNT from to -> Doc Source #
Instance details
Defined in Distribution.FieldGrammar.Newtypes
Instance details
Defined in Distribution.FieldGrammar.Newtypes
Instance details
Defined in Distribution.FieldGrammar.Newtypes
Instance details
Defined in Distribution.Utils.Path
Methods
pretty :: SymbolicPathX allowAbsolute from to -> Doc Source #
prettyVersioned :: CabalSpecVersion -> SymbolicPathX allowAbsolute from to -> Doc Source #
prettyShow :: Pretty a => a -> String 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.
Utilities
showFilePath :: FilePath -> Doc Source #
showTokenStr :: String -> String Source #
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: 3.0.0.0
commaSpaceSep :: Pretty a => [a] -> Doc Source #
Separate a list of documents by commas and spaces.