{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}

module Distribution.Types.BuildInfo (
    BuildInfo(..),

    emptyBuildInfo,
    allLanguages,
    allExtensions,
    usedExtensions,
    usesTemplateHaskellOrQQ,

    hcOptions,
    hcProfOptions,
    hcSharedOptions,
    hcStaticOptions,
) where

import Prelude ()
import Distribution.Compat.Prelude

import Distribution.Types.Mixin
import Distribution.Types.Dependency
import Distribution.Types.ExeDependency
import Distribution.Types.LegacyExeDependency
import Distribution.Types.PkgconfigDependency

import Distribution.ModuleName
import Distribution.Compiler
import Language.Haskell.Extension

-- Consider refactoring into executable and library versions.
data BuildInfo = BuildInfo {
        -- | component is buildable here
        BuildInfo -> Bool
buildable         :: Bool,
        -- | Tools needed to build this bit.
        --
        -- This is a legacy field that 'buildToolDepends' largely supersedes.
        --
        -- Unless use are very sure what you are doing, use the functions in
        -- "Distribution.Simple.BuildToolDepends" rather than accessing this
        -- field directly.
        BuildInfo -> [LegacyExeDependency]
buildTools        :: [LegacyExeDependency],
        -- | Haskell tools needed to build this bit
        --
        -- This field is better than 'buildTools' because it allows one to
        -- precisely specify an executable in a package.
        --
        -- Unless use are very sure what you are doing, use the functions in
        -- "Distribution.Simple.BuildToolDepends" rather than accessing this
        -- field directly.
        BuildInfo -> [ExeDependency]
buildToolDepends  :: [ExeDependency],
        BuildInfo -> [String]
cppOptions        :: [String],  -- ^ options for pre-processing Haskell code
        BuildInfo -> [String]
asmOptions        :: [String],  -- ^ options for assmebler
        BuildInfo -> [String]
cmmOptions        :: [String],  -- ^ options for C-- compiler
        BuildInfo -> [String]
ccOptions         :: [String],  -- ^ options for C compiler
        BuildInfo -> [String]
cxxOptions        :: [String],  -- ^ options for C++ compiler
        BuildInfo -> [String]
ldOptions         :: [String],  -- ^ options for linker
        BuildInfo -> [PkgconfigDependency]
pkgconfigDepends  :: [PkgconfigDependency], -- ^ pkg-config packages that are used
        BuildInfo -> [String]
frameworks        :: [String], -- ^support frameworks for Mac OS X
        BuildInfo -> [String]
extraFrameworkDirs:: [String], -- ^ extra locations to find frameworks.
        BuildInfo -> [String]
asmSources        :: [FilePath], -- ^ Assembly files.
        BuildInfo -> [String]
cmmSources        :: [FilePath], -- ^ C-- files.
        BuildInfo -> [String]
cSources          :: [FilePath],
        BuildInfo -> [String]
cxxSources        :: [FilePath],
        BuildInfo -> [String]
jsSources         :: [FilePath],
        BuildInfo -> [String]
hsSourceDirs      :: [FilePath], -- ^ where to look for the Haskell module hierarchy
        BuildInfo -> [ModuleName]
otherModules      :: [ModuleName], -- ^ non-exposed or non-main modules
        BuildInfo -> [ModuleName]
virtualModules    :: [ModuleName], -- ^ exposed modules that do not have a source file (e.g. @GHC.Prim@ from @ghc-prim@ package)
        BuildInfo -> [ModuleName]
autogenModules    :: [ModuleName], -- ^ not present on sdist, Paths_* or user-generated with a custom Setup.hs

        BuildInfo -> Maybe Language
defaultLanguage   :: Maybe Language,-- ^ language used when not explicitly specified
        BuildInfo -> [Language]
otherLanguages    :: [Language],    -- ^ other languages used within the package
        BuildInfo -> [Extension]
defaultExtensions :: [Extension],   -- ^ language extensions used by all modules
        BuildInfo -> [Extension]
otherExtensions   :: [Extension],   -- ^ other language extensions used within the package
        BuildInfo -> [Extension]
oldExtensions     :: [Extension],   -- ^ the old extensions field, treated same as 'defaultExtensions'

        BuildInfo -> [String]
extraLibs         :: [String], -- ^ what libraries to link with when compiling a program that uses your package
        BuildInfo -> [String]
extraGHCiLibs     :: [String], -- ^ if present, overrides extraLibs when package is loaded with GHCi.
        BuildInfo -> [String]
extraBundledLibs  :: [String], -- ^ if present, adds libs to hs-libraries, which become part of the package.
                                       --   Example: the Cffi library shipping with the rts, alognside the HSrts-1.0.a,.o,...
                                       --   Example 2: a library that is being built by a foreing tool (e.g. rust)
                                       --              and copied and registered together with this library.  The
                                       --              logic on how this library is built will have to be encoded in a
                                       --              custom Setup for now.  Otherwise cabal would need to lear how to
                                       --              call arbitrary library builders.
        BuildInfo -> [String]
extraLibFlavours  :: [String], -- ^ Hidden Flag.  This set of strings, will be appended to all libraries when
                                       --   copying. E.g. [libHS<name>_<flavour> | flavour <- extraLibFlavours]. This
                                       --   should only be needed in very specific cases, e.g. the `rts` package, where
                                       --   there are multiple copies of slightly differently built libs.
        BuildInfo -> [String]
extraDynLibFlavours :: [String], -- ^ Hidden Flag. This set of strings will be be appended to all /dynamic/
                                         --   libraries when copying. This is particularly useful with the `rts` package,
                                         --   where we want different dynamic flavours of the RTS library to be installed.
        BuildInfo -> [String]
extraLibDirs      :: [String],
        BuildInfo -> [String]
includeDirs       :: [FilePath], -- ^directories to find .h files
        BuildInfo -> [String]
includes          :: [FilePath], -- ^ The .h files to be found in includeDirs
        BuildInfo -> [String]
autogenIncludes   :: [FilePath], -- ^ The .h files to be generated (e.g. by @autoconf@)
        BuildInfo -> [String]
installIncludes   :: [FilePath], -- ^ .h files to install with the package
        BuildInfo -> PerCompilerFlavor [String]
options           :: PerCompilerFlavor [String],
        BuildInfo -> PerCompilerFlavor [String]
profOptions       :: PerCompilerFlavor [String],
        BuildInfo -> PerCompilerFlavor [String]
sharedOptions     :: PerCompilerFlavor [String],
        BuildInfo -> PerCompilerFlavor [String]
staticOptions     :: PerCompilerFlavor [String],
        BuildInfo -> [(String, String)]
customFieldsBI    :: [(String,String)], -- ^Custom fields starting
                                                -- with x-, stored in a
                                                -- simple assoc-list.
        BuildInfo -> [Dependency]
targetBuildDepends :: [Dependency], -- ^ Dependencies specific to a library or executable target
        BuildInfo -> [Mixin]
mixins :: [Mixin]
    }
    deriving ((forall x. BuildInfo -> Rep BuildInfo x)
-> (forall x. Rep BuildInfo x -> BuildInfo) -> Generic BuildInfo
forall x. Rep BuildInfo x -> BuildInfo
forall x. BuildInfo -> Rep BuildInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BuildInfo x -> BuildInfo
$cfrom :: forall x. BuildInfo -> Rep BuildInfo x
Generic, Int -> BuildInfo -> ShowS
[BuildInfo] -> ShowS
BuildInfo -> String
(Int -> BuildInfo -> ShowS)
-> (BuildInfo -> String)
-> ([BuildInfo] -> ShowS)
-> Show BuildInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BuildInfo] -> ShowS
$cshowList :: [BuildInfo] -> ShowS
show :: BuildInfo -> String
$cshow :: BuildInfo -> String
showsPrec :: Int -> BuildInfo -> ShowS
$cshowsPrec :: Int -> BuildInfo -> ShowS
External instance of the constraint type Show Mixin
External instance of the constraint type Show Dependency
External instance of the constraint type forall a b. (Show a, Show b) => Show (a, b)
External instance of the constraint type Show Extension
External instance of the constraint type Show Language
External instance of the constraint type Show ModuleName
External instance of the constraint type Show PkgconfigDependency
External instance of the constraint type Show Char
External instance of the constraint type Show Char
External instance of the constraint type Show ExeDependency
External instance of the constraint type Show LegacyExeDependency
External instance of the constraint type Show Mixin
External instance of the constraint type Show Dependency
External instance of the constraint type forall a b. (Show a, Show b) => Show (a, b)
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
External instance of the constraint type forall v. Show v => Show (PerCompilerFlavor v)
External instance of the constraint type forall v. Show v => Show (PerCompilerFlavor v)
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
External instance of the constraint type Show Extension
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Extension
External instance of the constraint type Show Language
External instance of the constraint type forall a. Show a => Show (Maybe a)
External instance of the constraint type Show ModuleName
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show ModuleName
External instance of the constraint type Show PkgconfigDependency
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
External instance of the constraint type Show ExeDependency
External instance of the constraint type Show LegacyExeDependency
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Bool
External instance of the constraint type Ord Int
Show, ReadPrec [BuildInfo]
ReadPrec BuildInfo
Int -> ReadS BuildInfo
ReadS [BuildInfo]
(Int -> ReadS BuildInfo)
-> ReadS [BuildInfo]
-> ReadPrec BuildInfo
-> ReadPrec [BuildInfo]
-> Read BuildInfo
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BuildInfo]
$creadListPrec :: ReadPrec [BuildInfo]
readPrec :: ReadPrec BuildInfo
$creadPrec :: ReadPrec BuildInfo
readList :: ReadS [BuildInfo]
$creadList :: ReadS [BuildInfo]
readsPrec :: Int -> ReadS BuildInfo
$creadsPrec :: Int -> ReadS BuildInfo
External instance of the constraint type Read Mixin
External instance of the constraint type Read Dependency
External instance of the constraint type forall a b. (Read a, Read b) => Read (a, b)
External instance of the constraint type Read Extension
External instance of the constraint type Read Language
External instance of the constraint type Read ModuleName
External instance of the constraint type Read PkgconfigDependency
External instance of the constraint type Read Char
External instance of the constraint type Read Char
External instance of the constraint type Read ExeDependency
External instance of the constraint type Read LegacyExeDependency
External instance of the constraint type Read Mixin
External instance of the constraint type Read Dependency
External instance of the constraint type forall a b. (Read a, Read b) => Read (a, b)
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Read Char
External instance of the constraint type forall v. Read v => Read (PerCompilerFlavor v)
External instance of the constraint type forall v. Read v => Read (PerCompilerFlavor v)
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Read Char
External instance of the constraint type Read Extension
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Read Extension
External instance of the constraint type Read Language
External instance of the constraint type forall a. Read a => Read (Maybe a)
External instance of the constraint type Read ModuleName
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Read ModuleName
External instance of the constraint type Read PkgconfigDependency
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Read Char
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Read Char
External instance of the constraint type Read ExeDependency
External instance of the constraint type Read LegacyExeDependency
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Read Bool
External instance of the constraint type Monad ReadPrec
External instance of the constraint type Monad ReadPrec
Instance of class: Read of the constraint type Read BuildInfo
Read, BuildInfo -> BuildInfo -> Bool
(BuildInfo -> BuildInfo -> Bool)
-> (BuildInfo -> BuildInfo -> Bool) -> Eq BuildInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BuildInfo -> BuildInfo -> Bool
$c/= :: BuildInfo -> BuildInfo -> Bool
== :: BuildInfo -> BuildInfo -> Bool
$c== :: BuildInfo -> BuildInfo -> Bool
External instance of the constraint type Eq Mixin
External instance of the constraint type Eq Dependency
External instance of the constraint type forall a b. (Eq a, Eq b) => Eq (a, b)
External instance of the constraint type Eq Extension
External instance of the constraint type Eq Language
External instance of the constraint type Eq ModuleName
External instance of the constraint type Eq PkgconfigDependency
External instance of the constraint type Eq Char
External instance of the constraint type Eq Char
External instance of the constraint type Eq ExeDependency
External instance of the constraint type Eq LegacyExeDependency
External instance of the constraint type Eq Mixin
External instance of the constraint type Eq Dependency
External instance of the constraint type forall a b. (Eq a, Eq b) => Eq (a, b)
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
External instance of the constraint type forall v. Eq v => Eq (PerCompilerFlavor v)
External instance of the constraint type forall v. Eq v => Eq (PerCompilerFlavor v)
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
External instance of the constraint type Eq Extension
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Extension
External instance of the constraint type Eq Language
External instance of the constraint type forall a. Eq a => Eq (Maybe a)
External instance of the constraint type Eq ModuleName
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq ModuleName
External instance of the constraint type Eq PkgconfigDependency
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
External instance of the constraint type Eq ExeDependency
External instance of the constraint type Eq LegacyExeDependency
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Bool
Eq, Typeable, Typeable BuildInfo
DataType
Constr
Typeable BuildInfo
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> BuildInfo -> c BuildInfo)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c BuildInfo)
-> (BuildInfo -> Constr)
-> (BuildInfo -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c BuildInfo))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BuildInfo))
-> ((forall b. Data b => b -> b) -> BuildInfo -> BuildInfo)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> BuildInfo -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> BuildInfo -> r)
-> (forall u. (forall d. Data d => d -> u) -> BuildInfo -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> BuildInfo -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> BuildInfo -> m BuildInfo)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> BuildInfo -> m BuildInfo)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> BuildInfo -> m BuildInfo)
-> Data BuildInfo
BuildInfo -> DataType
BuildInfo -> Constr
(forall b. Data b => b -> b) -> BuildInfo -> BuildInfo
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BuildInfo -> c BuildInfo
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BuildInfo
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> BuildInfo -> u
forall u. (forall d. Data d => d -> u) -> BuildInfo -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BuildInfo -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BuildInfo -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> BuildInfo -> m BuildInfo
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BuildInfo -> m BuildInfo
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BuildInfo
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BuildInfo -> c BuildInfo
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c BuildInfo)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BuildInfo)
$cBuildInfo :: Constr
$tBuildInfo :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> BuildInfo -> m BuildInfo
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BuildInfo -> m BuildInfo
gmapMp :: (forall d. Data d => d -> m d) -> BuildInfo -> m BuildInfo
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BuildInfo -> m BuildInfo
gmapM :: (forall d. Data d => d -> m d) -> BuildInfo -> m BuildInfo
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> BuildInfo -> m BuildInfo
gmapQi :: Int -> (forall d. Data d => d -> u) -> BuildInfo -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> BuildInfo -> u
gmapQ :: (forall d. Data d => d -> u) -> BuildInfo -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> BuildInfo -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BuildInfo -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BuildInfo -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BuildInfo -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BuildInfo -> r
gmapT :: (forall b. Data b => b -> b) -> BuildInfo -> BuildInfo
$cgmapT :: (forall b. Data b => b -> b) -> BuildInfo -> BuildInfo
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BuildInfo)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BuildInfo)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c BuildInfo)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c BuildInfo)
dataTypeOf :: BuildInfo -> DataType
$cdataTypeOf :: BuildInfo -> DataType
toConstr :: BuildInfo -> Constr
$ctoConstr :: BuildInfo -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BuildInfo
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BuildInfo
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BuildInfo -> c BuildInfo
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BuildInfo -> c BuildInfo
External instance of the constraint type Data Char
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type Data Char
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type Data Char
External instance of the constraint type Data LegacyExeDependency
External instance of the constraint type Data ExeDependency
External instance of the constraint type Data PkgconfigDependency
External instance of the constraint type Data ModuleName
External instance of the constraint type Data Language
External instance of the constraint type Data Extension
External instance of the constraint type Data Char
External instance of the constraint type Data Char
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type Data Char
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type Data Char
External instance of the constraint type forall a b. (Data a, Data b) => Data (a, b)
External instance of the constraint type Data Dependency
External instance of the constraint type Data Mixin
External instance of the constraint type Data LegacyExeDependency
External instance of the constraint type Data ExeDependency
External instance of the constraint type Data PkgconfigDependency
External instance of the constraint type Data ModuleName
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type Data ModuleName
External instance of the constraint type Data Language
External instance of the constraint type Data Extension
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type Data Extension
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type Data Char
External instance of the constraint type forall v. Data v => Data (PerCompilerFlavor v)
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type Data Char
External instance of the constraint type forall a b. (Data a, Data b) => Data (a, b)
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type Data Char
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type Data Char
External instance of the constraint type Data Dependency
External instance of the constraint type Data Mixin
External instance of the constraint type Data Bool
External instance of the constraint type Data LegacyExeDependency
External instance of the constraint type Data ExeDependency
External instance of the constraint type Data PkgconfigDependency
External instance of the constraint type Data ModuleName
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type Data ModuleName
External instance of the constraint type forall a. Data a => Data (Maybe a)
External instance of the constraint type Data Language
External instance of the constraint type Data Extension
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type Data Extension
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type Data Char
External instance of the constraint type forall v. Data v => Data (PerCompilerFlavor v)
External instance of the constraint type forall v. Data v => Data (PerCompilerFlavor v)
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type Data Char
External instance of the constraint type forall a b. (Data a, Data b) => Data (a, b)
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type Data Char
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type Data Char
External instance of the constraint type Data Dependency
External instance of the constraint type Data Mixin
External instance of the constraint type forall a. Data a => Data [a]
Data)

instance Binary BuildInfo
instance Structured BuildInfo
instance NFData BuildInfo where rnf :: BuildInfo -> ()
rnf = BuildInfo -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type NFData Bool
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData LegacyExeDependency
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData ExeDependency
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData PkgconfigDependency
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData ModuleName
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData ModuleName
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData ModuleName
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData (Maybe a)
External instance of the constraint type NFData Language
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Language
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Extension
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Extension
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Extension
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData (PerCompilerFlavor a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData (PerCompilerFlavor a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData (PerCompilerFlavor a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData (PerCompilerFlavor a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a b. (NFData a, NFData b) => NFData (a, b)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Dependency
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Mixin
Instance of class: Generic of the constraint type Generic BuildInfo
genericRnf

instance Monoid BuildInfo where
  mempty :: BuildInfo
mempty = BuildInfo :: Bool
-> [LegacyExeDependency]
-> [ExeDependency]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [PkgconfigDependency]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo
BuildInfo {
    buildable :: Bool
buildable           = Bool
True,
    buildTools :: [LegacyExeDependency]
buildTools          = [],
    buildToolDepends :: [ExeDependency]
buildToolDepends    = [],
    cppOptions :: [String]
cppOptions          = [],
    asmOptions :: [String]
asmOptions          = [],
    cmmOptions :: [String]
cmmOptions          = [],
    ccOptions :: [String]
ccOptions           = [],
    cxxOptions :: [String]
cxxOptions          = [],
    ldOptions :: [String]
ldOptions           = [],
    pkgconfigDepends :: [PkgconfigDependency]
pkgconfigDepends    = [],
    frameworks :: [String]
frameworks          = [],
    extraFrameworkDirs :: [String]
extraFrameworkDirs  = [],
    asmSources :: [String]
asmSources          = [],
    cmmSources :: [String]
cmmSources          = [],
    cSources :: [String]
cSources            = [],
    cxxSources :: [String]
cxxSources          = [],
    jsSources :: [String]
jsSources           = [],
    hsSourceDirs :: [String]
hsSourceDirs        = [],
    otherModules :: [ModuleName]
otherModules        = [],
    virtualModules :: [ModuleName]
virtualModules      = [],
    autogenModules :: [ModuleName]
autogenModules      = [],
    defaultLanguage :: Maybe Language
defaultLanguage     = Maybe Language
forall a. Maybe a
Nothing,
    otherLanguages :: [Language]
otherLanguages      = [],
    defaultExtensions :: [Extension]
defaultExtensions   = [],
    otherExtensions :: [Extension]
otherExtensions     = [],
    oldExtensions :: [Extension]
oldExtensions       = [],
    extraLibs :: [String]
extraLibs           = [],
    extraGHCiLibs :: [String]
extraGHCiLibs       = [],
    extraBundledLibs :: [String]
extraBundledLibs    = [],
    extraLibFlavours :: [String]
extraLibFlavours    = [],
    extraDynLibFlavours :: [String]
extraDynLibFlavours = [],
    extraLibDirs :: [String]
extraLibDirs        = [],
    includeDirs :: [String]
includeDirs         = [],
    includes :: [String]
includes            = [],
    autogenIncludes :: [String]
autogenIncludes     = [],
    installIncludes :: [String]
installIncludes     = [],
    options :: PerCompilerFlavor [String]
options             = PerCompilerFlavor [String]
forall a. Monoid a => a
External instance of the constraint type forall a. (Semigroup a, Monoid a) => Monoid (PerCompilerFlavor a)
External instance of the constraint type forall a. Semigroup [a]
External instance of the constraint type forall a. Monoid [a]
mempty,
    profOptions :: PerCompilerFlavor [String]
profOptions         = PerCompilerFlavor [String]
forall a. Monoid a => a
External instance of the constraint type forall a. (Semigroup a, Monoid a) => Monoid (PerCompilerFlavor a)
External instance of the constraint type forall a. Semigroup [a]
External instance of the constraint type forall a. Monoid [a]
mempty,
    sharedOptions :: PerCompilerFlavor [String]
sharedOptions       = PerCompilerFlavor [String]
forall a. Monoid a => a
External instance of the constraint type forall a. (Semigroup a, Monoid a) => Monoid (PerCompilerFlavor a)
External instance of the constraint type forall a. Semigroup [a]
External instance of the constraint type forall a. Monoid [a]
mempty,
    staticOptions :: PerCompilerFlavor [String]
staticOptions       = PerCompilerFlavor [String]
forall a. Monoid a => a
External instance of the constraint type forall a. (Semigroup a, Monoid a) => Monoid (PerCompilerFlavor a)
External instance of the constraint type forall a. Semigroup [a]
External instance of the constraint type forall a. Monoid [a]
mempty,
    customFieldsBI :: [(String, String)]
customFieldsBI      = [],
    targetBuildDepends :: [Dependency]
targetBuildDepends  = [],
    mixins :: [Mixin]
mixins              = []
  }
  mappend :: BuildInfo -> BuildInfo -> BuildInfo
mappend = BuildInfo -> BuildInfo -> BuildInfo
forall a. Semigroup a => a -> a -> a
Instance of class: Semigroup of the constraint type Semigroup BuildInfo
(<>)

instance Semigroup BuildInfo where
  BuildInfo
a <> :: BuildInfo -> BuildInfo -> BuildInfo
<> BuildInfo
b = BuildInfo :: Bool
-> [LegacyExeDependency]
-> [ExeDependency]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [PkgconfigDependency]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo
BuildInfo {
    buildable :: Bool
buildable           = BuildInfo -> Bool
buildable BuildInfo
a Bool -> Bool -> Bool
&& BuildInfo -> Bool
buildable BuildInfo
b,
    buildTools :: [LegacyExeDependency]
buildTools          = (BuildInfo -> [LegacyExeDependency]) -> [LegacyExeDependency]
forall {a}. Monoid a => (BuildInfo -> a) -> a
External instance of the constraint type forall a. Monoid [a]
combine    BuildInfo -> [LegacyExeDependency]
buildTools,
    buildToolDepends :: [ExeDependency]
buildToolDepends    = (BuildInfo -> [ExeDependency]) -> [ExeDependency]
forall {a}. Monoid a => (BuildInfo -> a) -> a
External instance of the constraint type forall a. Monoid [a]
combine    BuildInfo -> [ExeDependency]
buildToolDepends,
    cppOptions :: [String]
cppOptions          = (BuildInfo -> [String]) -> [String]
forall {a}. Monoid a => (BuildInfo -> a) -> a
External instance of the constraint type forall a. Monoid [a]
combine    BuildInfo -> [String]
cppOptions,
    asmOptions :: [String]
asmOptions          = (BuildInfo -> [String]) -> [String]
forall {a}. Monoid a => (BuildInfo -> a) -> a
External instance of the constraint type forall a. Monoid [a]
combine    BuildInfo -> [String]
asmOptions,
    cmmOptions :: [String]
cmmOptions          = (BuildInfo -> [String]) -> [String]
forall {a}. Monoid a => (BuildInfo -> a) -> a
External instance of the constraint type forall a. Monoid [a]
combine    BuildInfo -> [String]
cmmOptions,
    ccOptions :: [String]
ccOptions           = (BuildInfo -> [String]) -> [String]
forall {a}. Monoid a => (BuildInfo -> a) -> a
External instance of the constraint type forall a. Monoid [a]
combine    BuildInfo -> [String]
ccOptions,
    cxxOptions :: [String]
cxxOptions          = (BuildInfo -> [String]) -> [String]
forall {a}. Monoid a => (BuildInfo -> a) -> a
External instance of the constraint type forall a. Monoid [a]
combine    BuildInfo -> [String]
cxxOptions,
    ldOptions :: [String]
ldOptions           = (BuildInfo -> [String]) -> [String]
forall {a}. Monoid a => (BuildInfo -> a) -> a
External instance of the constraint type forall a. Monoid [a]
combine    BuildInfo -> [String]
ldOptions,
    pkgconfigDepends :: [PkgconfigDependency]
pkgconfigDepends    = (BuildInfo -> [PkgconfigDependency]) -> [PkgconfigDependency]
forall {a}. Monoid a => (BuildInfo -> a) -> a
External instance of the constraint type forall a. Monoid [a]
combine    BuildInfo -> [PkgconfigDependency]
pkgconfigDepends,
    frameworks :: [String]
frameworks          = (BuildInfo -> [String]) -> [String]
forall {a}. Eq a => (BuildInfo -> [a]) -> [a]
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
combineNub BuildInfo -> [String]
frameworks,
    extraFrameworkDirs :: [String]
extraFrameworkDirs  = (BuildInfo -> [String]) -> [String]
forall {a}. Eq a => (BuildInfo -> [a]) -> [a]
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
combineNub BuildInfo -> [String]
extraFrameworkDirs,
    asmSources :: [String]
asmSources          = (BuildInfo -> [String]) -> [String]
forall {a}. Eq a => (BuildInfo -> [a]) -> [a]
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
combineNub BuildInfo -> [String]
asmSources,
    cmmSources :: [String]
cmmSources          = (BuildInfo -> [String]) -> [String]
forall {a}. Eq a => (BuildInfo -> [a]) -> [a]
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
combineNub BuildInfo -> [String]
cmmSources,
    cSources :: [String]
cSources            = (BuildInfo -> [String]) -> [String]
forall {a}. Eq a => (BuildInfo -> [a]) -> [a]
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
combineNub BuildInfo -> [String]
cSources,
    cxxSources :: [String]
cxxSources          = (BuildInfo -> [String]) -> [String]
forall {a}. Eq a => (BuildInfo -> [a]) -> [a]
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
combineNub BuildInfo -> [String]
cxxSources,
    jsSources :: [String]
jsSources           = (BuildInfo -> [String]) -> [String]
forall {a}. Eq a => (BuildInfo -> [a]) -> [a]
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
combineNub BuildInfo -> [String]
jsSources,
    hsSourceDirs :: [String]
hsSourceDirs        = (BuildInfo -> [String]) -> [String]
forall {a}. Eq a => (BuildInfo -> [a]) -> [a]
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
combineNub BuildInfo -> [String]
hsSourceDirs,
    otherModules :: [ModuleName]
otherModules        = (BuildInfo -> [ModuleName]) -> [ModuleName]
forall {a}. Eq a => (BuildInfo -> [a]) -> [a]
External instance of the constraint type Eq ModuleName
combineNub BuildInfo -> [ModuleName]
otherModules,
    virtualModules :: [ModuleName]
virtualModules      = (BuildInfo -> [ModuleName]) -> [ModuleName]
forall {a}. Eq a => (BuildInfo -> [a]) -> [a]
External instance of the constraint type Eq ModuleName
combineNub BuildInfo -> [ModuleName]
virtualModules,
    autogenModules :: [ModuleName]
autogenModules      = (BuildInfo -> [ModuleName]) -> [ModuleName]
forall {a}. Eq a => (BuildInfo -> [a]) -> [a]
External instance of the constraint type Eq ModuleName
combineNub BuildInfo -> [ModuleName]
autogenModules,
    defaultLanguage :: Maybe Language
defaultLanguage     = (BuildInfo -> Maybe Language) -> Maybe Language
forall {m :: * -> *} {a}. MonadPlus m => (BuildInfo -> m a) -> m a
External instance of the constraint type MonadPlus Maybe
combineMby BuildInfo -> Maybe Language
defaultLanguage,
    otherLanguages :: [Language]
otherLanguages      = (BuildInfo -> [Language]) -> [Language]
forall {a}. Eq a => (BuildInfo -> [a]) -> [a]
External instance of the constraint type Eq Language
combineNub BuildInfo -> [Language]
otherLanguages,
    defaultExtensions :: [Extension]
defaultExtensions   = (BuildInfo -> [Extension]) -> [Extension]
forall {a}. Eq a => (BuildInfo -> [a]) -> [a]
External instance of the constraint type Eq Extension
combineNub BuildInfo -> [Extension]
defaultExtensions,
    otherExtensions :: [Extension]
otherExtensions     = (BuildInfo -> [Extension]) -> [Extension]
forall {a}. Eq a => (BuildInfo -> [a]) -> [a]
External instance of the constraint type Eq Extension
combineNub BuildInfo -> [Extension]
otherExtensions,
    oldExtensions :: [Extension]
oldExtensions       = (BuildInfo -> [Extension]) -> [Extension]
forall {a}. Eq a => (BuildInfo -> [a]) -> [a]
External instance of the constraint type Eq Extension
combineNub BuildInfo -> [Extension]
oldExtensions,
    extraLibs :: [String]
extraLibs           = (BuildInfo -> [String]) -> [String]
forall {a}. Monoid a => (BuildInfo -> a) -> a
External instance of the constraint type forall a. Monoid [a]
combine    BuildInfo -> [String]
extraLibs,
    extraGHCiLibs :: [String]
extraGHCiLibs       = (BuildInfo -> [String]) -> [String]
forall {a}. Monoid a => (BuildInfo -> a) -> a
External instance of the constraint type forall a. Monoid [a]
combine    BuildInfo -> [String]
extraGHCiLibs,
    extraBundledLibs :: [String]
extraBundledLibs    = (BuildInfo -> [String]) -> [String]
forall {a}. Monoid a => (BuildInfo -> a) -> a
External instance of the constraint type forall a. Monoid [a]
combine    BuildInfo -> [String]
extraBundledLibs,
    extraLibFlavours :: [String]
extraLibFlavours    = (BuildInfo -> [String]) -> [String]
forall {a}. Monoid a => (BuildInfo -> a) -> a
External instance of the constraint type forall a. Monoid [a]
combine    BuildInfo -> [String]
extraLibFlavours,
    extraDynLibFlavours :: [String]
extraDynLibFlavours = (BuildInfo -> [String]) -> [String]
forall {a}. Monoid a => (BuildInfo -> a) -> a
External instance of the constraint type forall a. Monoid [a]
combine    BuildInfo -> [String]
extraDynLibFlavours,
    extraLibDirs :: [String]
extraLibDirs        = (BuildInfo -> [String]) -> [String]
forall {a}. Eq a => (BuildInfo -> [a]) -> [a]
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
combineNub BuildInfo -> [String]
extraLibDirs,
    includeDirs :: [String]
includeDirs         = (BuildInfo -> [String]) -> [String]
forall {a}. Eq a => (BuildInfo -> [a]) -> [a]
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
combineNub BuildInfo -> [String]
includeDirs,
    includes :: [String]
includes            = (BuildInfo -> [String]) -> [String]
forall {a}. Eq a => (BuildInfo -> [a]) -> [a]
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
combineNub BuildInfo -> [String]
includes,
    autogenIncludes :: [String]
autogenIncludes     = (BuildInfo -> [String]) -> [String]
forall {a}. Eq a => (BuildInfo -> [a]) -> [a]
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
combineNub BuildInfo -> [String]
autogenIncludes,
    installIncludes :: [String]
installIncludes     = (BuildInfo -> [String]) -> [String]
forall {a}. Eq a => (BuildInfo -> [a]) -> [a]
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
combineNub BuildInfo -> [String]
installIncludes,
    options :: PerCompilerFlavor [String]
options             = (BuildInfo -> PerCompilerFlavor [String])
-> PerCompilerFlavor [String]
forall {a}. Monoid a => (BuildInfo -> a) -> a
External instance of the constraint type forall a. (Semigroup a, Monoid a) => Monoid (PerCompilerFlavor a)
External instance of the constraint type forall a. Semigroup [a]
External instance of the constraint type forall a. Monoid [a]
combine    BuildInfo -> PerCompilerFlavor [String]
options,
    profOptions :: PerCompilerFlavor [String]
profOptions         = (BuildInfo -> PerCompilerFlavor [String])
-> PerCompilerFlavor [String]
forall {a}. Monoid a => (BuildInfo -> a) -> a
External instance of the constraint type forall a. (Semigroup a, Monoid a) => Monoid (PerCompilerFlavor a)
External instance of the constraint type forall a. Semigroup [a]
External instance of the constraint type forall a. Monoid [a]
combine    BuildInfo -> PerCompilerFlavor [String]
profOptions,
    sharedOptions :: PerCompilerFlavor [String]
sharedOptions       = (BuildInfo -> PerCompilerFlavor [String])
-> PerCompilerFlavor [String]
forall {a}. Monoid a => (BuildInfo -> a) -> a
External instance of the constraint type forall a. (Semigroup a, Monoid a) => Monoid (PerCompilerFlavor a)
External instance of the constraint type forall a. Semigroup [a]
External instance of the constraint type forall a. Monoid [a]
combine    BuildInfo -> PerCompilerFlavor [String]
sharedOptions,
    staticOptions :: PerCompilerFlavor [String]
staticOptions       = (BuildInfo -> PerCompilerFlavor [String])
-> PerCompilerFlavor [String]
forall {a}. Monoid a => (BuildInfo -> a) -> a
External instance of the constraint type forall a. (Semigroup a, Monoid a) => Monoid (PerCompilerFlavor a)
External instance of the constraint type forall a. Semigroup [a]
External instance of the constraint type forall a. Monoid [a]
combine    BuildInfo -> PerCompilerFlavor [String]
staticOptions,
    customFieldsBI :: [(String, String)]
customFieldsBI      = (BuildInfo -> [(String, String)]) -> [(String, String)]
forall {a}. Monoid a => (BuildInfo -> a) -> a
External instance of the constraint type forall a. Monoid [a]
combine    BuildInfo -> [(String, String)]
customFieldsBI,
    targetBuildDepends :: [Dependency]
targetBuildDepends  = (BuildInfo -> [Dependency]) -> [Dependency]
forall {a}. Eq a => (BuildInfo -> [a]) -> [a]
External instance of the constraint type Eq Dependency
combineNub BuildInfo -> [Dependency]
targetBuildDepends,
    mixins :: [Mixin]
mixins              = (BuildInfo -> [Mixin]) -> [Mixin]
forall {a}. Monoid a => (BuildInfo -> a) -> a
External instance of the constraint type forall a. Monoid [a]
combine    BuildInfo -> [Mixin]
mixins
  }
    where
      combine :: (BuildInfo -> a) -> a
combine    BuildInfo -> a
field = BuildInfo -> a
field BuildInfo
a a -> a -> a
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid a
`mappend` BuildInfo -> a
field BuildInfo
b
      combineNub :: (BuildInfo -> [a]) -> [a]
combineNub BuildInfo -> [a]
field = [a] -> [a]
forall a. Eq a => [a] -> [a]
Evidence bound by a type signature of the constraint type Eq a
nub ((BuildInfo -> [a]) -> [a]
forall {a}. Monoid a => (BuildInfo -> a) -> a
External instance of the constraint type forall a. Monoid [a]
combine BuildInfo -> [a]
field)
      combineMby :: (BuildInfo -> m a) -> m a
combineMby BuildInfo -> m a
field = BuildInfo -> m a
field BuildInfo
b m a -> m a -> m a
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
Evidence bound by a type signature of the constraint type MonadPlus m
`mplus` BuildInfo -> m a
field BuildInfo
a

emptyBuildInfo :: BuildInfo
emptyBuildInfo :: BuildInfo
emptyBuildInfo = BuildInfo
forall a. Monoid a => a
Instance of class: Monoid of the constraint type Monoid BuildInfo
mempty

-- | The 'Language's used by this component
--
allLanguages :: BuildInfo -> [Language]
allLanguages :: BuildInfo -> [Language]
allLanguages BuildInfo
bi = Maybe Language -> [Language]
forall a. Maybe a -> [a]
maybeToList (BuildInfo -> Maybe Language
defaultLanguage BuildInfo
bi)
               [Language] -> [Language] -> [Language]
forall a. [a] -> [a] -> [a]
++ BuildInfo -> [Language]
otherLanguages BuildInfo
bi

-- | The 'Extension's that are used somewhere by this component
--
allExtensions :: BuildInfo -> [Extension]
allExtensions :: BuildInfo -> [Extension]
allExtensions BuildInfo
bi = BuildInfo -> [Extension]
usedExtensions BuildInfo
bi
                [Extension] -> [Extension] -> [Extension]
forall a. [a] -> [a] -> [a]
++ BuildInfo -> [Extension]
otherExtensions BuildInfo
bi

-- | The 'Extensions' that are used by all modules in this component
--
usedExtensions :: BuildInfo -> [Extension]
usedExtensions :: BuildInfo -> [Extension]
usedExtensions BuildInfo
bi = BuildInfo -> [Extension]
oldExtensions BuildInfo
bi
                 [Extension] -> [Extension] -> [Extension]
forall a. [a] -> [a] -> [a]
++ BuildInfo -> [Extension]
defaultExtensions BuildInfo
bi

-- | Whether any modules in this component use Template Haskell or
-- Quasi Quotes
usesTemplateHaskellOrQQ :: BuildInfo -> Bool
usesTemplateHaskellOrQQ :: BuildInfo -> Bool
usesTemplateHaskellOrQQ BuildInfo
bi = (Extension -> Bool) -> [Extension] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
External instance of the constraint type Foldable []
any Extension -> Bool
p (BuildInfo -> [Extension]
allExtensions BuildInfo
bi)
  where
    p :: Extension -> Bool
p Extension
ex = Extension
ex Extension -> [Extension] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
External instance of the constraint type Eq Extension
External instance of the constraint type Foldable []
`elem`
      [KnownExtension -> Extension
EnableExtension KnownExtension
TemplateHaskell, KnownExtension -> Extension
EnableExtension KnownExtension
QuasiQuotes]

-- |Select options for a particular Haskell compiler.
hcOptions :: CompilerFlavor -> BuildInfo -> [String]
hcOptions :: CompilerFlavor -> BuildInfo -> [String]
hcOptions = (BuildInfo -> PerCompilerFlavor [String])
-> CompilerFlavor -> BuildInfo -> [String]
lookupHcOptions BuildInfo -> PerCompilerFlavor [String]
options

hcProfOptions :: CompilerFlavor -> BuildInfo -> [String]
hcProfOptions :: CompilerFlavor -> BuildInfo -> [String]
hcProfOptions = (BuildInfo -> PerCompilerFlavor [String])
-> CompilerFlavor -> BuildInfo -> [String]
lookupHcOptions BuildInfo -> PerCompilerFlavor [String]
profOptions

hcSharedOptions :: CompilerFlavor -> BuildInfo -> [String]
hcSharedOptions :: CompilerFlavor -> BuildInfo -> [String]
hcSharedOptions = (BuildInfo -> PerCompilerFlavor [String])
-> CompilerFlavor -> BuildInfo -> [String]
lookupHcOptions BuildInfo -> PerCompilerFlavor [String]
sharedOptions

hcStaticOptions :: CompilerFlavor -> BuildInfo -> [String]
hcStaticOptions :: CompilerFlavor -> BuildInfo -> [String]
hcStaticOptions = (BuildInfo -> PerCompilerFlavor [String])
-> CompilerFlavor -> BuildInfo -> [String]
lookupHcOptions BuildInfo -> PerCompilerFlavor [String]
staticOptions

lookupHcOptions :: (BuildInfo -> PerCompilerFlavor [String])
                -> CompilerFlavor -> BuildInfo -> [String]
lookupHcOptions :: (BuildInfo -> PerCompilerFlavor [String])
-> CompilerFlavor -> BuildInfo -> [String]
lookupHcOptions BuildInfo -> PerCompilerFlavor [String]
f CompilerFlavor
hc BuildInfo
bi = case BuildInfo -> PerCompilerFlavor [String]
f BuildInfo
bi of
    PerCompilerFlavor [String]
ghc [String]
ghcjs
        | CompilerFlavor
hc CompilerFlavor -> CompilerFlavor -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq CompilerFlavor
== CompilerFlavor
GHC   -> [String]
ghc
        | CompilerFlavor
hc CompilerFlavor -> CompilerFlavor -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq CompilerFlavor
== CompilerFlavor
GHCJS -> [String]
ghcjs
        | Bool
otherwise   -> [String]
forall a. Monoid a => a
External instance of the constraint type forall a. Monoid [a]
mempty