{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE LiberalTypeSynonyms #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE DataKinds #-}
module Hpack.Config (
-- | /__NOTE:__/ This module is exposed to allow integration of Hpack into
-- other tools.  It is not meant for general use by end users.  The following
-- caveats apply:
--
-- * The API is undocumented, consult the source instead.
--
-- * The exposed types and functions primarily serve Hpack's own needs, not
-- that of a public API.  Breaking changes can happen as Hpack evolves.
--
-- As an Hpack user you either want to use the @hpack@ executable or a build
-- tool that supports Hpack (e.g. @stack@ or @cabal2nix@).

  DecodeOptions(..)
, ProgramName(..)
, defaultDecodeOptions
, packageConfig
, DecodeResult(..)
, readPackageConfig
, readPackageConfigWithError

, renamePackage
, packageDependencies
, package
, section
, Package(..)
, Dependencies(..)
, DependencyInfo(..)
, VersionConstraint(..)
, DependencyVersion(..)
, SourceDependency(..)
, GitRef
, GitUrl
, BuildTool(..)
, SystemBuildTools(..)
, GhcOption
, Verbatim(..)
, VerbatimValue(..)
, verbatimValueToString
, CustomSetup(..)
, Section(..)
, Library(..)
, Executable(..)
, Conditional(..)
, Cond(..)
, Flag(..)
, SourceRepository(..)
, Language(..)
, BuildType(..)
, GhcProfOption
, GhcjsOption
, CppOption
, CcOption
, LdOption
, Path(..)
, Module(..)
#ifdef TEST
, renameDependencies
, Empty(..)
, pathsModuleFromPackageName

, LibrarySection(..)
, fromLibrarySectionInConditional
, formatOrList

, toBuildTool
#endif
) where

import           Imports

import           Data.Either
import           Data.Bitraversable
import           Data.Map.Lazy (Map)
import qualified Data.Map.Lazy as Map
import qualified Data.Aeson.Config.KeyMap as KeyMap
import           Data.Maybe
import           Data.Monoid (Last(..))
import           Data.Ord
import qualified Data.Text as T
import           Data.Text.Encoding (decodeUtf8)
import           Data.Scientific (Scientific)
import           System.Directory
import           System.FilePath
import           Control.Monad.Trans.Class
import           Control.Monad.Trans.Writer
import           Control.Monad.Trans.Except
import           Control.Monad.IO.Class
import           Data.Version (Version, makeVersion, showVersion)

import           Distribution.Pretty (prettyShow)
import qualified Distribution.SPDX.License as SPDX

import qualified Data.Yaml.Pretty as Yaml
import           Data.Aeson (object, (.=))
import           Data.Aeson.Config.Types
import           Data.Aeson.Config.FromValue hiding (decodeValue)
import qualified Data.Aeson.Config.FromValue as Config

import           Hpack.Error
import           Hpack.Syntax.Defaults
import           Hpack.Util hiding (expandGlobs)
import qualified Hpack.Util as Util
import           Hpack.Defaults
import qualified Hpack.Yaml as Yaml
import           Hpack.Syntax.DependencyVersion
import           Hpack.Syntax.Dependencies
import           Hpack.Syntax.BuildTools
import           Hpack.License
import           Hpack.CabalFile (parseVersion)
import           Hpack.Module

import qualified Path

import qualified Paths_hpack as Hpack (version)

package :: String -> String -> Package
package :: String -> String -> Package
package String
name String
version = Package {
    packageName :: String
packageName = String
name
  , packageVersion :: String
packageVersion = String
version
  , packageSynopsis :: Maybe String
packageSynopsis = forall a. Maybe a
Nothing
  , packageDescription :: Maybe String
packageDescription = forall a. Maybe a
Nothing
  , packageHomepage :: Maybe String
packageHomepage = forall a. Maybe a
Nothing
  , packageBugReports :: Maybe String
packageBugReports = forall a. Maybe a
Nothing
  , packageCategory :: Maybe String
packageCategory = forall a. Maybe a
Nothing
  , packageStability :: Maybe String
packageStability = forall a. Maybe a
Nothing
  , packageAuthor :: [String]
packageAuthor = []
  , packageMaintainer :: [String]
packageMaintainer = []
  , packageCopyright :: [String]
packageCopyright = []
  , packageBuildType :: BuildType
packageBuildType = BuildType
Simple
  , packageLicense :: Maybe String
packageLicense = forall a. Maybe a
Nothing
  , packageLicenseFile :: [String]
packageLicenseFile = []
  , packageTestedWith :: [String]
packageTestedWith = []
  , packageFlags :: [Flag]
packageFlags = []
  , packageExtraSourceFiles :: [Path]
packageExtraSourceFiles = []
  , packageExtraDocFiles :: [Path]
packageExtraDocFiles = []
  , packageDataFiles :: [Path]
packageDataFiles = []
  , packageDataDir :: Maybe String
packageDataDir = forall a. Maybe a
Nothing
  , packageSourceRepository :: Maybe SourceRepository
packageSourceRepository = forall a. Maybe a
Nothing
  , packageCustomSetup :: Maybe CustomSetup
packageCustomSetup = forall a. Maybe a
Nothing
  , packageLibrary :: Maybe (Section Library)
packageLibrary = forall a. Maybe a
Nothing
  , packageInternalLibraries :: Map String (Section Library)
packageInternalLibraries = forall a. Monoid a => a
mempty
  , packageExecutables :: Map String (Section Executable)
packageExecutables = forall a. Monoid a => a
mempty
  , packageTests :: Map String (Section Executable)
packageTests = forall a. Monoid a => a
mempty
  , packageBenchmarks :: Map String (Section Executable)
packageBenchmarks = forall a. Monoid a => a
mempty
  , packageVerbatim :: [Verbatim]
packageVerbatim = []
  }

renamePackage :: String -> Package -> Package
renamePackage :: String -> Package -> Package
renamePackage String
name p :: Package
p@Package{String
[String]
[Path]
[Flag]
[Verbatim]
Maybe String
Maybe SourceRepository
Maybe (Section Library)
Maybe CustomSetup
Map String (Section Executable)
Map String (Section Library)
BuildType
packageVerbatim :: [Verbatim]
packageBenchmarks :: Map String (Section Executable)
packageTests :: Map String (Section Executable)
packageExecutables :: Map String (Section Executable)
packageInternalLibraries :: Map String (Section Library)
packageLibrary :: Maybe (Section Library)
packageCustomSetup :: Maybe CustomSetup
packageSourceRepository :: Maybe SourceRepository
packageDataDir :: Maybe String
packageDataFiles :: [Path]
packageExtraDocFiles :: [Path]
packageExtraSourceFiles :: [Path]
packageFlags :: [Flag]
packageTestedWith :: [String]
packageLicenseFile :: [String]
packageLicense :: Maybe String
packageBuildType :: BuildType
packageCopyright :: [String]
packageMaintainer :: [String]
packageAuthor :: [String]
packageStability :: Maybe String
packageCategory :: Maybe String
packageBugReports :: Maybe String
packageHomepage :: Maybe String
packageDescription :: Maybe String
packageSynopsis :: Maybe String
packageVersion :: String
packageName :: String
packageVerbatim :: Package -> [Verbatim]
packageBenchmarks :: Package -> Map String (Section Executable)
packageTests :: Package -> Map String (Section Executable)
packageExecutables :: Package -> Map String (Section Executable)
packageInternalLibraries :: Package -> Map String (Section Library)
packageLibrary :: Package -> Maybe (Section Library)
packageCustomSetup :: Package -> Maybe CustomSetup
packageSourceRepository :: Package -> Maybe SourceRepository
packageDataDir :: Package -> Maybe String
packageDataFiles :: Package -> [Path]
packageExtraDocFiles :: Package -> [Path]
packageExtraSourceFiles :: Package -> [Path]
packageFlags :: Package -> [Flag]
packageTestedWith :: Package -> [String]
packageLicenseFile :: Package -> [String]
packageLicense :: Package -> Maybe String
packageBuildType :: Package -> BuildType
packageCopyright :: Package -> [String]
packageMaintainer :: Package -> [String]
packageAuthor :: Package -> [String]
packageStability :: Package -> Maybe String
packageCategory :: Package -> Maybe String
packageBugReports :: Package -> Maybe String
packageHomepage :: Package -> Maybe String
packageDescription :: Package -> Maybe String
packageSynopsis :: Package -> Maybe String
packageVersion :: Package -> String
packageName :: Package -> String
..} = Package
p {
    packageName :: String
packageName = String
name
  , packageExecutables :: Map String (Section Executable)
packageExecutables = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. String -> String -> Section a -> Section a
renameDependencies String
packageName String
name) Map String (Section Executable)
packageExecutables
  , packageTests :: Map String (Section Executable)
packageTests = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. String -> String -> Section a -> Section a
renameDependencies String
packageName String
name) Map String (Section Executable)
packageTests
  , packageBenchmarks :: Map String (Section Executable)
packageBenchmarks = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. String -> String -> Section a -> Section a
renameDependencies String
packageName String
name) Map String (Section Executable)
packageBenchmarks
  }

renameDependencies :: String -> String -> Section a -> Section a
renameDependencies :: forall a. String -> String -> Section a -> Section a
renameDependencies String
old String
new sect :: Section a
sect@Section{a
[String]
[Path]
[Conditional (Section a)]
[Verbatim]
Maybe Bool
Maybe Language
Map BuildTool DependencyVersion
Dependencies
SystemBuildTools
sectionVerbatim :: forall a. Section a -> [Verbatim]
sectionSystemBuildTools :: forall a. Section a -> SystemBuildTools
sectionBuildTools :: forall a. Section a -> Map BuildTool DependencyVersion
sectionConditionals :: forall a. Section a -> [Conditional (Section a)]
sectionBuildable :: forall a. Section a -> Maybe Bool
sectionLdOptions :: forall a. Section a -> [String]
sectionInstallIncludes :: forall a. Section a -> [String]
sectionIncludeDirs :: forall a. Section a -> [String]
sectionFrameworks :: forall a. Section a -> [String]
sectionExtraFrameworksDirs :: forall a. Section a -> [String]
sectionExtraLibraries :: forall a. Section a -> [String]
sectionExtraLibDirs :: forall a. Section a -> [String]
sectionJsSources :: forall a. Section a -> [Path]
sectionCxxSources :: forall a. Section a -> [Path]
sectionCxxOptions :: forall a. Section a -> [String]
sectionCSources :: forall a. Section a -> [Path]
sectionCcOptions :: forall a. Section a -> [String]
sectionCppOptions :: forall a. Section a -> [String]
sectionGhcjsOptions :: forall a. Section a -> [String]
sectionGhcSharedOptions :: forall a. Section a -> [String]
sectionGhcProfOptions :: forall a. Section a -> [String]
sectionGhcOptions :: forall a. Section a -> [String]
sectionLanguage :: forall a. Section a -> Maybe Language
sectionOtherExtensions :: forall a. Section a -> [String]
sectionDefaultExtensions :: forall a. Section a -> [String]
sectionPkgConfigDependencies :: forall a. Section a -> [String]
sectionDependencies :: forall a. Section a -> Dependencies
sectionSourceDirs :: forall a. Section a -> [String]
sectionData :: forall a. Section a -> a
sectionVerbatim :: [Verbatim]
sectionSystemBuildTools :: SystemBuildTools
sectionBuildTools :: Map BuildTool DependencyVersion
sectionConditionals :: [Conditional (Section a)]
sectionBuildable :: Maybe Bool
sectionLdOptions :: [String]
sectionInstallIncludes :: [String]
sectionIncludeDirs :: [String]
sectionFrameworks :: [String]
sectionExtraFrameworksDirs :: [String]
sectionExtraLibraries :: [String]
sectionExtraLibDirs :: [String]
sectionJsSources :: [Path]
sectionCxxSources :: [Path]
sectionCxxOptions :: [String]
sectionCSources :: [Path]
sectionCcOptions :: [String]
sectionCppOptions :: [String]
sectionGhcjsOptions :: [String]
sectionGhcSharedOptions :: [String]
sectionGhcProfOptions :: [String]
sectionGhcOptions :: [String]
sectionLanguage :: Maybe Language
sectionOtherExtensions :: [String]
sectionDefaultExtensions :: [String]
sectionPkgConfigDependencies :: [String]
sectionDependencies :: Dependencies
sectionSourceDirs :: [String]
sectionData :: a
..} = Section a
sect {sectionDependencies :: Dependencies
sectionDependencies = (Map String DependencyInfo -> Dependencies
Dependencies forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map forall {b}. (String, b) -> (String, b)
rename forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k a. Map k a -> [(k, a)]
Map.toList forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dependencies -> Map String DependencyInfo
unDependencies) Dependencies
sectionDependencies, sectionConditionals :: [Conditional (Section a)]
sectionConditionals = forall a b. (a -> b) -> [a] -> [b]
map forall a. Conditional (Section a) -> Conditional (Section a)
renameConditional [Conditional (Section a)]
sectionConditionals}
  where
    rename :: (String, b) -> (String, b)
rename dep :: (String, b)
dep@(String
name, b
version)
      | String
name forall a. Eq a => a -> a -> Bool
== String
old = (String
new, b
version)
      | Bool
otherwise = (String, b)
dep

    renameConditional :: Conditional (Section a) -> Conditional (Section a)
    renameConditional :: forall a. Conditional (Section a) -> Conditional (Section a)
renameConditional (Conditional Cond
condition Section a
then_ Maybe (Section a)
else_) = forall a. Cond -> a -> Maybe a -> Conditional a
Conditional Cond
condition (forall a. String -> String -> Section a -> Section a
renameDependencies String
old String
new Section a
then_) (forall a. String -> String -> Section a -> Section a
renameDependencies String
old String
new forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (Section a)
else_)

packageDependencies :: Package -> [(String, DependencyInfo)]
packageDependencies :: Package -> [(String, DependencyInfo)]
packageDependencies Package{String
[String]
[Path]
[Flag]
[Verbatim]
Maybe String
Maybe SourceRepository
Maybe (Section Library)
Maybe CustomSetup
Map String (Section Executable)
Map String (Section Library)
BuildType
packageVerbatim :: [Verbatim]
packageBenchmarks :: Map String (Section Executable)
packageTests :: Map String (Section Executable)
packageExecutables :: Map String (Section Executable)
packageInternalLibraries :: Map String (Section Library)
packageLibrary :: Maybe (Section Library)
packageCustomSetup :: Maybe CustomSetup
packageSourceRepository :: Maybe SourceRepository
packageDataDir :: Maybe String
packageDataFiles :: [Path]
packageExtraDocFiles :: [Path]
packageExtraSourceFiles :: [Path]
packageFlags :: [Flag]
packageTestedWith :: [String]
packageLicenseFile :: [String]
packageLicense :: Maybe String
packageBuildType :: BuildType
packageCopyright :: [String]
packageMaintainer :: [String]
packageAuthor :: [String]
packageStability :: Maybe String
packageCategory :: Maybe String
packageBugReports :: Maybe String
packageHomepage :: Maybe String
packageDescription :: Maybe String
packageSynopsis :: Maybe String
packageVersion :: String
packageName :: String
packageVerbatim :: Package -> [Verbatim]
packageBenchmarks :: Package -> Map String (Section Executable)
packageTests :: Package -> Map String (Section Executable)
packageExecutables :: Package -> Map String (Section Executable)
packageInternalLibraries :: Package -> Map String (Section Library)
packageLibrary :: Package -> Maybe (Section Library)
packageCustomSetup :: Package -> Maybe CustomSetup
packageSourceRepository :: Package -> Maybe SourceRepository
packageDataDir :: Package -> Maybe String
packageDataFiles :: Package -> [Path]
packageExtraDocFiles :: Package -> [Path]
packageExtraSourceFiles :: Package -> [Path]
packageFlags :: Package -> [Flag]
packageTestedWith :: Package -> [String]
packageLicenseFile :: Package -> [String]
packageLicense :: Package -> Maybe String
packageBuildType :: Package -> BuildType
packageCopyright :: Package -> [String]
packageMaintainer :: Package -> [String]
packageAuthor :: Package -> [String]
packageStability :: Package -> Maybe String
packageCategory :: Package -> Maybe String
packageBugReports :: Package -> Maybe String
packageHomepage :: Package -> Maybe String
packageDescription :: Package -> Maybe String
packageSynopsis :: Package -> Maybe String
packageVersion :: Package -> String
packageName :: Package -> String
..} = forall a. Ord a => [a] -> [a]
nub forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing (String -> (String, String)
lexicographically forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst)) forall a b. (a -> b) -> a -> b
$
     (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall {a}. Section a -> [(String, DependencyInfo)]
deps Map String (Section Executable)
packageExecutables)
  forall a. [a] -> [a] -> [a]
++ (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall {a}. Section a -> [(String, DependencyInfo)]
deps Map String (Section Executable)
packageTests)
  forall a. [a] -> [a] -> [a]
++ (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall {a}. Section a -> [(String, DependencyInfo)]
deps Map String (Section Executable)
packageBenchmarks)
  forall a. [a] -> [a] -> [a]
++ forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] forall {a}. Section a -> [(String, DependencyInfo)]
deps Maybe (Section Library)
packageLibrary
  where
    deps :: Section a -> [(String, DependencyInfo)]
deps Section a
xs = [(String
name, DependencyInfo
info) | (String
name, DependencyInfo
info) <- (forall k a. Map k a -> [(k, a)]
Map.toList forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dependencies -> Map String DependencyInfo
unDependencies forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Section a -> Dependencies
sectionDependencies) Section a
xs]

section :: a -> Section a
section :: forall a. a -> Section a
section a
a = forall a.
a
-> [String]
-> Dependencies
-> [String]
-> [String]
-> [String]
-> Maybe Language
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [Path]
-> [String]
-> [Path]
-> [Path]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> Maybe Bool
-> [Conditional (Section a)]
-> Map BuildTool DependencyVersion
-> SystemBuildTools
-> [Verbatim]
-> Section a
Section a
a [] forall a. Monoid a => a
mempty [] [] [] forall a. Maybe a
Nothing [] [] [] [] [] [] [] [] [] [] [] [] [] [] [] [] [] forall a. Maybe a
Nothing [] forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty []

packageConfig :: FilePath
packageConfig :: String
packageConfig = String
"package.yaml"

data CustomSetupSection = CustomSetupSection {
  CustomSetupSection -> Maybe Dependencies
customSetupSectionDependencies :: Maybe Dependencies
} deriving (CustomSetupSection -> CustomSetupSection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CustomSetupSection -> CustomSetupSection -> Bool
$c/= :: CustomSetupSection -> CustomSetupSection -> Bool
== :: CustomSetupSection -> CustomSetupSection -> Bool
$c== :: CustomSetupSection -> CustomSetupSection -> Bool
Eq, Int -> CustomSetupSection -> ShowS
[CustomSetupSection] -> ShowS
CustomSetupSection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CustomSetupSection] -> ShowS
$cshowList :: [CustomSetupSection] -> ShowS
show :: CustomSetupSection -> String
$cshow :: CustomSetupSection -> String
showsPrec :: Int -> CustomSetupSection -> ShowS
$cshowsPrec :: Int -> CustomSetupSection -> ShowS
Show, forall x. Rep CustomSetupSection x -> CustomSetupSection
forall x. CustomSetupSection -> Rep CustomSetupSection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CustomSetupSection x -> CustomSetupSection
$cfrom :: forall x. CustomSetupSection -> Rep CustomSetupSection x
Generic, Value -> Parser CustomSetupSection
forall a. (Value -> Parser a) -> FromValue a
fromValue :: Value -> Parser CustomSetupSection
$cfromValue :: Value -> Parser CustomSetupSection
FromValue)

data LibrarySection = LibrarySection {
  LibrarySection -> Maybe Bool
librarySectionExposed :: Maybe Bool
, LibrarySection -> Maybe String
librarySectionVisibility :: Maybe String
, LibrarySection -> Maybe (List Module)
librarySectionExposedModules :: Maybe (List Module)
, LibrarySection -> Maybe (List Module)
librarySectionGeneratedExposedModules :: Maybe (List Module)
, LibrarySection -> Maybe (List Module)
librarySectionOtherModules :: Maybe (List Module)
, LibrarySection -> Maybe (List Module)
librarySectionGeneratedOtherModules :: Maybe (List Module)
, LibrarySection -> Maybe (List String)
librarySectionReexportedModules :: Maybe (List String)
, LibrarySection -> Maybe (List String)
librarySectionSignatures :: Maybe (List String)
} deriving (LibrarySection -> LibrarySection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LibrarySection -> LibrarySection -> Bool
$c/= :: LibrarySection -> LibrarySection -> Bool
== :: LibrarySection -> LibrarySection -> Bool
$c== :: LibrarySection -> LibrarySection -> Bool
Eq, Int -> LibrarySection -> ShowS
[LibrarySection] -> ShowS
LibrarySection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LibrarySection] -> ShowS
$cshowList :: [LibrarySection] -> ShowS
show :: LibrarySection -> String
$cshow :: LibrarySection -> String
showsPrec :: Int -> LibrarySection -> ShowS
$cshowsPrec :: Int -> LibrarySection -> ShowS
Show, forall x. Rep LibrarySection x -> LibrarySection
forall x. LibrarySection -> Rep LibrarySection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LibrarySection x -> LibrarySection
$cfrom :: forall x. LibrarySection -> Rep LibrarySection x
Generic, Value -> Parser LibrarySection
forall a. (Value -> Parser a) -> FromValue a
fromValue :: Value -> Parser LibrarySection
$cfromValue :: Value -> Parser LibrarySection
FromValue)

instance Monoid LibrarySection where
  mempty :: LibrarySection
mempty = Maybe Bool
-> Maybe String
-> Maybe (List Module)
-> Maybe (List Module)
-> Maybe (List Module)
-> Maybe (List Module)
-> Maybe (List String)
-> Maybe (List String)
-> LibrarySection
LibrarySection forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  mappend :: LibrarySection -> LibrarySection -> LibrarySection
mappend = forall a. Semigroup a => a -> a -> a
(<>)

instance Semigroup LibrarySection where
  LibrarySection
a <> :: LibrarySection -> LibrarySection -> LibrarySection
<> LibrarySection
b = LibrarySection {
      librarySectionExposed :: Maybe Bool
librarySectionExposed = LibrarySection -> Maybe Bool
librarySectionExposed LibrarySection
b forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LibrarySection -> Maybe Bool
librarySectionExposed LibrarySection
a
    , librarySectionVisibility :: Maybe String
librarySectionVisibility = LibrarySection -> Maybe String
librarySectionVisibility LibrarySection
b forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LibrarySection -> Maybe String
librarySectionVisibility LibrarySection
a
    , librarySectionExposedModules :: Maybe (List Module)
librarySectionExposedModules = LibrarySection -> Maybe (List Module)
librarySectionExposedModules LibrarySection
a forall a. Semigroup a => a -> a -> a
<> LibrarySection -> Maybe (List Module)
librarySectionExposedModules LibrarySection
b
    , librarySectionGeneratedExposedModules :: Maybe (List Module)
librarySectionGeneratedExposedModules = LibrarySection -> Maybe (List Module)
librarySectionGeneratedExposedModules LibrarySection
a forall a. Semigroup a => a -> a -> a
<> LibrarySection -> Maybe (List Module)
librarySectionGeneratedExposedModules LibrarySection
b
    , librarySectionOtherModules :: Maybe (List Module)
librarySectionOtherModules = LibrarySection -> Maybe (List Module)
librarySectionOtherModules LibrarySection
a forall a. Semigroup a => a -> a -> a
<> LibrarySection -> Maybe (List Module)
librarySectionOtherModules LibrarySection
b
    , librarySectionGeneratedOtherModules :: Maybe (List Module)
librarySectionGeneratedOtherModules = LibrarySection -> Maybe (List Module)
librarySectionGeneratedOtherModules LibrarySection
a forall a. Semigroup a => a -> a -> a
<> LibrarySection -> Maybe (List Module)
librarySectionGeneratedOtherModules LibrarySection
b
    , librarySectionReexportedModules :: Maybe (List String)
librarySectionReexportedModules = LibrarySection -> Maybe (List String)
librarySectionReexportedModules LibrarySection
a forall a. Semigroup a => a -> a -> a
<> LibrarySection -> Maybe (List String)
librarySectionReexportedModules LibrarySection
b
    , librarySectionSignatures :: Maybe (List String)
librarySectionSignatures = LibrarySection -> Maybe (List String)
librarySectionSignatures LibrarySection
a forall a. Semigroup a => a -> a -> a
<> LibrarySection -> Maybe (List String)
librarySectionSignatures LibrarySection
b
    }

data ExecutableSection = ExecutableSection {
  ExecutableSection -> Alias 'True "main-is" (Last String)
executableSectionMain :: Alias 'True "main-is" (Last FilePath)
, ExecutableSection -> Maybe (List Module)
executableSectionOtherModules :: Maybe (List Module)
, ExecutableSection -> Maybe (List Module)
executableSectionGeneratedOtherModules :: Maybe (List Module)
} deriving (ExecutableSection -> ExecutableSection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExecutableSection -> ExecutableSection -> Bool
$c/= :: ExecutableSection -> ExecutableSection -> Bool
== :: ExecutableSection -> ExecutableSection -> Bool
$c== :: ExecutableSection -> ExecutableSection -> Bool
Eq, Int -> ExecutableSection -> ShowS
[ExecutableSection] -> ShowS
ExecutableSection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExecutableSection] -> ShowS
$cshowList :: [ExecutableSection] -> ShowS
show :: ExecutableSection -> String
$cshow :: ExecutableSection -> String
showsPrec :: Int -> ExecutableSection -> ShowS
$cshowsPrec :: Int -> ExecutableSection -> ShowS
Show, forall x. Rep ExecutableSection x -> ExecutableSection
forall x. ExecutableSection -> Rep ExecutableSection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ExecutableSection x -> ExecutableSection
$cfrom :: forall x. ExecutableSection -> Rep ExecutableSection x
Generic, Value -> Parser ExecutableSection
forall a. (Value -> Parser a) -> FromValue a
fromValue :: Value -> Parser ExecutableSection
$cfromValue :: Value -> Parser ExecutableSection
FromValue)

instance Monoid ExecutableSection where
  mempty :: ExecutableSection
mempty = Alias 'True "main-is" (Last String)
-> Maybe (List Module) -> Maybe (List Module) -> ExecutableSection
ExecutableSection forall a. Monoid a => a
mempty forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  mappend :: ExecutableSection -> ExecutableSection -> ExecutableSection
mappend = forall a. Semigroup a => a -> a -> a
(<>)

instance Semigroup ExecutableSection where
  ExecutableSection
a <> :: ExecutableSection -> ExecutableSection -> ExecutableSection
<> ExecutableSection
b = ExecutableSection {
      executableSectionMain :: Alias 'True "main-is" (Last String)
executableSectionMain = ExecutableSection -> Alias 'True "main-is" (Last String)
executableSectionMain ExecutableSection
a forall a. Semigroup a => a -> a -> a
<> ExecutableSection -> Alias 'True "main-is" (Last String)
executableSectionMain ExecutableSection
b
    , executableSectionOtherModules :: Maybe (List Module)
executableSectionOtherModules = ExecutableSection -> Maybe (List Module)
executableSectionOtherModules ExecutableSection
a forall a. Semigroup a => a -> a -> a
<> ExecutableSection -> Maybe (List Module)
executableSectionOtherModules ExecutableSection
b
    , executableSectionGeneratedOtherModules :: Maybe (List Module)
executableSectionGeneratedOtherModules = ExecutableSection -> Maybe (List Module)
executableSectionGeneratedOtherModules ExecutableSection
a forall a. Semigroup a => a -> a -> a
<> ExecutableSection -> Maybe (List Module)
executableSectionGeneratedOtherModules ExecutableSection
b
    }

data VerbatimValue =
    VerbatimString String
  | VerbatimNumber Scientific
  | VerbatimBool Bool
  | VerbatimNull
  deriving (VerbatimValue -> VerbatimValue -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerbatimValue -> VerbatimValue -> Bool
$c/= :: VerbatimValue -> VerbatimValue -> Bool
== :: VerbatimValue -> VerbatimValue -> Bool
$c== :: VerbatimValue -> VerbatimValue -> Bool
Eq, Int -> VerbatimValue -> ShowS
[VerbatimValue] -> ShowS
VerbatimValue -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerbatimValue] -> ShowS
$cshowList :: [VerbatimValue] -> ShowS
show :: VerbatimValue -> String
$cshow :: VerbatimValue -> String
showsPrec :: Int -> VerbatimValue -> ShowS
$cshowsPrec :: Int -> VerbatimValue -> ShowS
Show)

instance FromValue VerbatimValue where
  fromValue :: Value -> Parser VerbatimValue
fromValue Value
v = case Value
v of
    String Text
s -> forall (m :: * -> *) a. Monad m => a -> m a
return (String -> VerbatimValue
VerbatimString forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
s)
    Number Scientific
n -> forall (m :: * -> *) a. Monad m => a -> m a
return (Scientific -> VerbatimValue
VerbatimNumber Scientific
n)
    Bool Bool
b -> forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> VerbatimValue
VerbatimBool Bool
b)
    Value
Null -> forall (m :: * -> *) a. Monad m => a -> m a
return VerbatimValue
VerbatimNull
    Object Object
_ -> forall {a}. Parser a
err
    Array Array
_ -> forall {a}. Parser a
err
    where
      err :: Parser a
err = forall a. String -> Value -> Parser a
typeMismatch ([String] -> String
formatOrList [String
"String", String
"Number", String
"Bool", String
"Null"]) Value
v

data Verbatim = VerbatimLiteral String | VerbatimObject (Map String VerbatimValue)
  deriving (Verbatim -> Verbatim -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Verbatim -> Verbatim -> Bool
$c/= :: Verbatim -> Verbatim -> Bool
== :: Verbatim -> Verbatim -> Bool
$c== :: Verbatim -> Verbatim -> Bool
Eq, Int -> Verbatim -> ShowS
[Verbatim] -> ShowS
Verbatim -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Verbatim] -> ShowS
$cshowList :: [Verbatim] -> ShowS
show :: Verbatim -> String
$cshow :: Verbatim -> String
showsPrec :: Int -> Verbatim -> ShowS
$cshowsPrec :: Int -> Verbatim -> ShowS
Show)

instance FromValue Verbatim where
  fromValue :: Value -> Parser Verbatim
fromValue Value
v = case Value
v of
    String Text
s -> forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Verbatim
VerbatimLiteral forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
s)
    Object Object
_ -> Map String VerbatimValue -> Verbatim
VerbatimObject forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromValue a => Value -> Parser a
fromValue Value
v
    Value
_ -> forall a. String -> Value -> Parser a
typeMismatch ([String] -> String
formatOrList [String
"String", String
"Object"]) Value
v

data CommonOptions cSources cxxSources jsSources a = CommonOptions {
  forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Alias 'True "hs-source-dirs" (Maybe (List String))
commonOptionsSourceDirs :: Alias 'True "hs-source-dirs" (Maybe (List FilePath))
, forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Alias 'True "build-depends" (Maybe Dependencies)
commonOptionsDependencies :: Alias 'True "build-depends" (Maybe Dependencies)
, forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Alias 'False "pkgconfig-depends" (Maybe (List String))
commonOptionsPkgConfigDependencies :: Alias 'False "pkgconfig-depends" (Maybe (List String))
, forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsDefaultExtensions :: Maybe (List String)
, forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsOtherExtensions :: Maybe (List String)
, forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Alias 'True "default-language" (Last (Maybe Language))
commonOptionsLanguage :: Alias 'True "default-language" (Last (Maybe Language))
, forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsGhcOptions :: Maybe (List GhcOption)
, forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsGhcProfOptions :: Maybe (List GhcProfOption)
, forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsGhcSharedOptions :: Maybe (List GhcOption)
, forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsGhcjsOptions :: Maybe (List GhcjsOption)
, forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsCppOptions :: Maybe (List CppOption)
, forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsCcOptions :: Maybe (List CcOption)
, forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a -> cSources
commonOptionsCSources :: cSources
, forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsCxxOptions :: Maybe (List CxxOption)
, forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a -> cxxSources
commonOptionsCxxSources :: cxxSources
, forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a -> jsSources
commonOptionsJsSources :: jsSources
, forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsExtraLibDirs :: Maybe (List FilePath)
, forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsExtraLibraries :: Maybe (List FilePath)
, forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsExtraFrameworksDirs :: Maybe (List FilePath)
, forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsFrameworks :: Maybe (List String)
, forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsIncludeDirs :: Maybe (List FilePath)
, forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsInstallIncludes :: Maybe (List FilePath)
, forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsLdOptions :: Maybe (List LdOption)
, forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a -> Last Bool
commonOptionsBuildable :: Last Bool
, forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe
     (List (ConditionalSection cSources cxxSources jsSources a))
commonOptionsWhen :: Maybe (List (ConditionalSection cSources cxxSources jsSources a))
, forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Alias 'True "build-tool-depends" (Maybe BuildTools)
commonOptionsBuildTools :: Alias 'True "build-tool-depends" (Maybe BuildTools)
, forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe SystemBuildTools
commonOptionsSystemBuildTools :: Maybe SystemBuildTools
, forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List Verbatim)
commonOptionsVerbatim :: Maybe (List Verbatim)
} deriving (forall a b.
a
-> CommonOptions cSources cxxSources jsSources b
-> CommonOptions cSources cxxSources jsSources a
forall a b.
(a -> b)
-> CommonOptions cSources cxxSources jsSources a
-> CommonOptions cSources cxxSources jsSources b
forall cSources cxxSources jsSources a b.
a
-> CommonOptions cSources cxxSources jsSources b
-> CommonOptions cSources cxxSources jsSources a
forall cSources cxxSources jsSources a b.
(a -> b)
-> CommonOptions cSources cxxSources jsSources a
-> CommonOptions cSources cxxSources jsSources b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b.
a
-> CommonOptions cSources cxxSources jsSources b
-> CommonOptions cSources cxxSources jsSources a
$c<$ :: forall cSources cxxSources jsSources a b.
a
-> CommonOptions cSources cxxSources jsSources b
-> CommonOptions cSources cxxSources jsSources a
fmap :: forall a b.
(a -> b)
-> CommonOptions cSources cxxSources jsSources a
-> CommonOptions cSources cxxSources jsSources b
$cfmap :: forall cSources cxxSources jsSources a b.
(a -> b)
-> CommonOptions cSources cxxSources jsSources a
-> CommonOptions cSources cxxSources jsSources b
Functor, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall cSources cxxSources jsSources a x.
Rep (CommonOptions cSources cxxSources jsSources a) x
-> CommonOptions cSources cxxSources jsSources a
forall cSources cxxSources jsSources a x.
CommonOptions cSources cxxSources jsSources a
-> Rep (CommonOptions cSources cxxSources jsSources a) x
$cto :: forall cSources cxxSources jsSources a x.
Rep (CommonOptions cSources cxxSources jsSources a) x
-> CommonOptions cSources cxxSources jsSources a
$cfrom :: forall cSources cxxSources jsSources a x.
CommonOptions cSources cxxSources jsSources a
-> Rep (CommonOptions cSources cxxSources jsSources a) x
Generic)

type ParseCommonOptions = CommonOptions ParseCSources ParseCxxSources ParseJsSources
instance FromValue a => FromValue (ParseCommonOptions a)

instance (Semigroup cSources, Semigroup cxxSources, Semigroup jsSources, Monoid cSources, Monoid cxxSources, Monoid jsSources) => Monoid (CommonOptions cSources cxxSources jsSources a) where
  mempty :: CommonOptions cSources cxxSources jsSources a
mempty = CommonOptions {
    commonOptionsSourceDirs :: Alias 'True "hs-source-dirs" (Maybe (List String))
commonOptionsSourceDirs = forall (deprecated :: Bool) (alias :: Symbol) a.
a -> Alias deprecated alias a
Alias forall a. Maybe a
Nothing
  , commonOptionsDependencies :: Alias 'True "build-depends" (Maybe Dependencies)
commonOptionsDependencies = forall (deprecated :: Bool) (alias :: Symbol) a.
a -> Alias deprecated alias a
Alias forall a. Maybe a
Nothing
  , commonOptionsPkgConfigDependencies :: Alias 'False "pkgconfig-depends" (Maybe (List String))
commonOptionsPkgConfigDependencies = forall (deprecated :: Bool) (alias :: Symbol) a.
a -> Alias deprecated alias a
Alias forall a. Maybe a
Nothing
  , commonOptionsDefaultExtensions :: Maybe (List String)
commonOptionsDefaultExtensions = forall a. Maybe a
Nothing
  , commonOptionsOtherExtensions :: Maybe (List String)
commonOptionsOtherExtensions = forall a. Maybe a
Nothing
  , commonOptionsLanguage :: Alias 'True "default-language" (Last (Maybe Language))
commonOptionsLanguage = forall a. Monoid a => a
mempty
  , commonOptionsGhcOptions :: Maybe (List String)
commonOptionsGhcOptions = forall a. Maybe a
Nothing
  , commonOptionsGhcProfOptions :: Maybe (List String)
commonOptionsGhcProfOptions = forall a. Maybe a
Nothing
  , commonOptionsGhcSharedOptions :: Maybe (List String)
commonOptionsGhcSharedOptions = forall a. Maybe a
Nothing
  , commonOptionsGhcjsOptions :: Maybe (List String)
commonOptionsGhcjsOptions = forall a. Maybe a
Nothing
  , commonOptionsCppOptions :: Maybe (List String)
commonOptionsCppOptions = forall a. Maybe a
Nothing
  , commonOptionsCcOptions :: Maybe (List String)
commonOptionsCcOptions = forall a. Maybe a
Nothing
  , commonOptionsCSources :: cSources
commonOptionsCSources = forall a. Monoid a => a
mempty
  , commonOptionsCxxOptions :: Maybe (List String)
commonOptionsCxxOptions = forall a. Maybe a
Nothing
  , commonOptionsCxxSources :: cxxSources
commonOptionsCxxSources = forall a. Monoid a => a
mempty
  , commonOptionsJsSources :: jsSources
commonOptionsJsSources = forall a. Monoid a => a
mempty
  , commonOptionsExtraLibDirs :: Maybe (List String)
commonOptionsExtraLibDirs = forall a. Maybe a
Nothing
  , commonOptionsExtraLibraries :: Maybe (List String)
commonOptionsExtraLibraries = forall a. Maybe a
Nothing
  , commonOptionsExtraFrameworksDirs :: Maybe (List String)
commonOptionsExtraFrameworksDirs = forall a. Maybe a
Nothing
  , commonOptionsFrameworks :: Maybe (List String)
commonOptionsFrameworks = forall a. Maybe a
Nothing
  , commonOptionsIncludeDirs :: Maybe (List String)
commonOptionsIncludeDirs = forall a. Maybe a
Nothing
  , commonOptionsInstallIncludes :: Maybe (List String)
commonOptionsInstallIncludes = forall a. Maybe a
Nothing
  , commonOptionsLdOptions :: Maybe (List String)
commonOptionsLdOptions = forall a. Maybe a
Nothing
  , commonOptionsBuildable :: Last Bool
commonOptionsBuildable = forall a. Monoid a => a
mempty
  , commonOptionsWhen :: Maybe (List (ConditionalSection cSources cxxSources jsSources a))
commonOptionsWhen = forall a. Maybe a
Nothing
  , commonOptionsBuildTools :: Alias 'True "build-tool-depends" (Maybe BuildTools)
commonOptionsBuildTools = forall (deprecated :: Bool) (alias :: Symbol) a.
a -> Alias deprecated alias a
Alias forall a. Maybe a
Nothing
  , commonOptionsSystemBuildTools :: Maybe SystemBuildTools
commonOptionsSystemBuildTools = forall a. Maybe a
Nothing
  , commonOptionsVerbatim :: Maybe (List Verbatim)
commonOptionsVerbatim = forall a. Maybe a
Nothing
  }
  mappend :: CommonOptions cSources cxxSources jsSources a
-> CommonOptions cSources cxxSources jsSources a
-> CommonOptions cSources cxxSources jsSources a
mappend = forall a. Semigroup a => a -> a -> a
(<>)

instance (Semigroup cSources, Semigroup cxxSources, Semigroup jsSources) => Semigroup (CommonOptions cSources cxxSources jsSources a) where
  CommonOptions cSources cxxSources jsSources a
a <> :: CommonOptions cSources cxxSources jsSources a
-> CommonOptions cSources cxxSources jsSources a
-> CommonOptions cSources cxxSources jsSources a
<> CommonOptions cSources cxxSources jsSources a
b = CommonOptions {
    commonOptionsSourceDirs :: Alias 'True "hs-source-dirs" (Maybe (List String))
commonOptionsSourceDirs = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Alias 'True "hs-source-dirs" (Maybe (List String))
commonOptionsSourceDirs CommonOptions cSources cxxSources jsSources a
a forall a. Semigroup a => a -> a -> a
<> forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Alias 'True "hs-source-dirs" (Maybe (List String))
commonOptionsSourceDirs CommonOptions cSources cxxSources jsSources a
b
  , commonOptionsDependencies :: Alias 'True "build-depends" (Maybe Dependencies)
commonOptionsDependencies = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Alias 'True "build-depends" (Maybe Dependencies)
commonOptionsDependencies CommonOptions cSources cxxSources jsSources a
b forall a. Semigroup a => a -> a -> a
<> forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Alias 'True "build-depends" (Maybe Dependencies)
commonOptionsDependencies CommonOptions cSources cxxSources jsSources a
a
  , commonOptionsPkgConfigDependencies :: Alias 'False "pkgconfig-depends" (Maybe (List String))
commonOptionsPkgConfigDependencies = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Alias 'False "pkgconfig-depends" (Maybe (List String))
commonOptionsPkgConfigDependencies CommonOptions cSources cxxSources jsSources a
a forall a. Semigroup a => a -> a -> a
<> forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Alias 'False "pkgconfig-depends" (Maybe (List String))
commonOptionsPkgConfigDependencies CommonOptions cSources cxxSources jsSources a
b
  , commonOptionsDefaultExtensions :: Maybe (List String)
commonOptionsDefaultExtensions = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsDefaultExtensions CommonOptions cSources cxxSources jsSources a
a forall a. Semigroup a => a -> a -> a
<> forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsDefaultExtensions CommonOptions cSources cxxSources jsSources a
b
  , commonOptionsOtherExtensions :: Maybe (List String)
commonOptionsOtherExtensions = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsOtherExtensions CommonOptions cSources cxxSources jsSources a
a forall a. Semigroup a => a -> a -> a
<> forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsOtherExtensions CommonOptions cSources cxxSources jsSources a
b
  , commonOptionsLanguage :: Alias 'True "default-language" (Last (Maybe Language))
commonOptionsLanguage = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Alias 'True "default-language" (Last (Maybe Language))
commonOptionsLanguage CommonOptions cSources cxxSources jsSources a
a forall a. Semigroup a => a -> a -> a
<> forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Alias 'True "default-language" (Last (Maybe Language))
commonOptionsLanguage CommonOptions cSources cxxSources jsSources a
b
  , commonOptionsGhcOptions :: Maybe (List String)
commonOptionsGhcOptions = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsGhcOptions CommonOptions cSources cxxSources jsSources a
a forall a. Semigroup a => a -> a -> a
<> forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsGhcOptions CommonOptions cSources cxxSources jsSources a
b
  , commonOptionsGhcProfOptions :: Maybe (List String)
commonOptionsGhcProfOptions = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsGhcProfOptions CommonOptions cSources cxxSources jsSources a
a forall a. Semigroup a => a -> a -> a
<> forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsGhcProfOptions CommonOptions cSources cxxSources jsSources a
b
  , commonOptionsGhcSharedOptions :: Maybe (List String)
commonOptionsGhcSharedOptions = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsGhcSharedOptions CommonOptions cSources cxxSources jsSources a
a forall a. Semigroup a => a -> a -> a
<> forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsGhcSharedOptions CommonOptions cSources cxxSources jsSources a
b
  , commonOptionsGhcjsOptions :: Maybe (List String)
commonOptionsGhcjsOptions = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsGhcjsOptions CommonOptions cSources cxxSources jsSources a
a forall a. Semigroup a => a -> a -> a
<> forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsGhcjsOptions CommonOptions cSources cxxSources jsSources a
b
  , commonOptionsCppOptions :: Maybe (List String)
commonOptionsCppOptions = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsCppOptions CommonOptions cSources cxxSources jsSources a
a forall a. Semigroup a => a -> a -> a
<> forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsCppOptions CommonOptions cSources cxxSources jsSources a
b
  , commonOptionsCcOptions :: Maybe (List String)
commonOptionsCcOptions = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsCcOptions CommonOptions cSources cxxSources jsSources a
a forall a. Semigroup a => a -> a -> a
<> forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsCcOptions CommonOptions cSources cxxSources jsSources a
b
  , commonOptionsCSources :: cSources
commonOptionsCSources = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a -> cSources
commonOptionsCSources CommonOptions cSources cxxSources jsSources a
a forall a. Semigroup a => a -> a -> a
<> forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a -> cSources
commonOptionsCSources CommonOptions cSources cxxSources jsSources a
b
  , commonOptionsCxxOptions :: Maybe (List String)
commonOptionsCxxOptions = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsCxxOptions CommonOptions cSources cxxSources jsSources a
a forall a. Semigroup a => a -> a -> a
<> forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsCxxOptions CommonOptions cSources cxxSources jsSources a
b
  , commonOptionsCxxSources :: cxxSources
commonOptionsCxxSources = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a -> cxxSources
commonOptionsCxxSources CommonOptions cSources cxxSources jsSources a
a forall a. Semigroup a => a -> a -> a
<> forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a -> cxxSources
commonOptionsCxxSources CommonOptions cSources cxxSources jsSources a
b
  , commonOptionsJsSources :: jsSources
commonOptionsJsSources = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a -> jsSources
commonOptionsJsSources CommonOptions cSources cxxSources jsSources a
a forall a. Semigroup a => a -> a -> a
<> forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a -> jsSources
commonOptionsJsSources CommonOptions cSources cxxSources jsSources a
b
  , commonOptionsExtraLibDirs :: Maybe (List String)
commonOptionsExtraLibDirs = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsExtraLibDirs CommonOptions cSources cxxSources jsSources a
a forall a. Semigroup a => a -> a -> a
<> forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsExtraLibDirs CommonOptions cSources cxxSources jsSources a
b
  , commonOptionsExtraLibraries :: Maybe (List String)
commonOptionsExtraLibraries = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsExtraLibraries CommonOptions cSources cxxSources jsSources a
a forall a. Semigroup a => a -> a -> a
<> forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsExtraLibraries CommonOptions cSources cxxSources jsSources a
b
  , commonOptionsExtraFrameworksDirs :: Maybe (List String)
commonOptionsExtraFrameworksDirs = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsExtraFrameworksDirs CommonOptions cSources cxxSources jsSources a
a forall a. Semigroup a => a -> a -> a
<> forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsExtraFrameworksDirs CommonOptions cSources cxxSources jsSources a
b
  , commonOptionsFrameworks :: Maybe (List String)
commonOptionsFrameworks = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsFrameworks CommonOptions cSources cxxSources jsSources a
a forall a. Semigroup a => a -> a -> a
<> forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsFrameworks CommonOptions cSources cxxSources jsSources a
b
  , commonOptionsIncludeDirs :: Maybe (List String)
commonOptionsIncludeDirs = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsIncludeDirs CommonOptions cSources cxxSources jsSources a
a forall a. Semigroup a => a -> a -> a
<> forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsIncludeDirs CommonOptions cSources cxxSources jsSources a
b
  , commonOptionsInstallIncludes :: Maybe (List String)
commonOptionsInstallIncludes = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsInstallIncludes CommonOptions cSources cxxSources jsSources a
a forall a. Semigroup a => a -> a -> a
<> forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsInstallIncludes CommonOptions cSources cxxSources jsSources a
b
  , commonOptionsLdOptions :: Maybe (List String)
commonOptionsLdOptions = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsLdOptions CommonOptions cSources cxxSources jsSources a
a forall a. Semigroup a => a -> a -> a
<> forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsLdOptions CommonOptions cSources cxxSources jsSources a
b
  , commonOptionsBuildable :: Last Bool
commonOptionsBuildable = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a -> Last Bool
commonOptionsBuildable CommonOptions cSources cxxSources jsSources a
a forall a. Semigroup a => a -> a -> a
<> forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a -> Last Bool
commonOptionsBuildable CommonOptions cSources cxxSources jsSources a
b
  , commonOptionsWhen :: Maybe (List (ConditionalSection cSources cxxSources jsSources a))
commonOptionsWhen = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe
     (List (ConditionalSection cSources cxxSources jsSources a))
commonOptionsWhen CommonOptions cSources cxxSources jsSources a
a forall a. Semigroup a => a -> a -> a
<> forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe
     (List (ConditionalSection cSources cxxSources jsSources a))
commonOptionsWhen CommonOptions cSources cxxSources jsSources a
b
  , commonOptionsBuildTools :: Alias 'True "build-tool-depends" (Maybe BuildTools)
commonOptionsBuildTools = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Alias 'True "build-tool-depends" (Maybe BuildTools)
commonOptionsBuildTools CommonOptions cSources cxxSources jsSources a
a forall a. Semigroup a => a -> a -> a
<> forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Alias 'True "build-tool-depends" (Maybe BuildTools)
commonOptionsBuildTools CommonOptions cSources cxxSources jsSources a
b
  , commonOptionsSystemBuildTools :: Maybe SystemBuildTools
commonOptionsSystemBuildTools = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe SystemBuildTools
commonOptionsSystemBuildTools CommonOptions cSources cxxSources jsSources a
b forall a. Semigroup a => a -> a -> a
<> forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe SystemBuildTools
commonOptionsSystemBuildTools CommonOptions cSources cxxSources jsSources a
a
  , commonOptionsVerbatim :: Maybe (List Verbatim)
commonOptionsVerbatim = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List Verbatim)
commonOptionsVerbatim CommonOptions cSources cxxSources jsSources a
a forall a. Semigroup a => a -> a -> a
<> forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List Verbatim)
commonOptionsVerbatim CommonOptions cSources cxxSources jsSources a
b
  }

type ParseCSources = Maybe (List FilePath)
type ParseCxxSources = Maybe (List FilePath)
type ParseJsSources = Maybe (List FilePath)

type CSources = [Path]
type CxxSources = [Path]
type JsSources = [Path]

type WithCommonOptions cSources cxxSources jsSources a = Product (CommonOptions cSources cxxSources jsSources a) a

data Traverse m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_ = Traverse {
  forall (m :: * -> *) cSources cSources_ cxxSources cxxSources_
       jsSources jsSources_.
Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
-> cSources -> m cSources_
traverseCSources :: cSources -> m cSources_
, forall (m :: * -> *) cSources cSources_ cxxSources cxxSources_
       jsSources jsSources_.
Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
-> cxxSources -> m cxxSources_
traverseCxxSources :: cxxSources -> m cxxSources_
, forall (m :: * -> *) cSources cSources_ cxxSources cxxSources_
       jsSources jsSources_.
Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
-> jsSources -> m jsSources_
traverseJsSources :: jsSources -> m jsSources_
}

type Traversal t = forall m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_. Monad m
  => Traverse m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
  -> t cSources cxxSources jsSources
  -> m (t cSources_ cxxSources_ jsSources_)

type Traversal_ t = forall m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_ a. Monad m
  => Traverse m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
  -> t cSources cxxSources jsSources a
  -> m (t cSources_ cxxSources_ jsSources_ a)

traverseCommonOptions :: Traversal_ CommonOptions
traverseCommonOptions :: Traversal_ CommonOptions
traverseCommonOptions t :: Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
t@Traverse{cSources -> m cSources_
cxxSources -> m cxxSources_
jsSources -> m jsSources_
traverseJsSources :: jsSources -> m jsSources_
traverseCxxSources :: cxxSources -> m cxxSources_
traverseCSources :: cSources -> m cSources_
traverseJsSources :: forall (m :: * -> *) cSources cSources_ cxxSources cxxSources_
       jsSources jsSources_.
Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
-> jsSources -> m jsSources_
traverseCxxSources :: forall (m :: * -> *) cSources cSources_ cxxSources cxxSources_
       jsSources jsSources_.
Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
-> cxxSources -> m cxxSources_
traverseCSources :: forall (m :: * -> *) cSources cSources_ cxxSources cxxSources_
       jsSources jsSources_.
Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
-> cSources -> m cSources_
..} c :: CommonOptions cSources cxxSources jsSources a
c@CommonOptions{cSources
cxxSources
jsSources
Maybe (List String)
Maybe (List (ConditionalSection cSources cxxSources jsSources a))
Maybe (List Verbatim)
Maybe SystemBuildTools
Last Bool
Alias 'False "pkgconfig-depends" (Maybe (List String))
Alias 'True "hs-source-dirs" (Maybe (List String))
Alias 'True "build-depends" (Maybe Dependencies)
Alias 'True "default-language" (Last (Maybe Language))
Alias 'True "build-tool-depends" (Maybe BuildTools)
commonOptionsVerbatim :: Maybe (List Verbatim)
commonOptionsSystemBuildTools :: Maybe SystemBuildTools
commonOptionsBuildTools :: Alias 'True "build-tool-depends" (Maybe BuildTools)
commonOptionsWhen :: Maybe (List (ConditionalSection cSources cxxSources jsSources a))
commonOptionsBuildable :: Last Bool
commonOptionsLdOptions :: Maybe (List String)
commonOptionsInstallIncludes :: Maybe (List String)
commonOptionsIncludeDirs :: Maybe (List String)
commonOptionsFrameworks :: Maybe (List String)
commonOptionsExtraFrameworksDirs :: Maybe (List String)
commonOptionsExtraLibraries :: Maybe (List String)
commonOptionsExtraLibDirs :: Maybe (List String)
commonOptionsJsSources :: jsSources
commonOptionsCxxSources :: cxxSources
commonOptionsCxxOptions :: Maybe (List String)
commonOptionsCSources :: cSources
commonOptionsCcOptions :: Maybe (List String)
commonOptionsCppOptions :: Maybe (List String)
commonOptionsGhcjsOptions :: Maybe (List String)
commonOptionsGhcSharedOptions :: Maybe (List String)
commonOptionsGhcProfOptions :: Maybe (List String)
commonOptionsGhcOptions :: Maybe (List String)
commonOptionsLanguage :: Alias 'True "default-language" (Last (Maybe Language))
commonOptionsOtherExtensions :: Maybe (List String)
commonOptionsDefaultExtensions :: Maybe (List String)
commonOptionsPkgConfigDependencies :: Alias 'False "pkgconfig-depends" (Maybe (List String))
commonOptionsDependencies :: Alias 'True "build-depends" (Maybe Dependencies)
commonOptionsSourceDirs :: Alias 'True "hs-source-dirs" (Maybe (List String))
commonOptionsVerbatim :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List Verbatim)
commonOptionsSystemBuildTools :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe SystemBuildTools
commonOptionsBuildTools :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Alias 'True "build-tool-depends" (Maybe BuildTools)
commonOptionsWhen :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe
     (List (ConditionalSection cSources cxxSources jsSources a))
commonOptionsBuildable :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a -> Last Bool
commonOptionsLdOptions :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsInstallIncludes :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsIncludeDirs :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsFrameworks :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsExtraFrameworksDirs :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsExtraLibraries :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsExtraLibDirs :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsJsSources :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a -> jsSources
commonOptionsCxxSources :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a -> cxxSources
commonOptionsCxxOptions :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsCSources :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a -> cSources
commonOptionsCcOptions :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsCppOptions :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsGhcjsOptions :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsGhcSharedOptions :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsGhcProfOptions :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsGhcOptions :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsLanguage :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Alias 'True "default-language" (Last (Maybe Language))
commonOptionsOtherExtensions :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsDefaultExtensions :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsPkgConfigDependencies :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Alias 'False "pkgconfig-depends" (Maybe (List String))
commonOptionsDependencies :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Alias 'True "build-depends" (Maybe Dependencies)
commonOptionsSourceDirs :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Alias 'True "hs-source-dirs" (Maybe (List String))
..} = do
  cSources_
cSources <- cSources -> m cSources_
traverseCSources cSources
commonOptionsCSources
  cxxSources_
cxxSources <- cxxSources -> m cxxSources_
traverseCxxSources cxxSources
commonOptionsCxxSources
  jsSources_
jsSources <- jsSources -> m jsSources_
traverseJsSources jsSources
commonOptionsJsSources
  Maybe
  (List (ConditionalSection cSources_ cxxSources_ jsSources_ a))
xs <- forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (Traversal_ ConditionalSection
traverseConditionalSection Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
t)) Maybe (List (ConditionalSection cSources cxxSources jsSources a))
commonOptionsWhen
  forall (m :: * -> *) a. Monad m => a -> m a
return CommonOptions cSources cxxSources jsSources a
c {
      commonOptionsCSources :: cSources_
commonOptionsCSources = cSources_
cSources
    , commonOptionsCxxSources :: cxxSources_
commonOptionsCxxSources = cxxSources_
cxxSources
    , commonOptionsJsSources :: jsSources_
commonOptionsJsSources = jsSources_
jsSources
    , commonOptionsWhen :: Maybe
  (List (ConditionalSection cSources_ cxxSources_ jsSources_ a))
commonOptionsWhen = Maybe
  (List (ConditionalSection cSources_ cxxSources_ jsSources_ a))
xs
    }

traverseConditionalSection :: Traversal_ ConditionalSection
traverseConditionalSection :: Traversal_ ConditionalSection
traverseConditionalSection Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
t = \ case
  ThenElseConditional Product (ThenElse cSources cxxSources jsSources a) Condition
c -> forall cSources cxxSources jsSources a.
Product (ThenElse cSources cxxSources jsSources a) Condition
-> ConditionalSection cSources cxxSources jsSources a
ThenElseConditional forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> * -> *) (f :: * -> *) a c b d.
(Bitraversable t, Applicative f) =>
(a -> f c) -> (b -> f d) -> t a b -> f (t c d)
bitraverse (Traversal_ ThenElse
traverseThenElse Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
t) forall (m :: * -> *) a. Monad m => a -> m a
return Product (ThenElse cSources cxxSources jsSources a) Condition
c
  FlatConditional Product
  (WithCommonOptions cSources cxxSources jsSources a) Condition
c -> forall cSources cxxSources jsSources a.
Product
  (WithCommonOptions cSources cxxSources jsSources a) Condition
-> ConditionalSection cSources cxxSources jsSources a
FlatConditional forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> * -> *) (f :: * -> *) a c b d.
(Bitraversable t, Applicative f) =>
(a -> f c) -> (b -> f d) -> t a b -> f (t c d)
bitraverse (Traversal_ WithCommonOptions
traverseWithCommonOptions Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
t) forall (m :: * -> *) a. Monad m => a -> m a
return Product
  (WithCommonOptions cSources cxxSources jsSources a) Condition
c

traverseThenElse :: Traversal_ ThenElse
traverseThenElse :: Traversal_ ThenElse
traverseThenElse Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
t c :: ThenElse cSources cxxSources jsSources a
c@ThenElse{WithCommonOptions cSources cxxSources jsSources a
thenElseElse :: forall cSources cxxSources jsSources a.
ThenElse cSources cxxSources jsSources a
-> WithCommonOptions cSources cxxSources jsSources a
thenElseThen :: forall cSources cxxSources jsSources a.
ThenElse cSources cxxSources jsSources a
-> WithCommonOptions cSources cxxSources jsSources a
thenElseElse :: WithCommonOptions cSources cxxSources jsSources a
thenElseThen :: WithCommonOptions cSources cxxSources jsSources a
..} = do
  WithCommonOptions cSources_ cxxSources_ jsSources_ a
then_ <- Traversal_ WithCommonOptions
traverseWithCommonOptions Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
t WithCommonOptions cSources cxxSources jsSources a
thenElseThen
  WithCommonOptions cSources_ cxxSources_ jsSources_ a
else_ <- Traversal_ WithCommonOptions
traverseWithCommonOptions Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
t WithCommonOptions cSources cxxSources jsSources a
thenElseElse
  forall (m :: * -> *) a. Monad m => a -> m a
return ThenElse cSources cxxSources jsSources a
c{thenElseThen :: WithCommonOptions cSources_ cxxSources_ jsSources_ a
thenElseThen = WithCommonOptions cSources_ cxxSources_ jsSources_ a
then_, thenElseElse :: WithCommonOptions cSources_ cxxSources_ jsSources_ a
thenElseElse = WithCommonOptions cSources_ cxxSources_ jsSources_ a
else_}

traverseWithCommonOptions :: Traversal_ WithCommonOptions
traverseWithCommonOptions :: Traversal_ WithCommonOptions
traverseWithCommonOptions Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
t = forall (t :: * -> * -> *) (f :: * -> *) a c b d.
(Bitraversable t, Applicative f) =>
(a -> f c) -> (b -> f d) -> t a b -> f (t c d)
bitraverse (Traversal_ CommonOptions
traverseCommonOptions Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
t) forall (m :: * -> *) a. Monad m => a -> m a
return

data ConditionalSection cSources cxxSources jsSources a =
    ThenElseConditional (Product (ThenElse cSources cxxSources jsSources a) Condition)
  | FlatConditional (Product (WithCommonOptions cSources cxxSources jsSources a) Condition)

instance Functor (ConditionalSection cSources cxxSources jsSources) where
  fmap :: forall a b.
(a -> b)
-> ConditionalSection cSources cxxSources jsSources a
-> ConditionalSection cSources cxxSources jsSources b
fmap a -> b
f = \ case
    ThenElseConditional Product (ThenElse cSources cxxSources jsSources a) Condition
c -> forall cSources cxxSources jsSources a.
Product (ThenElse cSources cxxSources jsSources a) Condition
-> ConditionalSection cSources cxxSources jsSources a
ThenElseConditional (forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) Product (ThenElse cSources cxxSources jsSources a) Condition
c)
    FlatConditional Product
  (WithCommonOptions cSources cxxSources jsSources a) Condition
c -> forall cSources cxxSources jsSources a.
Product
  (WithCommonOptions cSources cxxSources jsSources a) Condition
-> ConditionalSection cSources cxxSources jsSources a
FlatConditional (forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) a -> b
f) Product
  (WithCommonOptions cSources cxxSources jsSources a) Condition
c)

type ParseConditionalSection = ConditionalSection ParseCSources ParseCxxSources ParseJsSources

instance FromValue a => FromValue (ParseConditionalSection a) where
  fromValue :: Value -> Parser (ParseConditionalSection a)
fromValue Value
v
    | Key -> Value -> Bool
hasKey Key
"then" Value
v Bool -> Bool -> Bool
|| Key -> Value -> Bool
hasKey Key
"else" Value
v = forall cSources cxxSources jsSources a.
Product (ThenElse cSources cxxSources jsSources a) Condition
-> ConditionalSection cSources cxxSources jsSources a
ThenElseConditional forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromValue a => Value -> Parser a
fromValue Value
v forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ()
giveHint
    | Bool
otherwise = forall cSources cxxSources jsSources a.
Product
  (WithCommonOptions cSources cxxSources jsSources a) Condition
-> ConditionalSection cSources cxxSources jsSources a
FlatConditional forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromValue a => Value -> Parser a
fromValue Value
v
    where
      giveHint :: Parser ()
giveHint = case Value
v of
        Object Object
o -> case (,,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall v. Key -> KeyMap v -> Maybe v
KeyMap.lookup Key
"then" Object
o forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall v. Key -> KeyMap v -> Maybe v
KeyMap.lookup Key
"else" Object
o forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall v. Key -> KeyMap v -> Maybe v
KeyMap.lookup Key
"condition" Object
o of
          Just (Object Object
then_, Object Object
else_, String Text
condition) -> do
            forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (forall v. KeyMap v -> Bool
KeyMap.null Object
then_) forall a b. (a -> b) -> a -> b
$ String
"then" String -> Value -> Parser ()
`emptyTryInstead` Value
flatElse
            forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (forall v. KeyMap v -> Bool
KeyMap.null Object
else_) forall a b. (a -> b) -> a -> b
$ String
"else" String -> Value -> Parser ()
`emptyTryInstead` Value
flatThen
            where
              flatThen :: Value
flatThen = Text -> Object -> Value
flatConditional Text
condition Object
then_
              flatElse :: Value
flatElse = Text -> Object -> Value
flatConditional (forall {a}. (Semigroup a, IsString a) => a -> a
negate_ Text
condition) Object
else_
          Maybe (Value, Value, Value)
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
        Value
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return ()

      negate_ :: a -> a
negate_ a
condition = a
"!(" forall a. Semigroup a => a -> a -> a
<> a
condition forall a. Semigroup a => a -> a -> a
<> a
")"

      flatConditional :: Text -> Object -> Value
flatConditional Text
condition Object
sect = [Pair] -> Value
object [(Key
"when" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall v. Key -> v -> KeyMap v -> KeyMap v
KeyMap.insert Key
"condition" (Text -> Value
String Text
condition) Object
sect)]

      emptyTryInstead :: String -> Value -> Parser ()
      emptyTryInstead :: String -> Value -> Parser ()
emptyTryInstead String
name Value
sect = do
        forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$ String
"an empty " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show String
name forall a. Semigroup a => a -> a -> a
<> String
" section is not allowed, try the following instead:\n\n" forall a. [a] -> [a] -> [a]
++ Value -> String
encodePretty Value
sect

      encodePretty :: Value -> String
encodePretty = Text -> String
T.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
decodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => Config -> a -> ByteString
Yaml.encodePretty Config
c
        where
          c :: Yaml.Config
          c :: Config
c = (Text -> Text -> Ordering) -> Config -> Config
Yaml.setConfCompare forall {a}. (IsString a, Ord a) => a -> a -> Ordering
f Config
Yaml.defConfig
            where
              f :: a -> a -> Ordering
f a
a a
b = case (a
a, a
b) of
                (a
"condition", a
"condition") -> Ordering
EQ
                (a
"condition", a
_) -> Ordering
LT
                (a
_, a
"condition") -> Ordering
GT
                (a, a)
_ -> forall a. Ord a => a -> a -> Ordering
compare a
a a
b

hasKey :: Key -> Value -> Bool
hasKey :: Key -> Value -> Bool
hasKey Key
key (Object Object
o) = forall a. Key -> KeyMap a -> Bool
KeyMap.member Key
key Object
o
hasKey Key
_ Value
_ = Bool
False

newtype Condition = Condition {
  Condition -> Cond
conditionCondition :: Cond
} deriving (Condition -> Condition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Condition -> Condition -> Bool
$c/= :: Condition -> Condition -> Bool
== :: Condition -> Condition -> Bool
$c== :: Condition -> Condition -> Bool
Eq, Int -> Condition -> ShowS
[Condition] -> ShowS
Condition -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Condition] -> ShowS
$cshowList :: [Condition] -> ShowS
show :: Condition -> String
$cshow :: Condition -> String
showsPrec :: Int -> Condition -> ShowS
$cshowsPrec :: Int -> Condition -> ShowS
Show, forall x. Rep Condition x -> Condition
forall x. Condition -> Rep Condition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Condition x -> Condition
$cfrom :: forall x. Condition -> Rep Condition x
Generic, Value -> Parser Condition
forall a. (Value -> Parser a) -> FromValue a
fromValue :: Value -> Parser Condition
$cfromValue :: Value -> Parser Condition
FromValue)

data Cond = CondBool Bool | CondExpression String
  deriving (Cond -> Cond -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Cond -> Cond -> Bool
$c/= :: Cond -> Cond -> Bool
== :: Cond -> Cond -> Bool
$c== :: Cond -> Cond -> Bool
Eq, Int -> Cond -> ShowS
[Cond] -> ShowS
Cond -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Cond] -> ShowS
$cshowList :: [Cond] -> ShowS
show :: Cond -> String
$cshow :: Cond -> String
showsPrec :: Int -> Cond -> ShowS
$cshowsPrec :: Int -> Cond -> ShowS
Show)

instance FromValue Cond where
  fromValue :: Value -> Parser Cond
fromValue Value
v = case Value
v of
    String Text
c -> forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Cond
CondExpression forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
c)
    Bool Bool
c -> forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> Cond
CondBool Bool
c)
    Value
_ -> forall a. String -> Value -> Parser a
typeMismatch String
"Boolean or String" Value
v

data ThenElse cSources cxxSources jsSources a = ThenElse {
  forall cSources cxxSources jsSources a.
ThenElse cSources cxxSources jsSources a
-> WithCommonOptions cSources cxxSources jsSources a
thenElseThen :: WithCommonOptions cSources cxxSources jsSources a
, forall cSources cxxSources jsSources a.
ThenElse cSources cxxSources jsSources a
-> WithCommonOptions cSources cxxSources jsSources a
thenElseElse :: WithCommonOptions cSources cxxSources jsSources a
} deriving forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall cSources cxxSources jsSources a x.
Rep (ThenElse cSources cxxSources jsSources a) x
-> ThenElse cSources cxxSources jsSources a
forall cSources cxxSources jsSources a x.
ThenElse cSources cxxSources jsSources a
-> Rep (ThenElse cSources cxxSources jsSources a) x
$cto :: forall cSources cxxSources jsSources a x.
Rep (ThenElse cSources cxxSources jsSources a) x
-> ThenElse cSources cxxSources jsSources a
$cfrom :: forall cSources cxxSources jsSources a x.
ThenElse cSources cxxSources jsSources a
-> Rep (ThenElse cSources cxxSources jsSources a) x
Generic

instance Functor (ThenElse cSources cxxSources jsSources) where
  fmap :: forall a b.
(a -> b)
-> ThenElse cSources cxxSources jsSources a
-> ThenElse cSources cxxSources jsSources b
fmap a -> b
f c :: ThenElse cSources cxxSources jsSources a
c@ThenElse{WithCommonOptions cSources cxxSources jsSources a
thenElseElse :: WithCommonOptions cSources cxxSources jsSources a
thenElseThen :: WithCommonOptions cSources cxxSources jsSources a
thenElseElse :: forall cSources cxxSources jsSources a.
ThenElse cSources cxxSources jsSources a
-> WithCommonOptions cSources cxxSources jsSources a
thenElseThen :: forall cSources cxxSources jsSources a.
ThenElse cSources cxxSources jsSources a
-> WithCommonOptions cSources cxxSources jsSources a
..} = ThenElse cSources cxxSources jsSources a
c{thenElseThen :: WithCommonOptions cSources cxxSources jsSources b
thenElseThen = WithCommonOptions cSources cxxSources jsSources a
-> WithCommonOptions cSources cxxSources jsSources b
map_ WithCommonOptions cSources cxxSources jsSources a
thenElseThen, thenElseElse :: WithCommonOptions cSources cxxSources jsSources b
thenElseElse = WithCommonOptions cSources cxxSources jsSources a
-> WithCommonOptions cSources cxxSources jsSources b
map_ WithCommonOptions cSources cxxSources jsSources a
thenElseElse}
    where
      map_ :: WithCommonOptions cSources cxxSources jsSources a
-> WithCommonOptions cSources cxxSources jsSources b
map_ = forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) a -> b
f

type ParseThenElse = ThenElse ParseCSources ParseCxxSources ParseJsSources

instance FromValue a => FromValue (ParseThenElse a)

data Empty = Empty
  deriving (Empty -> Empty -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Empty -> Empty -> Bool
$c/= :: Empty -> Empty -> Bool
== :: Empty -> Empty -> Bool
$c== :: Empty -> Empty -> Bool
Eq, Int -> Empty -> ShowS
[Empty] -> ShowS
Empty -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Empty] -> ShowS
$cshowList :: [Empty] -> ShowS
show :: Empty -> String
$cshow :: Empty -> String
showsPrec :: Int -> Empty -> ShowS
$cshowsPrec :: Int -> Empty -> ShowS
Show)

instance Monoid Empty where
  mempty :: Empty
mempty = Empty
Empty
  mappend :: Empty -> Empty -> Empty
mappend = forall a. Semigroup a => a -> a -> a
(<>)

instance Semigroup Empty where
  Empty
Empty <> :: Empty -> Empty -> Empty
<> Empty
Empty = Empty
Empty

instance FromValue Empty where
  fromValue :: Value -> Parser Empty
fromValue Value
_ = forall (m :: * -> *) a. Monad m => a -> m a
return Empty
Empty

newtype Language = Language String
  deriving (Language -> Language -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Language -> Language -> Bool
$c/= :: Language -> Language -> Bool
== :: Language -> Language -> Bool
$c== :: Language -> Language -> Bool
Eq, Int -> Language -> ShowS
[Language] -> ShowS
Language -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Language] -> ShowS
$cshowList :: [Language] -> ShowS
show :: Language -> String
$cshow :: Language -> String
showsPrec :: Int -> Language -> ShowS
$cshowsPrec :: Int -> Language -> ShowS
Show)

instance IsString Language where
  fromString :: String -> Language
fromString = String -> Language
Language

instance FromValue Language where
  fromValue :: Value -> Parser Language
fromValue = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Language
Language forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromValue a => Value -> Parser a
fromValue

data BuildType =
    Simple
  | Configure
  | Make
  | Custom
  deriving (BuildType -> BuildType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BuildType -> BuildType -> Bool
$c/= :: BuildType -> BuildType -> Bool
== :: BuildType -> BuildType -> Bool
$c== :: BuildType -> BuildType -> Bool
Eq, Int -> BuildType -> ShowS
[BuildType] -> ShowS
BuildType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BuildType] -> ShowS
$cshowList :: [BuildType] -> ShowS
show :: BuildType -> String
$cshow :: BuildType -> String
showsPrec :: Int -> BuildType -> ShowS
$cshowsPrec :: Int -> BuildType -> ShowS
Show, Int -> BuildType
BuildType -> Int
BuildType -> [BuildType]
BuildType -> BuildType
BuildType -> BuildType -> [BuildType]
BuildType -> BuildType -> BuildType -> [BuildType]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: BuildType -> BuildType -> BuildType -> [BuildType]
$cenumFromThenTo :: BuildType -> BuildType -> BuildType -> [BuildType]
enumFromTo :: BuildType -> BuildType -> [BuildType]
$cenumFromTo :: BuildType -> BuildType -> [BuildType]
enumFromThen :: BuildType -> BuildType -> [BuildType]
$cenumFromThen :: BuildType -> BuildType -> [BuildType]
enumFrom :: BuildType -> [BuildType]
$cenumFrom :: BuildType -> [BuildType]
fromEnum :: BuildType -> Int
$cfromEnum :: BuildType -> Int
toEnum :: Int -> BuildType
$ctoEnum :: Int -> BuildType
pred :: BuildType -> BuildType
$cpred :: BuildType -> BuildType
succ :: BuildType -> BuildType
$csucc :: BuildType -> BuildType
Enum, BuildType
forall a. a -> a -> Bounded a
maxBound :: BuildType
$cmaxBound :: BuildType
minBound :: BuildType
$cminBound :: BuildType
Bounded)

instance FromValue BuildType where
  fromValue :: Value -> Parser BuildType
fromValue = forall a. (Text -> Parser a) -> Value -> Parser a
withText forall a b. (a -> b) -> a -> b
$ \ (Text -> String
T.unpack -> String
t) -> do
    forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall {a}. Parser a
err forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup String
t [(String, BuildType)]
options)
    where
      err :: Parser a
err = forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"expected one of " forall a. [a] -> [a] -> [a]
++ [String] -> String
formatOrList [String]
buildTypesAsString)
      buildTypes :: [BuildType]
buildTypes = [forall a. Bounded a => a
minBound .. forall a. Bounded a => a
maxBound]
      buildTypesAsString :: [String]
buildTypesAsString = forall a b. (a -> b) -> [a] -> [b]
map forall a. Show a => a -> String
show [BuildType]
buildTypes
      options :: [(String, BuildType)]
options = forall a b. [a] -> [b] -> [(a, b)]
zip [String]
buildTypesAsString [BuildType]
buildTypes

formatOrList :: [String] -> String
formatOrList :: [String] -> String
formatOrList [String]
xs = case forall a. [a] -> [a]
reverse [String]
xs of
  [] -> String
""
  String
x : [] -> String
x
  String
y : String
x : [] -> String
x forall a. [a] -> [a] -> [a]
++ String
" or " forall a. [a] -> [a] -> [a]
++ String
y
  String
x : ys :: [String]
ys@(String
_:String
_:[String]
_) -> forall a. [a] -> [[a]] -> [a]
intercalate String
", " forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
reverse forall a b. (a -> b) -> a -> b
$ (String
"or " forall a. [a] -> [a] -> [a]
++ String
x) forall a. a -> [a] -> [a]
: [String]
ys

type SectionConfigWithDefaults cSources cxxSources jsSources a = Product DefaultsConfig (WithCommonOptions cSources cxxSources jsSources a)

type PackageConfigWithDefaults cSources cxxSources jsSources = PackageConfig_
  (SectionConfigWithDefaults cSources cxxSources jsSources LibrarySection)
  (SectionConfigWithDefaults cSources cxxSources jsSources ExecutableSection)

type PackageConfig cSources cxxSources jsSources = PackageConfig_
  (WithCommonOptions cSources cxxSources jsSources LibrarySection)
  (WithCommonOptions cSources cxxSources jsSources ExecutableSection)

data PackageVersion = PackageVersion {PackageVersion -> String
unPackageVersion :: String}

instance FromValue PackageVersion where
  fromValue :: Value -> Parser PackageVersion
fromValue Value
v = String -> PackageVersion
PackageVersion forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> case Value
v of
    Number Scientific
n -> forall (m :: * -> *) a. Monad m => a -> m a
return (Scientific -> String
scientificToVersion Scientific
n)
    String Text
s -> forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> String
T.unpack Text
s)
    Value
_ -> forall a. String -> Value -> Parser a
typeMismatch String
"Number or String" Value
v

data PackageConfig_ library executable = PackageConfig {
  forall library executable.
PackageConfig_ library executable -> Maybe String
packageConfigName :: Maybe String
, forall library executable.
PackageConfig_ library executable -> Maybe PackageVersion
packageConfigVersion :: Maybe PackageVersion
, forall library executable.
PackageConfig_ library executable -> Maybe String
packageConfigSynopsis :: Maybe String
, forall library executable.
PackageConfig_ library executable -> Maybe String
packageConfigDescription :: Maybe String
, forall library executable.
PackageConfig_ library executable -> Maybe (Maybe String)
packageConfigHomepage :: Maybe (Maybe String)
, forall library executable.
PackageConfig_ library executable -> Maybe (Maybe String)
packageConfigBugReports :: Maybe (Maybe String)
, forall library executable.
PackageConfig_ library executable -> Maybe String
packageConfigCategory :: Maybe String
, forall library executable.
PackageConfig_ library executable -> Maybe String
packageConfigStability :: Maybe String
, forall library executable.
PackageConfig_ library executable -> Maybe (List String)
packageConfigAuthor :: Maybe (List String)
, forall library executable.
PackageConfig_ library executable -> Maybe (Maybe (List String))
packageConfigMaintainer :: Maybe (Maybe (List String))
, forall library executable.
PackageConfig_ library executable -> Maybe (List String)
packageConfigCopyright :: Maybe (List String)
, forall library executable.
PackageConfig_ library executable -> Maybe BuildType
packageConfigBuildType :: Maybe BuildType
, forall library executable.
PackageConfig_ library executable -> Maybe (Maybe String)
packageConfigLicense :: Maybe (Maybe String)
, forall library executable.
PackageConfig_ library executable -> Maybe (List String)
packageConfigLicenseFile :: Maybe (List String)
, forall library executable.
PackageConfig_ library executable -> Maybe (List String)
packageConfigTestedWith :: Maybe (List String)
, forall library executable.
PackageConfig_ library executable -> Maybe (Map String FlagSection)
packageConfigFlags :: Maybe (Map String FlagSection)
, forall library executable.
PackageConfig_ library executable -> Maybe (List String)
packageConfigExtraSourceFiles :: Maybe (List FilePath)
, forall library executable.
PackageConfig_ library executable -> Maybe (List String)
packageConfigExtraDocFiles :: Maybe (List FilePath)
, forall library executable.
PackageConfig_ library executable -> Maybe (List String)
packageConfigDataFiles :: Maybe (List FilePath)
, forall library executable.
PackageConfig_ library executable -> Maybe String
packageConfigDataDir :: Maybe FilePath
, forall library executable.
PackageConfig_ library executable -> Maybe GitHub
packageConfigGithub :: Maybe GitHub
, forall library executable.
PackageConfig_ library executable -> Maybe String
packageConfigGit :: Maybe String
, forall library executable.
PackageConfig_ library executable -> Maybe CustomSetupSection
packageConfigCustomSetup :: Maybe CustomSetupSection
, forall library executable.
PackageConfig_ library executable -> Maybe library
packageConfigLibrary :: Maybe library
, forall library executable.
PackageConfig_ library executable -> Maybe (Map String library)
packageConfigInternalLibraries :: Maybe (Map String library)
, forall library executable.
PackageConfig_ library executable -> Maybe executable
packageConfigExecutable :: Maybe executable
, forall library executable.
PackageConfig_ library executable -> Maybe (Map String executable)
packageConfigExecutables :: Maybe (Map String executable)
, forall library executable.
PackageConfig_ library executable -> Maybe (Map String executable)
packageConfigTests :: Maybe (Map String executable)
, forall library executable.
PackageConfig_ library executable -> Maybe (Map String executable)
packageConfigBenchmarks :: Maybe (Map String executable)
} deriving forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall library executable x.
Rep (PackageConfig_ library executable) x
-> PackageConfig_ library executable
forall library executable x.
PackageConfig_ library executable
-> Rep (PackageConfig_ library executable) x
$cto :: forall library executable x.
Rep (PackageConfig_ library executable) x
-> PackageConfig_ library executable
$cfrom :: forall library executable x.
PackageConfig_ library executable
-> Rep (PackageConfig_ library executable) x
Generic

data GitHub = GitHub {
  GitHub -> String
_gitHubOwner :: String
, GitHub -> String
_gitHubRepo :: String
, GitHub -> Maybe String
_gitHubSubdir :: Maybe String
}

instance FromValue GitHub where
  fromValue :: Value -> Parser GitHub
fromValue Value
v = do
    Text
input <- forall a. FromValue a => Value -> Parser a
fromValue Value
v
    case forall a b. (a -> b) -> [a] -> [b]
map Text -> String
T.unpack forall a b. (a -> b) -> a -> b
$ Text -> Text -> [Text]
T.splitOn Text
"/" Text
input of
      [String
owner, String
repo, String
subdir] -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ String -> String -> Maybe String -> GitHub
GitHub String
owner String
repo (forall a. a -> Maybe a
Just String
subdir)
      [String
owner, String
repo] -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ String -> String -> Maybe String -> GitHub
GitHub String
owner String
repo forall a. Maybe a
Nothing
      [String]
_ -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$ String
"expected owner/repo or owner/repo/subdir, but encountered " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Text
input

data DefaultsConfig = DefaultsConfig {
  DefaultsConfig -> Maybe (List Defaults)
defaultsConfigDefaults :: Maybe (List Defaults)
} deriving (forall x. Rep DefaultsConfig x -> DefaultsConfig
forall x. DefaultsConfig -> Rep DefaultsConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DefaultsConfig x -> DefaultsConfig
$cfrom :: forall x. DefaultsConfig -> Rep DefaultsConfig x
Generic, Value -> Parser DefaultsConfig
forall a. (Value -> Parser a) -> FromValue a
fromValue :: Value -> Parser DefaultsConfig
$cfromValue :: Value -> Parser DefaultsConfig
FromValue)

traversePackageConfig :: Traversal PackageConfig
traversePackageConfig :: Traversal PackageConfig
traversePackageConfig Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
t p :: PackageConfig cSources cxxSources jsSources
p@PackageConfig{Maybe String
Maybe (Maybe String)
Maybe (Maybe (List String))
Maybe
  (Map
     String
     (WithCommonOptions
        cSources cxxSources jsSources ExecutableSection))
Maybe
  (Map
     String
     (WithCommonOptions cSources cxxSources jsSources LibrarySection))
Maybe (Map String FlagSection)
Maybe
  (WithCommonOptions cSources cxxSources jsSources ExecutableSection)
Maybe
  (WithCommonOptions cSources cxxSources jsSources LibrarySection)
Maybe (List String)
Maybe GitHub
Maybe PackageVersion
Maybe BuildType
Maybe CustomSetupSection
packageConfigBenchmarks :: Maybe
  (Map
     String
     (WithCommonOptions
        cSources cxxSources jsSources ExecutableSection))
packageConfigTests :: Maybe
  (Map
     String
     (WithCommonOptions
        cSources cxxSources jsSources ExecutableSection))
packageConfigExecutables :: Maybe
  (Map
     String
     (WithCommonOptions
        cSources cxxSources jsSources ExecutableSection))
packageConfigExecutable :: Maybe
  (WithCommonOptions cSources cxxSources jsSources ExecutableSection)
packageConfigInternalLibraries :: Maybe
  (Map
     String
     (WithCommonOptions cSources cxxSources jsSources LibrarySection))
packageConfigLibrary :: Maybe
  (WithCommonOptions cSources cxxSources jsSources LibrarySection)
packageConfigCustomSetup :: Maybe CustomSetupSection
packageConfigGit :: Maybe String
packageConfigGithub :: Maybe GitHub
packageConfigDataDir :: Maybe String
packageConfigDataFiles :: Maybe (List String)
packageConfigExtraDocFiles :: Maybe (List String)
packageConfigExtraSourceFiles :: Maybe (List String)
packageConfigFlags :: Maybe (Map String FlagSection)
packageConfigTestedWith :: Maybe (List String)
packageConfigLicenseFile :: Maybe (List String)
packageConfigLicense :: Maybe (Maybe String)
packageConfigBuildType :: Maybe BuildType
packageConfigCopyright :: Maybe (List String)
packageConfigMaintainer :: Maybe (Maybe (List String))
packageConfigAuthor :: Maybe (List String)
packageConfigStability :: Maybe String
packageConfigCategory :: Maybe String
packageConfigBugReports :: Maybe (Maybe String)
packageConfigHomepage :: Maybe (Maybe String)
packageConfigDescription :: Maybe String
packageConfigSynopsis :: Maybe String
packageConfigVersion :: Maybe PackageVersion
packageConfigName :: Maybe String
packageConfigBenchmarks :: forall library executable.
PackageConfig_ library executable -> Maybe (Map String executable)
packageConfigTests :: forall library executable.
PackageConfig_ library executable -> Maybe (Map String executable)
packageConfigExecutables :: forall library executable.
PackageConfig_ library executable -> Maybe (Map String executable)
packageConfigExecutable :: forall library executable.
PackageConfig_ library executable -> Maybe executable
packageConfigInternalLibraries :: forall library executable.
PackageConfig_ library executable -> Maybe (Map String library)
packageConfigLibrary :: forall library executable.
PackageConfig_ library executable -> Maybe library
packageConfigCustomSetup :: forall library executable.
PackageConfig_ library executable -> Maybe CustomSetupSection
packageConfigGit :: forall library executable.
PackageConfig_ library executable -> Maybe String
packageConfigGithub :: forall library executable.
PackageConfig_ library executable -> Maybe GitHub
packageConfigDataDir :: forall library executable.
PackageConfig_ library executable -> Maybe String
packageConfigDataFiles :: forall library executable.
PackageConfig_ library executable -> Maybe (List String)
packageConfigExtraDocFiles :: forall library executable.
PackageConfig_ library executable -> Maybe (List String)
packageConfigExtraSourceFiles :: forall library executable.
PackageConfig_ library executable -> Maybe (List String)
packageConfigFlags :: forall library executable.
PackageConfig_ library executable -> Maybe (Map String FlagSection)
packageConfigTestedWith :: forall library executable.
PackageConfig_ library executable -> Maybe (List String)
packageConfigLicenseFile :: forall library executable.
PackageConfig_ library executable -> Maybe (List String)
packageConfigLicense :: forall library executable.
PackageConfig_ library executable -> Maybe (Maybe String)
packageConfigBuildType :: forall library executable.
PackageConfig_ library executable -> Maybe BuildType
packageConfigCopyright :: forall library executable.
PackageConfig_ library executable -> Maybe (List String)
packageConfigMaintainer :: forall library executable.
PackageConfig_ library executable -> Maybe (Maybe (List String))
packageConfigAuthor :: forall library executable.
PackageConfig_ library executable -> Maybe (List String)
packageConfigStability :: forall library executable.
PackageConfig_ library executable -> Maybe String
packageConfigCategory :: forall library executable.
PackageConfig_ library executable -> Maybe String
packageConfigBugReports :: forall library executable.
PackageConfig_ library executable -> Maybe (Maybe String)
packageConfigHomepage :: forall library executable.
PackageConfig_ library executable -> Maybe (Maybe String)
packageConfigDescription :: forall library executable.
PackageConfig_ library executable -> Maybe String
packageConfigSynopsis :: forall library executable.
PackageConfig_ library executable -> Maybe String
packageConfigVersion :: forall library executable.
PackageConfig_ library executable -> Maybe PackageVersion
packageConfigName :: forall library executable.
PackageConfig_ library executable -> Maybe String
..} = do
  Maybe
  (WithCommonOptions cSources_ cxxSources_ jsSources_ LibrarySection)
library <- forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (Traversal_ WithCommonOptions
traverseWithCommonOptions Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
t) Maybe
  (WithCommonOptions cSources cxxSources jsSources LibrarySection)
packageConfigLibrary
  Maybe
  (Map
     String
     (WithCommonOptions
        cSources_ cxxSources_ jsSources_ LibrarySection))
internalLibraries <- forall {cSources} {cSources_} {cxxSources} {cxxSources_}
       {jsSources} {jsSources_} {a}.
Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
-> Maybe
     (Map String (WithCommonOptions cSources cxxSources jsSources a))
-> m (Maybe
        (Map
           String (WithCommonOptions cSources_ cxxSources_ jsSources_ a)))
traverseNamedConfigs Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
t Maybe
  (Map
     String
     (WithCommonOptions cSources cxxSources jsSources LibrarySection))
packageConfigInternalLibraries
  Maybe
  (WithCommonOptions
     cSources_ cxxSources_ jsSources_ ExecutableSection)
executable <- forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (Traversal_ WithCommonOptions
traverseWithCommonOptions Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
t) Maybe
  (WithCommonOptions cSources cxxSources jsSources ExecutableSection)
packageConfigExecutable
  Maybe
  (Map
     String
     (WithCommonOptions
        cSources_ cxxSources_ jsSources_ ExecutableSection))
executables <- forall {cSources} {cSources_} {cxxSources} {cxxSources_}
       {jsSources} {jsSources_} {a}.
Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
-> Maybe
     (Map String (WithCommonOptions cSources cxxSources jsSources a))
-> m (Maybe
        (Map
           String (WithCommonOptions cSources_ cxxSources_ jsSources_ a)))
traverseNamedConfigs Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
t Maybe
  (Map
     String
     (WithCommonOptions
        cSources cxxSources jsSources ExecutableSection))
packageConfigExecutables
  Maybe
  (Map
     String
     (WithCommonOptions
        cSources_ cxxSources_ jsSources_ ExecutableSection))
tests <- forall {cSources} {cSources_} {cxxSources} {cxxSources_}
       {jsSources} {jsSources_} {a}.
Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
-> Maybe
     (Map String (WithCommonOptions cSources cxxSources jsSources a))
-> m (Maybe
        (Map
           String (WithCommonOptions cSources_ cxxSources_ jsSources_ a)))
traverseNamedConfigs Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
t Maybe
  (Map
     String
     (WithCommonOptions
        cSources cxxSources jsSources ExecutableSection))
packageConfigTests
  Maybe
  (Map
     String
     (WithCommonOptions
        cSources_ cxxSources_ jsSources_ ExecutableSection))
benchmarks <- forall {cSources} {cSources_} {cxxSources} {cxxSources_}
       {jsSources} {jsSources_} {a}.
Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
-> Maybe
     (Map String (WithCommonOptions cSources cxxSources jsSources a))
-> m (Maybe
        (Map
           String (WithCommonOptions cSources_ cxxSources_ jsSources_ a)))
traverseNamedConfigs Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
t Maybe
  (Map
     String
     (WithCommonOptions
        cSources cxxSources jsSources ExecutableSection))
packageConfigBenchmarks
  forall (m :: * -> *) a. Monad m => a -> m a
return PackageConfig cSources cxxSources jsSources
p {
      packageConfigLibrary :: Maybe
  (WithCommonOptions cSources_ cxxSources_ jsSources_ LibrarySection)
packageConfigLibrary = Maybe
  (WithCommonOptions cSources_ cxxSources_ jsSources_ LibrarySection)
library
    , packageConfigInternalLibraries :: Maybe
  (Map
     String
     (WithCommonOptions
        cSources_ cxxSources_ jsSources_ LibrarySection))
packageConfigInternalLibraries = Maybe
  (Map
     String
     (WithCommonOptions
        cSources_ cxxSources_ jsSources_ LibrarySection))
internalLibraries
    , packageConfigExecutable :: Maybe
  (WithCommonOptions
     cSources_ cxxSources_ jsSources_ ExecutableSection)
packageConfigExecutable = Maybe
  (WithCommonOptions
     cSources_ cxxSources_ jsSources_ ExecutableSection)
executable
    , packageConfigExecutables :: Maybe
  (Map
     String
     (WithCommonOptions
        cSources_ cxxSources_ jsSources_ ExecutableSection))
packageConfigExecutables = Maybe
  (Map
     String
     (WithCommonOptions
        cSources_ cxxSources_ jsSources_ ExecutableSection))
executables
    , packageConfigTests :: Maybe
  (Map
     String
     (WithCommonOptions
        cSources_ cxxSources_ jsSources_ ExecutableSection))
packageConfigTests = Maybe
  (Map
     String
     (WithCommonOptions
        cSources_ cxxSources_ jsSources_ ExecutableSection))
tests
    , packageConfigBenchmarks :: Maybe
  (Map
     String
     (WithCommonOptions
        cSources_ cxxSources_ jsSources_ ExecutableSection))
packageConfigBenchmarks = Maybe
  (Map
     String
     (WithCommonOptions
        cSources_ cxxSources_ jsSources_ ExecutableSection))
benchmarks
    }
  where
    traverseNamedConfigs :: Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
-> Maybe
     (Map String (WithCommonOptions cSources cxxSources jsSources a))
-> m (Maybe
        (Map
           String (WithCommonOptions cSources_ cxxSources_ jsSources_ a)))
traverseNamedConfigs = forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. Traversal_ WithCommonOptions
traverseWithCommonOptions

type ParsePackageConfig = PackageConfigWithDefaults ParseCSources ParseCxxSources ParseJsSources

instance FromValue ParsePackageConfig

type Warnings m = WriterT [String] m
type Errors = ExceptT HpackError

liftEither :: IO (Either HpackError a) -> Warnings (Errors IO) a
liftEither :: forall a. IO (Either HpackError a) -> Warnings (Errors IO) a
liftEither = forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT

type FormatYamlParseError = FilePath -> Yaml.ParseException -> String

decodeYaml :: FromValue a => FormatYamlParseError -> FilePath -> Warnings (Errors IO) a
decodeYaml :: forall a.
FromValue a =>
FormatYamlParseError -> String -> Warnings (Errors IO) a
decodeYaml FormatYamlParseError
formatYamlParseError String
file = do
  ([String]
warnings, Value
a) <- forall a. IO (Either HpackError a) -> Warnings (Errors IO) a
liftEither forall a b. (a -> b) -> a -> b
$ forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (String -> HpackError
ParseError forall b c a. (b -> c) -> (a -> b) -> a -> c
. FormatYamlParseError
formatYamlParseError String
file) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO (Either ParseException ([String], Value))
Yaml.decodeYamlWithParseError String
file
  forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell [String]
warnings
  forall a. FromValue a => String -> Value -> Warnings (Errors IO) a
decodeValue String
file Value
a

data DecodeOptions = DecodeOptions {
  DecodeOptions -> ProgramName
decodeOptionsProgramName :: ProgramName
, DecodeOptions -> String
decodeOptionsTarget :: FilePath
, DecodeOptions -> Maybe String
decodeOptionsUserDataDir :: Maybe FilePath
, DecodeOptions -> String -> IO (Either String ([String], Value))
decodeOptionsDecode :: FilePath -> IO (Either String ([String], Value))
, DecodeOptions -> FormatYamlParseError
decodeOptionsFormatYamlParseError :: FilePath -> Yaml.ParseException -> String
}

defaultDecodeOptions :: DecodeOptions
defaultDecodeOptions :: DecodeOptions
defaultDecodeOptions = ProgramName
-> String
-> Maybe String
-> (String -> IO (Either String ([String], Value)))
-> FormatYamlParseError
-> DecodeOptions
DecodeOptions ProgramName
"hpack" String
packageConfig forall a. Maybe a
Nothing String -> IO (Either String ([String], Value))
Yaml.decodeYaml FormatYamlParseError
Yaml.formatYamlParseError

data DecodeResult = DecodeResult {
  DecodeResult -> Package
decodeResultPackage :: Package
, DecodeResult -> String
decodeResultCabalVersion :: String
, DecodeResult -> String
decodeResultCabalFile :: FilePath
, DecodeResult -> [String]
decodeResultWarnings :: [String]
} deriving (DecodeResult -> DecodeResult -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DecodeResult -> DecodeResult -> Bool
$c/= :: DecodeResult -> DecodeResult -> Bool
== :: DecodeResult -> DecodeResult -> Bool
$c== :: DecodeResult -> DecodeResult -> Bool
Eq, Int -> DecodeResult -> ShowS
[DecodeResult] -> ShowS
DecodeResult -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DecodeResult] -> ShowS
$cshowList :: [DecodeResult] -> ShowS
show :: DecodeResult -> String
$cshow :: DecodeResult -> String
showsPrec :: Int -> DecodeResult -> ShowS
$cshowsPrec :: Int -> DecodeResult -> ShowS
Show)

readPackageConfig :: DecodeOptions -> IO (Either String DecodeResult)
readPackageConfig :: DecodeOptions -> IO (Either String DecodeResult)
readPackageConfig DecodeOptions
options = forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (ProgramName -> HpackError -> String
formatHpackError forall a b. (a -> b) -> a -> b
$ DecodeOptions -> ProgramName
decodeOptionsProgramName DecodeOptions
options) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DecodeOptions -> IO (Either HpackError DecodeResult)
readPackageConfigWithError DecodeOptions
options

readPackageConfigWithError :: DecodeOptions -> IO (Either HpackError DecodeResult)
readPackageConfigWithError :: DecodeOptions -> IO (Either HpackError DecodeResult)
readPackageConfigWithError (DecodeOptions ProgramName
_ String
file Maybe String
mUserDataDir String -> IO (Either String ([String], Value))
readValue FormatYamlParseError
formatYamlParseError) = forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Package, String), [String]) -> DecodeResult
addCabalFile forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT forall a b. (a -> b) -> a -> b
$ do
  ([String]
warnings, Value
value) <- forall a. IO (Either HpackError a) -> Warnings (Errors IO) a
liftEither forall a b. (a -> b) -> a -> b
$ forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first String -> HpackError
ParseError forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO (Either String ([String], Value))
readValue String
file
  forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell [String]
warnings
  ConfigWithDefaults
config <- forall a. FromValue a => String -> Value -> Warnings (Errors IO) a
decodeValue String
file Value
value
  String
dir <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ ShowS
takeDirectory forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO String
canonicalizePath String
file
  String
userDataDir <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> IO String
getAppUserDataDirectory String
"hpack") forall (m :: * -> *) a. Monad m => a -> m a
return Maybe String
mUserDataDir
  FormatYamlParseError
-> String
-> String
-> ConfigWithDefaults
-> WriterT [String] (Errors IO) (Package, String)
toPackage FormatYamlParseError
formatYamlParseError String
userDataDir String
dir ConfigWithDefaults
config
  where
    addCabalFile :: ((Package, String), [String]) -> DecodeResult
    addCabalFile :: ((Package, String), [String]) -> DecodeResult
addCabalFile ((Package
pkg, String
cabalVersion), [String]
warnings) = Package -> String -> String -> [String] -> DecodeResult
DecodeResult Package
pkg String
cabalVersion (ShowS
takeDirectory_ String
file String -> ShowS
</> (Package -> String
packageName Package
pkg forall a. [a] -> [a] -> [a]
++ String
".cabal")) [String]
warnings

    takeDirectory_ :: FilePath -> FilePath
    takeDirectory_ :: ShowS
takeDirectory_ String
p
      | ShowS
takeFileName String
p forall a. Eq a => a -> a -> Bool
== String
p = String
""
      | Bool
otherwise = ShowS
takeDirectory String
p

deleteVerbatimField :: String -> [Verbatim] -> [Verbatim]
deleteVerbatimField :: String -> [Verbatim] -> [Verbatim]
deleteVerbatimField String
name = forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a -> b) -> a -> b
$ \ case
  literal :: Verbatim
literal@VerbatimLiteral {} -> Verbatim
literal
  VerbatimObject Map String VerbatimValue
o -> Map String VerbatimValue -> Verbatim
VerbatimObject (forall k a. Ord k => k -> Map k a -> Map k a
Map.delete String
name Map String VerbatimValue
o)

verbatimValueToString :: VerbatimValue -> String
verbatimValueToString :: VerbatimValue -> String
verbatimValueToString = \ case
  VerbatimString String
s -> String
s
  VerbatimNumber Scientific
n -> Scientific -> String
scientificToVersion Scientific
n
  VerbatimBool Bool
b -> forall a. Show a => a -> String
show Bool
b
  VerbatimValue
VerbatimNull -> String
""

addPathsModuleToGeneratedModules  :: Package -> Version -> Package
addPathsModuleToGeneratedModules :: Package -> Version -> Package
addPathsModuleToGeneratedModules Package
pkg Version
cabalVersion
  | Version
cabalVersion forall a. Ord a => a -> a -> Bool
< [Int] -> Version
makeVersion [Int
2] = Package
pkg
  | Bool
otherwise = Package
pkg {
      packageLibrary :: Maybe (Section Library)
packageLibrary = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Library -> Library
mapLibrary forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Package -> Maybe (Section Library)
packageLibrary Package
pkg
    , packageInternalLibraries :: Map String (Section Library)
packageInternalLibraries = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Library -> Library
mapLibrary forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Package -> Map String (Section Library)
packageInternalLibraries Package
pkg
    , packageExecutables :: Map String (Section Executable)
packageExecutables = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Executable -> Executable
mapExecutable forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Package -> Map String (Section Executable)
packageExecutables Package
pkg
    , packageTests :: Map String (Section Executable)
packageTests = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Executable -> Executable
mapExecutable forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Package -> Map String (Section Executable)
packageTests Package
pkg
    , packageBenchmarks :: Map String (Section Executable)
packageBenchmarks = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Executable -> Executable
mapExecutable forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Package -> Map String (Section Executable)
packageBenchmarks Package
pkg
    }
  where
    pathsModule :: Module
pathsModule = String -> Module
pathsModuleFromPackageName (Package -> String
packageName Package
pkg)

    mapLibrary :: Library -> Library
    mapLibrary :: Library -> Library
mapLibrary Library
lib
      | Module
pathsModule forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` Library -> [Module]
getLibraryModules Library
lib = Library
lib {
          libraryGeneratedModules :: [Module]
libraryGeneratedModules = if Module
pathsModule forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Module]
generatedModules then [Module]
generatedModules else Module
pathsModule forall a. a -> [a] -> [a]
: [Module]
generatedModules
        }
      | Bool
otherwise = Library
lib
      where
        generatedModules :: [Module]
generatedModules = Library -> [Module]
libraryGeneratedModules Library
lib

    mapExecutable :: Executable -> Executable
    mapExecutable :: Executable -> Executable
mapExecutable Executable
executable
      | Module
pathsModule forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` Executable -> [Module]
executableOtherModules Executable
executable = Executable
executable {
          executableGeneratedModules :: [Module]
executableGeneratedModules = if Module
pathsModule forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Module]
generatedModules then [Module]
generatedModules else Module
pathsModule forall a. a -> [a] -> [a]
: [Module]
generatedModules
        }
      | Bool
otherwise = Executable
executable
      where
        generatedModules :: [Module]
generatedModules = Executable -> [Module]
executableGeneratedModules Executable
executable

determineCabalVersion :: Maybe (License SPDX.License) -> Package -> (Package, String, Maybe Version)
determineCabalVersion :: Maybe (License License)
-> Package -> (Package, String, Maybe Version)
determineCabalVersion Maybe (License License)
inferredLicense pkg :: Package
pkg@Package{String
[String]
[Path]
[Flag]
[Verbatim]
Maybe String
Maybe SourceRepository
Maybe (Section Library)
Maybe CustomSetup
Map String (Section Executable)
Map String (Section Library)
BuildType
packageVerbatim :: [Verbatim]
packageBenchmarks :: Map String (Section Executable)
packageTests :: Map String (Section Executable)
packageExecutables :: Map String (Section Executable)
packageInternalLibraries :: Map String (Section Library)
packageLibrary :: Maybe (Section Library)
packageCustomSetup :: Maybe CustomSetup
packageSourceRepository :: Maybe SourceRepository
packageDataDir :: Maybe String
packageDataFiles :: [Path]
packageExtraDocFiles :: [Path]
packageExtraSourceFiles :: [Path]
packageFlags :: [Flag]
packageTestedWith :: [String]
packageLicenseFile :: [String]
packageLicense :: Maybe String
packageBuildType :: BuildType
packageCopyright :: [String]
packageMaintainer :: [String]
packageAuthor :: [String]
packageStability :: Maybe String
packageCategory :: Maybe String
packageBugReports :: Maybe String
packageHomepage :: Maybe String
packageDescription :: Maybe String
packageSynopsis :: Maybe String
packageVersion :: String
packageName :: String
packageVerbatim :: Package -> [Verbatim]
packageBenchmarks :: Package -> Map String (Section Executable)
packageTests :: Package -> Map String (Section Executable)
packageExecutables :: Package -> Map String (Section Executable)
packageInternalLibraries :: Package -> Map String (Section Library)
packageLibrary :: Package -> Maybe (Section Library)
packageCustomSetup :: Package -> Maybe CustomSetup
packageSourceRepository :: Package -> Maybe SourceRepository
packageDataDir :: Package -> Maybe String
packageDataFiles :: Package -> [Path]
packageExtraDocFiles :: Package -> [Path]
packageExtraSourceFiles :: Package -> [Path]
packageFlags :: Package -> [Flag]
packageTestedWith :: Package -> [String]
packageLicenseFile :: Package -> [String]
packageLicense :: Package -> Maybe String
packageBuildType :: Package -> BuildType
packageCopyright :: Package -> [String]
packageMaintainer :: Package -> [String]
packageAuthor :: Package -> [String]
packageStability :: Package -> Maybe String
packageCategory :: Package -> Maybe String
packageBugReports :: Package -> Maybe String
packageHomepage :: Package -> Maybe String
packageDescription :: Package -> Maybe String
packageSynopsis :: Package -> Maybe String
packageVersion :: Package -> String
packageName :: Package -> String
..} = (
    Package
pkg {
        packageVerbatim :: [Verbatim]
packageVerbatim = String -> [Verbatim] -> [Verbatim]
deleteVerbatimField String
"cabal-version" [Verbatim]
packageVerbatim
      , packageLicense :: Maybe String
packageLicense = License String -> String
formatLicense forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (License String)
license
      }
  , String
"cabal-version: " forall a. [a] -> [a] -> [a]
++ String
effectiveCabalVersion forall a. [a] -> [a] -> [a]
++ String
"\n\n"
  , String -> Maybe Version
parseVersion String
effectiveCabalVersion
  )
  where
    effectiveCabalVersion :: String
effectiveCabalVersion = forall a. a -> Maybe a -> a
fromMaybe String
inferredCabalVersion Maybe String
verbatimCabalVersion

    license :: Maybe (License String)
license = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Pretty a => a -> String
prettyShow forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Maybe (License License)
parsedLicense forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe (License License)
inferredLicense)

    parsedLicense :: Maybe (License License)
parsedLicense = String -> License License
parseLicense forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String
packageLicense

    formatLicense :: License String -> String
formatLicense = \ case
      MustSPDX String
spdx -> String
spdx
      CanSPDX License
_ String
spdx | Version
version forall a. Ord a => a -> a -> Bool
>= [Int] -> Version
makeVersion [Int
2,Int
2] -> String
spdx
      CanSPDX License
cabal String
_ -> forall a. Pretty a => a -> String
prettyShow License
cabal
      DontTouch String
original -> String
original

    mustSPDX :: Bool
    mustSPDX :: Bool
mustSPDX = forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False forall {a}. License a -> Bool
f Maybe (License String)
license
      where
        f :: License a -> Bool
f = \case
          DontTouch String
_ -> Bool
False
          CanSPDX License
_ a
_ -> Bool
False
          MustSPDX a
_ -> Bool
True

    verbatimCabalVersion :: Maybe String
    verbatimCabalVersion :: Maybe String
verbatimCabalVersion = forall a. [a] -> Maybe a
listToMaybe (forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Verbatim -> Maybe String
f [Verbatim]
packageVerbatim)
      where
        f :: Verbatim -> Maybe String
        f :: Verbatim -> Maybe String
f = \ case
          VerbatimLiteral String
_ -> forall a. Maybe a
Nothing
          VerbatimObject Map String VerbatimValue
o -> case forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup String
"cabal-version" Map String VerbatimValue
o of
            Just VerbatimValue
v -> forall a. a -> Maybe a
Just (VerbatimValue -> String
verbatimValueToString VerbatimValue
v)
            Maybe VerbatimValue
Nothing -> forall a. Maybe a
Nothing

    inferredCabalVersion :: String
    inferredCabalVersion :: String
inferredCabalVersion = Version -> String
showVersion Version
version

    version :: Version
version = forall a. a -> Maybe a -> a
fromMaybe ([Int] -> Version
makeVersion [Int
1,Int
12]) forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum [
        Maybe Version
packageCabalVersion
      , Maybe (Section Library)
packageLibrary forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Section Library -> Maybe Version
libraryCabalVersion
      , Map String (Section Library) -> Maybe Version
internalLibsCabalVersion Map String (Section Library)
packageInternalLibraries
      , Map String (Section Executable) -> Maybe Version
executablesCabalVersion Map String (Section Executable)
packageExecutables
      , Map String (Section Executable) -> Maybe Version
executablesCabalVersion Map String (Section Executable)
packageTests
      , Map String (Section Executable) -> Maybe Version
executablesCabalVersion Map String (Section Executable)
packageBenchmarks
      ]

    packageCabalVersion :: Maybe Version
    packageCabalVersion :: Maybe Version
packageCabalVersion = forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum [
        forall a. Maybe a
Nothing
      , [Int] -> Version
makeVersion [Int
2,Int
2] forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ forall (f :: * -> *). Alternative f => Bool -> f ()
guard Bool
mustSPDX
      , [Int] -> Version
makeVersion [Int
1,Int
24] forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Maybe CustomSetup
packageCustomSetup
      , [Int] -> Version
makeVersion [Int
1,Int
18] forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Path]
packageExtraDocFiles))
      ]

    libraryCabalVersion :: Section Library -> Maybe Version
    libraryCabalVersion :: Section Library -> Maybe Version
libraryCabalVersion Section Library
sect = forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum [
        [Int] -> Version
makeVersion [Int
1,Int
22] forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ forall (f :: * -> *). Alternative f => Bool -> f ()
guard (forall {t :: * -> *} {a}. Foldable t => (Library -> t a) -> Bool
has Library -> [String]
libraryReexportedModules)
      , [Int] -> Version
makeVersion [Int
2,Int
0]  forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ forall (f :: * -> *). Alternative f => Bool -> f ()
guard (forall {t :: * -> *} {a}. Foldable t => (Library -> t a) -> Bool
has Library -> [String]
librarySignatures)
      , [Int] -> Version
makeVersion [Int
2,Int
0] forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ forall (f :: * -> *). Alternative f => Bool -> f ()
guard (forall {t :: * -> *} {a}. Foldable t => (Library -> t a) -> Bool
has Library -> [Module]
libraryGeneratedModules)
      , [Int] -> Version
makeVersion [Int
3,Int
0] forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ forall (f :: * -> *). Alternative f => Bool -> f ()
guard (forall {t :: * -> *} {a}. Foldable t => (Library -> t a) -> Bool
has Library -> Maybe String
libraryVisibility)
      , forall a. (Section a -> [Module]) -> Section a -> Maybe Version
sectionCabalVersion (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Library -> [Module]
getLibraryModules) Section Library
sect
      ]
      where
        has :: (Library -> t a) -> Bool
has Library -> t a
field = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall b c a. (b -> c) -> (a -> b) -> a -> c
. Library -> t a
field) Section Library
sect

    internalLibsCabalVersion :: Map String (Section Library) -> Maybe Version
    internalLibsCabalVersion :: Map String (Section Library) -> Maybe Version
internalLibsCabalVersion Map String (Section Library)
internalLibraries
      | forall k a. Map k a -> Bool
Map.null Map String (Section Library)
internalLibraries = forall a. Maybe a
Nothing
      | Bool
otherwise = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall a. Ord a => a -> a -> a
max (forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ [Int] -> Version
makeVersion [Int
2,Int
0]) [Maybe Version]
versions
      where
        versions :: [Maybe Version]
versions = Section Library -> Maybe Version
libraryCabalVersion forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall k a. Map k a -> [a]
Map.elems Map String (Section Library)
internalLibraries

    executablesCabalVersion :: Map String (Section Executable) -> Maybe Version
    executablesCabalVersion :: Map String (Section Executable) -> Maybe Version
executablesCabalVersion = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall a. Ord a => a -> a -> a
max forall a. Maybe a
Nothing forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map Section Executable -> Maybe Version
executableCabalVersion forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k a. Map k a -> [a]
Map.elems

    executableCabalVersion :: Section Executable -> Maybe Version
    executableCabalVersion :: Section Executable -> Maybe Version
executableCabalVersion Section Executable
sect = forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum [
        [Int] -> Version
makeVersion [Int
2,Int
0] forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Section Executable -> Bool
executableHasGeneratedModules Section Executable
sect)
      , forall a. (Section a -> [Module]) -> Section a -> Maybe Version
sectionCabalVersion (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Executable -> [Module]
getExecutableModules) Section Executable
sect
      ]

    executableHasGeneratedModules :: Section Executable -> Bool
    executableHasGeneratedModules :: Section Executable -> Bool
executableHasGeneratedModules = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall b c a. (b -> c) -> (a -> b) -> a -> c
. Executable -> [Module]
executableGeneratedModules)

    sectionCabalVersion :: (Section a -> [Module]) -> Section a -> Maybe Version
    sectionCabalVersion :: forall a. (Section a -> [Module]) -> Section a -> Maybe Version
sectionCabalVersion Section a -> [Module]
getMentionedModules Section a
sect = forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum forall a b. (a -> b) -> a -> b
$ [
        [Int] -> Version
makeVersion [Int
2,Int
2] forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ forall (f :: * -> *). Alternative f => Bool -> f ()
guard (forall a. (Section a -> Bool) -> Section a -> Bool
sectionSatisfies (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Section a -> [Path]
sectionCxxSources) Section a
sect)
      , [Int] -> Version
makeVersion [Int
2,Int
2] forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ forall (f :: * -> *). Alternative f => Bool -> f ()
guard (forall a. (Section a -> Bool) -> Section a -> Bool
sectionSatisfies (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Section a -> [String]
sectionCxxOptions) Section a
sect)
      , [Int] -> Version
makeVersion [Int
2,Int
0] forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ forall (f :: * -> *). Alternative f => Bool -> f ()
guard (forall a. (Section a -> Bool) -> Section a -> Bool
sectionSatisfies (forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any DependencyInfo -> Bool
hasMixins forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dependencies -> Map String DependencyInfo
unDependencies forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Section a -> Dependencies
sectionDependencies) Section a
sect)
      , [Int] -> Version
makeVersion [Int
3,Int
0] forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ forall (f :: * -> *). Alternative f => Bool -> f ()
guard (forall a. (Section a -> Bool) -> Section a -> Bool
sectionSatisfies (forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any String -> Bool
hasSubcomponents forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k a. Map k a -> [k]
Map.keys forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dependencies -> Map String DependencyInfo
unDependencies forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Section a -> Dependencies
sectionDependencies) Section a
sect)
      , [Int] -> Version
makeVersion [Int
2,Int
2] forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ forall (f :: * -> *). Alternative f => Bool -> f ()
guard (
              String -> Bool
uses String
"RebindableSyntax"
          Bool -> Bool -> Bool
&& (String -> Bool
uses String
"OverloadedStrings" Bool -> Bool -> Bool
|| String -> Bool
uses String
"OverloadedLists")
          Bool -> Bool -> Bool
&& Module
pathsModule forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` Section a -> [Module]
getMentionedModules Section a
sect)
      ] forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map String -> Maybe Version
versionFromSystemBuildTool [String]
systemBuildTools
      where
        defaultExtensions :: [String]
defaultExtensions = forall b a.
(Semigroup b, Monoid b) =>
(Section a -> b) -> Section a -> b
sectionAll forall a. Section a -> [String]
sectionDefaultExtensions Section a
sect
        uses :: String -> Bool
uses = (forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
defaultExtensions)

        pathsModule :: Module
pathsModule = String -> Module
pathsModuleFromPackageName String
packageName

        versionFromSystemBuildTool :: String -> Maybe Version
versionFromSystemBuildTool String
name
          | String
name forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
known_1_10 = forall a. Maybe a
Nothing
          | String
name forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
known_1_14 = forall a. a -> Maybe a
Just ([Int] -> Version
makeVersion [Int
1,Int
14])
          | String
name forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
known_1_22 = forall a. a -> Maybe a
Just ([Int] -> Version
makeVersion [Int
1,Int
22])
          | Bool
otherwise = forall a. a -> Maybe a
Just ([Int] -> Version
makeVersion [Int
2,Int
0])

        known_1_10 :: [String]
known_1_10 = [
            String
"ghc"
          , String
"ghc-pkg"
          , String
"hugs"
          , String
"ffihugs"
          , String
"nhc98"
          , String
"hmake"
          , String
"jhc"
          , String
"lhc"
          , String
"lhc-pkg"
          , String
"uhc"
          , String
"gcc"
          , String
"ranlib"
          , String
"ar"
          , String
"strip"
          , String
"ld"
          , String
"tar"
          , String
"pkg-config"
          ] forall a. Eq a => [a] -> [a] -> [a]
\\ [
          -- Support for these build tools has been removed from Cabal at some point
            String
"hugs"
          , String
"ffihugs"
          , String
"nhc98"
          , String
"ranlib"
          , String
"lhc"
          , String
"lhc-pkg"
          ]
        known_1_14 :: [String]
known_1_14 = [
            String
"hpc"
          ]
        known_1_22 :: [String]
known_1_22 = [
            String
"ghcjs"
          , String
"ghcjs-pkg"
          -- , "haskell-suite" // not a real build tool
          -- , "haskell-suite-pkg" // not a real build tool
          ]

        systemBuildTools :: [String]
        systemBuildTools :: [String]
systemBuildTools = forall k a. Map k a -> [k]
Map.keys forall a b. (a -> b) -> a -> b
$ SystemBuildTools -> Map String VersionConstraint
unSystemBuildTools forall a b. (a -> b) -> a -> b
$ forall b a.
(Semigroup b, Monoid b) =>
(Section a -> b) -> Section a -> b
sectionAll forall a. Section a -> SystemBuildTools
sectionSystemBuildTools Section a
sect

    sectionSatisfies :: (Section a -> Bool) -> Section a -> Bool
    sectionSatisfies :: forall a. (Section a -> Bool) -> Section a -> Bool
sectionSatisfies Section a -> Bool
p Section a
sect = forall (t :: * -> *). Foldable t => t Bool -> Bool
or [
        Section a -> Bool
p Section a
sect
      , forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (forall a. (Section a -> Bool) -> Section a -> Bool
sectionSatisfies Section a -> Bool
p)) (forall a. Section a -> [Conditional (Section a)]
sectionConditionals Section a
sect)
      ]

    hasMixins :: DependencyInfo -> Bool
    hasMixins :: DependencyInfo -> Bool
hasMixins (DependencyInfo [String]
mixins DependencyVersion
_) = Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
mixins)

    hasSubcomponents :: String -> Bool
    hasSubcomponents :: String -> Bool
hasSubcomponents = forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem Char
':'

sectionAll :: (Semigroup b, Monoid b) => (Section a -> b) -> Section a -> b
sectionAll :: forall b a.
(Semigroup b, Monoid b) =>
(Section a -> b) -> Section a -> b
sectionAll Section a -> b
f Section a
sect = Section a -> b
f Section a
sect forall a. Semigroup a => a -> a -> a
<> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap forall a b. (a -> b) -> a -> b
$ forall b a.
(Semigroup b, Monoid b) =>
(Section a -> b) -> Section a -> b
sectionAll Section a -> b
f) (forall a. Section a -> [Conditional (Section a)]
sectionConditionals Section a
sect)

decodeValue :: FromValue a => FilePath -> Value -> Warnings (Errors IO) a
decodeValue :: forall a. FromValue a => String -> Value -> Warnings (Errors IO) a
decodeValue String
file Value
value = do
  (CheckSpecVersion a
r, [String]
unknown, [(String, String)]
deprecated) <- forall a. IO (Either HpackError a) -> Warnings (Errors IO) a
liftEither forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (String -> String -> HpackError
DecodeValueError String
file) (forall a. FromValue a => Value -> Result a
Config.decodeValue Value
value)
  case CheckSpecVersion a
r of
    UnsupportedSpecVersion Version
v -> do
      forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) e a. Monad m => e -> ExceptT e m a
throwE forall a b. (a -> b) -> a -> b
$ String -> Version -> Version -> HpackError
HpackVersionNotSupported String
file Version
v Version
Hpack.version
    SupportedSpecVersion a
a -> do
      forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell (forall a b. (a -> b) -> [a] -> [b]
map ShowS
formatUnknownField [String]
unknown)
      forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell (forall a b. (a -> b) -> [a] -> [b]
map (String, String) -> String
formatDeprecatedField [(String, String)]
deprecated)
      forall (m :: * -> *) a. Monad m => a -> m a
return a
a
  where
    prefix :: String
prefix = String
file forall a. [a] -> [a] -> [a]
++ String
": "
    formatUnknownField :: ShowS
formatUnknownField String
name = String
prefix forall a. [a] -> [a] -> [a]
++ String
"Ignoring unrecognized field " forall a. [a] -> [a] -> [a]
++ String
name
    formatDeprecatedField :: (String, String) -> String
formatDeprecatedField (String
name, String
substitute) = String
prefix forall a. Semigroup a => a -> a -> a
<> String
name forall a. Semigroup a => a -> a -> a
<> String
" is deprecated, use " forall a. Semigroup a => a -> a -> a
<> String
substitute forall a. Semigroup a => a -> a -> a
<> String
" instead"

data CheckSpecVersion a = SupportedSpecVersion a | UnsupportedSpecVersion Version

instance FromValue a => FromValue (CheckSpecVersion a) where
  fromValue :: Value -> Parser (CheckSpecVersion a)
fromValue = forall a. (Object -> Parser a) -> Value -> Parser a
withObject forall a b. (a -> b) -> a -> b
$ \ Object
o -> Object
o forall a. FromValue a => Object -> Key -> Parser (Maybe a)
.:? Key
"spec-version" forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \ case
    Just (ParseSpecVersion Version
v) | Version
Hpack.version forall a. Ord a => a -> a -> Bool
< Version
v -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. Version -> CheckSpecVersion a
UnsupportedSpecVersion Version
v
    Maybe ParseSpecVersion
_ -> forall a. a -> CheckSpecVersion a
SupportedSpecVersion forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromValue a => Value -> Parser a
fromValue (Object -> Value
Object Object
o)

newtype ParseSpecVersion = ParseSpecVersion Version

instance FromValue ParseSpecVersion where
  fromValue :: Value -> Parser ParseSpecVersion
fromValue Value
value = do
    String
s <- case Value
value of
      Number Scientific
n -> forall (m :: * -> *) a. Monad m => a -> m a
return (Scientific -> String
scientificToVersion Scientific
n)
      String Text
s -> forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> String
T.unpack Text
s)
      Value
_ -> forall a. String -> Value -> Parser a
typeMismatch String
"Number or String" Value
value
    case String -> Maybe Version
parseVersion String
s of
      Just Version
v -> forall (m :: * -> *) a. Monad m => a -> m a
return (Version -> ParseSpecVersion
ParseSpecVersion Version
v)
      Maybe Version
Nothing -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"invalid value " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show String
s)

data Package = Package {
  Package -> String
packageName :: String
, Package -> String
packageVersion :: String
, Package -> Maybe String
packageSynopsis :: Maybe String
, Package -> Maybe String
packageDescription :: Maybe String
, Package -> Maybe String
packageHomepage :: Maybe String
, Package -> Maybe String
packageBugReports :: Maybe String
, Package -> Maybe String
packageCategory :: Maybe String
, Package -> Maybe String
packageStability :: Maybe String
, Package -> [String]
packageAuthor :: [String]
, Package -> [String]
packageMaintainer :: [String]
, Package -> [String]
packageCopyright :: [String]
, Package -> BuildType
packageBuildType :: BuildType
, Package -> Maybe String
packageLicense :: Maybe String
, Package -> [String]
packageLicenseFile :: [FilePath]
, Package -> [String]
packageTestedWith :: [String]
, Package -> [Flag]
packageFlags :: [Flag]
, Package -> [Path]
packageExtraSourceFiles :: [Path]
, Package -> [Path]
packageExtraDocFiles :: [Path]
, Package -> [Path]
packageDataFiles :: [Path]
, Package -> Maybe String
packageDataDir :: Maybe FilePath
, Package -> Maybe SourceRepository
packageSourceRepository :: Maybe SourceRepository
, Package -> Maybe CustomSetup
packageCustomSetup :: Maybe CustomSetup
, Package -> Maybe (Section Library)
packageLibrary :: Maybe (Section Library)
, Package -> Map String (Section Library)
packageInternalLibraries :: Map String (Section Library)
, Package -> Map String (Section Executable)
packageExecutables :: Map String (Section Executable)
, Package -> Map String (Section Executable)
packageTests :: Map String (Section Executable)
, Package -> Map String (Section Executable)
packageBenchmarks :: Map String (Section Executable)
, Package -> [Verbatim]
packageVerbatim :: [Verbatim]
} deriving (Package -> Package -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Package -> Package -> Bool
$c/= :: Package -> Package -> Bool
== :: Package -> Package -> Bool
$c== :: Package -> Package -> Bool
Eq, Int -> Package -> ShowS
[Package] -> ShowS
Package -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Package] -> ShowS
$cshowList :: [Package] -> ShowS
show :: Package -> String
$cshow :: Package -> String
showsPrec :: Int -> Package -> ShowS
$cshowsPrec :: Int -> Package -> ShowS
Show)

data CustomSetup = CustomSetup {
  CustomSetup -> Dependencies
customSetupDependencies :: Dependencies
} deriving (CustomSetup -> CustomSetup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CustomSetup -> CustomSetup -> Bool
$c/= :: CustomSetup -> CustomSetup -> Bool
== :: CustomSetup -> CustomSetup -> Bool
$c== :: CustomSetup -> CustomSetup -> Bool
Eq, Int -> CustomSetup -> ShowS
[CustomSetup] -> ShowS
CustomSetup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CustomSetup] -> ShowS
$cshowList :: [CustomSetup] -> ShowS
show :: CustomSetup -> String
$cshow :: CustomSetup -> String
showsPrec :: Int -> CustomSetup -> ShowS
$cshowsPrec :: Int -> CustomSetup -> ShowS
Show)

data Library = Library {
  Library -> Maybe Bool
libraryExposed :: Maybe Bool
, Library -> Maybe String
libraryVisibility :: Maybe String
, Library -> [Module]
libraryExposedModules :: [Module]
, Library -> [Module]
libraryOtherModules :: [Module]
, Library -> [Module]
libraryGeneratedModules :: [Module]
, Library -> [String]
libraryReexportedModules :: [String]
, Library -> [String]
librarySignatures :: [String]
} deriving (Library -> Library -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Library -> Library -> Bool
$c/= :: Library -> Library -> Bool
== :: Library -> Library -> Bool
$c== :: Library -> Library -> Bool
Eq, Int -> Library -> ShowS
[Library] -> ShowS
Library -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Library] -> ShowS
$cshowList :: [Library] -> ShowS
show :: Library -> String
$cshow :: Library -> String
showsPrec :: Int -> Library -> ShowS
$cshowsPrec :: Int -> Library -> ShowS
Show)

data Executable = Executable {
  Executable -> Maybe String
executableMain :: Maybe FilePath
, Executable -> [Module]
executableOtherModules :: [Module]
, Executable -> [Module]
executableGeneratedModules :: [Module]
} deriving (Executable -> Executable -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Executable -> Executable -> Bool
$c/= :: Executable -> Executable -> Bool
== :: Executable -> Executable -> Bool
$c== :: Executable -> Executable -> Bool
Eq, Int -> Executable -> ShowS
[Executable] -> ShowS
Executable -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Executable] -> ShowS
$cshowList :: [Executable] -> ShowS
show :: Executable -> String
$cshow :: Executable -> String
showsPrec :: Int -> Executable -> ShowS
$cshowsPrec :: Int -> Executable -> ShowS
Show)

data BuildTool = BuildTool String String | LocalBuildTool String
  deriving (Int -> BuildTool -> ShowS
[BuildTool] -> ShowS
BuildTool -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BuildTool] -> ShowS
$cshowList :: [BuildTool] -> ShowS
show :: BuildTool -> String
$cshow :: BuildTool -> String
showsPrec :: Int -> BuildTool -> ShowS
$cshowsPrec :: Int -> BuildTool -> ShowS
Show, BuildTool -> BuildTool -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BuildTool -> BuildTool -> Bool
$c/= :: BuildTool -> BuildTool -> Bool
== :: BuildTool -> BuildTool -> Bool
$c== :: BuildTool -> BuildTool -> Bool
Eq, Eq BuildTool
BuildTool -> BuildTool -> Bool
BuildTool -> BuildTool -> Ordering
BuildTool -> BuildTool -> BuildTool
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: BuildTool -> BuildTool -> BuildTool
$cmin :: BuildTool -> BuildTool -> BuildTool
max :: BuildTool -> BuildTool -> BuildTool
$cmax :: BuildTool -> BuildTool -> BuildTool
>= :: BuildTool -> BuildTool -> Bool
$c>= :: BuildTool -> BuildTool -> Bool
> :: BuildTool -> BuildTool -> Bool
$c> :: BuildTool -> BuildTool -> Bool
<= :: BuildTool -> BuildTool -> Bool
$c<= :: BuildTool -> BuildTool -> Bool
< :: BuildTool -> BuildTool -> Bool
$c< :: BuildTool -> BuildTool -> Bool
compare :: BuildTool -> BuildTool -> Ordering
$ccompare :: BuildTool -> BuildTool -> Ordering
Ord)

data Section a = Section {
  forall a. Section a -> a
sectionData :: a
, forall a. Section a -> [String]
sectionSourceDirs :: [FilePath]
, forall a. Section a -> Dependencies
sectionDependencies :: Dependencies
, forall a. Section a -> [String]
sectionPkgConfigDependencies :: [String]
, forall a. Section a -> [String]
sectionDefaultExtensions :: [String]
, forall a. Section a -> [String]
sectionOtherExtensions :: [String]
, forall a. Section a -> Maybe Language
sectionLanguage :: Maybe Language
, forall a. Section a -> [String]
sectionGhcOptions :: [GhcOption]
, forall a. Section a -> [String]
sectionGhcProfOptions :: [GhcProfOption]
, forall a. Section a -> [String]
sectionGhcSharedOptions :: [GhcOption]
, forall a. Section a -> [String]
sectionGhcjsOptions :: [GhcjsOption]
, forall a. Section a -> [String]
sectionCppOptions :: [CppOption]
, forall a. Section a -> [String]
sectionCcOptions :: [CcOption]
, forall a. Section a -> [Path]
sectionCSources :: [Path]
, forall a. Section a -> [String]
sectionCxxOptions :: [CxxOption]
, forall a. Section a -> [Path]
sectionCxxSources :: [Path]
, forall a. Section a -> [Path]
sectionJsSources :: [Path]
, forall a. Section a -> [String]
sectionExtraLibDirs :: [FilePath]
, forall a. Section a -> [String]
sectionExtraLibraries :: [FilePath]
, forall a. Section a -> [String]
sectionExtraFrameworksDirs :: [FilePath]
, forall a. Section a -> [String]
sectionFrameworks :: [FilePath]
, forall a. Section a -> [String]
sectionIncludeDirs :: [FilePath]
, forall a. Section a -> [String]
sectionInstallIncludes :: [FilePath]
, forall a. Section a -> [String]
sectionLdOptions :: [LdOption]
, forall a. Section a -> Maybe Bool
sectionBuildable :: Maybe Bool
, forall a. Section a -> [Conditional (Section a)]
sectionConditionals :: [Conditional (Section a)]
, forall a. Section a -> Map BuildTool DependencyVersion
sectionBuildTools :: Map BuildTool DependencyVersion
, forall a. Section a -> SystemBuildTools
sectionSystemBuildTools :: SystemBuildTools
, forall a. Section a -> [Verbatim]
sectionVerbatim :: [Verbatim]
} deriving (Section a -> Section a -> Bool
forall a. Eq a => Section a -> Section a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Section a -> Section a -> Bool
$c/= :: forall a. Eq a => Section a -> Section a -> Bool
== :: Section a -> Section a -> Bool
$c== :: forall a. Eq a => Section a -> Section a -> Bool
Eq, Int -> Section a -> ShowS
forall a. Show a => Int -> Section a -> ShowS
forall a. Show a => [Section a] -> ShowS
forall a. Show a => Section a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Section a] -> ShowS
$cshowList :: forall a. Show a => [Section a] -> ShowS
show :: Section a -> String
$cshow :: forall a. Show a => Section a -> String
showsPrec :: Int -> Section a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Section a -> ShowS
Show, forall a b. a -> Section b -> Section a
forall a b. (a -> b) -> Section a -> Section b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Section b -> Section a
$c<$ :: forall a b. a -> Section b -> Section a
fmap :: forall a b. (a -> b) -> Section a -> Section b
$cfmap :: forall a b. (a -> b) -> Section a -> Section b
Functor, forall a. Eq a => a -> Section a -> Bool
forall a. Num a => Section a -> a
forall a. Ord a => Section a -> a
forall m. Monoid m => Section m -> m
forall a. Section a -> Bool
forall a. Section a -> Int
forall a. Section a -> [a]
forall a. (a -> a -> a) -> Section a -> a
forall m a. Monoid m => (a -> m) -> Section a -> m
forall b a. (b -> a -> b) -> b -> Section a -> b
forall a b. (a -> b -> b) -> b -> Section a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => Section a -> a
$cproduct :: forall a. Num a => Section a -> a
sum :: forall a. Num a => Section a -> a
$csum :: forall a. Num a => Section a -> a
minimum :: forall a. Ord a => Section a -> a
$cminimum :: forall a. Ord a => Section a -> a
maximum :: forall a. Ord a => Section a -> a
$cmaximum :: forall a. Ord a => Section a -> a
elem :: forall a. Eq a => a -> Section a -> Bool
$celem :: forall a. Eq a => a -> Section a -> Bool
length :: forall a. Section a -> Int
$clength :: forall a. Section a -> Int
null :: forall a. Section a -> Bool
$cnull :: forall a. Section a -> Bool
toList :: forall a. Section a -> [a]
$ctoList :: forall a. Section a -> [a]
foldl1 :: forall a. (a -> a -> a) -> Section a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Section a -> a
foldr1 :: forall a. (a -> a -> a) -> Section a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Section a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> Section a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Section a -> b
foldl :: forall b a. (b -> a -> b) -> b -> Section a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Section a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> Section a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Section a -> b
foldr :: forall a b. (a -> b -> b) -> b -> Section a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> Section a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> Section a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Section a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> Section a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Section a -> m
fold :: forall m. Monoid m => Section m -> m
$cfold :: forall m. Monoid m => Section m -> m
Foldable, Functor Section
Foldable Section
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => Section (m a) -> m (Section a)
forall (f :: * -> *) a.
Applicative f =>
Section (f a) -> f (Section a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Section a -> m (Section b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Section a -> f (Section b)
sequence :: forall (m :: * -> *) a. Monad m => Section (m a) -> m (Section a)
$csequence :: forall (m :: * -> *) a. Monad m => Section (m a) -> m (Section a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Section a -> m (Section b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Section a -> m (Section b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
Section (f a) -> f (Section a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
Section (f a) -> f (Section a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Section a -> f (Section b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Section a -> f (Section b)
Traversable)

data Conditional a = Conditional {
  forall a. Conditional a -> Cond
conditionalCondition :: Cond
, forall a. Conditional a -> a
conditionalThen :: a
, forall a. Conditional a -> Maybe a
conditionalElse :: Maybe a
} deriving (Conditional a -> Conditional a -> Bool
forall a. Eq a => Conditional a -> Conditional a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Conditional a -> Conditional a -> Bool
$c/= :: forall a. Eq a => Conditional a -> Conditional a -> Bool
== :: Conditional a -> Conditional a -> Bool
$c== :: forall a. Eq a => Conditional a -> Conditional a -> Bool
Eq, Int -> Conditional a -> ShowS
forall a. Show a => Int -> Conditional a -> ShowS
forall a. Show a => [Conditional a] -> ShowS
forall a. Show a => Conditional a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Conditional a] -> ShowS
$cshowList :: forall a. Show a => [Conditional a] -> ShowS
show :: Conditional a -> String
$cshow :: forall a. Show a => Conditional a -> String
showsPrec :: Int -> Conditional a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Conditional a -> ShowS
Show, forall a b. a -> Conditional b -> Conditional a
forall a b. (a -> b) -> Conditional a -> Conditional b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Conditional b -> Conditional a
$c<$ :: forall a b. a -> Conditional b -> Conditional a
fmap :: forall a b. (a -> b) -> Conditional a -> Conditional b
$cfmap :: forall a b. (a -> b) -> Conditional a -> Conditional b
Functor, forall a. Eq a => a -> Conditional a -> Bool
forall a. Num a => Conditional a -> a
forall a. Ord a => Conditional a -> a
forall m. Monoid m => Conditional m -> m
forall a. Conditional a -> Bool
forall a. Conditional a -> Int
forall a. Conditional a -> [a]
forall a. (a -> a -> a) -> Conditional a -> a
forall m a. Monoid m => (a -> m) -> Conditional a -> m
forall b a. (b -> a -> b) -> b -> Conditional a -> b
forall a b. (a -> b -> b) -> b -> Conditional a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => Conditional a -> a
$cproduct :: forall a. Num a => Conditional a -> a
sum :: forall a. Num a => Conditional a -> a
$csum :: forall a. Num a => Conditional a -> a
minimum :: forall a. Ord a => Conditional a -> a
$cminimum :: forall a. Ord a => Conditional a -> a
maximum :: forall a. Ord a => Conditional a -> a
$cmaximum :: forall a. Ord a => Conditional a -> a
elem :: forall a. Eq a => a -> Conditional a -> Bool
$celem :: forall a. Eq a => a -> Conditional a -> Bool
length :: forall a. Conditional a -> Int
$clength :: forall a. Conditional a -> Int
null :: forall a. Conditional a -> Bool
$cnull :: forall a. Conditional a -> Bool
toList :: forall a. Conditional a -> [a]
$ctoList :: forall a. Conditional a -> [a]
foldl1 :: forall a. (a -> a -> a) -> Conditional a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Conditional a -> a
foldr1 :: forall a. (a -> a -> a) -> Conditional a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Conditional a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> Conditional a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Conditional a -> b
foldl :: forall b a. (b -> a -> b) -> b -> Conditional a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Conditional a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> Conditional a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Conditional a -> b
foldr :: forall a b. (a -> b -> b) -> b -> Conditional a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> Conditional a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> Conditional a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Conditional a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> Conditional a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Conditional a -> m
fold :: forall m. Monoid m => Conditional m -> m
$cfold :: forall m. Monoid m => Conditional m -> m
Foldable, Functor Conditional
Foldable Conditional
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
Conditional (m a) -> m (Conditional a)
forall (f :: * -> *) a.
Applicative f =>
Conditional (f a) -> f (Conditional a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Conditional a -> m (Conditional b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Conditional a -> f (Conditional b)
sequence :: forall (m :: * -> *) a.
Monad m =>
Conditional (m a) -> m (Conditional a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
Conditional (m a) -> m (Conditional a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Conditional a -> m (Conditional b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Conditional a -> m (Conditional b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
Conditional (f a) -> f (Conditional a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
Conditional (f a) -> f (Conditional a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Conditional a -> f (Conditional b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Conditional a -> f (Conditional b)
Traversable)

data FlagSection = FlagSection {
  FlagSection -> Maybe String
_flagSectionDescription :: Maybe String
, FlagSection -> Bool
_flagSectionManual :: Bool
, FlagSection -> Bool
_flagSectionDefault :: Bool
} deriving (FlagSection -> FlagSection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FlagSection -> FlagSection -> Bool
$c/= :: FlagSection -> FlagSection -> Bool
== :: FlagSection -> FlagSection -> Bool
$c== :: FlagSection -> FlagSection -> Bool
Eq, Int -> FlagSection -> ShowS
[FlagSection] -> ShowS
FlagSection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FlagSection] -> ShowS
$cshowList :: [FlagSection] -> ShowS
show :: FlagSection -> String
$cshow :: FlagSection -> String
showsPrec :: Int -> FlagSection -> ShowS
$cshowsPrec :: Int -> FlagSection -> ShowS
Show, forall x. Rep FlagSection x -> FlagSection
forall x. FlagSection -> Rep FlagSection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FlagSection x -> FlagSection
$cfrom :: forall x. FlagSection -> Rep FlagSection x
Generic, Value -> Parser FlagSection
forall a. (Value -> Parser a) -> FromValue a
fromValue :: Value -> Parser FlagSection
$cfromValue :: Value -> Parser FlagSection
FromValue)

data Flag = Flag {
  Flag -> String
flagName :: String
, Flag -> Maybe String
flagDescription :: Maybe String
, Flag -> Bool
flagManual :: Bool
, Flag -> Bool
flagDefault :: Bool
} deriving (Flag -> Flag -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Flag -> Flag -> Bool
$c/= :: Flag -> Flag -> Bool
== :: Flag -> Flag -> Bool
$c== :: Flag -> Flag -> Bool
Eq, Int -> Flag -> ShowS
[Flag] -> ShowS
Flag -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Flag] -> ShowS
$cshowList :: [Flag] -> ShowS
show :: Flag -> String
$cshow :: Flag -> String
showsPrec :: Int -> Flag -> ShowS
$cshowsPrec :: Int -> Flag -> ShowS
Show)

toFlag :: (String, FlagSection) -> Flag
toFlag :: (String, FlagSection) -> Flag
toFlag (String
name, FlagSection Maybe String
description Bool
manual Bool
def) = String -> Maybe String -> Bool -> Bool -> Flag
Flag String
name Maybe String
description Bool
manual Bool
def

data SourceRepository = SourceRepository {
  SourceRepository -> String
sourceRepositoryUrl :: String
, SourceRepository -> Maybe String
sourceRepositorySubdir :: Maybe String
} deriving (SourceRepository -> SourceRepository -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SourceRepository -> SourceRepository -> Bool
$c/= :: SourceRepository -> SourceRepository -> Bool
== :: SourceRepository -> SourceRepository -> Bool
$c== :: SourceRepository -> SourceRepository -> Bool
Eq, Int -> SourceRepository -> ShowS
[SourceRepository] -> ShowS
SourceRepository -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SourceRepository] -> ShowS
$cshowList :: [SourceRepository] -> ShowS
show :: SourceRepository -> String
$cshow :: SourceRepository -> String
showsPrec :: Int -> SourceRepository -> ShowS
$cshowsPrec :: Int -> SourceRepository -> ShowS
Show)

type Config cSources cxxSources jsSources =
  Product (CommonOptions cSources cxxSources jsSources Empty) (PackageConfig cSources cxxSources jsSources)

traverseConfig :: Traversal Config
traverseConfig :: Traversal Config
traverseConfig Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
t = forall (t :: * -> * -> *) (f :: * -> *) a c b d.
(Bitraversable t, Applicative f) =>
(a -> f c) -> (b -> f d) -> t a b -> f (t c d)
bitraverse (Traversal_ CommonOptions
traverseCommonOptions Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
t) (Traversal PackageConfig
traversePackageConfig Traverse
  m cSources cSources_ cxxSources cxxSources_ jsSources jsSources_
t)

type ConfigWithDefaults = Product
  (CommonOptionsWithDefaults Empty)
  (PackageConfigWithDefaults ParseCSources ParseCxxSources ParseJsSources)

type CommonOptionsWithDefaults a = Product DefaultsConfig (CommonOptions ParseCSources ParseCxxSources ParseJsSources a)
type WithCommonOptionsWithDefaults a = Product DefaultsConfig (WithCommonOptions ParseCSources ParseCxxSources ParseJsSources a)

toPackage :: FormatYamlParseError -> FilePath -> FilePath -> ConfigWithDefaults -> Warnings (Errors IO) (Package, String)
toPackage :: FormatYamlParseError
-> String
-> String
-> ConfigWithDefaults
-> WriterT [String] (Errors IO) (Package, String)
toPackage FormatYamlParseError
formatYamlParseError String
userDataDir String
dir =
      FormatYamlParseError
-> String
-> String
-> ConfigWithDefaults
-> Warnings
     (Errors IO)
     (Config
        (Maybe (List String)) (Maybe (List String)) (Maybe (List String)))
expandDefaultsInConfig FormatYamlParseError
formatYamlParseError String
userDataDir String
dir
  forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> forall {p :: * -> * -> *} {cSources} {cxxSources} {jsSources} {a}
       {c}.
(Bifunctor p, Monoid cSources, Monoid cxxSources,
 Monoid jsSources) =>
Language
-> p (CommonOptions cSources cxxSources jsSources a) c
-> p (CommonOptions cSources cxxSources jsSources a) c
setDefaultLanguage Language
"Haskell2010"
  forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> Traversal Config
traverseConfig (forall (m :: * -> *).
MonadIO m =>
String
-> Traverse
     (Warnings m)
     (Maybe (List String))
     [Path]
     (Maybe (List String))
     [Path]
     (Maybe (List String))
     [Path]
expandForeignSources String
dir)
  forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> forall (m :: * -> *).
MonadIO m =>
String
-> Product GlobalOptions (PackageConfig [Path] [Path] [Path])
-> Warnings m (Package, String)
toPackage_ String
dir
  where
    setDefaultLanguage :: Language
-> p (CommonOptions cSources cxxSources jsSources a) c
-> p (CommonOptions cSources cxxSources jsSources a) c
setDefaultLanguage Language
language p (CommonOptions cSources cxxSources jsSources a) c
config = forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first forall {a}.
CommonOptions cSources cxxSources jsSources a
-> CommonOptions cSources cxxSources jsSources a
setLanguage p (CommonOptions cSources cxxSources jsSources a) c
config
      where
        setLanguage :: CommonOptions cSources cxxSources jsSources a
-> CommonOptions cSources cxxSources jsSources a
setLanguage = (forall a. Monoid a => a
mempty { commonOptionsLanguage :: Alias 'True "default-language" (Last (Maybe Language))
commonOptionsLanguage = forall (deprecated :: Bool) (alias :: Symbol) a.
a -> Alias deprecated alias a
Alias forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Maybe a -> Last a
Last forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just (forall a. a -> Maybe a
Just Language
language) } forall a. Semigroup a => a -> a -> a
<>)

expandDefaultsInConfig
  :: FormatYamlParseError
  -> FilePath
  -> FilePath
  -> ConfigWithDefaults
  -> Warnings (Errors IO) (Config ParseCSources ParseCxxSources ParseJsSources)
expandDefaultsInConfig :: FormatYamlParseError
-> String
-> String
-> ConfigWithDefaults
-> Warnings
     (Errors IO)
     (Config
        (Maybe (List String)) (Maybe (List String)) (Maybe (List String)))
expandDefaultsInConfig FormatYamlParseError
formatYamlParseError String
userDataDir String
dir = forall (t :: * -> * -> *) (f :: * -> *) a c b d.
(Bitraversable t, Applicative f) =>
(a -> f c) -> (b -> f d) -> t a b -> f (t c d)
bitraverse (FormatYamlParseError
-> String
-> String
-> Product
     DefaultsConfig
     (CommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        Empty)
-> Warnings
     (Errors IO)
     (CommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        Empty)
expandGlobalDefaults FormatYamlParseError
formatYamlParseError String
userDataDir String
dir) (FormatYamlParseError
-> String
-> String
-> ParsePackageConfig
-> Warnings
     (Errors IO)
     (PackageConfig
        (Maybe (List String)) (Maybe (List String)) (Maybe (List String)))
expandSectionDefaults FormatYamlParseError
formatYamlParseError String
userDataDir String
dir)

expandGlobalDefaults
  :: FormatYamlParseError
  -> FilePath
  -> FilePath
  -> CommonOptionsWithDefaults Empty
  -> Warnings (Errors IO) (CommonOptions ParseCSources ParseCxxSources ParseJsSources Empty)
expandGlobalDefaults :: FormatYamlParseError
-> String
-> String
-> Product
     DefaultsConfig
     (CommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        Empty)
-> Warnings
     (Errors IO)
     (CommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        Empty)
expandGlobalDefaults FormatYamlParseError
formatYamlParseError String
userDataDir String
dir = do
  forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a b. a -> b -> Product a b
`Product` Empty
Empty) forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> forall a.
(FromValue a, Semigroup a, Monoid a) =>
FormatYamlParseError
-> String
-> String
-> WithCommonOptionsWithDefaults a
-> Warnings
     (Errors IO)
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        a)
expandDefaults FormatYamlParseError
formatYamlParseError String
userDataDir String
dir forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> \ (Product CommonOptions
  (Maybe (List String))
  (Maybe (List String))
  (Maybe (List String))
  Empty
c Empty
Empty) -> forall (m :: * -> *) a. Monad m => a -> m a
return CommonOptions
  (Maybe (List String))
  (Maybe (List String))
  (Maybe (List String))
  Empty
c

expandSectionDefaults
  :: FormatYamlParseError
  -> FilePath
  -> FilePath
  -> PackageConfigWithDefaults ParseCSources ParseCxxSources ParseJsSources
  -> Warnings (Errors IO) (PackageConfig ParseCSources ParseCxxSources ParseJsSources)
expandSectionDefaults :: FormatYamlParseError
-> String
-> String
-> ParsePackageConfig
-> Warnings
     (Errors IO)
     (PackageConfig
        (Maybe (List String)) (Maybe (List String)) (Maybe (List String)))
expandSectionDefaults FormatYamlParseError
formatYamlParseError String
userDataDir String
dir p :: ParsePackageConfig
p@PackageConfig{Maybe String
Maybe (Maybe String)
Maybe (Maybe (List String))
Maybe
  (Map
     String
     (Product
        DefaultsConfig
        (WithCommonOptions
           (Maybe (List String))
           (Maybe (List String))
           (Maybe (List String))
           ExecutableSection)))
Maybe
  (Map
     String
     (Product
        DefaultsConfig
        (WithCommonOptions
           (Maybe (List String))
           (Maybe (List String))
           (Maybe (List String))
           LibrarySection)))
Maybe (Map String FlagSection)
Maybe
  (Product
     DefaultsConfig
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        ExecutableSection))
Maybe
  (Product
     DefaultsConfig
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        LibrarySection))
Maybe (List String)
Maybe GitHub
Maybe PackageVersion
Maybe BuildType
Maybe CustomSetupSection
packageConfigBenchmarks :: Maybe
  (Map
     String
     (Product
        DefaultsConfig
        (WithCommonOptions
           (Maybe (List String))
           (Maybe (List String))
           (Maybe (List String))
           ExecutableSection)))
packageConfigTests :: Maybe
  (Map
     String
     (Product
        DefaultsConfig
        (WithCommonOptions
           (Maybe (List String))
           (Maybe (List String))
           (Maybe (List String))
           ExecutableSection)))
packageConfigExecutables :: Maybe
  (Map
     String
     (Product
        DefaultsConfig
        (WithCommonOptions
           (Maybe (List String))
           (Maybe (List String))
           (Maybe (List String))
           ExecutableSection)))
packageConfigExecutable :: Maybe
  (Product
     DefaultsConfig
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        ExecutableSection))
packageConfigInternalLibraries :: Maybe
  (Map
     String
     (Product
        DefaultsConfig
        (WithCommonOptions
           (Maybe (List String))
           (Maybe (List String))
           (Maybe (List String))
           LibrarySection)))
packageConfigLibrary :: Maybe
  (Product
     DefaultsConfig
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        LibrarySection))
packageConfigCustomSetup :: Maybe CustomSetupSection
packageConfigGit :: Maybe String
packageConfigGithub :: Maybe GitHub
packageConfigDataDir :: Maybe String
packageConfigDataFiles :: Maybe (List String)
packageConfigExtraDocFiles :: Maybe (List String)
packageConfigExtraSourceFiles :: Maybe (List String)
packageConfigFlags :: Maybe (Map String FlagSection)
packageConfigTestedWith :: Maybe (List String)
packageConfigLicenseFile :: Maybe (List String)
packageConfigLicense :: Maybe (Maybe String)
packageConfigBuildType :: Maybe BuildType
packageConfigCopyright :: Maybe (List String)
packageConfigMaintainer :: Maybe (Maybe (List String))
packageConfigAuthor :: Maybe (List String)
packageConfigStability :: Maybe String
packageConfigCategory :: Maybe String
packageConfigBugReports :: Maybe (Maybe String)
packageConfigHomepage :: Maybe (Maybe String)
packageConfigDescription :: Maybe String
packageConfigSynopsis :: Maybe String
packageConfigVersion :: Maybe PackageVersion
packageConfigName :: Maybe String
packageConfigBenchmarks :: forall library executable.
PackageConfig_ library executable -> Maybe (Map String executable)
packageConfigTests :: forall library executable.
PackageConfig_ library executable -> Maybe (Map String executable)
packageConfigExecutables :: forall library executable.
PackageConfig_ library executable -> Maybe (Map String executable)
packageConfigExecutable :: forall library executable.
PackageConfig_ library executable -> Maybe executable
packageConfigInternalLibraries :: forall library executable.
PackageConfig_ library executable -> Maybe (Map String library)
packageConfigLibrary :: forall library executable.
PackageConfig_ library executable -> Maybe library
packageConfigCustomSetup :: forall library executable.
PackageConfig_ library executable -> Maybe CustomSetupSection
packageConfigGit :: forall library executable.
PackageConfig_ library executable -> Maybe String
packageConfigGithub :: forall library executable.
PackageConfig_ library executable -> Maybe GitHub
packageConfigDataDir :: forall library executable.
PackageConfig_ library executable -> Maybe String
packageConfigDataFiles :: forall library executable.
PackageConfig_ library executable -> Maybe (List String)
packageConfigExtraDocFiles :: forall library executable.
PackageConfig_ library executable -> Maybe (List String)
packageConfigExtraSourceFiles :: forall library executable.
PackageConfig_ library executable -> Maybe (List String)
packageConfigFlags :: forall library executable.
PackageConfig_ library executable -> Maybe (Map String FlagSection)
packageConfigTestedWith :: forall library executable.
PackageConfig_ library executable -> Maybe (List String)
packageConfigLicenseFile :: forall library executable.
PackageConfig_ library executable -> Maybe (List String)
packageConfigLicense :: forall library executable.
PackageConfig_ library executable -> Maybe (Maybe String)
packageConfigBuildType :: forall library executable.
PackageConfig_ library executable -> Maybe BuildType
packageConfigCopyright :: forall library executable.
PackageConfig_ library executable -> Maybe (List String)
packageConfigMaintainer :: forall library executable.
PackageConfig_ library executable -> Maybe (Maybe (List String))
packageConfigAuthor :: forall library executable.
PackageConfig_ library executable -> Maybe (List String)
packageConfigStability :: forall library executable.
PackageConfig_ library executable -> Maybe String
packageConfigCategory :: forall library executable.
PackageConfig_ library executable -> Maybe String
packageConfigBugReports :: forall library executable.
PackageConfig_ library executable -> Maybe (Maybe String)
packageConfigHomepage :: forall library executable.
PackageConfig_ library executable -> Maybe (Maybe String)
packageConfigDescription :: forall library executable.
PackageConfig_ library executable -> Maybe String
packageConfigSynopsis :: forall library executable.
PackageConfig_ library executable -> Maybe String
packageConfigVersion :: forall library executable.
PackageConfig_ library executable -> Maybe PackageVersion
packageConfigName :: forall library executable.
PackageConfig_ library executable -> Maybe String
..} = do
  Maybe
  (WithCommonOptions
     (Maybe (List String))
     (Maybe (List String))
     (Maybe (List String))
     LibrarySection)
library <- forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (forall a.
(FromValue a, Semigroup a, Monoid a) =>
FormatYamlParseError
-> String
-> String
-> WithCommonOptionsWithDefaults a
-> Warnings
     (Errors IO)
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        a)
expandDefaults FormatYamlParseError
formatYamlParseError String
userDataDir String
dir) Maybe
  (Product
     DefaultsConfig
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        LibrarySection))
packageConfigLibrary
  Maybe
  (Map
     String
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        LibrarySection))
internalLibraries <- forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (forall a.
(FromValue a, Semigroup a, Monoid a) =>
FormatYamlParseError
-> String
-> String
-> WithCommonOptionsWithDefaults a
-> Warnings
     (Errors IO)
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        a)
expandDefaults FormatYamlParseError
formatYamlParseError String
userDataDir String
dir)) Maybe
  (Map
     String
     (Product
        DefaultsConfig
        (WithCommonOptions
           (Maybe (List String))
           (Maybe (List String))
           (Maybe (List String))
           LibrarySection)))
packageConfigInternalLibraries
  Maybe
  (WithCommonOptions
     (Maybe (List String))
     (Maybe (List String))
     (Maybe (List String))
     ExecutableSection)
executable <- forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (forall a.
(FromValue a, Semigroup a, Monoid a) =>
FormatYamlParseError
-> String
-> String
-> WithCommonOptionsWithDefaults a
-> Warnings
     (Errors IO)
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        a)
expandDefaults FormatYamlParseError
formatYamlParseError String
userDataDir String
dir) Maybe
  (Product
     DefaultsConfig
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        ExecutableSection))
packageConfigExecutable
  Maybe
  (Map
     String
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        ExecutableSection))
executables <- forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (forall a.
(FromValue a, Semigroup a, Monoid a) =>
FormatYamlParseError
-> String
-> String
-> WithCommonOptionsWithDefaults a
-> Warnings
     (Errors IO)
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        a)
expandDefaults FormatYamlParseError
formatYamlParseError String
userDataDir String
dir)) Maybe
  (Map
     String
     (Product
        DefaultsConfig
        (WithCommonOptions
           (Maybe (List String))
           (Maybe (List String))
           (Maybe (List String))
           ExecutableSection)))
packageConfigExecutables
  Maybe
  (Map
     String
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        ExecutableSection))
tests <- forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (forall a.
(FromValue a, Semigroup a, Monoid a) =>
FormatYamlParseError
-> String
-> String
-> WithCommonOptionsWithDefaults a
-> Warnings
     (Errors IO)
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        a)
expandDefaults FormatYamlParseError
formatYamlParseError String
userDataDir String
dir)) Maybe
  (Map
     String
     (Product
        DefaultsConfig
        (WithCommonOptions
           (Maybe (List String))
           (Maybe (List String))
           (Maybe (List String))
           ExecutableSection)))
packageConfigTests
  Maybe
  (Map
     String
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        ExecutableSection))
benchmarks <- forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (forall a.
(FromValue a, Semigroup a, Monoid a) =>
FormatYamlParseError
-> String
-> String
-> WithCommonOptionsWithDefaults a
-> Warnings
     (Errors IO)
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        a)
expandDefaults FormatYamlParseError
formatYamlParseError String
userDataDir String
dir)) Maybe
  (Map
     String
     (Product
        DefaultsConfig
        (WithCommonOptions
           (Maybe (List String))
           (Maybe (List String))
           (Maybe (List String))
           ExecutableSection)))
packageConfigBenchmarks
  forall (m :: * -> *) a. Monad m => a -> m a
return ParsePackageConfig
p{
      packageConfigLibrary :: Maybe
  (WithCommonOptions
     (Maybe (List String))
     (Maybe (List String))
     (Maybe (List String))
     LibrarySection)
packageConfigLibrary = Maybe
  (WithCommonOptions
     (Maybe (List String))
     (Maybe (List String))
     (Maybe (List String))
     LibrarySection)
library
    , packageConfigInternalLibraries :: Maybe
  (Map
     String
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        LibrarySection))
packageConfigInternalLibraries = Maybe
  (Map
     String
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        LibrarySection))
internalLibraries
    , packageConfigExecutable :: Maybe
  (WithCommonOptions
     (Maybe (List String))
     (Maybe (List String))
     (Maybe (List String))
     ExecutableSection)
packageConfigExecutable = Maybe
  (WithCommonOptions
     (Maybe (List String))
     (Maybe (List String))
     (Maybe (List String))
     ExecutableSection)
executable
    , packageConfigExecutables :: Maybe
  (Map
     String
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        ExecutableSection))
packageConfigExecutables = Maybe
  (Map
     String
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        ExecutableSection))
executables
    , packageConfigTests :: Maybe
  (Map
     String
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        ExecutableSection))
packageConfigTests = Maybe
  (Map
     String
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        ExecutableSection))
tests
    , packageConfigBenchmarks :: Maybe
  (Map
     String
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        ExecutableSection))
packageConfigBenchmarks = Maybe
  (Map
     String
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        ExecutableSection))
benchmarks
    }

expandDefaults
  :: (FromValue a, Semigroup a, Monoid a)
  => FormatYamlParseError
  -> FilePath
  -> FilePath
  -> WithCommonOptionsWithDefaults a
  -> Warnings (Errors IO) (WithCommonOptions ParseCSources ParseCxxSources ParseJsSources a)
expandDefaults :: forall a.
(FromValue a, Semigroup a, Monoid a) =>
FormatYamlParseError
-> String
-> String
-> WithCommonOptionsWithDefaults a
-> Warnings
     (Errors IO)
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        a)
expandDefaults FormatYamlParseError
formatYamlParseError String
userDataDir = forall a.
(FromValue a, Semigroup a, Monoid a) =>
[String]
-> String
-> WithCommonOptionsWithDefaults a
-> Warnings
     (Errors IO)
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        a)
expand []
  where
    expand :: (FromValue a, Semigroup a, Monoid a) =>
         [FilePath]
      -> FilePath
      -> WithCommonOptionsWithDefaults a
      -> Warnings (Errors IO) (WithCommonOptions ParseCSources ParseCxxSources ParseJsSources a)
    expand :: forall a.
(FromValue a, Semigroup a, Monoid a) =>
[String]
-> String
-> WithCommonOptionsWithDefaults a
-> Warnings
     (Errors IO)
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        a)
expand [String]
seen String
dir (Product DefaultsConfig{Maybe (List Defaults)
defaultsConfigDefaults :: Maybe (List Defaults)
defaultsConfigDefaults :: DefaultsConfig -> Maybe (List Defaults)
..} WithCommonOptions
  (Maybe (List String)) (Maybe (List String)) (Maybe (List String)) a
c) = do
      WithCommonOptions
  (Maybe (List String)) (Maybe (List String)) (Maybe (List String)) a
d <- forall a. Monoid a => [a] -> a
mconcat forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (forall a.
(FromValue a, Semigroup a, Monoid a) =>
[String]
-> String
-> Defaults
-> Warnings
     (Errors IO)
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        a)
get [String]
seen String
dir) (forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List Defaults)
defaultsConfigDefaults)
      forall (m :: * -> *) a. Monad m => a -> m a
return (WithCommonOptions
  (Maybe (List String)) (Maybe (List String)) (Maybe (List String)) a
d forall a. Semigroup a => a -> a -> a
<> WithCommonOptions
  (Maybe (List String)) (Maybe (List String)) (Maybe (List String)) a
c)

    get :: forall a. (FromValue a, Semigroup a, Monoid a) =>
         [FilePath]
      -> FilePath
      -> Defaults
      -> Warnings (Errors IO) (WithCommonOptions ParseCSources ParseCxxSources ParseJsSources a)
    get :: forall a.
(FromValue a, Semigroup a, Monoid a) =>
[String]
-> String
-> Defaults
-> Warnings
     (Errors IO)
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        a)
get [String]
seen String
dir Defaults
defaults = do
      String
file <- forall a. IO (Either HpackError a) -> Warnings (Errors IO) a
liftEither (String -> String -> Defaults -> IO (Either HpackError String)
ensure String
userDataDir String
dir Defaults
defaults)
      [String]
seen_ <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ([String] -> String -> Errors IO [String]
checkCycle [String]
seen String
file)
      let dir_ :: String
dir_ = ShowS
takeDirectory String
file
      forall a.
FromValue a =>
FormatYamlParseError -> String -> Warnings (Errors IO) a
decodeYaml FormatYamlParseError
formatYamlParseError String
file forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a.
(FromValue a, Semigroup a, Monoid a) =>
[String]
-> String
-> WithCommonOptionsWithDefaults a
-> Warnings
     (Errors IO)
     (WithCommonOptions
        (Maybe (List String))
        (Maybe (List String))
        (Maybe (List String))
        a)
expand [String]
seen_ String
dir_

    checkCycle :: [FilePath] -> FilePath -> Errors IO [FilePath]
    checkCycle :: [String] -> String -> Errors IO [String]
checkCycle [String]
seen String
file = do
      String
canonic <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ String -> IO String
canonicalizePath String
file
      let seen_ :: [String]
seen_ = String
canonic forall a. a -> [a] -> [a]
: [String]
seen
      forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (String
canonic forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
seen) forall a b. (a -> b) -> a -> b
$ do
        forall (m :: * -> *) e a. Monad m => e -> ExceptT e m a
throwE forall a b. (a -> b) -> a -> b
$ [String] -> HpackError
CycleInDefaults (forall a. [a] -> [a]
reverse [String]
seen_)
      forall (m :: * -> *) a. Monad m => a -> m a
return [String]
seen_

toExecutableMap :: Monad m => String -> Maybe (Map String a) -> Maybe a -> Warnings m (Maybe (Map String a))
toExecutableMap :: forall (m :: * -> *) a.
Monad m =>
String
-> Maybe (Map String a)
-> Maybe a
-> Warnings m (Maybe (Map String a))
toExecutableMap String
name Maybe (Map String a)
executables Maybe a
mExecutable = do
  case Maybe a
mExecutable of
    Just a
executable -> do
      forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (forall a. Maybe a -> Bool
isJust Maybe (Map String a)
executables) forall a b. (a -> b) -> a -> b
$ do
        forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell [String
"Ignoring field \"executables\" in favor of \"executable\""]
      forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just (forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(String
name, a
executable)])
    Maybe a
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (Map String a)
executables

type GlobalOptions = CommonOptions CSources CxxSources JsSources Empty

toPackage_ :: MonadIO m => FilePath -> Product GlobalOptions (PackageConfig CSources CxxSources JsSources) -> Warnings m (Package, String)
toPackage_ :: forall (m :: * -> *).
MonadIO m =>
String
-> Product GlobalOptions (PackageConfig [Path] [Path] [Path])
-> Warnings m (Package, String)
toPackage_ String
dir (Product GlobalOptions
g PackageConfig{Maybe String
Maybe (Maybe String)
Maybe (Maybe (List String))
Maybe
  (Map
     String (WithCommonOptions [Path] [Path] [Path] ExecutableSection))
Maybe
  (Map
     String (WithCommonOptions [Path] [Path] [Path] LibrarySection))
Maybe (Map String FlagSection)
Maybe (WithCommonOptions [Path] [Path] [Path] ExecutableSection)
Maybe (WithCommonOptions [Path] [Path] [Path] LibrarySection)
Maybe (List String)
Maybe GitHub
Maybe PackageVersion
Maybe BuildType
Maybe CustomSetupSection
packageConfigBenchmarks :: Maybe
  (Map
     String (WithCommonOptions [Path] [Path] [Path] ExecutableSection))
packageConfigTests :: Maybe
  (Map
     String (WithCommonOptions [Path] [Path] [Path] ExecutableSection))
packageConfigExecutables :: Maybe
  (Map
     String (WithCommonOptions [Path] [Path] [Path] ExecutableSection))
packageConfigExecutable :: Maybe (WithCommonOptions [Path] [Path] [Path] ExecutableSection)
packageConfigInternalLibraries :: Maybe
  (Map
     String (WithCommonOptions [Path] [Path] [Path] LibrarySection))
packageConfigLibrary :: Maybe (WithCommonOptions [Path] [Path] [Path] LibrarySection)
packageConfigCustomSetup :: Maybe CustomSetupSection
packageConfigGit :: Maybe String
packageConfigGithub :: Maybe GitHub
packageConfigDataDir :: Maybe String
packageConfigDataFiles :: Maybe (List String)
packageConfigExtraDocFiles :: Maybe (List String)
packageConfigExtraSourceFiles :: Maybe (List String)
packageConfigFlags :: Maybe (Map String FlagSection)
packageConfigTestedWith :: Maybe (List String)
packageConfigLicenseFile :: Maybe (List String)
packageConfigLicense :: Maybe (Maybe String)
packageConfigBuildType :: Maybe BuildType
packageConfigCopyright :: Maybe (List String)
packageConfigMaintainer :: Maybe (Maybe (List String))
packageConfigAuthor :: Maybe (List String)
packageConfigStability :: Maybe String
packageConfigCategory :: Maybe String
packageConfigBugReports :: Maybe (Maybe String)
packageConfigHomepage :: Maybe (Maybe String)
packageConfigDescription :: Maybe String
packageConfigSynopsis :: Maybe String
packageConfigVersion :: Maybe PackageVersion
packageConfigName :: Maybe String
packageConfigBenchmarks :: forall library executable.
PackageConfig_ library executable -> Maybe (Map String executable)
packageConfigTests :: forall library executable.
PackageConfig_ library executable -> Maybe (Map String executable)
packageConfigExecutables :: forall library executable.
PackageConfig_ library executable -> Maybe (Map String executable)
packageConfigExecutable :: forall library executable.
PackageConfig_ library executable -> Maybe executable
packageConfigInternalLibraries :: forall library executable.
PackageConfig_ library executable -> Maybe (Map String library)
packageConfigLibrary :: forall library executable.
PackageConfig_ library executable -> Maybe library
packageConfigCustomSetup :: forall library executable.
PackageConfig_ library executable -> Maybe CustomSetupSection
packageConfigGit :: forall library executable.
PackageConfig_ library executable -> Maybe String
packageConfigGithub :: forall library executable.
PackageConfig_ library executable -> Maybe GitHub
packageConfigDataDir :: forall library executable.
PackageConfig_ library executable -> Maybe String
packageConfigDataFiles :: forall library executable.
PackageConfig_ library executable -> Maybe (List String)
packageConfigExtraDocFiles :: forall library executable.
PackageConfig_ library executable -> Maybe (List String)
packageConfigExtraSourceFiles :: forall library executable.
PackageConfig_ library executable -> Maybe (List String)
packageConfigFlags :: forall library executable.
PackageConfig_ library executable -> Maybe (Map String FlagSection)
packageConfigTestedWith :: forall library executable.
PackageConfig_ library executable -> Maybe (List String)
packageConfigLicenseFile :: forall library executable.
PackageConfig_ library executable -> Maybe (List String)
packageConfigLicense :: forall library executable.
PackageConfig_ library executable -> Maybe (Maybe String)
packageConfigBuildType :: forall library executable.
PackageConfig_ library executable -> Maybe BuildType
packageConfigCopyright :: forall library executable.
PackageConfig_ library executable -> Maybe (List String)
packageConfigMaintainer :: forall library executable.
PackageConfig_ library executable -> Maybe (Maybe (List String))
packageConfigAuthor :: forall library executable.
PackageConfig_ library executable -> Maybe (List String)
packageConfigStability :: forall library executable.
PackageConfig_ library executable -> Maybe String
packageConfigCategory :: forall library executable.
PackageConfig_ library executable -> Maybe String
packageConfigBugReports :: forall library executable.
PackageConfig_ library executable -> Maybe (Maybe String)
packageConfigHomepage :: forall library executable.
PackageConfig_ library executable -> Maybe (Maybe String)
packageConfigDescription :: forall library executable.
PackageConfig_ library executable -> Maybe String
packageConfigSynopsis :: forall library executable.
PackageConfig_ library executable -> Maybe String
packageConfigVersion :: forall library executable.
PackageConfig_ library executable -> Maybe PackageVersion
packageConfigName :: forall library executable.
PackageConfig_ library executable -> Maybe String
..}) = do
  Maybe
  (Map
     String (WithCommonOptions [Path] [Path] [Path] ExecutableSection))
executableMap <- forall (m :: * -> *) a.
Monad m =>
String
-> Maybe (Map String a)
-> Maybe a
-> Warnings m (Maybe (Map String a))
toExecutableMap String
packageName_ Maybe
  (Map
     String (WithCommonOptions [Path] [Path] [Path] ExecutableSection))
packageConfigExecutables Maybe (WithCommonOptions [Path] [Path] [Path] ExecutableSection)
packageConfigExecutable
  let
    globalVerbatim :: Maybe (List Verbatim)
globalVerbatim = forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List Verbatim)
commonOptionsVerbatim GlobalOptions
g
    globalOptions :: GlobalOptions
globalOptions = GlobalOptions
g {commonOptionsVerbatim :: Maybe (List Verbatim)
commonOptionsVerbatim = forall a. Maybe a
Nothing}

    executableNames :: [String]
executableNames = forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] forall k a. Map k a -> [k]
Map.keys Maybe
  (Map
     String (WithCommonOptions [Path] [Path] [Path] ExecutableSection))
executableMap

    toSect :: (Monad m, Monoid a) => WithCommonOptions CSources CxxSources JsSources a -> Warnings m (Section a)
    toSect :: forall (m :: * -> *) a.
(Monad m, Monoid a) =>
WithCommonOptions [Path] [Path] [Path] a -> Warnings m (Section a)
toSect = forall (m :: * -> *) a.
Monad m =>
String
-> [String]
-> WithCommonOptions [Path] [Path] [Path] a
-> Warnings m (Section a)
toSection String
packageName_ [String]
executableNames forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first ((forall a. Monoid a => a
mempty forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ GlobalOptions
globalOptions) forall a. Semigroup a => a -> a -> a
<>)

    toSections :: (Monad m, Monoid a) => Maybe (Map String (WithCommonOptions CSources CxxSources JsSources a)) -> Warnings m (Map String (Section a))
    toSections :: forall (m :: * -> *) a.
(Monad m, Monoid a) =>
Maybe (Map String (WithCommonOptions [Path] [Path] [Path] a))
-> Warnings m (Map String (Section a))
toSections = forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Monoid a => a
mempty) (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse forall (m :: * -> *) a.
(Monad m, Monoid a) =>
WithCommonOptions [Path] [Path] [Path] a -> Warnings m (Section a)
toSect)

    toLib :: Section LibrarySection -> WriterT [String] m (Section Library)
toLib = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String -> Section LibrarySection -> IO (Section Library)
toLibrary String
dir String
packageName_
    toExecutables :: Maybe
  (Map
     String (WithCommonOptions [Path] [Path] [Path] ExecutableSection))
-> WriterT [String] m (Map String (Section Executable))
toExecutables = forall (m :: * -> *) a.
(Monad m, Monoid a) =>
Maybe (Map String (WithCommonOptions [Path] [Path] [Path] a))
-> Warnings m (Map String (Section a))
toSections forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. String
-> String -> Section ExecutableSection -> IO (Section Executable)
toExecutable String
dir String
packageName_)

  Maybe (Section Library)
mLibrary <- forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (forall (m :: * -> *) a.
(Monad m, Monoid a) =>
WithCommonOptions [Path] [Path] [Path] a -> Warnings m (Section a)
toSect forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Section LibrarySection -> WriterT [String] m (Section Library)
toLib) Maybe (WithCommonOptions [Path] [Path] [Path] LibrarySection)
packageConfigLibrary
  Map String (Section Library)
internalLibraries <- forall (m :: * -> *) a.
(Monad m, Monoid a) =>
Maybe (Map String (WithCommonOptions [Path] [Path] [Path] a))
-> Warnings m (Map String (Section a))
toSections Maybe
  (Map
     String (WithCommonOptions [Path] [Path] [Path] LibrarySection))
packageConfigInternalLibraries forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Section LibrarySection -> WriterT [String] m (Section Library)
toLib

  Map String (Section Executable)
executables <- Maybe
  (Map
     String (WithCommonOptions [Path] [Path] [Path] ExecutableSection))
-> WriterT [String] m (Map String (Section Executable))
toExecutables Maybe
  (Map
     String (WithCommonOptions [Path] [Path] [Path] ExecutableSection))
executableMap
  Map String (Section Executable)
tests <- Maybe
  (Map
     String (WithCommonOptions [Path] [Path] [Path] ExecutableSection))
-> WriterT [String] m (Map String (Section Executable))
toExecutables Maybe
  (Map
     String (WithCommonOptions [Path] [Path] [Path] ExecutableSection))
packageConfigTests
  Map String (Section Executable)
benchmarks <- Maybe
  (Map
     String (WithCommonOptions [Path] [Path] [Path] ExecutableSection))
-> WriterT [String] m (Map String (Section Executable))
toExecutables Maybe
  (Map
     String (WithCommonOptions [Path] [Path] [Path] ExecutableSection))
packageConfigBenchmarks

  Bool
licenseFileExists <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ String -> IO Bool
doesFileExist (String
dir String -> ShowS
</> String
"LICENSE")

  [String]
missingSourceDirs <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. Ord a => [a] -> [a]
nub forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> [String]
sort forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Bool -> Bool
not forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO Bool
doesDirectoryExist forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String
dir String -> ShowS
</>)) (
       forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] forall a. Section a -> [String]
sectionSourceDirs Maybe (Section Library)
mLibrary
    forall a. [a] -> [a] -> [a]
++ forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall a. Section a -> [String]
sectionSourceDirs Map String (Section Library)
internalLibraries
    forall a. [a] -> [a] -> [a]
++ forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall a. Section a -> [String]
sectionSourceDirs Map String (Section Executable)
executables
    forall a. [a] -> [a] -> [a]
++ forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall a. Section a -> [String]
sectionSourceDirs Map String (Section Executable)
tests
    forall a. [a] -> [a] -> [a]
++ forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall a. Section a -> [String]
sectionSourceDirs Map String (Section Executable)
benchmarks
    )

  [Path]
extraSourceFiles <- forall (m :: * -> *).
MonadIO m =>
String -> String -> [String] -> Warnings m [Path]
expandGlobs String
"extra-source-files" String
dir (forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List String)
packageConfigExtraSourceFiles)
  [Path]
extraDocFiles <- forall (m :: * -> *).
MonadIO m =>
String -> String -> [String] -> Warnings m [Path]
expandGlobs String
"extra-doc-files" String
dir (forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List String)
packageConfigExtraDocFiles)

  let dataBaseDir :: String
dataBaseDir = forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
dir (String
dir String -> ShowS
</>) Maybe String
packageConfigDataDir

  [Path]
dataFiles <- forall (m :: * -> *).
MonadIO m =>
String -> String -> [String] -> Warnings m [Path]
expandGlobs String
"data-files" String
dataBaseDir (forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List String)
packageConfigDataFiles)

  let
    licenseFiles :: [String]
    licenseFiles :: [String]
licenseFiles = forall a. Maybe (List a) -> [a]
fromMaybeList forall a b. (a -> b) -> a -> b
$ Maybe (List String)
packageConfigLicenseFile forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> do
      forall (f :: * -> *). Alternative f => Bool -> f ()
guard Bool
licenseFileExists
      forall a. a -> Maybe a
Just (forall a. [a] -> List a
List [String
"LICENSE"])

  Maybe (License License)
inferredLicense <- case (Maybe (Maybe String)
packageConfigLicense, [String]
licenseFiles) of
    (Maybe (Maybe String)
Nothing, [String
file]) -> do
      Maybe String
input <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (String -> IO (Maybe String)
tryReadFile (String
dir String -> ShowS
</> String
file))
      case Maybe String
input forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= String -> Maybe (License License)
inferLicense of
        Maybe (License License)
Nothing -> do
          forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell [String
"Inferring license from file " forall a. [a] -> [a] -> [a]
++ String
file forall a. [a] -> [a] -> [a]
++ String
" failed!"]
          forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
        Maybe (License License)
license -> forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (License License)
license
    (Maybe (Maybe String), [String])
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing

  let defaultBuildType :: BuildType
      defaultBuildType :: BuildType
defaultBuildType = forall b a. b -> (a -> b) -> Maybe a -> b
maybe BuildType
Simple (forall a b. a -> b -> a
const BuildType
Custom) Maybe CustomSetup
mCustomSetup

      pkg :: Package
pkg = Package {
        packageName :: String
packageName = String
packageName_
      , packageVersion :: String
packageVersion = forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"0.0.0" PackageVersion -> String
unPackageVersion Maybe PackageVersion
packageConfigVersion
      , packageSynopsis :: Maybe String
packageSynopsis = Maybe String
packageConfigSynopsis
      , packageDescription :: Maybe String
packageDescription = Maybe String
packageConfigDescription
      , packageHomepage :: Maybe String
packageHomepage = Maybe String
homepage
      , packageBugReports :: Maybe String
packageBugReports = Maybe String
bugReports
      , packageCategory :: Maybe String
packageCategory = Maybe String
packageConfigCategory
      , packageStability :: Maybe String
packageStability = Maybe String
packageConfigStability
      , packageAuthor :: [String]
packageAuthor = forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List String)
packageConfigAuthor
      , packageMaintainer :: [String]
packageMaintainer = forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List String)
maintainer
      , packageCopyright :: [String]
packageCopyright = forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List String)
packageConfigCopyright
      , packageBuildType :: BuildType
packageBuildType = forall a. a -> Maybe a -> a
fromMaybe BuildType
defaultBuildType Maybe BuildType
packageConfigBuildType
      , packageLicense :: Maybe String
packageLicense = forall (m :: * -> *) a. Monad m => m (m a) -> m a
join Maybe (Maybe String)
packageConfigLicense
      , packageLicenseFile :: [String]
packageLicenseFile = [String]
licenseFiles
      , packageTestedWith :: [String]
packageTestedWith = forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List String)
packageConfigTestedWith
      , packageFlags :: [Flag]
packageFlags = [Flag]
flags
      , packageExtraSourceFiles :: [Path]
packageExtraSourceFiles = [Path]
extraSourceFiles
      , packageExtraDocFiles :: [Path]
packageExtraDocFiles = [Path]
extraDocFiles
      , packageDataFiles :: [Path]
packageDataFiles = [Path]
dataFiles
      , packageDataDir :: Maybe String
packageDataDir = Maybe String
packageConfigDataDir
      , packageSourceRepository :: Maybe SourceRepository
packageSourceRepository = Maybe SourceRepository
sourceRepository
      , packageCustomSetup :: Maybe CustomSetup
packageCustomSetup = Maybe CustomSetup
mCustomSetup
      , packageLibrary :: Maybe (Section Library)
packageLibrary = Maybe (Section Library)
mLibrary
      , packageInternalLibraries :: Map String (Section Library)
packageInternalLibraries = Map String (Section Library)
internalLibraries
      , packageExecutables :: Map String (Section Executable)
packageExecutables = Map String (Section Executable)
executables
      , packageTests :: Map String (Section Executable)
packageTests = Map String (Section Executable)
tests
      , packageBenchmarks :: Map String (Section Executable)
packageBenchmarks = Map String (Section Executable)
benchmarks
      , packageVerbatim :: [Verbatim]
packageVerbatim = forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List Verbatim)
globalVerbatim
      }

  forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell [String]
nameWarnings
  forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell ([String] -> [String]
formatMissingSourceDirs [String]
missingSourceDirs)

  let (Package
pkg_, String
renderedCabalVersion, Maybe Version
cabalVersion) = Maybe (License License)
-> Package -> (Package, String, Maybe Version)
determineCabalVersion Maybe (License License)
inferredLicense Package
pkg
  forall (m :: * -> *) a. Monad m => a -> m a
return (forall b a. b -> (a -> b) -> Maybe a -> b
maybe Package
pkg_ (Package -> Version -> Package
addPathsModuleToGeneratedModules Package
pkg_) Maybe Version
cabalVersion, String
renderedCabalVersion)
  where
    nameWarnings :: [String]
    packageName_ :: String
    ([String]
nameWarnings, String
packageName_) = case Maybe String
packageConfigName of
      Maybe String
Nothing -> let inferredName :: String
inferredName = ShowS
takeBaseName String
dir in
        ([String
"Package name not specified, inferred " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show String
inferredName], String
inferredName)
      Just String
n -> ([], String
n)

    mCustomSetup :: Maybe CustomSetup
    mCustomSetup :: Maybe CustomSetup
mCustomSetup = CustomSetupSection -> CustomSetup
toCustomSetup forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe CustomSetupSection
packageConfigCustomSetup

    flags :: [Flag]
flags = forall a b. (a -> b) -> [a] -> [b]
map (String, FlagSection) -> Flag
toFlag forall a b. (a -> b) -> a -> b
$ forall a. Maybe (Map String a) -> [(String, a)]
toList Maybe (Map String FlagSection)
packageConfigFlags

    toList :: Maybe (Map String a) -> [(String, a)]
    toList :: forall a. Maybe (Map String a) -> [(String, a)]
toList = forall k a. Map k a -> [(k, a)]
Map.toList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a -> a
fromMaybe forall a. Monoid a => a
mempty

    formatMissingSourceDirs :: [String] -> [String]
formatMissingSourceDirs = forall a b. (a -> b) -> [a] -> [b]
map forall a. Show a => a -> String
f
      where
        f :: a -> String
f a
name = String
"Specified source-dir " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show a
name forall a. [a] -> [a] -> [a]
++ String
" does not exist"

    sourceRepository :: Maybe SourceRepository
    sourceRepository :: Maybe SourceRepository
sourceRepository = Maybe SourceRepository
github forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (String -> Maybe String -> SourceRepository
`SourceRepository` forall a. Maybe a
Nothing) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String
packageConfigGit

    github :: Maybe SourceRepository
    github :: Maybe SourceRepository
github = GitHub -> SourceRepository
toSourceRepository forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe GitHub
packageConfigGithub
      where
        toSourceRepository :: GitHub -> SourceRepository
        toSourceRepository :: GitHub -> SourceRepository
toSourceRepository (GitHub String
owner String
repo Maybe String
subdir) = String -> Maybe String -> SourceRepository
SourceRepository (String
githubBaseUrl forall a. [a] -> [a] -> [a]
++ String
owner forall a. [a] -> [a] -> [a]
++ String
"/" forall a. [a] -> [a] -> [a]
++ String
repo) Maybe String
subdir

    homepage :: Maybe String
    homepage :: Maybe String
homepage = case Maybe (Maybe String)
packageConfigHomepage of
      Just Maybe String
Nothing -> forall a. Maybe a
Nothing
      Maybe (Maybe String)
_ -> forall (m :: * -> *) a. Monad m => m (m a) -> m a
join Maybe (Maybe String)
packageConfigHomepage forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe String
fromGithub
      where
        fromGithub :: Maybe String
fromGithub = (forall a. [a] -> [a] -> [a]
++ String
"#readme") forall b c a. (b -> c) -> (a -> b) -> a -> c
. SourceRepository -> String
sourceRepositoryUrl forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe SourceRepository
github

    bugReports :: Maybe String
    bugReports :: Maybe String
bugReports = case Maybe (Maybe String)
packageConfigBugReports of
      Just Maybe String
Nothing -> forall a. Maybe a
Nothing
      Maybe (Maybe String)
_ -> forall (m :: * -> *) a. Monad m => m (m a) -> m a
join Maybe (Maybe String)
packageConfigBugReports forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe String
fromGithub
      where
        fromGithub :: Maybe String
fromGithub = (forall a. [a] -> [a] -> [a]
++ String
"/issues") forall b c a. (b -> c) -> (a -> b) -> a -> c
. SourceRepository -> String
sourceRepositoryUrl forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe SourceRepository
github

    maintainer :: Maybe (List String)
    maintainer :: Maybe (List String)
maintainer = case (Maybe (List String)
packageConfigAuthor, Maybe (Maybe (List String))
packageConfigMaintainer) of
      (Just List String
_, Maybe (Maybe (List String))
Nothing) -> Maybe (List String)
packageConfigAuthor
      (Maybe (List String)
_, Just Maybe (List String)
m) -> Maybe (List String)
m
      (Maybe (List String), Maybe (Maybe (List String)))
_            -> forall a. Maybe a
Nothing

expandForeignSources
  :: MonadIO m
  => FilePath
  -> Traverse (Warnings m) ParseCSources CSources ParseCxxSources CxxSources ParseJsSources JsSources
expandForeignSources :: forall (m :: * -> *).
MonadIO m =>
String
-> Traverse
     (Warnings m)
     (Maybe (List String))
     [Path]
     (Maybe (List String))
     [Path]
     (Maybe (List String))
     [Path]
expandForeignSources String
dir = Traverse {
    traverseCSources :: Maybe (List String) -> WriterT [String] m [Path]
traverseCSources = forall {m :: * -> *}.
MonadIO m =>
String -> Maybe (List String) -> Warnings m [Path]
expand String
"c-sources"
  , traverseCxxSources :: Maybe (List String) -> WriterT [String] m [Path]
traverseCxxSources = forall {m :: * -> *}.
MonadIO m =>
String -> Maybe (List String) -> Warnings m [Path]
expand String
"cxx-sources"
  , traverseJsSources :: Maybe (List String) -> WriterT [String] m [Path]
traverseJsSources = forall {m :: * -> *}.
MonadIO m =>
String -> Maybe (List String) -> Warnings m [Path]
expand String
"js-sources"
  }
  where
    expand :: String -> Maybe (List String) -> Warnings m [Path]
expand String
fieldName Maybe (List String)
xs = do
      forall (m :: * -> *).
MonadIO m =>
String -> String -> [String] -> Warnings m [Path]
expandGlobs String
fieldName String
dir (forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List String)
xs)

newtype Path = Path { Path -> String
unPath :: FilePath }
  deriving (Path -> Path -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Path -> Path -> Bool
$c/= :: Path -> Path -> Bool
== :: Path -> Path -> Bool
$c== :: Path -> Path -> Bool
Eq, Int -> Path -> ShowS
[Path] -> ShowS
Path -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Path] -> ShowS
$cshowList :: [Path] -> ShowS
show :: Path -> String
$cshow :: Path -> String
showsPrec :: Int -> Path -> ShowS
$cshowsPrec :: Int -> Path -> ShowS
Show, Eq Path
Path -> Path -> Bool
Path -> Path -> Ordering
Path -> Path -> Path
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Path -> Path -> Path
$cmin :: Path -> Path -> Path
max :: Path -> Path -> Path
$cmax :: Path -> Path -> Path
>= :: Path -> Path -> Bool
$c>= :: Path -> Path -> Bool
> :: Path -> Path -> Bool
$c> :: Path -> Path -> Bool
<= :: Path -> Path -> Bool
$c<= :: Path -> Path -> Bool
< :: Path -> Path -> Bool
$c< :: Path -> Path -> Bool
compare :: Path -> Path -> Ordering
$ccompare :: Path -> Path -> Ordering
Ord)

instance IsString Path where
  fromString :: String -> Path
fromString = String -> Path
Path

expandGlobs :: MonadIO m => String -> FilePath -> [String] -> Warnings m [Path]
expandGlobs :: forall (m :: * -> *).
MonadIO m =>
String -> String -> [String] -> Warnings m [Path]
expandGlobs String
name String
dir [String]
patterns = forall a b. (a -> b) -> [a] -> [b]
map String -> Path
Path forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> do
  ([String]
warnings, [String]
files) <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ String -> String -> [String] -> IO ([String], [String])
Util.expandGlobs String
name String
dir [String]
patterns
  forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell [String]
warnings
  forall (m :: * -> *) a. Monad m => a -> m a
return [String]
files

toCustomSetup :: CustomSetupSection -> CustomSetup
toCustomSetup :: CustomSetupSection -> CustomSetup
toCustomSetup CustomSetupSection{Maybe Dependencies
customSetupSectionDependencies :: Maybe Dependencies
customSetupSectionDependencies :: CustomSetupSection -> Maybe Dependencies
..} = CustomSetup
  { customSetupDependencies :: Dependencies
customSetupDependencies = forall a. a -> Maybe a -> a
fromMaybe forall a. Monoid a => a
mempty Maybe Dependencies
customSetupSectionDependencies }

traverseSectionAndConditionals :: Monad m
  => (acc -> Section a -> m (acc, b))
  -> (acc -> Section a -> m (acc, b))
  -> acc
  -> Section a
  -> m (Section b)
traverseSectionAndConditionals :: forall (m :: * -> *) acc a b.
Monad m =>
(acc -> Section a -> m (acc, b))
-> (acc -> Section a -> m (acc, b))
-> acc
-> Section a
-> m (Section b)
traverseSectionAndConditionals acc -> Section a -> m (acc, b)
fData acc -> Section a -> m (acc, b)
fConditionals acc
acc0 sect :: Section a
sect@Section{a
[String]
[Path]
[Conditional (Section a)]
[Verbatim]
Maybe Bool
Maybe Language
Map BuildTool DependencyVersion
Dependencies
SystemBuildTools
sectionVerbatim :: [Verbatim]
sectionSystemBuildTools :: SystemBuildTools
sectionBuildTools :: Map BuildTool DependencyVersion
sectionConditionals :: [Conditional (Section a)]
sectionBuildable :: Maybe Bool
sectionLdOptions :: [String]
sectionInstallIncludes :: [String]
sectionIncludeDirs :: [String]
sectionFrameworks :: [String]
sectionExtraFrameworksDirs :: [String]
sectionExtraLibraries :: [String]
sectionExtraLibDirs :: [String]
sectionJsSources :: [Path]
sectionCxxSources :: [Path]
sectionCxxOptions :: [String]
sectionCSources :: [Path]
sectionCcOptions :: [String]
sectionCppOptions :: [String]
sectionGhcjsOptions :: [String]
sectionGhcSharedOptions :: [String]
sectionGhcProfOptions :: [String]
sectionGhcOptions :: [String]
sectionLanguage :: Maybe Language
sectionOtherExtensions :: [String]
sectionDefaultExtensions :: [String]
sectionPkgConfigDependencies :: [String]
sectionDependencies :: Dependencies
sectionSourceDirs :: [String]
sectionData :: a
sectionVerbatim :: forall a. Section a -> [Verbatim]
sectionSystemBuildTools :: forall a. Section a -> SystemBuildTools
sectionBuildTools :: forall a. Section a -> Map BuildTool DependencyVersion
sectionConditionals :: forall a. Section a -> [Conditional (Section a)]
sectionBuildable :: forall a. Section a -> Maybe Bool
sectionLdOptions :: forall a. Section a -> [String]
sectionInstallIncludes :: forall a. Section a -> [String]
sectionIncludeDirs :: forall a. Section a -> [String]
sectionFrameworks :: forall a. Section a -> [String]
sectionExtraFrameworksDirs :: forall a. Section a -> [String]
sectionExtraLibraries :: forall a. Section a -> [String]
sectionExtraLibDirs :: forall a. Section a -> [String]
sectionJsSources :: forall a. Section a -> [Path]
sectionCxxSources :: forall a. Section a -> [Path]
sectionCxxOptions :: forall a. Section a -> [String]
sectionCSources :: forall a. Section a -> [Path]
sectionCcOptions :: forall a. Section a -> [String]
sectionCppOptions :: forall a. Section a -> [String]
sectionGhcjsOptions :: forall a. Section a -> [String]
sectionGhcSharedOptions :: forall a. Section a -> [String]
sectionGhcProfOptions :: forall a. Section a -> [String]
sectionGhcOptions :: forall a. Section a -> [String]
sectionLanguage :: forall a. Section a -> Maybe Language
sectionOtherExtensions :: forall a. Section a -> [String]
sectionDefaultExtensions :: forall a. Section a -> [String]
sectionPkgConfigDependencies :: forall a. Section a -> [String]
sectionDependencies :: forall a. Section a -> Dependencies
sectionSourceDirs :: forall a. Section a -> [String]
sectionData :: forall a. Section a -> a
..} = do
  (acc
acc1, b
x) <- acc -> Section a -> m (acc, b)
fData acc
acc0 Section a
sect
  [Conditional (Section b)]
xs <- acc -> [Conditional (Section a)] -> m [Conditional (Section b)]
traverseConditionals acc
acc1 [Conditional (Section a)]
sectionConditionals
  forall (m :: * -> *) a. Monad m => a -> m a
return Section a
sect{sectionData :: b
sectionData = b
x, sectionConditionals :: [Conditional (Section b)]
sectionConditionals = [Conditional (Section b)]
xs}
  where
    traverseConditionals :: acc -> [Conditional (Section a)] -> m [Conditional (Section b)]
traverseConditionals = forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) acc a b.
Monad m =>
(acc -> Section a -> m (acc, b))
-> (acc -> Section a -> m (acc, b))
-> acc
-> Section a
-> m (Section b)
traverseSectionAndConditionals acc -> Section a -> m (acc, b)
fConditionals acc -> Section a -> m (acc, b)
fConditionals

getMentionedLibraryModules :: LibrarySection -> [Module]
getMentionedLibraryModules :: LibrarySection -> [Module]
getMentionedLibraryModules (LibrarySection Maybe Bool
_ Maybe String
_ Maybe (List Module)
exposedModules Maybe (List Module)
generatedExposedModules Maybe (List Module)
otherModules Maybe (List Module)
generatedOtherModules Maybe (List String)
_ Maybe (List String)
_)
  = forall a. Maybe (List a) -> [a]
fromMaybeList (Maybe (List Module)
exposedModules forall a. Semigroup a => a -> a -> a
<> Maybe (List Module)
generatedExposedModules forall a. Semigroup a => a -> a -> a
<> Maybe (List Module)
otherModules forall a. Semigroup a => a -> a -> a
<> Maybe (List Module)
generatedOtherModules)

getLibraryModules :: Library -> [Module]
getLibraryModules :: Library -> [Module]
getLibraryModules Library{[String]
[Module]
Maybe Bool
Maybe String
librarySignatures :: [String]
libraryReexportedModules :: [String]
libraryGeneratedModules :: [Module]
libraryOtherModules :: [Module]
libraryExposedModules :: [Module]
libraryVisibility :: Maybe String
libraryExposed :: Maybe Bool
libraryOtherModules :: Library -> [Module]
libraryExposedModules :: Library -> [Module]
libraryExposed :: Library -> Maybe Bool
libraryVisibility :: Library -> Maybe String
librarySignatures :: Library -> [String]
libraryReexportedModules :: Library -> [String]
libraryGeneratedModules :: Library -> [Module]
..} = [Module]
libraryExposedModules forall a. [a] -> [a] -> [a]
++ [Module]
libraryOtherModules

getExecutableModules :: Executable -> [Module]
getExecutableModules :: Executable -> [Module]
getExecutableModules Executable{[Module]
Maybe String
executableGeneratedModules :: [Module]
executableOtherModules :: [Module]
executableMain :: Maybe String
executableMain :: Executable -> Maybe String
executableGeneratedModules :: Executable -> [Module]
executableOtherModules :: Executable -> [Module]
..} = [Module]
executableOtherModules

listModules :: FilePath -> Section a -> IO [Module]
listModules :: forall a. String -> Section a -> IO [Module]
listModules String
dir Section{a
[String]
[Path]
[Conditional (Section a)]
[Verbatim]
Maybe Bool
Maybe Language
Map BuildTool DependencyVersion
Dependencies
SystemBuildTools
sectionVerbatim :: [Verbatim]
sectionSystemBuildTools :: SystemBuildTools
sectionBuildTools :: Map BuildTool DependencyVersion
sectionConditionals :: [Conditional (Section a)]
sectionBuildable :: Maybe Bool
sectionLdOptions :: [String]
sectionInstallIncludes :: [String]
sectionIncludeDirs :: [String]
sectionFrameworks :: [String]
sectionExtraFrameworksDirs :: [String]
sectionExtraLibraries :: [String]
sectionExtraLibDirs :: [String]
sectionJsSources :: [Path]
sectionCxxSources :: [Path]
sectionCxxOptions :: [String]
sectionCSources :: [Path]
sectionCcOptions :: [String]
sectionCppOptions :: [String]
sectionGhcjsOptions :: [String]
sectionGhcSharedOptions :: [String]
sectionGhcProfOptions :: [String]
sectionGhcOptions :: [String]
sectionLanguage :: Maybe Language
sectionOtherExtensions :: [String]
sectionDefaultExtensions :: [String]
sectionPkgConfigDependencies :: [String]
sectionDependencies :: Dependencies
sectionSourceDirs :: [String]
sectionData :: a
sectionVerbatim :: forall a. Section a -> [Verbatim]
sectionSystemBuildTools :: forall a. Section a -> SystemBuildTools
sectionBuildTools :: forall a. Section a -> Map BuildTool DependencyVersion
sectionConditionals :: forall a. Section a -> [Conditional (Section a)]
sectionBuildable :: forall a. Section a -> Maybe Bool
sectionLdOptions :: forall a. Section a -> [String]
sectionInstallIncludes :: forall a. Section a -> [String]
sectionIncludeDirs :: forall a. Section a -> [String]
sectionFrameworks :: forall a. Section a -> [String]
sectionExtraFrameworksDirs :: forall a. Section a -> [String]
sectionExtraLibraries :: forall a. Section a -> [String]
sectionExtraLibDirs :: forall a. Section a -> [String]
sectionJsSources :: forall a. Section a -> [Path]
sectionCxxSources :: forall a. Section a -> [Path]
sectionCxxOptions :: forall a. Section a -> [String]
sectionCSources :: forall a. Section a -> [Path]
sectionCcOptions :: forall a. Section a -> [String]
sectionCppOptions :: forall a. Section a -> [String]
sectionGhcjsOptions :: forall a. Section a -> [String]
sectionGhcSharedOptions :: forall a. Section a -> [String]
sectionGhcProfOptions :: forall a. Section a -> [String]
sectionGhcOptions :: forall a. Section a -> [String]
sectionLanguage :: forall a. Section a -> Maybe Language
sectionOtherExtensions :: forall a. Section a -> [String]
sectionDefaultExtensions :: forall a. Section a -> [String]
sectionPkgConfigDependencies :: forall a. Section a -> [String]
sectionDependencies :: forall a. Section a -> Dependencies
sectionSourceDirs :: forall a. Section a -> [String]
sectionData :: forall a. Section a -> a
..} = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (String -> String -> IO [Module]
getModules String
dir) [String]
sectionSourceDirs

removeConditionalsThatAreAlwaysFalse :: Section a -> Section a
removeConditionalsThatAreAlwaysFalse :: forall a. Section a -> Section a
removeConditionalsThatAreAlwaysFalse Section a
sect = Section a
sect {
    sectionConditionals :: [Conditional (Section a)]
sectionConditionals = forall a. (a -> Bool) -> [a] -> [a]
filter forall a. Conditional a -> Bool
p forall a b. (a -> b) -> a -> b
$ forall a. Section a -> [Conditional (Section a)]
sectionConditionals Section a
sect
  }
  where
    p :: Conditional a -> Bool
p = (forall a. Eq a => a -> a -> Bool
/= Bool -> Cond
CondBool Bool
False) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Conditional a -> Cond
conditionalCondition

inferModules ::
     FilePath
  -> String
  -> (a -> [Module])
  -> (b -> [Module])
  -> ([Module] -> [Module] -> a -> b)
  -> ([Module] -> a -> b)
  -> Section a
  -> IO (Section b)
inferModules :: forall a b.
String
-> String
-> (a -> [Module])
-> (b -> [Module])
-> ([Module] -> [Module] -> a -> b)
-> ([Module] -> a -> b)
-> Section a
-> IO (Section b)
inferModules String
dir String
packageName_ a -> [Module]
getMentionedModules b -> [Module]
getInferredModules [Module] -> [Module] -> a -> b
fromData [Module] -> a -> b
fromConditionals = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Section a -> Section a
removeConditionalsThatAreAlwaysFalse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) acc a b.
Monad m =>
(acc -> Section a -> m (acc, b))
-> (acc -> Section a -> m (acc, b))
-> acc
-> Section a
-> m (Section b)
traverseSectionAndConditionals
  (([Module] -> [Module] -> a -> b)
-> [Module] -> [Module] -> Section a -> IO ([Module], b)
fromConfigSection [Module] -> [Module] -> a -> b
fromData [String -> Module
pathsModuleFromPackageName String
packageName_])
  (([Module] -> [Module] -> a -> b)
-> [Module] -> [Module] -> Section a -> IO ([Module], b)
fromConfigSection (\ [] -> [Module] -> a -> b
fromConditionals) [])
  []
  where
    fromConfigSection :: ([Module] -> [Module] -> a -> b)
-> [Module] -> [Module] -> Section a -> IO ([Module], b)
fromConfigSection [Module] -> [Module] -> a -> b
fromConfig [Module]
pathsModule_ [Module]
outerModules sect :: Section a
sect@Section{sectionData :: forall a. Section a -> a
sectionData = a
conf} = do
      [Module]
modules <- forall a. String -> Section a -> IO [Module]
listModules String
dir Section a
sect
      let
        mentionedModules :: [Module]
mentionedModules = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap a -> [Module]
getMentionedModules Section a
sect
        inferableModules :: [Module]
inferableModules = ([Module]
modules forall a. Eq a => [a] -> [a] -> [a]
\\ [Module]
outerModules) forall a. Eq a => [a] -> [a] -> [a]
\\ [Module]
mentionedModules
        pathsModule :: [Module]
pathsModule = ([Module]
pathsModule_ forall a. Eq a => [a] -> [a] -> [a]
\\ [Module]
outerModules) forall a. Eq a => [a] -> [a] -> [a]
\\ [Module]
mentionedModules
        r :: b
r = [Module] -> [Module] -> a -> b
fromConfig [Module]
pathsModule [Module]
inferableModules a
conf
      forall (m :: * -> *) a. Monad m => a -> m a
return ([Module]
outerModules forall a. [a] -> [a] -> [a]
++ b -> [Module]
getInferredModules b
r, b
r)

toLibrary :: FilePath -> String -> Section LibrarySection -> IO (Section Library)
toLibrary :: String -> String -> Section LibrarySection -> IO (Section Library)
toLibrary String
dir String
name =
    forall a b.
String
-> String
-> (a -> [Module])
-> (b -> [Module])
-> ([Module] -> [Module] -> a -> b)
-> ([Module] -> a -> b)
-> Section a
-> IO (Section b)
inferModules String
dir String
name LibrarySection -> [Module]
getMentionedLibraryModules Library -> [Module]
getLibraryModules [Module] -> [Module] -> LibrarySection -> Library
fromLibrarySectionTopLevel [Module] -> LibrarySection -> Library
fromLibrarySectionInConditional
  where
    fromLibrarySectionTopLevel :: [Module] -> [Module] -> LibrarySection -> Library
    fromLibrarySectionTopLevel :: [Module] -> [Module] -> LibrarySection -> Library
fromLibrarySectionTopLevel [Module]
pathsModule [Module]
inferableModules LibrarySection{Maybe Bool
Maybe String
Maybe (List String)
Maybe (List Module)
librarySectionSignatures :: Maybe (List String)
librarySectionReexportedModules :: Maybe (List String)
librarySectionGeneratedOtherModules :: Maybe (List Module)
librarySectionOtherModules :: Maybe (List Module)
librarySectionGeneratedExposedModules :: Maybe (List Module)
librarySectionExposedModules :: Maybe (List Module)
librarySectionVisibility :: Maybe String
librarySectionExposed :: Maybe Bool
librarySectionSignatures :: LibrarySection -> Maybe (List String)
librarySectionReexportedModules :: LibrarySection -> Maybe (List String)
librarySectionGeneratedOtherModules :: LibrarySection -> Maybe (List Module)
librarySectionOtherModules :: LibrarySection -> Maybe (List Module)
librarySectionGeneratedExposedModules :: LibrarySection -> Maybe (List Module)
librarySectionExposedModules :: LibrarySection -> Maybe (List Module)
librarySectionVisibility :: LibrarySection -> Maybe String
librarySectionExposed :: LibrarySection -> Maybe Bool
..} =
      Maybe Bool
-> Maybe String
-> [Module]
-> [Module]
-> [Module]
-> [String]
-> [String]
-> Library
Library Maybe Bool
librarySectionExposed Maybe String
librarySectionVisibility [Module]
exposedModules [Module]
otherModules [Module]
generatedModules [String]
reexportedModules [String]
signatures
      where
        ([Module]
exposedModules, [Module]
otherModules, [Module]
generatedModules) =
          [Module]
-> [Module]
-> Maybe (List Module)
-> Maybe (List Module)
-> Maybe (List Module)
-> Maybe (List Module)
-> ([Module], [Module], [Module])
determineModules [Module]
pathsModule [Module]
inferableModules Maybe (List Module)
librarySectionExposedModules Maybe (List Module)
librarySectionGeneratedExposedModules Maybe (List Module)
librarySectionOtherModules Maybe (List Module)
librarySectionGeneratedOtherModules
        reexportedModules :: [String]
reexportedModules = forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List String)
librarySectionReexportedModules
        signatures :: [String]
signatures = forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List String)
librarySectionSignatures

determineModules :: [Module] -> [Module] -> Maybe (List Module) -> Maybe (List Module) -> Maybe (List Module) -> Maybe (List Module) -> ([Module], [Module], [Module])
determineModules :: [Module]
-> [Module]
-> Maybe (List Module)
-> Maybe (List Module)
-> Maybe (List Module)
-> Maybe (List Module)
-> ([Module], [Module], [Module])
determineModules [Module]
pathsModule [Module]
inferable Maybe (List Module)
mExposed Maybe (List Module)
mGeneratedExposed Maybe (List Module)
mOther Maybe (List Module)
mGeneratedOther =
  ([Module]
exposed, [Module]
others, [Module]
generated)
  where
    generated :: [Module]
generated = forall a. Maybe (List a) -> [a]
fromMaybeList (Maybe (List Module)
mGeneratedExposed forall a. Semigroup a => a -> a -> a
<> Maybe (List Module)
mGeneratedOther)
    exposed :: [Module]
exposed = forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Module]
inferable forall a. List a -> [a]
fromList Maybe (List Module)
mExposed forall a. [a] -> [a] -> [a]
++ forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List Module)
mGeneratedExposed
    others :: [Module]
others = forall b a. b -> (a -> b) -> Maybe a -> b
maybe (([Module]
inferable forall a. Eq a => [a] -> [a] -> [a]
\\ [Module]
exposed) forall a. [a] -> [a] -> [a]
++ [Module]
pathsModule) forall a. List a -> [a]
fromList Maybe (List Module)
mOther forall a. [a] -> [a] -> [a]
++ forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List Module)
mGeneratedOther

fromLibrarySectionInConditional :: [Module] -> LibrarySection -> Library
fromLibrarySectionInConditional :: [Module] -> LibrarySection -> Library
fromLibrarySectionInConditional [Module]
inferableModules lib :: LibrarySection
lib@(LibrarySection Maybe Bool
_ Maybe String
_ Maybe (List Module)
exposedModules Maybe (List Module)
_ Maybe (List Module)
otherModules Maybe (List Module)
_ Maybe (List String)
_ Maybe (List String)
_) =
  case (Maybe (List Module)
exposedModules, Maybe (List Module)
otherModules) of
    (Maybe (List Module)
Nothing, Maybe (List Module)
Nothing) -> [Module] -> Library -> Library
addToOtherModules [Module]
inferableModules (LibrarySection -> Library
fromLibrarySectionPlain LibrarySection
lib)
    (Maybe (List Module), Maybe (List Module))
_ -> LibrarySection -> Library
fromLibrarySectionPlain LibrarySection
lib
  where
    addToOtherModules :: [Module] -> Library -> Library
addToOtherModules [Module]
xs Library
r = Library
r {libraryOtherModules :: [Module]
libraryOtherModules = [Module]
xs forall a. [a] -> [a] -> [a]
++ Library -> [Module]
libraryOtherModules Library
r}

fromLibrarySectionPlain :: LibrarySection -> Library
fromLibrarySectionPlain :: LibrarySection -> Library
fromLibrarySectionPlain LibrarySection{Maybe Bool
Maybe String
Maybe (List String)
Maybe (List Module)
librarySectionSignatures :: Maybe (List String)
librarySectionReexportedModules :: Maybe (List String)
librarySectionGeneratedOtherModules :: Maybe (List Module)
librarySectionOtherModules :: Maybe (List Module)
librarySectionGeneratedExposedModules :: Maybe (List Module)
librarySectionExposedModules :: Maybe (List Module)
librarySectionVisibility :: Maybe String
librarySectionExposed :: Maybe Bool
librarySectionSignatures :: LibrarySection -> Maybe (List String)
librarySectionReexportedModules :: LibrarySection -> Maybe (List String)
librarySectionGeneratedOtherModules :: LibrarySection -> Maybe (List Module)
librarySectionOtherModules :: LibrarySection -> Maybe (List Module)
librarySectionGeneratedExposedModules :: LibrarySection -> Maybe (List Module)
librarySectionExposedModules :: LibrarySection -> Maybe (List Module)
librarySectionVisibility :: LibrarySection -> Maybe String
librarySectionExposed :: LibrarySection -> Maybe Bool
..} = Library {
    libraryExposed :: Maybe Bool
libraryExposed = Maybe Bool
librarySectionExposed
  , libraryVisibility :: Maybe String
libraryVisibility = Maybe String
librarySectionVisibility
  , libraryExposedModules :: [Module]
libraryExposedModules = forall a. Maybe (List a) -> [a]
fromMaybeList (Maybe (List Module)
librarySectionExposedModules forall a. Semigroup a => a -> a -> a
<> Maybe (List Module)
librarySectionGeneratedExposedModules)
  , libraryOtherModules :: [Module]
libraryOtherModules = forall a. Maybe (List a) -> [a]
fromMaybeList (Maybe (List Module)
librarySectionOtherModules forall a. Semigroup a => a -> a -> a
<> Maybe (List Module)
librarySectionGeneratedOtherModules)
  , libraryGeneratedModules :: [Module]
libraryGeneratedModules = forall a. Maybe (List a) -> [a]
fromMaybeList (Maybe (List Module)
librarySectionGeneratedOtherModules forall a. Semigroup a => a -> a -> a
<> Maybe (List Module)
librarySectionGeneratedExposedModules)
  , libraryReexportedModules :: [String]
libraryReexportedModules = forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List String)
librarySectionReexportedModules
  , librarySignatures :: [String]
librarySignatures = forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List String)
librarySectionSignatures
  }

getMentionedExecutableModules :: ExecutableSection -> [Module]
getMentionedExecutableModules :: ExecutableSection -> [Module]
getMentionedExecutableModules (ExecutableSection (Alias (Last Maybe String
main)) Maybe (List Module)
otherModules Maybe (List Module)
generatedModules)=
  forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (:) (Path -> Module
toModule forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Path
Path.fromFilePath forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String
main) forall a b. (a -> b) -> a -> b
$ forall a. Maybe (List a) -> [a]
fromMaybeList (Maybe (List Module)
otherModules forall a. Semigroup a => a -> a -> a
<> Maybe (List Module)
generatedModules)

toExecutable :: FilePath -> String -> Section ExecutableSection -> IO (Section Executable)
toExecutable :: String
-> String -> Section ExecutableSection -> IO (Section Executable)
toExecutable String
dir String
packageName_ =
    forall a b.
String
-> String
-> (a -> [Module])
-> (b -> [Module])
-> ([Module] -> [Module] -> a -> b)
-> ([Module] -> a -> b)
-> Section a
-> IO (Section b)
inferModules String
dir String
packageName_ ExecutableSection -> [Module]
getMentionedExecutableModules Executable -> [Module]
getExecutableModules [Module] -> [Module] -> ExecutableSection -> Executable
fromExecutableSection ([Module] -> [Module] -> ExecutableSection -> Executable
fromExecutableSection [])
  forall b c a. (b -> c) -> (a -> b) -> a -> c
. Section ExecutableSection -> Section ExecutableSection
expandMain
  where
    fromExecutableSection :: [Module] -> [Module] -> ExecutableSection -> Executable
    fromExecutableSection :: [Module] -> [Module] -> ExecutableSection -> Executable
fromExecutableSection [Module]
pathsModule [Module]
inferableModules ExecutableSection{Maybe (List Module)
Alias 'True "main-is" (Last String)
executableSectionGeneratedOtherModules :: Maybe (List Module)
executableSectionOtherModules :: Maybe (List Module)
executableSectionMain :: Alias 'True "main-is" (Last String)
executableSectionGeneratedOtherModules :: ExecutableSection -> Maybe (List Module)
executableSectionOtherModules :: ExecutableSection -> Maybe (List Module)
executableSectionMain :: ExecutableSection -> Alias 'True "main-is" (Last String)
..} =
      (Maybe String -> [Module] -> [Module] -> Executable
Executable (forall a. Last a -> Maybe a
getLast forall a b. (a -> b) -> a -> b
$ forall (deprecated :: Bool) (alias :: Symbol) a.
Alias deprecated alias a -> a
unAlias Alias 'True "main-is" (Last String)
executableSectionMain) ([Module]
otherModules forall a. [a] -> [a] -> [a]
++ [Module]
generatedModules) [Module]
generatedModules)
      where
        otherModules :: [Module]
otherModules = forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([Module]
inferableModules forall a. [a] -> [a] -> [a]
++ [Module]
pathsModule) forall a. List a -> [a]
fromList Maybe (List Module)
executableSectionOtherModules
        generatedModules :: [Module]
generatedModules = forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] forall a. List a -> [a]
fromList Maybe (List Module)
executableSectionGeneratedOtherModules

expandMain :: Section ExecutableSection -> Section ExecutableSection
expandMain :: Section ExecutableSection -> Section ExecutableSection
expandMain = Section ([String], ExecutableSection) -> Section ExecutableSection
flatten forall b c a. (b -> c) -> (a -> b) -> a -> c
. Section ExecutableSection -> Section ([String], ExecutableSection)
expand
  where
    expand :: Section ExecutableSection -> Section ([GhcOption], ExecutableSection)
    expand :: Section ExecutableSection -> Section ([String], ExecutableSection)
expand = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ExecutableSection -> ([String], ExecutableSection)
go
      where
        go :: ExecutableSection -> ([String], ExecutableSection)
go exec :: ExecutableSection
exec@ExecutableSection{Maybe (List Module)
Alias 'True "main-is" (Last String)
executableSectionGeneratedOtherModules :: Maybe (List Module)
executableSectionOtherModules :: Maybe (List Module)
executableSectionMain :: Alias 'True "main-is" (Last String)
executableSectionGeneratedOtherModules :: ExecutableSection -> Maybe (List Module)
executableSectionOtherModules :: ExecutableSection -> Maybe (List Module)
executableSectionMain :: ExecutableSection -> Alias 'True "main-is" (Last String)
..} =
          let
            (Maybe String
mainSrcFile, [String]
ghcOptions) = forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall a. Maybe a
Nothing, []) (forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> (String, [String])
parseMain) (forall a. Last a -> Maybe a
getLast forall a b. (a -> b) -> a -> b
$ forall (deprecated :: Bool) (alias :: Symbol) a.
Alias deprecated alias a -> a
unAlias Alias 'True "main-is" (Last String)
executableSectionMain)
          in
            ([String]
ghcOptions, ExecutableSection
exec{executableSectionMain :: Alias 'True "main-is" (Last String)
executableSectionMain = forall (deprecated :: Bool) (alias :: Symbol) a.
a -> Alias deprecated alias a
Alias forall a b. (a -> b) -> a -> b
$ forall a. Maybe a -> Last a
Last Maybe String
mainSrcFile})

    flatten :: Section ([GhcOption], ExecutableSection) -> Section ExecutableSection
    flatten :: Section ([String], ExecutableSection) -> Section ExecutableSection
flatten sect :: Section ([String], ExecutableSection)
sect@Section{sectionData :: forall a. Section a -> a
sectionData = ([String]
ghcOptions, ExecutableSection
exec), [String]
[Path]
[Conditional (Section ([String], ExecutableSection))]
[Verbatim]
Maybe Bool
Maybe Language
Map BuildTool DependencyVersion
Dependencies
SystemBuildTools
sectionVerbatim :: [Verbatim]
sectionSystemBuildTools :: SystemBuildTools
sectionBuildTools :: Map BuildTool DependencyVersion
sectionConditionals :: [Conditional (Section ([String], ExecutableSection))]
sectionBuildable :: Maybe Bool
sectionLdOptions :: [String]
sectionInstallIncludes :: [String]
sectionIncludeDirs :: [String]
sectionFrameworks :: [String]
sectionExtraFrameworksDirs :: [String]
sectionExtraLibraries :: [String]
sectionExtraLibDirs :: [String]
sectionJsSources :: [Path]
sectionCxxSources :: [Path]
sectionCxxOptions :: [String]
sectionCSources :: [Path]
sectionCcOptions :: [String]
sectionCppOptions :: [String]
sectionGhcjsOptions :: [String]
sectionGhcSharedOptions :: [String]
sectionGhcProfOptions :: [String]
sectionGhcOptions :: [String]
sectionLanguage :: Maybe Language
sectionOtherExtensions :: [String]
sectionDefaultExtensions :: [String]
sectionPkgConfigDependencies :: [String]
sectionDependencies :: Dependencies
sectionSourceDirs :: [String]
sectionVerbatim :: forall a. Section a -> [Verbatim]
sectionSystemBuildTools :: forall a. Section a -> SystemBuildTools
sectionBuildTools :: forall a. Section a -> Map BuildTool DependencyVersion
sectionConditionals :: forall a. Section a -> [Conditional (Section a)]
sectionBuildable :: forall a. Section a -> Maybe Bool
sectionLdOptions :: forall a. Section a -> [String]
sectionInstallIncludes :: forall a. Section a -> [String]
sectionIncludeDirs :: forall a. Section a -> [String]
sectionFrameworks :: forall a. Section a -> [String]
sectionExtraFrameworksDirs :: forall a. Section a -> [String]
sectionExtraLibraries :: forall a. Section a -> [String]
sectionExtraLibDirs :: forall a. Section a -> [String]
sectionJsSources :: forall a. Section a -> [Path]
sectionCxxSources :: forall a. Section a -> [Path]
sectionCxxOptions :: forall a. Section a -> [String]
sectionCSources :: forall a. Section a -> [Path]
sectionCcOptions :: forall a. Section a -> [String]
sectionCppOptions :: forall a. Section a -> [String]
sectionGhcjsOptions :: forall a. Section a -> [String]
sectionGhcSharedOptions :: forall a. Section a -> [String]
sectionGhcProfOptions :: forall a. Section a -> [String]
sectionGhcOptions :: forall a. Section a -> [String]
sectionLanguage :: forall a. Section a -> Maybe Language
sectionOtherExtensions :: forall a. Section a -> [String]
sectionDefaultExtensions :: forall a. Section a -> [String]
sectionPkgConfigDependencies :: forall a. Section a -> [String]
sectionDependencies :: forall a. Section a -> Dependencies
sectionSourceDirs :: forall a. Section a -> [String]
..} = Section ([String], ExecutableSection)
sect{
        sectionData :: ExecutableSection
sectionData = ExecutableSection
exec
      , sectionGhcOptions :: [String]
sectionGhcOptions = [String]
sectionGhcOptions forall a. [a] -> [a] -> [a]
++ [String]
ghcOptions
      , sectionConditionals :: [Conditional (Section ExecutableSection)]
sectionConditionals = forall a b. (a -> b) -> [a] -> [b]
map (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Section ([String], ExecutableSection) -> Section ExecutableSection
flatten) [Conditional (Section ([String], ExecutableSection))]
sectionConditionals
      }

toSection :: Monad m => String -> [String] -> WithCommonOptions CSources CxxSources JsSources a -> Warnings m (Section a)
toSection :: forall (m :: * -> *) a.
Monad m =>
String
-> [String]
-> WithCommonOptions [Path] [Path] [Path] a
-> Warnings m (Section a)
toSection String
packageName_ [String]
executableNames = forall {m :: * -> *} {a}.
Monad m =>
Product (CommonOptions [Path] [Path] [Path] a) a
-> WriterT [String] m (Section a)
go
  where
    go :: Product (CommonOptions [Path] [Path] [Path] a) a
-> WriterT [String] m (Section a)
go (Product CommonOptions{[Path]
Maybe (List String)
Maybe (List (ConditionalSection [Path] [Path] [Path] a))
Maybe (List Verbatim)
Maybe SystemBuildTools
Last Bool
Alias 'False "pkgconfig-depends" (Maybe (List String))
Alias 'True "hs-source-dirs" (Maybe (List String))
Alias 'True "build-depends" (Maybe Dependencies)
Alias 'True "default-language" (Last (Maybe Language))
Alias 'True "build-tool-depends" (Maybe BuildTools)
commonOptionsVerbatim :: Maybe (List Verbatim)
commonOptionsSystemBuildTools :: Maybe SystemBuildTools
commonOptionsBuildTools :: Alias 'True "build-tool-depends" (Maybe BuildTools)
commonOptionsWhen :: Maybe (List (ConditionalSection [Path] [Path] [Path] a))
commonOptionsBuildable :: Last Bool
commonOptionsLdOptions :: Maybe (List String)
commonOptionsInstallIncludes :: Maybe (List String)
commonOptionsIncludeDirs :: Maybe (List String)
commonOptionsFrameworks :: Maybe (List String)
commonOptionsExtraFrameworksDirs :: Maybe (List String)
commonOptionsExtraLibraries :: Maybe (List String)
commonOptionsExtraLibDirs :: Maybe (List String)
commonOptionsJsSources :: [Path]
commonOptionsCxxSources :: [Path]
commonOptionsCxxOptions :: Maybe (List String)
commonOptionsCSources :: [Path]
commonOptionsCcOptions :: Maybe (List String)
commonOptionsCppOptions :: Maybe (List String)
commonOptionsGhcjsOptions :: Maybe (List String)
commonOptionsGhcSharedOptions :: Maybe (List String)
commonOptionsGhcProfOptions :: Maybe (List String)
commonOptionsGhcOptions :: Maybe (List String)
commonOptionsLanguage :: Alias 'True "default-language" (Last (Maybe Language))
commonOptionsOtherExtensions :: Maybe (List String)
commonOptionsDefaultExtensions :: Maybe (List String)
commonOptionsPkgConfigDependencies :: Alias 'False "pkgconfig-depends" (Maybe (List String))
commonOptionsDependencies :: Alias 'True "build-depends" (Maybe Dependencies)
commonOptionsSourceDirs :: Alias 'True "hs-source-dirs" (Maybe (List String))
commonOptionsVerbatim :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List Verbatim)
commonOptionsSystemBuildTools :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe SystemBuildTools
commonOptionsBuildTools :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Alias 'True "build-tool-depends" (Maybe BuildTools)
commonOptionsWhen :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe
     (List (ConditionalSection cSources cxxSources jsSources a))
commonOptionsBuildable :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a -> Last Bool
commonOptionsLdOptions :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsInstallIncludes :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsIncludeDirs :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsFrameworks :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsExtraFrameworksDirs :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsExtraLibraries :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsExtraLibDirs :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsJsSources :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a -> jsSources
commonOptionsCxxSources :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a -> cxxSources
commonOptionsCxxOptions :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsCSources :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a -> cSources
commonOptionsCcOptions :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsCppOptions :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsGhcjsOptions :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsGhcSharedOptions :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsGhcProfOptions :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsGhcOptions :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsLanguage :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Alias 'True "default-language" (Last (Maybe Language))
commonOptionsOtherExtensions :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsDefaultExtensions :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Maybe (List String)
commonOptionsPkgConfigDependencies :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Alias 'False "pkgconfig-depends" (Maybe (List String))
commonOptionsDependencies :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Alias 'True "build-depends" (Maybe Dependencies)
commonOptionsSourceDirs :: forall cSources cxxSources jsSources a.
CommonOptions cSources cxxSources jsSources a
-> Alias 'True "hs-source-dirs" (Maybe (List String))
..} a
a) = do
      (SystemBuildTools
systemBuildTools, Map BuildTool DependencyVersion
buildTools) <- forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Monoid a => a
mempty) forall (m :: * -> *).
Monad m =>
BuildTools
-> Warnings m (SystemBuildTools, Map BuildTool DependencyVersion)
toBuildTools (forall (deprecated :: Bool) (alias :: Symbol) a.
Alias deprecated alias a -> a
unAlias Alias 'True "build-tool-depends" (Maybe BuildTools)
commonOptionsBuildTools)

      [Conditional (Section a)]
conditionals <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall (m :: * -> *) a.
Monad m =>
ConditionalSection [Path] [Path] [Path] a
-> Warnings m (Conditional (Section a))
toConditional (forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List (ConditionalSection [Path] [Path] [Path] a))
commonOptionsWhen)
      forall (m :: * -> *) a. Monad m => a -> m a
return Section {
        sectionData :: a
sectionData = a
a
      , sectionSourceDirs :: [String]
sectionSourceDirs = forall a. Ord a => [a] -> [a]
nub forall a b. (a -> b) -> a -> b
$ forall a. Maybe (List a) -> [a]
fromMaybeList (forall (deprecated :: Bool) (alias :: Symbol) a.
Alias deprecated alias a -> a
unAlias Alias 'True "hs-source-dirs" (Maybe (List String))
commonOptionsSourceDirs)
      , sectionDependencies :: Dependencies
sectionDependencies = forall a. a -> Maybe a -> a
fromMaybe forall a. Monoid a => a
mempty (forall (deprecated :: Bool) (alias :: Symbol) a.
Alias deprecated alias a -> a
unAlias Alias 'True "build-depends" (Maybe Dependencies)
commonOptionsDependencies)
      , sectionPkgConfigDependencies :: [String]
sectionPkgConfigDependencies = forall a. Maybe (List a) -> [a]
fromMaybeList (forall (deprecated :: Bool) (alias :: Symbol) a.
Alias deprecated alias a -> a
unAlias Alias 'False "pkgconfig-depends" (Maybe (List String))
commonOptionsPkgConfigDependencies)
      , sectionDefaultExtensions :: [String]
sectionDefaultExtensions = forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List String)
commonOptionsDefaultExtensions
      , sectionOtherExtensions :: [String]
sectionOtherExtensions = forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List String)
commonOptionsOtherExtensions
      , sectionLanguage :: Maybe Language
sectionLanguage = forall (m :: * -> *) a. Monad m => m (m a) -> m a
join forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Last a -> Maybe a
getLast forall a b. (a -> b) -> a -> b
$ forall (deprecated :: Bool) (alias :: Symbol) a.
Alias deprecated alias a -> a
unAlias Alias 'True "default-language" (Last (Maybe Language))
commonOptionsLanguage
      , sectionGhcOptions :: [String]
sectionGhcOptions = forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List String)
commonOptionsGhcOptions
      , sectionGhcProfOptions :: [String]
sectionGhcProfOptions = forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List String)
commonOptionsGhcProfOptions
      , sectionGhcSharedOptions :: [String]
sectionGhcSharedOptions = forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List String)
commonOptionsGhcSharedOptions
      , sectionGhcjsOptions :: [String]
sectionGhcjsOptions = forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List String)
commonOptionsGhcjsOptions
      , sectionCppOptions :: [String]
sectionCppOptions = forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List String)
commonOptionsCppOptions
      , sectionCcOptions :: [String]
sectionCcOptions = forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List String)
commonOptionsCcOptions
      , sectionCSources :: [Path]
sectionCSources = [Path]
commonOptionsCSources
      , sectionCxxOptions :: [String]
sectionCxxOptions = forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List String)
commonOptionsCxxOptions
      , sectionCxxSources :: [Path]
sectionCxxSources = [Path]
commonOptionsCxxSources
      , sectionJsSources :: [Path]
sectionJsSources = [Path]
commonOptionsJsSources
      , sectionExtraLibDirs :: [String]
sectionExtraLibDirs = forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List String)
commonOptionsExtraLibDirs
      , sectionExtraLibraries :: [String]
sectionExtraLibraries = forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List String)
commonOptionsExtraLibraries
      , sectionExtraFrameworksDirs :: [String]
sectionExtraFrameworksDirs = forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List String)
commonOptionsExtraFrameworksDirs
      , sectionFrameworks :: [String]
sectionFrameworks = forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List String)
commonOptionsFrameworks
      , sectionIncludeDirs :: [String]
sectionIncludeDirs = forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List String)
commonOptionsIncludeDirs
      , sectionInstallIncludes :: [String]
sectionInstallIncludes = forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List String)
commonOptionsInstallIncludes
      , sectionLdOptions :: [String]
sectionLdOptions = forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List String)
commonOptionsLdOptions
      , sectionBuildable :: Maybe Bool
sectionBuildable = forall a. Last a -> Maybe a
getLast Last Bool
commonOptionsBuildable
      , sectionConditionals :: [Conditional (Section a)]
sectionConditionals = [Conditional (Section a)]
conditionals
      , sectionBuildTools :: Map BuildTool DependencyVersion
sectionBuildTools = Map BuildTool DependencyVersion
buildTools
      , sectionSystemBuildTools :: SystemBuildTools
sectionSystemBuildTools = SystemBuildTools
systemBuildTools forall a. Semigroup a => a -> a -> a
<> forall a. a -> Maybe a -> a
fromMaybe forall a. Monoid a => a
mempty Maybe SystemBuildTools
commonOptionsSystemBuildTools
      , sectionVerbatim :: [Verbatim]
sectionVerbatim = forall a. Maybe (List a) -> [a]
fromMaybeList Maybe (List Verbatim)
commonOptionsVerbatim
      }
    toBuildTools :: Monad m => BuildTools -> Warnings m (SystemBuildTools, Map BuildTool DependencyVersion)
    toBuildTools :: forall (m :: * -> *).
Monad m =>
BuildTools
-> Warnings m (SystemBuildTools, Map BuildTool DependencyVersion)
toBuildTools = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall b. [Either SystemBuildTool b] -> SystemBuildTools
mkSystemBuildTools forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& forall {a} {a}. [Either a (BuildTool, a)] -> Map BuildTool a
mkBuildTools) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (forall (m :: * -> *).
Monad m =>
String
-> [String]
-> (ParseBuildTool, DependencyVersion)
-> Warnings
     m (Either SystemBuildTool (BuildTool, DependencyVersion))
toBuildTool String
packageName_ [String]
executableNames)forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuildTools -> [(ParseBuildTool, DependencyVersion)]
unBuildTools
      where
        mkSystemBuildTools :: [Either (String, VersionConstraint) b] -> SystemBuildTools
        mkSystemBuildTools :: forall b. [Either SystemBuildTool b] -> SystemBuildTools
mkSystemBuildTools = Map String VersionConstraint -> SystemBuildTools
SystemBuildTools forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. [Either a b] -> [a]
lefts

        mkBuildTools :: [Either a (BuildTool, a)] -> Map BuildTool a
mkBuildTools = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. [Either a b] -> [b]
rights

    toConditional :: Monad m => ConditionalSection CSources CxxSources JsSources a -> Warnings m (Conditional (Section a))
    toConditional :: forall (m :: * -> *) a.
Monad m =>
ConditionalSection [Path] [Path] [Path] a
-> Warnings m (Conditional (Section a))
toConditional ConditionalSection [Path] [Path] [Path] a
x = case ConditionalSection [Path] [Path] [Path] a
x of
      ThenElseConditional (Product (ThenElse WithCommonOptions [Path] [Path] [Path] a
then_ WithCommonOptions [Path] [Path] [Path] a
else_) Condition
c) -> forall {a}. Condition -> a -> Maybe a -> Conditional a
conditional Condition
c forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall {m :: * -> *} {a}.
Monad m =>
Product (CommonOptions [Path] [Path] [Path] a) a
-> WriterT [String] m (Section a)
go WithCommonOptions [Path] [Path] [Path] a
then_ forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a. a -> Maybe a
Just forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall {m :: * -> *} {a}.
Monad m =>
Product (CommonOptions [Path] [Path] [Path] a) a
-> WriterT [String] m (Section a)
go WithCommonOptions [Path] [Path] [Path] a
else_)
      FlatConditional (Product WithCommonOptions [Path] [Path] [Path] a
sect Condition
c) -> forall {a}. Condition -> a -> Maybe a -> Conditional a
conditional Condition
c forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall {m :: * -> *} {a}.
Monad m =>
Product (CommonOptions [Path] [Path] [Path] a) a
-> WriterT [String] m (Section a)
go WithCommonOptions [Path] [Path] [Path] a
sect) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing
      where
        conditional :: Condition -> a -> Maybe a -> Conditional a
conditional = forall a. Cond -> a -> Maybe a -> Conditional a
Conditional forall b c a. (b -> c) -> (a -> b) -> a -> c
. Condition -> Cond
conditionCondition

type SystemBuildTool = (String, VersionConstraint)

toBuildTool :: Monad m => String -> [String] -> (ParseBuildTool, DependencyVersion)
  -> Warnings m (Either SystemBuildTool (BuildTool, DependencyVersion))
toBuildTool :: forall (m :: * -> *).
Monad m =>
String
-> [String]
-> (ParseBuildTool, DependencyVersion)
-> Warnings
     m (Either SystemBuildTool (BuildTool, DependencyVersion))
toBuildTool String
packageName_ [String]
executableNames = \ case
  (QualifiedBuildTool String
pkg String
executable, DependencyVersion
v)
    | String
pkg forall a. Eq a => a -> a -> Bool
== String
packageName_ Bool -> Bool -> Bool
&& String
executable forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
executableNames -> forall {m :: * -> *} {b} {a}.
Monad m =>
String -> b -> m (Either a (BuildTool, b))
localBuildTool String
executable DependencyVersion
v
    | Bool
otherwise -> forall {m :: * -> *} {b} {a}.
Monad m =>
String -> String -> b -> m (Either a (BuildTool, b))
buildTool String
pkg String
executable DependencyVersion
v
  (UnqualifiedBuildTool String
executable, DependencyVersion
v)
    | String
executable forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
executableNames -> forall {m :: * -> *} {b} {a}.
Monad m =>
String -> b -> m (Either a (BuildTool, b))
localBuildTool String
executable DependencyVersion
v
    | Just String
pkg <- forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup String
executable [(String, String)]
legacyTools -> forall {m :: * -> *} {b} {a}.
Monad m =>
String
-> String -> b -> WriterT [String] m (Either a (BuildTool, b))
legacyBuildTool String
pkg String
executable DependencyVersion
v
    | String
executable forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
legacySystemTools, DependencyVersion Maybe SourceDependency
Nothing VersionConstraint
c <- DependencyVersion
v -> forall {a} {b} {b}.
Show a =>
a -> b -> WriterT [String] m (Either (a, b) b)
legacySystemBuildTool String
executable VersionConstraint
c
    | Bool
otherwise -> forall {m :: * -> *} {b} {a}.
Monad m =>
String -> String -> b -> m (Either a (BuildTool, b))
buildTool String
executable String
executable DependencyVersion
v
  where
    buildTool :: String -> String -> b -> m (Either a (BuildTool, b))
buildTool String
pkg String
executable b
v = forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ (String -> String -> BuildTool
BuildTool String
pkg String
executable, b
v)

    systemBuildTool :: a -> WriterT [String] m (Either a b)
systemBuildTool = forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> Either a b
Left

    localBuildTool :: String -> b -> m (Either a (BuildTool, b))
localBuildTool String
executable b
v = forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ (String -> BuildTool
LocalBuildTool String
executable, b
v)
    legacyBuildTool :: String
-> String -> b -> WriterT [String] m (Either a (BuildTool, b))
legacyBuildTool String
pkg String
executable b
v = forall {m :: * -> *}.
Monad m =>
String -> String -> WriterT [String] m ()
warnLegacyTool String
pkg String
executable forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall {m :: * -> *} {b} {a}.
Monad m =>
String -> String -> b -> m (Either a (BuildTool, b))
buildTool String
pkg String
executable b
v
    legacySystemBuildTool :: a -> b -> WriterT [String] m (Either (a, b) b)
legacySystemBuildTool a
executable b
c = forall {m :: * -> *} {a}.
(Monad m, Show a) =>
a -> WriterT [String] m ()
warnLegacySystemTool a
executable forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall {a} {b}. a -> WriterT [String] m (Either a b)
systemBuildTool (a
executable, b
c)

    legacyTools :: [(String, String)]
legacyTools = [
        (String
"gtk2hsTypeGen", String
"gtk2hs-buildtools")
      , (String
"gtk2hsHookGenerator", String
"gtk2hs-buildtools")
      , (String
"gtk2hsC2hs", String
"gtk2hs-buildtools")
      , (String
"cabal", String
"cabal-install")
      , (String
"grgen", String
"cgen")
      , (String
"cgen-hs", String
"cgen")
      ]
    legacySystemTools :: [String]
legacySystemTools = [
        String
"ghc"
      , String
"git"
      , String
"llvm-config"
      , String
"gfortran"
      , String
"gcc"
      , String
"couchdb"
      , String
"mcc"
      , String
"nix-store"
      , String
"nix-instantiate"
      , String
"nix-hash"
      , String
"nix-env"
      , String
"nix-build"
      ]
    warnLegacyTool :: String -> String -> WriterT [String] m ()
warnLegacyTool String
pkg String
name = forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell [String
"Usage of the unqualified build-tool name " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show String
name forall a. [a] -> [a] -> [a]
++ String
" is deprecated! Please use the qualified name \"" forall a. [a] -> [a] -> [a]
++ String
pkg forall a. [a] -> [a] -> [a]
++ String
":" forall a. [a] -> [a] -> [a]
++ String
name forall a. [a] -> [a] -> [a]
++ String
"\" instead!"]
    warnLegacySystemTool :: a -> WriterT [String] m ()
warnLegacySystemTool a
name = forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell [String
"Listing " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show a
name forall a. [a] -> [a] -> [a]
++ String
" under build-tools is deperecated! Please list system executables under system-build-tools instead!"]

pathsModuleFromPackageName :: String -> Module
pathsModuleFromPackageName :: String -> Module
pathsModuleFromPackageName String
name = String -> Module
Module (String
"Paths_" forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
f String
name)
  where
    f :: Char -> Char
f Char
'-' = Char
'_'
    f Char
x = Char
x