{-# LANGUAGE OverloadedStrings #-}
module Distribution.PackageDescription.PrettyPrint
(
writeGenericPackageDescription
, showGenericPackageDescription
, ppGenericPackageDescription
, writePackageDescription
, showPackageDescription
, writeHookedBuildInfo
, showHookedBuildInfo
) where
import Distribution.Compat.Prelude
import Prelude ()
import Distribution.CabalSpecVersion
import Distribution.Compat.Lens
import Distribution.FieldGrammar (PrettyFieldGrammar', prettyFieldGrammar)
import Distribution.Fields.Pretty
import Distribution.PackageDescription
import Distribution.PackageDescription.Configuration (transformAllBuildInfos)
import Distribution.PackageDescription.FieldGrammar
( benchmarkFieldGrammar
, buildInfoFieldGrammar
, executableFieldGrammar
, flagFieldGrammar
, foreignLibFieldGrammar
, libraryFieldGrammar
, packageDescriptionFieldGrammar
, setupBInfoFieldGrammar
, sourceRepoFieldGrammar
, testSuiteFieldGrammar
)
import Distribution.Pretty
import Distribution.Utils.Generic (writeFileAtomic, writeUTF8File)
import qualified Distribution.PackageDescription.FieldGrammar as FG
import qualified Distribution.Types.BuildInfo.Lens as L
import qualified Distribution.Types.SetupBuildInfo.Lens as L
import Text.PrettyPrint (Doc, char, hsep, parens, text)
import qualified Data.ByteString.Lazy.Char8 as BS.Char8
import qualified Distribution.Compat.NonEmptySet as NES
writeGenericPackageDescription :: FilePath -> GenericPackageDescription -> IO ()
writeGenericPackageDescription :: String -> GenericPackageDescription -> IO ()
writeGenericPackageDescription String
fpath GenericPackageDescription
pkg = String -> String -> IO ()
writeUTF8File String
fpath (GenericPackageDescription -> String
showGenericPackageDescription GenericPackageDescription
pkg)
showGenericPackageDescription :: GenericPackageDescription -> String
showGenericPackageDescription :: GenericPackageDescription -> String
showGenericPackageDescription GenericPackageDescription
gpd = (() -> CommentPosition) -> [PrettyField ()] -> String
forall ann. (ann -> CommentPosition) -> [PrettyField ann] -> String
showFields (CommentPosition -> () -> CommentPosition
forall a b. a -> b -> a
const CommentPosition
NoComment) ([PrettyField ()] -> String) -> [PrettyField ()] -> String
forall a b. (a -> b) -> a -> b
$ CabalSpecVersion -> GenericPackageDescription -> [PrettyField ()]
ppGenericPackageDescription CabalSpecVersion
v GenericPackageDescription
gpd
where
v :: CabalSpecVersion
v = PackageDescription -> CabalSpecVersion
specVersion (PackageDescription -> CabalSpecVersion)
-> PackageDescription -> CabalSpecVersion
forall a b. (a -> b) -> a -> b
$ GenericPackageDescription -> PackageDescription
packageDescription GenericPackageDescription
gpd
ppGenericPackageDescription :: CabalSpecVersion -> GenericPackageDescription -> [PrettyField ()]
ppGenericPackageDescription :: CabalSpecVersion -> GenericPackageDescription -> [PrettyField ()]
ppGenericPackageDescription CabalSpecVersion
v GenericPackageDescription
gpd0 =
[[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 -> [PackageFlag] -> [PrettyField ()]
ppGenPackageFlags CabalSpecVersion
v (GenericPackageDescription -> [PackageFlag]
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)
]
where
gpd :: GenericPackageDescription
gpd = CabalSpecVersion
-> GenericPackageDescription -> GenericPackageDescription
preProcessInternalDeps (PackageDescription -> CabalSpecVersion
specVersion (GenericPackageDescription -> PackageDescription
packageDescription GenericPackageDescription
gpd0)) GenericPackageDescription
gpd0
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 (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g PackageDescription),
Applicative (g PackageIdentifier), c (Identity BuildType),
c (Identity PackageName), c (Identity Version),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List VCat (RelativePathNT from to) (RelativePath from to)),
c (List FSep TestedWith (CompilerFlavor, VersionRange)),
c CompatLicenseFile, c CompatDataDir) =>
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 (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g SourceRepo),
c (Identity RepoType), c Token, c FilePathNT) =>
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 a. a -> [a]
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 (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Functor (g SetupBuildInfo),
c (List CommaVCat (Identity Dependency) Dependency)) =>
Bool -> g SetupBuildInfo SetupBuildInfo
setupBInfoFieldGrammar Bool
False) SetupBuildInfo
sbi
ppGenPackageFlags :: CabalSpecVersion -> [PackageFlag] -> [PrettyField ()]
ppGenPackageFlags :: CabalSpecVersion -> [PackageFlag] -> [PrettyField ()]
ppGenPackageFlags = (PackageFlag -> PrettyField ())
-> [PackageFlag] -> [PrettyField ()]
forall a b. (a -> b) -> [a] -> [b]
map ((PackageFlag -> PrettyField ())
-> [PackageFlag] -> [PrettyField ()])
-> (CabalSpecVersion -> PackageFlag -> PrettyField ())
-> CabalSpecVersion
-> [PackageFlag]
-> [PrettyField ()]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CabalSpecVersion -> PackageFlag -> PrettyField ()
ppFlag
ppFlag :: CabalSpecVersion -> PackageFlag -> PrettyField ()
ppFlag :: CabalSpecVersion -> PackageFlag -> PrettyField ()
ppFlag CabalSpecVersion
v flag :: PackageFlag
flag@(MkPackageFlag FlagName
name String
_ 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 PackageFlag PackageFlag
-> PackageFlag
-> [PrettyField ()]
forall s a.
CabalSpecVersion -> PrettyFieldGrammar s a -> s -> [PrettyField ()]
prettyFieldGrammar CabalSpecVersion
v (FlagName -> PrettyFieldGrammar PackageFlag PackageFlag
forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g PackageFlag)) =>
FlagName -> g PackageFlag PackageFlag
flagFieldGrammar FlagName
name) PackageFlag
flag
ppCondTree2 :: CabalSpecVersion -> PrettyFieldGrammar' s -> CondTree ConfVar [Dependency] s -> [PrettyField ()]
ppCondTree2 :: forall s.
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
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)
| 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)) =
[ 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 a. a -> [a]
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 (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g Library),
Applicative (g BuildInfo), c (Identity LibraryVisibility),
c (List CommaFSep (Identity ExeDependency) ExeDependency),
c (List
CommaFSep (Identity LegacyExeDependency) LegacyExeDependency),
c (List
CommaFSep (Identity PkgconfigDependency) PkgconfigDependency),
c (List CommaVCat (Identity Dependency) Dependency),
c (List CommaVCat (Identity Mixin) Mixin),
c (List CommaVCat (Identity ModuleReexport) ModuleReexport),
c (List FSep (MQuoted Extension) Extension),
c (List FSep (MQuoted Language) Language),
c (List FSep Token String), c (List NoCommaFSep Token' String),
c (List VCat (MQuoted ModuleName) ModuleName),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List VCat (SymbolicPathNT from to) (SymbolicPath from to)),
c (List VCat Token String), c (MQuoted Language)) =>
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 (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g Library),
Applicative (g BuildInfo), c (Identity LibraryVisibility),
c (List CommaFSep (Identity ExeDependency) ExeDependency),
c (List
CommaFSep (Identity LegacyExeDependency) LegacyExeDependency),
c (List
CommaFSep (Identity PkgconfigDependency) PkgconfigDependency),
c (List CommaVCat (Identity Dependency) Dependency),
c (List CommaVCat (Identity Mixin) Mixin),
c (List CommaVCat (Identity ModuleReexport) ModuleReexport),
c (List FSep (MQuoted Extension) Extension),
c (List FSep (MQuoted Language) Language),
c (List FSep Token String), c (List NoCommaFSep Token' String),
c (List VCat (MQuoted ModuleName) ModuleName),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List VCat (SymbolicPathNT from to) (SymbolicPath from to)),
c (List VCat Token String), c (MQuoted Language)) =>
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 (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g ForeignLib),
Applicative (g BuildInfo), c (Identity ForeignLibType),
c (Identity LibVersionInfo), c (Identity Version),
c (List CommaFSep (Identity ExeDependency) ExeDependency),
c (List
CommaFSep (Identity LegacyExeDependency) LegacyExeDependency),
c (List
CommaFSep (Identity PkgconfigDependency) PkgconfigDependency),
c (List CommaVCat (Identity Dependency) Dependency),
c (List CommaVCat (Identity Mixin) Mixin),
c (List FSep (Identity ForeignLibOption) ForeignLibOption),
c (List FSep (MQuoted Extension) Extension),
c (List FSep (MQuoted Language) Language),
c (List FSep Token String),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List VCat (SymbolicPathNT from to) (SymbolicPath from to)),
c (List NoCommaFSep Token' String),
c (List VCat (MQuoted ModuleName) ModuleName),
c (List VCat Token String), c (MQuoted Language)) =>
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 (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g Executable),
Applicative (g BuildInfo), c (Identity ExecutableScope),
c (List CommaFSep (Identity ExeDependency) ExeDependency),
c (List
CommaFSep (Identity LegacyExeDependency) LegacyExeDependency),
c (List
CommaFSep (Identity PkgconfigDependency) PkgconfigDependency),
c (List CommaVCat (Identity Dependency) Dependency),
c (List CommaVCat (Identity Mixin) Mixin),
c (List FSep (MQuoted Extension) Extension),
c (List FSep (MQuoted Language) Language),
c (List FSep Token String),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List VCat (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir). c (SymbolicPathNT from to),
forall from (to :: FileOrDir). c (RelativePathNT from to),
c (List NoCommaFSep Token' String),
c (List VCat (MQuoted ModuleName) ModuleName),
c (List VCat Token String), c (MQuoted Language)) =>
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 (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g TestSuiteStanza),
Applicative (g BuildInfo), c (Identity ModuleName),
c (Identity TestType),
c (List CommaFSep (Identity ExeDependency) ExeDependency),
c (List
CommaFSep (Identity LegacyExeDependency) LegacyExeDependency),
c (List
CommaFSep (Identity PkgconfigDependency) PkgconfigDependency),
c (List CommaFSep Token String),
c (List CommaVCat (Identity Dependency) Dependency),
c (List CommaVCat (Identity Mixin) Mixin),
c (List FSep (MQuoted Extension) Extension),
c (List FSep (MQuoted Language) Language),
c (List FSep Token String), c (List NoCommaFSep Token' String),
c (List VCat (MQuoted ModuleName) ModuleName),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List VCat (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir). c (RelativePathNT from to),
c (List VCat Token String), c (MQuoted Language)) =>
g TestSuiteStanza TestSuiteStanza
testSuiteFieldGrammar ((TestSuite -> TestSuiteStanza)
-> CondTree ConfVar [Dependency] TestSuite
-> CondTree ConfVar [Dependency] TestSuiteStanza
forall a b.
(a -> b)
-> CondTree ConfVar [Dependency] a
-> CondTree ConfVar [Dependency] b
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 (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g BenchmarkStanza),
Applicative (g BuildInfo), c (Identity BenchmarkType),
c (Identity ModuleName),
c (List CommaFSep (Identity ExeDependency) ExeDependency),
c (List
CommaFSep (Identity LegacyExeDependency) LegacyExeDependency),
c (List
CommaFSep (Identity PkgconfigDependency) PkgconfigDependency),
c (List CommaVCat (Identity Dependency) Dependency),
c (List CommaVCat (Identity Mixin) Mixin),
c (List FSep (MQuoted Extension) Extension),
c (List FSep (MQuoted Language) Language),
c (List FSep Token String), c (List NoCommaFSep Token' String),
c (List VCat (MQuoted ModuleName) ModuleName),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List VCat (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir). c (RelativePathNT from to),
c (List VCat Token String), c (MQuoted Language)) =>
g BenchmarkStanza BenchmarkStanza
benchmarkFieldGrammar ((Benchmark -> BenchmarkStanza)
-> CondTree ConfVar [Dependency] Benchmark
-> CondTree ConfVar [Dependency] BenchmarkStanza
forall a b.
(a -> b)
-> CondTree ConfVar [Dependency] a
-> CondTree ConfVar [Dependency] b
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) = String -> Doc
text (Bool -> String
forall a. Show a => a -> String
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
, String -> Doc
text String
"||"
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
, String -> Doc
text String
"&&"
Doc -> Doc -> Doc
<+> Condition ConfVar -> Doc
ppCondition Condition ConfVar
c2
]
)
ppConfVar :: ConfVar -> Doc
ppConfVar :: ConfVar -> Doc
ppConfVar (OS OS
os) = String -> Doc
text String
"os" Doc -> Doc -> Doc
<<>> Doc -> Doc
parens (OS -> Doc
forall a. Pretty a => a -> Doc
pretty OS
os)
ppConfVar (Arch Arch
arch) = String -> Doc
text String
"arch" Doc -> Doc -> Doc
<<>> Doc -> Doc
parens (Arch -> Doc
forall a. Pretty a => a -> Doc
pretty Arch
arch)
ppConfVar (PackageFlag FlagName
name) = String -> Doc
text String
"flag" Doc -> Doc -> Doc
<<>> Doc -> Doc
parens (FlagName -> Doc
ppFlagName FlagName
name)
ppConfVar (Impl CompilerFlavor
c VersionRange
v) = String -> Doc
text String
"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 = String -> Doc
text (String -> Doc) -> (FlagName -> String) -> FlagName -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FlagName -> String
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]
writePackageDescription :: FilePath -> PackageDescription -> IO ()
writePackageDescription :: String -> PackageDescription -> IO ()
writePackageDescription String
fpath PackageDescription
pkg = String -> String -> IO ()
writeUTF8File String
fpath (PackageDescription -> String
showPackageDescription PackageDescription
pkg)
showPackageDescription :: PackageDescription -> String
showPackageDescription :: PackageDescription -> String
showPackageDescription = GenericPackageDescription -> String
showGenericPackageDescription (GenericPackageDescription -> String)
-> (PackageDescription -> GenericPackageDescription)
-> PackageDescription
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageDescription -> GenericPackageDescription
pdToGpd
pdToGpd :: PackageDescription -> GenericPackageDescription
pdToGpd :: PackageDescription -> GenericPackageDescription
pdToGpd PackageDescription
pd =
GenericPackageDescription
{ packageDescription :: PackageDescription
packageDescription = PackageDescription
pd
, gpdScannedVersion :: Maybe Version
gpdScannedVersion = Maybe Version
forall a. Maybe a
Nothing
, genPackageFlags :: [PackageFlag]
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
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 (String -> UnqualComponentName
mkUnqualComponentName String
"") (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' :: forall a.
(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 [] [])
preProcessInternalDeps :: CabalSpecVersion -> GenericPackageDescription -> GenericPackageDescription
preProcessInternalDeps :: CabalSpecVersion
-> GenericPackageDescription -> GenericPackageDescription
preProcessInternalDeps CabalSpecVersion
specVer GenericPackageDescription
gpd
| CabalSpecVersion
specVer CabalSpecVersion -> CabalSpecVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= CabalSpecVersion
CabalSpecV3_4 = GenericPackageDescription
gpd
| Bool
otherwise = (BuildInfo -> BuildInfo)
-> (SetupBuildInfo -> SetupBuildInfo)
-> GenericPackageDescription
-> GenericPackageDescription
transformAllBuildInfos BuildInfo -> BuildInfo
transformBI SetupBuildInfo -> SetupBuildInfo
transformSBI GenericPackageDescription
gpd
where
transformBI :: BuildInfo -> BuildInfo
transformBI :: BuildInfo -> BuildInfo
transformBI =
ASetter BuildInfo BuildInfo [Dependency] [Dependency]
-> ([Dependency] -> [Dependency]) -> BuildInfo -> BuildInfo
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter BuildInfo BuildInfo [Dependency] [Dependency]
forall a. HasBuildInfo a => Lens' a [Dependency]
Lens' BuildInfo [Dependency]
L.targetBuildDepends ((Dependency -> [Dependency]) -> [Dependency] -> [Dependency]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Dependency -> [Dependency]
transformD)
(BuildInfo -> BuildInfo)
-> (BuildInfo -> BuildInfo) -> BuildInfo -> BuildInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ASetter BuildInfo BuildInfo [Mixin] [Mixin]
-> ([Mixin] -> [Mixin]) -> BuildInfo -> BuildInfo
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter BuildInfo BuildInfo [Mixin] [Mixin]
forall a. HasBuildInfo a => Lens' a [Mixin]
Lens' BuildInfo [Mixin]
L.mixins ((Mixin -> Mixin) -> [Mixin] -> [Mixin]
forall a b. (a -> b) -> [a] -> [b]
map Mixin -> Mixin
transformM)
transformSBI :: SetupBuildInfo -> SetupBuildInfo
transformSBI :: SetupBuildInfo -> SetupBuildInfo
transformSBI = ASetter SetupBuildInfo SetupBuildInfo [Dependency] [Dependency]
-> ([Dependency] -> [Dependency])
-> SetupBuildInfo
-> SetupBuildInfo
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter SetupBuildInfo SetupBuildInfo [Dependency] [Dependency]
Lens' SetupBuildInfo [Dependency]
L.setupDepends ((Dependency -> [Dependency]) -> [Dependency] -> [Dependency]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Dependency -> [Dependency]
transformD)
transformD :: Dependency -> [Dependency]
transformD :: Dependency -> [Dependency]
transformD (Dependency PackageName
pn VersionRange
vr NonEmptySet LibraryName
ln)
| PackageName
pn PackageName -> PackageName -> Bool
forall a. Eq a => a -> a -> Bool
== PackageName
thisPn =
if LibraryName
LMainLibName LibraryName -> NonEmptySet LibraryName -> Bool
forall a. Ord a => a -> NonEmptySet a -> Bool
`NES.member` NonEmptySet LibraryName
ln
then PackageName
-> VersionRange -> NonEmptySet LibraryName -> Dependency
Dependency PackageName
thisPn VersionRange
vr NonEmptySet LibraryName
mainLibSet Dependency -> [Dependency] -> [Dependency]
forall a. a -> [a] -> [a]
: [Dependency]
sublibs
else [Dependency]
sublibs
where
sublibs :: [Dependency]
sublibs =
[ PackageName
-> VersionRange -> NonEmptySet LibraryName -> Dependency
Dependency (UnqualComponentName -> PackageName
unqualComponentNameToPackageName UnqualComponentName
uqn) VersionRange
vr NonEmptySet LibraryName
mainLibSet
| LSubLibName UnqualComponentName
uqn <- NonEmptySet LibraryName -> [LibraryName]
forall a. NonEmptySet a -> [a]
NES.toList NonEmptySet LibraryName
ln
]
transformD Dependency
d = [Dependency
d]
transformM :: Mixin -> Mixin
transformM :: Mixin -> Mixin
transformM (Mixin PackageName
pn (LSubLibName UnqualComponentName
uqn) IncludeRenaming
inc)
| PackageName
pn PackageName -> PackageName -> Bool
forall a. Eq a => a -> a -> Bool
== PackageName
thisPn =
PackageName -> LibraryName -> IncludeRenaming -> Mixin
mkMixin (UnqualComponentName -> PackageName
unqualComponentNameToPackageName UnqualComponentName
uqn) LibraryName
LMainLibName IncludeRenaming
inc
transformM Mixin
m = Mixin
m
thisPn :: PackageName
thisPn :: PackageName
thisPn = PackageIdentifier -> PackageName
pkgName (PackageDescription -> PackageIdentifier
package (GenericPackageDescription -> PackageDescription
packageDescription GenericPackageDescription
gpd))
writeHookedBuildInfo :: FilePath -> HookedBuildInfo -> IO ()
writeHookedBuildInfo :: String -> HookedBuildInfo -> IO ()
writeHookedBuildInfo String
fpath =
String -> ByteString -> IO ()
writeFileAtomic String
fpath
(ByteString -> IO ())
-> (HookedBuildInfo -> ByteString) -> HookedBuildInfo -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString
BS.Char8.pack
(String -> ByteString)
-> (HookedBuildInfo -> String) -> HookedBuildInfo -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HookedBuildInfo -> String
showHookedBuildInfo
showHookedBuildInfo :: HookedBuildInfo -> String
showHookedBuildInfo :: HookedBuildInfo -> String
showHookedBuildInfo (Maybe BuildInfo
mb_lib_bi, [(UnqualComponentName, BuildInfo)]
ex_bis) =
(() -> CommentPosition) -> [PrettyField ()] -> String
forall ann. (ann -> CommentPosition) -> [PrettyField ann] -> String
showFields (CommentPosition -> () -> CommentPosition
forall a b. a -> b -> a
const CommentPosition
NoComment) ([PrettyField ()] -> String) -> [PrettyField ()] -> String
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 (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g BuildInfo),
c (List CommaFSep (Identity ExeDependency) ExeDependency),
c (List
CommaFSep (Identity LegacyExeDependency) LegacyExeDependency),
c (List
CommaFSep (Identity PkgconfigDependency) PkgconfigDependency),
c (List CommaVCat (Identity Dependency) Dependency),
c (List CommaVCat (Identity Mixin) Mixin),
c (List FSep (MQuoted Extension) Extension),
c (List FSep (MQuoted Language) Language),
c (List FSep Token String), c (List NoCommaFSep Token' String),
c (List VCat (MQuoted ModuleName) ModuleName),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List VCat (SymbolicPathNT from to) (SymbolicPath from to)),
c (List VCat Token String), c (MQuoted Language)) =>
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 (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g BuildInfo),
c (List CommaFSep (Identity ExeDependency) ExeDependency),
c (List
CommaFSep (Identity LegacyExeDependency) LegacyExeDependency),
c (List
CommaFSep (Identity PkgconfigDependency) PkgconfigDependency),
c (List CommaVCat (Identity Dependency) Dependency),
c (List CommaVCat (Identity Mixin) Mixin),
c (List FSep (MQuoted Extension) Extension),
c (List FSep (MQuoted Language) Language),
c (List FSep Token String), c (List NoCommaFSep Token' String),
c (List VCat (MQuoted ModuleName) ModuleName),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List VCat (SymbolicPathNT from to) (SymbolicPath from to)),
c (List VCat Token String), c (MQuoted Language)) =>
g BuildInfo BuildInfo
buildInfoFieldGrammar BuildInfo
bi
| (UnqualComponentName
name, BuildInfo
bi) <- [(UnqualComponentName, BuildInfo)]
ex_bis
]