Skip to content
Snippets Groups Projects
Commit e6647bd3 authored by Ian D. Bollinger's avatar Ian D. Bollinger
Browse files

Fix #1788

- Remove redundant space after `description:` field name.
- Eliminate trailing spaces on *some* blank lines.
- Convert all field names to lower case.
- Eliminate redundant `buildable: True` and `exposed: True` fields.
- Fix Haddock module comment.
parent 320af25e
No related branches found
No related tags found
No related merge requests found
-----------------------------------------------------------------------------
--
-- |
-- Module : Distribution.PackageDescription.PrettyPrint
-- Copyright : Jürgen Nicklisch-Franken 2010
-- License : BSD3
......@@ -8,7 +8,7 @@
-- Stability : provisional
-- Portability : portable
--
-- | Pretty printing for cabal files
-- Pretty printing for cabal files
--
-----------------------------------------------------------------------------
......@@ -74,6 +74,12 @@ ppSourceRepo repo =
where
sourceRepoFieldDescrs' = [fd | fd <- sourceRepoFieldDescrs, fieldName fd /= "kind"]
ppFieldsFiltered :: [String] -> [FieldDescr a] -> a -> Doc
ppFieldsFiltered removable fields x = ppFields (filter nondefault fields) x
where
nondefault (FieldDescr name getter _) =
name `notElem` removable || render (getter x) /= "True"
ppDiffFields :: [FieldDescr a] -> a -> a -> Doc
ppDiffFields fields x y =
vcat [ ppField name (getter x)
......@@ -95,16 +101,16 @@ ppFlag (MkFlag name desc dflt manual) =
emptyLine $ text "flag" <+> ppFlagName name $+$
(nest indentWith ((if null desc
then empty
else text "Description: " <+> showFreeText desc) $+$
(if dflt then empty else text "Default: False") $+$
(if manual then text "Manual: True" else empty)))
else text "description:" <+> showFreeText desc) $+$
(if dflt then empty else text "default: False") $+$
(if manual then text "manual: True" else empty)))
ppLibrary :: (Maybe (CondTree ConfVar [Dependency] Library)) -> Doc
ppLibrary Nothing = empty
ppLibrary (Just condTree) =
emptyLine $ text "library" $+$ nest indentWith (ppCondTree condTree Nothing ppLib)
where
ppLib lib Nothing = ppFields libFieldDescrs lib
ppLib lib Nothing = ppFieldsFiltered ["buildable", "exposed"] libFieldDescrs lib
$$ ppCustomFields (customFieldsBI (libBuildInfo lib))
ppLib lib (Just plib) = ppDiffFields libFieldDescrs lib plib
$$ ppCustomFields (customFieldsBI (libBuildInfo lib))
......@@ -116,7 +122,7 @@ ppExecutables exes =
where
ppExe (Executable _ modulePath' buildInfo') Nothing =
(if modulePath' == "" then empty else text "main-is:" <+> text modulePath')
$+$ ppFields binfoFieldDescrs buildInfo'
$+$ ppFieldsFiltered ["buildable"] binfoFieldDescrs buildInfo'
$+$ ppCustomFields (customFieldsBI buildInfo')
ppExe (Executable _ modulePath' buildInfo')
(Just (Executable _ modulePath2 buildInfo2)) =
......@@ -138,7 +144,7 @@ ppTestSuites suites =
(testSuiteMainIs testsuite)
$+$ maybe empty (\m -> text "test-module:" <+> disp m)
(testSuiteModule testsuite)
$+$ ppFields binfoFieldDescrs (testBuildInfo testsuite)
$+$ ppFieldsFiltered ["buildable"] binfoFieldDescrs (testBuildInfo testsuite)
$+$ ppCustomFields (customFieldsBI (testBuildInfo testsuite))
where
maybeTestType | testInterface testsuite == mempty = Nothing
......@@ -168,7 +174,7 @@ ppBenchmarks suites =
maybeBenchmarkType
$+$ maybe empty (\f -> text "main-is:" <+> text f)
(benchmarkMainIs benchmark)
$+$ ppFields binfoFieldDescrs (benchmarkBuildInfo benchmark)
$+$ ppFieldsFiltered ["buildable"] binfoFieldDescrs (benchmarkBuildInfo benchmark)
$+$ ppCustomFields (customFieldsBI (benchmarkBuildInfo benchmark))
where
maybeBenchmarkType | benchmarkInterface benchmark == mempty = Nothing
......@@ -209,6 +215,7 @@ ppCondTree ct@(CondNode it deps ifs) mbIt ppIt =
then ppCondTree ct Nothing ppIt
else res
where
-- TODO: this ends up printing trailing spaces when combined with nest.
ppIf (c,thenTree,mElseTree) =
((emptyLine $ text "if" <+> ppCondition c) $$
nest indentWith (ppCondTree thenTree
......@@ -225,7 +232,7 @@ ppDeps deps =
text "build-depends:" $+$ nest indentWith (vcat (punctuate comma (map disp deps)))
emptyLine :: Doc -> Doc
emptyLine d = text " " $+$ d
emptyLine d = text "" $+$ d
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment