{-# LANGUAGE OverloadedStrings #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  Distribution.PackageDescription.PrettyPrint
-- Copyright   :  Jürgen Nicklisch-Franken 2010
-- License     :  BSD3
--
-- Maintainer  : cabal-devel@haskell.org
-- Stability   : provisional
-- Portability : portable
--
-- Pretty printing for cabal files
--
-----------------------------------------------------------------------------

module Distribution.PackageDescription.PrettyPrint (
    -- * Generic package descriptions
    writeGenericPackageDescription,
    showGenericPackageDescription,
    ppGenericPackageDescription,

    -- * Package descriptions
     writePackageDescription,
     showPackageDescription,

     -- ** Supplementary build information
     writeHookedBuildInfo,
     showHookedBuildInfo,
) where

import Distribution.Compat.Prelude
import Prelude ()

import Distribution.Types.CondTree
import Distribution.Types.Dependency
import Distribution.Types.ForeignLib          (ForeignLib (foreignLibName))
import Distribution.Types.LibraryName
import Distribution.Types.UnqualComponentName

import Distribution.CabalSpecVersion
import Distribution.Fields.Pretty
import Distribution.PackageDescription
import Distribution.Pretty
import Distribution.Simple.Utils
import Distribution.Types.Version (versionNumbers)

import Distribution.FieldGrammar                    (PrettyFieldGrammar', prettyFieldGrammar)
import Distribution.PackageDescription.FieldGrammar
       (benchmarkFieldGrammar, buildInfoFieldGrammar, executableFieldGrammar, flagFieldGrammar,
       foreignLibFieldGrammar, libraryFieldGrammar, packageDescriptionFieldGrammar,
       setupBInfoFieldGrammar, sourceRepoFieldGrammar, testSuiteFieldGrammar)

import qualified Distribution.PackageDescription.FieldGrammar as FG

import Text.PrettyPrint (Doc, char, hsep, parens, text, (<+>))

import qualified Data.ByteString.Lazy.Char8 as BS.Char8

-- | Writes a .cabal file from a generic package description
writeGenericPackageDescription :: FilePath -> GenericPackageDescription -> NoCallStackIO ()
writeGenericPackageDescription :: FilePath -> GenericPackageDescription -> NoCallStackIO ()
writeGenericPackageDescription FilePath
fpath GenericPackageDescription
pkg = FilePath -> FilePath -> NoCallStackIO ()
writeUTF8File FilePath
fpath (GenericPackageDescription -> FilePath
showGenericPackageDescription GenericPackageDescription
pkg)

-- | Writes a generic package description to a string
showGenericPackageDescription :: GenericPackageDescription -> String
showGenericPackageDescription :: GenericPackageDescription -> FilePath
showGenericPackageDescription GenericPackageDescription
gpd = (() -> [FilePath]) -> [PrettyField ()] -> FilePath
forall ann. (ann -> [FilePath]) -> [PrettyField ann] -> FilePath
showFields ([FilePath] -> () -> [FilePath]
forall a b. a -> b -> a
const []) ([PrettyField ()] -> FilePath) -> [PrettyField ()] -> FilePath
forall a b. (a -> b) -> a -> b
$ CabalSpecVersion -> GenericPackageDescription -> [PrettyField ()]
ppGenericPackageDescription CabalSpecVersion
v GenericPackageDescription
gpd
  where
    v :: CabalSpecVersion
v = [Int] -> CabalSpecVersion
cabalSpecFromVersionDigits
      ([Int] -> CabalSpecVersion) -> [Int] -> CabalSpecVersion
forall a b. (a -> b) -> a -> b
$ Version -> [Int]
versionNumbers
      (Version -> [Int]) -> Version -> [Int]
forall a b. (a -> b) -> a -> b
$ PackageDescription -> Version
specVersion
      (PackageDescription -> Version) -> PackageDescription -> Version
forall a b. (a -> b) -> a -> b
$ GenericPackageDescription -> PackageDescription
packageDescription GenericPackageDescription
gpd

-- | Convert a generic package description to 'PrettyField's.
ppGenericPackageDescription :: CabalSpecVersion -> GenericPackageDescription -> [PrettyField ()]
ppGenericPackageDescription :: CabalSpecVersion -> GenericPackageDescription -> [PrettyField ()]
ppGenericPackageDescription CabalSpecVersion
v GenericPackageDescription
gpd = [[PrettyField ()]] -> [PrettyField ()]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
    [ CabalSpecVersion -> PackageDescription -> [PrettyField ()]
ppPackageDescription CabalSpecVersion
v (GenericPackageDescription -> PackageDescription
packageDescription GenericPackageDescription
gpd)
    , CabalSpecVersion -> Maybe SetupBuildInfo -> [PrettyField ()]
ppSetupBInfo CabalSpecVersion
v (PackageDescription -> Maybe SetupBuildInfo
setupBuildInfo (GenericPackageDescription -> PackageDescription
packageDescription GenericPackageDescription
gpd))
    , CabalSpecVersion -> [Flag] -> [PrettyField ()]
ppGenPackageFlags CabalSpecVersion
v (GenericPackageDescription -> [Flag]
genPackageFlags GenericPackageDescription
gpd)
    , CabalSpecVersion
-> Maybe (CondTree ConfVar [Dependency] Library)
-> [PrettyField ()]
ppCondLibrary CabalSpecVersion
v (GenericPackageDescription
-> Maybe (CondTree ConfVar [Dependency] Library)
condLibrary GenericPackageDescription
gpd)
    , CabalSpecVersion
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
-> [PrettyField ()]
ppCondSubLibraries CabalSpecVersion
v (GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
condSubLibraries GenericPackageDescription
gpd)
    , CabalSpecVersion
-> [(UnqualComponentName,
     CondTree ConfVar [Dependency] ForeignLib)]
-> [PrettyField ()]
ppCondForeignLibs CabalSpecVersion
v (GenericPackageDescription
-> [(UnqualComponentName,
     CondTree ConfVar [Dependency] ForeignLib)]
condForeignLibs GenericPackageDescription
gpd)
    , CabalSpecVersion
-> [(UnqualComponentName,
     CondTree ConfVar [Dependency] Executable)]
-> [PrettyField ()]
ppCondExecutables CabalSpecVersion
v (GenericPackageDescription
-> [(UnqualComponentName,
     CondTree ConfVar [Dependency] Executable)]
condExecutables GenericPackageDescription
gpd)
    , CabalSpecVersion
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> [PrettyField ()]
ppCondTestSuites CabalSpecVersion
v (GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
condTestSuites GenericPackageDescription
gpd)
    , CabalSpecVersion
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> [PrettyField ()]
ppCondBenchmarks CabalSpecVersion
v (GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
condBenchmarks GenericPackageDescription
gpd)
    ]

ppPackageDescription :: CabalSpecVersion -> PackageDescription -> [PrettyField ()]
ppPackageDescription :: CabalSpecVersion -> PackageDescription -> [PrettyField ()]
ppPackageDescription CabalSpecVersion
v PackageDescription
pd =
    CabalSpecVersion
-> PrettyFieldGrammar PackageDescription PackageDescription
-> PackageDescription
-> [PrettyField ()]
forall s a.
CabalSpecVersion -> PrettyFieldGrammar s a -> s -> [PrettyField ()]
prettyFieldGrammar CabalSpecVersion
v PrettyFieldGrammar PackageDescription PackageDescription
forall (g :: * -> * -> *).
(FieldGrammar g, Applicative (g PackageDescription),
 Applicative (g PackageIdentifier)) =>
g PackageDescription PackageDescription
packageDescriptionFieldGrammar PackageDescription
pd
    [PrettyField ()] -> [PrettyField ()] -> [PrettyField ()]
forall a. [a] -> [a] -> [a]
++ CabalSpecVersion -> [SourceRepo] -> [PrettyField ()]
ppSourceRepos CabalSpecVersion
v (PackageDescription -> [SourceRepo]
sourceRepos PackageDescription
pd)

ppSourceRepos :: CabalSpecVersion -> [SourceRepo] -> [PrettyField ()]
ppSourceRepos :: CabalSpecVersion -> [SourceRepo] -> [PrettyField ()]
ppSourceRepos = (SourceRepo -> PrettyField ()) -> [SourceRepo] -> [PrettyField ()]
forall a b. (a -> b) -> [a] -> [b]
map ((SourceRepo -> PrettyField ())
 -> [SourceRepo] -> [PrettyField ()])
-> (CabalSpecVersion -> SourceRepo -> PrettyField ())
-> CabalSpecVersion
-> [SourceRepo]
-> [PrettyField ()]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CabalSpecVersion -> SourceRepo -> PrettyField ()
ppSourceRepo

ppSourceRepo :: CabalSpecVersion -> SourceRepo -> PrettyField ()
ppSourceRepo :: CabalSpecVersion -> SourceRepo -> PrettyField ()
ppSourceRepo CabalSpecVersion
v SourceRepo
repo = () -> FieldName -> [Doc] -> [PrettyField ()] -> PrettyField ()
forall ann.
ann -> FieldName -> [Doc] -> [PrettyField ann] -> PrettyField ann
PrettySection () FieldName
"source-repository" [RepoKind -> Doc
forall a. Pretty a => a -> Doc
pretty RepoKind
kind] ([PrettyField ()] -> PrettyField ())
-> [PrettyField ()] -> PrettyField ()
forall a b. (a -> b) -> a -> b
$
    CabalSpecVersion
-> PrettyFieldGrammar SourceRepo SourceRepo
-> SourceRepo
-> [PrettyField ()]
forall s a.
CabalSpecVersion -> PrettyFieldGrammar s a -> s -> [PrettyField ()]
prettyFieldGrammar CabalSpecVersion
v (RepoKind -> PrettyFieldGrammar SourceRepo SourceRepo
forall (g :: * -> * -> *).
(FieldGrammar g, Applicative (g SourceRepo)) =>
RepoKind -> g SourceRepo SourceRepo
sourceRepoFieldGrammar RepoKind
kind) SourceRepo
repo
  where
    kind :: RepoKind
kind = SourceRepo -> RepoKind
repoKind SourceRepo
repo

ppSetupBInfo :: CabalSpecVersion -> Maybe SetupBuildInfo -> [PrettyField ()]
ppSetupBInfo :: CabalSpecVersion -> Maybe SetupBuildInfo -> [PrettyField ()]
ppSetupBInfo CabalSpecVersion
_ Maybe SetupBuildInfo
Nothing = [PrettyField ()]
forall a. Monoid a => a
mempty
ppSetupBInfo CabalSpecVersion
v (Just SetupBuildInfo
sbi)
    | SetupBuildInfo -> Bool
defaultSetupDepends SetupBuildInfo
sbi = [PrettyField ()]
forall a. Monoid a => a
mempty
    | Bool
otherwise = PrettyField () -> [PrettyField ()]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PrettyField () -> [PrettyField ()])
-> PrettyField () -> [PrettyField ()]
forall a b. (a -> b) -> a -> b
$ () -> FieldName -> [Doc] -> [PrettyField ()] -> PrettyField ()
forall ann.
ann -> FieldName -> [Doc] -> [PrettyField ann] -> PrettyField ann
PrettySection () FieldName
"custom-setup" [] ([PrettyField ()] -> PrettyField ())
-> [PrettyField ()] -> PrettyField ()
forall a b. (a -> b) -> a -> b
$
        CabalSpecVersion
-> PrettyFieldGrammar SetupBuildInfo SetupBuildInfo
-> SetupBuildInfo
-> [PrettyField ()]
forall s a.
CabalSpecVersion -> PrettyFieldGrammar s a -> s -> [PrettyField ()]
prettyFieldGrammar CabalSpecVersion
v (Bool -> PrettyFieldGrammar SetupBuildInfo SetupBuildInfo
forall (g :: * -> * -> *).
(FieldGrammar g, Functor (g SetupBuildInfo)) =>
Bool -> g SetupBuildInfo SetupBuildInfo
setupBInfoFieldGrammar Bool
False) SetupBuildInfo
sbi

ppGenPackageFlags :: CabalSpecVersion -> [Flag] -> [PrettyField ()]
ppGenPackageFlags :: CabalSpecVersion -> [Flag] -> [PrettyField ()]
ppGenPackageFlags = (Flag -> PrettyField ()) -> [Flag] -> [PrettyField ()]
forall a b. (a -> b) -> [a] -> [b]
map ((Flag -> PrettyField ()) -> [Flag] -> [PrettyField ()])
-> (CabalSpecVersion -> Flag -> PrettyField ())
-> CabalSpecVersion
-> [Flag]
-> [PrettyField ()]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CabalSpecVersion -> Flag -> PrettyField ()
ppFlag

ppFlag :: CabalSpecVersion -> Flag -> PrettyField ()
ppFlag :: CabalSpecVersion -> Flag -> PrettyField ()
ppFlag CabalSpecVersion
v flag :: Flag
flag@(MkFlag FlagName
name FilePath
_ Bool
_ Bool
_)  = () -> FieldName -> [Doc] -> [PrettyField ()] -> PrettyField ()
forall ann.
ann -> FieldName -> [Doc] -> [PrettyField ann] -> PrettyField ann
PrettySection () FieldName
"flag" [FlagName -> Doc
ppFlagName FlagName
name] ([PrettyField ()] -> PrettyField ())
-> [PrettyField ()] -> PrettyField ()
forall a b. (a -> b) -> a -> b
$
    CabalSpecVersion
-> PrettyFieldGrammar Flag Flag -> Flag -> [PrettyField ()]
forall s a.
CabalSpecVersion -> PrettyFieldGrammar s a -> s -> [PrettyField ()]
prettyFieldGrammar CabalSpecVersion
v (FlagName -> PrettyFieldGrammar Flag Flag
forall (g :: * -> * -> *).
(FieldGrammar g, Applicative (g Flag)) =>
FlagName -> g Flag Flag
flagFieldGrammar FlagName
name) Flag
flag

ppCondTree2 :: CabalSpecVersion -> PrettyFieldGrammar' s -> CondTree ConfVar [Dependency] s -> [PrettyField ()]
ppCondTree2 :: CabalSpecVersion
-> PrettyFieldGrammar' s
-> CondTree ConfVar [Dependency] s
-> [PrettyField ()]
ppCondTree2 CabalSpecVersion
v PrettyFieldGrammar' s
grammar = CondTree ConfVar [Dependency] s -> [PrettyField ()]
forall c. CondTree ConfVar c s -> [PrettyField ()]
go
  where
    -- TODO: recognise elif opportunities
    go :: CondTree ConfVar c s -> [PrettyField ()]
go (CondNode s
it c
_ [CondBranch ConfVar c s]
ifs) =
        CabalSpecVersion -> PrettyFieldGrammar' s -> s -> [PrettyField ()]
forall s a.
CabalSpecVersion -> PrettyFieldGrammar s a -> s -> [PrettyField ()]
prettyFieldGrammar CabalSpecVersion
v PrettyFieldGrammar' s
grammar s
it [PrettyField ()] -> [PrettyField ()] -> [PrettyField ()]
forall a. [a] -> [a] -> [a]
++
        (CondBranch ConfVar c s -> [PrettyField ()])
-> [CondBranch ConfVar c s] -> [PrettyField ()]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap CondBranch ConfVar c s -> [PrettyField ()]
ppIf [CondBranch ConfVar c s]
ifs

    ppIf :: CondBranch ConfVar c s -> [PrettyField ()]
ppIf (CondBranch Condition ConfVar
c CondTree ConfVar c s
thenTree Maybe (CondTree ConfVar c s)
Nothing)
--        | isEmpty thenDoc = mempty
        | Bool
otherwise       = [Condition ConfVar -> [PrettyField ()] -> PrettyField ()
ppIfCondition Condition ConfVar
c [PrettyField ()]
thenDoc]
      where
        thenDoc :: [PrettyField ()]
thenDoc = CondTree ConfVar c s -> [PrettyField ()]
go CondTree ConfVar c s
thenTree

    ppIf (CondBranch Condition ConfVar
c CondTree ConfVar c s
thenTree (Just CondTree ConfVar c s
elseTree)) =
      -- See #6193
      [ Condition ConfVar -> [PrettyField ()] -> PrettyField ()
ppIfCondition Condition ConfVar
c (CondTree ConfVar c s -> [PrettyField ()]
go CondTree ConfVar c s
thenTree)
      , () -> FieldName -> [Doc] -> [PrettyField ()] -> PrettyField ()
forall ann.
ann -> FieldName -> [Doc] -> [PrettyField ann] -> PrettyField ann
PrettySection () FieldName
"else" [] (CondTree ConfVar c s -> [PrettyField ()]
go CondTree ConfVar c s
elseTree)
      ]

ppCondLibrary :: CabalSpecVersion -> Maybe (CondTree ConfVar [Dependency] Library) -> [PrettyField ()]
ppCondLibrary :: CabalSpecVersion
-> Maybe (CondTree ConfVar [Dependency] Library)
-> [PrettyField ()]
ppCondLibrary CabalSpecVersion
_ Maybe (CondTree ConfVar [Dependency] Library)
Nothing = [PrettyField ()]
forall a. Monoid a => a
mempty
ppCondLibrary CabalSpecVersion
v (Just CondTree ConfVar [Dependency] Library
condTree) = PrettyField () -> [PrettyField ()]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PrettyField () -> [PrettyField ()])
-> PrettyField () -> [PrettyField ()]
forall a b. (a -> b) -> a -> b
$ () -> FieldName -> [Doc] -> [PrettyField ()] -> PrettyField ()
forall ann.
ann -> FieldName -> [Doc] -> [PrettyField ann] -> PrettyField ann
PrettySection () FieldName
"library" [] ([PrettyField ()] -> PrettyField ())
-> [PrettyField ()] -> PrettyField ()
forall a b. (a -> b) -> a -> b
$
    CabalSpecVersion
-> PrettyFieldGrammar' Library
-> CondTree ConfVar [Dependency] Library
-> [PrettyField ()]
forall s.
CabalSpecVersion
-> PrettyFieldGrammar' s
-> CondTree ConfVar [Dependency] s
-> [PrettyField ()]
ppCondTree2 CabalSpecVersion
v (LibraryName -> PrettyFieldGrammar' Library
forall (g :: * -> * -> *).
(FieldGrammar g, Applicative (g Library),
 Applicative (g BuildInfo)) =>
LibraryName -> g Library Library
libraryFieldGrammar LibraryName
LMainLibName) CondTree ConfVar [Dependency] Library
condTree

ppCondSubLibraries :: CabalSpecVersion -> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)] -> [PrettyField ()]
ppCondSubLibraries :: CabalSpecVersion
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
-> [PrettyField ()]
ppCondSubLibraries CabalSpecVersion
v [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
libs =
    [ () -> FieldName -> [Doc] -> [PrettyField ()] -> PrettyField ()
forall ann.
ann -> FieldName -> [Doc] -> [PrettyField ann] -> PrettyField ann
PrettySection () FieldName
"library" [UnqualComponentName -> Doc
forall a. Pretty a => a -> Doc
pretty UnqualComponentName
n]
    ([PrettyField ()] -> PrettyField ())
-> [PrettyField ()] -> PrettyField ()
forall a b. (a -> b) -> a -> b
$ CabalSpecVersion
-> PrettyFieldGrammar' Library
-> CondTree ConfVar [Dependency] Library
-> [PrettyField ()]
forall s.
CabalSpecVersion
-> PrettyFieldGrammar' s
-> CondTree ConfVar [Dependency] s
-> [PrettyField ()]
ppCondTree2 CabalSpecVersion
v (LibraryName -> PrettyFieldGrammar' Library
forall (g :: * -> * -> *).
(FieldGrammar g, Applicative (g Library),
 Applicative (g BuildInfo)) =>
LibraryName -> g Library Library
libraryFieldGrammar (LibraryName -> PrettyFieldGrammar' Library)
-> LibraryName -> PrettyFieldGrammar' Library
forall a b. (a -> b) -> a -> b
$ UnqualComponentName -> LibraryName
LSubLibName UnqualComponentName
n) CondTree ConfVar [Dependency] Library
condTree
    | (UnqualComponentName
n, CondTree ConfVar [Dependency] Library
condTree) <- [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
libs
    ]

ppCondForeignLibs :: CabalSpecVersion -> [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)] -> [PrettyField ()]
ppCondForeignLibs :: CabalSpecVersion
-> [(UnqualComponentName,
     CondTree ConfVar [Dependency] ForeignLib)]
-> [PrettyField ()]
ppCondForeignLibs CabalSpecVersion
v [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
flibs =
    [ () -> FieldName -> [Doc] -> [PrettyField ()] -> PrettyField ()
forall ann.
ann -> FieldName -> [Doc] -> [PrettyField ann] -> PrettyField ann
PrettySection () FieldName
"foreign-library" [UnqualComponentName -> Doc
forall a. Pretty a => a -> Doc
pretty UnqualComponentName
n]
    ([PrettyField ()] -> PrettyField ())
-> [PrettyField ()] -> PrettyField ()
forall a b. (a -> b) -> a -> b
$ CabalSpecVersion
-> PrettyFieldGrammar' ForeignLib
-> CondTree ConfVar [Dependency] ForeignLib
-> [PrettyField ()]
forall s.
CabalSpecVersion
-> PrettyFieldGrammar' s
-> CondTree ConfVar [Dependency] s
-> [PrettyField ()]
ppCondTree2 CabalSpecVersion
v (UnqualComponentName -> PrettyFieldGrammar' ForeignLib
forall (g :: * -> * -> *).
(FieldGrammar g, Applicative (g ForeignLib),
 Applicative (g BuildInfo)) =>
UnqualComponentName -> g ForeignLib ForeignLib
foreignLibFieldGrammar UnqualComponentName
n) CondTree ConfVar [Dependency] ForeignLib
condTree
    | (UnqualComponentName
n, CondTree ConfVar [Dependency] ForeignLib
condTree) <- [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
flibs
    ]

ppCondExecutables :: CabalSpecVersion -> [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)] -> [PrettyField ()]
ppCondExecutables :: CabalSpecVersion
-> [(UnqualComponentName,
     CondTree ConfVar [Dependency] Executable)]
-> [PrettyField ()]
ppCondExecutables CabalSpecVersion
v [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
exes =
    [ () -> FieldName -> [Doc] -> [PrettyField ()] -> PrettyField ()
forall ann.
ann -> FieldName -> [Doc] -> [PrettyField ann] -> PrettyField ann
PrettySection () FieldName
"executable" [UnqualComponentName -> Doc
forall a. Pretty a => a -> Doc
pretty UnqualComponentName
n]
    ([PrettyField ()] -> PrettyField ())
-> [PrettyField ()] -> PrettyField ()
forall a b. (a -> b) -> a -> b
$ CabalSpecVersion
-> PrettyFieldGrammar' Executable
-> CondTree ConfVar [Dependency] Executable
-> [PrettyField ()]
forall s.
CabalSpecVersion
-> PrettyFieldGrammar' s
-> CondTree ConfVar [Dependency] s
-> [PrettyField ()]
ppCondTree2 CabalSpecVersion
v (UnqualComponentName -> PrettyFieldGrammar' Executable
forall (g :: * -> * -> *).
(FieldGrammar g, Applicative (g Executable),
 Applicative (g BuildInfo)) =>
UnqualComponentName -> g Executable Executable
executableFieldGrammar UnqualComponentName
n) CondTree ConfVar [Dependency] Executable
condTree
    | (UnqualComponentName
n, CondTree ConfVar [Dependency] Executable
condTree) <- [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
exes
    ]

ppCondTestSuites :: CabalSpecVersion -> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)] -> [PrettyField ()]
ppCondTestSuites :: CabalSpecVersion
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> [PrettyField ()]
ppCondTestSuites CabalSpecVersion
v [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
suites =
    [ () -> FieldName -> [Doc] -> [PrettyField ()] -> PrettyField ()
forall ann.
ann -> FieldName -> [Doc] -> [PrettyField ann] -> PrettyField ann
PrettySection () FieldName
"test-suite" [UnqualComponentName -> Doc
forall a. Pretty a => a -> Doc
pretty UnqualComponentName
n]
    ([PrettyField ()] -> PrettyField ())
-> [PrettyField ()] -> PrettyField ()
forall a b. (a -> b) -> a -> b
$ CabalSpecVersion
-> PrettyFieldGrammar' TestSuiteStanza
-> CondTree ConfVar [Dependency] TestSuiteStanza
-> [PrettyField ()]
forall s.
CabalSpecVersion
-> PrettyFieldGrammar' s
-> CondTree ConfVar [Dependency] s
-> [PrettyField ()]
ppCondTree2 CabalSpecVersion
v PrettyFieldGrammar' TestSuiteStanza
forall (g :: * -> * -> *).
(FieldGrammar g, Applicative (g TestSuiteStanza),
 Applicative (g BuildInfo)) =>
g TestSuiteStanza TestSuiteStanza
testSuiteFieldGrammar ((TestSuite -> TestSuiteStanza)
-> CondTree ConfVar [Dependency] TestSuite
-> CondTree ConfVar [Dependency] TestSuiteStanza
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TestSuite -> TestSuiteStanza
FG.unvalidateTestSuite CondTree ConfVar [Dependency] TestSuite
condTree)
    | (UnqualComponentName
n, CondTree ConfVar [Dependency] TestSuite
condTree) <- [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
suites
    ]

ppCondBenchmarks :: CabalSpecVersion -> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)] -> [PrettyField ()]
ppCondBenchmarks :: CabalSpecVersion
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> [PrettyField ()]
ppCondBenchmarks CabalSpecVersion
v [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
suites =
    [ () -> FieldName -> [Doc] -> [PrettyField ()] -> PrettyField ()
forall ann.
ann -> FieldName -> [Doc] -> [PrettyField ann] -> PrettyField ann
PrettySection () FieldName
"benchmark" [UnqualComponentName -> Doc
forall a. Pretty a => a -> Doc
pretty UnqualComponentName
n]
    ([PrettyField ()] -> PrettyField ())
-> [PrettyField ()] -> PrettyField ()
forall a b. (a -> b) -> a -> b
$ CabalSpecVersion
-> PrettyFieldGrammar' BenchmarkStanza
-> CondTree ConfVar [Dependency] BenchmarkStanza
-> [PrettyField ()]
forall s.
CabalSpecVersion
-> PrettyFieldGrammar' s
-> CondTree ConfVar [Dependency] s
-> [PrettyField ()]
ppCondTree2 CabalSpecVersion
v PrettyFieldGrammar' BenchmarkStanza
forall (g :: * -> * -> *).
(FieldGrammar g, Applicative (g BenchmarkStanza),
 Applicative (g BuildInfo)) =>
g BenchmarkStanza BenchmarkStanza
benchmarkFieldGrammar ((Benchmark -> BenchmarkStanza)
-> CondTree ConfVar [Dependency] Benchmark
-> CondTree ConfVar [Dependency] BenchmarkStanza
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Benchmark -> BenchmarkStanza
FG.unvalidateBenchmark CondTree ConfVar [Dependency] Benchmark
condTree)
    | (UnqualComponentName
n, CondTree ConfVar [Dependency] Benchmark
condTree) <- [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
suites
    ]

ppCondition :: Condition ConfVar -> Doc
ppCondition :: Condition ConfVar -> Doc
ppCondition (Var ConfVar
x)                      = ConfVar -> Doc
ppConfVar ConfVar
x
ppCondition (Lit Bool
b)                      = FilePath -> Doc
text (Bool -> FilePath
forall a. Show a => a -> FilePath
show Bool
b)
ppCondition (CNot Condition ConfVar
c)                     = Char -> Doc
char Char
'!' Doc -> Doc -> Doc
<<>> (Condition ConfVar -> Doc
ppCondition Condition ConfVar
c)
ppCondition (COr Condition ConfVar
c1 Condition ConfVar
c2)                  = Doc -> Doc
parens ([Doc] -> Doc
hsep [Condition ConfVar -> Doc
ppCondition Condition ConfVar
c1, FilePath -> Doc
text FilePath
"||"
                                                         Doc -> Doc -> Doc
<+> Condition ConfVar -> Doc
ppCondition Condition ConfVar
c2])
ppCondition (CAnd Condition ConfVar
c1 Condition ConfVar
c2)                 = Doc -> Doc
parens ([Doc] -> Doc
hsep [Condition ConfVar -> Doc
ppCondition Condition ConfVar
c1, FilePath -> Doc
text FilePath
"&&"
                                                         Doc -> Doc -> Doc
<+> Condition ConfVar -> Doc
ppCondition Condition ConfVar
c2])
ppConfVar :: ConfVar -> Doc
ppConfVar :: ConfVar -> Doc
ppConfVar (OS OS
os)                        = FilePath -> Doc
text FilePath
"os"   Doc -> Doc -> Doc
<<>> Doc -> Doc
parens (OS -> Doc
forall a. Pretty a => a -> Doc
pretty OS
os)
ppConfVar (Arch Arch
arch)                    = FilePath -> Doc
text FilePath
"arch" Doc -> Doc -> Doc
<<>> Doc -> Doc
parens (Arch -> Doc
forall a. Pretty a => a -> Doc
pretty Arch
arch)
ppConfVar (Flag FlagName
name)                    = FilePath -> Doc
text FilePath
"flag" Doc -> Doc -> Doc
<<>> Doc -> Doc
parens (FlagName -> Doc
ppFlagName FlagName
name)
ppConfVar (Impl CompilerFlavor
c VersionRange
v)                     = FilePath -> Doc
text FilePath
"impl" Doc -> Doc -> Doc
<<>> Doc -> Doc
parens (CompilerFlavor -> Doc
forall a. Pretty a => a -> Doc
pretty CompilerFlavor
c Doc -> Doc -> Doc
<+> VersionRange -> Doc
forall a. Pretty a => a -> Doc
pretty VersionRange
v)

ppFlagName :: FlagName -> Doc
ppFlagName :: FlagName -> Doc
ppFlagName                               = FilePath -> Doc
text (FilePath -> Doc) -> (FlagName -> FilePath) -> FlagName -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FlagName -> FilePath
unFlagName

ppIfCondition :: Condition ConfVar -> [PrettyField ()] -> PrettyField ()
ppIfCondition :: Condition ConfVar -> [PrettyField ()] -> PrettyField ()
ppIfCondition Condition ConfVar
c = () -> FieldName -> [Doc] -> [PrettyField ()] -> PrettyField ()
forall ann.
ann -> FieldName -> [Doc] -> [PrettyField ann] -> PrettyField ann
PrettySection () FieldName
"if" [Condition ConfVar -> Doc
ppCondition Condition ConfVar
c]

-- | @since 2.0.0.2
writePackageDescription :: FilePath -> PackageDescription -> NoCallStackIO ()
writePackageDescription :: FilePath -> PackageDescription -> NoCallStackIO ()
writePackageDescription FilePath
fpath PackageDescription
pkg = FilePath -> FilePath -> NoCallStackIO ()
writeUTF8File FilePath
fpath (PackageDescription -> FilePath
showPackageDescription PackageDescription
pkg)

--TODO: make this use section syntax
-- add equivalent for GenericPackageDescription

-- | @since 2.0.0.2
showPackageDescription :: PackageDescription -> String
showPackageDescription :: PackageDescription -> FilePath
showPackageDescription = GenericPackageDescription -> FilePath
showGenericPackageDescription (GenericPackageDescription -> FilePath)
-> (PackageDescription -> GenericPackageDescription)
-> PackageDescription
-> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageDescription -> GenericPackageDescription
pdToGpd

pdToGpd :: PackageDescription -> GenericPackageDescription
pdToGpd :: PackageDescription -> GenericPackageDescription
pdToGpd PackageDescription
pd = GenericPackageDescription :: PackageDescription
-> [Flag]
-> Maybe (CondTree ConfVar [Dependency] Library)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
-> [(UnqualComponentName,
     CondTree ConfVar [Dependency] ForeignLib)]
-> [(UnqualComponentName,
     CondTree ConfVar [Dependency] Executable)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> GenericPackageDescription
GenericPackageDescription
    { packageDescription :: PackageDescription
packageDescription = PackageDescription
pd
    , genPackageFlags :: [Flag]
genPackageFlags    = []
    , condLibrary :: Maybe (CondTree ConfVar [Dependency] Library)
condLibrary        = Library -> CondTree ConfVar [Dependency] Library
forall a v a. a -> CondTree v [a] a
mkCondTree (Library -> CondTree ConfVar [Dependency] Library)
-> Maybe Library -> Maybe (CondTree ConfVar [Dependency] Library)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PackageDescription -> Maybe Library
library PackageDescription
pd
    , condSubLibraries :: [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
condSubLibraries   = Library
-> (UnqualComponentName, CondTree ConfVar [Dependency] Library)
forall v a.
Library -> (UnqualComponentName, CondTree v [a] Library)
mkCondTreeL (Library
 -> (UnqualComponentName, CondTree ConfVar [Dependency] Library))
-> [Library]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PackageDescription -> [Library]
subLibraries PackageDescription
pd
    , condForeignLibs :: [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
condForeignLibs    = (ForeignLib -> UnqualComponentName)
-> ForeignLib
-> (UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)
forall a.
(a -> UnqualComponentName)
-> a -> (UnqualComponentName, CondTree ConfVar [Dependency] a)
mkCondTree' ForeignLib -> UnqualComponentName
foreignLibName (ForeignLib
 -> (UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib))
-> [ForeignLib]
-> [(UnqualComponentName,
     CondTree ConfVar [Dependency] ForeignLib)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PackageDescription -> [ForeignLib]
foreignLibs PackageDescription
pd
    , condExecutables :: [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
condExecutables    = (Executable -> UnqualComponentName)
-> Executable
-> (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
forall a.
(a -> UnqualComponentName)
-> a -> (UnqualComponentName, CondTree ConfVar [Dependency] a)
mkCondTree' Executable -> UnqualComponentName
exeName (Executable
 -> (UnqualComponentName, CondTree ConfVar [Dependency] Executable))
-> [Executable]
-> [(UnqualComponentName,
     CondTree ConfVar [Dependency] Executable)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PackageDescription -> [Executable]
executables PackageDescription
pd
    , condTestSuites :: [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
condTestSuites     = (TestSuite -> UnqualComponentName)
-> TestSuite
-> (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
forall a.
(a -> UnqualComponentName)
-> a -> (UnqualComponentName, CondTree ConfVar [Dependency] a)
mkCondTree' TestSuite -> UnqualComponentName
testName (TestSuite
 -> (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite))
-> [TestSuite]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PackageDescription -> [TestSuite]
testSuites PackageDescription
pd
    , condBenchmarks :: [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
condBenchmarks     = (Benchmark -> UnqualComponentName)
-> Benchmark
-> (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
forall a.
(a -> UnqualComponentName)
-> a -> (UnqualComponentName, CondTree ConfVar [Dependency] a)
mkCondTree' Benchmark -> UnqualComponentName
benchmarkName (Benchmark
 -> (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark))
-> [Benchmark]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PackageDescription -> [Benchmark]
benchmarks PackageDescription
pd
    }
  where
    -- We set CondTree's [Dependency] to an empty list, as it
    -- is not pretty printed anyway.
    mkCondTree :: a -> CondTree v [a] a
mkCondTree  a
x = a -> [a] -> [CondBranch v [a] a] -> CondTree v [a] a
forall v c a. a -> c -> [CondBranch v c a] -> CondTree v c a
CondNode a
x [] []
    mkCondTreeL :: Library -> (UnqualComponentName, CondTree v [a] Library)
mkCondTreeL Library
l = (UnqualComponentName
-> Maybe UnqualComponentName -> UnqualComponentName
forall a. a -> Maybe a -> a
fromMaybe (FilePath -> UnqualComponentName
mkUnqualComponentName FilePath
"") (LibraryName -> Maybe UnqualComponentName
libraryNameString (Library -> LibraryName
libName Library
l)), Library
-> [a] -> [CondBranch v [a] Library] -> CondTree v [a] Library
forall v c a. a -> c -> [CondBranch v c a] -> CondTree v c a
CondNode Library
l [] [])

    mkCondTree'
        :: (a -> UnqualComponentName)
        -> a -> (UnqualComponentName, CondTree ConfVar [Dependency] a)
    mkCondTree' :: (a -> UnqualComponentName)
-> a -> (UnqualComponentName, CondTree ConfVar [Dependency] a)
mkCondTree' a -> UnqualComponentName
f a
x = (a -> UnqualComponentName
f a
x, a
-> [Dependency]
-> [CondBranch ConfVar [Dependency] a]
-> CondTree ConfVar [Dependency] a
forall v c a. a -> c -> [CondBranch v c a] -> CondTree v c a
CondNode a
x [] [])

-- | @since 2.0.0.2
writeHookedBuildInfo :: FilePath -> HookedBuildInfo -> NoCallStackIO ()
writeHookedBuildInfo :: FilePath -> HookedBuildInfo -> NoCallStackIO ()
writeHookedBuildInfo FilePath
fpath = FilePath -> ByteString -> NoCallStackIO ()
writeFileAtomic FilePath
fpath (ByteString -> NoCallStackIO ())
-> (HookedBuildInfo -> ByteString)
-> HookedBuildInfo
-> NoCallStackIO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> ByteString
BS.Char8.pack
                             (FilePath -> ByteString)
-> (HookedBuildInfo -> FilePath) -> HookedBuildInfo -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HookedBuildInfo -> FilePath
showHookedBuildInfo

-- | @since 2.0.0.2
showHookedBuildInfo :: HookedBuildInfo -> String
showHookedBuildInfo :: HookedBuildInfo -> FilePath
showHookedBuildInfo (Maybe BuildInfo
mb_lib_bi, [(UnqualComponentName, BuildInfo)]
ex_bis) = (() -> [FilePath]) -> [PrettyField ()] -> FilePath
forall ann. (ann -> [FilePath]) -> [PrettyField ann] -> FilePath
showFields ([FilePath] -> () -> [FilePath]
forall a b. a -> b -> a
const []) ([PrettyField ()] -> FilePath) -> [PrettyField ()] -> FilePath
forall a b. (a -> b) -> a -> b
$
    [PrettyField ()]
-> (BuildInfo -> [PrettyField ()])
-> Maybe BuildInfo
-> [PrettyField ()]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [PrettyField ()]
forall a. Monoid a => a
mempty (CabalSpecVersion
-> PrettyFieldGrammar BuildInfo BuildInfo
-> BuildInfo
-> [PrettyField ()]
forall s a.
CabalSpecVersion -> PrettyFieldGrammar s a -> s -> [PrettyField ()]
prettyFieldGrammar CabalSpecVersion
cabalSpecLatest PrettyFieldGrammar BuildInfo BuildInfo
forall (g :: * -> * -> *).
(FieldGrammar g, Applicative (g BuildInfo)) =>
g BuildInfo BuildInfo
buildInfoFieldGrammar) Maybe BuildInfo
mb_lib_bi [PrettyField ()] -> [PrettyField ()] -> [PrettyField ()]
forall a. [a] -> [a] -> [a]
++
    [ () -> FieldName -> [Doc] -> [PrettyField ()] -> PrettyField ()
forall ann.
ann -> FieldName -> [Doc] -> [PrettyField ann] -> PrettyField ann
PrettySection () FieldName
"executable:" [UnqualComponentName -> Doc
forall a. Pretty a => a -> Doc
pretty UnqualComponentName
name]
    ([PrettyField ()] -> PrettyField ())
-> [PrettyField ()] -> PrettyField ()
forall a b. (a -> b) -> a -> b
$ CabalSpecVersion
-> PrettyFieldGrammar BuildInfo BuildInfo
-> BuildInfo
-> [PrettyField ()]
forall s a.
CabalSpecVersion -> PrettyFieldGrammar s a -> s -> [PrettyField ()]
prettyFieldGrammar CabalSpecVersion
cabalSpecLatest PrettyFieldGrammar BuildInfo BuildInfo
forall (g :: * -> * -> *).
(FieldGrammar g, Applicative (g BuildInfo)) =>
g BuildInfo BuildInfo
buildInfoFieldGrammar BuildInfo
bi
    | (UnqualComponentName
name, BuildInfo
bi) <- [(UnqualComponentName, BuildInfo)]
ex_bis
    ]